Skip to content

Commit

Permalink
Modify units in temperature and salinity comments
Browse files Browse the repository at this point in the history
  Modified comments in 20 files to prepare for the addition of dimensional
rescaling of temperature and salinity.  All answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed May 1, 2022
1 parent f52c40a commit 5d88f2e
Show file tree
Hide file tree
Showing 20 changed files with 314 additions and 310 deletions.
4 changes: 2 additions & 2 deletions src/ALE/MOM_hybgen_regrid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -361,8 +361,8 @@ subroutine hybgen_regrid(G, GV, US, dp, tv, CS, dzInterface, PCM_cell)

! These arrays work with the input column
real :: p_col(GV%ke) ! A column of reference pressures [R L2 T-2 ~> Pa]
real :: temp_in(GV%ke) ! A column of input potential temperatures [degC]
real :: saln_in(GV%ke) ! A column of input layer salinities [ppt]
real :: temp_in(GV%ke) ! A column of input potential temperatures [C ~> degC]
real :: saln_in(GV%ke) ! A column of input layer salinities [S ~> ppt]
real :: Rcv_in(GV%ke) ! An input column of coordinate potential density [R ~> kg m-3]
real :: dp_in(GV%ke) ! The input column of layer thicknesses [H ~> m or kg m-2]
logical :: PCM_lay(GV%ke) ! If true for a layer, use PCM remapping for that layer
Expand Down
24 changes: 12 additions & 12 deletions src/ALE/MOM_hybgen_unmix.F90
Original file line number Diff line number Diff line change
Expand Up @@ -139,8 +139,8 @@ subroutine hybgen_unmix(G, GV, US, CS, tv, Reg, ntr, h)
real :: dp0cum(GV%ke+1) ! minimum interface depth [H ~> m or kg m-2]

real :: Rcv_tgt(GV%ke) ! Target potential density [R ~> kg m-3]
real :: temp(GV%ke) ! A column of potential temperature [degC]
real :: saln(GV%ke) ! A column of salinity [ppt]
real :: temp(GV%ke) ! A column of potential temperature [C ~> degC]
real :: saln(GV%ke) ! A column of salinity [S ~> ppt]
real :: Rcv(GV%ke) ! A column of coordinate potential density [R ~> kg m-3]
real :: h_col(GV%ke) ! A column of layer thicknesses [H ~> m or kg m-2]
real :: p_col(GV%ke) ! A column of reference pressures [R L2 T-2 ~> Pa]
Expand All @@ -151,8 +151,8 @@ subroutine hybgen_unmix(G, GV, US, CS, tv, Reg, ntr, h)
! vanished layers [H ~> m or kg m-2]
real :: dilate ! A factor by which to dilate the target positions from z to z* [nondim]

real :: Th_tot_in, Th_tot_out ! Column integrated temperature [degC H ~> degC m or degC kg m-2]
real :: Sh_tot_in, Sh_tot_out ! Column integrated salinity [ppt H ~> ppt m or ppt kg m-2]
real :: Th_tot_in, Th_tot_out ! Column integrated temperature [C H ~> degC m or degC kg m-2]
real :: Sh_tot_in, Sh_tot_out ! Column integrated salinity [S H ~> ppt m or ppt kg m-2]
real :: Trh_tot_in(max(ntr,1)) ! Initial column integrated tracer amounts [conc H ~> conc m or conc kg m-2]
real :: Trh_tot_out(max(ntr,1)) ! Final column integrated tracer amounts [conc H ~> conc m or conc kg m-2]

Expand Down Expand Up @@ -280,8 +280,8 @@ subroutine hybgen_column_unmix(CS, nk, Rcv_tgt, temp, saln, Rcv, eqn_of_state, &
integer, intent(in) :: fixlay !< deepest fixed coordinate layer
real, intent(in) :: qhrlx(nk+1) !< Relaxation fraction per timestep [nondim], < 1.
real, intent(in) :: Rcv_tgt(nk) !< Target potential density [R ~> kg m-3]
real, intent(inout) :: temp(nk) !< A column of potential temperature [degC]
real, intent(inout) :: saln(nk) !< A column of salinity [ppt]
real, intent(inout) :: temp(nk) !< A column of potential temperature [C ~> degC]
real, intent(inout) :: saln(nk) !< A column of salinity [S ~> ppt]
real, intent(inout) :: Rcv(nk) !< Coordinate potential density [R ~> kg m-3]
type(EOS_type), intent(in) :: eqn_of_state !< Equation of state structure
integer, intent(in) :: ntr !< The number of registered passive tracers
Expand All @@ -299,20 +299,20 @@ subroutine hybgen_column_unmix(CS, nk, Rcv_tgt, temp, saln, Rcv, eqn_of_state, &
!
! Local variables
real :: h_hat ! A portion of a layer to move across an interface [H ~> m or kg m-2]
real :: delt, deltm ! Temperature differences between successive layers [degC]
real :: dels, delsm ! Salinity differences between successive layers [ppt]
real :: delt, deltm ! Temperature differences between successive layers [C ~> degC]
real :: dels, delsm ! Salinity differences between successive layers [S ~> ppt]
real :: abs_dRdT ! The absolute value of the derivative of the coordinate density
! with temperature [R degC-1 ~> kg m-3 degC-1]
! with temperature [R C-1 ~> kg m-3 degC-1]
real :: abs_dRdS ! The absolute value of the derivative of the coordinate density
! with salinity [R ppt-1 ~> kg m-3 ppt-1]
! with salinity [R S-1 ~> kg m-3 ppt-1]
real :: q, qts ! Nondimensional fractions in the range of 0 to 1 [nondim]
real :: frac_dts ! The fraction of the temperature or salinity difference between successive
! layers by which the source layer's property changes by the loss of water
! that matches the destination layers properties via unmixing [nondim].
real :: qtr ! The fraction of the water that will come from the layer below,
! used for updating the concentration of passive tracers [nondim]
real :: swap_T ! A swap variable for temperature [degC]
real :: swap_S ! A swap variable for salinity [ppt]
real :: swap_T ! A swap variable for temperature [C ~> degC]
real :: swap_S ! A swap variable for salinity [S ~> ppt]
real :: swap_tr ! A temporary swap variable for the tracers [conc]
logical, parameter :: lunmix=.true. ! unmix a too light deepest layer
integer :: k, ka, kp, kt, m
Expand Down
12 changes: 6 additions & 6 deletions src/ALE/MOM_regridding.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1594,7 +1594,7 @@ subroutine build_grid_adaptive(G, GV, US, h, tv, dzInterface, remapCS, CS)

! local variables
integer :: i, j, k, nz ! indices and dimension lengths
! temperature, salinity and pressure on interfaces
! temperature [C ~> degC], salinity [S ~> ppt] and pressure on interfaces
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: tInt, sInt
! current interface positions and after tendency term is applied
! positive downward
Expand Down Expand Up @@ -1936,8 +1936,8 @@ subroutine convective_adjustment(G, GV, h, tv)
!------------------------------------------------------------------------------

! Local variables
real :: T0, T1 ! temperatures of two layers [degC]
real :: S0, S1 ! salinities of two layers [ppt]
real :: T0, T1 ! temperatures of two layers [C ~> degC]
real :: S0, S1 ! salinities of two layers [S ~> ppt]
real :: r0, r1 ! densities of two layers [R ~> kg m-3]
real :: h0, h1 ! Layer thicknesses [H ~> m or kg m-2]
real, dimension(GV%ke) :: p_col ! A column of zero pressures [R L2 T-2 ~> Pa]
Expand All @@ -1953,7 +1953,7 @@ subroutine convective_adjustment(G, GV, h, tv)
do j = G%jsc-1,G%jec+1 ; do i = G%isc-1,G%iec+1

! Compute densities within current water column
call calculate_density( tv%T(i,j,:), tv%S(i,j,:), p_col, densities, tv%eqn_of_state)
call calculate_density(tv%T(i,j,:), tv%S(i,j,:), p_col, densities, tv%eqn_of_state)

! Repeat restratification until complete
do
Expand All @@ -1972,8 +1972,8 @@ subroutine convective_adjustment(G, GV, h, tv)
tv%S(i,j,k) = S1 ; tv%S(i,j,k+1) = S0
h(i,j,k) = h1 ; h(i,j,k+1) = h0
! Recompute densities at levels k and k+1
call calculate_density( tv%T(i,j,k), tv%S(i,j,k), p_col(k), densities(k), tv%eqn_of_state)
call calculate_density( tv%T(i,j,k+1), tv%S(i,j,k+1), p_col(k+1), &
call calculate_density(tv%T(i,j,k), tv%S(i,j,k), p_col(k), densities(k), tv%eqn_of_state)
call calculate_density(tv%T(i,j,k+1), tv%S(i,j,k+1), p_col(k+1), &
densities(k+1), tv%eqn_of_state )
! Because p_col is has uniform values, these calculate_density calls are equivalent to
! densities(k) = r1 ; densities(k+1) = r0
Expand Down
8 changes: 4 additions & 4 deletions src/ALE/coord_adapt.F90
Original file line number Diff line number Diff line change
Expand Up @@ -122,17 +122,17 @@ subroutine build_adapt_column(CS, G, GV, US, tv, i, j, zInt, tInt, sInt, h, zNex
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 [degC]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: sInt !< Interface salinities [ppt]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: tInt !< Interface temperatures [C ~> degC]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: sInt !< Interface salinities [S ~> 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

! Local variables
integer :: k, nz
real :: h_up, b1, b_denom_1, d1, depth, nominal_z, stretching
real :: drdz ! The vertical density gradient [R H-1 ~> kg m-4 or m-1]
real, dimension(SZK_(GV)+1) :: alpha ! drho/dT [R degC-1 ~> kg m-3 degC-1]
real, dimension(SZK_(GV)+1) :: beta ! drho/dS [R ppt-1 ~> kg m-3 ppt-1]
real, dimension(SZK_(GV)+1) :: alpha ! drho/dT [R C-1 ~> kg m-3 degC-1]
real, dimension(SZK_(GV)+1) :: beta ! drho/dS [R S-1 ~> kg m-3 ppt-1]
real, dimension(SZK_(GV)+1) :: del2sigma ! Laplacian of in situ density times grid spacing [R ~> kg m-3]
real, dimension(SZK_(GV)+1) :: dh_d2s ! Thickness change in response to del2sigma [H ~> m or kg m-2]
real, dimension(SZK_(GV)) :: kGrid, c1 ! grid diffusivity on layers, and tridiagonal work array
Expand Down
4 changes: 2 additions & 2 deletions src/ALE/coord_hycom.F90
Original file line number Diff line number Diff line change
Expand Up @@ -101,8 +101,8 @@ subroutine build_hycom1_column(CS, eqn_of_state, nz, depth, h, T, S, p_col, &
type(EOS_type), intent(in) :: eqn_of_state !< Equation of state structure
integer, intent(in) :: nz !< Number of levels
real, intent(in) :: depth !< Depth of ocean bottom (positive [H ~> m or kg m-2])
real, dimension(nz), intent(in) :: T !< Temperature of column [degC]
real, dimension(nz), intent(in) :: S !< Salinity of column [ppt]
real, dimension(nz), intent(in) :: T !< Temperature of column [C ~> degC]
real, dimension(nz), intent(in) :: S !< Salinity of column [S ~> ppt]
real, dimension(nz), intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
real, dimension(nz), intent(in) :: p_col !< Layer pressure [R L2 T-2 ~> Pa]
real, dimension(nz+1), intent(in) :: z_col !< Interface positions relative to the surface [H ~> m or kg m-2]
Expand Down
12 changes: 6 additions & 6 deletions src/ALE/coord_rho.F90
Original file line number Diff line number Diff line change
Expand Up @@ -93,8 +93,8 @@ subroutine build_rho_column(CS, nz, depth, h, T, S, eqn_of_state, z_interface, &
integer, intent(in) :: nz !< Number of levels on source grid (i.e. length of h, T, S)
real, intent(in) :: depth !< Depth of ocean bottom (positive downward) [H ~> m or kg m-2]
real, dimension(nz), intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
real, dimension(nz), intent(in) :: T !< Temperature for source column [degC]
real, dimension(nz), intent(in) :: S !< Salinity for source column [ppt]
real, dimension(nz), intent(in) :: T !< Temperature for source column [C ~> degC]
real, dimension(nz), intent(in) :: S !< Salinity for source column [S ~> ppt]
type(EOS_type), intent(in) :: eqn_of_state !< Equation of state structure
real, dimension(CS%nk+1), &
intent(inout) :: z_interface !< Absolute positions of interfaces
Expand Down Expand Up @@ -206,8 +206,8 @@ subroutine build_rho_column_iteratively(CS, remapCS, nz, depth, h, T, S, eqn_of_
integer, intent(in) :: nz !< Number of levels
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]
real, dimension(nz), intent(in) :: T !< T for column [C ~> degC]
real, dimension(nz), intent(in) :: S !< S for column [S ~> ppt]
type(EOS_type), intent(in) :: 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
Expand All @@ -224,7 +224,7 @@ subroutine build_rho_column_iteratively(CS, remapCS, nz, depth, h, T, S, eqn_of_
real, dimension(nz+1) :: x0, x1, xTmp ! Temporary interface heights [Z ~> m]
real, dimension(nz) :: pres ! The pressure used in the equation of state [R L2 T-2 ~> Pa].
real, dimension(nz) :: densities ! Layer densities [R ~> kg m-3]
real, dimension(nz) :: T_tmp, S_tmp ! A temporary profile of temperature [degC] and salinity [ppt].
real, dimension(nz) :: T_tmp, S_tmp ! A temporary profile of temperature [C ~> degC] and salinity [S ~> ppt].
real, dimension(nz) :: Tmp ! A temporary variable holding a remapped variable.
real, dimension(nz) :: h0, h1, hTmp ! Temporary thicknesses [Z ~> m]
real :: deviation ! When iterating to determine the final grid, this is the
Expand Down Expand Up @@ -263,7 +263,7 @@ subroutine build_rho_column_iteratively(CS, remapCS, nz, depth, h, T, S, eqn_of_
enddo

! Compute densities within current water column
call calculate_density( T_tmp, S_tmp, pres, densities, eqn_of_state)
call calculate_density(T_tmp, S_tmp, pres, densities, eqn_of_state)

do k = 1,count_nonzero_layers
densities(k) = densities(mapping(k))
Expand Down
16 changes: 8 additions & 8 deletions src/ALE/coord_slight.F90
Original file line number Diff line number Diff line change
Expand Up @@ -187,8 +187,8 @@ subroutine build_slight_column(CS, eqn_of_state, H_to_pres, H_subroundoff, &
real, intent(in) :: H_subroundoff !< GV%H_subroundoff
integer, intent(in) :: nz !< Number of levels
real, intent(in) :: depth !< Depth of ocean bottom (positive [H ~> m or kg m-2])
real, dimension(nz), intent(in) :: T_col !< T for column
real, dimension(nz), intent(in) :: S_col !< S for column
real, dimension(nz), intent(in) :: T_col !< T for column [C ~> degC]
real, dimension(nz), intent(in) :: S_col !< S for column [S ~> ppt]
real, dimension(nz), intent(in) :: h_col !< Layer thicknesses [H ~> m or kg m-2]
real, dimension(nz), intent(in) :: p_col !< Layer center pressure [R L2 T-2 ~> Pa]
real, dimension(nz+1), intent(in) :: z_col !< Interface positions relative to the surface [H ~> m or kg m-2]
Expand All @@ -199,20 +199,20 @@ subroutine build_slight_column(CS, eqn_of_state, H_to_pres, H_subroundoff, &
!! of edge value calculations [H ~> m or kg m-2].
! Local variables
real, dimension(nz) :: rho_col ! Layer densities [R ~> kg m-3]
real, dimension(nz) :: T_f, S_f ! Filtered layer temperature [degC] and salinity [ppt]
real, dimension(nz) :: T_f, S_f ! Filtered layer temperature [C ~> degC] and salinity [S ~> ppt]
logical, dimension(nz+1) :: reliable ! If true, this interface is in a reliable position.
real, dimension(nz+1) :: T_int, S_int ! Temperature [degC] and salinity [ppt] interpolated to interfaces.
real, dimension(nz+1) :: T_int, S_int ! Temperature [C ~> degC] and salinity [S ~> ppt] interpolated to interfaces.
real, dimension(nz+1) :: rho_tmp ! A temporary density [R ~> kg m-3]
real, dimension(nz+1) :: drho_dp ! The partial derivative of density with pressure [T2 L-2 ~> kg m-3 Pa-1]
real, dimension(nz+1) :: p_IS, p_R ! Pressures [R L2 T-2 ~> Pa]
real, dimension(nz+1) :: drhoIS_dT ! The partial derivative of in situ density with temperature
! in [R degC-1 ~> kg m-3 degC-1]
! in [R C-1 ~> kg m-3 degC-1]
real, dimension(nz+1) :: drhoIS_dS ! The partial derivative of in situ density with salinity
! in [R ppt-1 ~> kg m-3 ppt-1]
! in [R S-1 ~> kg m-3 ppt-1]
real, dimension(nz+1) :: drhoR_dT ! The partial derivative of reference density with temperature
! in [R degC-1 ~> kg m-3 degC-1]
! in [R C-1 ~> kg m-3 degC-1]
real, dimension(nz+1) :: drhoR_dS ! The partial derivative of reference density with salinity
! in [R ppt-1 ~> kg m-3 ppt-1]
! in [R S-1 ~> kg m-3 ppt-1]
real, dimension(nz+1) :: strat_rat
real :: H_to_cPa ! A conversion factor from thicknesses to the compressibility fraction times
! the units of pressure [R L2 T-2 H-1 ~> Pa m-1 or Pa m2 kg-1]
Expand Down
Loading

0 comments on commit 5d88f2e

Please sign in to comment.