MOM6
MOM_PointAccel.F90
Go to the documentation of this file.
2 !***********************************************************************
3 !* GNU General Public License *
4 !* This file is a part of MOM. *
5 !* *
6 !* MOM is free software; you can redistribute it and/or modify it and *
7 !* are expected to follow the terms of the GNU General Public License *
8 !* as published by the Free Software Foundation; either version 2 of *
9 !* the License, or (at your option) any later version. *
10 !* *
11 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
13 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
14 !* License for more details. *
15 !* *
16 !* For the full text of the GNU General Public License, *
17 !* write to: Free Software Foundation, Inc., *
18 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
19 !* or see: http://www.gnu.org/licenses/gpl.html *
20 !***********************************************************************
21 
22 !***********************************************************************
23 !* *
24 !* The two subroutines in this file write out all of the terms *
25 !* in the u- or v-momentum balance at a given point. Usually *
26 !* these subroutines are called after the velocities exceed some *
27 !* threshold, in order to determine which term is culpable. *
28 !* often this is done for debugging purposes. *
29 !* *
30 !* Macros written all in capital letters are defined in MOM_memory.h *
31 !* *
32 !* A small fragment of the grid is shown below: *
33 !* *
34 !* j+1 x ^ x ^ x At x: q, CoriolisBu *
35 !* j+1 > o > o > At ^: v, PFv, CAv, vh, diffv, vbt, vhtr *
36 !* j x ^ x ^ x At >: u, PFu, CAu, uh, diffu, ubt, uhtr *
37 !* j > o > o > At o: h, bathyT, tr, T, S *
38 !* j-1 x ^ x ^ x *
39 !* i-1 i i+1 At x & ^: *
40 !* i i+1 At > & o: *
41 !* *
42 !* The boundaries always run through q grid points (x). *
43 !* *
44 !********+*********+*********+*********+*********+*********+*********+**
45 
46 use mom_diag_mediator, only : diag_ctrl
47 use mom_domains, only : pe_here
48 use mom_error_handler, only : mom_error, note
50 use mom_get_input, only : directories
51 use mom_grid, only : ocean_grid_type
52 use mom_io, only : open_file
53 use mom_io, only : append_file, ascii_file, multiple, single_file
54 use mom_time_manager, only : time_type, get_time, get_date, set_date, operator(-)
57 
58 implicit none ; private
59 
60 #include <MOM_memory.h>
61 
63 
64 type, public :: pointaccel_cs ; private
65  character(len=200) :: u_trunc_file ! The complete path to files in which a
66  character(len=200) :: v_trunc_file ! column's worth of accelerations are
67  ! written if velocity truncations occur.
68  integer :: u_file, v_file ! The unit numbers for opened u- or v- truncation
69  ! files, or -1 if they have not yet been opened.
70  integer :: cols_written ! The number of columns whose output has been
71  ! written by this PE during the current run.
72  integer :: max_writes ! The maximum number of times any PE can write out
73  ! a column's worth of accelerations during a run.
74  type(time_type), pointer :: time ! A pointer to the ocean model's clock.
75  type(diag_ctrl), pointer :: diag ! A pointer to a structure of shareable
76  ! ocean diagnostic fields.
77 ! The following are pointers to many of the state variables and accelerations
78 ! that are used to step the physical model forward. They all use the same
79 ! names as the variables they point to in MOM.F90
80  real, pointer, dimension(:,:,:) :: &
81  u_av => null(), v_av => null(), & ! Time average velocities in m s-1.
82  u_prev => null(), v_prev => null(), & ! Previous velocities in m s-1.
83  t => null(), s => null(), & ! Temperature and salinity in C and psu.
84  pbce => null(), & ! pbce times eta gives the baroclinic
85  ! pressure anomaly in each layer due to
86  ! free surface height anomalies.
87  ! pbce has units of m s-2.
88  u_accel_bt => null(), & ! Barotropic acclerations in m s-2.
89  v_accel_bt => null()
90 
91 end type pointaccel_cs
92 
93 contains
94 
95 !> This subroutine writes to an output file all of the accelerations
96 !! that have been applied to a column of zonal velocities over the
97 !! previous timestep. This subroutine is called from vertvisc.
98 subroutine write_u_accel(I, j, um, hin, ADp, CDp, dt, G, GV, CS, &
99  maxvel, minvel, str, a, hv)
100  integer, intent(in) :: I !< The zonal index of the column to be documented.
101  integer, intent(in) :: j !< The meridional index of the column to be
102  !! documented.
103  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
104  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
105  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
106  intent(in) :: um !< The new zonal velocity, in m s-1.
107  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
108  intent(in) :: hin !< The layer thickness, in m.
109  type(accel_diag_ptrs), intent(in) :: ADp !< A structure pointing to the various
110  !! accelerations in the momentum equations.
111  type(cont_diag_ptrs), intent(in) :: CDp !< A structure with pointers to various terms
112  !! in the continuity equations.
113  real, intent(in) :: dt !< The ocean dynamics time step, in s.
114  type(pointaccel_cs), pointer :: CS !< The control structure returned by a previous
115  !! call to PointAccel_init.
116  real, intent(in) :: maxvel, minvel
117  real, optional, intent(in) :: str !< The surface wind stress integrated over a time
118  !! step, in m2 s-1.
119  real, dimension(SZIB_(G),SZK_(G)), &
120  optional, intent(in) :: a !< The layer coupling coefficients from
121  !! vertvisc, m.
122  real, dimension(SZIB_(G),SZK_(G)), &
123  optional, intent(in) :: hv !< The layer thicknesses at velocity grid points,
124  !! from vertvisc, in m.
125 
126 ! This subroutine writes to an output file all of the accelerations
127 ! that have been applied to a column of zonal velocities over the
128 ! previous timestep. This subroutine is called from vertvisc.
129 
130 ! Arguments: I - The zonal index of the column to be documented.
131 ! (in) j - The meridional index of the column to be documented.
132 ! (in) um - The new zonal velocity, in m s-1.
133 ! (in) hin - The layer thickness, in m.
134 ! (in) ADp - A structure pointing to the various accelerations in
135 ! the momentum equations.
136 ! (in) CDp - A structure with pointers to various terms in the continuity
137 ! equations.
138 ! (in) dt - The model's dynamics time step.
139 ! (in) G - The ocean's grid structure.
140 ! (in) GV - The ocean's vertical grid structure.
141 ! (in) CS - The control structure returned by a previous call to
142 ! PointAccel_init.
143 ! (in) str - The surface wind stress integrated over a time
144 ! step, in m2 s-1.
145 ! (in) a - The layer coupling coefficients from vertvisc, m.
146 ! (in) hv - The layer thicknesses at velocity grid points, from
147 ! vertvisc, in m.
148 
149  real :: f_eff, CFL
150  real :: Angstrom
151  real :: truncvel, du
152  real :: Inorm(szk_(g))
153  real :: e(szk_(g)+1)
154  integer :: yr, mo, day, hr, minute, sec, yearday
155  integer :: k, ks, ke
156  integer :: nz
157  logical :: do_k(szk_(g)+1)
158  logical :: prev_avail
159  integer :: file
160 
161  angstrom = gv%Angstrom + gv%H_subroundoff
162 
163 ! if (.not.associated(CS)) return
164  nz = g%ke
165  if (cs%cols_written < cs%max_writes) then
166  cs%cols_written = cs%cols_written + 1
167 
168  ks = 1 ; ke = nz
169  do_k(:) = .false.
170 
171  ! Open up the file for output if this is the first call.
172  if (cs%u_file < 0) then
173  if (len_trim(cs%u_trunc_file) < 1) return
174  call open_file(cs%u_file, trim(cs%u_trunc_file), action=append_file, &
175  form=ascii_file, threading=multiple, fileset=single_file)
176  if (cs%u_file < 0) then
177  call mom_error(note, 'Unable to open file '//trim(cs%u_trunc_file)//'.')
178  return
179  endif
180  endif
181  file = cs%u_file
182 
183  prev_avail = (associated(cs%u_prev) .and. associated(cs%v_prev))
184 
185  ! Determine which layers to write out accelerations for.
186  do k=1,nz
187  if (((max(cs%u_av(i,j,k),um(i,j,k)) >= maxvel) .or. &
188  (min(cs%u_av(i,j,k),um(i,j,k)) <= minvel)) .and. &
189  ((hin(i,j,k) + hin(i+1,j,k)) > 3.0*angstrom)) exit
190  enddo
191  ks = k
192  do k=nz,1,-1
193  if (((max(cs%u_av(i,j,k), um(i,j,k)) >= maxvel) .or. &
194  (min(cs%u_av(i,j,k), um(i,j,k)) <= minvel)) .and. &
195  ((hin(i,j,k) + hin(i+1,j,k)) > 3.0*angstrom)) exit
196  enddo
197  ke = k
198  if (ke < ks) then
199  ks = 1; ke = nz; write(file,'("U: Unable to set ks & ke.")')
200  endif
201 
202  call get_date(cs%Time, yr, mo, day, hr, minute, sec)
203  call get_time((cs%Time - set_date(yr, 1, 1, 0, 0, 0)), sec, yearday)
204  write (file,'(/,"--------------------------")')
205  write (file,'(/,"Time ",i5,i4,F6.2," U-velocity violation at ",I4,": ",2(I3), &
206  & " (",F7.2," E "F7.2," N) Layers ",I3," to ",I3,". dt = ",1PG10.4)') &
207  yr, yearday, (REAL(sec)/3600.0), pe_here(), i, j, &
208  G%geoLonCu(i,j), G%geoLatCu(i,j), ks, ke, dt
209 
210  if (ks <= gv%nk_rho_varies) ks = 1
211  do k=ks,ke
212  if ((hin(i,j,k) + hin(i+1,j,k)) > 3.0*angstrom) do_k(k) = .true.
213  enddo
214 
215  write(file,'(/,"Layers:",$)')
216  do k=ks,ke ; if (do_k(k)) write(file,'(I10," ",$)') (k); enddo
217  write(file,'(/,"u(m): ",$)')
218  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (um(i,j,k)); enddo
219  if (prev_avail) then
220  write(file,'(/,"u(mp): ",$)')
221  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (cs%u_prev(i,j,k)); enddo
222  endif
223  write(file,'(/,"u(3): ",$)')
224  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (cs%u_av(i,j,k)); enddo
225 
226  write(file,'(/,"CFL u: ",$)')
227  do k=ks,ke ; if (do_k(k)) then
228  cfl = abs(um(i,j,k)) * dt * g%dy_Cu(i,j)
229  if (um(i,j,k) < 0.0) then ; cfl = cfl * g%IareaT(i+1,j)
230  else ; cfl = cfl * g%IareaT(i,j) ; endif
231  write(file,'(ES10.3," ",$)') cfl
232  endif ; enddo
233  write(file,'(/,"CFL0 u:",$)')
234  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
235  abs(um(i,j,k)) * dt * g%IdxCu(i,j) ; enddo
236 
237  if (prev_avail) then
238  write(file,'(/,"du: ",$)')
239  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
240  ((um(i,j,k)-cs%u_prev(i,j,k))); enddo
241  endif
242  write(file,'(/,"CAu: ",$)')
243  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (dt*adp%CAu(i,j,k)); enddo
244  write(file,'(/,"PFu: ",$)')
245  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (dt*adp%PFu(i,j,k)); enddo
246  write(file,'(/,"diffu: ",$)')
247  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (dt*adp%diffu(i,j,k)); enddo
248 
249  if (ASSOCIATED(adp%gradKEu)) then
250  write(file,'(/,"KEu: ",$)')
251  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
252  (dt*adp%gradKEu(i,j,k)); enddo
253  endif
254  if (ASSOCIATED(adp%rv_x_v)) then
255  write(file,'(/,"Coru: ",$)')
256  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
257  dt*(adp%CAu(i,j,k)-adp%rv_x_v(i,j,k)); enddo
258  endif
259  if (ASSOCIATED(adp%du_dt_visc)) then
260  write(file,'(/,"ubv: ",$)')
261  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
262  (um(i,j,k)-dt*adp%du_dt_visc(i,j,k)); enddo
263  write(file,'(/,"duv: ",$)')
264  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
265  (dt*adp%du_dt_visc(i,j,k)); enddo
266  endif
267  if (ASSOCIATED(adp%du_other)) then
268  write(file,'(/,"du_other: ",$)')
269  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
270  (adp%du_other(i,j,k)); enddo
271  endif
272  if (present(a)) then
273  write(file,'(/,"a: ",$)')
274  do k=ks,ke+1 ; if (do_k(k)) write(file,'(ES10.3," ",$)') a(i,k); enddo
275  endif
276  if (present(hv)) then
277  write(file,'(/,"hvel: ",$)')
278  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') hv(i,k); enddo
279  endif
280  write(file,'(/,"Stress: ",ES10.3)') str
281 
282  if (ASSOCIATED(cs%u_accel_bt)) then
283  write(file,'("dubt: ",$)')
284  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
285  (dt*cs%u_accel_bt(i,j,k)) ; enddo
286  write(file,'(/)')
287  endif
288 
289  write(file,'(/,"h--: ",$)')
290  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (hin(i,j-1,k)); enddo
291  write(file,'(/,"h+-: ",$)')
292  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (hin(i+1,j-1,k)); enddo
293  write(file,'(/,"h-0: ",$)')
294  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (hin(i,j,k)); enddo
295  write(file,'(/,"h+0: ",$)')
296  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (hin(i+1,j,k)); enddo
297  write(file,'(/,"h-+: ",$)')
298  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (hin(i,j+1,k)); enddo
299  write(file,'(/,"h++: ",$)')
300  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (hin(i+1,j+1,k)); enddo
301 
302 
303  e(nz+1) = -g%bathyT(i,j)
304  do k=nz,1,-1 ; e(k) = e(k+1) + hin(i,j,k) ; enddo
305  write(file,'(/,"e-: ",$)')
306  write(file,'(ES10.3," ",$)') e(ks)
307  do k=ks+1,ke+1 ; if (do_k(k-1)) write(file,'(ES10.3," ",$)') e(k); enddo
308 
309  e(nz+1) = -g%bathyT(i+1,j)
310  do k=nz,1,-1 ; e(k) = e(k+1) + hin(i+1,j,k) ; enddo
311  write(file,'(/,"e+: ",$)')
312  write(file,'(ES10.3," ",$)') e(ks)
313  do k=ks+1,ke+1 ; if (do_k(k-1)) write(file,'(ES10.3," ",$)') e(k) ; enddo
314  if (ASSOCIATED(cs%T)) then
315  write(file,'(/,"T-: ",$)')
316  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%T(i,j,k); enddo
317  write(file,'(/,"T+: ",$)')
318  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%T(i+1,j,k); enddo
319  endif
320  if (ASSOCIATED(cs%S)) then
321  write(file,'(/,"S-: ",$)')
322  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%S(i,j,k); enddo
323  write(file,'(/,"S+: ",$)')
324  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%S(i+1,j,k); enddo
325  endif
326 
327  if (prev_avail) then
328  write(file,'(/,"v--: ",$)')
329  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (cs%v_prev(i,j-1,k)); enddo
330  write(file,'(/,"v-+: ",$)')
331  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (cs%v_prev(i,j,k)); enddo
332  write(file,'(/,"v+-: ",$)')
333  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (cs%v_prev(i+1,j-1,k)); enddo
334  write(file,'(/,"v++: ",$)')
335  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (cs%v_prev(i+1,j,k)); enddo
336  endif
337 
338  write(file,'(/,"vh--: ",$)')
339  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
340  (cdp%vh(i,j-1,k)*g%IdxCv(i,j-1)); enddo
341  write(file,'(/," vhC--:",$)')
342  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
343  (0.5*cs%v_av(i,j-1,k)*(hin(i,j-1,k) + hin(i,j,k))); enddo
344  if (prev_avail) then
345  write(file,'(/," vhCp--:",$)')
346  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
347  (0.5*cs%v_prev(i,j-1,k)*(hin(i,j-1,k) + hin(i,j,k))); enddo
348  endif
349 
350  write(file,'(/,"vh-+: ",$)')
351  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
352  (cdp%vh(i,j,k)*g%IdxCv(i,j)); enddo
353  write(file,'(/," vhC-+:",$)')
354  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
355  (0.5*cs%v_av(i,j,k)*(hin(i,j,k) + hin(i,j+1,k))); enddo
356  if (prev_avail) then
357  write(file,'(/," vhCp-+:",$)')
358  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
359  (0.5*cs%v_prev(i,j,k)*(hin(i,j,k) + hin(i,j+1,k))); enddo
360  endif
361 
362  write(file,'(/,"vh+-: ",$)')
363  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
364  (cdp%vh(i+1,j-1,k)*g%IdxCv(i+1,j-1)); enddo
365  write(file,'(/," vhC+-:",$)')
366  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
367  (0.5*cs%v_av(i+1,j-1,k)*(hin(i+1,j-1,k) + hin(i+1,j,k))); enddo
368  if (prev_avail) then
369  write(file,'(/," vhCp+-:",$)')
370  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
371  (0.5*cs%v_prev(i+1,j-1,k)*(hin(i+1,j-1,k) + hin(i+1,j,k))); enddo
372  endif
373 
374  write(file,'(/,"vh++: ",$)')
375  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
376  (cdp%vh(i+1,j,k)*g%IdxCv(i+1,j)); enddo
377  write(file,'(/," vhC++:",$)')
378  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
379  (0.5*cs%v_av(i+1,j,k)*(hin(i+1,j,k) + hin(i+1,j+1,k))); enddo
380  if (prev_avail) then
381  write(file,'(/," vhCp++:",$)')
382  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
383  (0.5*cs%v_av(i+1,j,k)*(hin(i+1,j,k) + hin(i+1,j+1,k))); enddo
384  endif
385 
386  write(file,'(/,"D: ",2(ES10.3))') g%bathyT(i,j),g%bathyT(i+1,j)
387 
388  ! From here on, the normalized accelerations are written.
389  if (prev_avail) then
390  do k=ks,ke
391  du = um(i,j,k)-cs%u_prev(i,j,k)
392  if (abs(du) < 1.0e-6) du = 1.0e-6
393  inorm(k) = 1.0 / du
394  enddo
395 
396  write(file,'(2/,"Norm: ",$)')
397  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') (1.0/inorm(k)); enddo
398 
399  write(file,'(/,"du: ",$)')
400  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
401  ((um(i,j,k)-cs%u_prev(i,j,k))*inorm(k)); enddo
402 
403  write(file,'(/,"CAu: ",$)')
404  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
405  (dt*adp%CAu(i,j,k)*inorm(k)); enddo
406 
407  write(file,'(/,"PFu: ",$)')
408  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
409  (dt*adp%PFu(i,j,k)*inorm(k)); enddo
410 
411  write(file,'(/,"diffu: ",$)')
412  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
413  (dt*adp%diffu(i,j,k)*inorm(k)); enddo
414 
415  if (ASSOCIATED(adp%gradKEu)) then
416  write(file,'(/,"KEu: ",$)')
417  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
418  (dt*adp%gradKEu(i,j,k)*inorm(k)); enddo
419  endif
420  if (ASSOCIATED(adp%rv_x_v)) then
421  write(file,'(/,"Coru: ",$)')
422  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
423  dt*(adp%CAu(i,j,k)-adp%rv_x_v(i,j,k))*inorm(k); enddo
424  endif
425  if (ASSOCIATED(adp%du_dt_visc)) then
426  write(file,'(/,"duv: ",$)')
427  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
428  (dt*adp%du_dt_visc(i,j,k))*inorm(k); enddo
429  endif
430  if (ASSOCIATED(adp%du_other)) then
431  write(file,'(/,"du_other: ",$)')
432  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
433  (adp%du_other(i,j,k))*inorm(k); enddo
434  endif
435  if (ASSOCIATED(cs%u_accel_bt)) then
436  write(file,'(/,"dubt: ",$)')
437  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
438  (dt*cs%u_accel_bt(i,j,k)*inorm(k)) ; enddo
439  endif
440  endif
441 
442  write(file,'(2/)')
443 
444  call flush(file)
445  endif
446 
447 end subroutine write_u_accel
448 
449 !> This subroutine writes to an output file all of the accelerations
450 !! that have been applied to a column of meridional velocities over
451 !! the previous timestep. This subroutine is called from vertvisc.
452 subroutine write_v_accel(i, J, vm, hin, ADp, CDp, dt, G, GV, CS, &
453  maxvel, minvel, str, a, hv)
454  integer, intent(in) :: i !< The zonal index of the column to be documented.
455  integer, intent(in) :: J !< The meridional index of the column to be
456  !! documented.
457  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
458  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
459  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
460  intent(in) :: vm !< The new meridional velocity, in m s-1.
461  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
462  intent(in) :: hin !< The layer thickness, in m.
463  type(accel_diag_ptrs), intent(in) :: ADp !< A structure pointing to the various
464  !! accelerations in the momentum equations.
465  type(cont_diag_ptrs), intent(in) :: CDp !< A structure with pointers to various terms in
466  !! the continuity equations.
467  real, intent(in) :: dt !< The ocean dynamics time step, in s.
468  type(pointaccel_cs), pointer :: CS !< The control structure returned by a previous
469  !! call to PointAccel_init.
470  real, intent(in) :: maxvel, minvel
471  real, optional, intent(in) :: str !< The surface wind stress integrated over a time
472  !! step, in m2 s-1.
473  real, dimension(SZI_(G),SZK_(G)), &
474  optional, intent(in) :: a !< The layer coupling coefficients from
475  !! vertvisc, m.
476  real, dimension(SZI_(G),SZK_(G)), &
477  optional, intent(in) :: hv !< The layer thicknesses at velocity grid points,
478  !! from vertvisc, in m.
479 
480 ! This subroutine writes to an output file all of the accelerations
481 ! that have been applied to a column of meridional velocities over
482 ! the previous timestep. This subroutine is called from vertvisc.
483 
484 ! Arguments: i - The zonal index of the column to be documented.
485 ! (in) J - The meridional index of the column to be documented.
486 ! (in) vm - The new meridional velocity, in m s-1.
487 ! (in) hin - The layer thickness, in m.
488 ! (in) ADp - A structure pointing to the various accelerations in
489 ! the momentum equations.
490 ! (in) CDp - A structure with pointers to various terms in the continuity
491 ! equations.
492 ! (in) dt - The model's dynamics time step.
493 ! (in) G - The ocean's grid structure.
494 ! (in) GV - The ocean's vertical grid structure.
495 ! (in) CS - The control structure returned by a previous call to
496 ! PointAccel_init.
497 ! (in) str - The surface wind stress integrated over a time
498 ! step, in m2 s-1.
499 ! (in) a - The layer coupling coefficients from vertvisc, m.
500 ! (in) hv - The layer thicknesses at velocity grid points, from
501 ! vertvisc, in m.
502 
503  real :: f_eff, CFL
504  real :: Angstrom
505  real :: truncvel, dv
506  real :: Inorm(szk_(g))
507  real :: e(szk_(g)+1)
508  integer :: yr, mo, day, hr, minute, sec, yearday
509  integer :: k, ks, ke
510  integer :: nz
511  logical :: do_k(szk_(g)+1)
512  logical :: prev_avail
513  integer :: file
514 
515  angstrom = gv%Angstrom + gv%H_subroundoff
516 
517 ! if (.not.associated(CS)) return
518  nz = g%ke
519  if (cs%cols_written < cs%max_writes) then
520  cs%cols_written = cs%cols_written + 1
521 
522  ks = 1 ; ke = nz
523  do_k(:) = .false.
524 
525  ! Open up the file for output if this is the first call.
526  if (cs%v_file < 0) then
527  if (len_trim(cs%v_trunc_file) < 1) return
528  call open_file(cs%v_file, trim(cs%v_trunc_file), action=append_file, &
529  form=ascii_file, threading=multiple, fileset=single_file)
530  if (cs%v_file < 0) then
531  call mom_error(note, 'Unable to open file '//trim(cs%v_trunc_file)//'.')
532  return
533  endif
534  endif
535  file = cs%v_file
536 
537  prev_avail = (associated(cs%u_prev) .and. associated(cs%v_prev))
538 
539  do k=1,nz
540  if (((max(cs%v_av(i,j,k), vm(i,j,k)) >= maxvel) .or. &
541  (min(cs%v_av(i,j,k), vm(i,j,k)) <= minvel)) .and. &
542  ((hin(i,j,k) + hin(i,j+1,k)) > 3.0*angstrom)) exit
543  enddo
544  ks = k
545  do k=nz,1,-1
546  if (((max(cs%v_av(i,j,k), vm(i,j,k)) >= maxvel) .or. &
547  (min(cs%v_av(i,j,k), vm(i,j,k)) <= minvel)) .and. &
548  ((hin(i,j,k) + hin(i,j+1,k)) > 3.0*angstrom)) exit
549  enddo
550  ke = k
551  if (ke < ks) then
552  ks = 1; ke = nz; write(file,'("V: Unable to set ks & ke.")')
553  endif
554 
555  call get_date(cs%Time, yr, mo, day, hr, minute, sec)
556  call get_time((cs%Time - set_date(yr, 1, 1, 0, 0, 0)), sec, yearday)
557  write (file,'(/,"--------------------------")')
558  write (file,'(/,"Time ",i5,i4,F6.2," V-velocity violation at ",I4,": ",2(I3), &
559  & " (",F7.2," E ",F7.2," N) Layers ",I3," to ",I3,". dt = ",1PG10.4)') &
560  yr, yearday, (REAL(sec)/3600.0), pe_here(), i, j, &
561  G%geoLonCv(i,j), G%geoLatCv(i,j), ks, ke, dt
562 
563  if (ks <= gv%nk_rho_varies) ks = 1
564  do k=ks,ke
565  if ((hin(i,j,k) + hin(i,j+1,k)) > 3.0*angstrom) do_k(k) = .true.
566  enddo
567 
568  write(file,'(/,"Layers:",$)')
569  do k=ks,ke ; if (do_k(k)) write(file,'(I10," ",$)') (k); enddo
570  write(file,'(/,"v(m): ",$)')
571  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (vm(i,j,k)); enddo
572 
573  if (prev_avail) then
574  write(file,'(/,"v(mp): ",$)')
575  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (cs%v_prev(i,j,k)); enddo
576  endif
577 
578  write(file,'(/,"v(3): ",$)')
579  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (cs%v_av(i,j,k)); enddo
580  write(file,'(/,"CFL v: ",$)')
581  do k=ks,ke ; if (do_k(k)) then
582  cfl = abs(vm(i,j,k)) * dt * g%dx_Cv(i,j)
583  if (vm(i,j,k) < 0.0) then ; cfl = cfl * g%IareaT(i,j+1)
584  else ; cfl = cfl * g%IareaT(i,j) ; endif
585  write(file,'(ES10.3," ",$)') cfl
586  endif ; enddo
587  write(file,'(/,"CFL0 v:",$)')
588  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
589  abs(vm(i,j,k)) * dt * g%IdyCv(i,j) ; enddo
590 
591  if (prev_avail) then
592  write(file,'(/,"dv: ",$)')
593  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
594  ((vm(i,j,k)-cs%v_prev(i,j,k))); enddo
595  endif
596 
597  write(file,'(/,"CAv: ",$)')
598  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (dt*adp%CAv(i,j,k)); enddo
599 
600  write(file,'(/,"PFv: ",$)')
601  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (dt*adp%PFv(i,j,k)); enddo
602 
603  write(file,'(/,"diffv: ",$)')
604  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') (dt*adp%diffv(i,j,k)); enddo
605 
606  if (ASSOCIATED(adp%gradKEv)) then
607  write(file,'(/,"KEv: ",$)')
608  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
609  (dt*adp%gradKEv(i,j,k)); enddo
610  endif
611  if (ASSOCIATED(adp%rv_x_u)) then
612  write(file,'(/,"Corv: ",$)')
613  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
614  dt*(adp%CAv(i,j,k)-adp%rv_x_u(i,j,k)); enddo
615  endif
616  if (ASSOCIATED(adp%dv_dt_visc)) then
617  write(file,'(/,"vbv: ",$)')
618  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
619  (vm(i,j,k)-dt*adp%dv_dt_visc(i,j,k)); enddo
620 
621  write(file,'(/,"dvv: ",$)')
622  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
623  (dt*adp%dv_dt_visc(i,j,k)); enddo
624  endif
625  if (ASSOCIATED(adp%dv_other)) then
626  write(file,'(/,"dv_other: ",$)')
627  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
628  (adp%dv_other(i,j,k)); enddo
629  endif
630  if (present(a)) then
631  write(file,'(/,"a: ",$)')
632  do k=ks,ke+1 ; if (do_k(k)) write(file,'(ES10.3," ",$)') a(i,k); enddo
633  endif
634  if (present(hv)) then
635  write(file,'(/,"hvel: ",$)')
636  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') hv(i,k); enddo
637  endif
638  write(file,'(/,"Stress: ",ES10.3)') str
639 
640  if (ASSOCIATED(cs%v_accel_bt)) then
641  write(file,'("dvbt: ",$)')
642  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
643  (dt*cs%v_accel_bt(i,j,k)) ; enddo
644  write(file,'(/)')
645  endif
646 
647  write(file,'("h--: ",$)')
648  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') hin(i-1,j,k); enddo
649  write(file,'(/,"h0-: ",$)')
650  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') hin(i,j,k); enddo
651  write(file,'(/,"h+-: ",$)')
652  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') hin(i+1,j,k); enddo
653  write(file,'(/,"h-+: ",$)')
654  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') hin(i-1,j+1,k); enddo
655  write(file,'(/,"h0+: ",$)')
656  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') hin(i,j+1,k); enddo
657  write(file,'(/,"h++: ",$)')
658  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') hin(i+1,j+1,k); enddo
659 
660  e(nz+1) = -g%bathyT(i,j)
661  do k=nz,1,-1 ; e(k) = e(k+1) + hin(i,j,k); enddo
662  write(file,'(/,"e-: ",$)')
663  write(file,'(ES10.3," ",$)') e(ks)
664  do k=ks+1,ke+1 ; if (do_k(k-1)) write(file,'(ES10.3," ",$)') e(k); enddo
665 
666  e(nz+1) = -g%bathyT(i,j+1)
667  do k=nz,1,-1 ; e(k) = e(k+1) + hin(i,j+1,k) ; enddo
668  write(file,'(/,"e+: ",$)')
669  write(file,'(ES10.3," ",$)') e(ks)
670  do k=ks+1,ke+1 ; if (do_k(k-1)) write(file,'(ES10.3," ",$)') e(k); enddo
671  if (ASSOCIATED(cs%T)) then
672  write(file,'(/,"T-: ",$)')
673  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%T(i,j,k); enddo
674  write(file,'(/,"T+: ",$)')
675  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%T(i,j+1,k); enddo
676  endif
677  if (ASSOCIATED(cs%S)) then
678  write(file,'(/,"S-: ",$)')
679  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%S(i,j,k); enddo
680  write(file,'(/,"S+: ",$)')
681  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%S(i,j+1,k); enddo
682  endif
683 
684  if (prev_avail) then
685  write(file,'(/,"u--: ",$)')
686  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%u_prev(i-1,j,k); enddo
687  write(file,'(/,"u-+: ",$)')
688  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%u_prev(i-1,j+1,k); enddo
689  write(file,'(/,"u+-: ",$)')
690  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%u_prev(i,j,k); enddo
691  write(file,'(/,"u++: ",$)')
692  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') cs%u_prev(i,j+1,k); enddo
693  endif
694 
695  write(file,'(/,"uh--: ",$)')
696  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
697  (cdp%uh(i-1,j,k)*g%IdyCu(i-1,j)); enddo
698  write(file,'(/," uhC--: ",$)')
699  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
700  (cs%u_av(i-1,j,k) * 0.5*(hin(i-1,j,k) + hin(i,j,k))); enddo
701  if (prev_avail) then
702  write(file,'(/," uhCp--:",$)')
703  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
704  (0.5*cs%u_prev(i-1,j,k)*(hin(i-1,j,k) + hin(i,j,k))); enddo
705  endif
706 
707  write(file,'(/,"uh-+: ",$)')
708  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
709  (cdp%uh(i-1,j+1,k)*g%IdyCu(i-1,j+1)); enddo
710  write(file,'(/," uhC-+: ",$)')
711  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
712  (cs%u_av(i-1,j+1,k) * 0.5*(hin(i-1,j+1,k) + hin(i,j+1,k))); enddo
713  if (prev_avail) then
714  write(file,'(/," uhCp-+:",$)')
715  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
716  (0.5*cs%u_prev(i-1,j+1,k)*(hin(i-1,j+1,k) + hin(i,j+1,k))); enddo
717  endif
718 
719  write(file,'(/,"uh+-: ",$)')
720  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
721  (cdp%uh(i,j,k)*g%IdyCu(i,j)); enddo
722  write(file,'(/," uhC+-: ",$)')
723  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
724  (cs%u_av(i,j,k) * 0.5*(hin(i,j,k) + hin(i+1,j,k))); enddo
725  if (prev_avail) then
726  write(file,'(/," uhCp+-:",$)')
727  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
728  (0.5*cs%u_prev(i,j,k)*(hin(i,j,k) + hin(i+1,j,k))); enddo
729  endif
730 
731  write(file,'(/,"uh++: ",$)')
732  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
733  (cdp%uh(i,j+1,k)*g%IdyCu(i,j+1)); enddo
734  write(file,'(/," uhC++: ",$)')
735  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
736  (cs%u_av(i,j+1,k) * 0.5*(hin(i,j+1,k) + hin(i+1,j+1,k))); enddo
737  if (prev_avail) then
738  write(file,'(/," uhCp++:",$)')
739  do k=ks,ke ; if (do_k(k)) write(file,'(ES10.3," ",$)') &
740  (0.5*cs%u_prev(i,j+1,k)*(hin(i,j+1,k) + hin(i+1,j+1,k))); enddo
741  endif
742 
743  write(file,'(/,"D: ",2(ES10.3))') g%bathyT(i,j),g%bathyT(i,j+1)
744 
745  ! From here on, the normalized accelerations are written.
746  if (prev_avail) then
747  do k=ks,ke
748  dv = vm(i,j,k)-cs%v_prev(i,j,k)
749  if (abs(dv) < 1.0e-6) dv = 1.0e-6
750  inorm(k) = 1.0 / dv
751  enddo
752 
753  write(file,'(2/,"Norm: ",$)')
754  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') (1.0/inorm(k)); enddo
755  write(file,'(/,"dv: ",$)')
756  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
757  ((vm(i,j,k)-cs%v_prev(i,j,k))*inorm(k)); enddo
758  write(file,'(/,"CAv: ",$)')
759  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
760  (dt*adp%CAv(i,j,k)*inorm(k)); enddo
761  write(file,'(/,"PFv: ",$)')
762  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
763  (dt*adp%PFv(i,j,k)*inorm(k)); enddo
764  write(file,'(/,"diffv: ",$)')
765  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
766  (dt*adp%diffv(i,j,k)*inorm(k)); enddo
767 
768  if (ASSOCIATED(adp%gradKEu)) then
769  write(file,'(/,"KEv: ",$)')
770  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
771  (dt*adp%gradKEv(i,j,k)*inorm(k)); enddo
772  endif
773  if (ASSOCIATED(adp%rv_x_u)) then
774  write(file,'(/,"Corv: ",$)')
775  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
776  dt*(adp%CAv(i,j,k)-adp%rv_x_u(i,j,k))*inorm(k); enddo
777  endif
778  if (ASSOCIATED(adp%dv_dt_visc)) then
779  write(file,'(/,"dvv: ",$)')
780  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
781  (dt*adp%dv_dt_visc(i,j,k)*inorm(k)); enddo
782  endif
783  if (ASSOCIATED(adp%dv_other)) then
784  write(file,'(/,"dv_other: ",$)')
785  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
786  (adp%dv_other(i,j,k)*inorm(k)); enddo
787  endif
788  if (ASSOCIATED(cs%v_accel_bt)) then
789  write(file,'(/,"dvbt: ",$)')
790  do k=ks,ke ; if (do_k(k)) write(file,'(F10.6," ",$)') &
791  (dt*cs%v_accel_bt(i,j,k)*inorm(k)) ; enddo
792  endif
793  endif
794 
795  write(file,'(2/)')
796 
797  call flush(file)
798  endif
799 
800 end subroutine write_v_accel
801 
802 ! #@# This subroutine needs a doxygen description
803 subroutine pointaccel_init(MIS, Time, G, param_file, diag, dirs, CS)
805  target, intent(in) :: MIS !< For "MOM Internal State" a set of pointers
806  !! to the fields and accelerations that make
807  !! up the ocean's physical state.
808  type(time_type), target, intent(in) :: Time !< The current model time.
809  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
810  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time
811  !! parameters.
812  type(diag_ctrl), target, intent(inout) :: diag !< A structure that is used to regulate
813  !! diagnostic output.
814  type(directories), intent(in) :: dirs !< A structure containing several relevant
815  !! directory paths.
816  type(pointaccel_cs), pointer :: CS !< A pointer that is set to point to the
817  !! control structure for this module.
818 
819 ! Arguments: MIS - For "MOM Internal State" a set of pointers to the fields and
820 ! accelerations that make up the ocean's physical state.
821 ! (in) Time - The current model time.
822 ! (in) G - The ocean's grid structure.
823 ! (in) param_file - A structure indicating the open file to parse for
824 ! model parameter values.
825 ! (in) diag - A structure that is used to regulate diagnostic output.
826 ! (in) dirs - A structure containing several relevant directory paths.
827 ! (in/out) CS - A pointer that is set to point to the control structure
828 ! for this module
829 ! This include declares and sets the variable "version".
830 #include "version_variable.h"
831  character(len=40) :: mdl = "MOM_PointAccel" ! This module's name.
832 
833  if (associated(cs)) return
834  allocate(cs)
835 
836  cs%diag => diag ; cs%Time => time
837 
838  cs%T => mis%T ; cs%S => mis%S ; cs%pbce => mis%pbce
839  cs%u_accel_bt => mis%u_accel_bt ; cs%v_accel_bt => mis%v_accel_bt
840  cs%u_prev => mis%u_prev ; cs%v_prev => mis%v_prev
841  cs%u_av => mis%u_av; if (.not.associated(mis%u_av)) cs%u_av => mis%u(:,:,:)
842  cs%v_av => mis%v_av; if (.not.associated(mis%v_av)) cs%v_av => mis%v(:,:,:)
843 
844  ! Read all relevant parameters and write them to the model log.
845  call log_version(param_file, mdl, version, "")
846  call get_param(param_file, mdl, "U_TRUNC_FILE", cs%u_trunc_file, &
847  "The absolute path to the file where the accelerations \n"//&
848  "leading to zonal velocity truncations are written. \n"//&
849  "Leave this empty for efficiency if this diagnostic is \n"//&
850  "not needed.", default="")
851  call get_param(param_file, mdl, "V_TRUNC_FILE", cs%v_trunc_file, &
852  "The absolute path to the file where the accelerations \n"//&
853  "leading to meridional velocity truncations are written. \n"//&
854  "Leave this empty for efficiency if this diagnostic is \n"//&
855  "not needed.", default="")
856  call get_param(param_file, mdl, "MAX_TRUNC_FILE_SIZE_PER_PE", cs%max_writes, &
857  "The maximum number of colums of truncations that any PE \n"//&
858  "will write out during a run.", default=50)
859 
860  if (len_trim(dirs%output_directory) > 0) then
861  if (len_trim(cs%u_trunc_file) > 0) &
862  cs%u_trunc_file = trim(dirs%output_directory)//trim(cs%u_trunc_file)
863  if (len_trim(cs%v_trunc_file) > 0) &
864  cs%v_trunc_file = trim(dirs%output_directory)//trim(cs%v_trunc_file)
865  call log_param(param_file, mdl, "output_dir/U_TRUNC_FILE", cs%u_trunc_file)
866  call log_param(param_file, mdl, "output_dir/V_TRUNC_FILE", cs%v_trunc_file)
867  endif
868  cs%u_file = -1 ; cs%v_file = -1 ; cs%cols_written = 0
869 
870 end subroutine pointaccel_init
871 end module mom_pointaccel
subroutine, public pointaccel_init(MIS, Time, G, param_file, diag, dirs, CS)
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Provides the ocean grid type.
Definition: MOM_grid.F90:2
This module contains I/O framework code.
Definition: MOM_io.F90:2
The accel_diag_ptrs structure contains pointers to arrays with accelerations, which can later be used...
The cont_diag_ptrs structure contains pointers to arrays with transports, which can later be used for...
The ocean_internal_state structure contains pointers to all of the prognostic variables allocated in ...
subroutine, public write_v_accel(i, J, vm, hin, ADp, CDp, dt, G, GV, CS, maxvel, minvel, str, a, hv)
This subroutine writes to an output file all of the accelerations that have been applied to a column ...
subroutine, public write_u_accel(I, j, um, hin, ADp, CDp, dt, G, GV, CS, maxvel, minvel, str, a, hv)
This subroutine writes to an output file all of the accelerations that have been applied to a column ...
subroutine, public mom_error(level, message, all_print)