Skip to content

Commit

Permalink
Allow generic tracers with accessom_coupler
Browse files Browse the repository at this point in the history
  • Loading branch information
dougiesquire committed Aug 16, 2024
1 parent db01ae0 commit 29d5441
Show file tree
Hide file tree
Showing 6 changed files with 818 additions and 72 deletions.
10 changes: 8 additions & 2 deletions exp/MOM_compile.csh
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,9 @@ if ( $help ) then
echo " ACCESS-CM : ocean component of ACCESS-CM model."
echo " ACCESS-OM : ocean component of ACCESS-OM model."
echo " ACCESS-ESM : ocean component of ACCESS-ESM model with CSIRO BGC (Wombat)."
echo " ACCESS-OM-BGC: ocean component of ACCESS-OM model with CSIRO BGC (Wombat)."
echo " ACCESS-OM-BGC: ocean component of ACCESS-OM model with CSIRO BGC (Wombat). Wombat has now been"
echo " implemented as a generic tracer and is available in the ACCESS-OM model type."
echo " ACCESS-OM-BGC is retained only for legacy."
echo
echo "--platform followed by the platform name that has a corresponding environ file in the ../bin dir, default is gfortran"
echo
Expand Down Expand Up @@ -104,7 +106,7 @@ endif
if ( $type == EBM ) then
set cppDefs = ( "-Duse_netCDF -Duse_netCDF3 -Duse_libMPI -DLAND_BND_TRACERS -DOVERLOAD_C8 -DOVERLOAD_C4 -DOVERLOAD_R4" )
else if( $type == ACCESS-OM ) then
set cppDefs = ( "-Duse_netCDF -Duse_libMPI -DACCESS_OM" )
set cppDefs = ( "-Duse_netCDF -Duse_libMPI -DACCESS_OM -DUSE_OCEAN_BGC" )
else if( $type == ACCESS-OM-BGC ) then
set cppDefs = ( "-Duse_netCDF -Duse_libMPI -DACCESS_OM -DCSIRO_BGC" )
else if( $type == ACCESS-CM ) then
Expand Down Expand Up @@ -254,6 +256,10 @@ else
exit 1
endif

if( $type == ACCESS-OM ) then
set srcList = ( $srcList access/shared )
endif

# Always include FMS
set libs = "$libs $executable:h:h/lib_FMS/lib_FMS.a"

Expand Down
2 changes: 2 additions & 0 deletions exp/ocean_compile.csh
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,8 @@ if( $type == ACCESS-OM || $type == ACCESS-CM || $type == ACCESS-OM-BGC || $type
set srcList = ( $srcList mom5/ocean_access )
if( $type == ACCESS-OM-BGC || $type == ACCESS-ESM) then
set srcList = ( $srcList mom5/ocean_csiro_bgc )
else if ( $type == ACCESS-OM ) then
set srcList = ( $srcList mom5/ocean_bgc access/generic_tracers/generic_tracers access/generic_tracers/mocsy/src )
endif
mkdir -p $executable:h:h/$type/$lib_name
cd $executable:h:h/$type/$lib_name
Expand Down
File renamed without changes.
19 changes: 17 additions & 2 deletions src/access/accessom_coupler/mom_oasis3_interface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,7 @@ module mom_oasis3_interface_mod
ocean_public_type, &
ocean_domain_type
use time_manager_mod, only: time_type, get_time
use gtracer_flux_mod, only: set_coupler_type_data

! Timing

Expand Down Expand Up @@ -657,24 +658,26 @@ subroutine into_coupler(step, Ocean_sfc, Time, before_ocean_update)
end subroutine into_coupler

!-----------------------------------------------------------------------------------
subroutine from_coupler(step,Ocean_sfc,Ice_ocean_boundary, Time)
subroutine from_coupler(step,Ocean_sfc,Ice_ocean_boundary, Atm_fields, Time)

! This is all highly user dependent.

use constants_mod, only : hlv ! 2.500e6 J/kg
use auscom_ice_mod, only : chk_i2o_fields, chk_fields_period, chk_fields_start_time
use coupler_types_mod, only: coupler_2d_bc_type, ind_u10, ind_psurf
implicit none

type (ocean_public_type) :: Ocean_sfc
type (ice_ocean_boundary_type) :: Ice_ocean_boundary
type (coupler_2d_bc_type) :: Atm_fields
type (time_type),optional :: Time

real, dimension(isg:ieg,jsg:jeg) :: gtmp

integer, intent(in) :: step

character*80 :: fname = 'fields_i2o_in_ocn.nc'
integer :: ncid,currstep,ll,ilout
integer :: ncid,currstep,ll,ilout,n
data currstep/0/
save currstep

Expand Down Expand Up @@ -798,6 +801,18 @@ subroutine from_coupler(step,Ocean_sfc,Ice_ocean_boundary, Time)

if(jf .ne. 1) call mpp_clock_end(id_oasis_recv1)
enddo !jf

! Set the u10 and psurf fields in the Atm_fields coupler_bc_types
do n = 1, Atm_fields%num_bcs
if ((Atm_fields%bc(n)%flux_type .eq. 'air_sea_gas_flux_generic') .or. &
(Atm_fields%bc(n)%flux_type .eq. 'air_sea_gas_flux')) then
call set_coupler_type_data(ice_ocean_boundary%wnd, Atm_fields%bc(n)%name, ind_u10, &
Atm_fields, idim=(/iisc,iisc,iiec,iiec/), jdim=(/jjsc,jjsc,jjec,jjec/))
call set_coupler_type_data(ice_ocean_boundary%p, Atm_fields%bc(n)%name, ind_psurf, &
Atm_fields, idim=(/iisc,iisc,iiec,iiec/), jdim=(/jjsc,jjsc,jjec,jjec/))
endif
enddo

call mpp_clock_end(id_oasis_recv)

if (chk_i2o_fields .and. (mod(step, chk_fields_period) == 0) .and. (step >= chk_fields_start_time) .and. (mpp_pe() == mpp_root_pe())) then
Expand Down
121 changes: 53 additions & 68 deletions src/access/accessom_coupler/ocean_solo.F90
Original file line number Diff line number Diff line change
Expand Up @@ -111,11 +111,16 @@ program main
use accessom2_mod, only : accessom2_type => accessom2
use coupler_mod, only : coupler_type => coupler

use coupler_types_mod, only: coupler_2d_bc_type, coupler_type_data_override, coupler_type_send_data
use gtracer_flux_mod, only: flux_exchange_init, atmos_ocean_fluxes_calc
use gtracer_flux_mod, only: gas_fields_restore, gas_fields_restart

implicit none

type (ocean_public_type) :: Ocean_sfc
type (ocean_state_type), pointer :: Ocean_state
type(ice_ocean_boundary_type), target :: Ice_ocean_boundary
type(coupler_2d_bc_type), target :: Atm_fields
type(accessom2_type) :: accessom2
type(coupler_type) :: coupler

Expand All @@ -130,7 +135,8 @@ program main
type(time_type) :: Time_restart
type(time_type) :: Time_restart_current
type(time_type) :: Time_last_sfix
type(time_type) :: Time_sfix
type(time_type) :: Time_sfix
type(time_type) :: Time_next
integer :: sfix_seconds

character(len=17) :: calendar = 'julian'
Expand Down Expand Up @@ -388,61 +394,14 @@ program main
call data_override_init(Ocean_domain_in = Ocean_sfc%domain)

override_clock = mpp_clock_id('Override', flags=flags,grain=CLOCK_COMPONENT)

! Initialise the boundary values, including initialising and setting boundary values
! in FMS coupler types
call flux_exchange_init(Time, Ocean_sfc, Ocean_state, Ice_ocean_boundary, Atm_fields)

! Restore ocean FMS coupler type fields from restart file
call gas_fields_restore(Ocean_sfc)

call mpp_get_compute_domain(Ocean_sfc%domain, isc, iec, jsc, jec)

allocate ( Ice_ocean_boundary% u_flux (isc:iec,jsc:jec), &
Ice_ocean_boundary% v_flux (isc:iec,jsc:jec), &
Ice_ocean_boundary% t_flux (isc:iec,jsc:jec), &
Ice_ocean_boundary% q_flux (isc:iec,jsc:jec), &
Ice_ocean_boundary% salt_flux (isc:iec,jsc:jec), &
Ice_ocean_boundary% lw_flux (isc:iec,jsc:jec), &
Ice_ocean_boundary% sw_flux_vis_dir (isc:iec,jsc:jec), &
Ice_ocean_boundary% sw_flux_vis_dif (isc:iec,jsc:jec), &
Ice_ocean_boundary% sw_flux_nir_dir (isc:iec,jsc:jec), &
Ice_ocean_boundary% sw_flux_nir_dif (isc:iec,jsc:jec), &
Ice_ocean_boundary% lprec (isc:iec,jsc:jec), &
Ice_ocean_boundary% fprec (isc:iec,jsc:jec), &
Ice_ocean_boundary% runoff (isc:iec,jsc:jec), &
Ice_ocean_boundary% calving (isc:iec,jsc:jec), &
Ice_ocean_boundary% p (isc:iec,jsc:jec), &
Ice_ocean_boundary% aice(isc:iec,jsc:jec), &
Ice_ocean_boundary% mh_flux(isc:iec,jsc:jec), &
Ice_ocean_boundary% wfimelt(isc:iec,jsc:jec), &
Ice_ocean_boundary% wfiform(isc:iec,jsc:jec), &
Ice_ocean_boundary% licefw(isc:iec,jsc:jec), &
Ice_ocean_boundary% liceht(isc:iec,jsc:jec), &
Ice_ocean_boundary%wnd(isc:iec,jsc:jec))
#if defined(ACCESS_OM) && defined(CSIRO_BGC)
allocate ( Ice_ocean_boundary%iof_nit(isc:iec,jsc:jec), &
Ice_ocean_boundary%iof_alg(isc:iec,jsc:jec))
#endif
Ice_ocean_boundary%u_flux = 0.0
Ice_ocean_boundary%v_flux = 0.0
Ice_ocean_boundary%t_flux = 0.0
Ice_ocean_boundary%q_flux = 0.0
Ice_ocean_boundary%salt_flux = 0.0
Ice_ocean_boundary%lw_flux = 0.0
Ice_ocean_boundary%sw_flux_vis_dir = 0.0
Ice_ocean_boundary%sw_flux_vis_dif = 0.0
Ice_ocean_boundary%sw_flux_nir_dir = 0.0
Ice_ocean_boundary%sw_flux_nir_dif = 0.0
Ice_ocean_boundary%lprec = 0.0
Ice_ocean_boundary%fprec = 0.0
Ice_ocean_boundary%runoff = 0.0
Ice_ocean_boundary%calving = 0.0
Ice_ocean_boundary%p = 0.0
Ice_ocean_boundary%aice = 0.0
Ice_ocean_boundary%mh_flux = 0.0
Ice_ocean_boundary% wfimelt = 0.0
Ice_ocean_boundary% wfiform = 0.0
Ice_ocean_boundary%licefw = 0.0
Ice_ocean_boundary%liceht = 0.0
Ice_ocean_boundary%wnd = 0.0
#if defined(ACCESS_OM) && defined(CSIRO_BGC)
Ice_ocean_boundary%iof_nit = 0.0
Ice_ocean_boundary%iof_alg = 0.0
#endif
coupler_init_clock = mpp_clock_id('OASIS init', grain=CLOCK_COMPONENT)
call mpp_clock_begin(coupler_init_clock)
call external_coupler_sbc_init(Ocean_sfc%domain, dt_cpld, Run_len, &
Expand All @@ -454,12 +413,25 @@ program main
call mpp_clock_begin(main_clock)
do nc=1, num_cpld_calls

call external_coupler_sbc_before(Ice_ocean_boundary, Ocean_sfc, nc, dt_cpld)
call external_coupler_sbc_before(Ice_ocean_boundary, Ocean_sfc, Atm_fields, nc, dt_cpld)

! Potentially override fields from the data_table
call mpp_clock_begin(override_clock)
call ice_ocn_bnd_from_data(Ice_ocean_boundary)
Time_next = Time + Time_step_coupled
call coupler_type_data_override('OCN', Atm_fields, Time_next)
call ice_ocn_bnd_from_data(Ice_ocean_boundary, Time_next)
call mpp_clock_end(override_clock)

! Calculate the extra tracer fluxes
call mpp_get_compute_domain(Ocean_sfc%domain, isc, iec, jsc, jec)
call atmos_ocean_fluxes_calc(Atm_fields, Ocean_sfc%fields, Ice_ocean_boundary%fluxes, &
Ice_ocean_boundary%aice, isc, iec, jsc, jec)

! Send FMS coupler type diagnostics
call coupler_type_send_data(Ice_ocean_boundary%fluxes, Time_next)
call coupler_type_send_data(Ocean_sfc%fields, Time_next)
call coupler_type_send_data(Atm_fields, Time_next)

if (debug_this_module) then
call write_boundary_chksums(Ice_ocean_boundary)
endif
Expand All @@ -475,20 +447,21 @@ program main

call update_ocean_model(Ice_ocean_boundary, Ocean_state, Ocean_sfc, Time, Time_step_coupled)

Time = Time + Time_step_coupled
Time = Time_next
if ( mpp_pe() == mpp_root_pe() ) then
call accessom2%progress_date(int(dt_cpld))
endif

if( Time >= Time_restart ) then
Time_restart_current = Time
Time_restart = increment_date(Time, restart_interval(1), restart_interval(2), &
Time_restart_current = Time
Time_restart = increment_date(Time, restart_interval(1), restart_interval(2), &
restart_interval(3), restart_interval(4), restart_interval(5), restart_interval(6) )
timestamp = date_to_string(time_restart_current)
timestamp = date_to_string(time_restart_current)
write(stdoutunit,*) '=> NOTE from program ocean_solo: intermediate restart file is written and ', &
trim(timestamp),' is appended as prefix to each restart file name'
call ocean_model_restart(Ocean_state, timestamp)
call ocean_solo_restart(Time, Time_restart_current, timestamp)
call gas_fields_restart(Ocean_sfc, timestamp)
end if

call external_coupler_sbc_after(Ice_ocean_boundary, Ocean_sfc, nc, dt_cpld )
Expand All @@ -508,8 +481,9 @@ program main
! need to reset pelist before calling mpp_clock_end
! call mpp_set_current_pelist()

! write restart file
! write restart files
call ocean_solo_restart(Time_end, Time_restart_current)
call gas_fields_restart(Ocean_sfc)

call fms_io_exit

Expand Down Expand Up @@ -574,12 +548,13 @@ end subroutine ocean_solo_restart

!====================================================================
! get forcing data from data_overide
subroutine ice_ocn_bnd_from_data(x)
subroutine ice_ocn_bnd_from_data(x, Time_next)

type (ice_ocean_boundary_type) :: x
type(time_type) :: Time_next

Time_next = Time + Time_step_coupled
integer :: m, n

call data_override('OCN', 't_flux', x%t_flux , Time_next)
call data_override('OCN', 'u_flux', x%u_flux , Time_next)
call data_override('OCN', 'v_flux', x%v_flux , Time_next)
Expand All @@ -597,12 +572,21 @@ subroutine ice_ocn_bnd_from_data(x)
call data_override('OCN', 'p', x%p , Time_next)
call data_override('OCN', 'aice', x%aice , Time_next)
call data_override('OCN', 'mh_flux', x%mh_flux , Time_next)

! Overriding ice_ocean_boundary%fluxes here avoids unnecessary calculation
! of overridden fluxes. However, we cannot use coupler_type_data_override
! here since it does not set the override flag on overridden fields
do n = 1, x%fluxes%num_bcs
do m = 1, x%fluxes%bc(n)%num_fields
call data_override('OCN', x%fluxes%bc(n)%field(m)%name, &
x%fluxes%bc(n)%field(m)%values, Time_next, &
override=x%fluxes%bc(n)%field(m)%override)
enddo
enddo
call mpp_sync()

end subroutine ice_ocn_bnd_from_data



! Here we provide some hooks for calling an interface between the OASIS3 coupler and MOM.
! The mom_oasis3_interface module is NOT general and it is expected that the user will
! heavily modify it depending on the coupling strategy.
Expand All @@ -626,7 +610,7 @@ subroutine external_coupler_sbc_init(Dom, dt_cpld, Run_len, &
coupling_field_timesteps=coupling_field_timesteps)
end subroutine external_coupler_sbc_init

subroutine external_coupler_sbc_before(Ice_ocean_boundary, Ocean_sfc, nsteps, dt_cpld )
subroutine external_coupler_sbc_before(Ice_ocean_boundary, Ocean_sfc, Atm_fields, nsteps, dt_cpld )
! Perform transfers before ocean time stepping
! May need special tratment on first call.

Expand All @@ -635,14 +619,15 @@ subroutine external_coupler_sbc_before(Ice_ocean_boundary, Ocean_sfc, nsteps, dt
implicit none
type (ice_ocean_boundary_type), intent(INOUT) :: Ice_ocean_boundary
type (ocean_public_type) , intent(INOUT) :: Ocean_sfc
type (coupler_2d_bc_type), intent(INOUT) :: Atm_fields
integer , intent(IN) :: nsteps, dt_cpld

integer :: rtimestep ! Receive timestep
integer :: stimestep ! Send timestep

rtimestep = (nsteps-1) * dt_cpld ! runtime in this run segment!
stimestep = rtimestep
call from_coupler( rtimestep, Ocean_sfc, Ice_ocean_boundary )
call from_coupler( rtimestep, Ocean_sfc, Ice_ocean_boundary, Atm_fields )
call into_coupler( stimestep, Ocean_sfc, before_ocean_update = .true.)
end subroutine external_coupler_sbc_before

Expand Down
Loading

0 comments on commit 29d5441

Please sign in to comment.