Skip to content

Commit

Permalink
Note on the argument FLG2D in DEFAULT_META(FLG2D)
Browse files Browse the repository at this point in the history
  • Loading branch information
CarstenHansen committed Jan 16, 2024
1 parent f2494eb commit 6072e83
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 8 deletions.
22 changes: 15 additions & 7 deletions model/src/w3ounf3metamd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -330,7 +330,8 @@ MODULE W3OUNF3METAMD
!> @author Chris Bunney @date 09-Mar-2020
!/ ------------------------------------------------------------------- /
SUBROUTINE INIT_META(FLG2D,VEC)
!/! W3_MFIT! C Hansen note: FLG2D is for the fb_xsmf
! FLG2D is for the fb_xsmf branch.
! See the CHA note on FLG2D in SUBROUTINE DEFAULT_META
!/
!/ +-----------------------------------+
!/ | WAVEWATCH III NOAA/NCEP |
Expand Down Expand Up @@ -470,7 +471,8 @@ SUBROUTINE INIT_META(FLG2D,VEC)

! 3. Set the default values for the OUNF netCDF meta data.
CALL DEFAULT_META(FLG2D)
!/! W3_MFIT! FLG2D is for the fb_xsmf branch
! FLG2D is for the fb_xsmf branch only
! See the CHA note on FLG2D in SUBROUTINE DEFAULT_META

! Set the default coordiante reference system (if applicable)
CALL DEFAULT_CRS_META()
Expand Down Expand Up @@ -2621,7 +2623,13 @@ END FUNCTION META_DEEP_COPY
!> @author Chris Bunney @date 22-Mar-2021
!/ ------------------------------------------------------------------- /
SUBROUTINE DEFAULT_META(FLG2D)
!/! W3_MFIT! FLG2D is for the fb_xsmf branch
! CHA note: FLG2D is for the fb_xsmf branch, only.
! A true value of FLG2D(ISVP,JSVP) lets the vector of the
! wave pseudo-momentum (scaled by multiplication with 2 * ksc)
! be written to netcdf (even if not the full Stokes profile is selected).
! TODO, change this use of FLG2D: Declare a logical in the present module
! to be USEd in ww3_ounf to indicate that the pseudo-momentum is
! defined and should be output to netcdf.wave
!/
!/ +-----------------------------------+
!/ | WAVEWATCH III NOAA/NCEP |
Expand Down Expand Up @@ -2654,10 +2662,12 @@ SUBROUTINE DEFAULT_META(FLG2D)
USE W3IOGOMD, ONLY: W3FLDTOIJ
#endif
#ifdef W3_MFIT
USE W3ODATMD, ONLY: NOEXTR, NGRPP
USE W3ODATMD, ONLY: NOEXTR
#endif
IMPLICIT NONE
!/! MFIT: NGRPP, FLG2D are for the fb_xsmf branch
USE W3ODATMD, ONLY: NGRPP
!
IMPLICIT NONE
LOGICAL, INTENT(IN) :: FLG2D(NOGRP,NGRPP)
TYPE(META_T), POINTER :: META(:)
INTEGER :: IFJ
Expand Down Expand Up @@ -4281,7 +4291,6 @@ SUBROUTINE DEFAULT_META(FLG2D)
#ifdef W3_MFIT
! IFI=10, IFJ=3 (IXMF=10,JXMF=NOEXTR+1=3)
! ISP=1
! IF ( FLG2D(IXMF,JXMF) ) THEN
META => GROUP(IXMF)%FIELD(JXMF)%SUBFIELD(1)%META
! The seven subfields (ISP=1..7) are joined in the netCDF file
META(1)%FSC = 0.001
Expand Down Expand Up @@ -4345,7 +4354,6 @@ SUBROUTINE DEFAULT_META(FLG2D)
META(1)%FSC = 1
META(1)%vmin = -32766
META(1)%vmax = 32766
! END IF ! ( FLG2D(IXMF,JXMF) )
NOGE(10) = NOGE(10)-1 ! Need NOGE(10)-1 for u1, u2 below
#endif
! IFI=10, IFJ=1
Expand Down
4 changes: 3 additions & 1 deletion model/src/ww3_ounf3.F90
Original file line number Diff line number Diff line change
Expand Up @@ -607,6 +607,7 @@ PROGRAM W3OUNF3
END DO
#ifdef W3_MFIT
! Write USVP(1:3) to netCDF if not the Stokes profile is selected
! See the CHA note on FLG2D in SUBROUTINE DEFAULT_META
IF ( FLG2D(10,NOEXTR+1) .AND. .NOT. FLG2D(ISVP,JSVP) ) THEN
SVP=.FALSE.
FLG2D(ISVP,JSVP) = .TRUE.
Expand Down Expand Up @@ -690,7 +691,8 @@ PROGRAM W3OUNF3
!
! 4.4 Initialise meta-data
CALL INIT_META(FLG2D,VECTOR)
!/MFIT! C Hansen note: FLG2D is for the fb_xsmf branch only
! FLG2D is for the fb_xsmf branch only
! See the CHA note on FLG2D in SUBROUTINE DEFAULT_META

! 4.5 Max number of sub-fields or partitions, and netCDF ID register

Expand Down

0 comments on commit 6072e83

Please sign in to comment.