Skip to content

Commit

Permalink
Merge pull request #605 from NOAA-GFDL/halo_update_clock
Browse files Browse the repository at this point in the history
Added a clock argument to halo update calls
  • Loading branch information
adcroft authored Sep 21, 2017
2 parents 4ac331c + a204620 commit 2350dba
Show file tree
Hide file tree
Showing 10 changed files with 348 additions and 284 deletions.
132 changes: 58 additions & 74 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -630,11 +630,8 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
call disable_averaging(CS%diag)
endif

if (G%nonblocking_updates) then
call cpu_clock_begin(id_clock_pass)
call complete_group_pass(CS%pass_tau_ustar_psurf, G%Domain)
call cpu_clock_end(id_clock_pass)
endif
if (G%nonblocking_updates) &
call complete_group_pass(CS%pass_tau_ustar_psurf, G%Domain, clock=id_clock_pass)

if (CS%interp_p_surf) then
if (.not.ASSOCIATED(CS%p_surf_end)) allocate(CS%p_surf_end(isd:ied,jsd:jed))
Expand Down Expand Up @@ -706,20 +703,19 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
call set_viscous_BBL(u, v, h, CS%tv, CS%visc, G, GV, CS%set_visc_CSp)
call cpu_clock_end(id_clock_BBL_visc)

call cpu_clock_begin(id_clock_pass)
if (do_pass_Ray) call do_group_pass(CS%pass_ray, G%Domain )
if (do_pass_kv_bbl_thick) call do_group_pass(CS%pass_bbl_thick_kv_bbl, G%Domain)
call cpu_clock_end(id_clock_pass)
if (do_pass_Ray) call do_group_pass(CS%pass_ray, G%Domain, clock=id_clock_pass)
if (do_pass_kv_bbl_thick) &
call do_group_pass(CS%pass_bbl_thick_kv_bbl, G%Domain, clock=id_clock_pass)
if (showCallTree) call callTree_wayPoint("done with set_viscous_BBL (diabatic_first)")

call cpu_clock_begin(id_clock_thermo)

! Apply diabatic forcing, do mixing, and regrid.
call step_MOM_thermo(CS, G, GV, u, v, h, CS%tv, fluxes, dtdia)
do_pass_kv_turb = associated(CS%visc%Kv_turb)

! The diabatic processes are now ahead of the dynamics by dtdia.
CS%t_dyn_rel_thermo = -dtdia
do_pass_kv_turb = associated(CS%visc%Kv_turb)
if (showCallTree) call callTree_waypoint("finished diabatic_first (step_MOM)")

call disable_averaging(CS%diag)
Expand All @@ -733,32 +729,27 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
call cpu_clock_begin(id_clock_dynamics)
call disable_averaging(CS%diag)

if (CS%thickness_diffuse .and. CS%thickness_diffuse_first) then
if (CS%t_dyn_rel_adv == 0.0) then
if (thermo_does_span_coupling) then
dtth = dt_therm
else
dtth = dt*min(ntstep,n_max-n+1)
endif

call enable_averaging(dtth,Time_local+set_time(int(floor(dtth-dt+0.5))), CS%diag)
call cpu_clock_begin(id_clock_thick_diff)
if (associated(CS%VarMix)) &
call calc_slope_functions(h, CS%tv, dt, G, GV, CS%VarMix)
call thickness_diffuse(h, CS%uhtr, CS%vhtr, CS%tv, dtth, G, GV, &
CS%MEKE, CS%VarMix, CS%CDp, CS%thickness_diffuse_CSp)
call cpu_clock_end(id_clock_thick_diff)
call cpu_clock_begin(id_clock_pass)
call pass_var(h, G%Domain) !###, halo=max(2,cont_stensil))
call cpu_clock_end(id_clock_pass)
call disable_averaging(CS%diag)
if (showCallTree) call callTree_waypoint("finished thickness_diffuse_first (step_MOM)")
if ((CS%t_dyn_rel_adv == 0.0) .and. CS%thickness_diffuse .and. CS%thickness_diffuse_first) then
if (thermo_does_span_coupling) then
dtth = dt_therm
else
dtth = dt*min(ntstep,n_max-n+1)
endif

! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated.
call diag_update_remap_grids(CS%diag)
call enable_averaging(dtth,Time_local+set_time(int(floor(dtth-dt+0.5))), CS%diag)
call cpu_clock_begin(id_clock_thick_diff)
if (associated(CS%VarMix)) &
call calc_slope_functions(h, CS%tv, dt, G, GV, CS%VarMix)
call thickness_diffuse(h, CS%uhtr, CS%vhtr, CS%tv, dtth, G, GV, &
CS%MEKE, CS%VarMix, CS%CDp, CS%thickness_diffuse_CSp)
call cpu_clock_end(id_clock_thick_diff)
call pass_var(h, G%Domain, clock=id_clock_pass) !###, halo=max(2,cont_stensil))
call disable_averaging(CS%diag)
if (showCallTree) call callTree_waypoint("finished thickness_diffuse_first (step_MOM)")

endif
! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated.
call diag_update_remap_grids(CS%diag)
endif

! The bottom boundary layer properties are out-of-date and need to be
Expand All @@ -777,22 +768,23 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
if (showCallTree) call callTree_wayPoint("done with set_viscous_BBL (step_MOM)")
endif

call cpu_clock_begin(id_clock_pass)
if (do_pass_kv_turb) call do_group_pass(CS%pass_kv_turb, G%Domain)
if (do_pass_kv_turb) &
call do_group_pass(CS%pass_kv_turb, G%Domain, clock=id_clock_pass)
do_pass_kv_turb = .false.
call cpu_clock_end(id_clock_pass)

if (do_calc_bbl) then
call cpu_clock_begin(id_clock_pass)
if (G%nonblocking_updates) then
if (do_pass_Ray) call start_group_pass(CS%pass_Ray, G%Domain)
if (do_pass_kv_bbl_thick) call start_group_pass(CS%pass_bbl_thick_kv_bbl, G%Domain)
if (do_pass_Ray) &
call start_group_pass(CS%pass_Ray, G%Domain, clock=id_clock_pass)
if (do_pass_kv_bbl_thick) &
call start_group_pass(CS%pass_bbl_thick_kv_bbl, G%Domain, clock=id_clock_pass)
! do_calc_bbl will be set to .false. when the message passing is complete.
else
if (do_pass_Ray) call do_group_pass(CS%pass_Ray, G%Domain)
if (do_pass_kv_bbl_thick) call do_group_pass(CS%pass_bbl_thick_kv_bbl, G%Domain)
if (do_pass_Ray) &
call do_group_pass(CS%pass_Ray, G%Domain, clock=id_clock_pass)
if (do_pass_kv_bbl_thick) &
call do_group_pass(CS%pass_bbl_thick_kv_bbl, G%Domain, clock=id_clock_pass)
endif
call cpu_clock_end(id_clock_pass)
endif

if (CS%interp_p_surf) then
Expand All @@ -806,6 +798,7 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
enddo ; enddo
endif

! The original velocities might be stored for debugging.
if (associated(CS%u_prev) .and. associated(CS%v_prev)) then
do k=1,nz ; do j=jsd,jed ; do I=IsdB,IedB
CS%u_prev(I,j,k) = u(I,j,k)
Expand All @@ -821,10 +814,10 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
enddo ; enddo ; enddo

if (G%nonblocking_updates) then ; if (do_calc_bbl) then
call cpu_clock_begin(id_clock_pass)
if (do_pass_Ray) call complete_group_pass(CS%pass_Ray, G%Domain)
if (do_pass_kv_bbl_thick) call complete_group_pass(CS%pass_bbl_thick_kv_bbl, G%Domain)
call cpu_clock_end(id_clock_pass)
if (do_pass_Ray) &
call complete_group_pass(CS%pass_Ray, G%Domain, clock=id_clock_pass)
if (do_pass_kv_bbl_thick) &
call complete_group_pass(CS%pass_bbl_thick_kv_bbl, G%Domain, clock=id_clock_pass)
endif ; endif

if (CS%do_dynamics .and. CS%split) then !--------------------------- start SPLIT
Expand Down Expand Up @@ -880,9 +873,7 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)

if (CS%debug) call hchksum(h,"Post-thickness_diffuse h", G%HI, haloshift=1, scale=GV%H_to_m)
call cpu_clock_end(id_clock_thick_diff)
call cpu_clock_begin(id_clock_pass)
call pass_var(h, G%Domain) !###, halo=max(2,cont_stensil))
call cpu_clock_end(id_clock_pass)
call pass_var(h, G%Domain, clock=id_clock_pass) !###, halo=max(2,cont_stensil))
if (showCallTree) call callTree_waypoint("finished thickness_diffuse (step_MOM)")
endif

Expand All @@ -897,9 +888,7 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
call mixedlayer_restrat(h, CS%uhtr, CS%vhtr, CS%tv, forces, dt, CS%visc%MLD, &
CS%VarMix, G, GV, CS%mixedlayer_restrat_CSp)
call cpu_clock_end(id_clock_ml_restrat)
call cpu_clock_begin(id_clock_pass)
call pass_var(h, G%Domain) !###, halo=max(2,cont_stensil))
call cpu_clock_end(id_clock_pass)
call pass_var(h, G%Domain, clock=id_clock_pass) !###, halo=max(2,cont_stensil))
if (CS%debug) then
call hchksum(h,"Post-mixedlayer_restrat h", G%HI, haloshift=1, scale=GV%H_to_m)
call uvchksum("Post-mixedlayer_restrat [uv]htr", &
Expand Down Expand Up @@ -979,6 +968,12 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
CS%t_dyn_rel_adv = 0.0
call cpu_clock_end(id_clock_tracer) ; call cpu_clock_end(id_clock_thermo)

if (CS%diabatic_first .and. CS%use_temperature) then
! Temperature and salinity need halo updates because they will be used
! in the dynamics before they are changed again.
call do_group_pass(CS%pass_T_S, G%Domain, clock=id_clock_pass)
endif

endif

!===========================================================================
Expand All @@ -1001,19 +996,11 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)

call disable_averaging(CS%diag)

else ! "else branch for if (.not.CS%diabatic_first) then"
if (abs(CS%t_dyn_rel_thermo) > 1e-6*dt) call MOM_error(FATAL, &
endif

if (CS%diabatic_first .and. abs(CS%t_dyn_rel_thermo) > 1e-6*dt) call MOM_error(FATAL, &
"step_MOM: Mismatch between the dynamics and diabatic times "//&
"with DIABATIC_FIRST.")

! Tracers have been advected and diffused, and need halo updates.
if (CS%use_temperature) then
call cpu_clock_begin(id_clock_pass)
call do_group_pass(CS%pass_T_S, G%Domain)
call cpu_clock_end(id_clock_pass)
endif
endif ! close of "if (.not.CS%diabatic_first) then ; if (.not.CS%adiabatic)"

! Record that the dynamics and diabatic processes are synchronized.
CS%t_dyn_rel_thermo = 0.0
call cpu_clock_end(id_clock_thermo)
Expand All @@ -1034,7 +1021,7 @@ subroutine step_MOM(forces, fluxes, sfc_state, Time_start, time_interval, CS)
! Calculate diagnostics at the end of the time step.
call cpu_clock_begin(id_clock_other) ; call cpu_clock_begin(id_clock_diagnostics)

call enable_averaging(dt,Time_local, CS%diag)
call enable_averaging(dt, Time_local, CS%diag)
! These diagnostics are available every time step.
if (CS%id_u > 0) call post_data(CS%id_u, u, CS%diag)
if (CS%id_v > 0) call post_data(CS%id_v, v, CS%diag)
Expand Down Expand Up @@ -1204,9 +1191,7 @@ subroutine step_MOM_thermo(CS, G, GV, u, v, h, tv, fluxes, dtdia)
call cpu_clock_end(id_clock_ALE)
endif ! endif for the block "if ( CS%use_ALE_algorithm )"

call cpu_clock_begin(id_clock_pass)
call do_group_pass(CS%pass_uv_T_S_h, G%Domain)
call cpu_clock_end(id_clock_pass)
call do_group_pass(CS%pass_uv_T_S_h, G%Domain, clock=id_clock_pass)

if (CS%debug .and. CS%use_ALE_algorithm) then
call MOM_state_chksum("Post-ALE ", u, v, h, CS%uh, CS%vh, G, GV)
Expand Down Expand Up @@ -1247,9 +1232,7 @@ subroutine step_MOM_thermo(CS, G, GV, u, v, h, tv, fluxes, dtdia)
call cpu_clock_end(id_clock_diabatic)

if (CS%use_temperature) then
call cpu_clock_begin(id_clock_pass)
call do_group_pass(CS%pass_T_S, G%Domain)
call cpu_clock_end(id_clock_pass)
call do_group_pass(CS%pass_T_S, G%Domain, clock=id_clock_pass)
if (CS%debug) then
if (associated(tv%T)) call hchksum(tv%T, "Post-diabatic T", G%HI, haloshift=1)
if (associated(tv%S)) call hchksum(tv%S, "Post-diabatic S", G%HI, haloshift=1)
Expand Down Expand Up @@ -1635,6 +1618,7 @@ subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in, offline_tracer_mo
"If true, do thickness diffusion before dynamics.\n"//&
"This is only used if THICKNESSDIFFUSE is true.", &
default=.false.)
if (.not.CS%thickness_diffuse) CS%thickness_diffuse_first = .false.
call get_param(param_file, "MOM", "BATHYMETRY_AT_VEL", bathy_at_vel, &
"If true, there are separate values for the basin depths \n"//&
"at velocity points. Otherwise the effects of topography \n"//&
Expand Down Expand Up @@ -1927,7 +1911,7 @@ subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in, offline_tracer_mo

if (CS%debug_truncations) then
allocate(CS%u_prev(IsdB:IedB,jsd:jed,nz)) ; CS%u_prev(:,:,:) = 0.0
allocate(CS%v_prev(isd:ied,JsdB:JedB,nz)) ; CS%u_prev(:,:,:) = 0.0
allocate(CS%v_prev(isd:ied,JsdB:JedB,nz)) ; CS%v_prev(:,:,:) = 0.0
endif

MOM_internal_state%u => CS%u ; MOM_internal_state%v => CS%v
Expand Down Expand Up @@ -2081,6 +2065,7 @@ subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in, offline_tracer_mo
else
call ALE_main( G, GV, CS%h, CS%u, CS%v, CS%tv, CS%tracer_Reg, CS%ALE_CSp )
endif

call cpu_clock_begin(id_clock_pass_init)
call create_group_pass(tmp_pass_uv_T_S_h, CS%u, CS%v, G%Domain)
if (CS%use_temperature) then
Expand Down Expand Up @@ -2249,9 +2234,8 @@ subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in, offline_tracer_mo
call register_diags_offline_transport(Time, CS%diag, CS%offline_CSp)
endif

call cpu_clock_begin(id_clock_pass_init)
!--- set up group pass for u,v,T,S and h. pass_uv_T_S_h also is used in step_MOM

call cpu_clock_begin(id_clock_pass_init)
dynamics_stencil = min(3, G%Domain%nihalo, G%Domain%njhalo)
call create_group_pass(CS%pass_uv_T_S_h, CS%u, CS%v, G%Domain, halo=dynamics_stencil)
if (CS%use_temperature) then
Expand Down
14 changes: 4 additions & 10 deletions src/core/MOM_barotropic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -822,13 +822,11 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, &
! These calculations can be done almost immediately, but the halo updates
! must be done before the [abcd]mer and [abcd]zon are calculated.
if (id_clock_calc_pre > 0) call cpu_clock_end(id_clock_calc_pre)
if (id_clock_pass_pre > 0) call cpu_clock_begin(id_clock_pass_pre)
if (nonblock_setup) then
call start_group_pass(CS%pass_q_DCor, CS%BT_Domain)
call start_group_pass(CS%pass_q_DCor, CS%BT_Domain, clock=id_clock_pass_pre)
else
call do_group_pass(CS%pass_q_DCor, CS%BT_Domain)
call do_group_pass(CS%pass_q_DCor, CS%BT_Domain, clock=id_clock_pass_pre)
endif
if (id_clock_pass_pre > 0) call cpu_clock_end(id_clock_pass_pre)
if (id_clock_calc_pre > 0) call cpu_clock_begin(id_clock_calc_pre)
endif

Expand Down Expand Up @@ -940,9 +938,7 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, &

if (nonblock_setup .and. .not.CS%linearized_BT_PV) then
if (id_clock_calc_pre > 0) call cpu_clock_end(id_clock_calc_pre)
if (id_clock_pass_pre > 0) call cpu_clock_begin(id_clock_pass_pre)
call complete_group_pass(CS%pass_q_DCor, CS%BT_Domain)
if (id_clock_pass_pre > 0) call cpu_clock_end(id_clock_pass_pre)
call complete_group_pass(CS%pass_q_DCor, CS%BT_Domain, clock=id_clock_pass_pre)
if (id_clock_calc_pre > 0) call cpu_clock_begin(id_clock_calc_pre)
endif

Expand Down Expand Up @@ -1529,10 +1525,8 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, &

if ((iev - stencil < ie) .or. (jev - stencil < je)) then
if (id_clock_calc > 0) call cpu_clock_end(id_clock_calc)
if (id_clock_pass_step > 0) call cpu_clock_begin(id_clock_pass_step)
call do_group_pass(CS%pass_eta_ubt, CS%BT_Domain)
call do_group_pass(CS%pass_eta_ubt, CS%BT_Domain, clock=id_clock_pass_step)
isv = isvf ; iev = ievf ; jsv = jsvf ; jev = jevf
if (id_clock_pass_step > 0) call cpu_clock_end(id_clock_pass_step)
if (id_clock_calc > 0) call cpu_clock_begin(id_clock_calc)
else
isv = isv+stencil ; iev = iev-stencil
Expand Down
Loading

0 comments on commit 2350dba

Please sign in to comment.