Skip to content

Commit

Permalink
Updates for dimensional scaling test
Browse files Browse the repository at this point in the history
Currently fails T-scaling test with solo driver, probably fails lots of other
scaling tests as well. This commit

1. Adds debug output to MARBL_tracers.F90
2. Gets dimensions correct in comments of MOM_forcing_type, MARBL_forcing_mod,
   and MARBL_tracers
3. Scales forcings correctly for the MARBL surface_flux_compute() step (at
   least in T); output highlights issues in computing source / sink term from
   interior_tendency_compute()

One of the biggest changes from this commit is the handling of units for the
nitrogen deposition fluxes. It looks like they were coming in as kg/m^2/s,
being converted to mol/L^2/T in fluxes%{nhx_dep,noy_dep}, and then converted to
mmol/m^2/s when copied into MARBL. Now the intermediate stage is mmol/m^3 Z/T;
this is not bit-for-bit with the previous setup because I went from multiplying
by (1000/14) (kg -> mol) and then another 1000 in the third step (mol -> mmol)
to just multiplying by 1e6/14 (kg -> mmol) in the second step.
  • Loading branch information
mnlevy1981 committed Apr 4, 2024
1 parent 3c8beb7 commit 315e1cd
Show file tree
Hide file tree
Showing 5 changed files with 100 additions and 69 deletions.
3 changes: 2 additions & 1 deletion config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1422,7 +1422,8 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
endif

! Set up MARBL forcing control structure
call MARBL_forcing_init(G, param_file, diag, Time, CS%inputdir, CS%use_marbl_tracers, CS%marbl_forcing_CSp)
call MARBL_forcing_init(G, US, param_file, diag, Time, CS%inputdir, CS%use_marbl_tracers, &
CS%marbl_forcing_CSp)

if (present(restore_salt)) then ; if (restore_salt) then
salt_file = trim(CS%inputdir) // trim(CS%salt_restore_file)
Expand Down
35 changes: 19 additions & 16 deletions config_src/drivers/solo_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1562,13 +1562,13 @@ subroutine MARBL_forcing_from_data_override(fluxes, day, G, US, CS)
! Local variables
real, pointer, dimension(:,:) :: atm_co2_prog =>NULL() !< Prognostic atmospheric CO2 concentration [ppm]
real, pointer, dimension(:,:) :: atm_co2_diag =>NULL() !< Diagnostic atmospheric CO2 concentration [ppm]
real, pointer, dimension(:,:) :: atm_fine_dust_flux =>NULL() !< Fine dust flux from atmosphere [kg/m^2/s]
real, pointer, dimension(:,:) :: atm_coarse_dust_flux =>NULL() !< Coarse dust flux from atmosphere [kg/m^2/s]
real, pointer, dimension(:,:) :: seaice_dust_flux =>NULL() !< Dust flux from seaice [kg/m^2/s]
real, pointer, dimension(:,:) :: atm_bc_flux =>NULL() !< Black carbon flux from atmosphere [kg/m^2/s]
real, pointer, dimension(:,:) :: seaice_bc_flux =>NULL() !< Black carbon flux from seaice [kg/m^2/s]
real, pointer, dimension(:,:) :: nhx_dep =>NULL() !< Nitrogen deposition [kg/m^2/s]
real, pointer, dimension(:,:) :: noy_dep =>NULL() !< Nitrogen deposition [kg/m^2/s]
real, pointer, dimension(:,:) :: atm_fine_dust_flux =>NULL() !< Fine dust flux from atmosphere [kg/m^2/s ~> RZ/T]
real, pointer, dimension(:,:) :: atm_coarse_dust_flux =>NULL() !< Coarse dust flux from atmosphere [kg/m^2/s ~> RZ/T]
real, pointer, dimension(:,:) :: seaice_dust_flux =>NULL() !< Dust flux from seaice [kg/m^2/s ~> RZ/T]
real, pointer, dimension(:,:) :: atm_bc_flux =>NULL() !< Black carbon flux from atmosphere [kg/m^2/s ~> RZ/T]
real, pointer, dimension(:,:) :: seaice_bc_flux =>NULL() !< Black carbon flux from seaice [kg/m^2/s ~> RZ/T]
real, pointer, dimension(:,:) :: nhx_dep =>NULL() !< Nitrogen deposition [kg/m^2/s ~> RZ/T]
real, pointer, dimension(:,:) :: noy_dep =>NULL() !< Nitrogen deposition [kg/m^2/s ~> RZ/T]
integer :: isc, iec, jsc, jec

! Necessary null pointers for arguments to convert_marbl_IOB_to_forcings()
Expand Down Expand Up @@ -1608,16 +1608,18 @@ subroutine MARBL_forcing_from_data_override(fluxes, day, G, US, CS)
noy_dep(:,:) = 0.0

call data_override(G%Domain, 'ice_fraction', fluxes%ice_fraction, day)
call data_override(G%Domain, 'u10_sqr', fluxes%u10_sqr, day)
call data_override(G%Domain, 'u10_sqr', fluxes%u10_sqr, day, scale=US%m_s_to_L_T**2)
call data_override(G%Domain, 'atm_co2_prog', atm_co2_prog, day)
call data_override(G%Domain, 'atm_co2_diag', atm_co2_diag, day)
call data_override(G%Domain, 'atm_fine_dust_flux', atm_fine_dust_flux, day)
call data_override(G%Domain, 'atm_coarse_dust_flux', atm_coarse_dust_flux, day)
call data_override(G%Domain, 'atm_bc_flux', atm_bc_flux, day)
call data_override(G%Domain, 'seaice_dust_flux', seaice_dust_flux, day)
call data_override(G%Domain, 'seaice_bc_flux', seaice_bc_flux, day)
call data_override(G%Domain, 'nhx_dep', nhx_dep, day)
call data_override(G%Domain, 'noy_dep', noy_dep, day)
call data_override(G%Domain, 'atm_fine_dust_flux', atm_fine_dust_flux, day, &
scale=US%kg_m2s_to_RZ_T)
call data_override(G%Domain, 'atm_coarse_dust_flux', atm_coarse_dust_flux, day, &
scale=US%kg_m2s_to_RZ_T)
call data_override(G%Domain, 'atm_bc_flux', atm_bc_flux, day, scale=US%kg_m2s_to_RZ_T)
call data_override(G%Domain, 'seaice_dust_flux', seaice_dust_flux, day, scale=US%kg_m2s_to_RZ_T)
call data_override(G%Domain, 'seaice_bc_flux', seaice_bc_flux, day, scale=US%kg_m2s_to_RZ_T)
call data_override(G%Domain, 'nhx_dep', nhx_dep, day, scale=US%kg_m2s_to_RZ_T)
call data_override(G%Domain, 'noy_dep', noy_dep, day, scale=US%kg_m2s_to_RZ_T)

call convert_marbl_IOB_to_forcings(atm_fine_dust_flux, atm_coarse_dust_flux, &
seaice_dust_flux, atm_bc_flux, seaice_bc_flux, &
Expand Down Expand Up @@ -2078,7 +2080,8 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, tracer_flow_C
endif

! Set up MARBL forcing control structure
call MARBL_forcing_init(G, param_file, diag, Time, CS%inputdir, CS%use_marbl_tracers, CS%marbl_forcing_CSp)
call MARBL_forcing_init(G, US, param_file, diag, Time, CS%inputdir, CS%use_marbl_tracers, &
CS%marbl_forcing_CSp)

call register_forcing_type_diags(Time, diag, US, CS%use_temperature, CS%handles)

Expand Down
8 changes: 4 additions & 4 deletions src/core/MOM_forcing_type.F90
Original file line number Diff line number Diff line change
Expand Up @@ -220,12 +220,12 @@ module MOM_forcing_type

! Forcing fields required for MARBL
real, pointer, dimension(:,:) :: &
noy_dep => NULL(), & !< NOy Deposition [R Z T-1 ~> kgN m-2 s-1]
nhx_dep => NULL(), & !< NHx Deposition [R Z T-1 ~> kgN m-2 s-1]
noy_dep => NULL(), & !< NOy Deposition [conc Z T-1 ~> conc m s-1]
nhx_dep => NULL(), & !< NHx Deposition [conc Z T-1 ~> conc m s-1]
atm_co2 => NULL(), & !< Atmospheric CO2 Concentration [ppm]
atm_alt_co2 => NULL(), & !< Alternate atmospheric CO2 Concentration [ppm]
dust_flux => NULL(), & !< Flux of dust into the ocean [m2 m-2]
iron_flux => NULL() !< Flux of dust into the ocean [m2 m-2]
dust_flux => NULL(), & !< Flux of dust into the ocean [R Z T-1 ~> kgN m-2 s-1]
iron_flux => NULL() !< Flux of dust into the ocean [conc Z T-1 ~> conc m s-1]

real, pointer, dimension(:,:,:) :: &
fracr_cat => NULL(), & !< per-category ice fraction
Expand Down
56 changes: 26 additions & 30 deletions src/tracer/MARBL_forcing_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -69,8 +69,9 @@ module MARBL_forcing_mod

contains

subroutine MARBL_forcing_init(G, param_file, diag, day, inputdir, use_marbl, CS)
subroutine MARBL_forcing_init(G, US, param_file, diag, day, inputdir, use_marbl, CS)
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
type(diag_ctrl), target, intent(in) :: diag !< Structure used to regulate diagnostic output.
type(time_type), target, intent(in) :: day !< Time of the start of the run.
Expand Down Expand Up @@ -162,20 +163,20 @@ subroutine MARBL_forcing_init(G, param_file, diag, day, inputdir, use_marbl, CS)
! Register diagnostic fields for outputing forcing values
CS%diag_ids%atm_fine_dust = register_diag_field("ocean_model", "ATM_FINE_DUST_FLUX_CPL", &
CS%diag%axesT1, & ! T=> tracer grid? 1 => no vertical grid
day, "ATM_FINE_DUST_FLUX from cpl", "kg/m^2/s")
day, "ATM_FINE_DUST_FLUX from cpl", "kg/m^2/s", conversion=US%RZ_T_to_kg_m2s)
CS%diag_ids%atm_coarse_dust = register_diag_field("ocean_model", "ATM_COARSE_DUST_FLUX_CPL", &
CS%diag%axesT1, & ! T=> tracer grid? 1 => no vertical grid
day, "ATM_COARSE_DUST_FLUX from cpl", "kg/m^2/s")
day, "ATM_COARSE_DUST_FLUX from cpl", "kg/m^2/s", conversion=US%RZ_T_to_kg_m2s)
CS%diag_ids%atm_bc = register_diag_field("ocean_model", "ATM_BLACK_CARBON_FLUX_CPL", &
CS%diag%axesT1, & ! T=> tracer grid? 1 => no vertical grid
day, "ATM_BLACK_CARBON_FLUX from cpl", "kg/m^2/s")
day, "ATM_BLACK_CARBON_FLUX from cpl", "kg/m^2/s", conversion=US%RZ_T_to_kg_m2s)

CS%diag_ids%ice_dust = register_diag_field("ocean_model", "SEAICE_DUST_FLUX_CPL", &
CS%diag%axesT1, & ! T=> tracer grid? 1 => no vertical grid
day, "SEAICE_DUST_FLUX from cpl", "kg/m^2/s")
day, "SEAICE_DUST_FLUX from cpl", "kg/m^2/s", conversion=US%RZ_T_to_kg_m2s)
CS%diag_ids%ice_bc = register_diag_field("ocean_model", "SEAICE_BLACK_CARBON_FLUX_CPL", &
CS%diag%axesT1, & ! T=> tracer grid? 1 => no vertical grid
day, "SEAICE_BLACK_CARBON_FLUX from cpl", "kg/m^2/s")
day, "SEAICE_BLACK_CARBON_FLUX from cpl", "kg/m^2/s", conversion=US%RZ_T_to_kg_m2s)

end subroutine MARBL_forcing_init

Expand All @@ -186,14 +187,14 @@ subroutine convert_marbl_IOB_to_forcings(atm_fine_dust_flux, atm_coarse_dust_flu
afracr, swnet_afracr, ifrac_n, &
swpen_ifrac_n, Time, G, US, i0, j0, fluxes, CS)

real, dimension(:,:), pointer, intent(in) :: atm_fine_dust_flux !< atmosphere fine dust flux from IOB
real, dimension(:,:), pointer, intent(in) :: atm_coarse_dust_flux !< atmosphere coarse dust flux from IOB
real, dimension(:,:), pointer, intent(in) :: seaice_dust_flux !< sea ice dust flux from IOB
real, dimension(:,:), pointer, intent(in) :: atm_bc_flux !< atmosphere black carbon flux from IOB
real, dimension(:,:), pointer, intent(in) :: seaice_bc_flux !< sea ice black carbon flux from IOB
real, dimension(:,:), pointer, intent(in) :: atm_fine_dust_flux !< atmosphere fine dust flux from IOB [R Z T-1]
real, dimension(:,:), pointer, intent(in) :: atm_coarse_dust_flux !< atmosphere coarse dust flux from IOB [R Z T-1]
real, dimension(:,:), pointer, intent(in) :: seaice_dust_flux !< sea ice dust flux from IOB [R Z T-1]
real, dimension(:,:), pointer, intent(in) :: atm_bc_flux !< atmosphere black carbon flux from IOB [R Z T-1]
real, dimension(:,:), pointer, intent(in) :: seaice_bc_flux !< sea ice black carbon flux from IOB [R Z T-1]
real, dimension(:,:), pointer, intent(in) :: afracr !< open ocean fraction
real, dimension(:,:), pointer, intent(in) :: nhx_dep !< NHx flux from atmosphere
real, dimension(:,:), pointer, intent(in) :: noy_dep !< NOy flux from atmosphere
real, dimension(:,:), pointer, intent(in) :: nhx_dep !< NHx flux from atmosphere [R Z T-1]
real, dimension(:,:), pointer, intent(in) :: noy_dep !< NOy flux from atmosphere [R Z T-1]
real, dimension(:,:), pointer, intent(in) :: atm_co2_prog !< Prognostic atmospheric CO2 concentration
real, dimension(:,:), pointer, intent(in) :: atm_co2_diag !< Diagnostic atmospheric CO2 concentration
real, dimension(:,:), pointer, intent(in) :: swnet_afracr !< shortwave flux * open ocean fraction
Expand Down Expand Up @@ -221,29 +222,25 @@ subroutine convert_marbl_IOB_to_forcings(atm_fine_dust_flux, atm_coarse_dust_flu
if (.not. CS%use_marbl_tracers) return

is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec
ndep_conversion = (1000./14.) * ((US%L_to_m**2) * US%T_to_s)
iron_flux_conversion = US%kg_m2s_to_RZ_T * 1.e6 / molw_Fe ! kg / m^2 / s -> mmol / m^2 / s
ndep_conversion = (US%RZ_T_to_kg_m2s * US%m_to_Z * US%T_to_s) * (1.e6/14.) ! R Z / T -> mmol / m^3 Z / T
iron_flux_conversion = (US%RZ_T_to_kg_m2s * US%m_to_Z * US%T_to_s) * 1.e6 / molw_Fe ! R Z / T -> mmol / m^3 Z / T

! Post fields from coupler to diagnostics
! TODO: units from diag register are incorrect; we should be converting these in the cap, I think
if (CS%diag_ids%atm_fine_dust > 0) &
call post_data(CS%diag_ids%atm_fine_dust, &
US%kg_m2s_to_RZ_T * atm_fine_dust_flux(is-i0:ie-i0,js-j0:je-j0), CS%diag, &
mask=G%mask2dT(is:ie,js:je))
call post_data(CS%diag_ids%atm_fine_dust, atm_fine_dust_flux(is-i0:ie-i0,js-j0:je-j0), &
CS%diag, mask=G%mask2dT(is:ie,js:je))
if (CS%diag_ids%atm_coarse_dust > 0) &
call post_data(CS%diag_ids%atm_coarse_dust, &
US%kg_m2s_to_RZ_T * atm_coarse_dust_flux(is-i0:ie-i0,js-j0:je-j0), CS%diag, &
mask=G%mask2dT(is:ie,js:je))
if (CS%diag_ids%atm_bc > 0) &
call post_data(CS%diag_ids%atm_bc, US%kg_m2s_to_RZ_T * atm_bc_flux(is-i0:ie-i0,js-j0:je-j0), &
call post_data(CS%diag_ids%atm_coarse_dust, atm_coarse_dust_flux(is-i0:ie-i0,js-j0:je-j0), &
CS%diag, mask=G%mask2dT(is:ie,js:je))
if (CS%diag_ids%atm_bc > 0) &
call post_data(CS%diag_ids%atm_bc, atm_bc_flux(is-i0:ie-i0,js-j0:je-j0), CS%diag, &
mask=G%mask2dT(is:ie,js:je))
if (CS%diag_ids%ice_dust > 0) &
call post_data(CS%diag_ids%ice_dust, &
US%kg_m2s_to_RZ_T * seaice_dust_flux(is-i0:ie-i0,js-j0:je-j0), CS%diag, &
call post_data(CS%diag_ids%ice_dust, seaice_dust_flux(is-i0:ie-i0,js-j0:je-j0), CS%diag, &
mask=G%mask2dT(is:ie,js:je))
if (CS%diag_ids%ice_bc > 0) &
call post_data(CS%diag_ids%ice_bc, &
US%kg_m2s_to_RZ_T * seaice_bc_flux(is-i0:ie-i0,js-j0:je-j0), CS%diag, &
call post_data(CS%diag_ids%ice_bc, seaice_bc_flux(is-i0:ie-i0,js-j0:je-j0), CS%diag, &
mask=G%mask2dT(is:ie,js:je))

do j=js,je ; do i=is,ie
Expand Down Expand Up @@ -306,9 +303,8 @@ subroutine convert_marbl_IOB_to_forcings(atm_fine_dust_flux, atm_coarse_dust_flu

if (associated(atm_fine_dust_flux)) then
do j=js,je ; do i=is,ie
fluxes%dust_flux(i,j) = (G%mask2dT(i,j) * US%kg_m2s_to_RZ_T) * &
(atm_fine_dust_flux(i-i0,j-j0) + atm_coarse_dust_flux(i-i0,j-j0) + &
seaice_dust_flux(i-i0,j-j0))
fluxes%dust_flux(i,j) = G%mask2dT(i,j) * (atm_fine_dust_flux(i-i0,j-j0) + &
atm_coarse_dust_flux(i-i0,j-j0) + seaice_dust_flux(i-i0,j-j0))
enddo ; enddo
endif

Expand Down
Loading

0 comments on commit 315e1cd

Please sign in to comment.