Skip to content

Commit

Permalink
Clean up comments and interface to diag grid definition update. #62
Browse files Browse the repository at this point in the history
  • Loading branch information
nichannah committed Jul 17, 2015
1 parent bc8a185 commit b690e3b
Show file tree
Hide file tree
Showing 12 changed files with 72 additions and 67 deletions.
25 changes: 13 additions & 12 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -971,9 +971,9 @@ subroutine step_MOM(fluxes, state, Time_start, time_interval, CS)
call do_group_pass(CS%pass_uv_T_S_h, G%Domain)
call cpu_clock_end(id_clock_pass)

! The diag mediator may need to re-generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, CS%diag)
! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated.
call diag_update_target_grids(CS%diag)

if (CS%debug) then
call uchksum(u,"Post-dia first u", G, haloshift=2)
Expand Down Expand Up @@ -1050,9 +1050,9 @@ subroutine step_MOM(fluxes, state, Time_start, time_interval, CS)
call disable_averaging(CS%diag)
if (showCallTree) call callTree_waypoint("finished thickness_diffuse_first (step_MOM)")

! The diag mediator may need to re-generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, CS%diag)
! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated.
call diag_update_target_grids(CS%diag)

endif
endif
Expand Down Expand Up @@ -1273,9 +1273,10 @@ subroutine step_MOM(fluxes, state, Time_start, time_interval, CS)
endif
endif

! The diag mediator may need to re-generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, CS%diag)
! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated. This needs to
! happen after the H update and before the next post_data.
call diag_update_target_grids(CS%diag)

call cpu_clock_begin(id_clock_pass)
call do_group_pass(CS%pass_uv_T_S_h, G%Domain)
Expand Down Expand Up @@ -2017,9 +2018,9 @@ subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in)
! e.g. to generate the target grids below.
call set_axes_info(G, param_file, diag)

! The diag mediator may need to (re)generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, diag)
! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated. This needs to
call diag_update_target_grids(diag)

call cpu_clock_begin(id_clock_MOM_init)
if (CS%use_ALE_algorithm) then
Expand Down
5 changes: 3 additions & 2 deletions src/core/MOM_continuity.F90
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ module MOM_continuity

contains

subroutine continuity(u, v, hin, h, uh, vh, dt, G, CS, uhbt, vhbt, OBC, &
subroutine continuity(u, v, hin, h, uh, vh, dt, G, CS, diag_cs, uhbt, vhbt, OBC, &
visc_rem_u, visc_rem_v, u_cor, v_cor, &
uhbt_aux, vhbt_aux, u_cor_aux, v_cor_aux, BT_cont)
real, intent(in), dimension(NIMEMB_,NJMEM_,NKMEM_) :: u
Expand All @@ -84,6 +84,7 @@ subroutine continuity(u, v, hin, h, uh, vh, dt, G, CS, uhbt, vhbt, OBC, &
real, intent(in) :: dt
type(ocean_grid_type), intent(inout) :: G
type(continuity_CS), pointer :: CS
type(diag_ctrl), intent(inout) :: diag_cs
real, intent(in), optional, dimension(NIMEMB_,NJMEM_) :: uhbt
real, intent(in), optional, dimension(NIMEM_,NJMEMB_) :: vhbt
type(ocean_OBC_type), pointer, optional :: OBC
Expand Down Expand Up @@ -150,7 +151,7 @@ subroutine continuity(u, v, hin, h, uh, vh, dt, G, CS, uhbt, vhbt, OBC, &
" or neither.")

if (CS%continuity_scheme == PPM_SCHEME) then
call continuity_PPM(u, v, hin, h, uh, vh, dt, G, CS%PPM_CSp, uhbt, vhbt, OBC, &
call continuity_PPM(u, v, hin, h, uh, vh, dt, G, CS%PPM_CSp, diag_cs, uhbt, vhbt, OBC, &
visc_rem_u, visc_rem_v, u_cor, v_cor, &
uhbt_aux, vhbt_aux, u_cor_aux, v_cor_aux, BT_cont)
else
Expand Down
9 changes: 7 additions & 2 deletions src/core/MOM_continuity_PPM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module MOM_continuity_PPM
!********+*********+*********+*********+*********+*********+*********+**

use MOM_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end, CLOCK_ROUTINE
use MOM_diag_mediator, only : time_type, diag_ctrl
use MOM_diag_mediator, only : time_type, diag_ctrl, diag_update_target_grids
use MOM_error_handler, only : MOM_error, FATAL, WARNING, is_root_pe
use MOM_file_parser, only : get_param, log_version, param_file_type
use MOM_grid, only : ocean_grid_type
Expand Down Expand Up @@ -103,7 +103,7 @@ module MOM_continuity_PPM

contains

subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, CS, uhbt, vhbt, OBC, &
subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, CS, diag_cs, uhbt, vhbt, OBC, &
visc_rem_u, visc_rem_v, u_cor, v_cor, &
uhbt_aux, vhbt_aux, u_cor_aux, v_cor_aux, BT_cont)
real, dimension(NIMEMB_,NJMEM_,NKMEM_), intent(in) :: u
Expand All @@ -115,6 +115,7 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, CS, uhbt, vhbt, OBC, &
real, intent(in) :: dt
type(ocean_grid_type), intent(inout) :: G
type(continuity_PPM_CS), pointer :: CS
type(diag_ctrl), intent(inout) :: diag_cs
real, dimension(NIMEMB_,NJMEM_), intent(in), optional :: uhbt
real, dimension(NIMEM_,NJMEMB_), intent(in), optional :: vhbt
type(ocean_OBC_type), pointer, optional :: OBC
Expand Down Expand Up @@ -316,6 +317,10 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, CS, uhbt, vhbt, OBC, &
endif
endif

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

end subroutine continuity_PPM

subroutine zonal_mass_flux(u, h_in, uh, dt, G, CS, LB, uhbt, OBC, &
Expand Down
21 changes: 11 additions & 10 deletions src/core/MOM_dynamics_legacy_split.F90
Original file line number Diff line number Diff line change
Expand Up @@ -588,7 +588,7 @@ subroutine step_MOM_dyn_legacy_split(u, v, h, tv, visc, &
if (CS%readjust_velocity) then
! Adjust the input velocites so that their transports match uhbt_out & vhbt_out.
call continuity(u, v, h, hp, uh_in, vh_in, dt, G, &
CS%continuity_CSp, uhbt_in, vhbt_in, CS%OBC, &
CS%continuity_CSp, CS%diag, uhbt_in, vhbt_in, CS%OBC, &
CS%visc_rem_u, CS%visc_rem_v, u_adj, v_adj, &
BT_cont=CS%BT_cont)
u_init => u_adj ; v_init => v_adj
Expand All @@ -601,7 +601,7 @@ subroutine step_MOM_dyn_legacy_split(u, v, h, tv, visc, &
CS%readjust_velocity = .false.
else
call continuity(u, v, h, hp, uh_in, vh_in, dt, G, &
CS%continuity_CSp, OBC=CS%OBC, BT_cont=CS%BT_cont)
CS%continuity_CSp, CS%diag, OBC=CS%OBC, BT_cont=CS%BT_cont)
!### call continuity(u, v, h, hp, uh_in, vh_in, dt, G, &
!### CS%continuity_CSp, OBC=CS%OBC, visc_rem_u=CS%visc_rem_u, &
!### visc_rem_v=CS%visc_rem_v, BT_cont=CS%BT_cont)
Expand Down Expand Up @@ -631,8 +631,9 @@ subroutine step_MOM_dyn_legacy_split(u, v, h, tv, visc, &
if (associated(CS%BT_cont) .or. CS%BT_use_layer_fluxes) then
call cpu_clock_begin(id_clock_continuity)
call continuity(u, v, h, hp, uh_in, vh_in, dt, G, &
CS%continuity_CSp, OBC=CS%OBC, visc_rem_u=CS%visc_rem_u, &
visc_rem_v=CS%visc_rem_v, BT_cont=CS%BT_cont)
CS%continuity_CSp, CS%diag, OBC=CS%OBC, &
visc_rem_u=CS%visc_rem_u, visc_rem_v=CS%visc_rem_v, &
BT_cont=CS%BT_cont)
call cpu_clock_end(id_clock_continuity)
if (BT_cont_BT_thick) then
call cpu_clock_begin(id_clock_pass)
Expand Down Expand Up @@ -716,8 +717,8 @@ subroutine step_MOM_dyn_legacy_split(u, v, h, tv, visc, &
! hp = h + dt * div . uh
call cpu_clock_begin(id_clock_continuity)
call continuity(up, vp, h, hp, uh, vh, dt, G, CS%continuity_CSp, &
CS%uhbt, CS%vhbt, CS%OBC, CS%visc_rem_u, CS%visc_rem_v, &
u_av, v_av, BT_cont=CS%BT_cont)
CS%diag, CS%uhbt, CS%vhbt, CS%OBC, CS%visc_rem_u, &
CS%visc_rem_v, u_av, v_av, BT_cont=CS%BT_cont)
call cpu_clock_end(id_clock_continuity)

call cpu_clock_begin(id_clock_pass)
Expand Down Expand Up @@ -927,7 +928,7 @@ subroutine step_MOM_dyn_legacy_split(u, v, h, tv, visc, &
enddo ; enddo ; enddo ; endif
call cpu_clock_begin(id_clock_continuity)
call continuity(u, v, h, h, uh, vh, dt, G, &
CS%continuity_CSp, CS%uhbt, CS%vhbt, CS%OBC, &
CS%continuity_CSp, CS%diag, CS%uhbt, CS%vhbt, CS%OBC, &
CS%visc_rem_u, CS%visc_rem_v, u_av, v_av, &
uhbt_out, vhbt_out, u, v)
call cpu_clock_end(id_clock_continuity)
Expand Down Expand Up @@ -966,7 +967,7 @@ subroutine step_MOM_dyn_legacy_split(u, v, h, tv, visc, &
! u_av and v_av adjusted so their mass transports match uhbt and vhbt.
call cpu_clock_begin(id_clock_continuity)
call continuity(u, v, h, h, uh, vh, dt, G, &
CS%continuity_CSp, CS%uhbt, CS%vhbt, CS%OBC, &
CS%continuity_CSp, CS%diag, CS%uhbt, CS%vhbt, CS%OBC, &
CS%visc_rem_u, CS%visc_rem_v, u_av, v_av)
call cpu_clock_end(id_clock_continuity)
call cpu_clock_begin(id_clock_pass)
Expand Down Expand Up @@ -1066,7 +1067,7 @@ subroutine adjustments_dyn_legacy_split(u, v, h, dt, G, CS)
if (CS%readjust_BT_trans) then
call cpu_clock_begin(id_clock_continuity)
call continuity(u, v, h, h_temp, uh_temp, vh_temp, dt, G, &
CS%continuity_CSp, OBC=CS%OBC)
CS%continuity_CSp, CS%diag, OBC=CS%OBC)
call cpu_clock_end(id_clock_continuity)
!$OMP parallel default(none) shared(is,ie,js,je,nz,CS,uh_temp,vh_temp)
!$OMP do
Expand Down Expand Up @@ -1406,7 +1407,7 @@ subroutine initialize_dyn_legacy_split(u, v, h, uh, vh, eta, Time, G, param_file
if (.not. query_initialized(uh,"uh",restart_CS) .or. &
.not. query_initialized(vh,"vh",restart_CS)) then
h_tmp(:,:,:) = h(:,:,:)
call continuity(u, v, h, h_tmp, uh, vh, dt, G, CS%continuity_CSp, OBC=CS%OBC)
call continuity(u, v, h, h_tmp, uh, vh, dt, G, CS%continuity_CSp, CS%diag, OBC=CS%OBC)
call cpu_clock_begin(id_clock_pass_init)
call pass_var(h_tmp, G%Domain)
call cpu_clock_end(id_clock_pass_init)
Expand Down
18 changes: 4 additions & 14 deletions src/core/MOM_dynamics_split_RK2.F90
Original file line number Diff line number Diff line change
Expand Up @@ -605,7 +605,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, &
if (associated(CS%BT_cont) .or. CS%BT_use_layer_fluxes) then
call cpu_clock_begin(id_clock_continuity)
call continuity(u, v, h, hp, uh_in, vh_in, dt, G, &
CS%continuity_CSp, OBC=CS%OBC, visc_rem_u=CS%visc_rem_u, &
CS%continuity_CSp, CS%diag, OBC=CS%OBC, visc_rem_u=CS%visc_rem_u, &
visc_rem_v=CS%visc_rem_v, BT_cont=CS%BT_cont)
call cpu_clock_end(id_clock_continuity)
if (BT_cont_BT_thick) then
Expand Down Expand Up @@ -695,16 +695,12 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, &
! uh = u_av * h
! hp = h + dt * div . uh
call cpu_clock_begin(id_clock_continuity)
call continuity(up, vp, h, hp, uh, vh, dt, G, CS%continuity_CSp, &
call continuity(up, vp, h, hp, uh, vh, dt, G, CS%continuity_CSp, CS%diag, &
CS%uhbt, CS%vhbt, CS%OBC, CS%visc_rem_u, CS%visc_rem_v, &
u_av, v_av, BT_cont=CS%BT_cont)
call cpu_clock_end(id_clock_continuity)
if (showCallTree) call callTree_wayPoint("done with continuity (step_MOM_dyn_split_RK2)")

! The diag mediator may need to re-generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, CS%diag)

call cpu_clock_begin(id_clock_pass)
call do_group_pass(CS%pass_hp_uv, G%Domain)
if (G%nonblocking_updates) then
Expand Down Expand Up @@ -905,18 +901,14 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, &
! u_av and v_av adjusted so their mass transports match uhbt and vhbt.
call cpu_clock_begin(id_clock_continuity)
call continuity(u, v, h, h, uh, vh, dt, G, &
CS%continuity_CSp, CS%uhbt, CS%vhbt, CS%OBC, &
CS%continuity_CSp, CS%diag, CS%uhbt, CS%vhbt, CS%OBC, &
CS%visc_rem_u, CS%visc_rem_v, u_av, v_av)
call cpu_clock_end(id_clock_continuity)
call cpu_clock_begin(id_clock_pass)
call do_group_pass(CS%pass_h, G%Domain)
call cpu_clock_end(id_clock_pass)
if (showCallTree) call callTree_wayPoint("done with continuity (step_MOM_dyn_split_RK2)")

! The diag mediator may need to re-generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, CS%diag)

call cpu_clock_begin(id_clock_pass)
if (G%nonblocking_updates) then
call start_group_pass(CS%pass_av_uvh, G%Domain)
Expand Down Expand Up @@ -1266,7 +1258,7 @@ subroutine initialize_dyn_split_RK2(u, v, h, uh, vh, eta, Time, G, param_file, &
if (.not. query_initialized(uh,"uh",restart_CS) .or. &
.not. query_initialized(vh,"vh",restart_CS)) then
h_tmp(:,:,:) = h(:,:,:)
call continuity(u, v, h, h_tmp, uh, vh, dt, G, CS%continuity_CSp, OBC=CS%OBC)
call continuity(u, v, h, h_tmp, uh, vh, dt, G, CS%continuity_CSp, CS%diag, OBC=CS%OBC)
call cpu_clock_begin(id_clock_pass_init)
call create_group_pass(pass_h_tmp, h_tmp, G%Domain)
call do_group_pass(pass_h_tmp, G%Domain)
Expand All @@ -1277,8 +1269,6 @@ subroutine initialize_dyn_split_RK2(u, v, h, uh, vh, eta, Time, G, param_file, &
CS%h_av(:,:,:) = h(:,:,:)
endif

call diag_update_target_grids(G, CS%diag)

call cpu_clock_begin(id_clock_pass_init)
call create_group_pass(pass_av_h_uvh, CS%u_av,CS%v_av, G%Domain)
call create_group_pass(pass_av_h_uvh, CS%h_av, G%Domain)
Expand Down
7 changes: 4 additions & 3 deletions src/core/MOM_dynamics_unsplit.F90
Original file line number Diff line number Diff line change
Expand Up @@ -268,7 +268,8 @@ subroutine step_MOM_dyn_unsplit(u, v, h, tv, visc, Time_local, dt, fluxes, &
! uh = u*h
! hp = h + dt/2 div . uh
call cpu_clock_begin(id_clock_continuity)
call continuity(u, v, h, hp, uh, vh, dt*0.5, G, CS%continuity_CSp, OBC=CS%OBC)
call continuity(u, v, h, hp, uh, vh, dt*0.5, G, CS%continuity_CSp, CS%diag, &
OBC=CS%OBC)
call cpu_clock_end(id_clock_continuity)
call cpu_clock_begin(id_clock_pass)
call pass_var(hp, G%Domain)
Expand Down Expand Up @@ -377,7 +378,7 @@ subroutine step_MOM_dyn_unsplit(u, v, h, tv, visc, Time_local, dt, fluxes, &
! h_av = hp + dt/2 div . uh
call cpu_clock_begin(id_clock_continuity)
call continuity(up, vp, hp, h_av, uh, vh, &
(0.5*dt), G, CS%continuity_CSp, OBC=CS%OBC)
(0.5*dt), G, CS%continuity_CSp, CS%diag, OBC=CS%OBC)
call cpu_clock_end(id_clock_continuity)
call cpu_clock_begin(id_clock_pass)
call pass_var(h_av, G%Domain)
Expand Down Expand Up @@ -436,7 +437,7 @@ subroutine step_MOM_dyn_unsplit(u, v, h, tv, visc, Time_local, dt, fluxes, &
! h = hp + dt/2 div . uh
call cpu_clock_begin(id_clock_continuity)
call continuity(upp, vpp, hp, h, uh, vh, &
(dt*0.5), G, CS%continuity_CSp, OBC=CS%OBC)
(dt*0.5), G, CS%continuity_CSp, CS%diag, OBC=CS%OBC)
call cpu_clock_end(id_clock_continuity)
call cpu_clock_begin(id_clock_pass)
call pass_var(h, G%Domain)
Expand Down
7 changes: 4 additions & 3 deletions src/core/MOM_dynamics_unsplit_RK2.F90
Original file line number Diff line number Diff line change
Expand Up @@ -282,7 +282,8 @@ subroutine step_MOM_dyn_unsplit_RK2(u_in, v_in, h_in, tv, visc, Time_local, dt,
call cpu_clock_begin(id_clock_continuity)
! This is a duplicate caclulation of the last continuity from the previous step
! and could/should be optimized out. -AJA
call continuity(u_in, v_in, h_in, hp, uh, vh, dt_pred, G, CS%continuity_CSp, OBC=CS%OBC)
call continuity(u_in, v_in, h_in, hp, uh, vh, dt_pred, G, CS%continuity_CSp, &
CS%diag, OBC=CS%OBC)
call cpu_clock_end(id_clock_continuity)
call cpu_clock_begin(id_clock_pass)
call pass_var(hp, G%Domain)
Expand Down Expand Up @@ -369,7 +370,7 @@ subroutine step_MOM_dyn_unsplit_RK2(u_in, v_in, h_in, tv, visc, Time_local, dt,
! h_av = h + dt div . uh
call cpu_clock_begin(id_clock_continuity)
call continuity(up, vp, h_in, hp, uh, vh, &
dt, G, CS%continuity_CSp, OBC=CS%OBC)
dt, G, CS%continuity_CSp, CS%diag, OBC=CS%OBC)
call cpu_clock_end(id_clock_continuity)
call cpu_clock_begin(id_clock_pass)
call pass_var(hp, G%Domain)
Expand Down Expand Up @@ -426,7 +427,7 @@ subroutine step_MOM_dyn_unsplit_RK2(u_in, v_in, h_in, tv, visc, Time_local, dt,
! h[n+1] = h[n] + dt div . uh
call cpu_clock_begin(id_clock_continuity)
call continuity(up, vp, h_in, h_in, uh, vh, &
dt, G, CS%continuity_CSp, OBC=CS%OBC)
dt, G, CS%continuity_CSp, CS%diag, OBC=CS%OBC)
call cpu_clock_end(id_clock_continuity)
call cpu_clock_begin(id_clock_pass)
call pass_var(h_in, G%Domain)
Expand Down
8 changes: 5 additions & 3 deletions src/framework/MOM_diag_mediator.F90
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,8 @@ module MOM_diag_mediator
#define DIM_J(a) lbound(a, 2):ubound(a, 2)
#define DIM_K(a) lbound(a, 3):ubound(a, 3)

#define __DO_SAFETY_CHECKS__

public set_axes_info, post_data, register_diag_field, time_type
public post_data_1d_k
public safe_alloc_ptr, safe_alloc_alloc
Expand Down Expand Up @@ -755,27 +757,27 @@ subroutine remap_diag_to_z(field, diag, diag_cs, remapped_field)

end subroutine remap_diag_to_z

subroutine diag_update_target_grids(G, diag_cs)
subroutine diag_update_target_grids(diag_cs)
! Build/update target vertical grids for diagnostic remapping.
!
! The target grids need to be updated whenever sea surface
! height changes.

type(ocean_grid_type), intent(in) :: G
type(diag_ctrl), intent(inout) :: diag_cs

! Arguments:
! (in) G - ocean grid structure.
! (inout) diag_cs - structure used to regulate diagnostic output.

real, dimension(size(diag_cs%h, 3)) :: h_src
type(ocean_grid_type), pointer :: G
real :: depth
integer :: nz_src, nz_dest
integer :: i, j, k
logical :: force, h_changed

nz_dest = diag_cs%nz_remap
nz_src = size(diag_cs%h, 3)
G => diag_cs%G

if (.not. diag_cs%remapping_initialized) then
call assert(allocated(diag_cs%zi_remap), &
Expand Down
13 changes: 7 additions & 6 deletions src/parameterizations/lateral/MOM_mixed_layer_restrat.F90
Original file line number Diff line number Diff line change
Expand Up @@ -395,9 +395,10 @@ subroutine mixedlayer_restrat_general(h, uhtr, vhtr, tv, fluxes, dt, G, CS)
enddo ; enddo ; enddo
!$OMP end parallel

! The diag mediator may need to re-generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, CS%diag)
! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated.
! This needs to happen after the H update and before the next post_data.
call diag_update_target_grids(CS%diag)

! Offer fields for averaging.
if (query_averaging_enabled(CS%diag)) then
Expand Down Expand Up @@ -649,9 +650,9 @@ subroutine mixedlayer_restrat_BML(h, uhtr, vhtr, tv, fluxes, dt, G, CS)
enddo ; enddo ; enddo
!$OMP end parallel

! The diag mediator may need to re-generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, CS%diag)
! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated.
call diag_update_target_grids(CS%diag)

! Offer fields for averaging.
if (query_averaging_enabled(CS%diag) .and. &
Expand Down
7 changes: 4 additions & 3 deletions src/parameterizations/lateral/MOM_thickness_diffuse.F90
Original file line number Diff line number Diff line change
Expand Up @@ -339,9 +339,10 @@ subroutine thickness_diffuse(h, uhtr, vhtr, tv, dt, G, MEKE, VarMix, CDp, CS)
enddo ; enddo
enddo

! The diag mediator may need to re-generate target grids for remmapping when
! total thickness changes.
call diag_update_target_grids(G, CS%diag)
! Whenever thickness changes let the diag manager know, target grids
! for vertical remapping may need to be regenerated.
! This needs to happen after the H update and before the next post_data.
call diag_update_target_grids(CS%diag)

if (MEKE_not_null .AND. ASSOCIATED(VarMix)) then
if (ASSOCIATED(MEKE%Rd_dx_h) .and. ASSOCIATED(VarMix%Rd_dx_h)) then
Expand Down
Loading

0 comments on commit b690e3b

Please sign in to comment.