Skip to content

Commit

Permalink
Merge branch 'iulian787/moab_data_rof' into next (PR #6410)
Browse files Browse the repository at this point in the history
Extend moab driver for a case with ROF data

Case tested: --compset GMPAS-IAF --res T62_oQU240wLI

iMOAB_MergeVertices is not used anymore in moab land driver, small correction incorporated into this PR
  • Loading branch information
rljacob committed Jun 18, 2024
2 parents d06e69d + 102b54d commit 27923fa
Show file tree
Hide file tree
Showing 8 changed files with 283 additions and 22 deletions.
185 changes: 183 additions & 2 deletions components/data_comps/drof/src/drof_comp_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,11 @@ module drof_comp_mod
use drof_shr_mod , only: rest_file ! namelist input
use drof_shr_mod , only: rest_file_strm ! namelist input
use drof_shr_mod , only: nullstr

#ifdef HAVE_MOAB
use seq_comm_mct, only : mrofid ! id of moab rof app
use seq_comm_mct, only : mbrof_data ! turn on if the data rof
use iso_c_binding
#endif
!
! !PUBLIC TYPES:
implicit none
Expand Down Expand Up @@ -67,6 +71,12 @@ subroutine drof_comp_init(Eclock, x2r, r2x, &
SDROF, gsmap, ggrid, mpicom, compid, my_task, master_task, &
inst_suffix, inst_name, logunit, read_restart)

#ifdef HAVE_MOAB
use iMOAB, only: iMOAB_DefineTagStorage, iMOAB_GetDoubleTagStorage, &
iMOAB_SetIntTagStorage, iMOAB_SetDoubleTagStorage, &
iMOAB_ResolveSharedEntities, iMOAB_CreateVertices, &
iMOAB_GetMeshInfo, iMOAB_UpdateMeshInfo, iMOAB_WriteMesh
#endif
! !DESCRIPTION: initialize drof model
implicit none

Expand All @@ -92,7 +102,19 @@ subroutine drof_comp_init(Eclock, x2r, r2x, &
logical :: exists ! file existance logical
integer(IN) :: nu ! unit number
character(CL) :: calendar ! model calendar

#ifdef HAVE_MOAB
character*400 tagname
real(R8) latv, lonv
integer iv, tagindex, ilat, ilon, ierr !, arrsize, nfields
real(R8), allocatable, target :: data(:)
integer(IN), pointer :: idata(:) ! temporary
real(r8), dimension(:), allocatable :: moab_vert_coords ! temporary
!real(R8), allocatable, target :: vtags_zero(:, :)

#ifdef MOABDEBUG
character*100 outfile, wopts
#endif
#endif
!--- formats ---
character(*), parameter :: F00 = "('(drof_comp_init) ',8a)"
character(*), parameter :: F0L = "('(drof_comp_init) ',a, l2)"
Expand Down Expand Up @@ -164,6 +186,121 @@ subroutine drof_comp_init(Eclock, x2r, r2x, &

call t_stopf('drof_initmctdom')


#ifdef HAVE_MOAB
ilat = mct_aVect_indexRA(ggrid%data,'lat')
ilon = mct_aVect_indexRA(ggrid%data,'lon')
allocate(moab_vert_coords(lsize*3))
do iv = 1, lsize
lonv = ggrid%data%rAttr(ilon, iv) * SHR_CONST_PI/180.
latv = ggrid%data%rAttr(ilat, iv) * SHR_CONST_PI/180.
moab_vert_coords(3*iv-2)=COS(latv)*COS(lonv)
moab_vert_coords(3*iv-1)=COS(latv)*SIN(lonv)
moab_vert_coords(3*iv )=SIN(latv)
enddo

! create the vertices with coordinates from MCT domain
ierr = iMOAB_CreateVertices(mrofid, lsize*3, 3, moab_vert_coords)
if (ierr .ne. 0) &
call shr_sys_abort('Error: fail to create MOAB vertices in land model')

tagname='GLOBAL_ID'//C_NULL_CHAR
ierr = iMOAB_DefineTagStorage(mrofid, tagname, &
0, & ! dense, integer
1, & ! number of components
tagindex )
if (ierr .ne. 0) &
call shr_sys_abort('Error: fail to retrieve GLOBAL_ID tag ')

! get list of global IDs for Dofs
call mct_gsMap_orderedPoints(gsMap, my_task, idata)

ierr = iMOAB_SetIntTagStorage ( mrofid, tagname, lsize, &
0, & ! vertex type
idata)
if (ierr .ne. 0) &
call shr_sys_abort('Error: fail to set GLOBAL_ID tag ')

ierr = iMOAB_ResolveSharedEntities( mrofid, lsize, idata );
if (ierr .ne. 0) &
call shr_sys_abort('Error: fail to resolve shared entities')

deallocate(moab_vert_coords)
deallocate(idata)

ierr = iMOAB_UpdateMeshInfo( mrofid )
if (ierr .ne. 0) &
call shr_sys_abort('Error: fail to update mesh info ')

allocate(data(lsize))
ierr = iMOAB_DefineTagStorage( mrofid, "area:aream:frac:mask"//C_NULL_CHAR, &
1, & ! dense, double
1, & ! number of components
tagindex )
if (ierr > 0 ) &
call shr_sys_abort('Error: fail to create tag: area:aream:frac:mask' )

data(:) = ggrid%data%rAttr(mct_aVect_indexRA(ggrid%data,'area'),:)
tagname='area'//C_NULL_CHAR
ierr = iMOAB_SetDoubleTagStorage ( mrofid, tagname, lsize, &
0, & ! set data on vertices
data)
if (ierr > 0 ) &
call shr_sys_abort('Error: fail to get area tag ')

! set the same data for aream (model area) as area
! data(:) = ggrid%data%rAttr(mct_aVect_indexRA(ggrid%data,'aream'),:)
tagname='aream'//C_NULL_CHAR
ierr = iMOAB_SetDoubleTagStorage ( mrofid, tagname, lsize, &
0, & ! set data on vertices
data)
if (ierr > 0 ) &
call shr_sys_abort('Error: fail to set aream tag ')

data(:) = ggrid%data%rAttr(mct_aVect_indexRA(ggrid%data,'mask'),:)
tagname='mask'//C_NULL_CHAR
ierr = iMOAB_SetDoubleTagStorage ( mrofid, tagname, lsize, &
0, & ! set data on vertices
data)
if (ierr > 0 ) &
call shr_sys_abort('Error: fail to set mask tag ')

data(:) = ggrid%data%rAttr(mct_aVect_indexRA(ggrid%data,'frac'),:)
tagname='frac'//C_NULL_CHAR
ierr = iMOAB_SetDoubleTagStorage ( mrofid, tagname, lsize, &
0, & ! set data on vertices
data)
if (ierr > 0 ) &
call shr_sys_abort('Error: fail to set frac tag ')

deallocate(data)

! define tags
ierr = iMOAB_DefineTagStorage( mrofid, trim(seq_flds_x2r_fields)//C_NULL_CHAR, &
1, & ! dense, double
1, & ! number of components
tagindex )
if (ierr > 0 ) &
call shr_sys_abort('Error: fail to create seq_flds_x2r_fields tags ')

ierr = iMOAB_DefineTagStorage( mrofid, trim(seq_flds_r2x_fields)//C_NULL_CHAR, &
1, & ! dense, double
1, & ! number of components
tagindex )
if (ierr > 0 ) &
call shr_sys_abort('Error: fail to create seq_flds_r2x_fields tags ')
mbrof_data = .true. ! will have effects
#ifdef MOABDEBUG
! debug test
outfile = 'RofDataMesh.h5m'//C_NULL_CHAR
wopts = ';PARALLEL=WRITE_PART'//C_NULL_CHAR !
! write out the mesh file to disk
ierr = iMOAB_WriteMesh(mrofid, trim(outfile), trim(wopts))
if (ierr .ne. 0) then
call shr_sys_abort(subname//' ERROR in writing data mesh rof ')
endif
#endif
#endif
!----------------------------------------------------------------------------
! Initialize MCT attribute vectors
!----------------------------------------------------------------------------
Expand Down Expand Up @@ -256,6 +393,13 @@ subroutine drof_comp_run(EClock, x2r, r2x, &
SDROF, gsmap, ggrid, mpicom, compid, my_task, master_task, &
inst_suffix, logunit, case_name)

#ifdef MOABDEBUG
use iMOAB, only: iMOAB_WriteMesh
#endif
#ifdef HAVE_MOAB
use seq_flds_mod , only: seq_flds_r2x_fields
use seq_flds_mod , only: moab_set_tag_from_av
#endif
! !DESCRIPTION: run method for drof model
implicit none

Expand Down Expand Up @@ -285,7 +429,18 @@ subroutine drof_comp_run(EClock, x2r, r2x, &
integer(IN) :: nu ! unit number
integer(IN) :: nflds_r2x
character(len=18) :: date_str
#ifdef HAVE_MOAB
real(R8), allocatable, target :: datam(:)
type(mct_list) :: temp_list
integer :: size_list, index_list
type(mct_string) :: mctOStr !
character*400 tagname, mct_field
#ifdef MOABDEBUG
integer :: cur_drof_stepno, ierr
character*100 outfile, wopts, lnum
#endif

#endif
character(*), parameter :: F00 = "('(drof_comp_run) ',8a)"
character(*), parameter :: F04 = "('(drof_comp_run) ',2a,2i8,'s')"
character(*), parameter :: subName = "(drof_comp_run) "
Expand Down Expand Up @@ -384,6 +539,32 @@ subroutine drof_comp_run(EClock, x2r, r2x, &
!----------------------------------------------------------------------------
! Log output for model date
!----------------------------------------------------------------------------
#ifdef HAVE_MOAB
lsize = mct_avect_lsize(r2x) ! is it the same as mct_avect_lsize(avstrm) ?
allocate(datam(lsize)) !
call mct_list_init(temp_list ,seq_flds_r2x_fields)
size_list=mct_list_nitem (temp_list)
do index_list = 1, size_list
call mct_list_get(mctOStr,index_list,temp_list)
mct_field = mct_string_toChar(mctOStr)
tagname= trim(mct_field)//C_NULL_CHAR
call moab_set_tag_from_av(tagname, r2x, index_list, mrofid, datam, lsize) ! loop over all a2x fields, not just a few
enddo
call mct_list_clean(temp_list)
deallocate(datam) ! maybe we should keep it around, deallocate at the final only?

#ifdef MOABDEBUG
call seq_timemgr_EClockGetData( EClock, stepno=cur_drof_stepno )
write(lnum,"(I0.2)")cur_drof_stepno
outfile = 'drof_comp_run_'//trim(lnum)//'.h5m'//C_NULL_CHAR
wopts = 'PARALLEL=WRITE_PART'//C_NULL_CHAR
ierr = iMOAB_WriteMesh(mrofid, outfile, wopts)
if (ierr > 0 ) then
write(logunit,*) 'Failed to write data rof component state '
endif
#endif

#endif

call t_startf('drof_run2')
if (my_task == master_task) then
Expand Down
38 changes: 36 additions & 2 deletions components/data_comps/drof/src/rof_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,11 @@ module rof_comp_mct
use drof_comp_mod , only: drof_comp_init, drof_comp_run, drof_comp_final
use drof_shr_mod , only: drof_shr_read_namelists
use seq_flds_mod , only: seq_flds_x2r_fields, seq_flds_r2x_fields

#ifdef HAVE_MOAB
use seq_comm_mct, only : mrofid ! iMOAB app id for rof
use iso_c_binding
use iMOAB , only: iMOAB_RegisterApplication
#endif
! !PUBLIC TYPES:
implicit none
private ! except
Expand Down Expand Up @@ -53,6 +57,9 @@ module rof_comp_mct
!===============================================================================
subroutine rof_init_mct( EClock, cdata, x2r, r2x, NLFilename )

#ifdef HAVE_MOAB
use shr_stream_mod, only: shr_stream_getDomainInfo, shr_stream_getFile
#endif
! !DESCRIPTION: initialize drof model
implicit none

Expand All @@ -74,6 +81,16 @@ subroutine rof_init_mct( EClock, cdata, x2r, r2x, NLFilename )
integer(IN) :: shrloglev ! original log level
logical :: read_restart ! start from restart
integer(IN) :: ierr ! error code

character(CL) :: filePath ! generic file path
character(CL) :: fileName ! generic file name
character(CS) :: timeName ! domain file: time variable name
character(CS) :: lonName ! domain file: lon variable name
character(CS) :: latName ! domain file: lat variable name
character(CS) :: hgtName ! domain file: hgt variable name
character(CS) :: maskName ! domain file: mask variable name
character(CS) :: areaName ! domain file: area variable name

character(*), parameter :: subName = "(rof_init_mct) "
!-------------------------------------------------------------------------------

Expand Down Expand Up @@ -140,11 +157,28 @@ subroutine rof_init_mct( EClock, cdata, x2r, r2x, NLFilename )
! Initialize drof
!----------------------------------------------------------------------------

#ifdef HAVE_MOAB
ierr = iMOAB_RegisterApplication(trim("DROF")//C_NULL_CHAR, mpicom, compid, mrofid)
if (ierr .ne. 0) then
write(logunit,*) subname,' error in registering data rof comp'
call shr_sys_abort(subname//' ERROR in registering data rof comp')
endif
#endif

call drof_comp_init(Eclock, x2r, r2x, &
seq_flds_x2r_fields, seq_flds_r2x_fields, &
SDROF, gsmap, ggrid, mpicom, compid, my_task, master_task, &
inst_suffix, inst_name, logunit, read_restart)

#ifdef HAVE_MOAB
if (my_task == master_task) then
call shr_stream_getDomainInfo(SDROF%stream(1), filePath,fileName,timeName,lonName, &
latName,hgtName,maskName,areaName)
call shr_stream_getFile(filePath,fileName)
! send path of river domain to MOAB coupler.
call seq_infodata_PutData( infodata, rof_domain=fileName)
write(logunit,*), ' filename: ', filename
endif
#endif
!----------------------------------------------------------------------------
! Fill infodata that needs to be returned from drof
!----------------------------------------------------------------------------
Expand Down
2 changes: 1 addition & 1 deletion components/elm/src/cpl/lnd_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -846,7 +846,7 @@ subroutine init_moab_land(bounds, LNDID)
use spmdmod , only: masterproc
use iMOAB , only: iMOAB_CreateVertices, iMOAB_WriteMesh, iMOAB_RegisterApplication, &
iMOAB_DefineTagStorage, iMOAB_SetIntTagStorage, iMOAB_SetDoubleTagStorage, &
iMOAB_ResolveSharedEntities, iMOAB_CreateElements, iMOAB_MergeVertices, iMOAB_UpdateMeshInfo
iMOAB_ResolveSharedEntities, iMOAB_CreateElements, iMOAB_UpdateMeshInfo

type(bounds_type) , intent(in) :: bounds
integer , intent(in) :: LNDID ! id of the land app
Expand Down
2 changes: 1 addition & 1 deletion driver-moab/main/component_type_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -508,7 +508,7 @@ subroutine compare_mct_av_moab_tag(comp, attrVect, mct_field, appId, tagname, en
difference = sqrt(differenceg)
iamroot = seq_comm_iamroot(CPLID)
if ( iamroot ) then
print * , subname, trim(comp%ntype), ' comp, difference on tag ', trim(tagname), ' = ', difference
print * , subname, trim(comp%ntype), ' on cpl, difference on tag ', trim(tagname), ' = ', difference
!call shr_sys_abort(subname//'differences between mct and moab values')
endif
deallocate(GlobalIds)
Expand Down
Loading

0 comments on commit 27923fa

Please sign in to comment.