Skip to content

Commit

Permalink
simplify calcef routine
Browse files Browse the repository at this point in the history
* calc ebd as scalar and use it directly as the wav_elevation_spectrum
* changes are b4b compared to the initial implementation of calcef
  • Loading branch information
DeniseWorthen committed Oct 31, 2022
1 parent f84c218 commit 4293329
Show file tree
Hide file tree
Showing 3 changed files with 31 additions and 35 deletions.
13 changes: 10 additions & 3 deletions model/src/wav_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ module wav_comp_nuopc
use wav_import_export , only : advertise_fields, realize_fields
use wav_shr_mod , only : state_diagnose, state_getfldptr, state_fldchk
use wav_shr_mod , only : chkerr, state_setscalar, state_getscalar, alarmInit, ymd2date
use wav_shr_mod , only : wav_coupling_to_cice
use wav_shr_mod , only : wav_coupling_to_cice, nwav_elev_spectrum
use wav_shr_mod , only : merge_import, dbug_flag
use w3odatmd , only : nds, iaproc, napout
use w3odatmd , only : runtype, use_user_histname, user_histfname, use_user_restname, user_restfname
Expand Down Expand Up @@ -81,7 +81,7 @@ module wav_comp_nuopc
integer :: flds_scalar_index_nx = 0 !< the default size of the scalar field nx
integer :: flds_scalar_index_ny = 0 !< the default size of the scalar field ny
logical :: profile_memory = .false. !< default logical to control use of ESMF
!! memory profiling
!! memory profiling

logical :: root_task = .false. !< logical to indicate root task
#ifdef W3_CESMCOUPLED
Expand Down Expand Up @@ -398,7 +398,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
use w3timemd , only : stme21
use w3adatmd , only : w3naux, w3seta
use w3idatmd , only : w3seti, w3ninp
use w3gdatmd , only : nseal, nsea, nx, ny, mapsf, w3nmod, w3setg
use w3gdatmd , only : nk, nseal, nsea, nx, ny, mapsf, w3nmod, w3setg
use w3wdatmd , only : va, time, w3ndat, w3dimw, w3setw
#ifndef W3_CESMCOUPLED
use wminitmd , only : wminit, wminitnml
Expand Down Expand Up @@ -671,6 +671,13 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
print *,'WW3 log written to '//trim(logfile)
end if

if (wav_coupling_to_cice) then
if (nwav_elev_spectrum .gt. nk) then
call ESMF_LogWrite('nwav_elev_spectrum is greater than nk ', ESMF_LOGMSG_INFO)
call ESMF_Finalize(endflag=ESMF_END_ABORT)
end if
end if

!--------------------------------------------------------------------
! Intialize the list of requested output variables for netCDF output
!--------------------------------------------------------------------
Expand Down
49 changes: 18 additions & 31 deletions model/src/wav_import_export.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ module wav_import_export
use wav_shr_mod , only : ymd2date
use wav_shr_mod , only : chkerr
use wav_shr_mod , only : state_diagnose, state_reset, state_getfldptr, state_fldchk
use wav_shr_mod , only : wav_coupling_to_cice, merge_import, dbug_flag, multigrid
use wav_shr_mod , only : wav_coupling_to_cice, nwav_elev_spectrum, merge_import, dbug_flag, multigrid
use constants , only : grav, tpi, dwat

implicit none
Expand All @@ -42,7 +42,7 @@ module wav_import_export
module procedure fillglobal_with_merge_import
end interface FillGlobalInput

type fld_list_type !< @private a structure for the list of fields
type fld_list_type !< @private a structure for the list of fields
character(len=128) :: stdname !< a standard field name
integer :: ungridded_lbound = 0 !< the ungridded dimension lower bound
integer :: ungridded_ubound = 0 !< the ugridded dimension upper bound
Expand All @@ -62,9 +62,6 @@ module wav_import_export
#else
logical :: cesmcoupled = .false. !< logical defining a non-CESM use case (UWM)
#endif

integer, parameter :: nwav_elev_spectrum = 25 !< the size of the wave spectrum exported if coupling
!! waves to cice6
character(*),parameter :: u_FILE_u = & !< a character string for an ESMF log message
__FILE__

Expand Down Expand Up @@ -604,7 +601,7 @@ subroutine export_fields (gcomp, rc)
! Local variables
real(R8) :: fillvalue = 1.0e30_R8 ! special missing value
type(ESMF_State) :: exportState
integer :: n, jsea, isea, ix, iy, lsize, ib
integer :: n, jsea, isea, ix, iy, ib

real(r8), pointer :: z0rlen(:)
real(r8), pointer :: charno(:)
Expand Down Expand Up @@ -753,6 +750,7 @@ subroutine export_fields (gcomp, rc)
if (wav_coupling_to_cice) then
call state_getfldptr(exportState, 'wave_elevation_spectrum', wave_elevation_spectrum, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
! Initialize wave elevation spectrum
wave_elevation_spectrum(:,:) = fillvalue
call CalcEF(va, wave_elevation_spectrum)
end if
Expand Down Expand Up @@ -1286,7 +1284,7 @@ end subroutine CalcRadstr2D
subroutine CalcEF (a, wave_elevation_spectrum)

use constants, only : tpi
use w3gdatmd, only : nth, nk, nseal, e3df, mapsf, mapsta, dden, dsii
use w3gdatmd, only : nth, nk, nseal, mapsf, mapsta, dden, dsii
use w3adatmd, only : nsealm, cg
use w3parall, only : init_get_isea

Expand All @@ -1295,44 +1293,33 @@ subroutine CalcEF (a, wave_elevation_spectrum)
real(r8), pointer :: wave_elevation_spectrum(:,:)

! local variables
real :: ebd(nk,nseal), ab(nseal), efloc(nsealm,e3df(2,1):e3df(3,1))
real :: factor
real :: ab(nseal)
real :: ebd, factor
integer :: ik, ith, isea, jsea, ix, iy

efloc = 0.0
ebd = 0.0
do ik = 1,nk
do ik = 1,nwav_elev_spectrum
ab = 0.0
do ith = 1, nth
do jsea = 1,nseal
ab(jsea) = ab(jsea) + a(ith,ik,jsea)
ab(jsea) = ab(jsea) + a(ith,ik,jsea)
end do
end do

do jsea = 1,nseal
call init_get_isea(isea, jsea)
factor = dden(ik) / cg(ik,isea)
ebd(ik,jsea) = ab(jsea) * factor
ebd(ik,jsea) = ebd(ik,jsea) / dsii(ik)
if (ik .ge. e3df(2,1) .and. ik .le. e3df(3,1)) then
efloc(jsea,ik) = ebd(ik,jsea) * tpi
ix = mapsf(isea,1) ! global ix
iy = mapsf(isea,2) ! global iy
if (mapsta(iy,ix) .eq. 1) then ! active sea point
factor = dden(ik) / cg(ik,isea)
ebd = ab(jsea) * factor
ebd = ebd / dsii(ik)
wave_elevation_spectrum(ik,jsea) = ebd * tpi
else
wave_elevation_spectrum(ik,jsea) = 0.
end if
end do
end do

do jsea=1, nseal
call init_get_isea(isea, jsea)
ix = mapsf(isea,1) ! global ix
iy = mapsf(isea,2) ! global iy
if (mapsta(iy,ix) .eq. 1) then ! active sea point
! if wave_elevation_spectrum is undef - needs ouput flag to be turned on
! wave_elevation_spectrum as 25 variables
wave_elevation_spectrum(1:nwav_elev_spectrum,jsea) = efloc(jsea,1:nwav_elev_spectrum)
else
wave_elevation_spectrum(:,jsea) = 0.
endif
enddo

end subroutine CalcEF

!====================================================================================
Expand Down
4 changes: 3 additions & 1 deletion model/src/wav_shr_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,9 @@ module wav_shr_mod

! used by both CESM and UFS
logical , public :: wav_coupling_to_cice = .false. !< @public flag to specify additional wave export
!! fields for coupling to CICE (TODO: generalize)
!! fields for coupling to CICE (TODO: generalize)
integer, parameter , public :: nwav_elev_spectrum = 25 !< the size of the wave spectrum exported if coupling
!! waves to cice6
integer , public :: dbug_flag = 0 !< @public flag used to produce additional output
character(len=256) , public :: casename = '' !< @public the name pre-prended to an output file

Expand Down

0 comments on commit 4293329

Please sign in to comment.