Skip to content

Commit

Permalink
Merge branch 'work/reconcile-scaling' of https://github.com/esmf-org/…
Browse files Browse the repository at this point in the history
…esmf into work/reconcile-scaling
  • Loading branch information
oehmke committed Sep 26, 2024
2 parents 6c647d3 + bf55e92 commit 36740fc
Show file tree
Hide file tree
Showing 7 changed files with 237 additions and 478 deletions.
2 changes: 1 addition & 1 deletion src/Infrastructure/Array/interface/ESMF_ArrayGet.cppF90
Original file line number Diff line number Diff line change
Expand Up @@ -583,7 +583,7 @@ type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
call c_ESMC_GetVM(array, vm, localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
! Set init code
! Set init code on the VM object before returning
call ESMF_VMSetInitCreated(vm, rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
Expand Down
1 change: 0 additions & 1 deletion src/Superstructure/State/src/ESMF_State.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,6 @@ module ESMF_StateMod

public ESMF_StateAdd, ESMF_StateAddReplace
public ESMF_StateGet
public ESMF_StateIsReconcileNeeded

public ESMF_StateLog

Expand Down
137 changes: 0 additions & 137 deletions src/Superstructure/State/src/ESMF_StateAPI.cppF90
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,6 @@ module ESMF_StateAPIMod
public ESMF_StateAdd, ESMF_StateAddReplace
public ESMF_StateGet
public ESMF_StateIsCreated
public ESMF_StateIsReconcileNeeded

public ESMF_StateLog
public ESMF_StatePrint
Expand Down Expand Up @@ -1703,140 +1702,6 @@ type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
!------------------------------------------------------------------------------




!------------------------------------------------------------------------------
^undef ESMF_METHOD
^define ESMF_METHOD "ESMF_StateIsReconcileNeeded"
!BOPI
! !IROUTINE: ESMF_StateIsReconcileNeeded -- Return logical true if reconciliation needed
!
! !INTERFACE:
function ESMF_StateIsReconcileNeeded(state, keywordEnforcer, collectiveflag, vm, rc)
!
! !RETURN VALUE:
logical :: ESMF_StateIsReconcileNeeded
!
! !ARGUMENTS:
type(ESMF_State), intent(in) :: state
type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
logical, intent(in), optional :: collectiveflag
type(ESMF_VM), intent(in), optional :: vm
integer, intent(out), optional :: rc

!
! !DESCRIPTION:
! Returns true if the {\tt state} needs to be reconciled in order
! to be coherent across PETs. By default, this is a local call.
! Optionally, the {\tt collectiveflag} may be set to collectively
! determine whether other PETs in the VM may need to be reconciled.
!
! The arguments are:
! \begin{description}
! \item[state]
! {\tt ESMF\_State} to query.
! \item[{[collectiveflag]}]
! Perform a collective style call across all PETs in the VM.
! \item[vm]
! The current {\tt ESMF\_VM} (virtual machine). All PETs in this
! {\tt ESMF\_VM} will exchange information about objects which might
! only be known to one or more PETs, and ensure all PETs in this VM
! have a consistent view of the object list in this {\tt ESMF\_State}.
! Required when {\tt collectiveflag} is set to {\tt .true.}.
! \item[{[rc]}]
! Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
! \end{description}
!
!EOPI

logical :: localrecflag
integer :: localrc
integer :: commsend, commrecv

ESMF_StateIsReconcileNeeded = .false.

! check input variables
ESMF_INIT_CHECK_DEEP(ESMF_StateGetInit,state,rc)
ESMF_INIT_CHECK_DEEP(ESMF_VMGetInit,vm,rc)

localrecflag = is_rec_needed_worker (state%statep)

if (present (collectiveflag)) then
if (collectiveflag) then

if (.not. present (vm)) then
localrc = ESMF_RC_ARG_INCOMP
if (ESMF_LogFoundError(localrc, &
msg="VM is required for collective inquiry", &
ESMF_CONTEXT, rcToReturn=rc)) return
end if

commsend = merge (1, 0, localrecflag)
call ESMF_VMAllReduce (vm=vm, &
sendData=commsend, recvData=commrecv, reduceflag=ESMF_REDUCE_SUM, &
rc=localrc)
if (ESMF_LogFoundError(localrc, &
ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
localrecflag = commrecv /= 0
end if
end if

ESMF_StateIsReconcileNeeded = localrecflag
if (present (rc)) rc = ESMF_SUCCESS

contains

recursive function is_rec_needed_worker (sp1) result (is_rec_needed)
type(ESMF_StateClass), intent(in) :: sp1
logical :: is_rec_needed

type(ESMF_StateItem) , pointer :: nextitem1
integer :: i1

type(ESMF_StateItemWrap), pointer :: siwrap(:)
integer :: ptrcnt

integer :: localrc1
integer :: memstat1

! Default return this levels flag

is_rec_needed = sp1%reconcileneededflag
if (is_rec_needed) return

! Then search nested States

siwrap => null ()
call ESMF_ContainerGet (sp1%stateContainer, &
itemCount=ptrcnt, itemList=siwrap, rc=localrc1)
if (ESMF_LogFoundError(localrc1, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return

do, i1 = 1, ptrcnt
nextitem1 => siwrap(i1)%si
if (nextitem1%otype == ESMF_STATEITEM_STATE) then
is_rec_needed = &
is_rec_needed_worker (nextitem1%datap%spp)
if (is_rec_needed) then
deallocate (siwrap, stat=memstat1)
if (ESMF_LogFoundDeallocError(memstat1, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
return
end if
end if
end do

if (associated (siwrap)) &
deallocate (siwrap, stat=memstat1)
if (ESMF_LogFoundDeallocError(memstat1, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return

end function is_rec_needed_worker

end function ESMF_StateIsReconcileNeeded


! -------------------------- ESMF-public method -----------------------------
^undef ESMF_METHOD
^define ESMF_METHOD "ESMF_StateLog()"
Expand Down Expand Up @@ -2277,8 +2142,6 @@ type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
write (ESMF_UtilIOStdout,'(1x,4a,i0)') nestr, &
" status: ", trim(msgbuf), &
", object count: ", ptrcnt
write (ESMF_UtilIOStdout,'(1x,2a,L1)') nestr, &
" reconcile needed: ", sp1%reconcileneededflag

! Prints Attributes associated with the State
call ESMF_UtilIOUnitFlush (unit=ESMF_UtilIOstdout, rc=localrc1)
Expand Down
4 changes: 0 additions & 4 deletions src/Superstructure/State/src/ESMF_StateInternals.cppF90
Original file line number Diff line number Diff line change
Expand Up @@ -377,7 +377,6 @@ ESMF_INIT_CHECK_DEEP(ESMF_RouteHandleGetInit,routehandles(i),rc)
else
stypep%st = ESMF_STATEINTENT_UNSPECIFIED
endif
stypep%reconcileneededflag = .false.

stypep%stateContainer = ESMF_ContainerCreate (rc=localrc)
if (ESMF_LogFoundError(localrc, &
Expand Down Expand Up @@ -698,7 +697,6 @@ ESMF_INIT_CHECK_DEEP(ESMF_RouteHandleGetInit,routehandles(i),rc)
^if defined(stateversion) @\
! TODO: This needs to be verified... @\
sip%datap%spp => mname(i)%statep ! State version @\
sip%datap%spp%reconcileneededFlag = .false. @\
^else @\
sip%datap%mtypecomponent = mname(i) @\
^endif @\
Expand All @@ -725,8 +723,6 @@ ESMF_INIT_CHECK_DEEP(ESMF_RouteHandleGetInit,routehandles(i),rc)
end if @\
@\
end do @\
@\
stypep%reconcileneededFlag = .true. @\
@\
if (present(rc)) rc = ESMF_SUCCESS @\
@\
Expand Down
1 change: 0 additions & 1 deletion src/Superstructure/State/src/ESMF_StateItem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -260,7 +260,6 @@ module ESMF_StateItemMod
#endif
type(ESMF_Container):: stateContainer
integer :: alloccount
logical :: reconcileneededflag
ESMF_INIT_DECLARE
end type

Expand Down
37 changes: 3 additions & 34 deletions src/Superstructure/StateReconcile/src/ESMF_StateReconcile.F90
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ module ESMF_StateReconcileMod
! to be called by ESMF users.
! public :: ESMF_ReconcileDeserialize, ESMF_ReconcileSerialize
! public :: ESMF_ReconcileSendItems
public :: ESMF_ReconcileExchgAttributes

!EOPI

Expand Down Expand Up @@ -511,7 +512,7 @@ recursive subroutine StateReconcileIsNoopLoc(stateR, isNoopLoc, rc)
ESMF_CONTEXT, rcToReturn=rc)) return
endif

!call ESMF_LogWrite("processing "//trim(itemNameList(item)), ESMF_LOGMSG_DEBUG, rc=localrc)
call ESMF_LogWrite("processing "//trim(itemNameList(item)), ESMF_LOGMSG_DEBUG, rc=localrc)

call ESMF_VMGetThis(vmItem, thisItem, rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, ESMF_CONTEXT, &
Expand All @@ -525,7 +526,7 @@ recursive subroutine StateReconcileIsNoopLoc(stateR, isNoopLoc, rc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, ESMF_CONTEXT, &
rcToReturn=rc)) return

!call ESMF_VMIdLog(vmIdItem, prefix="vmIdItem: ", rc=rc)
call ESMF_VMIdLog(vmIdItem, prefix="vmIdItem: ", rc=rc)

isNoopLoc = ESMF_VMIdCompare(vmIdItem, vmId, keyOnly=.true., &
rc=localrc)
Expand Down Expand Up @@ -1135,38 +1136,6 @@ subroutine ESMF_StateReconcile_driver (state, vm, attreconflag, rc)
! -------------------------------------------------------------------------
if (meminfo) call ESMF_VMLogMemInfo ("after 7.) Deserialize received objects and create proxies")

! -------------------------------------------------------------------------
! 8.) Attributes on the State itself
! -------------------------------------------------------------------------
if (profile) then
call ESMF_TraceRegionEnter("8.) Attributes on the State itself", rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, &
rcToReturn=rc)) return
endif
! -------------------------------------------------------------------------
if (attreconflag == ESMF_ATTRECONCILE_ON) then
if (trace) then
call ESMF_ReconcileDebugPrint (ESMF_METHOD // &
': *** Step 8 - Exchange Base Attributes', ask=.false.)
call ESMF_VMBarrier (vm)
end if
call ESMF_ReconcileExchgAttributes (state, vm, rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, &
rcToReturn=rc)) return
end if
state%statep%reconcileneededflag = .false.
! -------------------------------------------------------------------------
if (profile) then
call ESMF_TraceRegionExit("8.) Attributes on the State itself", rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, &
rcToReturn=rc)) return
endif
! -------------------------------------------------------------------------
if (meminfo) call ESMF_VMLogMemInfo ("after 8.) Attributes on the State itself")

if (trace) then
call ESMF_ReconcileDebugPrint (ESMF_METHOD // ': Complete!')
call ESMF_VMBarrier (vm)
Expand Down
Loading

0 comments on commit 36740fc

Please sign in to comment.