replica nfl jerseysreplica nfl jerseyssoccer jerseyreplica nfl jerseys forums.silverfrost.com :: View topic - help to fix this code
forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

help to fix this code
Goto page 1, 2  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
pashupati



Joined: 16 Aug 2012
Posts: 8

PostPosted: Tue Aug 21, 2012 2:45 pm    Post subject: help to fix this code Reply with quote

I can only get first data point after that it shows error.

Please help


PROGRAM TDGL


IMPLICIT NONE

!c **************** Initialization of variables *********************
INTEGER, PARAMETER :: IMAX=100,JMAX=100
INTEGER Nx ! number of cells in x
INTEGER Ny ! number of cells in x

REAL Ax ! mesh spacing in x
REAL Ay ! mesh spacing in y

REAL dt ! time step
REAL k ! kappa ( = lambda / xi )
REAL Eta ! eta
REAL T ! temperature ( scaled with Tc )
REAL He ! applied external magnetic field
REAL Ho ! initial applied external magnetic field
REAL Hi ! magnetic field in the interior hole
REAL dHe ! applied external magnetic field increment
REAL Ruido ! Standard deviation of random noise
REAL Eo ! Parameter for random noise
INTEGER TotSteps! number of time steps
INTEGER Step ! step counter
INTEGER OutSteps! number of steps between outputs
INTEGER OutStp2 ! number of steps between run-time information
INTEGER HeSteps ! number of steps between applied field increments

INTEGER idum ! auxiliary
INTEGER i,j ! auxiliary
CHARACTER*36 Label ! auxiliary
INTEGER iHe ! auxiliary for naming restart files

COMPLEX F(IMAX+1,JMAX+1) ! order parameter
COMPLEX Ux(IMAX,JMAX+1) ! link variable in x
COMPLEX Uy(IMAX+1,JMAX) ! link variable in y
COMPLEX bloop(IMAX,JMAX) ! exp(-i a_x a_y B_z)
!c The following three arrays are auxiliary to avoid copies
COMPLEX G(IMAX+1,JMAX+1) ! order parameter
COMPLEX Vx(IMAX,JMAX+1) ! link variable in x
COMPLEX Vy(IMAX+1,JMAX) ! link variable in y
!c
LOGICAL Bulk(IMAX,JMAX) ! bulk cell indicator
INTEGER iswnod (IMAX+1,JMAX+1) ! vertex indicator
INTEGER iswlx (IMAX,JMAX+1) ! x-link indicator
INTEGER iswly (IMAX+1,JMAX) ! y-link indicator

REAL rAx2 ! auxiliar
REAL rAy2 ! auxiliar
REAL rAxAy ! auxiliar
REAL k2 ! auxiliar
REAL rEta ! auxiliar
REAL T1 ! auxiliar
REAL rT1 ! auxiliar
REAL k2rT12 ! auxiliar
REAL AxAy ! auxiliar
REAL AxAyHe ! auxiliar
REAL AxAyHi ! auxiliar
REAL AxAydHi ! auxiliar
COMPLEX EiAxAyHe! auxiliar, approx. exp(-i*ax*ay*He)
COMPLEX EiAxAyHi! auxiliar, approx. exp(-i*ax*ay*Hi)
REAL rotA ! auxiliar
COMPLEX EiMAxAydHi ! var. aux., approx. exp(-i*M*ax*ay*dHi)
COMPLEX EiMAxAyHi ! var. aux., approx. exp(-i*M*ax*ay*dHi)
REAL FFF ! auxiliar


REAL FreeEnergy ! !
REAL Bz ! mean field
REAL Magnetization ! !

COMPLEX GaussDev! complex numbers generator (Gaussian distrib.)

INTEGER d ! auxiliar
REAL Flux ! total fluxoid
REAL Flux1 ! internal fluxoid
REAL PATHx1 !
REAL PATHx2 !
REAL PATHy1 !
REAL PATHy2 ! circulations
COMPLEX PTHx1 !
COMPLEX PTHx2 !
COMPLEX PTHy1 !
COMPLEX PTHy2 ! circulations
REAL MinF !
REAL MinF1 !

INTEGER N ! Hole N boundary
INTEGER S ! Hole S boundary
INTEGER E ! Hole E boundary
INTEGER W ! Hole W boundary
INTEGER M ! auxiliar
REAL rM ! auxiliar

integer iaux

!c ******************************************************************

iHe = 9000000

!c ********************** Input data **************************

OPEN (8,FILE='tdgl.in
Back to top
View user's profile Send private message
jjgermis



Joined: 21 Jun 2006
Posts: 404
Location: N�rnberg, Germany

PostPosted: Wed Aug 22, 2012 9:52 am    Post subject: Reply with quote

Thanks for posting some code - this is alway helps to get down to the problem. However, since the number of code lines posted in the forum is limited, you should try to reduce the code so that one can at least reproduce it.

I always like cut, paste and compile examples Smile

Give it try - and you will get the help you are looking for.
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2402
Location: Yateley, Hants, UK

PostPosted: Wed Aug 22, 2012 11:36 am    Post subject: Reply with quote

If the code is long, you could always upload it to one of the (legal) file sharing websites and provide a link to it. I often use DropBox (www.dropbox.com) to share files that are too long even for e mail attachments or are of types like .EXE that many e mail systems won't accept.

Eddie
Back to top
View user's profile Send private message
jjgermis



Joined: 21 Jun 2006
Posts: 404
Location: N�rnberg, Germany

PostPosted: Wed Aug 22, 2012 11:45 am    Post subject: Reply with quote

Hi Eddie,

thanks for the DropBox tipp. It seems like one need to install some software before one can use it. We for example are not allowed to install software that is not approved - difficult situation. But on the otherhand our IT always try to avoid the worst case scenario.
Back to top
View user's profile Send private message
pashupati



Joined: 16 Aug 2012
Posts: 8

PostPosted: Thu Aug 23, 2012 3:04 pm    Post subject: Help, my code is not working Reply with quote

Anyone willing to help me to take a look at the code?
Please help

my email :dklpashupati at yahoo.com
Back to top
View user's profile Send private message
jjgermis



Joined: 21 Jun 2006
Posts: 404
Location: N�rnberg, Germany

PostPosted: Thu Aug 23, 2012 3:16 pm    Post subject: Reply with quote

We are willing to help if you post a working example of your code. The part of the program given above is only variable declaration. It is not fair to expect from anybody to figure out what is happening with such little information.

The only "real" code is the line where a file is opened. So for a start you must at least specify:
1.) are you able to read the file?
2.) occur the error before/after any calls to subroutines or functions
3.) what sort of files are you reading.

You need to reduce you problem. Once you have done that we can help you. Give it a try Wink
Back to top
View user's profile Send private message
pashupati



Joined: 16 Aug 2012
Posts: 8

PostPosted: Thu Aug 23, 2012 3:35 pm    Post subject: Help, my code is not working Reply with quote

Sorry about the code, I didn't realize that only a part of the code is posted Sad .
I am reading .ini files with the input parameters. After I start "run", it reads the parameter and generate the first data point. After that it gives "floating point overflow". floating point co-processor fault at address 0040a7e5 in the line 917". I am running this in window 7 32 bit laptop.

I used a gfortan in mac computer the same code works fine. I am not planning to buy Mac. Crying or Very sad
Back to top
View user's profile Send private message
jjgermis



Joined: 21 Jun 2006
Posts: 404
Location: N�rnberg, Germany

PostPosted: Thu Aug 23, 2012 3:49 pm    Post subject: Reply with quote

You have to post something like this:
Code:
open(8,file=tdgl.ini')

C
C your code here
C

close(8)


and if possible what the file looks like. Without this information you will sit on your problem - not what you want Wink

Code:
34455
jhgfd
jhgfd
12345 6788
Back to top
View user's profile Send private message
pashupati



Joined: 16 Aug 2012
Posts: 8

PostPosted: Thu Aug 23, 2012 6:40 pm    Post subject: Reply with quote

Code:

   OPEN (8,FILE='tdgl.ini',FORM='FORMATTED')
     
      READ (8,*) Label,Nx
      WRITE (6,*) Label,'Nx:       ',Nx
      READ (8,*) Label,Ny
      WRITE (6,*) Label,'Ny:       ',Ny
      READ (8,*) Label,Ax
      WRITE (6,*) Label,'Ax:       ',Ax
      READ (8,*) Label,Ay
      WRITE (6,*) Label,'Ay:       ',Ay
      READ (8,*) Label,dt
      WRITE (6,*) Label,'dt:       ',dt
      READ (8,*) Label,k
      WRITE (6,*) Label,'k:        ',k
      READ (8,*) Label,Eta
      WRITE (6,*) Label,'Eta:      ',Eta     
      READ (8,*) Label,T
      WRITE (6,*) Label,'T:        ',T
      READ (8,*) Label,He
      WRITE (6,*) Label,'He:       ',He
      READ (8,*) Label,dHe
      WRITE (6,*) Label,'dHe:      ',dHe
      READ (8,*) Label,Eo
      WRITE (6,*) Label,'Eo:       ',Eo
      READ (8,*) Label,TotSteps
      WRITE (6,*) Label,'TotSteps: ',TotSteps
      READ (8,*) Label,OutSteps
      WRITE (6,*) Label,'OutSteps: ',OutSteps
      READ (8,*) Label,OutStp2
      WRITE (6,*) Label,'OutStp2:  ',OutStp2
      READ (8,*) Label,HeSteps
      WRITE (6,*) Label,'HeSteps:  ',HeSteps
      READ (8,*) Label,d
      WRITE (6,*) Label,'d:        ',d
      READ (8,*) Label,N
      WRITE (6,*) Label,'N:        ',N
      READ (8,*) Label,S
      WRITE (6,*) Label,'S:        ',S
      READ (8,*) Label,E
      WRITE (6,*) Label,'E:        ',E
      READ (8,*) Label,W
      WRITE (6,*) Label,'W:        ',W
   
      CLOSE (8)
     
Back to top
View user's profile Send private message
pashupati



Joined: 16 Aug 2012
Posts: 8

PostPosted: Thu Aug 23, 2012 6:41 pm    Post subject: Reply with quote

Code:

M=(N-S)*(E-W)+2*(N-S)+2*(E-W)
      rM=1.0 / M
     
      Ho=He
      Hi=0.0
     
      k2=k*k
      rEta=1/Eta
     
      T1=1-T
      rT1=1/T1
      k2rT12=(k*k)/(T1*T1)
     
      rAx2=1/(Ax*Ax)
      rAy2=1/(Ay*Ay)
      rAxAy=1/(Ax*Ay)     
      AxAy=Ax*Ay
      AxAyHe=Ax*Ay*He                                   
      EiAxAyHe=COS(AxAyHe)-(0,1)*SIN(AxAyHe)
     
      Ruido=dt*SQRT(0.5235987755983*Eo*dt*T)
      idum=0
OPEN (13,FILE='s.dat',STATUS='NEW',FORM='FORMATTED')
      WRITE (13,*)  '# Step',' He',' Hi',  &
                   ' Bz',' Magnetization',  &
                   ' FreeEnergy',' Flux',   &
                   ' Flux1'                 &
                  ,' MinF',' MinF1'
      CLOSE (13)
             
      OPEN (15,FILE='c.dat',STATUS='NEW',FORM='FORMATTED')     
      WRITE (15,*)  '     He','     Bz','     Flux','     Hi'
      CLOSE (15)
OPEN (11,FILE='tdgl.ree',STATUS='OLD',FORM='FORMATTED',ERR=10)
      WRITE (6,*) 'Reading the restart file: tdgl.ree... '
      READ (11,*) Hi
      READ (11,*) ((F(i,j),i=1,Nx+1),j=1,Ny+1)
      READ (11,*) ((Ux(i,j),i=1,Nx),j=1,Ny+1)
      READ (11,*) ((Uy(i,j),i=1,Nx+1),j=1,Ny)
      CLOSE (11, STATUS='KEEP')     
      GO TO   20
     
 10   WRITE (6,*) 'Initializing to a perfect Meissner state... '
      DO i=1,Nx+1
      DO j=1,Ny+1
          F(i,j)=1     
      END DO
      END DO

      DO i=1,Nx
      DO j=1,Ny+1
          Ux(i,j)=1     
      END DO
      END DO

      DO i=1,Nx+1
      DO j=1,Ny
          Uy(i,j)=1     
      END DO
      END DO
     
 20   DO i=1,Nx
      DO j=1,Ny
          Bulk(i,j)=.TRUE.     
      END DO
      END DO

      DO i=1,Nx+1
      DO j=1,Ny+1
          iswnod(i,j)=0     
      END DO
      END DO

      DO i=1,Nx
      DO j=1,Ny+1
          iswlx(i,j)=0     
      END DO
      END DO

      DO i=1,Nx+1
      DO j=1,Ny
          iswly(i,j)=0     
      END DO
      END DO

      DO i=W,E-1
      DO j=S,N-1
          Bulk(i,j)=.FALSE.     
      END DO
      END DO

      DO i=1,Nx
      DO j=1,Ny
         if (Bulk(i,j)) then
            iswnod(i,j)=iswnod(i,j)+1     
            iswnod(i+1,j)=iswnod(i+1,j)+1     
            iswnod(i,j+1)=iswnod(i,j+1)+1     
            iswnod(i+1,j+1)=iswnod(i+1,j+1)+1
            iswlx(i,j)=iswlx(i,j)+1
            iswlx(i,j+1)=iswlx(i,j+1)+1
            iswly(i,j)=iswly(i,j)+1
            iswly(i+1,j)=iswly(i+1,j)+1
         end if     
      END DO
      END DO


      DO i=W+1,E-1
      DO j=S+1,N-1
          F(i,j)=0     
      END DO
      END DO

      AxAyHi=AxAy*Hi
      EiMAxAyHi=COS(M*AxAyHi)-(0,1)*SIN(M*AxAyHi)
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2402
Location: Yateley, Hants, UK

PostPosted: Thu Aug 23, 2012 6:42 pm    Post subject: Reply with quote

Jaques,

Drop Box is only one of several legal file sharing sites. You only need to instal software to post to it, as reading from it is a simple internet download. You get 2 Gb free, but if you buy a licence, you can have much more space, and then your IT section could add it to the list of accepted applications (or whatever system you chose would probably work the same). In my experience, IT organisations distrust free software, but they are happy to pay for stuff you can get free - and then they won't pay for the updates!

I found it useful for sharing EXE files.

Eddie
Back to top
View user's profile Send private message
pashupati



Joined: 16 Aug 2012
Posts: 8

PostPosted: Thu Aug 23, 2012 6:48 pm    Post subject: Reply with quote

Code is very long
May I email to someone willing to help me?

email: dklpashupati at yahoo.com

Thank you !
Back to top
View user's profile Send private message
jjgermis



Joined: 21 Jun 2006
Posts: 404
Location: N�rnberg, Germany

PostPosted: Fri Aug 24, 2012 7:51 am    Post subject: Reply with quote

Seeing some code is a help - we are getting there Smile

However, where does the error occur. Can you isolate it:
1.) are you able to read the file?
2.) occur the error before/after any calls to subroutines or functions
3.) what sort of files are you reading.
Back to top
View user's profile Send private message
pashupati



Joined: 16 Aug 2012
Posts: 8

PostPosted: Fri Aug 24, 2012 7:25 pm    Post subject: Reply with quote

I can read the input file and it gives the first data point (valid point) and it terminate due floating point error
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2923
Location: South Pole, Antarctica

PostPosted: Sat Aug 25, 2012 6:34 pm    Post subject: Reply with quote

In the DOS prompt window (better use for that the Total Commander - to me it's #1 program on all computers and the best and the most useful app of all times) compile it like this

FTN95 yourfile.for /checkmate /link

Yourfile.for is the name of your file of course. If this is free form source add
/free to this line

Then run the debugger
>SDBG yourfile.exe

You will find all your errors in seconds. If not ask here again what's specifically wrong. Post here how many errors Apple compiler missed
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General All times are GMT + 1 Hour
Goto page 1, 2  Next
Page 1 of 2

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group