Skip to content

Commit

Permalink
Merge pull request #2191 from GEOS-ESM/feature/bmauer/extdatadriver_b…
Browse files Browse the repository at this point in the history
…enchmark_updates

ExtDataDriver.x updates for benchmarking
  • Loading branch information
mathomp4 authored Jun 15, 2023
2 parents b6487e2 + e8e7547 commit 33b7aed
Show file tree
Hide file tree
Showing 2 changed files with 33 additions and 7 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
### Added

- Added field utilities to perform basic numeric operations on fields
- Added new fill option and run mode for ExtDataDriver.x

### Changed

Expand Down
39 changes: 32 additions & 7 deletions Tests/ExtDataRoot_GridComp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ MODULE ExtDataUtRoot_GridCompMod
end type SyntheticFieldSupportWrapper

character(len=*), parameter :: runModeGenerateExports = "GenerateExports"
character(len=*), parameter :: runModeGenerateImports = "GenerateImports"
character(len=*), parameter :: runModeCompareImports = "CompareImports"
character(len=*), parameter :: runModeFillExportFromImport = "FillExportsFromImports"
character(len=*), parameter :: runModeFillImport = "FillImport"
Expand Down Expand Up @@ -114,6 +115,13 @@ subroutine SetServices ( GC, RC )
units = 'na', &
dims = MAPL_DimsHorzOnly, &
vlocation = MAPL_VLocationNone, _RC)
call MAPL_AddInternalSpec(GC,&
short_name='rand', &
long_name='random number' , &
units = 'na', &
dims = MAPL_DimsHorzOnly, &
vlocation = MAPL_VLocationNone, _RC)


call MAPL_GenericSetServices ( GC, _RC)

Expand Down Expand Up @@ -241,6 +249,10 @@ SUBROUTINE Run_ ( GC, IMPORT, EXPORT, CLOCK, rc )

call FillState(internal,export,currTime,grid,synth,_RC)

case(RunModeGenerateImports)

call FillState(internal,import,currTime,grid,synth,_RC)

case(runModecompareImports)
call FillState(internal,export,currTime,grid,synth,_RC)
call CompareState(import,export,0.001,_RC)
Expand Down Expand Up @@ -478,11 +490,12 @@ subroutine FillState(inState,outState,time,grid,Synth,rc)
real, pointer :: Exptr2(:,:) => null()
integer :: itemcount
character(len=ESMF_MAXSTR), allocatable :: outNameList(:)
type(ESMF_Field) :: expf,farray(6)
type(ESMF_Field) :: expf,farray(7)
type(ESMF_State) :: pstate
character(len=:), pointer :: fexpr
integer :: i1,in,j1,jn,ldims(3),i,j
real(kind=ESMF_KIND_R8) :: doy,time_delta
integer :: i1,in,j1,jn,ldims(3),i,j,seed_size,mypet
integer, allocatable :: seeds(:)
type(ESMF_VM) :: vm

call MAPL_GridGet(grid,localcellcountperdim=ldims,_RC)
call MAPL_Grid_Interior(grid,i1,in,j1,jn)
Expand All @@ -491,6 +504,9 @@ subroutine FillState(inState,outState,time,grid,Synth,rc)
_VERIFY(status)
call ESMF_StateGet(outState,itemNameList=outNameList,_RC)

call MAPL_GetPointer(inState,exPtr2,'time',_RC)
exPtr2=synth%tFunc%evaluate_time(Time,_RC)

call MAPL_GetPointer(inState,exPtr2,'i_index',_RC)
do j = 1,ldims(2)
do i=1,ldims(1)
Expand All @@ -504,16 +520,25 @@ subroutine FillState(inState,outState,time,grid,Synth,rc)
enddo
enddo

call MAPL_GetPointer(inState,exPtr2,'doy',_RC)
exPtr2 = compute_doy(time,_RC)

call MAPL_GetPointer(inState,exPtr2,'rand',_RC)
call random_seed(size=seed_size)
allocate(seeds(seed_size))
call ESMF_VMGetCurrent(vm,_RC)
call ESMF_VMGet(vm,localPet=mypet,_RC)
seeds = mypet
call random_seed(put=seeds)
call random_number(exPtr2)

call ESMF_StateGet(inState,'time',farray(1),_RC)
time_delta = synth%tFunc%evaluate_time(Time,_RC)
call FieldSet(farray(1), time_delta,_RC)
call ESMF_StateGet(inState,'lons',farray(2),_RC)
call ESMF_StateGet(inState,'lats',farray(3),_RC)
call ESMF_StateGet(inState,'i_index',farray(4),_RC)
call ESMF_StateGet(inState,'j_index',farray(5),_RC)
call ESMF_StateGet(inState,'doy',farray(6),_RC)
doy = compute_doy(time,_RC)
call FieldSet(farray(6), doy,_RC)
call ESMF_StateGet(inState,'rand',farray(7),_RC)
pstate = ESMF_StateCreate(_RC)
call ESMF_StateAdd(pstate,farray,_RC)

Expand Down

0 comments on commit 33b7aed

Please sign in to comment.