Skip to content

Commit

Permalink
Documented 72 salinity-related variable units
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 72 salinity-related variables, mostly using the notation [gSalt kg-1] for
salinities.  Only comments have been changed and all answers are bitwise
identical.
  • Loading branch information
Hallberg-NOAA committed Feb 1, 2019
1 parent 62e1aa1 commit 0c114e6
Show file tree
Hide file tree
Showing 10 changed files with 74 additions and 74 deletions.
84 changes: 42 additions & 42 deletions src/SIS2_ice_thm.F90

Large diffs are not rendered by default.

4 changes: 2 additions & 2 deletions src/SIS_fast_thermo.F90
Original file line number Diff line number Diff line change
Expand Up @@ -612,7 +612,7 @@ subroutine do_update_ice_model_fast(Atmos_boundary, IST, sOSS, Rad, FIA, &
flux_sw ! The downward shortwave heat fluxes [W m-2]. The fourth
! dimension is a combination of angular orientation and frequency.
real, dimension(0:IG%NkIce) :: T_col ! The temperature of a column of ice and snow [degC].
real, dimension(IG%NkIce) :: S_col ! The thermodynamic salinity of a column of ice, in g/kg.
real, dimension(IG%NkIce) :: S_col ! The thermodynamic salinity of a column of ice [gSalt kg-1].
real, dimension(0:IG%NkIce) :: enth_col ! The enthalpy of a column of snow and ice, in enth_unit (J/kg?).
real, dimension(0:IG%NkIce) :: SW_abs_col ! The shortwave absorption within a column of snow and ice [W m-2].
real :: dt_fast ! The fast thermodynamic time step [s].
Expand Down Expand Up @@ -873,7 +873,7 @@ subroutine redo_update_ice_model_fast(IST, sOSS, Rad, FIA, TSF, optics_CSp, &
type(ice_grid_type), intent(in) :: IG !< The ice vertical grid type

real, dimension(IG%NkIce) :: &
S_col ! The thermodynamic salinity of a column of ice, in g/kg.
S_col ! The thermodynamic salinity of a column of ice [gSalt kg-1].
real, dimension(0:IG%NkIce) :: &
T_col, & ! The temperature of a column of ice and snow [degC].
SW_abs_col, & ! The shortwave absorption within a column of snow and ice [W m-2].
Expand Down
4 changes: 2 additions & 2 deletions src/SIS_optics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -190,7 +190,7 @@ subroutine ice_optics_SIS2(mp, hs, hi, ts, tfw, NkIce, albedos, abs_sfc, &
real :: rho_water ! The nominal density of sea water [kg m-3].
real :: pen ! The fraction of the shortwave flux that will pass below
! the surface (frac 1-pen absorbed at the surface) [nondim]
real :: sal_ice_top(1) ! A specified surface salinity of ice [ppt].
real :: sal_ice_top(1) ! A specified surface salinity of ice [gSalt kg-1].
real :: temp_ice_freeze ! The freezing temperature of the top ice layer [degC].
integer :: m, b, nb
character(len=200) :: mesg
Expand Down Expand Up @@ -402,7 +402,7 @@ function bright_ice_temp(CS, ITV) result(bright_temp)
type(ice_thermo_type), intent(in) :: ITV !< The ice thermodynamic parameter structure.
real :: bright_temp

real :: salin_max ! The maximum attainable salinity, in PSU.
real :: salin_max ! The maximum attainable salinity [gSalt kg-1].
real :: temp_freeze_min ! The freezing temperature of water at salin_max [degC].

salin_max = 40.0
Expand Down
8 changes: 4 additions & 4 deletions src/SIS_slow_thermo.F90
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ module SIS_slow_thermo
type slow_thermo_CS ; private
logical :: specified_ice !< If true, the sea ice is specified and there is
!! no need for ice dynamics.
real :: ice_bulk_salin !< The globally constant sea ice bulk salinity, in g/kg
real :: ice_bulk_salin !< The globally constant sea ice bulk salinity [gSalt kg-1]
!! that is used to calculate the ocean salt flux.
real :: ice_rel_salin !< The initial bulk salinity of sea-ice relative to the
!! salinity of the water from which it formed, nondim.
Expand Down Expand Up @@ -589,13 +589,13 @@ subroutine SIS2_thermodynamics(IST, dt_slow, CS, OSS, FIA, IOF, G, IG)
real, dimension(SZI_(G),SZJ_(G),1:IG%CatIce) :: heat_in, enth_prev, enth
real, dimension(SZI_(G),SZJ_(G)) :: heat_in_col, enth_prev_col, enth_col, enth_mass_in_col

real, dimension(IG%NkIce) :: S_col ! The salinity of a column of ice, in g/kg.
real, dimension(IG%NkIce) :: S_col ! The salinity of a column of ice [gSalt kg-1].
real, dimension(IG%NkIce+1) :: Salin ! The conserved bulk salinity of each
! layer in g/kg, with the salinity of
! layer [gSalt kg-1], with the salinity of
! newly formed ice in layer NkIce+1.
real, dimension(0:IG%NkIce) :: m_lay ! The masses of a column of ice and snow [kg m-2].
real, dimension(0:IG%NkIce) :: Tcol0 ! The temperature of a column of ice and snow [degC].
real, dimension(0:IG%NkIce) :: S_col0 ! The salinity of a column of ice and snow, in g/kg.
real, dimension(0:IG%NkIce) :: S_col0 ! The salinity of a column of ice and snow [gSalt kg-1].
real, dimension(0:IG%NkIce) :: Tfr_col0 ! The freezing temperature of a column of ice and snow [degC].
real, dimension(0:IG%NkIce+1) :: &
enthalpy ! The initial enthalpy of a column of ice and snow
Expand Down
24 changes: 12 additions & 12 deletions src/SIS_sum_output.F90
Original file line number Diff line number Diff line change
Expand Up @@ -53,9 +53,9 @@ module SIS_sum_output
real :: fresh_water_input !< The total mass of fresh water added by
!! surface fluxes since the last time that
real :: salt_prev !< The total amount of salt in the sea ice the last
!! time that write_ice_statistics was called, in PSU kg.
!! time that write_ice_statistics was called [gSalt].
real :: net_salt_input !< The total salt added by surface fluxes since the last
!! time that write_ice_statistics was called, in PSU kg.
!! time that write_ice_statistics was called [gSalt].
real :: heat_prev !< The total amount of heat in the sea ice the last
!! time that write_ice_statistics was called [J].
real :: net_heat_input !< The total heat added by surface fluxes since the last
Expand Down Expand Up @@ -242,25 +242,25 @@ subroutine write_ice_statistics(IST, day, n, G, IG, CS, message, check_column, t
Heat_NS, & ! The total sea-ice enthalpy in the two hemispheres [J].
mass_NS, & ! The total sea-ice mass in the two hemispheres [kg].
salt_NS, & ! The total sea-ice salt in the two hemispheres [kg].
salinity_NS ! The average sea-ice salinity in the two hemispheres, in g/kg.
salinity_NS ! The average sea-ice salinity in the two hemispheres [gSalt kg-1].

real :: Mass ! The total mass of the sea ice and snow atop it [kg].
real :: mass_chg ! The change in total sea ice mass of fresh water since
! the last call to this subroutine [kg].
real :: mass_anom ! The change in fresh water that cannot be accounted for
! by the surface fluxes [kg].
real :: I_Mass ! Adcroft's rule reciprocal of mass: 1/Mass or 0 [kg-1].
real :: Salt ! The total amount of salt in the ocean, in PSU kg.
real :: Salt ! The total amount of salt in the ocean [gSalt].
real :: Salt_chg ! The change in total sea ice salt since the last call
! to this subroutine, in PSU kg.
! to this subroutine [gSalt].
real :: Salt_anom ! The change in salt that cannot be accounted for by
! the surface fluxes, in PSU kg.
! the surface fluxes [gSalt].
real :: Salt_anom_norm ! The salt anomaly normalized by salt (if it is nonzero).
real :: salin ! The mean salinity of the ocean, in PSU.
real :: salin ! The mean salinity of the ocean [gSalt kg-1].
real :: salin_chg ! The change in total salt since the last call
! to this subroutine divided by total mass, in PSU.
! to this subroutine divided by total mass [gSalt kg-1].
real :: salin_anom ! The change in total salt that cannot be accounted for by
! the surface fluxes divided by total mass in PSU.
! the surface fluxes divided by total mass [gSalt kg-1].
real :: salin_mass_in ! The mass of salt input since the last call [kg].
real :: Heat ! The total amount of Heat in the ocean [J].
real :: Heat_chg ! The change in total sea ice heat since the last call
Expand Down Expand Up @@ -525,8 +525,8 @@ subroutine write_ice_statistics(IST, day, n, G, IG, CS, message, check_column, t
! if (G%Boussinesq) then
mass_anom_EFP = mass_chg_EFP - CS%fresh_water_in_EFP
! else
! net_salt_input needs to be converted from psu m s-1 to kg m-2 s-1.
! mass_anom_EFP = mass_chg_EFP - CS%fresh_water_in_EFP
! net_salt_input needs to be converted from gSalt kg-1 m s-1 to kg m-2 s-1.
! salin_mass_in = 0.001*EFP_to_real(CS%net_salt_in_EFP)
! endif
mass_chg = EFP_to_real(mass_chg_EFP)
Expand Down Expand Up @@ -775,7 +775,7 @@ subroutine accumulate_input_1(IST, FIA, OSS, dt, G, IG, CS)
real, dimension(SZI_(G),SZJ_(G)) :: &
FW_in, & ! The net fresh water input, integrated over a timestep [kg].
salt_in, & ! The total salt added by surface fluxes, integrated
! over a time step [PSU kg].
! over a time step [gSalt].
heat_in ! The total heat added by surface fluxes, integrated
! over a time step [J].
real :: FW_input ! The net fresh water input, integrated over a timestep
Expand All @@ -788,7 +788,7 @@ subroutine accumulate_input_1(IST, FIA, OSS, dt, G, IG, CS)
real :: enth_units
type(EFP_type) :: &
FW_in_EFP, & ! Extended fixed point version of FW_input [kg]
salt_in_EFP, & ! Extended fixed point version of salt_input [PSU kg]
salt_in_EFP, & ! Extended fixed point version of salt_input [gSalt]
heat_in_EFP ! Extended fixed point version of heat_input [J]
integer :: i, j, k, isc, iec, jsc, jec, ncat, b, nb

Expand Down
6 changes: 3 additions & 3 deletions src/SIS_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ module SIS_types
t_surf !< The surface temperature, in Kelvin.

real, allocatable, dimension(:,:,:,:) :: sal_ice !< The salinity of the sea ice
!! in each category and fractional thickness layer, in g/kg.
!! in each category and fractional thickness layer [gSalt kg-1].
real, allocatable, dimension(:,:,:,:) :: enth_ice !< The enthalpy of the sea ice
!! in each category and fractional thickness layer, in enth_unit (J/kg or rescaled).
real, allocatable, dimension(:,:,:,:) :: enth_snow !< The enthalpy of the snow
Expand All @@ -99,7 +99,7 @@ module SIS_types
type ocean_sfc_state_type
! 7 of the following 9 variables describe the ocean state as seen by the sea ice.
real, allocatable, dimension(:,:) :: &
s_surf , & !< The ocean's surface salinity in g/kg.
s_surf , & !< The ocean's surface salinity [gSalt kg-1].
SST_C , & !< The ocean's bulk surface temperature [degC].
T_fr_ocn, & !< The freezing point temperature at the ocean's surface salinity [degC].
u_ocn_B, & !< The ocean's zonal velocity on B-grid points [m s-1].
Expand Down Expand Up @@ -139,7 +139,7 @@ module SIS_types
! The following 5 variables describe the ocean state as seen by the
! atmosphere and use for the rapid thermodynamic sea ice changes.
real, allocatable, dimension(:,:) :: &
s_surf , & !< The ocean's surface salinity in g/kg.
s_surf , & !< The ocean's surface salinity [gSalt kg-1].
SST_C , & !< The ocean's bulk surface temperature [degC].
T_fr_ocn, & !< The freezing point temperature at the ocean's surface salinity [degC].
u_ocn_A, & !< The ocean's zonal surface velocity on A-grid points [m s-1].
Expand Down
8 changes: 4 additions & 4 deletions src/ice_age_tracer.F90
Original file line number Diff line number Diff line change
Expand Up @@ -50,11 +50,11 @@ module ice_age_tracer
! can be found, or an empty string for internal initialization.
type(time_type), pointer :: Time !< A pointer to the ocean model's clock.
type(SIS_tracer_registry_type), pointer :: TrReg => NULL() !< A pointer to the tracer registry
real, pointer :: tr(:,:,:,:,:) => NULL() !< The array of tracers used in this subroutine, in g m-3?
real, pointer :: tr_aux(:,:,:,:,:) => NULL() !< The masked tracer concentration for output, in g m-3.
real, pointer :: tr(:,:,:,:,:) => NULL() !< The array of tracers used in this subroutine [g kg-1].
real, pointer :: tr_aux(:,:,:,:,:) => NULL() !< The masked tracer concentration for output [g kg-1].
type(p3d), dimension(NTR_MAX) :: &
tr_adx, & !< Tracer zonal advective fluxes in g m-3 m3 s-1.
tr_ady !< Tracer meridional advective fluxes in g m-3 m3 s-1.
tr_adx, & !< Tracer zonal advective fluxes [g s-1].
tr_ady !< Tracer meridional advective fluxes [g s-1].

real, pointer :: ocean_BC(:,:,:,:)=>NULL() !< Ocean boundary value of the tracer by category
real, pointer :: snow_BC(:,:,:,:)=>NULL() !< Snow boundary value of the tracer by category
Expand Down
2 changes: 1 addition & 1 deletion src/ice_boundary_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ module ice_boundary_types
v => NULL(), & !< The y-direction ocean velocity at a position
!! determined by stagger [m s-1].
t => NULL(), & !< The ocean's surface temperature, in Kelvin.
s => NULL(), & !< The ocean's surface salinity, in g/kg.
s => NULL(), & !< The ocean's surface salinity [gSalt kg-1].
frazil => NULL(), & !< The frazil heat rejected by the ocean [J m-2].
sea_level => NULL() !< The sea level after adjustment for any surface
!! pressure that the ocean allows to be expressed [m].
Expand Down
2 changes: 1 addition & 1 deletion src/ice_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1721,7 +1721,7 @@ subroutine ice_model_init(Ice, Time_Init, Time, Time_step_fast, Time_step_slow,
real, allocatable, target, dimension(:,:,:) :: t_snow_tmp
real, parameter :: T_0degC = 273.15 ! 0 degrees C in Kelvin
real :: g_Earth ! The gravitational acceleration [m s-2].
real :: ice_bulk_salin ! The globally constant sea ice bulk salinity, in g/kg
real :: ice_bulk_salin ! The globally constant sea ice bulk salinity [gSalt kg-1] = [ppt]
! that is used to calculate the ocean salt flux.
real :: ice_rel_salin ! The initial bulk salinity of sea-ice relative to the
! salinity of the water from which it formed, nondim.
Expand Down
6 changes: 3 additions & 3 deletions src/ice_type.F90
Original file line number Diff line number Diff line change
Expand Up @@ -77,17 +77,17 @@ module ice_type_mod
albedo_nir_dif => NULL(), & !< The surface albedo for diffuse near-infrared shortwave radiation
!! in each ice-thickness category. Nondim, between 0 and 1.
rough_mom => NULL(), & !< The roughness for momentum at the ocean surface, as provided by
!! ocean_rough_mod, apparently in m.
!! ocean_rough_mod, apparently [m].
rough_heat => NULL(), & !< The roughness for heat at the ocean surface, as provided by
!! ocean_rough_mod, apparently in m.
rough_moist => NULL(), & !< The roughness for moisture at the ocean surface, as provided by
!! ocean_rough_mod, apparently in m.
!! ocean_rough_mod, apparently [m].
t_surf => NULL(), & !< The surface temperature for the ocean or for
!! each ice-thickness category, in Kelvin.
u_surf => NULL(), & !< The eastward surface velocities of the ocean (:,:,1) or sea-ice [m s-1].
v_surf => NULL() !< The northward surface elocities of the ocean (:,:,1) or sea-ice [m s-1].
real, pointer, dimension(:,:) :: &
s_surf =>NULL() !< The ocean's surface salinity, in g/kg.
s_surf =>NULL() !< The ocean's surface salinity [gSalt kg-1].

! These arrays will be used to set the forcing for the ocean.
real, pointer, dimension(:,:) :: &
Expand Down

0 comments on commit 0c114e6

Please sign in to comment.