diff --git a/config_src/drivers/nuopc_cap/mom_cap.F90 b/config_src/drivers/nuopc_cap/mom_cap.F90
index d0ee3aad87..5f4b2e19ca 100644
--- a/config_src/drivers/nuopc_cap/mom_cap.F90
+++ b/config_src/drivers/nuopc_cap/mom_cap.F90
@@ -737,6 +737,10 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
Ice_ocean_boundary% hrofi (isc:iec,jsc:jec), &
Ice_ocean_boundary% hevap (isc:iec,jsc:jec), &
Ice_ocean_boundary% hcond (isc:iec,jsc:jec), &
+ Ice_ocean_boundary% lrunoff_glc (isc:iec,jsc:jec), &
+ Ice_ocean_boundary% frunoff_glc (isc:iec,jsc:jec), &
+ Ice_ocean_boundary% hrofl_glc (isc:iec,jsc:jec), &
+ Ice_ocean_boundary% hrofi_glc (isc:iec,jsc:jec), &
source=0.0)
! Needed for MARBL
@@ -797,6 +801,10 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
call fld_list_add(fldsToOcn_num, fldsToOcn, "Sa_pslv" , "will provide")
call fld_list_add(fldsToOcn_num, fldsToOcn, "Foxx_rofl" , "will provide") !-> liquid runoff
call fld_list_add(fldsToOcn_num, fldsToOcn, "Foxx_rofi" , "will provide") !-> ice runoff
+ if (cesm_coupled) then
+ call fld_list_add(fldsToOcn_num, fldsToOcn, "Forr_rofl_glc" , "will provide") !-> liquid glc runoff
+ call fld_list_add(fldsToOcn_num, fldsToOcn, "Forr_rofi_glc" , "will provide") !-> frozen glc runoff
+ endif
call fld_list_add(fldsToOcn_num, fldsToOcn, "Si_ifrac" , "will provide") !-> ice fraction
call fld_list_add(fldsToOcn_num, fldsToOcn, "So_duu10n" , "will provide") !-> wind^2 at 10m
call fld_list_add(fldsToOcn_num, fldsToOcn, "Fioi_meltw" , "will provide")
@@ -808,6 +816,10 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
call fld_list_add(fldsToOcn_num, fldsToOcn, "Foxx_hcond" , "will provide")
call fld_list_add(fldsToOcn_num, fldsToOcn, "Foxx_hrofl" , "will provide")
call fld_list_add(fldsToOcn_num, fldsToOcn, "Foxx_hrofi" , "will provide")
+ if (cesm_coupled) then
+ call fld_list_add(fldsToOcn_num, fldsToOcn, "Foxx_hrofl_glc" , "will provide")
+ call fld_list_add(fldsToOcn_num, fldsToOcn, "Foxx_hrofi_glc" , "will provide")
+ endif
if (Ice_ocean_boundary%ice_ncat > 0) then
call fld_list_add(fldsToOcn_num, fldsToOcn, "Sf_afracr", "will provide")
@@ -2855,6 +2867,34 @@ end subroutine shr_log_setLogUnit
!!
|
!!
!!
+!! Forr_rofl_glc |
+!! kg m-2 s-1 |
+!! runoff |
+!! mass flux of liquid glc runoff |
+!! |
+!!
+!!
+!! Forr_rofi_glc |
+!! kg m-2 s-1 |
+!! runoff |
+!! mass flux of frozen glc runoff |
+!! |
+!!
+!!
+!! Foxx_hrofi_glc |
+!! W m-2 |
+!! hrofi_glc |
+!! heat content (enthalpy) of frozen glc runoff |
+!! |
+!!
+!!
+!! Foxx_hrofl_glc |
+!! W m-2 |
+!! hrofl_glc |
+!! heat content (enthalpy) of liquid glc runoff |
+!! |
+!!
+!!
!! Fioi_salt |
!! kg m-2 s-1 |
!! salt_flux |
diff --git a/config_src/drivers/nuopc_cap/mom_cap_methods.F90 b/config_src/drivers/nuopc_cap/mom_cap_methods.F90
index d5ec9dc259..bb12dc6092 100644
--- a/config_src/drivers/nuopc_cap/mom_cap_methods.F90
+++ b/config_src/drivers/nuopc_cap/mom_cap_methods.F90
@@ -216,6 +216,22 @@ subroutine mom_import(ocean_public, ocean_grid, importState, ice_ocean_boundary,
isc, iec, jsc, jec, ice_ocean_boundary%frunoff, areacor=med2mod_areacor, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
+ ! liquid glc runoff
+ if ( associated(ice_ocean_boundary%lrunoff_glc) ) then
+ ice_ocean_boundary%lrunoff_glc (:,:) = 0._ESMF_KIND_R8
+ call state_getimport(importState, 'Forr_rofl_glc', &
+ isc, iec, jsc, jec, ice_ocean_boundary%lrunoff_glc, areacor=med2mod_areacor, rc=rc)
+ if (ChkErr(rc,__LINE__,u_FILE_u)) return
+ endif
+
+ ! frozen glc runoff
+ if ( associated(ice_ocean_boundary%frunoff_glc) ) then
+ ice_ocean_boundary%frunoff_glc (:,:) = 0._ESMF_KIND_R8
+ call state_getimport(importState, 'Forr_rofi_glc', &
+ isc, iec, jsc, jec, ice_ocean_boundary%frunoff_glc, areacor=med2mod_areacor, rc=rc)
+ if (ChkErr(rc,__LINE__,u_FILE_u)) return
+ endif
+
!----
! Enthalpy terms
!----
@@ -256,6 +272,23 @@ subroutine mom_import(ocean_public, ocean_grid, importState, ice_ocean_boundary,
if (ChkErr(rc,__LINE__,u_FILE_u)) return
end if
+ !----
+ ! enthalpy from liquid glc runoff (hrofl_glc)
+ !----
+ if ( associated(ice_ocean_boundary%hrofl_glc) ) then
+ call state_getimport(importState, 'Foxx_hrofl_glc', isc, iec, jsc, jec, &
+ ice_ocean_boundary%hrofl_glc, areacor=med2mod_areacor, rc=rc)
+ if (ChkErr(rc,__LINE__,u_FILE_u)) return
+ end if
+
+ !----
+ ! enthalpy from frozen glc runoff (hrofi_glc)
+ !----
+ if ( associated(ice_ocean_boundary%hrofi_glc) ) then
+ call state_getimport(importState, 'Foxx_hrofi_glc', isc, iec, jsc, jec, &
+ ice_ocean_boundary%hrofi_glc, areacor=med2mod_areacor, rc=rc)
+ if (ChkErr(rc,__LINE__,u_FILE_u)) return
+ end if
!----
! enthalpy from evaporation (hevap)
!----
diff --git a/config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90 b/config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
index 122a9d00ca..9f409a1af9 100644
--- a/config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
+++ b/config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
@@ -164,6 +164,8 @@ module MOM_surface_forcing_nuopc
type, public :: ice_ocean_boundary_type
real, pointer, dimension(:,:) :: lrunoff =>NULL() !< liquid runoff [kg/m2/s]
real, pointer, dimension(:,:) :: frunoff =>NULL() !< ice runoff [kg/m2/s]
+ real, pointer, dimension(:,:) :: lrunoff_glc =>NULL() !< liquid glc runoff via rof [kg/m2/s]
+ real, pointer, dimension(:,:) :: frunoff_glc =>NULL() !< frozen glc runoff via rof [kg/m2/s]
real, pointer, dimension(:,:) :: u_flux =>NULL() !< i-direction wind stress [Pa]
real, pointer, dimension(:,:) :: v_flux =>NULL() !< j-direction wind stress [Pa]
real, pointer, dimension(:,:) :: t_flux =>NULL() !< sensible heat flux [W/m2]
@@ -183,6 +185,8 @@ module MOM_surface_forcing_nuopc
real, pointer, dimension(:,:) :: mass_berg =>NULL() !< mass of icebergs(kg/m2)
real, pointer, dimension(:,:) :: hrofl =>NULL() !< heat content from liquid runoff [W/m2]
real, pointer, dimension(:,:) :: hrofi =>NULL() !< heat content from frozen runoff [W/m2]
+ real, pointer, dimension(:,:) :: hrofl_glc =>NULL() !< heat content from liquid glc runoff [W/m2]
+ real, pointer, dimension(:,:) :: hrofi_glc =>NULL() !< heat content from frozen glc runoff [W/m2]
real, pointer, dimension(:,:) :: hrain =>NULL() !< heat content from liquid precipitation [W/m2]
real, pointer, dimension(:,:) :: hsnow =>NULL() !< heat content from frozen precipitation [W/m2]
real, pointer, dimension(:,:) :: hevap =>NULL() !< heat content from evaporation [W/m2]
@@ -494,6 +498,16 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
fluxes%frunoff(i,j) = kg_m2_s_conversion * IOB%frunoff(i-i0,j-j0) * G%mask2dT(i,j)
endif
+ ! add liquid glc runoff flux via rof
+ if (associated(IOB%lrunoff_glc)) then
+ fluxes%lrunoff_glc(i,j) = kg_m2_s_conversion * IOB%lrunoff_glc(i-i0,j-j0) * G%mask2dT(i,j)
+ endif
+
+ ! ice glc runoff flux via rof
+ if (associated(IOB%frunoff_glc)) then
+ fluxes%frunoff_glc(i,j) = kg_m2_s_conversion * IOB%frunoff_glc(i-i0,j-j0) * G%mask2dT(i,j)
+ endif
+
if (associated(IOB%ustar_berg)) &
fluxes%ustar_berg(i,j) = US%m_to_Z*US%T_to_s * IOB%ustar_berg(i-i0,j-j0) * G%mask2dT(i,j)
@@ -531,6 +545,13 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
fluxes%latent_frunoff_diag(i,j) = - G%mask2dT(i,j) * &
IOB%frunoff(i-i0,j-j0) * US%W_m2_to_QRZ_T * CS%latent_heat_fusion
endif
+ ! notice minus sign since frunoff_glc is positive into the ocean
+ if (associated(IOB%frunoff_glc)) then
+ fluxes%latent(i,j) = fluxes%latent(i,j) - &
+ IOB%frunoff_glc(i-i0,j-j0) * US%W_m2_to_QRZ_T * CS%latent_heat_fusion
+ fluxes%latent_frunoff_glc_diag(i,j) = fluxes%latent_frunoff_glc_diag(i,j) - G%mask2dT(i,j) * &
+ IOB%frunoff_glc(i-i0,j-j0) * US%W_m2_to_QRZ_T * CS%latent_heat_fusion
+ endif
if (associated(IOB%q_flux)) then
fluxes%latent(i,j) = fluxes%latent(i,j) + &
IOB%q_flux(i-i0,j-j0)*US%W_m2_to_QRZ_T*CS%latent_heat_vapor
@@ -572,6 +593,12 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
if (associated(IOB%hcond)) &
fluxes%heat_content_cond(i,j) = US%W_m2_to_QRZ_T * IOB%hcond(i-i0,j-j0) * G%mask2dT(i,j)
+
+ if (associated(IOB%hrofl_glc)) &
+ fluxes%heat_content_lrunoff_glc(i,j) = US%W_m2_to_QRZ_T * IOB%hrofl_glc(i-i0,j-j0) * G%mask2dT(i,j)
+
+ if (associated(IOB%hrofi_glc)) &
+ fluxes%heat_content_frunoff_glc(i,j) = US%W_m2_to_QRZ_T * IOB%hrofi_glc(i-i0,j-j0) * G%mask2dT(i,j)
endif
! sea ice fraction [nondim]
@@ -633,7 +660,8 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
do j=js,je ; do i=is,ie
net_FW(i,j) = US%RZ_T_to_kg_m2s * &
(((fluxes%lprec(i,j) + fluxes%fprec(i,j) + fluxes%seaice_melt(i,j)) + &
- (fluxes%lrunoff(i,j) + fluxes%frunoff(i,j))) + &
+ (fluxes%lrunoff(i,j) + fluxes%frunoff(i,j) + &
+ fluxes%lrunoff_glc(i,j) + fluxes%frunoff_glc(i,j))) + &
(fluxes%evap(i,j) + fluxes%vprec(i,j)) ) * US%L_to_m**2*G%areaT(i,j)
net_FW2(i,j) = net_FW(i,j) / (US%L_to_m**2*G%areaT(i,j))
enddo ; enddo
@@ -1133,7 +1161,7 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
! Local variables
real :: utide ! The RMS tidal velocity [Z T-1 ~> m s-1].
type(directories) :: dirs
- logical :: new_sim, iceberg_flux_diags, fix_ustar_gustless_bug
+ logical :: new_sim, iceberg_flux_diags, glc_runoff_diags, fix_ustar_gustless_bug
logical :: test_value ! This is used to determine whether a logical parameter is being set explicitly.
logical :: explicit_bug, explicit_fix ! These indicate which parameters are set explicitly.
type(time_type) :: Time_frc
@@ -1431,8 +1459,13 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
"If true, makes available diagnostics of fluxes from icebergs "//&
"as seen by MOM6.", default=.false.)
+ call get_param(param_file, mdl, "ALLOW_GLC_RUNOFF_DIAGNOSTICS", glc_runoff_diags, &
+ "If true, makes available diagnostics of separate glacier runoff fluxes"//&
+ "as seen by MOM6.", default=.false.)
+
call register_forcing_type_diags(Time, diag, US, CS%use_temperature, CS%handles, &
- use_berg_fluxes=iceberg_flux_diags, use_waves=use_waves, use_cfcs=CS%use_CFC)
+ use_berg_fluxes=iceberg_flux_diags, use_waves=use_waves, &
+ use_cfcs=CS%use_CFC, use_glc_runoff=glc_runoff_diags)
call get_param(param_file, mdl, "ALLOW_FLUX_ADJUSTMENTS", CS%allow_flux_adjustments, &
"If true, allows flux adjustments to specified via the "//&
@@ -1541,6 +1574,8 @@ subroutine ice_ocn_bnd_type_chksum(id, timestep, iobt)
chks = field_chksum( iobt%fprec ) ; if (root) write(outunit,100) 'iobt%fprec ', chks
chks = field_chksum( iobt%lrunoff ) ; if (root) write(outunit,100) 'iobt%lrunoff ', chks
chks = field_chksum( iobt%frunoff ) ; if (root) write(outunit,100) 'iobt%frunoff ', chks
+ chks = field_chksum( iobt%lrunoff_glc ) ; if (root) write(outunit,100) 'iobt%lrunoff_glc ', chks
+ chks = field_chksum( iobt%frunoff_glc ) ; if (root) write(outunit,100) 'iobt%frunoff_glc ', chks
chks = field_chksum( iobt%p ) ; if (root) write(outunit,100) 'iobt%p ', chks
if (associated(iobt%ice_fraction)) then
chks = field_chksum( iobt%ice_fraction ) ; if (root) write(outunit,100) 'iobt%ice_fraction ', chks
@@ -1631,6 +1666,12 @@ subroutine ice_ocn_bnd_type_chksum(id, timestep, iobt)
if (associated(iobt%hcond)) then
chks = field_chksum( iobt%hcond ) ; if (root) write(outunit,100) 'iobt%hcond ', chks
endif
+ if (associated(iobt%hrofl_glc)) then
+ chks = field_chksum( iobt%hrofl_glc ) ; if (root) write(outunit,100) 'iobt%hrofl_glc ', chks
+ endif
+ if (associated(iobt%hrofl_glc)) then
+ chks = field_chksum( iobt%hrofl_glc ) ; if (root) write(outunit,100) 'iobt%hrofl_glc ', chks
+ endif
100 FORMAT(" CHECKSUM::",A20," = ",Z20)
110 FORMAT(" CHECKSUM::",A30," = ",Z20)
diff --git a/src/core/MOM_forcing_type.F90 b/src/core/MOM_forcing_type.F90
index adf9d29ea3..bef29ffe86 100644
--- a/src/core/MOM_forcing_type.F90
+++ b/src/core/MOM_forcing_type.F90
@@ -114,9 +114,10 @@ module MOM_forcing_type
! components of latent heat fluxes used for diagnostic purposes
real, pointer, dimension(:,:) :: &
- latent_evap_diag => NULL(), & !< latent [Q R Z T-1 ~> W m-2] from evaporating liquid water (typically < 0)
- latent_fprec_diag => NULL(), & !< latent [Q R Z T-1 ~> W m-2] from melting fprec (typically < 0)
- latent_frunoff_diag => NULL() !< latent [Q R Z T-1 ~> W m-2] from melting frunoff (calving) (typically < 0)
+ latent_evap_diag => NULL(), & !< latent [Q R Z T-1 ~> W m-2] from evaporating liquid water (typically < 0)
+ latent_fprec_diag => NULL(), & !< latent [Q R Z T-1 ~> W m-2] from melting fprec (typically < 0)
+ latent_frunoff_diag => NULL(), & !< latent [Q R Z T-1 ~> W m-2] from melting frunoff (calving) (typically < 0)
+ latent_frunoff_glc_diag => NULL() !< latent [Q R Z T-1 ~> W m-2] from melting glacier frunoff (typically < 0)
! water mass fluxes into the ocean [R Z T-1 ~> kg m-2 s-1]; these fluxes impact the ocean mass
real, pointer, dimension(:,:) :: &
@@ -126,6 +127,8 @@ module MOM_forcing_type
vprec => NULL(), & !< virtual liquid precip associated w/ SSS restoring [R Z T-1 ~> kg m-2 s-1]
lrunoff => NULL(), & !< liquid river runoff entering ocean [R Z T-1 ~> kg m-2 s-1]
frunoff => NULL(), & !< frozen river runoff (calving) entering ocean [R Z T-1 ~> kg m-2 s-1]
+ lrunoff_glc => NULL(), & !< liquid river glacier runoff entering ocean [R Z T-1 ~> kg m-2 s-1]
+ frunoff_glc => NULL(), & !< frozen river glacier runoff entering ocean [R Z T-1 ~> kg m-2 s-1]
seaice_melt => NULL() !< snow/seaice melt (positive) or formation (negative) [R Z T-1 ~> kg m-2 s-1]
! Integrated water mass fluxes into the ocean, used for passive tracer sources [H ~> m or kg m-2]
@@ -137,15 +140,17 @@ module MOM_forcing_type
! heat associated with water crossing ocean surface
real, pointer, dimension(:,:) :: &
- heat_content_cond => NULL(), & !< heat content associated with condensating water [Q R Z T-1 ~> W m-2]
- heat_content_evap => NULL(), & !< heat content associated with evaporating water [Q R Z T-1 ~> W m-2]
- heat_content_lprec => NULL(), & !< heat content associated with liquid >0 precip [Q R Z T-1 ~> W m-2]
- heat_content_fprec => NULL(), & !< heat content associated with frozen precip [Q R Z T-1 ~> W m-2]
- heat_content_vprec => NULL(), & !< heat content associated with virtual >0 precip [Q R Z T-1 ~> W m-2]
- heat_content_lrunoff => NULL(), & !< heat content associated with liquid runoff [Q R Z T-1 ~> W m-2]
- heat_content_frunoff => NULL(), & !< heat content associated with frozen runoff [Q R Z T-1 ~> W m-2]
- heat_content_massout => NULL(), & !< heat content associated with mass leaving ocean [Q R Z T-1 ~> W m-2]
- heat_content_massin => NULL() !< heat content associated with mass entering ocean [Q R Z T-1 ~> W m-2]
+ heat_content_cond => NULL(), & !< heat content associated with condensating water [Q R Z T-1 ~> W m-2]
+ heat_content_evap => NULL(), & !< heat content associated with evaporating water [Q R Z T-1 ~> W m-2]
+ heat_content_lprec => NULL(), & !< heat content associated with liquid >0 precip [Q R Z T-1 ~> W m-2]
+ heat_content_fprec => NULL(), & !< heat content associated with frozen precip [Q R Z T-1 ~> W m-2]
+ heat_content_vprec => NULL(), & !< heat content associated with virtual >0 precip [Q R Z T-1 ~> W m-2]
+ heat_content_lrunoff => NULL(), & !< heat content associated with liquid runoff [Q R Z T-1 ~> W m-2]
+ heat_content_frunoff => NULL(), & !< heat content associated with frozen runoff [Q R Z T-1 ~> W m-2]
+ heat_content_lrunoff_glc => NULL(), & !< heat content associated with liquid runoff [Q R Z T-1 ~> W m-2]
+ heat_content_frunoff_glc => NULL(), & !< heat content associated with frozen runoff [Q R Z T-1 ~> W m-2]
+ heat_content_massout => NULL(), & !< heat content associated with mass leaving ocean [Q R Z T-1 ~> W m-2]
+ heat_content_massin => NULL() !< heat content associated with mass entering ocean [Q R Z T-1 ~> W m-2]
! salt mass flux (contributes to ocean mass only if non-Bouss )
real, pointer, dimension(:,:) :: &
@@ -323,6 +328,7 @@ module MOM_forcing_type
integer :: id_precip = -1, id_vprec = -1
integer :: id_lprec = -1, id_fprec = -1
integer :: id_lrunoff = -1, id_frunoff = -1
+ integer :: id_lrunoff_glc = -1, id_frunoff_glc = -1
integer :: id_net_massout = -1, id_net_massin = -1
integer :: id_massout_flux = -1, id_massin_flux = -1
integer :: id_seaice_melt = -1
@@ -332,6 +338,7 @@ module MOM_forcing_type
integer :: id_total_precip = -1, id_total_vprec = -1
integer :: id_total_lprec = -1, id_total_fprec = -1
integer :: id_total_lrunoff = -1, id_total_frunoff = -1
+ integer :: id_total_lrunoff_glc = -1, id_total_frunoff_glc = -1
integer :: id_total_net_massout = -1, id_total_net_massin = -1
integer :: id_total_seaice_melt = -1
@@ -341,34 +348,38 @@ module MOM_forcing_type
integer :: id_precip_ga = -1, id_vprec_ga= -1
! heat flux diagnostic handles
- integer :: id_net_heat_coupler = -1, id_net_heat_surface = -1
- integer :: id_sens = -1, id_LwLatSens = -1
- integer :: id_sw = -1, id_lw = -1
- integer :: id_sw_vis = -1, id_sw_nir = -1
- integer :: id_lat_evap = -1, id_lat_frunoff = -1
- integer :: id_lat = -1, id_lat_fprec = -1
- integer :: id_heat_content_lrunoff= -1, id_heat_content_frunoff = -1
- integer :: id_heat_content_lprec = -1, id_heat_content_fprec = -1
- integer :: id_heat_content_cond = -1, id_heat_content_surfwater= -1
- integer :: id_heat_content_evap = -1
- integer :: id_heat_content_vprec = -1, id_heat_content_massout = -1
- integer :: id_heat_added = -1, id_heat_content_massin = -1
- integer :: id_hfrainds = -1, id_hfrunoffds = -1
- integer :: id_seaice_melt_heat = -1
+ integer :: id_net_heat_coupler = -1, id_net_heat_surface = -1
+ integer :: id_sens = -1, id_LwLatSens = -1
+ integer :: id_sw = -1, id_lw = -1
+ integer :: id_sw_vis = -1, id_sw_nir = -1
+ integer :: id_lat_evap = -1, id_lat_frunoff = -1
+ integer :: id_lat_frunoff_glc = -1
+ integer :: id_lat = -1, id_lat_fprec = -1
+ integer :: id_heat_content_lrunoff = -1, id_heat_content_frunoff = -1
+ integer :: id_heat_content_lrunoff_glc= -1, id_heat_content_frunoff_glc= -1
+ integer :: id_heat_content_lprec = -1, id_heat_content_fprec = -1
+ integer :: id_heat_content_cond = -1, id_heat_content_surfwater = -1
+ integer :: id_heat_content_evap = -1
+ integer :: id_heat_content_vprec = -1, id_heat_content_massout = -1
+ integer :: id_heat_added = -1, id_heat_content_massin = -1
+ integer :: id_hfrainds = -1, id_hfrunoffds = -1
+ integer :: id_seaice_melt_heat = -1
! global area integrated heat flux diagnostic handles
- integer :: id_total_net_heat_coupler = -1, id_total_net_heat_surface = -1
- integer :: id_total_sens = -1, id_total_LwLatSens = -1
- integer :: id_total_sw = -1, id_total_lw = -1
- integer :: id_total_lat_evap = -1, id_total_lat_frunoff = -1
- integer :: id_total_lat = -1, id_total_lat_fprec = -1
- integer :: id_total_heat_content_lrunoff= -1, id_total_heat_content_frunoff = -1
- integer :: id_total_heat_content_lprec = -1, id_total_heat_content_fprec = -1
- integer :: id_total_heat_content_cond = -1, id_total_heat_content_surfwater= -1
- integer :: id_total_heat_content_evap = -1
- integer :: id_total_heat_content_vprec = -1, id_total_heat_content_massout = -1
- integer :: id_total_heat_added = -1, id_total_heat_content_massin = -1
- integer :: id_total_seaice_melt_heat = -1
+ integer :: id_total_net_heat_coupler = -1, id_total_net_heat_surface = -1
+ integer :: id_total_sens = -1, id_total_LwLatSens = -1
+ integer :: id_total_sw = -1, id_total_lw = -1
+ integer :: id_total_lat_evap = -1, id_total_lat_frunoff = -1
+ integer :: id_total_lat_frunoff_glc = -1
+ integer :: id_total_lat = -1, id_total_lat_fprec = -1
+ integer :: id_total_heat_content_lrunoff = -1, id_total_heat_content_frunoff = -1
+ integer :: id_total_heat_content_lrunoff_glc= -1, id_total_heat_content_frunoff_glc=-1
+ integer :: id_total_heat_content_lprec = -1, id_total_heat_content_fprec = -1
+ integer :: id_total_heat_content_cond = -1, id_total_heat_content_surfwater = -1
+ integer :: id_total_heat_content_evap = -1
+ integer :: id_total_heat_content_vprec = -1, id_total_heat_content_massout = -1
+ integer :: id_total_heat_added = -1, id_total_heat_content_massin = -1
+ integer :: id_total_seaice_melt_heat = -1
! global area averaged heat flux diagnostic handles
integer :: id_net_heat_coupler_ga = -1, id_net_heat_surface_ga = -1
@@ -609,23 +620,27 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
! net volume/mass of liquid and solid passing through surface boundary fluxes
netMassInOut(i) = dt * (scale * &
- (((((( fluxes%lprec(i,j) &
+ (((((((( fluxes%lprec(i,j) &
+ fluxes%fprec(i,j) ) &
+ fluxes%evap(i,j) ) &
+ fluxes%lrunoff(i,j) ) &
+ + fluxes%lrunoff_glc(i,j)) &
+ fluxes%vprec(i,j) ) &
+ fluxes%seaice_melt(i,j)) &
- + fluxes%frunoff(i,j) ))
+ + fluxes%frunoff(i,j) ) &
+ + fluxes%frunoff_glc(i,j)))
if (do_NMIOr) then ! Repeat the above code without multiplying by a timestep for legacy reasons
netMassInOut_rate(i) = (scale * &
- (((((( fluxes%lprec(i,j) &
+ (((((((( fluxes%lprec(i,j) &
+ fluxes%fprec(i,j) ) &
+ fluxes%evap(i,j) ) &
+ fluxes%lrunoff(i,j) ) &
+ + fluxes%lrunoff_glc(i,j)) &
+ fluxes%vprec(i,j) ) &
+ fluxes%seaice_melt(i,j)) &
- + fluxes%frunoff(i,j) ))
+ + fluxes%frunoff(i,j) ) &
+ + fluxes%frunoff_glc(i,j)))
endif
! smg:
@@ -700,6 +715,8 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
! remove lrunoff*SST here, to counteract its addition elsewhere
net_heat(i) = (net_heat(i) + (scale*(dt * I_Cp_Hconvert)) * fluxes%heat_content_lrunoff(i,j)) - &
(GV%RZ_to_H * (scale * dt)) * fluxes%lrunoff(i,j) * T(i,1)
+ net_heat(i) = (net_heat(i) + (scale*(dt * I_Cp_Hconvert)) * fluxes%heat_content_lrunoff_glc(i,j)) - &
+ (GV%RZ_to_H * (scale * dt)) * fluxes%lrunoff_glc(i,j) * T(i,1)
!BGR-Jul 5, 2017{
!Intentionally neglect the following contribution to rate for legacy reasons.
!if (do_NHR) net_heat_rate(i) = (net_heat_rate(i) + (scale*I_Cp_Hconvert) * fluxes%heat_content_lrunoff(i,j)) - &
@@ -708,6 +725,8 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
if (calculate_diags .and. associated(tv%TempxPmE)) then
tv%TempxPmE(i,j) = tv%TempxPmE(i,j) + (scale * dt) * &
(I_Cp*fluxes%heat_content_lrunoff(i,j) - fluxes%lrunoff(i,j)*T(i,1))
+ tv%TempxPmE(i,j) = tv%TempxPmE(i,j) + (scale * dt) * &
+ (I_Cp*fluxes%heat_content_lrunoff_glc(i,j) - fluxes%lrunoff_glc(i,j)*T(i,1))
endif
endif
@@ -717,6 +736,8 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
! remove frunoff*SST here, to counteract its addition elsewhere
net_heat(i) = net_heat(i) + (scale*(dt * I_Cp_Hconvert)) * fluxes%heat_content_frunoff(i,j) - &
(GV%RZ_to_H * (scale * dt)) * fluxes%frunoff(i,j) * T(i,1)
+ net_heat(i) = net_heat(i) + (scale*(dt * I_Cp_Hconvert)) * fluxes%heat_content_frunoff_glc(i,j) - &
+ (GV%RZ_to_H * (scale * dt)) * fluxes%frunoff_glc(i,j) * T(i,1)
!BGR-Jul 5, 2017{
!Intentionally neglect the following contribution to rate for legacy reasons.
! if (do_NHR) net_heat_rate(i) = net_heat_rate(i) + (scale*I_Cp_Hconvert) * fluxes%heat_content_frunoff(i,j) - &
@@ -725,6 +746,8 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
if (calculate_diags .and. associated(tv%TempxPmE)) then
tv%TempxPmE(i,j) = tv%TempxPmE(i,j) + (scale * dt) * &
(I_Cp*fluxes%heat_content_frunoff(i,j) - fluxes%frunoff(i,j)*T(i,1))
+ tv%TempxPmE(i,j) = tv%TempxPmE(i,j) + (scale * dt) * &
+ (I_Cp*fluxes%heat_content_frunoff_glc(i,j) - fluxes%frunoff_glc(i,j)*T(i,1))
endif
endif
@@ -748,6 +771,7 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
if (.not. do_enthalpy) then
net_heat(i) = net_heat(i) + (scale * dt * I_Cp_Hconvert * &
(fluxes%heat_content_lrunoff(i,j) + fluxes%heat_content_frunoff(i,j) + &
+ fluxes%heat_content_lrunoff_glc(i,j) + fluxes%heat_content_frunoff_glc(i,j) + &
fluxes%heat_content_lprec(i,j) + fluxes%heat_content_fprec(i,j) + &
fluxes%heat_content_evap(i,j) + fluxes%heat_content_cond(i,j)))
endif
@@ -876,6 +900,9 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
if (associated(fluxes%lrunoff) .and. associated(fluxes%heat_content_lrunoff)) then
fluxes%heat_content_lrunoff(i,j) = tv%C_p*fluxes%lrunoff(i,j)*T(i,1)
endif
+ if (associated(fluxes%lrunoff_glc) .and. associated(fluxes%heat_content_lrunoff_glc)) then
+ fluxes%heat_content_lrunoff_glc(i,j) = tv%C_p*fluxes%lrunoff_glc(i,j)*T(i,1)
+ endif
endif
! Icebergs enter ocean at SST if land model does not provide calving heat content.
@@ -883,6 +910,9 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
if (associated(fluxes%frunoff) .and. associated(fluxes%heat_content_frunoff)) then
fluxes%heat_content_frunoff(i,j) = tv%C_p*fluxes%frunoff(i,j)*T(i,1)
endif
+ if (associated(fluxes%frunoff_glc) .and. associated(fluxes%heat_content_frunoff_glc)) then
+ fluxes%heat_content_frunoff_glc(i,j) = tv%C_p*fluxes%frunoff_glc(i,j)*T(i,1)
+ endif
endif
elseif (.not. do_enthalpy) then
@@ -905,6 +935,8 @@ subroutine extractFluxes1d(G, GV, US, fluxes, optics, nsw, j, dt, &
fluxes%heat_content_fprec(i,j) + &
fluxes%heat_content_lrunoff(i,j) + &
fluxes%heat_content_frunoff(i,j) + &
+ fluxes%heat_content_lrunoff_glc(i,j) + &
+ fluxes%heat_content_frunoff_glc(i,j) + &
fluxes%heat_content_evap(i,j) + &
fluxes%heat_content_cond(i,j))
endif
@@ -1309,6 +1341,9 @@ subroutine MOM_forcing_chksum(mesg, fluxes, G, US, haloshift)
if (associated(fluxes%latent_frunoff_diag)) &
call hchksum(fluxes%latent_frunoff_diag, mesg//" fluxes%latent_frunoff_diag", G%HI, &
haloshift=hshift, scale=US%QRZ_T_to_W_m2)
+ if (associated(fluxes%latent_frunoff_glc_diag)) &
+ call hchksum(fluxes%latent_frunoff_glc_diag, mesg//" fluxes%latent_frunoff_glc_diag", G%HI, &
+ haloshift=hshift, scale=US%QRZ_T_to_W_m2)
if (associated(fluxes%sens)) &
call hchksum(fluxes%sens, mesg//" fluxes%sens", G%HI, haloshift=hshift, scale=US%QRZ_T_to_W_m2)
if (associated(fluxes%evap)) &
@@ -1338,14 +1373,24 @@ subroutine MOM_forcing_chksum(mesg, fluxes, G, US, haloshift)
call hchksum(fluxes%ustar_tidal, mesg//" fluxes%ustar_tidal", G%HI, haloshift=hshift, scale=US%Z_to_m*US%s_to_T)
if (associated(fluxes%lrunoff)) &
call hchksum(fluxes%lrunoff, mesg//" fluxes%lrunoff", G%HI, haloshift=hshift, scale=US%RZ_T_to_kg_m2s)
+ if (associated(fluxes%lrunoff_glc)) &
+ call hchksum(fluxes%lrunoff_glc, mesg//" fluxes%lrunoff_glc", G%HI, haloshift=hshift, scale=US%RZ_T_to_kg_m2s)
if (associated(fluxes%frunoff)) &
call hchksum(fluxes%frunoff, mesg//" fluxes%frunoff", G%HI, haloshift=hshift, scale=US%RZ_T_to_kg_m2s)
+ if (associated(fluxes%frunoff_glc)) &
+ call hchksum(fluxes%frunoff_glc, mesg//" fluxes%frunoff_glc", G%HI, haloshift=hshift, scale=US%RZ_T_to_kg_m2s)
if (associated(fluxes%heat_content_lrunoff)) &
call hchksum(fluxes%heat_content_lrunoff, mesg//" fluxes%heat_content_lrunoff", G%HI, &
haloshift=hshift, scale=US%QRZ_T_to_W_m2)
+ if (associated(fluxes%heat_content_lrunoff_glc)) &
+ call hchksum(fluxes%heat_content_lrunoff_glc, mesg//" fluxes%heat_content_lrunoff_glc", G%HI, &
+ haloshift=hshift, scale=US%QRZ_T_to_W_m2)
if (associated(fluxes%heat_content_frunoff)) &
call hchksum(fluxes%heat_content_frunoff, mesg//" fluxes%heat_content_frunoff", G%HI, &
haloshift=hshift, scale=US%QRZ_T_to_W_m2)
+ if (associated(fluxes%heat_content_frunoff_glc)) &
+ call hchksum(fluxes%heat_content_frunoff_glc, mesg//" fluxes%heat_content_frunoff_glc", G%HI, &
+ haloshift=hshift, scale=US%QRZ_T_to_W_m2)
if (associated(fluxes%heat_content_lprec)) &
call hchksum(fluxes%heat_content_lprec, mesg//" fluxes%heat_content_lprec", G%HI, &
haloshift=hshift, scale=US%QRZ_T_to_W_m2)
@@ -1448,6 +1493,7 @@ subroutine forcing_SinglePointPrint(fluxes, G, i, j, mesg)
call locMsg(fluxes%latent_evap_diag,'latent_evap_diag')
call locMsg(fluxes%latent_fprec_diag,'latent_fprec_diag')
call locMsg(fluxes%latent_frunoff_diag,'latent_frunoff_diag')
+ call locMsg(fluxes%latent_frunoff_glc_diag,'latent_frunoff_glc_diag')
call locMsg(fluxes%sens,'sens')
call locMsg(fluxes%evap,'evap')
call locMsg(fluxes%lprec,'lprec')
@@ -1460,9 +1506,13 @@ subroutine forcing_SinglePointPrint(fluxes, G, i, j, mesg)
call locMsg(fluxes%TKE_tidal,'TKE_tidal')
call locMsg(fluxes%ustar_tidal,'ustar_tidal')
call locMsg(fluxes%lrunoff,'lrunoff')
+ call locMsg(fluxes%lrunoff_glc,'lrunoff_glc')
call locMsg(fluxes%frunoff,'frunoff')
+ call locMsg(fluxes%frunoff_glc,'frunoff_glc')
call locMsg(fluxes%heat_content_lrunoff,'heat_content_lrunoff')
+ call locMsg(fluxes%heat_content_lrunoff_glc,'heat_content_lrunoff_glc')
call locMsg(fluxes%heat_content_frunoff,'heat_content_frunoff')
+ call locMsg(fluxes%heat_content_frunoff_glc,'heat_content_frunoff_glc')
call locMsg(fluxes%heat_content_lprec,'heat_content_lprec')
call locMsg(fluxes%heat_content_fprec,'heat_content_fprec')
call locMsg(fluxes%heat_content_vprec,'heat_content_vprec')
@@ -1489,7 +1539,8 @@ end subroutine forcing_SinglePointPrint
!> Register members of the forcing type for diagnostics
-subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles, use_berg_fluxes, use_waves, use_cfcs)
+subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles, use_berg_fluxes, use_waves, &
+ use_cfcs, use_glc_runoff)
type(time_type), intent(in) :: Time !< time type
type(diag_ctrl), intent(inout) :: diag !< diagnostic control type
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
@@ -1498,6 +1549,7 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
logical, optional, intent(in) :: use_berg_fluxes !< If true, allow iceberg flux diagnostics
logical, optional, intent(in) :: use_waves !< If true, allow wave forcing diagnostics
logical, optional, intent(in) :: use_cfcs !< If true, allow cfc related diagnostics
+ logical, optional, intent(in) :: use_glc_runoff !< If true, allow separate glacial runoff diagnostics
! Clock for forcing diagnostics
handles%id_clock_forcing=cpu_clock_id('(Ocean forcing diagnostics)', grain=CLOCK_ROUTINE)
@@ -1634,6 +1686,18 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
cmor_standard_name='water_flux_into_sea_water_from_rivers', &
cmor_long_name='Water Flux into Sea Water From Rivers')
+ if (present(use_glc_runoff)) then
+ handles%id_frunoff_glc = register_diag_field('ocean_model', 'frunoff_glc', diag%axesT1, Time, &
+ 'Frozen glacier runoff (calving) and iceberg melt into ocean', &
+ units='kg m-2 s-1', conversion=US%RZ_T_to_kg_m2s, &
+ standard_name='glc_water_flux_into_sea_water_from_icebergs') ! todo: update cmor names
+
+ handles%id_lrunoff_glc = register_diag_field('ocean_model', 'lrunoff_glc', diag%axesT1, Time, &
+ 'Liquid runoff (glaciers) into ocean', &
+ units='kg m-2 s-1', conversion=US%RZ_T_to_kg_m2s, &
+ standard_name='water_flux_into_sea_water_from_glaciers') ! todo: update cmor names
+ endif
+
handles%id_net_massout = register_diag_field('ocean_model', 'net_massout', diag%axesT1, Time, &
'Net mass leaving the ocean due to evaporation, seaice formation', &
'kg m-2 s-1', conversion=US%RZ_T_to_kg_m2s)
@@ -1707,6 +1771,14 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
cmor_standard_name='water_flux_into_sea_water_from_rivers_area_integrated', &
cmor_long_name='Water Flux into Sea Water From Rivers Area Integrated')
+ if (present(use_glc_runoff)) then
+ handles%id_total_frunoff_glc = register_scalar_field('ocean_model', 'total_frunoff_glc', Time, diag, &
+ long_name='Area integrated frozen glacier runoff (calving) & iceberg melt into ocean', units='kg s-1')
+
+ handles%id_total_lrunoff_glc = register_scalar_field('ocean_model', 'total_lrunoff_glc', Time, diag,&
+ long_name='Area integrated liquid glacier runoff into ocean', units='kg s-1')
+ endif
+
handles%id_total_net_massout = register_scalar_field('ocean_model', 'total_net_massout', Time, diag, &
long_name='Area integrated mass leaving ocean due to evap and seaice form', units='kg s-1')
@@ -1765,6 +1837,16 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
'W m-2', conversion=US%QRZ_T_to_W_m2, &
standard_name='temperature_flux_due_to_runoff_expressed_as_heat_flux_into_sea_water')
+ if (present(use_glc_runoff)) then
+ handles%id_heat_content_frunoff_glc = register_diag_field('ocean_model', 'heat_content_frunoff_glc', &
+ diag%axesT1, Time, 'Heat content (relative to 0C) of solid glacier runoff into ocean', &
+ 'W m-2', conversion=US%QRZ_T_to_W_m2)
+
+ handles%id_heat_content_lrunoff_glc = register_diag_field('ocean_model', 'heat_content_lrunoff_glc', &
+ diag%axesT1, Time, 'Heat content (relative to 0C) of liquid glacier runoff into ocean', &
+ 'W m-2', conversion=US%QRZ_T_to_W_m2)
+ endif
+
handles%id_hfrunoffds = register_diag_field('ocean_model', 'hfrunoffds', &
diag%axesT1, Time, 'Heat content (relative to 0C) of liquid+solid runoff into ocean', &
'W m-2', conversion=US%QRZ_T_to_W_m2, &
@@ -1868,6 +1950,11 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
cmor_standard_name='heat_flux_into_sea_water_due_to_iceberg_thermodynamics', &
cmor_long_name='Latent Heat to Melt Frozen Runoff/Iceberg')
+ if (present(use_glc_runoff)) then
+ handles%id_lat_frunoff_glc = register_diag_field('ocean_model', 'latent_frunoff_glc', diag%axesT1, Time, &
+ 'Latent heat flux into ocean due to melting of frozen glacier runoff', 'W m-2', conversion=US%QRZ_T_to_W_m2)
+ endif
+
handles%id_sens = register_diag_field('ocean_model', 'sensible', diag%axesT1, Time, &
'Sensible heat flux into ocean', 'W m-2', conversion=US%QRZ_T_to_W_m2, &
standard_name='surface_downward_sensible_heat_flux', &
@@ -1907,6 +1994,18 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
cmor_long_name= &
'Temperature Flux due to Runoff Expressed as Heat Flux into Sea Water Area Integrated')
+ if (present(use_glc_runoff)) then
+ handles%id_total_heat_content_frunoff_glc = register_scalar_field('ocean_model', &
+ 'total_heat_content_frunoff_glc', Time, diag, &
+ long_name='Area integrated heat content (relative to 0C) of solid glacier runoff', &
+ units='W') ! todo: update cmor names
+
+ handles%id_total_heat_content_lrunoff_glc = register_scalar_field('ocean_model', &
+ 'total_heat_content_lrunoff_glc', Time, diag, &
+ long_name='Area integrated heat content (relative to 0C) of liquid glacier runoff', &
+ units='W') ! todo: update cmor names
+ endif
+
handles%id_total_heat_content_lprec = register_scalar_field('ocean_model', &
'total_heat_content_lprec', Time, diag, &
long_name='Area integrated heat content (relative to 0C) of liquid precip', &
@@ -2024,6 +2123,13 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
cmor_long_name= &
'Heat Flux into Sea Water due to Iceberg Thermodynamics Area Integrated')
+ if (present(use_glc_runoff)) then
+ handles%id_total_lat_frunoff_glc = register_scalar_field('ocean_model', &
+ 'total_lat_frunoff_glc', Time, diag, &
+ long_name='Area integrated latent heat flux due to melting frozen glacier runoff', &
+ units='W') ! todo: update cmor names
+ endif
+
handles%id_total_sens = register_scalar_field('ocean_model', &
'total_sens', Time, diag, &
long_name='Area integrated downward sensible heat flux', &
@@ -2287,6 +2393,8 @@ subroutine fluxes_accumulate(flux_tmp, fluxes, G, wt2, forces)
fluxes%vprec(i,j) = wt1*fluxes%vprec(i,j) + wt2*flux_tmp%vprec(i,j)
fluxes%lrunoff(i,j) = wt1*fluxes%lrunoff(i,j) + wt2*flux_tmp%lrunoff(i,j)
fluxes%frunoff(i,j) = wt1*fluxes%frunoff(i,j) + wt2*flux_tmp%frunoff(i,j)
+ fluxes%lrunoff_glc(i,j) = wt1*fluxes%lrunoff_glc(i,j) + wt2*flux_tmp%lrunoff_glc(i,j)
+ fluxes%frunoff_glc(i,j) = wt1*fluxes%frunoff_glc(i,j) + wt2*flux_tmp%frunoff_glc(i,j)
fluxes%seaice_melt(i,j) = wt1*fluxes%seaice_melt(i,j) + wt2*flux_tmp%seaice_melt(i,j)
fluxes%sw(i,j) = wt1*fluxes%sw(i,j) + wt2*flux_tmp%sw(i,j)
fluxes%sw_vis_dir(i,j) = wt1*fluxes%sw_vis_dir(i,j) + wt2*flux_tmp%sw_vis_dir(i,j)
@@ -2340,6 +2448,18 @@ subroutine fluxes_accumulate(flux_tmp, fluxes, G, wt2, forces)
fluxes%heat_content_frunoff(i,j) = wt1*fluxes%heat_content_frunoff(i,j) + wt2*flux_tmp%heat_content_frunoff(i,j)
enddo ; enddo
endif
+ if (associated(fluxes%heat_content_lrunoff_glc) .and. associated(flux_tmp%heat_content_lrunoff_glc)) then
+ do j=js,je ; do i=is,ie
+ fluxes%heat_content_lrunoff_glc(i,j) = wt1*fluxes%heat_content_lrunoff_glc(i,j) + &
+ wt2*flux_tmp%heat_content_lrunoff_glc(i,j)
+ enddo ; enddo
+ endif
+ if (associated(fluxes%heat_content_frunoff_glc) .and. associated(flux_tmp%heat_content_frunoff_glc)) then
+ do j=js,je ; do i=is,ie
+ fluxes%heat_content_frunoff_glc(i,j) = wt1*fluxes%heat_content_frunoff_glc(i,j) + &
+ wt2*flux_tmp%heat_content_frunoff_glc(i,j)
+ enddo ; enddo
+ endif
if (associated(fluxes%ustar_shelf) .and. associated(flux_tmp%ustar_shelf)) then
do i=isd,ied ; do j=jsd,jed
@@ -2511,6 +2631,12 @@ subroutine get_net_mass_forcing(fluxes, G, US, net_mass_src)
if (associated(fluxes%frunoff)) then ; do j=js,je ; do i=is,ie
net_mass_src(i,j) = net_mass_src(i,j) + fluxes%frunoff(i,j)
enddo ; enddo ; endif
+ if (associated(fluxes%lrunoff_glc)) then ; do j=js,je ; do i=is,ie
+ net_mass_src(i,j) = net_mass_src(i,j) + fluxes%lrunoff_glc(i,j)
+ enddo ; enddo ; endif
+ if (associated(fluxes%frunoff_glc)) then ; do j=js,je ; do i=is,ie
+ net_mass_src(i,j) = net_mass_src(i,j) + fluxes%frunoff_glc(i,j)
+ enddo ; enddo ; endif
if (associated(fluxes%evap)) then ; do j=js,je ; do i=is,ie
net_mass_src(i,j) = net_mass_src(i,j) + fluxes%evap(i,j)
enddo ; enddo ; endif
@@ -2671,6 +2797,8 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
if (associated(fluxes%evap)) res(i,j) = res(i,j) + fluxes%evap(i,j)
if (associated(fluxes%lrunoff)) res(i,j) = res(i,j) + fluxes%lrunoff(i,j)
if (associated(fluxes%frunoff)) res(i,j) = res(i,j) + fluxes%frunoff(i,j)
+ if (associated(fluxes%lrunoff_glc)) res(i,j) = res(i,j) + fluxes%lrunoff_glc(i,j)
+ if (associated(fluxes%frunoff_glc)) res(i,j) = res(i,j) + fluxes%frunoff_glc(i,j)
if (associated(fluxes%vprec)) res(i,j) = res(i,j) + fluxes%vprec(i,j)
if (associated(fluxes%seaice_melt)) res(i,j) = res(i,j) + fluxes%seaice_melt(i,j)
enddo ; enddo
@@ -2718,6 +2846,8 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
if (associated(fluxes%fprec)) res(i,j) = res(i,j) + fluxes%fprec(i,j)
if (associated(fluxes%lrunoff)) res(i,j) = res(i,j) + fluxes%lrunoff(i,j)
if (associated(fluxes%frunoff)) res(i,j) = res(i,j) + fluxes%frunoff(i,j)
+ if (associated(fluxes%lrunoff_glc)) res(i,j) = res(i,j) + fluxes%lrunoff_glc(i,j)
+ if (associated(fluxes%frunoff_glc)) res(i,j) = res(i,j) + fluxes%frunoff_glc(i,j)
if (associated(fluxes%lprec)) then
if (fluxes%lprec(i,j) > 0.0) res(i,j) = res(i,j) + fluxes%lprec(i,j)
@@ -2813,6 +2943,14 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
endif
endif
+ if (associated(fluxes%lrunoff_glc)) then
+ if (handles%id_lrunoff_glc > 0) call post_data(handles%id_lrunoff_glc, fluxes%lrunoff_glc, diag)
+ if (handles%id_total_lrunoff_glc > 0) then
+ total_transport = global_area_integral(fluxes%lrunoff_glc, G, scale=US%RZ_T_to_kg_m2s)
+ call post_data(handles%id_total_lrunoff_glc, total_transport, diag)
+ endif
+ endif
+
if (associated(fluxes%frunoff)) then
if (handles%id_frunoff > 0) call post_data(handles%id_frunoff, fluxes%frunoff, diag)
if (handles%id_total_frunoff > 0) then
@@ -2821,6 +2959,14 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
endif
endif
+ if (associated(fluxes%frunoff_glc)) then
+ if (handles%id_frunoff_glc > 0) call post_data(handles%id_frunoff_glc, fluxes%frunoff_glc, diag)
+ if (handles%id_total_frunoff_glc > 0) then
+ total_transport = global_area_integral(fluxes%frunoff_glc, G, scale=US%RZ_T_to_kg_m2s)
+ call post_data(handles%id_total_frunoff_glc, total_transport, diag)
+ endif
+ endif
+
if (associated(fluxes%seaice_melt)) then
if (handles%id_seaice_melt > 0) call post_data(handles%id_seaice_melt, fluxes%seaice_melt, diag)
if (handles%id_total_seaice_melt > 0) then
@@ -2838,12 +2984,26 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
call post_data(handles%id_total_heat_content_lrunoff, total_transport, diag)
endif
+
+ if ((handles%id_heat_content_lrunoff_glc > 0) .and. associated(fluxes%heat_content_lrunoff_glc)) &
+ call post_data(handles%id_heat_content_lrunoff_glc, fluxes%heat_content_lrunoff_glc, diag)
+ if ((handles%id_total_heat_content_lrunoff_glc > 0) .and. associated(fluxes%heat_content_lrunoff_glc)) then
+ total_transport = global_area_integral(fluxes%heat_content_lrunoff_glc, G, scale=US%QRZ_T_to_W_m2)
+ call post_data(handles%id_total_heat_content_lrunoff_glc, total_transport, diag)
+ endif
+
if ((handles%id_heat_content_frunoff > 0) .and. associated(fluxes%heat_content_frunoff)) &
call post_data(handles%id_heat_content_frunoff, fluxes%heat_content_frunoff, diag)
if ((handles%id_total_heat_content_frunoff > 0) .and. associated(fluxes%heat_content_frunoff)) then
total_transport = global_area_integral(fluxes%heat_content_frunoff, G, scale=US%QRZ_T_to_W_m2)
call post_data(handles%id_total_heat_content_frunoff, total_transport, diag)
endif
+ if ((handles%id_heat_content_frunoff_glc > 0) .and. associated(fluxes%heat_content_frunoff_glc)) &
+ call post_data(handles%id_heat_content_frunoff_glc, fluxes%heat_content_frunoff_glc, diag)
+ if ((handles%id_total_heat_content_frunoff_glc > 0) .and. associated(fluxes%heat_content_frunoff_glc)) then
+ total_transport = global_area_integral(fluxes%heat_content_frunoff_glc, G, scale=US%QRZ_T_to_W_m2)
+ call post_data(handles%id_total_heat_content_frunoff_glc, total_transport, diag)
+ endif
if ((handles%id_heat_content_lprec > 0) .and. associated(fluxes%heat_content_lprec)) &
call post_data(handles%id_heat_content_lprec, fluxes%heat_content_lprec, diag)
@@ -2929,6 +3089,10 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
res(i,j) = res(i,j) + fluxes%heat_content_lrunoff(i,j)
if (associated(fluxes%heat_content_frunoff)) &
res(i,j) = res(i,j) + fluxes%heat_content_frunoff(i,j)
+ if (associated(fluxes%heat_content_lrunoff_glc)) &
+ res(i,j) = res(i,j) + fluxes%heat_content_lrunoff_glc(i,j)
+ if (associated(fluxes%heat_content_frunoff_glc)) &
+ res(i,j) = res(i,j) + fluxes%heat_content_frunoff_glc(i,j)
if (associated(fluxes%heat_content_lprec)) &
res(i,j) = res(i,j) + fluxes%heat_content_lprec(i,j)
if (associated(fluxes%heat_content_fprec)) &
@@ -2961,12 +3125,14 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
if (handles%id_heat_content_surfwater > 0 .or. handles%id_total_heat_content_surfwater > 0) then
do j=js,je ; do i=is,ie
res(i,j) = 0.0
- if (associated(fluxes%heat_content_lrunoff)) res(i,j) = res(i,j) + fluxes%heat_content_lrunoff(i,j)
- if (associated(fluxes%heat_content_frunoff)) res(i,j) = res(i,j) + fluxes%heat_content_frunoff(i,j)
- if (associated(fluxes%heat_content_lprec)) res(i,j) = res(i,j) + fluxes%heat_content_lprec(i,j)
- if (associated(fluxes%heat_content_fprec)) res(i,j) = res(i,j) + fluxes%heat_content_fprec(i,j)
- if (associated(fluxes%heat_content_vprec)) res(i,j) = res(i,j) + fluxes%heat_content_vprec(i,j)
- if (associated(fluxes%heat_content_cond)) res(i,j) = res(i,j) + fluxes%heat_content_cond(i,j)
+ if (associated(fluxes%heat_content_lrunoff)) res(i,j) = res(i,j) + fluxes%heat_content_lrunoff(i,j)
+ if (associated(fluxes%heat_content_frunoff)) res(i,j) = res(i,j) + fluxes%heat_content_frunoff(i,j)
+ if (associated(fluxes%heat_content_lrunoff_glc)) res(i,j) = res(i,j) + fluxes%heat_content_lrunoff_glc(i,j)
+ if (associated(fluxes%heat_content_frunoff_glc)) res(i,j) = res(i,j) + fluxes%heat_content_frunoff_glc(i,j)
+ if (associated(fluxes%heat_content_lprec)) res(i,j) = res(i,j) + fluxes%heat_content_lprec(i,j)
+ if (associated(fluxes%heat_content_fprec)) res(i,j) = res(i,j) + fluxes%heat_content_fprec(i,j)
+ if (associated(fluxes%heat_content_vprec)) res(i,j) = res(i,j) + fluxes%heat_content_vprec(i,j)
+ if (associated(fluxes%heat_content_cond)) res(i,j) = res(i,j) + fluxes%heat_content_cond(i,j)
if (mom_enthalpy) then
if (associated(fluxes%heat_content_massout)) res(i,j) = res(i,j) + fluxes%heat_content_massout(i,j)
else
@@ -2986,6 +3152,8 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
res(i,j) = 0.0
if (associated(fluxes%heat_content_lrunoff)) res(i,j) = res(i,j) + fluxes%heat_content_lrunoff(i,j)
if (associated(fluxes%heat_content_frunoff)) res(i,j) = res(i,j) + fluxes%heat_content_frunoff(i,j)
+ if (associated(fluxes%heat_content_lrunoff_glc)) res(i,j) = res(i,j) + fluxes%heat_content_lrunoff_glc(i,j)
+ if (associated(fluxes%heat_content_frunoff_glc)) res(i,j) = res(i,j) + fluxes%heat_content_frunoff_glc(i,j)
enddo ; enddo
call post_data(handles%id_hfrunoffds, res, diag)
endif
@@ -3095,6 +3263,14 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
call post_data(handles%id_total_lat_frunoff, total_transport, diag)
endif
+ if ((handles%id_lat_frunoff_glc > 0) .and. associated(fluxes%latent_frunoff_glc_diag)) then
+ call post_data(handles%id_lat_frunoff_glc, fluxes%latent_frunoff_glc_diag, diag)
+ endif
+ if (handles%id_total_lat_frunoff_glc > 0 .and. associated(fluxes%latent_frunoff_glc_diag)) then
+ total_transport = global_area_integral(fluxes%latent_frunoff_glc_diag, G, scale=US%QRZ_T_to_W_m2)
+ call post_data(handles%id_total_lat_frunoff_glc, total_transport, diag)
+ endif
+
if ((handles%id_sens > 0) .and. associated(fluxes%sens)) then
call post_data(handles%id_sens, fluxes%sens, diag)
endif
@@ -3278,6 +3454,8 @@ subroutine allocate_forcing_by_group(G, fluxes, water, heat, ustar, press, &
call myAlloc(fluxes%vprec,isd,ied,jsd,jed, water)
call myAlloc(fluxes%lrunoff,isd,ied,jsd,jed, water)
call myAlloc(fluxes%frunoff,isd,ied,jsd,jed, water)
+ call myAlloc(fluxes%lrunoff_glc,isd,ied,jsd,jed, water)
+ call myAlloc(fluxes%frunoff_glc,isd,ied,jsd,jed, water)
call myAlloc(fluxes%seaice_melt,isd,ied,jsd,jed, water)
call myAlloc(fluxes%netMassOut,isd,ied,jsd,jed, water)
call myAlloc(fluxes%netMassIn,isd,ied,jsd,jed, water)
@@ -3289,6 +3467,7 @@ subroutine allocate_forcing_by_group(G, fluxes, water, heat, ustar, press, &
call myAlloc(fluxes%latent_evap_diag,isd,ied,jsd,jed, heat)
call myAlloc(fluxes%latent_fprec_diag,isd,ied,jsd,jed, heat)
call myAlloc(fluxes%latent_frunoff_diag,isd,ied,jsd,jed, heat)
+ call myAlloc(fluxes%latent_frunoff_glc_diag,isd,ied,jsd,jed, heat)
call myAlloc(fluxes%salt_flux,isd,ied,jsd,jed, salt)
@@ -3300,6 +3479,8 @@ subroutine allocate_forcing_by_group(G, fluxes, water, heat, ustar, press, &
call myAlloc(fluxes%heat_content_vprec,isd,ied,jsd,jed, .true.)
call myAlloc(fluxes%heat_content_lrunoff,isd,ied,jsd,jed, .true.)
call myAlloc(fluxes%heat_content_frunoff,isd,ied,jsd,jed, .true.)
+ call myAlloc(fluxes%heat_content_lrunoff_glc,isd,ied,jsd,jed, .true.)
+ call myAlloc(fluxes%heat_content_frunoff_glc,isd,ied,jsd,jed, .true.)
call myAlloc(fluxes%heat_content_massout,isd,ied,jsd,jed, enthalpy_mom)
call myAlloc(fluxes%heat_content_massin,isd,ied,jsd,jed, enthalpy_mom)
endif ; endif
@@ -3583,10 +3764,13 @@ subroutine deallocate_forcing_type(fluxes)
if (associated(fluxes%latent_evap_diag)) deallocate(fluxes%latent_evap_diag)
if (associated(fluxes%latent_fprec_diag)) deallocate(fluxes%latent_fprec_diag)
if (associated(fluxes%latent_frunoff_diag)) deallocate(fluxes%latent_frunoff_diag)
+ if (associated(fluxes%latent_frunoff_glc_diag)) deallocate(fluxes%latent_frunoff_glc_diag)
if (associated(fluxes%sens)) deallocate(fluxes%sens)
if (associated(fluxes%heat_added)) deallocate(fluxes%heat_added)
if (associated(fluxes%heat_content_lrunoff)) deallocate(fluxes%heat_content_lrunoff)
if (associated(fluxes%heat_content_frunoff)) deallocate(fluxes%heat_content_frunoff)
+ if (associated(fluxes%heat_content_lrunoff_glc)) deallocate(fluxes%heat_content_lrunoff_glc)
+ if (associated(fluxes%heat_content_frunoff_glc)) deallocate(fluxes%heat_content_frunoff_glc)
if (associated(fluxes%heat_content_lprec)) deallocate(fluxes%heat_content_lprec)
if (associated(fluxes%heat_content_fprec)) deallocate(fluxes%heat_content_fprec)
if (associated(fluxes%heat_content_cond)) deallocate(fluxes%heat_content_cond)
@@ -3599,6 +3783,8 @@ subroutine deallocate_forcing_type(fluxes)
if (associated(fluxes%vprec)) deallocate(fluxes%vprec)
if (associated(fluxes%lrunoff)) deallocate(fluxes%lrunoff)
if (associated(fluxes%frunoff)) deallocate(fluxes%frunoff)
+ if (associated(fluxes%lrunoff_glc)) deallocate(fluxes%lrunoff_glc)
+ if (associated(fluxes%frunoff_glc)) deallocate(fluxes%frunoff_glc)
if (associated(fluxes%seaice_melt)) deallocate(fluxes%seaice_melt)
if (associated(fluxes%netMassOut)) deallocate(fluxes%netMassOut)
if (associated(fluxes%netMassIn)) deallocate(fluxes%netMassIn)
@@ -3682,6 +3868,8 @@ subroutine rotate_forcing(fluxes_in, fluxes, turns)
call rotate_array(fluxes_in%vprec, turns, fluxes%vprec)
call rotate_array(fluxes_in%lrunoff, turns, fluxes%lrunoff)
call rotate_array(fluxes_in%frunoff, turns, fluxes%frunoff)
+ call rotate_array(fluxes_in%lrunoff_glc, turns, fluxes%lrunoff_glc)
+ call rotate_array(fluxes_in%frunoff_glc, turns, fluxes%frunoff_glc)
call rotate_array(fluxes_in%seaice_melt, turns, fluxes%seaice_melt)
call rotate_array(fluxes_in%netMassOut, turns, fluxes%netMassOut)
call rotate_array(fluxes_in%netMassIn, turns, fluxes%netMassIn)
@@ -3696,6 +3884,7 @@ subroutine rotate_forcing(fluxes_in, fluxes, turns)
call rotate_array(fluxes_in%latent_evap_diag, turns, fluxes%latent_evap_diag)
call rotate_array(fluxes_in%latent_fprec_diag, turns, fluxes%latent_fprec_diag)
call rotate_array(fluxes_in%latent_frunoff_diag, turns, fluxes%latent_frunoff_diag)
+ call rotate_array(fluxes_in%latent_frunoff_glc_diag, turns, fluxes%latent_frunoff_glc_diag)
endif
if (do_salt) then
@@ -3708,7 +3897,9 @@ subroutine rotate_forcing(fluxes_in, fluxes, turns)
call rotate_array(fluxes_in%heat_content_fprec, turns, fluxes%heat_content_fprec)
call rotate_array(fluxes_in%heat_content_vprec, turns, fluxes%heat_content_vprec)
call rotate_array(fluxes_in%heat_content_lrunoff, turns, fluxes%heat_content_lrunoff)
+ call rotate_array(fluxes_in%heat_content_lrunoff_glc, turns, fluxes%heat_content_lrunoff_glc)
call rotate_array(fluxes_in%heat_content_frunoff, turns, fluxes%heat_content_frunoff)
+ call rotate_array(fluxes_in%heat_content_frunoff_glc, turns, fluxes%heat_content_frunoff_glc)
if (associated (fluxes_in%heat_content_evap)) then
call rotate_array(fluxes_in%heat_content_evap, turns, fluxes%heat_content_evap)
else
@@ -3956,6 +4147,8 @@ subroutine homogenize_forcing(fluxes, G, GV, US)
call homogenize_field_t(fluxes%vprec, G, tmp_scale=US%RZ_T_to_kg_m2s)
call homogenize_field_t(fluxes%lrunoff, G, tmp_scale=US%RZ_T_to_kg_m2s)
call homogenize_field_t(fluxes%frunoff, G, tmp_scale=US%RZ_T_to_kg_m2s)
+ call homogenize_field_t(fluxes%lrunoff_glc, G, tmp_scale=US%RZ_T_to_kg_m2s)
+ call homogenize_field_t(fluxes%frunoff_glc, G, tmp_scale=US%RZ_T_to_kg_m2s)
call homogenize_field_t(fluxes%seaice_melt, G, tmp_scale=US%RZ_T_to_kg_m2s)
! These two calls might not be needed.
call homogenize_field_t(fluxes%netMassOut, G, tmp_scale=GV%H_to_mks)
@@ -3974,6 +4167,7 @@ subroutine homogenize_forcing(fluxes, G, GV, US)
call homogenize_field_t(fluxes%latent_evap_diag, G, tmp_scale=US%QRZ_T_to_W_m2)
call homogenize_field_t(fluxes%latent_fprec_diag, G, tmp_scale=US%QRZ_T_to_W_m2)
call homogenize_field_t(fluxes%latent_frunoff_diag, G, tmp_scale=US%QRZ_T_to_W_m2)
+ call homogenize_field_t(fluxes%latent_frunoff_glc_diag, G, tmp_scale=US%QRZ_T_to_W_m2)
endif
if (do_salt) call homogenize_field_t(fluxes%salt_flux, G, tmp_scale=US%RZ_T_to_kg_m2s)
@@ -3985,6 +4179,8 @@ subroutine homogenize_forcing(fluxes, G, GV, US)
call homogenize_field_t(fluxes%heat_content_vprec, G, tmp_scale=US%QRZ_T_to_W_m2)
call homogenize_field_t(fluxes%heat_content_lrunoff, G, tmp_scale=US%QRZ_T_to_W_m2)
call homogenize_field_t(fluxes%heat_content_frunoff, G, tmp_scale=US%QRZ_T_to_W_m2)
+ call homogenize_field_t(fluxes%heat_content_lrunoff_glc, G, tmp_scale=US%QRZ_T_to_W_m2)
+ call homogenize_field_t(fluxes%heat_content_frunoff_glc, G, tmp_scale=US%QRZ_T_to_W_m2)
call homogenize_field_t(fluxes%heat_content_massout, G, tmp_scale=US%QRZ_T_to_W_m2)
call homogenize_field_t(fluxes%heat_content_massin, G, tmp_scale=US%QRZ_T_to_W_m2)
endif
diff --git a/src/diagnostics/MOM_sum_output.F90 b/src/diagnostics/MOM_sum_output.F90
index fb95b79a91..fdcee8107d 100644
--- a/src/diagnostics/MOM_sum_output.F90
+++ b/src/diagnostics/MOM_sum_output.F90
@@ -966,8 +966,8 @@ subroutine accumulate_net_input(fluxes, sfc_state, tv, dt, G, US, CS)
if (associated(fluxes%lprec) .and. associated(fluxes%fprec)) then
do j=js,je ; do i=is,ie
FW_in(i,j) = RZL2_to_kg * dt*G%areaT(i,j)*(fluxes%evap(i,j) + &
- (((fluxes%lprec(i,j) + fluxes%vprec(i,j)) + fluxes%lrunoff(i,j)) + &
- (fluxes%fprec(i,j) + fluxes%frunoff(i,j))))
+ (((fluxes%lprec(i,j) + fluxes%vprec(i,j)) + fluxes%lrunoff(i,j) + fluxes%lrunoff_glc(i,j)) + &
+ (fluxes%fprec(i,j) + fluxes%frunoff(i,j) + fluxes%frunoff_glc(i,j))))
enddo ; enddo
else
call MOM_error(WARNING, &
diff --git a/src/parameterizations/vertical/MOM_bulk_mixed_layer.F90 b/src/parameterizations/vertical/MOM_bulk_mixed_layer.F90
index 561ace60a7..e3560dc03e 100644
--- a/src/parameterizations/vertical/MOM_bulk_mixed_layer.F90
+++ b/src/parameterizations/vertical/MOM_bulk_mixed_layer.F90
@@ -528,13 +528,15 @@ subroutine bulkmixedlayer(h_3d, u_3d, v_3d, tv, fluxes, dt, ea, eb, G, GV, US, C
RmixConst = -0.5*CS%rivermix_depth * GV%g_Earth
do i=is,ie
TKE_river(i) = max(0.0, RmixConst * dSpV0_dS(i) * &
- (fluxes%lrunoff(i,j) + fluxes%frunoff(i,j)) * S(i,1))
+ (fluxes%lrunoff(i,j) + fluxes%frunoff(i,j) + &
+ fluxes%lrunoff_glc(i,j) + fluxes%frunoff_glc(i,j)) * S(i,1))
enddo
else
RmixConst = 0.5*CS%rivermix_depth * GV%g_Earth * Irho0**2
do i=is,ie
TKE_river(i) = max(0.0, RmixConst*dR0_dS(i)* &
- (fluxes%lrunoff(i,j) + fluxes%frunoff(i,j)) * S(i,1))
+ (fluxes%lrunoff(i,j) + fluxes%frunoff(i,j) + &
+ fluxes%lrunoff_glc(i,j) + fluxes%frunoff_glc(i,j)) * S(i,1))
enddo
endif
else
diff --git a/src/parameterizations/vertical/MOM_diabatic_aux.F90 b/src/parameterizations/vertical/MOM_diabatic_aux.F90
index aa31024b24..c54240aae2 100644
--- a/src/parameterizations/vertical/MOM_diabatic_aux.F90
+++ b/src/parameterizations/vertical/MOM_diabatic_aux.F90
@@ -1431,7 +1431,8 @@ subroutine applyBoundaryFluxesInOut(CS, G, GV, US, dt, fluxes, optics, nsw, h, t
RivermixConst = -0.5*(CS%rivermix_depth*dt) * GV%Rho0 * ( US%L_to_Z**2*GV%g_Earth )
endif
cTKE(i,j,k) = cTKE(i,j,k) + max(0.0, RivermixConst*dSV_dS(i,j,1) * &
- (fluxes%lrunoff(i,j) + fluxes%frunoff(i,j)) * tv%S(i,j,1))
+ (fluxes%lrunoff(i,j) + fluxes%frunoff(i,j) + &
+ fluxes%lrunoff_glc(i,j) + fluxes%frunoff_glc(i,j)) * tv%S(i,j,1))
endif
! Update state