Skip to content

Commit

Permalink
add verbose log option
Browse files Browse the repository at this point in the history
* verboselog is true by default, but can be set false by config
* the header text for ww3 logging as it steps through time is now
turned off in w3init and placed into the mesh cap. this allows the
mesh cap to order the logging correctly
  • Loading branch information
DeniseWorthen committed Sep 16, 2024
1 parent 9cb49d1 commit 4674dae
Show file tree
Hide file tree
Showing 6 changed files with 80 additions and 31 deletions.
6 changes: 4 additions & 2 deletions model/src/w3initmd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1440,7 +1440,7 @@ SUBROUTINE W3INIT ( IMOD, IsMulti, FEXT, MDS, MTRACE, ODAT, FLGRD, FLGR2, FLGD,
!
! 7. Write info to log file ----------------------------------------- /
!
IF ( IAPROC .EQ. NAPLOG ) THEN
IF ( IAPROC .EQ. NAPLOG) THEN
!
WRITE (NDSO,970) GNAME
IF ( FLLEV ) WRITE (NDSO,971) 'Prescribed'
Expand Down Expand Up @@ -1527,7 +1527,9 @@ SUBROUTINE W3INIT ( IMOD, IsMulti, FEXT, MDS, MTRACE, ODAT, FLGRD, FLGR2, FLGD,
WRITE (NDSO,990) DTME21
END IF
!
WRITE (NDSO,984)
if (.not. logfile_is_assigned) then
WRITE (NDSO,984)
end if
!
END IF
!
Expand Down
39 changes: 20 additions & 19 deletions model/src/w3odatmd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -558,27 +558,28 @@ 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
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
logical :: logfile_is_assigned = .false. !< @public logical flag for assignment of nds(1) to specified
!! log file in mesh cap
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
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
!/
CONTAINS
!/ ------------------------------------------------------------------- /
Expand Down
7 changes: 4 additions & 3 deletions model/src/w3wavemd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -494,6 +494,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
use wav_restart_mod , only : write_restart
use wav_history_mod , only : write_history
use w3odatmd , only : histwr, rstwr, use_historync, use_restartnc, user_restfname
use w3odatmd , only : verboselog
use w3timemd , only : set_user_timestring
!
#ifdef W3_MPI
Expand Down Expand Up @@ -2312,7 +2313,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
DTG = DTTST / REAL(NT-IT)
END IF
!
IF ( FLACT .AND. IT.NE.NT .AND. IAPROC.EQ.NAPLOG ) THEN
IF ( FLACT .AND. IT.NE.NT .AND. IAPROC.EQ.NAPLOG .and. verboselog) THEN
CALL STME21 ( TIME , IDTIME )
IF ( IDLAST .NE. TIME(1) ) THEN
WRITE (NDSO,900) ITIME, IPASS, IDTIME(01:19), IDACT, OUTID
Expand Down Expand Up @@ -2775,7 +2776,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
!
! 5. Update log file ------------------------------------------------ /
!
IF ( IAPROC.EQ.NAPLOG ) THEN
IF ( IAPROC.EQ.NAPLOG .and. verboselog) THEN
!
CALL STME21 ( TIME , IDTIME )
IF ( FLCUR ) THEN
Expand Down Expand Up @@ -2828,7 +2829,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
WRITE (SCREEN,951) STTIME
END IF

IF ( IAPROC .EQ. NAPLOG ) WRITE (NDSO,902)
IF ( IAPROC .EQ. NAPLOG .and. verboselog) WRITE (NDSO,902)
!
DEALLOCATE(FIELD)
DEALLOCATE(TAUWX, TAUWY)
Expand Down
29 changes: 24 additions & 5 deletions model/src/wav_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module wav_comp_nuopc
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, user_histfname, user_restfname
use w3odatmd , only : runtype, user_histfname, user_restfname, verboselog
use w3odatmd , only : use_historync, use_restartnc, restart_from_binary, logfile_is_assigned
use w3odatmd , only : time_origin, calendar_name, elapsed_secs
use wav_shr_mod , only : casename, multigrid, inst_suffix, inst_index, unstr_mesh
Expand Down Expand Up @@ -375,6 +375,14 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
if (runtimelog) then
call ufs_file_setLogUnit('./log.ww3.timer',nu_timer,runtimelog)
end if

! Determine verbose native WW3 logging
call NUOPC_CompAttributeGet(gcomp, name="verboselog", value=cvalue, isPresent=isPresent, isSet=isSet, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
if (isPresent .and. isSet) verboselog=(trim(cvalue)=="true")
write(logmsg,*) verboselog
call ESMF_LogWrite('WW3_cap: Verbose WW3 native logging is = '//trim(logmsg), ESMF_LOGMSG_INFO)

call advertise_fields(importState, exportState, flds_scalar_name, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

Expand Down Expand Up @@ -422,7 +430,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
use wav_shel_inp , only : set_shel_io
use wav_history_mod , only : wav_history_init
use wav_pio_mod , only : wav_pio_init
use wav_shr_mod , only : diagnose_mesh, write_meshdecomp
use wav_shr_mod , only : diagnose_mesh, write_meshdecomp, wav_loginit
#ifdef W3_PDLIB
use yowNodepool , only : ng
#endif
Expand Down Expand Up @@ -955,12 +963,23 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
end if
#endif
!--------------------------------------------------------------------
! Intialize the list of requested output variables for netCDF output
! Intialize the list of requested output variables for netCDF output.
! This needs to occur after mod_def has been read in w3init since
! some variables are available only if they are defined in the mod_def
!--------------------------------------------------------------------

if (use_historync) then
call wav_history_init(stdout)
end if

!--------------------------------------------------------------------
! Write the header string for WW3 native logging
!--------------------------------------------------------------------

if (root_task) then
if (verboselog) call wav_loginit(stdout)
end if

if (root_task) call ufs_logtimer(nu_timer,time,start_tod,'InitializeRealize time: ',runtimelog,wtime)

if (dbug_flag > 5) call ESMF_LogWrite(trim(subname)//' done', ESMF_LOGMSG_INFO)
Expand Down Expand Up @@ -1136,8 +1155,8 @@ subroutine ModelAdvance(gcomp, rc)
ss = tod - (hh*3600) - (mm*60)
time0(1) = ymd
time0(2) = hh*10000 + mm*100 + ss
if ( root_task ) then
if (dbug_flag > 5)write(nds(1),'(a,3i4,i10)') 'ymd2date currTime wav_comp_nuopc hh,mm,ss,ymd', hh,mm,ss,ymd
if (dbug_flag > 5) then
if ( root_task ) write(nds(1),'(a,3i4,i10)') 'ymd2date currTime wav_comp_nuopc hh,mm,ss,ymd', hh,mm,ss,ymd
end if
if (root_task) call ufs_logtimer(nu_timer,time,tod,'ModelAdvance time since last step: ',runtimelog,wtime)
call ufs_settimer(wtime)
Expand Down
7 changes: 5 additions & 2 deletions model/src/wav_history_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,7 @@ subroutine write_history ( timen )
use w3wdatmd , only : wlv, ice, icef, iceh, berg, ust, ustdir, asf, rhoair
use w3gdatmd , only : e3df, p2msf, us3df, usspf
use w3odatmd , only : noswll
use w3odatmd , only : ndso, iaproc
use w3adatmd , only : dw, ua, ud, as, cx, cy, taua, tauadir
use w3adatmd , only : hs, wlm, t02, t0m1, t01, fp0, thm, ths, thp0, wbt, wnmean
use w3adatmd , only : dtdyn
Expand Down Expand Up @@ -134,6 +135,7 @@ subroutine write_history ( timen )
endif
ierr = pio_createfile(wav_pio_subsystem, pioid, pio_iotype, trim(fname), nmode)
call handle_err(ierr, 'pio_create')
if (iaproc == 1) write(ndso,'(a)')' Writing history file '//trim(fname)

len_s = noswll + 1 ! 0:noswll
len_m = p2msf(3)-p2msf(2) + 1 ! ?
Expand Down Expand Up @@ -641,7 +643,7 @@ end subroutine write_var3d
subroutine wav_history_init(stdout)

use w3gdatmd, only: e3df, p2msf, us3df, usspf
use w3odatmd, only: iaproc, napout, nogrp, ngrpp
use w3odatmd, only: iaproc, nogrp, ngrpp
use w3iogomd, only: fldout
use w3servmd, only: strsplit

Expand Down Expand Up @@ -715,7 +717,7 @@ subroutine wav_history_init(stdout)
end do

! check
if ( iaproc == napout ) then
if ( iaproc == 1 ) then
write(stdout,*)
write(stdout,'(a)')' --------------------------------------------------'
write(stdout,'(a)')' Requested gridded output variables : '
Expand All @@ -727,6 +729,7 @@ subroutine wav_history_init(stdout)
' '//trim(outvars(n)%long_name)
end do
write(stdout,*)
call flush (stdout)
end if

end subroutine wav_history_init
Expand Down
23 changes: 23 additions & 0 deletions model/src/wav_shr_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ module wav_shr_mod
private :: field_getfldptr !< @private obtain a pointer to a field
public :: diagnose_mesh !< @public write out info about mesh
public :: write_meshdecomp !< @public write the mesh decomposition to a file
public :: wav_loginit !< @public write the verbose WW3 log header

interface state_getfldptr
module procedure state_getfldptr_1d
Expand Down Expand Up @@ -1343,6 +1344,28 @@ subroutine ymd2date_long(year,month,day,date)
if (year < 0) date = -date
end subroutine ymd2date_long

!===============================================================================
!> Write the verbose WW3 log header
!!
!! @param[in] stdout the logfile unit on the root task
!!
!> @author Denise.Worthen@noaa.gov
!> @date 09-14-2024

subroutine wav_loginit(stdout)

integer, intent(in) :: stdout

write(stdout,984)
984 format (// &
37x,'| input | output |'/ &
37x,'|-----------------------|------------------|'/ &
2x,' step | pass | date time | b w l c t r i i1 i5 d | g p t r b f c r2 |'/ &
2x,'--------|------|---------------------|-----------------------|------------------|'/ &
2x,'--------+------+---------------------+---------------------------+--------------+')

end subroutine wav_loginit

!===============================================================================
!> Return a logical true if ESMF_LogFoundError detects an error
!!
Expand Down

0 comments on commit 4674dae

Please sign in to comment.