Skip to content

Commit

Permalink
Bug fixs
Browse files Browse the repository at this point in the history
Variables initialization implies 'save' attribute in Fortran
subroutines ('static' in C). As the result, specifing a value to
variable at declaration block would not take effect after first call
to the function.
I'd like to appreciate Mr. Hong from HIT
(Harbin Institute of Technology) for discovering and suggesting
a solution regarding this situation!

Fix RSTAT in landslide.f90 in case of multi-calls
  • Loading branch information
AndybnACT committed Jan 31, 2022
1 parent a8be928 commit bbeb89b
Show file tree
Hide file tree
Showing 4 changed files with 18 additions and 16 deletions.
4 changes: 2 additions & 2 deletions deform.f90
Original file line number Diff line number Diff line change
Expand Up @@ -761,11 +761,11 @@ SUBROUTINE READ_XYZ_DEFORM (LO,FAULT_INFO)
INTEGER LENGTH, RC, POS !, FLAG
INTEGER COUNT
REAL TEMP,TEMP1,TEMP2,TEMP3
INTEGER :: RSTAT = 0
INTEGER :: RSTAT
! CHARACTER(LEN=20) FNAME
COMMON /CONS/ ELMAX,GRAV,PI,R_EARTH,GX,EPS,ZERO,ONE,NUM_GRID, &
NUM_FLT,V_LIMIT,RAD_DEG,RAD_MIN

RSTAT = 0
Z = 0.0
COUNT = -1

Expand Down
22 changes: 12 additions & 10 deletions initialization.f90
Original file line number Diff line number Diff line change
Expand Up @@ -610,11 +610,11 @@ SUBROUTINE READ_MULTIFAULT_DATA (LO,FLT)
INTEGER NUM_FLT,COUNT
CHARACTER(LEN=200) :: line,line1,line2,line3
CHARACTER(LEN=200) :: dump,tmp,tmpname,fname
INTEGER :: RSTAT=0
INTEGER :: RSTAT
COMMON /CONS/ ELMAX,GRAV,PI,R_EARTH,GX,EPS,ZERO,ONE,NUM_GRID, &
NUM_FLT,V_LIMIT,RAD_DEG,RAD_MIN
DATA OSIXTY/0.016666666667/, BIG/-999./

RSTAT = 0
!* WRITE(*,*) ' MULTI-FAULTING CONFIGURATION IS IMPLEMENTED...'
OPEN(UNIT=23,FILE=FLT(1)%DEFORM_NAME,STATUS='OLD',IOSTAT=ISTAT)
IF (ISTAT /=0) THEN
Expand Down Expand Up @@ -1890,10 +1890,10 @@ SUBROUTINE READ_XYZ_BATHY (LO)
INTEGER STAT, IS, JS, I, J
! INTEGER LENGTH, RC, POS !, FLAG
INTEGER COUNT
INTEGER :: RSTAT = 0
INTEGER :: RSTAT
COMMON /CONS/ ELMAX,GRAV,PI,R_EARTH,GX,EPS,ZERO,ONE,NUM_GRID, &
NUM_FLT,V_LIMIT,RAD_DEG,RAD_MIN

RSTAT = 0
WRITE (*,*) ' READING XYZ BATHMETRY DATA FOR LAYER ID',LO%ID
OPEN (UNIT=23,FILE=LO%DEPTH_NAME,STATUS='OLD', &
IOSTAT=ISTAT,FORM='FORMATTED')
Expand Down Expand Up @@ -2088,8 +2088,10 @@ SUBROUTINE READ_ETOPO_BATHY (LO)
INTEGER COUNT
COMMON /CONS/ ELMAX,GRAV,PI,R_EARTH,GX,EPS,ZERO,ONE,NUM_GRID, &
NUM_FLT,V_LIMIT,RAD_DEG,RAD_MIN
INTEGER :: ISTAT = 0
INTEGER :: RSTAT = 0
INTEGER :: ISTAT
INTEGER :: RSTAT
ISTAT = 0
RSTAT = 0
WRITE (*,*) ' READING ETOPO BATHMETRY DATA FOR LAYER ID',LO%ID
OPEN (UNIT=23,FILE=LO%DEPTH_NAME,STATUS='OLD', &
IOSTAT=ISTAT,FORM='FORMATTED')
Expand Down Expand Up @@ -2548,9 +2550,9 @@ SUBROUTINE READ_FRIC_COEF1 (LO)
INTEGER STAT, IS, JS, I, J
! INTEGER LENGTH, RC, POS !, FLAG
INTEGER COUNT
INTEGER :: RSTAT = 0
INTEGER :: RSTAT
CHARACTER(LEN=40) FNAME,FNAME1

RSTAT = 0
!----------------------------------------
! READING PARAMETERS FOR FRICTION COEF.
!----------------------------------------
Expand Down Expand Up @@ -2700,11 +2702,11 @@ SUBROUTINE READ_FRIC_COEF (LO)
REAL,ALLOCATABLE :: X(:),Y(:),XTMP(:),YTMP(:)
INTEGER STAT, IS, JS, I, J, NXY
INTEGER COUNT
INTEGER :: RSTAT = 0
INTEGER :: RSTAT
CHARACTER(LEN=40) FNAME,FNAME1
COMMON /CONS/ ELMAX,GRAV,PI,R_EARTH,GX,EPS,ZERO,ONE,NUM_GRID, &
NUM_FLT,V_LIMIT,RAD_DEG,RAD_MIN

RSTAT = 0
!----------------------------------------
! READING PARAMETERS FOR FRICTION COEF.
!----------------------------------------
Expand Down
4 changes: 2 additions & 2 deletions landslide.f90
Original file line number Diff line number Diff line change
Expand Up @@ -82,10 +82,10 @@ SUBROUTINE READ_LANDSLIDE (LO,LANDSLIDE_INFO)
TYPE (LAYER) :: LO
REAL, ALLOCATABLE:: SNAPSHOT(:,:,:),X(:),Y(:),T(:)
INTEGER COUNT,NX,NY,NT
INTEGER :: RSTAT = 0
INTEGER :: RSTAT
REAL LATIN,LONIN,XS,YS,XE,YE,XT,YT,X0,Y0
CHARACTER(LEN=80) FNAME

RSTAT = 0
DO K = 1,LO%NX-1
IF (LANDSLIDE_INFO%X_START.GT.LO%X(K) .AND. &
LANDSLIDE_INFO%X_START.LE.LO%X(K+1)) THEN
Expand Down
4 changes: 2 additions & 2 deletions wavemaker.f90
Original file line number Diff line number Diff line change
Expand Up @@ -362,8 +362,8 @@ SUBROUTINE READ_WAVE (WAVE_INFO)
REAL TEMP1,TEMP2
INTEGER COUNT
CHARACTER(LEN=80) FNAME
INTEGER :: RSTAT = 0

INTEGER :: RSTAT
RSTAT = 0
TEMP1 = 0.0
TEMP2 = 0.0
IF (WAVE_INFO%MK_TYPE==2) THEN
Expand Down

0 comments on commit bbeb89b

Please sign in to comment.