Skip to content

Commit

Permalink
Merge pull request #242 from klindsay28/cfc_cap_mv_code_out_of_cap
Browse files Browse the repository at this point in the history
migrate nearly all refs to CFC_cap into MOM_tracer_flow_control and MOM_CFC_cap
  • Loading branch information
gustavo-marques authored Mar 28, 2023
2 parents 72e5535 + ebf11d7 commit 59cc9ed
Show file tree
Hide file tree
Showing 8 changed files with 166 additions and 238 deletions.
17 changes: 11 additions & 6 deletions config_src/drivers/nuopc_cap/mom_ocean_model_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ module MOM_ocean_model_nuopc
use MOM_time_manager, only : operator(/=), operator(<=), operator(>=)
use MOM_time_manager, only : operator(<), real_to_time_type, time_type_to_real
use MOM_interpolate, only : time_interp_external_init
use MOM_tracer_flow_control, only : call_tracer_flux_init
use MOM_tracer_flow_control, only : tracer_flow_control_CS, call_tracer_flux_init, call_tracer_set_forcing
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : surface
use MOM_verticalGrid, only : verticalGrid_type
Expand Down Expand Up @@ -210,6 +210,8 @@ module MOM_ocean_model_nuopc
type(marine_ice_CS), pointer :: &
marine_ice_CSp => NULL() !< A pointer to the control structure for the
!! marine ice effects module.
type(tracer_flow_control_CS), pointer :: &
tracer_flow_CSp => NULL() !< A pointer to the tracer flow control structure
type(wave_parameters_CS), pointer, public :: &
Waves => NULL() !< A pointer to the surface wave control structure
type(surface_forcing_CS), pointer :: &
Expand Down Expand Up @@ -255,7 +257,6 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
!! min(HFrz, OBLD), where OBLD is the boundary layer depth.
!! If HFrz <= 0 (default), melt potential will not be computed.
logical :: use_melt_pot !< If true, allocate melt_potential array
logical :: use_CFC !< If true, allocated arrays for surface CFCs.


! This include declares and sets the variable "version".
Expand Down Expand Up @@ -283,7 +284,8 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
call initialize_MOM(OS%Time, Time_init, param_file, OS%dirs, OS%MOM_CSp, &
OS%restart_CSp, Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
input_restart_file=input_restart_file, &
diag_ptr=OS%diag, count_calls=.true., waves_CSp=OS%Waves)
diag_ptr=OS%diag, count_calls=.true., tracer_flow_CSp=OS%tracer_flow_CSp, &
waves_CSp=OS%Waves)
call get_MOM_state_elements(OS%MOM_CSp, G=OS%grid, GV=OS%GV, US=OS%US, C_p=OS%C_p, &
C_p_scaled=OS%fluxes%C_p, use_temp=use_temperature)

Expand Down Expand Up @@ -375,16 +377,14 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
use_melt_pot=.false.
endif

call get_param(param_file, mdl, "USE_CFC_CAP", use_CFC, &
default=.false., do_not_log=.true.)
call get_param(param_file, mdl, "USE_WAVES", OS%Use_Waves, &
"If true, enables surface wave modules.", default=.false.)

! Consider using a run-time flag to determine whether to do the diagnostic
! vertical integrals, since the related 3-d sums are not negligible in cost.
call allocate_surface_state(OS%sfc_state, OS%grid, use_temperature, &
do_integrals=.true., gas_fields_ocn=gas_fields_ocn, &
use_meltpot=use_melt_pot, use_cfcs=use_CFC)
use_meltpot=use_melt_pot)

call surface_forcing_init(Time_in, OS%grid, OS%US, param_file, OS%diag, &
OS%forcing_CSp, OS%restore_salinity, OS%restore_temp, OS%use_waves)
Expand Down Expand Up @@ -610,6 +610,11 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp, OS%restart_CSp)
endif

if (do_thermo) &
call call_tracer_set_forcing(OS%sfc_state, OS%fluxes, OS%Time, &
real_to_time_type(dt_coupling), OS%grid, OS%US, OS%GV%Rho0, &
OS%tracer_flow_CSp)

call disable_averaging(OS%diag)
Master_time = OS%Time ; Time1 = OS%Time

Expand Down
56 changes: 0 additions & 56 deletions config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@ module MOM_surface_forcing_nuopc
use MOM_grid, only : ocean_grid_type
use MOM_interpolate, only : init_external_field, time_interp_external
use MOM_interpolate, only : time_interp_external_init
use MOM_CFC_cap, only : CFC_cap_fluxes
use MOM_io, only : slasher, write_version_number, MOM_read_data
use MOM_io, only : stdout
use MOM_restart, only : register_restart_field, restart_init, MOM_restart_CS
Expand Down Expand Up @@ -129,7 +128,6 @@ module MOM_surface_forcing_nuopc

type(diag_ctrl), pointer :: diag !< structure to regulate diagnostic output timing
character(len=200) :: inputdir !< directory where NetCDF input files are
character(len=200) :: CFC_BC_file !< filename with cfc11 and cfc12 data
character(len=200) :: salt_restore_file !< filename for salt restoring data
character(len=30) :: salt_restore_var_name !< name of surface salinity in salt_restore_file
logical :: mask_srestore !< if true, apply a 2-dimensional mask to the surface
Expand All @@ -146,11 +144,6 @@ module MOM_surface_forcing_nuopc
real, pointer, dimension(:,:) :: trestore_mask => NULL() !< mask for SST restoring
integer :: id_srestore = -1 !< id number for time_interp_external.
integer :: id_trestore = -1 !< id number for time_interp_external.
integer :: CFC_BC_year_offset = 0 !< offset to add to model time to get time value used in CFC_BC_file
integer :: id_cfc11_atm_nh = -1 !< id number for time_interp_external.
integer :: id_cfc11_atm_sh = -1 !< id number for time_interp_external.
integer :: id_cfc12_atm_nh = -1 !< id number for time_interp_external.
integer :: id_cfc12_atm_sh = -1 !< id number for time_interp_external.

! Diagnostics handles
type(forcing_diags), public :: handles
Expand Down Expand Up @@ -593,13 +586,6 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
fluxes%accumulate_p_surf = .true. ! Multiple components may contribute to surface pressure.
endif

! CFCs
if (CS%use_CFC) then
call CFC_cap_fluxes(fluxes, sfc_state, G, US, CS%Rho0, Time, CS%CFC_BC_year_offset, &
CS%id_cfc11_atm_nh, CS%id_cfc11_atm_sh, &
CS%id_cfc12_atm_nh, CS%id_cfc12_atm_sh)
endif

if (associated(IOB%salt_flux)) then
do j=js,je ; do i=is,ie
fluxes%salt_flux(i,j) = G%mask2dT(i,j)*(fluxes%salt_flux(i,j) + kg_m2_s_conversion*IOB%salt_flux(i-i0,j-j0))
Expand Down Expand Up @@ -1117,13 +1103,7 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
character(len=48) :: stagger
character(len=48) :: flnam
character(len=240) :: basin_file
character(len=30) :: cfc11_nh_var_name ! name of cfc11 nh in CFC_BC_file
character(len=30) :: cfc11_sh_var_name ! name of cfc11 sh in CFC_BC_file
character(len=30) :: cfc12_nh_var_name ! name of cfc12 nh in CFC_BC_file
character(len=30) :: cfc12_sh_var_name ! name of cfc12 sh in CFC_BC_file
integer :: i, j, isd, ied, jsd, jed
integer :: CFC_BC_data_year ! specific year in CFC BC data calendar
integer :: CFC_BC_model_year ! model year corresponding to CFC_BC_data_year

isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed

Expand Down Expand Up @@ -1419,42 +1399,6 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt,
endif
endif ; endif

! Do not log these params here since they are logged in the CFC cap module
if (CS%use_CFC) then
call get_param(param_file, mdl, "CFC_BC_FILE", CS%CFC_BC_file, &
"The file in which the CFC-11 and CFC-12 atm concentrations can be "//&
"found (units must be parts per trillion).", default=" ", do_not_log=.true.)
if (len_trim(CS%CFC_BC_file) == 0) then
call MOM_error(FATAL, "CFC_BC_FILE must be specified if USE_CFC_CAP=.true.")
endif
if (scan(CS%CFC_BC_file, '/') == 0) then
! Add the directory if CFC_BC_file is not already a complete path.
CS%CFC_BC_file = trim(CS%inputdir)//trim(CS%CFC_BC_file)
endif
call get_param(param_file, mdl, "CFC_BC_DATA_YEAR", CFC_BC_data_year, &
"Specific year in CFC_BC_FILE data calendar", default=2000, do_not_log=.true.)
call get_param(param_file, mdl, "CFC_BC_MODEL_YEAR", CFC_BC_model_year, &
"Model year corresponding to CFC_BC_MODEL_YEAR", default=2000, do_not_log=.true.)
CS%CFC_BC_year_offset = CFC_BC_data_year - CFC_BC_model_year
call get_param(param_file, mdl, "CFC11_NH_VARIABLE", cfc11_nh_var_name, &
"Variable name of NH CFC-11 atm mole fraction in CFC_BC_FILE.", &
default="cfc11_nh", do_not_log=.true.)
call get_param(param_file, mdl, "CFC11_SH_VARIABLE", cfc11_sh_var_name, &
"Variable name of SH CFC-11 atm mole fraction in CFC_BC_FILE.", &
default="cfc11_sh", do_not_log=.true.)
call get_param(param_file, mdl, "CFC12_NH_VARIABLE", cfc12_nh_var_name, &
"Variable name of NH CFC-12 atm mole fraction in CFC_BC_FILE.", &
default="cfc12_nh", do_not_log=.true.)
call get_param(param_file, mdl, "CFC12_SH_VARIABLE", cfc12_sh_var_name, &
"Variable name of SH CFC-12 atm mole fraction in CFC_BC_FILE.", &
default="cfc12_sh", do_not_log=.true.)

CS%id_cfc11_atm_nh = init_external_field(CS%CFC_BC_file, cfc11_nh_var_name)
CS%id_cfc11_atm_sh = init_external_field(CS%CFC_BC_file, cfc11_sh_var_name)
CS%id_cfc12_atm_nh = init_external_field(CS%CFC_BC_file, cfc12_nh_var_name)
CS%id_cfc12_atm_sh = init_external_field(CS%CFC_BC_file, cfc12_sh_var_name)
endif

! Set up any restart fields associated with the forcing.
call restart_init(param_file, CS%restart_CSp, "MOM_forcing.res")
call restart_init_end(CS%restart_CSp)
Expand Down
3 changes: 2 additions & 1 deletion config_src/drivers/solo_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -345,7 +345,8 @@ subroutine set_forcing(sfc_state, forces, fluxes, day_start, day_interval, G, US
endif

if (associated(CS%tracer_flow_CSp)) then
call call_tracer_set_forcing(sfc_state, fluxes, day_start, day_interval, G, CS%tracer_flow_CSp)
call call_tracer_set_forcing(sfc_state, fluxes, day_start, day_interval, G, US, CS%Rho0, &
CS%tracer_flow_CSp)
endif

! Allow for user-written code to alter the fluxes after all the above
Expand Down
44 changes: 5 additions & 39 deletions src/core/MOM_forcing_type.F90
Original file line number Diff line number Diff line change
Expand Up @@ -191,10 +191,8 @@ module MOM_forcing_type
real :: C_p !< heat capacity of seawater [Q C-1 ~> J kg-1 degC-1].
!! C_p is is the same value as in thermovar_ptrs_type.

! CFC-related arrays needed in the MOM_CFC_cap module
! arrays needed in the some tracer modules, e.g., MOM_CFC_cap
real, pointer, dimension(:,:) :: &
cfc11_flux => NULL(), & !< flux of cfc_11 into the ocean [CU R Z T-1 ~> mol m-2 s-1]
cfc12_flux => NULL(), & !< flux of cfc_12 into the ocean [CU R Z T-1 ~> mol m-2 s-1]
ice_fraction => NULL(), & !< fraction of sea ice coverage at h-cells, from 0 to 1 [nondim].
u10_sqr => NULL() !< wind magnitude at 10 m squared [L2 T-2 ~> m2 s-2]

Expand Down Expand Up @@ -364,9 +362,7 @@ module MOM_forcing_type
integer :: id_TKE_tidal = -1
integer :: id_buoy = -1

! cfc-related diagnostics handles
integer :: id_cfc11 = -1
integer :: id_cfc12 = -1
! tracer surface flux related diagnostics handles
integer :: id_ice_fraction = -1
integer :: id_u10_sqr = -1

Expand Down Expand Up @@ -1129,10 +1125,6 @@ subroutine MOM_forcing_chksum(mesg, fluxes, G, US, haloshift)
call hchksum(fluxes%u10_sqr, mesg//" fluxes%u10_sqr", G%HI, haloshift=hshift, scale=US%L_to_m**2*US%s_to_T**2)
if (associated(fluxes%ice_fraction)) &
call hchksum(fluxes%ice_fraction, mesg//" fluxes%ice_fraction", G%HI, haloshift=hshift)
if (associated(fluxes%cfc11_flux)) &
call hchksum(fluxes%cfc11_flux, mesg//" fluxes%cfc11_flux", G%HI, haloshift=hshift, scale=US%RZ_T_to_kg_m2s)
if (associated(fluxes%cfc12_flux)) &
call hchksum(fluxes%cfc12_flux, mesg//" fluxes%cfc12_flux", G%HI, haloshift=hshift, scale=US%RZ_T_to_kg_m2s)
if (associated(fluxes%salt_flux)) &
call hchksum(fluxes%salt_flux, mesg//" fluxes%salt_flux", G%HI, haloshift=hshift, scale=US%RZ_T_to_kg_m2s)
if (associated(fluxes%TKE_tidal)) &
Expand Down Expand Up @@ -1340,26 +1332,9 @@ subroutine register_forcing_type_diags(Time, diag, US, use_temperature, handles,
endif
endif

! units for cfc11_flux and cfc12_flux are [Conc R Z T-1 ~> mol m-2 s-1]
! See:
! http://clipc-services.ceda.ac.uk/dreq/u/0940cbee6105037e4b7aa5579004f124.html
! http://clipc-services.ceda.ac.uk/dreq/u/e9e21426e4810d0bb2d3dddb24dbf4dc.html
if (present(use_cfcs)) then
if (use_cfcs) then
handles%id_cfc11 = register_diag_field('ocean_model', 'cfc11_flux', diag%axesT1, Time, &
'Gas exchange flux of CFC11 into the ocean ', &
'mol m-2 s-1', conversion=US%RZ_T_to_kg_m2s, &
cmor_field_name='fgcfc11', &
cmor_long_name='Surface Downward CFC11 Flux', &
cmor_standard_name='surface_downward_cfc11_flux')

handles%id_cfc12 = register_diag_field('ocean_model', 'cfc12_flux', diag%axesT1, Time, &
'Gas exchange flux of CFC12 into the ocean ', &
'mol m-2 s-1', conversion=US%RZ_T_to_kg_m2s, &
cmor_field_name='fgcfc12', &
cmor_long_name='Surface Downward CFC12 Flux', &
cmor_standard_name='surface_downward_cfc12_flux')

handles%id_ice_fraction = register_diag_field('ocean_model', 'ice_fraction', diag%axesT1, Time, &
'Fraction of cell area covered by sea ice', 'm2 m-2')

Expand Down Expand Up @@ -2921,13 +2896,7 @@ subroutine forcing_diagnostics(fluxes_in, sfc_state, G_in, US, time_end, diag, h
if (handles%id_netFWGlobalScl > 0) &
call post_data(handles%id_netFWGlobalScl, fluxes%netFWGlobalScl, diag)

! post diagnostics related to cfcs ====================================

if ((handles%id_cfc11 > 0) .and. associated(fluxes%cfc11_flux)) &
call post_data(handles%id_cfc11, fluxes%cfc11_flux, diag)

if ((handles%id_cfc11 > 0) .and. associated(fluxes%cfc12_flux)) &
call post_data(handles%id_cfc12, fluxes%cfc12_flux, diag)
! post diagnostics related to tracer surface fluxes ========================

if ((handles%id_ice_fraction > 0) .and. associated(fluxes%ice_fraction)) &
call post_data(handles%id_ice_fraction, fluxes%ice_fraction, diag)
Expand Down Expand Up @@ -2989,7 +2958,8 @@ subroutine allocate_forcing_by_group(G, fluxes, water, heat, ustar, press, &
logical, optional, intent(in) :: salt !< If present and true, allocate salt fluxes
logical, optional, intent(in) :: fix_accum_bug !< If present and true, avoid using a bug in
!! accumulation of ustar_gustless
logical, optional, intent(in) :: cfc !< If present and true, allocate cfc fluxes
logical, optional, intent(in) :: cfc !< If present and true, allocate fields needed
!! for cfc surface fluxes
logical, optional, intent(in) :: waves !< If present and true, allocate wave fields
logical, optional, intent(in) :: shelf_sfc_accumulation !< If present and true, and shelf is true,
!! then allocate surface flux deposition from the atmosphere
Expand Down Expand Up @@ -3064,8 +3034,6 @@ subroutine allocate_forcing_by_group(G, fluxes, water, heat, ustar, press, &
call myAlloc(fluxes%mass_berg,isd,ied,jsd,jed, iceberg)

!These fields should only on allocated when USE_CFC_CAP is activated.
call myAlloc(fluxes%cfc11_flux,isd,ied,jsd,jed, cfc)
call myAlloc(fluxes%cfc12_flux,isd,ied,jsd,jed, cfc)
call myAlloc(fluxes%ice_fraction,isd,ied,jsd,jed, cfc)
call myAlloc(fluxes%u10_sqr,isd,ied,jsd,jed, cfc)

Expand Down Expand Up @@ -3322,8 +3290,6 @@ subroutine deallocate_forcing_type(fluxes)
if (associated(fluxes%mass_berg)) deallocate(fluxes%mass_berg)
if (associated(fluxes%ice_fraction)) deallocate(fluxes%ice_fraction)
if (associated(fluxes%u10_sqr)) deallocate(fluxes%u10_sqr)
if (associated(fluxes%cfc11_flux)) deallocate(fluxes%cfc11_flux)
if (associated(fluxes%cfc12_flux)) deallocate(fluxes%cfc12_flux)

call coupler_type_destructor(fluxes%tr_fluxes)

Expand Down
Loading

0 comments on commit 59cc9ed

Please sign in to comment.