Skip to content

Commit

Permalink
To aid in the debugging of tracer routines, a new subroutine is created
Browse files Browse the repository at this point in the history
in MOM_tracer_registry.F90: MOM_tracer_chkinv. This routine calculates
the global inventories of all tracers in the registry. Some of the
debugging checksums in the offline tracer routines are updated to use this
new function.
  • Loading branch information
Andrew Shao committed Jun 1, 2017
1 parent ab0575d commit ff690d1
Show file tree
Hide file tree
Showing 5 changed files with 73 additions and 69 deletions.
30 changes: 18 additions & 12 deletions src/ALE/MOM_ALE.F90
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ module MOM_ALE
use MOM_remapping, only : remappingSchemesDoc, remappingDefaultScheme
use MOM_remapping, only : remapping_CS, dzFromH1H2
use MOM_string_functions, only : uppercase, extractWord, extract_integer
use MOM_tracer_registry, only : tracer_registry_type
use MOM_tracer_registry, only : tracer_registry_type, MOM_tracer_chkinv
use MOM_variables, only : ocean_grid_type, thermo_var_ptrs
use MOM_verticalGrid, only : verticalGrid_type

Expand Down Expand Up @@ -492,17 +492,19 @@ subroutine ALE_main_offline( G, GV, h, tv, Reg, CS, dt)

end subroutine ALE_main_offline

subroutine ALE_offline_inputs(CS, G, GV, h_input, h_regrid, tv, Reg, uhtr, vhtr, Kd)
type(ocean_grid_type), intent(in ) :: G !< Ocean grid informations
type(verticalGrid_type), intent(in ) :: GV !< Ocean vertical grid structure
subroutine ALE_offline_inputs(CS, G, GV, h_start, h_input, h_regrid, tv, Reg, uhtr, vhtr, Kd, debug)
type(ALE_CS), pointer :: CS !< Regridding parameters and options
type(ocean_grid_type), intent(in ) :: G !< Ocean grid informations
type(verticalGrid_type), intent(in ) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h_start !< Thicknesses at start of timestep
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h_input !< Thicknesses of input fields
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent( out) :: h_regrid !< Thicknesses after regridding
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamic variable structure
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(inout) :: uhtr !< Zonal mass fluxes
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(inout) :: vhtr !< Meridional mass fluxes
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(inout) :: Kd !< Input diffusivites
type(ALE_CS), pointer :: CS !< Regridding parameters and options
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamic variable structure
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(inout) :: uhtr !< Zonal mass fluxes
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(inout) :: vhtr !< Meridional mass fluxes
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(inout) :: Kd !< Input diffusivites
logical, intent(in ) :: debug !< If true, then turn checksums
! Local variables
integer :: nk, i, j, k, isc, iec, jsc, jec
real, dimension(SZI_(G), SZJ_(G), SZK_(GV)+1) :: dzRegrid ! The change in grid interface positions
Expand All @@ -514,14 +516,16 @@ subroutine ALE_offline_inputs(CS, G, GV, h_input, h_regrid, tv, Reg, uhtr, vhtr,
dzRegrid(:,:,:) = 0.0
h_regrid(:,:,:) = 0.0

if (debug) call MOM_tracer_chkinv("Before ALE_offline_inputs", G, h_input, Reg%Tr, Reg%ntr)

! Build new grid. The new grid is stored in h_new. The old grid is h.
! Both are needed for the subsequent remapping of variables.
call regridding_main( CS%remapCS, CS%regridCS, G, GV, h_input, tv, h_regrid, dzRegrid, conv_adjust = .false. )
call check_grid( G, GV, h_regrid, 0. )
if (CS%show_call_tree) call callTree_waypoint("new grid generated (ALE_main)")

! Remap all variables from old grid h onto new grid h_new
call remap_all_state_vars( CS%remapCS, CS, G, GV, h_input, h_regrid, Reg, debug=CS%show_call_tree )
call remap_all_state_vars( CS%remapCS, CS, G, GV, h_start, h_regrid, Reg, debug=CS%show_call_tree )
if (CS%show_call_tree) call callTree_waypoint("state remapped (ALE_main)")

! Reintegrate mass transports
Expand Down Expand Up @@ -553,6 +557,8 @@ subroutine ALE_offline_inputs(CS, G, GV, h_input, h_regrid, tv, Reg, uhtr, vhtr,

call ALE_remap_scalar(CS%remapCS, G, GV, nk, h_input, tv%T, h_regrid, tv%T)
call ALE_remap_scalar(CS%remapCS, G, GV, nk, h_input, tv%S, h_regrid, tv%S)

if (debug) call MOM_tracer_chkinv("After ALE_offline_inputs", G, h_regrid, Reg%Tr, Reg%ntr)

if (CS%show_call_tree) call callTree_leave("ALE_offline_inputs()")
end subroutine ALE_offline_inputs
Expand All @@ -565,7 +571,7 @@ subroutine ALE_offline_tracer_final( G, GV, h, tv, h_target, Reg, CS)
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after last time step (m or Pa)
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamic variable structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h_target !< Current 3D grid obtained after last time step (m or Pa)
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h_target !< Current 3D grid obtained after last time step (m or Pa)
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
type(ALE_CS), pointer :: CS !< Regridding parameters and options
! Local variables
Expand Down
7 changes: 1 addition & 6 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1621,10 +1621,6 @@ subroutine step_tracers(fluxes, state, Time_start, time_interval, CS)

! Apply any fluxes into the ocean
call offline_fw_fluxes_into_ocean(G, GV, CS%offline_CSp, fluxes, CS%h)
! Ensure that layer thicknesses are reasonable
do k=1,GV%ke ; do j=js,je ; do i=is,ie
CS%h(i,j,k) = MAX(CS%h(i,j,k),GV%Angstrom)
enddo ; enddo ; enddo

if (.not.CS%diabatic_first) then
call offline_advection_ale(fluxes, Time_start, time_interval, CS%offline_CSp, id_clock_ALE, &
Expand All @@ -1647,8 +1643,7 @@ subroutine step_tracers(fluxes, state, Time_start, time_interval, CS)
endif

if (do_vertical) then
call offline_diabatic_ale(fluxes, Time_start, Time_end, CS%offline_CSp, &
CS%h, eatr, ebtr)
call offline_diabatic_ale(fluxes, Time_start, Time_end, CS%offline_CSp, CS%h, eatr, ebtr)
endif

! Last thing that needs to be done is the final ALE remapping
Expand Down
2 changes: 1 addition & 1 deletion src/tracer/MOM_offline_aux.F90
Original file line number Diff line number Diff line change
Expand Up @@ -609,7 +609,7 @@ subroutine update_offline_from_files(G, GV, nk_input, mean_file, sum_file, snap_
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: h_end !< End of timestep layer thickness
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: temp_mean !< Averaged temperature
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: salt_mean !< Averaged salinity
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: mld !< Averaged mixed layer depth
real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: mld !< Averaged mixed layer depth
real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1),intent(inout) :: Kd !< Averaged mixed layer depth
type(forcing), intent(inout) :: fluxes !< Fields with surface fluxes
integer, intent(in ) :: ridx_sum !< Read index for sum, mean, and surf files
Expand Down
52 changes: 23 additions & 29 deletions src/tracer/MOM_offline_main.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ module MOM_offline_main
use MOM_tracer_advect, only : tracer_advect_CS, advect_tracer
use MOM_tracer_diabatic, only : applyTracerBoundaryFluxesInOut
use MOM_tracer_flow_control, only : tracer_flow_control_CS, call_tracer_column_fns, call_tracer_stocks
use MOM_tracer_registry, only : tracer_registry_type, MOM_tracer_chksum
use MOM_tracer_registry, only : tracer_registry_type, MOM_tracer_chksum, MOM_tracer_chkinv
use MOM_variables, only : thermo_var_ptrs
use MOM_verticalGrid, only : verticalGrid_type

Expand Down Expand Up @@ -289,8 +289,6 @@ subroutine offline_advection_ale(fluxes, Time_start, time_interval, CS, &

! This loop does essentially a flux-limited, nonlinear advection scheme until all mass fluxes
! are used. ALE is done after the horizontal advection.


do iter=1,CS%num_off_iter

do k=1,nz ; do j=js,je ; do i=is,ie
Expand All @@ -302,7 +300,7 @@ subroutine offline_advection_ale(fluxes, Time_start, time_interval, CS, &
call hchksum(h_vol,"h_vol before advect",G%HI)
call uvchksum("[uv]htr_sub before advect", uhtr_sub, vhtr_sub, G%HI)
write(debug_msg, '(A,I4.4)') 'Before advect ', iter
call MOM_tracer_chksum(debug_msg, CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h_pre)
call MOM_tracer_chkinv(debug_msg, G, h_pre, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif

call advect_tracer(h_pre, uhtr_sub, vhtr_sub, CS%OBC, CS%dt_offline, G, GV, &
Expand All @@ -317,13 +315,13 @@ subroutine offline_advection_ale(fluxes, Time_start, time_interval, CS, &
h_new(i,j,k) = h_new(i,j,k)/G%areaT(i,j)
enddo ; enddo ; enddo

if (MODULO(iter,100)==0) then
if (MODULO(iter,1)==0) then
! Do ALE remapping/regridding to allow for more advection to occur in the next iteration
call pass_var(h_new,G%Domain)
if (CS%debug) then
call hchksum(h_new,"h_new before ALE",G%HI)
write(debug_msg, '(A,I4.4)') 'Before ALE ', iter
call MOM_tracer_chksum(debug_msg, CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h_new)
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%dt_offline)
Expand All @@ -332,19 +330,14 @@ subroutine offline_advection_ale(fluxes, Time_start, time_interval, CS, &
if (CS%debug) then
call hchksum(h_new,"h_new after ALE",G%HI)
write(debug_msg, '(A,I4.4)') 'After ALE ', iter
call MOM_tracer_chksum(debug_msg, CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h_new)
call MOM_tracer_chkinv(debug_msg, G, h_new, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif
else
do k=1,nz; do j=js,je ; do i=is,ie
uhtr_sub(I,j,k) = uhtr(I,j,k)
vhtr_sub(i,J,k) = vhtr(i,J,k)
enddo ; enddo ; enddo
endif

do k=1,nz; do j=js,je ; do i=is,ie
uhtr_sub(I,j,k) = uhtr(I,j,k)
vhtr_sub(i,J,k) = vhtr(i,J,k)
enddo ; enddo ; enddo
do k=1,nz; do j=js,je ; do i=is,ie
uhtr_sub(I,j,k) = uhtr(I,j,k)
vhtr_sub(i,J,k) = vhtr(i,J,k)
enddo ; enddo ; enddo
call pass_var(h_new, G%Domain)
call pass_vector(uhtr_sub,vhtr_sub,G%Domain)

Expand Down Expand Up @@ -379,7 +372,7 @@ subroutine offline_advection_ale(fluxes, Time_start, time_interval, CS, &
if (CS%debug) then
call hchksum(h_pre,"h after offline_advection_ale",G%HI)
call uvchksum("[uv]htr after offline_advection_ale", uhtr, vhtr, G%HI)
call MOM_tracer_chksum("After offline_advection_ale", CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h_pre)
call MOM_tracer_chkinv("After offline_advection_ale", G, h_pre, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif

call cpu_clock_end(CS%id_clock_offline_adv)
Expand Down Expand Up @@ -441,7 +434,7 @@ subroutine offline_redistribute_residual(CS, h_pre, uhtr, vhtr, converged, id_cl
if (converged) return

if (CS%debug) then
call MOM_tracer_chksum("Before redistribute ", CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h_pre)
call MOM_tracer_chkinv("Before redistribute ", G, h_pre, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif

call cpu_clock_begin(CS%id_clock_redistribute)
Expand Down Expand Up @@ -573,8 +566,7 @@ subroutine offline_redistribute_residual(CS, h_pre, uhtr, vhtr, converged, id_cl
if (CS%debug) then
call hchksum(h_pre,"h_pre after redistribute",G%HI)
call uvchksum("uhtr after redistribute", uhtr, vhtr, G%HI)
call MOM_tracer_chksum("after redistribute ", CS%tracer_Reg%Tr, &
CS%tracer_Reg%ntr, G)
call MOM_tracer_chkinv("after redistribute ", G, h_new, CS%tracer_Reg%Tr, CS%tracer_Reg%ntr)
endif

call cpu_clock_end(CS%id_clock_redistribute)
Expand Down Expand Up @@ -643,7 +635,7 @@ subroutine offline_diabatic_ale(fluxes, Time_start, Time_end, CS, h_pre, eatr, e
call hchksum(h_pre,"h_pre before offline_diabatic_ale",CS%G%HI)
call hchksum(eatr,"eatr before offline_diabatic_ale",CS%G%HI)
call hchksum(ebtr,"ebtr before offline_diabatic_ale",CS%G%HI)
call MOM_tracer_chksum("Before offline_diabatic_ale", CS%tracer_reg%Tr, CS%tracer_reg%ntr, CS%G, h_pre)
call MOM_tracer_chkinv("Before offline_diabatic_ale", CS%G, h_pre, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif

eatr(:,:,:) = 0.
Expand Down Expand Up @@ -706,6 +698,7 @@ subroutine offline_diabatic_ale(fluxes, Time_start, Time_end, CS, h_pre, eatr, e
call hchksum(h_pre,"h_pre after offline_diabatic_ale",CS%G%HI)
call hchksum(eatr,"eatr after offline_diabatic_ale",CS%G%HI)
call hchksum(ebtr,"ebtr after offline_diabatic_ale",CS%G%HI)
call MOM_tracer_chkinv("After offline_diabatic_ale", CS%G, h_pre, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif

call cpu_clock_end(CS%id_clock_offline_diabatic)
Expand Down Expand Up @@ -743,7 +736,7 @@ subroutine offline_fw_fluxes_into_ocean(G, GV, CS, fluxes, h, in_flux_optional)

if (CS%debug) then
call hchksum(h,"h before fluxes into ocean",G%HI)
call MOM_tracer_chksum("Before fluxes into ocean", CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h)
call MOM_tracer_chkinv("Before fluxes into ocean", G, h, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif
do m = 1,CS%tracer_reg%ntr
! Layer thicknesses should only be updated after the last tracer is finished
Expand All @@ -753,7 +746,7 @@ subroutine offline_fw_fluxes_into_ocean(G, GV, CS, fluxes, h, in_flux_optional)
enddo
if (CS%debug) then
call hchksum(h,"h after fluxes into ocean",G%HI)
call MOM_tracer_chksum("After fluxes into ocean", CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h)
call MOM_tracer_chkinv("After fluxes into ocean", G, h, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif

! Now that fluxes into the ocean are done, save the negative fluxes for later
Expand All @@ -779,7 +772,7 @@ subroutine offline_fw_fluxes_out_ocean(G, GV, CS, fluxes, h, out_flux_optional)

if (CS%debug) then
call hchksum(h,"h before fluxes out of ocean",G%HI)
call MOM_tracer_chksum("Before fluxes out of ocean", CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h)
call MOM_tracer_chkinv("Before fluxes out of ocean", G, h, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif
do m = 1, CS%tracer_reg%ntr
! Layer thicknesses should only be updated after the last tracer is finished
Expand All @@ -789,7 +782,7 @@ subroutine offline_fw_fluxes_out_ocean(G, GV, CS, fluxes, h, out_flux_optional)
enddo
if (CS%debug) then
call hchksum(h,"h after fluxes out of ocean",G%HI)
call MOM_tracer_chksum("Before fluxes out of ocean", CS%tracer_reg%Tr, CS%tracer_reg%ntr, G, h)
call MOM_tracer_chkinv("Before fluxes out of ocean", G, h, CS%tracer_reg%Tr, CS%tracer_reg%ntr)
endif

end subroutine offline_fw_fluxes_out_ocean
Expand Down Expand Up @@ -990,7 +983,8 @@ subroutine update_offline_fields(CS, h, fluxes, do_ale)
call pass_var(CS%h_start, CS%G%Domain)
call pass_var(CS%tv%T, CS%G%Domain)
call pass_var(CS%tv%S, CS%G%Domain)
call ALE_offline_inputs(CS%ALE_CSp, CS%G, CS%GV, CS%h_start, h, CS%tv, CS%tracer_Reg, CS%uhtr, CS%vhtr, CS%Kd)
call ALE_offline_inputs(CS%ALE_CSp, CS%G, CS%GV, h, CS%h_start, h, CS%tv, CS%tracer_Reg, CS%uhtr, CS%vhtr,&
CS%Kd, CS%debug)

if (CS%id_temp_regrid>0) call post_data(CS%id_temp_regrid, CS%tv%T, CS%diag, alt_h = CS%h_start)
if (CS%id_salt_regrid>0) call post_data(CS%id_salt_regrid, CS%tv%S, CS%diag, alt_h =CS%h_start)
Expand Down Expand Up @@ -1394,10 +1388,10 @@ subroutine read_all_input(CS)
if (allocated(CS%temp_all)) call MOM_error(FATAL, "temp_all is already allocated")
if (allocated(CS%salt_all)) call MOM_error(FATAL, "salt_all is already allocated")

allocate(CS%uhtr_all(IsdB:IedB,jsd:jed,nz,ntime)) ; CS%uhtr_all(:,:,:,:) = 0.0
allocate(CS%vhtr_all(isd:ied,JsdB:JedB,nz,ntime)) ; CS%vhtr_all(:,:,:,:) = 0.0
allocate(CS%uhtr_all(IsdB:IedB,jsd:jed,nz,ntime)) ; CS%uhtr_all(:,:,:,:) = 0.0
allocate(CS%vhtr_all(isd:ied,JsdB:JedB,nz,ntime)) ; CS%vhtr_all(:,:,:,:) = 0.0
allocate(CS%hstart_all(isd:ied,jsd:jed,nz,ntime)) ; CS%hend_all(:,:,:,:) = 0.0
allocate(CS%hend_all(isd:ied,jsd:jed,nz,ntime)) ; CS%hend_all(:,:,:,:) = 0.0
allocate(CS%hend_all(isd:ied,jsd:jed,nz,ntime)) ; CS%hend_all(:,:,:,:) = 0.0
allocate(CS%temp_all(isd:ied,jsd:jed,nz,1:ntime)) ; CS%temp_all(:,:,:,:) = 0.0
allocate(CS%salt_all(isd:ied,jsd:jed,nz,1:ntime)) ; CS%salt_all(:,:,:,:) = 0.0

Expand Down
51 changes: 30 additions & 21 deletions src/tracer/MOM_tracer_registry.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module MOM_tracer_registry
! This file is part of MOM6. See LICENSE.md for the license.

! use MOM_diag_mediator, only : diag_ctrl
use MOM_coms, only : reproducing_sum
use MOM_debugging, only : hchksum
use MOM_error_handler, only : MOM_error, FATAL, WARNING, MOM_mesg, is_root_pe
use MOM_file_parser, only : get_param, log_version, param_file_type
Expand All @@ -23,6 +24,7 @@ module MOM_tracer_registry
public register_tracer
public tracer_registry_init
public MOM_tracer_chksum
public MOM_tracer_chkinv
public add_tracer_diagnostics
public add_tracer_OBC_values
public lock_tracer_registry
Expand Down Expand Up @@ -246,39 +248,46 @@ subroutine add_tracer_diagnostics(name, Reg, ad_x, ad_y, df_x, df_y, &

end subroutine add_tracer_diagnostics

!> This subroutine writes out chksums for tracers. If
subroutine MOM_tracer_chksum(mesg, Tr, ntr, G, h)
!> This subroutine writes out chksums for tracers.
subroutine MOM_tracer_chksum(mesg, Tr, ntr, G)
character(len=*), intent(in) :: mesg !< message that appears on the chksum lines
type(tracer_type), intent(in) :: Tr(:) !< array of all of registered tracers
integer, intent(in) :: ntr !< number of registered tracers
type(ocean_grid_type), intent(in) :: G !< ocean grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), optional, intent(in) :: h !< Layer thicknesses, if present
!! inventories will be checksummed

integer :: is, ie, js, je, nz
integer :: i, j, k, m

real, dimension(:,:,:), allocatable :: tr_inv

is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = G%ke

! Check for presence of h if inventories are requested
if (present(h)) then
if (.not. ALLOCATED(tr_inv)) allocate(tr_inv(SZI_(G),SZJ_(G),SZK_(G)))
do m=1,ntr
do k=1,nz ; do j=js,je ; do i=is,ie
tr_inv(i,j,k) = Tr(m)%t(i,j,k) * h(i,j,k) * G%areaT(i,j) * G%mask2dT(i,j)
enddo ; enddo ; enddo
call hchksum(Tr(m)%t, mesg//trim(Tr(m)%name), G%HI)
enddo
else ! Concentrations are checksummed
do m=1,ntr
call hchksum(Tr(m)%t, mesg//trim(Tr(m)%name), G%HI)
enddo
endif
do m=1,ntr
call hchksum(Tr(m)%t, mesg//trim(Tr(m)%name), G%HI)
enddo

end subroutine MOM_tracer_chksum

!> Calculates and prints the global inventory of all tracers in the registry.
subroutine MOM_tracer_chkinv(mesg, G, h, Tr, ntr)
character(len=*), intent(in) :: mesg !< message that appears on the chksum lines
type(ocean_grid_type), intent(in) :: G !< ocean grid structure
type(tracer_type), intent(in) :: Tr(:) !< array of all of registered tracers
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses
integer, intent(in) :: ntr !< number of registered tracers

real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: tr_inv !< Tracer inventory
real :: total_inv
integer :: is, ie, js, je, nz
integer :: i, j, k, m

is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = G%ke
do m=1,ntr
do k=1,nz ; do j=js,je ; do i=is,ie
tr_inv(i,j,k) = Tr(m)%t(i,j,k)*h(i,j,k)*G%areaT(i,j)*G%mask2dT(i,j)
enddo ; enddo ; enddo
total_inv = reproducing_sum(tr_inv, is, ie, js, je)
if (is_root_pe()) write(0,'(A,1X,A5,1X,ES25.16,1X,A)') "h-point: inventory", Tr(m)%name, total_inv, mesg
enddo

end subroutine MOM_tracer_chkinv

!> This routine include declares and sets the variable "version".
subroutine tracer_registry_init(param_file, Reg)
Expand Down

0 comments on commit ff690d1

Please sign in to comment.