Skip to content

Commit

Permalink
Documented units of 280 more variables
Browse files Browse the repository at this point in the history
  Changed comments to use the square bracket notation to document the units of
about 280 more variables, including lateral viscosities.  Also eliminated
another redundant argument documentation block.  Only comments have been changed
and all answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Dec 22, 2018
1 parent e0c3d49 commit 3d0c946
Show file tree
Hide file tree
Showing 25 changed files with 298 additions and 305 deletions.
4 changes: 2 additions & 2 deletions src/ALE/coord_adapt.F90
Original file line number Diff line number Diff line change
Expand Up @@ -123,8 +123,8 @@ subroutine build_adapt_column(CS, G, GV, tv, i, j, zInt, tInt, sInt, h, zNext)
integer, intent(in) :: i !< The i-index of the column to work on
integer, intent(in) :: j !< The j-index of the column to work on
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: zInt !< Interface heights [H ~> m or kg m-2].
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: tInt !< Interface temperatures, in C
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: sInt !< Interface salinities, in psu
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: tInt !< Interface temperatures [degC]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: sInt !< Interface salinities [ppt]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
real, dimension(SZK_(GV)+1), intent(inout) :: zNext !< updated interface positions

Expand Down
22 changes: 11 additions & 11 deletions src/ALE/coord_rho.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,10 +16,10 @@ module coord_rho
!> Number of layers
integer :: nk

!> Minimum thickness allowed for layers, in m
!> Minimum thickness allowed for layers, often in [H ~> m or kg m-2]
real :: min_thickness = 0.

!> Reference pressure for density calculations, in Pa
!> Reference pressure for density calculations [Pa]
real :: ref_pressure

!> If true, integrate for interface positions from the top downward.
Expand Down Expand Up @@ -73,7 +73,7 @@ end subroutine end_coord_rho
!> This subroutine can be used to set the parameters for the coord_rho module
subroutine set_rho_params(CS, min_thickness, integrate_downward_for_e, interp_CS)
type(rho_CS), pointer :: CS !< Coordinate control structure
real, optional, intent(in) :: min_thickness !< Minimum allowed thickness, in m
real, optional, intent(in) :: min_thickness !< Minimum allowed thickness [H ~> m or kg m-2]
logical, optional, intent(in) :: integrate_downward_for_e !< If true, integrate for interface
!! positions from the top downward. If false, integrate
!! from the bottom upward, as does the rest of the model.
Expand Down Expand Up @@ -189,18 +189,18 @@ subroutine build_rho_column_iteratively(CS, remapCS, nz, depth, h, T, S, eqn_of_
type(rho_CS), intent(in) :: CS !< Regridding control structure
type(remapping_CS), intent(in) :: remapCS !< Remapping parameters and options
integer, intent(in) :: nz !< Number of levels
real, intent(in) :: depth !< Depth of ocean bottom (positive in m)
real, dimension(nz), intent(in) :: h !< Layer thicknesses, in m
real, dimension(nz), intent(in) :: T !< T for column
real, dimension(nz), intent(in) :: S !< S for column
real, intent(in) :: depth !< Depth of ocean bottom [Z ~> m]
real, dimension(nz), intent(in) :: h !< Layer thicknesses in Z coordinates [Z ~> m]
real, dimension(nz), intent(in) :: T !< T for column [degC]
real, dimension(nz), intent(in) :: S !< S for column [ppt]
type(EOS_type), pointer :: eqn_of_state !< Equation of state structure
real, dimension(nz+1), intent(inout) :: zInterface !< Absolute positions of interfaces
real, optional, intent(in) :: h_neglect !< A negligibly small width for the
!! purpose of cell reconstructions
!! in the same units as h
!! in the same units as h [Z ~> m]
real, optional, intent(in) :: h_neglect_edge !< A negligibly small width
!! for the purpose of edge value calculations
!! in the same units as h
!! in the same units as h [Z ~> m]
! Local variables
integer :: k, m
integer :: count_nonzero_layers
Expand Down Expand Up @@ -349,9 +349,9 @@ end subroutine copy_finite_thicknesses
subroutine old_inflate_layers_1d( min_thickness, nk, h )

! Argument
real, intent(in) :: min_thickness !< Minimum allowed thickness, in m
real, intent(in) :: min_thickness !< Minimum allowed thickness [H ~> m or kg m-2]
integer, intent(in) :: nk !< Number of layers in the grid
real, dimension(:), intent(inout) :: h !< Layer thicknesses, in m
real, dimension(:), intent(inout) :: h !< Layer thicknesses [H ~> m or kg m-2]

! Local variable
integer :: k
Expand Down
8 changes: 4 additions & 4 deletions src/ALE/coord_zlike.F90
Original file line number Diff line number Diff line change
Expand Up @@ -13,11 +13,11 @@ module coord_zlike
!> Number of levels to be generated
integer :: nk

!> Minimum thickness allowed for layers, in the same thickness units that will
!! be used in all subsequent calls to build_zstar_column with this structure.
!> Minimum thickness allowed for layers, in the same thickness units (perhaps [H ~> m or kg m-2])
!! that will be used in all subsequent calls to build_zstar_column with this structure.
real :: min_thickness

!> Target coordinate resolution, usually in Z (often m)
!> Target coordinate resolution, usually in [Z ~> m]
real, allocatable, dimension(:) :: coordinateResolution
end type zlike_CS

Expand All @@ -29,7 +29,7 @@ module coord_zlike
subroutine init_coord_zlike(CS, nk, coordinateResolution)
type(zlike_CS), pointer :: CS !< Unassociated pointer to hold the control structure
integer, intent(in) :: nk !< Number of levels in the grid
real, dimension(:), intent(in) :: coordinateResolution !< Target coordinate resolution, in Z (often m)
real, dimension(:), intent(in) :: coordinateResolution !< Target coordinate resolution [Z ~> m]

if (associated(CS)) call MOM_error(FATAL, "init_coord_zlike: CS already associated!")
allocate(CS)
Expand Down
36 changes: 19 additions & 17 deletions src/core/MOM_PressureForce_analytic_FV.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ module MOM_PressureForce_AFV
real :: Rho0 !< The density used in the Boussinesq
!! approximation [kg m-3].
real :: GFS_scale !< A scaling of the surface pressure gradients to
!! allow the use of a reduced gravity model.
!! allow the use of a reduced gravity model [nondim].
type(time_type), pointer :: Time !< A pointer to the ocean model's clock.
type(diag_ctrl), pointer :: diag !< A structure that is used to regulate the
!! timing of diagnostic output.
Expand Down Expand Up @@ -103,7 +103,7 @@ subroutine PressureForce_AFV_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_(G)), intent(in) :: h !< Layer thickness (kg/m2)
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thickness [H ~> kg/m2]
type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamic variables
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(out) :: PFu !< Zonal acceleration [m s-2]
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(out) :: PFv !< Meridional acceleration [m s-2]
Expand All @@ -121,17 +121,19 @@ subroutine PressureForce_AFV_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p
real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1) :: p ! Interface pressure in Pa.
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), target :: &
T_tmp, & ! Temporary array of temperatures where layers that are lighter
! than the mixed layer have the mixed layer's properties, in C.
! than the mixed layer have the mixed layer's properties [degC].
S_tmp ! Temporary array of salinities where layers that are lighter
! than the mixed layer have the mixed layer's properties [PSU].
real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: &
S_t, S_b, T_t, T_b ! Top and bottom edge values for linear reconstructions
! of salinity and temperature within each layer.
S_t, & ! Top and bottom edge values for linear reconstructions
S_b, & ! of salinity within each layer [ppt].
T_t, & ! Top and bottom edge values for linear reconstructions
T_b ! of temperature within each layer [degC].
real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: &
dza, & ! The change in geopotential anomaly between the top and bottom
! of a layer [m2 s-2].
intp_dza ! The vertical integral in depth of the pressure anomaly less
! the pressure anomaly at the top of the layer, in Pa m2 s-2.
! the pressure anomaly at the top of the layer [Pa m2 s-2].
real, dimension(SZI_(G),SZJ_(G)) :: &
dp, & ! The (positive) change in pressure across a layer [Pa].
SSH, & ! The sea surface height anomaly, in depth units [Z ~> m].
Expand All @@ -146,16 +148,16 @@ subroutine PressureForce_AFV_nonBouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p
! density near-surface layer [kg m-3].
real, dimension(SZIB_(G),SZJ_(G)) :: &
intx_za ! The zonal integral of the geopotential anomaly along the
! interface below a layer, divided by the grid spacing, m2 s-2.
! interface below a layer, divided by the grid spacing [m2 s-2].
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)) :: &
intx_dza ! The change in intx_za through a layer [m2 s-2].
real, dimension(SZI_(G),SZJB_(G)) :: &
inty_za ! The meridional integral of the geopotential anomaly along the
! interface below a layer, divided by the grid spacing, m2 s-2.
! interface below a layer, divided by the grid spacing [m2 s-2].
real, dimension(SZI_(G),SZJB_(G),SZK_(G)) :: &
inty_dza ! The change in inty_za through a layer [m2 s-2].
real :: p_ref(SZI_(G)) ! The pressure used to calculate the coordinate
! density, in Pa (usually 2e7 Pa = 2000 dbar).
! density, [Pa] (usually 2e7 Pa = 2000 dbar).

real :: dp_neglect ! A thickness that is so small it is usually lost
! in roundoff and can be neglected [Pa].
Expand Down Expand Up @@ -444,14 +446,14 @@ subroutine PressureForce_AFV_Bouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_at
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_(G)), intent(in) :: h !< Layer thickness (kg/m2)
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thickness [H ~> m]
type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamic variables
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(out) :: PFu !< Zonal acceleration [m s-2]
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(out) :: PFv !< Meridional acceleration [m s-2]
type(PressureForce_AFV_CS), pointer :: CS !< Finite volume PGF control structure
type(ALE_CS), pointer :: ALE_CSp !< ALE control structure
real, dimension(:,:), optional, pointer :: p_atm !< The pressure at the ice-ocean
!! or atmosphere-ocean interface in Pa.
!! or atmosphere-ocean interface [Pa].
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), optional, intent(out) :: pbce !< The baroclinic pressure
!! anomaly in each layer due to eta anomalies
!! [m2 s-2 H-1 ~> m s-2 or m4 s-2 kg-1].
Expand All @@ -469,7 +471,7 @@ subroutine PressureForce_AFV_Bouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_at
Rho_cv_BL ! The coordinate potential density in the deepest variable
! density near-surface layer [kg m-3].
real, dimension(SZI_(G),SZJ_(G)) :: &
dz, & ! The change in geopotential thickness through a layer, m2 s-2.
dz, & ! The change in geopotential thickness through a layer [m2 s-2].
pa, & ! The pressure anomaly (i.e. pressure + g*RHO_0*e) at the
! the interface atop a layer [Pa].
dpa, & ! The change in pressure anomaly between the top and bottom
Expand All @@ -487,21 +489,21 @@ subroutine PressureForce_AFV_Bouss(h, tv, PFu, PFv, G, GV, US, CS, ALE_CSp, p_at

real, dimension(SZI_(G),SZJ_(G),SZK_(G)), target :: &
T_tmp, & ! Temporary array of temperatures where layers that are lighter
! than the mixed layer have the mixed layer's properties, in C.
! than the mixed layer have the mixed layer's properties [degC].
S_tmp ! Temporary array of salinities where layers that are lighter
! than the mixed layer have the mixed layer's properties [PSU].
real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: &
S_t, S_b, T_t, T_b ! Top and bottom edge values for linear reconstructions
! of salinity and temperature within each layer.
real :: rho_in_situ(SZI_(G)) ! The in situ density [kg m-3].
real :: p_ref(SZI_(G)) ! The pressure used to calculate the coordinate
! density, in Pa (usually 2e7 Pa = 2000 dbar).
real :: p0(SZI_(G)) ! An array of zeros to use for pressure in Pa.
! density, [Pa] (usually 2e7 Pa = 2000 dbar).
real :: p0(SZI_(G)) ! An array of zeros to use for pressure [Pa].
real :: h_neglect ! A thickness that is so small it is usually lost
! in roundoff and can be neglected, in m.
! in roundoff and can be neglected [H ~> m].
real :: g_Earth_z ! A scaled version of g_Earth [m2 Z-1 s-2 ~> m s-2].
real :: I_Rho0 ! 1/Rho0 [m3 kg-1].
real :: G_Rho0 ! G_Earth / Rho0 in m5 Z-1 s-2 kg-1.
real :: G_Rho0 ! G_Earth / Rho0 in [m5 Z-1 s-2 kg-1 ~> m4 s-2 kg-1].
real :: Rho_ref ! The reference density [kg m-3].
real :: dz_neglect ! A minimal thickness [Z ~> m], like e.
logical :: use_p_atm ! If true, use the atmospheric pressure.
Expand Down
2 changes: 1 addition & 1 deletion src/core/MOM_barotropic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -566,7 +566,7 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
dyn_coef_eta, & ! The coefficient relating the changes in eta to the
! dynamic surface pressure under rigid ice
! [m2 s-2 H-1 ~> m s-2 or m4 s-2 kg-1].
p_surf_dyn ! A dynamic surface pressure under rigid ice, in m2 s-2.
p_surf_dyn ! A dynamic surface pressure under rigid ice [m2 s-2].
type(local_BT_cont_u_type), dimension(SZIBW_(CS),SZJW_(CS)) :: &
BTCL_u ! A repackaged version of the u-point information in BT_cont.
type(local_BT_cont_v_type), dimension(SZIW_(CS),SZJBW_(CS)) :: &
Expand Down
12 changes: 6 additions & 6 deletions src/core/MOM_continuity.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,9 +44,9 @@ subroutine continuity(u, v, hin, h, uh, vh, dt, G, GV, CS, uhbt, vhbt, OBC, &
type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure.
type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure.
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
intent(in) :: u !< Zonal velocity, in m/s.
intent(in) :: u !< Zonal velocity [m s-1].
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
intent(in) :: v !< Meridional velocity, in m/s.
intent(in) :: v !< Meridional velocity [m s-1].
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
intent(in) :: hin !< Initial layer thickness [H ~> m or kg m-2].
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
Expand Down Expand Up @@ -79,10 +79,10 @@ subroutine continuity(u, v, hin, h, uh, vh, dt, G, GV, CS, uhbt, vhbt, OBC, &
!! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom).
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
optional, intent(out) :: u_cor !< The zonal velocities that
!! give uhbt as the depth-integrated transport, in m/s.
!! give uhbt as the depth-integrated transport [m s-1].
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
optional, intent(out) :: v_cor !< The meridional velocities that
!! give vhbt as the depth-integrated transport, in m/s.
!! give vhbt as the depth-integrated transport [m s-1].
real, dimension(SZIB_(G),SZJ_(G)), &
optional, intent(in) :: uhbt_aux !< A second summed zonal
!! volume flux in m3/s.
Expand All @@ -91,10 +91,10 @@ subroutine continuity(u, v, hin, h, uh, vh, dt, G, GV, CS, uhbt, vhbt, OBC, &
!! volume flux in m3/s.
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
optional, intent(inout) :: u_cor_aux !< The zonal velocities
!! that give uhbt_aux as the depth-integrated transport, in m/s.
!! that give uhbt_aux as the depth-integrated transport [m s-1].
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
optional, intent(inout) :: v_cor_aux !< The meridional velocities
!! that give vhbt_aux as the depth-integrated transport, in m/s.
!! that give vhbt_aux as the depth-integrated transport [m s-1].
type(BT_cont_type), &
optional, pointer :: BT_cont !< A structure with elements
!! that describe the effective open face areas as a function of barotropic flow.
Expand Down
4 changes: 2 additions & 2 deletions src/core/MOM_open_boundary.F90
Original file line number Diff line number Diff line change
Expand Up @@ -251,10 +251,10 @@ module MOM_open_boundary
real, pointer, dimension(:,:,:) :: cff_normal => NULL() !< Array storage for restarts
real :: silly_h !< A silly value of thickness outside of the domain that
!! can be used to test the independence of the OBCs to
!! this external data, in m.
!! this external data [H ~> m or kg m-2].
real :: silly_u !< A silly value of velocity outside of the domain that
!! can be used to test the independence of the OBCs to
!! this external data, in m/s.
!! this external data [m s-1].
end type ocean_OBC_type

!> Control structure for open boundaries that read from files.
Expand Down
Loading

0 comments on commit 3d0c946

Please sign in to comment.