Skip to content

Commit

Permalink
Merge pull request mom-ocean#1032 from Hallberg-NOAA/rescale_cleanup
Browse files Browse the repository at this point in the history
MOM6: Dimensional rescaling cleanup
  • Loading branch information
adcroft authored Nov 22, 2019
2 parents 8791de3 + 2ae0a68 commit be50409
Show file tree
Hide file tree
Showing 36 changed files with 590 additions and 548 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
33 changes: 16 additions & 17 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -784,7 +784,7 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_int_in, CS, &
call calculate_diagnostic_fields(u, v, h, CS%uh, CS%vh, CS%tv, CS%ADp, &
CS%CDp, p_surf, CS%t_dyn_rel_diag, CS%diag_pre_sync,&
G, GV, US, CS%diagnostics_CSp)
call post_tracer_diagnostics(CS%Tracer_reg, h, CS%diag_pre_sync, CS%diag, G, GV, US%T_to_s*CS%t_dyn_rel_diag)
call post_tracer_diagnostics(CS%Tracer_reg, h, CS%diag_pre_sync, CS%diag, G, GV, CS%t_dyn_rel_diag)
call diag_copy_diag_to_storage(CS%diag_pre_sync, h, CS%diag)
if (showCallTree) call callTree_waypoint("finished calculate_diagnostic_fields (step_MOM)")
call disable_averaging(CS%diag)
Expand Down 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 @@ -1252,7 +1252,7 @@ subroutine step_MOM_thermo(CS, G, GV, US, u, v, h, tv, fluxes, dtdia, &
call diag_update_remap_grids(CS%diag)

!### Consider moving this up into the if ALE block.
call postALE_tracer_diagnostics(CS%tracer_Reg, G, GV, CS%diag, US%T_to_s*dtdia)
call postALE_tracer_diagnostics(CS%tracer_Reg, G, GV, CS%diag, dtdia)

if (CS%debug) then
call uvchksum("Post-diabatic u", u, v, G%HI, haloshift=2, scale=US%L_T_to_m_s)
Expand All @@ -1276,7 +1276,7 @@ subroutine step_MOM_thermo(CS, G, GV, US, u, v, h, tv, fluxes, dtdia, &
else ! complement of "if (.not.CS%adiabatic)"

call cpu_clock_begin(id_clock_diabatic)
call adiabatic(h, tv, fluxes, US%T_to_s*dtdia, G, GV, CS%diabatic_CSp)
call adiabatic(h, tv, fluxes, dtdia, G, GV, US, CS%diabatic_CSp)
fluxes%fluxes_used = .true.
call cpu_clock_end(id_clock_diabatic)

Expand Down Expand Up @@ -1325,8 +1325,8 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
logical :: do_vertical !< If enough time has elapsed, do the diabatic tracer sources/sinks
logical :: adv_converged !< True if all the horizontal fluxes have been used

real :: dt_off ! The offline timestep [T ~> s]
integer :: dt_offline, dt_offline_vertical
real :: dt_offline ! The offline timestep for advection [T ~> s]
real :: dt_offline_vertical ! The offline timestep for vertical fluxes and remapping [T ~> s]
logical :: skip_diffusion
integer :: id_eta_diff_end

Expand Down Expand Up @@ -1354,7 +1354,6 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
call extract_offline_main(CS%offline_CSp, uhtr, vhtr, eatr, ebtr, h_end, accumulated_time, &
dt_offline, dt_offline_vertical, skip_diffusion)
Time_end = increment_date(Time_start, seconds=floor(time_interval+0.001))
dt_off = US%s_to_T*REAL(dt_offline)

call enable_averaging(time_interval, Time_end, CS%diag)

Expand All @@ -1366,14 +1365,14 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
endif

! Check to see if vertical tracer functions should be done
if ( mod(accumulated_time, dt_offline_vertical) == 0 ) then
if ( mod(accumulated_time, floor(US%T_to_s*dt_offline_vertical + 1e-6)) == 0 ) then
do_vertical = .true.
else
do_vertical = .false.
endif

! Increment the amount of time elapsed since last read and check if it's time to roll around
accumulated_time = mod(accumulated_time + int(time_interval), dt_offline)
accumulated_time = mod(accumulated_time + int(time_interval), floor(US%T_to_s*dt_offline+1e-6))
if (accumulated_time==0) then
last_iter = .true.
else
Expand Down Expand Up @@ -1406,9 +1405,9 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
if (associated(CS%VarMix)) then
call pass_var(CS%h, G%Domain)
call calc_resoln_function(CS%h, CS%tv, G, GV, US, CS%VarMix)
call calc_slope_functions(CS%h, CS%tv, dt_off, G, GV, US, CS%VarMix)
call calc_slope_functions(CS%h, CS%tv, dt_offline, G, GV, US, CS%VarMix)
endif
call tracer_hordiff(CS%h, dt_off, CS%MEKE, CS%VarMix, G, GV, US, &
call tracer_hordiff(CS%h, dt_offline, CS%MEKE, CS%VarMix, G, GV, US, &
CS%tracer_diff_CSp, CS%tracer_Reg, CS%tv)
endif
endif
Expand All @@ -1431,9 +1430,9 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
if (associated(CS%VarMix)) then
call pass_var(CS%h, G%Domain)
call calc_resoln_function(CS%h, CS%tv, G, GV, US, CS%VarMix)
call calc_slope_functions(CS%h, CS%tv, dt_off, G, GV, US, CS%VarMix)
call calc_slope_functions(CS%h, CS%tv, dt_offline, G, GV, US, CS%VarMix)
endif
call tracer_hordiff(CS%h, dt_off, CS%MEKE, CS%VarMix, G, GV, US, &
call tracer_hordiff(CS%h, dt_offline, CS%MEKE, CS%VarMix, G, GV, US, &
CS%tracer_diff_CSp, CS%tracer_Reg, CS%tv)
endif
endif
Expand All @@ -1459,7 +1458,7 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
! Note that for the layer mode case, the calls to tracer sources and sinks is embedded in
! main_offline_advection_layer. Warning: this may not be appropriate for tracers that
! exchange with the atmosphere
if (time_interval /= dt_offline) then
if (abs(time_interval - US%T_to_s*dt_offline) > 1.0e-6) then
call MOM_error(FATAL, &
"For offline tracer mode in a non-ALE configuration, dt_offline must equal time_interval")
endif
Expand All @@ -1468,7 +1467,7 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
CS%h, eatr, ebtr, uhtr, vhtr)
! Perform offline diffusion if requested
if (.not. skip_diffusion) then
call tracer_hordiff(h_end, dt_off, CS%MEKE, CS%VarMix, G, GV, US, &
call tracer_hordiff(h_end, dt_offline, CS%MEKE, CS%VarMix, G, GV, US, &
CS%tracer_diff_CSp, CS%tracer_Reg, CS%tv)
endif

Expand Down Expand Up @@ -2232,7 +2231,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
6 changes: 3 additions & 3 deletions src/core/MOM_variables.F90
Original file line number Diff line number Diff line change
Expand Up @@ -164,10 +164,10 @@ module MOM_variables
dv_dt_dia => NULL() !< Meridional acceleration due to diapycnal mixing [L T-2 ~> m s-2]
real, pointer, dimension(:,:,:) :: du_other => NULL()
!< Zonal velocity changes due to any other processes that are
!! not due to any explicit accelerations [m s-1].
!! not due to any explicit accelerations [L T-1 ~> m s-1].
real, pointer, dimension(:,:,:) :: dv_other => NULL()
!< Meridional velocity changes due to any other processes that are
!! not due to any explicit accelerations [m s-1].
!< Meridional velocity changes due to any other processes that are
!! not due to any explicit accelerations [L T-1 ~> m s-1].

! These accelerations are sub-terms included in the accelerations above.
real, pointer :: gradKEu(:,:,:) => NULL() !< gradKEu = - d/dx(u2) [L T-2 ~> m s-2]
Expand Down
Loading

0 comments on commit be50409

Please sign in to comment.