Skip to content

Commit

Permalink
add optional restart files via nml
Browse files Browse the repository at this point in the history
  • Loading branch information
DeniseWorthen committed Sep 20, 2024
1 parent 4674dae commit 7c43376
Show file tree
Hide file tree
Showing 5 changed files with 163 additions and 48 deletions.
52 changes: 30 additions & 22 deletions model/src/w3odatmd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -558,28 +558,36 @@ MODULE W3ODATMD
LOGICAL, POINTER :: FLFORM, FLCOMB, O6INIT
INTEGER, POINTER :: PTMETH ! C. Bunney; Partitioning method
REAL, POINTER :: PTFCUT ! C. Bunney; Part. 5 freq cut
character(len=8) :: runtype = '' !< @public the run type (startup,branch,continue)
character(len=256) :: initfile = '' !< @public name of wave initial condition file
!! if runtype is startup or branch run, then initfile is used
character(len=512) :: user_histfname = '' !< @public user history filename prefix, timestring
!! YYYY-MM-DD-SSSSS will be appended
character(len=512) :: user_restfname = '' !< @public user restart filename prefix, timestring
!! YYYY-MM-DD-SSSSS will be appended
logical :: histwr = .false. !< @public logical to trigger history write
!! if true => write history file (snapshot)
logical :: rstwr = .false. !< @public logical to trigger restart write
!! if true => write restart
logical :: use_historync = .false. !< @public logical flag to use netCDF for gridded
!! field output
logical :: use_restartnc = .false. !< @public logical flag to read and write netCDF restarts
logical :: restart_from_binary = .false. !< @public logical flag for restarting from binary restart
! when use_restartnc is true
logical :: logfile_is_assigned = .false. !< @public logical flag for assignment of nds(1) to specified
!! log file in mesh cap
logical :: verboselog = .true. !< @public logical flag to enable verbose WW3 native logging
character(len= 36) :: time_origin = '' !< @public the time_origin used for netCDF output
character(len= 36) :: calendar_name = '' !< @public the calendar used for netCDF output
integer(kind=8) :: elapsed_secs = 0 !< @public the time in seconds from the time_origin

character(len=8) :: runtype = '' !< @public the run type (startup,branch,continue)
character(len=256) :: initfile = '' !< @public name of wave initial condition file
!! if runtype is startup or branch run, then initfile is used
character(len=512) :: user_histfname = '' !< @public user history filename prefix, timestring
!! YYYY-MM-DD-SSSSS will be appended
character(len=512) :: user_restfname = '' !< @public user restart filename prefix, timestring
!! YYYY-MM-DD-SSSSS will be appended
logical :: histwr = .false. !< @public logical to trigger history write
!! if true => write history file (snapshot)
logical :: rstwr = .false. !< @public logical to trigger restart write
!! if true => write restart
logical :: use_historync = .false. !< @public logical flag to use netCDF for gridded
!! field output
logical :: use_restartnc = .false. !< @public logical flag to read and write netCDF restarts
logical :: restart_from_binary = .false. !< @public logical flag for restarting from binary restart
! when use_restartnc is true
logical :: logfile_is_assigned = .false. !< @public logical flag for assignment of nds(1) to specified
!! log file in mesh cap
logical :: verboselog = .true. !< @public logical flag to enable verbose WW3 native logging
logical :: addrstflds = .false. !< @public logical flag for additional restart fields
integer :: rstfldcnt = 0 !< @public the actual number of additional restart fields
character(len=10), dimension(10) :: rstfldlist = '' !< @public a list of additional fields for the restart file,
!! currently set to a maximum of 10. Additional restart fields
!! are required only when waves are in the slow loop and ice
!! is present. Note that waves should not be in the slow loop
!! if coupling to CICE is set
character(len=36) :: time_origin = '' !< @public the time_origin used for netCDF output
character(len=36) :: calendar_name = '' !< @public the calendar used for netCDF output
integer(kind=8) :: elapsed_secs = 0 !< @public the time in seconds from the time_origin
!/
CONTAINS
!/ ------------------------------------------------------------------- /
Expand Down
40 changes: 32 additions & 8 deletions model/src/wav_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -221,6 +221,7 @@ end subroutine InitializeP0
subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)

use wav_shr_flags, only : w3_pdlib_flag

! input/output arguments
type(ESMF_GridComp) :: gcomp
type(ESMF_State) :: importState, exportState
Expand Down Expand Up @@ -582,6 +583,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
if ( root_task ) then
write(stdout,'(a)')' *** WAVEWATCH III Program shell *** '
write(stdout,'(a)')'==============================================='
write(stdout,'(/)')
write(stdout,'(a,l)')' Wave wav_coupling_to_cice setting is ',wav_coupling_to_cice
end if

Expand All @@ -599,7 +601,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
runtype = "branch"
end if
if ( root_task ) then
write(stdout,'(a)') 'WW3 runtype is '//trim(runtype)
write(stdout,'(a)') ' WW3 runtype is '//trim(runtype)
end if
call ESMF_LogWrite('WW3 runtype is '//trim(runtype), ESMF_LOGMSG_INFO)

Expand Down Expand Up @@ -674,7 +676,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
call stme21 ( time0 , dtme21 )
if ( root_task ) then
write (stdout,'(a)')' Starting time : '//trim(dtme21)
write (stdout,'(a,i8,2x,i8)') 'start_ymd, stop_ymd = ',start_ymd, stop_ymd
write (stdout,'(a,i8,2x,i8)') ' start_ymd, stop_ymd = ',start_ymd, stop_ymd
end if
#ifndef W3_CESMCOUPLED
stime = time0
Expand Down Expand Up @@ -1672,9 +1674,10 @@ subroutine waveinit_ufs( gcomp, stdout, ntrace, mpi_comm, mds, rc)

! Initialize ww3 for ufs (called from InitializeRealize)

use w3odatmd , only : fnmpre
use w3odatmd , only : fnmpre, addrstflds, rstfldlist, rstfldcnt
use w3gdatmd , only : dtcfl, dtcfli, dtmax, dtmin
use w3initmd , only : w3init
use w3servmd , only : strsplit
use w3timemd , only : set_user_timestring
use wav_shel_inp , only : read_shel_config
use wav_shel_inp , only : npts, odat, iprt, x, y, pnames, prtfrm
Expand All @@ -1689,9 +1692,13 @@ subroutine waveinit_ufs( gcomp, stdout, ntrace, mpi_comm, mds, rc)
integer, intent(out) :: rc

! local variables
logical :: isPresent, isSet
character(len=CL) :: cvalue
integer :: dt_in(4)
logical :: isPresent, isSet
character(len=CL) :: cvalue
character(len=CL) :: logmsg
character(len=CL) :: fldrst = ''
character(len=100) :: tmplist(100) = ''
integer :: dt_in(4)
integer :: i, cnt
character(len=*), parameter :: subname = '(wav_comp_nuopc:wavinit_ufs)'
! -------------------------------------------------------------------

Expand All @@ -1700,7 +1707,7 @@ subroutine waveinit_ufs( gcomp, stdout, ntrace, mpi_comm, mds, rc)

fnmpre = './'
if (root_task) write(stdout,'(a)') trim(subname)//' call read_shel_config'
call read_shel_config(mpi_comm, mds, time0_overwrite=time0, timen_overwrite=timen)
call read_shel_config(mpi_comm, mds, time0_overwrite=time0, timen_overwrite=timen, rstfldlist=fldrst)

call ESMF_LogWrite(trim(subname)//' call w3init', ESMF_LOGMSG_INFO)
call w3init ( 1, .false., 'ww3', mds, ntrace, odat, flgrd, flgr2, flgd, flg2, &
Expand All @@ -1720,10 +1727,27 @@ subroutine waveinit_ufs( gcomp, stdout, ntrace, mpi_comm, mds, rc)
dtcfli = real(dt_in(3),4)
dtmin = real(dt_in(4),4)
end if
!TODO: why doesn't this line get written?
write(cvalue,'(4f10.1)')dtmax,dtcfl,dtcfli,dtmin
if (root_task) write(stdout,'(a)') trim(subname)//': WW3 timesteps '//trim(cvalue)

! Define any additional restart fields
if(len_trim(fldrst) > 0) then
addrstflds = .true.
call strsplit(fldrst, tmplist)

do i = 1,size(rstfldlist)
rstfldlist(i) = trim(tmplist(i))
if (len_trim(rstfldlist(i)) > 0) rstfldcnt = rstfldcnt + 1
end do
if (root_task) then
do i = 1,rstfldcnt
write(stdout,'(a,i3,a)') trim(subname)//': WW3 additional restart field : ',i,' '//trim(rstfldlist(i))
end do
end if
else
if (root_task) write(stdout,'(/,a)') trim(subname)//': WW3 NO additional restart fields will be written '
end if

if (dbug_flag > 5) call ESMF_LogWrite(trim(subname)//' done', ESMF_LOGMSG_INFO)
end subroutine waveinit_ufs

Expand Down
2 changes: 1 addition & 1 deletion model/src/wav_history_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -334,7 +334,7 @@ subroutine write_history ( timen )
if (vname .eq. 'AS') call write_var2d(vname, as (1:nsea), init0='false', global='true')
if (vname .eq. 'WLV') call write_var2d(vname, wlv (1:nsea), init0='false', global='true')
if (vname .eq. 'ICE') call write_var2d(vname, ice (1:nsea), init0='false', global='true')
if (vname .eq. 'BERG') call write_var2d(vname, berg (1:nsea), init0='false', global='true')
if (vname .eq. 'IBG') call write_var2d(vname, berg (1:nsea), init0='false', global='true')
if (vname .eq. 'TAUX') call write_var2d(vname, taua (1:nsea), dir=cos(tauadir(1:nsea)), init0='false', global='true')
if (vname .eq. 'TAUY') call write_var2d(vname, taua (1:nsea), dir=sin(tauadir(1:nsea)), init0='false', global='true')
if (vname .eq. 'RHOAIR') call write_var2d(vname, rhoair (1:nsea), init0='false', global='true')
Expand Down
100 changes: 88 additions & 12 deletions model/src/wav_restart_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,8 @@ module wav_restart_mod
use w3parall , only : init_get_isea
use w3adatmd , only : nsealm
use w3gdatmd , only : nth, nk, nx, ny, mapsf, nspec, nseal, nsea
use w3odatmd , only : ndso, iaproc
use w3odatmd , only : ndso, iaproc, addrstflds, rstfldlist, rstfldcnt
use w3wdatmd , only : ice
use wav_pio_mod , only : pio_iotype, pio_ioformat, wav_pio_subsystem
use wav_pio_mod , only : handle_err, wav_pio_initdecomp
#ifdef W3_PDLIB
Expand All @@ -25,6 +26,7 @@ module wav_restart_mod
type(file_desc_t) :: pioid
type(var_desc_t) :: varid
type(io_desc_t) :: iodesc2dint
type(io_desc_t) :: iodesc2d
type(io_desc_t) :: iodesc3dk

integer(kind=Pio_Offset_Kind) :: frame
Expand All @@ -34,7 +36,7 @@ module wav_restart_mod

! used/reused in module
character(len=12) :: vname
integer :: ik, ith, ix, iy, kk, nseal_cpl, isea, jsea, ierr
integer :: ik, ith, ix, iy, kk, nseal_cpl, isea, jsea, ierr, i

!===============================================================================
contains
Expand Down Expand Up @@ -64,6 +66,7 @@ subroutine write_restart (fname, va, mapsta)
integer :: dimid(4)
real , allocatable :: lva(:,:)
integer, allocatable :: lmap(:)
real , allocatable :: lvar(:)
!-------------------------------------------------------------------------------

#ifdef W3_PDLIB
Expand All @@ -73,6 +76,7 @@ subroutine write_restart (fname, va, mapsta)
#endif
allocate(lmap(1:nseal_cpl))
allocate(lva(1:nseal_cpl,1:nspec))
allocate(lvar(1:nseal_cpl))

! create the netcdf file
frame = 1
Expand Down Expand Up @@ -112,12 +116,23 @@ subroutine write_restart (fname, va, mapsta)
ierr = pio_put_att(pioid, varid, '_FillValue', nf90_fill_int)
call handle_err(ierr, 'define _FillValue '//trim(vname))

! define any requested additional fields
if (addrstflds) then
do i = 1,rstfldcnt
vname = trim(rstfldlist(i))
ierr = pio_def_var(pioid, trim(vname), PIO_REAL, (/xtid, ytid, timid/), varid)
call handle_err(ierr, 'define variable '//trim(vname))
ierr = pio_put_att(pioid, varid, '_FillValue', nf90_fill_float)
call handle_err(ierr, 'define _FillValue '//trim(vname))
end do
end if
! end variable definitions
ierr = pio_enddef(pioid)
call handle_err(ierr, 'end variable definition')

! initialize the decomp
call wav_pio_initdecomp(iodesc2dint, use_int=.true.)
if (addrstflds) call wav_pio_initdecomp(iodesc2d)
call wav_pio_initdecomp(nspec, iodesc3dk)

! write the time
Expand Down Expand Up @@ -162,7 +177,30 @@ subroutine write_restart (fname, va, mapsta)
call pio_write_darray(pioid, varid, iodesc3dk, lva, ierr)
call handle_err(ierr, 'put variable '//trim(vname))

! write requested additional fields
if (addrstflds) then
do i = 1,rstfldcnt
vname = trim(rstfldlist(i))
! TODO: make generic routine (in=ice, out=lvar)
if (vname == 'ice') then
lvar(:) = 0.0
do jsea = 1,nseal_cpl
call init_get_isea(isea, jsea)
lvar(jsea) = ice(isea)
end do
end if

! write PE local field
ierr = pio_inq_varid(pioid, trim(vname), varid)
call handle_err(ierr, 'inquire variable '//trim(vname))
call pio_setframe(pioid, varid, int(1,kind=Pio_Offset_Kind))
call pio_write_darray(pioid, varid, iodesc2d, lvar, ierr)
call handle_err(ierr, 'put variable '//trim(vname))
end do
end if

call pio_syncfile(pioid)
if (addrstflds) call pio_freedecomp(pioid, iodesc2d)
call pio_freedecomp(pioid, iodesc2dint)
call pio_freedecomp(pioid, iodesc3dk)
call pio_closefile(pioid)
Expand All @@ -183,11 +221,11 @@ end subroutine write_restart
!> author DeniseWorthen@noaa.gov
!> @date 08-26-2024
subroutine read_restart (fname, va, mapsta, mapst2)
!subroutine read_restart (fname, va, mapsta)

use mpi_f08
use w3adatmd , only : mpi_comm_wave
use w3gdatmd , only : sig
use w3wdatmd , only : time, tlev, tice, trho, tic1, tic5, wlv, asf, ice, fpis
use w3wdatmd , only : time, tlev, tice, trho, tic1, tic5, wlv, asf, fpis

character(len=*) , intent(in) :: fname
real , optional , intent(out) :: va(1:nspec,0:nsealm)
Expand All @@ -196,10 +234,11 @@ subroutine read_restart (fname, va, mapsta, mapst2)

! local variables
type(MPI_Comm) :: wave_communicator ! needed for mpi_f08
integer :: global_input(nsea), global_output(nsea)
real :: global_input(nsea), global_output(nsea)
integer :: ifill
real :: rfill
real , allocatable :: lva(:,:)
real , allocatable :: lvar(:)
integer, allocatable :: lmap(:)
integer, allocatable :: lmap2d(:,:)
integer, allocatable :: st2init(:,:)
Expand Down Expand Up @@ -233,10 +272,12 @@ subroutine read_restart (fname, va, mapsta, mapst2)
nseal_cpl = nseal
#endif
allocate(lva(1:nseal_cpl,1:nspec))
allocate(lvar(1:nseal_cpl))
allocate(lmap2d(1:ny,1:nx))
allocate(st2init(1:ny,1:nx))
allocate(lmap(1:nseal_cpl))
lva(:,:) = 0.0
lvar(:) = 0.0
lmap2d(:,:) = 0
lmap(:) = 0
! save a copy of initial mapst2 from mod_def
Expand All @@ -255,6 +296,7 @@ subroutine read_restart (fname, va, mapsta, mapst2)

! initialize the decomp
call wav_pio_initdecomp(iodesc2dint, use_int=.true.)
if (addrstflds) call wav_pio_initdecomp(iodesc2d)
call wav_pio_initdecomp(nspec, iodesc3dk)

vname = 'va'
Expand Down Expand Up @@ -289,31 +331,65 @@ subroutine read_restart (fname, va, mapsta, mapst2)
call handle_err(ierr, 'get variable _FillValue'//trim(vname))

! fill global array with PE local values
global_input = 0
global_output = 0
global_input = 0.0
global_output = 0.0
do jsea = 1,nseal_cpl
call init_get_isea(isea, jsea)
ix = mapsf(isea,1)
iy = mapsf(isea,2)
if (lmap(jsea) .ne. ifill) then
global_input(isea) = lmap(jsea)
global_input(isea) = real(lmap(jsea))
end if
end do
! reduce across all PEs to create global array
call MPI_AllReduce(global_input, global_output, nsea, MPI_INTEGER, MPI_SUM, wave_communicator, ierr)
call MPI_AllReduce(global_input, global_output, nsea, MPI_REAL, MPI_SUM, wave_communicator, ierr)

! fill global array on each PE
lmap2d = 0
do isea = 1,nsea
ix = mapsf(isea,1)
iy = mapsf(isea,2)
lmap2d(iy,ix) = global_output(isea)
lmap2d(iy,ix) = int(global_output(isea))
end do

mapsta = mod(lmap2d+2,8) - 2
mapst2 = st2init + (lmap2d-mapsta)/8

! read additional restart fields
if (addrstflds) then
do i = 1,rstfldcnt
vname = trim(rstfldlist(i))
ierr = pio_inq_varid(pioid, trim(vname), varid)
call handle_err(ierr, 'inquire variable '//trim(vname))
call pio_setframe(pioid, varid, frame)
call pio_read_darray(pioid, varid, iodesc2d, lvar, ierr)
call handle_err(ierr, 'get variable '//trim(vname))
ierr = pio_get_att(pioid, varid, "_FillValue", rfill)
call handle_err(ierr, 'get variable _FillValue'//trim(vname))

! fill global array with PE local values
global_input = 0.0
global_output = 0.0
do jsea = 1,nseal_cpl
call init_get_isea(isea, jsea)
if (lvar(jsea) .ne. rfill) then
global_input(isea) = lvar(jsea)
end if
end do
! reduce across all PEs to create global array
call MPI_AllReduce(global_input, global_output, nsea, MPI_REAL, MPI_SUM, wave_communicator, ierr)

if (vname == 'ice') then
! fill global array on each PE
! TODO : make generic routine (in=global_ouput, out=ice)
ice = 0.0
do isea = 1,nsea
ice(isea) = global_output(isea)
end do
end if
end do
end if

call pio_syncfile(pioid)
if (addrstflds) call pio_freedecomp(pioid, iodesc2d)
call pio_freedecomp(pioid, iodesc2dint)
call pio_freedecomp(pioid, iodesc3dk)
call pio_closefile(pioid)
Expand Down
Loading

0 comments on commit 7c43376

Please sign in to comment.