Skip to content

Commit

Permalink
Merge pull request #87 from gustavo-marques/update_mct_fluxes
Browse files Browse the repository at this point in the history
Introduces additional fluxes used in the CESM framework
  • Loading branch information
alperaltuntas authored Dec 17, 2018
2 parents dd6cb7f + 4b81577 commit c7121e5
Show file tree
Hide file tree
Showing 7 changed files with 231 additions and 94 deletions.
37 changes: 27 additions & 10 deletions config_src/mct_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -152,11 +152,13 @@ module MOM_surface_forcing
! MOM-based coupled models.
type, public :: ice_ocean_boundary_type
real, pointer, dimension(:,:) :: latent_flux =>NULL() !< latent flux (W/m2)
real, pointer, dimension(:,:) :: rofl_flux =>NULL() !< liquid runoff (W/m2)
real, pointer, dimension(:,:) :: rofi_flux =>NULL() !< ice runoff (W/m2)
real, pointer, dimension(:,:) :: rofl_flux =>NULL() !< liquid runoff (kg/m2/s)
real, pointer, dimension(:,:) :: rofi_flux =>NULL() !< ice runoff (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)
real, pointer, dimension(:,:) :: melth =>NULL() !< sea ice and snow melt heat flux (W/m2)
real, pointer, dimension(:,:) :: meltw =>NULL() !< water flux due to sea ice and snow melting (kg/m2/s)
real, pointer, dimension(:,:) :: q_flux =>NULL() !< specific humidity flux (kg/m2/s)
real, pointer, dimension(:,:) :: salt_flux =>NULL() !< salt flux (kg/m2/s)
real, pointer, dimension(:,:) :: lw_flux =>NULL() !< long wave radiation (W/m2)
Expand All @@ -166,7 +168,6 @@ module MOM_surface_forcing
real, pointer, dimension(:,:) :: sw_flux_nir_dif =>NULL() !< diffuse Near InfraRed sw radiation (W/m2)
real, pointer, dimension(:,:) :: lprec =>NULL() !< mass flux of liquid precip (kg/m2/s)
real, pointer, dimension(:,:) :: fprec =>NULL() !< mass flux of frozen precip (kg/m2/s)
real, pointer, dimension(:,:) :: runoff =>NULL() !< mass flux of liquid runoff (kg/m2/s)
real, pointer, dimension(:,:) :: calving =>NULL() !< mass flux of frozen runoff (kg/m2/s)
real, pointer, dimension(:,:) :: ustar_berg =>NULL() !< frictional velocity beneath icebergs (m/s)
real, pointer, dimension(:,:) :: area_berg =>NULL() !< area covered by icebergs(m2/m2)
Expand Down Expand Up @@ -443,6 +444,14 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, Time, G, CS, &
if (associated(fluxes%sens)) &
fluxes%sens(i,j) = G%mask2dT(i,j) * IOB%t_flux(i-i0,j-j0)

! sea ice and snow melt heat flux (W/m2)
if (associated(fluxes%melth)) &
fluxes%melth(i,j) = G%mask2dT(i,j) * IOB%melth(i-i0,j-j0)

! water flux due to sea ice and snow melt (kg/m2/s)
if (associated(fluxes%meltw)) &
fluxes%meltw(i,j) = G%mask2dT(i,j) * IOB%meltw(i-i0,j-j0)

! latent heat flux (W/m^2)
if (associated(fluxes%latent)) &
fluxes%latent(i,j) = G%mask2dT(i,j) * IOB%latent_flux(i-i0,j-j0)
Expand Down Expand Up @@ -474,7 +483,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, Time, G, CS, &
sign_for_net_FW_bug = 1.
if (CS%use_net_FW_adjustment_sign_bug) sign_for_net_FW_bug = -1.
do j=js,je ; do i=is,ie
net_FW(i,j) = (((fluxes%lprec(i,j) + fluxes%fprec(i,j)) + &
net_FW(i,j) = (((fluxes%lprec(i,j) + fluxes%fprec(i,j) + fluxes%meltw(i,j)) + &
(fluxes%lrunoff(i,j) + fluxes%frunoff(i,j))) + &
(fluxes%evap(i,j) + fluxes%vprec(i,j)) ) * G%areaT(i,j)
! The following contribution appears to be calculating the volume flux of sea-ice
Expand All @@ -483,9 +492,12 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, Time, G, CS, &
! Bob thinks this is trying ensure the net fresh-water of the ocean + sea-ice system
! is constant.
! To do this correctly we will need a sea-ice melt field added to IOB. -AJA
if (associated(IOB%salt_flux) .and. (CS%ice_salt_concentration>0.0)) &
net_FW(i,j) = net_FW(i,j) + sign_for_net_FW_bug * G%areaT(i,j) * &
(IOB%salt_flux(i-i0,j-j0) / CS%ice_salt_concentration)
! GMM: as stated above, the following is wrong. CIME deals with volume/mass and
! heat from sea ice/snow via meltw and melth, respectively.
if (associated(fluxes%salt_flux) .and. (CS%ice_salt_concentration>0.0)) &
net_FW(i,j) = net_FW(i,j) + G%areaT(i,j) * &
(fluxes%salt_flux(i,j) / CS%ice_salt_concentration)

net_FW2(i,j) = net_FW(i,j)/G%areaT(i,j)
enddo; enddo

Expand Down Expand Up @@ -775,6 +787,8 @@ subroutine IOB_allocate(IOB, isc, iec, jsc, jec)
IOB% u_flux (isc:iec,jsc:jec), &
IOB% v_flux (isc:iec,jsc:jec), &
IOB% t_flux (isc:iec,jsc:jec), &
IOB% melth (isc:iec,jsc:jec), &
IOB% meltw (isc:iec,jsc:jec), &
IOB% q_flux (isc:iec,jsc:jec), &
IOB% salt_flux (isc:iec,jsc:jec), &
IOB% lw_flux (isc:iec,jsc:jec), &
Expand All @@ -784,7 +798,6 @@ subroutine IOB_allocate(IOB, isc, iec, jsc, jec)
IOB% sw_flux_nir_dif (isc:iec,jsc:jec), &
IOB% lprec (isc:iec,jsc:jec), &
IOB% fprec (isc:iec,jsc:jec), &
IOB% runoff (isc:iec,jsc:jec), &
IOB% ustar_berg (isc:iec,jsc:jec), &
IOB% area_berg (isc:iec,jsc:jec), &
IOB% mass_berg (isc:iec,jsc:jec), &
Expand All @@ -800,6 +813,8 @@ subroutine IOB_allocate(IOB, isc, iec, jsc, jec)
IOB%u_flux = 0.0
IOB%v_flux = 0.0
IOB%t_flux = 0.0
IOB%melth = 0.0
IOB%meltw = 0.0
IOB%q_flux = 0.0
IOB%salt_flux = 0.0
IOB%lw_flux = 0.0
Expand All @@ -809,7 +824,6 @@ subroutine IOB_allocate(IOB, isc, iec, jsc, jec)
IOB%sw_flux_nir_dif = 0.0
IOB%lprec = 0.0
IOB%fprec = 0.0
IOB%runoff = 0.0
IOB%ustar_berg = 0.0
IOB%area_berg = 0.0
IOB%mass_berg = 0.0
Expand Down Expand Up @@ -1320,7 +1334,11 @@ subroutine ice_ocn_bnd_type_chksum(id, timestep, iobt)
write(outunit,100) 'iobt%u_flux ', mpp_chksum( iobt%u_flux )
write(outunit,100) 'iobt%v_flux ', mpp_chksum( iobt%v_flux )
write(outunit,100) 'iobt%t_flux ', mpp_chksum( iobt%t_flux )
write(outunit,100) 'iobt%melth ', mpp_chksum( iobt%melth )
write(outunit,100) 'iobt%meltw ', mpp_chksum( iobt%meltw )
write(outunit,100) 'iobt%q_flux ', mpp_chksum( iobt%q_flux )
write(outunit,100) 'iobt%rofl_flux ', mpp_chksum( iobt%rofl_flux )
write(outunit,100) 'iobt%rofi_flux ', mpp_chksum( iobt%rofi_flux )
write(outunit,100) 'iobt%salt_flux ', mpp_chksum( iobt%salt_flux )
write(outunit,100) 'iobt%lw_flux ', mpp_chksum( iobt%lw_flux )
write(outunit,100) 'iobt%sw_flux_vis_dir', mpp_chksum( iobt%sw_flux_vis_dir)
Expand All @@ -1329,7 +1347,6 @@ subroutine ice_ocn_bnd_type_chksum(id, timestep, iobt)
write(outunit,100) 'iobt%sw_flux_nir_dif', mpp_chksum( iobt%sw_flux_nir_dif)
write(outunit,100) 'iobt%lprec ', mpp_chksum( iobt%lprec )
write(outunit,100) 'iobt%fprec ', mpp_chksum( iobt%fprec )
write(outunit,100) 'iobt%runoff ', mpp_chksum( iobt%runoff )
write(outunit,100) 'iobt%calving ', mpp_chksum( iobt%calving )
write(outunit,100) 'iobt%p ', mpp_chksum( iobt%p )
if (associated(iobt%ustar_berg)) &
Expand Down
42 changes: 24 additions & 18 deletions config_src/mct_driver/ocn_cap_methods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ subroutine ocn_import(x2o, ind, grid, ice_ocean_boundary, ocean_public, logunit,
real(kind=8), optional , intent(in) :: c1, c2, c3, c4 !< Coeffs. used in the shortwave decomposition

! Local variables
integer :: i, j, ig, jg, isc, iec, jsc, jec ! Grid indices
integer :: i, j, isc, iec, jsc, jec ! Grid indices
integer :: k
integer :: day, secs, rc
type(ESMF_time) :: currTime
Expand All @@ -44,9 +44,7 @@ subroutine ocn_import(x2o, ind, grid, ice_ocean_boundary, ocean_public, logunit,

k = 0
do j = jsc, jec
jg = j + grid%jsc - jsc
do i = isc, iec
ig = i + grid%jsc - isc
k = k + 1 ! Increment position within gindex

! taux
Expand All @@ -65,41 +63,47 @@ subroutine ocn_import(x2o, ind, grid, ice_ocean_boundary, ocean_public, logunit,
ice_ocean_boundary%lw_flux(i,j) = (x2o(ind%x2o_Faxa_lwdn,k) + x2o(ind%x2o_Foxx_lwup,k))

! specific humitidy flux
ice_ocean_boundary%q_flux(i,j) = x2o(ind%x2o_Foxx_evap,k) !???TODO: should this be a minus sign
ice_ocean_boundary%q_flux(i,j) = x2o(ind%x2o_Foxx_evap,k)

! sensible heat flux (W/m2)
ice_ocean_boundary%t_flux(i,j) = x2o(ind%x2o_Foxx_sen,k) !???TODO: should this be a minus sign
ice_ocean_boundary%t_flux(i,j) = x2o(ind%x2o_Foxx_sen,k)

! latent heat flux (W/m^2)
ice_ocean_boundary%latent_flux(i,j) = x2o(ind%x2o_Foxx_lat,k) !???TODO: should this be a minus sign
ice_ocean_boundary%latent_flux(i,j) = x2o(ind%x2o_Foxx_lat,k)

! snow&ice melt heat flux (W/m^2)
ice_ocean_boundary%melth(i,j) = x2o(ind%x2o_Fioi_melth,k)

! water flux from snow&ice melt (kg/m2/s)
ice_ocean_boundary%meltw(i,j) = x2o(ind%x2o_Fioi_meltw,k)

! liquid runoff
ice_ocean_boundary%rofl_flux(i,j) = x2o(ind%x2o_Foxx_rofl,k) * GRID%mask2dT(ig,jg)
ice_ocean_boundary%rofl_flux(i,j) = x2o(ind%x2o_Foxx_rofl,k) * GRID%mask2dT(i,j)

! ice runoff
ice_ocean_boundary%rofi_flux(i,j) = x2o(ind%x2o_Foxx_rofi,k) * GRID%mask2dT(ig,jg)
ice_ocean_boundary%rofi_flux(i,j) = x2o(ind%x2o_Foxx_rofi,k) * GRID%mask2dT(i,j)

! surface pressure
ice_ocean_boundary%p(i,j) = x2o(ind%x2o_Sa_pslv,k) * GRID%mask2dT(ig,jg)
ice_ocean_boundary%p(i,j) = x2o(ind%x2o_Sa_pslv,k) * GRID%mask2dT(i,j)

! salt flux (minus sign needed here -GMM)
ice_ocean_boundary%salt_flux(i,j) = -x2o(ind%x2o_Fioi_salt,k) * GRID%mask2dT(ig,jg)
ice_ocean_boundary%salt_flux(i,j) = -x2o(ind%x2o_Fioi_salt,k) * GRID%mask2dT(i,j)

! 1) visible, direct shortwave (W/m2)
! 2) visible, diffuse shortwave (W/m2)
! 3) near-IR, direct shortwave (W/m2)
! 4) near-IR, diffuse shortwave (W/m2)
if (present(c1) .and. present(c2) .and. present(c3) .and. present(c4)) then
! Use runtime coefficients to decompose net short-wave heat flux into 4 components
ice_ocean_boundary%sw_flux_vis_dir(i,j) = x2o(ind%x2o_Foxx_swnet,k) * c1 * GRID%mask2dT(ig,jg)
ice_ocean_boundary%sw_flux_vis_dif(i,j) = x2o(ind%x2o_Foxx_swnet,k) * c2 * GRID%mask2dT(ig,jg)
ice_ocean_boundary%sw_flux_nir_dir(i,j) = x2o(ind%x2o_Foxx_swnet,k) * c3 * GRID%mask2dT(ig,jg)
ice_ocean_boundary%sw_flux_nir_dif(i,j) = x2o(ind%x2o_Foxx_swnet,k) * c4 * GRID%mask2dT(ig,jg)
ice_ocean_boundary%sw_flux_vis_dir(i,j) = x2o(ind%x2o_Foxx_swnet,k) * c1 * GRID%mask2dT(i,j)
ice_ocean_boundary%sw_flux_vis_dif(i,j) = x2o(ind%x2o_Foxx_swnet,k) * c2 * GRID%mask2dT(i,j)
ice_ocean_boundary%sw_flux_nir_dir(i,j) = x2o(ind%x2o_Foxx_swnet,k) * c3 * GRID%mask2dT(i,j)
ice_ocean_boundary%sw_flux_nir_dif(i,j) = x2o(ind%x2o_Foxx_swnet,k) * c4 * GRID%mask2dT(i,j)
else
ice_ocean_boundary%sw_flux_vis_dir(i,j) = x2o(ind%x2o_Faxa_swvdr,k) * GRID%mask2dT(ig,jg)
ice_ocean_boundary%sw_flux_vis_dif(i,j) = x2o(ind%x2o_Faxa_swvdf,k) * GRID%mask2dT(ig,jg)
ice_ocean_boundary%sw_flux_nir_dir(i,j) = x2o(ind%x2o_Faxa_swndr,k) * GRID%mask2dT(ig,jg)
ice_ocean_boundary%sw_flux_nir_dif(i,j) = x2o(ind%x2o_Faxa_swndf,k) * GRID%mask2dT(ig,jg)
ice_ocean_boundary%sw_flux_vis_dir(i,j) = x2o(ind%x2o_Faxa_swvdr,k) * GRID%mask2dT(i,j)
ice_ocean_boundary%sw_flux_vis_dif(i,j) = x2o(ind%x2o_Faxa_swvdf,k) * GRID%mask2dT(i,j)
ice_ocean_boundary%sw_flux_nir_dir(i,j) = x2o(ind%x2o_Faxa_swndr,k) * GRID%mask2dT(i,j)
ice_ocean_boundary%sw_flux_nir_dif(i,j) = x2o(ind%x2o_Faxa_swndf,k) * GRID%mask2dT(i,j)
endif
enddo
enddo
Expand All @@ -116,6 +120,8 @@ subroutine ocn_import(x2o, ind, grid, ice_ocean_boundary, ocean_public, logunit,
write(logunit,F01)'import: day, secs, j, i, lwrad = ',day,secs,j,i,ice_ocean_boundary%lw_flux(i,j)
write(logunit,F01)'import: day, secs, j, i, q_flux = ',day,secs,j,i,ice_ocean_boundary%q_flux(i,j)
write(logunit,F01)'import: day, secs, j, i, t_flux = ',day,secs,j,i,ice_ocean_boundary%t_flux(i,j)
write(logunit,F01)'import: day, secs, j, i, melth = ',day,secs,j,i,ice_ocean_boundary%melth(i,j)
write(logunit,F01)'import: day, secs, j, i, meltw = ',day,secs,j,i,ice_ocean_boundary%meltw(i,j)
write(logunit,F01)'import: day, secs, j, i, latent_flux = ',&
day,secs,j,i,ice_ocean_boundary%latent_flux(i,j)
write(logunit,F01)'import: day, secs, j, i, runoff = ',&
Expand Down
2 changes: 0 additions & 2 deletions config_src/mct_driver/ocn_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -773,8 +773,6 @@ end subroutine ocean_model_init_sfc
!! mi, mass of ice (kg/m2)
!!
!! Variables in the coupler that are **NOT** used in MOM6 (i.e., no corresponding field in fluxes):
!! x2o_Fioi_melth, heat flux from snow & ice melt (W/m2)
!! x2o_Fioi_meltw, snow melt flux (kg/m2/s)
!! x2o_Si_ifrac, fractional ice wrt ocean
!! x2o_So_duu10n, 10m wind speed squared (m^2/s^2)
!! x2o_Sa_co2prog, bottom atm level prognostic CO2
Expand Down
2 changes: 1 addition & 1 deletion config_src/mct_driver/ocn_cpl_indices.F90
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ module ocn_cpl_indices
integer :: x2o_Faxa_swndr !< near-IR, direct shortwave (W/m2)
integer :: x2o_Faxa_swndf !< near-IR, direct shortwave (W/m2)
integer :: x2o_Fioi_melth !< Heat flux from snow & ice melt (W/m2)
integer :: x2o_Fioi_meltw !< Snow melt flux (kg/m2/s)
integer :: x2o_Fioi_meltw !< Water flux from sea ice and snow melt (kg/m2/s)
integer :: x2o_Fioi_bcpho !< Black Carbon hydrophobic release from sea ice component
integer :: x2o_Fioi_bcphi !< Black Carbon hydrophilic release from sea ice component
integer :: x2o_Fioi_flxdst !< Dust release from sea ice component
Expand Down
Loading

0 comments on commit c7121e5

Please sign in to comment.