Skip to content

Commit 0983abb

Browse files
committed
fix issue with standalone ww3 run
1 parent 2de430d commit 0983abb

File tree

7 files changed

+17
-16
lines changed

7 files changed

+17
-16
lines changed

model/src/w3adatmd.F90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -940,7 +940,7 @@ SUBROUTINE W3DIMA ( IMOD, NDSE, NDST, D_ONLY )
940940
#ifdef W3_S
941941
USE W3SERVMD, ONLY: STRACE
942942
#endif
943-
use w3odatmd, only : use_cmeps
943+
use w3odatmd, only : use_cmeps, standalone
944944
!
945945
!/
946946
!/ ------------------------------------------------------------------- /
@@ -1343,7 +1343,7 @@ SUBROUTINE W3DIMA ( IMOD, NDSE, NDST, D_ONLY )
13431343
ALLOCATE (WADATS(IMOD)%IC3CG(0:NK+1,0:300), STAT=ISTAT )
13441344
CHECK_ALLOC_STATUS ( ISTAT )
13451345
#endif
1346-
if (use_cmeps) then
1346+
if (.not. standalone .and. use_cmeps) then
13471347
allocsize = 1
13481348
else
13491349
allocsize = nsea

model/src/w3idatmd.F90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -507,7 +507,7 @@ SUBROUTINE W3DIMI ( IMOD, NDSE, NDST, FLAGSTIDEIN )
507507
#ifdef W3_S
508508
USE W3SERVMD, ONLY: STRACE
509509
#endif
510-
use w3odatmd, only : use_cmeps
510+
use w3odatmd, only : use_cmeps, standalone
511511
!
512512
IMPLICIT NONE
513513
!/
@@ -633,7 +633,7 @@ SUBROUTINE W3DIMI ( IMOD, NDSE, NDST, FLAGSTIDEIN )
633633
CHECK_ALLOC_STATUS ( ISTAT )
634634
END IF
635635
!
636-
if (use_cmeps) then
636+
if (.not. standalone .and. use_cmeps) then
637637
allocsizex = 1
638638
allocsizey = 1
639639
else

model/src/w3odatmd.F90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -595,6 +595,7 @@ MODULE W3ODATMD
595595
character(len=36) :: calendar_name = '' !< @public the calendar used for netCDF output
596596
integer(kind=8) :: elapsed_secs = 0 !< @public the time in seconds from the time_origin
597597
logical :: use_cmeps = .false. !< @public a logical flag to indicate cmeps is providing the forcing
598+
logical :: standalone = .false. !< @public logical to control whether wave model is run standalone
598599
!/
599600
CONTAINS
600601
!/ ------------------------------------------------------------------- /

model/src/w3updtmd.F90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -150,7 +150,7 @@ MODULE W3UPDTMD
150150
USE W3SERVMD, ONLY : STRACE
151151
#endif
152152
USE W3TIMEMD, ONLY : DSEC21
153-
use w3odatmd, only : use_cmeps
153+
use w3odatmd, only : use_cmeps, standalone
154154
! used/reused in module
155155
real :: mag, dir
156156
!/
@@ -292,7 +292,7 @@ SUBROUTINE W3UCUR ( FLFRST )
292292
#ifdef W3_S
293293
CALL STRACE (IENT, 'W3UCUR')
294294
#endif
295-
if (use_cmeps) then
295+
if (.not. standalone .and. use_cmeps) then
296296
do isea = 1,nsea
297297
ix = mapsf(isea,1)
298298
iy = mapsf(isea,2)
@@ -475,7 +475,7 @@ SUBROUTINE W3UCUR ( FLFRST )
475475
#endif
476476
!
477477
END DO
478-
end if ! use_cmeps
478+
end if ! use_cmeps & standalone
479479
!
480480
RETURN
481481
!

model/src/wav_comp_nuopc.F90

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ module wav_comp_nuopc
4747
use w3odatmd , only : runtype, user_histfname, user_restfname, verboselog
4848
use w3odatmd , only : use_historync, use_restartnc, restart_from_binary, logfile_is_assigned
4949
use w3odatmd , only : time_origin, calendar_name, elapsed_secs
50-
use wav_shr_mod , only : casename, inst_suffix, inst_index, unstr_mesh, standalone
50+
use wav_shr_mod , only : casename, inst_suffix, inst_index, unstr_mesh
5151
use wav_wrapper_mod , only : ufs_settimer, ufs_logtimer, ufs_file_setlogunit, wtime
5252
#ifndef W3_CESMCOUPLED
5353
use shr_is_restart_fh_mod , only : init_is_restart_fh, is_restart_fh, is_restart_fh_type
@@ -214,7 +214,7 @@ end subroutine InitializeP0
214214
!> @date 01-05-2022
215215
subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
216216

217-
use w3odatmd , only : use_cmeps
217+
use w3odatmd , only : use_cmeps, standalone
218218
use w3adatmd , only : w3naux, w3seta
219219
use w3idatmd , only : w3seti, w3ninp
220220
use w3gdatmd , only : w3nmod, w3setg
@@ -268,7 +268,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
268268
call ESMF_LogWrite(trim(subname)//' called', ESMF_LOGMSG_INFO)
269269

270270
! if we're here, then cmeps is active
271-
use_cmeps = .true.
271+
if (.not. standalone) use_cmeps = .true.
272272

273273
!----------------------------------------------------------------------------
274274
! retrieve configuration settings
@@ -952,6 +952,7 @@ subroutine DataInitialize(gcomp, rc)
952952

953953
use wav_import_export, only : calcRoughl
954954
use w3gdatmd , only : nx, ny
955+
use w3odatmd , only : standalone
955956

956957
! input/output variables
957958
type(ESMF_GridComp) :: gcomp
@@ -1016,7 +1017,7 @@ subroutine DataInitialize(gcomp, rc)
10161017
if (ChkErr(rc,__LINE__,u_FILE_u)) return
10171018
end if
10181019

1019-
if ( dbug_flag > 5) then
1020+
if (.not. standalone .and. dbug_flag > 5) then
10201021
call state_diagnose(exportState, 'at DataInitialize ', rc=rc)
10211022
if (ChkErr(rc,__LINE__,u_FILE_u)) return
10221023
end if

model/src/wav_import_export.F90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ module wav_import_export
2020
use wav_shr_mod , only : chkerr
2121
use wav_shr_mod , only : state_diagnose, state_reset, state_getfldptr, state_fldchk
2222
use wav_shr_mod , only : wav_coupling_to_cice, nwav_elev_spectrum, merge_import, dbug_flag, unstr_mesh
23-
use wav_shr_mod , only : standalone
23+
use w3odatmd , only : standalone
2424
use constants , only : grav, tpi, dwat, dair
2525
use w3parall , only : init_get_isea
2626

@@ -244,7 +244,7 @@ subroutine realize_fields(gcomp, mesh, flds_scalar_name, flds_scalar_num, rc)
244244
call state_reset(ImportState, zero, rc=rc)
245245
if (ChkErr(rc,__LINE__,u_FILE_u)) return
246246

247-
if (dbug_flag > 5) then
247+
if (.not. standalone .and. dbug_flag > 5) then
248248
call state_diagnose(exportState, 'after state_reset', rc=rc)
249249
if (ChkErr(rc,__LINE__,u_FILE_u)) return
250250
end if
@@ -320,7 +320,7 @@ subroutine import_fields( gcomp, time0, timen, rc )
320320
call ESMF_GridCompGet(gcomp, clock=clock, importState=importState, vm=vm, rc=rc)
321321
if (ChkErr(rc,__LINE__,u_FILE_u)) return
322322

323-
if (dbug_flag > 5) then
323+
if (.not. standalone .and. dbug_flag > 5) then
324324
call state_diagnose(importState, 'at import ', rc=rc)
325325
if (ChkErr(rc,__LINE__,u_FILE_u)) return
326326
end if
@@ -867,7 +867,7 @@ subroutine export_fields (gcomp, rc)
867867
enddo
868868
end if
869869

870-
if (dbug_flag > 5) then
870+
if (.not. standalone .and. dbug_flag > 5) then
871871
call state_diagnose(exportState, 'at export ', rc=rc)
872872
if (ChkErr(rc,__LINE__,u_FILE_u)) return
873873
end if

model/src/wav_shr_mod.F90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,6 @@ module wav_shr_mod
7474

7575
! Only used by ufs
7676
logical , public :: merge_import = .false. !< @public logical to specify whether import fields will
77-
logical , public :: standalone = .false. !< @public logical to control whether wave model is run
7877
interface ymd2date
7978
module procedure ymd2date_int
8079
module procedure ymd2date_long

0 commit comments

Comments
 (0)