Skip to content

Commit

Permalink
Correct a few more temperature and salin units
Browse files Browse the repository at this point in the history
  Corrected the units in comments describing some temperature and salinity
variables that had been accidentally omitted from the previous commits in this
sequence.  Also rescaled some local temperature and salinity variables used in
seamount_initialize_thickness and added missing unit conversion factors for
several diagnostics in MOM_oda_incupd.  All answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed May 8, 2022
1 parent 6d78d2b commit 31d4117
Show file tree
Hide file tree
Showing 10 changed files with 62 additions and 61 deletions.
14 changes: 5 additions & 9 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -182,7 +182,7 @@ module MOM
real ALLOCABLE_, dimension(NIMEM_,NJMEM_,NKMEM_) :: &
h, & !< layer thickness [H ~> m or kg m-2]
T, & !< potential temperature [C ~> degC]
S !< salinity [ppt]
S !< salinity [S ~> ppt]
real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NKMEM_) :: &
u, & !< zonal velocity component [L T-1 ~> m s-1]
uh, & !< uh = u * h * dy at u grid points [H L2 T-1 ~> m3 s-1 or kg s-1]
Expand Down Expand Up @@ -286,10 +286,6 @@ module MOM
real, dimension(:,:), pointer :: frac_shelf_h => NULL() !< fraction of total area occupied
!! by ice shelf [nondim]
real, dimension(:,:), pointer :: mass_shelf => NULL() !< Mass of ice shelf [R Z ~> kg m-2]
real, dimension(:,:,:), pointer :: &
h_pre_dyn => NULL(), & !< The thickness before the transports [H ~> m or kg m-2].
T_pre_dyn => NULL(), & !< Temperature before the transports [degC].
S_pre_dyn => NULL() !< Salinity before the transports [ppt].
type(accel_diag_ptrs) :: ADp !< structure containing pointers to accelerations,
!! for derived diagnostics (e.g., energy budgets)
type(cont_diag_ptrs) :: CDp !< structure containing pointers to continuity equation
Expand Down Expand Up @@ -3600,15 +3596,15 @@ subroutine rotate_initial_state(u_in, v_in, h_in, T_in, S_in, &
real, dimension(:,:,:), intent(in) :: u_in !< Zonal velocity on the initial grid [L T-1 ~> m s-1]
real, dimension(:,:,:), intent(in) :: v_in !< Meridional velocity on the initial grid [L T-1 ~> m s-1]
real, dimension(:,:,:), intent(in) :: h_in !< Layer thickness on the initial grid [H ~> m or kg m-2]
real, dimension(:,:,:), intent(in) :: T_in !< Temperature on the initial grid [degC]
real, dimension(:,:,:), intent(in) :: S_in !< Salinity on the initial grid [ppt]
real, dimension(:,:,:), intent(in) :: T_in !< Temperature on the initial grid [C ~> degC]
real, dimension(:,:,:), intent(in) :: S_in !< Salinity on the initial grid [S ~> ppt]
logical, intent(in) :: use_temperature !< If true, temperature and salinity are active
integer, intent(in) :: turns !< The number quarter-turns to apply
real, dimension(:,:,:), intent(out) :: u !< Zonal velocity on the rotated grid [L T-1 ~> m s-1]
real, dimension(:,:,:), intent(out) :: v !< Meridional velocity on the rotated grid [L T-1 ~> m s-1]
real, dimension(:,:,:), intent(out) :: h !< Layer thickness on the rotated grid [H ~> m or kg m-2]
real, dimension(:,:,:), intent(out) :: T !< Temperature on the rotated grid [degC]
real, dimension(:,:,:), intent(out) :: S !< Salinity on the rotated grid [ppt]
real, dimension(:,:,:), intent(out) :: T !< Temperature on the rotated grid [C ~> degC]
real, dimension(:,:,:), intent(out) :: S !< Salinity on the rotated grid [S ~> ppt]

call rotate_vector(u_in, v_in, turns, u, v)
call rotate_array(h_in, turns, h)
Expand Down
20 changes: 10 additions & 10 deletions src/ocean_data_assim/MOM_oda_incupd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -527,8 +527,8 @@ subroutine apply_oda_incupd(h, tv, u, v, dt, G, GV, US, CS)
real, dimension(SZK_(GV)) :: tmp_val1 ! data values remapped to model grid
real, dimension(SZK_(GV)) :: hu, hv ! A column of thicknesses at u or v points [H ~> m or kg m-2]

real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: tmp_t !< A temporary array for t increments [degC]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: tmp_s !< A temporary array for s increments [ppt]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: tmp_t !< A temporary array for t increments [C ~> degC]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: tmp_s !< A temporary array for s increments [S ~> ppt]
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: tmp_u !< A temporary array for u increments [L T-1 ~> m s-1]
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: tmp_v !< A temporary array for v increments [L T-1 ~> m s-1]

Expand Down Expand Up @@ -726,6 +726,7 @@ subroutine apply_oda_incupd(h, tv, u, v, dt, G, GV, US, CS)
if (CS%id_u_oda_inc > 0) call post_data(CS%id_u_oda_inc, tmp_u, CS%diag)
if (CS%id_v_oda_inc > 0) call post_data(CS%id_v_oda_inc, tmp_v, CS%diag)
endif
!### The argument here seems wrong.
if (CS%id_h_oda_inc > 0) call post_data(CS%id_h_oda_inc, h , CS%diag)
if (CS%id_T_oda_inc > 0) call post_data(CS%id_T_oda_inc, tmp_t, CS%diag)
if (CS%id_S_oda_inc > 0) call post_data(CS%id_S_oda_inc, tmp_s, CS%diag)
Expand Down Expand Up @@ -795,7 +796,7 @@ end subroutine output_oda_incupd_inc
subroutine init_oda_incupd_diags(Time, G, GV, diag, CS, US)
type(time_type), target, intent(in) :: Time !< The current model time
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(diag_ctrl), target, intent(inout) :: diag !< A structure that is used to regulate diagnostic
!! output.
type(oda_incupd_CS), pointer :: CS !< ALE sponge control structure
Expand All @@ -804,18 +805,17 @@ subroutine init_oda_incupd_diags(Time, G, GV, diag, CS, US)
if (.not.associated(CS)) return

CS%diag => diag
! These diagnostics of the state variables increments,useful for debugging the
! ODA code.
! These diagnostics of the state variables increments are useful for debugging the ODA code.
CS%id_u_oda_inc = register_diag_field('ocean_model', 'u_oda_inc', diag%axesCuL, Time, &
'Zonal velocity ODA inc.', 'm s-1')
'Zonal velocity ODA inc.', 'm s-1', conversion=US%L_T_to_m_s)
CS%id_v_oda_inc = register_diag_field('ocean_model', 'v_oda_inc', diag%axesCvL, Time, &
'Meridional velocity ODA inc.', 'm s-1')
'Meridional velocity ODA inc.', 'm s-1', conversion=US%L_T_to_m_s)
CS%id_h_oda_inc = register_diag_field('ocean_model', 'h_oda_inc', diag%axesTL, Time, &
'Layer Thickness ODA inc.', get_thickness_units(GV))
'Layer Thickness ODA inc.', get_thickness_units(GV), conversion=GV%H_to_mks)
CS%id_T_oda_inc = register_diag_field('ocean_model', 'T_oda_inc', diag%axesTL, Time, &
'Temperature ODA inc.', 'degC')
'Temperature ODA inc.', 'degC', conversion=US%C_to_degC)
CS%id_S_oda_inc = register_diag_field('ocean_model', 'S_oda_inc', diag%axesTL, Time, &
'Salinity ODA inc.', 'PSU')
'Salinity ODA inc.', 'PSU', conversion=US%S_to_ppt)

end subroutine init_oda_incupd_diags

Expand Down
8 changes: 4 additions & 4 deletions src/parameterizations/vertical/MOM_CVMix_KPP.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1394,12 +1394,12 @@ subroutine KPP_NonLocalTransport_temp(CS, G, GV, h, nonLocalTrans, surfFlux, &
real, dimension(SZI_(G),SZJ_(G)), intent(in) :: surfFlux !< Surface flux of temperature
!! [C H T-1 ~> degC m s-1 or degC kg m-2 s-1]
real, intent(in) :: dt !< Time-step [T ~> s]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: scalar !< temperature [degC]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: scalar !< temperature [C ~> degC]
real, intent(in) :: C_p !< Seawater specific heat capacity
!! [Q C-1 ~> J kg-1 degC-1]

integer :: i, j, k
real, dimension( SZI_(G), SZJ_(G),SZK_(GV) ) :: dtracer ! Rate of tracer change [degC T-1 ~> degC s-1]
real, dimension( SZI_(G), SZJ_(G),SZK_(GV) ) :: dtracer ! Rate of tracer change [C T-1 ~> degC s-1]


dtracer(:,:,:) = 0.0
Expand Down Expand Up @@ -1458,10 +1458,10 @@ subroutine KPP_NonLocalTransport_saln(CS, G, GV, h, nonLocalTrans, surfFlux, dt,
real, dimension(SZI_(G),SZJ_(G)), intent(in) :: surfFlux !< Surface flux of salt
!! [S H T-1 ~> ppt m s-1 or ppt kg m-2 s-1]
real, intent(in) :: dt !< Time-step [T ~> s]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: scalar !< Salinity [ppt]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: scalar !< Salinity [S ~> ppt]

integer :: i, j, k
real, dimension( SZI_(G), SZJ_(G),SZK_(GV) ) :: dtracer ! Rate of tracer change [ppt T-1 ~> ppt s-1]
real, dimension( SZI_(G), SZJ_(G),SZK_(GV) ) :: dtracer ! Rate of tracer change [S T-1 ~> ppt s-1]


dtracer(:,:,:) = 0.0
Expand Down
24 changes: 12 additions & 12 deletions src/parameterizations/vertical/MOM_bulk_mixed_layer.F90
Original file line number Diff line number Diff line change
Expand Up @@ -761,7 +761,7 @@ subroutine convective_adjustment(h, u, v, R0, Rcv, T, S, eps, d_eb, &
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: Rcv !< The coordinate defining potential
!! density [R ~> kg m-3].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: T !< Layer temperatures [C ~> degC].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: S !< Layer salinities [ppt].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: S !< Layer salinities [S ~> ppt].
real, dimension(SZI_(G),SZK_(GV)), intent(in) :: eps !< The negligibly small amount of water
!! that will be left in each layer [H ~> m or kg m-2].
real, dimension(SZI_(G),SZK_(GV)), intent(inout) :: d_eb !< The downward increase across a layer
Expand Down Expand Up @@ -908,7 +908,7 @@ subroutine mixedlayer_convection(h, d_eb, htot, Ttot, Stot, uhtot, vhtot, &
real, dimension(SZI_(G),SZK0_(GV)), &
intent(in) :: T !< Layer temperatures [C ~> degC].
real, dimension(SZI_(G),SZK0_(GV)), &
intent(in) :: S !< Layer salinities [ppt].
intent(in) :: S !< Layer salinities [C ~> ppt].
real, dimension(SZI_(G),SZK0_(GV)), &
intent(in) :: R0 !< Potential density referenced to
!! surface pressure [R ~> kg m-3].
Expand Down Expand Up @@ -940,7 +940,7 @@ subroutine mixedlayer_convection(h, d_eb, htot, Ttot, Stot, uhtot, vhtot, &
!! shortwave radiation.
real, dimension(max(nsw,1),SZI_(G)), intent(inout) :: Pen_SW_bnd !< The penetrating shortwave
!! heating at the sea surface in each penetrating
!! band [degC H ~> C m or degC kg m-2].
!! band [C H ~> degC m or degC kg m-2].
real, dimension(max(nsw,1),SZI_(G),SZK_(GV)), intent(in) :: opacity_band !< The opacity in each band of
!! penetrating shortwave radiation [H-1 ~> m-1 or m2 kg-1].
real, dimension(SZI_(G)), intent(out) :: Conv_En !< The buoyant turbulent kinetic energy source
Expand Down Expand Up @@ -1465,9 +1465,9 @@ subroutine mechanical_entrainment(h, d_eb, htot, Ttot, Stot, uhtot, vhtot, &
real, dimension(SZI_(G),SZK_(GV)), &
intent(in) :: v !< Zonal velocities interpolated to h points [L T-1 ~> m s-1].
real, dimension(SZI_(G),SZK0_(GV)), &
intent(in) :: T !< Layer temperatures [degC].
intent(in) :: T !< Layer temperatures [C ~> degC].
real, dimension(SZI_(G),SZK0_(GV)), &
intent(in) :: S !< Layer salinities [ppt].
intent(in) :: S !< Layer salinities [S ~> ppt].
real, dimension(SZI_(G),SZK0_(GV)), &
intent(in) :: R0 !< Potential density referenced to
!! surface pressure [R ~> kg m-3].
Expand All @@ -1478,7 +1478,7 @@ subroutine mechanical_entrainment(h, d_eb, htot, Ttot, Stot, uhtot, vhtot, &
intent(in) :: eps !< The negligibly small amount of water
!! that will be left in each layer [H ~> m or kg m-2].
real, dimension(SZI_(G)), intent(in) :: dR0_dT !< The partial derivative of R0 with respect to
!! temperature [R degC-1 ~> kg m-3 degC-1].
!! temperature [R C-1 ~> kg m-3 degC-1].
real, dimension(SZI_(G)), intent(in) :: dRcv_dT !< The partial derivative of Rcv with respect to
!! temperature [R C-1 ~> kg m-3 degC-1].
real, dimension(2,SZI_(G)), intent(in) :: cMKE !< Coefficients of HpE and HpE^2 used in calculating the
Expand Down Expand Up @@ -1832,8 +1832,8 @@ subroutine resort_ML(h, T, S, R0, Rcv, RcvTgt, eps, d_ea, d_eb, ksort, G, GV, CS
!! structure.
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: h !< Layer thickness [H ~> m or kg m-2].
!! Layer 0 is the new mixed layer.
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: T !< Layer temperatures [degC].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: S !< Layer salinities [ppt].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: T !< Layer temperatures [C ~> degC].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: S !< Layer salinities [S ~> ppt].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: R0 !< Potential density referenced to
!! surface pressure [R ~> kg m-3].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: Rcv !< The coordinate defining
Expand Down Expand Up @@ -2151,8 +2151,8 @@ subroutine mixedlayer_detrain_2(h, T, S, R0, Rcv, RcvTgt, dt, dt_diag, d_ea, j,
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: h !< Layer thickness [H ~> m or kg m-2].
!! Layer 0 is the new mixed layer.
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: T !< Potential temperature [degC].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: S !< Salinity [ppt].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: T !< Potential temperature [C ~> degC].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: S !< Salinity [S ~> ppt].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: R0 !< Potential density referenced to
!! surface pressure [R ~> kg m-3].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: Rcv !< The coordinate defining potential
Expand Down Expand Up @@ -3040,8 +3040,8 @@ subroutine mixedlayer_detrain_1(h, T, S, R0, Rcv, RcvTgt, dt, dt_diag, d_ea, d_e
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: h !< Layer thickness [H ~> m or kg m-2].
!! Layer 0 is the new mixed layer.
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: T !< Potential temperature [degC].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: S !< Salinity [ppt].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: T !< Potential temperature [C ~> degC].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: S !< Salinity [S ~> ppt].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: R0 !< Potential density referenced to
!! surface pressure [R ~> kg m-3].
real, dimension(SZI_(G),SZK0_(GV)), intent(inout) :: Rcv !< The coordinate defining potential
Expand Down
24 changes: 12 additions & 12 deletions src/parameterizations/vertical/MOM_full_convection.F90
Original file line number Diff line number Diff line change
Expand Up @@ -270,22 +270,22 @@ end subroutine full_convection
!! above and below, including partial calculations from a tridiagonal solver.
function is_unstable(dRho_dT, dRho_dS, h_a, h_b, mix_A, mix_B, T_a, T_b, S_a, S_b, &
Te_aa, Te_bb, Se_aa, Se_bb, d_A, d_B)
real, intent(in) :: dRho_dT !< The derivative of in situ density with temperature [R degC-1 ~> kg m-3 degC-1]
real, intent(in) :: dRho_dS !< The derivative of in situ density with salinity [R ppt-1 ~> kg m-3 ppt-1]
real, intent(in) :: dRho_dT !< The derivative of in situ density with temperature [R C-1 ~> kg m-3 degC-1]
real, intent(in) :: dRho_dS !< The derivative of in situ density with salinity [R S-1 ~> kg m-3 ppt-1]
real, intent(in) :: h_a !< The thickness of the layer above [H ~> m or kg m-2]
real, intent(in) :: h_b !< The thickness of the layer below [H ~> m or kg m-2]
real, intent(in) :: mix_A !< The time integrated mixing rate of the interface above [H ~> m or kg m-2]
real, intent(in) :: mix_B !< The time integrated mixing rate of the interface below [H ~> m or kg m-2]
real, intent(in) :: T_a !< The initial temperature of the layer above [degC]
real, intent(in) :: T_b !< The initial temperature of the layer below [degC]
real, intent(in) :: S_a !< The initial salinity of the layer below [ppt]
real, intent(in) :: S_b !< The initial salinity of the layer below [ppt]
real, intent(in) :: Te_aa !< The estimated temperature two layers above rescaled by d_A [degC]
real, intent(in) :: Te_bb !< The estimated temperature two layers below rescaled by d_B [degC]
real, intent(in) :: Se_aa !< The estimated salinity two layers above rescaled by d_A [ppt]
real, intent(in) :: Se_bb !< The estimated salinity two layers below rescaled by d_B [ppt]
real, intent(in) :: d_A !< The rescaling dependency across the interface above, nondim.
real, intent(in) :: d_B !< The rescaling dependency across the interface below, nondim.
real, intent(in) :: T_a !< The initial temperature of the layer above [C ~> degC]
real, intent(in) :: T_b !< The initial temperature of the layer below [C ~> degC]
real, intent(in) :: S_a !< The initial salinity of the layer below [S ~> ppt]
real, intent(in) :: S_b !< The initial salinity of the layer below [S ~> ppt]
real, intent(in) :: Te_aa !< The estimated temperature two layers above rescaled by d_A [C ~> degC]
real, intent(in) :: Te_bb !< The estimated temperature two layers below rescaled by d_B [C ~> degC]
real, intent(in) :: Se_aa !< The estimated salinity two layers above rescaled by d_A [S ~> ppt]
real, intent(in) :: Se_bb !< The estimated salinity two layers below rescaled by d_B [S ~> ppt]
real, intent(in) :: d_A !< The rescaling dependency across the interface above [nondim]
real, intent(in) :: d_B !< The rescaling dependency across the interface below [nondim]
logical :: is_unstable !< The return value, true if the profile is statically unstable
!! around the interface in question.

Expand Down
2 changes: 1 addition & 1 deletion src/parameterizations/vertical/MOM_opacity.F90
Original file line number Diff line number Diff line change
Expand Up @@ -568,7 +568,7 @@ subroutine absorbRemainingSW(G, GV, US, h, opacity_band, nsw, optics, j, dt, H_l
real, dimension(SZI_(G)), optional, intent(inout) :: Ttot !< Depth integrated mixed layer
!! temperature [C H ~> degC m or degC kg m-2]
real, dimension(SZI_(G),SZK_(GV)), optional, intent(in) :: dSV_dT !< The partial derivative of specific volume
!! with temperature [R-1 degC-1 ~> m3 kg-1 degC-1]
!! with temperature [R-1 C-1 ~> m3 kg-1 degC-1]
real, dimension(SZI_(G),SZK_(GV)), optional, intent(inout) :: TKE !< The TKE sink from mixing the heating
!! throughout a layer [R Z3 T-2 ~> J m-2].

Expand Down
Loading

0 comments on commit 31d4117

Please sign in to comment.