Skip to content

Commit

Permalink
+Correct units in 1 get_param call and 64 comments
Browse files Browse the repository at this point in the history
  Corrected the units in the get_param call for WAVE_HEIGHT_SCALE_FACTOR, and
corrected the units descriptions in comments of 22 wind stress related variables
in 6 driver routines, from [R L Z T-1 ~> Pa] to [R L Z T-2 ~> Pa], but the
actual conversion factors in the code are correct.  Also fixed 42 other
inconsistent units in comments in 28 files scattered throughout the MOM6 code.
WAVE_HEIGHT_SCALE_FACTOR was added in December 2022 as a part of PR #289 to
dev/gfdl. These inconsistent units were detected because they do not match the
patterns of other valid units; most are recent additions.  Apart from a single
unit in a get_param call, only comments are changed, and all answers are bitwise
identical.
  • Loading branch information
Hallberg-NOAA authored and marshallward committed Mar 1, 2023
1 parent 6dc4de6 commit 00854d0
Show file tree
Hide file tree
Showing 33 changed files with 70 additions and 72 deletions.
4 changes: 2 additions & 2 deletions config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -83,14 +83,14 @@ module MOM_surface_forcing_gfdl
!! type without any further adjustments to drive the ocean dynamics.
!! The actual net mass source may differ due to corrections.

real :: gust_const !< Constant unresolved background gustiness for ustar [R L Z T-1 ~> Pa]
real :: gust_const !< Constant unresolved background gustiness for ustar [R L Z T-2 ~> Pa]
logical :: read_gust_2d !< If true, use a 2-dimensional gustiness supplied from an input file.
real, pointer, dimension(:,:) :: &
TKE_tidal => NULL() !< Turbulent kinetic energy introduced to the bottom boundary layer
!! by drag on the tidal flows [R Z3 T-3 ~> W m-2].
real, pointer, dimension(:,:) :: &
gust => NULL() !< A spatially varying unresolved background gustiness that
!! contributes to ustar [R L Z T-1 ~> Pa]. gust is used when read_gust_2d is true.
!! contributes to ustar [R L Z T-2 ~> Pa]. gust is used when read_gust_2d is true.
real, pointer, dimension(:,:) :: &
ustar_tidal => NULL() !< Tidal contribution to the bottom friction velocity [Z T-1 ~> m s-1]
real :: cd_tides !< Drag coefficient that applies to the tides [nondim]
Expand Down
4 changes: 2 additions & 2 deletions config_src/drivers/mct_cap/mom_surface_forcing_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -76,14 +76,14 @@ module MOM_surface_forcing_mct
!! the correction for the atmospheric (and sea-ice)
!! pressure limited by max_p_surf instead of the
!! full atmospheric pressure. The default is true.
real :: gust_const !< constant unresolved background gustiness for ustar [R L Z T-1 ~> Pa]
real :: gust_const !< constant unresolved background gustiness for ustar [R L Z T-2 ~> Pa]
logical :: read_gust_2d !< If true, use a 2-dimensional gustiness supplied
!! from an input file.
real, pointer, dimension(:,:) :: &
TKE_tidal => NULL(), & !< turbulent kinetic energy introduced to the
!! bottom boundary layer by drag on the tidal flows [R Z3 T-3 ~> W m-2]
gust => NULL(), & !< spatially varying unresolved background
!! gustiness that contributes to ustar [R L Z T-1 ~> Pa].
!! gustiness that contributes to ustar [R L Z T-2 ~> Pa].
!! gust is used when read_gust_2d is true.
ustar_tidal => NULL() !< tidal contribution to the bottom friction velocity [Z T-1 ~> m s-1]
real :: cd_tides !< drag coefficient that applies to the tides (nondimensional)
Expand Down
4 changes: 2 additions & 2 deletions config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -81,14 +81,14 @@ module MOM_surface_forcing_nuopc
logical :: use_CFC !< enables the MOM_CFC_cap tracer package.
logical :: enthalpy_cpl !< Controls if enthalpy terms are provided by the coupler or computed
!! internally.
real :: gust_const !< constant unresolved background gustiness for ustar [R L Z T-1 ~> Pa]
real :: gust_const !< constant unresolved background gustiness for ustar [R L Z T-2 ~> Pa]
logical :: read_gust_2d !< If true, use a 2-dimensional gustiness supplied
!! from an input file.
real, pointer, dimension(:,:) :: &
TKE_tidal => NULL(), & !< turbulent kinetic energy introduced to the
!! bottom boundary layer by drag on the tidal flows [R Z3 T-3 ~> W m-2]
gust => NULL(), & !< spatially varying unresolved background
!! gustiness that contributes to ustar [R L Z T-1 ~> Pa].
!! gustiness that contributes to ustar [R L Z T-2 ~> Pa].
!! gust is used when read_gust_2d is true.
ustar_tidal => NULL() !< tidal contribution to the bottom friction velocity [Z T-1 ~> m s-1]
real :: cd_tides !< drag coefficient that applies to the tides (nondimensional)
Expand Down
2 changes: 1 addition & 1 deletion config_src/drivers/solo_driver/MESO_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ module MESO_surface_forcing
real :: G_Earth !< The gravitational acceleration [L2 Z-1 T-2 ~> m s-2].
real :: Flux_const !< The restoring rate at the surface [Z T-1 ~> m s-1].
real :: gust_const !< A constant unresolved background gustiness
!! that contributes to ustar [R L Z T-1 ~> Pa]
!! that contributes to ustar [R L Z T-2 ~> Pa]
real, dimension(:,:), pointer :: &
T_Restore(:,:) => NULL(), & !< The temperature to restore the SST toward [C ~> degC].
S_Restore(:,:) => NULL(), & !< The salinity to restore the sea surface salnity toward [S ~> ppt]
Expand Down
26 changes: 13 additions & 13 deletions config_src/drivers/solo_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -85,13 +85,13 @@ module MOM_surface_forcing
real :: latent_heat_fusion !< latent heat of fusion times [Q ~> J kg-1]
real :: latent_heat_vapor !< latent heat of vaporization [Q ~> J kg-1]
real :: tau_x0 !< Constant zonal wind stress used in the WIND_CONFIG="const"
!! forcing [R L Z T-1 ~> Pa]
!! forcing [R L Z T-2 ~> Pa]
real :: tau_y0 !< Constant meridional wind stress used in the WIND_CONFIG="const"
!! forcing [R L Z T-1 ~> Pa]
!! forcing [R L Z T-2 ~> Pa]

real :: gust_const !< constant unresolved background gustiness for ustar [R L Z T-1 ~> Pa]
real :: gust_const !< constant unresolved background gustiness for ustar [R L Z T-2 ~> Pa]
logical :: read_gust_2d !< if true, use 2-dimensional gustiness supplied from a file
real, pointer :: gust(:,:) => NULL() !< spatially varying unresolved background gustiness [R L Z T-1 ~> Pa]
real, pointer :: gust(:,:) => NULL() !< spatially varying unresolved background gustiness [R L Z T-2 ~> Pa]
!! gust is used when read_gust_2d is true.

real, pointer :: T_Restore(:,:) => NULL() !< temperature to damp (restore) the SST to [C ~> degC]
Expand All @@ -102,9 +102,9 @@ module MOM_surface_forcing

! if WIND_CONFIG=='gyres' then use the following as = A, B, C and n respectively for
! taux = A + B*sin(n*pi*y/L) + C*cos(n*pi*y/L)
real :: gyres_taux_const !< A constant wind stress [R L Z T-1 ~> Pa].
real :: gyres_taux_sin_amp !< The amplitude of cosine wind stress gyres [R L Z T-1 ~> Pa], if WIND_CONFIG=='gyres'
real :: gyres_taux_cos_amp !< The amplitude of cosine wind stress gyres [R L Z T-1 ~> Pa], if WIND_CONFIG=='gyres'
real :: gyres_taux_const !< A constant wind stress [R L Z T-2 ~> Pa].
real :: gyres_taux_sin_amp !< The amplitude of cosine wind stress gyres [R L Z T-2 ~> Pa], if WIND_CONFIG=='gyres'
real :: gyres_taux_cos_amp !< The amplitude of cosine wind stress gyres [R L Z T-2 ~> Pa], if WIND_CONFIG=='gyres'
real :: gyres_taux_n_pis !< The number of sine lobes in the basin if WIND_CONFIG=='gyres' [nondim]
integer :: answer_date !< This 8-digit integer gives the approximate date with which the order
!! of arithmetic and expressions were added to the code.
Expand All @@ -115,7 +115,7 @@ module MOM_surface_forcing
!! gustless wind friction velocity.
! if WIND_CONFIG=='scurves' then use the following to define a piecewise scurve profile
real :: scurves_ydata(20) = 90. !< Latitudes of scurve nodes [degreesN]
real :: scurves_taux(20) = 0. !< Zonal wind stress values at scurve nodes [R L Z T-1 ~> Pa]
real :: scurves_taux(20) = 0. !< Zonal wind stress values at scurve nodes [R L Z T-2 ~> Pa]

real :: T_north !< Target temperatures at north used in buoyancy_forcing_linear [C ~> degC]
real :: T_south !< Target temperatures at south used in buoyancy_forcing_linear [C ~> degC]
Expand Down Expand Up @@ -392,7 +392,7 @@ subroutine wind_forcing_const(sfc_state, forces, tau_x0, tau_y0, day, G, US, CS)

mag_tau = sqrt( tau_x0**2 + tau_y0**2)

! Set the steady surface wind stresses, in units of [R L Z T-1 ~> Pa].
! Set the steady surface wind stresses, in units of [R L Z T-2 ~> Pa].
do j=js,je ; do I=is-1,Ieq
forces%taux(I,j) = tau_x0
enddo ; enddo
Expand Down Expand Up @@ -438,7 +438,7 @@ subroutine wind_forcing_2gyre(sfc_state, forces, day, G, US, CS)
Pa_to_RLZ_T2 = US%kg_m3_to_R*US%m_s_to_L_T**2*US%L_to_Z
PI = 4.0*atan(1.0)

! Set the steady surface wind stresses, in units of [R L Z T-1 ~> Pa].
! Set the steady surface wind stresses, in units of [R L Z T-2 ~> Pa].
do j=js,je ; do I=is-1,Ieq
forces%taux(I,j) = 0.1 * Pa_to_RLZ_T2 * &
(1.0 - cos(2.0*PI*(G%geoLatCu(I,j)-CS%South_lat) / CS%len_lat))
Expand Down Expand Up @@ -513,7 +513,7 @@ subroutine wind_forcing_gyres(sfc_state, forces, day, G, US, CS)

PI = 4.0*atan(1.0)

! steady surface wind stresses [R L Z T-1 ~> Pa]
! steady surface wind stresses [R L Z T-2 ~> Pa]
do j=js-1,je+1 ; do I=is-1,Ieq
y = (G%geoLatCu(I,j)-CS%South_lat) / CS%len_lat
forces%taux(I,j) = CS%gyres_taux_const + &
Expand Down Expand Up @@ -670,8 +670,8 @@ subroutine wind_forcing_from_file(sfc_state, forces, day, G, US, CS)
!! a previous surface_forcing_init call
! Local variables
character(len=200) :: filename ! The name of the input file.
real :: temp_x(SZI_(G),SZJ_(G)) ! Pseudo-zonal wind stresses at h-points [R L Z T-1 ~> Pa]
real :: temp_y(SZI_(G),SZJ_(G)) ! Pseudo-meridional wind stresses at h-points [R L Z T-1 ~> Pa]
real :: temp_x(SZI_(G),SZJ_(G)) ! Pseudo-zonal wind stresses at h-points [R L Z T-2 ~> Pa]
real :: temp_y(SZI_(G),SZJ_(G)) ! Pseudo-meridional wind stresses at h-points [R L Z T-2 ~> Pa]
real :: Pa_to_RLZ_T2 ! A unit conversion factor from Pa to the internal units
! for wind stresses [R Z L T-2 Pa-1 ~> 1]
integer :: time_lev_daily ! The time levels to read for fields with
Expand Down
6 changes: 3 additions & 3 deletions config_src/drivers/solo_driver/user_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -33,10 +33,10 @@ module user_surface_forcing
logical :: use_temperature !< If true, temperature and salinity are used as state variables.
logical :: restorebuoy !< If true, use restoring surface buoyancy forcing.
real :: Rho0 !< The density used in the Boussinesq approximation [R ~> kg m-3].
real :: G_Earth !< The gravitational acceleration [L2 Z-1 s-2 ~> m s-2].
real :: G_Earth !< The gravitational acceleration [L2 Z-1 T-2 ~> m s-2].
real :: Flux_const !< The restoring rate at the surface [Z T-1 ~> m s-1].
real :: gust_const !< A constant unresolved background gustiness
!! that contributes to ustar [R L Z T-1 ~> Pa].
!! that contributes to ustar [R L Z T-2 ~> Pa].

type(diag_ctrl), pointer :: diag !< A structure that is used to regulate the
!! timing of diagnostic output.
Expand Down Expand Up @@ -71,7 +71,7 @@ subroutine USER_wind_forcing(sfc_state, forces, day, G, US, CS)
! Allocate the forcing arrays, if necessary.
call allocate_mech_forcing(G, forces, stress=.true., ustar=.true.)

! Set the surface wind stresses, in units of [R L Z T-1 ~> Pa]. A positive taux
! Set the surface wind stresses, in units of [R L Z T-2 ~> Pa]. A positive taux
! accelerates the ocean to the (pseudo-)east.

! The i-loop extends to is-1 so that taux can be used later in the
Expand Down
2 changes: 1 addition & 1 deletion config_src/drivers/unit_drivers/MOM_sum_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -183,7 +183,7 @@ subroutine benchmark_init_topog_local(D, G, param_file, max_depth)
real :: PI ! 3.1415926... calculated as 4*atan(1) [nondim]
real :: D0 ! A constant to make the maximum
! basin depth MAXIMUM_DEPTH [m]
real :: m_to_Z ! A dimensional rescaling factor [m ~> Z]
real :: m_to_Z ! A dimensional rescaling factor [Z m-1 ~> 1]
real :: x ! A fractional position in the x-direction [nondim]
real :: y ! A fractional position in the y-direction [nondim]
! This include declares and sets the variable "version".
Expand Down
4 changes: 2 additions & 2 deletions src/ALE/MOM_hybgen_remap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -263,7 +263,7 @@ subroutine hybgen_weno_coefs(s, h_src, edges, nk, ns, thin, PCM_lay)
! real, parameter :: dsmll=1.0e-8 ! This has units of [A2], and hence can not be a parameter.
!
real :: curv_cell ! An estimate of the tracer curvature centered on a cell times the grid
! spacing [A H-1 ~> A m-1 or A kg m-2]
! spacing [A H-1 ~> A m-1 or A m2 kg-1]
real :: seh1, seh2 ! Tracer slopes at the cell edges times the cell grid spacing [A]
real :: q01, q02 ! Various tracer differences between a cell average and the edge values [A]
real :: q001, q002 ! Tracer slopes at the cell edges times the cell grid spacing [A]
Expand All @@ -277,7 +277,7 @@ subroutine hybgen_weno_coefs(s, h_src, edges, nk, ns, thin, PCM_lay)
! concentrations and the left and right edges [A2]
real :: min_ratio ! The minimum ratio of the values of zw used to interpolate the edge values [nondim]
real :: wt1 ! The weight of the upper layer in the interpolated shared edge value [nondim]
real :: slope_edge(nk+1) ! Tracer slopes at the edges [A H-1 ~> A m-1 or A kg m-2]
real :: slope_edge(nk+1) ! Tracer slopes at the edges [A H-1 ~> A m-1 or A m2 kg-1]
real :: val_edge(nk+1) ! A weighted average edge concentration [A]
integer :: i, k

Expand Down
2 changes: 1 addition & 1 deletion src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1976,7 +1976,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
real :: salin_underflow ! A tiny value of salinity below which the it is set to 0 [S ~> ppt]
real :: temp_underflow ! A tiny magnitude of temperatures below which they are set to 0 [C ~> degC]
real :: conv2watt ! A conversion factor from temperature fluxes to heat
! fluxes [J m-2 H-1 degC-1 ~> J m-3 degC-1 or J kg-1 degC-1]
! fluxes [J m-2 H-1 C-1 ~> J m-3 degC-1 or J kg-1 degC-1]
real :: conv2salt ! A conversion factor for salt fluxes [m H-1 ~> 1] or [kg m-2 H-1 ~> 1]
real :: RL2_T2_rescale, Z_rescale, QRZ_rescale ! Unit conversion factors
character(len=48) :: S_flux_units
Expand Down
2 changes: 1 addition & 1 deletion src/core/MOM_continuity_PPM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1044,7 +1044,7 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, LB, OBC, por_fac
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to
!! calculate fluxes [H ~> m or kg m-2]
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: vh !< Volume flux through meridional
!! faces = v*h*dx [H L2 s-1 ~> m3 s-1 or kg s-1]
!! faces = v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]
real, intent(in) :: dt !< Time increment [T ~> s].
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure.G
Expand Down
8 changes: 4 additions & 4 deletions src/core/MOM_forcing_type.F90
Original file line number Diff line number Diff line change
Expand Up @@ -969,7 +969,7 @@ subroutine calculateBuoyancyFlux1d(G, GV, US, fluxes, optics, nsw, h, Temp, Salt
! [H T-1 ~> m s-1 or kg m-2 s-1]
real, dimension(SZI_(G)) :: netHeat ! net temp flux [C H T-1 ~> degC m s-1 or degC kg m-2 s-1]
real, dimension(max(nsw,1), SZI_(G)) :: penSWbnd ! penetrating SW radiation by band
! [degC H T-1 ~> degC m s-1 or degC kg m-2 s-1]
! [C H T-1 ~> degC m s-1 or degC kg m-2 s-1]
real, dimension(SZI_(G)) :: pressure ! pressure at the surface [R L2 T-2 ~> Pa]
real, dimension(SZI_(G)) :: dRhodT ! density partial derivative wrt temp [R C-1 ~> kg m-3 degC-1]
real, dimension(SZI_(G)) :: dRhodS ! density partial derivative wrt saln [R S-1 ~> kg m-3 ppt-1]
Expand All @@ -996,7 +996,7 @@ subroutine calculateBuoyancyFlux1d(G, GV, US, fluxes, optics, nsw, h, Temp, Salt
! The surface forcing is contained in the fluxes type.
! We aggregate the thermodynamic forcing for a time step into the following:
! netH = water added/removed via surface fluxes [H T-1 ~> m s-1 or kg m-2 s-1]
! netHeat = heat via surface fluxes [degC H T-1 ~> degC m s-1 or degC kg m-2 s-1]
! netHeat = heat via surface fluxes [C H T-1 ~> degC m s-1 or degC kg m-2 s-1]
! netSalt = salt via surface fluxes [S H T-1 ~> ppt m s-1 or gSalt m-2 s-1]
! Note that unlike other calls to extractFLuxes1d() that return the time-integrated flux
! this call returns the rate because dt=1 (in arbitrary time units)
Expand All @@ -1015,12 +1015,12 @@ subroutine calculateBuoyancyFlux1d(G, GV, US, fluxes, optics, nsw, h, Temp, Salt
tv%eqn_of_state, EOS_domain(G%HI))

! Adjust netSalt to reflect dilution effect of FW flux
! [ppt H T-1 ~> ppt m s-1 or ppt kg m-2 s-1]
! [S H T-1 ~> ppt m s-1 or ppt kg m-2 s-1]
netSalt(G%isc:G%iec) = netSalt(G%isc:G%iec) - Salt(G%isc:G%iec,j,1) * netH(G%isc:G%iec)

! Add in the SW heating for purposes of calculating the net
! surface buoyancy flux affecting the top layer.
! [degC H T-1 ~> degC m s-1 or degC kg m-2 s-1]
! [C H T-1 ~> degC m s-1 or degC kg m-2 s-1]
!netHeat(:) = netHeatMinusSW(:) + sum( penSWbnd, dim=1 )
netHeat(G%isc:G%iec) = netHeatMinusSW(G%isc:G%iec) + netPen(G%isc:G%iec,1)

Expand Down
2 changes: 1 addition & 1 deletion src/core/MOM_porous_barriers.F90
Original file line number Diff line number Diff line change
Expand Up @@ -285,7 +285,7 @@ subroutine calc_eta_at_uv(eta_u, eta_v, interp, dmask, h, tv, G, GV, US, eta_bt)
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)+1), intent(out) :: eta_v !< Layer interface heights at v points [Z ~> m]

! local variables
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: eta ! Layer interface heights [Z ~> m or 1/eta_to_m].
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: eta ! Layer interface heights [Z ~> m].
real :: h_neglect ! Negligible thicknesses [Z ~> m]
integer :: i, j, k, nk, is, ie, js, je, Isq, Ieq, Jsq, Jeq

Expand Down
2 changes: 1 addition & 1 deletion src/core/MOM_variables.F90
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,7 @@ module MOM_variables
real, dimension(:,:), pointer :: salt_deficit => NULL()
!< The salt needed to maintain the ocean column
!! at a minimum salinity of MIN_SALINITY since the last time
!! that calculate_surface_state was called, [ppt R Z ~> gSalt m-2].
!! that calculate_surface_state was called, [S R Z ~> gSalt m-2].
real, dimension(:,:), pointer :: TempxPmE => NULL()
!< The net inflow of water into the ocean times the
!! temperature at which this inflow occurs since the
Expand Down
4 changes: 2 additions & 2 deletions src/equation_of_state/MOM_EOS.F90
Original file line number Diff line number Diff line change
Expand Up @@ -632,11 +632,11 @@ end subroutine calc_spec_vol_1d

!> Calls the appropriate subroutine to calculate the freezing point for scalar inputs.
subroutine calculate_TFreeze_scalar(S, pressure, T_fr, EOS, pres_scale, scale_from_EOS)
real, intent(in) :: S !< Salinity, [ppt] or [Z ~> ppt] depending on scale_from_EOS
real, intent(in) :: S !< Salinity, [ppt] or [S ~> ppt] depending on scale_from_EOS
real, intent(in) :: pressure !< Pressure, in [Pa] or [R L2 T-2 ~> Pa] depending on
!! pres_scale or scale_from_EOS
real, intent(out) :: T_fr !< Freezing point potential temperature referenced to the
!! surface [degC] or [degC ~> C] depending on scale_from_EOS
!! surface [degC] or [C ~> degC] depending on scale_from_EOS
type(EOS_type), intent(in) :: EOS !< Equation of state structure
real, optional, intent(in) :: pres_scale !< A multiplicative factor to convert pressure
!! into Pa [Pa T2 R-1 L-2 ~> 1].
Expand Down
Loading

0 comments on commit 00854d0

Please sign in to comment.