MOM6
mom_checksum_packages Module Reference

Detailed Description

Provides routines that do checksums of groups of MOM variables.

Data Types

interface  mom_state_chksum
 Write out checksums of the MOM6 state variables. More...
 
type  stats
 A type for storing statistica about a variable. More...
 

Functions/Subroutines

subroutine mom_state_chksum_5arg (mesg, u, v, h, uh, vh, G, GV, US, haloshift, symmetric, vel_scale)
 Write out chksums for the model's basic state variables, including transports. More...
 
subroutine mom_state_chksum_3arg (mesg, u, v, h, G, GV, US, haloshift, symmetric)
 Write out chksums for the model's basic state variables. More...
 
subroutine, public mom_thermo_chksum (mesg, tv, G, US, haloshift)
 Write out chksums for the model's thermodynamic state variables. More...
 
subroutine, public mom_surface_chksum (mesg, sfc, G, haloshift, symmetric)
 Write out chksums for the ocean surface variables. More...
 
subroutine, public mom_accel_chksum (mesg, CAu, CAv, PFu, PFv, diffu, diffv, G, GV, US, pbce, u_accel_bt, v_accel_bt, symmetric)
 Write out chksums for the model's accelerations. More...
 
subroutine, public mom_state_stats (mesg, u, v, h, Temp, Salt, G, GV, US, allowChange, permitDiminishing)
 Monitor and write out statistics for the model's state variables. More...
 

Function/Subroutine Documentation

◆ mom_accel_chksum()

subroutine, public mom_checksum_packages::mom_accel_chksum ( character(len=*), intent(in)  mesg,
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(in)  CAu,
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(in)  CAv,
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(in)  PFu,
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(in)  PFv,
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(in)  diffu,
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(in)  diffv,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
type(unit_scale_type), intent(in)  US,
real, dimension( g %isd: g %ied, g %jsd: g %jed, g %ke), intent(in), optional  pbce,
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(in), optional  u_accel_bt,
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(in), optional  v_accel_bt,
logical, intent(in), optional  symmetric 
)

Write out chksums for the model's accelerations.

Parameters
[in]mesgA message that appears on the chksum lines.
[in]gThe ocean's grid structure.
[in]gvThe ocean's vertical grid structure.
[in]cauZonal acceleration due to Coriolis
[in]cavMeridional acceleration due to Coriolis
[in]pfuZonal acceleration due to pressure gradients
[in]pfvMeridional acceleration due to pressure gradients
[in]diffuZonal acceleration due to convergence of the
[in]diffvMeridional acceleration due to convergence of
[in]usA dimensional unit scaling type
[in]pbceThe baroclinic pressure anomaly in each layer
[in]u_accel_btThe zonal acceleration from terms in the
[in]v_accel_btThe meridional acceleration from terms in
[in]symmetricIf true, do checksums on the fully symmetric computational domain.

Definition at line 175 of file MOM_checksum_packages.F90.

175  character(len=*), intent(in) :: mesg !< A message that appears on the chksum lines.
176  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
177  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
178  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
179  intent(in) :: CAu !< Zonal acceleration due to Coriolis
180  !! and momentum advection terms [L T-2 ~> m s-2].
181  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
182  intent(in) :: CAv !< Meridional acceleration due to Coriolis
183  !! and momentum advection terms [L T-2 ~> m s-2].
184  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
185  intent(in) :: PFu !< Zonal acceleration due to pressure gradients
186  !! (equal to -dM/dx) [L T-2 ~> m s-2].
187  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
188  intent(in) :: PFv !< Meridional acceleration due to pressure gradients
189  !! (equal to -dM/dy) [L T-2 ~> m s-2].
190  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
191  intent(in) :: diffu !< Zonal acceleration due to convergence of the
192  !! along-isopycnal stress tensor [L T-2 ~> m s-2].
193  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
194  intent(in) :: diffv !< Meridional acceleration due to convergence of
195  !! the along-isopycnal stress tensor [L T-2 ~> m s-2].
196  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
197  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
198  optional, intent(in) :: pbce !< The baroclinic pressure anomaly in each layer
199  !! due to free surface height anomalies
200  !! [L2 T-2 H-1 ~> m s-2 or m4 s-2 kg-1].
201  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
202  optional, intent(in) :: u_accel_bt !< The zonal acceleration from terms in the
203  !! barotropic solver [L T-2 ~> m s-2].
204  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
205  optional, intent(in) :: v_accel_bt !< The meridional acceleration from terms in
206  !! the barotropic solver [L T-2 ~> m s-2].
207  logical, optional, intent(in) :: symmetric !< If true, do checksums on the fully symmetric
208  !! computational domain.
209 
210  integer :: is, ie, js, je, nz
211  logical :: sym
212 
213  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
214  sym=.false.; if (present(symmetric)) sym=symmetric
215 
216  ! Note that for the chksum calls to be useful for reproducing across PE
217  ! counts, there must be no redundant points, so all variables use is..ie
218  ! and js...je as their extent.
219  call uvchksum(mesg//" CA[uv]", cau, cav, g%HI, haloshift=0, symmetric=sym, scale=us%L_T2_to_m_s2)
220  call uvchksum(mesg//" PF[uv]", pfu, pfv, g%HI, haloshift=0, symmetric=sym, scale=us%L_T2_to_m_s2)
221  call uvchksum(mesg//" diffu", diffu, diffv, g%HI,haloshift=0, symmetric=sym, scale=us%L_T2_to_m_s2)
222  if (present(pbce)) &
223  call hchksum(pbce, mesg//" pbce",g%HI,haloshift=0, scale=gv%m_to_H*us%L_T_to_m_s**2)
224  if (present(u_accel_bt) .and. present(v_accel_bt)) &
225  call uvchksum(mesg//" [uv]_accel_bt", u_accel_bt, v_accel_bt, g%HI,haloshift=0, symmetric=sym, &
226  scale=us%L_T2_to_m_s2)

Referenced by mom_dynamics_split_rk2::step_mom_dyn_split_rk2(), mom_dynamics_unsplit::step_mom_dyn_unsplit(), and mom_dynamics_unsplit_rk2::step_mom_dyn_unsplit_rk2().

Here is the caller graph for this function:

◆ mom_state_chksum_3arg()

subroutine mom_checksum_packages::mom_state_chksum_3arg ( character(len=*), intent(in)  mesg,
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(in)  u,
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(in)  v,
real, dimension( g %isd: g %ied, g %jsd: g %jed, g %ke), intent(in)  h,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
type(unit_scale_type), intent(in), optional  US,
integer, intent(in), optional  haloshift,
logical, intent(in), optional  symmetric 
)
private

Write out chksums for the model's basic state variables.

Parameters
[in]mesgA message that appears on the chksum lines.
[in]gThe ocean's grid structure.
[in]gvThe ocean's vertical grid structure.
[in]uZonal velocity [L T-1 ~> m s-1] or [m s-1].
[in]vMeridional velocity [L T-1 ~> m s-1] or [m s-1]..
[in]hLayer thicknesses [H ~> m or kg m-2].
[in]usA dimensional unit scaling type, which is used to rescale u and v if present.
[in]haloshiftThe width of halos to check (default 0).
[in]symmetricIf true, do checksums on the fully symmetric computational domain.

Definition at line 87 of file MOM_checksum_packages.F90.

87  character(len=*), intent(in) :: mesg !< A message that appears on the chksum lines.
88  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
89  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
90  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
91  intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1] or [m s-1].
92  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
93  intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1] or [m s-1]..
94  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
95  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2].
96  type(unit_scale_type), optional, intent(in) :: US !< A dimensional unit scaling type, which is
97  !! used to rescale u and v if present.
98  integer, optional, intent(in) :: haloshift !< The width of halos to check (default 0).
99  logical, optional, intent(in) :: symmetric !< If true, do checksums on the fully
100  !! symmetric computational domain.
101  real :: L_T_to_m_s ! A rescaling factor for velocities [m T s-1 L-1 ~> nondim] or [nondim]
102  integer :: is, ie, js, je, nz, hs
103  logical :: sym
104 
105  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
106  l_t_to_m_s = 1.0 ; if (present(us)) l_t_to_m_s = us%L_T_to_m_s
107 
108  ! Note that for the chksum calls to be useful for reproducing across PE
109  ! counts, there must be no redundant points, so all variables use is..ie
110  ! and js...je as their extent.
111  hs=1; if (present(haloshift)) hs=haloshift
112  sym=.false.; if (present(symmetric)) sym=symmetric
113  call uvchksum(mesg//" u", u, v, g%HI, haloshift=hs, symmetric=sym, scale=l_t_to_m_s)
114  call hchksum(h, mesg//" h",g%HI, haloshift=hs, scale=gv%H_to_m)

◆ mom_state_chksum_5arg()

subroutine mom_checksum_packages::mom_state_chksum_5arg ( character(len=*), intent(in)  mesg,
real, dimension(szib_(g),szj_(g),szk_(g)), intent(in)  u,
real, dimension(szi_(g),szjb_(g),szk_(g)), intent(in)  v,
real, dimension(szi_(g),szj_(g),szk_(g)), intent(in)  h,
real, dimension(szib_(g),szj_(g),szk_(g)), intent(in)  uh,
real, dimension(szi_(g),szjb_(g),szk_(g)), intent(in)  vh,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
type(unit_scale_type), intent(in)  US,
integer, intent(in), optional  haloshift,
logical, intent(in), optional  symmetric,
real, intent(in), optional  vel_scale 
)
private

Write out chksums for the model's basic state variables, including transports.

Parameters
[in]mesgA message that appears on the chksum lines.
[in]gThe ocean's grid structure.
[in]gvThe ocean's vertical grid structure.
[in]uThe zonal velocity [L T-1 ~> m s-1] or other units.
[in]vThe meridional velocity [L T-1 ~> m s-1] or other units.
[in]hLayer thicknesses [H ~> m or kg m-2].
[in]uhVolume flux through zonal faces = u*h*dy
[in]vhVolume flux through meridional faces = v*h*dx
[in]usA dimensional unit scaling type
[in]haloshiftThe width of halos to check (default 0).
[in]symmetricIf true, do checksums on the fully symmetric computational domain.
[in]vel_scaleThe scaling factor to convert velocities to [m s-1]

Definition at line 43 of file MOM_checksum_packages.F90.

43  character(len=*), &
44  intent(in) :: mesg !< A message that appears on the chksum lines.
45  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
46  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
47  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
48  intent(in) :: u !< The zonal velocity [L T-1 ~> m s-1] or other units.
49  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
50  intent(in) :: v !< The meridional velocity [L T-1 ~> m s-1] or other units.
51  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
52  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2].
53  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
54  intent(in) :: uh !< Volume flux through zonal faces = u*h*dy
55  !! [H L2 T-1 ~> m3 s-1 or kg s-1].
56  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
57  intent(in) :: vh !< Volume flux through meridional faces = v*h*dx
58  !! [H L2 T-1 ~> m3 s-1 or kg s-1].
59  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
60  integer, optional, intent(in) :: haloshift !< The width of halos to check (default 0).
61  logical, optional, intent(in) :: symmetric !< If true, do checksums on the fully symmetric
62  !! computational domain.
63  real, optional, intent(in) :: vel_scale !< The scaling factor to convert velocities to [m s-1]
64 
65  real :: scale_vel ! The scaling factor to convert velocities to [m s-1]
66  logical :: sym
67  integer :: is, ie, js, je, nz, hs
68  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
69 
70  ! Note that for the chksum calls to be useful for reproducing across PE
71  ! counts, there must be no redundant points, so all variables use is..ie
72  ! and js...je as their extent.
73  hs = 1 ; if (present(haloshift)) hs=haloshift
74  sym = .false. ; if (present(symmetric)) sym=symmetric
75  scale_vel = us%L_T_to_m_s ; if (present(vel_scale)) scale_vel = vel_scale
76 
77  call uvchksum(mesg//" [uv]", u, v, g%HI, haloshift=hs, symmetric=sym, scale=scale_vel)
78  call hchksum(h, mesg//" h", g%HI, haloshift=hs, scale=gv%H_to_m)
79  call uvchksum(mesg//" [uv]h", uh, vh, g%HI, haloshift=hs, &
80  symmetric=sym, scale=gv%H_to_m*us%L_to_m**2*us%s_to_T)

◆ mom_state_stats()

subroutine, public mom_checksum_packages::mom_state_stats ( character(len=*), intent(in)  mesg,
real, dimension(szib_(g),szj_(g),szk_(g)), intent(in)  u,
real, dimension(szi_(g),szjb_(g),szk_(g)), intent(in)  v,
real, dimension(szi_(g),szj_(g),szk_(g)), intent(in)  h,
real, dimension(:,:,:), intent(in), pointer  Temp,
real, dimension(:,:,:), intent(in), pointer  Salt,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
type(unit_scale_type), intent(in)  US,
logical, intent(in), optional  allowChange,
logical, intent(in), optional  permitDiminishing 
)

Monitor and write out statistics for the model's state variables.

Parameters
[in]gThe ocean's grid structure.
[in]gvThe ocean's vertical grid structure.
[in]mesgA message that appears on the chksum lines.
[in]uThe zonal velocity [L T-1 ~> m s-1].
[in]vThe meridional velocity [L T-1 ~> m s-1].
[in]hLayer thicknesses [H ~> m or kg m-2].
[in]tempTemperature [degC].
[in]saltSalinity [ppt].
[in]usA dimensional unit scaling type
[in]allowchangedo not flag an error if the statistics change.
[in]permitdiminishingdo not flag error if the extrema are diminishing.

Definition at line 233 of file MOM_checksum_packages.F90.

233  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
234  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
235  character(len=*), intent(in) :: mesg !< A message that appears on the chksum lines.
236  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
237  intent(in) :: u !< The zonal velocity [L T-1 ~> m s-1].
238  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
239  intent(in) :: v !< The meridional velocity [L T-1 ~> m s-1].
240  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
241  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2].
242  real, pointer, dimension(:,:,:), &
243  intent(in) :: Temp !< Temperature [degC].
244  real, pointer, dimension(:,:,:), &
245  intent(in) :: Salt !< Salinity [ppt].
246  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
247  logical, optional, intent(in) :: allowChange !< do not flag an error
248  !! if the statistics change.
249  logical, optional, intent(in) :: permitDiminishing !< do not flag error if the
250  !! extrema are diminishing.
251 
252  ! Local variables
253  real :: Vol, dV ! The total ocean volume and its change [m3] (unscaled to permit reproducing sum).
254  real :: Area ! The total ocean surface area [m2] (unscaled to permit reproducing sum).
255  real :: h_minimum ! The minimum layer thicknesses [H ~> m or kg m-2]
256  logical :: do_TS ! If true, evaluate statistics for temperature and salinity
257  type(stats) :: T, S, delT, delS
258 
259  ! NOTE: save data is not normally allowed but we use it for debugging purposes here on the
260  ! assumption we will not turn this on with threads
261  type(stats), save :: oldT, oldS
262  logical, save :: firstCall = .true.
263  real, save :: oldVol ! The previous total ocean volume [m3]
264 
265  character(len=80) :: lMsg
266  integer :: is, ie, js, je, nz, i, j, k
267 
268  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
269  do_ts = associated(temp) .and. associated(salt)
270 
271  ! First collect local stats
272  area = 0. ; vol = 0.
273  do j = js, je ; do i = is, ie
274  area = area + us%L_to_m**2*g%areaT(i,j)
275  enddo ; enddo
276  t%minimum = 1.e34 ; t%maximum = -1.e34 ; t%average = 0.
277  s%minimum = 1.e34 ; s%maximum = -1.e34 ; s%average = 0.
278  h_minimum = 1.e34*gv%m_to_H
279  do k = 1, nz ; do j = js, je ; do i = is, ie
280  if (g%mask2dT(i,j)>0.) then
281  dv = us%L_to_m**2*g%areaT(i,j)*gv%H_to_m*h(i,j,k) ; vol = vol + dv
282  if (do_ts .and. h(i,j,k)>0.) then
283  t%minimum = min( t%minimum, temp(i,j,k) ) ; t%maximum = max( t%maximum, temp(i,j,k) )
284  t%average = t%average + dv*temp(i,j,k)
285  s%minimum = min( s%minimum, salt(i,j,k) ) ; s%maximum = max( s%maximum, salt(i,j,k) )
286  s%average = s%average + dv*salt(i,j,k)
287  endif
288  if (h_minimum > h(i,j,k)) h_minimum = h(i,j,k)
289  endif
290  enddo ; enddo ; enddo
291  call sum_across_pes( area ) ; call sum_across_pes( vol )
292  if (do_ts) then
293  call min_across_pes( t%minimum ) ; call max_across_pes( t%maximum ) ; call sum_across_pes( t%average )
294  call min_across_pes( s%minimum ) ; call max_across_pes( s%maximum ) ; call sum_across_pes( s%average )
295  t%average = t%average / vol ; s%average = s%average / vol
296  endif
297  if (is_root_pe()) then
298  if (.not.firstcall) then
299  dv = vol - oldvol
300  delt%minimum = t%minimum - oldt%minimum ; delt%maximum = t%maximum - oldt%maximum
301  delt%average = t%average - oldt%average
302  dels%minimum = s%minimum - olds%minimum ; dels%maximum = s%maximum - olds%maximum
303  dels%average = s%average - olds%average
304  write(lmsg(1:80),'(2(a,es12.4))') 'Mean thickness =', vol/area,' frac. delta=',dv/vol
305  call mom_mesg(lmsg//trim(mesg))
306  if (do_ts) then
307  write(lmsg(1:80),'(a,3es12.4)') 'Temp min/mean/max =',t%minimum,t%average,t%maximum
308  call mom_mesg(lmsg//trim(mesg))
309  write(lmsg(1:80),'(a,3es12.4)') 'delT min/mean/max =',delt%minimum,delt%average,delt%maximum
310  call mom_mesg(lmsg//trim(mesg))
311  write(lmsg(1:80),'(a,3es12.4)') 'Salt min/mean/max =',s%minimum,s%average,s%maximum
312  call mom_mesg(lmsg//trim(mesg))
313  write(lmsg(1:80),'(a,3es12.4)') 'delS min/mean/max =',dels%minimum,dels%average,dels%maximum
314  call mom_mesg(lmsg//trim(mesg))
315  endif
316  else
317  write(lmsg(1:80),'(a,es12.4)') 'Mean thickness =', vol/area
318  call mom_mesg(lmsg//trim(mesg))
319  if (do_ts) then
320  write(lmsg(1:80),'(a,3es12.4)') 'Temp min/mean/max =', t%minimum, t%average, t%maximum
321  call mom_mesg(lmsg//trim(mesg))
322  write(lmsg(1:80),'(a,3es12.4)') 'Salt min/mean/max =', s%minimum, s%average, s%maximum
323  call mom_mesg(lmsg//trim(mesg))
324  endif
325  endif
326  endif
327  firstcall = .false. ; oldvol = vol
328  oldt%minimum = t%minimum ; oldt%maximum = t%maximum ; oldt%average = t%average
329  olds%minimum = s%minimum ; olds%maximum = s%maximum ; olds%average = s%average
330 
331  if (do_ts .and. t%minimum<-5.0) then
332  do j = js, je ; do i = is, ie
333  if (minval(temp(i,j,:)) == t%minimum) then
334  write(0,'(a,2f12.5)') 'x,y=', g%geoLonT(i,j), g%geoLatT(i,j)
335  write(0,'(a3,3a12)') 'k','h','Temp','Salt'
336  do k = 1, nz
337  write(0,'(i3,3es12.4)') k, h(i,j,k), temp(i,j,k), salt(i,j,k)
338  enddo
339  stop 'Extremum detected'
340  endif
341  enddo ; enddo
342  endif
343 
344  if (h_minimum<0.0) then
345  do j = js, je ; do i = is, ie
346  if (minval(h(i,j,:)) == h_minimum) then
347  write(0,'(a,2f12.5)') 'x,y=',g%geoLonT(i,j),g%geoLatT(i,j)
348  write(0,'(a3,3a12)') 'k','h','Temp','Salt'
349  do k = 1, nz
350  write(0,'(i3,3es12.4)') k, h(i,j,k), temp(i,j,k), salt(i,j,k)
351  enddo
352  stop 'Negative thickness detected'
353  endif
354  enddo ; enddo
355  endif
356 

References mom_error_handler::is_root_pe(), and mom_error_handler::mom_mesg().

Referenced by mom_diabatic_driver::diabatic(), mom_diabatic_driver::diabatic_ale(), mom_diabatic_driver::diabatic_ale_legacy(), and mom_diabatic_driver::layered_diabatic().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ mom_surface_chksum()

subroutine, public mom_checksum_packages::mom_surface_chksum ( character(len=*), intent(in)  mesg,
type(surface), intent(inout)  sfc,
type(ocean_grid_type), intent(in)  G,
integer, intent(in), optional  haloshift,
logical, intent(in), optional  symmetric 
)

Write out chksums for the ocean surface variables.

Parameters
[in]mesgA message that appears on the chksum lines.
[in,out]sfctransparent ocean surface state structure shared with the calling routine data in this structure is intent out.
[in]gThe ocean's grid structure.
[in]haloshiftThe width of halos to check (default 0).
[in]symmetricIf true, do checksums on the fully symmetric computational domain.

Definition at line 144 of file MOM_checksum_packages.F90.

144  character(len=*), intent(in) :: mesg !< A message that appears on the chksum lines.
145  type(surface), intent(inout) :: sfc !< transparent ocean surface state
146  !! structure shared with the calling routine
147  !! data in this structure is intent out.
148  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
149  integer, optional, intent(in) :: haloshift !< The width of halos to check (default 0).
150  logical, optional, intent(in) :: symmetric !< If true, do checksums on the fully symmetric
151  !! computational domain.
152 
153  integer :: hs
154  logical :: sym
155 
156  sym = .false. ; if (present(symmetric)) sym = symmetric
157  hs = 1 ; if (present(haloshift)) hs = haloshift
158 
159  if (allocated(sfc%SST)) call hchksum(sfc%SST, mesg//" SST",g%HI,haloshift=hs)
160  if (allocated(sfc%SSS)) call hchksum(sfc%SSS, mesg//" SSS",g%HI,haloshift=hs)
161  if (allocated(sfc%sea_lev)) call hchksum(sfc%sea_lev, mesg//" sea_lev",g%HI,haloshift=hs)
162  if (allocated(sfc%Hml)) call hchksum(sfc%Hml, mesg//" Hml",g%HI,haloshift=hs)
163  if (allocated(sfc%u) .and. allocated(sfc%v)) &
164  call uvchksum(mesg//" SSU", sfc%u, sfc%v, g%HI, haloshift=hs, symmetric=sym)
165 ! if (allocated(sfc%salt_deficit)) call hchksum(sfc%salt_deficit, mesg//" salt deficit",G%HI,haloshift=hs)
166  if (associated(sfc%frazil)) call hchksum(sfc%frazil, mesg//" frazil",g%HI,haloshift=hs)
167 

Referenced by mom::extract_surface_state().

Here is the caller graph for this function:

◆ mom_thermo_chksum()

subroutine, public mom_checksum_packages::mom_thermo_chksum ( character(len=*), intent(in)  mesg,
type(thermo_var_ptrs), intent(in)  tv,
type(ocean_grid_type), intent(in)  G,
type(unit_scale_type), intent(in)  US,
integer, intent(in), optional  haloshift 
)

Write out chksums for the model's thermodynamic state variables.

Parameters
[in]mesgA message that appears on the chksum lines.
[in]tvA structure pointing to various thermodynamic variables.
[in]gThe ocean's grid structure.
[in]usA dimensional unit scaling type
[in]haloshiftThe width of halos to check (default 0).

Definition at line 121 of file MOM_checksum_packages.F90.

121  character(len=*), intent(in) :: mesg !< A message that appears on the chksum lines.
122  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various
123  !! thermodynamic variables.
124  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
125  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
126  integer, optional, intent(in) :: haloshift !< The width of halos to check (default 0).
127 
128  integer :: is, ie, js, je, nz, hs
129  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
130  hs=1; if (present(haloshift)) hs=haloshift
131 
132  if (associated(tv%T)) call hchksum(tv%T, mesg//" T",g%HI,haloshift=hs)
133  if (associated(tv%S)) call hchksum(tv%S, mesg//" S",g%HI,haloshift=hs)
134  if (associated(tv%frazil)) call hchksum(tv%frazil, mesg//" frazil",g%HI,haloshift=hs)
135  if (associated(tv%salt_deficit)) &
136  call hchksum(tv%salt_deficit, mesg//" salt deficit",g%HI,haloshift=hs, scale=us%R_to_kg_m3*us%Z_to_m)
137