Skip to content

Commit

Permalink
+Pass ocean_grid_type to call_tracer_register
Browse files Browse the repository at this point in the history
  Pass ocean_grid_type arguments to call_tracer_register and call_OBC_register
in place of the hor_index_type arguments that had been used previously.  Also
use these ocean_grid_type arguments in calls to register_shelfwave_OBC,
register_RGC_tracer and register_advection_test_tracer.  Within these three
routines, the contents of the ocean_grid_type are used to specify axis units.
The new runtime parameter SHELFWAVE_AMPLITUDE was added to allow for run-time
control of the amplitude of the shelfwave test case.  By default all answers are
bitwise identical, but there are some changes in the units of parameters as
documented in the MOM_parameter_doc files and a new entry in these files for the
shelfwave test case.
  • Loading branch information
Hallberg-NOAA authored and marshallward committed Jan 4, 2023
1 parent e198296 commit f86d762
Show file tree
Hide file tree
Showing 6 changed files with 114 additions and 127 deletions.
6 changes: 3 additions & 3 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2177,7 +2177,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
"at the end of the step.", default=.false.)

if (CS%split) then
call get_param(param_file, "MOM", "DTBT", dtbt, default=-0.98)
call get_param(param_file, "MOM", "DTBT", dtbt, units="s or nondim", default=-0.98)
default_val = US%T_to_s*CS%dt_therm ; if (dtbt > 0.0) default_val = -1.0
CS%dtbt_reset_period = -1.0
call get_param(param_file, "MOM", "DTBT_RESET_PERIOD", CS%dtbt_reset_period, &
Expand Down Expand Up @@ -2637,7 +2637,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &

! This subroutine calls user-specified tracer registration routines.
! Additional calls can be added to MOM_tracer_flow_control.F90.
call call_tracer_register(HI, GV, US, param_file, CS%tracer_flow_CSp, &
call call_tracer_register(G, GV, US, param_file, CS%tracer_flow_CSp, &
CS%tracer_Reg, restart_CSp)

call MEKE_alloc_register_restart(HI, US, param_file, CS%MEKE, restart_CSp)
Expand All @@ -2661,7 +2661,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &

if (associated(CS%OBC)) then
! Set up remaining information about open boundary conditions that is needed for OBCs.
call call_OBC_register(param_file, CS%update_OBC_CSp, US, CS%OBC, CS%tracer_Reg)
call call_OBC_register(G, GV, US, param_file, CS%update_OBC_CSp, CS%OBC, CS%tracer_Reg)
!### Package specific changes to OBCs need to go here?

! This is the equivalent to 2 calls to register_segment_tracer (per segment), which
Expand Down
16 changes: 9 additions & 7 deletions src/core/MOM_boundary_update.F90
Original file line number Diff line number Diff line change
Expand Up @@ -59,12 +59,14 @@ module MOM_boundary_update
!> The following subroutines and associated definitions provide the
!! machinery to register and call the subroutines that initialize
!! open boundary conditions.
subroutine call_OBC_register(param_file, CS, US, OBC, tr_Reg)
type(param_file_type), intent(in) :: param_file !< Parameter file to parse
type(update_OBC_CS), pointer :: CS !< Control structure for OBCs
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
type(tracer_registry_type), pointer :: tr_Reg !< Tracer registry.
subroutine call_OBC_register(G, GV, US, param_file, CS, OBC, tr_Reg)
type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
type(param_file_type), intent(in) :: param_file !< Parameter file to parse
type(update_OBC_CS), pointer :: CS !< Control structure for OBCs
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
type(tracer_registry_type), pointer :: tr_Reg !< Tracer registry.

! Local variables
character(len=200) :: config
Expand Down Expand Up @@ -124,7 +126,7 @@ subroutine call_OBC_register(param_file, CS, US, OBC, tr_Reg)
register_Kelvin_OBC(param_file, CS%Kelvin_OBC_CSp, US, &
OBC%OBC_Reg)
if (CS%use_shelfwave) CS%use_shelfwave = &
register_shelfwave_OBC(param_file, CS%shelfwave_OBC_CSp, US, &
register_shelfwave_OBC(param_file, CS%shelfwave_OBC_CSp, G, US, &
OBC%OBC_Reg)
if (CS%use_dyed_channel) CS%use_dyed_channel = &
register_dyed_channel_OBC(param_file, CS%dyed_channel_OBC_CSp, US, &
Expand Down
36 changes: 18 additions & 18 deletions src/tracer/MOM_tracer_flow_control.F90
Original file line number Diff line number Diff line change
Expand Up @@ -152,8 +152,8 @@ end subroutine call_tracer_flux_init

!> This subroutine determines which tracer packages are to be used and does the calls to
!! register their tracers to be advected, diffused, and read from restarts.
subroutine call_tracer_register(HI, GV, US, param_file, CS, tr_Reg, restart_CS)
type(hor_index_type), intent(in) :: HI !< A horizontal index type structure.
subroutine call_tracer_register(G, GV, US, param_file, CS, tr_Reg, restart_CS)
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical 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
Expand All @@ -163,7 +163,7 @@ subroutine call_tracer_register(HI, GV, US, param_file, CS, tr_Reg, restart_CS)
type(tracer_registry_type), pointer :: tr_Reg !< A pointer that is set to point to the
!! control structure for the tracer
!! advection and diffusion module.
type(MOM_restart_CS), intent(inout) :: restart_CS !< A pointer to the restart control
type(MOM_restart_CS), intent(inout) :: restart_CS !< A pointer to the restart control
!! structure.

! This include declares and sets the variable "version".
Expand Down Expand Up @@ -230,49 +230,49 @@ subroutine call_tracer_register(HI, GV, US, param_file, CS, tr_Reg, restart_CS)
! tracer package registration call returns a logical false if it cannot be run
! for some reason. This then overrides the run-time selection from above.
if (CS%use_USER_tracer_example) CS%use_USER_tracer_example = &
USER_register_tracer_example(HI, GV, param_file, CS%USER_tracer_example_CSp, &
USER_register_tracer_example(G%HI, GV, param_file, CS%USER_tracer_example_CSp, &
tr_Reg, restart_CS)
if (CS%use_DOME_tracer) CS%use_DOME_tracer = &
register_DOME_tracer(HI, GV, param_file, CS%DOME_tracer_CSp, &
register_DOME_tracer(G%HI, GV, param_file, CS%DOME_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_ISOMIP_tracer) CS%use_ISOMIP_tracer = &
register_ISOMIP_tracer(HI, GV, param_file, CS%ISOMIP_tracer_CSp, &
register_ISOMIP_tracer(G%HI, GV, param_file, CS%ISOMIP_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_RGC_tracer) CS%use_RGC_tracer = &
register_RGC_tracer(HI, GV, param_file, CS%RGC_tracer_CSp, &
register_RGC_tracer(G, GV, param_file, CS%RGC_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_ideal_age) CS%use_ideal_age = &
register_ideal_age_tracer(HI, GV, param_file, CS%ideal_age_tracer_CSp, &
register_ideal_age_tracer(G%HI, GV, param_file, CS%ideal_age_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_regional_dyes) CS%use_regional_dyes = &
register_dye_tracer(HI, GV, US, param_file, CS%dye_tracer_CSp, &
register_dye_tracer(G%HI, GV, US, param_file, CS%dye_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_oil) CS%use_oil = &
register_oil_tracer(HI, GV, US, param_file, CS%oil_tracer_CSp, &
register_oil_tracer(G%HI, GV, US, param_file, CS%oil_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_advection_test_tracer) CS%use_advection_test_tracer = &
register_advection_test_tracer(HI, GV, param_file, CS%advection_test_tracer_CSp, &
register_advection_test_tracer(G, GV, param_file, CS%advection_test_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_OCMIP2_CFC) CS%use_OCMIP2_CFC = &
register_OCMIP2_CFC(HI, GV, param_file, CS%OCMIP2_CFC_CSp, &
register_OCMIP2_CFC(G%HI, GV, param_file, CS%OCMIP2_CFC_CSp, &
tr_Reg, restart_CS)
if (CS%use_CFC_cap) CS%use_CFC_cap = &
register_CFC_cap(HI, GV, param_file, CS%CFC_cap_CSp, &
register_CFC_cap(G%HI, GV, param_file, CS%CFC_cap_CSp, &
tr_Reg, restart_CS)
if (CS%use_MOM_generic_tracer) CS%use_MOM_generic_tracer = &
register_MOM_generic_tracer(HI, GV, param_file, CS%MOM_generic_tracer_CSp, &
register_MOM_generic_tracer(G%HI, GV, param_file, CS%MOM_generic_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_pseudo_salt_tracer) CS%use_pseudo_salt_tracer = &
register_pseudo_salt_tracer(HI, GV, param_file, CS%pseudo_salt_tracer_CSp, &
register_pseudo_salt_tracer(G%HI, GV, param_file, CS%pseudo_salt_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_boundary_impulse_tracer) CS%use_boundary_impulse_tracer = &
register_boundary_impulse_tracer(HI, GV, US, param_file, CS%boundary_impulse_tracer_CSp, &
register_boundary_impulse_tracer(G%HI, GV, US, param_file, CS%boundary_impulse_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_dyed_obc_tracer) CS%use_dyed_obc_tracer = &
register_dyed_obc_tracer(HI, GV, param_file, CS%dyed_obc_tracer_CSp, &
register_dyed_obc_tracer(G%HI, GV, param_file, CS%dyed_obc_tracer_CSp, &
tr_Reg, restart_CS)
if (CS%use_nw2_tracers) CS%use_nw2_tracers = &
register_nw2_tracers(HI, GV, US, param_file, CS%nw2_tracers_CSp, tr_Reg, restart_CS)
register_nw2_tracers(G%HI, GV, US, param_file, CS%nw2_tracers_CSp, tr_Reg, restart_CS)

end subroutine call_tracer_register

Expand Down
15 changes: 6 additions & 9 deletions src/tracer/RGC_tracer.F90
Original file line number Diff line number Diff line change
Expand Up @@ -60,10 +60,9 @@ module RGC_tracer

contains


!> This subroutine is used to register tracer fields
function register_RGC_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
type(hor_index_type), intent(in) :: HI !< A horizontal index type structure.
function register_RGC_tracer(G, GV, param_file, CS, tr_Reg, restart_CS)
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
type(param_file_type), intent(in) :: param_file !<A structure indicating the open file to parse
!! for model parameter values.
Expand All @@ -80,7 +79,7 @@ function register_RGC_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
real, pointer :: tr_ptr(:,:,:) => NULL() ! A pointer to one of the tracers in this module [kg kg-1]
logical :: register_RGC_tracer
integer :: isd, ied, jsd, jed, nz, m
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed ; nz = GV%ke
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed ; nz = GV%ke

if (associated(CS)) then
call MOM_error(FATAL, "RGC_register_tracer called with an "// &
Expand Down Expand Up @@ -108,13 +107,11 @@ function register_RGC_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)

call get_param(param_file, mdl, "CONT_SHELF_LENGTH", CS%CSL, &
"The length of the continental shelf (x dir, km).", &
units="km", default=15.0)
! units=G%x_ax_unit_short, default=15.0)
units=G%x_ax_unit_short, default=15.0)

call get_param(param_file, mdl, "LENSPONGE", CS%lensponge, &
"The length of the sponge layer (km).", &
units="km", default=10.0)
! units=G%x_ax_unit_short, default=10.0)
units=G%x_ax_unit_short, default=10.0)

allocate(CS%tr(isd:ied,jsd:jed,nz,NTR), source=0.0)
if (CS%mask_tracers) then
Expand All @@ -130,7 +127,7 @@ function register_RGC_tracer(HI, GV, param_file, CS, tr_Reg, restart_CS)
! This is needed to force the compiler not to do a copy in the registration calls.
tr_ptr => CS%tr(:,:,:,m)
! Register the tracer for horizontal advection & diffusion.
call register_tracer(tr_ptr, tr_Reg, param_file, HI, GV, &
call register_tracer(tr_ptr, tr_Reg, param_file, G%HI, GV, &
name=name, longname=longname, units="kg kg-1", &
registry_diags=.true., flux_units="kg/s", &
restart_CS=restart_CS)
Expand Down
Loading

0 comments on commit f86d762

Please sign in to comment.