Skip to content

Commit

Permalink
Documented 105 heat flux 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 105 variables, including numerous heat fluxes.  Only comments have been
changed and all answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Jan 31, 2019
1 parent e7de91a commit 42d6116
Show file tree
Hide file tree
Showing 9 changed files with 105 additions and 105 deletions.
28 changes: 14 additions & 14 deletions src/SIS2_ice_thm.F90
Original file line number Diff line number Diff line change
Expand Up @@ -165,12 +165,12 @@ subroutine ice_temp_SIS2(m_pond, m_snow, m_ice, enthalpy, sice, SF_0, dSF_dT, so
!! snow and ice, in enth_unit (J kg-1).
real, dimension(NkIce), &
intent(in) :: Sice !< ice salinity by layer (g/kg)
real, intent(in ) :: SF_0 !< net upward surface heat flux at ts=0 (W/m^2)
real, intent(in ) :: SF_0 !< net upward surface heat flux at ts=0 [W m-2]
real, intent(in ) :: dSF_dT !< d(sfc heat flux)/d(ts) [W m-2 degC-1]
real, dimension(0:NkIce), &
intent(in) :: sol !< Solar heating of the snow and ice layers (W m-2)
intent(in) :: sol !< Solar heating of the snow and ice layers [W m-2]
real, intent(in ) :: tfw !< seawater freezing temperature [degC]
real, intent(in ) :: fb !< heat flux upward from ocean to ice bottom (W/m^2)
real, intent(in ) :: fb !< heat flux upward from ocean to ice bottom [W m-2]
real, intent( out) :: tsurf !< surface temperature [degC]
real, intent(in ) :: dtt !< timestep (sec)
integer, intent(in ) :: NkIce !< The number of ice layers.
Expand All @@ -183,7 +183,7 @@ subroutine ice_temp_SIS2(m_pond, m_snow, m_ice, enthalpy, sice, SF_0, dSF_dT, so
! variables for temperature calculation [see Winton (1999) section II.A.]
! note: here equations are multiplied by hi to improve thin ice accuracy
!
! real :: A ! Net downward surface heat flux from the atmosphere at 0C (W/m^2)
! real :: A ! Net downward surface heat flux from the atmosphere at 0C [W m-2]
! real, dimension(0:NkIce) :: &
! temp_est, & ! An estimated snow and ice temperature [degC].
! temp_IC, & ! The temperatures of the snow and ice based on the initial
Expand Down Expand Up @@ -216,7 +216,7 @@ subroutine ice_temp_SIS2(m_pond, m_snow, m_ice, enthalpy, sice, SF_0, dSF_dT, so
real, dimension(0:NkIce) :: bb ! Effective layer heat capacities.
real, dimension(0:NkIce) :: cc_bb ! Remaining coupling ratios.
real, dimension(-1:NkIce) :: heat_flux_int ! The downward heat fluxes at the
! interfaces between layers, in W m-2.
! interfaces between layers [W m-2].
! heat_flux_int uses the index convention from
! MOM6 that interface K is below layer k.
real :: I_liq_lim ! The inverse of CS%liq_lim.
Expand Down Expand Up @@ -546,10 +546,10 @@ subroutine estimate_tsurf(m_pond, m_snow, m_ice, enthalpy, sice, SF_0, dSF_dT, &
!! snow and ice, in enth_unit (J kg-1).
real, dimension(NkIce), &
intent(in) :: Sice !< ice salinity by layer (g/kg)
real, intent(in ) :: SF_0 !< net upward surface heat flux when Tsurf=0 (W/m^2)
real, intent(in ) :: SF_0 !< net upward surface heat flux when Tsurf=0 [W m-2]
real, intent(in ) :: dSF_dT !< d(sfc heat flux)/d(ts) [W m-2 degC-1]
real, dimension(0:NkIce), &
intent(in) :: sol !< Solar heating of the snow and ice layers (W m-2)
intent(in) :: sol !< Solar heating of the snow and ice layers [W m-2]
real, intent(in ) :: tfw !< seawater freezing temperature [degC]
real, intent( out) :: tsurf !< surface temperature [degC]
real, intent(in ) :: dtt !< timestep (sec)
Expand Down Expand Up @@ -581,7 +581,7 @@ subroutine estimate_tsurf(m_pond, m_snow, m_ice, enthalpy, sice, SF_0, dSF_dT, &
real :: tsf ! The surface freezing temperature [degC].
real :: k0a_x_ta ! The surface heat flux times normalized by 1 + the ratio
! of the temperature feedback on surface fluces to the
! skin-snow conductive sensitivity, in W m-2.
! skin-snow conductive sensitivity [W m-2].
real :: tsurf_est ! An estimate of the surface temperature [degC].
real, dimension(0:NkIce+1) :: cc ! Interfacial coupling coefficients.
real, dimension(0:NkIce) :: bb ! Effective layer heat capacities.
Expand Down Expand Up @@ -864,20 +864,20 @@ subroutine update_lay_enth(m_lay, sice, enth, ftop, ht_body, fbot, dftop_dT, &
real, intent(inout) :: enth !< ice enthalpy in enth_units [Enth ~> J kg-1].
real, intent(inout) :: ftop !< Downward heat flux atop the layer at T = 0 degC, or
!! the prescribed heat flux if dftop_dT = 0 [W m-2].
real, intent(in) :: ht_body !< Body forcing to layer in W/m2
real, intent(in) :: ht_body !< Body heating to layer [W m-2]
real, intent(inout) :: fbot !< Downward heat below the layer at T = 0 degC [W m-2].
real, intent(in) :: dftop_dT !< The linearization of ftop with layer temperature [W m-2 degC-1].
real, intent(in) :: dfbot_dT !< The linearization of fbot with layer temperature [W m-2 degC-1].
real, intent(in) :: dtt !< The timestep in s.
real, intent(in) :: hf_err_rat !< A conversion factor for comparing the errors
!! in explicit and implicit estimates of the updated
!! heat fluxes [ (kg m-2) / (W m-2 K-1) ].
!! heat fluxes [kg degC W-1].
type(ice_thermo_type), intent(in) :: ITV !< The ice thermodynamic parameter structure.
real, intent(out) :: extra_heat !< The heat above the melt point, in J.
real, optional, intent(out) :: temp_new !< The new temperature [degC].
real, optional, intent(in) :: temp_max !< The maximum new temperature [degC].

real :: htg ! The rate of heating of the layer in W m-2.
real :: htg ! The rate of heating of the layer [W m-2].
real :: new_temp ! The new layer temperature [degC].
real :: max_temp ! The maximum new layer temperature [degC].
real :: max_enth ! The maximum new layer enthalpy [degC].
Expand All @@ -892,7 +892,7 @@ subroutine update_lay_enth(m_lay, sice, enth, ftop, ht_body, fbot, dftop_dT, &
! in units of K / Enth_unit.
real :: En_J ! The enthalpy in Joules with 0 offset for liquid at 0 degC.
real :: T_fr ! Ice freezing temperature (determined by bulk salinity) [degC].
real :: fbot_in, ftop_in ! Input values of fbot and ftop in W m-2.
real :: fbot_in, ftop_in ! Input values of fbot and ftop [W m-2].
real :: dflux_dtot_dT ! A temporary work array in units of degC.

real :: T_g ! The latest best guess at Temp [degC].
Expand Down Expand Up @@ -1121,8 +1121,8 @@ subroutine ice_check(ms, mi, enthalpy, s_ice, NkIce, msg_part, ITV, &
integer, intent(in) :: NkIce !< The number of vertical temperature layers in the ice
character(len=*), intent(in) :: msg_part !< An identifying message
type(ice_thermo_type), intent(in) :: ITV !< The ice thermodynamic parameter structure.
real, optional, intent(in) :: bmelt !< The heat flux assocated with bottom melt in W m-2
real, optional, intent(in) :: tmelt !< The heat flux assocated with top melt in W m-2
real, optional, intent(in) :: bmelt !< The heat flux assocated with bottom melt [W m-2]
real, optional, intent(in) :: tmelt !< The heat flux assocated with top melt [W m-2]
real, optional, intent(in) :: t_sfc !< The ice surface temperature [degC]

character(len=300) :: mesg
Expand Down
46 changes: 23 additions & 23 deletions src/SIS_fast_thermo.F90
Original file line number Diff line number Diff line change
Expand Up @@ -110,29 +110,29 @@ subroutine sum_top_quantities (FIA, ABT, flux_u, flux_v, flux_sh, evap, &
intent(in) :: flux_v !< The grid-wise quasi-meridional wind stress on the ice [Pa].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: flux_sh !< The upward sensible heat flux from the top of the ice into
!! the atmosphere in W m-2.
!! the atmosphere [W m-2].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: evap !< The upward flux of water due to sublimation or evaporation
!! from the top of the ice to the atmosphere [kg m-2 s-1].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: flux_lw !< The net longwave heat flux from the atmosphere into the
!! ice or ocean, in W m-2.
!! ice or ocean [W m-2].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: lprec !< The liquid precipitation onto the ice [kg m-2 s-1].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: fprec !< The frozen precipitation onto the ice [kg m-2 s-1].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: flux_lh !< The upward latent heat flux associated with sublimation or
!! evaporation, in W m-2.
!! evaporation [W m-2].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: sh_T0 !< The upward sensible heat flux from the top of the ice into
!! the atmosphere when the skin temperature is 0 degC, in W m-2.
!! the atmosphere when the skin temperature is 0 degC [W m-2].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: evap_T0 !< The sublimation rate when the skin temperature is 0 degC,
!! [kg m-2 s-1].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: lw_T0 !< The downward longwave heat flux from the atmosphere into the
!! ice or ocean when the skin temperature is 0 degC, in W m-2.
!! ice or ocean when the skin temperature is 0 degC [W m-2].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce), &
intent(in) :: dshdt !< The derivative of the upward sensible heat flux from the
!! the top of the ice into the atmosphere with ice skin
Expand All @@ -148,7 +148,7 @@ subroutine sum_top_quantities (FIA, ABT, flux_u, flux_v, flux_sh, evap, &
real, dimension(G%isd:G%ied,G%jsd:G%jed), &
intent(in) :: SST !< The sea surface temperature [degC].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce,size(FIA%flux_sw_top,4)), &
intent(in) :: flux_sw !< The downward shortwave heat fluxes in W m-2. The 4th
intent(in) :: flux_sw !< The downward shortwave heat fluxes [W m-2]. The 4th
!! dimension is a combination of angular orientation & frequency.

real :: t_sfc
Expand Down Expand Up @@ -588,39 +588,39 @@ subroutine do_update_ice_model_fast(Atmos_boundary, IST, sOSS, Rad, FIA, &

real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce) :: &
flux_sh, & ! The upward sensible heat flux from the ice to the atmosphere
! at the surface of the ice, in W m-2.
! at the surface of the ice [W m-2].
evap, & ! The upward flux of water due to sublimation or evaporation
! from the top of the ice to the atmosphere [kg m-2 s-1].
flux_lh, & ! The upward latent heat flux associated with sublimation or
! evaporation, in W m-2.
flux_lw, & ! The net downward longwave heat flux into the ice, in W m-2.
! evaporation [W m-2].
flux_lw, & ! The net downward longwave heat flux into the ice [W m-2].
flux_u, flux_v, lprec, fprec, &

sh_T0, & ! The upward sensible heat flux from the top of the ice into
! the atmosphere when the skin temperature is 0 degC, in W m-2.
! the atmosphere when the skin temperature is 0 degC [W m-2].
evap_T0, & ! The sublimation rate when the skin temperature is 0 degC,
! [kg m-2 s-1].
lw_T0, & ! The downward longwave heat flux from the atmosphere into the
! ice or ocean when the skin temperature is 0 degC, in W m-2.
! ice or ocean when the skin temperature is 0 degC [W m-2].
dshdt, & ! The derivative of the upward sensible heat flux with the surface
! temperature [W m-2 degC-1].
devapdt, & ! The derivative of the sublimation rate with the surface
! temperature [kg m-2 s-1 degC-1].
dlwdt ! The derivative of the downward radiative heat flux with surface
! temperature (i.e. d(flux_lw)/d(surf_temp)) [W m-2 degC-1].
real, dimension(G%isd:G%ied,G%jsd:G%jed,0:IG%CatIce,size(FIA%flux_sw_top,4)) :: &
flux_sw ! The downward shortwave heat fluxes in W m-2. The fourth
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(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, in W m-2.
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, in s.
real :: Tskin ! The new skin temperature [degC].
real :: dTskin ! The change in the skin temperatue [degC].
real :: latent ! The latent heat of sublimation of ice or snow, in J kg.
real :: hf_0 ! The positive upward surface heat flux when T_sfc = 0 degC, in W m-2.
real :: dhf_dt ! The deriviative of the upward surface heat flux with Ts, in W m-2 C-1.
real :: hf_0 ! The positive upward surface heat flux when T_sfc = 0 degC [W m-2].
real :: dhf_dt ! The deriviative of the upward surface heat flux with Ts [W m-2 degC-1].
real :: sw_tot ! sum over all shortwave (dir/dif and vis/nir) components
real :: snow_wt ! A fractional weighting of snow in the category surface area.
real :: LatHtVap ! The latent heat of vaporization of water at 0C in J/kg.
Expand Down Expand Up @@ -876,16 +876,16 @@ subroutine redo_update_ice_model_fast(IST, sOSS, Rad, FIA, TSF, optics_CSp, &
S_col ! The thermodynamic salinity of a column of ice, in g/kg.
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, in W m-2.
SW_abs_col, & ! The shortwave absorption within a column of snow and ice [W m-2].
enth_col, & ! The enthalpy of a column of snow and ice, in enth_unit (J/kg?).
enth_col_in ! The initial enthalpy of a column of snow and ice,
! in enth_unit (J/kg?).

real :: dt_here ! The time step here, in s.
real :: Tskin ! The new skin temperature [degC].
real :: latent ! The latent heat of sublimation of ice or snow, in J kg.
real :: hf_0 ! The positive upward surface heat flux when T_sfc = 0 degC, in W m-2.
real :: dhf_dt ! The deriviative of the upward surface heat flux with Ts, in W m-2 C-1.
real :: hf_0 ! The positive upward surface heat flux when T_sfc = 0 degC [W m-2].
real :: dhf_dt ! The deriviative of the upward surface heat flux with Ts [W m-2 degC-1].
real :: sw_tot ! sum over dir/dif vis/nir components
real :: rho_ice ! The nominal density of sea ice [kg m-3].
real :: rho_snow ! The nominal density of snow [kg m-3].
Expand All @@ -899,13 +899,13 @@ subroutine redo_update_ice_model_fast(IST, sOSS, Rad, FIA, TSF, optics_CSp, &
real, dimension(G%isd:G%ied,size(FIA%flux_sw_top,4)) :: &
sw_tot_ice_band ! The total shortwave radiation by band, integrated
! across the ice thickness partitions, but not the open
! ocean partition, in W m-2.
! ocean partition [W m-2].
real, dimension(G%isd:G%ied,G%jsd:G%jed,IG%CatIce,size(FIA%flux_sw_top,4)) :: &
sw_top_chg ! The change in the shortwave down due to the new albedos.
real :: flux_sw_prev ! The previous value of flux_sw_top, in W m-2.
real :: flux_sw_prev ! The previous value of flux_sw_top [W m-2].
real :: rescale ! A rescaling factor between 0 and 1.
real :: bmelt_tmp, tmelt_tmp ! Temporary arrays, in J m-2.
real :: dSWt_dt ! The derivative of SW_tot with skin temperature, in W m-2 C-1.
real :: dSWt_dt ! The derivative of SW_tot with skin temperature [W m-2 degC-1].
real :: Tskin_prev ! The previous value of Tskin
real :: T_bright ! A skin temperature below which the snow and ice attain
! their greatest brightness and albedo no longer varies [degC].
Expand All @@ -919,9 +919,9 @@ subroutine redo_update_ice_model_fast(IST, sOSS, Rad, FIA, TSF, optics_CSp, &
integer :: b, b2, nb, nbmerge, itt, max_itt

real :: ice_sw_tot ! The sum of shortwave fluxes into the ice and snow, but
! excluding the fluxes transmitted to the ocean, in W m-2.
! excluding the fluxes transmitted to the ocean [W m-2].
real :: TSF_sw_tot ! The total of all shortwave fluxes into the snow, ice,
! and ocean that were previouslly stored in TSF, in W m-2.
! and ocean that were previouslly stored in TSF [W m-2].

real :: enth_units ! A conversion factor from Joules kg-1 to enthalpy units.
real :: I_Nk
Expand Down
16 changes: 8 additions & 8 deletions src/SIS_optics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -213,10 +213,10 @@ subroutine ice_optics_SIS2(mp, hs, hi, ts, tfw, NkIce, albedos, abs_sfc, &
Tsfc , & ! surface temperature
coszen , & ! cosine of solar zenith angle
tarea , & ! cell area - not used
swvdr , & ! sw down, visible, direct (W/m^2)
swvdf , & ! sw down, visible, diffuse (W/m^2)
swidr , & ! sw down, near IR, direct (W/m^2)
swidf ! sw down, near IR, diffuse (W/m^2)
swvdr , & ! sw down, visible, direct [W m-2]
swvdf , & ! sw down, visible, diffuse [W m-2]
swidr , & ! sw down, near IR, direct [W m-2]
swidf ! sw down, near IR, diffuse [W m-2]

! outputs
real (kind=dbl_kind), dimension (1,1) :: &
Expand All @@ -236,15 +236,15 @@ subroutine ice_optics_SIS2(mp, hs, hi, ts, tfw, NkIce, albedos, abs_sfc, &
alvdf , & ! visible, diffuse, albedo (fraction)
alidr , & ! near-ir, direct, albedo (fraction)
alidf , & ! near-ir, diffuse, albedo (fraction)
fswsfc , & ! SW absorbed at snow/bare ice/pondedi ice surface (W m-2)
fswsfc , & ! SW absorbed at snow/bare ice/pondedi ice surface [W m-2]
fswint , & ! SW interior absorption (below surface, above ocean,W m-2)
fswthru ! SW through snow/bare ice/ponded ice into ocean (W m-2)
fswthru ! SW through snow/bare ice/ponded ice into ocean [W m-2]

real (kind=dbl_kind), dimension (1,1,1) :: &
Sswabs ! SW absorbed in snow layer (W m-2)
Sswabs ! SW absorbed in snow layer [W m-2]

real (kind=dbl_kind), dimension (1,1,NkIce) :: &
Iswabs ! SW absorbed in ice layer (W m-2)
Iswabs ! SW absorbed in ice layer [W m-2]

real (kind=dbl_kind), dimension (1,1) :: &
albice , & ! bare ice albedo, for history
Expand Down
Loading

0 comments on commit 42d6116

Please sign in to comment.