Skip to content

Commit

Permalink
Corrected the units of 124 variables
Browse files Browse the repository at this point in the history
  Corrected the units in comments describing 124 variables in 39 files.  In
addition three unused variables were eliminated.  All answers and output are
bitwise identical.
  • Loading branch information
Hallberg-NOAA authored and marshallward committed Nov 19, 2021
1 parent d7b2e32 commit e2e5787
Show file tree
Hide file tree
Showing 39 changed files with 164 additions and 154 deletions.
26 changes: 13 additions & 13 deletions src/ALE/MOM_ALE.F90
Original file line number Diff line number Diff line change
Expand Up @@ -293,7 +293,7 @@ subroutine adjustGridForIntegrity( CS, G, GV, h )
type(ocean_grid_type), intent(in) :: G !< Ocean grid informations
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid thickness that
!! are to be adjusted [H ~> m or kg-2]
!! are to be adjusted [H ~> m or kg m-2]
call inflate_vanished_layers_old( CS%regridCS, G, GV, h(:,:,:) )

end subroutine adjustGridForIntegrity
Expand Down Expand Up @@ -334,7 +334,7 @@ subroutine ALE_main( G, GV, US, h, u, v, tv, Reg, CS, OBC, dt, frac_shelf_h)
! Local variables
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: dzRegrid ! The change in grid interface positions
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: eta_preale
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_new ! New 3D grid obtained after last time step [H ~> m or kg-2]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_new ! New 3D grid obtained after last time step [H ~> m or kg m-2]
integer :: nk, i, j, k, isc, iec, jsc, jec
logical :: ice_shelf

Expand Down Expand Up @@ -405,15 +405,15 @@ subroutine ALE_main_offline( G, GV, h, tv, Reg, CS, OBC, dt)
type(ocean_grid_type), intent(in) :: G !< Ocean grid informations
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the
!! last time step [H ~> m or kg-2]
!! last time step [H ~> m or kg m-2]
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamic variable structure
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
type(ALE_CS), pointer :: CS !< Regridding parameters and options
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
real, optional, intent(in) :: dt !< Time step between calls to ALE_main [T ~> s]
! Local variables
real, dimension(SZI_(G), SZJ_(G), SZK_(GV)+1) :: dzRegrid ! The change in grid interface positions
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_new ! New 3D grid obtained after last time step [H ~> m or kg-2]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_new ! New 3D grid obtained after last time step [H ~> m or kg m-2]
integer :: nk, i, j, k, isc, iec, jsc, jec

nk = GV%ke; isc = G%isc; iec = G%iec; jsc = G%jsc; jec = G%jec
Expand Down Expand Up @@ -540,10 +540,10 @@ subroutine ALE_offline_tracer_final( G, GV, h, tv, h_target, Reg, CS, OBC)
type(ocean_grid_type), intent(in) :: G !< Ocean grid informations
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the
!! last time step [H ~> m or kg-2]
!! last time step [H ~> m or kg m-2]
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamic variable structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h_target !< Current 3D grid obtained after
!! last time step [H ~> m or kg-2]
!! last time step [H ~> m or kg m-2]
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
type(ALE_CS), pointer :: CS !< Regridding parameters and options
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
Expand Down Expand Up @@ -615,7 +615,7 @@ subroutine ALE_build_grid( G, GV, regridCS, remapCS, h, tv, debug, frac_shelf_h
type(remapping_CS), intent(in) :: remapCS !< Remapping parameters and options
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamical variable structure
real, dimension(SZI_(G),SZJ_(G), SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the
!! last time step [H ~> m or kg-2]
!! last time step [H ~> m or kg m-2]
logical, optional, intent(in) :: debug !< If true, show the call tree
real, dimension(SZI_(G),SZJ_(G)), optional, intent(in):: frac_shelf_h !< Fractional ice shelf coverage [nondim]
! Local variables
Expand Down Expand Up @@ -654,7 +654,7 @@ subroutine ALE_regrid_accelerated(CS, G, GV, h, tv, n, u, v, OBC, Reg, dt, dzReg
type(ocean_grid_type), intent(inout) :: G !< Ocean grid
type(verticalGrid_type), intent(in) :: GV !< Vertical grid
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
intent(inout) :: h !< Original thicknesses [H ~> m or kg-2]
intent(inout) :: h !< Original thicknesses [H ~> m or kg m-2]
type(thermo_var_ptrs), intent(inout) :: tv !< Thermo vars (T/S/EOS)
integer, intent(in) :: n !< Number of times to regrid
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), &
Expand Down Expand Up @@ -741,14 +741,14 @@ subroutine remap_all_state_vars(CS_remapping, CS_ALE, G, GV, h_old, h_new, Reg,
type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_old !< Thickness of source grid
!! [H ~> m or kg-2]
!! [H ~> m or kg m-2]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_new !< Thickness of destination grid
!! [H ~> m or kg-2]
!! [H ~> m or kg m-2]
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), &
optional, intent(in) :: dxInterface !< Change in interface position
!! [H ~> m or kg-2]
!! [H ~> m or kg m-2]
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), &
optional, intent(inout) :: u !< Zonal velocity [L T-1 ~> m s-1]
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), &
Expand Down Expand Up @@ -940,10 +940,10 @@ subroutine ALE_remap_scalar(CS, G, GV, nk_src, h_src, s_src, h_dst, s_dst, all_c
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
integer, intent(in) :: nk_src !< Number of levels on source grid
real, dimension(SZI_(G),SZJ_(G),nk_src), intent(in) :: h_src !< Level thickness of source grid
!! [H ~> m or kg-2]
!! [H ~> m or kg m-2]
real, dimension(SZI_(G),SZJ_(G),nk_src), intent(in) :: s_src !< Scalar on source grid
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)),intent(in) :: h_dst !< Level thickness of destination grid
!! [H ~> m or kg-2]
!! [H ~> m or kg m-2]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)),intent(inout) :: s_dst !< Scalar on destination grid
logical, optional, intent(in) :: all_cells !< If false, only reconstruct for
!! non-vanished cells. Use all vanished
Expand Down
2 changes: 1 addition & 1 deletion src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3541,7 +3541,7 @@ subroutine get_MOM_state_elements(CS, G, GV, US, C_p, C_p_scaled, use_temp)
type(unit_scale_type), optional, pointer :: US !< A dimensional unit scaling type
real, optional, intent(out) :: C_p !< The heat capacity [J kg degC-1]
real, optional, intent(out) :: C_p_scaled !< The heat capacity in scaled
!! units [Q degC-1 ~> J kg degC-1]
!! units [Q degC-1 ~> J kg-1 degC-1]
logical, optional, intent(out) :: use_temp !< True if temperature is a state variable

if (present(G)) G => CS%G_in
Expand Down
4 changes: 2 additions & 2 deletions src/core/MOM_CoriolisAdv.F90
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,7 @@ subroutine CorAdCalc(u, v, h, uh, vh, CAu, CAv, OBC, AD, G, GV, US, CS)
vh_min, vh_max, & ! fluxes through the faces (i.e. u*h*dy & v*h*dx)
! [H L2 T-1 ~> m3 s-1 or kg s-1].
ep_u, ep_v ! Additional pseudo-Coriolis terms in the Arakawa and Lamb
! discretization [H-1 s-1 ~> m-1 s-1 or m2 kg-1 s-1].
! discretization [H-1 T-1 ~> m-1 s-1 or m2 kg-1 s-1].
real, dimension(SZIB_(G),SZJB_(G)) :: &
dvdx, dudy, & ! Contributions to the circulation around q-points [L2 T-1 ~> m2 s-1]
rel_vort, & ! Relative vorticity at q-points [T-1 ~> s-1].
Expand Down Expand Up @@ -218,7 +218,7 @@ subroutine CorAdCalc(u, v, h, uh, vh, CAu, CAv, OBC, AD, G, GV, US, CS)
real :: Heff3, Heff4 ! Temporary effective H at U or V points [H ~> m or kg m-2].
real :: h_tiny ! A very small thickness [H ~> m or kg m-2].
real :: UHeff, VHeff ! More temporary variables [H L2 T-1 ~> m3 s-1 or kg s-1].
real :: QUHeff,QVHeff ! More temporary variables [H L2 T-1 s-1 ~> m3 s-2 or kg s-2].
real :: QUHeff,QVHeff ! More temporary variables [H L2 T-2 ~> m3 s-2 or kg s-2].
integer :: i, j, k, n, is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz

! Diagnostics for fractional thickness-weighted terms
Expand Down
14 changes: 8 additions & 6 deletions src/core/MOM_PressureForce_FV.F90
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ subroutine PressureForce_FV_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_
type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thickness [H ~> kg/m2]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thickness [H ~> kg m-2]
type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamic variables
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(out) :: PFu !< Zonal acceleration [L T-2 ~> m s-2]
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: PFv !< Meridional acceleration [L T-2 ~> m s-2]
Expand Down Expand Up @@ -109,9 +109,9 @@ subroutine PressureForce_FV_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_
dza, & ! The change in geopotential anomaly between the top and bottom
! of a layer [L2 T-2 ~> m2 s-2].
intp_dza ! The vertical integral in depth of the pressure anomaly less
! the pressure anomaly at the top of the layer [R L4 Z-4 ~> Pa m2 s-2].
! the pressure anomaly at the top of the layer [R L4 T-4 ~> Pa m2 s-2].
real, dimension(SZI_(G),SZJ_(G)) :: &
dp, & ! The (positive) change in pressure across a layer [R L2 Z-2 ~> Pa].
dp, & ! The (positive) change in pressure across a layer [R L2 T-2 ~> Pa].
SSH, & ! The sea surface height anomaly, in depth units [Z ~> m].
e_tidal, & ! The bottom geopotential anomaly due to tidal forces from
! astronomical sources and self-attraction and loading [Z ~> m].
Expand All @@ -137,7 +137,7 @@ subroutine PressureForce_FV_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_

real :: dp_neglect ! A thickness that is so small it is usually lost
! in roundoff and can be neglected [R L2 T-2 ~> Pa].
real :: I_gEarth ! The inverse of GV%g_Earth [L2 Z L-2 ~> s2 m-1]
real :: I_gEarth ! The inverse of GV%g_Earth [T2 Z L-2 ~> s2 m-1]
real :: alpha_anom ! The in-situ specific volume, averaged over a
! layer, less alpha_ref [R-1 ~> m3 kg-1].
logical :: use_p_atm ! If true, use the atmospheric pressure.
Expand All @@ -148,8 +148,10 @@ subroutine PressureForce_FV_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_
real :: alpha_ref ! A reference specific volume [R-1 ~> m3 kg-1] that is used
! to reduce the impact of truncation errors.
real :: rho_in_situ(SZI_(G)) ! The in situ density [R ~> kg m-3].
real :: Pa_to_H ! A factor to convert from Pa to the thicknesss units (H) [H T2 R-1 L-2 ~> H Pa-1].
real :: H_to_RL2_T2 ! A factor to convert from thicknesss units (H) to pressure units [R L2 T-2 H-1 ~> Pa H-1].
real :: Pa_to_H ! A factor to convert from Pa to the thickness units (H)
! [H T2 R-1 L-2 ~> m Pa-1 or kg m-2 Pa-1].
real :: H_to_RL2_T2 ! A factor to convert from thickness units (H) to pressure
! units [R L2 T-2 H-1 ~> Pa m-1 or Pa m2 kg-1].
! real :: oneatm = 101325.0 ! 1 atm in [Pa] = [kg m-1 s-2]
real, parameter :: C1_6 = 1.0/6.0
integer :: is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz, nkmb
Expand Down
6 changes: 3 additions & 3 deletions src/core/MOM_PressureForce_Montgomery.F90
Original file line number Diff line number Diff line change
Expand Up @@ -365,7 +365,7 @@ subroutine PressureForce_Mont_Bouss(h, tv, PFu, PFv, G, GV, US, CS, p_atm, pbce,
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(out) :: PFu !< Zonal acceleration due to pressure gradients
!! (equal to -dM/dx) [L T-2 ~> m s-2].
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: PFv !< Meridional acceleration due to pressure gradients
!! (equal to -dM/dy) [L T-2 ~> m s2].
!! (equal to -dM/dy) [L T-2 ~> m s-2].
type(PressureForce_Mont_CS), pointer :: CS !< Control structure for Montgomery potential PGF
real, dimension(:,:), pointer :: p_atm !< The pressure at the ice-ocean or
!! atmosphere-ocean [R L2 T-2 ~> Pa].
Expand All @@ -377,7 +377,7 @@ subroutine PressureForce_Mont_Bouss(h, tv, PFu, PFv, G, GV, US, CS, p_atm, pbce,
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: &
M, & ! The Montgomery potential, M = (p/rho + gz) [L2 T-2 ~> m2 s-2].
rho_star ! In-situ density divided by the derivative with depth of the
! corrected e times (G_Earth/Rho0) [m2 Z-1 s-2 ~> m s-2].
! corrected e times (G_Earth/Rho0) [L2 Z-1 T-2 ~> m s-2].
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: e ! Interface height in m.
! e may be adjusted (with a nonlinear equation of state) so that
! its derivative compensates for the adiabatic compressibility
Expand Down Expand Up @@ -629,7 +629,7 @@ subroutine Set_pbce_Bouss(e, tv, G, GV, US, Rho0, GFS_scale, pbce, rho_star)
real :: dR_dS(SZI_(G)) ! Partial derivative of density with salinity [R ppt-1 ~> kg m-3 ppt-1].
real :: rho_in_situ(SZI_(G)) ! In-situ density at the top of a layer [R ~> kg m-3].
real :: G_Rho0 ! A scaled version of g_Earth / Rho0 [L2 Z-1 T-2 R-1 ~> m4 s-2 kg-1]
real :: Rho0xG ! g_Earth * Rho0 [kg s-2 m-1 Z-1 ~> kg s-2 m-2]
real :: Rho0xG ! g_Earth * Rho0 [R L2 Z-1 T-2 ~> kg s-2 m-2]
logical :: use_EOS ! If true, density is calculated from T & S using
! an equation of state.
real :: z_neglect ! A thickness that is so small it is usually lost
Expand Down
12 changes: 6 additions & 6 deletions src/core/MOM_barotropic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -447,10 +447,10 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
!! height anomaly or column mass anomaly [H ~> m or kg m-2].
real, dimension(SZIB_(G),SZJ_(G)), intent(out) :: uhbtav !< the barotropic zonal volume or mass
!! fluxes averaged through the barotropic steps
!! [H L2 T-1 ~> m3 or kg s-1].
!! [H L2 T-1 ~> m3 s-1 or kg s-1].
real, dimension(SZI_(G),SZJB_(G)), intent(out) :: vhbtav !< the barotropic meridional volume or mass
!! fluxes averaged through the barotropic steps
!! [H L2 T-1 ~> m3 or kg s-1].
!! [H L2 T-1 ~> m3 s-1 or kg s-1].
type(barotropic_CS), pointer :: CS !< The control structure returned by a
!! previous call to barotropic_init.
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(in) :: visc_rem_u !< Both the fraction of the momentum
Expand Down Expand Up @@ -623,7 +623,7 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
vhbt_prev, vhbt_sum_prev, & ! Previous transports stored for OBCs [L2 H T-1 ~> m3 s-1]
vbt_int_prev, & ! Previous value of time-integrated velocity stored for OBCs [L ~> m]
vhbt_int_prev ! Previous value of time-integrated transport stored for OBCs [L2 H ~> m3]
real :: mass_to_Z ! The depth unit conversion divided by the mean density (Rho0) [Z m-1 R-1 ~> m3 kg-1].
real :: mass_to_Z ! The depth unit conversion divided by the mean density (Rho0) [Z m-1 R-1 ~> m3 kg-1] !### R-1
real :: mass_accel_to_Z ! The inverse of the mean density (Rho0) [R-1 ~> m3 kg-1].
real :: visc_rem ! A work variable that may equal visc_rem_[uv]. Nondim.
real :: vel_prev ! The previous velocity [L T-1 ~> m s-1].
Expand Down Expand Up @@ -773,7 +773,7 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
bebt = CS%bebt
be_proj = CS%bebt
mass_accel_to_Z = 1.0 / GV%Rho0
mass_to_Z = US%m_to_Z / GV%Rho0
mass_to_Z = US%m_to_Z / GV%Rho0 !### THis should be the same as mass_accel_to_Z.

!--- setup the weight when computing vbt_trans and ubt_trans
if (project_velocity) then
Expand Down Expand Up @@ -3566,7 +3566,7 @@ function find_duhbt_du(u, BTC) result(duhbt_du)
!! allow the barotropic transports to be calculated consistently
!! with the layers' continuity equations. The dimensions of some
!! of the elements in this type vary depending on INTEGRAL_BT_CONT.
real :: duhbt_du !< The zonal barotropic face area [L H ~> m2]
real :: duhbt_du !< The zonal barotropic face area [L H ~> m2 or kg m-1]

if (u == 0.0) then
duhbt_du = 0.5*(BTC%FA_u_E0 + BTC%FA_u_W0) ! Note the potential discontinuity here.
Expand Down Expand Up @@ -3701,7 +3701,7 @@ function find_dvhbt_dv(v, BTC) result(dvhbt_dv)
!! allow the barotropic transports to be calculated consistently
!! with the layers' continuity equations. The dimensions of some
!! of the elements in this type vary depending on INTEGRAL_BT_CONT.
real :: dvhbt_dv !< The meridional barotropic face area [L H ~> m2]
real :: dvhbt_dv !< The meridional barotropic face area [L H ~> m2 or kg m-1]

if (v == 0.0) then
dvhbt_dv = 0.5*(BTC%FA_v_N0 + BTC%FA_v_S0) ! Note the potential discontinuity here.
Expand Down
Loading

0 comments on commit e2e5787

Please sign in to comment.