Skip to content

Commit

Permalink
Fix odd if
Browse files Browse the repository at this point in the history
  • Loading branch information
mathomp4 committed Jul 20, 2023
1 parent c678485 commit 67f2520
Showing 1 changed file with 18 additions and 20 deletions.
38 changes: 18 additions & 20 deletions Tests/ExtDataRoot_GridComp.F90
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@

!-------------------------------------------------------------------------
! NASA/GSFC, Global Modeling and Assimilation Office, Code 610.1 !
!-------------------------------------------------------------------------
!
#include "MAPL_Generic.h"

MODULE ExtDataUtRoot_GridCompMod
use ESMF
use MAPL
Expand Down Expand Up @@ -152,7 +152,7 @@ SUBROUTINE Initialize_ ( GC, IMPORT, EXPORT, CLOCK, rc )
type(ESMF_State), intent(inout) :: EXPORT ! Export State
integer, intent(out) :: rc ! Error return code:

type(ESMF_Config) :: CF ! Universal Config
type(ESMF_Config) :: CF ! Universal Config
integer :: status
character(len=ESMF_MAXSTR) :: comp_name

Expand Down Expand Up @@ -290,25 +290,25 @@ SUBROUTINE Run_ ( GC, IMPORT, EXPORT, CLOCK, rc )
call MAPL_GetPointer(internal,ptrR4,'lats',_RC)
call ESMF_GridGetCoord (Grid, coordDim=2, localDE=0, &
staggerloc=ESMF_STAGGERLOC_CENTER, &
farrayPtr=ptrR8, _RC)
farrayPtr=ptrR8, _RC)
ptrR4=ptrR8
end if

select case (trim(synth%runMode))

case(RunModeGenerateExports)

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

case(RunModeGenerateImports)

call FillState(internal,import,currTime,grid,synth,_RC)
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)
call CompareState(import,export,0.001,_RC)

case(runModeFillImport)
case(runModeFillImport)
! Nothing to do, we are just letting ExtData run

case(runModeFillExportFromImport)
Expand Down Expand Up @@ -430,9 +430,9 @@ function evaluate_time(this,currTime,rc) result(dt)
call ESMF_TimeIntervalSet(yearInterval,yy=yint,_RC)
currTime = currTime+yearInterval
end if
periodic_time = this%set_time_for_date(currTime,_RC)
periodic_time = this%set_time_for_date(currTime,_RC)
if (this%have_offset) then
timeInterval = periodic_time + this%update_offset - this%refTime
timeInterval = periodic_time + this%update_offset - this%refTime
else
timeInterval = periodic_time - this%refTime
end if
Expand Down Expand Up @@ -469,7 +469,7 @@ function set_time_for_date(this,input_time,rc) result(returned_time)
returned_time = input_time
else if (new_time < input_time) then
returned_time = new_time
else if (new_time > input_time) then
else if (new_time > input_time) then
call ESMF_TimeSet(new_time,yy=year,mm=month,dd=day-1,h=hour,m=minute,s=second,_RC)
returned_time = new_time
end if
Expand Down Expand Up @@ -529,7 +529,7 @@ subroutine CopyState(inState,outState,rc)
EXptr3=IMptr3
end if
end do
deallocate(inNameList,outNameList)
deallocate(inNameList,outNameList)
_RETURN(ESMF_SUCCESS)

end subroutine CopyState
Expand All @@ -554,9 +554,7 @@ subroutine FillState(inState,outState,time,grid,Synth,rc)
integer, allocatable :: seeds(:)
type(ESMF_VM) :: vm

if (synth%on_tiles) then

else
if (.not. synth%on_tiles) then
call MAPL_GridGet(grid,localcellcountperdim=ldims,_RC)
call MAPL_Grid_Interior(grid,i1,in,j1,jn)
end if
Expand Down Expand Up @@ -649,7 +647,7 @@ subroutine CompareState(State1,State2,tol,rc)
logical, allocatable :: foundDiff(:)
type(ESMF_Field) :: Field1,Field2
logical :: all_undef1, all_undef2

call ESMF_StateGet(State1,itemcount=itemCount,_RC)
allocate(NameList(itemCount),stat=status)
_VERIFY(status)
Expand Down Expand Up @@ -687,21 +685,21 @@ subroutine CompareState(State1,State2,tol,rc)
foundDiff(i) = .true.
end if
end if
if (foundDiff(i)) then
if (foundDiff(i)) then
_FAIL('found difference when compare state')
end if
enddo

_RETURN(ESMF_SUCCESS)

end subroutine CompareState

subroutine ForceAllocation(state,rc)
type(ESMF_State), intent(inout) :: state
integer, optional, intent(out) :: rc

integer :: status

real, pointer :: ptr3d(:,:,:)
real, pointer :: ptr2d(:,:)
integer :: ii
Expand Down

0 comments on commit 67f2520

Please sign in to comment.