Skip to content

Commit

Permalink
deallocate between runs; allow for timesearies of data
Browse files Browse the repository at this point in the history
  • Loading branch information
IvanaEscobar committed Nov 8, 2023
1 parent 1211ca5 commit a164a8f
Show file tree
Hide file tree
Showing 11 changed files with 165 additions and 93 deletions.
9 changes: 5 additions & 4 deletions inc/IHOP.h
Original file line number Diff line number Diff line change
Expand Up @@ -52,20 +52,23 @@

!-- COMMON /IHOP_PARAMS_I/ IHOP Integer-type parameters:
! IHOP_nalpha :: No. of rays to propagate
! IHOP_nts :: No. of sample times
! IHOP_nsd :: No. of source depths (m)
! IHOP_nrd :: No. of receiver depths (m)
! IHOP_nrr :: No. of receiver ranges (km)
! IHOP_iter :: GCM iteration to run ihop

INTEGER IHOP_nalpha
INTEGER IHOP_nts
INTEGER IHOP_nsd
INTEGER IHOP_nrd
INTEGER IHOP_nrr
INTEGER ihop_iter
INTEGER ihop_iter(nts)
INTEGER IHOP_npts_range
INTEGER IHOP_npts_idw

COMMON /IHOP_PARAMS_I/ &
& IHOP_nsd, &
& IHOP_nts, IHOP_nsd, &
& IHOP_nrd, IHOP_nrr, &
& IHOP_npts_range, IHOP_npts_idw, &
& IHOP_nalpha, ihop_iter
Expand All @@ -83,8 +86,6 @@
! IHOP_rr :: receiver ranges (km)
! IHOP_alpha :: bearing launch angles (degrees)
! IHOP_step :: step length (m)
! IHOP_zbox :: acoustic domain depth (m)
! IHOP_rbox :: acoustic domain range (km)

_RL IHOP_freq
_RL IHOP_depth
Expand Down
2 changes: 2 additions & 0 deletions inc/IHOP_OPTIONS.h
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,8 @@
#define IHOP_2D_STATE
#define IHOP_TENDENCY

#define IHOP_MULTIPLE_TIMES

#undef IHOP_MULTIPLE_SOURCES

#undef IHOP_MULTIPLE_RECEIVER_DEPTHS
Expand Down
12 changes: 12 additions & 0 deletions inc/IHOP_SIZE.h
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,18 @@
! \ev
!EOP

! nts :: No. of time series points
! ================================
! Number of time series:
! ================================
INTEGER nts
#ifdef IHOP_MULTIPLE_TIMES
PARAMETER ( nts=10 )
#else
PARAMETER ( nts=1 )
#endif


! nsd :: No. of sound sources at range of 0 m
! nrd :: No. of sound receivers at a single range
! nrr :: No. of sound receivers at a single depth
Expand Down
2 changes: 1 addition & 1 deletion mitgcm_input/data.ihop
Original file line number Diff line number Diff line change
Expand Up @@ -26,5 +26,5 @@

&IHOP_PARM03
IHOP_interpfile = 'bc-gyre_ihop-grid.nc',
ihop_iter = 9,
ihop_iter = 4,9,
&
2 changes: 2 additions & 0 deletions src/bdry_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,7 @@ SUBROUTINE ReadATI( FileRoot, TopATI, DepthT, myThid )
! we'll be extending the altimetry to infinity to the left and right
NatiPts = NatiPts + 2

IF (ALLOCATED(phi)) DEALLOCATE(phi)
ALLOCATE( Top( NatiPts ), phi( NatiPts ), Stat = IAllocStat )
IF ( IAllocStat /= 0 ) THEN
#ifdef IHOP_WRITE_OUT
Expand Down Expand Up @@ -538,6 +539,7 @@ SUBROUTINE ComputeBdryTangentNormal( Bdry, BotTop )
END SELECT

! compute curvature in each segment
IF (ALLOCATED(phi)) DEALLOCATE(phi)
ALLOCATE( phi( NPts ), Stat = IAllocStat )
! phi is the angle at each node
phi = atan2( Bdry( : )%Nodet( 2 ), Bdry( : )%Nodet( 1 ) )
Expand Down
2 changes: 2 additions & 0 deletions src/beampattern.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,7 @@ SUBROUTINE ReadPat( FileRoot, myThid )
WRITE( PRTFile, * ) 'Number of source beam pattern points', NSBPPts
#endif /* IHOP_WRITE_OUT */

IF (ALLOCATED(SrcBmPat)) DEALLOCATE(SrcBmPat)
ALLOCATE( SrcBmPat( NSBPPts, 2 ), Stat = IAllocStat )
IF ( IAllocStat /= 0 ) THEN
#ifdef IHOP_WRITE_OUT
Expand All @@ -86,6 +87,7 @@ SUBROUTINE ReadPat( FileRoot, myThid )

ELSE ! no pattern given, use omni source pattern
NSBPPts = 2
IF (ALLOCATED(SrcBmPat)) DEALLOCATE(SrcBmPat)
ALLOCATE( SrcBmPat( 2, 2 ), Stat = IAllocStat )
IF ( IAllocStat /= 0 ) THEN
#ifdef IHOP_WRITE_OUT
Expand Down
50 changes: 31 additions & 19 deletions src/bellhop.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ MODULE BELLHOP
USE ihop_mod, only: rad2deg, i, MaxN, Title, Beam, ray2D, istep, &
NRz_per_range, afreq, SrcDeclAngle, &
PRTFile, SHDFile, ARRFile, RAYFile, DELFile
USE readEnviHop, only: ReadEnvironment, OpenOutputFiles
USE readEnviHop, only: ReadEnvironment, OpenOutputFiles, resetMemory
USE angle_mod, only: Angles, ialpha
USE srPos_mod, only: Pos
USE ssp_mod, only: EvaluateSSP, HSInfo, Bdry, SSP, betaPowerLaw, fT
Expand Down Expand Up @@ -65,11 +65,13 @@ MODULE BELLHOP
EXTERNAL ILNBLNK

CONTAINS
SUBROUTINE IHOP_INIT ( myThid )
SUBROUTINE IHOP_INIT ( myTime, myIter, myThid )
! !INPUT/OUTPUT PARAMETERS:
! == Routine Arguments ==
! myThid :: Thread number. Unused by IESCO
! msgBuf :: Used to build messages for printing.
_RL, INTENT( IN ) :: myTime
INTEGER, INTENT( IN ) :: myIter
INTEGER, INTENT( IN ) :: myThid
CHARACTER*(MAX_LEN_MBUF):: msgBuf

Expand All @@ -81,34 +83,41 @@ SUBROUTINE IHOP_INIT ( myThid )
! added locally previously read in from unknown mod ... IEsco2022
CHARACTER ( LEN=2 ) :: AttenUnit
! For MPI writing: copying eeboot_minimal.F
CHARACTER*(13) :: fNam
CHARACTER*(6) :: fmtStr
INTEGER :: mpiRC, iTmp
CHARACTER*(MAX_LEN_FNAM) :: fNam
CHARACTER*(6) :: fmtStr
INTEGER :: mpiRC, IL
! ===========================================================================

! Open the print file: template from eeboot_minimal.F
#ifdef IHOP_WRITE_OUT
IF ( .NOT.usingMPI ) THEN
WRITE(myProcessStr, '(I4.4)') myProcId
WRITE(fNam,'(A,A,A,A)') TRIM(IHOP_fileroot),'.',myProcessStr(1:4),'.prt'
WRITE(myProcessStr, '(I10.10)') myIter
IL=ILNBLNK( myProcessStr )
WRITE(fNam,'(A,A,A,A)') TRIM(IHOP_fileroot),'.',myProcessStr(1:IL),'.prt'
OPEN(PRTFile, FILE = fNam, STATUS = 'UNKNOWN', IOSTAT = iostat )
#ifdef ALLOW_USE_MPI
ELSE ! using MPI
CALL MPI_COMM_RANK( MPI_COMM_MODEL, mpiMyId, mpiRC )
myProcId = mpiMyId
iTmp = MAX(4,1+INT(LOG10(DFLOAT(nPx*nPy))))
WRITE(fmtStr,'(2(A,I1),A)') '(I',iTmp,'.',iTmp,')'
IL = MAX(4,1+INT(LOG10(DFLOAT(nPx*nPy))))
WRITE(fmtStr,'(2(A,I1),A)') '(I',IL,'.',IL,')'
WRITE(myProcessStr,fmtStr) myProcId
iTmp = ILNBLNK( myProcessStr )
IL = ILNBLNK( myProcessStr )
mpiPidIo = myProcId
pidIO = mpiPidIo

IF( mpiPidIo.EQ.myProcId ) THEN
# ifdef SINGLE_DISK_IO
IF( myProcId.eq.0) THEN
# endif
WRITE(fNam,'(A,A,A,A)') &
TRIM(IHOP_fileroot),'.',myProcessStr(1:iTmp),'.prt'
IF (myIter.GE.0) THEN
WRITE(fNam,'(4A,I10.10,A)') &
TRIM(IHOP_fileroot),'.',myProcessStr(1:IL),'.',myIter,'.prt'
ELSE
WRITE(fNam,'(4A)') &
TRIM(IHOP_fileroot),'.',myProcessStr(1:IL),'.prt'
ENDIF

OPEN(PRTFile, FILE=fNam, STATUS='UNKNOWN', IOSTAT=iostat )
IF ( iostat /= 0 ) THEN
WRITE(*,*) 'ihop: IHOP_fileroot not recognized, ', &
Expand All @@ -124,7 +133,9 @@ SUBROUTINE IHOP_INIT ( myThid )
# endif /* ALLOW_USE_MPI */
END IF
#endif /* IHOP_WRITE_OUT */


! Reset memory
CALL resetMemory()
! ===========================================================================
! Read in or otherwise initialize inline all the variables by BELLHOP
IF ( Inline ) THEN
Expand Down Expand Up @@ -230,8 +241,8 @@ SUBROUTINE IHOP_INIT ( myThid )


ELSE ! Read and allocate user input
! Read .env file: REQUIRED
CALL ReadEnvironment( IHOP_fileroot, myThid )
! save data.ihop, gcm SSP: REQUIRED
CALL ReadEnvironment( myTime, myIter, myThid )
! AlTImetry: OPTIONAL, default is no ATIFile
CALL ReadATI( IHOP_fileroot, Bdry%Top%HS%Opt( 5:5 ), Bdry%Top%HS%Depth, myThid )
! BaThYmetry: OPTIONAL, default is BTYFile
Expand All @@ -255,9 +266,9 @@ SUBROUTINE IHOP_INIT ( myThid )
END IF

! open all output files
CALL OpenOutputFiles( IHOP_fileroot )
CALL OpenOutputFiles( IHOP_fileroot, myTime, myIter, myThid )

! Run Bellhop solver
! Run Bellhop solver on a single processor
if (numberOfProcs.gt.1) then
if(myProcId.eq.(numberOfProcs-1)) then
CALL CPU_TIME( Tstart )
Expand All @@ -274,7 +285,7 @@ SUBROUTINE IHOP_INIT ( myThid )
! print run time
if (numberOfProcs.gt.1) then
if(myProcId.ne.(numberOfProcs-1)) then
WRITE(msgBuf,'(A,I4,A)') 'Proc ',myProcId, " didn't run ihop"
WRITE(msgBuf,'(A,I4,A)') 'NOTE: Proc ',myProcId, " didn't run ihop"
CALL PRINT_MESSAGE(msgBuf, PRTFile, SQUEEZE_RIGHT, myThid)
endif
endif
Expand Down Expand Up @@ -315,7 +326,7 @@ SUBROUTINE BellhopCore( myThid )

! == Local Variables ==
INTEGER :: iAllocStat
INTEGER, PARAMETER :: ArrivalsStorage = 200000, MinNArr = 10
INTEGER, PARAMETER :: ArrivalsStorage = 20000, MinNArr = 10
INTEGER :: IBPvec( 1 ), ibp, is, iBeamWindow2, Irz1, Irec, &
NalphaOpt, iSeg
REAL (KIND=_RL90) :: Amp0, DalphaOpt, xs( 2 ), RadMax, s, &
Expand Down Expand Up @@ -369,6 +380,7 @@ SUBROUTINE BellhopCore( myThid )
NRz_per_range = Pos%NRz ! rectilinear grid
END SELECT

IF (ALLOCATED(U)) DEALLOCATE(U)
SELECT CASE ( Beam%RunType( 1 : 1 ) )
! for a TL calculation, allocate space for the pressure matrix
CASE ( 'C', 'S', 'I' ) ! TL calculation
Expand Down
42 changes: 8 additions & 34 deletions src/ihop_driver.F
Original file line number Diff line number Diff line change
Expand Up @@ -13,13 +13,6 @@ SUBROUTINE IHOP_DRIVER( myTime, myIter, myThid )
USE bellhop

IMPLICIT NONE
C == Global variables ==
C#include "SIZE.h"
C#include "GRID.h"
C#include "EEPARAMS.h"
C#include "PARAMS.h"
C#include "IHOP_SIZE.h"
C#include "IHOP.h"

C !INPUT PARAMETERS: ===================================================
C myTime :: Current time in simulation
Expand All @@ -31,36 +24,17 @@ SUBROUTINE IHOP_DRIVER( myTime, myIter, myThid )
C !OUTPUT PARAMETERS: ==================================================

C !LOCAL VARIABLES: ====================================================
C bi,bj :: Tile indices
C lat2d :: latitude of grid-cell center [rad]
C pHalf3d :: pressure at interface between 2 levels [Pa]
C pFull3d :: pressure at level center [Pa]
C zHalf3d :: height of interface between 2 levels [m]
C zFull3d :: height of level center [m]
C t3d :: absolute temperature [K]
C q3d :: specific humidity [kg/kg]
C u3d :: wind speed, 1rst component (X-dir) [m/s]
C v3d :: wind speed, 2nd component (Y-dir) [m/s]
INTEGER bi, bj
_RL lat2d (sNx,sNy)
_RL pHalf3d (sNx,sNy,Nr+1)
_RL pFull3d (sNx,sNy,Nr)
_RL zHalf3d (sNx,sNy,Nr+1)
_RL zFull3d (sNx,sNy,Nr)
_RL t3d (sNx,sNy,Nr)
_RL q3d (sNx,sNy,Nr)
_RL u3d (sNx,sNy,Nr)
_RL v3d (sNx,sNy,Nr)
_RL tdt3d (sNx,sNy,Nr)
_RL qdt3d (sNx,sNy,Nr)
_RL udt3d (sNx,sNy,Nr)
_RL vdt3d (sNx,sNy,Nr)
INTEGER t
CEOP

#ifdef ALLOW_IHOP
IF ( ihop_iter .EQ. myIter ) THEN
CALL IHOP_INIT( myThid )
ENDIF
DO t=1,nts
IF ( IHOP_iter(t).GE.0 ) THEN
IF ( IHOP_iter(t).EQ.myIter ) THEN
CALL IHOP_INIT( myTime, myIter, myThid )
ENDIF
ENDIF
ENDDO
#endif /* ALLOW_IHOP */

RETURN
Expand Down
18 changes: 10 additions & 8 deletions src/ihop_readparms.F
Original file line number Diff line number Diff line change
Expand Up @@ -235,7 +235,9 @@ SUBROUTINE IHOP_READPARMS( myThid )
C ihop_init_fixed.f
useSSPFile = .FALSE.
IHOP_interpfile = ''
ihop_iter = 0
DO i=1,nts
ihop_iter(i) = -1
ENDDO
IHOP_npts_range = 0
IHOP_npts_idw = 0
DO i=1,IHOP_MAX_NC_SIZE
Expand All @@ -255,13 +257,13 @@ SUBROUTINE IHOP_READPARMS( myThid )
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
& SQUEEZE_RIGHT, myThid )

CC Check paramters of IHOP_PARM03
C IF ( IHOP_interpfile.EQ.'' ) THEN
C WRITE(msgBuf, '(2A)') 'S/R IHOP_READPARMS: "IHOP_interpfile" ',
C & 'Provide interpolation file name for ihop package'
C CALL PRINT_ERROR( msgBuf, myThid )
C STOP 'ABNORMAL END: S/R IHOP_READPARMS'
C ENDIF
C Check paramters of IHOP_PARM03
IF ( IHOP_interpfile.EQ.'' ) THEN
WRITE(msgBuf, '(2A)') 'S/R IHOP_READPARMS: "IHOP_interpfile" ',
& 'Provide interpolation file name for ihop package'
CALL PRINT_ERROR( msgBuf, myThid )
STOP 'ABNORMAL END: S/R IHOP_READPARMS'
ENDIF

C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

Expand Down
Loading

0 comments on commit a164a8f

Please sign in to comment.