ROMS
Loading...
Searching...
No Matches
read_phypar.F
Go to the documentation of this file.
1#include "cppdefs.h"
2 SUBROUTINE read_phypar (model, inp, out, Lwrite)
3!
4!git $Id$
5!================================================== Hernan G. Arango ===
6! Copyright (c) 2002-2025 The ROMS Group !
7! Licensed under a MIT/X style license !
8! See License_ROMS.md !
9!=======================================================================
10! !
11! This routine reads and reports physical model input parameters. !
12! !
13!=======================================================================
14!
15 USE mod_param
16 USE mod_parallel
17#ifdef BIOLOGY
18 USE mod_biology
19#endif
20#ifdef ICE_MODEL
21 USE mod_ice
22#endif
23#if defined MODEL_COUPLING && defined MCT_LIB
24 USE mod_coupler
25#endif
26#if defined FOUR_DVAR || defined VERIFICATION
27 USE mod_fourdvar
28#endif
29 USE mod_iounits
30 USE mod_ncparam
31#ifdef NESTING
32 USE mod_nesting
33#endif
34 USE mod_netcdf
35#if defined PIO_LIB && defined DISTRIBUTE
37#endif
38 USE mod_scalars
39#if defined SEDIMENT || defined BBL_MODEL
40 USE mod_sediment
41#endif
42 USE mod_stepping
43#ifdef PROPAGATOR
44 USE mod_storage
45#endif
46 USE mod_strings
47!
49#if defined DISTRIBUTE && defined PIO_LIB
50 USE set_pio_mod
51#endif
52!
53 USE dateclock_mod, ONLY : ref_clock
54 USE strings_mod, ONLY : founderror
55!
56 implicit none
57!
58! Imported variable declarations
59!
60 logical, intent(inout) :: Lwrite
61!
62 integer, intent(in) :: model, inp, out
63!
64! Local variable declarations.
65!
66 logical :: got_Ngrids, got_NestLayers
67 logical :: obc_data
68 logical :: Lvalue(1)
69#if defined SOLVE3D && defined SEDIMENT
70 logical :: LreadNCS = .false.
71 logical :: LreadNNS = .false.
72#endif
73 logical, allocatable :: Lswitch(:)
74#if defined SOLVE3D && defined T_PASSIVE
75 logical, allocatable :: Linert(:,:)
76#endif
77#if defined SOLVE3D && (defined BBL_MODEL || defined SEDIMENT)
78 logical, allocatable :: Lbottom(:,:)
79#endif
80 logical, allocatable :: Ltracer(:,:)
81#if defined AD_SENSITIVITY || defined I4DVAR_ANA_SENSITIVITY || \
82 defined forcing_sv || defined opt_observations || \
83 defined sensitivity_4dvar || defined so_semi || \
84 defined stochastic_opt
85# ifndef OBS_SPACE
86 logical, allocatable :: Ladsen(:)
87# endif
88#endif
89!
90 integer :: Npts, Nval, i, itrc, ivar, k, lstr, ng, nl, status
91 integer :: ifield, ifile, igrid, itracer, nline, max_Ffiles
92 integer :: ibcfile, iclmfile
93 integer :: Cdim, Clen, Rdim
94 integer :: nPETs, maxPETs
95 integer :: OutFiles
96 integer :: Ivalue(1)
97#ifdef ICE_MODEL
98 integer :: ioff
99#endif
100
101 integer, allocatable :: Nfiles(:)
102 integer, allocatable :: Ncount(:,:)
103 integer, allocatable :: NBCcount(:,:)
104 integer, allocatable :: NCLMcount(:,:)
105!
106 real(dp), allocatable :: Dtracer(:,:)
107 real(r8), allocatable :: Rtracer(:,:)
108 real(r8), allocatable :: tracer(:,:)
109#ifdef NESTING
110 real(r8), allocatable :: RunTimeDay(:), RunTimeSec(:)
111#endif
112 real(dp) :: Dvalue(1)
113 real(r8) :: Rvalue(1)
114
115 real(dp), dimension(nRval) :: Rval
116!
117 character (len=1 ), parameter :: blank = ' '
118 character (len=40 ) :: KeyWord
119 character (len=50 ) :: label
120 character (len=80 ) :: text
121 character (len=256) :: fname, line
122 character (len=256), dimension(nCval) :: Cval
123
124 character (len=*), parameter :: MyFile = &
125 & __FILE__
126!
127!-----------------------------------------------------------------------
128! Initialize.
129!-----------------------------------------------------------------------
130!
131 ifile=1 ! multiple file counter
132 ibcfile=1 ! multiple BC file counter
133 iclmfile=1 ! multiple CLM file counter
134 igrid=1 ! nested grid counter
135 itracer=0 ! LBC tracer counter
136 nline=0 ! LBC multi-line counter
137 DO i=1,len(label)
138 label(i:i)=blank
139 END DO
140 got_ngrids=.false.
141 got_nestlayers=.false.
142 cdim=SIZE(cval,1)
143 clen=len(cval(1))
144 rdim=SIZE(rval,1)
145 nval=0
146!
147!-----------------------------------------------------------------------
148! Read in physical model parameters. Then, load input data into module.
149! Take into account nested grid configurations.
150!-----------------------------------------------------------------------
151!
152 DO WHILE (.true.)
153 READ (inp,'(a)',err=10,END=20) line
154 status=decode_line(line, keyword, nval, cval, rval)
155 IF (status.gt.0) THEN
156 SELECT CASE (trim(keyword))
157 CASE ('TITLE')
158 IF (nval.eq.1) THEN
159 title=trim(adjustl(cval(nval)))
160 ELSE
161 WRITE(title,'(a,1x,a)') trim(adjustl(title)), &
162 & trim(adjustl(cval(nval)))
163 END IF
164 CASE ('MyAppCPP')
165 DO i=1,len(myappcpp)
166 myappcpp(i:i)=blank
167 END DO
168 myappcpp=trim(adjustl(cval(nval)))
169 CASE ('VARNAME')
170 DO i=1,len(varname)
171 varname(i:i)=blank
172 END DO
173 varname=trim(adjustl(cval(nval)))
174 CASE ('Ngrids')
175 npts=load_i(nval, rval, 1, ivalue)
176 ngrids=ivalue(1)
177 IF (ngrids.le.0) THEN
178 IF (master) WRITE (out,290) 'Ngrids', ngrids, &
179 & 'must be greater than zero.'
180 exit_flag=5
181 RETURN
182 END IF
183 got_ngrids=.true. ! Allocating variables in
184 CALL allocate_param ! modules that solely
185 CALL allocate_parallel (ngrids) ! depend on the number
186 CALL allocate_iounits (ngrids) ! nested grids
187 CALL allocate_stepping (ngrids)
188#if defined PIO_LIB && defined DISTRIBUTE
189 IF (.not.associated(var_desc)) THEN
190 allocate ( var_desc(mvars) )
191 END IF
192#endif
193#if defined FOUR_DVAR || defined VERIFICATION
194 CALL allocate_fourdvar
195#endif
196 IF (.not.allocated(lswitch)) THEN
197 allocate ( lswitch(ngrids) )
198 END IF
199#if defined SOLVE3D && (defined BBL_MODEL || defined SEDIMENT)
200 IF (.not.allocated(lbottom)) THEN
201 allocate ( lbottom(mbotp,ngrids) )
202 END IF
203#endif
204 IF (.not.allocated(nfiles)) THEN
205 allocate ( nfiles(ngrids) )
206 nfiles(1:ngrids)=0
207 END IF
208 CASE ('NestLayers')
209 npts=load_i(nval, rval, 1, ivalue)
210 nestlayers=ivalue(1)
211 IF (nestlayers.lt.1) THEN
212 IF (master) WRITE (out,290) 'NestLayers', nestlayers, &
213 & 'must be greater or equal than one.'
214 exit_flag=5
215 RETURN
216 END IF
217#ifndef NESTING
218 IF (nestlayers.gt.1) THEN
219 IF (master) WRITE (out,290) 'NestLayers', nestlayers, &
220 & 'must be equal to one in non-nesting applications.'
221 exit_flag=5
222 RETURN
223 END IF
224#endif
225 got_nestlayers=.true.
226 IF (.not.allocated(gridsinlayer)) THEN
227 allocate ( gridsinlayer(nestlayers) )
228#ifndef NESTING
229 gridsinlayer(1:nestlayers)=1
230#endif
231 END IF
232 IF (.not.allocated(gridnumber)) THEN
233 allocate ( gridnumber(ngrids,nestlayers) )
234 gridnumber(1:ngrids,1:nestlayers)=0 ! Important
235 END IF
236 CASE ('GridsInLayer')
237 IF (.not.got_nestlayers) THEN
238 IF (master) WRITE (out,320) 'NestLayers', &
239 & 'Add "NestLayers" keyword before GridsInLayer.'
240 exit_flag=5
241 RETURN
242 END IF
243 npts=load_i(nval, rval, nestlayers, gridsinlayer)
244 ng=0
245 DO nl=1,nestlayers
246 DO i=1,gridsinlayer(nl)
247 ng=ng+1 ! order of grids are very in
248 gridnumber(i,nl)=ng ! nesting applications. See
249 END DO ! WikiROMS for details.
250 END DO
251 CASE ('Lm')
252 IF (.not.got_ngrids) THEN
253 IF (master) WRITE (out,320) 'Ngrids', &
254 & 'Add "Ngrids" keyword before grid dimension (Lm, Mm).'
255 exit_flag=5
256 RETURN
257 END IF
258 npts=load_i(nval, rval, ngrids, lm)
259 DO ng=1,ngrids
260 IF (lm(ng).le.0) THEN
261 IF (master) WRITE (out,300) 'Lm', ng, &
262 & 'must be greater than zero.'
263 exit_flag=5
264 RETURN
265 END IF
266 END DO
267 CASE ('Mm')
268 npts=load_i(nval, rval, ngrids, mm)
269 DO ng=1,ngrids
270 IF (mm(ng).le.0) THEN
271 IF (master) WRITE (out,300) 'Mm', ng, &
272 & 'must be greater than zero.'
273 exit_flag=5
274 RETURN
275 END IF
276 END DO
277 CASE ('N')
278 npts=load_i(nval, rval, ngrids, n)
279 DO ng=1,ngrids
280 IF (n(ng).lt.0) THEN
281 IF (master) WRITE (out,300) 'N', ng, &
282 & 'must be greater than zero.'
283 exit_flag=5
284 RETURN
285 END IF
286 END DO
287#if defined SEDIMENT && defined SOLVE3D
288 CASE ('Nbed')
289 npts=load_i(nval, rval, 1, ivalue)
290 nbed=ivalue(1)
291 IF (nbed.le.0) THEN
292 IF (master) WRITE (out,290) 'Nbed = ', nbed, &
293 & 'must be greater than zero.'
294 exit_flag=5
295 RETURN
296 END IF
297#endif
298#ifdef SOLVE3D
299 CASE ('NAT')
300 npts=load_i(nval, rval, 1, ivalue)
301 nat=ivalue(1)
302 IF ((nat.lt.1).or.(nat.gt.2)) THEN
303 IF (master) WRITE (out,290) 'NAT = ', nat, &
304 & 'make sure that NAT is either 1 or 2.'
305 exit_flag=5
306 RETURN
307 END IF
308# ifdef SALINITY
309 IF (nat.ne.2) THEN
310 IF (master) WRITE (out,290) 'NAT = ', nat, &
311 & 'make sure that NAT is equal to 2.'
312 exit_flag=5
313 RETURN
314 END IF
315# endif
316#endif
317#if defined T_PASSIVE && defined SOLVE3D
318 CASE ('NPT')
319 npts=load_i(nval, rval, 1, ivalue)
320 npt=ivalue(1)
321 IF (npt.le.0) THEN
322 IF (master) WRITE (out,290) 'NPT = ', npt, &
323 & 'must be greater than zero.'
324 exit_flag=5
325 RETURN
326 END IF
327# ifdef AGE_MEAN
328 IF (mod(npt,2).ne.0) THEN
329 IF (master) WRITE (out,290) 'NPT = ', npt, &
330 & 'must be an even number when Mean Age is activated.'
331 exit_flag=5
332 RETURN
333 END IF
334# endif
335#endif
336#if defined SEDIMENT && defined SOLVE3D
337 CASE ('NCS')
338 npts=load_i(nval, rval, 1, ivalue)
339 ncs=ivalue(1)
340 IF (ncs.lt.0) THEN
341 IF (master) WRITE (out,290) 'NCS = ', ncs, &
342 & 'must be greater than zero.'
343 exit_flag=5
344 RETURN
345 END IF
346 lreadncs=.true.
347 IF (lreadnns.and.((ncs+nns).le.0)) THEN
348 IF (master) WRITE (out,290) 'NST = ', ncs+nns, &
349 & 'either NCS or NNS must be greater than zero.'
350 exit_flag=5
351 RETURN
352 END IF
353 nst=nst+ncs
354 CASE ('NNS')
355 npts=load_i(nval, rval, 1, ivalue)
356 nns=ivalue(1)
357 IF (nns.lt.0) THEN
358 IF (master) WRITE (out,290) 'NNS = ', &
359 & 'must be greater than zero.'
360 exit_flag=5
361 RETURN
362 END IF
363 lreadnns=.true.
364 IF (lreadncs.and.((ncs+nns).le.0)) THEN
365 IF (master) WRITE (out,290) 'NST = ', ncs+nns, &
366 & 'either NCS or NNS must be greater than zero.'
367 exit_flag=5
368 RETURN
369 END IF
370 nst=nst+nns
371#endif
372 CASE ('NtileI')
373 npts=load_i(nval, rval, ngrids, ntilei)
374 ntilex(1:ngrids)=ntilei(1:ngrids)
375 CASE ('NtileJ')
376 npts=load_i(nval, rval, ngrids, ntilej)
377 ntilee(1:ngrids)=ntilej(1:ngrids)
378#ifdef BIOLOGY
379 CALL initialize_biology
380#endif
381#if defined SEDIMENT || defined BBL_MODEL
382 CALL initialize_sediment
383#endif
384 CALL initialize_param ! Continue allocating/initalizing
385 CALL allocate_scalars ! variables since the application
386 CALL initialize_scalars ! number of nested grids and
387 CALL allocate_ncparam ! domain parameters are known
388 CALL initialize_ncparam
389#if defined AD_SENSITIVITY || defined I4DVAR_ANA_SENSITIVITY || \
390 defined forcing_sv || defined opt_observations || \
391 defined sensitivity_4dvar || defined so_semi || \
392 defined stochastic_opt
393# ifndef OBS_SPACE
394 IF (.not.allocated(ladsen)) THEN
395 allocate (ladsen(mt*ngrids))
396 END IF
397# endif
398#endif
399 IF (.not.allocated(ltracer)) THEN
400 allocate (ltracer(nat+npt,ngrids))
401 END IF
402#if defined SOLVE3D && defined T_PASSIVE
403 IF (.not.allocated(linert)) THEN
404 allocate (linert(npt,ngrids))
405 END IF
406 IF (maxval(inert).eq.0) THEN
407 IF (master) WRITE (out,280) 'inert'
408 exit_flag=5
409 RETURN
410 END IF
411#endif
412 IF (.not.allocated(dtracer)) THEN
413 allocate (dtracer(nat+npt,ngrids))
414 END IF
415 IF (.not.allocated(rtracer)) THEN
416 allocate (rtracer(nat+npt,ngrids))
417 END IF
418 IF (.not.allocated(tracer)) THEN
419 allocate (tracer(mt,ngrids))
420 END IF
421#ifdef SOLVE3D
422 CASE ('Hadvection')
423 IF (itracer.lt.(nat+npt)) THEN
424 itracer=itracer+1
425 ELSE
426 itracer=1 ! next nested grid
427 END IF
428 itrc=itracer
429 npts=load_tadv(nval, cval, line, nline, itrc, igrid, &
430 & itracer, 1, nat+npt, &
431 & vname(1,idtvar(itrc)), &
432 & hadvection)
433 IF (founderror(exit_flag, noerror, &
434 & __line__, myfile)) RETURN
435 CASE ('Vadvection')
436 IF (itracer.lt.(nat+npt)) THEN
437 itracer=itracer+1
438 ELSE
439 itracer=1 ! next nested grid
440 END IF
441 itrc=itracer
442 npts=load_tadv(nval, cval, line, nline, itrc, igrid, &
443 & itracer, 1, nat+npt, &
444 & vname(1,idtvar(itrc)), &
445 & vadvection)
446 IF (founderror(exit_flag, noerror, &
447 & __line__, myfile)) RETURN
448# if defined ADJOINT || defined TANGENT || defined TL_IOMS
449 CASE ('ad_Hadvection')
450 IF (itracer.lt.(nat+npt)) THEN
451 itracer=itracer+1
452 ELSE
453 itracer=1 ! next nested grid
454 END IF
455 itrc=itracer
456 npts=load_tadv(nval, cval, line, nline, itrc, igrid, &
457 & itracer, 1, nat+npt, &
458 & vname(1,idtvar(itrc)), &
459 & ad_hadvection)
460 IF (founderror(exit_flag, noerror, &
461 & __line__, myfile)) RETURN
462 CASE ('ad_Vadvection')
463 IF (itracer.lt.(nat+npt)) THEN
464 itracer=itracer+1
465 ELSE
466 itracer=1 ! next nested grid
467 END IF
468 itrc=itracer
469 npts=load_tadv(nval, cval, line, nline, itrc, igrid, &
470 & itracer, 1, nat+npt, &
471 & vname(1,idtvar(itracer)), &
472 & ad_vadvection)
473 IF (founderror(exit_flag, noerror, &
474 & __line__, myfile)) RETURN
475# endif
476#endif
477 CASE ('LBC(isFsur)')
478 npts=load_lbc(nval, cval, line, nline, isfsur, igrid, &
479 & 0, 0, vname(1,idfsur), lbc)
480 CASE ('LBC(isUbar)')
481 npts=load_lbc(nval, cval, line, nline, isubar, igrid, &
482 & 0, 0, vname(1,idubar), lbc)
483 CASE ('LBC(isVbar)')
484 npts=load_lbc(nval, cval, line, nline, isvbar, igrid, &
485 & 0, 0, vname(1,idvbar), lbc)
486#ifdef WEC
487 CASE ('LBC(isU2Sd)')
488 npts=load_lbc(nval, cval, line, nline, isu2sd, igrid, &
489 & 0, 0, vname(1,idu2sd), lbc)
490 CASE ('LBC(isV2Sd)')
491 npts=load_lbc(nval, cval, line, nline, isv2sd, igrid, &
492 & 0, 0, vname(1,idv2sd), lbc)
493#endif
494#ifdef SOLVE3D
495 CASE ('LBC(isUvel)')
496 npts=load_lbc(nval, cval, line, nline, isuvel, igrid, &
497 & 0, 0, vname(1,iduvel), lbc)
498 CASE ('LBC(isVvel)')
499 npts=load_lbc(nval, cval, line, nline, isvvel, igrid, &
500 & 0, 0, vname(1,idvvel), lbc)
501# ifdef WEC
502 CASE ('LBC(isU3Sd)')
503 npts=load_lbc(nval, cval, line, nline, isu3sd, igrid, &
504 & 0, 0, vname(1,idu3sd), lbc)
505 CASE ('LBC(isV3Sd)')
506 npts=load_lbc(nval, cval, line, nline, isv3sd, igrid, &
507 & 0, 0, vname(1,idv3sd), lbc)
508# endif
509# if defined GLS_MIXING || defined MY25_MIXING
510 CASE ('LBC(isMtke)')
511 npts=load_lbc(nval, cval, line, nline, ismtke, igrid, &
512 & 0, 0, vname(1,idmtke), lbc)
513# endif
514 CASE ('LBC(isTvar)')
515 IF (itracer.lt.(nat+npt)) THEN
516 itracer=itracer+1
517 ELSE
518 itracer=1 ! next nested grid
519 END IF
520 ifield=istvar(itracer)
521 npts=load_lbc(nval, cval, line, nline, ifield, igrid, &
522 & 1, nat+npt, vname(1,idtvar(itracer)), lbc)
523# ifdef ICE_MODEL
524 CASE ('LBC(isAice)')
525 ioff = isaice+(nlbcvar-11)
526 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
527 & 0, 0, vname(1,idaice), lbc)
528 CASE ('LBC(isHice)')
529 ioff = ishice+(nlbcvar-11)
530 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
531 & 0, 0, vname(1,idhice), lbc)
532 CASE ('LBC(isHsno)')
533 ioff = ishsno+(nlbcvar-11)
534 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
535 & 0, 0, vname(1,idhsno), lbc)
536 CASE ('LBC(isTice)')
537 ioff = istice+(nlbcvar-11)
538 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
539 & 0, 0, vname(1,idtice), lbc)
540 CASE ('LBC(isHmel)')
541 ioff = ishmel+(nlbcvar-11)
542 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
543 & 0, 0, vname(1,idhmel), lbc)
544 CASE ('LBC(isIage)')
545 ioff = isiage+(nlbcvar-11)
546 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
547 & 0, 0, vname(1,idiage), lbc)
548 CASE ('LBC(isISxx)')
549 ioff = isisxx+(nlbcvar-11)
550 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
551 & 0, 0, vname(1,idisxx), lbc)
552 CASE ('LBC(isISxy)')
553 ioff = isisxy+(nlbcvar-11)
554 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
555 & 0, 0, vname(1,idisxy), lbc)
556 CASE ('LBC(isISyy)')
557 ioff = isisyy+(nlbcvar-11)
558 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
559 & 0, 0, vname(1,idisyy), lbc)
560 CASE ('LBC(isUice)')
561 ioff = isuice+(nlbcvar-11)
562 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
563 & 0, 0, vname(1,iduice), lbc)
564 CASE ('LBC(isVice)')
565 ioff = isvice+(nlbcvar-11)
566 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
567 & 0, 0, vname(1,idvice), lbc)
568# endif
569#endif
570#if defined ADJOINT || defined TANGENT || defined TL_IOMS
571 CASE ('ad_LBC(isFsur)')
572 npts=load_lbc(nval, cval, line, nline, isfsur, igrid, &
573 & 0, 0, vname(1,idfsur), ad_lbc)
574 CASE ('ad_LBC(isUbar)')
575 npts=load_lbc(nval, cval, line, nline, isubar, igrid, &
576 & 0, 0, vname(1,idubar), ad_lbc)
577 CASE ('ad_LBC(isVbar)')
578 npts=load_lbc(nval, cval, line, nline, isvbar, igrid, &
579 & 0, 0, vname(1,idvbar), ad_lbc)
580# ifdef SOLVE3D
581 CASE ('ad_LBC(isUvel)')
582 npts=load_lbc(nval, cval, line, nline, isuvel, igrid, &
583 & 0, 0, vname(1,iduvel), ad_lbc)
584 CASE ('ad_LBC(isVvel)')
585 npts=load_lbc(nval, cval, line, nline, isvvel, igrid, &
586 & 0, 0, vname(1,idvvel), ad_lbc)
587# if defined GLS_MIXING || defined MY25_MIXING
588 CASE ('ad_LBC(isMtke)')
589 npts=load_lbc(nval, cval, line, nline, ismtke, igrid, &
590 & 0, 0, vname(1,idmtke), ad_lbc)
591# endif
592 CASE ('ad_LBC(isTvar)')
593 IF (itracer.lt.(nat+npt)) THEN
594 itracer=itracer+1
595 ELSE
596 itracer=1 ! next nested grid
597 END IF
598 ifield=istvar(itracer)
599 npts=load_lbc(nval, cval, line, nline, ifield, igrid, &
600 & 1, nat+npt, vname(1,idtvar(itracer)), &
601 & ad_lbc)
602# endif
603#endif
604 CASE ('VolCons(west)')
605 npts=load_l(nval, cval, ngrids, lswitch)
606 volcons(iwest,1:ngrids)=lswitch(1:ngrids)
607 CASE ('VolCons(east)')
608 npts=load_l(nval, cval, ngrids, lswitch)
609 volcons(ieast,1:ngrids)=lswitch(1:ngrids)
610 CASE ('VolCons(south)')
611 npts=load_l(nval, cval, ngrids, lswitch)
612 volcons(isouth,1:ngrids)=lswitch(1:ngrids)
613 CASE ('VolCons(north)')
614 npts=load_l(nval, cval, ngrids, lswitch)
615 volcons(inorth,1:ngrids)=lswitch(1:ngrids)
616#if defined ADJOINT || defined TANGENT || defined TL_IOMS
617 CASE ('ad_VolCons(west)')
618 npts=load_l(nval, cval, ngrids, lswitch)
619 ad_volcons(iwest,1:ngrids)=lswitch(1:ngrids)
620 tl_volcons(iwest,1:ngrids)=lswitch(1:ngrids)
621 CASE ('ad_VolCons(east)')
622 npts=load_l(nval, cval, ngrids, lswitch)
623 ad_volcons(ieast,1:ngrids)=lswitch(1:ngrids)
624 tl_volcons(ieast,1:ngrids)=lswitch(1:ngrids)
625 CASE ('ad_VolCons(south)')
626 npts=load_l(nval, cval, ngrids, lswitch)
627 ad_volcons(isouth,1:ngrids)=lswitch(1:ngrids)
628 tl_volcons(isouth,1:ngrids)=lswitch(1:ngrids)
629 CASE ('ad_VolCons(north)')
630 npts=load_l(nval, cval, ngrids, lswitch)
631 ad_volcons(inorth,1:ngrids)=lswitch(1:ngrids)
632 tl_volcons(inorth,1:ngrids)=lswitch(1:ngrids)
633#endif
634 CASE ('NTIMES')
635 npts=load_i(nval, rval, ngrids, ntimes)
636#ifdef RBL4DVAR_FCT_SENSITIVITY
637 CASE ('NTIMES_ANA')
638 npts=load_i(nval, rval, ngrids, ntimes_ana)
639 CASE ('NTIMES_FCT')
640 npts=load_i(nval, rval, ngrids, ntimes_fct)
641#endif
642 CASE ('DT')
643 npts=load_r(nval, rval, ngrids, dt)
644#if defined MODEL_COUPLING && defined MCT_LIB
645 IF (.not.allocated(couplesteps)) THEN
646 allocate (couplesteps(nmodels,ngrids))
647 couplesteps=0
648 END IF
649 DO ng=1,ngrids
650 DO i=1,nmodels
651 couplesteps(i,ng)=max(1, &
652 & int(timeinterval(iocean,i)/ &
653 & dt(ng)))
654 END DO
655 END DO
656#endif
657 CASE ('NDTFAST')
658 npts=load_i(nval, rval, ngrids, ndtfast)
659 CASE ('ERstr')
660 npts=load_i(nval, rval, 1, ivalue)
661 erstr=ivalue(1)
662 CASE ('ERend')
663 npts=load_i(nval, rval, 1, ivalue)
664 erend=ivalue(1)
665 CASE ('Nouter')
666 npts=load_i(nval, rval, 1, ivalue)
667 nouter=ivalue(1)
668 CASE ('Ninner')
669 npts=load_i(nval, rval, 1, ivalue)
670 ninner=ivalue(1)
671 CASE ('Nsaddle')
672 npts=load_i(nval, rval, 1, ivalue)
673 nsaddle=ivalue(1)
674 CASE ('Nintervals')
675 npts=load_i(nval, rval, 1, ivalue)
676 nintervals=ivalue(1)
677#ifdef PROPAGATOR
678 CASE ('NEV')
679 npts=load_i(nval, rval, 1, ivalue)
680 nev=ivalue(1)
681 CASE ('NCV')
682 npts=load_i(nval, rval, 1, ivalue)
683 ncv=ivalue(1)
684# if defined FT_EIGENMMODES || defined AFT_EIGENMODES
685 IF (ncv.lt.(2*nev+1)) THEN
686 IF (master) WRITE (out,260) 'NCV = ', ncv, &
687 & 'Must be greater than or equal to 2*NEV+1'
688 exit_flag=5
689 RETURN
690 END IF
691# else
692 IF (ncv.lt.nev) THEN
693 IF (master) WRITE (out,260) 'NCV = ', ncv, &
694 & 'Must be greater than NEV'
695 exit_flag=5
696 RETURN
697 END IF
698# endif
699#endif
700 CASE ('NRREC')
701 npts=load_i(nval, rval, ngrids, nrrec)
702 DO ng=1,ngrids
703 IF (nrrec(ng).lt.0) THEN
704 lastrec(ng)=.true.
705 ELSE
706 lastrec(ng)=.false.
707 END IF
708 END DO
709 CASE ('LcycleRST')
710 npts=load_l(nval, cval, ngrids, lcyclerst)
711 CASE ('NRST')
712 npts=load_i(nval, rval, ngrids, nrst)
713 CASE ('NSTA')
714 npts=load_i(nval, rval, ngrids, nsta)
715 CASE ('NFLT')
716 npts=load_i(nval, rval, ngrids, nflt)
717 CASE ('NINFO')
718 npts=load_i(nval, rval, ngrids, ninfo)
719 DO ng=1,ngrids
720 IF (ninfo(ng).le.0) THEN
721 WRITE (text,'(a,i2.2,a)') 'ninfo(', ng, ') = '
722 IF (master) WRITE (out,260) trim(text), ninfo(ng), &
723 & 'must be greater than zero.'
724 exit_flag=5
725 RETURN
726 END IF
727 END DO
728 CASE ('LDEFOUT')
729 npts=load_l(nval, cval, ngrids, ldefout)
730 CASE ('NHIS')
731 npts=load_i(nval, rval, ngrids, nhis)
732 CASE ('NDEFHIS')
733 npts=load_i(nval, rval, ngrids, ndefhis)
734 CASE ('NXTR')
735 npts=load_i(nval, rval, ngrids, nxtr)
736 CASE ('NDEFXTR')
737 npts=load_i(nval, rval, ngrids, ndefxtr)
738 CASE ('NQCK')
739 npts=load_i(nval, rval, ngrids, nqck)
740#if defined FORWARD_FLUXES && \
741 (defined bulk_fluxes || defined frc_coupling)
742 DO ng=1,ngrids
743 IF (nqck(ng).le.0) THEN
744 WRITE (text,'(a,i2.2,a)') 'nQCK(', ng, ') = '
745 IF (master) WRITE (out,260) trim(text), nqck(ng), &
746 & 'must be greater than zero because the QCK '// &
747 & 'file is used as surface forcing basic state.'
748 exit_flag=5
749 RETURN
750 END IF
751 END DO
752#endif
753 CASE ('NDEFQCK')
754 npts=load_i(nval, rval, ngrids, ndefqck)
755 CASE ('NTSAVG')
756 npts=load_i(nval, rval, ngrids, ntsavg)
757#ifdef ADJOINT
758 DO ng=1,ngrids
759 IF (ntsavg(ng).eq.1) ntsavg(ng)=ntimes(ng)
760 END DO
761#endif
762 CASE ('NAVG')
763 npts=load_i(nval, rval, ngrids, navg)
764 CASE ('NDEFAVG')
765 npts=load_i(nval, rval, ngrids, ndefavg)
766 CASE ('NTSDIA')
767 npts=load_i(nval, rval, ngrids, ntsdia)
768 CASE ('NDIA')
769 npts=load_i(nval, rval, ngrids, ndia)
770 CASE ('NDEFDIA')
771 npts=load_i(nval, rval, ngrids, ndefdia)
772 CASE ('LcycleTLM')
773 npts=load_l(nval, cval, ngrids, lcycletlm)
774 CASE ('NTLM')
775 npts=load_i(nval, rval, ngrids, ntlm)
776 CASE ('NDEFTLM')
777 npts=load_i(nval, rval, ngrids, ndeftlm)
778 CASE ('LcycleADJ')
779 npts=load_l(nval, cval, ngrids, lcycleadj)
780 CASE ('NADJ')
781 npts=load_i(nval, rval, ngrids, nadj)
782 CASE ('NDEFADJ')
783 npts=load_i(nval, rval, ngrids, ndefadj)
784 CASE ('NOBC')
785 npts=load_i(nval, rval, ngrids, nobc)
786#ifdef ADJUST_BOUNDARY
787# ifdef RBL4DVAR_FCT_SENSITIVITY
788 DO ng=1,ngrids
789 nbrec(ng)=1+ntimes_ana(ng)/nobc(ng)
790 END DO
791 allocate ( obc_time(maxval(nbrec),ngrids) )
792# else
793 DO ng=1,ngrids
794 nbrec(ng)=1+ntimes(ng)/nobc(ng)
795 END DO
796 allocate ( obc_time(maxval(nbrec),ngrids) )
797# endif
798#endif
799 CASE ('NSFF')
800 npts=load_i(nval, rval, ngrids, nsff)
801#if defined ADJUST_STFLUX || defined ADJUST_WSTRESS
802# ifdef RBL4DVAR_FCT_SENSITIVITY
803 DO ng=1,ngrids
804 nfrec(ng)=1+ntimes_ana(ng)/nsff(ng)
805 END DO
806 allocate ( sf_time(maxval(nfrec),ngrids) )
807# else
808 DO ng=1,ngrids
809 nfrec(ng)=1+ntimes(ng)/nsff(ng)
810 END DO
811 allocate ( sf_time(maxval(nfrec),ngrids) )
812# endif
813#endif
814 CASE ('LmultiGST')
815 npts=load_l(nval, cval, 1, lvalue)
816 lmultigst=lvalue(1)
817 CASE ('LrstGST')
818 npts=load_l(nval, cval, 1, lvalue)
819 lrstgst=lvalue(1)
820 CASE ('MaxIterGST')
821 npts=load_i(nval, rval, 1, ivalue)
822 maxitergst=ivalue(1)
823 CASE ('NGST')
824 npts=load_i(nval, rval, 1, ivalue)
825 ngst=ivalue(1)
826#ifdef PROPAGATOR
827 CASE ('Ritz_tol')
828 npts=load_r(nval, rval, 1, dvalue)
829 ritz_tol=dvalue(1)
830#endif
831 CASE ('TNU2')
832 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
833 DO ng=1,ngrids
834 DO itrc=1,nat
835 nl_tnu2(itrc,ng)=rtracer(itrc,ng)
836 END DO
837#ifdef T_PASSIVE
838 DO i=1,npt
839 itrc=inert(i)
840 nl_tnu2(itrc,ng)=rtracer(nat+i,ng)
841 END DO
842#endif
843 END DO
844 CASE ('TNU4')
845 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
846 DO ng=1,ngrids
847 DO itrc=1,nat
848 nl_tnu4(itrc,ng)=rtracer(itrc,ng)
849 END DO
850#ifdef T_PASSIVE
851 DO i=1,npt
852 itrc=inert(i)
853 nl_tnu4(itrc,ng)=rtracer(nat+i,ng)
854 END DO
855#endif
856 END DO
857 CASE ('ad_TNU2')
858 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
859 DO ng=1,ngrids
860 DO itrc=1,nat
861 ad_tnu2(itrc,ng)=rtracer(itrc,ng)
862 tl_tnu2(itrc,ng)=rtracer(itrc,ng)
863 END DO
864#ifdef T_PASSIVE
865 DO i=1,npt
866 itrc=inert(i)
867 ad_tnu2(itrc,ng)=rtracer(nat+i,ng)
868 tl_tnu2(itrc,ng)=rtracer(nat+i,ng)
869 END DO
870#endif
871 END DO
872 CASE ('ad_TNU4')
873 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
874 DO ng=1,ngrids
875 DO itrc=1,nat
876 ad_tnu4(itrc,ng)=rtracer(itrc,ng)
877 tl_tnu4(itrc,ng)=rtracer(itrc,ng)
878 END DO
879#ifdef T_PASSIVE
880 DO i=1,npt
881 itrc=inert(i)
882 ad_tnu4(itrc,ng)=rtracer(nat+i,ng)
883 tl_tnu4(itrc,ng)=rtracer(nat+i,ng)
884 END DO
885#endif
886 END DO
887 CASE ('VISC2')
888 npts=load_r(nval, rval, ngrids, nl_visc2)
889 CASE ('VISC4')
890 npts=load_r(nval, rval, ngrids, nl_visc4)
891 CASE ('ad_VISC2')
892 npts=load_r(nval, rval, ngrids, ad_visc2)
893 DO ng=1,ngrids
894 tl_visc2(ng)=ad_visc2(ng)
895 END DO
896 CASE ('ad_VISC4')
897 npts=load_r(nval, rval, ngrids, ad_visc4)
898 DO ng=1,ngrids
899 tl_visc4(ng)=ad_visc4(ng)
900 END DO
901 CASE ('LuvSponge')
902 npts=load_l(nval, cval, ngrids, luvsponge)
903#ifdef SOLVE3D
904 CASE ('LtracerSponge')
905 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
906 DO ng=1,ngrids
907 DO itrc=1,nat
908 ltracersponge(itrc,ng)=ltracer(itrc,ng)
909 END DO
910# ifdef T_PASSIVE
911 DO i=1,npt
912 itrc=inert(i)
913 ltracersponge(itrc,ng)=ltracer(nat+i,ng)
914 END DO
915# endif
916 END DO
917#endif
918 CASE ('AKT_BAK')
919 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
920 DO ng=1,ngrids
921 DO itrc=1,nat
922 akt_bak(itrc,ng)=rtracer(itrc,ng)
923 END DO
924# ifdef T_PASSIVE
925 DO i=1,npt
926 itrc=inert(i)
927 akt_bak(itrc,ng)=rtracer(nat+i,ng)
928 END DO
929# endif
930 END DO
931 CASE ('AKT_LIMIT')
932 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
933 DO ng=1,ngrids
934 DO itrc=1,nat
935 akt_limit(itrc,ng)=rtracer(itrc,ng)
936 END DO
937 END DO
938 CASE ('ad_AKT_fac')
939 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
940 DO ng=1,ngrids
941 DO itrc=1,nat
942 ad_akt_fac(itrc,ng)=rtracer(itrc,ng)
943 tl_akt_fac(itrc,ng)=rtracer(itrc,ng)
944 END DO
945# ifdef T_PASSIVE
946 DO i=1,npt
947 itrc=inert(i)
948 ad_akt_fac(itrc,ng)=rtracer(nat+i,ng)
949 tl_akt_fac(itrc,ng)=rtracer(nat+i,ng)
950 END DO
951# endif
952 END DO
953 CASE ('AKV_BAK')
954 npts=load_r(nval, rval, ngrids, akv_bak)
955 CASE ('AKV_LIMIT')
956 npts=load_r(nval, rval, ngrids, akv_limit)
957 CASE ('ad_AKV_fac')
958 npts=load_r(nval, rval, ngrids, ad_akv_fac)
959 DO ng=1,ngrids
960 tl_akv_fac(ng)=ad_akv_fac(ng)
961 END DO
962 CASE ('AKK_BAK')
963 npts=load_r(nval, rval, ngrids, akk_bak)
964 CASE ('AKP_BAK')
965 npts=load_r(nval, rval, ngrids, akp_bak)
966 CASE ('TKENU2')
967 npts=load_r(nval, rval, ngrids, tkenu2)
968 CASE ('TKENU4')
969 npts=load_r(nval, rval, ngrids, tkenu4)
970 CASE ('GLS_P')
971 npts=load_r(nval, rval, ngrids, gls_p)
972 CASE ('GLS_M')
973 npts=load_r(nval, rval, ngrids, gls_m)
974 CASE ('GLS_N')
975 npts=load_r(nval, rval, ngrids, gls_n)
976 CASE ('GLS_Kmin')
977 npts=load_r(nval, rval, ngrids, gls_kmin)
978 CASE ('GLS_Pmin')
979 npts=load_r(nval, rval, ngrids, gls_pmin)
980 CASE ('GLS_CMU0')
981 npts=load_r(nval, rval, ngrids, gls_cmu0)
982 CASE ('GLS_C1')
983 npts=load_r(nval, rval, ngrids, gls_c1)
984 CASE ('GLS_C2')
985 npts=load_r(nval, rval, ngrids, gls_c2)
986 CASE ('GLS_C3M')
987 npts=load_r(nval, rval, ngrids, gls_c3m)
988 CASE ('GLS_C3P')
989 npts=load_r(nval, rval, ngrids, gls_c3p)
990 CASE ('GLS_SIGK')
991 npts=load_r(nval, rval, ngrids, gls_sigk)
992 CASE ('GLS_SIGP')
993 npts=load_r(nval, rval, ngrids, gls_sigp)
994 CASE ('CHARNOK_ALPHA')
995 npts=load_r(nval, rval, ngrids, charnok_alpha)
996 CASE ('ZOS_HSIG_ALPHA')
997 npts=load_r(nval, rval, ngrids, zos_hsig_alpha)
998 CASE ('SZ_ALPHA')
999 npts=load_r(nval, rval, ngrids, sz_alpha)
1000 CASE ('CRGBAN_CW')
1001 npts=load_r(nval, rval, ngrids, crgban_cw)
1002 CASE ('WEC_ALPHA')
1003 npts=load_r(nval, rval, ngrids, wec_alpha)
1004 CASE ('RDRG')
1005 npts=load_r(nval, rval, ngrids, rdrg)
1006 CASE ('RDRG2')
1007 npts=load_r(nval, rval, ngrids, rdrg2)
1008 CASE ('Zob')
1009 npts=load_r(nval, rval, ngrids, zob)
1010 CASE ('Zos')
1011 npts=load_r(nval, rval, ngrids, zos)
1012#ifdef BULK_FLUXES
1013 CASE ('BLK_ZQ')
1014 npts=load_r(nval, rval, ngrids, blk_zq)
1015 CASE ('BLK_ZT')
1016 npts=load_r(nval, rval, ngrids, blk_zt)
1017 CASE ('BLK_ZW')
1018 npts=load_r(nval, rval, ngrids, blk_zw)
1019#endif
1020 CASE ('DCRIT')
1021 npts=load_r(nval, rval, ngrids, dcrit)
1022 CASE ('WTYPE')
1023 npts=load_i(nval, rval, ngrids, lmd_jwt)
1024 CASE ('LEVSFRC')
1025 npts=load_i(nval, rval, ngrids, levsfrc)
1026 CASE ('LEVBFRC')
1027 npts=load_i(nval, rval, ngrids, levbfrc)
1028 CASE ('Vtransform')
1029 npts=load_i(nval, rval, ngrids, vtransform)
1030 DO ng=1,ngrids
1031 IF ((vtransform(ng).lt.0).or. &
1032 & (vtransform(ng).gt.2)) THEN
1033 IF (master) WRITE (out,260) 'Vtransform = ', &
1034 & vtransform(ng), &
1035 & 'Must be either 1 or 2'
1036 exit_flag=5
1037 RETURN
1038 END IF
1039 END DO
1040 CASE ('Vstretching')
1041 npts=load_i(nval, rval, ngrids, vstretching)
1042 DO ng=1,ngrids
1043 IF ((vstretching(ng).lt.0).or. &
1044 & (vstretching(ng).gt.5)) THEN
1045 IF (master) WRITE (out,260) 'Vstretching = ', &
1046 & vstretching(ng), &
1047 & 'Must between 1 and 5'
1048 exit_flag=5
1049 RETURN
1050 END IF
1051 END DO
1052 CASE ('THETA_S')
1053 npts=load_r(nval, rval, ngrids, theta_s)
1054 CASE ('THETA_B')
1055 npts=load_r(nval, rval, ngrids, theta_b)
1056 CASE ('TCLINE')
1057 npts=load_r(nval, rval, ngrids, tcline)
1058 DO ng=1,ngrids
1059 hc(ng)=tcline(ng)
1060 END DO
1061 CASE ('RHO0')
1062 npts=load_r(nval, rval, 1, rvalue)
1063 rho0=rvalue(1)
1064 CASE ('BVF_BAK')
1065 npts=load_r(nval, rval, 1, rvalue)
1066 bvf_bak=rvalue(1)
1067#ifdef TIDE_GENERATING_FORCES
1068 CASE ('Lnodal')
1069 npts=load_l(nval, cval, 1, lvalue)
1070 lnodal=lvalue(1)
1071#endif
1072 CASE ('DSTART')
1073 npts=load_r(nval, rval, 1, dvalue)
1074 dstart=dvalue(1)
1075 CASE ('TIDE_START')
1076 npts=load_r(nval, rval, 1, dvalue)
1077 tide_start=dvalue(1)
1078 CASE ('TIME_REF')
1079 npts=load_r(nval, rval, 1, dvalue)
1080 time_ref=dvalue(1)
1081 CALL ref_clock (time_ref)
1082 CASE ('TNUDG')
1083 npts=load_r(nval, rval, nat+npt, ngrids, dtracer)
1084 DO ng=1,ngrids
1085 DO itrc=1,nat
1086 tnudg(itrc,ng)=dtracer(itrc,ng)
1087 END DO
1088#ifdef T_PASSIVE
1089 DO i=1,npt
1090 itrc=inert(i)
1091 tnudg(itrc,ng)=dtracer(nat+i,ng)
1092 END DO
1093#endif
1094 END DO
1095 CASE ('ZNUDG')
1096 npts=load_r(nval, rval, ngrids, znudg)
1097 CASE ('M2NUDG')
1098 npts=load_r(nval, rval, ngrids, m2nudg)
1099 CASE ('M3NUDG')
1100 npts=load_r(nval, rval, ngrids, m3nudg)
1101 CASE ('OBCFAC')
1102 npts=load_r(nval, rval, ngrids, obcfac)
1103 CASE ('R0')
1104 npts=load_r(nval, rval, ngrids, r0)
1105 DO ng=1,ngrids
1106 IF (r0(ng).lt.100.0_r8) r0(ng)=r0(ng)+1000.0_r8
1107 END DO
1108 CASE ('T0')
1109 npts=load_r(nval, rval, ngrids, t0)
1110 CASE ('S0')
1111 npts=load_r(nval, rval, ngrids, s0)
1112 CASE ('TCOEF')
1113 npts=load_r(nval, rval, ngrids, tcoef)
1114 DO ng=1,ngrids
1115 tcoef(ng)=abs(tcoef(ng))
1116 END DO
1117 CASE ('SCOEF')
1118 npts=load_r(nval, rval, ngrids, scoef)
1119 DO ng=1,ngrids
1120 scoef(ng)=abs(scoef(ng))
1121 END DO
1122 CASE ('GAMMA2')
1123 npts=load_r(nval, rval, ngrids, gamma2)
1124 CASE ('LuvSrc')
1125 npts=load_l(nval, cval, ngrids, luvsrc)
1126 CASE ('LwSrc')
1127 npts=load_l(nval, cval, ngrids, lwsrc)
1128#ifdef SOLVE3D
1129 CASE ('LtracerSrc')
1130 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
1131 DO ng=1,ngrids
1132 DO itrc=1,nat
1133 ltracersrc(itrc,ng)=ltracer(itrc,ng)
1134 END DO
1135# ifdef T_PASSIVE
1136 DO i=1,npt
1137 itrc=inert(i)
1138 ltracersrc(itrc,ng)=ltracer(nat+i,ng)
1139 END DO
1140# endif
1141 END DO
1142#endif
1143 CASE ('LsshCLM')
1144 npts=load_l(nval, cval, ngrids, lsshclm)
1145 CASE ('Lm2CLM')
1146 npts=load_l(nval, cval, ngrids, lm2clm)
1147#ifdef SOLVE3D
1148 CASE ('Lm3CLM')
1149 npts=load_l(nval, cval, ngrids, lm3clm)
1150 CASE ('LtracerCLM')
1151 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
1152 DO ng=1,ngrids
1153 DO itrc=1,nat
1154 ltracerclm(itrc,ng)=ltracer(itrc,ng)
1155 END DO
1156# ifdef T_PASSIVE
1157 DO i=1,npt
1158 itrc=inert(i)
1159 ltracerclm(itrc,ng)=ltracer(nat+i,ng)
1160 END DO
1161# endif
1162 END DO
1163#endif
1164 CASE ('LnudgeM2CLM')
1165 npts=load_l(nval, cval, ngrids, lnudgem2clm)
1166#ifdef SOLVE3D
1167 CASE ('LnudgeM3CLM')
1168 npts=load_l(nval, cval, ngrids, lnudgem3clm)
1169 CASE ('LnudgeTCLM')
1170 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
1171 DO ng=1,ngrids
1172 DO itrc=1,nat
1173 lnudgetclm(itrc,ng)=ltracer(itrc,ng)
1174 END DO
1175# ifdef T_PASSIVE
1176 DO i=1,npt
1177 itrc=inert(i)
1178 lnudgetclm(itrc,ng)=ltracer(nat+i,ng)
1179 END DO
1180# endif
1181 END DO
1182#endif
1183#if defined AD_SENSITIVITY || defined I4DVAR_ANA_SENSITIVITY || \
1184 defined opt_observations || defined sensitivity_4dvar || \
1185 defined so_semi
1186 CASE ('DstrS')
1187 npts=load_r(nval, rval, ngrids, dstrs)
1188 CASE ('DendS')
1189 npts=load_r(nval, rval, ngrids, dends)
1190# ifndef OBS_SPACE
1191 CASE ('KstrS')
1192 npts=load_i(nval, rval, ngrids, kstrs)
1193 CASE ('KendS')
1194 npts=load_i(nval, rval, ngrids, kends)
1195 CASE ('Lstate(isFsur)')
1196 IF (isfsur.eq.0) THEN
1197 IF (master) WRITE (out,280) 'isFsur'
1198 exit_flag=5
1199 RETURN
1200 END IF
1201 npts=load_l(nval, cval, ngrids, ladsen)
1202 DO ng=1,ngrids
1203 scalars(ng)%Lstate(isfsur)=ladsen(ng)
1204 END DO
1205 CASE ('Lstate(isUbar)')
1206 IF (isubar.eq.0) THEN
1207 IF (master) WRITE (out,280) 'isUbar'
1208 exit_flag=5
1209 RETURN
1210 END IF
1211 npts=load_l(nval, cval, ngrids, ladsen)
1212 DO ng=1,ngrids
1213 scalars(ng)%Lstate(isubar)=ladsen(ng)
1214 END DO
1215 CASE ('Lstate(isVbar)')
1216 IF (isvbar.eq.0) THEN
1217 IF (master) WRITE (out,280) 'isVbar'
1218 exit_flag=5
1219 RETURN
1220 END IF
1221 npts=load_l(nval, cval, ngrids, ladsen)
1222 DO ng=1,ngrids
1223 scalars(ng)%Lstate(isvbar)=ladsen(ng)
1224 END DO
1225# ifdef SOLVE3D
1226 CASE ('Lstate(isUvel)')
1227 IF (isuvel.eq.0) THEN
1228 IF (master) WRITE (out,280) 'isUvel'
1229 exit_flag=5
1230 RETURN
1231 END IF
1232 npts=load_l(nval, cval, ngrids, ladsen)
1233 DO ng=1,ngrids
1234 scalars(ng)%Lstate(isuvel)=ladsen(ng)
1235 END DO
1236 CASE ('Lstate(isVvel)')
1237 IF (isvvel.eq.0) THEN
1238 IF (master) WRITE (out,280) 'isVvel'
1239 exit_flag=5
1240 RETURN
1241 END IF
1242 npts=load_l(nval, cval, ngrids, ladsen)
1243 DO ng=1,ngrids
1244 scalars(ng)%Lstate(isvvel)=ladsen(ng)
1245 END DO
1246 CASE ('Lstate(isWvel)')
1247 IF (iswvel.eq.0) THEN
1248 IF (master) WRITE (out,280) 'isWvel'
1249 exit_flag=5
1250 RETURN
1251 END IF
1252 npts=load_l(nval, cval, ngrids, ladsen)
1253 DO ng=1,ngrids
1254 scalars(ng)%Lstate(iswvel)=ladsen(ng)
1255 END DO
1256 CASE ('Lstate(isTvar)')
1257 IF (maxval(istvar).eq.0) THEN
1258 IF (master) WRITE (out,280) 'isTvar'
1259 exit_flag=5
1260 RETURN
1261 END IF
1262 npts=load_l(nval, cval, mt*ngrids, ladsen)
1263 k=0
1264 DO ng=1,ngrids
1265 DO itrc=1,mt
1266 k=k+1
1267 i=istvar(itrc)
1268 scalars(ng)%Lstate(i)=ladsen(k)
1269 END DO
1270 END DO
1271# endif
1272# endif
1273#endif
1274#if defined FORCING_SV || defined SO_SEMI || \
1275 defined stochastic_opt
1276 CASE ('Fstate(isFsur)')
1277 IF (isfsur.eq.0) THEN
1278 IF (master) WRITE (out,280) 'isFsur'
1279 exit_flag=5
1280 RETURN
1281 END IF
1282 npts=load_l(nval, cval, ngrids, ladsen)
1283 DO ng=1,ngrids
1284 scalars(ng)%Fstate(isfsur)=ladsen(ng)
1285 END DO
1286 CASE ('Fstate(isUbar)')
1287 IF (isubar.eq.0) THEN
1288 IF (master) WRITE (out,280) 'isUbar'
1289 exit_flag=5
1290 RETURN
1291 END IF
1292 npts=load_l(nval, cval, ngrids, ladsen)
1293 DO ng=1,ngrids
1294 scalars(ng)%Fstate(isubar)=ladsen(ng)
1295 END DO
1296 CASE ('Fstate(isVbar)')
1297 IF (isvbar.eq.0) THEN
1298 IF (master) WRITE (out,280) 'isVbar'
1299 exit_flag=5
1300 RETURN
1301 END IF
1302 npts=load_l(nval, cval, ngrids, ladsen)
1303 DO ng=1,ngrids
1304 scalars(ng)%Fstate(isvbar)=ladsen(ng)
1305 END DO
1306# ifdef SOLVE3D
1307 CASE ('Fstate(isUvel)')
1308 IF (isuvel.eq.0) THEN
1309 IF (master) WRITE (out,280) 'isUvel'
1310 exit_flag=5
1311 RETURN
1312 END IF
1313 npts=load_l(nval, cval, ngrids, ladsen)
1314 DO ng=1,ngrids
1315 scalars(ng)%Fstate(isuvel)=ladsen(ng)
1316 END DO
1317 CASE ('Fstate(isVvel)')
1318 IF (isvvel.eq.0) THEN
1319 IF (master) WRITE (out,280) 'isVvel'
1320 exit_flag=5
1321 RETURN
1322 END IF
1323 npts=load_l(nval, cval, ngrids, ladsen)
1324 DO ng=1,ngrids
1325 scalars(ng)%Fstate(isvvel)=ladsen(ng)
1326 END DO
1327 CASE ('Fstate(isTvar)')
1328 IF (maxval(istvar).eq.0) THEN
1329 IF (master) WRITE (out,280) 'isTvar'
1330 exit_flag=5
1331 RETURN
1332 END IF
1333 npts=load_l(nval, cval, mt*ngrids, ladsen)
1334 k=0
1335 DO ng=1,ngrids
1336 DO itrc=1,mt
1337 k=k+1
1338 i=istvar(itrc)
1339 scalars(ng)%Fstate(i)=ladsen(k)
1340 END DO
1341 END DO
1342# endif
1343 CASE ('Fstate(isUstr)')
1344 IF (isustr.eq.0) THEN
1345 IF (master) WRITE (out,280) 'isUstr'
1346 exit_flag=5
1347 RETURN
1348 END IF
1349 npts=load_l(nval, cval, ngrids, ladsen)
1350 DO ng=1,ngrids
1351 scalars(ng)%Fstate(isustr)=ladsen(ng)
1352 END DO
1353 CASE ('Fstate(isVstr)')
1354 IF (isustr.eq.0) THEN
1355 IF (master) WRITE (out,280) 'isVstr'
1356 exit_flag=5
1357 RETURN
1358 END IF
1359 npts=load_l(nval, cval, ngrids, ladsen)
1360 DO ng=1,ngrids
1361 scalars(ng)%Fstate(isvstr)=ladsen(ng)
1362 END DO
1363# ifdef SOLVE3D
1364 CASE ('Fstate(isTsur)')
1365 IF (maxval(istsur).eq.0) THEN
1366 IF (master) WRITE (out,280) 'isTsur'
1367 exit_flag=5
1368 RETURN
1369 END IF
1370 npts=load_l(nval, cval, mt*ngrids, ladsen)
1371 k=0
1372 DO ng=1,ngrids
1373 DO itrc=1,mt
1374 k=k+1
1375 i=istsur(itrc)
1376 scalars(ng)%Fstate(i)=ladsen(k)
1377 END DO
1378 END DO
1379# endif
1380#endif
1381#if defined SO_SEMI || \
1382 (defined stochastic_opt && !defined STOCH_OPT_WHITE)
1383 CASE ('SO_decay')
1384 npts=load_r(nval, rval, ngrids, so_decay)
1385 CASE ('SO_sdev(isFsur)')
1386 npts=load_r(nval, rval, ngrids, so_sdev(isfsur,1))
1387 CASE ('SO_sdev(isUbar)')
1388 npts=load_r(nval, rval, ngrids, so_sdev(isubar,1))
1389 CASE ('SO_sdev(isVbar)')
1390 npts=load_r(nval, rval, ngrids, so_sdev(isvbar,1))
1391# ifdef SOLVE3D
1392 CASE ('SO_sdev(isUvel)')
1393 npts=load_r(nval, rval, ngrids, so_sdev(isuvel,1))
1394 CASE ('SO_sdev(isVvel)')
1395 npts=load_r(nval, rval, ngrids, so_sdev(isvvel,1))
1396 CASE ('SO_sdev(isTvar)')
1397 npts=load_r(nval, rval, mt, ngrids, tracer)
1398 k=0
1399 DO ng=1,ngrids
1400 DO itrc=1,mt
1401 k=k+1
1402 i=istvar(itrc)
1403 so_sdev(i,ng)=tracer(k,ng)
1404 END DO
1405 END DO
1406# endif
1407 CASE ('SO_sdev(isUstr)')
1408 npts=load_r(nval, rval, ngrids, so_sdev(isustr,1))
1409 CASE ('SO_sdev(isVstr)')
1410 npts=load_r(nval, rval, ngrids, so_sdev(isvstr,1))
1411# ifdef SOLVE3D
1412 CASE ('SO_sdev(isTsur)')
1413 npts=load_r(nval, rval, mt, ngrids, tracer)
1414 k=0
1415 DO ng=1,ngrids
1416 DO itrc=1,mt
1417 k=k+1
1418 i=istsur(itrc)
1419 so_sdev(i,ng)=tracer(k,ng)
1420 END DO
1421 END DO
1422# endif
1423#endif
1424 CASE ('Hout(idUvel)')
1425 IF (iduvel.eq.0) THEN
1426 IF (master) WRITE (out,280) 'idUvel'
1427 exit_flag=5
1428 RETURN
1429 END IF
1430 npts=load_l(nval, cval, ngrids, lswitch)
1431 hout(iduvel,1:ngrids)=lswitch(1:ngrids)
1432 CASE ('Hout(idVvel)')
1433 IF (idvvel.eq.0) THEN
1434 IF (master) WRITE (out,280) 'idVvel'
1435 exit_flag=5
1436 RETURN
1437 END IF
1438 npts=load_l(nval, cval, ngrids, lswitch)
1439 hout(idvvel,1:ngrids)=lswitch(1:ngrids)
1440 CASE ('Hout(idWvel)')
1441 IF (idwvel.eq.0) THEN
1442 IF (master) WRITE (out,280) 'idWvel'
1443 exit_flag=5
1444 RETURN
1445 END IF
1446 npts=load_l(nval, cval, ngrids, lswitch)
1447 hout(idwvel,1:ngrids)=lswitch(1:ngrids)
1448 CASE ('Hout(idOvel)')
1449 IF (idovel.eq.0) THEN
1450 IF (master) WRITE (out,280) 'idOvel'
1451 exit_flag=5
1452 RETURN
1453 END IF
1454 npts=load_l(nval, cval, ngrids, lswitch)
1455 hout(idovel,1:ngrids)=lswitch(1:ngrids)
1456# if defined OMEGA_IMPLICIT && defined SOLVE3D
1457 CASE ('Hout(idOvil)')
1458 IF (idovil.eq.0) THEN
1459 IF (master) WRITE (out,280) 'idOvil'
1460 exit_flag=5
1461 RETURN
1462 END IF
1463 npts=load_l(nval, cval, ngrids, lswitch)
1464 hout(idovel,1:ngrids)=lswitch(1:ngrids)
1465# endif
1466 CASE ('Hout(idUbar)')
1467 IF (idubar.eq.0) THEN
1468 IF (master) WRITE (out,280) 'idUbar'
1469 exit_flag=5
1470 RETURN
1471 END IF
1472 npts=load_l(nval, cval, ngrids, lswitch)
1473 hout(idubar,1:ngrids)=lswitch(1:ngrids)
1474 CASE ('Hout(idVbar)')
1475 IF (idvbar.eq.0) THEN
1476 IF (master) WRITE (out,280) 'idVbar'
1477 exit_flag=5
1478 RETURN
1479 END IF
1480 npts=load_l(nval, cval, ngrids, lswitch)
1481 hout(idvbar,1:ngrids)=lswitch(1:ngrids)
1482 CASE ('Hout(idFsur)')
1483 IF (idfsur.eq.0) THEN
1484 IF (master) WRITE (out,280) 'idFsur'
1485 exit_flag=5
1486 RETURN
1487 END IF
1488 npts=load_l(nval, cval, ngrids, lswitch)
1489 hout(idfsur,1:ngrids)=lswitch(1:ngrids)
1490#if defined SEDIMENT && defined SED_MORPH
1491 CASE ('Hout(idBath)')
1492 IF (idbath.eq.0) THEN
1493 IF (master) WRITE (out,280) 'idbath'
1494 exit_flag=5
1495 RETURN
1496 END IF
1497 npts=load_l(nval, cval, ngrids, lswitch)
1498 hout(idbath,1:ngrids)=lswitch(1:ngrids)
1499#endif
1500 CASE ('Hout(idu2dE)')
1501 IF (idu2de.eq.0) THEN
1502 IF (master) WRITE (out,280) 'idu2dE'
1503 exit_flag=5
1504 RETURN
1505 END IF
1506 npts=load_l(nval, cval, ngrids, lswitch)
1507 hout(idu2de,1:ngrids)=lswitch(1:ngrids)
1508 CASE ('Hout(idv2dN)')
1509 IF (idv2dn.eq.0) THEN
1510 IF (master) WRITE (out,280) 'idv2dN'
1511 exit_flag=5
1512 RETURN
1513 END IF
1514 npts=load_l(nval, cval, ngrids, lswitch)
1515 hout(idv2dn,1:ngrids)=lswitch(1:ngrids)
1516 CASE ('Hout(idu3dE)')
1517 IF (idu3de.eq.0) THEN
1518 IF (master) WRITE (out,280) 'idu3dE'
1519 exit_flag=5
1520 RETURN
1521 END IF
1522 npts=load_l(nval, cval, ngrids, lswitch)
1523 hout(idu3de,1:ngrids)=lswitch(1:ngrids)
1524 CASE ('Hout(idv3dN)')
1525 IF (idv3dn.eq.0) THEN
1526 IF (master) WRITE (out,280) 'idv3dN'
1527 exit_flag=5
1528 RETURN
1529 END IF
1530 npts=load_l(nval, cval, ngrids, lswitch)
1531 hout(idv3dn,1:ngrids)=lswitch(1:ngrids)
1532#ifdef SOLVE3D
1533 CASE ('Hout(idTvar)')
1534 IF (maxval(idtvar).eq.0) THEN
1535 IF (master) WRITE (out,280) 'idTvar'
1536 exit_flag=5
1537 RETURN
1538 END IF
1539 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
1540 DO ng=1,ngrids
1541 DO itrc=1,nat
1542 i=idtvar(itrc)
1543 hout(i,ng)=ltracer(itrc,ng)
1544 END DO
1545 END DO
1546#endif
1547 CASE ('Hout(idpthR)')
1548 IF (idpthr.eq.0) THEN
1549 IF (master) WRITE (out,280) 'idpthR'
1550 exit_flag=5
1551 RETURN
1552 END IF
1553 npts=load_l(nval, cval, ngrids, lswitch)
1554 hout(idpthr,1:ngrids)=lswitch(1:ngrids)
1555 CASE ('Hout(idpthU)')
1556 IF (idpthu.eq.0) THEN
1557 IF (master) WRITE (out,280) 'idpthU'
1558 exit_flag=5
1559 RETURN
1560 END IF
1561 npts=load_l(nval, cval, ngrids, lswitch)
1562 hout(idpthu,1:ngrids)=lswitch(1:ngrids)
1563 CASE ('Hout(idpthV)')
1564 IF (idpthv.eq.0) THEN
1565 IF (master) WRITE (out,280) 'idpthV'
1566 exit_flag=5
1567 RETURN
1568 END IF
1569 npts=load_l(nval, cval, ngrids, lswitch)
1570 hout(idpthv,1:ngrids)=lswitch(1:ngrids)
1571 CASE ('Hout(idpthW)')
1572 IF (idpthw.eq.0) THEN
1573 IF (master) WRITE (out,280) 'idpthW'
1574 exit_flag=5
1575 RETURN
1576 END IF
1577 npts=load_l(nval, cval, ngrids, lswitch)
1578 hout(idpthw,1:ngrids)=lswitch(1:ngrids)
1579 CASE ('Hout(idUsms)')
1580 IF (idusms.eq.0) THEN
1581 IF (master) WRITE (out,280) 'idUsms'
1582 exit_flag=5
1583 RETURN
1584 END IF
1585 npts=load_l(nval, cval, ngrids, lswitch)
1586 hout(idusms,1:ngrids)=lswitch(1:ngrids)
1587 CASE ('Hout(idVsms)')
1588 IF (idvsms.eq.0) THEN
1589 IF (master) WRITE (out,280) 'idVsms'
1590 exit_flag=5
1591 RETURN
1592 END IF
1593 npts=load_l(nval, cval, ngrids, lswitch)
1594 hout(idvsms,1:ngrids)=lswitch(1:ngrids)
1595 CASE ('Hout(idUbms)')
1596 IF (idubms.eq.0) THEN
1597 IF (master) WRITE (out,280) 'idUbms'
1598 exit_flag=5
1599 RETURN
1600 END IF
1601 npts=load_l(nval, cval, ngrids, lswitch)
1602 hout(idubms,1:ngrids)=lswitch(1:ngrids)
1603 CASE ('Hout(idVbms)')
1604 IF (idvbms.eq.0) THEN
1605 IF (master) WRITE (out,280) 'idVbms'
1606 exit_flag=5
1607 RETURN
1608 END IF
1609 npts=load_l(nval, cval, ngrids, lswitch)
1610 hout(idvbms,1:ngrids)=lswitch(1:ngrids)
1611#ifdef BBL_MODEL
1612 CASE ('Hout(idUbrs)')
1613 IF (idubrs.eq.0) THEN
1614 IF (master) WRITE (out,280) 'idUbrs'
1615 exit_flag=5
1616 RETURN
1617 END IF
1618 npts=load_l(nval, cval, ngrids, lswitch)
1619 hout(idubrs,1:ngrids)=lswitch(1:ngrids)
1620 CASE ('Hout(idVbrs)')
1621 IF (idvbrs.eq.0) THEN
1622 IF (master) WRITE (out,280) 'idVbrs'
1623 exit_flag=5
1624 RETURN
1625 END IF
1626 npts=load_l(nval, cval, ngrids, lswitch)
1627 hout(idvbrs,1:ngrids)=lswitch(1:ngrids)
1628 CASE ('Hout(idUbws)')
1629 IF (idubws.eq.0) THEN
1630 IF (master) WRITE (out,280) 'idUbws'
1631 exit_flag=5
1632 RETURN
1633 END IF
1634 npts=load_l(nval, cval, ngrids, lswitch)
1635 hout(idubws,1:ngrids)=lswitch(1:ngrids)
1636 CASE ('Hout(idVbws)')
1637 IF (idvbws.eq.0) THEN
1638 IF (master) WRITE (out,280) 'idVbws'
1639 exit_flag=5
1640 RETURN
1641 END IF
1642 npts=load_l(nval, cval, ngrids, lswitch)
1643 hout(idvbws,1:ngrids)=lswitch(1:ngrids)
1644 CASE ('Hout(idUbcs)')
1645 IF (idubcs.eq.0) THEN
1646 IF (master) WRITE (out,280) 'idUbcs'
1647 exit_flag=5
1648 RETURN
1649 END IF
1650 npts=load_l(nval, cval, ngrids, lswitch)
1651 hout(idubcs,1:ngrids)=lswitch(1:ngrids)
1652 CASE ('Hout(idVbcs)')
1653 IF (idvbcs.eq.0) THEN
1654 IF (master) WRITE (out,280) 'idVbcs'
1655 exit_flag=5
1656 RETURN
1657 END IF
1658 npts=load_l(nval, cval, ngrids, lswitch)
1659 hout(idvbcs,1:ngrids)=lswitch(1:ngrids)
1660 CASE ('Hout(idUVwc)')
1661 IF (iduvwc.eq.0) THEN
1662 IF (master) WRITE (out,280) 'idUVwc'
1663 exit_flag=5
1664 RETURN
1665 END IF
1666 npts=load_l(nval, cval, ngrids, lswitch)
1667 hout(iduvwc,1:ngrids)=lswitch(1:ngrids)
1668 CASE ('Hout(idUbot)')
1669 IF (idubot.eq.0) THEN
1670 IF (master) WRITE (out,280) 'idUbot'
1671 exit_flag=5
1672 RETURN
1673 END IF
1674 npts=load_l(nval, cval, ngrids, lswitch)
1675 hout(idubot,1:ngrids)=lswitch(1:ngrids)
1676 CASE ('Hout(idVbot)')
1677 IF (idvbot.eq.0) THEN
1678 IF (master) WRITE (out,280) 'idVbot'
1679 exit_flag=5
1680 RETURN
1681 END IF
1682 npts=load_l(nval, cval, ngrids, lswitch)
1683 hout(idvbot,1:ngrids)=lswitch(1:ngrids)
1684 CASE ('Hout(idUbur)')
1685 IF (idubur.eq.0) THEN
1686 IF (master) WRITE (out,280) 'idUbur'
1687 exit_flag=5
1688 RETURN
1689 END IF
1690 npts=load_l(nval, cval, ngrids, lswitch)
1691 hout(idubur,1:ngrids)=lswitch(1:ngrids)
1692 CASE ('Hout(idVbvr)')
1693 IF (idvbvr.eq.0) THEN
1694 IF (master) WRITE (out,280) 'idVbvr'
1695 exit_flag=5
1696 RETURN
1697 END IF
1698 npts=load_l(nval, cval, ngrids, lswitch)
1699 hout(idvbvr,1:ngrids)=lswitch(1:ngrids)
1700#endif
1701#ifdef WEC_VF
1702 CASE ('Hout(idWztw)')
1703 IF (idwztw.eq.0) THEN
1704 IF (master) WRITE (out,280) 'idWztw'
1705 exit_flag=5
1706 RETURN
1707 END IF
1708 npts=load_l(nval, cval, ngrids, lswitch)
1709 hout(idwztw,1:ngrids)=lswitch(1:ngrids)
1710 CASE ('Hout(idWqsp)')
1711 IF (idwqsp.eq.0) THEN
1712 IF (master) WRITE (out,280) 'idWqsp'
1713 exit_flag=5
1714 RETURN
1715 END IF
1716 npts=load_l(nval, cval, ngrids, lswitch)
1717 hout(idwqsp,1:ngrids)=lswitch(1:ngrids)
1718 CASE ('Hout(idWbeh)')
1719 IF (idwbeh.eq.0) THEN
1720 IF (master) WRITE (out,280) 'idWbeh'
1721 exit_flag=5
1722 RETURN
1723 END IF
1724 npts=load_l(nval, cval, ngrids, lswitch)
1725 hout(idwbeh,1:ngrids)=lswitch(1:ngrids)
1726#endif
1727#ifdef WEC
1728 CASE ('Hout(idU2rs)')
1729 IF (idu2rs.eq.0) THEN
1730 IF (master) WRITE (out,280) 'idU2rs'
1731 exit_flag=5
1732 RETURN
1733 END IF
1734 npts=load_l(nval, cval, ngrids, lswitch)
1735 hout(idu2rs,1:ngrids)=lswitch(1:ngrids)
1736 CASE ('Hout(idV2rs)')
1737 IF (idv2rs.eq.0) THEN
1738 IF (master) WRITE (out,280) 'idV2rs'
1739 exit_flag=5
1740 RETURN
1741 END IF
1742 npts=load_l(nval, cval, ngrids, lswitch)
1743 hout(idv2rs,1:ngrids)=lswitch(1:ngrids)
1744 CASE ('Hout(idU3rs)')
1745 IF (idu3rs.eq.0) THEN
1746 IF (master) WRITE (out,280) 'idU3rs'
1747 exit_flag=5
1748 RETURN
1749 END IF
1750 npts=load_l(nval, cval, ngrids, lswitch)
1751 hout(idu3rs,1:ngrids)=lswitch(1:ngrids)
1752 CASE ('Hout(idV3rs)')
1753 IF (idv3rs.eq.0) THEN
1754 IF (master) WRITE (out,280) 'idV3rs'
1755 exit_flag=5
1756 RETURN
1757 END IF
1758 npts=load_l(nval, cval, ngrids, lswitch)
1759 hout(idv3rs,1:ngrids)=lswitch(1:ngrids)
1760 CASE ('Hout(idU2Sd)')
1761 IF (idu2sd.eq.0) THEN
1762 IF (master) WRITE (out,280) 'idU2Sd'
1763 exit_flag=5
1764 RETURN
1765 END IF
1766 npts=load_l(nval, cval, ngrids, lswitch)
1767 hout(idu2sd,1:ngrids)=lswitch(1:ngrids)
1768 CASE ('Hout(idV2Sd)')
1769 IF (idv2sd.eq.0) THEN
1770 IF (master) WRITE (out,280) 'idV2Sd'
1771 exit_flag=5
1772 RETURN
1773 END IF
1774 npts=load_l(nval, cval, ngrids, lswitch)
1775 hout(idv2sd,1:ngrids)=lswitch(1:ngrids)
1776 CASE ('Hout(idU3Sd)')
1777 IF (idu3sd.eq.0) THEN
1778 IF (master) WRITE (out,280) 'idU3Sd'
1779 exit_flag=5
1780 RETURN
1781 END IF
1782 npts=load_l(nval, cval, ngrids, lswitch)
1783 hout(idu3sd,1:ngrids)=lswitch(1:ngrids)
1784 CASE ('Hout(idV3Sd)')
1785 IF (idv3sd.eq.0) THEN
1786 IF (master) WRITE (out,280) 'idV3Sd'
1787 exit_flag=5
1788 RETURN
1789 END IF
1790 npts=load_l(nval, cval, ngrids, lswitch)
1791 hout(idv3sd,1:ngrids)=lswitch(1:ngrids)
1792 CASE ('Hout(idW3Sd)')
1793 IF (idw3sd.eq.0) THEN
1794 IF (master) WRITE (out,280) 'idW3Sd'
1795 exit_flag=5
1796 RETURN
1797 END IF
1798 npts=load_l(nval, cval, ngrids, lswitch)
1799 hout(idw3sd,1:ngrids)=lswitch(1:ngrids)
1800 CASE ('Hout(idW3St)')
1801 IF (idw3st.eq.0) THEN
1802 IF (master) WRITE (out,280) 'idW3St'
1803 exit_flag=5
1804 RETURN
1805 END IF
1806 npts=load_l(nval, cval, ngrids, lswitch)
1807 hout(idw3st,1:ngrids)=lswitch(1:ngrids)
1808#endif
1809#ifdef WAVES_HEIGHT
1810 CASE ('Hout(idWamp)')
1811 IF (idwamp.eq.0) THEN
1812 IF (master) WRITE (out,280) 'idWamp'
1813 exit_flag=5
1814 RETURN
1815 END IF
1816 npts=load_l(nval, cval, ngrids, lswitch)
1817 hout(idwamp,1:ngrids)=lswitch(1:ngrids)
1818#endif
1819#ifdef WAVES_LENGTH
1820
1821 CASE ('Hout(idWlen)')
1822 IF (idwlen.eq.0) THEN
1823 IF (master) WRITE (out,280) 'idWlen'
1824 exit_flag=5
1825 RETURN
1826 END IF
1827 npts=load_l(nval, cval, ngrids, lswitch)
1828 hout(idwlen,1:ngrids)=lswitch(1:ngrids)
1829#endif
1830#ifdef WAVES_LENGTHP
1831 CASE ('Hout(idWlep)')
1832 IF (idwlep.eq.0) THEN
1833 IF (master) WRITE (out,280) 'idWlep'
1834 exit_flag=5
1835 RETURN
1836 END IF
1837 npts=load_l(nval, cval, ngrids, lswitch)
1838 hout(idwlep,1:ngrids)=lswitch(1:ngrids)
1839#endif
1840#ifdef WAVES_DIR
1841 CASE ('Hout(idWdir)')
1842 IF (idwdir.eq.0) THEN
1843 IF (master) WRITE (out,280) 'idWdir'
1844 exit_flag=5
1845 RETURN
1846 END IF
1847 npts=load_l(nval, cval, ngrids, lswitch)
1848 hout(idwdir,1:ngrids)=lswitch(1:ngrids)
1849#endif
1850#ifdef WAVES_DIRP
1851 CASE ('Hout(idWdip)')
1852 IF (idwdip.eq.0) THEN
1853 IF (master) WRITE (out,280) 'idWdip'
1854 exit_flag=5
1855 RETURN
1856 END IF
1857 npts=load_l(nval, cval, ngrids, lswitch)
1858 hout(idwdip,1:ngrids)=lswitch(1:ngrids)
1859#endif
1860#ifdef WAVES_TOP_PERIOD
1861 CASE ('Hout(idWptp)')
1862 IF (idwptp.eq.0) THEN
1863 IF (master) WRITE (out,280) 'idWptp'
1864 exit_flag=5
1865 RETURN
1866 END IF
1867 npts=load_l(nval, cval, ngrids, lswitch)
1868 hout(idwptp,1:ngrids)=lswitch(1:ngrids)
1869#endif
1870#ifdef WAVES_BOT_PERIOD
1871 CASE ('Hout(idWpbt)')
1872 IF (idwpbt.eq.0) THEN
1873 IF (master) WRITE (out,280) 'idWpbt'
1874 exit_flag=5
1875 RETURN
1876 END IF
1877 npts=load_l(nval, cval, ngrids, lswitch)
1878 hout(idwpbt,1:ngrids)=lswitch(1:ngrids)
1879#endif
1880#if defined BBL_MODEL || defined BEDLOAD_SOULSBY || \
1881 defined bedload_vandera || defined wav_coupling
1882 CASE ('Hout(idWorb)')
1883 IF (idworb.eq.0) THEN
1884 IF (master) WRITE (out,280) 'idWorb'
1885 exit_flag=5
1886 RETURN
1887 END IF
1888 npts=load_l(nval, cval, ngrids, lswitch)
1889 hout(idworb,1:ngrids)=lswitch(1:ngrids)
1890#endif
1891#if defined ROLLER_SVENDSEN
1892 CASE ('Hout(idWbrk)')
1893 IF (idwbrk.eq.0) THEN
1894 IF (master) WRITE (out,280) 'idWbrk'
1895 exit_flag=5
1896 RETURN
1897 END IF
1898 npts=load_l(nval, cval, ngrids, lswitch)
1899 hout(idwbrk,1:ngrids)=lswitch(1:ngrids)
1900#endif
1901#if defined UV_KIRBY
1902 CASE ('Hout(idUwav)')
1903 IF (iduwav.eq.0) THEN
1904 IF (master) WRITE (out,280) 'idUwav'
1905 exit_flag=5
1906 RETURN
1907 END IF
1908 npts=load_l(nval, cval, ngrids, lswitch)
1909 hout(iduwav,1:ngrids)=lswitch(1:ngrids)
1910 CASE ('Hout(idVwav)')
1911 IF (idvwav.eq.0) THEN
1912 IF (master) WRITE (out,280) 'idVwav'
1913 exit_flag=5
1914 RETURN
1915 END IF
1916 npts=load_l(nval, cval, ngrids, lswitch)
1917 hout(idvwav,1:ngrids)=lswitch(1:ngrids)
1918#endif
1919#if defined WAV_COUPLING || (defined WEC_VF && defined BOTTOM_STREAMING)
1920 CASE ('Hout(idWdif)')
1921 IF (idwdif.eq.0) THEN
1922 IF (master) WRITE (out,280) 'idWdif'
1923 exit_flag=5
1924 RETURN
1925 END IF
1926 npts=load_l(nval, cval, ngrids, lswitch)
1927 hout(idwdif,1:ngrids)=lswitch(1:ngrids)
1928#endif
1929#if defined TKE_WAVEDISS || defined WAV_COUPLING || \
1930 defined wdiss_thorguza || defined wdiss_churthor || \
1931 defined waves_diss || defined wdiss_inwave
1932 CASE ('Hout(idWdib)')
1933 IF (idwdib.eq.0) THEN
1934 IF (master) WRITE (out,280) 'idWdib'
1935 exit_flag=5
1936 RETURN
1937 END IF
1938 npts=load_l(nval, cval, ngrids, lswitch)
1939 hout(idwdib,1:ngrids)=lswitch(1:ngrids)
1940 CASE ('Hout(idWdiw)')
1941 IF (idwdiw.eq.0) THEN
1942 IF (master) WRITE (out,280) 'idWdiw'
1943 exit_flag=5
1944 RETURN
1945 END IF
1946 npts=load_l(nval, cval, ngrids, lswitch)
1947 hout(idwdiw,1:ngrids)=lswitch(1:ngrids)
1948#endif
1949#if defined WEC_ROLLER
1950 CASE ('Hout(idWdis)')
1951 IF (idwdis.eq.0) THEN
1952 IF (master) WRITE (out,280) 'idWdis'
1953 exit_flag=5
1954 RETURN
1955 END IF
1956 npts=load_l(nval, cval, ngrids, lswitch)
1957 hout(idwdis,1:ngrids)=lswitch(1:ngrids)
1958 CASE ('Hout(idWrol)')
1959 IF (idwrol.eq.0) THEN
1960 IF (master) WRITE (out,280) 'idWrol'
1961 exit_flag=5
1962 RETURN
1963 END IF
1964 npts=load_l(nval, cval, ngrids, lswitch)
1965 hout(idwrol,1:ngrids)=lswitch(1:ngrids)
1966#endif
1967#if defined WAVES_DSPR
1968 CASE ('Hout(idWvds)')
1969 IF (idwvds.eq.0) THEN
1970 IF (master) WRITE (out,280) 'idWvds'
1971 exit_flag=5
1972 RETURN
1973 END IF
1974 npts=load_l(nval, cval, ngrids, lswitch)
1975 hout(idwvds,1:ngrids)=lswitch(1:ngrids)
1976 CASE ('Hout(idWvqp)')
1977 IF (idwvqp.eq.0) THEN
1978 IF (master) WRITE (out,280) 'idWvqp'
1979 exit_flag=5
1980 RETURN
1981 END IF
1982 npts=load_l(nval, cval, ngrids, lswitch)
1983 hout(idwvqp,1:ngrids)=lswitch(1:ngrids)
1984#endif
1985#if defined INWAVE_MODEL
1986 CASE ('Hout(idACen)')
1987 IF (idacen.eq.0) THEN
1988 IF (master) WRITE (out,280) 'idACen'
1989 exit_flag=5
1990 RETURN
1991 END IF
1992 npts=load_l(nval, cval, ngrids, lswitch)
1993 hout(idacen,1:ngrids)=lswitch(1:ngrids)
1994 CASE ('Hout(idACct)')
1995 IF (idacct.eq.0) THEN
1996 IF (master) WRITE (out,280) 'idACct'
1997 exit_flag=5
1998 RETURN
1999 END IF
2000 npts=load_l(nval, cval, ngrids, lswitch)
2001 hout(idacct,1:ngrids)=lswitch(1:ngrids)
2002 CASE ('Hout(idACcx)')
2003 IF (idaccx.eq.0) THEN
2004 IF (master) WRITE (out,280) 'idACcx'
2005 exit_flag=5
2006 RETURN
2007 END IF
2008 npts=load_l(nval, cval, ngrids, lswitch)
2009 hout(idaccx,1:ngrids)=lswitch(1:ngrids)
2010 CASE ('Hout(idACcy)')
2011 IF (idaccy.eq.0) THEN
2012 IF (master) WRITE (out,280) 'idACcy'
2013 exit_flag=5
2014 RETURN
2015 END IF
2016 npts=load_l(nval, cval, ngrids, lswitch)
2017 hout(idaccy,1:ngrids)=lswitch(1:ngrids)
2018 CASE ('Hout(idACtp)')
2019 IF (idactp.eq.0) THEN
2020 IF (master) WRITE (out,280) 'idACtp'
2021 exit_flag=5
2022 RETURN
2023 END IF
2024 npts=load_l(nval, cval, ngrids, lswitch)
2025 hout(idactp,1:ngrids)=lswitch(1:ngrids)
2026#endif
2027#ifdef SOLVE3D
2028# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
2029 CASE ('Hout(idPair)')
2030 IF (idpair.eq.0) THEN
2031 IF (master) WRITE (out,280) 'idPair'
2032 exit_flag=5
2033 RETURN
2034 END IF
2035 npts=load_l(nval, cval, ngrids, lswitch)
2036 hout(idpair,1:ngrids)=lswitch(1:ngrids)
2037# endif
2038# if defined BULK_FLUXES
2039 CASE ('Hout(idTair)')
2040 IF (idtair.eq.0) THEN
2041 IF (master) WRITE (out,280) 'idTair'
2042 exit_flag=5
2043 RETURN
2044 END IF
2045 npts=load_l(nval, cval, ngrids, lswitch)
2046 hout(idtair,1:ngrids)=lswitch(1:ngrids)
2047# endif
2048# if defined BULK_FLUXES || defined ECOSIM
2049 CASE ('Hout(idUair)')
2050 IF (iduair.eq.0) THEN
2051 IF (master) WRITE (out,280) 'idUair'
2052 exit_flag=5
2053 RETURN
2054 END IF
2055 npts=load_l(nval, cval, ngrids, lswitch)
2056 hout(iduair,1:ngrids)=lswitch(1:ngrids)
2057 CASE ('Hout(idVair)')
2058 IF (idvair.eq.0) THEN
2059 IF (master) WRITE (out,280) 'idVair'
2060 exit_flag=5
2061 RETURN
2062 END IF
2063 npts=load_l(nval, cval, ngrids, lswitch)
2064 hout(idvair,1:ngrids)=lswitch(1:ngrids)
2065 CASE ('Hout(idUaiE)')
2066 IF (iduaie.eq.0) THEN
2067 IF (master) WRITE (out,280) 'idUaiE'
2068 exit_flag=5
2069 RETURN
2070 END IF
2071 npts=load_l(nval, cval, ngrids, lswitch)
2072 hout(iduaie,1:ngrids)=lswitch(1:ngrids)
2073 CASE ('Hout(idVaiN)')
2074 IF (idvain.eq.0) THEN
2075 IF (master) WRITE (out,280) 'idVaiN'
2076 exit_flag=5
2077 RETURN
2078 END IF
2079 npts=load_l(nval, cval, ngrids, lswitch)
2080 hout(idvain,1:ngrids)=lswitch(1:ngrids)
2081# endif
2082 CASE ('Hout(idTsur)')
2083 IF (idtsur(itemp).eq.0) THEN
2084 IF (master) WRITE (out,280) 'idTsur'
2085 exit_flag=5
2086 RETURN
2087 END IF
2088 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2089 DO ng=1,ngrids
2090 DO itrc=1,nat
2091 i=idtsur(itrc)
2092 hout(i,ng)=ltracer(itrc,ng)
2093 END DO
2094 END DO
2095#endif
2096 CASE ('Hout(idLhea)')
2097 IF (idlhea.eq.0) THEN
2098 IF (master) WRITE (out,280) 'idLhea'
2099 exit_flag=5
2100 RETURN
2101 END IF
2102 npts=load_l(nval, cval, ngrids, lswitch)
2103 hout(idlhea,1:ngrids)=lswitch(1:ngrids)
2104 CASE ('Hout(idShea)')
2105 IF (idshea.eq.0) THEN
2106 IF (master) WRITE (out,280) 'idShea'
2107 exit_flag=5
2108 RETURN
2109 END IF
2110 npts=load_l(nval, cval, ngrids, lswitch)
2111 hout(idshea,1:ngrids)=lswitch(1:ngrids)
2112 CASE ('Hout(idLrad)')
2113 IF (idlrad.eq.0) THEN
2114 IF (master) WRITE (out,280) 'idLrad'
2115 exit_flag=5
2116 RETURN
2117 END IF
2118 npts=load_l(nval, cval, ngrids, lswitch)
2119 hout(idlrad,1:ngrids)=lswitch(1:ngrids)
2120 CASE ('Hout(idSrad)')
2121 IF (idsrad.eq.0) THEN
2122 IF (master) WRITE (out,280) 'idSrad'
2123 exit_flag=5
2124 RETURN
2125 END IF
2126 npts=load_l(nval, cval, ngrids, lswitch)
2127 hout(idsrad,1:ngrids)=lswitch(1:ngrids)
2128 CASE ('Hout(idEmPf)')
2129 IF (idempf.eq.0) THEN
2130 IF (master) WRITE (out,280) 'idEmPf'
2131 exit_flag=5
2132 RETURN
2133 END IF
2134 npts=load_l(nval, cval, ngrids, lswitch)
2135 hout(idempf,1:ngrids)=lswitch(1:ngrids)
2136 CASE ('Hout(idevap)')
2137 IF (idevap.eq.0) THEN
2138 IF (master) WRITE (out,280) 'idevap'
2139 exit_flag=5
2140 RETURN
2141 END IF
2142 npts=load_l(nval, cval, ngrids, lswitch)
2143 hout(idevap,1:ngrids)=lswitch(1:ngrids)
2144 CASE ('Hout(idrain)')
2145 IF (idrain.eq.0) THEN
2146 IF (master) WRITE (out,280) 'idrain'
2147 exit_flag=5
2148 RETURN
2149 END IF
2150 npts=load_l(nval, cval, ngrids, lswitch)
2151 hout(idrain,1:ngrids)=lswitch(1:ngrids)
2152 CASE ('Hout(idDano)')
2153 IF (iddano.eq.0) THEN
2154 IF (master) WRITE (out,280) 'idDano'
2155 exit_flag=5
2156 RETURN
2157 END IF
2158 npts=load_l(nval, cval, ngrids, lswitch)
2159 hout(iddano,1:ngrids)=lswitch(1:ngrids)
2160 CASE ('Hout(idVvis)')
2161 IF (idvvis.eq.0) THEN
2162 IF (master) WRITE (out,280) 'idVvis'
2163 exit_flag=5
2164 RETURN
2165 END IF
2166 npts=load_l(nval, cval, ngrids, lswitch)
2167 hout(idvvis,1:ngrids)=lswitch(1:ngrids)
2168 CASE ('Hout(idTdif)')
2169 IF (idtdif.eq.0) THEN
2170 IF (master) WRITE (out,280) 'idTdif'
2171 exit_flag=5
2172 RETURN
2173 END IF
2174 npts=load_l(nval, cval, ngrids, lswitch)
2175 hout(idtdif,1:ngrids)=lswitch(1:ngrids)
2176#ifdef SALINITY
2177 CASE ('Hout(idSdif)')
2178 IF (idsdif.eq.0) THEN
2179 IF (master) WRITE (out,280) 'idSdif'
2180 exit_flag=5
2181 RETURN
2182 END IF
2183 npts=load_l(nval, cval, ngrids, lswitch)
2184 hout(idsdif,1:ngrids)=lswitch(1:ngrids)
2185#endif
2186 CASE ('Hout(idHsbl)')
2187 IF (idhsbl.eq.0) THEN
2188 IF (master) WRITE (out,280) 'idHsbl'
2189 exit_flag=5
2190 RETURN
2191 END IF
2192 npts=load_l(nval, cval, ngrids, lswitch)
2193 hout(idhsbl,1:ngrids)=lswitch(1:ngrids)
2194 CASE ('Hout(idHbbl)')
2195 IF (idhbbl.eq.0) THEN
2196 IF (master) WRITE (out,280) 'idHbbl'
2197 exit_flag=5
2198 RETURN
2199 END IF
2200 npts=load_l(nval, cval, ngrids, lswitch)
2201 hout(idhbbl,1:ngrids)=lswitch(1:ngrids)
2202 CASE ('Hout(idMtke)')
2203 IF (idmtke.eq.0) THEN
2204 IF (master) WRITE (out,280) 'idMtke'
2205 exit_flag=5
2206 RETURN
2207 END IF
2208 npts=load_l(nval, cval, ngrids, lswitch)
2209 hout(idmtke,1:ngrids)=lswitch(1:ngrids)
2210 CASE ('Hout(idMtls)')
2211 IF (idmtls.eq.0) THEN
2212 IF (master) WRITE (out,280) 'idMtls'
2213 exit_flag=5
2214 RETURN
2215 END IF
2216 npts=load_l(nval, cval, ngrids, lswitch)
2217 hout(idmtls,1:ngrids)=lswitch(1:ngrids)
2218#if defined SOLVE3D && defined T_PASSIVE
2219 CASE ('Hout(inert)')
2220 npts=load_l(nval, cval, npt, ngrids, linert)
2221 DO ng=1,ngrids
2222 DO i=1,npt
2223 itrc=idtvar(inert(i))
2224 hout(itrc,ng)=linert(i,ng)
2225 END DO
2226 END DO
2227#endif
2228 CASE ('Qout(idUvel)')
2229 npts=load_l(nval, cval, ngrids, lswitch)
2230 qout(iduvel,1:ngrids)=lswitch(1:ngrids)
2231 CASE ('Qout(idVvel)')
2232 npts=load_l(nval, cval, ngrids, lswitch)
2233 qout(idvvel,1:ngrids)=lswitch(1:ngrids)
2234 CASE ('Qout(idWvel)')
2235 npts=load_l(nval, cval, ngrids, lswitch)
2236 qout(idwvel,1:ngrids)=lswitch(1:ngrids)
2237 CASE ('Qout(idOvel)')
2238 npts=load_l(nval, cval, ngrids, lswitch)
2239 qout(idovel,1:ngrids)=lswitch(1:ngrids)
2240 CASE ('Qout(idUbar)')
2241 npts=load_l(nval, cval, ngrids, lswitch)
2242 qout(idubar,1:ngrids)=lswitch(1:ngrids)
2243 CASE ('Qout(idVbar)')
2244 npts=load_l(nval, cval, ngrids, lswitch)
2245 qout(idvbar,1:ngrids)=lswitch(1:ngrids)
2246 CASE ('Qout(idFsur)')
2247 npts=load_l(nval, cval, ngrids, lswitch)
2248 qout(idfsur,1:ngrids)=lswitch(1:ngrids)
2249#if defined SEDIMENT && defined SED_MORPH
2250 CASE ('Qout(idBath)')
2251 npts=load_l(nval, cval, ngrids, lswitch)
2252 qout(idbath,1:ngrids)=lswitch(1:ngrids)
2253#endif
2254 CASE ('Qout(idu2dE)')
2255 npts=load_l(nval, cval, ngrids, lswitch)
2256 qout(idu2de,1:ngrids)=lswitch(1:ngrids)
2257 CASE ('Qout(idv2dN)')
2258 npts=load_l(nval, cval, ngrids, lswitch)
2259 qout(idv2dn,1:ngrids)=lswitch(1:ngrids)
2260 CASE ('Qout(idu3dE)')
2261 npts=load_l(nval, cval, ngrids, lswitch)
2262 qout(idu3de,1:ngrids)=lswitch(1:ngrids)
2263 CASE ('Qout(idv3dN)')
2264 npts=load_l(nval, cval, ngrids, lswitch)
2265 qout(idv3dn,1:ngrids)=lswitch(1:ngrids)
2266#ifdef SOLVE3D
2267 CASE ('Qout(idTvar)')
2268 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2269 DO ng=1,ngrids
2270 DO itrc=1,nat
2271 i=idtvar(itrc)
2272 qout(i,ng)=ltracer(itrc,ng)
2273 END DO
2274 END DO
2275#endif
2276 CASE ('Qout(idUsur)')
2277 IF (idusur.eq.0) THEN
2278 IF (master) WRITE (out,280) 'idUsur'
2279 exit_flag=5
2280 RETURN
2281 END IF
2282 npts=load_l(nval, cval, ngrids, lswitch)
2283 qout(idusur,1:ngrids)=lswitch(1:ngrids)
2284 CASE ('Qout(idVsur)')
2285 IF (idusur.eq.0) THEN
2286 IF (master) WRITE (out,280) 'idVsur'
2287 exit_flag=5
2288 RETURN
2289 END IF
2290 npts=load_l(nval, cval, ngrids, lswitch)
2291 qout(idvsur,1:ngrids)=lswitch(1:ngrids)
2292 CASE ('Qout(idUsuE)')
2293 IF (idusue.eq.0) THEN
2294 IF (master) WRITE (out,280) 'idUsuE'
2295 exit_flag=5
2296 RETURN
2297 END IF
2298 npts=load_l(nval, cval, ngrids, lswitch)
2299 qout(idusue,1:ngrids)=lswitch(1:ngrids)
2300 CASE ('Qout(idVsuN)')
2301 IF (idvsun.eq.0) THEN
2302 IF (master) WRITE (out,280) 'idVsuN'
2303 exit_flag=5
2304 RETURN
2305 END IF
2306 npts=load_l(nval, cval, ngrids, lswitch)
2307 qout(idvsun,1:ngrids)=lswitch(1:ngrids)
2308#ifdef SOLVE3D
2309 CASE ('Qout(idsurT)')
2310 IF (maxval(idsurt).eq.0) THEN
2311 IF (master) WRITE (out,280) 'idsurT'
2312 exit_flag=5
2313 RETURN
2314 END IF
2315 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2316 DO ng=1,ngrids
2317 DO itrc=1,nat
2318 i=idsurt(itrc)
2319 qout(i,ng)=ltracer(itrc,ng)
2320 END DO
2321 END DO
2322#endif
2323 CASE ('Qout(idpthR)')
2324 npts=load_l(nval, cval, ngrids, lswitch)
2325 qout(idpthr,1:ngrids)=lswitch(1:ngrids)
2326 CASE ('Qout(idpthU)')
2327 npts=load_l(nval, cval, ngrids, lswitch)
2328 qout(idpthu,1:ngrids)=lswitch(1:ngrids)
2329 CASE ('Qout(idpthV)')
2330 npts=load_l(nval, cval, ngrids, lswitch)
2331 qout(idpthv,1:ngrids)=lswitch(1:ngrids)
2332 CASE ('Qout(idpthW)')
2333 npts=load_l(nval, cval, ngrids, lswitch)
2334 qout(idpthw,1:ngrids)=lswitch(1:ngrids)
2335 CASE ('Qout(idUsms)')
2336 npts=load_l(nval, cval, ngrids, lswitch)
2337 qout(idusms,1:ngrids)=lswitch(1:ngrids)
2338 CASE ('Qout(idVsms)')
2339 npts=load_l(nval, cval, ngrids, lswitch)
2340 qout(idvsms,1:ngrids)=lswitch(1:ngrids)
2341 CASE ('Qout(idUbms)')
2342 npts=load_l(nval, cval, ngrids, lswitch)
2343 qout(idubms,1:ngrids)=lswitch(1:ngrids)
2344 CASE ('Qout(idVbms)')
2345 npts=load_l(nval, cval, ngrids, lswitch)
2346 qout(idvbms,1:ngrids)=lswitch(1:ngrids)
2347#ifdef BBL_MODEL
2348 CASE ('Qout(idUbrs)')
2349 npts=load_l(nval, cval, ngrids, lswitch)
2350 qout(idubrs,1:ngrids)=lswitch(1:ngrids)
2351 CASE ('Qout(idVbrs)')
2352 npts=load_l(nval, cval, ngrids, lswitch)
2353 qout(idvbrs,1:ngrids)=lswitch(1:ngrids)
2354 CASE ('Qout(idUbws)')
2355 npts=load_l(nval, cval, ngrids, lswitch)
2356 qout(idubws,1:ngrids)=lswitch(1:ngrids)
2357 CASE ('Qout(idVbws)')
2358 npts=load_l(nval, cval, ngrids, lswitch)
2359 qout(idvbws,1:ngrids)=lswitch(1:ngrids)
2360 CASE ('Qout(idUbcs)')
2361 npts=load_l(nval, cval, ngrids, lswitch)
2362 qout(idubcs,1:ngrids)=lswitch(1:ngrids)
2363 CASE ('Qout(idVbcs)')
2364 npts=load_l(nval, cval, ngrids, lswitch)
2365 qout(idvbcs,1:ngrids)=lswitch(1:ngrids)
2366 CASE ('Qout(idUbot)')
2367 npts=load_l(nval, cval, ngrids, lswitch)
2368 qout(idubot,1:ngrids)=lswitch(1:ngrids)
2369 CASE ('Qout(idVbot)')
2370 npts=load_l(nval, cval, ngrids, lswitch)
2371 qout(idvbot,1:ngrids)=lswitch(1:ngrids)
2372 CASE ('Qout(idUbur)')
2373 npts=load_l(nval, cval, ngrids, lswitch)
2374 qout(idubur,1:ngrids)=lswitch(1:ngrids)
2375 CASE ('Qout(idVbvr)')
2376 npts=load_l(nval, cval, ngrids, lswitch)
2377 qout(idvbvr,1:ngrids)=lswitch(1:ngrids)
2378#endif
2379#ifdef WEC_VF
2380 CASE ('Qout(idWztw)')
2381 npts=load_l(nval, cval, ngrids, lswitch)
2382 qout(idwztw,1:ngrids)=lswitch(1:ngrids)
2383 CASE ('Qout(idWqsp)')
2384 npts=load_l(nval, cval, ngrids, lswitch)
2385 qout(idwqsp,1:ngrids)=lswitch(1:ngrids)
2386 CASE ('Qout(idWbeh)')
2387 npts=load_l(nval, cval, ngrids, lswitch)
2388 qout(idwbeh,1:ngrids)=lswitch(1:ngrids)
2389#endif
2390#ifdef WEC
2391 CASE ('Qout(idU2rs)')
2392 npts=load_l(nval, cval, ngrids, lswitch)
2393 qout(idu2rs,1:ngrids)=lswitch(1:ngrids)
2394 CASE ('Qout(idV2rs)')
2395 npts=load_l(nval, cval, ngrids, lswitch)
2396 qout(idv2rs,1:ngrids)=lswitch(1:ngrids)
2397 CASE ('Qout(idU3rs)')
2398 npts=load_l(nval, cval, ngrids, lswitch)
2399 qout(idu3rs,1:ngrids)=lswitch(1:ngrids)
2400 CASE ('Qout(idV3rs)')
2401 npts=load_l(nval, cval, ngrids, lswitch)
2402 qout(idv3rs,1:ngrids)=lswitch(1:ngrids)
2403 CASE ('Qout(idU2Sd)')
2404 npts=load_l(nval, cval, ngrids, lswitch)
2405 qout(idu2sd,1:ngrids)=lswitch(1:ngrids)
2406 CASE ('Qout(idV2Sd)')
2407 npts=load_l(nval, cval, ngrids, lswitch)
2408 qout(idv2sd,1:ngrids)=lswitch(1:ngrids)
2409 CASE ('Qout(idU3Sd)')
2410 npts=load_l(nval, cval, ngrids, lswitch)
2411 qout(idu3sd,1:ngrids)=lswitch(1:ngrids)
2412 CASE ('Qout(idV3Sd)')
2413 npts=load_l(nval, cval, ngrids, lswitch)
2414 qout(idv3sd,1:ngrids)=lswitch(1:ngrids)
2415 CASE ('Qout(idW3Sd)')
2416 npts=load_l(nval, cval, ngrids, lswitch)
2417 qout(idw3sd,1:ngrids)=lswitch(1:ngrids)
2418 CASE ('Qout(idW3St)')
2419 npts=load_l(nval, cval, ngrids, lswitch)
2420 qout(idw3st,1:ngrids)=lswitch(1:ngrids)
2421#endif
2422#ifdef WAVES_HEIGHT
2423 CASE ('Qout(idWamp)')
2424 npts=load_l(nval, cval, ngrids, lswitch)
2425 qout(idwamp,1:ngrids)=lswitch(1:ngrids)
2426#endif
2427#ifdef WAVES_LENGTH
2428 CASE ('Qout(idWlen)')
2429 npts=load_l(nval, cval, ngrids, lswitch)
2430 qout(idwlen,1:ngrids)=lswitch(1:ngrids)
2431#endif
2432#ifdef WAVES_LENGTHP
2433 CASE ('Qout(idWlep)')
2434 npts=load_l(nval, cval, ngrids, lswitch)
2435 qout(idwlep,1:ngrids)=lswitch(1:ngrids)
2436#endif
2437#ifdef WAVES_DIR
2438 CASE ('Qout(idWdir)')
2439 npts=load_l(nval, cval, ngrids, lswitch)
2440 qout(idwdir,1:ngrids)=lswitch(1:ngrids)
2441#endif
2442#ifdef WAVES_DIRP
2443 CASE ('Qout(idWdip)')
2444 npts=load_l(nval, cval, ngrids, lswitch)
2445 qout(idwdip,1:ngrids)=lswitch(1:ngrids)
2446#endif
2447#ifdef WAVES_TOP_PERIOD
2448 CASE ('Qout(idWptp)')
2449 npts=load_l(nval, cval, ngrids, lswitch)
2450 qout(idwptp,1:ngrids)=lswitch(1:ngrids)
2451#endif
2452#ifdef WAVES_BOT_PERIOD
2453 CASE ('Qout(idWpbt)')
2454 npts=load_l(nval, cval, ngrids, lswitch)
2455 qout(idwpbt,1:ngrids)=lswitch(1:ngrids)
2456#endif
2457#if defined BBL_MODEL || defined BEDLOAD_SOULSBY || \
2458 defined bedload_vandera || defined wav_coupling
2459 CASE ('Qout(idWorb)')
2460 npts=load_l(nval, cval, ngrids, lswitch)
2461 qout(idworb,1:ngrids)=lswitch(1:ngrids)
2462#endif
2463#if defined ROLLER_SVENDSEN
2464 CASE ('Qout(idWbrk)')
2465 npts=load_l(nval, cval, ngrids, lswitch)
2466 qout(idwbrk,1:ngrids)=lswitch(1:ngrids)
2467#endif
2468#if defined UV_KIRBY
2469 CASE ('Qout(idUwav)')
2470 npts=load_l(nval, cval, ngrids, lswitch)
2471 qout(iduwav,1:ngrids)=lswitch(1:ngrids)
2472 CASE ('Qout(idVwav)')
2473 npts=load_l(nval, cval, ngrids, lswitch)
2474 qout(idvwav,1:ngrids)=lswitch(1:ngrids)
2475#endif
2476#if defined WAV_COUPLING || (defined WEC_VF && defined BOTTOM_STREAMING)
2477 CASE ('Qout(idWdif)')
2478 npts=load_l(nval, cval, ngrids, lswitch)
2479 qout(idwdif,1:ngrids)=lswitch(1:ngrids)
2480#endif
2481#if defined TKE_WAVEDISS || defined WAV_COUPLING || \
2482 defined wdiss_thorguza || defined wdiss_churthor || \
2483 defined waves_diss || defined wdiss_inwave
2484 CASE ('Qout(idWdib)')
2485 npts=load_l(nval, cval, ngrids, lswitch)
2486 qout(idwdib,1:ngrids)=lswitch(1:ngrids)
2487 CASE ('Qout(idWdiw)')
2488 npts=load_l(nval, cval, ngrids, lswitch)
2489 qout(idwdiw,1:ngrids)=lswitch(1:ngrids)
2490#endif
2491#if defined WEC_ROLLER
2492 CASE ('Qout(idWdis)')
2493 npts=load_l(nval, cval, ngrids, lswitch)
2494 hout(idwdis,1:ngrids)=lswitch(1:ngrids)
2495 CASE ('Qout(idWrol)')
2496 npts=load_l(nval, cval, ngrids, lswitch)
2497 qout(idwrol,1:ngrids)=lswitch(1:ngrids)
2498#endif
2499#if defined WAVES_DSPR
2500 CASE ('Qout(idWvds)')
2501 npts=load_l(nval, cval, ngrids, lswitch)
2502 qout(idwvds,1:ngrids)=lswitch(1:ngrids)
2503 CASE ('Hout(idWvqp)')
2504 npts=load_l(nval, cval, ngrids, lswitch)
2505 qout(idwvqp,1:ngrids)=lswitch(1:ngrids)
2506#endif
2507#ifdef SOLVE3D
2508# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
2509 CASE ('Qout(idPair)')
2510 npts=load_l(nval, cval, ngrids, lswitch)
2511 qout(idpair,1:ngrids)=lswitch(1:ngrids)
2512# endif
2513# if defined BULK_FLUXES
2514 CASE ('Qout(idTair)')
2515 npts=load_l(nval, cval, ngrids, lswitch)
2516 qout(idtair,1:ngrids)=lswitch(1:ngrids)
2517# endif
2518# if defined BULK_FLUXES || defined ECOSIM
2519 CASE ('Qout(idUair)')
2520 npts=load_l(nval, cval, ngrids, lswitch)
2521 qout(iduair,1:ngrids)=lswitch(1:ngrids)
2522 CASE ('Qout(idVair)')
2523 npts=load_l(nval, cval, ngrids, lswitch)
2524 qout(idvair,1:ngrids)=lswitch(1:ngrids)
2525 CASE ('Qout(idUaiE)')
2526 npts=load_l(nval, cval, ngrids, lswitch)
2527 qout(iduaie,1:ngrids)=lswitch(1:ngrids)
2528 CASE ('Qout(idVaiN)')
2529 npts=load_l(nval, cval, ngrids, lswitch)
2530 qout(idvain,1:ngrids)=lswitch(1:ngrids)
2531# endif
2532 CASE ('Qout(idTsur)')
2533 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2534 DO ng=1,ngrids
2535 DO itrc=1,nat
2536 i=idtsur(itrc)
2537 qout(i,ng)=ltracer(itrc,ng)
2538 END DO
2539 END DO
2540#endif
2541 CASE ('Qout(idLhea)')
2542 npts=load_l(nval, cval, ngrids, lswitch)
2543 qout(idlhea,1:ngrids)=lswitch(1:ngrids)
2544 CASE ('Qout(idShea)')
2545 npts=load_l(nval, cval, ngrids, lswitch)
2546 qout(idshea,1:ngrids)=lswitch(1:ngrids)
2547 CASE ('Qout(idLrad)')
2548 npts=load_l(nval, cval, ngrids, lswitch)
2549 qout(idlrad,1:ngrids)=lswitch(1:ngrids)
2550 CASE ('Qout(idSrad)')
2551 npts=load_l(nval, cval, ngrids, lswitch)
2552 qout(idsrad,1:ngrids)=lswitch(1:ngrids)
2553 CASE ('Qout(idEmPf)')
2554 npts=load_l(nval, cval, ngrids, lswitch)
2555 qout(idempf,1:ngrids)=lswitch(1:ngrids)
2556 CASE ('Qout(idevap)')
2557 npts=load_l(nval, cval, ngrids, lswitch)
2558 qout(idevap,1:ngrids)=lswitch(1:ngrids)
2559 CASE ('Qout(idrain)')
2560 npts=load_l(nval, cval, ngrids, lswitch)
2561 qout(idrain,1:ngrids)=lswitch(1:ngrids)
2562 CASE ('Qout(idDano)')
2563 npts=load_l(nval, cval, ngrids, lswitch)
2564 qout(iddano,1:ngrids)=lswitch(1:ngrids)
2565 CASE ('Qout(idVvis)')
2566 npts=load_l(nval, cval, ngrids, lswitch)
2567 qout(idvvis,1:ngrids)=lswitch(1:ngrids)
2568 CASE ('Qout(idTdif)')
2569 npts=load_l(nval, cval, ngrids, lswitch)
2570 qout(idtdif,1:ngrids)=lswitch(1:ngrids)
2571#ifdef SALINITY
2572 CASE ('Qout(idSdif)')
2573 npts=load_l(nval, cval, ngrids, lswitch)
2574 qout(idsdif,1:ngrids)=lswitch(1:ngrids)
2575#endif
2576 CASE ('Qout(idHsbl)')
2577 npts=load_l(nval, cval, ngrids, lswitch)
2578 qout(idhsbl,1:ngrids)=lswitch(1:ngrids)
2579 CASE ('Qout(idHbbl)')
2580 npts=load_l(nval, cval, ngrids, lswitch)
2581 qout(idhbbl,1:ngrids)=lswitch(1:ngrids)
2582 CASE ('Qout(idMtke)')
2583 npts=load_l(nval, cval, ngrids, lswitch)
2584 qout(idmtke,1:ngrids)=lswitch(1:ngrids)
2585 CASE ('Qout(idMtls)')
2586 npts=load_l(nval, cval, ngrids, lswitch)
2587 qout(idmtls,1:ngrids)=lswitch(1:ngrids)
2588#if defined SOLVE3D && defined T_PASSIVE
2589 CASE ('Qout(inert)')
2590 npts=load_l(nval, cval, npt, ngrids, linert)
2591 DO ng=1,ngrids
2592 DO i=1,npt
2593 itrc=idtvar(inert(i))
2594 qout(itrc,ng)=linert(i,ng)
2595 END DO
2596 END DO
2597 CASE ('Qout(Snert)')
2598 npts=load_l(nval, cval, npt, ngrids, linert)
2599 DO ng=1,ngrids
2600 DO i=1,npt
2601 itrc=idsurt(inert(i))
2602 qout(itrc,ng)=linert(i,ng)
2603 END DO
2604 END DO
2605#endif
2606#if defined AVERAGES || \
2607 (defined ad_averages && defined adjoint) || \
2608 (defined rp_averages && defined tl_ioms) || \
2609 (defined tl_averages && defined tangent)
2610 CASE ('Aout(idUvel)')
2611 npts=load_l(nval, cval, ngrids, lswitch)
2612 aout(iduvel,1:ngrids)=lswitch(1:ngrids)
2613 CASE ('Aout(idVvel)')
2614 npts=load_l(nval, cval, ngrids, lswitch)
2615 aout(idvvel,1:ngrids)=lswitch(1:ngrids)
2616 CASE ('Aout(idWvel)')
2617 npts=load_l(nval, cval, ngrids, lswitch)
2618 aout(idwvel,1:ngrids)=lswitch(1:ngrids)
2619 CASE ('Aout(idOvel)')
2620 npts=load_l(nval, cval, ngrids, lswitch)
2621 aout(idovel,1:ngrids)=lswitch(1:ngrids)
2622 CASE ('Aout(idUbar)')
2623 npts=load_l(nval, cval, ngrids, lswitch)
2624 aout(idubar,1:ngrids)=lswitch(1:ngrids)
2625 CASE ('Aout(idVbar)')
2626 npts=load_l(nval, cval, ngrids, lswitch)
2627 aout(idvbar,1:ngrids)=lswitch(1:ngrids)
2628 CASE ('Aout(idFsur)')
2629 npts=load_l(nval, cval, ngrids, lswitch)
2630 aout(idfsur,1:ngrids)=lswitch(1:ngrids)
2631 CASE ('Aout(idu2dE)')
2632 npts=load_l(nval, cval, ngrids, lswitch)
2633 aout(idu2de,1:ngrids)=lswitch(1:ngrids)
2634 CASE ('Aout(idv2dN)')
2635 npts=load_l(nval, cval, ngrids, lswitch)
2636 aout(idv2dn,1:ngrids)=lswitch(1:ngrids)
2637 CASE ('Aout(idu3dE)')
2638 npts=load_l(nval, cval, ngrids, lswitch)
2639 aout(idu3de,1:ngrids)=lswitch(1:ngrids)
2640 CASE ('Aout(idv3dN)')
2641 npts=load_l(nval, cval, ngrids, lswitch)
2642 aout(idv3dn,1:ngrids)=lswitch(1:ngrids)
2643# ifdef SOLVE3D
2644 CASE ('Aout(idTvar)')
2645 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2646 DO ng=1,ngrids
2647 DO itrc=1,nat
2648 i=idtvar(itrc)
2649 aout(i,ng)=ltracer(itrc,ng)
2650 END DO
2651 END DO
2652# endif
2653 CASE ('Aout(idUsms)')
2654 npts=load_l(nval, cval, ngrids, lswitch)
2655 aout(idusms,1:ngrids)=lswitch(1:ngrids)
2656 CASE ('Aout(idVsms)')
2657 npts=load_l(nval, cval, ngrids, lswitch)
2658 aout(idvsms,1:ngrids)=lswitch(1:ngrids)
2659 CASE ('Aout(idUbms)')
2660 npts=load_l(nval, cval, ngrids, lswitch)
2661 aout(idubms,1:ngrids)=lswitch(1:ngrids)
2662 CASE ('Aout(idVbms)')
2663 npts=load_l(nval, cval, ngrids, lswitch)
2664 aout(idvbms,1:ngrids)=lswitch(1:ngrids)
2665# ifdef BBL_MODEL
2666 CASE ('Aout(idUbrs)')
2667 npts=load_l(nval, cval, ngrids, lswitch)
2668 aout(idubrs,1:ngrids)=lswitch(1:ngrids)
2669 CASE ('Aout(idVbrs)')
2670 npts=load_l(nval, cval, ngrids, lswitch)
2671 aout(idvbrs,1:ngrids)=lswitch(1:ngrids)
2672 CASE ('Aout(idUbws)')
2673 npts=load_l(nval, cval, ngrids, lswitch)
2674 aout(idubws,1:ngrids)=lswitch(1:ngrids)
2675 CASE ('Aout(idVbws)')
2676 npts=load_l(nval, cval, ngrids, lswitch)
2677 aout(idvbws,1:ngrids)=lswitch(1:ngrids)
2678 CASE ('Aout(idUbcs)')
2679 npts=load_l(nval, cval, ngrids, lswitch)
2680 aout(idubcs,1:ngrids)=lswitch(1:ngrids)
2681 CASE ('Aout(idVbcs)')
2682 npts=load_l(nval, cval, ngrids, lswitch)
2683 aout(idvbcs,1:ngrids)=lswitch(1:ngrids)
2684 CASE ('Aout(idUVwc)')
2685 npts=load_l(nval, cval, ngrids, lswitch)
2686 aout(iduvwc,1:ngrids)=lswitch(1:ngrids)
2687 CASE ('Aout(idUbot)')
2688 npts=load_l(nval, cval, ngrids, lswitch)
2689 aout(idubot,1:ngrids)=lswitch(1:ngrids)
2690 CASE ('Aout(idVbot)')
2691 npts=load_l(nval, cval, ngrids, lswitch)
2692 aout(idvbot,1:ngrids)=lswitch(1:ngrids)
2693 CASE ('Aout(idUbur)')
2694 npts=load_l(nval, cval, ngrids, lswitch)
2695 aout(idubur,1:ngrids)=lswitch(1:ngrids)
2696 CASE ('Aout(idVbvr)')
2697 npts=load_l(nval, cval, ngrids, lswitch)
2698 aout(idvbvr,1:ngrids)=lswitch(1:ngrids)
2699# endif
2700# ifdef WEC
2701 CASE ('Aout(idU2rs)')
2702 npts=load_l(nval, cval, ngrids, lswitch)
2703 aout(idu2rs,1:ngrids)=lswitch(1:ngrids)
2704 CASE ('Aout(idV2rs)')
2705 npts=load_l(nval, cval, ngrids, lswitch)
2706 aout(idv2rs,1:ngrids)=lswitch(1:ngrids)
2707 CASE ('Aout(idU2Sd)')
2708 npts=load_l(nval, cval, ngrids, lswitch)
2709 aout(idu2sd,1:ngrids)=lswitch(1:ngrids)
2710 CASE ('Aout(idV2Sd)')
2711 npts=load_l(nval, cval, ngrids, lswitch)
2712 aout(idv2sd,1:ngrids)=lswitch(1:ngrids)
2713# endif
2714# ifdef WEC
2715# ifdef SOLVE3D
2716 CASE ('Aout(idU3rs)')
2717 npts=load_l(nval, cval, ngrids, lswitch)
2718 aout(idu3rs,1:ngrids)=lswitch(1:ngrids)
2719 CASE ('Aout(idV3rs)')
2720 npts=load_l(nval, cval, ngrids, lswitch)
2721 aout(idv3rs,1:ngrids)=lswitch(1:ngrids)
2722 CASE ('Aout(idU3Sd)')
2723 npts=load_l(nval, cval, ngrids, lswitch)
2724 aout(idu3sd,1:ngrids)=lswitch(1:ngrids)
2725 CASE ('Aout(idV3Sd)')
2726 npts=load_l(nval, cval, ngrids, lswitch)
2727 aout(idv3sd,1:ngrids)=lswitch(1:ngrids)
2728 CASE ('Aout(idW3Sd)')
2729 npts=load_l(nval, cval, ngrids, lswitch)
2730 aout(idw3sd,1:ngrids)=lswitch(1:ngrids)
2731 CASE ('Aout(idW3St)')
2732 npts=load_l(nval, cval, ngrids, lswitch)
2733 aout(idw3st,1:ngrids)=lswitch(1:ngrids)
2734# endif
2735 CASE ('Aout(idWztw)')
2736 npts=load_l(nval, cval, ngrids, lswitch)
2737 aout(idwztw,1:ngrids)=lswitch(1:ngrids)
2738 CASE ('Aout(idWqsp)')
2739 npts=load_l(nval, cval, ngrids, lswitch)
2740 aout(idwqsp,1:ngrids)=lswitch(1:ngrids)
2741 CASE ('Aout(idWbeh)')
2742 npts=load_l(nval, cval, ngrids, lswitch)
2743 aout(idwbeh,1:ngrids)=lswitch(1:ngrids)
2744# endif
2745# ifdef WAVES_HEIGHT
2746 CASE ('Aout(idWamp)')
2747 npts=load_l(nval, cval, ngrids, lswitch)
2748 aout(idwamp,1:ngrids)=lswitch(1:ngrids)
2749 CASE ('Aout(idWam2)')
2750 npts=load_l(nval, cval, ngrids, lswitch)
2751 aout(idwam2,1:ngrids)=lswitch(1:ngrids)
2752# endif
2753# ifdef WAVES_LENGTH
2754 CASE ('Aout(idWlen)')
2755 npts=load_l(nval, cval, ngrids, lswitch)
2756 aout(idwlen,1:ngrids)=lswitch(1:ngrids)
2757# endif
2758# ifdef WAVES_LENGTHP
2759 CASE ('Aout(idWlep)')
2760 npts=load_l(nval, cval, ngrids, lswitch)
2761 aout(idwlep,1:ngrids)=lswitch(1:ngrids)
2762# endif
2763# ifdef WAVES_DIR
2764 CASE ('Aout(idWdir)')
2765 npts=load_l(nval, cval, ngrids, lswitch)
2766 aout(idwdir,1:ngrids)=lswitch(1:ngrids)
2767# endif
2768# ifdef WAVES_DIRP
2769 CASE ('Aout(idWdip)')
2770 npts=load_l(nval, cval, ngrids, lswitch)
2771 aout(idwdip,1:ngrids)=lswitch(1:ngrids)
2772# endif
2773# ifdef WAVES_TOP_PERIOD
2774 CASE ('Aout(idWptp)')
2775 npts=load_l(nval, cval, ngrids, lswitch)
2776 aout(idwptp,1:ngrids)=lswitch(1:ngrids)
2777# endif
2778# ifdef WAVES_BOT_PERIOD
2779 CASE ('Aout(idWpbt)')
2780 npts=load_l(nval, cval, ngrids, lswitch)
2781 aout(idwpbt,1:ngrids)=lswitch(1:ngrids)
2782# endif
2783# if defined BBL_MODEL || defined BEDLOAD_SOULSBY || \
2784 defined bedload_vandera || defined wav_coupling
2785 CASE ('Aout(idWorb)')
2786 npts=load_l(nval, cval, ngrids, lswitch)
2787 aout(idworb,1:ngrids)=lswitch(1:ngrids)
2788# endif
2789# if defined WAV_COUPLING || (defined WEC_VF && defined BOTTOM_STREAMING)
2790 CASE ('Aout(idWdif)')
2791 npts=load_l(nval, cval, ngrids, lswitch)
2792 aout(idwdif,1:ngrids)=lswitch(1:ngrids)
2793# endif
2794# if defined TKE_WAVEDISS || defined WAV_COUPLING || \
2795 defined wdiss_thorguza || defined wdiss_churthor || \
2796 defined waves_diss || defined wdiss_inwave
2797 CASE ('Aout(idWdib)')
2798 npts=load_l(nval, cval, ngrids, lswitch)
2799 aout(idwdib,1:ngrids)=lswitch(1:ngrids)
2800 CASE ('Aout(idWdiw)')
2801 npts=load_l(nval, cval, ngrids, lswitch)
2802 aout(idwdiw,1:ngrids)=lswitch(1:ngrids)
2803# endif
2804# ifdef ROLLER_SVENDSEN
2805 CASE ('Aout(idWbrk)')
2806 npts=load_l(nval, cval, ngrids, lswitch)
2807 aout(idwbrk,1:ngrids)=lswitch(1:ngrids)
2808# endif
2809# ifdef WEC_ROLLER
2810 CASE ('Aout(idWdis)')
2811 npts=load_l(nval, cval, ngrids, lswitch)
2812 aout(idwdis,1:ngrids)=lswitch(1:ngrids)
2813# endif
2814# ifdef ROLLER_RENIERS
2815 CASE ('Aout(idWrol)')
2816 npts=load_l(nval, cval, ngrids, lswitch)
2817 aout(idwrol,1:ngrids)=lswitch(1:ngrids)
2818# endif
2819# ifdef WAVES_DSPR
2820 CASE ('Aout(idWvds)')
2821 npts=load_l(nval, cval, ngrids, lswitch)
2822 aout(idwvds,1:ngrids)=lswitch(1:ngrids)
2823 CASE ('Aout(idWvqp)')
2824 npts=load_l(nval, cval, ngrids, lswitch)
2825 aout(idwvqp,1:ngrids)=lswitch(1:ngrids)
2826# endif
2827# ifdef UV_KIRBY
2828 CASE ('Aout(idUwav)')
2829 npts=load_l(nval, cval, ngrids, lswitch)
2830 aout(iduwav,1:ngrids)=lswitch(1:ngrids)
2831 CASE ('Aout(idVwav)')
2832 npts=load_l(nval, cval, ngrids, lswitch)
2833 aout(idvwav,1:ngrids)=lswitch(1:ngrids)
2834# endif
2835# ifdef SOLVE3D
2836# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
2837 CASE ('Aout(idPair)')
2838 npts=load_l(nval, cval, ngrids, lswitch)
2839 aout(idpair,1:ngrids)=lswitch(1:ngrids)
2840# endif
2841# if defined BULK_FLUXES
2842 CASE ('Aout(idTair)')
2843 npts=load_l(nval, cval, ngrids, lswitch)
2844 aout(idtair,1:ngrids)=lswitch(1:ngrids)
2845# endif
2846# if defined BULK_FLUXES || defined ECOSIM
2847 CASE ('Aout(idUair)')
2848 npts=load_l(nval, cval, ngrids, lswitch)
2849 aout(iduair,1:ngrids)=lswitch(1:ngrids)
2850 CASE ('Aout(idVair)')
2851 npts=load_l(nval, cval, ngrids, lswitch)
2852 aout(idvair,1:ngrids)=lswitch(1:ngrids)
2853 CASE ('Aout(idUaiE)')
2854 npts=load_l(nval, cval, ngrids, lswitch)
2855 aout(iduaie,1:ngrids)=lswitch(1:ngrids)
2856 CASE ('Aout(idVaiN)')
2857 npts=load_l(nval, cval, ngrids, lswitch)
2858 aout(idvain,1:ngrids)=lswitch(1:ngrids)
2859# endif
2860 CASE ('Aout(idTsur)')
2861 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2862 DO ng=1,ngrids
2863 DO itrc=1,nat
2864 i=idtsur(itrc)
2865 aout(i,ng)=ltracer(itrc,ng)
2866 END DO
2867 END DO
2868# endif
2869 CASE ('Aout(idLhea)')
2870 npts=load_l(nval, cval, ngrids, lswitch)
2871 aout(idlhea,1:ngrids)=lswitch(1:ngrids)
2872 CASE ('Aout(idShea)')
2873 npts=load_l(nval, cval, ngrids, lswitch)
2874 aout(idshea,1:ngrids)=lswitch(1:ngrids)
2875 CASE ('Aout(idLrad)')
2876 npts=load_l(nval, cval, ngrids, lswitch)
2877 aout(idlrad,1:ngrids)=lswitch(1:ngrids)
2878 CASE ('Aout(idSrad)')
2879 npts=load_l(nval, cval, ngrids, lswitch)
2880 aout(idsrad,1:ngrids)=lswitch(1:ngrids)
2881 CASE ('Aout(idevap)')
2882 npts=load_l(nval, cval, ngrids, lswitch)
2883 aout(idevap,1:ngrids)=lswitch(1:ngrids)
2884 CASE ('Aout(idrain)')
2885 npts=load_l(nval, cval, ngrids, lswitch)
2886 aout(idrain,1:ngrids)=lswitch(1:ngrids)
2887 CASE ('Aout(idDano)')
2888 npts=load_l(nval, cval, ngrids, lswitch)
2889 aout(iddano,1:ngrids)=lswitch(1:ngrids)
2890 CASE ('Aout(idVvis)')
2891 npts=load_l(nval, cval, ngrids, lswitch)
2892 aout(idvvis,1:ngrids)=lswitch(1:ngrids)
2893 CASE ('Aout(idTdif)')
2894 npts=load_l(nval, cval, ngrids, lswitch)
2895 aout(idtdif,1:ngrids)=lswitch(1:ngrids)
2896# ifdef SALINITY
2897 CASE ('Aout(idSdif)')
2898 npts=load_l(nval, cval, ngrids, lswitch)
2899 aout(idsdif,1:ngrids)=lswitch(1:ngrids)
2900# endif
2901 CASE ('Aout(idHsbl)')
2902 npts=load_l(nval, cval, ngrids, lswitch)
2903 aout(idhsbl,1:ngrids)=lswitch(1:ngrids)
2904 CASE ('Aout(idHbbl)')
2905 npts=load_l(nval, cval, ngrids, lswitch)
2906 aout(idhbbl,1:ngrids)=lswitch(1:ngrids)
2907 CASE ('Aout(id2dRV)')
2908 IF (id2drv.eq.0) THEN
2909 IF (master) WRITE (out,280) 'id2dRV'
2910 exit_flag=5
2911 RETURN
2912 END IF
2913 npts=load_l(nval, cval, ngrids, lswitch)
2914 aout(id2drv,1:ngrids)=lswitch(1:ngrids)
2915 CASE ('Aout(id3dRV)')
2916 IF (id3drv.eq.0) THEN
2917 IF (master) WRITE (out,280) 'id3dRV'
2918 exit_flag=5
2919 RETURN
2920 END IF
2921 npts=load_l(nval, cval, ngrids, lswitch)
2922 aout(id3drv,1:ngrids)=lswitch(1:ngrids)
2923 CASE ('Aout(id2dPV)')
2924 IF (id2dpv.eq.0) THEN
2925 IF (master) WRITE (out,280) 'id2dPV'
2926 exit_flag=5
2927 RETURN
2928 END IF
2929 npts=load_l(nval, cval, ngrids, lswitch)
2930 aout(id2dpv,1:ngrids)=lswitch(1:ngrids)
2931 CASE ('Aout(id3dPV)')
2932 IF (id3dpv.eq.0) THEN
2933 IF (master) WRITE (out,280) 'id3dPV'
2934 exit_flag=5
2935 RETURN
2936 END IF
2937 npts=load_l(nval, cval, ngrids, lswitch)
2938 aout(id3dpv,1:ngrids)=lswitch(1:ngrids)
2939# if defined AVERAGES && defined AVERAGES_DETIDE && \
2940 (defined ssh_tides || defined uv_tides)
2941 CASE ('Aout(idFsuD)')
2942 IF (idfsud.eq.0) THEN
2943 IF (master) WRITE (out,280) 'idFsuD'
2944 exit_flag=5
2945 RETURN
2946 END IF
2947 npts=load_l(nval, cval, ngrids, lswitch)
2948 aout(idfsud,1:ngrids)=lswitch(1:ngrids)
2949 CASE ('Aout(idu2dD)')
2950 IF (idu2dd.eq.0) THEN
2951 IF (master) WRITE (out,280) 'idu2dD'
2952 exit_flag=5
2953 RETURN
2954 END IF
2955 npts=load_l(nval, cval, ngrids, lswitch)
2956 aout(idu2dd,1:ngrids)=lswitch(1:ngrids)
2957 CASE ('Aout(idv2dD)')
2958 IF (idv2dd.eq.0) THEN
2959 IF (master) WRITE (out,280) 'idv2dD'
2960 exit_flag=5
2961 RETURN
2962 END IF
2963 npts=load_l(nval, cval, ngrids, lswitch)
2964 aout(idv2dd,1:ngrids)=lswitch(1:ngrids)
2965# ifdef SOLVE3D
2966 CASE ('Aout(idu3dD)')
2967 IF (idu3dd.eq.0) THEN
2968 IF (master) WRITE (out,280) 'idu3dD'
2969 exit_flag=5
2970 RETURN
2971 END IF
2972 npts=load_l(nval, cval, ngrids, lswitch)
2973 aout(idu3dd,1:ngrids)=lswitch(1:ngrids)
2974 CASE ('Aout(idv3dD)')
2975 IF (idv3dd.eq.0) THEN
2976 IF (master) WRITE (out,280) 'idv3dD'
2977 exit_flag=5
2978 RETURN
2979 END IF
2980 npts=load_l(nval, cval, ngrids, lswitch)
2981 aout(idv3dd,1:ngrids)=lswitch(1:ngrids)
2982 CASE ('Aout(idTrcD)')
2983 IF (maxval(idtrcd).eq.0) THEN
2984 IF (master) WRITE (out,280) 'idTrcD'
2985 exit_flag=5
2986 RETURN
2987 END IF
2988 npts=load_l(nval, cval, nat, ngrids, ltracer)
2989 DO ng=1,ngrids
2990 DO itrc=1,nat
2991 i=idtrcd(itrc)
2992 aout(i,ng)=ltracer(itrc,ng)
2993 END DO
2994 END DO
2995# endif
2996# endif
2997# ifdef SOLVE3D
2998 CASE ('Aout(idHUav)')
2999 IF (idhuav.eq.0) THEN
3000 IF (master) WRITE (out,280) 'idHUav'
3001 exit_flag=5
3002 RETURN
3003 END IF
3004 npts=load_l(nval, cval, ngrids, lswitch)
3005 aout(idhuav,1:ngrids)=lswitch(1:ngrids)
3006 CASE ('Aout(idHVav)')
3007 IF (idhvav.eq.0) THEN
3008 IF (master) WRITE (out,280) 'idHVav'
3009 exit_flag=5
3010 RETURN
3011 END IF
3012 npts=load_l(nval, cval, ngrids, lswitch)
3013 aout(idhvav,1:ngrids)=lswitch(1:ngrids)
3014 CASE ('Aout(idUUav)')
3015 IF (iduuav.eq.0) THEN
3016 IF (master) WRITE (out,280) 'idUUav'
3017 exit_flag=5
3018 RETURN
3019 END IF
3020 npts=load_l(nval, cval, ngrids, lswitch)
3021 aout(iduuav,1:ngrids)=lswitch(1:ngrids)
3022 CASE ('Aout(idUVav)')
3023 IF (iduvav.eq.0) THEN
3024 IF (master) WRITE (out,280) 'idUVav'
3025 exit_flag=5
3026 RETURN
3027 END IF
3028 npts=load_l(nval, cval, ngrids, lswitch)
3029 aout(iduvav,1:ngrids)=lswitch(1:ngrids)
3030 CASE ('Aout(idVVav)')
3031 IF (idvvav.eq.0) THEN
3032 IF (master) WRITE (out,280) 'idVVav'
3033 exit_flag=5
3034 RETURN
3035 END IF
3036 npts=load_l(nval, cval, ngrids, lswitch)
3037 aout(idvvav,1:ngrids)=lswitch(1:ngrids)
3038# endif
3039 CASE ('Aout(idU2av)')
3040 IF (idu2av.eq.0) THEN
3041 IF (master) WRITE (out,280) 'idU2av'
3042 exit_flag=5
3043 RETURN
3044 END IF
3045 npts=load_l(nval, cval, ngrids, lswitch)
3046 aout(idu2av,1:ngrids)=lswitch(1:ngrids)
3047 CASE ('Aout(idV2av)')
3048 IF (idv2av.eq.0) THEN
3049 IF (master) WRITE (out,280) 'idV2av'
3050 exit_flag=5
3051 RETURN
3052 END IF
3053 npts=load_l(nval, cval, ngrids, lswitch)
3054 aout(idv2av,1:ngrids)=lswitch(1:ngrids)
3055 CASE ('Aout(idZZav)')
3056 IF (idzzav.eq.0) THEN
3057 IF (master) WRITE (out,280) 'idZZav'
3058 exit_flag=5
3059 RETURN
3060 END IF
3061 npts=load_l(nval, cval, ngrids, lswitch)
3062 aout(idzzav,1:ngrids)=lswitch(1:ngrids)
3063# ifdef SOLVE3D
3064 CASE ('Aout(idTTav)')
3065 IF (maxval(idttav).eq.0) THEN
3066 IF (master) WRITE (out,280) 'idTTav'
3067 exit_flag=5
3068 RETURN
3069 END IF
3070 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3071 DO ng=1,ngrids
3072 DO itrc=1,nat+npt
3073 i=idttav(itrc)
3074 aout(i,ng)=ltracer(itrc,ng)
3075 END DO
3076 END DO
3077 CASE ('Aout(idUTav)')
3078 IF (maxval(idutav).eq.0) THEN
3079 IF (master) WRITE (out,280) 'idUTav'
3080 exit_flag=5
3081 RETURN
3082 END IF
3083 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3084 DO ng=1,ngrids
3085 DO itrc=1,nat+npt
3086 i=idutav(itrc)
3087 aout(i,ng)=ltracer(itrc,ng)
3088 END DO
3089 END DO
3090 CASE ('Aout(idVTav)')
3091 IF (maxval(idvtav).eq.0) THEN
3092 IF (master) WRITE (out,280) 'idVTav'
3093 exit_flag=5
3094 RETURN
3095 END IF
3096 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3097 DO ng=1,ngrids
3098 DO itrc=1,nat+npt
3099 i=idvtav(itrc)
3100 aout(i,ng)=ltracer(itrc,ng)
3101 END DO
3102 END DO
3103 CASE ('Aout(iHUTav)')
3104 IF (maxval(ihutav).eq.0) THEN
3105 IF (master) WRITE (out,280) 'iHUTav'
3106 exit_flag=5
3107 RETURN
3108 END IF
3109 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3110 DO ng=1,ngrids
3111 DO itrc=1,nat+npt
3112 i=ihutav(itrc)
3113 aout(i,ng)=ltracer(itrc,ng)
3114 END DO
3115 END DO
3116 CASE ('Aout(iHVTav)')
3117 IF (maxval(ihvtav).eq.0) THEN
3118 IF (master) WRITE (out,280) 'iHVTav'
3119 exit_flag=5
3120 RETURN
3121 END IF
3122 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3123 DO ng=1,ngrids
3124 DO itrc=1,nat+npt
3125 i=ihvtav(itrc)
3126 aout(i,ng)=ltracer(itrc,ng)
3127 END DO
3128 END DO
3129# endif
3130# if defined SOLVE3D && defined T_PASSIVE
3131 CASE ('Aout(inert)')
3132 npts=load_l(nval, cval, npt, ngrids, linert)
3133 DO ng=1,ngrids
3134 DO i=1,npt
3135 itrc=idtvar(inert(i))
3136 aout(itrc,ng)=linert(i,ng)
3137 END DO
3138 END DO
3139# endif
3140#endif
3141#ifdef DIAGNOSTICS_UV
3142 CASE ('Dout(M2rate)')
3143 IF (m2rate.le.0) THEN
3144 IF (master) WRITE (out,280) 'M2rate'
3145 exit_flag=5
3146 RETURN
3147 END IF
3148 npts=load_l(nval, cval, ngrids, lswitch)
3149 DO ng=1,ngrids
3150 dout(iddu2d(m2rate),ng)=lswitch(ng)
3151 dout(iddv2d(m2rate),ng)=lswitch(ng)
3152 END DO
3153 CASE ('Dout(M2pgrd)')
3154 IF (m2pgrd.le.0) THEN
3155 IF (master) WRITE (out,280) 'M2pgrd'
3156 exit_flag=5
3157 RETURN
3158 END IF
3159 npts=load_l(nval, cval, ngrids, lswitch)
3160 DO ng=1,ngrids
3161 dout(iddu2d(m2pgrd),ng)=lswitch(ng)
3162 dout(iddv2d(m2pgrd),ng)=lswitch(ng)
3163 END DO
3164# ifdef UV_COR
3165 CASE ('Dout(M2fcor)')
3166 IF (m2fcor.le.0) THEN
3167 IF (master) WRITE (out,280) 'M2fcor'
3168 exit_flag=5
3169 RETURN
3170 END IF
3171 npts=load_l(nval, cval, ngrids, lswitch)
3172 DO ng=1,ngrids
3173 dout(iddu2d(m2fcor),ng)=lswitch(ng)
3174 dout(iddv2d(m2fcor),ng)=lswitch(ng)
3175 END DO
3176# endif
3177# ifdef UV_ADV
3178 CASE ('Dout(M2hadv)')
3179 IF (m2hadv.le.0) THEN
3180 IF (master) WRITE (out,280) 'M2hadv'
3181 exit_flag=5
3182 RETURN
3183 END IF
3184 npts=load_l(nval, cval, ngrids, lswitch)
3185 DO ng=1,ngrids
3186 dout(iddu2d(m2hadv),ng)=lswitch(ng)
3187 dout(iddv2d(m2hadv),ng)=lswitch(ng)
3188 END DO
3189 CASE ('Dout(M2xadv)')
3190 IF (m2xadv.le.0) THEN
3191 IF (master) WRITE (out,280) 'M2xadv'
3192 exit_flag=5
3193 RETURN
3194 END IF
3195 npts=load_l(nval, cval, ngrids, lswitch)
3196 DO ng=1,ngrids
3197 dout(iddu2d(m2xadv),ng)=lswitch(ng)
3198 dout(iddv2d(m2xadv),ng)=lswitch(ng)
3199 END DO
3200 CASE ('Dout(M2yadv)')
3201 IF (m2yadv.le.0) THEN
3202 IF (master) WRITE (out,280) 'M2yadv'
3203 exit_flag=5
3204 RETURN
3205 END IF
3206 npts=load_l(nval, cval, ngrids, lswitch)
3207 DO ng=1,ngrids
3208 dout(iddu2d(m2yadv),ng)=lswitch(ng)
3209 dout(iddv2d(m2yadv),ng)=lswitch(ng)
3210 END DO
3211# endif
3212# ifdef WEC_VF
3213 CASE ('Dout(M2hjvf)')
3214 IF (m2hjvf.le.0) THEN
3215 IF (master) WRITE (out,280) 'M2hjvf'
3216 exit_flag=5
3217 RETURN
3218 END IF
3219 npts=load_l(nval, cval, ngrids, lswitch)
3220 DO ng=1,ngrids
3221 dout(iddu2d(m2hjvf),ng)=lswitch(ng)
3222 dout(iddv2d(m2hjvf),ng)=lswitch(ng)
3223 END DO
3224 CASE ('Dout(M2kvrf)')
3225 IF (m2kvrf.le.0) THEN
3226 IF (master) WRITE (out,280) 'M2kvrf'
3227 exit_flag=5
3228 RETURN
3229 END IF
3230 npts=load_l(nval, cval, ngrids, lswitch)
3231 DO ng=1,ngrids
3232 dout(iddu2d(m2kvrf),ng)=lswitch(ng)
3233 dout(iddv2d(m2kvrf),ng)=lswitch(ng)
3234 END DO
3235# ifdef UV_COR
3236 CASE ('Dout(M2fsco)')
3237 IF (m2fsco.le.0) THEN
3238 IF (master) WRITE (out,280) 'M2fsco'
3239 exit_flag=5
3240 RETURN
3241 END IF
3242 npts=load_l(nval, cval, ngrids, lswitch)
3243 DO ng=1,ngrids
3244 dout(iddu2d(m2fsco),ng)=lswitch(ng)
3245 dout(iddv2d(m2fsco),ng)=lswitch(ng)
3246 END DO
3247# endif
3248# ifdef SURFACE_STREAMING
3249 CASE ('Dout(M2sstm)')
3250 IF (m2sstm.le.0) THEN
3251 IF (master) WRITE (out,280) 'M2sstm'
3252 exit_flag=5
3253 RETURN
3254 END IF
3255 npts=load_l(nval, cval, ngrids, lswitch)
3256 DO ng=1,ngrids
3257 dout(iddu2d(m2sstm),ng)=lswitch(ng)
3258 dout(iddv2d(m2sstm),ng)=lswitch(ng)
3259 END DO
3260# endif
3261# ifdef BOTTOM_STREAMING
3262 CASE ('Dout(M2bstm)')
3263 IF (m2bstm.le.0) THEN
3264 IF (master) WRITE (out,280) 'M2bstm'
3265 exit_flag=5
3266 RETURN
3267 END IF
3268 npts=load_l(nval, cval, ngrids, lswitch)
3269 DO ng=1,ngrids
3270 dout(iddu2d(m2bstm),ng)=lswitch(ng)
3271 dout(iddv2d(m2bstm),ng)=lswitch(ng)
3272 END DO
3273# endif
3274 CASE ('Dout(M2wrol)')
3275 IF (m2wrol.le.0) THEN
3276 IF (master) WRITE (out,280) 'M2wrol'
3277 exit_flag=5
3278 RETURN
3279 END IF
3280 npts=load_l(nval, cval, ngrids, lswitch)
3281 DO ng=1,ngrids
3282 dout(iddu2d(m2wrol),ng)=lswitch(ng)
3283 dout(iddv2d(m2wrol),ng)=lswitch(ng)
3284 END DO
3285 CASE ('Dout(M2wbrk)')
3286 IF (m2wbrk.le.0) THEN
3287 IF (master) WRITE (out,280) 'M2wbrk'
3288 exit_flag=5
3289 RETURN
3290 END IF
3291 npts=load_l(nval, cval, ngrids, lswitch)
3292 DO ng=1,ngrids
3293 dout(iddu2d(m2wbrk),ng)=lswitch(ng)
3294 dout(iddv2d(m2wbrk),ng)=lswitch(ng)
3295 END DO
3296 CASE ('Dout(M2zeta)')
3297 IF (m2zeta.le.0) THEN
3298 IF (master) WRITE (out,280) 'M2zeta'
3299 exit_flag=5
3300 RETURN
3301 END IF
3302 npts=load_l(nval, cval, ngrids, lswitch)
3303 DO ng=1,ngrids
3304 dout(iddu2d(m2zeta),ng)=lswitch(ng)
3305 dout(iddv2d(m2zeta),ng)=lswitch(ng)
3306 END DO
3307 CASE ('Dout(M2zetw)')
3308 IF (m2zetw.le.0) THEN
3309 IF (master) WRITE (out,280) 'M2zetw'
3310 exit_flag=5
3311 RETURN
3312 END IF
3313 npts=load_l(nval, cval, ngrids, lswitch)
3314 DO ng=1,ngrids
3315 dout(iddu2d(m2zetw),ng)=lswitch(ng)
3316 dout(iddv2d(m2zetw),ng)=lswitch(ng)
3317 END DO
3318 CASE ('Dout(M2zqsp)')
3319 IF (m2zqsp.le.0) THEN
3320 IF (master) WRITE (out,280) 'M2zqsp'
3321 exit_flag=5
3322 RETURN
3323 END IF
3324 npts=load_l(nval, cval, ngrids, lswitch)
3325 DO ng=1,ngrids
3326 dout(iddu2d(m2zqsp),ng)=lswitch(ng)
3327 dout(iddv2d(m2zqsp),ng)=lswitch(ng)
3328 END DO
3329 CASE ('Dout(M2zbeh)')
3330 IF (m2zbeh.le.0) THEN
3331 IF (master) WRITE (out,280) 'M2zbeh'
3332 exit_flag=5
3333 RETURN
3334 END IF
3335 npts=load_l(nval, cval, ngrids, lswitch)
3336 DO ng=1,ngrids
3337 dout(iddu2d(m2zbeh),ng)=lswitch(ng)
3338 dout(iddv2d(m2zbeh),ng)=lswitch(ng)
3339 END DO
3340# endif
3341# if defined UV_VIS2 || defined UV_VIS4
3342 CASE ('Dout(M2hvis)')
3343 IF (m2hvis.le.0) THEN
3344 IF (master) WRITE (out,280) 'M2hvis'
3345 exit_flag=5
3346 RETURN
3347 END IF
3348 npts=load_l(nval, cval, ngrids, lswitch)
3349 DO ng=1,ngrids
3350 dout(iddu2d(m2hvis),ng)=lswitch(ng)
3351 dout(iddv2d(m2hvis),ng)=lswitch(ng)
3352 END DO
3353 CASE ('Dout(M2xvis)')
3354 IF (m2xvis.le.0) THEN
3355 IF (master) WRITE (out,280) 'M2xvis'
3356 exit_flag=5
3357 RETURN
3358 END IF
3359 npts=load_l(nval, cval, ngrids, lswitch)
3360 DO ng=1,ngrids
3361 dout(iddu2d(m2xvis),ng)=lswitch(ng)
3362 dout(iddv2d(m2xvis),ng)=lswitch(ng)
3363 END DO
3364 CASE ('Dout(M2yvis)')
3365 IF (m2yvis.le.0) THEN
3366 IF (master) WRITE (out,280) 'M2yvis'
3367 exit_flag=5
3368 RETURN
3369 END IF
3370 npts=load_l(nval, cval, ngrids, lswitch)
3371 DO ng=1,ngrids
3372 dout(iddu2d(m2yvis),ng)=lswitch(ng)
3373 dout(iddv2d(m2yvis),ng)=lswitch(ng)
3374 END DO
3375# endif
3376 CASE ('Dout(M2sstr)')
3377 IF (m2sstr.le.0) THEN
3378 IF (master) WRITE (out,280) 'M2sstr'
3379 exit_flag=5
3380 RETURN
3381 END IF
3382 npts=load_l(nval, cval, ngrids, lswitch)
3383 DO ng=1,ngrids
3384 dout(iddu2d(m2sstr),ng)=lswitch(ng)
3385 dout(iddv2d(m2sstr),ng)=lswitch(ng)
3386 END DO
3387 CASE ('Dout(M2bstr)')
3388 IF (m2bstr.le.0) THEN
3389 IF (master) WRITE (out,280) 'M2bstr'
3390 exit_flag=5
3391 RETURN
3392 END IF
3393 npts=load_l(nval, cval, ngrids, lswitch)
3394 DO ng=1,ngrids
3395 dout(iddu2d(m2bstr),ng)=lswitch(ng)
3396 dout(iddv2d(m2bstr),ng)=lswitch(ng)
3397 END DO
3398# ifdef SOLVE3D
3399 CASE ('Dout(M3rate)')
3400 IF (m3rate.le.0) THEN
3401 IF (master) WRITE (out,280) 'M3rate'
3402 exit_flag=5
3403 RETURN
3404 END IF
3405 npts=load_l(nval, cval, ngrids, lswitch)
3406 DO ng=1,ngrids
3407 dout(iddu3d(m3rate),ng)=lswitch(ng)
3408 dout(iddv3d(m3rate),ng)=lswitch(ng)
3409 END DO
3410 CASE ('Dout(M3pgrd)')
3411 IF (m3pgrd.le.0) THEN
3412 IF (master) WRITE (out,280) 'M3pgrd'
3413 exit_flag=5
3414 RETURN
3415 END IF
3416 npts=load_l(nval, cval, ngrids, lswitch)
3417 DO ng=1,ngrids
3418 dout(iddu3d(m3pgrd),ng)=lswitch(ng)
3419 dout(iddv3d(m3pgrd),ng)=lswitch(ng)
3420 END DO
3421# ifdef UV_COR
3422 CASE ('Dout(M3fcor)')
3423 IF (m3fcor.le.0) THEN
3424 IF (master) WRITE (out,280) 'M3fcor'
3425 exit_flag=5
3426 RETURN
3427 END IF
3428 npts=load_l(nval, cval, ngrids, lswitch)
3429 DO ng=1,ngrids
3430 dout(iddu3d(m3fcor),ng)=lswitch(ng)
3431 dout(iddv3d(m3fcor),ng)=lswitch(ng)
3432 END DO
3433# endif
3434# ifdef UV_ADV
3435 CASE ('Dout(M3hadv)')
3436 IF (m3hadv.le.0) THEN
3437 IF (master) WRITE (out,280) 'M3hadv'
3438 exit_flag=5
3439 RETURN
3440 END IF
3441 npts=load_l(nval, cval, ngrids, lswitch)
3442 DO ng=1,ngrids
3443 dout(iddu3d(m3hadv),ng)=lswitch(ng)
3444 dout(iddv3d(m3hadv),ng)=lswitch(ng)
3445 END DO
3446 CASE ('Dout(M3xadv)')
3447 IF (m3xadv.le.0) THEN
3448 IF (master) WRITE (out,280) 'M3xadv'
3449 exit_flag=5
3450 RETURN
3451 END IF
3452 npts=load_l(nval, cval, ngrids, lswitch)
3453 DO ng=1,ngrids
3454 dout(iddu3d(m3xadv),ng)=lswitch(ng)
3455 dout(iddv3d(m3xadv),ng)=lswitch(ng)
3456 END DO
3457 CASE ('Dout(M3yadv)')
3458 IF (m3yadv.le.0) THEN
3459 IF (master) WRITE (out,280) 'M3yadv'
3460 exit_flag=5
3461 RETURN
3462 END IF
3463 npts=load_l(nval, cval, ngrids, lswitch)
3464 DO ng=1,ngrids
3465 dout(iddu3d(m3yadv),ng)=lswitch(ng)
3466 dout(iddv3d(m3yadv),ng)=lswitch(ng)
3467 END DO
3468 CASE ('Dout(M3vadv)')
3469 IF (m3vadv.le.0) THEN
3470 IF (master) WRITE (out,280) 'M3vadv'
3471 exit_flag=5
3472 RETURN
3473 END IF
3474 npts=load_l(nval, cval, ngrids, lswitch)
3475 DO ng=1,ngrids
3476 dout(iddu3d(m3vadv),ng)=lswitch(ng)
3477 dout(iddv3d(m3vadv),ng)=lswitch(ng)
3478 END DO
3479# endif
3480# ifdef WEC_VF
3481 CASE ('Dout(M3hjvf)')
3482 IF (m3hjvf.le.0) THEN
3483 IF (master) WRITE (out,280) 'M3hjvf'
3484 exit_flag=5
3485 RETURN
3486 END IF
3487 npts=load_l(nval, cval, ngrids, lswitch)
3488 DO ng=1,ngrids
3489 dout(iddu3d(m3hjvf),ng)=lswitch(ng)
3490 dout(iddv3d(m3hjvf),ng)=lswitch(ng)
3491 END DO
3492 CASE ('Dout(M3vjvf)')
3493 IF (m3vjvf.le.0) THEN
3494 IF (master) WRITE (out,280) 'M3vjvf'
3495 exit_flag=5
3496 RETURN
3497 END IF
3498 npts=load_l(nval, cval, ngrids, lswitch)
3499 DO ng=1,ngrids
3500 dout(iddu3d(m3vjvf),ng)=lswitch(ng)
3501 dout(iddv3d(m3vjvf),ng)=lswitch(ng)
3502 END DO
3503 CASE ('Dout(M3kvrf)')
3504 IF (m3kvrf.le.0) THEN
3505 IF (master) WRITE (out,280) 'M3kvrf'
3506 exit_flag=5
3507 RETURN
3508 END IF
3509 npts=load_l(nval, cval, ngrids, lswitch)
3510 DO ng=1,ngrids
3511 dout(iddu3d(m3kvrf),ng)=lswitch(ng)
3512 dout(iddv3d(m3kvrf),ng)=lswitch(ng)
3513 END DO
3514# ifdef UV_COR
3515 CASE ('Dout(M3fsco)')
3516 IF (m3fsco.le.0) THEN
3517 IF (master) WRITE (out,280) 'M3fsco'
3518 exit_flag=5
3519 RETURN
3520 END IF
3521 npts=load_l(nval, cval, ngrids, lswitch)
3522 DO ng=1,ngrids
3523 dout(iddu3d(m3fsco),ng)=lswitch(ng)
3524 dout(iddv3d(m3fsco),ng)=lswitch(ng)
3525 END DO
3526# endif
3527# ifdef SURFACE_STREAMING
3528 CASE ('Dout(M3sstm)')
3529 IF (m3sstm.le.0) THEN
3530 IF (master) WRITE (out,280) 'M3sstm'
3531 exit_flag=5
3532 RETURN
3533 END IF
3534 npts=load_l(nval, cval, ngrids, lswitch)
3535 DO ng=1,ngrids
3536 dout(iddu3d(m3sstm),ng)=lswitch(ng)
3537 dout(iddv3d(m3sstm),ng)=lswitch(ng)
3538 END DO
3539# endif
3540# ifdef BOTTOM_STREAMING
3541 CASE ('Dout(M3bstm)')
3542 IF (m3bstm.le.0) THEN
3543 IF (master) WRITE (out,280) 'M3bstm'
3544 exit_flag=5
3545 RETURN
3546 END IF
3547 npts=load_l(nval, cval, ngrids, lswitch)
3548 DO ng=1,ngrids
3549 dout(iddu3d(m3bstm),ng)=lswitch(ng)
3550 dout(iddv3d(m3bstm),ng)=lswitch(ng)
3551 END DO
3552# endif
3553 CASE ('Dout(M3wrol)')
3554 IF (m3wrol.le.0) THEN
3555 IF (master) WRITE (out,280) 'M3wrol'
3556 exit_flag=5
3557 RETURN
3558 END IF
3559 npts=load_l(nval, cval, ngrids, lswitch)
3560 DO ng=1,ngrids
3561 dout(iddu3d(m3wrol),ng)=lswitch(ng)
3562 dout(iddv3d(m3wrol),ng)=lswitch(ng)
3563 END DO
3564 CASE ('Dout(M3wbrk)')
3565 IF (m3wbrk.le.0) THEN
3566 IF (master) WRITE (out,280) 'M3wbrk'
3567 exit_flag=5
3568 RETURN
3569 END IF
3570 npts=load_l(nval, cval, ngrids, lswitch)
3571 DO ng=1,ngrids
3572 dout(iddu3d(m3wbrk),ng)=lswitch(ng)
3573 dout(iddv3d(m3wbrk),ng)=lswitch(ng)
3574 END DO
3575# endif
3576# if defined UV_VIS2 || defined UV_VIS4
3577 CASE ('Dout(M3hvis)')
3578 IF (m3hvis.le.0) THEN
3579 IF (master) WRITE (out,280) 'M3hvis'
3580 exit_flag=5
3581 RETURN
3582 END IF
3583 npts=load_l(nval, cval, ngrids, lswitch)
3584 DO ng=1,ngrids
3585 dout(iddu3d(m3hvis),ng)=lswitch(ng)
3586 dout(iddv3d(m3hvis),ng)=lswitch(ng)
3587 END DO
3588 CASE ('Dout(M3xvis)')
3589 IF (m3xvis.le.0) THEN
3590 IF (master) WRITE (out,280) 'M3xvis'
3591 exit_flag=5
3592 RETURN
3593 END IF
3594 npts=load_l(nval, cval, ngrids, lswitch)
3595 DO ng=1,ngrids
3596 dout(iddu3d(m3xvis),ng)=lswitch(ng)
3597 dout(iddv3d(m3xvis),ng)=lswitch(ng)
3598 END DO
3599 CASE ('Dout(M3yvis)')
3600 IF (m3yvis.le.0) THEN
3601 IF (master) WRITE (out,280) 'M3yvis'
3602 exit_flag=5
3603 RETURN
3604 END IF
3605 npts=load_l(nval, cval, ngrids, lswitch)
3606 DO ng=1,ngrids
3607 dout(iddu3d(m3yvis),ng)=lswitch(ng)
3608 dout(iddv3d(m3yvis),ng)=lswitch(ng)
3609 END DO
3610# endif
3611 CASE ('Dout(M3vvis)')
3612 IF (m3vvis.le.0) THEN
3613 IF (master) WRITE (out,280) 'M3vvis'
3614 exit_flag=5
3615 RETURN
3616 END IF
3617 npts=load_l(nval, cval, ngrids, lswitch)
3618 DO ng=1,ngrids
3619 dout(iddu3d(m3vvis),ng)=lswitch(ng)
3620 dout(iddv3d(m3vvis),ng)=lswitch(ng)
3621 END DO
3622# endif
3623#endif
3624#if defined DIAGNOSTICS_TS && defined SOLVE3D
3625 CASE ('Dout(iTrate)')
3626 IF (itrate.le.0) THEN
3627 IF (master) WRITE (out,280) 'iTrate'
3628 exit_flag=5
3629 RETURN
3630 END IF
3631 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3632 DO ng=1,ngrids
3633 DO itrc=1,nat
3634 dout(iddtrc(itrc,itrate),ng)=ltracer(itrc,ng)
3635 END DO
3636# ifdef T_PASSIVE
3637 DO i=1,npt
3638 itrc=inert(i)
3639 dout(iddtrc(itrc,itrate),ng)=ltracer(nat+i,ng)
3640 END DO
3641# endif
3642 END DO
3643 CASE ('Dout(iThadv)')
3644 IF (ithadv.le.0) THEN
3645 IF (master) WRITE (out,280) 'iThadv'
3646 exit_flag=5
3647 RETURN
3648 END IF
3649 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3650 DO ng=1,ngrids
3651 DO itrc=1,nat
3652 dout(iddtrc(itrc,ithadv),ng)=ltracer(itrc,ng)
3653 END DO
3654# ifdef T_PASSIVE
3655 DO i=1,npt
3656 itrc=inert(i)
3657 dout(iddtrc(itrc,ithadv),ng)=ltracer(nat+i,ng)
3658 END DO
3659# endif
3660 END DO
3661 CASE ('Dout(iTxadv)')
3662 IF (itxadv.le.0) THEN
3663 IF (master) WRITE (out,280) 'iTxadv'
3664 exit_flag=5
3665 RETURN
3666 END IF
3667 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3668 DO ng=1,ngrids
3669 DO itrc=1,nat
3670 dout(iddtrc(itrc,itxadv),ng)=ltracer(itrc,ng)
3671 END DO
3672# ifdef T_PASSIVE
3673 DO i=1,npt
3674 itrc=inert(i)
3675 dout(iddtrc(itrc,itxadv),ng)=ltracer(nat+i,ng)
3676 END DO
3677# endif
3678 END DO
3679 CASE ('Dout(iTyadv)')
3680 IF (ityadv.le.0) THEN
3681 IF (master) WRITE (out,280) 'iTyadv'
3682 exit_flag=5
3683 RETURN
3684 END IF
3685 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3686 DO ng=1,ngrids
3687 DO itrc=1,nat
3688 dout(iddtrc(itrc,ityadv),ng)=ltracer(itrc,ng)
3689 END DO
3690# ifdef T_PASSIVE
3691 DO i=1,npt
3692 itrc=inert(i)
3693 dout(iddtrc(itrc,ityadv),ng)=ltracer(nat+i,ng)
3694 END DO
3695# endif
3696 END DO
3697 CASE ('Dout(iTvadv)')
3698 IF (itvadv.le.0) THEN
3699 IF (master) WRITE (out,280) 'iTvadv'
3700 exit_flag=5
3701 RETURN
3702 END IF
3703 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3704 DO ng=1,ngrids
3705 DO itrc=1,nat
3706 dout(iddtrc(itrc,itvadv),ng)=ltracer(itrc,ng)
3707 END DO
3708# ifdef T_PASSIVE
3709 DO i=1,npt
3710 itrc=inert(i)
3711 dout(iddtrc(itrc,itvadv),ng)=ltracer(nat+i,ng)
3712 END DO
3713# endif
3714 END DO
3715# if defined TS_DIF2 || defined TS_DIF4
3716 CASE ('Dout(iThdif)')
3717 IF (ithdif.le.0) THEN
3718 IF (master) WRITE (out,280) 'iThdif'
3719 exit_flag=5
3720 RETURN
3721 END IF
3722 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3723 DO ng=1,ngrids
3724 DO itrc=1,nat
3725 dout(iddtrc(itrc,ithdif),ng)=ltracer(itrc,ng)
3726 END DO
3727# ifdef T_PASSIVE
3728 DO i=1,npt
3729 itrc=inert(i)
3730 dout(iddtrc(itrc,ithdif),ng)=ltracer(nat+i,ng)
3731 END DO
3732# endif
3733 END DO
3734 CASE ('Dout(iTxdif)')
3735 IF (itxdif.le.0) THEN
3736 IF (master) WRITE (out,280) 'iTxdif'
3737 exit_flag=5
3738 RETURN
3739 END IF
3740 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3741 DO ng=1,ngrids
3742 DO itrc=1,nat
3743 dout(iddtrc(itrc,itxdif),ng)=ltracer(itrc,ng)
3744 END DO
3745# ifdef T_PASSIVE
3746 DO i=1,npt
3747 itrc=inert(i)
3748 dout(iddtrc(itrc,itxdif),ng)=ltracer(nat+i,ng)
3749 END DO
3750# endif
3751 END DO
3752 CASE ('Dout(iTydif)')
3753 IF (itydif.le.0) THEN
3754 IF (master) WRITE (out,280) 'iTydif'
3755 exit_flag=5
3756 RETURN
3757 END IF
3758 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3759 DO ng=1,ngrids
3760 DO itrc=1,nat
3761 dout(iddtrc(itrc,itydif),ng)=ltracer(itrc,ng)
3762 END DO
3763# ifdef T_PASSIVE
3764 DO i=1,npt
3765 itrc=inert(i)
3766 dout(iddtrc(itrc,itydif),ng)=ltracer(nat+i,ng)
3767 END DO
3768# endif
3769 END DO
3770# if defined MIX_GEO_TS || defined MIX_ISO_TS
3771 CASE ('Dout(iTsdif)')
3772 IF (itsdif.le.0) THEN
3773 IF (master) WRITE (out,280) 'iTsdif'
3774 exit_flag=5
3775 RETURN
3776 END IF
3777 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3778 DO ng=1,ngrids
3779 DO itrc=1,nat
3780 dout(iddtrc(itrc,itsdif),ng)=ltracer(itrc,ng)
3781 END DO
3782# ifdef T_PASSIVE
3783 DO i=1,npt
3784 itrc=inert(i)
3785 dout(iddtrc(itrc,itsdif),ng)=ltracer(nat+i,ng)
3786 END DO
3787# endif
3788 END DO
3789# endif
3790# endif
3791 CASE ('Dout(iTvdif)')
3792 IF (itvdif.le.0) THEN
3793 IF (master) WRITE (out,280) 'iTvdif'
3794 exit_flag=5
3795 RETURN
3796 END IF
3797 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3798 DO ng=1,ngrids
3799 DO itrc=1,nat
3800 dout(iddtrc(itrc,itvdif),ng)=ltracer(itrc,ng)
3801 END DO
3802# ifdef T_PASSIVE
3803 DO i=1,npt
3804 itrc=inert(i)
3805 dout(iddtrc(itrc,itvdif),ng)=ltracer(nat+i,ng)
3806 END DO
3807# endif
3808 END DO
3809#endif
3810 CASE ('NUSER')
3811 npts=load_i(nval, rval, 1, ivalue)
3812 nuser=ivalue(1)
3813 IF (nuser.gt.0) THEN
3814 IF (allocated(user)) deallocate (user)
3815 allocate ( user(nuser) )
3816 user=spval
3817 END IF
3818 CASE ('USER')
3819 IF (nuser.gt.0) THEN
3820 npts=load_r(nval, rval, nuser, user)
3821 END IF
3822 CASE ('INP_LIB')
3823 npts=load_i(nval, rval, 1, ivalue)
3824#if defined PIO_LIB && defined DISTRIBUTE
3825 inp_lib=ivalue(1)
3826 IF ((inp_lib.lt.1).or.(inp_lib.gt.2)) THEN
3827 IF (master) WRITE (out,260) 'inp_lib = ', &
3828 & inp_lib, &
3829 & 'Must be either 1 or 2'
3830 exit_flag=5
3831 RETURN
3832 END IF
3833#else
3834 inp_lib=1
3835#endif
3836 CASE ('OUT_LIB')
3837 npts=load_i(nval, rval, 1, ivalue)
3838#if defined PIO_LIB && defined DISTRIBUTE
3839 out_lib=ivalue(1)
3840 IF ((inp_lib.lt.1).or.(inp_lib.gt.2)) THEN
3841 IF (master) WRITE (out,260) 'out_lib = ', &
3842 & out_lib, &
3843 & 'Must be either 1 or 2'
3844 exit_flag=5
3845 RETURN
3846 END IF
3847#else
3848 out_lib=1
3849#endif
3850 CASE ('ExtractFlag')
3851 npts=load_i(nval, rval, ngrids, extractflag)
3852
3853#if defined PIO_LIB && defined DISTRIBUTE
3854 CASE ('PIO_METHOD')
3855 npts=load_i(nval, rval, 1, ivalue)
3856 IF ((ivalue(1).lt.0).or.(ivalue(1).gt.4)) THEN
3857 IF (master) WRITE (out,260) 'pio_method = ', &
3858 & ivalue(1), &
3859 & 'Must be between 1 and 4'
3860 ELSE
3861 SELECT CASE (ivalue(1))
3862 CASE (0)
3863 typecdf5=.true. ! CDF-5, not portable
3864 pio_method=pio_iotype_pnetcdf
3865 pio_methodname='PnetCDF'
3866 CASE (1)
3867 typecdf5=.false. ! NetCDF-3 64-bit
3868 pio_method=pio_iotype_pnetcdf
3869 pio_methodname='PnetCDF'
3870 CASE (2)
3871 pio_method=pio_iotype_netcdf
3872 pio_methodname='NetCDF'
3873 CASE (3)
3874 pio_method=pio_iotype_netcdf4c
3875 pio_methodname='NetCDF4c'
3876 CASE (4)
3877 pio_method=pio_iotype_netcdf4p
3878 pio_methodname='NetCDF4p'
3879 END SELECT
3880 END IF
3881 CASE ('PIO_IOTASKS')
3882 npts=load_i(nval, rval, 1, ivalue)
3883 pio_numiotasks=ivalue(1)
3884 IF ((pio_numiotasks.lt.1).or. &
3885 & (pio_numiotasks.gt.numthreads)) THEN
3886 IF (master) WRITE (out,260) 'pio_NumIOtasks = ', &
3887 & pio_numiotasks, &
3888 & 'Must be between 1 and NtileI*NtileJ'
3889 exit_flag=5
3890 RETURN
3891 END IF
3892 CASE ('PIO_STRIDE')
3893 npts=load_i(nval, rval, 1, ivalue)
3894 pio_stride=ivalue(1)
3895 IF ((pio_stride.lt.1).or. &
3896 (pio_stride*pio_numiotasks.gt.numthreads)) THEN
3897 IF (master) WRITE (out,260) 'pio_stride = ', &
3898 & pio_stride, &
3899 & 'Must be greater than 0 and not exceed NtileI*NtileJ'
3900 exit_flag=5
3901 RETURN
3902 END IF
3903 CASE ('PIO_BASE')
3904 npts=load_i(nval, rval, 1, ivalue)
3905 pio_base=ivalue(1)
3906 IF (pio_base.lt.0) THEN
3907 IF (master) WRITE (out,260) 'pio_base = ', &
3908 & pio_base, &
3909 & 'Is usually 0 or greater'
3910 exit_flag=5
3911 RETURN
3912 ELSE
3913 IF ((numthreads.eq.1).and.(pio_base.ne.0)) THEN
3914 IF (master) WRITE (out,260) 'pio_base = ', &
3915 & pio_base, &
3916 & 'Reset to 0 since running on a single process'
3917 pio_base=0 ! reset since offset is not needed
3918 END IF
3919 END IF
3920 CASE ('PIO_AGGREG')
3921 npts=load_i(nval, rval, 1, ivalue)
3922 pio_aggregator=ivalue(1)
3923 IF (pio_aggregator.lt.1) THEN
3924 IF (master) WRITE (out,260) 'pio_aggregator = ', &
3925 & pio_aggregator, &
3926 & 'Must be greater than 0'
3927 exit_flag=5
3928 RETURN
3929 END IF
3930 CASE ('PIO_REARR')
3931 npts=load_i(nval, rval, 1, ivalue)
3932 IF ((ivalue(1).lt.1).or.(ivalue(1).gt.2)) THEN
3933 IF (master) WRITE (out,260) 'pio_rearranger = ', &
3934 & ivalue(1), &
3935 & 'Must be 1 or 2'
3936 exit_flag=5
3937 RETURN
3938 ELSE
3939 SELECT CASE (ivalue(1))
3940 CASE (1)
3941 pio_rearranger=pio_rearr_box
3942 CASE (2)
3943 pio_rearranger=pio_rearr_subset
3944 END SELECT
3945 END IF
3946 CASE ('PIO_REARRCOM')
3947 npts=load_i(nval, rval, 1, ivalue)
3948 IF ((ivalue(1).lt.0).or.(ivalue(1).gt.1)) THEN
3949 IF (master) WRITE (out,260) 'pio_rearr_opt_comm = ', &
3950 & ivalue(1), &
3951 & 'Must be 0 or 1'
3952 exit_flag=5
3953 RETURN
3954 ELSE
3955 SELECT CASE (ivalue(1))
3956 CASE (0)
3957 pio_rearr_comm=pio_rearr_comm_p2p
3958 CASE (1)
3959 pio_rearr_comm=pio_rearr_comm_coll
3960 END SELECT
3961 END IF
3962 CASE ('PIO_REARRDIR')
3963 npts=load_i(nval, rval, 1, ivalue)
3964 IF ((ivalue(1).lt.0).or.(ivalue(1).gt.3)) THEN
3965 IF (master) WRITE (out,260) 'pio_rearr_opt_fcd = ', &
3966 & ivalue(1), &
3967 & 'Must be between 0 and 3'
3968 exit_flag=5
3969 RETURN
3970 ELSE
3971 SELECT CASE (ivalue(1))
3972 CASE (0)
3973 pio_rearr_fcd=pio_rearr_comm_fc_2d_enable
3974 CASE (1)
3975 pio_rearr_fcd=pio_rearr_comm_fc_1d_comp2io
3976 CASE (2)
3977 pio_rearr_fcd=pio_rearr_comm_fc_1d_io2comp
3978 CASE (3)
3979 pio_rearr_fcd=pio_rearr_comm_fc_2d_disable
3980 END SELECT
3981 END IF
3982 CASE ('PIO_C2I_HS')
3983 npts=load_l(nval, cval, 1, lvalue)
3984 pio_rearr_c2i_hs=lvalue(1)
3985 CASE ('PIO_C2I_Send')
3986 npts=load_l(nval, cval, 1, lvalue)
3987 pio_rearr_c2i_is=lvalue(1)
3988 CASE ('PIO_C2I_Preq')
3989 npts=load_i(nval, rval, 1, ivalue)
3990 IF (ivalue(1).lt.0) THEN
3991 pio_rearr_c2i_pr=pio_rearr_comm_unlimited_pend_req
3992 ELSE
3993 pio_rearr_c2i_pr=ivalue(1)
3994 END IF
3995 CASE ('PIO_I2C_HS')
3996 npts=load_l(nval, cval, 1, lvalue)
3997 pio_rearr_i2c_hs=lvalue(1)
3998 CASE ('PIO_I2C_Send')
3999 npts=load_l(nval, cval, 1, lvalue)
4000 pio_rearr_i2c_is=lvalue(1)
4001 CASE ('PIO_I2C_Preq')
4002 npts=load_i(nval, rval, 1, ivalue)
4003 IF (ivalue(1).lt.0) THEN
4004 pio_rearr_i2c_pr=pio_rearr_comm_unlimited_pend_req
4005 ELSE
4006 pio_rearr_i2c_pr=ivalue(1)
4007 END IF
4008#endif
4009 CASE ('NC_SHUFFLE')
4010 npts=load_i(nval, rval, 1, ivalue)
4011 shuffle=ivalue(1)
4012 CASE ('NC_DEFLATE')
4013 npts=load_i(nval, rval, 1, ivalue)
4014 deflate=ivalue(1)
4015 CASE ('NC_DLEVEL')
4016 npts=load_i(nval, rval, 1, ivalue)
4017 deflate_level=ivalue(1)
4018 CASE ('DAINAME')
4019 label='DAI - Data Assimilation Initial/Restart fields'
4020 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4021 & ngrids, nfiles, out_lib, dai)
4022 CASE ('GSTNAME')
4023 label='GST - generalized stability theory analysis'
4024 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4025 & ngrids, nfiles, out_lib, gst)
4026 CASE ('RSTNAME')
4027 label='RST - restart fields'
4028 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4029 & ngrids, nfiles, out_lib, rst)
4030 CASE ('HISNAME')
4031 label='HIS - nonlinear model history fields'
4032 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4033 & ngrids, nfiles, out_lib, his)
4034 CASE ('XTRNAME')
4035 label='XTR - nonlinear model extraction history fields'
4036 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4037 & ngrids, nfiles, out_lib, xtr)
4038 CASE ('QCKNAME')
4039 label='QCK - nonlinear model quicksave fields'
4040 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4041 & ngrids, nfiles, out_lib, qck)
4042 CASE ('TLMNAME')
4043 label='TLM - tangent linear model history fields'
4044 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4045 & ngrids, nfiles, out_lib, tlm)
4046 CASE ('TLFNAME')
4047 label='TLF - tangent linear model impulse forcing'
4048 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4049 & ngrids, nfiles, out_lib, tlf)
4050 CASE ('ADJNAME')
4051 label='ADM - adjoint model history fields'
4052 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4053 & ngrids, nfiles, out_lib, adm)
4054 CASE ('AVGNAME')
4055 label='AVG - time-averaged history fields'
4056 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4057 & ngrids, nfiles, out_lib, avg)
4058 CASE ('HARNAME')
4059 label='HAR - least-squares detiding harmonics'
4060 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4061 & ngrids, nfiles, out_lib, har)
4062 CASE ('DIANAME')
4063 label='DIA - time-averaged diagnostics fields'
4064 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4065 & ngrids, nfiles, out_lib, dia)
4066 CASE ('STANAME')
4067 label='STA - stations time-series'
4068 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4069 & ngrids, nfiles, out_lib, sta)
4070 CASE ('FLTNAME')
4071 label='FLT - Lagragian particles trajectories'
4072 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4073 & ngrids, nfiles, out_lib, flt)
4074 CASE ('GRDNAME')
4075 label='GRD - application grid'
4076 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4077 & ngrids, nfiles, inp_lib, grd)
4078 CASE ('GRXNAME')
4079 label='GRX - I/O histrory extract grid'
4080 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4081 & ngrids, nfiles, inp_lib, grx)
4082 CASE ('ININAME')
4083 label='INI - nonlinear model initial conditions'
4084 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4085 & ngrids, nfiles, inp_lib, ini)
4086 CASE ('IRPNAME')
4087 label='IRP - representer model initial conditions'
4088 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4089 & ngrids, nfiles, inp_lib, irp)
4090 CASE ('ITLNAME')
4091 label='ITL - tangent linear model initial conditions'
4092 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4093 & ngrids, nfiles, inp_lib, itl)
4094 CASE ('IADNAME')
4095 label='IAD - adjoint model initial conditions'
4096 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4097 & ngrids, nfiles, inp_lib, iad)
4098 CASE ('FWDNAME')
4099 label='FWD - basic state forward trajectory'
4100 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4101 & ngrids, nfiles, inp_lib, fwd)
4102 CASE ('ADSNAME')
4103 label='ADS - adjoint sensitivity functional'
4104 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4105 & ngrids, nfiles, inp_lib, ads)
4106#ifdef RBL4DVAR_FCT_SENSITIVITY
4107# ifndef OBS_SPACE
4108 CASE ('FOInameA')
4109 label='FOIA - adjoint sensitivity functional A'
4110 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4111 & ngrids, nfiles, inp_lib, foia)
4112 CASE ('FOInameB')
4113 label='FOIB - adjoint sensitivity functional B'
4114 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4115 & ngrids, nfiles, inp_lib, foib)
4116# endif
4117 CASE ('FCTnameA')
4118 label='FCTA - forecast state forward trajectory A'
4119 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4120 & ngrids, nfiles, inp_lib, fcta)
4121 CASE ('FCTnameB')
4122 label='FCTB - forecast state forward trajectory B'
4123 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4124 & ngrids, nfiles, inp_lib, fctb)
4125#endif
4126 CASE ('NGCNAME')
4127 DO i=1,len(ngcname)
4128 ngcname(i:i)=blank
4129 END DO
4130 ngcname=trim(adjustl(cval(nval)))
4131 CASE ('NBCFILES')
4132 npts=load_i(nval, rval, ngrids, nbcfiles)
4133 DO ng=1,ngrids
4134 IF (nbcfiles(ng).le.0) THEN
4135 IF (master) WRITE (out,260) 'NBCFILES', nbcfiles(ng), &
4136 & 'Must be equal or greater than one.'
4137 exit_flag=4
4138 RETURN
4139 END IF
4140 END DO
4141 max_ffiles=maxval(nbcfiles)
4142 allocate ( bry(max_ffiles,ngrids) )
4143 allocate ( bryids(max_ffiles,ngrids) )
4144# if defined PIO_LIB && defined DISTRIBUTE
4145 allocate ( brydesc(max_ffiles,ngrids) )
4146# endif
4147 allocate ( nbccount(max_ffiles,ngrids) )
4148 bryids(1:max_ffiles,1:ngrids)=-1
4149# if defined PIO_LIB && defined DISTRIBUTE
4150 brydesc(1:max_ffiles,1:ngrids)%fh=-1
4151# endif
4152 nbccount(1:max_ffiles,1:ngrids)=0
4153 CASE ('BRYNAME')
4154 label='BRY - lateral open boundary conditions'
4155 DO ng=1,ngrids
4156 IF (nbcfiles(ng).lt.0) THEN
4157 IF (master) WRITE (out,290) 'nBCfiles = ', &
4158 & nbcfiles(ng), &
4159 & 'KeyWord ''NBCFILES'' unread or misssing from '// &
4160 & 'input script ''roms.in''.'
4161 exit_flag=4
4162 RETURN
4163 END IF
4164 END DO
4165 npts=load_s2d(nval, cval, cdim, line, label, ibcfile, &
4166 & igrid, ngrids, nbcfiles, nbccount, &
4167 & max_ffiles, inp_lib, bry)
4168 CASE ('NCLMFILES')
4169 npts=load_i(nval, rval, ngrids, nclmfiles)
4170 DO ng=1,ngrids
4171 IF (nclmfiles(ng).le.0) THEN
4172 IF (master) WRITE (out,260) 'NCLMFILES', &
4173 & nclmfiles(ng), &
4174 & 'Must be equal or greater than one.'
4175 exit_flag=4
4176 RETURN
4177 END IF
4178 END DO
4179 max_ffiles=maxval(nclmfiles)
4180 allocate ( clm(max_ffiles,ngrids) )
4181 allocate ( clmids(max_ffiles,ngrids) )
4182# if defined PIO_LIB && defined DISTRIBUTE
4183 allocate ( clmdesc(max_ffiles,ngrids) )
4184# endif
4185 allocate ( nclmcount(max_ffiles,ngrids) )
4186 clmids(1:max_ffiles,1:ngrids)=-1
4187# if defined PIO_LIB && defined DISTRIBUTE
4188 clmdesc(1:max_ffiles,1:ngrids)%fh=-1
4189# endif
4190 nclmcount(1:max_ffiles,1:ngrids)=0
4191 CASE ('CLMNAME')
4192 label='CLM - climatology fields'
4193 DO ng=1,ngrids
4194 IF (nclmfiles(ng).lt.0) THEN
4195 IF (master) WRITE (out,290) 'nCLMfiles = ', &
4196 & nclmfiles(ng), &
4197 & 'KeyWord ''NCLMFILES'' unread or misssing from '// &
4198 & 'input script ''roms.in''.'
4199 exit_flag=4
4200 RETURN
4201 END IF
4202 END DO
4203 npts=load_s2d(nval, cval, cdim, line, label, iclmfile, &
4204 & igrid, ngrids, nclmfiles, nclmcount, &
4205 & max_ffiles, inp_lib, clm)
4206 CASE ('NUDNAME')
4207 label='NUD - nudging coefficients'
4208 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4209 & ngrids, nfiles, inp_lib, nud)
4210 CASE ('SSFNAME')
4211 label='SSF - Sources/Sinks forcing fields'
4212 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4213 & ngrids, nfiles, inp_lib, ssf)
4214# if defined SSH_TIDES || defined UV_TIDES || \
4215 defined tide_generating_forces
4216 CASE ('TIDENAME')
4217 label='TIDE - Tidal forcing fields'
4218 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4219 & ngrids, nfiles, inp_lib, tide)
4220# endif
4221 CASE ('NFFILES')
4222 npts=load_i(nval, rval, ngrids, nffiles)
4223 DO ng=1,ngrids
4224 IF (nffiles(ng).le.0) THEN
4225 IF (master) WRITE (out,260) 'NFFILES', nffiles(ng), &
4226 & 'Must be equal or greater than one.'
4227 exit_flag=4
4228 RETURN
4229 END IF
4230 END DO
4231 max_ffiles=maxval(nffiles)
4232 allocate ( frc(max_ffiles,ngrids) )
4233 allocate ( frcids(max_ffiles,ngrids) )
4234# if defined PIO_LIB && defined DISTRIBUTE
4235 allocate ( frcdesc(max_ffiles,ngrids) )
4236# endif
4237 allocate ( ncount(max_ffiles,ngrids) )
4238 frcids(1:max_ffiles,1:ngrids)=-1
4239# if defined PIO_LIB && defined DISTRIBUTE
4240 frcdesc(1:max_ffiles,1:ngrids)%fh=-1
4241# endif
4242 ncount(1:max_ffiles,1:ngrids)=0
4243 CASE ('FRCNAME')
4244 label='FRC - forcing fields'
4245 DO ng=1,ngrids
4246 IF (nffiles(ng).lt.0) THEN
4247 IF (master) WRITE (out,290) 'nFfiles = ', &
4248 & nffiles(ng), &
4249 & 'KeyWord ''NFFILES'' unread or misssing from '// &
4250 & 'input script ''roms.in''.'
4251 exit_flag=4
4252 RETURN
4253 END IF
4254 END DO
4255 npts=load_s2d(nval, cval, cdim, line, label, ifile, &
4256 & igrid, ngrids, nffiles, ncount, max_ffiles, &
4257 & inp_lib, frc)
4258 CASE ('APARNAM')
4259 DO i=1,len(aparnam)
4260 aparnam(i:i)=blank
4261 END DO
4262 aparnam=trim(adjustl(cval(nval)))
4263 CASE ('SPOSNAM')
4264 DO i=1,len(sposnam)
4265 sposnam(i:i)=blank
4266 END DO
4267 sposnam=trim(adjustl(cval(nval)))
4268 CASE ('FPOSNAM')
4269 DO i=1,len(fposnam)
4270 fposnam(i:i)=blank
4271 END DO
4272 fposnam=trim(adjustl(cval(nval)))
4273 CASE ('IPARNAM')
4274 DO i=1,len(iparnam)
4275 iparnam(i:i)=blank
4276 END DO
4277 iparnam=trim(adjustl(cval(nval)))
4278 CASE ('BPARNAM')
4279 DO i=1,len(bparnam)
4280 bparnam(i:i)=blank
4281 END DO
4282 bparnam=trim(adjustl(cval(nval)))
4283 CASE ('SPARNAM')
4284 DO i=1,len(sparnam)
4285 sparnam(i:i)=blank
4286 END DO
4287 sparnam=trim(adjustl(cval(nval)))
4288 CASE ('USRNAME')
4289 DO i=1,len(usrname)
4290 usrname(i:i)=blank
4291 END DO
4292 usrname=trim(adjustl(cval(nval)))
4293 END SELECT
4294 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
4295 END IF
4296 END DO
4297 10 IF (master) WRITE (out,50) line
4298 exit_flag=4
4299 RETURN
4300 20 CLOSE (inp)
4301!
4302!-----------------------------------------------------------------------
4303! Process input parameters.
4304!-----------------------------------------------------------------------
4305!
4306! Check if nesting parameters "NestLayers", "GridsInLayer", and
4307! "GridNumber" have been assigned. The code below is necessary
4308! for compatability with old "roms.in" input scripts.
4309!
4310#ifndef NESTING
4311 IF (.not.got_nestlayers) THEN
4312 nestlayers=1
4313 IF (.not.allocated(gridsinlayer)) THEN
4314 allocate ( gridsinlayer(nestlayers) )
4315 END IF
4316 IF (.not.allocated(gridnumber)) THEN
4317 allocate ( gridnumber(ngrids,nestlayers) )
4318 END IF
4319 END IF
4320 gridsinlayer=1 ! In case that users set illegal
4321 gridnumber=1 ! values in non-nesting applications
4322#else
4323 IF (.not.got_nestlayers) THEN
4324 IF (master) THEN
4325 WRITE (out,320) 'NestLayers', &
4326 & 'Add "NestLayers" keyword after "Ngrids".'
4327 exit_flag=5
4328 RETURN
4329 END IF
4330 END IF
4331 IF (.not.allocated(gridsinlayer)) THEN
4332 IF (master) THEN
4333 WRITE (out,320) 'GridsInLayer', &
4334 & 'Add "GridsInLayer" keyword after "NestLayers".'
4335 exit_flag=5
4336 RETURN
4337 END IF
4338 END IF
4339#endif
4340
4341#ifdef SP4DVAR
4342!
4343! Check if the number of split time intervals (Nsaddle) in the saddle-
4344! point 4D-Var is legal for a simulation.
4345!
4346 DO ng=1,ngrids
4347 IF (mod((ntimes(ng)/nhis(ng)),nsaddle).ne.0) THEN
4348 IF (master) THEN
4349 WRITE (out,350) 'Nsaddle = ', nsaddle, ng, &
4350 & 'ntimes/nHIS = ', ntimes(ng)/nhis(ng), &
4351 & 'MOD(ntimes/nHis,Nsaddle) = ', &
4352 & mod((ntimes(ng)/nhis(ng)),nsaddle), &
4353 & 'must be zero for legal computations.', &
4354 & 'Revise input parameters.'
4355 END IF
4356 exit_flag=4
4357 RETURN
4358 END IF
4359 END DO
4360#endif
4361
4362# if defined FORWARD_FLUXES && \
4363 (defined bulk_fluxes || defined frc_coupling)
4364!
4365! Make sure that logical output switches are activated for wind
4366! stress, shortwave radiation, and surface active tracers fluxes
4367! when using fluxes from the nonlinear model via (bulk_flux).
4368!
4369 DO ng=1,ngrids
4370 qout(idusms,ng)=.true.
4371 qout(idvsms,ng)=.true.
4372# ifdef ATM_PRESS
4373 qout(idpair,ng)=.true.
4374# endif
4375# ifdef SOLVE3D
4376 qout(idsrad,ng)=.true.
4377 qout(idtsur(itemp),ng)=.true.
4378# if defined EMINUSP || defined FRC_COUPLING
4379 qout(idempf,ng)=.true.
4380# endif
4381# endif
4382 END DO
4383#endif
4384
4385#if defined FORWARD_MIXING && defined SOLVE3D && \
4386 (defined gls_mixing || defined lmd_mixing || \
4387 defined my25_mixing)
4388!
4389! Make sure that logical output switches are activated for vertical
4390! diffusion and viscosity mixing coefficients.
4391!
4392 DO ng=1,ngrids
4393 hout(idsdif,ng)=.true.
4394 hout(idtdif,ng)=.true.
4395 hout(idvvis,ng)=.true.
4396 END DO
4397#endif
4398
4399#if defined FORCING_SV || defined SO_SEMI || \
4400 defined stochastic_opt
4401!
4402! Make sure that logical output switches are activated for the
4403! Forcing Singular Vectors or Stochastic Optimals variables.
4404!
4405 DO ng=1,ngrids
4406 IF (scalars(ng)%Fstate(isfsur)) hout(idfsur,ng)=.true.
4407# ifndef SOLVE3D
4408 IF (scalars(ng)%Fstate(isubar)) hout(idubar,ng)=.true.
4409 IF (scalars(ng)%Fstate(isvbar)) hout(idvbar,ng)=.true.
4410# else
4411 IF (scalars(ng)%Fstate(isuvel)) hout(iduvel,ng)=.true.
4412 IF (scalars(ng)%Fstate(isvvel)) hout(idvvel,ng)=.true.
4413 DO itrc=1,nt(ng)
4414 IF (scalars(ng)%Fstate(istvar(itrc))) THEN
4415 hout(idtvar(itrc),ng)=.true.
4416 END IF
4417 IF (scalars(ng)%Fstate(istsur(itrc))) THEN
4418 hout(idtsur(itrc),ng)=.true.
4419 END IF
4420 END DO
4421# endif
4422 IF (scalars(ng)%Fstate(isustr)) hout(idusms,ng)=.true.
4423 IF (scalars(ng)%Fstate(isvstr)) hout(idvsms,ng)=.true.
4424 END DO
4425#endif
4426!
4427! Make sure that both component switches are activated when processing
4428! (Eastward,Northward) momentum components at RHO-points.
4429!
4430 DO ng=1,ngrids
4431 IF (.not.hout(idu2de,ng).and.hout(idv2dn,ng)) THEN
4432 hout(idu2de,ng)=.true.
4433 END IF
4434 IF (.not.hout(idv2dn,ng).and.hout(idu2de,ng)) THEN
4435 hout(idv2dn,ng)=.true.
4436 END IF
4437#ifdef SOLVE3D
4438 IF (.not.hout(idu3de,ng).and.hout(idv3dn,ng)) THEN
4439 hout(idu3de,ng)=.true.
4440 END IF
4441 IF (.not.hout(idv3dn,ng).and.hout(idu3de,ng)) THEN
4442 hout(idv3dn,ng)=.true.
4443 END IF
4444#endif
4445#ifdef AVERAGES
4446 IF (.not.aout(idu2de,ng).and.aout(idv2dn,ng)) THEN
4447 aout(idu2de,ng)=.true.
4448 END IF
4449 IF (.not.aout(idv2dn,ng).and.aout(idu2de,ng)) THEN
4450 aout(idv2dn,ng)=.true.
4451 END IF
4452# ifdef SOLVE3D
4453 IF (.not.aout(idu3de,ng).and.aout(idv3dn,ng)) THEN
4454 aout(idu3de,ng)=.true.
4455 END IF
4456 IF (.not.aout(idv3dn,ng).and.aout(idu3de,ng)) THEN
4457 aout(idv3dn,ng)=.true.
4458 END IF
4459# endif
4460#endif
4461 END DO
4462!
4463! Set various parameters.
4464!
4465 DO ng=1,ngrids
4466!
4467! Set switch to create history NetCDF file.
4468!
4469 IF ((nhis(ng).gt.0).and.any(hout(:,ng))) THEN
4470 ldefhis(ng)=.true.
4471 END IF
4472
4473#ifdef GRID_EXTRACT
4474!
4475! Set switch to create extract history NetCDF file.
4476!
4477 IF ((nxtr(ng).gt.0).and.any(hout(:,ng))) THEN
4478 ldefxtr(ng)=.true.
4479 END IF
4480#endif
4481!
4482! Set switch to create quicksave NetCDF file.
4483!
4484 IF ((nqck(ng).gt.0).and.any(qout(:,ng))) THEN
4485 ldefqck(ng)=.true.
4486 END IF
4487
4488# if defined AVERAGES && defined AVERAGES_DETIDE && \
4489 (defined ssh_tides || defined uv_tides)
4490!
4491! If restart, turn off definition of detide harmonics NetCDF file
4492! since we only need to update time-averaged accumulated harmonics.
4493!
4494 IF (nrrec(ng).ne.0) THEN
4495 ldeftide(ng)=.false.
4496 END IF
4497# endif
4498!
4499! Set switch to process climatology file.
4500!
4501#ifndef ANA_SSH
4502 IF (lsshclm(ng)) clm_file(ng)=.true.
4503#endif
4504#ifndef ANA_M2CLIMA
4505 IF (lm2clm(ng)) clm_file(ng)=.true.
4506#endif
4507#ifdef SOLVE3D
4508# ifndef ANA_M3CLIMA
4509 IF (lm3clm(ng)) clm_file(ng)=.true.
4510# endif
4511# ifndef ANA_TCLIMA
4512 IF (any(ltracerclm(:,ng))) clm_file(ng)=.true.
4513# endif
4514# if defined TS_MIX_CLIMA && (defined TS_DIF2 || defined TS_DIF4)
4515 clm_file(ng)=.true.
4516# endif
4517#endif
4518
4519#if defined I4DVAR || defined WEAK_CONSTRAINT
4520!
4521! If weak constraint, disallow recycling of the adjoint model.
4522!
4523 lcycleadj(ng)=.false.
4524#endif
4525
4526#if defined AVERAGES && defined AVERAGES_DETIDE && \
4527 (defined ssh_tides || defined uv_tides)
4528!
4529! If computing time-averaged detided fields, make sure the the regular
4530! time-averaged switches are activated for such variables.
4531!
4532 IF (.not.aout(idfsur,ng).and.aout(idfsud,ng)) THEN
4533 aout(idfsur,ng)=.true.
4534 END IF
4535 IF (.not.aout(idubar,ng).and.aout(idu2dd,ng)) THEN
4536 aout(idubar,ng)=.true.
4537 END IF
4538 IF (.not.aout(idvbar,ng).and.aout(idv2dd,ng)) THEN
4539 aout(idvbar,ng)=.true.
4540 END IF
4541# ifdef SOLVE3D
4542 IF (.not.aout(iduvel,ng).and.aout(idu3dd,ng)) THEN
4543 aout(iduvel,ng)=.true.
4544 END IF
4545 IF (.not.aout(idvvel,ng).and.aout(idv3dd,ng)) THEN
4546 aout(idvvel,ng)=.true.
4547 END IF
4548 DO itrc=1,nat
4549 IF (.not.aout(idtvar(itrc),ng).and. &
4550 & aout(idtrcd(itrc),ng)) THEN
4551 aout(idtvar(itrc),ng)=.true.
4552 END IF
4553 END DO
4554# endif
4555#endif
4556#if defined I4DVAR
4557!
4558! If strong constraint, write only final adjoint solution since only
4559! we are estimating initial conditions.
4560!
4561 nadj(ng)=ntimes(ng)
4562#endif
4563#if defined RBL4DVAR || defined R4DVAR
4564!
4565! If dual formulation and strong constraint, limit writing the adjoint
4566! solution to the end of time-stepping.
4567!
4568 IF (nadj(ng).gt.ntimes(ng)) THEN
4569 nadj(ng)=ntimes(ng)
4570 END IF
4571#endif
4572#if defined I4DVAR || defined RBL4DVAR || defined R4DVAR
4573!
4574! Ensure that restart file is written only at least at the end. In
4575! sequential data assimilation the restart file can be used as the
4576! first guess for the next assimilation cycle. Notice that we can
4577! also use the DAINAME file for such purpose. However, in lagged
4578! data assimilation windows, "nRST" can be set to a value less than
4579! "ntimes" (say, daily) and "LcycleRST" is set to false. So, there
4580! are several initialization record possibilities for the next
4581! assimilation cycle.
4582!
4583 IF (nrst(ng).gt.ntimes(ng)) THEN
4584 nrst(ng)=ntimes(ng)
4585 END IF
4586#endif
4587#if defined STOCHASTIC_OPT && !defined STOCH_OPT_WHITE
4588!
4589! For red noise stochastic optimals, nADJ must equal the number of
4590! trapezoidal intervals.
4591!
4592 nadj(ng)=ntimes(ng)/nintervals
4593#endif
4594#if defined FOUR_DVAR || defined IMPULSE
4595!
4596! Set size of additonal dimension for error covariance normalization
4597! and standard deviation factors.
4598!
4599# if defined CORRELATION || defined WEAK_CONSTRAINT
4600# ifdef SP4DVAR
4601 nsa=2
4602# else
4603 IF (nadj(ng).lt.ntimes(ng)) THEN
4604 nsa=2
4605 ELSE
4606 nsa=1
4607 END IF
4608# ifdef CORRELATION
4609 ntimes=1 ! no time-stepping required
4610# endif
4611# endif
4612# else
4613 nsa=1
4614# endif
4615#endif
4616#ifdef WEAK_CONSTRAINT
4617# ifndef ARRAY_MODES
4618!
4619! If weak constraint assimilation, set tangent linear number of
4620! time-steps between writing of fields the same as the basic
4621! state. Disallow recycling.
4622!
4623# ifdef SP4DVAR
4624 ntlm(ng)=ntimes(ng)/nsaddle
4625 nadj(ng)=ntlm(ng)
4626 nspt(ng)=ntlm(ng)
4627 nspa(ng)=ntlm(ng)
4628 nsct(ng)=ntlm(ng)
4629 nsca(ng)=ntlm(ng)
4630 lcycletlm(ng)=.false.
4631# else
4632 ntlm(ng)=nhis(ng)
4633 lcycletlm(ng)=.false.
4634# endif
4635# endif
4636#endif
4637#if defined TIME_CONV && defined WEAK_CONSTRAINT
4638!
4639! Set number of full state records needed for time convolutions.
4640!
4641 nrectc(ng)=(ntimes(ng)/nadj(ng))+1
4642#endif
4643#if defined FOUR_DVAR
4644!
4645! If variational data assimilation, disallow creation of multiple
4646! output adjoint history files and the tangent linear history file
4647! in I4D-Var. Multiple TLM history are allow in R4d-Var and
4648! irrelevant in RBL4D-Var since TLM history is turned off. The
4649! adjoint history files are special at the unlimited dimension
4650! is not associated with time records.
4651!
4652 ndefadj(ng)=0
4653# if defined I4DVAR || defined I4DVAR_ANA_SENSITIVITY
4654 ndeftlm(ng)=0
4655# endif
4656#endif
4657!
4658! If appropriate, deactive outpur NetCDF files switches.
4659!
4660 IF (((nrrec(ng).eq.0).and.(navg(ng).gt.ntimes(ng))).or. &
4661 & (navg(ng).eq.0)) THEN
4662 ldefavg(ng)=.false.
4663 END IF
4664 IF (((nrrec(ng).eq.0).and.(ndia(ng).gt.ntimes(ng))).or. &
4665 & (ndia(ng).eq.0)) THEN
4666 ldefdia(ng)=.false.
4667 END IF
4668 IF (((nrrec(ng).eq.0).and.(nflt(ng).gt.ntimes(ng))).or. &
4669 & (nflt(ng).eq.0)) THEN
4670 ldefflt(ng)=.false.
4671 END IF
4672 IF (((nrrec(ng).eq.0).and.(nhis(ng).gt.ntimes(ng))).or. &
4673 & (nhis(ng).eq.0)) THEN
4674 ldefhis(ng)=.false.
4675 END IF
4676 IF (((nrrec(ng).eq.0).and.(nqck(ng).gt.ntimes(ng))).or. &
4677 & (nqck(ng).eq.0)) THEN
4678 ldefqck(ng)=.false.
4679 END IF
4680 IF (((nrrec(ng).eq.0).and.(nrst(ng).gt.ntimes(ng))).or. &
4681 & (nrst(ng).eq.0)) THEN
4682 ldefrst(ng)=.false.
4683 END IF
4684 IF (((nrrec(ng).eq.0).and.(nsta(ng).gt.ntimes(ng))).or. &
4685 & (nsta(ng).eq.0)) THEN
4686 ldefsta(ng)=.false.
4687 END IF
4688!
4689! Determine switch to process boundary NetCDF file.
4690!
4691 obcdata(ng)=.false.
4692#ifndef ANA_FSOBC
4693 obcdata(ng)=obcdata(ng).or.any(lbc(:,isfsur,ng)%acquire)
4694# if defined ADJOINT || defined TANGENT || defined TL_IOMS
4695 obcdata(ng)=obcdata(ng).or.any(ad_lbc(:,isfsur,ng)%acquire)
4696# endif
4697#endif
4698#ifndef ANA_M2OBC
4699 obcdata(ng)=obcdata(ng).or.any(lbc(:,isubar,ng)%acquire) &
4700 & .or.any(lbc(:,isvbar,ng)%acquire)
4701# if defined ADJOINT || defined TANGENT || defined TL_IOMS
4702 obcdata(ng)=obcdata(ng).or.any(ad_lbc(:,isubar,ng)%acquire) &
4703 & .or.any(ad_lbc(:,isvbar,ng)%acquire)
4704# endif
4705#endif
4706#ifdef SOLVE3D
4707# ifndef ANA_M3OBC
4708 obcdata(ng)=obcdata(ng).or.any(lbc(:,isuvel,ng)%acquire) &
4709 & .or.any(lbc(:,isvvel,ng)%acquire)
4710# if defined ADJOINT || defined TANGENT || defined TL_IOMS
4711 obcdata(ng)=obcdata(ng).or.any(ad_lbc(:,isuvel,ng)%acquire) &
4712 & .or.any(ad_lbc(:,isvvel,ng)%acquire)
4713# endif
4714# endif
4715# ifndef ANA_TOBC
4716 obcdata(ng)=obcdata(ng).or.any(lbc(:,istvar(:),ng)%acquire)
4717# if defined ADJOINT || defined TANGENT || defined TL_IOMS
4718 obcdata(ng)=obcdata(ng).or.any(ad_lbc(:,istvar(:),ng)%acquire)
4719# endif
4720# endif
4721#endif
4722 END DO
4723!
4724! If multiple output files, edit derived type structure to store the
4725! information about all multi-files.
4726!
4727 DO ng=1,ngrids
4728 IF ((nhis(ng).gt.0).and.(ndefhis(ng).gt.0)) THEN
4729 outfiles=ntimes(ng)/ndefhis(ng)
4730 IF ((nhis(ng).eq.ndefhis(ng)).or. &
4731 & (mod(ntimes(ng),ndefhis(ng)).ge.nhis(ng))) THEN
4732 outfiles=outfiles+1
4733 END IF
4734 CALL edit_file_struct (ng, outfiles, his)
4735 END IF
4736#ifdef GRID_EXTRACT
4737 IF ((nxtr(ng).gt.0).and.(ndefxtr(ng).gt.0)) THEN
4738 outfiles=ntimes(ng)/ndefxtr(ng)
4739 IF ((nxtr(ng).eq.ndefxtr(ng)).or. &
4740 & (mod(ntimes(ng),ndefxtr(ng)).ge.nxtr(ng))) THEN
4741 outfiles=outfiles+1
4742 END IF
4743 CALL edit_file_struct (ng, outfiles, xtr)
4744 END IF
4745#endif
4746 IF ((nqck(ng).gt.0).and.(ndefqck(ng).gt.0)) THEN
4747 outfiles=ntimes(ng)/ndefqck(ng)
4748 IF ((nqck(ng).eq.ndefqck(ng)).or. &
4749 & (mod(ntimes(ng),ndefqck(ng)).ge.nqck(ng))) THEN
4750 outfiles=outfiles+1
4751 END IF
4752 CALL edit_file_struct (ng, outfiles, qck)
4753 END IF
4754#ifdef ADJOINT
4755 IF ((nadj(ng).gt.0).and.(ndefadj(ng).gt.0)) THEN
4756 outfiles=ntimes(ng)/ndefadj(ng)
4757 IF ((nadj(ng).eq.ndefadj(ng)).or. &
4758 & (mod(ntimes(ng),ndefadj(ng)).ge.nadj(ng))) THEN
4759 outfiles=outfiles+1
4760 END IF
4761 CALL edit_file_struct (ng, outfiles, adm)
4762 END IF
4763#endif
4764#ifdef AVERAGES
4765 IF ((navg(ng).gt.0).and.(ndefavg(ng).gt.0)) THEN
4766 outfiles=ntimes(ng)/ndefavg(ng)
4767 IF ((navg(ng).eq.ndefavg(ng)).or. &
4768 & (mod(ntimes(ng),ndefavg(ng)).ge.navg(ng))) THEN
4769 outfiles=outfiles+1
4770 END IF
4771 CALL edit_file_struct (ng, outfiles, avg)
4772 avg(ng)%load=0 ! because delayed creation of NetCDF file
4773 END IF ! due to time-averaging
4774#endif
4775#ifdef DIAGNOSTICS
4776 IF ((ndia(ng).gt.0).and.(ndefdia(ng).gt.0)) THEN
4777 outfiles=ntimes(ng)/ndefdia(ng)
4778 IF ((ndia(ng).eq.ndefdia(ng)).or. &
4779 & (mod(ntimes(ng),ndefdia(ng)).ge.ndia(ng))) THEN
4780 outfiles=outfiles+1
4781 END IF
4782 CALL edit_file_struct (ng, outfiles, dia)
4783 dia(ng)%load=0 ! because delayed creation of NetCDF file
4784 END IF ! due to time-averaging
4785#endif
4786#if defined TANGENT || defined TL_IOMS
4787 IF ((ntlm(ng).gt.0).and.(ndeftlm(ng).gt.0)) THEN
4788 outfiles=ntimes(ng)/ndeftlm(ng)
4789 IF ((ntlm(ng).eq.ndeftlm(ng)).or. &
4790 & (mod(ntimes(ng),ndeftlm(ng)).ge.ntlm(ng))) THEN
4791 outfiles=outfiles+1
4792 END IF
4793 CALL edit_file_struct (ng, outfiles, tlm)
4794 END IF
4795#endif
4796 END DO
4797
4798#ifdef FORWARD_FLUXES
4799!
4800! Allocate and initialize BLK I/O structure with the same values as
4801! QCK.
4802!
4803 DO ng=1,ngrids
4804 outfiles=qck(ng)%Nfiles
4805 allocate ( blk(ng)%Nrec(outfiles) )
4806 allocate ( blk(ng)%time_min(outfiles) )
4807 allocate ( blk(ng)%time_max(outfiles) )
4808 allocate ( blk(ng)%Vid(nv) )
4809 allocate ( blk(ng)%Tid(mt) )
4810 allocate ( blk(ng)%files(outfiles) )
4811 blk(ng)%Nfiles=outfiles
4812 blk(ng)%Fcount=1
4813 blk(ng)%Rindex=0
4814 blk(ng)%ncid=-1
4815 blk(ng)%Vid(1:nv)=-1
4816 blk(ng)%Tid(1:mt)=-1
4817 blk(ng)%Nrec=0
4818 blk(ng)%time_min=0.0_dp
4819 blk(ng)%time_max=0.0_dp
4820 blk(ng)%label='BLK - nonlinear model bulk fluxes'
4821 lstr=len(blk(ng)%name)
4822 DO i=1,lstr
4823 blk(ng)%head(i:i)=blank
4824 blk(ng)%base(i:i)=blank
4825 blk(ng)%name(i:i)=blank
4826 END DO
4827 DO k=1,outfiles
4828 DO i=1,lstr
4829 blk(ng)%files(k)(i:i)=blank
4830 END DO
4831 END DO
4832 END DO
4833#endif
4834!
4835!-----------------------------------------------------------------------
4836! Report input parameters.
4837!-----------------------------------------------------------------------
4838!
4839#if defined PIO_LIB && defined DISTRIBUTE
4840# ifdef ASYNCHRONOUS_SCORPIO
4841!
4842! If SCORPIO library and asynchronous I/O, split the distributed-
4843! memory communicator into disjointed computational and dedicated
4844! I/O processes. (HGA: It doesn't work. There are bugs in the
4845! SCORPIO library).
4846!
4847 CALL set_pio_async
4848 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
4849# endif
4850!
4851! Initialize PIO system for either synchronous or asynchronous I/O.
4852!
4853 CALL initialize_pio
4854 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
4855!
4856! Reset Lwrite switch since the Master may have changed when splitting
4857! the initial communicator.
4858!
4859 lwrite=master
4860!
4861! Report to standard output.
4862!
4863#endif
4864 IF (master.and.lwrite) THEN
4865 lstr=len_trim(my_fflags)
4866 WRITE (out,60) trim(title), trim(my_os), trim(my_cpu), &
4867 & trim(my_fort), trim(my_fc), my_fflags(1:lstr), &
4868#ifdef DISTRIBUTE
4869# if defined PIO_LIB && \
4870 (defined asynchronous_pio || defined asynchronous_scorpio)
4871 & peer_comm_world, peersize, &
4872 & ocn_comm_world, numthreads, &
4873 & io_comm_world, pio_numiotasks, trim(cioranks), &
4874# ifdef ASYNCHRONOUS_SCORPIO
4875 & inter_comm_world, &
4876# endif
4877# endif
4878# ifdef DISJOINTED
4879 & full_comm_world, fullsize, nsubgroups, &
4880 & fork_comm_world, forksize, &
4881 & 0, (fullsize/forksize)-1, &
4882# ifdef CONCURRENT_KERNEL
4883 & task_comm_world, tasksize, &
4884 & 0, (fullsize/tasksize)-1, &
4885# endif
4886# endif
4887# if !(defined PIO_LIB && \
4888 (defined asynchronous_pio || defined asynchronous_scorpio)) && \
4889 !defined DISJOINTED
4890 & ocn_comm_world, numthreads, &
4891# endif
4892 & trim(iname), &
4893#endif
4894#ifdef GIT_URL
4895 & trim(git_url), trim(git_rev), &
4896#endif
4897 & trim(svn_url), trim(svn_rev), &
4898 & trim(rdir), trim(hdir), trim(hfile), trim(adir)
4899!
4900 DO ng=1,ngrids
4901!
4902! Report grid size and domain decomposition. Check for correct tile
4903! decomposition.
4904!
4905#ifdef DISTRIBUTE
4906 WRITE (out,70) ng, lm(ng), mm(ng), n(ng), numthreads, &
4907 & ntilei(ng), ntilej(ng)
4908 maxpets=numthreads ! regular unsplit
4909 npets=ntilei(ng)*ntilej(ng) ! values
4910 label='NtileI * NtileJ ='
4911!
4912# ifdef SP4DVAR
4913# ifdef DISJOINTED
4914# ifdef CONCURRENT_KERNEL
4915 maxpets=fullsize
4916 npets=ntilei(ng)*ntilej(ng)*nsaddle*2
4917 label='NtileI * NtileJ * Nsaddle * 2 ='
4918# else
4919 maxpets=fullsize
4920 npets=ntilei(ng)*ntilej(ng)*nsaddle
4921 label='NtileI * NtileJ * Nsaddle ='
4922# endif
4923# else
4924 maxpets=numthreads
4925 npets=ntilei(ng)*ntilej(ng)
4926 label='NtileI * NtileJ ='
4927# endif
4928# endif
4929# if defined PIO_LIB && defined DISTRIBUTE && \
4930 (defined asynchronous_pio || defined asynchronous_scorpio)
4931 maxpets=peersize
4932 IF ((inp_lib.eq.io_pio).or.(out_lib.eq.io_pio)) THEN
4933 npets=(ntilei(ng)*ntilej(ng))+pio_numiotasks
4934 label='(NtileI * NtileJ) + pio_NumIOtasks ='
4935 ELSE
4936 npets=(ntilei(ng)*ntilej(ng))
4937 label='NtileI * NtileJ ='
4938 END IF
4939# endif
4940 IF (npets.ne.maxpets) THEN
4941 WRITE (out,80) ng, trim(label), npets, maxpets
4942 exit_flag=6
4943 RETURN
4944 END IF
4945#else
4946 WRITE (out,90) ng, lm(ng), mm(ng), n(ng), numthreads, &
4947 & ntilei(ng), ntilej(ng)
4948 IF (ntilei(ng)*ntilej(ng).le.0) THEN
4949 WRITE (out,100) ng
4950 exit_flag=6
4951 RETURN
4952 END IF
4953 IF (mod(ntilei(ng)*ntilej(ng),numthreads).ne.0) THEN
4954 WRITE (out,100) ng
4955 exit_flag=6
4956 RETURN
4957 END IF
4958#endif
4959!
4960! Report physical parameters.
4961!
4962 WRITE (out,110) ng
4963 WRITE (out,120) ntimes(ng), 'ntimes', &
4964 & 'Number of timesteps for 3-D equations.'
4965#if defined RBL4DVAR_FCT_SENSITIVITY
4966 WRITE (out,120) ntimes_ana(ng), 'ntimes_ana', &
4967 & 'Observation impacts analysis interval.'
4968 WRITE (out,120) ntimes_fct(ng), 'ntimes_fct', &
4969 & 'Observation impacts forecast interval.'
4970#endif
4971 WRITE (out,140) dt(ng), 'dt', &
4972 & 'Timestep size (s) for 3-D equations.'
4973 WRITE (out,130) ndtfast(ng), 'ndtfast', &
4974 & 'Number of timesteps for 2-D equations between', &
4975 & 'each 3D timestep.'
4976 WRITE (out,120) erstr, 'ERstr', &
4977 & 'Starting ensemble/perturbation run number.'
4978 WRITE (out,120) erend, 'ERend', &
4979 & 'Ending ensemble/perturbation run number.'
4980#ifdef FOUR_DVAR
4981 WRITE (out,120) nouter, 'Nouter', &
4982 & 'Maximun number of 4DVAR outer loop iterations.'
4983#endif
4984#if defined I4DVAR || defined I4DVAR_ANA_SENSITIVITY || \
4985 defined hessian_fsv || defined hessian_so || \
4986 defined hessian_sv || defined sensitivity_4dvar || \
4987 defined rbl4dvar || defined r4dvar || \
4988 defined sp4dvar || defined tl_rbl4dvar || \
4989 defined tl_r4dvar
4990 WRITE (out,120) ninner, 'Ninner', &
4991 & 'Maximum number of 4D-Var inner loop iterations.'
4992# ifdef SP4DVAR
4993 WRITE (out,120) nsaddle, 'Nsaddle', &
4994 & 'Number of intervals for saddle point algorithm.'
4995# endif
4996#endif
4997#ifdef STOCHASTIC_OPT
4998 WRITE (out,120) nintervals, 'Nintervals', &
4999 & 'Number of stochastic optimals timestep intervals.'
5000#endif
5001#ifdef PROPAGATOR
5002 WRITE (out,120) nev, 'NEV', &
5003 & 'Number of Lanczos/Arnoldi eigenvalues to compute.'
5004 WRITE (out,120) ncv, 'NCV', &
5005 & 'Number of Lanczos/Arnoldi eigenvectors to compute.'
5006#endif
5007 WRITE (out,120) nrrec(ng), 'nrrec', &
5008 & 'Number of restart records to read from disk.'
5009 WRITE (out,170) lcyclerst(ng), 'LcycleRST', &
5010 & 'Switch to recycle time-records in restart file.'
5011 WRITE (out,130) nrst(ng), 'nRST', &
5012 & 'Number of timesteps between the writing of data', &
5013 & 'into restart fields.'
5014 WRITE (out,130) ninfo(ng), 'ninfo', &
5015 & 'Number of timesteps between print of information', &
5016 & 'to standard output.'
5017#ifdef STATIONS
5018 WRITE (out,130) nsta(ng), 'nSTA', &
5019 & 'Number of timesteps between the writing of data', &
5020 & 'the stations file.'
5021#endif
5022#ifdef FLOATS
5023 WRITE (out,130) nflt(ng), 'nFLT', &
5024 & 'Number of timesteps between the writing of data', &
5025 & 'into floats file.'
5026#endif
5027 WRITE (out,170) ldefout(ng), 'ldefout', &
5028 & 'Switch to create a new output NetCDF file(s).'
5029 WRITE (out,130) nhis(ng), 'nHIS', &
5030 & 'Number of timesteps between the writing fields', &
5031 & 'into history file.'
5032 IF (ndefhis(ng).gt.0) THEN
5033 WRITE (out,130) ndefhis(ng), 'ndefHIS', &
5034 & 'Number of timesteps between the creation of new', &
5035 & 'history files.'
5036 END IF
5037#ifdef GRID_EXTRACT
5038 WRITE (out,130) nxtr(ng), 'nXTR', &
5039 & 'Number of timesteps between the writing fields', &
5040 & 'into the extract file.'
5041 IF (ndefxtr(ng).gt.0) THEN
5042 WRITE (out,130) ndefxtr(ng), 'ndefXTR', &
5043 & 'Number of timesteps between the creation of new', &
5044 & 'extract files.'
5045 END IF
5046#endif
5047 WRITE (out,130) nqck(ng), 'nQCK', &
5048 & 'Number of timesteps between the writing fields', &
5049 & 'into quicksave file.'
5050 IF (ndefqck(ng).gt.0) THEN
5051 WRITE (out,130) ndefqck(ng), 'ndefQCK', &
5052 & 'Number of timesteps between the creation of new', &
5053 & 'quicksave files.'
5054 END IF
5055#if defined AVERAGES || \
5056 (defined ad_averages && defined adjoint) || \
5057 (defined rp_averages && defined tl_ioms) || \
5058 (defined tl_averages && defined tangent)
5059 WRITE (out,130) ntsavg(ng), 'ntsAVG', &
5060 & 'Starting timestep for the accumulation of output', &
5061 & 'time-averaged data.'
5062 WRITE (out,130) navg(ng), 'nAVG', &
5063 & 'Number of timesteps between the writing of', &
5064 & 'time-averaged data into averages file.'
5065 IF (ndefavg(ng).gt.0) THEN
5066 WRITE (out,130) ndefavg(ng), 'ndefAVG', &
5067 & 'Number of timesteps between the creation of new', &
5068 & 'time-averaged files.'
5069 END IF
5070#endif
5071#ifdef DIAGNOSTICS
5072 WRITE (out,130) ntsdia(ng), 'ntsDIA', &
5073 & 'Starting timestep for the accumulation of output', &
5074 & 'time-averaged diagnostics data.'
5075 WRITE (out,130) ndia(ng), 'nDIA', &
5076 & 'Number of timesteps between the writing of', &
5077 & 'time-averaged data into diagnostics file.'
5078 IF (ndefdia(ng).gt.0) THEN
5079 WRITE (out,130) ndefdia(ng), 'ndefDIA', &
5080 & 'Number of timesteps between the creation of new', &
5081 & 'diagnostic files.'
5082 END IF
5083#endif
5084#ifdef TANGENT
5085 WRITE (out,170) lcycletlm(ng), 'LcycleTLM', &
5086 & 'Switch to recycle time-records in tangent file.'
5087 WRITE (out,130) ntlm(ng), 'nTLM', &
5088 & 'Number of timesteps between the writing of', &
5089 & 'data into tangent file.'
5090 IF (ndeftlm(ng).gt.0) THEN
5091 WRITE (out,130) ndeftlm(ng), 'ndefTLM', &
5092 & 'Number of timesteps between the creation of new', &
5093 & 'tangent files.'
5094 END IF
5095#endif
5096#ifdef ADJOINT
5097 WRITE (out,170) lcycleadj(ng), 'LcycleADJ', &
5098 & 'Switch to recycle time-records in adjoint file.'
5099 WRITE (out,130) nadj(ng), 'nADJ', &
5100 & 'Number of timesteps between the writing of', &
5101 & 'data into adjoint file.'
5102 IF (ndefadj(ng).gt.0) THEN
5103 WRITE (out,130) ndefadj(ng), 'ndefADJ', &
5104 & 'Number of timesteps between the creation of new', &
5105 & 'adjoint files.'
5106 END IF
5107#endif
5108#ifdef ADJUST_BOUNDARY
5109 WRITE (text,'(i8)') nbrec(ng)
5110 WRITE (out,130) nobc(ng), 'nOBC', &
5111 & 'Number of timesteps between 4D-Var adjustment of', &
5112 & 'open boundaries, Nbrec = '//trim(adjustl(text))
5113 IF (nbrec(ng).gt.500) THEN
5114 WRITE (out,'(t32,a)') 'WARNING: ''Nbrec'' is large, '// &
5115 & 'change ''ntimes'' or ''nOBC'' to lower memory demand.'
5116 END IF
5117#endif
5118#if defined ADJUST_STFLUX || defined ADJUST_WSTRESS
5119 WRITE (text,'(i8)') nfrec(ng)
5120 WRITE (out,130) nsff(ng), 'nSFF', &
5121 & 'Number of timesteps between 4D-Var adjustment of', &
5122 & 'surface forcing fields, Nfrec = '//trim(adjustl(text))
5123 IF (nfrec(ng).gt.500) THEN
5124 WRITE (out,'(t32,a)') 'WARNING: ''Nfrec'' is large, '// &
5125 & 'change ''ntimes'' or ''nSFF'' to lower memory demand.'
5126 END IF
5127#endif
5128#ifdef PROPAGATOR
5129 WRITE (out,170) lmultigst, 'LmultiGST', &
5130 & 'Switch to write one GST eigenvector per file.'
5131 WRITE (out,170) lrstgst, 'LrstGST', &
5132 & 'Switch to restart GST analysis.'
5133 WRITE (out,120) maxitergst, 'MaxIterGST', &
5134 & 'Maximum number of GST algorithm iterations.'
5135 WRITE (out,130) ngst, 'nGST', &
5136 & 'Number of GST iterations between storing check', &
5137 & 'pointing data into NetCDF file.'
5138 WRITE (out,210) ritz_tol, 'Ritz_tol', &
5139 & 'Relative accuracy of Ritz values computed in the', &
5140 & 'GST analysis.'
5141#endif
5142#ifdef SOLVE3D
5143# ifdef TS_DIF2
5144 DO i=1,nat+npt
5145 itrc=i
5146# ifdef T_PASSIVE
5147 IF (i.gt.nat) itrc=inert(i-nat)
5148# endif
5149 WRITE (out,190) nl_tnu2(itrc,ng), 'nl_tnu2', itrc, &
5150 & 'NLM Horizontal, harmonic mixing coefficient', &
5151 & '(m2/s) for tracer ', itrc, &
5152 & trim(vname(1,idtvar(itrc)))
5153# ifdef ADJOINT
5154 WRITE (out,190) ad_tnu2(itrc,ng), 'ad_tnu2', itrc, &
5155 & 'ADM Horizontal, harmonic mixing coefficient', &
5156 & '(m2/s) for tracer ', itrc, &
5157 & trim(vname(1,idtvar(itrc)))
5158# endif
5159# if defined TANGENT || defined TL_IOMS
5160 WRITE (out,190) tl_tnu2(itrc,ng), 'tl_tnu2', itrc, &
5161 & 'TLM Horizontal, harmonic mixing coefficient', &
5162 & '(m2/s) for tracer ', itrc, &
5163 & trim(vname(1,idtvar(itrc)))
5164# endif
5165 END DO
5166# endif
5167# ifdef TS_DIF4
5168 DO i=1,nat+npt
5169 itrc=i
5170# ifdef T_PASSIVE
5171 IF (i.gt.nat) itrc=inert(i-nat)
5172# endif
5173 WRITE (out,190) nl_tnu4(itrc,ng), 'nl_tnu4', itrc, &
5174 & 'NLM Horizontal, biharmonic mixing coefficient', &
5175 & '(m4/s) for tracer ', itrc, &
5176 & trim(vname(1,idtvar(itrc)))
5177# ifdef ADJOINT
5178 WRITE (out,190) ad_tnu4(itrc,ng), 'ad_tnu4', itrc, &
5179 & 'ADM Horizontal, biharmonic mixing coefficient', &
5180 & '(m4/s) for tracer ', itrc, &
5181 & trim(vname(1,idtvar(itrc)))
5182# endif
5183# if defined TANGENT || defined TL_IOMS
5184 WRITE (out,190) tl_tnu4(itrc,ng), 'tl_tnu4', itrc, &
5185 & 'TLM Horizontal, biharmonic mixing coefficient', &
5186 & '(m4/s) for tracer ', itrc, &
5187 & trim(vname(1,idtvar(itrc)))
5188# endif
5189 END DO
5190# endif
5191#endif
5192#ifdef UV_VIS2
5193 WRITE (out,210) nl_visc2(ng), 'nl_visc2', &
5194 & 'NLM Horizontal, harmonic mixing coefficient', &
5195 & '(m2/s) for momentum.'
5196# ifdef ADJOINT
5197 WRITE (out,210) ad_visc2(ng), 'ad_visc2', &
5198 & 'ADM Horizontal, harmonic mixing coefficient', &
5199 & '(m2/s) for momentum.'
5200# endif
5201# if defined TANGENT || defined TL_IOMS
5202 WRITE (out,210) tl_visc2(ng), 'tl_visc2', &
5203 & 'TLM Horizontal, harmonic mixing coefficient', &
5204 & '(m2/s) for momentum.'
5205# endif
5206#endif
5207#ifdef UV_VIS4
5208 WRITE (out,210) nl_visc4(ng), 'nl_visc4', &
5209 & 'NLM Horizontal, biharmonic mixing coefficient', &
5210 & '(m4/s) for momentum.'
5211# ifdef ADJOINT
5212 WRITE (out,210) ad_visc4(ng), 'ad_visc4', &
5213 & 'ADM Horizontal, biharmonic mixing coefficient', &
5214 & '(m4/s) for momentum.'
5215# endif
5216# if defined TANGENT || defined TL_IOMS
5217 WRITE (out,210) tl_visc4(ng), 'tl_visc4', &
5218 & 'TLM Horizontal, biharmonic mixing coefficient', &
5219 & '(m4/s) for momentum.'
5220# endif
5221#endif
5222 IF (luvsponge(ng)) THEN
5223 WRITE (out,170) luvsponge(ng), 'LuvSponge', &
5224 & 'Turning ON sponge on horizontal momentum.'
5225 ELSE
5226 WRITE (out,170) luvsponge(ng), 'LuvSponge', &
5227 & 'Turning OFF sponge on horizontal momentum.'
5228 END IF
5229#ifdef SOLVE3D
5230 DO i=1,nat
5231 IF (ltracersponge(i,ng)) THEN
5232 WRITE (out,185) ltracersponge(i,ng), 'LtracerSponge', i, &
5233 & 'Turning ON sponge on tracer ', i, &
5234 & trim(vname(1,idtvar(i)))
5235 ELSE
5236 WRITE (out,185) ltracersponge(i,ng), 'LtracerSponge', i, &
5237 & 'Turning OFF sponge on tracer ', i, &
5238 & trim(vname(1,idtvar(i)))
5239 END IF
5240 END DO
5241# ifdef T_PASSIVE
5242 DO itrc=1,npt
5243 i=inert(itrc)
5244 IF (ltracersponge(i,ng)) THEN
5245 WRITE (out,185) ltracersponge(i,ng), 'LtracerSponge', i, &
5246 & 'Turning ON sponge on tracer ', i, &
5247 & trim(vname(1,idtvar(i)))
5248 ELSE
5249 WRITE (out,185) ltracersponge(i,ng), 'LtracerSponge', i, &
5250 & 'Turning OFF sponge on tracer ', i, &
5251 & trim(vname(1,idtvar(i)))
5252 END IF
5253 END DO
5254# endif
5255 DO i=1,nat+npt
5256 itrc=i
5257# ifdef T_PASSIVE
5258 IF (i.gt.nat) itrc=inert(i-nat)
5259# endif
5260 WRITE (out,190) akt_bak(itrc,ng), 'Akt_bak', itrc, &
5261 & 'Background vertical mixing coefficient (m2/s)', &
5262 & 'for tracer ', itrc, trim(vname(1,idtvar(itrc)))
5263 END DO
5264# if defined LIMIT_VDIFF && \
5265 (defined gls_mixing || defined lmd_mixing || defined my25_mixing)
5266 DO itrc=1,nat
5267 WRITE (out,190) akt_limit(itrc,ng), 'Akt_limit', itrc, &
5268 & 'Vertical diffusion upper threshold (m2/s)', &
5269 & 'for tracer ', itrc, trim(vname(1,idtvar(itrc)))
5270 END DO
5271# endif
5272 WRITE (out,210) akv_bak(ng), 'Akv_bak', &
5273 & 'Background vertical mixing coefficient (m2/s)', &
5274 & 'for momentum.'
5275# if defined LIMIT_VVISC && \
5276 (defined gls_mixing || defined lmd_mixing || defined my25_mixing)
5277 WRITE (out,210) akv_limit(ng), 'Akv_limit', &
5278 & 'Vertical viscosity upper threshold (m2/s)', &
5279 & 'for momentum.'
5280# endif
5281# if defined MY25_MIXING || defined GLS_MIXING
5282 WRITE (out,210) akk_bak(ng), 'Akk_bak', &
5283 & 'Background vertical mixing coefficient (m2/s)', &
5284 & 'for turbulent energy.'
5285 WRITE (out,210) akp_bak(ng), 'Akp_bak', &
5286 & 'Background vertical mixing coefficient (m2/s)', &
5287 & 'for turbulent generic statistical field.'
5288# ifdef TKE_DIF2
5289 WRITE (out,210) tkenu2(ng), 'tkenu2', &
5290 & 'Horizontal, harmonic mixing coefficient (m2/s)', &
5291 & 'for turbulent energy.'
5292# endif
5293# ifdef TKE_DIF4
5294 WRITE (out,210) tkenu4(ng), 'tkenu4', &
5295 & 'Horizontal, biharmonic mixing coefficient (m4/s)', &
5296 & 'for turbulent energy.'
5297# endif
5298# endif
5299# ifdef GLS_MIXING
5300 WRITE (out,140) gls_p(ng), 'gls_p', &
5301 & 'GLS stability exponent.'
5302 WRITE (out,140) gls_m(ng), 'gls_m', &
5303 & 'GLS turbulent kinetic energy exponent.'
5304 WRITE (out,140) gls_n(ng), 'gls_n', &
5305 & 'GLS turbulent length scale exponent.'
5306 WRITE (out,200) gls_kmin(ng), 'gls_Kmin', &
5307 & 'GLS minimum value of turbulent kinetic energy.'
5308 WRITE (out,200) gls_pmin(ng), 'gls_Pmin', &
5309 & 'GLS minimum value of dissipation.'
5310 WRITE (out,200) gls_cmu0(ng), 'gls_cmu0', &
5311 & 'GLS stability coefficient.'
5312 WRITE (out,200) gls_c1(ng), 'gls_c1', &
5313 & 'GLS shear production coefficient.'
5314 WRITE (out,200) gls_c2(ng), 'gls_c2', &
5315 & 'GLS dissipation coefficient.'
5316 WRITE (out,200) gls_c3m(ng), 'gls_c3m', &
5317 & 'GLS stable buoyancy production coefficient.'
5318 WRITE (out,200) gls_c3p(ng), 'gls_c3p', &
5319 & 'GLS unstable buoyancy production coefficient.'
5320 WRITE (out,200) gls_sigk(ng), 'gls_sigk', &
5321 & 'GLS constant Schmidt number for TKE.'
5322 WRITE (out,200) gls_sigp(ng), 'gls_sigp', &
5323 & 'GLS constant Schmidt number for PSI.'
5324 WRITE (out,140) charnok_alpha(ng), 'charnok_alpha', &
5325 & 'Charnock factor for Zos calculation.'
5326 WRITE (out,140) zos_hsig_alpha(ng), 'zos_hsig_alpha', &
5327 & 'Factor for Zos calculation using Hsig(Awave).'
5328 WRITE (out,140) sz_alpha(ng), 'sz_alpha', &
5329 & 'Factor for Wave dissipation surface tke flux .'
5330 WRITE (out,140) crgban_cw(ng), 'crgban_cw', &
5331 & 'Factor for Craig/Banner surface tke flux.'
5332 WRITE (out,140) wec_alpha(ng), 'wec_alpha', &
5333 & 'WEC factor for roller/breaking energy distribution.'
5334# endif
5335# ifdef FORWARD_MIXING
5336 DO i=1,nat+npt
5337 itrc=i
5338# ifdef T_PASSIVE
5339 IF (i.gt.nat) itrc=inert(i-nat)
5340# endif
5341# ifdef ADJOINT
5342 WRITE (out,190) ad_akt_fac(itrc,ng), 'ad_Akt_fac', itrc, &
5343 & 'ADM basic state vertical mixing scale factor', &
5344 & 'for tracer ', itrc, trim(vname(1,idtvar(itrc)))
5345# endif
5346# if defined TANGENT || defined TL_IOMS
5347 WRITE (out,190) tl_akt_fac(itrc,ng), 'tl_Akt_fac', itrc, &
5348 & 'TLM basic state vertical mixing scale factor', &
5349 & 'for tracer ', itrc, trim(vname(1,idtvar(itrc)))
5350# endif
5351 END DO
5352# ifdef ADJOINT
5353 WRITE (out,210) ad_akv_fac(ng), 'ad_Akv_fac', &
5354 & 'ADM basic state vertical mixing scale factor', &
5355 & 'for momentum.'
5356# endif
5357# if defined TANGENT || defined TL_IOMS
5358 WRITE (out,210) tl_akv_fac(ng), 'tl_Akv_fac', &
5359 & 'TLM basic state vertical mixing scale factor', &
5360 & 'for momentum.'
5361# endif
5362# endif
5363#endif
5364 WRITE (out,200) rdrg(ng), 'rdrg', &
5365 & 'Linear bottom drag coefficient (m/s).'
5366 WRITE (out,200) rdrg2(ng), 'rdrg2', &
5367 & 'Quadratic bottom drag coefficient.'
5368 WRITE (out,200) zob(ng), 'Zob', &
5369 & 'Bottom roughness (m).'
5370#ifdef BBL_MODEL
5371 IF (zob(ng).le.0.0_r8) THEN
5372 WRITE (out,265) 'Zob = ', zob(ng), &
5373 & 'It must be greater than zero when BBL is activated.'
5374 exit_flag=5
5375 RETURN
5376 END IF
5377#endif
5378#ifdef SOLVE3D
5379# ifdef GLS_MIXING
5380 WRITE (out,200) zos(ng), 'Zos', &
5381 & 'Surface roughness (m).'
5382# endif
5383# ifdef BULK_FLUXES
5384 WRITE (out,200) blk_zq(ng), 'blk_ZQ', &
5385 & 'Height (m) of surface air humidity measurement.'
5386 IF (blk_zq(ng).le.0.0_r8) THEN
5387 WRITE (out,265) 'blk_ZQ = ', blk_zq(ng), &
5388 & 'It must be greater than zero.'
5389 exit_flag=5
5390 RETURN
5391 END IF
5392 WRITE (out,200) blk_zt(ng), 'blk_ZT', &
5393 & 'Height (m) of surface air temperature measurement.'
5394 IF (blk_zt(ng).le.0.0_r8) THEN
5395 WRITE (out,265) 'blk_ZT = ', blk_zt(ng), &
5396 & 'It must be greater than zero.'
5397 exit_flag=5
5398 RETURN
5399 END IF
5400 WRITE (out,200) blk_zw(ng), 'blk_ZW', &
5401 & 'Height (m) of surface winds measurement.'
5402 IF (blk_zw(ng).le.0.0_r8) THEN
5403 WRITE (out,265) 'blk_ZW = ', blk_zw(ng), &
5404 & 'It must be greater than zero.'
5405 exit_flag=5
5406 RETURN
5407 END IF
5408# endif
5409#endif
5410#if defined WET_DRY
5411 WRITE (out,200) dcrit(ng), 'Dcrit', &
5412 & 'Minimum depth for wetting and drying (m).'
5413#endif
5414#ifdef SOLVE3D
5415# if defined LMD_SKPP || defined SOLAR_SOURCE
5416 WRITE (out,120) lmd_jwt(ng), 'lmd_Jwt', &
5417 & 'Jerlov water type.'
5418 IF ((lmd_jwt(ng).lt.1).or.(lmd_jwt(ng).gt.9)) THEN
5419 WRITE (out,260) 'lmd_Jwt = ', lmd_jwt(ng), &
5420 & 'It must between one and nine.'
5421 exit_flag=5
5422 RETURN
5423 END IF
5424# endif
5425# ifdef BODYFORCE
5426 WRITE (out,130) levsfrc(ng), 'levsfrc', &
5427 & 'Deepest level to apply surface stress as a', &
5428 & 'bodyforce.'
5429 IF ((levsfrc(ng).lt.1).or.(levsfrc(ng).gt.n(ng))) THEN
5430 WRITE (out,260) 'levsfrc = ', levsfrc(ng), &
5431 & 'Out of range surface bodyforce level.'
5432 exit_flag=5
5433 RETURN
5434 END IF
5435 WRITE (out,130) levbfrc(ng), 'levbfrc', &
5436 & 'Shallowest level to apply bottom stress as a', &
5437 & 'bodyforce.'
5438 IF ((levbfrc(ng).lt.1).or.(levbfrc(ng).gt.n(ng))) THEN
5439 WRITE (out,260) 'levbfrc = ', levbfrc(ng), &
5440 & 'Out of range bottom bodyforce level.'
5441 exit_flag=5
5442 RETURN
5443 END IF
5444# endif
5445#endif
5446#ifdef SOLVE3D
5447 WRITE (out,120) vtransform(ng), 'Vtransform', &
5448 & 'S-coordinate transformation equation.'
5449 WRITE (out,120) vstretching(ng), 'Vstretching', &
5450 & 'S-coordinate stretching function.'
5451 WRITE (out,200) theta_s(ng), 'theta_s', &
5452 & 'S-coordinate surface control parameter.'
5453 WRITE (out,200) theta_b(ng), 'theta_b', &
5454 & 'S-coordinate bottom control parameter.'
5455 IF (tcline(ng).gt.1.0e+5_r8) THEN
5456 WRITE (out,210) tcline(ng), 'Tcline', &
5457 & 'S-coordinate surface/bottom layer width (m) used', &
5458 & 'in vertical coordinate stretching.'
5459 ELSE
5460 WRITE (out,160) tcline(ng), 'Tcline', &
5461 & 'S-coordinate surface/bottom layer width (m) used', &
5462 & 'in vertical coordinate stretching.'
5463 END IF
5464#endif
5465 WRITE (out,140) rho0, 'rho0', &
5466 & 'Mean density (kg/m3) for Boussinesq approximation.'
5467#if defined SOLVE3D && (defined FOUR_DVAR || defined PROPAGATOR)
5468 WRITE (out,200) bvf_bak, 'bvf_bak', &
5469 & 'Background Brunt-Vaisala frequency squared (1/s2).'
5470#endif
5471#ifdef TIDE_GENERATING_FORCES
5472 WRITE (out,170) lnodal, 'Lnodal', &
5473 & 'Switch to apply a 18.5-year lunar nodal correction.'
5474#endif
5475 WRITE (out,140) dstart, 'dstart', &
5476 & 'Time-stamp assigned to model initialization (days).'
5477#if defined SSH_TIDES || defined UV_TIDES
5478 WRITE (out,140) tide_start, 'tide_start', &
5479 & 'Reference time origin for tidal forcing (days).'
5480#endif
5481 WRITE (out,150) time_ref, 'time_ref', &
5482 & 'Reference time for units attribute (yyyymmdd.dd)'
5483#ifdef SOLVE3D
5484 DO i=1,nat+npt
5485 itrc=i
5486# ifdef T_PASSIVE
5487 IF (i.gt.nat) itrc=inert(i-nat)
5488# endif
5489 WRITE (out,190) tnudg(itrc,ng), 'Tnudg', itrc, &
5490 & 'Nudging/relaxation time scale (days)', &
5491 & 'for tracer ', itrc, trim(vname(1,idtvar(itrc)))
5492 END DO
5493# if defined SCORRECTION && defined SALINITY
5494 IF (tnudg(isalt,ng).le.0.0_r8) THEN
5495 WRITE (out,265) 'Tnudg(isalt) = ', tnudg(isalt,ng), &
5496 & 'Must be greater than zero for salt flux correction.'
5497 exit_flag=5
5498 RETURN
5499 END IF
5500# endif
5501#endif
5502 WRITE (out,210) znudg(ng), 'Znudg', &
5503 & 'Nudging/relaxation time scale (days)', &
5504 & 'for free-surface.'
5505 WRITE (out,210) m2nudg(ng), 'M2nudg', &
5506 & 'Nudging/relaxation time scale (days)', &
5507 & 'for 2D momentum.'
5508#ifdef SOLVE3D
5509 WRITE (out,210) m3nudg(ng), 'M3nudg', &
5510 & 'Nudging/relaxation time scale (days)', &
5511 & 'for 3D momentum.'
5512#endif
5513 WRITE (out,210) obcfac(ng), 'obcfac', &
5514 & 'Factor between passive and active', &
5515 & 'open boundary conditions.'
5516 WRITE (out,170) volcons(1,ng), 'VolCons(1)', &
5517 & 'NLM western edge boundary volume conservation.'
5518 WRITE (out,170) volcons(2,ng), 'VolCons(2)', &
5519 & 'NLM southern edge boundary volume conservation.'
5520 WRITE (out,170) volcons(3,ng), 'VolCons(3)', &
5521 & 'NLM eastern edge boundary volume conservation.'
5522 WRITE (out,170) volcons(4,ng), 'VolCons(4)', &
5523 & 'NLM northern edge boundary volume conservation.'
5524#ifdef ADJOINT
5525 WRITE (out,170) ad_volcons(1,ng), 'ad_VolCons(1)', &
5526 & 'ADM western edge boundary volume conservation.'
5527 WRITE (out,170) ad_volcons(2,ng), 'ad_VolCons(2)', &
5528 & 'ADM southern edge boundary volume conservation.'
5529 WRITE (out,170) ad_volcons(3,ng), 'ad_VolCons(3)', &
5530 & 'ADM eastern edge boundary volume conservation.'
5531 WRITE (out,170) ad_volcons(4,ng), 'ad_VolCons(4)', &
5532 & 'ADM northern edge boundary volume conservation.'
5533#endif
5534#if defined TANGENT || defined TL_IOMS
5535 WRITE (out,170) tl_volcons(1,ng), 'tl_VolCons(1)', &
5536 & 'TLM western edge boundary volume conservation.'
5537 WRITE (out,170) tl_volcons(2,ng), 'tl_VolCons(2)', &
5538 & 'TLM southern edge boundary volume conservation.'
5539 WRITE (out,170) tl_volcons(3,ng), 'tl_VolCons(3)', &
5540 & 'TLM eastern edge boundary volume conservation.'
5541 WRITE (out,170) tl_volcons(4,ng), 'tl_VolCons(4)', &
5542 & 'TLM northern edge boundary volume conservation.'
5543#endif
5544#ifdef SOLVE3D
5545 WRITE (out,140) t0(ng), 'T0', &
5546 & 'Background potential temperature (C) constant.'
5547 WRITE (out,140) s0(ng), 'S0', &
5548 & 'Background salinity (PSU) constant.'
5549# ifndef NONLIN_EOS
5550 WRITE (out,160) r0(ng), 'R0', &
5551 & 'Background density (kg/m3) used in linear Equation', &
5552 & 'of State.'
5553# endif
5554# if !defined NONLIN_EOS || defined FOUR_DVAR || defined PROPAGATOR
5555 WRITE (out,200) tcoef(ng), 'Tcoef', &
5556 & 'Thermal expansion coefficient (1/Celsius).'
5557 WRITE (out,200) scoef(ng), 'Scoef', &
5558 & 'Saline contraction coefficient (1/PSU).'
5559# endif
5560#endif
5561 WRITE (out,160) gamma2(ng), 'gamma2', &
5562 & 'Slipperiness variable: free-slip (1.0) or ', &
5563 & ' no-slip (-1.0).'
5564 IF (luvsrc(ng)) THEN
5565 WRITE (out,170) luvsrc(ng), 'LuvSrc', &
5566 & 'Turning ON momentum point Sources/Sinks.'
5567 ELSE
5568 WRITE (out,170) luvsrc(ng), 'LuvSrc', &
5569 & 'Turning OFF momentum point Sources/Sinks.'
5570 END IF
5571 IF (lwsrc(ng)) THEN
5572 WRITE (out,170) lwsrc(ng), 'LwSrc', &
5573 & 'Turning ON volume influx point Sources/Sinks.'
5574 ELSE
5575 WRITE (out,170) lwsrc(ng), 'LwSrc', &
5576 & 'Turning OFF volume influx point Sources/Sinks.'
5577 END IF
5578#ifdef SOLVE3D
5579 DO itrc=1,nat
5580 IF (ltracersrc(itrc,ng)) THEN
5581 WRITE (out,185) ltracersrc(itrc,ng), 'LtracerSrc', itrc, &
5582 & 'Turning ON point Sources/Sinks on tracer ', itrc, &
5583 & trim(vname(1,idtvar(itrc)))
5584 ELSE
5585 WRITE (out,185) ltracersrc(itrc,ng), 'LtracerSrc', itrc, &
5586 & 'Turning OFF point Sources/Sinks on tracer ', itrc, &
5587 & trim(vname(1,idtvar(itrc)))
5588 END IF
5589 END DO
5590# ifdef T_PASSIVE
5591 DO i=1,npt
5592 itrc=inert(i)
5593 IF (ltracersrc(itrc,ng)) THEN
5594 WRITE (out,185) ltracersrc(itrc,ng), 'LtracerSrc', itrc, &
5595 & 'Turning ON point Sources/Sinks on tracer ', itrc, &
5596 & trim(vname(1,idtvar(itrc)))
5597 ELSE
5598 WRITE (out,185) ltracersrc(itrc,ng), 'LtracerSrc', itrc, &
5599 & 'Turning OFF point Sources/Sinks on tracer ', itrc, &
5600 & trim(vname(1,idtvar(itrc)))
5601 END IF
5602 END DO
5603# endif
5604#endif
5605 IF (lsshclm(ng)) THEN
5606 WRITE (out,170) lsshclm(ng), 'LsshCLM', &
5607 & 'Turning ON processing of SSH climatology.'
5608 ELSE
5609 WRITE (out,170) lsshclm(ng), 'LsshCLM', &
5610 & 'Turning OFF processing of SSH climatology.'
5611 END IF
5612 IF (lm2clm(ng)) THEN
5613 WRITE (out,170) lm2clm(ng), 'Lm2CLM', &
5614 & 'Turning ON processing of 2D momentum climatology.'
5615 ELSE
5616 WRITE (out,170) lm2clm(ng), 'Lm2CLM', &
5617 & 'Turning OFF processing of 2D momentum climatology.'
5618 END IF
5619#ifdef SOLVE3D
5620 IF (lm3clm(ng)) THEN
5621 WRITE (out,170) lm3clm(ng), 'Lm3CLM', &
5622 & 'Turning ON processing of 3D momentum climatology.'
5623 ELSE
5624 WRITE (out,170) lm3clm(ng), 'Lm3CLM', &
5625 & 'Turning OFF processing of 3D momentum climatology.'
5626 END IF
5627 DO i=1,nat
5628 IF (ltracerclm(i,ng)) THEN
5629 WRITE (out,185) ltracerclm(i,ng), 'LtracerCLM', i, &
5630 & 'Turning ON processing of climatology tracer ', i, &
5631 & trim(vname(1,idtvar(i)))
5632 ELSE
5633 WRITE (out,185) ltracerclm(i,ng), 'LtracerCLM', i, &
5634 & 'Turning OFF processing of climatology tracer ', i, &
5635 & trim(vname(1,idtvar(i)))
5636 END IF
5637 END DO
5638# ifdef T_PASSIVE
5639 DO itrc=1,npt
5640 i=inert(itrc)
5641 IF (ltracerclm(i,ng)) THEN
5642 WRITE (out,185) ltracerclm(i,ng), 'LtracerCLM', i, &
5643 & 'Turning ON processing of climatology tracer ', i, &
5644 & trim(vname(1,idtvar(i)))
5645 ELSE
5646 WRITE (out,185) ltracerclm(i,ng), 'LtracerCLM', i, &
5647 & 'Turning OFF processing of climatology tracer ', i, &
5648 & trim(vname(1,idtvar(i)))
5649 END IF
5650 END DO
5651# endif
5652#endif
5653 IF (lnudgem2clm(ng)) THEN
5654 WRITE (out,170) lnudgem2clm(ng), 'LnudgeM2CLM', &
5655 & 'Turning ON nudging of 2D momentum climatology.'
5656 ELSE
5657 WRITE (out,170) lnudgem2clm(ng), 'LnudgeM2CLM', &
5658 & 'Turning OFF nudging of 2D momentum climatology.'
5659 END IF
5660#ifdef SOLVE3D
5661 IF (lnudgem3clm(ng)) THEN
5662 WRITE (out,170) lnudgem3clm(ng), 'LnudgeM3CLM', &
5663 & 'Turning ON nudging of 3D momentum climatology.'
5664 ELSE
5665 WRITE (out,170) lnudgem3clm(ng), 'LnudgeM3CLM', &
5666 & 'Turning OFF nudging of 3D momentum climatology.'
5667 END IF
5668 DO i=1,nat
5669 IF (lnudgetclm(i,ng)) THEN
5670 WRITE (out,185) lnudgetclm(i,ng), 'LnudgeTCLM', i, &
5671 & 'Turning ON nudging of climatology tracer ', i, &
5672 & trim(vname(1,idtvar(i)))
5673 ELSE
5674 WRITE (out,185) lnudgetclm(i,ng), 'LnudgeTCLM', i, &
5675 & 'Turning OFF nudging of climatology tracer ', i, &
5676 & trim(vname(1,idtvar(i)))
5677 END IF
5678 END DO
5679# ifdef T_PASSIVE
5680 DO itrc=1,npt
5681 i=inert(itrc)
5682 IF (lnudgetclm(i,ng)) THEN
5683 WRITE (out,185) lnudgetclm(i,ng), 'LnudgeTCLM', i, &
5684 & 'Turning ON nudging of climatology tracer ', i, &
5685 & trim(vname(1,idtvar(i)))
5686 ELSE
5687 WRITE (out,185) lnudgetclm(i,ng), 'LnudgeTCLM', i, &
5688 & 'Turning OFF nudging of climatology tracer ', i, &
5689 & trim(vname(1,idtvar(i)))
5690 END IF
5691 END DO
5692# endif
5693#endif
5694#if defined AD_SENSITIVITY || defined I4DVAR_ANA_SENSITIVITY || \
5695 defined opt_observations || defined sensitivity_4dvar || \
5696 defined so_semi
5697 WRITE (out,140) dstrs(ng), 'DstrS', &
5698 & 'Starting day for ADM sensitivity forcing.'
5699 WRITE (out,140) dends(ng), 'DendS', &
5700 & 'Ending day for ADM sensitivity forcing.'
5701# ifndef OBS_SPACE
5702# ifdef SOLVE3D
5703 WRITE (out,120) kstrs(ng), 'KstrS', &
5704 & 'Deepest level whose ADM sensitivity is required.'
5705 IF ((kstrs(ng).lt.1).or.(kstrs(ng).gt.n(ng))) THEN
5706 WRITE (out,260) 'KstrS = ', kstrs(ng), &
5707 & 'Out of range ADM sensitivity starting level.'
5708 exit_flag=5
5709 RETURN
5710 END IF
5711 WRITE (out,120) kends(ng), 'KendS', &
5712 & 'Shallowest level whose ADM sensitivity is required.'
5713 IF ((kends(ng).lt.1).or.(kends(ng).gt.n(ng))) THEN
5714 WRITE (out,260) 'KendS = ', kends(ng), &
5715 & 'Out of range ADM sensitivity level.'
5716 exit_flag=5
5717 RETURN
5718 END IF
5719# endif
5720 IF (scalars(ng)%Lstate(isfsur)) &
5721 & WRITE (out,170) scalars(ng)%Lstate(isfsur), &
5722 & 'Lstate(isFsur)', &
5723 & 'Adjoint sensitivity on free-surface.'
5724 IF (scalars(ng)%Lstate(isubar)) &
5725 & WRITE (out,170) scalars(ng)%Lstate(isubar), &
5726 & 'Lstate(isUbar)', &
5727 & 'Adjoint sensitivity on 2D U-momentum component.'
5728 IF (scalars(ng)%Lstate(isvbar)) &
5729 & WRITE (out,170) scalars(ng)%Lstate(isvbar), &
5730 & 'Lstate(isVbar)', &
5731 & 'Adjoint sensitivity on 2D V-momentum component.'
5732# ifdef SOLVE3D
5733 IF (scalars(ng)%Lstate(isuvel)) &
5734 & WRITE (out,170) scalars(ng)%Lstate(isuvel), &
5735 & 'Lstate(isUvel)', &
5736 & 'Adjoint sensitivity on 3D U-momentum component.'
5737 IF (scalars(ng)%Lstate(isvvel)) &
5738 & WRITE (out,170) scalars(ng)%Lstate(isvvel), &
5739 & 'Lstate(isVvel)', &
5740 & 'Adjoint sensitivity on 3D V-momentum component.'
5741 IF (scalars(ng)%Lstate(iswvel)) &
5742 & WRITE (out,170) scalars(ng)%Lstate(iswvel), &
5743 & 'Lstate(isWvel)', &
5744 & 'Adjoint sensitivity on 3D W-momentum component.'
5745 DO itrc=1,nt(ng)
5746 IF (scalars(ng)%Lstate(istvar(itrc))) &
5747 & WRITE (out,180) scalars(ng)%Lstate(istvar(itrc)), &
5748 & 'Lstate(idTvar)', &
5749 & 'Adjoint sensitivity on tracer ', &
5750 & itrc, trim(vname(1,idtvar(itrc)))
5751 END DO
5752# endif
5753# endif
5754#endif
5755#if defined FORCING_SV || defined SO_SEMI || defined STOCHASTIC_OPT
5756 IF (scalars(ng)%Fstate(isfsur)) &
5757 & WRITE (out,170) scalars(ng)%Fstate(isfsur), &
5758 & 'Fstate(isFsur)', &
5759# ifdef FORCING_SV
5760 & 'Singular Forcing Vectors on free-surface.'
5761# else
5762 & 'Stochastic Optimals on free-surface.'
5763# endif
5764# ifdef SOLVE3D
5765 IF (scalars(ng)%Fstate(isuvel)) &
5766 & WRITE (out,170) scalars(ng)%Fstate(isuvel), &
5767 & 'Fstate(isUvel)', &
5768# ifdef FORCING_SV
5769 & 'Singular Forcing Vectors on 3D U-momentum component.'
5770# else
5771 & 'Stochastic Optimals on 3D U-momentum component.'
5772# endif
5773 IF (scalars(ng)%Fstate(isvvel)) &
5774 & WRITE (out,170) scalars(ng)%Fstate(isvvel), &
5775 & 'Fstate(isVvel)', &
5776# ifdef FORCING_SV
5777 & 'Singular Forcing Vectors on 3D V-momentum component.'
5778# else
5779 & 'Stochastic Optimals on 3D V-momentum component.'
5780# endif
5781 DO itrc=1,nt(ng)
5782 IF (scalars(ng)%Fstate(istvar(itrc))) &
5783 & WRITE (out,180) scalars(ng)%Fstate(istvar(itrc)), &
5784 & 'Fstate(idTVar)', &
5785# ifdef FORCING_SV
5786 & 'Singular Forcing Vectors on tracer', &
5787# else
5788 & 'Stochastic Optimals on tracer', &
5789# endif
5790 & itrc, trim(vname(1,idtvar(itrc)))
5791 END DO
5792# else
5793 IF (scalars(ng)%Fstate(isubar)) &
5794 & WRITE (out,170) scalars(ng)%Fstate(isubar), &
5795 & 'Fstate(isUbar)', &
5796# ifdef FORCING_SV
5797 & 'Singular Forcing Vectors on 2D U-momentum component.'
5798# else
5799 & 'Stochastic Optimals on 2D U-momentum component.'
5800# endif
5801 IF (scalars(ng)%Fstate(isvbar)) &
5802 & WRITE (out,170) scalars(ng)%Fstate(isvbar), &
5803 & 'Fstate(isVbar)', &
5804# ifdef FORCING_SV
5805 & 'Singular Forcing Vectors on 2D V-momentum component.'
5806# else
5807 & 'Stochastic Optimals on 2D V-momentum component.'
5808# endif
5809# endif
5810 IF (scalars(ng)%Fstate(isustr)) &
5811 & WRITE (out,170) scalars(ng)%Fstate(isustr), &
5812 & 'Fstate(isUstr)', &
5813# ifdef FORCING_SV
5814 & 'Singular Forcing Vectors on surface U-stress.'
5815# else
5816 & 'Stochastic Optimals on surface U-stress.'
5817# endif
5818 IF (scalars(ng)%Fstate(isvstr)) &
5819 & WRITE (out,170) scalars(ng)%Fstate(isvstr), &
5820 & 'Fstate(isVstr)', &
5821# ifdef FORCING_SV
5822 & 'Singular Forcing Vectors on surface V-stress.'
5823# else
5824 & 'Stochastic Optimals on surface V-stress.'
5825# endif
5826# ifdef SOLVE3D
5827 DO itrc=1,nt(ng)
5828 IF (scalars(ng)%Fstate(istsur(itrc))) &
5829 & WRITE (out,180) scalars(ng)%Fstate(istsur(itrc)), &
5830 & 'Fstate(idTsur)', &
5831# ifdef FORCING_SV
5832 & 'Singular Forcing Vectors on surface flux of tracer', &
5833# else
5834 & 'Stochastic Optimals on surface flux of tracer', &
5835# endif
5836 & itrc, trim(vname(1,idtvar(itrc)))
5837 END DO
5838# endif
5839#endif
5840#ifdef SO_SEMI
5841# ifndef SO_SEMI_WHITE
5842 WRITE (out,140) so_decay(ng), 'SO_decay', &
5843 & 'Stochastic optimals time decorrelation scale (days).'
5844# endif
5845 IF (scalars(ng)%Fstate(isfsur)) &
5846 WRITE (out,200) so_sdev(isfsur,ng), 'SO_sdev(isFsur)', &
5847 & 'Stochastic Optimals scale, free-surface'
5848# ifdef SOLVE3D
5849 IF (scalars(ng)%Fstate(isuvel)) &
5850 WRITE (out,200) so_sdev(isuvel,ng), 'SO_sdev(isUvel)', &
5851 & 'Stochastic Optimals scale, 3D U-momentum'
5852 IF (scalars(ng)%Fstate(isvvel)) &
5853 WRITE (out,200) so_sdev(isvvel,ng), 'SO_sdev(isVvel)', &
5854 & 'Stochastic Optimals scale, 3D V-momentum'
5855 DO itrc=1,nt(ng)
5856 IF (scalars(ng)%Fstate(istvar(itrc))) &
5857 & WRITE (out,195) so_sdev(istvar(itrc),ng), &
5858 & 'SO_sdev(idTvar)', &
5859 & 'Stochastic Optimals scale, tracer', &
5860 & itrc, trim(vname(1,idtvar(itrc)))
5861 END DO
5862# else
5863 IF (scalars(ng)%Fstate(isubar)) &
5864 WRITE (out,200) so_sdev(isubar,ng), 'SO_sdev(isUbar)', &
5865 & 'Stochastic Optimals scale, 2D U-momentum'
5866 IF (scalars(ng)%Fstate(isvbar)) &
5867 WRITE (out,200) so_sdev(isvbar,ng), 'SO_sdev(isVbar)', &
5868 & 'Stochastic Optimals scale, 2D V-momentum'
5869# endif
5870 IF (scalars(ng)%Fstate(isustr)) &
5871 WRITE (out,200) so_sdev(isustr,ng), 'SO_sdev(isUstr)', &
5872 & 'Stochastic Optimals scale, surface U-stress'
5873 IF (scalars(ng)%Fstate(isvstr)) &
5874 WRITE (out,200) so_sdev(isvstr,ng), 'SO_sdev(isVstr)', &
5875 & 'Stochastic Optimals scale, surface V-stress'
5876# ifdef SOLVE3D
5877 DO itrc=1,nt(ng)
5878 IF (scalars(ng)%Fstate(istsur(itrc))) &
5879 & WRITE (out,195) so_sdev(istsur(itrc),ng), &
5880 & 'SO_sdev(idTsur)', &
5881 & 'Stochastic Optimals scale, surface flux of tracer', &
5882 & itrc, trim(vname(1,idtvar(itrc)))
5883 END DO
5884# endif
5885#endif
5886 IF ((nhis(ng).gt.0).and.any(hout(:,ng))) THEN
5887 WRITE (out,'(1x)')
5888#if defined SEDIMENT && defined SED_MORPH
5889 IF (hout(idbath,ng)) WRITE (out,170) hout(idbath,ng), &
5890 & 'Hout(idBath)', &
5891 & 'Write out time-dependent bathymetry.'
5892#endif
5893 IF (hout(idfsur,ng)) WRITE (out,170) hout(idfsur,ng), &
5894 & 'Hout(idFsur)', &
5895 & 'Write out free-surface.'
5896 IF (hout(idubar,ng)) WRITE (out,170) hout(idubar,ng), &
5897 & 'Hout(idUbar)', &
5898 & 'Write out 2D U-momentum component.'
5899 IF (hout(idvbar,ng)) WRITE (out,170) hout(idvbar,ng), &
5900 & 'Hout(idVbar)', &
5901 & 'Write out 2D V-momentum component.'
5902 IF (hout(idu2de,ng)) WRITE (out,170) hout(idu2de,ng), &
5903 & 'Hout(idu2dE)', &
5904 & 'Write out 2D U-eastward at RHO-points.'
5905 IF (hout(idv2dn,ng)) WRITE (out,170) hout(idv2dn,ng), &
5906 & 'Hout(idv2dN)', &
5907 & 'Write out 2D V-northward at RHO-points.'
5908#ifdef SOLVE3D
5909 IF (hout(iduvel,ng)) WRITE (out,170) hout(iduvel,ng), &
5910 & 'Hout(idUvel)', &
5911 & 'Write out 3D U-momentum component.'
5912 IF (hout(idvvel,ng)) WRITE (out,170) hout(idvvel,ng), &
5913 & 'Hout(idVvel)', &
5914 & 'Write out 3D V-momentum component.'
5915 IF (hout(idu3de,ng)) WRITE (out,170) hout(idu3de,ng), &
5916 & 'Hout(idu3dE)', &
5917 & 'Write out 3D U-wastward component at RHO-points.'
5918 IF (hout(idv3dn,ng)) WRITE (out,170) hout(idv3dn,ng), &
5919 & 'Hout(idv3dN)', &
5920 & 'Write out 3D V-northward component at RHO-points.'
5921 IF (hout(idwvel,ng)) WRITE (out,170) hout(idwvel,ng), &
5922 & 'Hout(idWvel)', &
5923 & 'Write out W-momentum component.'
5924 IF (hout(idovel,ng)) WRITE (out,170) hout(idovel,ng), &
5925 & 'Hout(idOvel)', &
5926 & 'Write out omega vertical velocity.'
5927# ifdef OMEGA_IMPLICIT
5928 IF (hout(idovil,ng)) WRITE (out,170) hout(idovil,ng), &
5929 & 'Hout(idOvil)', &
5930 & 'Write out omega implicit vertical velocity.'
5931# endif
5932 DO itrc=1,nat
5933 IF (hout(idtvar(itrc),ng)) WRITE (out,180) &
5934 & hout(idtvar(itrc),ng), 'Hout(idTvar)', &
5935 & 'Write out tracer ', itrc, trim(vname(1,idtvar(itrc)))
5936 END DO
5937 IF (hout(idpthr,ng)) WRITE (out,170) hout(idpthr,ng), &
5938 & 'Hout(idpthR)', &
5939 & 'Write out time-varying dephts of RHO-points.'
5940 IF (hout(idpthu,ng)) WRITE (out,170) hout(idpthu,ng), &
5941 & 'Hout(idpthU)', &
5942 & 'Write out time-varying dephts of U-points.'
5943 IF (hout(idpthv,ng)) WRITE (out,170) hout(idpthv,ng), &
5944 & 'Hout(idpthV)', &
5945 & 'Write out time-varying dephts of V-points.'
5946 IF (hout(idpthw,ng)) WRITE (out,170) hout(idpthw,ng), &
5947 & 'Hout(idpthW)', &
5948 & 'Write out time-varying dephts of W-points.'
5949#endif
5950 IF (hout(idusms,ng)) WRITE (out,170) hout(idusms,ng), &
5951 & 'Hout(idUsms)', &
5952 & 'Write out surface U-momentum stress.'
5953 IF (hout(idvsms,ng)) WRITE (out,170) hout(idvsms,ng), &
5954 & 'Hout(idVsms)', &
5955 & 'Write out surface V-momentum stress.'
5956 IF (hout(idubms,ng)) WRITE (out,170) hout(idubms,ng), &
5957 & 'Hout(idUbms)', &
5958 & 'Write out bottom U-momentum stress.'
5959 IF (hout(idvbms,ng)) WRITE (out,170) hout(idvbms,ng), &
5960 & 'Hout(idVbms)', &
5961 & 'Write out bottom V-momentum stress.'
5962#ifdef BBL_MODEL
5963 IF (hout(idubrs,ng)) WRITE (out,170) hout(idubrs,ng), &
5964 & 'Hout(idUbrs)', &
5965 & 'Write out bottom U-current stress.'
5966 IF (hout(idvbrs,ng)) WRITE (out,170) hout(idvbrs,ng), &
5967 & 'Hout(idVbrs)', &
5968 & 'Write out bottom V-current stress.'
5969 IF (hout(idubws,ng)) WRITE (out,170) hout(idubws,ng), &
5970 & 'Hout(idUbws)', &
5971 & 'Write out wind-induced, bottom U-wave stress.'
5972 IF (hout(idvbws,ng)) WRITE (out,170) hout(idvbws,ng), &
5973 & 'Hout(idVbws)', &
5974 & 'Write out wind-induced, bottom V-wave stress.'
5975 IF (hout(idubcs,ng)) WRITE (out,170) hout(idubcs,ng), &
5976 & 'Hout(idUbcs)', &
5977 & 'Write out max wind + current, bottom U-wave stress.'
5978 IF (hout(idvbcs,ng)) WRITE (out,170) hout(idvbcs,ng), &
5979 & 'Hout(idVbcs)', &
5980 & 'Write out max wind + current, bottom V-wave stress.'
5981 IF (hout(iduvwc,ng)) WRITE (out,170) hout(iduvwc,ng), &
5982 & 'Hout(idUVwc)', &
5983 & 'Write out max wind + current, bottom UV-wave stress.'
5984 IF (hout(idubot,ng)) WRITE (out,170) hout(idubot,ng), &
5985 & 'Hout(idUbot)', &
5986 & 'Write out bed wave orbital U-velocity.'
5987 IF (hout(idvbot,ng)) WRITE (out,170) hout(idvbot,ng), &
5988 & 'Hout(idVbot)', &
5989 & 'Write out bed wave orbital V-velocity.'
5990 IF (hout(idubur,ng)) WRITE (out,170) hout(idubur,ng), &
5991 & 'Hout(idUbur)', &
5992 & 'Write out bottom U-momentum above bed.'
5993 IF (hout(idvbvr,ng)) WRITE (out,170) hout(idvbvr,ng), &
5994 & 'Hout(idVbvr)', &
5995 & 'Write out bottom V-momentum above bed.'
5996#endif
5997#if defined WEC
5998 IF (hout(idu2rs,ng)) WRITE (out,170) hout(idu2rs,ng), &
5999 & 'Hout(idU2rs)', &
6000 & 'Write out 2D barotropic wec u-stress.'
6001 IF (hout(idv2rs,ng)) WRITE (out,170) hout(idv2rs,ng), &
6002 & 'Hout(idV2rs)', &
6003 & 'Write out 2D barotropic wec v-stress.'
6004 IF (hout(idu2sd,ng)) WRITE (out,170) hout(idu2sd,ng), &
6005 & 'Hout(idU2Sd)', &
6006 & 'Write out 2D barotropic Stokes u-velocity.'
6007 IF (hout(idv2sd,ng)) WRITE (out,170) hout(idv2sd,ng), &
6008 & 'Hout(idV2Sd)', &
6009 & 'Write out 2D barotropic Stokes v-velocity.'
6010#endif
6011#ifdef SOLVE3D
6012# ifdef WEC
6013 IF (hout(idu3rs,ng)) WRITE (out,170) hout(idu3rs,ng), &
6014 & 'Hout(idU3rs)', &
6015 & 'Write out 3D total wec u-stress.'
6016 IF (hout(idv3rs,ng)) WRITE (out,170) hout(idv3rs,ng), &
6017 & 'Hout(idV3rs)', &
6018 & 'Write out 3D total wec v-stress.'
6019 IF (hout(idu3sd,ng)) WRITE (out,170) hout(idu3sd,ng), &
6020 & 'Hout(idU3Sd)', &
6021 & 'Write out 3D total wec Stokes u-velocity.'
6022 IF (hout(idv3sd,ng)) WRITE (out,170) hout(idv3sd,ng), &
6023 & 'Hout(idV3Sd)', &
6024 & 'Write out 3D total wec Stokes v-velocity.'
6025 IF (hout(idw3sd,ng)) WRITE (out,170) hout(idw3sd,ng), &
6026 & 'Hout(idW3Sd)', &
6027 & 'Write out 3D wec omega Stokes vertical velocity.'
6028 IF (hout(idw3st,ng)) WRITE (out,170) hout(idw3st,ng), &
6029 & 'Hout(idW3St)', &
6030 & 'Write out 3D wec Stokes vertical velocity.'
6031# endif
6032# ifdef WEC_VF
6033 IF (hout(idwztw,ng)) WRITE (out,170) hout(idwztw,ng), &
6034 & 'Hout(idWztw)', &
6035 & 'Write out wec quasi-static sea level adjustment.'
6036 IF (hout(idwqsp,ng)) WRITE (out,170) hout(idwqsp,ng), &
6037 & 'Hout(idWqsp)', &
6038 & 'Write out wec quasi-static sea pressure adjustment.'
6039 IF (hout(idwbeh,ng)) WRITE (out,170) hout(idwbeh,ng), &
6040 & 'Hout(idWbeh)', &
6041 & 'Write out wec Bernoulli head sea level adjustment.'
6042# endif
6043#endif
6044#ifdef WAVES_HEIGHT
6045 IF (hout(idwamp,ng)) WRITE (out,170) hout(idwamp,ng), &
6046 & 'Hout(idWamp)', &
6047 & 'Write out wave height.'
6048#endif
6049#ifdef WAVES_LENGTH
6050 IF (hout(idwlen,ng)) WRITE (out,170) hout(idwlen,ng), &
6051 & 'Hout(idWlen)', &
6052 & 'Write out waves mean wavelength.'
6053#endif
6054#ifdef WAVES_LENGTHP
6055 IF (hout(idwlep,ng)) WRITE (out,170) hout(idwlep,ng), &
6056 & 'Hout(idWlep)', &
6057 & 'Write out waves peak wavelength.'
6058#endif
6059#ifdef WAVES_DIR
6060 IF (hout(idwdir,ng)) WRITE (out,170) hout(idwdir,ng), &
6061 & 'Hout(idWdir)', &
6062 & 'Write out waves mean direction.'
6063#endif
6064#ifdef WAVES_DIRP
6065 IF (hout(idwdip,ng)) WRITE (out,170) hout(idwdip,ng), &
6066 & 'Hout(idWdip)', &
6067 & 'Write out peak waves direction.'
6068#endif
6069#ifdef WAVES_TOP_PERIOD
6070 IF (hout(idwptp,ng)) WRITE (out,170) hout(idwptp,ng), &
6071 & 'Hout(idWptp)', &
6072 & 'Write out wave surface period.'
6073#endif
6074#ifdef WAVES_BOT_PERIOD
6075 IF (hout(idwpbt,ng)) WRITE (out,170) hout(idwpbt,ng), &
6076 & 'Hout(idWpbt)', &
6077 & 'Write out wave bottom period.'
6078#endif
6079#if defined BBL_MODEL || defined BEDLOAD_SOULSBY || \
6080 defined bedload_vandera || defined wav_coupling
6081 IF (hout(idworb,ng)) WRITE (out,170) hout(idworb,ng), &
6082 & 'Hout(idWorb)', &
6083 & 'Write out wave bottom orbital velocity.'
6084#endif
6085#if defined WAV_COUPLING || (defined WEC_VF && defined BOTTOM_STREAMING)
6086 IF (hout(idwdif,ng)) WRITE (out,170) hout(idwdif,ng), &
6087 & 'Hout(idWdif)', &
6088 & 'Write out wave dissipation due to bottom friction.'
6089#endif
6090#if defined TKE_WAVEDISS || defined WAV_COUPLING || \
6091 defined wdiss_thorguza || defined wdiss_churthor || \
6092 defined waves_diss || defined wdiss_inwave
6093 IF (hout(idwdib,ng)) WRITE (out,170) hout(idwdib,ng), &
6094 & 'Hout(idWdib)', &
6095 & 'Write out wave dissipation due to breaking.'
6096 IF (hout(idwdiw,ng)) WRITE (out,170) hout(idwdiw,ng), &
6097 & 'Hout(idWdiw)', &
6098 & 'Write out wave dissipation due to whitecapping.'
6099#endif
6100#ifdef ROLLER_SVENDSEN
6101 IF (hout(idwbrk,ng)) WRITE (out,170) hout(idwbrk,ng), &
6102 & 'Hout(idWbrk)', &
6103 & 'Write out percent wave breaking.'
6104#endif
6105#ifdef WEC_ROLLER
6106 IF (hout(idwdis,ng)) WRITE (out,170) hout(idwdis,ng), &
6107 & 'Hout(idWdis)', &
6108 & 'Write out wave roller dissipation.'
6109#endif
6110#ifdef ROLLER_RENIERS
6111 IF (hout(idwrol,ng)) WRITE (out,170) hout(idwrol,ng), &
6112 & 'Hout(idWrol)', &
6113 & 'Write out wave roller action density.'
6114#endif
6115#ifdef WAVES_DSPR
6116 IF (hout(idwvds,ng)) WRITE (out,170) hout(idwvds,ng), &
6117 & 'Hout(idWvds)', &
6118 & 'Write out wave directional spread.'
6119 IF (hout(idwvqp,ng)) WRITE (out,170) hout(idwvqp,ng), &
6120 & 'Hout(idWvqp)', &
6121 & 'Write out wave spectrum peakedness.'
6122#endif
6123#ifdef UV_KIRBY
6124 IF (hout(iduwav,ng)) WRITE (out,170) hout(iduwav,ng), &
6125 & 'Hout(idUwav)', &
6126 & 'Wave-avg surface u-velocity.'
6127 IF (hout(idvwav,ng)) WRITE (out,170) hout(idvwav,ng), &
6128 & 'Hout(idVwav)', &
6129 & 'Wave-avg surface v-velocity.'
6130#endif
6131#ifdef INWAVE_MODEL
6132 IF (hout(idacen,ng)) WRITE (out,170) hout(idacen,ng), &
6133 & 'Hout(idACen)', &
6134 & 'Write out 3D wave action'
6135 IF (hout(idacct,ng)) WRITE (out,170) hout(idacct,ng), &
6136 & 'Hout(idACct)', &
6137 & 'Wave group celerity in the theta coordinate.'
6138 IF (hout(idaccx,ng)) WRITE (out,170) hout(idaccx,ng), &
6139 & 'Hout(idACcx)', &
6140 & 'Wave group celerity in the xi coordinate.'
6141 IF (hout(idaccy,ng)) WRITE (out,170) hout(idaccy,ng), &
6142 & 'Hout(idACcy)', &
6143 & 'Wave group celerity in the eta space.'
6144 IF (hout(idactp,ng)) WRITE (out,170) hout(idactp,ng), &
6145 & 'Hout(idACtp)', &
6146 & 'Wave group peak period.'
6147#endif
6148#if defined SOLVE3D && defined T_PASSIVE
6149 DO itrc=1,npt
6150 IF (hout(idtvar(inert(itrc)),ng)) WRITE (out,180) &
6151 & hout(idtvar(inert(itrc)),ng), 'Hout(inert)', &
6152 & 'Write out inert passive tracer ', itrc, &
6153 & trim(vname(1,idtvar(inert(itrc))))
6154 END DO
6155#endif
6156#ifdef SOLVE3D
6157# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
6158 IF (hout(idpair,ng)) WRITE (out,170) hout(idpair,ng), &
6159 & 'Hout(idPair)', &
6160 & 'Write out surface air pressure.'
6161# endif
6162# if defined BULK_FLUXES
6163 IF (hout(idtair,ng)) WRITE (out,170) hout(idtair,ng), &
6164 & 'Hout(idTair)', &
6165 & 'Write out surface air temperature.'
6166# endif
6167# if defined BULK_FLUXES || defined ECOSIM
6168 IF (hout(iduair,ng)) WRITE (out,170) hout(iduair,ng), &
6169 & 'Hout(idUair)', &
6170 & 'Write out surface U-wind component.'
6171 IF (hout(idvair,ng)) WRITE (out,170) hout(idvair,ng), &
6172 & 'Hout(idVair)', &
6173 & 'Write out surface V-wind component.'
6174 IF (hout(iduaie,ng)) WRITE (out,170) hout(iduaie,ng), &
6175 & 'Hout(idUaiE)', &
6176 & 'Write out surface Eastward U-wind component.'
6177 IF (hout(idvain,ng)) WRITE (out,170) hout(idvain,ng), &
6178 & 'Hout(idVaiN)', &
6179 & 'Write out surface Northward V-wind component.'
6180# endif
6181 IF (hout(idtsur(itemp),ng)) WRITE (out,170) &
6182 & hout(idtsur(itemp),ng), 'Hout(idTsur)', &
6183 & 'Write out surface net heat flux.'
6184# ifdef SALINITY
6185 IF (hout(idtsur(isalt),ng)) WRITE (out,170) &
6186 & hout(idtsur(isalt),ng), 'Hout(idTsur)', &
6187 & 'Write out surface net salt flux.'
6188# endif
6189# ifdef SHORTWAVE
6190 IF (hout(idsrad,ng)) WRITE (out,170) hout(idsrad,ng), &
6191 & 'Hout(idSrad)', &
6192 & 'Write out shortwave radiation flux.'
6193# endif
6194# if defined BULK_FLUXES || defined FRC_COUPLING
6195 IF (hout(idlrad,ng)) WRITE (out,170) hout(idlrad,ng), &
6196 & 'Hout(idLrad)', &
6197 & 'Write out longwave radiation flux.'
6198 IF (hout(idlhea,ng)) WRITE (out,170) hout(idlhea,ng), &
6199 & 'Hout(idLhea)', &
6200 & 'Write out latent heat flux.'
6201 IF (hout(idshea,ng)) WRITE (out,170) hout(idshea,ng), &
6202 & 'Hout(idShea)', &
6203 & 'Write out sensible heat flux.'
6204# if defined EMINUSP || defined FRC_COUPLING
6205 IF (hout(idempf,ng)) WRITE (out,170) hout(idempf,ng), &
6206 & 'Hout(idEmPf)', &
6207 & 'Write out E-P flux.'
6208# endif
6209# ifdef EMINUSP
6210 IF (hout(idevap,ng)) WRITE (out,170) hout(idevap,ng), &
6211 & 'Hout(idevap)', &
6212 & 'Write out evaporation rate.'
6213 IF (hout(idrain,ng)) WRITE (out,170) hout(idrain,ng), &
6214 & 'Hout(idrain)', &
6215 & 'Write out rain rate.'
6216# endif
6217# endif
6218 IF (hout(iddano,ng)) WRITE (out,170) hout(iddano,ng), &
6219 & 'Hout(idDano)', &
6220 & 'Write out density anomaly.'
6221 IF (hout(idvvis,ng)) WRITE (out,170) hout(idvvis,ng), &
6222 & 'Hout(idVvis)', &
6223 & 'Write out vertical viscosity: AKv.'
6224 IF (hout(idtdif,ng)) WRITE (out,170) hout(idtdif,ng), &
6225 & 'Hout(idTdif)', &
6226 & 'Write out vertical diffusion: AKt(itemp).'
6227# ifdef SALINITY
6228 IF (hout(idsdif,ng)) WRITE (out,170) hout(idsdif,ng), &
6229 & 'Hout(idSdif)', &
6230 & 'Write out vertical diffusion: AKt(isalt).'
6231# endif
6232# ifdef LMD_SKPP
6233 IF (hout(idhsbl,ng)) WRITE (out,170) hout(idhsbl,ng), &
6234 & 'Hout(idHsbl)', &
6235 & 'Write out depth of surface boundary layer.'
6236# endif
6237# ifdef LMD_BKPP
6238 IF (hout(idhbbl,ng)) WRITE (out,170) hout(idhbbl,ng), &
6239 & 'Hout(idHbbl)', &
6240 & 'Write out depth of bottom boundary layer.'
6241# endif
6242# if defined GLS_MIXING || defined MY25_MIXING
6243 IF (hout(idmtke,ng)) WRITE (out,170) hout(idmtke,ng), &
6244 & 'Hout(idMtke)', &
6245 & 'Write out turbulent kinetic energy.'
6246 IF (hout(idmtls,ng)) WRITE (out,170) hout(idmtls,ng), &
6247 & 'Hout(idMtls)', &
6248 & 'Write out turbulent generic length-scale.'
6249# endif
6250#endif
6251 END IF
6252
6253 IF ((nqck(ng).gt.0).and.any(qout(:,ng))) THEN
6254 WRITE (out,'(1x)')
6255#if defined SEDIMENT && defined SED_MORPH
6256 IF (qout(idbath,ng)) WRITE (out,170) qout(idbath,ng), &
6257 & 'Qout(idBath)', &
6258 & 'Write out time-dependent bathymetry.'
6259#endif
6260 IF (qout(idfsur,ng)) WRITE (out,170) qout(idfsur,ng), &
6261 & 'Qout(idFsur)', &
6262 & 'Write out free-surface.'
6263 IF (qout(idubar,ng)) WRITE (out,170) qout(idubar,ng), &
6264 & 'Qout(idUbar)', &
6265 & 'Write out 2D U-momentum component.'
6266 IF (qout(idvbar,ng)) WRITE (out,170) qout(idvbar,ng), &
6267 & 'Qout(idVbar)', &
6268 & 'Write out 2D V-momentum component.'
6269 IF (qout(idu2de,ng)) WRITE (out,170) qout(idu2de,ng), &
6270 & 'Qout(idu2dE)', &
6271 & 'Write out 2D U-eastward at RHO-points.'
6272 IF (qout(idv2dn,ng)) WRITE (out,170) qout(idv2dn,ng), &
6273 & 'Qout(idv2dN)', &
6274 & 'Write out 2D V-northward at RHO-points.'
6275#ifdef SOLVE3D
6276 IF (qout(iduvel,ng)) WRITE (out,170) qout(iduvel,ng), &
6277 & 'Qout(idUvel)', &
6278 & 'Write out 3D U-momentum component.'
6279 IF (qout(idvvel,ng)) WRITE (out,170) qout(idvvel,ng), &
6280 & 'Qout(idVvel)', &
6281 & 'Write out 3D V-momentum component.'
6282 IF (qout(idusur,ng)) WRITE (out,170) qout(idusur,ng), &
6283 & 'Qout(idUsur)', &
6284 & 'Write out surface U-momentum component.'
6285 IF (qout(idvsur,ng)) WRITE (out,170) qout(idvsur,ng), &
6286 & 'Qout(idVsur)', &
6287 & 'Write out surface V-momentum component.'
6288 IF (qout(idu3de,ng)) WRITE (out,170) qout(idu3de,ng), &
6289 & 'Qout(idu3dE)', &
6290 & 'Write out 3D U-wastward component at RHO-points.'
6291 IF (qout(idv3dn,ng)) WRITE (out,170) qout(idv3dn,ng), &
6292 & 'Qout(idv3dN)', &
6293 & 'Write out 3D V-northward component at RHO-points.'
6294 IF (qout(idu3de,ng)) WRITE (out,170) qout(idu3de,ng), &
6295 & 'Qout(idu3dE)', &
6296 & 'Write out surface U-wastward component at RHO-points.'
6297 IF (qout(idv3dn,ng)) WRITE (out,170) qout(idv3dn,ng), &
6298 & 'Qout(idv3dN)', &
6299 & 'Write out surface V-northward component at RHO-points.'
6300 IF (qout(idwvel,ng)) WRITE (out,170) qout(idwvel,ng), &
6301 & 'Qout(idWvel)', &
6302 & 'Write out W-momentum component.'
6303 IF (qout(idovel,ng)) WRITE (out,170) qout(idovel,ng), &
6304 & 'Qout(idOvel)', &
6305 & 'Write out omega vertical velocity.'
6306 DO itrc=1,nat
6307 IF (qout(idtvar(itrc),ng)) WRITE (out,180) &
6308 & qout(idtvar(itrc),ng), 'Qout(idTvar)', &
6309 & 'Write out tracer ', itrc, trim(vname(1,idtvar(itrc)))
6310 END DO
6311 DO itrc=1,nat
6312 IF (qout(idsurt(itrc),ng)) WRITE (out,180) &
6313 & qout(idsurt(itrc),ng), 'Qout(idsurT)', &
6314 & 'Write out surface tracer ', itrc, &
6315 & trim(vname(1,idsurt(itrc)))
6316 END DO
6317 IF (qout(idpthr,ng)) WRITE (out,170) qout(idpthr,ng), &
6318 & 'Qout(idpthR)', &
6319 & 'Write out time-varying dephts of RHO-points.'
6320 IF (qout(idpthu,ng)) WRITE (out,170) qout(idpthu,ng), &
6321 & 'Qout(idpthU)', &
6322 & 'Write out time-varying dephts of U-points.'
6323 IF (qout(idpthv,ng)) WRITE (out,170) qout(idpthv,ng), &
6324 & 'Qout(idpthV)', &
6325 & 'Write out time-varying dephts of V-points.'
6326 IF (qout(idpthw,ng)) WRITE (out,170) qout(idpthw,ng), &
6327 & 'Qout(idpthW)', &
6328 & 'Write out time-varying dephts of W-points.'
6329#endif
6330 IF (qout(idusms,ng)) WRITE (out,170) qout(idusms,ng), &
6331 & 'Qout(idUsms)', &
6332 & 'Write out surface U-momentum stress.'
6333 IF (qout(idvsms,ng)) WRITE (out,170) qout(idvsms,ng), &
6334 & 'Qout(idVsms)', &
6335 & 'Write out surface V-momentum stress.'
6336 IF (qout(idubms,ng)) WRITE (out,170) qout(idubms,ng), &
6337 & 'Qout(idUbms)', &
6338 & 'Write out bottom U-momentum stress.'
6339 IF (qout(idvbms,ng)) WRITE (out,170) qout(idvbms,ng), &
6340 & 'Qout(idVbms)', &
6341 & 'Write out bottom V-momentum stress.'
6342#ifdef BBL_MODEL
6343 IF (qout(idubrs,ng)) WRITE (out,170) qout(idubrs,ng), &
6344 & 'Qout(idUbrs)', &
6345 & 'Write out bottom U-current stress.'
6346 IF (qout(idvbrs,ng)) WRITE (out,170) qout(idvbrs,ng), &
6347 & 'Qout(idVbrs)', &
6348 & 'Write out bottom V-current stress.'
6349 IF (qout(idubws,ng)) WRITE (out,170) qout(idubws,ng), &
6350 & 'Qout(idUbws)', &
6351 & 'Write out wind-induced, bottom U-wave stress.'
6352 IF (qout(idvbws,ng)) WRITE (out,170) qout(idvbws,ng), &
6353 & 'Qout(idVbws)', &
6354 & 'Write out wind-induced, bottom V-wave stress.'
6355 IF (qout(idubcs,ng)) WRITE (out,170) qout(idubcs,ng), &
6356 & 'Qout(idUbcs)', &
6357 & 'Write out max wind + current, bottom U-wave stress.'
6358 IF (qout(idvbcs,ng)) WRITE (out,170) qout(idvbcs,ng), &
6359 & 'Qout(idVbcs)', &
6360 & 'Write out max wind + current, bottom V-wave stress.'
6361 IF (qout(idubot,ng)) WRITE (out,170) qout(idubot,ng), &
6362 & 'Qout(idUbot)', &
6363 & 'Write out bed wave orbital U-velocity.'
6364 IF (qout(idvbot,ng)) WRITE (out,170) qout(idvbot,ng), &
6365 & 'Qout(idVbot)', &
6366 & 'Write out bed wave orbital V-velocity.'
6367 IF (qout(idubur,ng)) WRITE (out,170) qout(idubur,ng), &
6368 & 'Qout(idUbur)', &
6369 & 'Write out bottom U-momentum above bed.'
6370 IF (qout(idvbvr,ng)) WRITE (out,170) qout(idvbvr,ng), &
6371 & 'Qout(idVbvr)', &
6372 & 'Write out bottom V-momentum above bed.'
6373#endif
6374#if defined WEC
6375 IF (qout(idu2rs,ng)) WRITE (out,170) qout(idu2rs,ng), &
6376 & 'Qout(idU2rs)', &
6377 & 'Write out 2D barotropic wec u-stress.'
6378 IF (qout(idv2rs,ng)) WRITE (out,170) qout(idv2rs,ng), &
6379 & 'Qout(idV2rs)', &
6380 & 'Write out 2D barotropic wec v-stress.'
6381 IF (qout(idu2sd,ng)) WRITE (out,170) qout(idu2sd,ng), &
6382 & 'Qout(idU2Sd)', &
6383 & 'Write out 2D barotropic Stokes u-velocity.'
6384 IF (qout(idv2sd,ng)) WRITE (out,170) qout(idv2sd,ng), &
6385 & 'Qout(idV2Sd)', &
6386 & 'Write out 2D barotropic Stokes v-velocity.'
6387#endif
6388#ifdef SOLVE3D
6389# ifdef WEC
6390 IF (qout(idu3rs,ng)) WRITE (out,170) qout(idu3rs,ng), &
6391 & 'Qout(idU3rs)', &
6392 & 'Write out 3D total wec u-stress.'
6393 IF (qout(idv3rs,ng)) WRITE (out,170) qout(idv3rs,ng), &
6394 & 'Qout(idV3rs)', &
6395 & 'Write out 3D total wec v-stress.'
6396 IF (qout(idu3sd,ng)) WRITE (out,170) qout(idu3sd,ng), &
6397 & 'Qout(idU3Sd)', &
6398 & 'Write out 3D total wec Stokes u-velocity.'
6399 IF (qout(idv3sd,ng)) WRITE (out,170) qout(idv3sd,ng), &
6400 & 'Qout(idV3Sd)', &
6401 & 'Write out 3D total wec Stokes v-velocity.'
6402 IF (qout(idw3sd,ng)) WRITE (out,170) qout(idw3sd,ng), &
6403 & 'Qout(idW3Sd)', &
6404 & 'Write out 3D wec omega Stokes vertical velocity.'
6405 IF (qout(idw3st,ng)) WRITE (out,170) qout(idw3st,ng), &
6406 & 'Qout(idW3St)', &
6407 & 'Write out 3D wec Stokes vertical velocity.'
6408# endif
6409# ifdef WEC_VF
6410 IF (qout(idwztw,ng)) WRITE (out,170) qout(idwztw,ng), &
6411 & 'Qout(idWztw)', &
6412 & 'Write out wec quasi-static sea level adjustment.'
6413 IF (qout(idwqsp,ng)) WRITE (out,170) qout(idwqsp,ng), &
6414 & 'Qout(idWqsp)', &
6415 & 'Write out wec quasi-static sea pressure adjustment.'
6416 IF (qout(idwbeh,ng)) WRITE (out,170) qout(idwbeh,ng), &
6417 & 'Qout(idWbeh)', &
6418 & 'Write out wec Bernoulli head sea level adjustment.'
6419# endif
6420#endif
6421#ifdef WAVES_HEIGHT
6422 IF (qout(idwamp,ng)) WRITE (out,170) qout(idwamp,ng), &
6423 & 'Qout(idWamp)', &
6424 & 'Write out wave height.'
6425#endif
6426#ifdef WAVES_LENGTH
6427 IF (qout(idwlen,ng)) WRITE (out,170) qout(idwlen,ng), &
6428 & 'Qout(idWlen)', &
6429 & 'Write out waves mean wavelength.'
6430#endif
6431#ifdef WAVES_LENGTHP
6432 IF (qout(idwlep,ng)) WRITE (out,170) qout(idwlep,ng), &
6433 & 'Qout(idWlep)', &
6434 & 'Write out waves peak wavelength.'
6435#endif
6436#ifdef WAVES_DIR
6437 IF (qout(idwdir,ng)) WRITE (out,170) qout(idwdir,ng), &
6438 & 'Qout(idWdir)', &
6439 & 'Write out waves mean direction.'
6440#endif
6441#ifdef WAVES_DIRP
6442 IF (qout(idwdip,ng)) WRITE (out,170) qout(idwdip,ng), &
6443 & 'Qout(idWdip)', &
6444 & 'Write out peak waves direction.'
6445#endif
6446#ifdef WAVES_TOP_PERIOD
6447 IF (qout(idwptp,ng)) WRITE (out,170) qout(idwptp,ng), &
6448 & 'Qout(idWptp)', &
6449 & 'Write out wave surface period.'
6450#endif
6451#ifdef WAVES_BOT_PERIOD
6452 IF (qout(idwpbt,ng)) WRITE (out,170) qout(idwpbt,ng), &
6453 & 'Qout(idWpbt)', &
6454 & 'Write out wave bottom period.'
6455#endif
6456#if defined BBL_MODEL || defined BEDLOAD_SOULSBY || \
6457 defined bedload_vandera || defined wav_coupling
6458 IF (qout(idworb,ng)) WRITE (out,170) qout(idworb,ng), &
6459 & 'Qout(idWorb)', &
6460 & 'Write out wave bottom orbital velocity.'
6461#endif
6462#if defined WAV_COUPLING || (defined WEC_VF && defined BOTTOM_STREAMING)
6463 IF (qout(idwdif,ng)) WRITE (out,170) qout(idwdif,ng), &
6464 & 'Qout(idWdif)', &
6465 & 'Write out wave dissipation due to bottom friction.'
6466#endif
6467#if defined TKE_WAVEDISS || defined WAV_COUPLING || \
6468 defined wdiss_thorguza || defined wdiss_churthor || \
6469 defined waves_diss || defined wdiss_inwave
6470 IF (qout(idwdib,ng)) WRITE (out,170) qout(idwdib,ng), &
6471 & 'Qout(idWdib)', &
6472 & 'Write out wave dissipation due to breaking.'
6473 IF (qout(idwdiw,ng)) WRITE (out,170) qout(idwdiw,ng), &
6474 & 'Qout(idWdiw)', &
6475 & 'Write out wave dissipation due to whitecapping.'
6476#endif
6477#ifdef ROLLER_SVENDSEN
6478 IF (qout(idwbrk,ng)) WRITE (out,170) qout(idwbrk,ng), &
6479 & 'Qout(idWbrk)', &
6480 & 'Write out percent wave breaking.'
6481#endif
6482#ifdef WEC_ROLLER
6483 IF (qout(idwdis,ng)) WRITE (out,170) qout(idwdis,ng), &
6484 & 'Qout(idWdis)', &
6485 & 'Write out wave roller dissipation.'
6486#endif
6487#ifdef ROLLER_RENIERS
6488 IF (qout(idwrol,ng)) WRITE (out,170) qout(idwrol,ng), &
6489 & 'Qout(idWrol)', &
6490 & 'Write out wave roller action density.'
6491#endif
6492#ifdef WAVES_DSPR
6493 IF (qout(idwvds,ng)) WRITE (out,170) qout(idwvds,ng), &
6494 & 'Qout(idWvds)', &
6495 & 'Write out wave directional spread.'
6496 IF (qout(idwvqp,ng)) WRITE (out,170) qout(idwvqp,ng), &
6497 & 'Qout(idWvqp)', &
6498 & 'Write out wave spectrum peakedness.'
6499#endif
6500#ifdef UV_KIRBY
6501 IF (qout(iduwav,ng)) WRITE (out,170) qout(iduwav,ng), &
6502 & 'Qout(idUwav)', &
6503 & 'Wave-avg surface u-velocity.'
6504 IF (qout(idvwav,ng)) WRITE (out,170) qout(idvwav,ng), &
6505 & 'Qout(idVwav)', &
6506 & 'Wave-avg surface v-velocity.'
6507#endif
6508#if defined SOLVE3D && defined T_PASSIVE
6509 DO itrc=1,npt
6510 IF (qout(idtvar(inert(itrc)),ng)) WRITE (out,180) &
6511 & qout(idtvar(inert(itrc)),ng), 'Qout(inert)', &
6512 & 'Write out inert passive tracer ', itrc, &
6513 & trim(vname(1,idtvar(inert(itrc))))
6514 END DO
6515 DO itrc=1,npt
6516 IF (qout(idsurt(inert(itrc)),ng)) WRITE (out,180) &
6517 & qout(idsurt(inert(itrc)),ng), 'Qout(Snert)', &
6518 & 'Write out inert passive tracer ', itrc, &
6519 & trim(vname(1,idsurt(inert(itrc))))
6520 END DO
6521#endif
6522#ifdef SOLVE3D
6523# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
6524 IF (qout(idpair,ng)) WRITE (out,170) qout(idpair,ng), &
6525 & 'Qout(idPair)', &
6526 & 'Write out surface air pressure.'
6527# endif
6528# if defined BULK_FLUXES
6529 IF (qout(idtair,ng)) WRITE (out,170) qout(idtair,ng), &
6530 & 'Qout(idTair)', &
6531 & 'Write out surface air temperature.'
6532# endif
6533# if defined BULK_FLUXES || defined ECOSIM
6534 IF (qout(iduair,ng)) WRITE (out,170) qout(iduair,ng), &
6535 & 'Qout(idUair)', &
6536 & 'Write out surface U-wind component.'
6537 IF (qout(idvair,ng)) WRITE (out,170) qout(idvair,ng), &
6538 & 'Qout(idVair)', &
6539 & 'Write out surface V-wind component.'
6540 IF (qout(iduaie,ng)) WRITE (out,170) qout(iduaie,ng), &
6541 & 'Qout(idUaiE)', &
6542 & 'Write out surface Eastward U-wind component.'
6543 IF (qout(idvain,ng)) WRITE (out,170) qout(idvain,ng), &
6544 & 'Qout(idVaiN)', &
6545 & 'Write out surface Northward V-wind component.'
6546# endif
6547 IF (qout(idtsur(itemp),ng)) WRITE (out,170) &
6548 & qout(idtsur(itemp),ng), 'Qout(idTsur)', &
6549 & 'Write out surface net heat flux.'
6550# ifdef SALINITY
6551 IF (qout(idtsur(isalt),ng)) WRITE (out,170) &
6552 & qout(idtsur(isalt),ng), 'Qout(idTsur)', &
6553 & 'Write out surface net salt flux.'
6554# endif
6555# ifdef SHORTWAVE
6556 IF (qout(idsrad,ng)) WRITE (out,170) qout(idsrad,ng), &
6557 & 'Qout(idSrad)', &
6558 & 'Write out shortwave radiation flux.'
6559# endif
6560# if defined BULK_FLUXES || defined FRC_COUPLING
6561 IF (qout(idlrad,ng)) WRITE (out,170) qout(idlrad,ng), &
6562 & 'Qout(idLrad)', &
6563 & 'Write out longwave radiation flux.'
6564 IF (qout(idlhea,ng)) WRITE (out,170) qout(idlhea,ng), &
6565 & 'Qout(idLhea)', &
6566 & 'Write out latent heat flux.'
6567 IF (qout(idshea,ng)) WRITE (out,170) qout(idshea,ng), &
6568 & 'Qout(idShea)', &
6569 & 'Write out sensible heat flux.'
6570# if defined EMINUSP || defined FRC_COUPLING
6571 IF (qout(idempf,ng)) WRITE (out,170) qout(idempf,ng), &
6572 & 'Qout(idEmPf)', &
6573 & 'Write out E-P flux.'
6574# endif
6575# ifdef EMINUSP
6576 IF (qout(idevap,ng)) WRITE (out,170) qout(idevap,ng), &
6577 & 'Qout(idevap)', &
6578 & 'Write out evaporation rate.'
6579 IF (qout(idrain,ng)) WRITE (out,170) qout(idrain,ng), &
6580 & 'Qout(idrain)', &
6581 & 'Write out rain rate.'
6582# endif
6583# endif
6584 IF (qout(iddano,ng)) WRITE (out,170) qout(iddano,ng), &
6585 & 'Qout(idDano)', &
6586 & 'Write out density anomaly.'
6587 IF (qout(idvvis,ng)) WRITE (out,170) qout(idvvis,ng), &
6588 & 'Qout(idVvis)', &
6589 & 'Write out vertical viscosity: AKv.'
6590 IF (qout(idtdif,ng)) WRITE (out,170) qout(idtdif,ng), &
6591 & 'Qout(idTdif)', &
6592 & 'Write out vertical diffusion: AKt(itemp).'
6593# ifdef SALINITY
6594 IF (qout(idsdif,ng)) WRITE (out,170) qout(idsdif,ng), &
6595 & 'Qout(idSdif)', &
6596 & 'Write out vertical diffusion: AKt(isalt).'
6597# endif
6598# ifdef LMD_SKPP
6599 IF (qout(idhsbl,ng)) WRITE (out,170) qout(idhsbl,ng), &
6600 & 'Qout(idHsbl)', &
6601 & 'Write out depth of surface boundary layer.'
6602# endif
6603# ifdef LMD_BKPP
6604 IF (qout(idhbbl,ng)) WRITE (out,170) qout(idhbbl,ng), &
6605 & 'Qout(idHbbl)', &
6606 & 'Write out depth of bottom boundary layer.'
6607# endif
6608# if defined GLS_MIXING || defined MY25_MIXING
6609 IF (qout(idmtke,ng)) WRITE (out,170) qout(idmtke,ng), &
6610 & 'Qout(idMtke)', &
6611 & 'Write out turbulent kinetic energy.'
6612 IF (qout(idmtls,ng)) WRITE (out,170) qout(idmtls,ng), &
6613 & 'Qout(idMtls)', &
6614 & 'Write out turbulent generic length-scale.'
6615# endif
6616#endif
6617 END IF
6618#if defined AVERAGES || \
6619 (defined ad_averages && defined adjoint) || \
6620 (defined rp_averages && defined tl_ioms) || \
6621 (defined tl_averages && defined tangent)
6622 IF ((navg(ng).gt.0).and.any(aout(:,ng))) THEN
6623 WRITE (out,'(1x)')
6624 IF (aout(idfsur,ng)) WRITE (out,170) aout(idfsur,ng), &
6625 & 'Aout(idFsur)', &
6626 & 'Write out averaged free-surface.'
6627 IF (aout(idubar,ng)) WRITE (out,170) aout(idubar,ng), &
6628 & 'Aout(idUbar)', &
6629 & 'Write out averaged 2D U-momentum component.'
6630 IF (aout(idvbar,ng)) WRITE (out,170) aout(idvbar,ng), &
6631 & 'Aout(idVbar)', &
6632 & 'Write out averaged 2D V-momentum component.'
6633 IF (aout(idu2de,ng)) WRITE (out,170) aout(idu2de,ng), &
6634 & 'Aout(idu2dE)', &
6635 & 'Write out averaged 2D U-eastward at RHO-points.'
6636 IF (aout(idv2dn,ng)) WRITE (out,170) aout(idv2dn,ng), &
6637 & 'Aout(idv2dN)', &
6638 & 'Write out averaged 2D V-northward at RHO-points.'
6639# ifdef SOLVE3D
6640 IF (aout(iduvel,ng)) WRITE (out,170) aout(iduvel,ng), &
6641 & 'Aout(idUvel)', &
6642 & 'Write out averaged 3D U-momentum component.'
6643 IF (aout(idvvel,ng)) WRITE (out,170) aout(idvvel,ng), &
6644 & 'Aout(idVvel)', &
6645 & 'Write out averaged 3D V-momentum component.'
6646 IF (aout(idu3de,ng)) WRITE (out,170) aout(idu3de,ng), &
6647 & 'Aout(idu3dE)', &
6648 & 'Write out averaged 3D U-eastward at RHO-points.'
6649 IF (aout(idv3dn,ng)) WRITE (out,170) aout(idv3dn,ng), &
6650 & 'Aout(idv3dN)', &
6651 & 'Write out averaged 3D V-northward at RHO-points.'
6652 IF (aout(idwvel,ng)) WRITE (out,170) aout(idwvel,ng), &
6653 & 'Aout(idWvel)', &
6654 & 'Write out averaged W-momentum component.'
6655 IF (aout(idovel,ng)) WRITE (out,170) aout(idovel,ng), &
6656 & 'Aout(idOvel)', &
6657 & 'Write out averaged omega vertical velocity.'
6658 DO itrc=1,nat
6659 IF (aout(idtvar(itrc),ng)) WRITE (out,180) &
6660 & aout(idtvar(itrc),ng), 'Aout(idTvar)', &
6661 & 'Write out averaged tracer ', itrc, &
6662 & trim(vname(1,idtvar(itrc)))
6663 END DO
6664# endif
6665 IF (aout(idusms,ng)) WRITE (out,170) aout(idusms,ng), &
6666 & 'Aout(idUsms)', &
6667 & 'Write out averaged surface U-momentum stress.'
6668 IF (aout(idvsms,ng)) WRITE (out,170) aout(idvsms,ng), &
6669 & 'Aout(idVsms)', &
6670 & 'Write out averaged surface V-momentum stress.'
6671 IF (aout(idubms,ng)) WRITE (out,170) aout(idubms,ng), &
6672 & 'Aout(idUbms)', &
6673 & 'Write out averaged bottom U-momentum stress.'
6674 IF (aout(idvbms,ng)) WRITE (out,170) aout(idvbms,ng), &
6675 & 'Aout(idVbms)', &
6676 & 'Write out averaged bottom V-momentum stress.'
6677# ifdef BBL_MODEL
6678 IF (aout(idubrs,ng)) WRITE (out,170) aout(idubrs,ng), &
6679 & 'Aout(idUbrs)', &
6680 & 'Write out averaged bottom U-current stress.'
6681 IF (aout(idvbrs,ng)) WRITE (out,170) aout(idvbrs,ng), &
6682 & 'Aout(idVbrs)', &
6683 & 'Write out averaged bottom V-current stress.'
6684 IF (aout(idubws,ng)) WRITE (out,170) aout(idubws,ng), &
6685 & 'Aout(idUbws)', &
6686 & 'Write out averaged wind-induced, bottom U-wave stress.'
6687 IF (aout(idvbws,ng)) WRITE (out,170) aout(idvbws,ng), &
6688 & 'Aout(idVbws)', &
6689 & 'Write out averaged wind-induced, bottom V-wave stress.'
6690 IF (aout(idubcs,ng)) WRITE (out,170) aout(idubcs,ng), &
6691 & 'Aout(idUbcs)', &
6692 & 'Write out averaged max wind+curr bottom U-wave stress.'
6693 IF (aout(idvbcs,ng)) WRITE (out,170) aout(idvbcs,ng), &
6694 & 'Aout(idVbcs)', &
6695 & 'Write out averaged max wind+curr bottom V-wave stress.'
6696 IF (aout(iduvwc,ng)) WRITE (out,170) aout(iduvwc,ng), &
6697 & 'Aout(idUVwc)', &
6698 & 'Write out averaged max wind+curr bottom UV-wave stress.'
6699 IF (aout(idubot,ng)) WRITE (out,170) aout(idubot,ng), &
6700 & 'Aout(idUbot)', &
6701 & 'Write out averaged bed wave orbital U-velocity.'
6702 IF (aout(idvbot,ng)) WRITE (out,170) aout(idvbot,ng), &
6703 & 'Aout(idVbot)', &
6704 & 'Write out averaged bed wave orbital V-velocity.'
6705 IF (aout(idubur,ng)) WRITE (out,170) aout(idubur,ng), &
6706 & 'Aout(idUbur)', &
6707 & 'Write out averaged bottom U-momentum above bed.'
6708 IF (aout(idvbvr,ng)) WRITE (out,170) aout(idvbvr,ng), &
6709 & 'Aout(idVbvr)', &
6710 & 'Write out averaged bottom V-momentum above bed.'
6711# endif
6712# if defined WEC
6713 IF (aout(idu2rs,ng)) WRITE (out,170) aout(idu2rs,ng), &
6714 & 'Aout(idU2rs)', &
6715 & 'Write out 2D barotropic wec u-stress.'
6716 IF (aout(idv2rs,ng)) WRITE (out,170) aout(idv2rs,ng), &
6717 & 'Aout(idV2rs)', &
6718 & 'Write out 2D barotropic wec v-stress.'
6719 IF (aout(idu2sd,ng)) WRITE (out,170) aout(idu2sd,ng), &
6720 & 'Aout(idU2Sd)', &
6721 & 'Write out 2D barotropic Stokes u-velocity.'
6722 IF (aout(idv2sd,ng)) WRITE (out,170) aout(idv2sd,ng), &
6723 & 'Aout(idV2Sd)', &
6724 & 'Write out 2D barotropic Stokes v-velocity.'
6725# endif
6726# ifdef SOLVE3D
6727# ifdef WEC
6728 IF (aout(idu3rs,ng)) WRITE (out,170) aout(idu3rs,ng), &
6729 & 'Aout(idU3rs)', &
6730 & 'Write out 3D total wec u-stress.'
6731 IF (aout(idv3rs,ng)) WRITE (out,170) aout(idv3rs,ng), &
6732 & 'Aout(idV3rs)', &
6733 & 'Write out 3D total wec v-stress.'
6734 IF (aout(idu3sd,ng)) WRITE (out,170) aout(idu3sd,ng), &
6735 & 'Aout(idU3Sd)', &
6736 & 'Write out 3D total wec Stokes u-velocity.'
6737 IF (aout(idv3sd,ng)) WRITE (out,170) aout(idv3sd,ng), &
6738 & 'Aout(idV3Sd)', &
6739 & 'Write out 3D total wec Stokes v-velocity.'
6740 IF (aout(idw3sd,ng)) WRITE (out,170) aout(idw3sd,ng), &
6741 & 'Aout(idW3Sd)', &
6742 & 'Write out 3D wec omega Stokes vertical velocity.'
6743 IF (aout(idw3st,ng)) WRITE (out,170) aout(idw3st,ng), &
6744 & 'Aout(idW3St)', &
6745 & 'Write out 3D wec Stokes vertical velocity.'
6746# endif
6747# ifdef WEC_VF
6748 IF (aout(idwztw,ng)) WRITE (out,170) aout(idwztw,ng), &
6749 & 'Aout(idWztw)', &
6750 & 'Write out wec quasi-static sea level adjustment.'
6751 IF (aout(idwqsp,ng)) WRITE (out,170) aout(idwqsp,ng), &
6752 & 'Aout(idWqsp)', &
6753 & 'Write out wec quasi-static sea pressure adjustment.'
6754 IF (aout(idwbeh,ng)) WRITE (out,170) aout(idwbeh,ng), &
6755 & 'Aout(idWbeh)', &
6756 & 'Write out wec Bernoulli head sea level adjustment.'
6757# endif
6758# endif
6759# if defined SOLVE3D && defined T_PASSIVE
6760 DO itrc=1,npt
6761 IF (aout(idtvar(inert(itrc)),ng)) WRITE (out,180) &
6762 & aout(idtvar(inert(itrc)),ng), 'Aout(inert)', &
6763 & 'Write out averaged inert passive tracer ', itrc, &
6764 & trim(vname(1,idtvar(inert(itrc))))
6765 END DO
6766# endif
6767# ifdef SOLVE3D
6768# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
6769 IF (aout(idpair,ng)) WRITE (out,170) aout(idpair,ng), &
6770 & 'Aout(idPair)', &
6771 & 'Write out averaged surface air pressure.'
6772# endif
6773# if defined BULK_FLUXES
6774 IF (aout(idtair,ng)) WRITE (out,170) aout(idtair,ng), &
6775 & 'Aout(idTair)', &
6776 & 'Write out averaged surface air temperature.'
6777# endif
6778# if defined BULK_FLUXES || defined ECOSIM
6779 IF (aout(iduair,ng)) WRITE (out,170) aout(iduair,ng), &
6780 & 'Aout(idUair)', &
6781 & 'Write out averaged surface U-wind component.'
6782 IF (aout(idvair,ng)) WRITE (out,170) aout(idvair,ng), &
6783 & 'Aout(idVair)', &
6784 & 'Write out averaged surface V-wind component.'
6785 IF (aout(iduaie,ng)) WRITE (out,170) aout(iduaie,ng), &
6786 & 'Aout(idUaiE)', &
6787 & 'Write out averaged Eastward surface U-wind component.'
6788 IF (aout(idvain,ng)) WRITE (out,170) aout(idvain,ng), &
6789 & 'Aout(idVaiN)', &
6790 & 'Write out averaged Northward surface V-wind component.'
6791# endif
6792 IF (aout(idtsur(itemp),ng)) WRITE (out,170) &
6793 & aout(idtsur(itemp),ng), 'Aout(idTsur)', &
6794 & 'Write out averaged surface net heat flux.'
6795# ifdef SALINITY
6796 IF (aout(idtsur(isalt),ng)) WRITE (out,170) &
6797 & aout(idtsur(isalt),ng), 'Aout(idTsur)', &
6798 & 'Write out averaged surface net salt flux.'
6799# endif
6800# ifdef SHORTWAVE
6801 IF (aout(idsrad,ng)) WRITE (out,170) aout(idsrad,ng), &
6802 & 'Aout(idSrad)', &
6803 & 'Write out averaged shortwave radiation flux.'
6804# endif
6805# ifdef BULK_FLUXES
6806 IF (aout(idlrad,ng)) WRITE (out,170) aout(idlrad,ng), &
6807 & 'Aout(idLrad)', &
6808 & 'Write out averaged longwave radiation flux.'
6809 IF (aout(idlhea,ng)) WRITE (out,170) aout(idlhea,ng), &
6810 & 'Aout(idLhea)', &
6811 & 'Write out averaged latent heat flux.'
6812 IF (aout(idshea,ng)) WRITE (out,170) aout(idshea,ng), &
6813 & 'Aout(idShea)', &
6814 & 'Write out averaged sensible heat flux.'
6815# ifdef EMINUSP
6816 IF (aout(idevap,ng)) WRITE (out,170) aout(idevap,ng), &
6817 & 'Aout(idevap)', &
6818 & 'Write out averaged evaporation rate.'
6819 IF (aout(idrain,ng)) WRITE (out,170) aout(idrain,ng), &
6820 & 'Aout(idrain)', &
6821 & 'Write out averaged rain rate.'
6822# endif
6823# endif
6824 IF (aout(iddano,ng)) WRITE (out,170) aout(iddano,ng), &
6825 & 'Aout(idDano)', &
6826 & 'Write out averaged density anomaly.'
6827# if defined LMD_MIXING || defined MY25_MIXING || defined GLS_MIXING
6828 IF (aout(idvvis,ng)) WRITE (out,170) aout(idvvis,ng), &
6829 & 'Aout(idVvis)', &
6830 & 'Write out averaged vertical viscosity: AKv.'
6831 IF (aout(idtdif,ng)) WRITE (out,170) aout(idtdif,ng), &
6832 & 'Aout(idTdif)', &
6833 & 'Write out averaged vertical diffusion: AKt(itemp).'
6834# ifdef SALINITY
6835 IF (aout(idsdif,ng)) WRITE (out,170) aout(idsdif,ng), &
6836 & 'Aout(idSdif)', &
6837 & 'Write out averaged vertical diffusion: AKt(isalt).'
6838# endif
6839# endif
6840# ifdef LMD_SKPP
6841 IF (aout(idhsbl,ng)) WRITE (out,170) aout(idhsbl,ng), &
6842 & 'Aout(idHsbl)', &
6843 & 'Write out averaged depth of surface boundary layer.'
6844# endif
6845# ifdef LMD_BKPP
6846 IF (aout(idhbbl,ng)) WRITE (out,170) aout(idhbbl,ng), &
6847 & 'Aout(idHbbl)', &
6848 & 'Write out averaged depth of bottom boundary layer.'
6849# endif
6850# endif
6851 IF (aout(id2drv,ng)) WRITE (out,170) aout(id2drv,ng), &
6852 & 'Aout(id2dRV)', &
6853 & 'Write out averaged 2D relative vorticity.'
6854 IF (aout(id2dpv,ng)) WRITE (out,170) aout(id2dpv,ng), &
6855 & 'Aout(id2dPV)', &
6856 & 'Write out averaged 2D potential vorticity.'
6857# ifdef SOLVE3D
6858 IF (aout(id3drv,ng)) WRITE (out,170) aout(id3drv,ng), &
6859 & 'Aout(id3dRV)', &
6860 & 'Write out averaged 3D relative vorticity.'
6861 IF (aout(id3dpv,ng)) WRITE (out,170) aout(id3dpv,ng), &
6862 & 'Aout(id3dPV)', &
6863 & 'Write out averaged 3D potential vorticity.'
6864# endif
6865 IF (aout(idzzav,ng)) WRITE (out,170) aout(idzzav,ng), &
6866 & 'Aout(idZZav)', &
6867 & 'Write out averaged quadratic <zeta*zeta> term.'
6868 IF (aout(idu2av,ng)) WRITE (out,170) aout(idu2av,ng), &
6869 & 'Aout(idU2av)', &
6870 & 'Write out averaged quadratic <ubar*ubar> term.'
6871 IF (aout(idv2av,ng)) WRITE (out,170) aout(idv2av,ng), &
6872 & 'Aout(idV2av)', &
6873 & 'Write out averaged quadratic <vbar*vbar> term.'
6874# ifdef SOLVE3D
6875 IF (aout(idhuav,ng)) WRITE (out,170) aout(idhuav,ng), &
6876 & 'Aout(idHUav)', &
6877 & 'Write out averaged u-volume flux, Huon.'
6878 IF (aout(idhvav,ng)) WRITE (out,170) aout(idhvav,ng), &
6879 & 'Aout(idHVav)', &
6880 & 'Write out averaged v-volume flux, Hvom.'
6881 IF (aout(iduuav,ng)) WRITE (out,170) aout(iduuav,ng), &
6882 & 'Aout(idUUav)', &
6883 & 'Write out averaged quadratic <u*u> term.'
6884 IF (aout(iduvav,ng)) WRITE (out,170) aout(iduvav,ng), &
6885 & 'Aout(idUVav)', &
6886 & 'Write out averaged quadratic <u*v> term.'
6887 IF (aout(idvvav,ng)) WRITE (out,170) aout(idvvav,ng), &
6888 & 'Aout(idVVav)', &
6889 & 'Write out averaged quadratic <v*v> term.'
6890 DO itrc=1,nat+npt
6891 IF (aout(idttav(itrc),ng)) WRITE (out,180) &
6892 & aout(idttav(itrc),ng), 'Aout(idTTav)', &
6893 & 'Write out averaged <t*t> for tracer ', itrc, &
6894 & trim(vname(1,idtvar(itrc)))
6895 END DO
6896 DO itrc=1,nat+npt
6897 IF (aout(idutav(itrc),ng)) WRITE (out,180) &
6898 & aout(idutav(itrc),ng), 'Aout(idUTav)', &
6899 & 'Write out averaged <u*t> for tracer ', itrc, &
6900 & trim(vname(1,idtvar(itrc)))
6901 END DO
6902 DO itrc=1,nat+npt
6903 IF (aout(idvtav(itrc),ng)) WRITE (out,180) &
6904 & aout(idvtav(itrc),ng), 'Aout(idVTav)', &
6905 & 'Write out averaged <v*t> for tracer ', itrc, &
6906 & trim(vname(1,idtvar(itrc)))
6907 END DO
6908 DO itrc=1,nat+npt
6909 IF (aout(ihutav(itrc),ng)) WRITE (out,180) &
6910 & aout(ihutav(itrc),ng), 'Aout(iHUTav)', &
6911 & 'Write out averaged <Huon*t> for tracer ', itrc, &
6912 & trim(vname(1,idtvar(itrc)))
6913 END DO
6914 DO itrc=1,nat+npt
6915 IF (aout(ihvtav(itrc),ng)) WRITE (out,180) &
6916 & aout(ihvtav(itrc),ng), 'Aout(iHVTav)', &
6917 & 'Write out averaged <Hvom*t> for tracer ', itrc, &
6918 & trim(vname(1,idtvar(itrc)))
6919 END DO
6920# endif
6921# if defined AVERAGES && defined AVERAGES_DETIDE && \
6922 (defined ssh_tides || defined uv_tides)
6923 WRITE (out,'(1x)')
6924 IF (aout(idfsud,ng)) WRITE (out,170) aout(idfsud,ng), &
6925 & 'Aout(idFsuD)', &
6926 & 'Write out detided free-surface.'
6927 IF (aout(idu2dd,ng)) WRITE (out,170) aout(idu2dd,ng), &
6928 & 'Aout(idu2dD)', &
6929 & 'Write out detided 2D U-velocity.'
6930 IF (aout(idv2dd,ng)) WRITE (out,170) aout(idv2dd,ng), &
6931 & 'Aout(idv2dD)', &
6932 & 'Write out detided 2D V-velocity.'
6933# ifdef SOLVE3D
6934 IF (aout(idu3dd,ng)) WRITE (out,170) aout(idu3dd,ng), &
6935 & 'Aout(idu3dD)', &
6936 & 'Write out detided 3D U-velocity.'
6937 IF (aout(idv3dd,ng)) WRITE (out,170) aout(idv3dd,ng), &
6938 & 'Aout(idv3dD)', &
6939 & 'Write out detided 3D V-velocity.'
6940 DO itrc=1,nat
6941 IF (aout(idtrcd(itrc),ng)) WRITE (out,180) &
6942 & aout(idtrcd(itrc),ng), 'Aout(idTrcD)', &
6943 & 'Write out detided tracer ', itrc, &
6944 & trim(vname(1,idtvar(itrc)))
6945 END DO
6946# endif
6947# endif
6948 END IF
6949#endif
6950#ifdef DIAGNOSTICS_UV
6951 IF ((ndia(ng).gt.0).and.any(dout(:,ng))) THEN
6952 WRITE (out,'(1x)')
6953 IF (dout(iddu2d(m2rate),ng).or.dout(iddv2d(m2rate),ng)) &
6954 & WRITE (out,170) .true., 'Dout(M2rate)', &
6955 & 'Write out 2D momentum acceleration.'
6956 IF (dout(iddu2d(m2pgrd),ng).or.dout(iddv2d(m2pgrd),ng)) &
6957 & WRITE (out,170) .true., 'Dout(M2pgrd)', &
6958 & 'Write out 2D momentum pressure gradient.'
6959# ifdef UV_COR
6960 IF (dout(iddu2d(m2fcor),ng).or.dout(iddv2d(m2fcor),ng)) &
6961 & WRITE (out,170) .true., 'Dout(M2fcor)', &
6962 & 'Write out 2D momentum Coriolis force.'
6963# endif
6964# ifdef UV_ADV
6965 IF (dout(iddu2d(m2hadv),ng).or.dout(iddv2d(m2hadv),ng)) &
6966 & WRITE (out,170) .true., 'Dout(M2hadv)', &
6967 & 'Write out 2D momentum horizontal advection.'
6968 IF (dout(iddu2d(m2xadv),ng).or.dout(iddv2d(m2xadv),ng)) &
6969 & WRITE (out,170) .true., 'Dout(M2xadv)', &
6970 & 'Write out 2D momentum horizontal X-advection.'
6971 IF (dout(iddu2d(m2yadv),ng).or.dout(iddv2d(m2yadv),ng)) &
6972 & WRITE (out,170) .true., 'Dout(M2yadv)', &
6973 & 'Write out 2D momentum horizontal Y-advection.'
6974# endif
6975# if defined UV_VIS2 || defined UV_VIS4
6976 IF (dout(iddu2d(m2hvis),ng).or.dout(iddv2d(m2hvis),ng)) &
6977 & WRITE (out,170) .true., 'Dout(M2hvis)', &
6978 & 'Write out 2D momentum horizontal viscosity.'
6979 IF (dout(iddu2d(m2xvis),ng).or.dout(iddv2d(m2xvis),ng)) &
6980 & WRITE (out,170) .true., 'Dout(M2xvis)', &
6981 & 'Write out 2D momentum horizontal X-viscosity.'
6982 IF (dout(iddu2d(m2yvis),ng).or.dout(iddv2d(m2yvis),ng)) &
6983 & WRITE (out,170) .true., 'Dout(M2yvis)', &
6984 & 'Write out 2D momentum horizontal Y-viscosity.'
6985# endif
6986 IF (dout(iddu2d(m2sstr),ng).or.dout(iddv2d(m2sstr),ng)) &
6987 & WRITE (out,170) .true., 'Dout(M2sstr)', &
6988 & 'Write out 2D momentum surface stress.'
6989 IF (dout(iddu2d(m2bstr),ng).or.dout(iddv2d(m2bstr),ng)) &
6990 & WRITE (out,170) .true., 'Dout(M2bstr)', &
6991 & 'Write out 2D momentum bottom stress.'
6992# ifdef WEC_VF
6993 IF (dout(iddu2d(m2hjvf),ng).or.dout(iddv2d(m2hjvf),ng)) &
6994 & WRITE (out,170) .true., 'Dout(M2hjvf)', &
6995 & 'Write out 2D horizontal J-vortex force.'
6996 IF (dout(iddu2d(m2kvrf),ng).or.dout(iddv2d(m2kvrf),ng)) &
6997 & WRITE (out,170) .true., 'Dout(M2kvrf)', &
6998 & 'Write out 2D K-vortex force. '
6999# ifdef UV_COR
7000 IF (dout(iddu2d(m2fsco),ng).or.dout(iddv2d(m2fsco),ng)) &
7001 & WRITE (out,170) .true., 'Dout(M2fsco)', &
7002 & 'Write out 2D Stokes Coriolis.'
7003# endif
7004# ifdef SURFACE_STREAMING
7005 IF (dout(iddu2d(m2sstm),ng).or.dout(iddv2d(m2sstm),ng)) &
7006 & WRITE (out,170) .true., 'Dout(M2sstm)', &
7007 & 'Write out 2D surface streaming.'
7008# endif
7009# ifdef BOTTOM_STREAMING
7010 IF (dout(iddu2d(m2bstm),ng).or.dout(iddv2d(m2bstm),ng)) &
7011 & WRITE (out,170) .true., 'Dout(M2bstm)', &
7012 & 'Write out 2D bottom streaming.'
7013# endif
7014 IF (dout(iddu2d(m2wrol),ng).or.dout(iddv2d(m2wrol),ng)) &
7015 & WRITE (out,170) .true., 'Dout(M2wrol)', &
7016 & 'Write out wave roller acceleration.'
7017 IF (dout(iddu2d(m2wbrk),ng).or.dout(iddv2d(m2wbrk),ng)) &
7018 & WRITE (out,170) .true., 'Dout(M2wbrk)', &
7019 & 'Write out 2D wave breaking.'
7020 IF (dout(iddu2d(m2zeta),ng).or.dout(iddv2d(m2zeta),ng)) &
7021 & WRITE (out,170) .true., 'Dout(M2zeta)', &
7022 & 'Write out 2D Eulerian sea level adjustment.'
7023 IF (dout(iddu2d(m2zetw),ng).or.dout(iddv2d(m2zetw),ng)) &
7024 & WRITE (out,170) .true., 'Dout(M2zetw)', &
7025 & 'Write out 2D quasi-static sea level adjustment.'
7026 IF (dout(iddu2d(m2zqsp),ng).or.dout(iddv2d(m2zqsp),ng)) &
7027 & WRITE (out,170) .true., 'Dout(M2zqsp)', &
7028 & 'Write out 2D quasi-static pressure adjustment.'
7029 IF (dout(iddu2d(m2zbeh),ng).or.dout(iddv2d(m2zbeh),ng)) &
7030 & WRITE (out,170) .true., 'Dout(M2zbeh)', &
7031 & 'Write out 2D Bernoulli head adjustment.'
7032# endif
7033# ifdef SOLVE3D
7034 WRITE (out,'(1x)')
7035 IF (dout(iddu3d(m3rate),ng).or.dout(iddv3d(m3rate),ng)) &
7036 & WRITE (out,170) .true., 'Dout(M3rate)', &
7037 & 'Write out 3D momentum acceleration.'
7038 IF (dout(iddu3d(m3pgrd),ng).or.dout(iddv3d(m3pgrd),ng)) &
7039 & WRITE (out,170) .true., 'Dout(M3pgrd)', &
7040 & 'Write out 3D momentum pressure gradient.'
7041# ifdef UV_COR
7042 IF (dout(iddu3d(m3fcor),ng).or.dout(iddv3d(m3fcor),ng)) &
7043 & WRITE (out,170) .true., 'Dout(M3fcor)', &
7044 & 'Write out 3D momentum Coriolis force.'
7045# endif
7046# ifdef UV_ADV
7047 IF (dout(iddu3d(m3hadv),ng).or.dout(iddv3d(m3hadv),ng)) &
7048 & WRITE (out,170) .true., 'Dout(M3hadv)', &
7049 & 'Write out 3D momentum horizontal advection.'
7050 IF (dout(iddu3d(m3xadv),ng).or.dout(iddv3d(m3xadv),ng)) &
7051 & WRITE (out,170) .true., 'Dout(M3xadv)', &
7052 & 'Write out 3D momentum horizontal X-advection.'
7053 IF (dout(iddu3d(m3yadv),ng).or.dout(iddv3d(m3yadv),ng)) &
7054 & WRITE (out,170) .true., 'Dout(M3yadv)', &
7055 & 'Write out 3D momentum horizontal Y-advection.'
7056 IF (dout(iddu3d(m3vadv),ng).or.dout(iddv3d(m3vadv),ng)) &
7057 & WRITE (out,170) .true., 'Dout(M3vadv)', &
7058 & 'Write out 3D momentum vertical advection.'
7059# endif
7060# if defined UV_VIS2 || defined UV_VIS4
7061 IF (dout(iddu3d(m3hvis),ng).or.dout(iddv3d(m3hvis),ng)) &
7062 & WRITE (out,170) .true., 'Dout(M3hvis)', &
7063 & 'Write out 3D momentum horizontal viscosity.'
7064 IF (dout(iddu3d(m3xvis),ng).or.dout(iddv3d(m3xvis),ng)) &
7065 & WRITE (out,170) .true., 'Dout(M3xvis)', &
7066 & 'Write out 3D momentum horizontal X-viscosity.'
7067 IF (dout(iddu3d(m3yvis),ng).or.dout(iddv3d(m3yvis),ng)) &
7068 & WRITE (out,170) .true., 'Dout(M3yvis)', &
7069 & 'Write out 3D momentum horizontal Y-viscosity.'
7070# endif
7071 IF (dout(iddu3d(m3vvis),ng).or.dout(iddv3d(m3vvis),ng)) &
7072 & WRITE (out,170) .true., 'Dout(M3vvis)', &
7073 & 'Write out 3D momentum vertical viscosity.'
7074# endif
7075# ifdef WEC_VF
7076 IF (dout(iddu3d(m3hjvf),ng).or.dout(iddv3d(m3hjvf),ng)) &
7077 & WRITE (out,170) .true., 'Dout(M3hjvf)', &
7078 & 'Write out 3D horizontal J-vortex force.'
7079 IF (dout(iddu3d(m3vjvf),ng).or.dout(iddv3d(m3vjvf),ng)) &
7080 & WRITE (out,170) .true., 'Dout(M3vjvf)', &
7081 & 'Write out 3D vertical J-vortex force.'
7082 IF (dout(iddu3d(m3kvrf),ng).or.dout(iddv3d(m3kvrf),ng)) &
7083 & WRITE (out,170) .true., 'Dout(M3kvrf)', &
7084 & 'Write out 3D K-vortex force.'
7085# ifdef UV_COR
7086 IF (dout(iddu3d(m3fsco),ng).or.dout(iddv3d(m3fsco),ng)) &
7087 & WRITE (out,170) .true., 'Dout(M3fsco)', &
7088 & 'Write out 3D Stokes Coriolis'
7089# endif
7090# ifdef SURFACE_STREAMING
7091 IF (dout(iddu3d(m3sstm),ng).or.dout(iddv3d(m3sstm),ng)) &
7092 & WRITE (out,170) .true., 'Dout(M3sstm)', &
7093 & 'Write out 3D surface streaming.'
7094# endif
7095# ifdef BOTTOM_STREAMING
7096 IF (dout(iddu3d(m3bstm),ng).or.dout(iddv3d(m3bstm),ng)) &
7097 & WRITE (out,170) .true., 'Dout(M3bstm)', &
7098 & 'Write out 3D bottom streaming.'
7099# endif
7100 IF (dout(iddu3d(m3wrol),ng).or.dout(iddv3d(m3wrol),ng)) &
7101 & WRITE (out,170) .true., 'Dout(M3wrol)', &
7102 & 'Write out 3D wave roller acceleration.'
7103 IF (dout(iddu3d(m3wbrk),ng).or.dout(iddv3d(m3wbrk),ng)) &
7104 & WRITE (out,170) .true., 'Dout(M3wbrk)', &
7105 & 'Write out 3D wave breaking.'
7106# endif
7107 END IF
7108#endif
7109#if defined DIAGNOSTICS_TS && defined SOLVE3D
7110 IF (ndia(ng).gt.0) THEN
7111 WRITE (out,'(1x)')
7112 DO itrc=1,nat
7113 IF (dout(iddtrc(itrc,itrate),ng)) &
7114 & WRITE (out,180) .true., 'Dout(iTrate)', &
7115 & 'Write out rate of change of tracer ', itrc, &
7116 & trim(vname(1,idtvar(itrc)))
7117 END DO
7118# ifdef T_PASSIVE
7119 DO i=1,npt
7120 itrc=inert(i)
7121 IF (dout(iddtrc(itrc,itrate),ng)) &
7122 & WRITE (out,180) .true., 'Dout(iTrate)', &
7123 & 'Write out rate of change of tracer ', itrc, &
7124 & trim(vname(1,idtvar(itrc)))
7125 END DO
7126# endif
7127 DO itrc=1,nat
7128 IF (dout(iddtrc(itrc,ithadv),ng)) &
7129 & WRITE (out,180) .true., 'Dout(iThadv)', &
7130 & 'Write out horizontal advection, tracer ', itrc, &
7131 & trim(vname(1,idtvar(itrc)))
7132 END DO
7133# ifdef T_PASSIVE
7134 DO i=1,npt
7135 itrc=inert(i)
7136 IF (dout(iddtrc(itrc,ithadv),ng)) &
7137 & WRITE (out,180) .true., 'Dout(iThadv)', &
7138 & 'Write out horizontal advection, tracer ', itrc, &
7139 & trim(vname(1,idtvar(itrc)))
7140 END DO
7141# endif
7142 DO itrc=1,nat
7143 IF (dout(iddtrc(itrc,itxadv),ng)) &
7144 & WRITE (out,180) .true., 'Dout(iTxadv)', &
7145 & 'Write out horizontal X-advection, tracer ', itrc, &
7146 & trim(vname(1,idtvar(itrc)))
7147 END DO
7148# ifdef T_PASSIVE
7149 DO i=1,npt
7150 itrc=inert(i)
7151 IF (dout(iddtrc(itrc,itxadv),ng)) &
7152 & WRITE (out,180) .true., 'Dout(iTxadv)', &
7153 & 'Write out horizontal X-advection, tracer ', itrc, &
7154 & trim(vname(1,idtvar(itrc)))
7155 END DO
7156# endif
7157 DO itrc=1,nat
7158 IF (dout(iddtrc(itrc,ityadv),ng)) &
7159 & WRITE (out,180) .true., 'Dout(iTyadv)', &
7160 & 'Write out horizontal Y-advection, tracer ', itrc, &
7161 & trim(vname(1,idtvar(itrc)))
7162 END DO
7163# ifdef T_PASSIVE
7164 DO i=1,npt
7165 itrc=inert(i)
7166 IF (dout(iddtrc(itrc,ityadv),ng)) &
7167 & WRITE (out,180) .true., 'Dout(iTyadv)', &
7168 & 'Write out horizontal Y-advection, tracer ', itrc, &
7169 & trim(vname(1,idtvar(itrc)))
7170 END DO
7171# endif
7172 DO itrc=1,nat
7173 IF (dout(iddtrc(itrc,itvadv),ng)) &
7174 & WRITE (out,180) .true., 'Dout(iTvadv)', &
7175 & 'Write out vertical advection, tracer ', itrc, &
7176 & trim(vname(1,idtvar(itrc)))
7177 END DO
7178# ifdef T_PASSIVE
7179 DO i=1,npt
7180 itrc=inert(i)
7181 IF (dout(iddtrc(itrc,itvadv),ng)) &
7182 & WRITE (out,180) .true., 'Dout(iTvadv)', &
7183 & 'Write out vertical advection, tracer ', itrc, &
7184 & trim(vname(1,idtvar(itrc)))
7185 END DO
7186# endif
7187# if defined TS_DIF2 || defined TS_DIF4
7188 DO itrc=1,nat
7189 IF (dout(iddtrc(itrc,ithdif),ng)) &
7190 & WRITE (out,180) .true., 'Dout(iThdif)', &
7191 & 'Write out horizontal diffusion, tracer ', itrc, &
7192 & trim(vname(1,idtvar(itrc)))
7193 END DO
7194# ifdef T_PASSIVE
7195 DO i=1,npt
7196 itrc=inert(i)
7197 IF (dout(iddtrc(itrc,ithdif),ng)) &
7198 & WRITE (out,180) .true., 'Dout(iThdif)', &
7199 & 'Write out horizontal diffusion, tracer ', itrc, &
7200 & trim(vname(1,idtvar(itrc)))
7201 END DO
7202# endif
7203 DO itrc=1,nat
7204 IF (dout(iddtrc(itrc,itxdif),ng)) &
7205 & WRITE (out,180) .true., 'Dout(iTxdif)', &
7206 & 'Write out horizontal X-diffusion, tracer ', itrc, &
7207 & trim(vname(1,idtvar(itrc)))
7208 END DO
7209# ifdef T_PASSIVE
7210 DO i=1,npt
7211 itrc=inert(i)
7212 IF (dout(iddtrc(i,itxdif),ng)) &
7213 & WRITE (out,180) .true., 'Dout(iTxdif)', &
7214 & 'Write out horizontal X-diffusion, tracer ', itrc, &
7215 & trim(vname(1,idtvar(itrc)))
7216 END DO
7217# endif
7218 DO itrc=1,nat
7219 IF (dout(iddtrc(itrc,itydif),ng)) &
7220 & WRITE (out,180) .true., 'Dout(iTydif)', &
7221 & 'Write out horizontal Y-diffusion , tracer ', itrc, &
7222 & trim(vname(1,idtvar(itrc)))
7223 END DO
7224# ifdef T_PASSIVE
7225 DO i=1,npt
7226 itrc=inert(i)
7227 IF (dout(iddtrc(itrc,itydif),ng)) &
7228 & WRITE (out,180) .true., 'Dout(iTydif)', &
7229 & 'Write out horizontal Y-diffusion, tracer ', itrc, &
7230 & trim(vname(1,idtvar(itrc)))
7231 END DO
7232# endif
7233# if defined MIX_GEO_TS || defined MIX_ISO_TS
7234 DO itrc=1,nat
7235 IF (dout(iddtrc(itrc,itsdif),ng)) &
7236 & WRITE (out,180) .true., 'Dout(iTsdif)', &
7237 & 'Write out horizontal S-diffusion, tracer ', itrc, &
7238 & trim(vname(1,idtvar(itrc)))
7239 END DO
7240# ifdef T_PASSIVE
7241 DO i=1,npt
7242 itrc=inert(i)
7243 IF (dout(iddtrc(itrc,itsdif),ng)) &
7244 & WRITE (out,180) .true., 'Dout(iTsdif)', &
7245 & 'Write out horizontal S-diffusion, tracer ', itrc, &
7246 & trim(vname(1,idtvar(itrc)))
7247 END DO
7248# endif
7249# endif
7250# endif
7251 DO itrc=1,nat
7252 IF (dout(iddtrc(itrc,itvdif),ng)) &
7253 & WRITE (out,180) .true., 'Dout(iTvdif)', &
7254 & 'Write out vertical diffusion, tracer ', itrc, &
7255 & trim(vname(1,idtvar(itrc)))
7256 END DO
7257# ifdef T_PASSIVE
7258 DO i=1,npt
7259 itrc=inert(i)
7260 IF (dout(iddtrc(itrc,itvdif),ng)) &
7261 & WRITE (out,180) .true., 'Dout(iTvdif)', &
7262 & 'Write out vertical diffusion, tracer ', itrc, &
7263 & trim(vname(1,idtvar(itrc)))
7264 END DO
7265# endif
7266 END IF
7267#endif
7268
7269#ifdef GRID_EXTRACT
7270 WRITE (out,'(1x)')
7271 WRITE (out,120) extractflag(ng), 'ExtractFlag', &
7272 & 'Field extraction flag to interpolate or decimate.'
7273#endif
7274 WRITE (out,'(1x)')
7275 IF (inp_lib.eq.io_nf90) THEN
7276 WRITE (out,120) inp_lib, 'inp_lib', &
7277 & 'Using standard NetCDF library for input files.'
7278#if defined PIO_LIB && defined DISTRIBUTE
7279 ELSE IF (inp_lib.eq.io_pio) THEN
7280 WRITE (out,120) inp_lib, 'inp_lib', &
7281 & 'Using Parallel-IO (PIO) library for input files.'
7282#endif
7283 END IF
7284 IF (out_lib.eq.io_nf90) THEN
7285 WRITE (out,120) out_lib, 'out_lib', &
7286 & 'Using standard NetCDF library for output files.'
7287#if defined PIO_LIB && defined DISTRIBUTE
7288 ELSE IF (inp_lib.eq.io_pio) THEN
7289 WRITE (out,120) out_lib, 'out_lib', &
7290 & 'Using Parallel-IO (PIO) library for output files.'
7291#endif
7292 END IF
7293#if defined PIO_LIB && defined DISTRIBUTE
7294 SELECT CASE (pio_method)
7295 CASE (0)
7296 text='Parallel read and write of PnetCDF files (CDF-5).'
7297 CASE (pio_iotype_pnetcdf)
7298 text='Parallel read and write of PnetCDF files (NetCDF3).'
7299 CASE (pio_iotype_netcdf)
7300 text='Serial read and write of NetCDF3 files.'
7301 CASE (pio_iotype_netcdf4c)
7302 text='Parallel read and serial write of compressed '// &
7303 & 'NetCDF4 (HDF5) files.'
7304 CASE (pio_iotype_netcdf4p)
7305 text='Parallel read and write of NETCDF4 (HDF5) files.'
7306 END SELECT
7307
7308 WRITE (out,120) pio_method, 'pio_method', trim(text)
7309
7310 WRITE (out,120) pio_numiotasks, 'pio_NumIOtasks', &
7311 & 'Number of mpi-processors used for I/O.'
7312
7313 WRITE (out,120) pio_stride, 'pio_stride', &
7314 & 'Stride step in the mpi-rank between I/O tasks.'
7315
7316 WRITE (out,120) pio_base, 'pio_base', &
7317 & 'Offset for the first I/O task.'
7318
7319 WRITE (out,120) pio_aggregator, 'pio_aggregator', &
7320 & 'Number of mpi-aggregators for intra-communications.'
7321
7322 SELECT CASE (pio_rearranger)
7323 CASE (pio_rearr_box)
7324 text='Box rearrangement method.'
7325 CASE (pio_rearr_subset)
7326 text='Subset rearrangement method.'
7327 END SELECT
7328 WRITE (out,120) pio_rearranger, 'pio_rearranger', trim(text)
7329
7330 SELECT CASE (pio_rearr_comm)
7331 CASE (pio_rearr_comm_p2p)
7332 text='Point-to-Point rearranger communications.'
7333 CASE (pio_rearr_comm_coll)
7334 text='Collective rearranger communications.'
7335 END SELECT
7336 WRITE (out,120) pio_rearr_comm, 'pio_rearr_comm', trim(text)
7337
7338 SELECT CASE (pio_rearr_fcd)
7339 CASE (pio_rearr_comm_fc_2d_enable)
7340 text='Enabled C2I flow control, and vice versa.'
7341 CASE (pio_rearr_comm_fc_1d_comp2io)
7342 text='Enabled C2I flow control only.'
7343 CASE (pio_rearr_comm_fc_1d_io2comp)
7344 text='Enabled I2C flow control only.'
7345 CASE (pio_rearr_comm_fc_2d_disable)
7346 text='Disabled flow control'
7347 END SELECT
7348 WRITE (out,120) pio_rearr_fcd, 'pio_rearr_fcd', trim(text)
7349
7350 WRITE (out,170) pio_rearr_c2i_hs, 'pio_rearr_C2I_HS', &
7351 & 'Enabled C2I rearranger handshake.'
7352 WRITE (out,170) pio_rearr_i2c_hs, 'pio_rearr_I2C_HS', &
7353 & 'Enabled I2C rearranger handshake.'
7354
7355 WRITE (out,170) pio_rearr_c2i_is, 'pio_rearr_C2I_iS', &
7356 & 'Enabled C2I rearranger mpi-Isends.'
7357 WRITE (out,170) pio_rearr_i2c_is, 'pio_rearr_I2C_iS', &
7358 & 'Enabled I2C rearranger mpi-Isends.'
7359
7360 WRITE (out,120) pio_rearr_c2i_pr, 'pio_rearr_C2I_PR', &
7361 & 'Maximum C2I rearranger pending requests.'
7362 WRITE (out,120) pio_rearr_i2c_pr, 'pio_rearr_I2C_PR', &
7363 & 'Maximum I2C rearranger pending requests.'
7364#endif
7365#if defined HDF5 && defined DEFLATE
7366 WRITE (out,120) shuffle, 'shuffle', &
7367 & 'NetCDF-4/HDF5 file format shuffle filer flag.'
7368 WRITE (out,120) deflate, 'deflate', &
7369 & 'NetCDF-4/HDF5 file format deflate filer flag.'
7370 WRITE (out,120) deflate_level, 'deflate_level', &
7371 & 'NetCDF-4/HDF5 file format deflate level parameter.'
7372#endif
7373 END DO
7374 END IF
7375!
7376!-----------------------------------------------------------------------
7377! Report output/input files and check availability of input files.
7378!-----------------------------------------------------------------------
7379!
7380 DO ng=1,ngrids
7381 IF (master.and.lwrite) THEN
7382 WRITE (out,220)
7383#if !defined CORRELATION
7384# if defined FOUR_DVAR || defined ENKF_RESTART
7385 WRITE (out,230) ' Output DA Initial/Restart File: ', &
7386 & trim(dai(ng)%name)
7387# endif
7388# ifdef PROPAGATOR
7389 WRITE (out,230) ' Output GST Restart File: ', &
7390 & trim(gst(ng)%name)
7391# endif
7392 WRITE (out,230) ' Output Restart File: ', &
7393 & trim(rst(ng)%name)
7394 IF (ldefhis(ng)) THEN
7395 IF (ndefhis(ng).eq.0) THEN
7396 WRITE (out,230) ' Output History File: ', &
7397 & trim(his(ng)%name)
7398 ELSE
7399 WRITE (out,230) ' Prefix for History Files: ', &
7400 & trim(his(ng)%head)
7401 END IF
7402 END IF
7403# ifdef GRID_EXTRACT
7404 IF (ldefxtr(ng)) THEN
7405 IF (ndefxtr(ng).eq.0) THEN
7406 WRITE (out,230) ' Output History Extract File: ', &
7407 & trim(xtr(ng)%name)
7408 ELSE
7409 WRITE (out,230) 'Prefix for History Extract Files: ', &
7410 & trim(xtr(ng)%head)
7411 END IF
7412 END IF
7413# endif
7414# ifdef TANGENT
7415 IF (ndeftlm(ng).eq.0) THEN
7416 WRITE (out,230) ' Output Tangent File: ', &
7417 & trim(tlm(ng)%name)
7418 ELSE
7419 WRITE (out,230) ' Prefix for Tangent Files: ', &
7420 & trim(tlm(ng)%head)
7421 END IF
7422# endif
7423# ifdef WEAK_CONSTRAINT
7424 WRITE (out,230) ' Output Impulse Forcing File: ', &
7425 & trim(tlf(ng)%name)
7426# endif
7427#endif
7428#ifdef ADJOINT
7429 IF (ndefadj(ng).eq.0) THEN
7430 WRITE (out,230) ' Output Adjoint File: ', &
7431 & trim(adm(ng)%name)
7432 ELSE
7433 WRITE (out,230) ' Prefix for Adjoint Files: ', &
7434 & trim(adm(ng)%head)
7435 END IF
7436#endif
7437#if !defined CORRELATION
7438# if defined FORWARD_WRITE && !defined FOUR_DVAR
7439 WRITE (out,230) ' Output Forward State File: ', &
7440 & trim(fwd(ng)%name)
7441# endif
7442# if defined AVERAGES || \
7443 (defined ad_averages && defined adjoint) || \
7444 (defined rp_averages && defined tl_ioms) || \
7445 (defined tl_averages && defined tangent)
7446 IF (ndefavg(ng).eq.0) THEN
7447 WRITE (out,230) ' Output Averages File: ', &
7448 & trim(avg(ng)%name)
7449 ELSE
7450 WRITE (out,230) ' Prefix for Averages Files: ', &
7451 & trim(avg(ng)%head)
7452 END IF
7453# endif
7454# if defined AVERAGES && defined AVERAGES_DETIDE && \
7455 (defined ssh_tides || defined uv_tides)
7456 WRITE (out,230) ' Output Detiding Harmonics File: ', &
7457 & trim(har(ng)%name)
7458# endif
7459# ifdef DIAGNOSTICS
7460 IF (ndefdia(ng).eq.0) THEN
7461 WRITE (out,230) ' Output Diagnostics File: ', &
7462 & trim(dia(ng)%name)
7463 ELSE
7464 WRITE (out,230) ' Prefix for Diagnostics Files: ', &
7465 & trim(dia(ng)%head)
7466 END IF
7467# endif
7468# ifdef STATIONS
7469 WRITE (out,230) ' Output Stations File: ', &
7470 & trim(sta(ng)%name)
7471# endif
7472# ifdef FLOATS
7473 WRITE (out,230) ' Output Floats File: ', &
7474 & trim(flt(ng)%name)
7475# endif
7476# ifdef MODEL_COUPLING
7477 WRITE (out,230) ' Physical parameters File: ', &
7478 & trim(iname)
7479# endif
7480#endif
7481 END IF
7482#ifdef GRID_EXTRACT
7483 fname=grx(ng)%name
7484 IF (.not.find_file(ng, out, fname, 'GRXNAME')) THEN
7485 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7486 ELSE
7487 IF (master.and.lwrite) WRITE (out,230) &
7488 & ' Input History Extract Grid File: ', trim(fname)
7489 END IF
7490#endif
7491#ifndef ANA_GRID
7492 fname=grd(ng)%name
7493 IF (.not.find_file(ng, out, fname, 'GRDNAME')) THEN
7494 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7495 ELSE
7496 IF (master.and.lwrite) WRITE (out,230) &
7497 & ' Input Grid File: ', trim(fname)
7498 END IF
7499#endif
7500#if !defined CORRELATION
7501# ifdef NESTING
7502 fname=ngcname
7503 IF (.not.find_file(ng, out, fname, 'NGCNAME')) THEN
7504 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7505 ELSE
7506 IF (master.and.lwrite) WRITE (out,230) &
7507 & ' Nesting grid connectivity File: ', trim(fname)
7508 END IF
7509# endif
7510#endif
7511#ifdef INI_FILE
7512# ifdef NONLINEAR
7513 fname=ini(ng)%name
7514 IF (.not.find_file(ng, out, fname, 'ININAME')) THEN
7515 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7516 ELSE
7517 IF (master.and.lwrite) WRITE (out,230) &
7518 ' Input Nonlinear Initial File: ', trim(fname)
7519 END IF
7520# endif
7521# if !defined CORRELATION
7522# if defined TANGENT && \
7523 !(defined FOUR_DVAR || defined I4DVAR_ANA_SENSITIVITY || \
7524 defined jedi || defined opt_observations || \
7525 defined sanity_check || defined sensitivity_4dvar || \
7526 defined tlm_check)
7527 fname=itl(ng)%name
7528 IF (.not.find_file(ng, out, fname, 'ITLNAME')) THEN
7529 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7530 ELSE
7531 IF (master.and.lwrite) WRITE (out,230) &
7532 & ' Input Tangent Initial File: ', trim(fname)
7533 END IF
7534# endif
7535# if defined WEAK_CONSTRAINT && \
7536 !(defined RBL4DVAR || \
7537 defined rbl4dvar_ana_sensitivity || \
7538 defined rbl4dvar_fct_sensitivity || \
7539 defined r_symmetry || \
7540 defined sp4dvar)
7541 fname=irp(ng)%name
7542 IF (.not.find_file(ng, out, fname, 'IRPNAME')) THEN
7543 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7544 ELSE
7545 IF (master.and.lwrite) WRITE (out,230) &
7546 & ' Input Representer Initial File: ', trim(fname)
7547 END IF
7548# endif
7549# if defined ADJOINT && \
7550 !(defined AD_SENSITIVITY || defined FOUR_DVAR || \
7551 defined i4dvar_ana_sensitivity || defined forcing_sv || \
7552 defined opt_observations || defined opt_perturbation || \
7553 defined sanity_check || defined sensitivity_4dvar || \
7554 defined so_semi || defined stochastic_opt || \
7555 defined hessian_sv || defined hessian_so || \
7556 defined hessian_fsv || defined jedi)
7557 fname=iad(ng)%name
7558 IF (.not.find_file(ng, out, fname, 'IADNAME')) THEN
7559 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7560 ELSE
7561 IF (master.and.lwrite) WRITE (out,230) &
7562 & ' Input Adjoint Initial File: ', trim(fname)
7563 END IF
7564# endif
7565# endif
7566#endif
7567#if !defined CORRELATION
7568# ifndef ANA_PSOURCE
7569 IF (luvsrc(ng).or.lwsrc(ng).or.(any(ltracersrc(:,ng)))) THEN
7570 fname=ssf(ng)%name
7571 IF (.not.find_file(ng, out, fname, 'SSFNAME')) THEN
7572 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7573 ELSE
7574 IF (master.and.lwrite) WRITE (out,230) &
7575 & ' Input Sources/Sinks File: ', trim(fname)
7576 END IF
7577 END IF
7578# endif
7579# if defined SSH_TIDES || defined UV_TIDES
7580 IF (ng.eq.1) THEN ! only tidal forcing on grid 1
7581 fname=tide(ng)%name
7582 IF (.not.find_file(ng, out, fname, 'TIDENAME')) THEN
7583 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7584 ELSE
7585 IF (master.and.lwrite) WRITE (out,230) &
7586 & ' Tidal Forcing File: ', trim(fname)
7587 END IF
7588 END IF
7589# endif
7590# ifdef FRC_FILE
7591 DO i=1,nffiles(ng)
7592 DO ifile=1,frc(i,ng)%Nfiles
7593 fname=frc(i,ng)%files(ifile)
7594 IF (.not.find_file(ng, out, fname, 'FRCNAME')) THEN
7595 IF (founderror(exit_flag, noerror, __line__, myfile)) &
7596 & RETURN
7597 ELSE
7598 IF (ifile.eq.1) THEN
7599 IF (master.and.lwrite) WRITE (out,310) &
7600 & ' Input Forcing File ', i,': ', trim(fname)
7601 ELSE
7602 IF (master.and.lwrite) WRITE (out,'(37x,a)') trim(fname)
7603 END IF
7604 END IF
7605 END DO
7606 END DO
7607# endif
7608 DO i=1,nclmfiles(ng)
7609 IF (clm_file(ng)) THEN
7610 DO ifile=1,clm(i,ng)%Nfiles
7611 fname=clm(i,ng)%files(ifile)
7612 IF (.not.find_file(ng, out, fname, 'CLMNAME')) THEN
7613 IF (founderror(exit_flag, noerror, __line__, myfile)) &
7614 & RETURN
7615 ELSE
7616 IF (ifile.eq.1) THEN
7617 IF (master.and.lwrite) WRITE (out,310) &
7618 & ' Input Climatology File ',i,': ',trim(fname)
7619 ELSE
7620 IF (master.and.lwrite) WRITE (out,'(37x,a)') &
7621 & trim(fname)
7622 END IF
7623 END IF
7624 END DO
7625 END IF
7626 END DO
7627# ifndef ANA_NUDGCOEF
7628 IF (lnudgem2clm(ng).or.lnudgem3clm(ng).or. &
7629 & (any(lnudgetclm(:,ng)))) THEN
7630 fname=nud(ng)%name
7631 IF (.not.find_file(ng, out, fname, 'NUDNAME')) THEN
7632 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7633 ELSE
7634 IF (master.and.lwrite) WRITE (out,230) &
7635 & ' Input Nudge Coefficients File: ', trim(fname)
7636 END IF
7637 END IF
7638# endif
7639# if defined FORWARD_READ && \
7640 !(defined FOUR_DVAR || defined JEDI || defined PICARD_TEST)
7641 DO ifile=1,fwd(ng)%Nfiles
7642 fname=fwd(ng)%files(ifile)
7643 IF (.not.find_file(ng, out, fname, 'FWDNAME')) THEN
7644 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7645 ELSE
7646 IF (ifile.eq.1) THEN
7647 IF (master.and.lwrite) WRITE (out,230) &
7648 & ' Input Forward State File: ', trim(fname)
7649 ELSE
7650 WRITE (out,'(37x,a)') trim(fname)
7651 END IF
7652 END IF
7653 END DO
7654# endif
7655# if defined AD_SENSITIVITY || defined I4DVAR_ANA_SENSITIVITY || \
7656 defined opt_observations || defined sensitivity_4dvar || \
7657 defined so_semi
7658# ifndef OBS_SPACE
7659 fname=ads(ng)%name
7660 IF (.not.find_file(ng, out, fname, 'ADSNAME')) THEN
7661 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7662 ELSE
7663 IF (master.and.lwrite) WRITE (out,230) &
7664 & ' Input Adjoint Sensitivity File: ', trim(fname)
7665 END IF
7666# endif
7667# endif
7668!
7669 IF (obcdata(ng)) THEN
7670 DO i=1,nbcfiles(ng)
7671 DO ifile=1,bry(i,ng)%Nfiles
7672 fname=bry(i,ng)%files(ifile)
7673 IF (.not.find_file(ng, out, fname, 'BRYNAME')) THEN
7674 IF (founderror(exit_flag, noerror, __line__, myfile)) &
7675 & RETURN
7676 ELSE
7677 IF (ifile.eq.1) THEN
7678 IF (master.and.lwrite) WRITE (out,310) &
7679 & ' Input Lateral Boundary File ', i, ': ', &
7680 & trim(fname)
7681 ELSE
7682 IF (master.and.lwrite) WRITE (out,'(37x,a)') &
7683 & trim(fname)
7684 END IF
7685 END IF
7686 END DO
7687 END DO
7688 END IF
7689# ifdef STATIONS
7690 fname=sposnam
7691 IF (.not.find_file(ng, out, fname, 'SPOSNAM')) THEN
7692 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7693 ELSE
7694 IF (master.and.lwrite) WRITE (out,230) &
7695 & ' Station positions File: ', trim(fname)
7696 END IF
7697# endif
7698#endif
7699#ifdef FOUR_DVAR
7700 fname=aparnam
7701 IF (.not.find_file(ng, out, fname, 'APARNAM')) THEN
7702 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7703 ELSE
7704 IF (master.and.lwrite) WRITE (out,230) &
7705 & ' Assimilation Parameters File: ', trim(fname)
7706 END IF
7707#endif
7708#if !defined CORRELATION
7709# ifdef FLOATS
7710 fname=fposnam
7711 IF (.not.find_file(ng, out, fname, 'FPOSNAM')) THEN
7712 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7713 ELSE
7714 IF (master.and.lwrite) WRITE (out,230) &
7715 & ' Initial Floats Positions File: ', trim(fname)
7716 END IF
7717# endif
7718# ifdef ICE_MODEL
7719 fname=iparnam
7720 IF (.not.find_file(ng, out, fname, 'IPARNAM')) THEN
7721 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7722 ELSE
7723 IF (master.and.lwrite) WRITE (out,230) &
7724 & ' Ice Model Parameters File: ', trim(fname)
7725 END IF
7726# endif
7727# ifdef BIOLOGY
7728 fname=bparnam
7729 IF (.not.find_file(ng, out, fname, 'BPARNAM')) THEN
7730 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7731 ELSE
7732 IF (master.and.lwrite) WRITE (out,230) &
7733 & ' Biology Parameters File: ', trim(fname)
7734 END IF
7735# endif
7736#endif
7737 fname=varname
7738 IF (.not.find_file(ng, out, fname, 'VARNAME')) THEN
7739 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
7740 ELSE
7741 IF (master.and.lwrite) WRITE (out,230) &
7742 & 'ROMS I/O variables Metadata File: ', trim(fname)
7743 END IF
7744 END DO
7745 IF (nuser.gt.0) THEN
7746 IF (master.and.lwrite) WRITE (out,230) &
7747 & ' Input/Output USER File: ', trim(usrname)
7748 END IF
7749!
7750!-----------------------------------------------------------------------
7751! Report generic USER parameters.
7752!-----------------------------------------------------------------------
7753!
7754 IF (nuser.gt.0) THEN
7755 IF (master.and.lwrite) THEN
7756 WRITE (out,240)
7757 DO i=1,nuser
7758 WRITE (out,250) user(i), i, i
7759 END DO
7760 END IF
7761 END IF
7762
7763#if !defined ANA_TIDES && \
7764 (defined tide_generating_forces || \
7765 defined ssh_tides || defined uv_tides)
7766!
7767!-----------------------------------------------------------------------
7768! Check and report tidal reference date for zero phase.
7769!-----------------------------------------------------------------------
7770!
7771 DO ng=1,ngrids
7772 CALL tides_date (ng)
7773 END DO
7774#endif
7775
7776#if defined WEAK_CONSTRAINT && \
7777 (defined posterior_eofs || defined posterior_error_f || \
7778 defined posterior_error_i)
7779!
7780!-----------------------------------------------------------------------
7781! If weak constraint and estimating posterior analysis error
7782! covariance matrix, stop it using Nouter > 1. Currently, the
7783! analysis is only possible for Nouter = 1.
7784!-----------------------------------------------------------------------
7785!
7786 IF (nouter.gt.1) THEN
7787 IF (master) THEN
7788 WRITE (out,330) 'Nouter = ', nouter, &
7789 & 'Posterior analysis error available for Nouter=1 only.'
7790 END IF
7791 exit_flag=5
7792 RETURN
7793 END IF
7794#endif
7795
7796#ifdef NESTING
7797!
7798!-----------------------------------------------------------------------
7799! If nesting, make sure that all grids are computing solutions for the
7800! same amount of time (seconds).
7801!-----------------------------------------------------------------------
7802!
7803 IF (.not.allocated(runtimeday)) THEN
7804 allocate ( runtimeday(ngrids) )
7805 END IF
7806 IF (.not.allocated(runtimesec)) THEN
7807 allocate ( runtimesec(ngrids) )
7808 END IF
7809 DO ng=1,ngrids
7810 runtimesec(ng)=real(ntimes(ng),r8)*dt(ng)
7811 runtimeday(ng)=runtimesec(ng)*sec2day
7812 END DO
7813 DO ng=2,ngrids
7814 IF (abs(runtimesec(1)-runtimesec(ng)).ne.0.0_r8) THEN
7815 IF (master) THEN
7816 WRITE (out,340) 1, runtimesec( 1), runtimeday( 1), &
7817 & ng, runtimesec(ng), runtimeday(ng)
7818 END IF
7819 exit_flag=5
7820 RETURN
7821 END IF
7822 END DO
7823#endif
7824#ifdef SOLVE3D
7825!
7826!-----------------------------------------------------------------------
7827! Rescale active tracer parameters
7828!-----------------------------------------------------------------------
7829!
7830 DO ng=1,ngrids
7831 DO i=1,nat+npt
7832 itrc=i
7833# ifdef T_PASSIVE
7834 IF (i.gt.nat) itrc=inert(i-nat)
7835# endif
7836!
7837! Take the square root of the biharmonic coefficients so it can
7838! be applied to each harmonic operator.
7839!
7840 nl_tnu4(itrc,ng)=sqrt(abs(nl_tnu4(itrc,ng)))
7841#ifdef ADJOINT
7842 ad_tnu4(itrc,ng)=sqrt(abs(ad_tnu4(itrc,ng)))
7843#endif
7844#if defined TANGENT || defined TL_IOMS
7845 tl_tnu4(itrc,ng)=sqrt(abs(tl_tnu4(itrc,ng)))
7846#endif
7847!
7848! Compute inverse nudging coefficients (1/s) used in various tasks.
7849!
7850 IF (tnudg(itrc,ng).gt.0.0_r8) THEN
7851 tnudg(itrc,ng)=1.0_r8/(tnudg(itrc,ng)*86400.0_r8)
7852 ELSE
7853 tnudg(itrc,ng)=0.0_r8
7854 END IF
7855 END DO
7856 END DO
7857#endif
7858
7859#ifdef GRID_EXTRACT
7860!
7861!-----------------------------------------------------------------------
7862! Check grid extraction by decimation.
7863!-----------------------------------------------------------------------
7864!
7865 DO ng=1,ngrids
7866 IF (extractflag(ng).gt.1) THEN
7867 IF ((mod(lm(ng)+1, extractflag(ng)).ne.0).or. &
7868 & (mod(mm(ng)+1, extractflag(ng)).ne.0)) THEN
7869 WRITE (out,360) ng, extractflag(ng), &
7870 & mod(lm(ng)+1, extractflag(ng)), &
7871 & mod(mm(ng)+1, extractflag(ng))
7872 exit_flag=5
7873 RETURN
7874 END IF
7875# if defined FOUR_DVAR || defined FORWARD_WRITE
7876 IF (extractflag(ng).ne.2) THEN
7877 WRITE (out,370) ng, extractflag(ng)
7878 exit_flag=5
7879 RETURN
7880 END IF
7881# endif
7882 END IF
7883 END DO
7884#endif
7885!
7886 50 FORMAT (/,' READ_PhyPar - Error while processing line: ',/,a)
7887 60 FORMAT (/,1x,a,/, &
7888 & /,1x,'Operating system : ',a, &
7889 & /,1x,'CPU/hardware : ',a, &
7890 & /,1x,'Compiler system : ',a, &
7891 & /,1x,'Compiler command : ',a, &
7892 & /,1x,'Compiler flags : ',a, &
7893#ifdef DISTRIBUTE
7894# if defined PIO_LIB && \
7895 (defined asynchronous_pio || defined asynchronous_scorpio)
7896 & /,1x,'Peer Communicator : ',i0,', PET size = ',i0, &
7897 & /,1x,'OCN Communicator : ',i0,', PET size = ',i0, &
7898 & /,1x,'I/O Communicator : ',i0,', PET size = ',i0, &
7899 & 2x,'(Peer Ranks: ',a,')', &
7900# ifdef ASYNCHRONOUS_SCORPIO
7901 & /,1x,'InterCommunicator : ',i0, &
7902# endif
7903# endif
7904# ifdef DISJOINTED
7905 & /,1x,'Full Communicator : ',i0,', PET size = ',i0, &
7906 & ', Disjointed Subgroups = ',i0, &
7907 & /,1x,'Fork Communicator : ',i0,', PET size = ',i0, &
7908 & ', Color Range = ',i0,' to ',i0, &
7909# ifdef CONCURRENT_KERNEL
7910 & /,1x,'Task Communicator : ',i0,', PET size = ',i0, &
7911 & ', Color Range = ',i0,' to ',i0, &
7912# endif
7913# endif
7914# if !(defined PIO_LIB && \
7915 (defined asynchronous_pio || defined asynchronous_scorpio)) && \
7916 !defined DISJOINTED
7917 & /,1x,'OCN Communicator : ',i0,', PET size = ',i0,/, &
7918# endif
7919 & /,1x,'Input Script : ',a,/, &
7920#endif
7921#ifdef GIT_URL
7922 & /,1x,'GIT Root URL : ',a, &
7923 & /,1x,'GIT Revision : ',a, &
7924#endif
7925 & /,1x,'SVN Root URL : ',a, &
7926 & /,1x,'SVN Revision : ',a,/, &
7927 & /,1x,'Local Root : ',a, &
7928 & /,1x,'Header Dir : ',a, &
7929 & /,1x,'Header file : ',a, &
7930 & /,1x,'Analytical Dir : ',a)
7931 70 FORMAT (/,' Resolution, Grid ',i2.2,': ',i0,'x',i0,'x',i0, &
7932 & ',',2x,'Parallel Nodes: ',i0,',',2x,'Tiling: ',i0, &
7933 & 'x',i0)
7934 80 FORMAT (/,' ROMS: Wrong choice of grid ',i2.2,1x, &
7935 & 'partition or number of parallel nodes.', &
7936 & /,12x,a,1x,i0,/,12x, &
7937 & 'must be equal to the number of parallel processes = ', &
7938 & i0,/,12x,'Change -np value to mpirun or', &
7939 & /,12x,'change domain partition in input script.')
7940 90 FORMAT (/,' Resolution, Grid ',i2.2,': ',i0,'x',i0,'x',i0, &
7941 & ',',2x,'Parallel Threads: ',i0,',',2x,'Tiling: ',i0, &
7942 & 'x',i0)
7943 100 FORMAT (/,' ROMS: Wrong choice of grid ',i2.2,1x, &
7944 & 'partition or number of parallel threads.', &
7945 & /,12x,'NtileI*NtileJ must be a positive multiple of the', &
7946 & ' number of threads.', &
7947 & /,12x,'Change number of threads (environment variable) ', &
7948 & 'or',/,12x,'change domain partition in input script.')
7949 110 FORMAT (/,/,' Physical Parameters, Grid: ',i2.2, &
7950 & /, ' =============================',/)
7951 120 FORMAT (1x,i10,2x,a,t32,a)
7952 130 FORMAT (1x,i10,2x,a,t32,a,/,t34,a)
7953 140 FORMAT (f11.3,2x,a,t32,a)
7954 150 FORMAT (f11.2,2x,a,t32,a)
7955 160 FORMAT (f11.3,2x,a,t32,a,/,t34,a)
7956 170 FORMAT (10x,l1,2x,a,t32,a)
7957 180 FORMAT (10x,l1,2x,a,t32,a,i2.2,':',1x,a)
7958 185 FORMAT (10x,l1,2x,a,'(',i2.2,')',t32,a,i2.2,':',1x,a)
7959 190 FORMAT (1p,e11.4,2x,a,'(',i2.2,')',t32,a,/,t34,a,i2.2,':',1x,a)
7960 195 FORMAT (1p,e11.4,2x,a,t32,a,i2.2,':',1x,a)
7961 200 FORMAT (1p,e11.4,2x,a,t32,a)
7962 210 FORMAT (1p,e11.4,2x,a,t32,a,/,t34,a)
7963 220 FORMAT (/,' Output/Input Files:',/)
7964 230 FORMAT (2x,a,a)
7965 240 FORMAT (/,' Generic User Parameters:',/)
7966 250 FORMAT (1p,e11.4,2x,'user(',i2.2,')',t32, &
7967 & 'User parameter ',i2.2,'.')
7968 260 FORMAT (/,' READ_PHYPAR - Invalid input parameter, ',a, &
7969 & i4,/,15x,a)
7970 265 FORMAT (/,' READ_PHYPAR - Invalid input parameter, ',a, &
7971 & 1p,e11.4,/,15x,a)
7972 280 FORMAT (/,' READ_PHYPAR - Variable index not yet loaded, ', a)
7973 290 FORMAT (/,' READ_PHYPAR - Invalid dimension parameter, ',a,i0, &
7974 & /,15x,a)
7975 300 FORMAT (/,' READ_PHYPAR - Invalid dimension parameter, ',a,'(', &
7976 & i2.2,')',/,15x,a)
7977 310 FORMAT (2x,a,i2.2,a,a)
7978 320 FORMAT (/,' READ_PHYPAR - Could not find input parameter: ', a, &
7979 & /,15x,'in ROMS standard input script.',/,15x,a)
7980 330 FORMAT (/,' READ_PHYPAR - Invalid input parameter, ',a,i4,/,15x,a)
7981 340 FORMAT (/,' READ_PHYPAR - Inconsistent time-stepping period:', &
7982 & /,15x,'Grid ',i2.2,':',f14.1,' (sec)',2x,f14.2,' (days)', &
7983 & /,15x,'Grid ',i2.2,':',f14.1,' (sec)',2x,f14.2,' (days)', &
7984 & /,15x,'Adjust standard input parameter NTIMES in ', &
7985 & '''roms.in''.'/)
7986 350 FORMAT (/,' READ_PHYPAR - Invalid input parameter, ',a,i0, &
7987 & ', for grid ',i2.2,/,15x,a,i0,', ',a,i0,/,15x,a,/,15x,a)
7988 360 FORMAT (/,' READ_PHYPAR - Grid = ',i0,1x,'dimensions are',1x, &
7989 & 'inappropriate for the given decimation factor:',/,15x, &
7990 & 'ExtractFlag = ',i0,/,15x, &
7991 & 'MOD(Lm(ng)+1, ExtractFlag(ng)) = ',i0,/,15x, &
7992 & 'MOD(Mm(ng)+1, ExtractFlag(ng)) = ',i0,/,15x, &
7993 & 'because both division reminders must be zero.')
7994 370 FORMAT (/,' READ_PHYPAR - Unsupported decimation factor for',1x, &
7995 & 'coarsening split 4D-Var',/,15x, &
7996 & 'Grid = ',i0,', ExtractFlag = ',i0)
7997!
7998 RETURN
7999 END SUBROUTINE read_phypar
subroutine edit_file_struct(ng, nfiles, s)
subroutine, public ref_clock(r_time)
Definition dateclock.F:972
type(t_io), dimension(:), allocatable err
logical function, public founderror(flag, noerr, line, routine)
Definition strings.F:52
subroutine read_phypar(model, inp, out, lwrite)
Definition read_phypar.F:3