 |
forums.silverfrost.com Welcome to the Silverfrost forums
|
View previous topic :: View next topic |
Author |
Message |
Mehmet
Joined: 15 May 2012 Posts: 5
|
Posted: Tue May 15, 2012 9:45 pm Post subject: Floating point exception error |
|
|
Dear all,
I am very confused with this error in the following code. I've searched through the forums but I could'n find an answer, even a documentation about that error. As in the title, it says:
model project I.F95(49) : error 637 - Internal compiler error - floating point exception
The code is as followed, and error is on the first DO statement:
Code: |
!*************************************
!*******ChE 352 Term Project 1********
!*****Dynamics of Shell and Tube******
!***********Heat Exchanger************
!****with 3-pass Shell 1-pass Tube****
!*************************************
PROGRAM TERM_PROJECT1
IMPLICIT NONE
DOUBLE PRECISION :: PI,NT,U,MT,DTUBE,A,DENS_T,CPT,CONST1,CONST2,DSHELL,DENS_S,CPS,CONSS1,CONSS2
DOUBLE PRECISION, DIMENSION(10,50000) :: T1,T2,T3,TS,ERR1,ERR2,ERR3,ERRS
DOUBLE PRECISION :: TIME,EPS,DT,DX,MS,A_TUBE,A_SHELL,A_S
INTEGER, DIMENSION(0:10) :: I
INTEGER, DIMENSION(0:50000) :: J
PRINT*, 'Enter DeltaT?'
READ*, DT
! OPEN (20,file='Temp Distribution.xls') ! Open xls file to obtain temperature distribution
PI=4.0*ATAN(1.0)
NT=300
U=840
EPS=0.005
DX=0.4
! Define tube side properties and constants of equation
MT=31.4
DTUBE=0.02
A=PI*(NT/3.0)*(DTUBE**2)/4.0
DENS_T=800
CPT=2000
CONST1=MT/(A_TUBE*DENS_T)
CONST2=NT*U*PI*DTUBE/(3.0*A*DENS_T*CPT)
! Define shel side properties and constants of equation
MS=31.4
DSHELL=0.6
A_S=PI*(DSHELL**2)/4.0-(PI*NT*DTUBE**2)/4.0
DENS_S=1500
CPS=2200
CONSS1=MS/(A_S*DENS_S)
CONSS2=NT*U*PI*DSHELL/(3.0*A_S*DENS_S*CPS)
! Set initial temperatures of tubes and shell side along the system
DO I=0,10,1
T1(I,0)=295.0
T2(I,0)=295.0
T3(I,0)=295.0
TS(I,0)=295.0
END DO
DO J=1,50000,1
TS(10,J)=420.0
END DO
DO J=0,50000,1
! Calculate the temperature of pass 1
DO I=0,8,1
T1(I,J+1)=(-1.0)*CONST1*(DT/(2*DX))*((-1.0)*3.0*(T1(I,J))+4.0*(T1(I+1,J))-T1(I+2,J))+&
(DT*CONST2)*(TS(I,J)-T1(I,J))+T1(I,J)
END DO
DO I=9,10,1
T1(I,J+1)=(-1.0)*CONST1*(DT/(2*DX))*(3.0*(T1(I,J))-4.0*(T1(I-1,J))+T1(I-2,J))+&
(DT*CONST2)*(TS(I,J)-T1(I,J))+T1(I,J)
END DO
! Application of boundary condition 3
T2(10,J)=T1(10,J)
! Calculate the temperature of pass 2
DO I=10,2,-1
T2(I,J+1)=CONST1*(DT/(2*DX))*(3.0*(T2(I,J))-4.0*(T2(I-1,J))+T2(I-2,J))+&
(DT*CONST2)*(TS(I,J)-T2(I,J))+T2(I,J)
END DO
DO I=2,0,-1
T1(I,J+1)=CONST1*(DT/(2*DX))*((-1.0)*3.0*(T1(I,J))+4.0*(T1(I+1,J))-T1(I+2,J))+&
(DT*CONST2)*(TS(I,J)-T2(I,J))+T2(I,J)
END DO
! Application of boundary condition 2
T3(0,J)=T2(0,J)
! Calculate the temperature of pass 3
DO I=0,8,1
T3(I,J+1)=(-1.0)*CONST1*(DT/(2*DX))*((-1.0)*3.0*(T3(I,J))+4.0*(T3(I+1,J))-T3(I+2,J))+&
(DT*CONST2)*(TS(I,J)-T3(I,J))+T3(I,J)
END DO
DO I=9,10,1
T3(I,J+1)=(-1.0)*CONST1*(DT/(2*DX))*(3.0*(T3(I,J))-4.0*(T3(I-1,J))+T3(I-2,J))+&
(DT*CONST2)*(TS(I,J)-T3(I,J))+T3(I,J)
END DO
|
|
|
Back to top |
|
 |
Mehmet
Joined: 15 May 2012 Posts: 5
|
Posted: Tue May 15, 2012 9:47 pm Post subject: |
|
|
cont'd
Code: | ! Calculate the temperature of shell side
DO I=10,0,-1
TS(I,J+1)=CONSS1*(DT/(2*DX))*(3.0*(TS(I,J))-4.0*(TS(I-1,J))+TS(I-2,J))+&
(DT*CONSS2)*(3*(TS(I,J))-T1(I,J)-T2(I,J)-T3(I,J))+TS(I,J)
END DO
! Define errors here and let the loop to stop if satisfied
DO I=0,10,1
ERR1(I,J)=ABS(T1(I,J+1)-T1(I,J))
ERR2(I,J)=ABS(T2(I,J+1)-T2(I,J))
ERR3(I,J)=ABS(T3(I,J+1)-T3(I,J))
ERRS(I,J)=ABS(TS(I,J+1)-TS(I,J))
IF(ERR1(I,J)>=EPS)THEN
GO TO 10
ELSEIF(ERR2(I,J)>=EPS)THEN
GO TO 10
ELSEIF(ERR3(I,J)>=EPS)THEN
GO TO 10
ELSEIF(ERRS(I,J)>=EPS)THEN
GO TO 10
ELSEIF GO TO 20
ENDIF
END DO
10 END DO !End the grand DO (deltime)
20 TIME=J*DT
PRINT*, 'Time for steady state=',TIME
END PROGRAM TERM_PROJECT1 |
|
|
Back to top |
|
 |
davidb
Joined: 17 Jul 2009 Posts: 560 Location: UK
|
Posted: Tue May 15, 2012 10:42 pm Post subject: |
|
|
You have declared I and J to be arrays. They must be integer scalars if you want to use them as DO loop indices. The compiler error is not helpful, but if you fix this you will find other errors you can fix.
The notation:
INTEGER, DIMENSION(0:10) :: I
INTEGER, DIMENSION(0:50000) :: J
does NOT mean I goes from 0:10 and J goes from 0:50000
Change the lines to:
INTEGER :: I, J
There are numerous other errors too. Your array T1 has indices (1:10, 1:50000) but your first loop accesses elements (0,0). _________________ Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl |
|
Back to top |
|
 |
Mehmet
Joined: 15 May 2012 Posts: 5
|
Posted: Tue May 15, 2012 10:49 pm Post subject: |
|
|
Thanks davidb, I changed as you proposed but I just tried to define an array for i=0 to 10 and j=0 to 50000 but my definition might be wrong so how i can fix that?
Edit:
Thanks to david, i just corrected the definition of dimensions to
Code: | DOUBLE PRECISION, DIMENSION(0:10,0:50000) :: T1,T2,T3,TS,ERR1,ERR2,ERR3,ERRS |
and
Code: | INTEGER :: I
INTEGER :: J |
but i still have some errors to be solved |
|
Back to top |
|
 |
Mehmet
Joined: 15 May 2012 Posts: 5
|
Posted: Wed May 16, 2012 10:36 am Post subject: |
|
|
Problems are solved. I will be posting the last final code at late midnight with no errors and physically meaningful one (for those who are interested in). Thanks all for your support, especially David
Edit: The code is now working with zero errors.
Code: |
PROGRAM SHELLTUBE
DOUBLE PRECISION :: PI,NT,U,MT,DTUBE,DENS_T,CPT,CONST1,CONST2,DSHELL,DENS_S,CPS,CONSS1,CONSS2
DOUBLE PRECISION :: DX, ERRO, EPS, MS, A_TUBE,A_S,DISTANCE
DOUBLE PRECISION :: T1(11,0:100000),T2(11,0:100000),T3(11,0:100000),TS(11,0:100000)
PRINT*, 'INPUT TIME STEP'
READ*, DT
PI=4.0*ATAN(1.0)
NT=300.0
U=840.0
EPS=0.000001
DX=0.4
! Define tube side properties and constants of equation
MT=31.4
DTUBE=0.02
A_TUBE=PI*(NT/3.0)*(DTUBE**2)/4.0
DENS_T=800.0
CPT=2000.0
CONST1=MT/(A_TUBE*DENS_T)
CONST2=NT*U*PI*DTUBE/(3.0*A_TUBE*DENS_T*CPT)
! Define shel side properties and constants of equation
MS=31.4
DSHELL=0.6
A_S=PI*(DSHELL**2)/4.0-(PI*NT*DTUBE**2)/4.0
DENS_S=1500.0
CPS=2200.0
CONSS1=MS/(A_S*DENS_S)
CONSS2=NT*U*PI*DSHELL/(3.0*A_S*DENS_S*CPS)
OPEN (8,FILE='STEADY STATE TEMPERATURE DISTRIBUTION.TXT',STATUS='REPLACE')
OPEN (9,FILE='TIME EVOLUTION OF TEMPERATURES.TXT',STATUS='REPLACE')
DO I=1,11
T1(I,0)=295
T2(I,0)=295
T3(I,0)=295
TS(I,0)=295
END DO
TIMEZERO=0
WRITE(9,50) 'TIME', 'T1', 'T2', 'T3', 'TSHELL'
WRITE(9,40) TIMEZERO, T1(11,0), T2(1,0), T3(11,0), TS(1,0)
DO J=0,100000
T1(1,J)=295.0
END DO
DO J=1,100000
TS(11,J)=420.0
END DO
DO J=0,100000 !Grand DO LOOP for time evaluation
! First pass equations
DO I=2,11
T1(I,J+1)=(-CONST1*(DT/DX)*(T1(I,J)-T1(I-1,J)))+(CONST2*DT*(TS(I,J)-T1(I,J)))+T1(I,J)
END DO
! Apply boundary condition
T2(11,J+1)=T1(11,J+1)
! Second pass equations
DO I=10,1,-1
T2(I,J+1)=(CONST1*(DT/DX)*(T2(I+1,J)-T2(I,J)))+(CONST2*DT*(TS(I,J)-T2(I,J)))+T2(I,J)
END DO
! Apply boundary condition
T3(1,J+1)=T2(1,J+1)
! Third pass equations
DO I=2,11
T3(I,J+1)=(-CONST1*(DT/DX)*(T3(I,J)-T3(I-1,J)))+(CONST2*DT*(TS(I,J)-T3(I,J)))+T3(I,J)
END DO
! Shell pass equations
DO I=10,1,-1
TS(I,J+1)=(CONSS1*(DT/DX)*(TS(I+1,J)-TS(I,J)))-(CONSS2*DT*((3*TS(I,J))-T1(I,J)-T2(I,J)-T3(I,J)))+TS(I,J)
END DO
TIMEJ=DT*(J+1)
WRITE(9,40) TIMEJ, T1(11,J+1), T2(1,J+1), T3(11,J+1), TS(1,J+1)
K=J
DO I=11,1,-1
ERRO=ABS(TS(I,J+1)-TS(I,J))
IF(ERRO.GT.EPS) GOTO 100
END DO
GO TO 150
100 END DO !End of Grand DO LOOP
150 WRITE(8,10) 'T1','T2', 'T3', 'TSHELL'
DO I=1,11
DISTANCE=(I-1)*DX
WRITE(8,20) DISTANCE, T1(I,K), T2(I,K), T3(I,K), TS(I,K)
END DO
10 FORMAT(4(A8))
20 FORMAT(F4.1,4(F8.3))
TIME=DT*K
WRITE(8,30) 'TIME NEEDED TO REACH STEADY STATE:', TIME
30 FORMAT(A35,F8.3)
40 FORMAT(5(F8.3))
50 FORMAT(5(A8))
END PROGRAM SHELLTUBE |
|
|
Back to top |
|
 |
JohnCampbell
Joined: 16 Feb 2006 Posts: 2615 Location: Sydney
|
Posted: Thu May 17, 2012 2:01 am Post subject: |
|
|
A couple of comments on your program, that are intended to help you for next time.
You do not appear to need past itteration solutions. As this is a forward single step solution, you only need the last solution. You could have the dimension statement:
DOUBLE PRECISION, DIMENSION(0:10) :: T1,T2,T3,TS, T1L,T2L,T3L,TSL
where T1L is the solution estimate at the last step.
Your convergence test does not require storage of the error, only calculation and accumulation of a failure test, such as:
Code: | ! Define errors here and let the loop stop if all satisfied
! Why do you store the errors ?
!
DO I=0,10
IF (ABS (T1(I)-T1L(I)) >= EPS) EXIT
IF (ABS (T2(I)-T2L(I)) >= EPS) EXIT
IF (ABS (T3(I)-T3L(I)) >= EPS) EXIT
IF (ABS (TS(I)-TSL(I)) >= EPS) EXIT
END DO
if (I > 10) EXIT ! Exit loop if convergence was reached for all tests
!
! Store this itteration as last estimate
DO I=0,10
T1L(I) = T1(I)
T2L(I) = T2(I)
T3L(I) = T3(I)
TSL(I) = TS(I)
END DO
!
END DO ! End the grand DO (deltime)
|
Your code makes extensive use of unnecessary ( ).
I'd suggest that you could remove these and change the layout of the equations to make them easier to check.
Also, from your coding, as T1 is only a fn of T1N (the previous estimate), the order of the DO loop is not important. Below is an example of how I changed your equation to improve clarity.
Code: | ! Set initial temperatures of tubes and shell side along the system
!
DO I = 0,10
T1L(I) = 295.0
T2L(I) = 295.0
T3L(I) = 295.0
TSL(I) = 295.0
END DO
!
TSL(10) = 420.0
TS(10) = 420.0
!
DO J = 0,50000
!
! Calculate the temperature of pass 1
DO I = 0,8
! Original
! T1(I,J+1)=(-1.0)*CONST1*(DT/(2*DX))*((-1.0)*3.0*(T1(I,J))+4.0*(T1(I+1,J))-T1(I+2,J))+&
! (DT*CONST2)*(TS(I,J)-T1(I,J))+T1(I,J)
!
! becomes by removing ",J"
! T1(I) = (-1.0)*CONST1*(DT/(2*DX))*((-1.0)*3.0*(T1L(I))+4.0*(T1L(I+1))-T1L(I+2)) &
! + (DT*CONST2)*(TSL(I)-T1L(I))+T1L(I)
!
! becomes by removing unnesecary "()"
! T1(I) = -1.0 * CONST1 * DT/(2*DX) * ( -3.0 * T1L(I) + 4.0 * T1L(I+1) - T1L(I+2) ) &
! + DT*CONST2 * (TSL(I)-T1L(I)) + T1L(I)
!
! becomes by rearranging
T1(I) = T1L(I) &
+ CONST1 * DT / (2*DX) * ( 3.0 * T1L(I) - 4.0 * T1L(I+1) + T1L(I+2) ) &
+ CONST2 * DT * (TSL(I)-T1L(I))
END DO
|
I hope this helps.
John |
|
Back to top |
|
 |
Mehmet
Joined: 15 May 2012 Posts: 5
|
Posted: Mon May 21, 2012 8:28 pm Post subject: |
|
|
Thanks John for that great support. I will be using your suggestion for newly assigned term project I will share the new code with you |
|
Back to top |
|
 |
|
|
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
|