Skip to content

Commit

Permalink
Merge branch 'dev/gfdl' into document_EOS_units
Browse files Browse the repository at this point in the history
  • Loading branch information
marshallward authored Feb 2, 2023
2 parents 84fd11d + 454c5c6 commit 0903142
Show file tree
Hide file tree
Showing 42 changed files with 572 additions and 472 deletions.
12 changes: 6 additions & 6 deletions src/core/MOM_CoriolisAdv.F90
Original file line number Diff line number Diff line change
Expand Up @@ -189,12 +189,12 @@ subroutine CorAdCalc(u, v, h, uh, vh, CAu, CAv, OBC, AD, G, GV, US, CS, pbv, Wav
real, dimension(SZIB_(G),SZJB_(G),SZK_(GV)) :: &
PV, & ! A diagnostic array of the potential vorticities [H-1 T-1 ~> m-1 s-1 or m2 kg-1 s-1].
RV ! A diagnostic array of the relative vorticities [T-1 ~> s-1].
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)) :: CAuS !
real, dimension(SZI_(G),SZJB_(G),SZK_(G)) :: CAvS !
real :: fv1, fv2, fv3, fv4 ! (f+rv)*v [L T-2 ~> m s-2].
real :: fu1, fu2, fu3, fu4 ! -(f+rv)*u [L T-2 ~> m s-2].
real :: max_fv, max_fu ! The maximum or minimum of the neighboring Coriolis
real :: min_fv, min_fu ! accelerations [L T-2 ~> m s-2], i.e. max(min)_fu(v)q.
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)) :: CAuS ! Stokes contribution to CAu [L T-2 ~> m s-2]
real, dimension(SZI_(G),SZJB_(G),SZK_(G)) :: CAvS ! Stokes contribution to CAv [L T-2 ~> m s-2]
real :: fv1, fv2, fv3, fv4 ! (f+rv)*v at the 4 points surrounding a u points[L T-2 ~> m s-2]
real :: fu1, fu2, fu3, fu4 ! -(f+rv)*u at the 4 points surrounding a v point [L T-2 ~> m s-2]
real :: max_fv, max_fu ! The maximum of the neighboring Coriolis accelerations [L T-2 ~> m s-2]
real :: min_fv, min_fu ! The minimum of the neighboring Coriolis accelerations [L T-2 ~> m s-2]

real, parameter :: C1_12 = 1.0 / 12.0 ! C1_12 = 1/12 [nondim]
real, parameter :: C1_24 = 1.0 / 24.0 ! C1_24 = 1/24 [nondim]
Expand Down
6 changes: 3 additions & 3 deletions src/core/MOM_checksum_packages.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,9 +29,9 @@ module MOM_checksum_packages

!> A type for storing statistica about a variable
type :: stats ; private
real :: minimum = 1.E34 !< The minimum value
real :: maximum = -1.E34 !< The maximum value
real :: average = 0. !< The average value
real :: minimum = 1.E34 !< The minimum value [degC] or [ppt] or other units
real :: maximum = -1.E34 !< The maximum value [degC] or [ppt] or other units
real :: average = 0. !< The average value [degC] or [ppt] or other units
end type stats

contains
Expand Down
6 changes: 3 additions & 3 deletions src/core/MOM_density_integrals.F90
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,7 @@ subroutine int_density_dz_generic_pcm(T, S, z_t, z_b, rho_ref, rho_0, G_e, HI, &
real :: p5(5) ! Pressures at five quadrature points [R L2 T-2 ~> Pa]
real :: r5(5) ! Densities at five quadrature points [R ~> kg m-3]
real :: rho_anom ! The depth averaged density anomaly [R ~> kg m-3]
real, parameter :: C1_90 = 1.0/90.0 ! Rational constants.
real, parameter :: C1_90 = 1.0/90.0 ! A rational constant [nondim]
real :: GxRho ! The product of the gravitational acceleration and reference density [R L2 Z-1 T-2 ~> Pa m-1]
real :: I_Rho ! The inverse of the Boussinesq density [R-1 ~> m3 kg-1]
real :: dz ! The layer thickness [Z ~> m]
Expand Down Expand Up @@ -784,7 +784,7 @@ subroutine int_density_dz_generic_ppm(k, tv, T_t, T_b, S_t, S_b, e, &
real :: w_left, w_right ! Left and right weights [nondim]
real :: intz(5) ! The gravitational acceleration times the integrals of density
! with height at the 5 sub-column locations [R L2 T-2 ~> Pa]
real, parameter :: C1_90 = 1.0/90.0 ! Rational constants.
real, parameter :: C1_90 = 1.0/90.0 ! A rational constant [nondim]
real :: GxRho ! The gravitational acceleration times density [R L2 Z-1 T-2 ~> kg m-2 s-2]
real :: I_Rho ! The inverse of the Boussinesq density [R-1 ~> m3 kg-1]
real :: dz ! Layer thicknesses at tracer points [Z ~> m]
Expand Down Expand Up @@ -1175,7 +1175,7 @@ subroutine int_spec_vol_dp_generic_pcm(T, S, p_t, p_b, alpha_ref, HI, EOS, US, d
real :: intp(5) ! The integrals of specific volume with pressure at the
! 5 sub-column locations [L2 T-2 ~> m2 s-2]
logical :: do_massWeight ! Indicates whether to do mass weighting.
real, parameter :: C1_90 = 1.0/90.0 ! A rational constant.
real, parameter :: C1_90 = 1.0/90.0 ! A rational constant [nondim]
integer :: Isq, Ieq, Jsq, Jeq, ish, ieh, jsh, jeh, i, j, m, n, halo

Isq = HI%IscB ; Ieq = HI%IecB ; Jsq = HI%JscB ; Jeq = HI%JecB
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 @@ -29,7 +29,7 @@ module MOM_porous_barriers
type(diag_ctrl), pointer :: &
diag => Null() !< A structure to regulate diagnostic output timing
logical :: debug !< If true, write verbose checksums for debugging purposes.
real :: mask_depth !< The depth shallower than which porous barrier is not applied.
real :: mask_depth !< The depth shallower than which porous barrier is not applied [Z ~> m]
integer :: eta_interp !< An integer indicating how the interface heights at the velocity
!! points are calculated. Valid values are given by the parameters
!! defined below: MAX, MIN, ARITHMETIC and HARMONIC.
Expand Down
2 changes: 1 addition & 1 deletion src/ice_shelf/MOM_marine_ice.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ module MOM_marine_ice
type, public :: marine_ice_CS ; private
real :: kv_iceberg !< The viscosity of the icebergs [L4 Z-2 T-1 ~> m2 s-1] (for ice rigidity)
real :: berg_area_threshold !< Fraction of grid cell which iceberg must occupy
!! so that fluxes below are set to zero. (0.5 is a
!! so that fluxes below are set to zero [nondim]. (0.5 is a
!! good value to use.) Not applied for negative values.
real :: latent_heat_fusion !< Latent heat of fusion [Q ~> J kg-1]
real :: density_iceberg !< A typical density of icebergs [R ~> kg m-3] (for ice rigidity)
Expand Down
4 changes: 3 additions & 1 deletion src/ice_shelf/user_shelf_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,9 @@ subroutine USER_update_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, G, C
logical, intent(in) :: new_sim !< If true, this the start of a new run.


real :: c1, edge_pos, slope_pos
real :: c1 ! The inverse of the range over which the shelf slopes [km-1]
real :: edge_pos ! The time-evolving position the ice shelf edge [km]
real :: slope_pos ! The time-evolving position of the start of the ice shelf slope [km]
integer :: i, j

edge_pos = CS%pos_shelf_edge_0 + CS%shelf_speed*(time_type_to_real(Time) / 86400.0)
Expand Down
16 changes: 8 additions & 8 deletions src/initialization/MOM_grid_initialize.F90
Original file line number Diff line number Diff line change
Expand Up @@ -365,7 +365,7 @@ subroutine set_grid_metrics_cartesian(G, param_file, US)
real :: grid_lonT(G%isd:G%ied), grid_lonB(G%IsdB:G%IedB) ! Axis labels [degrees_E] or [km] or [m]
real :: dx_everywhere, dy_everywhere ! Grid spacings [L ~> m].
real :: I_dx, I_dy ! Inverse grid spacings [L-1 ~> m-1].
real :: PI
real :: PI ! The ratio of the circumference of a circle to its diameter [nondim]
character(len=80) :: units_temp
character(len=48) :: mdl = "MOM_grid_init set_grid_metrics_cartesian"

Expand Down Expand Up @@ -922,7 +922,7 @@ end function dL
!! function fn takes the value fnval, also returning in ittmax the number of iterations of
!! Newton's method that were used to polish the root.
function find_root( fn, dy_df, GP, fnval, y1, ymin, ymax, ittmax)
real :: find_root !< The value of y where fn(y) = fnval that will be returned
real :: find_root !< The value of y where fn(y) = fnval that will be returned [radians]
real, external :: fn !< The external function whose root is being sought [gridpoints]
real, external :: dy_df !< The inverse of the derivative of that function [radian gridpoint-1]
type(GPS), intent(in) :: GP !< A structure of grid parameters
Expand Down Expand Up @@ -1128,12 +1128,12 @@ end function Int_dj_dy

!> Extrapolates missing metric data into all the halo regions.
subroutine extrapolate_metric(var, jh, missing)
real, dimension(:,:), intent(inout) :: var !< The array in which to fill in halos [A]
real, dimension(:,:), intent(inout) :: var !< The array in which to fill in halos [abitrary]
integer, intent(in) :: jh !< The size of the halos to be filled
real, optional, intent(in) :: missing !< The missing data fill value, 0 by default [A]
real, optional, intent(in) :: missing !< The missing data fill value, 0 by default [abitrary]
! Local variables
real :: badval
integer :: i,j
real :: badval ! A bad data value [abitrary]
integer :: i, j

badval = 0.0 ; if (present(missing)) badval = missing

Expand Down Expand Up @@ -1162,8 +1162,8 @@ end subroutine extrapolate_metric
!> This function implements Adcroft's rule for reciprocals, namely that
!! Adcroft_Inv(x) = 1/x for |x|>0 or 0 for x=0.
function Adcroft_reciprocal(val) result(I_val)
real, intent(in) :: val !< The value being inverted.
real :: I_val !< The Adcroft reciprocal of val.
real, intent(in) :: val !< The value being inverted [abitrary]
real :: I_val !< The Adcroft reciprocal of val [abitrary-1]

I_val = 0.0
if (val /= 0.0) I_val = 1.0/val
Expand Down
6 changes: 3 additions & 3 deletions src/initialization/MOM_state_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -885,10 +885,10 @@ subroutine initialize_thickness_uniform(h, depth_tot, G, GV, param_file, just_re
!! parameters without changing h.
! Local variables
character(len=40) :: mdl = "initialize_thickness_uniform" ! This subroutine's name.
real :: e0(SZK_(GV)+1) ! The resting interface heights, in depth units, usually
real :: e0(SZK_(GV)+1) ! The resting interface heights [Z ~> m], usually
! negative because it is positive upward.
real :: eta1D(SZK_(GV)+1)! Interface height relative to the sea surface
! positive upward, in depth units.
real :: eta1D(SZK_(GV)+1)! Interface height relative to the sea surface,
! positive upward [Z ~> m].
integer :: i, j, k, is, ie, js, je, nz

is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = GV%ke
Expand Down
Loading

0 comments on commit 0903142

Please sign in to comment.