Skip to content

Commit

Permalink
Browse files Browse the repository at this point in the history
  • Loading branch information
danishyo committed Feb 21, 2022
2 parents e6ef960 + c378947 commit 2e7d408
Show file tree
Hide file tree
Showing 5 changed files with 39 additions and 66 deletions.
4 changes: 2 additions & 2 deletions src/schism/Makefile
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
# This code is part of the SCHISM-ESMF interface.
#
# @copyright (C) 2021 Helmholtz-Zentrum Hereon
# @copyright (C) 2021-2022 Helmholtz-Zentrum Hereon
# @copyright (C) 2020-2021 Helmholtz-Zentrum Geesthacht
#
# @author Carsten Lemmen [email protected]
# @author Carsten Lemmen <[email protected]>
#
# @license Apache License, Version 2.0 (the "License");
# you may not use this file except in compliance with the License.
Expand Down
12 changes: 6 additions & 6 deletions src/schism/Readme.md
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
This directory contains NUOPC cap for schism instances of NUOPC_Model and for the
ESMF gridded component.
This directory contains the ESMF/NUOPC caps for the SCHISM model, as well as supporting infrastructure and interfaces.

For each NUOPC_Model, there is a corresponding Makefile snippet. Currently
available components are
The ESMF cap `schism_esmf_cap` relies on utilities in `schism_esmf_utils` and the basic model interface `schism_bmi`.
The NUOPC cap `schism_nuopc_cap` relies on utilities in `schism_nuop_utils`and `schism_esmf_utils`and the `schism_bmi`.

For the NUOPC model instance in `schism_nuopc_cap` there are also corresponding Makefile snippets for standardized
inclusion in NUOPC compliant model systems.

schism_nuopc_cap
: NUOPC cap for SCHISM
34 changes: 3 additions & 31 deletions src/schism/schism_bmi.F90
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
! This code is part of the SCHISM-ESMF interface and defines
! a generic BMI (basic model interface) to schism
!
! @copyright 2021 Helmholtz-Zentrum Hereon
! @copyright 2021-2022 Helmholtz-Zentrum Hereon
! @copyright 2018-2021 Helmholtz-Zentrum Geesthacht
!
! @author Carsten Lemmen [email protected]
! @author Carsten Lemmen <[email protected]>
! @author Richard Hofmeister
!
! @license Apache License, Version 2.0 (the "License");
Expand Down Expand Up @@ -32,15 +32,14 @@
module schism_bmi

! We *should not* use ESMF in a BMI, but this is used here for logging only
use ESMF!, only:: ESMF_LogFoundError, ESMF_END_ABORT, ESMF_Finalize, ESMF_SUCCESS
use esmf!, only:: ESMF_LogFoundError, ESMF_END_ABORT, ESMF_Finalize, ESMF_SUCCESS

interface
subroutine parallel_init(communicator)
implicit none
integer, optional :: communicator
end subroutine parallel_init


subroutine parallel_finalize
implicit none
end subroutine parallel_finalize
Expand Down Expand Up @@ -109,31 +108,4 @@ function schismPtr1(varname) result(farrayPtr)

end function schismPtr1


! subroutine prepareMesh(nodeIds, nodeCoords2D, nodeOwners, nodeMask, &
! elementIds, elementCoords2d, elementTypes, elementMask, nv, &
! rc)
!
! use schism_glbl, only:: npa, np
!
! implicit none
!
! integer, dimension(:), allocatable :: nodeids,elementids,nv
! double precision, dimension(:), allocatable :: nodecoords2d, nodecoords3d
! double precision, dimension(:), allocatable :: elementcoords2d, elementcoords3d
! integer, dimension(:), allocatable :: nodeowners, elementtypes
! integer, dimension(:), allocatable :: nodemask, elementmask
! integer, dimension(:), allocatable :: tmpIdx, tmpIdx2, localNodes, nodeHaloIdx
! integer :: numLocalNodes, numNodeHaloIdx=0
!
! ! prepare mesh
! ! a) take local elements and get number of nodes for definition
! ! b) get number of augmented nodes, which are not connected to local elements
! ! c) allocate node arrays such that nodeids gives all nods belonging to local
! ! elements, all other nodes as part of the augmented domain are outside the
! ! exclusive region
! ! d) allocate element arrays such that local elements (ne) are in array and
! ! augmented elements are defined in the computational domain outside the
! ! exclusive domain

end module schism_bmi
2 changes: 1 addition & 1 deletion src/schism/schism_esmf_cap.F90
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
! This code is part of the SCHISM-ESMF interface
!
! @copyright (C) 2021 Helmholtz-Zentrum Hereon
! @copyright (C) 2021-2022 Helmholtz-Zentrum Hereon
! @copyright (C) 2018--2021 Helmholtz-Zentrum Geesthacht
!
! @author Carsten Lemmen <[email protected]>
Expand Down
53 changes: 27 additions & 26 deletions src/schism/schism_esmf_util.F90
Original file line number Diff line number Diff line change
@@ -1,9 +1,12 @@
! This code is part of the SCHISM-ESMF interface, it defines utility
! functions used both by the NUOPC and ESMF caps
!
! @copyright 2021 Helmholtz-Zentrum Hereon
! @copyright 2022 Virginia Institute of Marine Science
! @copyright 2021-2022 Helmholtz-Zentrum Hereon
! @copyright 2018-2021 Helmholtz-Zentrum Geesthacht
!
! @author Carsten Lemmen <[email protected]>
! @author Joseph Zhang <[email protected]>
! @author Richard Hofmeister
!
! @license Apache License, Version 2.0 (the "License");
Expand Down Expand Up @@ -51,19 +54,19 @@ subroutine addSchismMesh(comp, rc)
type(ESMF_GridComp) :: comp
integer, intent(out) :: rc

type(ESMF_Mesh) :: mesh2d, mesh3d
type(ESMF_Mesh) :: mesh2d
type(ESMF_DistGrid) :: elementDistgrid, distgrid
type(ESMF_CoordSys_Flag) :: coordsys
integer, dimension(:), allocatable :: nodeids, elementids, nv
real(ESMF_KIND_R8), dimension(:), allocatable :: nodecoords2d, nodecoords3d
real(ESMF_KIND_R8), dimension(:), allocatable :: elementcoords2d, elementcoords3d
real(ESMF_KIND_R8), dimension(:), allocatable :: nodecoords2d
real(ESMF_KIND_R8), dimension(:), allocatable :: elementcoords2d
integer, dimension(:), allocatable :: nodeowners, elementtypes
integer, dimension(:), allocatable :: nodemask, elementmask
integer, dimension(:), allocatable :: tmpIdx, tmpIdx2, localNodes, nodeHaloIdx
integer, dimension(:), allocatable :: schismTolocalNodes,testids
integer, dimension(1:4) :: elLocalNode
integer :: numNodeHaloIdx
integer :: i,n,nvcount,nvcount2
integer :: i,n,nvcount
integer :: ii,ip,ie, localrc
integer :: mynp,myne,rank2
type(llist_type),pointer :: nextp=>null()
Expand Down Expand Up @@ -119,10 +122,6 @@ subroutine addSchismMesh(comp, rc)
allocate(nodecoords2d(2*np), stat=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)

!Not used
! allocate(nodecoords3d(3*np), stat=localrc)
! _SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)

!A node is owned by same rank across PETs; interface nodes are owned by min rank
allocate(nodeowners(np), stat=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)
Expand All @@ -143,10 +142,9 @@ subroutine addSchismMesh(comp, rc)
allocate(elementcoords2d(2*ne), stat=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)

!nv (elemConn): 1D array for connectivity (packed from 2D array elnode).
!Outputs local node #
nvcount2=sum(i34(1:ne))
allocate(nv(nvcount2), stat=localrc)
! nv (elemConn): 1D array for connectivity (packed from 2D array elnode).
! Outputs local node #
allocate(nv(sum(i34(1:ne))), stat=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)

! set ESMF coordSys type
Expand Down Expand Up @@ -217,7 +215,7 @@ subroutine addSchismMesh(comp, rc)
elementcoords2d(2*i)=sum(nodecoords2d(2*elLocalNode(1:i34(i))))/i34(i)
end do !i

if(nvcount2/=nvcount) then
if(ubound(nv,1)/=nvcount) then
localrc=ESMF_RC_ARG_SIZE
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)
endif
Expand Down Expand Up @@ -248,37 +246,40 @@ subroutine addSchismMesh(comp, rc)
elementConn=nv, rc=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)

!#if 0
! output mesh information from schism and esmf
call ESMF_MeshGet(mesh2d,numOwnedNodes=mynp,numOwnedElements=myne,elementDistgrid=distgrid,rc=localrc)
call ESMF_MeshGet(mesh2d, numOwnedNodes=mynp, numOwnedElements=myne, elementDistgrid=distgrid, &
rc=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)

allocate(testids(myne))
call ESMF_DistGridGet(distgrid,localDE=0,seqIndexList=testids,rc=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)

write(message,*) 'esmf owned nodes,elements:',mynp,myne
write(message, '(A,I3.3,A,I3.3,A)') trim(compName)//' created mesh from "', np, &
'resident nodes and ', myne, ' resident elements in SCHISM'
call ESMF_LogWrite(trim(message), ESMF_LOGMSG_WARNING)
write(message,*) 'schism owned nodes,elements:',np,ne

write(message, '(A,I3.3,A,I3.3,A)') trim(compName)//' created mesh with "', mynp, &
'owned nodes and ', myne, ' owned elements'
call ESMF_LogWrite(trim(message), ESMF_LOGMSG_WARNING)

!> @todo the following might overflow the message buffer easily ...
write(message,*) 'elementIds:',elementIds
call ESMF_LogWrite(trim(message), ESMF_LOGMSG_WARNING)

write(message,*) 'distgridElementIds:',testids
call ESMF_LogWrite(trim(message), ESMF_LOGMSG_WARNING)

deallocate(testids)
!#endif

call ESMF_GridCompSet(comp, mesh=mesh2d, rc=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)

!YJZ: error
! return
!> @todo the following steps don't work in the NUOPC cap yet

!> Create fields for export to describe mesh (this information is not yet
!> accessible with ESMF_MeshGet calls)
!> @todo remove this part of the code once there is a suitable ESMF implementation

#if 0
!> Create a dummy field to satisfy ugrid conventions
field = ESMF_FieldEmptyCreate(name='mesh_topology', rc=localrc)
_SCHISM_LOG_AND_FINALIZE_ON_ERROR_(rc)
Expand Down Expand Up @@ -364,7 +365,6 @@ subroutine addSchismMesh(comp, rc)
call ESMF_LogWrite(trim(message), ESMF_LOGMSG_INFO)

nullify(farrayPtrI42)
#endif

! clean up
deallocate(nodeids, stat=localrc)
Expand All @@ -376,8 +376,9 @@ subroutine addSchismMesh(comp, rc)
deallocate(elementtypes, stat=localrc)
if (allocated(elementCoords2d)) deallocate(elementCoords2d, stat=localrc)
deallocate(nv, stat=localrc)
! deallocate(LocalNodes, stat=localrc)
! deallocate(schismToLocalNodes, stat=localrc)

write(message, '(A)') trim(compName)//' created 2D mesh"'
call ESMF_LogWrite(trim(message), ESMF_LOGMSG_INFO)

end subroutine addSchismMesh

Expand Down

0 comments on commit 2e7d408

Please sign in to comment.