Skip to content

Commit

Permalink
trigp test branch
Browse files Browse the repository at this point in the history
  • Loading branch information
DeniseWorthen committed Jan 22, 2025
1 parent 64b8442 commit 7244b76
Show file tree
Hide file tree
Showing 3 changed files with 37 additions and 6 deletions.
2 changes: 1 addition & 1 deletion model/src/wav_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -945,7 +945,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
end if

if (dbug_flag > 5) then
call write_meshdecomp(Emesh, 'emesh', rc=rc)
call write_meshdecomp(Emesh, 'emesh', nseal_cpl, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
end if

Expand Down
18 changes: 15 additions & 3 deletions model/src/wav_history_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -114,6 +114,7 @@ subroutine write_history ( timen )
logical :: s_axis = .false., m_axis = .false., p_axis = .false., k_axis = .false.

integer :: lmap(nseal_cpl)
integer :: ltrigp(3,nseal_cpl)

! -------------------------------------------------------------
! create the netcdf file
Expand Down Expand Up @@ -256,14 +257,25 @@ subroutine write_history ( timen )
call handle_err(ierr, 'put time')

if (gtype .eq. ungtype) then
! trigp is global
ltrigp(:,:) = 0
!call init_get_isea(isea, jsea)
!if (lglobal) then
! varloc = var(isea)
!else
!varout(jsea) = varloc*dir(isea)
do jsea = 1,nseal_cpl
call init_get_isea(isea, jsea)
ltrigp(:,jsea) = trigp(:,isea)
print *,'YYY ',jsea,isea,trigp(:,isea)
end do
print *,'XXX ',iaproc,size(trigp,1),size(trigp,2)
ierr = pio_inq_varid(pioid, 'nconn', varid)
call handle_err(ierr, 'inquire variable nconn ')
ierr = pio_put_var(pioid, varid, trigp)
ierr = pio_put_var(pioid, varid, ltrigp)
call handle_err(ierr, 'put trigp')
end if

! TODO: tried init decomp w/ use_int=.true. but getting garbage
! land values....sea values OK
! mapsta is global
lmap(:) = 0
do jsea = 1,nseal_cpl
Expand Down
23 changes: 21 additions & 2 deletions model/src/wav_shr_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -229,30 +229,35 @@ end subroutine diagnose_mesh
!!
!> @author mvertens@ucar.edu, Denise.Worthen@noaa.gov
!> @date 09-12-2022
subroutine write_meshdecomp(EMeshIn, mesh_name, rc)
subroutine write_meshdecomp(EMeshIn, mesh_name, nseal_cpl, rc)

use ESMF , only : ESMF_Mesh, ESMF_DistGrid, ESMF_Field, ESMF_FieldBundle, ESMF_FieldBundleAdd
use ESMF , only : ESMF_DistGridGet, ESMF_FieldBundleCreate, ESMF_FieldCreate, ESMF_FieldBundleGet
use ESMF , only : ESMF_MESHLOC_ELEMENT, ESMF_TYPEKIND_R8, ESMF_TYPEKIND_I4, ESMF_LOGMSG_Info
use ESMF , only : ESMF_FieldBundleWrite, ESMF_FieldBundleDestroy

use w3odatmd , only : iaproc
use w3gdatmd , only : ntri, trigp
use w3parall , only : init_get_isea

! input/output variables
type(ESMF_Mesh) , intent(in) :: EMeshIn
character(len=*), intent(in) :: mesh_name
integer , intent(in) :: nseal_cpl
integer , intent(out) :: rc

! local variables
type(ESMF_FieldBundle) :: FBTemp
type(ESMF_Field) :: lfield
type(ESMF_DistGrid) :: distgrid
type(ESMF_Field) :: doffield
type(ESMF_Field) :: doffield, trifield
character(len=6), dimension(4) :: lfieldlist
integer :: i,ndims,nelements
integer :: isea,jsea
real(r8), pointer :: fldptr1d(:)
integer(i4), allocatable :: dof(:)
integer(i4), pointer :: dofptr(:)
integer(i4), pointer :: itri(:,:)
real(r8), pointer :: ownedElemCoords(:), ownedElemCoords_x(:), ownedElemCoords_y(:)
character(len=*),parameter :: subname = '(wav_shr_mod:write_meshdecomp) '
!-------------------------------------------------------
Expand All @@ -266,6 +271,20 @@ subroutine write_meshdecomp(EMeshIn, mesh_name, rc)

call ESMF_MeshGet(EMeshIn, spatialDim=ndims, numOwnedElements=nelements, elementDistgrid=distgrid, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
if (unstr_mesh) then
trifield = ESMF_FieldCreate(EMeshIn, ESMF_TYPEKIND_I4, name='nconn', meshloc=ESMF_MESHLOC_ELEMENT, &
ungriddedLBound=(/1/), ungriddedUBound=(/size(trigp,1)/), gridToFieldMap=(/2/), rc=rc)
call ESMF_FieldGet(trifield, farrayPtr=itri, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
! retrieve DE local trigp array
itri = 0
do jsea = 1,nseal_cpl
call init_get_isea(isea, jsea)
itri(:,jsea) = trigp(:,isea)
end do
call ESMF_FieldBundleAdd(FBTemp, (/trifield/), rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
end if

lfieldlist = (/'dof ', 'coordx', 'coordy', 'decomp'/)
! index array
Expand Down

0 comments on commit 7244b76

Please sign in to comment.