Skip to content

Commit

Permalink
+Pass timesteps to ALE_main in [T]
Browse files Browse the repository at this point in the history
  Pass the timesteps to ALE_main, ALE_main_offline, and ALE_main_accelerated in
units of [T] for code simplicity and dimensional consistency testing.  This also
includes the rescaling of remapping-driven tracer tendencies.  All answers and
diagnostics are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed Nov 13, 2019
1 parent 08dbb59 commit 00da24e
Show file tree
Hide file tree
Showing 5 changed files with 21 additions and 20 deletions.
23 changes: 12 additions & 11 deletions src/ALE/MOM_ALE.F90
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ module MOM_ALE
!! remaps between grids described by h.

real :: regrid_time_scale !< The time-scale used in blending between the current (old) grid
!! and the target (new) grid. (s)
!! and the target (new) grid [T ~> s]

type(regridding_CS) :: regridCS !< Regridding parameters and work arrays
type(remapping_CS) :: remapCS !< Remapping parameters and work arrays
Expand Down Expand Up @@ -209,7 +209,7 @@ subroutine ALE_init( param_file, GV, US, max_depth, CS)
"and the target (new) grid. A short time-scale favors the target "//&
"grid (0. or anything less than DT_THERM) has no memory of the old "//&
"grid. A very long time-scale makes the model more Lagrangian.", &
units="s", default=0.)
units="s", default=0., scale=US%s_to_T)
call get_param(param_file, mdl, "REGRID_FILTER_SHALLOW_DEPTH", filter_shallow_depth, &
"The depth above which no time-filtering is applied. Above this depth "//&
"final grid exactly matches the target (new) grid.", &
Expand Down Expand Up @@ -269,7 +269,7 @@ subroutine ALE_register_diags(Time, G, GV, US, diag, CS)
conversion=GV%H_to_m, v_extensive=.true.)
cs%id_vert_remap_h_tendency = register_diag_field('ocean_model','vert_remap_h_tendency',diag%axestl,time, &
'Layer thicknesses tendency due to ALE regridding and remapping', 'm', &
conversion=GV%H_to_m, v_extensive = .true.)
conversion=GV%H_to_m*US%s_to_T, v_extensive = .true.)

end subroutine ALE_register_diags

Expand Down Expand Up @@ -319,7 +319,7 @@ subroutine ALE_main( G, GV, US, h, u, v, tv, Reg, CS, OBC, dt, frac_shelf_h)
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
type(ALE_CS), pointer :: CS !< Regridding parameters and options
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
real, optional, intent(in) :: dt !< Time step between calls to ALE_main()
real, optional, intent(in) :: dt !< Time step between calls to ALE_main [T ~> s]
real, dimension(:,:), optional, pointer :: frac_shelf_h !< Fractional ice shelf coverage
! Local variables
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: dzRegrid ! The change in grid interface positions
Expand Down Expand Up @@ -403,7 +403,7 @@ subroutine ALE_main_offline( G, GV, h, tv, Reg, CS, OBC, dt)
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
type(ALE_CS), pointer :: CS !< Regridding parameters and options
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
real, optional, intent(in) :: dt !< Time step between calls to ALE_main()
real, optional, intent(in) :: dt !< Time step between calls to ALE_main [T ~> s]
! Local variables
real, dimension(SZI_(G), SZJ_(G), SZK_(GV)+1) :: dzRegrid ! The change in grid interface positions
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_new ! New 3D grid obtained after last time step [H ~> m or kg-2]
Expand Down Expand Up @@ -660,7 +660,7 @@ subroutine ALE_regrid_accelerated(CS, G, GV, h, tv, n, u, v, OBC, Reg, dt, dzReg
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
type(tracer_registry_type), &
optional, pointer :: Reg !< Tracer registry to remap onto new grid
real, optional, intent(in) :: dt !< Model timestep to provide a timescale for regridding [s]
real, optional, intent(in) :: dt !< Model timestep to provide a timescale for regridding [T ~> s]
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), &
optional, intent(inout) :: dzRegrid !< Final change in interface positions
logical, optional, intent(in) :: initial !< Whether we're being called from an initialization
Expand Down Expand Up @@ -698,7 +698,7 @@ subroutine ALE_regrid_accelerated(CS, G, GV, h, tv, n, u, v, OBC, Reg, dt, dzReg

! Apply timescale to regridding (for e.g. filtered_grid_motion)
if (present(dt)) &
call ALE_update_regrid_weights(dt, CS)
call ALE_update_regrid_weights(dt, CS)

do k = 1, n
call do_group_pass(pass_T_S_h, G%domain)
Expand All @@ -718,7 +718,7 @@ subroutine ALE_regrid_accelerated(CS, G, GV, h, tv, n, u, v, OBC, Reg, dt, dzReg
enddo

! remap all state variables (including those that weren't needed for regridding)
call remap_all_state_vars(CS%remapCS, CS, G, GV, h_orig, h, Reg, OBC, dzIntTotal, u, v, dt=dt)
call remap_all_state_vars(CS%remapCS, CS, G, GV, h_orig, h, Reg, OBC, dzIntTotal, u, v)

! save total dzregrid for diags if needed?
if (present(dzRegrid)) dzRegrid(:,:,:) = dzIntTotal(:,:,:)
Expand Down Expand Up @@ -750,7 +750,7 @@ subroutine remap_all_state_vars(CS_remapping, CS_ALE, G, GV, h_old, h_new, Reg,
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), &
optional, intent(inout) :: v !< Meridional velocity [L T-1 ~> m s-1]
logical, optional, intent(in) :: debug !< If true, show the call tree
real, optional, intent(in) :: dt !< time step for diagnostics
real, optional, intent(in) :: dt !< time step for diagnostics [T ~> s]
! Local variables
integer :: i, j, k, m
integer :: nz, ntr
Expand All @@ -759,7 +759,8 @@ subroutine remap_all_state_vars(CS_remapping, CS_ALE, G, GV, h_old, h_new, Reg,
real, dimension(SZI_(G), SZJ_(G), SZK_(GV)) :: work_conc
real, dimension(SZI_(G), SZJ_(G), SZK_(GV)) :: work_cont
real, dimension(SZI_(G), SZJ_(G)) :: work_2d
real :: Idt, ppt2mks
real :: Idt ! The inverse of the timestep [T-1 ~> s-1]
real :: ppt2mks
real, dimension(GV%ke) :: h2
real :: h_neglect, h_neglect_edge
logical :: show_call_tree
Expand Down Expand Up @@ -1197,7 +1198,7 @@ end function ALE_remap_init_conds

!> Updates the weights for time filtering the new grid generated in regridding
subroutine ALE_update_regrid_weights( dt, CS )
real, intent(in) :: dt !< Time-step used between ALE calls
real, intent(in) :: dt !< Time-step used between ALE calls [T ~> s]
type(ALE_CS), pointer :: CS !< ALE control structure
! Local variables
real :: w ! An implicit weighting estimate.
Expand Down
6 changes: 3 additions & 3 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1221,9 +1221,9 @@ subroutine step_MOM_thermo(CS, G, GV, US, u, v, h, tv, fluxes, dtdia, &
call cpu_clock_begin(id_clock_ALE)
if (use_ice_shelf) then
call ALE_main(G, GV, US, h, u, v, tv, CS%tracer_Reg, CS%ALE_CSp, CS%OBC, &
US%T_to_s*dtdia, fluxes%frac_shelf_h)
dtdia, fluxes%frac_shelf_h)
else
call ALE_main(G, GV, US, h, u, v, tv, CS%tracer_Reg, CS%ALE_CSp, CS%OBC, US%T_to_s*dtdia)
call ALE_main(G, GV, US, h, u, v, tv, CS%tracer_Reg, CS%ALE_CSp, CS%OBC, dtdia)
endif

if (showCallTree) call callTree_waypoint("finished ALE_main (step_MOM_thermo)")
Expand Down Expand Up @@ -2232,7 +2232,7 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, restart_CSp, &
! pass to the pointer
shelf_area => frac_shelf_h
call ALE_main(G, GV, US, CS%h, CS%u, CS%v, CS%tv, CS%tracer_Reg, CS%ALE_CSp, &
CS%OBC, frac_shelf_h = shelf_area)
CS%OBC, frac_shelf_h=shelf_area)
else
call ALE_main( G, GV, US, CS%h, CS%u, CS%v, CS%tv, CS%tracer_Reg, CS%ALE_CSp, CS%OBC)
endif
Expand Down
4 changes: 2 additions & 2 deletions src/initialization/MOM_state_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,7 @@ subroutine MOM_initialize_state(u, v, h, tv, Time, G, GV, US, PF, dirs, &
! a restart file to the internal representation in this run.
real :: vel_rescale ! A rescaling factor for velocities from the representation in
! a restart file to the internal representation in this run.
real :: dt ! The baroclinic dynamics timestep for this run [s].
real :: dt ! The baroclinic dynamics timestep for this run [T ~> s].
logical :: from_Z_file, useALE
logical :: new_sim
integer :: write_geom
Expand Down Expand Up @@ -475,7 +475,7 @@ subroutine MOM_initialize_state(u, v, h, tv, Time, G, GV, US, PF, dirs, &
"an initial grid that is consistent with the initial conditions.", &
default=1, do_not_log=just_read)

call get_param(PF, mdl, "DT", dt, "Timestep", fail_if_missing=.true.)
call get_param(PF, mdl, "DT", dt, "Timestep", fail_if_missing=.true., scale=US%s_to_T)

if (new_sim .and. debug) &
call hchksum(h, "Pre-ALE_regrid: h ", G%HI, haloshift=1, scale=GV%H_to_m)
Expand Down
2 changes: 1 addition & 1 deletion src/tracer/MOM_offline_main.F90
Original file line number Diff line number Diff line change
Expand Up @@ -354,7 +354,7 @@ subroutine offline_advection_ale(fluxes, Time_start, time_interval, CS, id_clock
call MOM_tracer_chkinv(debug_msg, G, h_new, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif
call cpu_clock_begin(id_clock_ALE)
call ALE_main_offline(G, GV, h_new, CS%tv, CS%tracer_Reg, CS%ALE_CSp, CS%OBC, CS%dt_offline)
call ALE_main_offline(G, GV, h_new, CS%tv, CS%tracer_Reg, CS%ALE_CSp, CS%OBC, CS%US%s_to_T*CS%dt_offline)
call cpu_clock_end(id_clock_ALE)

if (CS%debug) then
Expand Down
6 changes: 3 additions & 3 deletions src/tracer/MOM_tracer_registry.F90
Original file line number Diff line number Diff line change
Expand Up @@ -546,18 +546,18 @@ subroutine register_tracer_diagnostics(Reg, h, Time, diag, G, GV, US, use_ALE)
var_lname = "Vertical remapping tracer concentration tendency for "//trim(Reg%Tr(m)%name)
Tr%id_remap_conc= register_diag_field('ocean_model', &
trim(Tr%flux_nameroot)//'_tendency_vert_remap', diag%axesTL, Time, var_lname, &
trim(units)//' s-1')
trim(units)//' s-1', conversion=US%s_to_T)

var_lname = "Vertical remapping tracer content tendency for "//trim(Reg%Tr(m)%flux_longname)
Tr%id_remap_cont = register_diag_field('ocean_model', &
trim(Tr%flux_nameroot)//'h_tendency_vert_remap', &
diag%axesTL, Time, var_lname, flux_units, v_extensive=.true., conversion = Tr%conv_scale)
diag%axesTL, Time, var_lname, flux_units, v_extensive=.true., conversion=Tr%conv_scale*US%s_to_T)

var_lname = "Vertical sum of vertical remapping tracer content tendency for "//&
trim(Reg%Tr(m)%flux_longname)
Tr%id_remap_cont_2d = register_diag_field('ocean_model', &
trim(Tr%flux_nameroot)//'h_tendency_vert_remap_2d', &
diag%axesT1, Time, var_lname, flux_units, conversion = Tr%conv_scale)
diag%axesT1, Time, var_lname, flux_units, conversion=Tr%conv_scale*US%s_to_T)

endif

Expand Down

0 comments on commit 00da24e

Please sign in to comment.