Skip to content

Commit

Permalink
Merge pull request #2237 from GEOS-ESM/feature/bmauer/extdatadriver_d…
Browse files Browse the repository at this point in the history
…elay

Feature/bmauer/extdatadriver delay
  • Loading branch information
bena-nasa authored Jul 18, 2023
2 parents 1f483b9 + b9198a6 commit 6d3402f
Show file tree
Hide file tree
Showing 5 changed files with 47 additions and 0 deletions.
2 changes: 2 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0

### Added

- Add ability to introduce a time-step delay in ExtDataDriver.x to simulate the timestep latency of a real model
- Added a MAPL\_Sleep function, equivalent to some vendor supplied but non-standard sleep function
- sampling IODA file with trajectory sampler (step-1): make it run
- Convert ExtData to use ESMF HConfig for YAML parsing rather than YaFYAML
- Set required ESMF version to 8.5.0
Expand Down
12 changes: 12 additions & 0 deletions Tests/ExtDataRoot_GridComp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
MODULE ExtDataUtRoot_GridCompMod
use ESMF
use MAPL
use MAPLShared
use VarspecDescriptionMod
use VarspecDescriptionVectorMod
use netcdf
Expand Down Expand Up @@ -38,6 +39,7 @@ MODULE ExtDataUtRoot_GridCompMod
type(StringStringMap) :: fillDefs
character(len=ESMF_MAXSTR) :: runMode
type(timeVar) :: tFunc
real :: delay ! in seconds
end type SyntheticFieldSupport

type :: SyntheticFieldSupportWrapper
Expand Down Expand Up @@ -153,6 +155,7 @@ SUBROUTINE Initialize_ ( GC, IMPORT, EXPORT, CLOCK, rc )
type(SyntheticFieldSupportWrapper) :: synthWrap
type(SyntheticFieldSupport), pointer :: synth => null()
character(len=ESMF_MaxStr) :: key, keyVal
logical :: isPresent

call ESMF_GridCompGet( GC, name=comp_name, config=CF, _RC )

Expand All @@ -161,6 +164,12 @@ SUBROUTINE Initialize_ ( GC, IMPORT, EXPORT, CLOCK, rc )
synth => synthWrap%ptr
call ESMF_ClockGet(Clock,currTime=currTime,_RC)

synth%delay = -1.0
call ESMF_ConfigFindLabel(cf,label='delay:',isPresent=isPresent,_RC)
if (isPresent) then
call ESMF_ConfigGetAttribute(cf,label='delay:',value=synth%delay,_RC)
end if

call ESMF_ConfigGetDim(cf,nrows,ncolumn,label="FILL_DEF::",rc=status)
if (status==ESMF_SUCCESS) then
call ESMF_ConfigFindLabel(cf,label="FILL_DEF::",_RC)
Expand Down Expand Up @@ -231,6 +240,9 @@ SUBROUTINE Run_ ( GC, IMPORT, EXPORT, CLOCK, rc )
call ESMF_UserCompGetInternalState(gc,wrap_name,synthWrap,status)
_VERIFY(status)
synth => synthWrap%ptr
if (synth%delay > -1.0) then
call MAPL_Sleep(synth%delay)
end if
call ESMF_GridCompGet(GC,grid=grid,_RC)
call MAPL_GetPointer(internal,ptrR4,'lons',_RC)
call ESMF_GridGetCoord (Grid, coordDim=1, localDE=0, &
Expand Down
1 change: 1 addition & 0 deletions shared/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ set (srcs
MAPL_DateTime_Parsing.F90
DownBit.F90
ShaveMantissa.c
MAPL_Sleep.F90
# Fortran submodules
Interp/Interp.F90 Interp/Interp_implementation.F90
Shmem/Shmem.F90 Shmem/Shmem_implementation.F90
Expand Down
31 changes: 31 additions & 0 deletions shared/MAPL_Sleep.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
module MAPL_SleepMod

use, intrinsic :: iso_fortran_env, only: REAL64,INT64
implicit none
private

public MAPL_Sleep

contains

! wait time in seconds
subroutine MAPL_Sleep(wait_time)
real, intent(in) :: wait_time

integer(kind=INT64) :: s1,s2,count_max,count_rate,delta
real(kind=REAL64) :: seconds_elapsed

call system_clock(count=s1,count_rate=count_rate,count_max=count_max)

do

call system_clock(count=s2)
delta = s2-s1
if (delta < 0) delta= s2 + (count_max - mod(s1,count_max))
seconds_elapsed = dble(delta)/dble(count_rate)
if (seconds_elapsed > wait_time) exit

enddo

end subroutine
end module MAPL_SleepMod
1 change: 1 addition & 0 deletions shared/MaplShared.F90
Original file line number Diff line number Diff line change
Expand Up @@ -21,5 +21,6 @@ module MaplShared
use mapl_CommGroupDescriptionMod
use mapl_AbstractCommSplitterMod
use mapl_DownbitMod
use mapl_sleepMod

end module MaplShared

0 comments on commit 6d3402f

Please sign in to comment.