23#if defined MODEL_COUPLING && defined MCT_LIB
26#if defined FOUR_DVAR || defined VERIFICATION
35#if defined PIO_LIB && defined DISTRIBUTE
39#if defined SEDIMENT || defined BBL_MODEL
49#if defined DISTRIBUTE && defined PIO_LIB
60 logical,
intent(inout) :: Lwrite
62 integer,
intent(in) :: model, inp, out
66 logical :: got_Ngrids, got_NestLayers
69#if defined SOLVE3D && defined SEDIMENT
70 logical :: LreadNCS = .false.
71 logical :: LreadNNS = .false.
73 logical,
allocatable :: Lswitch(:)
74#if defined SOLVE3D && defined T_PASSIVE
75 logical,
allocatable :: Linert(:,:)
77#if defined SOLVE3D && (defined BBL_MODEL || defined SEDIMENT)
78 logical,
allocatable :: Lbottom(:,:)
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
86 logical,
allocatable :: Ladsen(:)
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
101 integer,
allocatable :: Nfiles(:)
102 integer,
allocatable :: Ncount(:,:)
103 integer,
allocatable :: NBCcount(:,:)
104 integer,
allocatable :: NCLMcount(:,:)
106 real(dp),
allocatable :: Dtracer(:,:)
107 real(r8),
allocatable :: Rtracer(:,:)
108 real(r8),
allocatable :: tracer(:,:)
110 real(r8),
allocatable :: RunTimeDay(:), RunTimeSec(:)
112 real(dp) :: Dvalue(1)
113 real(r8) :: Rvalue(1)
115 real(dp),
dimension(nRval) :: Rval
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
124 character (len=*),
parameter :: MyFile = &
141 got_nestlayers=.false.
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))
159 title=trim(adjustl(cval(nval)))
161 WRITE(title,
'(a,1x,a)') trim(adjustl(title)), &
162 & trim(adjustl(cval(nval)))
168 myappcpp=trim(adjustl(cval(nval)))
173 varname=trim(adjustl(cval(nval)))
175 npts=load_i(nval, rval, 1, ivalue)
177 IF (ngrids.le.0)
THEN
178 IF (master)
WRITE (out,290)
'Ngrids', ngrids, &
179 &
'must be greater than zero.'
185 CALL allocate_parallel (ngrids)
186 CALL allocate_iounits (ngrids)
187 CALL allocate_stepping (ngrids)
188#if defined PIO_LIB && defined DISTRIBUTE
189 IF (.not.
associated(var_desc))
THEN
190 allocate ( var_desc(mvars) )
193#if defined FOUR_DVAR || defined VERIFICATION
194 CALL allocate_fourdvar
196 IF (.not.
allocated(lswitch))
THEN
197 allocate ( lswitch(ngrids) )
199#if defined SOLVE3D && (defined BBL_MODEL || defined SEDIMENT)
200 IF (.not.
allocated(lbottom))
THEN
201 allocate ( lbottom(mbotp,ngrids) )
204 IF (.not.
allocated(nfiles))
THEN
205 allocate ( nfiles(ngrids) )
209 npts=load_i(nval, rval, 1, ivalue)
211 IF (nestlayers.lt.1)
THEN
212 IF (master)
WRITE (out,290)
'NestLayers', nestlayers, &
213 &
'must be greater or equal than one.'
218 IF (nestlayers.gt.1)
THEN
219 IF (master)
WRITE (out,290)
'NestLayers', nestlayers, &
220 &
'must be equal to one in non-nesting applications.'
225 got_nestlayers=.true.
226 IF (.not.
allocated(gridsinlayer))
THEN
227 allocate ( gridsinlayer(nestlayers) )
229 gridsinlayer(1:nestlayers)=1
232 IF (.not.
allocated(gridnumber))
THEN
233 allocate ( gridnumber(ngrids,nestlayers) )
234 gridnumber(1:ngrids,1:nestlayers)=0
236 CASE (
'GridsInLayer')
237 IF (.not.got_nestlayers)
THEN
238 IF (master)
WRITE (out,320)
'NestLayers', &
239 &
'Add "NestLayers" keyword before GridsInLayer.'
243 npts=load_i(nval, rval, nestlayers, gridsinlayer)
246 DO i=1,gridsinlayer(nl)
252 IF (.not.got_ngrids)
THEN
253 IF (master)
WRITE (out,320)
'Ngrids', &
254 &
'Add "Ngrids" keyword before grid dimension (Lm, Mm).'
258 npts=load_i(nval, rval, ngrids, lm)
260 IF (lm(ng).le.0)
THEN
261 IF (master)
WRITE (out,300)
'Lm', ng, &
262 &
'must be greater than zero.'
268 npts=load_i(nval, rval, ngrids, mm)
270 IF (mm(ng).le.0)
THEN
271 IF (master)
WRITE (out,300)
'Mm', ng, &
272 &
'must be greater than zero.'
278 npts=load_i(nval, rval, ngrids, n)
281 IF (master)
WRITE (out,300)
'N', ng, &
282 &
'must be greater than zero.'
287#if defined SEDIMENT && defined SOLVE3D
289 npts=load_i(nval, rval, 1, ivalue)
292 IF (master)
WRITE (out,290)
'Nbed = ', nbed, &
293 &
'must be greater than zero.'
300 npts=load_i(nval, rval, 1, ivalue)
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.'
310 IF (master)
WRITE (out,290)
'NAT = ', nat, &
311 &
'make sure that NAT is equal to 2.'
317#if defined T_PASSIVE && defined SOLVE3D
319 npts=load_i(nval, rval, 1, ivalue)
322 IF (master)
WRITE (out,290)
'NPT = ', npt, &
323 &
'must be greater than zero.'
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.'
336#if defined SEDIMENT && defined SOLVE3D
338 npts=load_i(nval, rval, 1, ivalue)
341 IF (master)
WRITE (out,290)
'NCS = ', ncs, &
342 &
'must be greater than zero.'
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.'
355 npts=load_i(nval, rval, 1, ivalue)
358 IF (master)
WRITE (out,290)
'NNS = ', &
359 &
'must be greater than zero.'
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.'
373 npts=load_i(nval, rval, ngrids, ntilei)
374 ntilex(1:ngrids)=ntilei(1:ngrids)
376 npts=load_i(nval, rval, ngrids, ntilej)
377 ntilee(1:ngrids)=ntilej(1:ngrids)
379 CALL initialize_biology
381#if defined SEDIMENT || defined BBL_MODEL
382 CALL initialize_sediment
384 CALL initialize_param
385 CALL allocate_scalars
386 CALL initialize_scalars
387 CALL allocate_ncparam
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
394 IF (.not.
allocated(ladsen))
THEN
395 allocate (ladsen(mt*ngrids))
399 IF (.not.
allocated(ltracer))
THEN
400 allocate (ltracer(nat+npt,ngrids))
402#if defined SOLVE3D && defined T_PASSIVE
403 IF (.not.
allocated(linert))
THEN
404 allocate (linert(npt,ngrids))
406 IF (maxval(inert).eq.0)
THEN
407 IF (master)
WRITE (out,280)
'inert'
412 IF (.not.
allocated(dtracer))
THEN
413 allocate (dtracer(nat+npt,ngrids))
415 IF (.not.
allocated(rtracer))
THEN
416 allocate (rtracer(nat+npt,ngrids))
418 IF (.not.
allocated(tracer))
THEN
419 allocate (tracer(mt,ngrids))
423 IF (itracer.lt.(nat+npt))
THEN
429 npts=load_tadv(nval, cval, line, nline, itrc, igrid, &
430 & itracer, 1, nat+npt, &
431 & vname(1,idtvar(itrc)), &
433 IF (founderror(exit_flag, noerror, &
434 & __line__, myfile))
RETURN
436 IF (itracer.lt.(nat+npt))
THEN
442 npts=load_tadv(nval, cval, line, nline, itrc, igrid, &
443 & itracer, 1, nat+npt, &
444 & vname(1,idtvar(itrc)), &
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
456 npts=load_tadv(nval, cval, line, nline, itrc, igrid, &
457 & itracer, 1, nat+npt, &
458 & vname(1,idtvar(itrc)), &
460 IF (founderror(exit_flag, noerror, &
461 & __line__, myfile))
RETURN
462 CASE (
'ad_Vadvection')
463 IF (itracer.lt.(nat+npt))
THEN
469 npts=load_tadv(nval, cval, line, nline, itrc, igrid, &
470 & itracer, 1, nat+npt, &
471 & vname(1,idtvar(itracer)), &
473 IF (founderror(exit_flag, noerror, &
474 & __line__, myfile))
RETURN
478 npts=load_lbc(nval, cval, line, nline, isfsur, igrid, &
479 & 0, 0, vname(1,idfsur), lbc)
481 npts=load_lbc(nval, cval, line, nline, isubar, igrid, &
482 & 0, 0, vname(1,idubar), lbc)
484 npts=load_lbc(nval, cval, line, nline, isvbar, igrid, &
485 & 0, 0, vname(1,idvbar), lbc)
488 npts=load_lbc(nval, cval, line, nline, isu2sd, igrid, &
489 & 0, 0, vname(1,idu2sd), lbc)
491 npts=load_lbc(nval, cval, line, nline, isv2sd, igrid, &
492 & 0, 0, vname(1,idv2sd), lbc)
496 npts=load_lbc(nval, cval, line, nline, isuvel, igrid, &
497 & 0, 0, vname(1,iduvel), lbc)
499 npts=load_lbc(nval, cval, line, nline, isvvel, igrid, &
500 & 0, 0, vname(1,idvvel), lbc)
503 npts=load_lbc(nval, cval, line, nline, isu3sd, igrid, &
504 & 0, 0, vname(1,idu3sd), lbc)
506 npts=load_lbc(nval, cval, line, nline, isv3sd, igrid, &
507 & 0, 0, vname(1,idv3sd), lbc)
509# if defined GLS_MIXING || defined MY25_MIXING
511 npts=load_lbc(nval, cval, line, nline, ismtke, igrid, &
512 & 0, 0, vname(1,idmtke), lbc)
515 IF (itracer.lt.(nat+npt))
THEN
520 ifield=istvar(itracer)
521 npts=load_lbc(nval, cval, line, nline, ifield, igrid, &
522 & 1, nat+npt, vname(1,idtvar(itracer)), lbc)
525 ioff = isaice+(nlbcvar-11)
526 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
527 & 0, 0, vname(1,idaice), lbc)
529 ioff = ishice+(nlbcvar-11)
530 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
531 & 0, 0, vname(1,idhice), lbc)
533 ioff = ishsno+(nlbcvar-11)
534 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
535 & 0, 0, vname(1,idhsno), lbc)
537 ioff = istice+(nlbcvar-11)
538 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
539 & 0, 0, vname(1,idtice), lbc)
541 ioff = ishmel+(nlbcvar-11)
542 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
543 & 0, 0, vname(1,idhmel), lbc)
545 ioff = isiage+(nlbcvar-11)
546 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
547 & 0, 0, vname(1,idiage), lbc)
549 ioff = isisxx+(nlbcvar-11)
550 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
551 & 0, 0, vname(1,idisxx), lbc)
553 ioff = isisxy+(nlbcvar-11)
554 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
555 & 0, 0, vname(1,idisxy), lbc)
557 ioff = isisyy+(nlbcvar-11)
558 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
559 & 0, 0, vname(1,idisyy), lbc)
561 ioff = isuice+(nlbcvar-11)
562 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
563 & 0, 0, vname(1,iduice), lbc)
565 ioff = isvice+(nlbcvar-11)
566 npts=load_lbc(nval, cval, line, nline, ioff, igrid, &
567 & 0, 0, vname(1,idvice), lbc)
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)
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)
592 CASE (
'ad_LBC(isTvar)')
593 IF (itracer.lt.(nat+npt))
THEN
598 ifield=istvar(itracer)
599 npts=load_lbc(nval, cval, line, nline, ifield, igrid, &
600 & 1, nat+npt, vname(1,idtvar(itracer)), &
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)
635 npts=load_i(nval, rval, ngrids, ntimes)
636#ifdef RBL4DVAR_FCT_SENSITIVITY
638 npts=load_i(nval, rval, ngrids, ntimes_ana)
640 npts=load_i(nval, rval, ngrids, ntimes_fct)
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))
651 couplesteps(i,ng)=max(1, &
652 & int(timeinterval(iocean,i)/ &
658 npts=load_i(nval, rval, ngrids, ndtfast)
660 npts=load_i(nval, rval, 1, ivalue)
663 npts=load_i(nval, rval, 1, ivalue)
666 npts=load_i(nval, rval, 1, ivalue)
669 npts=load_i(nval, rval, 1, ivalue)
672 npts=load_i(nval, rval, 1, ivalue)
675 npts=load_i(nval, rval, 1, ivalue)
679 npts=load_i(nval, rval, 1, ivalue)
682 npts=load_i(nval, rval, 1, ivalue)
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'
693 IF (master)
WRITE (out,260)
'NCV = ', ncv, &
694 &
'Must be greater than NEV'
701 npts=load_i(nval, rval, ngrids, nrrec)
703 IF (nrrec(ng).lt.0)
THEN
710 npts=load_l(nval, cval, ngrids, lcyclerst)
712 npts=load_i(nval, rval, ngrids, nrst)
714 npts=load_i(nval, rval, ngrids, nsta)
716 npts=load_i(nval, rval, ngrids, nflt)
718 npts=load_i(nval, rval, ngrids, ninfo)
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.'
729 npts=load_l(nval, cval, ngrids, ldefout)
731 npts=load_i(nval, rval, ngrids, nhis)
733 npts=load_i(nval, rval, ngrids, ndefhis)
735 npts=load_i(nval, rval, ngrids, nxtr)
737 npts=load_i(nval, rval, ngrids, ndefxtr)
739 npts=load_i(nval, rval, ngrids, nqck)
740#if defined FORWARD_FLUXES && \
741 (defined bulk_fluxes || defined frc_coupling)
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.'
754 npts=load_i(nval, rval, ngrids, ndefqck)
756 npts=load_i(nval, rval, ngrids, ntsavg)
759 IF (ntsavg(ng).eq.1) ntsavg(ng)=ntimes(ng)
763 npts=load_i(nval, rval, ngrids, navg)
765 npts=load_i(nval, rval, ngrids, ndefavg)
767 npts=load_i(nval, rval, ngrids, ntsdia)
769 npts=load_i(nval, rval, ngrids, ndia)
771 npts=load_i(nval, rval, ngrids, ndefdia)
773 npts=load_l(nval, cval, ngrids, lcycletlm)
775 npts=load_i(nval, rval, ngrids, ntlm)
777 npts=load_i(nval, rval, ngrids, ndeftlm)
779 npts=load_l(nval, cval, ngrids, lcycleadj)
781 npts=load_i(nval, rval, ngrids, nadj)
783 npts=load_i(nval, rval, ngrids, ndefadj)
785 npts=load_i(nval, rval, ngrids, nobc)
786#ifdef ADJUST_BOUNDARY
787# ifdef RBL4DVAR_FCT_SENSITIVITY
789 nbrec(ng)=1+ntimes_ana(ng)/nobc(ng)
791 allocate ( obc_time(maxval(nbrec),ngrids) )
794 nbrec(ng)=1+ntimes(ng)/nobc(ng)
796 allocate ( obc_time(maxval(nbrec),ngrids) )
800 npts=load_i(nval, rval, ngrids, nsff)
801#if defined ADJUST_STFLUX || defined ADJUST_WSTRESS
802# ifdef RBL4DVAR_FCT_SENSITIVITY
804 nfrec(ng)=1+ntimes_ana(ng)/nsff(ng)
806 allocate ( sf_time(maxval(nfrec),ngrids) )
809 nfrec(ng)=1+ntimes(ng)/nsff(ng)
811 allocate ( sf_time(maxval(nfrec),ngrids) )
815 npts=load_l(nval, cval, 1, lvalue)
818 npts=load_l(nval, cval, 1, lvalue)
821 npts=load_i(nval, rval, 1, ivalue)
824 npts=load_i(nval, rval, 1, ivalue)
828 npts=load_r(nval, rval, 1, dvalue)
832 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
835 nl_tnu2(itrc,ng)=rtracer(itrc,ng)
840 nl_tnu2(itrc,ng)=rtracer(nat+i,ng)
845 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
848 nl_tnu4(itrc,ng)=rtracer(itrc,ng)
853 nl_tnu4(itrc,ng)=rtracer(nat+i,ng)
858 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
861 ad_tnu2(itrc,ng)=rtracer(itrc,ng)
862 tl_tnu2(itrc,ng)=rtracer(itrc,ng)
867 ad_tnu2(itrc,ng)=rtracer(nat+i,ng)
868 tl_tnu2(itrc,ng)=rtracer(nat+i,ng)
873 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
876 ad_tnu4(itrc,ng)=rtracer(itrc,ng)
877 tl_tnu4(itrc,ng)=rtracer(itrc,ng)
882 ad_tnu4(itrc,ng)=rtracer(nat+i,ng)
883 tl_tnu4(itrc,ng)=rtracer(nat+i,ng)
888 npts=load_r(nval, rval, ngrids, nl_visc2)
890 npts=load_r(nval, rval, ngrids, nl_visc4)
892 npts=load_r(nval, rval, ngrids, ad_visc2)
894 tl_visc2(ng)=ad_visc2(ng)
897 npts=load_r(nval, rval, ngrids, ad_visc4)
899 tl_visc4(ng)=ad_visc4(ng)
902 npts=load_l(nval, cval, ngrids, luvsponge)
904 CASE (
'LtracerSponge')
905 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
908 ltracersponge(itrc,ng)=ltracer(itrc,ng)
913 ltracersponge(itrc,ng)=ltracer(nat+i,ng)
919 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
922 akt_bak(itrc,ng)=rtracer(itrc,ng)
927 akt_bak(itrc,ng)=rtracer(nat+i,ng)
932 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
935 akt_limit(itrc,ng)=rtracer(itrc,ng)
939 npts=load_r(nval, rval, nat+npt, ngrids, rtracer)
942 ad_akt_fac(itrc,ng)=rtracer(itrc,ng)
943 tl_akt_fac(itrc,ng)=rtracer(itrc,ng)
948 ad_akt_fac(itrc,ng)=rtracer(nat+i,ng)
949 tl_akt_fac(itrc,ng)=rtracer(nat+i,ng)
954 npts=load_r(nval, rval, ngrids, akv_bak)
956 npts=load_r(nval, rval, ngrids, akv_limit)
958 npts=load_r(nval, rval, ngrids, ad_akv_fac)
960 tl_akv_fac(ng)=ad_akv_fac(ng)
963 npts=load_r(nval, rval, ngrids, akk_bak)
965 npts=load_r(nval, rval, ngrids, akp_bak)
967 npts=load_r(nval, rval, ngrids, tkenu2)
969 npts=load_r(nval, rval, ngrids, tkenu4)
971 npts=load_r(nval, rval, ngrids, gls_p)
973 npts=load_r(nval, rval, ngrids, gls_m)
975 npts=load_r(nval, rval, ngrids, gls_n)
977 npts=load_r(nval, rval, ngrids, gls_kmin)
979 npts=load_r(nval, rval, ngrids, gls_pmin)
981 npts=load_r(nval, rval, ngrids, gls_cmu0)
983 npts=load_r(nval, rval, ngrids, gls_c1)
985 npts=load_r(nval, rval, ngrids, gls_c2)
987 npts=load_r(nval, rval, ngrids, gls_c3m)
989 npts=load_r(nval, rval, ngrids, gls_c3p)
991 npts=load_r(nval, rval, ngrids, gls_sigk)
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)
999 npts=load_r(nval, rval, ngrids, sz_alpha)
1001 npts=load_r(nval, rval, ngrids, crgban_cw)
1003 npts=load_r(nval, rval, ngrids, wec_alpha)
1005 npts=load_r(nval, rval, ngrids, rdrg)
1007 npts=load_r(nval, rval, ngrids, rdrg2)
1009 npts=load_r(nval, rval, ngrids, zob)
1011 npts=load_r(nval, rval, ngrids, zos)
1014 npts=load_r(nval, rval, ngrids, blk_zq)
1016 npts=load_r(nval, rval, ngrids, blk_zt)
1018 npts=load_r(nval, rval, ngrids, blk_zw)
1021 npts=load_r(nval, rval, ngrids, dcrit)
1023 npts=load_i(nval, rval, ngrids, lmd_jwt)
1025 npts=load_i(nval, rval, ngrids, levsfrc)
1027 npts=load_i(nval, rval, ngrids, levbfrc)
1029 npts=load_i(nval, rval, ngrids, vtransform)
1031 IF ((vtransform(ng).lt.0).or. &
1032 & (vtransform(ng).gt.2))
THEN
1033 IF (master)
WRITE (out,260)
'Vtransform = ', &
1035 &
'Must be either 1 or 2'
1040 CASE (
'Vstretching')
1041 npts=load_i(nval, rval, ngrids, vstretching)
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'
1053 npts=load_r(nval, rval, ngrids, theta_s)
1055 npts=load_r(nval, rval, ngrids, theta_b)
1057 npts=load_r(nval, rval, ngrids, tcline)
1062 npts=load_r(nval, rval, 1, rvalue)
1065 npts=load_r(nval, rval, 1, rvalue)
1067#ifdef TIDE_GENERATING_FORCES
1069 npts=load_l(nval, cval, 1, lvalue)
1073 npts=load_r(nval, rval, 1, dvalue)
1076 npts=load_r(nval, rval, 1, dvalue)
1077 tide_start=dvalue(1)
1079 npts=load_r(nval, rval, 1, dvalue)
1081 CALL ref_clock (time_ref)
1083 npts=load_r(nval, rval, nat+npt, ngrids, dtracer)
1086 tnudg(itrc,ng)=dtracer(itrc,ng)
1091 tnudg(itrc,ng)=dtracer(nat+i,ng)
1096 npts=load_r(nval, rval, ngrids, znudg)
1098 npts=load_r(nval, rval, ngrids, m2nudg)
1100 npts=load_r(nval, rval, ngrids, m3nudg)
1102 npts=load_r(nval, rval, ngrids, obcfac)
1104 npts=load_r(nval, rval, ngrids, r0)
1106 IF (r0(ng).lt.100.0_r8) r0(ng)=r0(ng)+1000.0_r8
1109 npts=load_r(nval, rval, ngrids, t0)
1111 npts=load_r(nval, rval, ngrids, s0)
1113 npts=load_r(nval, rval, ngrids, tcoef)
1115 tcoef(ng)=abs(tcoef(ng))
1118 npts=load_r(nval, rval, ngrids, scoef)
1120 scoef(ng)=abs(scoef(ng))
1123 npts=load_r(nval, rval, ngrids, gamma2)
1125 npts=load_l(nval, cval, ngrids, luvsrc)
1127 npts=load_l(nval, cval, ngrids, lwsrc)
1130 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
1133 ltracersrc(itrc,ng)=ltracer(itrc,ng)
1138 ltracersrc(itrc,ng)=ltracer(nat+i,ng)
1144 npts=load_l(nval, cval, ngrids, lsshclm)
1146 npts=load_l(nval, cval, ngrids, lm2clm)
1149 npts=load_l(nval, cval, ngrids, lm3clm)
1151 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
1154 ltracerclm(itrc,ng)=ltracer(itrc,ng)
1159 ltracerclm(itrc,ng)=ltracer(nat+i,ng)
1164 CASE (
'LnudgeM2CLM')
1165 npts=load_l(nval, cval, ngrids, lnudgem2clm)
1167 CASE (
'LnudgeM3CLM')
1168 npts=load_l(nval, cval, ngrids, lnudgem3clm)
1170 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
1173 lnudgetclm(itrc,ng)=ltracer(itrc,ng)
1178 lnudgetclm(itrc,ng)=ltracer(nat+i,ng)
1183#if defined AD_SENSITIVITY || defined I4DVAR_ANA_SENSITIVITY || \
1184 defined opt_observations || defined sensitivity_4dvar || \
1187 npts=load_r(nval, rval, ngrids, dstrs)
1189 npts=load_r(nval, rval, ngrids, dends)
1192 npts=load_i(nval, rval, ngrids, kstrs)
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'
1201 npts=load_l(nval, cval, ngrids, ladsen)
1203 scalars(ng)%Lstate(isfsur)=ladsen(ng)
1205 CASE (
'Lstate(isUbar)')
1206 IF (isubar.eq.0)
THEN
1207 IF (master)
WRITE (out,280)
'isUbar'
1211 npts=load_l(nval, cval, ngrids, ladsen)
1213 scalars(ng)%Lstate(isubar)=ladsen(ng)
1215 CASE (
'Lstate(isVbar)')
1216 IF (isvbar.eq.0)
THEN
1217 IF (master)
WRITE (out,280)
'isVbar'
1221 npts=load_l(nval, cval, ngrids, ladsen)
1223 scalars(ng)%Lstate(isvbar)=ladsen(ng)
1226 CASE (
'Lstate(isUvel)')
1227 IF (isuvel.eq.0)
THEN
1228 IF (master)
WRITE (out,280)
'isUvel'
1232 npts=load_l(nval, cval, ngrids, ladsen)
1234 scalars(ng)%Lstate(isuvel)=ladsen(ng)
1236 CASE (
'Lstate(isVvel)')
1237 IF (isvvel.eq.0)
THEN
1238 IF (master)
WRITE (out,280)
'isVvel'
1242 npts=load_l(nval, cval, ngrids, ladsen)
1244 scalars(ng)%Lstate(isvvel)=ladsen(ng)
1246 CASE (
'Lstate(isWvel)')
1247 IF (iswvel.eq.0)
THEN
1248 IF (master)
WRITE (out,280)
'isWvel'
1252 npts=load_l(nval, cval, ngrids, ladsen)
1254 scalars(ng)%Lstate(iswvel)=ladsen(ng)
1256 CASE (
'Lstate(isTvar)')
1257 IF (maxval(istvar).eq.0)
THEN
1258 IF (master)
WRITE (out,280)
'isTvar'
1262 npts=load_l(nval, cval, mt*ngrids, ladsen)
1268 scalars(ng)%Lstate(i)=ladsen(k)
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'
1282 npts=load_l(nval, cval, ngrids, ladsen)
1284 scalars(ng)%Fstate(isfsur)=ladsen(ng)
1286 CASE (
'Fstate(isUbar)')
1287 IF (isubar.eq.0)
THEN
1288 IF (master)
WRITE (out,280)
'isUbar'
1292 npts=load_l(nval, cval, ngrids, ladsen)
1294 scalars(ng)%Fstate(isubar)=ladsen(ng)
1296 CASE (
'Fstate(isVbar)')
1297 IF (isvbar.eq.0)
THEN
1298 IF (master)
WRITE (out,280)
'isVbar'
1302 npts=load_l(nval, cval, ngrids, ladsen)
1304 scalars(ng)%Fstate(isvbar)=ladsen(ng)
1307 CASE (
'Fstate(isUvel)')
1308 IF (isuvel.eq.0)
THEN
1309 IF (master)
WRITE (out,280)
'isUvel'
1313 npts=load_l(nval, cval, ngrids, ladsen)
1315 scalars(ng)%Fstate(isuvel)=ladsen(ng)
1317 CASE (
'Fstate(isVvel)')
1318 IF (isvvel.eq.0)
THEN
1319 IF (master)
WRITE (out,280)
'isVvel'
1323 npts=load_l(nval, cval, ngrids, ladsen)
1325 scalars(ng)%Fstate(isvvel)=ladsen(ng)
1327 CASE (
'Fstate(isTvar)')
1328 IF (maxval(istvar).eq.0)
THEN
1329 IF (master)
WRITE (out,280)
'isTvar'
1333 npts=load_l(nval, cval, mt*ngrids, ladsen)
1339 scalars(ng)%Fstate(i)=ladsen(k)
1343 CASE (
'Fstate(isUstr)')
1344 IF (isustr.eq.0)
THEN
1345 IF (master)
WRITE (out,280)
'isUstr'
1349 npts=load_l(nval, cval, ngrids, ladsen)
1351 scalars(ng)%Fstate(isustr)=ladsen(ng)
1353 CASE (
'Fstate(isVstr)')
1354 IF (isustr.eq.0)
THEN
1355 IF (master)
WRITE (out,280)
'isVstr'
1359 npts=load_l(nval, cval, ngrids, ladsen)
1361 scalars(ng)%Fstate(isvstr)=ladsen(ng)
1364 CASE (
'Fstate(isTsur)')
1365 IF (maxval(istsur).eq.0)
THEN
1366 IF (master)
WRITE (out,280)
'isTsur'
1370 npts=load_l(nval, cval, mt*ngrids, ladsen)
1376 scalars(ng)%Fstate(i)=ladsen(k)
1381#if defined SO_SEMI || \
1382 (defined stochastic_opt &&
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))
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)
1403 so_sdev(i,ng)=tracer(k,ng)
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))
1412 CASE (
'SO_sdev(isTsur)')
1413 npts=load_r(nval, rval, mt, ngrids, tracer)
1419 so_sdev(i,ng)=tracer(k,ng)
1424 CASE (
'Hout(idUvel)')
1425 IF (iduvel.eq.0)
THEN
1426 IF (master)
WRITE (out,280)
'idUvel'
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'
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'
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'
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'
1463 npts=load_l(nval, cval, ngrids, lswitch)
1464 hout(idovel,1:ngrids)=lswitch(1:ngrids)
1466 CASE (
'Hout(idUbar)')
1467 IF (idubar.eq.0)
THEN
1468 IF (master)
WRITE (out,280)
'idUbar'
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'
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'
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'
1497 npts=load_l(nval, cval, ngrids, lswitch)
1498 hout(idbath,1:ngrids)=lswitch(1:ngrids)
1500 CASE (
'Hout(idu2dE)')
1501 IF (idu2de.eq.0)
THEN
1502 IF (master)
WRITE (out,280)
'idu2dE'
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'
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'
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'
1530 npts=load_l(nval, cval, ngrids, lswitch)
1531 hout(idv3dn,1:ngrids)=lswitch(1:ngrids)
1533 CASE (
'Hout(idTvar)')
1534 IF (maxval(idtvar).eq.0)
THEN
1535 IF (master)
WRITE (out,280)
'idTvar'
1539 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
1543 hout(i,ng)=ltracer(itrc,ng)
1547 CASE (
'Hout(idpthR)')
1548 IF (idpthr.eq.0)
THEN
1549 IF (master)
WRITE (out,280)
'idpthR'
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'
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'
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'
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'
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'
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'
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'
1609 npts=load_l(nval, cval, ngrids, lswitch)
1610 hout(idvbms,1:ngrids)=lswitch(1:ngrids)
1612 CASE (
'Hout(idUbrs)')
1613 IF (idubrs.eq.0)
THEN
1614 IF (master)
WRITE (out,280)
'idUbrs'
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'
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'
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'
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'
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'
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'
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'
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'
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'
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'
1698 npts=load_l(nval, cval, ngrids, lswitch)
1699 hout(idvbvr,1:ngrids)=lswitch(1:ngrids)
1702 CASE (
'Hout(idWztw)')
1703 IF (idwztw.eq.0)
THEN
1704 IF (master)
WRITE (out,280)
'idWztw'
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'
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'
1724 npts=load_l(nval, cval, ngrids, lswitch)
1725 hout(idwbeh,1:ngrids)=lswitch(1:ngrids)
1728 CASE (
'Hout(idU2rs)')
1729 IF (idu2rs.eq.0)
THEN
1730 IF (master)
WRITE (out,280)
'idU2rs'
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'
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'
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'
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'
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'
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'
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'
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'
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'
1806 npts=load_l(nval, cval, ngrids, lswitch)
1807 hout(idw3st,1:ngrids)=lswitch(1:ngrids)
1810 CASE (
'Hout(idWamp)')
1811 IF (idwamp.eq.0)
THEN
1812 IF (master)
WRITE (out,280)
'idWamp'
1816 npts=load_l(nval, cval, ngrids, lswitch)
1817 hout(idwamp,1:ngrids)=lswitch(1:ngrids)
1821 CASE (
'Hout(idWlen)')
1822 IF (idwlen.eq.0)
THEN
1823 IF (master)
WRITE (out,280)
'idWlen'
1827 npts=load_l(nval, cval, ngrids, lswitch)
1828 hout(idwlen,1:ngrids)=lswitch(1:ngrids)
1831 CASE (
'Hout(idWlep)')
1832 IF (idwlep.eq.0)
THEN
1833 IF (master)
WRITE (out,280)
'idWlep'
1837 npts=load_l(nval, cval, ngrids, lswitch)
1838 hout(idwlep,1:ngrids)=lswitch(1:ngrids)
1841 CASE (
'Hout(idWdir)')
1842 IF (idwdir.eq.0)
THEN
1843 IF (master)
WRITE (out,280)
'idWdir'
1847 npts=load_l(nval, cval, ngrids, lswitch)
1848 hout(idwdir,1:ngrids)=lswitch(1:ngrids)
1851 CASE (
'Hout(idWdip)')
1852 IF (idwdip.eq.0)
THEN
1853 IF (master)
WRITE (out,280)
'idWdip'
1857 npts=load_l(nval, cval, ngrids, lswitch)
1858 hout(idwdip,1:ngrids)=lswitch(1:ngrids)
1860#ifdef WAVES_TOP_PERIOD
1861 CASE (
'Hout(idWptp)')
1862 IF (idwptp.eq.0)
THEN
1863 IF (master)
WRITE (out,280)
'idWptp'
1867 npts=load_l(nval, cval, ngrids, lswitch)
1868 hout(idwptp,1:ngrids)=lswitch(1:ngrids)
1870#ifdef WAVES_BOT_PERIOD
1871 CASE (
'Hout(idWpbt)')
1872 IF (idwpbt.eq.0)
THEN
1873 IF (master)
WRITE (out,280)
'idWpbt'
1877 npts=load_l(nval, cval, ngrids, lswitch)
1878 hout(idwpbt,1:ngrids)=lswitch(1:ngrids)
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'
1888 npts=load_l(nval, cval, ngrids, lswitch)
1889 hout(idworb,1:ngrids)=lswitch(1:ngrids)
1891#if defined ROLLER_SVENDSEN
1892 CASE (
'Hout(idWbrk)')
1893 IF (idwbrk.eq.0)
THEN
1894 IF (master)
WRITE (out,280)
'idWbrk'
1898 npts=load_l(nval, cval, ngrids, lswitch)
1899 hout(idwbrk,1:ngrids)=lswitch(1:ngrids)
1902 CASE (
'Hout(idUwav)')
1903 IF (iduwav.eq.0)
THEN
1904 IF (master)
WRITE (out,280)
'idUwav'
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'
1916 npts=load_l(nval, cval, ngrids, lswitch)
1917 hout(idvwav,1:ngrids)=lswitch(1:ngrids)
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'
1926 npts=load_l(nval, cval, ngrids, lswitch)
1927 hout(idwdif,1:ngrids)=lswitch(1:ngrids)
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'
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'
1946 npts=load_l(nval, cval, ngrids, lswitch)
1947 hout(idwdiw,1:ngrids)=lswitch(1:ngrids)
1949#if defined WEC_ROLLER
1950 CASE (
'Hout(idWdis)')
1951 IF (idwdis.eq.0)
THEN
1952 IF (master)
WRITE (out,280)
'idWdis'
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'
1964 npts=load_l(nval, cval, ngrids, lswitch)
1965 hout(idwrol,1:ngrids)=lswitch(1:ngrids)
1967#if defined WAVES_DSPR
1968 CASE (
'Hout(idWvds)')
1969 IF (idwvds.eq.0)
THEN
1970 IF (master)
WRITE (out,280)
'idWvds'
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'
1982 npts=load_l(nval, cval, ngrids, lswitch)
1983 hout(idwvqp,1:ngrids)=lswitch(1:ngrids)
1985#if defined INWAVE_MODEL
1986 CASE (
'Hout(idACen)')
1987 IF (idacen.eq.0)
THEN
1988 IF (master)
WRITE (out,280)
'idACen'
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'
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'
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'
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'
2024 npts=load_l(nval, cval, ngrids, lswitch)
2025 hout(idactp,1:ngrids)=lswitch(1:ngrids)
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'
2035 npts=load_l(nval, cval, ngrids, lswitch)
2036 hout(idpair,1:ngrids)=lswitch(1:ngrids)
2038# if defined BULK_FLUXES
2039 CASE (
'Hout(idTair)')
2040 IF (idtair.eq.0)
THEN
2041 IF (master)
WRITE (out,280)
'idTair'
2045 npts=load_l(nval, cval, ngrids, lswitch)
2046 hout(idtair,1:ngrids)=lswitch(1:ngrids)
2048# if defined BULK_FLUXES || defined ECOSIM
2049 CASE (
'Hout(idUair)')
2050 IF (iduair.eq.0)
THEN
2051 IF (master)
WRITE (out,280)
'idUair'
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'
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'
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'
2079 npts=load_l(nval, cval, ngrids, lswitch)
2080 hout(idvain,1:ngrids)=lswitch(1:ngrids)
2082 CASE (
'Hout(idTsur)')
2083 IF (idtsur(itemp).eq.0)
THEN
2084 IF (master)
WRITE (out,280)
'idTsur'
2088 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2092 hout(i,ng)=ltracer(itrc,ng)
2096 CASE (
'Hout(idLhea)')
2097 IF (idlhea.eq.0)
THEN
2098 IF (master)
WRITE (out,280)
'idLhea'
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'
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'
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'
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'
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'
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'
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'
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'
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'
2174 npts=load_l(nval, cval, ngrids, lswitch)
2175 hout(idtdif,1:ngrids)=lswitch(1:ngrids)
2177 CASE (
'Hout(idSdif)')
2178 IF (idsdif.eq.0)
THEN
2179 IF (master)
WRITE (out,280)
'idSdif'
2183 npts=load_l(nval, cval, ngrids, lswitch)
2184 hout(idsdif,1:ngrids)=lswitch(1:ngrids)
2186 CASE (
'Hout(idHsbl)')
2187 IF (idhsbl.eq.0)
THEN
2188 IF (master)
WRITE (out,280)
'idHsbl'
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'
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'
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'
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)
2223 itrc=idtvar(inert(i))
2224 hout(itrc,ng)=linert(i,ng)
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)
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)
2267 CASE (
'Qout(idTvar)')
2268 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2272 qout(i,ng)=ltracer(itrc,ng)
2276 CASE (
'Qout(idUsur)')
2277 IF (idusur.eq.0)
THEN
2278 IF (master)
WRITE (out,280)
'idUsur'
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'
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'
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'
2306 npts=load_l(nval, cval, ngrids, lswitch)
2307 qout(idvsun,1:ngrids)=lswitch(1:ngrids)
2309 CASE (
'Qout(idsurT)')
2310 IF (maxval(idsurt).eq.0)
THEN
2311 IF (master)
WRITE (out,280)
'idsurT'
2315 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2319 qout(i,ng)=ltracer(itrc,ng)
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)
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)
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)
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)
2423 CASE (
'Qout(idWamp)')
2424 npts=load_l(nval, cval, ngrids, lswitch)
2425 qout(idwamp,1:ngrids)=lswitch(1:ngrids)
2428 CASE (
'Qout(idWlen)')
2429 npts=load_l(nval, cval, ngrids, lswitch)
2430 qout(idwlen,1:ngrids)=lswitch(1:ngrids)
2433 CASE (
'Qout(idWlep)')
2434 npts=load_l(nval, cval, ngrids, lswitch)
2435 qout(idwlep,1:ngrids)=lswitch(1:ngrids)
2438 CASE (
'Qout(idWdir)')
2439 npts=load_l(nval, cval, ngrids, lswitch)
2440 qout(idwdir,1:ngrids)=lswitch(1:ngrids)
2443 CASE (
'Qout(idWdip)')
2444 npts=load_l(nval, cval, ngrids, lswitch)
2445 qout(idwdip,1:ngrids)=lswitch(1:ngrids)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
2532 CASE (
'Qout(idTsur)')
2533 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2537 qout(i,ng)=ltracer(itrc,ng)
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)
2572 CASE (
'Qout(idSdif)')
2573 npts=load_l(nval, cval, ngrids, lswitch)
2574 qout(idsdif,1:ngrids)=lswitch(1:ngrids)
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)
2593 itrc=idtvar(inert(i))
2594 qout(itrc,ng)=linert(i,ng)
2597 CASE (
'Qout(Snert)')
2598 npts=load_l(nval, cval, npt, ngrids, linert)
2601 itrc=idsurt(inert(i))
2602 qout(itrc,ng)=linert(i,ng)
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)
2644 CASE (
'Aout(idTvar)')
2645 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2649 aout(i,ng)=ltracer(itrc,ng)
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)
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)
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)
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)
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)
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)
2754 CASE (
'Aout(idWlen)')
2755 npts=load_l(nval, cval, ngrids, lswitch)
2756 aout(idwlen,1:ngrids)=lswitch(1:ngrids)
2758# ifdef WAVES_LENGTHP
2759 CASE (
'Aout(idWlep)')
2760 npts=load_l(nval, cval, ngrids, lswitch)
2761 aout(idwlep,1:ngrids)=lswitch(1:ngrids)
2764 CASE (
'Aout(idWdir)')
2765 npts=load_l(nval, cval, ngrids, lswitch)
2766 aout(idwdir,1:ngrids)=lswitch(1:ngrids)
2769 CASE (
'Aout(idWdip)')
2770 npts=load_l(nval, cval, ngrids, lswitch)
2771 aout(idwdip,1:ngrids)=lswitch(1:ngrids)
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)
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)
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)
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)
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)
2804# ifdef ROLLER_SVENDSEN
2805 CASE (
'Aout(idWbrk)')
2806 npts=load_l(nval, cval, ngrids, lswitch)
2807 aout(idwbrk,1:ngrids)=lswitch(1:ngrids)
2810 CASE (
'Aout(idWdis)')
2811 npts=load_l(nval, cval, ngrids, lswitch)
2812 aout(idwdis,1:ngrids)=lswitch(1:ngrids)
2814# ifdef ROLLER_RENIERS
2815 CASE (
'Aout(idWrol)')
2816 npts=load_l(nval, cval, ngrids, lswitch)
2817 aout(idwrol,1:ngrids)=lswitch(1:ngrids)
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)
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)
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)
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)
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)
2860 CASE (
'Aout(idTsur)')
2861 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
2865 aout(i,ng)=ltracer(itrc,ng)
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)
2897 CASE (
'Aout(idSdif)')
2898 npts=load_l(nval, cval, ngrids, lswitch)
2899 aout(idsdif,1:ngrids)=lswitch(1:ngrids)
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'
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'
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'
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'
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'
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'
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'
2963 npts=load_l(nval, cval, ngrids, lswitch)
2964 aout(idv2dd,1:ngrids)=lswitch(1:ngrids)
2966 CASE (
'Aout(idu3dD)')
2967 IF (idu3dd.eq.0)
THEN
2968 IF (master)
WRITE (out,280)
'idu3dD'
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'
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'
2988 npts=load_l(nval, cval, nat, ngrids, ltracer)
2992 aout(i,ng)=ltracer(itrc,ng)
2998 CASE (
'Aout(idHUav)')
2999 IF (idhuav.eq.0)
THEN
3000 IF (master)
WRITE (out,280)
'idHUav'
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'
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'
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'
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'
3036 npts=load_l(nval, cval, ngrids, lswitch)
3037 aout(idvvav,1:ngrids)=lswitch(1:ngrids)
3039 CASE (
'Aout(idU2av)')
3040 IF (idu2av.eq.0)
THEN
3041 IF (master)
WRITE (out,280)
'idU2av'
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'
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'
3061 npts=load_l(nval, cval, ngrids, lswitch)
3062 aout(idzzav,1:ngrids)=lswitch(1:ngrids)
3064 CASE (
'Aout(idTTav)')
3065 IF (maxval(idttav).eq.0)
THEN
3066 IF (master)
WRITE (out,280)
'idTTav'
3070 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3074 aout(i,ng)=ltracer(itrc,ng)
3077 CASE (
'Aout(idUTav)')
3078 IF (maxval(idutav).eq.0)
THEN
3079 IF (master)
WRITE (out,280)
'idUTav'
3083 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3087 aout(i,ng)=ltracer(itrc,ng)
3090 CASE (
'Aout(idVTav)')
3091 IF (maxval(idvtav).eq.0)
THEN
3092 IF (master)
WRITE (out,280)
'idVTav'
3096 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3100 aout(i,ng)=ltracer(itrc,ng)
3103 CASE (
'Aout(iHUTav)')
3104 IF (maxval(ihutav).eq.0)
THEN
3105 IF (master)
WRITE (out,280)
'iHUTav'
3109 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3113 aout(i,ng)=ltracer(itrc,ng)
3116 CASE (
'Aout(iHVTav)')
3117 IF (maxval(ihvtav).eq.0)
THEN
3118 IF (master)
WRITE (out,280)
'iHVTav'
3122 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3126 aout(i,ng)=ltracer(itrc,ng)
3130# if defined SOLVE3D && defined T_PASSIVE
3131 CASE (
'Aout(inert)')
3132 npts=load_l(nval, cval, npt, ngrids, linert)
3135 itrc=idtvar(inert(i))
3136 aout(itrc,ng)=linert(i,ng)
3141#ifdef DIAGNOSTICS_UV
3142 CASE (
'Dout(M2rate)')
3143 IF (m2rate.le.0)
THEN
3144 IF (master)
WRITE (out,280)
'M2rate'
3148 npts=load_l(nval, cval, ngrids, lswitch)
3150 dout(iddu2d(m2rate),ng)=lswitch(ng)
3151 dout(iddv2d(m2rate),ng)=lswitch(ng)
3153 CASE (
'Dout(M2pgrd)')
3154 IF (m2pgrd.le.0)
THEN
3155 IF (master)
WRITE (out,280)
'M2pgrd'
3159 npts=load_l(nval, cval, ngrids, lswitch)
3161 dout(iddu2d(m2pgrd),ng)=lswitch(ng)
3162 dout(iddv2d(m2pgrd),ng)=lswitch(ng)
3165 CASE (
'Dout(M2fcor)')
3166 IF (m2fcor.le.0)
THEN
3167 IF (master)
WRITE (out,280)
'M2fcor'
3171 npts=load_l(nval, cval, ngrids, lswitch)
3173 dout(iddu2d(m2fcor),ng)=lswitch(ng)
3174 dout(iddv2d(m2fcor),ng)=lswitch(ng)
3178 CASE (
'Dout(M2hadv)')
3179 IF (m2hadv.le.0)
THEN
3180 IF (master)
WRITE (out,280)
'M2hadv'
3184 npts=load_l(nval, cval, ngrids, lswitch)
3186 dout(iddu2d(m2hadv),ng)=lswitch(ng)
3187 dout(iddv2d(m2hadv),ng)=lswitch(ng)
3189 CASE (
'Dout(M2xadv)')
3190 IF (m2xadv.le.0)
THEN
3191 IF (master)
WRITE (out,280)
'M2xadv'
3195 npts=load_l(nval, cval, ngrids, lswitch)
3197 dout(iddu2d(m2xadv),ng)=lswitch(ng)
3198 dout(iddv2d(m2xadv),ng)=lswitch(ng)
3200 CASE (
'Dout(M2yadv)')
3201 IF (m2yadv.le.0)
THEN
3202 IF (master)
WRITE (out,280)
'M2yadv'
3206 npts=load_l(nval, cval, ngrids, lswitch)
3208 dout(iddu2d(m2yadv),ng)=lswitch(ng)
3209 dout(iddv2d(m2yadv),ng)=lswitch(ng)
3213 CASE (
'Dout(M2hjvf)')
3214 IF (m2hjvf.le.0)
THEN
3215 IF (master)
WRITE (out,280)
'M2hjvf'
3219 npts=load_l(nval, cval, ngrids, lswitch)
3221 dout(iddu2d(m2hjvf),ng)=lswitch(ng)
3222 dout(iddv2d(m2hjvf),ng)=lswitch(ng)
3224 CASE (
'Dout(M2kvrf)')
3225 IF (m2kvrf.le.0)
THEN
3226 IF (master)
WRITE (out,280)
'M2kvrf'
3230 npts=load_l(nval, cval, ngrids, lswitch)
3232 dout(iddu2d(m2kvrf),ng)=lswitch(ng)
3233 dout(iddv2d(m2kvrf),ng)=lswitch(ng)
3236 CASE (
'Dout(M2fsco)')
3237 IF (m2fsco.le.0)
THEN
3238 IF (master)
WRITE (out,280)
'M2fsco'
3242 npts=load_l(nval, cval, ngrids, lswitch)
3244 dout(iddu2d(m2fsco),ng)=lswitch(ng)
3245 dout(iddv2d(m2fsco),ng)=lswitch(ng)
3248# ifdef SURFACE_STREAMING
3249 CASE (
'Dout(M2sstm)')
3250 IF (m2sstm.le.0)
THEN
3251 IF (master)
WRITE (out,280)
'M2sstm'
3255 npts=load_l(nval, cval, ngrids, lswitch)
3257 dout(iddu2d(m2sstm),ng)=lswitch(ng)
3258 dout(iddv2d(m2sstm),ng)=lswitch(ng)
3261# ifdef BOTTOM_STREAMING
3262 CASE (
'Dout(M2bstm)')
3263 IF (m2bstm.le.0)
THEN
3264 IF (master)
WRITE (out,280)
'M2bstm'
3268 npts=load_l(nval, cval, ngrids, lswitch)
3270 dout(iddu2d(m2bstm),ng)=lswitch(ng)
3271 dout(iddv2d(m2bstm),ng)=lswitch(ng)
3274 CASE (
'Dout(M2wrol)')
3275 IF (m2wrol.le.0)
THEN
3276 IF (master)
WRITE (out,280)
'M2wrol'
3280 npts=load_l(nval, cval, ngrids, lswitch)
3282 dout(iddu2d(m2wrol),ng)=lswitch(ng)
3283 dout(iddv2d(m2wrol),ng)=lswitch(ng)
3285 CASE (
'Dout(M2wbrk)')
3286 IF (m2wbrk.le.0)
THEN
3287 IF (master)
WRITE (out,280)
'M2wbrk'
3291 npts=load_l(nval, cval, ngrids, lswitch)
3293 dout(iddu2d(m2wbrk),ng)=lswitch(ng)
3294 dout(iddv2d(m2wbrk),ng)=lswitch(ng)
3296 CASE (
'Dout(M2zeta)')
3297 IF (m2zeta.le.0)
THEN
3298 IF (master)
WRITE (out,280)
'M2zeta'
3302 npts=load_l(nval, cval, ngrids, lswitch)
3304 dout(iddu2d(m2zeta),ng)=lswitch(ng)
3305 dout(iddv2d(m2zeta),ng)=lswitch(ng)
3307 CASE (
'Dout(M2zetw)')
3308 IF (m2zetw.le.0)
THEN
3309 IF (master)
WRITE (out,280)
'M2zetw'
3313 npts=load_l(nval, cval, ngrids, lswitch)
3315 dout(iddu2d(m2zetw),ng)=lswitch(ng)
3316 dout(iddv2d(m2zetw),ng)=lswitch(ng)
3318 CASE (
'Dout(M2zqsp)')
3319 IF (m2zqsp.le.0)
THEN
3320 IF (master)
WRITE (out,280)
'M2zqsp'
3324 npts=load_l(nval, cval, ngrids, lswitch)
3326 dout(iddu2d(m2zqsp),ng)=lswitch(ng)
3327 dout(iddv2d(m2zqsp),ng)=lswitch(ng)
3329 CASE (
'Dout(M2zbeh)')
3330 IF (m2zbeh.le.0)
THEN
3331 IF (master)
WRITE (out,280)
'M2zbeh'
3335 npts=load_l(nval, cval, ngrids, lswitch)
3337 dout(iddu2d(m2zbeh),ng)=lswitch(ng)
3338 dout(iddv2d(m2zbeh),ng)=lswitch(ng)
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'
3348 npts=load_l(nval, cval, ngrids, lswitch)
3350 dout(iddu2d(m2hvis),ng)=lswitch(ng)
3351 dout(iddv2d(m2hvis),ng)=lswitch(ng)
3353 CASE (
'Dout(M2xvis)')
3354 IF (m2xvis.le.0)
THEN
3355 IF (master)
WRITE (out,280)
'M2xvis'
3359 npts=load_l(nval, cval, ngrids, lswitch)
3361 dout(iddu2d(m2xvis),ng)=lswitch(ng)
3362 dout(iddv2d(m2xvis),ng)=lswitch(ng)
3364 CASE (
'Dout(M2yvis)')
3365 IF (m2yvis.le.0)
THEN
3366 IF (master)
WRITE (out,280)
'M2yvis'
3370 npts=load_l(nval, cval, ngrids, lswitch)
3372 dout(iddu2d(m2yvis),ng)=lswitch(ng)
3373 dout(iddv2d(m2yvis),ng)=lswitch(ng)
3376 CASE (
'Dout(M2sstr)')
3377 IF (m2sstr.le.0)
THEN
3378 IF (master)
WRITE (out,280)
'M2sstr'
3382 npts=load_l(nval, cval, ngrids, lswitch)
3384 dout(iddu2d(m2sstr),ng)=lswitch(ng)
3385 dout(iddv2d(m2sstr),ng)=lswitch(ng)
3387 CASE (
'Dout(M2bstr)')
3388 IF (m2bstr.le.0)
THEN
3389 IF (master)
WRITE (out,280)
'M2bstr'
3393 npts=load_l(nval, cval, ngrids, lswitch)
3395 dout(iddu2d(m2bstr),ng)=lswitch(ng)
3396 dout(iddv2d(m2bstr),ng)=lswitch(ng)
3399 CASE (
'Dout(M3rate)')
3400 IF (m3rate.le.0)
THEN
3401 IF (master)
WRITE (out,280)
'M3rate'
3405 npts=load_l(nval, cval, ngrids, lswitch)
3407 dout(iddu3d(m3rate),ng)=lswitch(ng)
3408 dout(iddv3d(m3rate),ng)=lswitch(ng)
3410 CASE (
'Dout(M3pgrd)')
3411 IF (m3pgrd.le.0)
THEN
3412 IF (master)
WRITE (out,280)
'M3pgrd'
3416 npts=load_l(nval, cval, ngrids, lswitch)
3418 dout(iddu3d(m3pgrd),ng)=lswitch(ng)
3419 dout(iddv3d(m3pgrd),ng)=lswitch(ng)
3422 CASE (
'Dout(M3fcor)')
3423 IF (m3fcor.le.0)
THEN
3424 IF (master)
WRITE (out,280)
'M3fcor'
3428 npts=load_l(nval, cval, ngrids, lswitch)
3430 dout(iddu3d(m3fcor),ng)=lswitch(ng)
3431 dout(iddv3d(m3fcor),ng)=lswitch(ng)
3435 CASE (
'Dout(M3hadv)')
3436 IF (m3hadv.le.0)
THEN
3437 IF (master)
WRITE (out,280)
'M3hadv'
3441 npts=load_l(nval, cval, ngrids, lswitch)
3443 dout(iddu3d(m3hadv),ng)=lswitch(ng)
3444 dout(iddv3d(m3hadv),ng)=lswitch(ng)
3446 CASE (
'Dout(M3xadv)')
3447 IF (m3xadv.le.0)
THEN
3448 IF (master)
WRITE (out,280)
'M3xadv'
3452 npts=load_l(nval, cval, ngrids, lswitch)
3454 dout(iddu3d(m3xadv),ng)=lswitch(ng)
3455 dout(iddv3d(m3xadv),ng)=lswitch(ng)
3457 CASE (
'Dout(M3yadv)')
3458 IF (m3yadv.le.0)
THEN
3459 IF (master)
WRITE (out,280)
'M3yadv'
3463 npts=load_l(nval, cval, ngrids, lswitch)
3465 dout(iddu3d(m3yadv),ng)=lswitch(ng)
3466 dout(iddv3d(m3yadv),ng)=lswitch(ng)
3468 CASE (
'Dout(M3vadv)')
3469 IF (m3vadv.le.0)
THEN
3470 IF (master)
WRITE (out,280)
'M3vadv'
3474 npts=load_l(nval, cval, ngrids, lswitch)
3476 dout(iddu3d(m3vadv),ng)=lswitch(ng)
3477 dout(iddv3d(m3vadv),ng)=lswitch(ng)
3481 CASE (
'Dout(M3hjvf)')
3482 IF (m3hjvf.le.0)
THEN
3483 IF (master)
WRITE (out,280)
'M3hjvf'
3487 npts=load_l(nval, cval, ngrids, lswitch)
3489 dout(iddu3d(m3hjvf),ng)=lswitch(ng)
3490 dout(iddv3d(m3hjvf),ng)=lswitch(ng)
3492 CASE (
'Dout(M3vjvf)')
3493 IF (m3vjvf.le.0)
THEN
3494 IF (master)
WRITE (out,280)
'M3vjvf'
3498 npts=load_l(nval, cval, ngrids, lswitch)
3500 dout(iddu3d(m3vjvf),ng)=lswitch(ng)
3501 dout(iddv3d(m3vjvf),ng)=lswitch(ng)
3503 CASE (
'Dout(M3kvrf)')
3504 IF (m3kvrf.le.0)
THEN
3505 IF (master)
WRITE (out,280)
'M3kvrf'
3509 npts=load_l(nval, cval, ngrids, lswitch)
3511 dout(iddu3d(m3kvrf),ng)=lswitch(ng)
3512 dout(iddv3d(m3kvrf),ng)=lswitch(ng)
3515 CASE (
'Dout(M3fsco)')
3516 IF (m3fsco.le.0)
THEN
3517 IF (master)
WRITE (out,280)
'M3fsco'
3521 npts=load_l(nval, cval, ngrids, lswitch)
3523 dout(iddu3d(m3fsco),ng)=lswitch(ng)
3524 dout(iddv3d(m3fsco),ng)=lswitch(ng)
3527# ifdef SURFACE_STREAMING
3528 CASE (
'Dout(M3sstm)')
3529 IF (m3sstm.le.0)
THEN
3530 IF (master)
WRITE (out,280)
'M3sstm'
3534 npts=load_l(nval, cval, ngrids, lswitch)
3536 dout(iddu3d(m3sstm),ng)=lswitch(ng)
3537 dout(iddv3d(m3sstm),ng)=lswitch(ng)
3540# ifdef BOTTOM_STREAMING
3541 CASE (
'Dout(M3bstm)')
3542 IF (m3bstm.le.0)
THEN
3543 IF (master)
WRITE (out,280)
'M3bstm'
3547 npts=load_l(nval, cval, ngrids, lswitch)
3549 dout(iddu3d(m3bstm),ng)=lswitch(ng)
3550 dout(iddv3d(m3bstm),ng)=lswitch(ng)
3553 CASE (
'Dout(M3wrol)')
3554 IF (m3wrol.le.0)
THEN
3555 IF (master)
WRITE (out,280)
'M3wrol'
3559 npts=load_l(nval, cval, ngrids, lswitch)
3561 dout(iddu3d(m3wrol),ng)=lswitch(ng)
3562 dout(iddv3d(m3wrol),ng)=lswitch(ng)
3564 CASE (
'Dout(M3wbrk)')
3565 IF (m3wbrk.le.0)
THEN
3566 IF (master)
WRITE (out,280)
'M3wbrk'
3570 npts=load_l(nval, cval, ngrids, lswitch)
3572 dout(iddu3d(m3wbrk),ng)=lswitch(ng)
3573 dout(iddv3d(m3wbrk),ng)=lswitch(ng)
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'
3583 npts=load_l(nval, cval, ngrids, lswitch)
3585 dout(iddu3d(m3hvis),ng)=lswitch(ng)
3586 dout(iddv3d(m3hvis),ng)=lswitch(ng)
3588 CASE (
'Dout(M3xvis)')
3589 IF (m3xvis.le.0)
THEN
3590 IF (master)
WRITE (out,280)
'M3xvis'
3594 npts=load_l(nval, cval, ngrids, lswitch)
3596 dout(iddu3d(m3xvis),ng)=lswitch(ng)
3597 dout(iddv3d(m3xvis),ng)=lswitch(ng)
3599 CASE (
'Dout(M3yvis)')
3600 IF (m3yvis.le.0)
THEN
3601 IF (master)
WRITE (out,280)
'M3yvis'
3605 npts=load_l(nval, cval, ngrids, lswitch)
3607 dout(iddu3d(m3yvis),ng)=lswitch(ng)
3608 dout(iddv3d(m3yvis),ng)=lswitch(ng)
3611 CASE (
'Dout(M3vvis)')
3612 IF (m3vvis.le.0)
THEN
3613 IF (master)
WRITE (out,280)
'M3vvis'
3617 npts=load_l(nval, cval, ngrids, lswitch)
3619 dout(iddu3d(m3vvis),ng)=lswitch(ng)
3620 dout(iddv3d(m3vvis),ng)=lswitch(ng)
3624#if defined DIAGNOSTICS_TS && defined SOLVE3D
3625 CASE (
'Dout(iTrate)')
3626 IF (itrate.le.0)
THEN
3627 IF (master)
WRITE (out,280)
'iTrate'
3631 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3634 dout(iddtrc(itrc,itrate),ng)=ltracer(itrc,ng)
3639 dout(iddtrc(itrc,itrate),ng)=ltracer(nat+i,ng)
3643 CASE (
'Dout(iThadv)')
3644 IF (ithadv.le.0)
THEN
3645 IF (master)
WRITE (out,280)
'iThadv'
3649 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3652 dout(iddtrc(itrc,ithadv),ng)=ltracer(itrc,ng)
3657 dout(iddtrc(itrc,ithadv),ng)=ltracer(nat+i,ng)
3661 CASE (
'Dout(iTxadv)')
3662 IF (itxadv.le.0)
THEN
3663 IF (master)
WRITE (out,280)
'iTxadv'
3667 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3670 dout(iddtrc(itrc,itxadv),ng)=ltracer(itrc,ng)
3675 dout(iddtrc(itrc,itxadv),ng)=ltracer(nat+i,ng)
3679 CASE (
'Dout(iTyadv)')
3680 IF (ityadv.le.0)
THEN
3681 IF (master)
WRITE (out,280)
'iTyadv'
3685 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3688 dout(iddtrc(itrc,ityadv),ng)=ltracer(itrc,ng)
3693 dout(iddtrc(itrc,ityadv),ng)=ltracer(nat+i,ng)
3697 CASE (
'Dout(iTvadv)')
3698 IF (itvadv.le.0)
THEN
3699 IF (master)
WRITE (out,280)
'iTvadv'
3703 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3706 dout(iddtrc(itrc,itvadv),ng)=ltracer(itrc,ng)
3711 dout(iddtrc(itrc,itvadv),ng)=ltracer(nat+i,ng)
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'
3722 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3725 dout(iddtrc(itrc,ithdif),ng)=ltracer(itrc,ng)
3730 dout(iddtrc(itrc,ithdif),ng)=ltracer(nat+i,ng)
3734 CASE (
'Dout(iTxdif)')
3735 IF (itxdif.le.0)
THEN
3736 IF (master)
WRITE (out,280)
'iTxdif'
3740 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3743 dout(iddtrc(itrc,itxdif),ng)=ltracer(itrc,ng)
3748 dout(iddtrc(itrc,itxdif),ng)=ltracer(nat+i,ng)
3752 CASE (
'Dout(iTydif)')
3753 IF (itydif.le.0)
THEN
3754 IF (master)
WRITE (out,280)
'iTydif'
3758 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3761 dout(iddtrc(itrc,itydif),ng)=ltracer(itrc,ng)
3766 dout(iddtrc(itrc,itydif),ng)=ltracer(nat+i,ng)
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'
3777 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3780 dout(iddtrc(itrc,itsdif),ng)=ltracer(itrc,ng)
3785 dout(iddtrc(itrc,itsdif),ng)=ltracer(nat+i,ng)
3791 CASE (
'Dout(iTvdif)')
3792 IF (itvdif.le.0)
THEN
3793 IF (master)
WRITE (out,280)
'iTvdif'
3797 npts=load_l(nval, cval, nat+npt, ngrids, ltracer)
3800 dout(iddtrc(itrc,itvdif),ng)=ltracer(itrc,ng)
3805 dout(iddtrc(itrc,itvdif),ng)=ltracer(nat+i,ng)
3811 npts=load_i(nval, rval, 1, ivalue)
3813 IF (nuser.gt.0)
THEN
3814 IF (
allocated(user))
deallocate (user)
3815 allocate ( user(nuser) )
3819 IF (nuser.gt.0)
THEN
3820 npts=load_r(nval, rval, nuser, user)
3823 npts=load_i(nval, rval, 1, ivalue)
3824#if defined PIO_LIB && defined DISTRIBUTE
3826 IF ((inp_lib.lt.1).or.(inp_lib.gt.2))
THEN
3827 IF (master)
WRITE (out,260)
'inp_lib = ', &
3829 &
'Must be either 1 or 2'
3837 npts=load_i(nval, rval, 1, ivalue)
3838#if defined PIO_LIB && defined DISTRIBUTE
3840 IF ((inp_lib.lt.1).or.(inp_lib.gt.2))
THEN
3841 IF (master)
WRITE (out,260)
'out_lib = ', &
3843 &
'Must be either 1 or 2'
3850 CASE (
'ExtractFlag')
3851 npts=load_i(nval, rval, ngrids, extractflag)
3853#if defined PIO_LIB && defined DISTRIBUTE
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 = ', &
3859 &
'Must be between 1 and 4'
3861 SELECT CASE (ivalue(1))
3864 pio_method=pio_iotype_pnetcdf
3865 pio_methodname=
'PnetCDF'
3868 pio_method=pio_iotype_pnetcdf
3869 pio_methodname=
'PnetCDF'
3871 pio_method=pio_iotype_netcdf
3872 pio_methodname=
'NetCDF'
3874 pio_method=pio_iotype_netcdf4c
3875 pio_methodname=
'NetCDF4c'
3877 pio_method=pio_iotype_netcdf4p
3878 pio_methodname=
'NetCDF4p'
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 = ', &
3888 &
'Must be between 1 and NtileI*NtileJ'
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 = ', &
3899 &
'Must be greater than 0 and not exceed NtileI*NtileJ'
3904 npts=load_i(nval, rval, 1, ivalue)
3906 IF (pio_base.lt.0)
THEN
3907 IF (master)
WRITE (out,260)
'pio_base = ', &
3909 &
'Is usually 0 or greater'
3913 IF ((numthreads.eq.1).and.(pio_base.ne.0))
THEN
3914 IF (master)
WRITE (out,260)
'pio_base = ', &
3916 &
'Reset to 0 since running on a single process'
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 = ', &
3926 &
'Must be greater than 0'
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 = ', &
3939 SELECT CASE (ivalue(1))
3941 pio_rearranger=pio_rearr_box
3943 pio_rearranger=pio_rearr_subset
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 = ', &
3955 SELECT CASE (ivalue(1))
3957 pio_rearr_comm=pio_rearr_comm_p2p
3959 pio_rearr_comm=pio_rearr_comm_coll
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 = ', &
3967 &
'Must be between 0 and 3'
3971 SELECT CASE (ivalue(1))
3973 pio_rearr_fcd=pio_rearr_comm_fc_2d_enable
3975 pio_rearr_fcd=pio_rearr_comm_fc_1d_comp2io
3977 pio_rearr_fcd=pio_rearr_comm_fc_1d_io2comp
3979 pio_rearr_fcd=pio_rearr_comm_fc_2d_disable
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
3993 pio_rearr_c2i_pr=ivalue(1)
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
4006 pio_rearr_i2c_pr=ivalue(1)
4010 npts=load_i(nval, rval, 1, ivalue)
4013 npts=load_i(nval, rval, 1, ivalue)
4016 npts=load_i(nval, rval, 1, ivalue)
4017 deflate_level=ivalue(1)
4019 label=
'DAI - Data Assimilation Initial/Restart fields'
4020 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4021 & ngrids, nfiles, out_lib, dai)
4023 label=
'GST - generalized stability theory analysis'
4024 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4025 & ngrids, nfiles, out_lib, gst)
4027 label=
'RST - restart fields'
4028 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4029 & ngrids, nfiles, out_lib, rst)
4031 label=
'HIS - nonlinear model history fields'
4032 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4033 & ngrids, nfiles, out_lib, his)
4035 label=
'XTR - nonlinear model extraction history fields'
4036 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4037 & ngrids, nfiles, out_lib, xtr)
4039 label=
'QCK - nonlinear model quicksave fields'
4040 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4041 & ngrids, nfiles, out_lib, qck)
4043 label=
'TLM - tangent linear model history fields'
4044 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4045 & ngrids, nfiles, out_lib, tlm)
4047 label=
'TLF - tangent linear model impulse forcing'
4048 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4049 & ngrids, nfiles, out_lib, tlf)
4051 label=
'ADM - adjoint model history fields'
4052 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4053 & ngrids, nfiles, out_lib, adm)
4055 label=
'AVG - time-averaged history fields'
4056 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4057 & ngrids, nfiles, out_lib, avg)
4059 label=
'HAR - least-squares detiding harmonics'
4060 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4061 & ngrids, nfiles, out_lib, har)
4063 label=
'DIA - time-averaged diagnostics fields'
4064 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4065 & ngrids, nfiles, out_lib, dia)
4067 label=
'STA - stations time-series'
4068 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4069 & ngrids, nfiles, out_lib, sta)
4071 label=
'FLT - Lagragian particles trajectories'
4072 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4073 & ngrids, nfiles, out_lib, flt)
4075 label=
'GRD - application grid'
4076 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4077 & ngrids, nfiles, inp_lib, grd)
4079 label=
'GRX - I/O histrory extract grid'
4080 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4081 & ngrids, nfiles, inp_lib, grx)
4083 label=
'INI - nonlinear model initial conditions'
4084 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4085 & ngrids, nfiles, inp_lib, ini)
4087 label=
'IRP - representer model initial conditions'
4088 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4089 & ngrids, nfiles, inp_lib, irp)
4091 label=
'ITL - tangent linear model initial conditions'
4092 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4093 & ngrids, nfiles, inp_lib, itl)
4095 label=
'IAD - adjoint model initial conditions'
4096 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4097 & ngrids, nfiles, inp_lib, iad)
4099 label=
'FWD - basic state forward trajectory'
4100 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4101 & ngrids, nfiles, inp_lib, fwd)
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
4109 label=
'FOIA - adjoint sensitivity functional A'
4110 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4111 & ngrids, nfiles, inp_lib, foia)
4113 label=
'FOIB - adjoint sensitivity functional B'
4114 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4115 & ngrids, nfiles, inp_lib, foib)
4118 label=
'FCTA - forecast state forward trajectory A'
4119 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4120 & ngrids, nfiles, inp_lib, fcta)
4122 label=
'FCTB - forecast state forward trajectory B'
4123 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4124 & ngrids, nfiles, inp_lib, fctb)
4130 ngcname=trim(adjustl(cval(nval)))
4132 npts=load_i(nval, rval, ngrids, nbcfiles)
4134 IF (nbcfiles(ng).le.0)
THEN
4135 IF (master)
WRITE (out,260)
'NBCFILES', nbcfiles(ng), &
4136 &
'Must be equal or greater than one.'
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) )
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
4152 nbccount(1:max_ffiles,1:ngrids)=0
4154 label=
'BRY - lateral open boundary conditions'
4156 IF (nbcfiles(ng).lt.0)
THEN
4157 IF (master)
WRITE (out,290)
'nBCfiles = ', &
4159 &
'KeyWord ''NBCFILES'' unread or misssing from '// &
4160 &
'input script ''roms.in''.'
4165 npts=load_s2d(nval, cval, cdim, line, label, ibcfile, &
4166 & igrid, ngrids, nbcfiles, nbccount, &
4167 & max_ffiles, inp_lib, bry)
4169 npts=load_i(nval, rval, ngrids, nclmfiles)
4171 IF (nclmfiles(ng).le.0)
THEN
4172 IF (master)
WRITE (out,260)
'NCLMFILES', &
4174 &
'Must be equal or greater than one.'
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) )
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
4190 nclmcount(1:max_ffiles,1:ngrids)=0
4192 label=
'CLM - climatology fields'
4194 IF (nclmfiles(ng).lt.0)
THEN
4195 IF (master)
WRITE (out,290)
'nCLMfiles = ', &
4197 &
'KeyWord ''NCLMFILES'' unread or misssing from '// &
4198 &
'input script ''roms.in''.'
4203 npts=load_s2d(nval, cval, cdim, line, label, iclmfile, &
4204 & igrid, ngrids, nclmfiles, nclmcount, &
4205 & max_ffiles, inp_lib, clm)
4207 label=
'NUD - nudging coefficients'
4208 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4209 & ngrids, nfiles, inp_lib, nud)
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
4217 label=
'TIDE - Tidal forcing fields'
4218 npts=load_s1d(nval, cval, cdim, line, label, igrid, &
4219 & ngrids, nfiles, inp_lib, tide)
4222 npts=load_i(nval, rval, ngrids, nffiles)
4224 IF (nffiles(ng).le.0)
THEN
4225 IF (master)
WRITE (out,260)
'NFFILES', nffiles(ng), &
4226 &
'Must be equal or greater than one.'
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) )
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
4242 ncount(1:max_ffiles,1:ngrids)=0
4244 label=
'FRC - forcing fields'
4246 IF (nffiles(ng).lt.0)
THEN
4247 IF (master)
WRITE (out,290)
'nFfiles = ', &
4249 &
'KeyWord ''NFFILES'' unread or misssing from '// &
4250 &
'input script ''roms.in''.'
4255 npts=load_s2d(nval, cval, cdim, line, label, ifile, &
4256 & igrid, ngrids, nffiles, ncount, max_ffiles, &
4262 aparnam=trim(adjustl(cval(nval)))
4267 sposnam=trim(adjustl(cval(nval)))
4272 fposnam=trim(adjustl(cval(nval)))
4277 iparnam=trim(adjustl(cval(nval)))
4282 bparnam=trim(adjustl(cval(nval)))
4287 sparnam=trim(adjustl(cval(nval)))
4292 usrname=trim(adjustl(cval(nval)))
4294 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
4297 10
IF (master)
WRITE (out,50) line
4311 IF (.not.got_nestlayers)
THEN
4313 IF (.not.
allocated(gridsinlayer))
THEN
4314 allocate ( gridsinlayer(nestlayers) )
4316 IF (.not.
allocated(gridnumber))
THEN
4317 allocate ( gridnumber(ngrids,nestlayers) )
4323 IF (.not.got_nestlayers)
THEN
4325 WRITE (out,320)
'NestLayers', &
4326 &
'Add "NestLayers" keyword after "Ngrids".'
4331 IF (.not.
allocated(gridsinlayer))
THEN
4333 WRITE (out,320)
'GridsInLayer', &
4334 &
'Add "GridsInLayer" keyword after "NestLayers".'
4347 IF (mod((ntimes(ng)/nhis(ng)),nsaddle).ne.0)
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.'
4362# if defined FORWARD_FLUXES && \
4363 (defined bulk_fluxes || defined frc_coupling)
4370 qout(idusms,ng)=.true.
4371 qout(idvsms,ng)=.true.
4373 qout(idpair,ng)=.true.
4376 qout(idsrad,ng)=.true.
4377 qout(idtsur(itemp),ng)=.true.
4378# if defined EMINUSP || defined FRC_COUPLING
4379 qout(idempf,ng)=.true.
4385#if defined FORWARD_MIXING && defined SOLVE3D && \
4386 (defined gls_mixing || defined lmd_mixing || \
4387 defined my25_mixing)
4393 hout(idsdif,ng)=.true.
4394 hout(idtdif,ng)=.true.
4395 hout(idvvis,ng)=.true.
4399#if defined FORCING_SV || defined SO_SEMI || \
4400 defined stochastic_opt
4406 IF (scalars(ng)%Fstate(isfsur)) hout(idfsur,ng)=.true.
4408 IF (scalars(ng)%Fstate(isubar)) hout(idubar,ng)=.true.
4409 IF (scalars(ng)%Fstate(isvbar)) hout(idvbar,ng)=.true.
4411 IF (scalars(ng)%Fstate(isuvel)) hout(iduvel,ng)=.true.
4412 IF (scalars(ng)%Fstate(isvvel)) hout(idvvel,ng)=.true.
4414 IF (scalars(ng)%Fstate(istvar(itrc)))
THEN
4415 hout(idtvar(itrc),ng)=.true.
4417 IF (scalars(ng)%Fstate(istsur(itrc)))
THEN
4418 hout(idtsur(itrc),ng)=.true.
4422 IF (scalars(ng)%Fstate(isustr)) hout(idusms,ng)=.true.
4423 IF (scalars(ng)%Fstate(isvstr)) hout(idvsms,ng)=.true.
4431 IF (.not.hout(idu2de,ng).and.hout(idv2dn,ng))
THEN
4432 hout(idu2de,ng)=.true.
4434 IF (.not.hout(idv2dn,ng).and.hout(idu2de,ng))
THEN
4435 hout(idv2dn,ng)=.true.
4438 IF (.not.hout(idu3de,ng).and.hout(idv3dn,ng))
THEN
4439 hout(idu3de,ng)=.true.
4441 IF (.not.hout(idv3dn,ng).and.hout(idu3de,ng))
THEN
4442 hout(idv3dn,ng)=.true.
4446 IF (.not.aout(idu2de,ng).and.aout(idv2dn,ng))
THEN
4447 aout(idu2de,ng)=.true.
4449 IF (.not.aout(idv2dn,ng).and.aout(idu2de,ng))
THEN
4450 aout(idv2dn,ng)=.true.
4453 IF (.not.aout(idu3de,ng).and.aout(idv3dn,ng))
THEN
4454 aout(idu3de,ng)=.true.
4456 IF (.not.aout(idv3dn,ng).and.aout(idu3de,ng))
THEN
4457 aout(idv3dn,ng)=.true.
4469 IF ((nhis(ng).gt.0).and.any(hout(:,ng)))
THEN
4477 IF ((nxtr(ng).gt.0).and.any(hout(:,ng)))
THEN
4484 IF ((nqck(ng).gt.0).and.any(qout(:,ng)))
THEN
4488# if defined AVERAGES && defined AVERAGES_DETIDE && \
4489 (defined ssh_tides || defined uv_tides)
4494 IF (nrrec(ng).ne.0)
THEN
4495 ldeftide(ng)=.false.
4502 IF (lsshclm(ng)) clm_file(ng)=.true.
4505 IF (lm2clm(ng)) clm_file(ng)=.true.
4509 IF (lm3clm(ng)) clm_file(ng)=.true.
4512 IF (any(ltracerclm(:,ng))) clm_file(ng)=.true.
4514# if defined TS_MIX_CLIMA && (defined TS_DIF2 || defined TS_DIF4)
4519#if defined I4DVAR || defined WEAK_CONSTRAINT
4523 lcycleadj(ng)=.false.
4526#if defined AVERAGES && defined AVERAGES_DETIDE && \
4527 (defined ssh_tides || defined uv_tides)
4532 IF (.not.aout(idfsur,ng).and.aout(idfsud,ng))
THEN
4533 aout(idfsur,ng)=.true.
4535 IF (.not.aout(idubar,ng).and.aout(idu2dd,ng))
THEN
4536 aout(idubar,ng)=.true.
4538 IF (.not.aout(idvbar,ng).and.aout(idv2dd,ng))
THEN
4539 aout(idvbar,ng)=.true.
4542 IF (.not.aout(iduvel,ng).and.aout(idu3dd,ng))
THEN
4543 aout(iduvel,ng)=.true.
4545 IF (.not.aout(idvvel,ng).and.aout(idv3dd,ng))
THEN
4546 aout(idvvel,ng)=.true.
4549 IF (.not.aout(idtvar(itrc),ng).and. &
4550 & aout(idtrcd(itrc),ng))
THEN
4551 aout(idtvar(itrc),ng)=.true.
4563#if defined RBL4DVAR || defined R4DVAR
4568 IF (nadj(ng).gt.ntimes(ng))
THEN
4572#if defined I4DVAR || defined RBL4DVAR || defined R4DVAR
4583 IF (nrst(ng).gt.ntimes(ng))
THEN
4587#if defined STOCHASTIC_OPT && !defined STOCH_OPT_WHITE
4592 nadj(ng)=ntimes(ng)/nintervals
4594#if defined FOUR_DVAR || defined IMPULSE
4599# if defined CORRELATION || defined WEAK_CONSTRAINT
4603 IF (nadj(ng).lt.ntimes(ng))
THEN
4616#ifdef WEAK_CONSTRAINT
4624 ntlm(ng)=ntimes(ng)/nsaddle
4630 lcycletlm(ng)=.false.
4633 lcycletlm(ng)=.false.
4637#if defined TIME_CONV && defined WEAK_CONSTRAINT
4641 nrectc(ng)=(ntimes(ng)/nadj(ng))+1
4643#if defined FOUR_DVAR
4653# if defined I4DVAR || defined I4DVAR_ANA_SENSITIVITY
4660 IF (((nrrec(ng).eq.0).and.(navg(ng).gt.ntimes(ng))).or. &
4661 & (navg(ng).eq.0))
THEN
4664 IF (((nrrec(ng).eq.0).and.(ndia(ng).gt.ntimes(ng))).or. &
4665 & (ndia(ng).eq.0))
THEN
4668 IF (((nrrec(ng).eq.0).and.(nflt(ng).gt.ntimes(ng))).or. &
4669 & (nflt(ng).eq.0))
THEN
4672 IF (((nrrec(ng).eq.0).and.(nhis(ng).gt.ntimes(ng))).or. &
4673 & (nhis(ng).eq.0))
THEN
4676 IF (((nrrec(ng).eq.0).and.(nqck(ng).gt.ntimes(ng))).or. &
4677 & (nqck(ng).eq.0))
THEN
4680 IF (((nrrec(ng).eq.0).and.(nrst(ng).gt.ntimes(ng))).or. &
4681 & (nrst(ng).eq.0))
THEN
4684 IF (((nrrec(ng).eq.0).and.(nsta(ng).gt.ntimes(ng))).or. &
4685 & (nsta(ng).eq.0))
THEN
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)
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)
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)
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)
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
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
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
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
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
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
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
4798#ifdef FORWARD_FLUXES
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
4815 blk(ng)%Vid(1:nv)=-1
4816 blk(ng)%Tid(1:mt)=-1
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)
4823 blk(ng)%head(i:i)=blank
4824 blk(ng)%base(i:i)=blank
4825 blk(ng)%name(i:i)=blank
4829 blk(ng)%files(k)(i:i)=blank
4839#if defined PIO_LIB && defined DISTRIBUTE
4840# ifdef ASYNCHRONOUS_SCORPIO
4848 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
4854 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
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), &
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, &
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, &
4887# if !(defined PIO_LIB && \
4888 (defined asynchronous_pio || defined asynchronous_scorpio)) && \
4890 & ocn_comm_world, numthreads, &
4895 & trim(git_url), trim(git_rev), &
4897 & trim(svn_url), trim(svn_rev), &
4898 & trim(rdir), trim(hdir), trim(hfile), trim(adir)
4906 WRITE (out,70) ng, lm(ng), mm(ng), n(ng), numthreads, &
4907 & ntilei(ng), ntilej(ng)
4909 npets=ntilei(ng)*ntilej(ng)
4910 label=
'NtileI * NtileJ ='
4914# ifdef CONCURRENT_KERNEL
4916 npets=ntilei(ng)*ntilej(ng)*nsaddle*2
4917 label=
'NtileI * NtileJ * Nsaddle * 2 ='
4920 npets=ntilei(ng)*ntilej(ng)*nsaddle
4921 label=
'NtileI * NtileJ * Nsaddle ='
4925 npets=ntilei(ng)*ntilej(ng)
4926 label=
'NtileI * NtileJ ='
4929# if defined PIO_LIB && defined DISTRIBUTE && \
4930 (defined asynchronous_pio || defined asynchronous_scorpio)
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 ='
4936 npets=(ntilei(ng)*ntilej(ng))
4937 label=
'NtileI * NtileJ ='
4940 IF (npets.ne.maxpets)
THEN
4941 WRITE (out,80) ng, trim(label), npets, maxpets
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
4953 IF (mod(ntilei(ng)*ntilej(ng),numthreads).ne.0)
THEN
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.'
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.'
4981 WRITE (out,120) nouter,
'Nouter', &
4982 &
'Maximun number of 4DVAR outer loop iterations.'
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 || \
4990 WRITE (out,120) ninner,
'Ninner', &
4991 &
'Maximum number of 4D-Var inner loop iterations.'
4993 WRITE (out,120) nsaddle,
'Nsaddle', &
4994 &
'Number of intervals for saddle point algorithm.'
4997#ifdef STOCHASTIC_OPT
4998 WRITE (out,120) nintervals,
'Nintervals', &
4999 &
'Number of stochastic optimals timestep intervals.'
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.'
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.'
5018 WRITE (out,130) nsta(ng),
'nSTA', &
5019 &
'Number of timesteps between the writing of data', &
5020 &
'the stations file.'
5023 WRITE (out,130) nflt(ng),
'nFLT', &
5024 &
'Number of timesteps between the writing of data', &
5025 &
'into floats file.'
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', &
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', &
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.'
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.'
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.'
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', &
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', &
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.'
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.'
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', &
5147 IF (i.gt.nat) itrc=inert(i-nat)
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)))
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)))
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)))
5171 IF (i.gt.nat) itrc=inert(i-nat)
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)))
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)))
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)))
5193 WRITE (out,210) nl_visc2(ng),
'nl_visc2', &
5194 &
'NLM Horizontal, harmonic mixing coefficient', &
5195 &
'(m2/s) for momentum.'
5197 WRITE (out,210) ad_visc2(ng),
'ad_visc2', &
5198 &
'ADM Horizontal, harmonic mixing coefficient', &
5199 &
'(m2/s) for momentum.'
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.'
5208 WRITE (out,210) nl_visc4(ng),
'nl_visc4', &
5209 &
'NLM Horizontal, biharmonic mixing coefficient', &
5210 &
'(m4/s) for momentum.'
5212 WRITE (out,210) ad_visc4(ng),
'ad_visc4', &
5213 &
'ADM Horizontal, biharmonic mixing coefficient', &
5214 &
'(m4/s) for momentum.'
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.'
5222 IF (luvsponge(ng))
THEN
5223 WRITE (out,170) luvsponge(ng),
'LuvSponge', &
5224 &
'Turning ON sponge on horizontal momentum.'
5226 WRITE (out,170) luvsponge(ng),
'LuvSponge', &
5227 &
'Turning OFF sponge on horizontal momentum.'
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)))
5236 WRITE (out,185) ltracersponge(i,ng),
'LtracerSponge', i, &
5237 &
'Turning OFF sponge on tracer ', i, &
5238 & trim(vname(1,idtvar(i)))
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)))
5249 WRITE (out,185) ltracersponge(i,ng),
'LtracerSponge', i, &
5250 &
'Turning OFF sponge on tracer ', i, &
5251 & trim(vname(1,idtvar(i)))
5258 IF (i.gt.nat) itrc=inert(i-nat)
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)))
5264# if defined LIMIT_VDIFF && \
5265 (defined gls_mixing || defined lmd_mixing || defined my25_mixing)
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)))
5272 WRITE (out,210) akv_bak(ng),
'Akv_bak', &
5273 &
'Background vertical mixing coefficient (m2/s)', &
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)', &
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.'
5289 WRITE (out,210) tkenu2(ng),
'tkenu2', &
5290 &
'Horizontal, harmonic mixing coefficient (m2/s)', &
5291 &
'for turbulent energy.'
5294 WRITE (out,210) tkenu4(ng),
'tkenu4', &
5295 &
'Horizontal, biharmonic mixing coefficient (m4/s)', &
5296 &
'for turbulent energy.'
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.'
5335# ifdef FORWARD_MIXING
5339 IF (i.gt.nat) itrc=inert(i-nat)
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)))
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)))
5353 WRITE (out,210) ad_akv_fac(ng),
'ad_Akv_fac', &
5354 &
'ADM basic state vertical mixing scale factor', &
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', &
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).'
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.'
5380 WRITE (out,200) zos(ng),
'Zos', &
5381 &
'Surface roughness (m).'
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.'
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.'
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.'
5411 WRITE (out,200) dcrit(ng),
'Dcrit', &
5412 &
'Minimum depth for wetting and drying (m).'
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.'
5426 WRITE (out,130) levsfrc(ng),
'levsfrc', &
5427 &
'Deepest level to apply surface stress as a', &
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.'
5435 WRITE (out,130) levbfrc(ng),
'levbfrc', &
5436 &
'Shallowest level to apply bottom stress as a', &
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.'
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.'
5460 WRITE (out,160) tcline(ng),
'Tcline', &
5461 &
'S-coordinate surface/bottom layer width (m) used', &
5462 &
'in vertical coordinate stretching.'
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).'
5471#ifdef TIDE_GENERATING_FORCES
5472 WRITE (out,170) lnodal,
'Lnodal', &
5473 &
'Switch to apply a 18.5-year lunar nodal correction.'
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).'
5481 WRITE (out,150) time_ref,
'time_ref', &
5482 &
'Reference time for units attribute (yyyymmdd.dd)'
5487 IF (i.gt.nat) itrc=inert(i-nat)
5489 WRITE (out,190) tnudg(itrc,ng),
'Tnudg', itrc, &
5490 &
'Nudging/relaxation time scale (days)', &
5491 &
'for tracer ', itrc, trim(vname(1,idtvar(itrc)))
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.'
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.'
5509 WRITE (out,210) m3nudg(ng),
'M3nudg', &
5510 &
'Nudging/relaxation time scale (days)', &
5511 &
'for 3D momentum.'
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.'
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.'
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.'
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.'
5550 WRITE (out,160) r0(ng),
'R0', &
5551 &
'Background density (kg/m3) used in linear Equation', &
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).'
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.'
5568 WRITE (out,170) luvsrc(ng),
'LuvSrc', &
5569 &
'Turning OFF momentum point Sources/Sinks.'
5572 WRITE (out,170) lwsrc(ng),
'LwSrc', &
5573 &
'Turning ON volume influx point Sources/Sinks.'
5575 WRITE (out,170) lwsrc(ng),
'LwSrc', &
5576 &
'Turning OFF volume influx point Sources/Sinks.'
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)))
5585 WRITE (out,185) ltracersrc(itrc,ng),
'LtracerSrc', itrc, &
5586 &
'Turning OFF point Sources/Sinks on tracer ', itrc, &
5587 & trim(vname(1,idtvar(itrc)))
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)))
5598 WRITE (out,185) ltracersrc(itrc,ng),
'LtracerSrc', itrc, &
5599 &
'Turning OFF point Sources/Sinks on tracer ', itrc, &
5600 & trim(vname(1,idtvar(itrc)))
5605 IF (lsshclm(ng))
THEN
5606 WRITE (out,170) lsshclm(ng),
'LsshCLM', &
5607 &
'Turning ON processing of SSH climatology.'
5609 WRITE (out,170) lsshclm(ng),
'LsshCLM', &
5610 &
'Turning OFF processing of SSH climatology.'
5612 IF (lm2clm(ng))
THEN
5613 WRITE (out,170) lm2clm(ng),
'Lm2CLM', &
5614 &
'Turning ON processing of 2D momentum climatology.'
5616 WRITE (out,170) lm2clm(ng),
'Lm2CLM', &
5617 &
'Turning OFF processing of 2D momentum climatology.'
5620 IF (lm3clm(ng))
THEN
5621 WRITE (out,170) lm3clm(ng),
'Lm3CLM', &
5622 &
'Turning ON processing of 3D momentum climatology.'
5624 WRITE (out,170) lm3clm(ng),
'Lm3CLM', &
5625 &
'Turning OFF processing of 3D momentum climatology.'
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)))
5633 WRITE (out,185) ltracerclm(i,ng),
'LtracerCLM', i, &
5634 &
'Turning OFF processing of climatology tracer ', i, &
5635 & trim(vname(1,idtvar(i)))
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)))
5646 WRITE (out,185) ltracerclm(i,ng),
'LtracerCLM', i, &
5647 &
'Turning OFF processing of climatology tracer ', i, &
5648 & trim(vname(1,idtvar(i)))
5653 IF (lnudgem2clm(ng))
THEN
5654 WRITE (out,170) lnudgem2clm(ng),
'LnudgeM2CLM', &
5655 &
'Turning ON nudging of 2D momentum climatology.'
5657 WRITE (out,170) lnudgem2clm(ng),
'LnudgeM2CLM', &
5658 &
'Turning OFF nudging of 2D momentum climatology.'
5661 IF (lnudgem3clm(ng))
THEN
5662 WRITE (out,170) lnudgem3clm(ng),
'LnudgeM3CLM', &
5663 &
'Turning ON nudging of 3D momentum climatology.'
5665 WRITE (out,170) lnudgem3clm(ng),
'LnudgeM3CLM', &
5666 &
'Turning OFF nudging of 3D momentum climatology.'
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)))
5674 WRITE (out,185) lnudgetclm(i,ng),
'LnudgeTCLM', i, &
5675 &
'Turning OFF nudging of climatology tracer ', i, &
5676 & trim(vname(1,idtvar(i)))
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)))
5687 WRITE (out,185) lnudgetclm(i,ng),
'LnudgeTCLM', i, &
5688 &
'Turning OFF nudging of climatology tracer ', i, &
5689 & trim(vname(1,idtvar(i)))
5694#if defined AD_SENSITIVITY || defined I4DVAR_ANA_SENSITIVITY || \
5695 defined opt_observations || defined sensitivity_4dvar || \
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.'
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.'
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.'
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.'
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.'
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)))
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)', &
5760 &
'Singular Forcing Vectors on free-surface.'
5762 &
'Stochastic Optimals on free-surface.'
5765 IF (scalars(ng)%Fstate(isuvel)) &
5766 &
WRITE (out,170) scalars(ng)%Fstate(isuvel), &
5767 &
'Fstate(isUvel)', &
5769 &
'Singular Forcing Vectors on 3D U-momentum component.'
5771 &
'Stochastic Optimals on 3D U-momentum component.'
5773 IF (scalars(ng)%Fstate(isvvel)) &
5774 &
WRITE (out,170) scalars(ng)%Fstate(isvvel), &
5775 &
'Fstate(isVvel)', &
5777 &
'Singular Forcing Vectors on 3D V-momentum component.'
5779 &
'Stochastic Optimals on 3D V-momentum component.'
5782 IF (scalars(ng)%Fstate(istvar(itrc))) &
5783 &
WRITE (out,180) scalars(ng)%Fstate(istvar(itrc)), &
5784 &
'Fstate(idTVar)', &
5786 &
'Singular Forcing Vectors on tracer', &
5788 &
'Stochastic Optimals on tracer', &
5790 & itrc, trim(vname(1,idtvar(itrc)))
5793 IF (scalars(ng)%Fstate(isubar)) &
5794 &
WRITE (out,170) scalars(ng)%Fstate(isubar), &
5795 &
'Fstate(isUbar)', &
5797 &
'Singular Forcing Vectors on 2D U-momentum component.'
5799 &
'Stochastic Optimals on 2D U-momentum component.'
5801 IF (scalars(ng)%Fstate(isvbar)) &
5802 &
WRITE (out,170) scalars(ng)%Fstate(isvbar), &
5803 &
'Fstate(isVbar)', &
5805 &
'Singular Forcing Vectors on 2D V-momentum component.'
5807 &
'Stochastic Optimals on 2D V-momentum component.'
5810 IF (scalars(ng)%Fstate(isustr)) &
5811 &
WRITE (out,170) scalars(ng)%Fstate(isustr), &
5812 &
'Fstate(isUstr)', &
5814 &
'Singular Forcing Vectors on surface U-stress.'
5816 &
'Stochastic Optimals on surface U-stress.'
5818 IF (scalars(ng)%Fstate(isvstr)) &
5819 &
WRITE (out,170) scalars(ng)%Fstate(isvstr), &
5820 &
'Fstate(isVstr)', &
5822 &
'Singular Forcing Vectors on surface V-stress.'
5824 &
'Stochastic Optimals on surface V-stress.'
5828 IF (scalars(ng)%Fstate(istsur(itrc))) &
5829 &
WRITE (out,180) scalars(ng)%Fstate(istsur(itrc)), &
5830 &
'Fstate(idTsur)', &
5832 &
'Singular Forcing Vectors on surface flux of tracer', &
5834 &
'Stochastic Optimals on surface flux of tracer', &
5836 & itrc, trim(vname(1,idtvar(itrc)))
5841# ifndef SO_SEMI_WHITE
5842 WRITE (out,140) so_decay(ng),
'SO_decay', &
5843 &
'Stochastic optimals time decorrelation scale (days).'
5845 IF (scalars(ng)%Fstate(isfsur)) &
5846 WRITE (out,200) so_sdev(isfsur,ng),
'SO_sdev(isFsur)', &
5847 &
'Stochastic Optimals scale, free-surface'
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'
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)))
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'
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'
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)))
5886 IF ((nhis(ng).gt.0).and.any(hout(:,ng)))
THEN
5888#if defined SEDIMENT && defined SED_MORPH
5889 IF (hout(idbath,ng))
WRITE (out,170) hout(idbath,ng), &
5891 &
'Write out time-dependent bathymetry.'
5893 IF (hout(idfsur,ng))
WRITE (out,170) hout(idfsur,ng), &
5895 &
'Write out free-surface.'
5896 IF (hout(idubar,ng))
WRITE (out,170) hout(idubar,ng), &
5898 &
'Write out 2D U-momentum component.'
5899 IF (hout(idvbar,ng))
WRITE (out,170) hout(idvbar,ng), &
5901 &
'Write out 2D V-momentum component.'
5902 IF (hout(idu2de,ng))
WRITE (out,170) hout(idu2de,ng), &
5904 &
'Write out 2D U-eastward at RHO-points.'
5905 IF (hout(idv2dn,ng))
WRITE (out,170) hout(idv2dn,ng), &
5907 &
'Write out 2D V-northward at RHO-points.'
5909 IF (hout(iduvel,ng))
WRITE (out,170) hout(iduvel,ng), &
5911 &
'Write out 3D U-momentum component.'
5912 IF (hout(idvvel,ng))
WRITE (out,170) hout(idvvel,ng), &
5914 &
'Write out 3D V-momentum component.'
5915 IF (hout(idu3de,ng))
WRITE (out,170) hout(idu3de,ng), &
5917 &
'Write out 3D U-wastward component at RHO-points.'
5918 IF (hout(idv3dn,ng))
WRITE (out,170) hout(idv3dn,ng), &
5920 &
'Write out 3D V-northward component at RHO-points.'
5921 IF (hout(idwvel,ng))
WRITE (out,170) hout(idwvel,ng), &
5923 &
'Write out W-momentum component.'
5924 IF (hout(idovel,ng))
WRITE (out,170) hout(idovel,ng), &
5926 &
'Write out omega vertical velocity.'
5927# ifdef OMEGA_IMPLICIT
5928 IF (hout(idovil,ng))
WRITE (out,170) hout(idovil,ng), &
5930 &
'Write out omega implicit vertical velocity.'
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)))
5937 IF (hout(idpthr,ng))
WRITE (out,170) hout(idpthr,ng), &
5939 &
'Write out time-varying dephts of RHO-points.'
5940 IF (hout(idpthu,ng))
WRITE (out,170) hout(idpthu,ng), &
5942 &
'Write out time-varying dephts of U-points.'
5943 IF (hout(idpthv,ng))
WRITE (out,170) hout(idpthv,ng), &
5945 &
'Write out time-varying dephts of V-points.'
5946 IF (hout(idpthw,ng))
WRITE (out,170) hout(idpthw,ng), &
5948 &
'Write out time-varying dephts of W-points.'
5950 IF (hout(idusms,ng))
WRITE (out,170) hout(idusms,ng), &
5952 &
'Write out surface U-momentum stress.'
5953 IF (hout(idvsms,ng))
WRITE (out,170) hout(idvsms,ng), &
5955 &
'Write out surface V-momentum stress.'
5956 IF (hout(idubms,ng))
WRITE (out,170) hout(idubms,ng), &
5958 &
'Write out bottom U-momentum stress.'
5959 IF (hout(idvbms,ng))
WRITE (out,170) hout(idvbms,ng), &
5961 &
'Write out bottom V-momentum stress.'
5963 IF (hout(idubrs,ng))
WRITE (out,170) hout(idubrs,ng), &
5965 &
'Write out bottom U-current stress.'
5966 IF (hout(idvbrs,ng))
WRITE (out,170) hout(idvbrs,ng), &
5968 &
'Write out bottom V-current stress.'
5969 IF (hout(idubws,ng))
WRITE (out,170) hout(idubws,ng), &
5971 &
'Write out wind-induced, bottom U-wave stress.'
5972 IF (hout(idvbws,ng))
WRITE (out,170) hout(idvbws,ng), &
5974 &
'Write out wind-induced, bottom V-wave stress.'
5975 IF (hout(idubcs,ng))
WRITE (out,170) hout(idubcs,ng), &
5977 &
'Write out max wind + current, bottom U-wave stress.'
5978 IF (hout(idvbcs,ng))
WRITE (out,170) hout(idvbcs,ng), &
5980 &
'Write out max wind + current, bottom V-wave stress.'
5981 IF (hout(iduvwc,ng))
WRITE (out,170) hout(iduvwc,ng), &
5983 &
'Write out max wind + current, bottom UV-wave stress.'
5984 IF (hout(idubot,ng))
WRITE (out,170) hout(idubot,ng), &
5986 &
'Write out bed wave orbital U-velocity.'
5987 IF (hout(idvbot,ng))
WRITE (out,170) hout(idvbot,ng), &
5989 &
'Write out bed wave orbital V-velocity.'
5990 IF (hout(idubur,ng))
WRITE (out,170) hout(idubur,ng), &
5992 &
'Write out bottom U-momentum above bed.'
5993 IF (hout(idvbvr,ng))
WRITE (out,170) hout(idvbvr,ng), &
5995 &
'Write out bottom V-momentum above bed.'
5998 IF (hout(idu2rs,ng))
WRITE (out,170) hout(idu2rs,ng), &
6000 &
'Write out 2D barotropic wec u-stress.'
6001 IF (hout(idv2rs,ng))
WRITE (out,170) hout(idv2rs,ng), &
6003 &
'Write out 2D barotropic wec v-stress.'
6004 IF (hout(idu2sd,ng))
WRITE (out,170) hout(idu2sd,ng), &
6006 &
'Write out 2D barotropic Stokes u-velocity.'
6007 IF (hout(idv2sd,ng))
WRITE (out,170) hout(idv2sd,ng), &
6009 &
'Write out 2D barotropic Stokes v-velocity.'
6013 IF (hout(idu3rs,ng))
WRITE (out,170) hout(idu3rs,ng), &
6015 &
'Write out 3D total wec u-stress.'
6016 IF (hout(idv3rs,ng))
WRITE (out,170) hout(idv3rs,ng), &
6018 &
'Write out 3D total wec v-stress.'
6019 IF (hout(idu3sd,ng))
WRITE (out,170) hout(idu3sd,ng), &
6021 &
'Write out 3D total wec Stokes u-velocity.'
6022 IF (hout(idv3sd,ng))
WRITE (out,170) hout(idv3sd,ng), &
6024 &
'Write out 3D total wec Stokes v-velocity.'
6025 IF (hout(idw3sd,ng))
WRITE (out,170) hout(idw3sd,ng), &
6027 &
'Write out 3D wec omega Stokes vertical velocity.'
6028 IF (hout(idw3st,ng))
WRITE (out,170) hout(idw3st,ng), &
6030 &
'Write out 3D wec Stokes vertical velocity.'
6033 IF (hout(idwztw,ng))
WRITE (out,170) hout(idwztw,ng), &
6035 &
'Write out wec quasi-static sea level adjustment.'
6036 IF (hout(idwqsp,ng))
WRITE (out,170) hout(idwqsp,ng), &
6038 &
'Write out wec quasi-static sea pressure adjustment.'
6039 IF (hout(idwbeh,ng))
WRITE (out,170) hout(idwbeh,ng), &
6041 &
'Write out wec Bernoulli head sea level adjustment.'
6045 IF (hout(idwamp,ng))
WRITE (out,170) hout(idwamp,ng), &
6047 &
'Write out wave height.'
6050 IF (hout(idwlen,ng))
WRITE (out,170) hout(idwlen,ng), &
6052 &
'Write out waves mean wavelength.'
6055 IF (hout(idwlep,ng))
WRITE (out,170) hout(idwlep,ng), &
6057 &
'Write out waves peak wavelength.'
6060 IF (hout(idwdir,ng))
WRITE (out,170) hout(idwdir,ng), &
6062 &
'Write out waves mean direction.'
6065 IF (hout(idwdip,ng))
WRITE (out,170) hout(idwdip,ng), &
6067 &
'Write out peak waves direction.'
6069#ifdef WAVES_TOP_PERIOD
6070 IF (hout(idwptp,ng))
WRITE (out,170) hout(idwptp,ng), &
6072 &
'Write out wave surface period.'
6074#ifdef WAVES_BOT_PERIOD
6075 IF (hout(idwpbt,ng))
WRITE (out,170) hout(idwpbt,ng), &
6077 &
'Write out wave bottom period.'
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), &
6083 &
'Write out wave bottom orbital velocity.'
6085#if defined WAV_COUPLING || (defined WEC_VF && defined BOTTOM_STREAMING)
6086 IF (hout(idwdif,ng))
WRITE (out,170) hout(idwdif,ng), &
6088 &
'Write out wave dissipation due to bottom friction.'
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), &
6095 &
'Write out wave dissipation due to breaking.'
6096 IF (hout(idwdiw,ng))
WRITE (out,170) hout(idwdiw,ng), &
6098 &
'Write out wave dissipation due to whitecapping.'
6100#ifdef ROLLER_SVENDSEN
6101 IF (hout(idwbrk,ng))
WRITE (out,170) hout(idwbrk,ng), &
6103 &
'Write out percent wave breaking.'
6106 IF (hout(idwdis,ng))
WRITE (out,170) hout(idwdis,ng), &
6108 &
'Write out wave roller dissipation.'
6110#ifdef ROLLER_RENIERS
6111 IF (hout(idwrol,ng))
WRITE (out,170) hout(idwrol,ng), &
6113 &
'Write out wave roller action density.'
6116 IF (hout(idwvds,ng))
WRITE (out,170) hout(idwvds,ng), &
6118 &
'Write out wave directional spread.'
6119 IF (hout(idwvqp,ng))
WRITE (out,170) hout(idwvqp,ng), &
6121 &
'Write out wave spectrum peakedness.'
6124 IF (hout(iduwav,ng))
WRITE (out,170) hout(iduwav,ng), &
6126 &
'Wave-avg surface u-velocity.'
6127 IF (hout(idvwav,ng))
WRITE (out,170) hout(idvwav,ng), &
6129 &
'Wave-avg surface v-velocity.'
6132 IF (hout(idacen,ng))
WRITE (out,170) hout(idacen,ng), &
6134 &
'Write out 3D wave action'
6135 IF (hout(idacct,ng))
WRITE (out,170) hout(idacct,ng), &
6137 &
'Wave group celerity in the theta coordinate.'
6138 IF (hout(idaccx,ng))
WRITE (out,170) hout(idaccx,ng), &
6140 &
'Wave group celerity in the xi coordinate.'
6141 IF (hout(idaccy,ng))
WRITE (out,170) hout(idaccy,ng), &
6143 &
'Wave group celerity in the eta space.'
6144 IF (hout(idactp,ng))
WRITE (out,170) hout(idactp,ng), &
6146 &
'Wave group peak period.'
6148#if defined SOLVE3D && defined T_PASSIVE
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))))
6157# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
6158 IF (hout(idpair,ng))
WRITE (out,170) hout(idpair,ng), &
6160 &
'Write out surface air pressure.'
6162# if defined BULK_FLUXES
6163 IF (hout(idtair,ng))
WRITE (out,170) hout(idtair,ng), &
6165 &
'Write out surface air temperature.'
6167# if defined BULK_FLUXES || defined ECOSIM
6168 IF (hout(iduair,ng))
WRITE (out,170) hout(iduair,ng), &
6170 &
'Write out surface U-wind component.'
6171 IF (hout(idvair,ng))
WRITE (out,170) hout(idvair,ng), &
6173 &
'Write out surface V-wind component.'
6174 IF (hout(iduaie,ng))
WRITE (out,170) hout(iduaie,ng), &
6176 &
'Write out surface Eastward U-wind component.'
6177 IF (hout(idvain,ng))
WRITE (out,170) hout(idvain,ng), &
6179 &
'Write out surface Northward V-wind component.'
6181 IF (hout(idtsur(itemp),ng))
WRITE (out,170) &
6182 & hout(idtsur(itemp),ng),
'Hout(idTsur)', &
6183 &
'Write out surface net heat flux.'
6185 IF (hout(idtsur(isalt),ng))
WRITE (out,170) &
6186 & hout(idtsur(isalt),ng),
'Hout(idTsur)', &
6187 &
'Write out surface net salt flux.'
6190 IF (hout(idsrad,ng))
WRITE (out,170) hout(idsrad,ng), &
6192 &
'Write out shortwave radiation flux.'
6194# if defined BULK_FLUXES || defined FRC_COUPLING
6195 IF (hout(idlrad,ng))
WRITE (out,170) hout(idlrad,ng), &
6197 &
'Write out longwave radiation flux.'
6198 IF (hout(idlhea,ng))
WRITE (out,170) hout(idlhea,ng), &
6200 &
'Write out latent heat flux.'
6201 IF (hout(idshea,ng))
WRITE (out,170) hout(idshea,ng), &
6203 &
'Write out sensible heat flux.'
6204# if defined EMINUSP || defined FRC_COUPLING
6205 IF (hout(idempf,ng))
WRITE (out,170) hout(idempf,ng), &
6207 &
'Write out E-P flux.'
6210 IF (hout(idevap,ng))
WRITE (out,170) hout(idevap,ng), &
6212 &
'Write out evaporation rate.'
6213 IF (hout(idrain,ng))
WRITE (out,170) hout(idrain,ng), &
6215 &
'Write out rain rate.'
6218 IF (hout(iddano,ng))
WRITE (out,170) hout(iddano,ng), &
6220 &
'Write out density anomaly.'
6221 IF (hout(idvvis,ng))
WRITE (out,170) hout(idvvis,ng), &
6223 &
'Write out vertical viscosity: AKv.'
6224 IF (hout(idtdif,ng))
WRITE (out,170) hout(idtdif,ng), &
6226 &
'Write out vertical diffusion: AKt(itemp).'
6228 IF (hout(idsdif,ng))
WRITE (out,170) hout(idsdif,ng), &
6230 &
'Write out vertical diffusion: AKt(isalt).'
6233 IF (hout(idhsbl,ng))
WRITE (out,170) hout(idhsbl,ng), &
6235 &
'Write out depth of surface boundary layer.'
6238 IF (hout(idhbbl,ng))
WRITE (out,170) hout(idhbbl,ng), &
6240 &
'Write out depth of bottom boundary layer.'
6242# if defined GLS_MIXING || defined MY25_MIXING
6243 IF (hout(idmtke,ng))
WRITE (out,170) hout(idmtke,ng), &
6245 &
'Write out turbulent kinetic energy.'
6246 IF (hout(idmtls,ng))
WRITE (out,170) hout(idmtls,ng), &
6248 &
'Write out turbulent generic length-scale.'
6253 IF ((nqck(ng).gt.0).and.any(qout(:,ng)))
THEN
6255#if defined SEDIMENT && defined SED_MORPH
6256 IF (qout(idbath,ng))
WRITE (out,170) qout(idbath,ng), &
6258 &
'Write out time-dependent bathymetry.'
6260 IF (qout(idfsur,ng))
WRITE (out,170) qout(idfsur,ng), &
6262 &
'Write out free-surface.'
6263 IF (qout(idubar,ng))
WRITE (out,170) qout(idubar,ng), &
6265 &
'Write out 2D U-momentum component.'
6266 IF (qout(idvbar,ng))
WRITE (out,170) qout(idvbar,ng), &
6268 &
'Write out 2D V-momentum component.'
6269 IF (qout(idu2de,ng))
WRITE (out,170) qout(idu2de,ng), &
6271 &
'Write out 2D U-eastward at RHO-points.'
6272 IF (qout(idv2dn,ng))
WRITE (out,170) qout(idv2dn,ng), &
6274 &
'Write out 2D V-northward at RHO-points.'
6276 IF (qout(iduvel,ng))
WRITE (out,170) qout(iduvel,ng), &
6278 &
'Write out 3D U-momentum component.'
6279 IF (qout(idvvel,ng))
WRITE (out,170) qout(idvvel,ng), &
6281 &
'Write out 3D V-momentum component.'
6282 IF (qout(idusur,ng))
WRITE (out,170) qout(idusur,ng), &
6284 &
'Write out surface U-momentum component.'
6285 IF (qout(idvsur,ng))
WRITE (out,170) qout(idvsur,ng), &
6287 &
'Write out surface V-momentum component.'
6288 IF (qout(idu3de,ng))
WRITE (out,170) qout(idu3de,ng), &
6290 &
'Write out 3D U-wastward component at RHO-points.'
6291 IF (qout(idv3dn,ng))
WRITE (out,170) qout(idv3dn,ng), &
6293 &
'Write out 3D V-northward component at RHO-points.'
6294 IF (qout(idu3de,ng))
WRITE (out,170) qout(idu3de,ng), &
6296 &
'Write out surface U-wastward component at RHO-points.'
6297 IF (qout(idv3dn,ng))
WRITE (out,170) qout(idv3dn,ng), &
6299 &
'Write out surface V-northward component at RHO-points.'
6300 IF (qout(idwvel,ng))
WRITE (out,170) qout(idwvel,ng), &
6302 &
'Write out W-momentum component.'
6303 IF (qout(idovel,ng))
WRITE (out,170) qout(idovel,ng), &
6305 &
'Write out omega vertical velocity.'
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)))
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)))
6317 IF (qout(idpthr,ng))
WRITE (out,170) qout(idpthr,ng), &
6319 &
'Write out time-varying dephts of RHO-points.'
6320 IF (qout(idpthu,ng))
WRITE (out,170) qout(idpthu,ng), &
6322 &
'Write out time-varying dephts of U-points.'
6323 IF (qout(idpthv,ng))
WRITE (out,170) qout(idpthv,ng), &
6325 &
'Write out time-varying dephts of V-points.'
6326 IF (qout(idpthw,ng))
WRITE (out,170) qout(idpthw,ng), &
6328 &
'Write out time-varying dephts of W-points.'
6330 IF (qout(idusms,ng))
WRITE (out,170) qout(idusms,ng), &
6332 &
'Write out surface U-momentum stress.'
6333 IF (qout(idvsms,ng))
WRITE (out,170) qout(idvsms,ng), &
6335 &
'Write out surface V-momentum stress.'
6336 IF (qout(idubms,ng))
WRITE (out,170) qout(idubms,ng), &
6338 &
'Write out bottom U-momentum stress.'
6339 IF (qout(idvbms,ng))
WRITE (out,170) qout(idvbms,ng), &
6341 &
'Write out bottom V-momentum stress.'
6343 IF (qout(idubrs,ng))
WRITE (out,170) qout(idubrs,ng), &
6345 &
'Write out bottom U-current stress.'
6346 IF (qout(idvbrs,ng))
WRITE (out,170) qout(idvbrs,ng), &
6348 &
'Write out bottom V-current stress.'
6349 IF (qout(idubws,ng))
WRITE (out,170) qout(idubws,ng), &
6351 &
'Write out wind-induced, bottom U-wave stress.'
6352 IF (qout(idvbws,ng))
WRITE (out,170) qout(idvbws,ng), &
6354 &
'Write out wind-induced, bottom V-wave stress.'
6355 IF (qout(idubcs,ng))
WRITE (out,170) qout(idubcs,ng), &
6357 &
'Write out max wind + current, bottom U-wave stress.'
6358 IF (qout(idvbcs,ng))
WRITE (out,170) qout(idvbcs,ng), &
6360 &
'Write out max wind + current, bottom V-wave stress.'
6361 IF (qout(idubot,ng))
WRITE (out,170) qout(idubot,ng), &
6363 &
'Write out bed wave orbital U-velocity.'
6364 IF (qout(idvbot,ng))
WRITE (out,170) qout(idvbot,ng), &
6366 &
'Write out bed wave orbital V-velocity.'
6367 IF (qout(idubur,ng))
WRITE (out,170) qout(idubur,ng), &
6369 &
'Write out bottom U-momentum above bed.'
6370 IF (qout(idvbvr,ng))
WRITE (out,170) qout(idvbvr,ng), &
6372 &
'Write out bottom V-momentum above bed.'
6375 IF (qout(idu2rs,ng))
WRITE (out,170) qout(idu2rs,ng), &
6377 &
'Write out 2D barotropic wec u-stress.'
6378 IF (qout(idv2rs,ng))
WRITE (out,170) qout(idv2rs,ng), &
6380 &
'Write out 2D barotropic wec v-stress.'
6381 IF (qout(idu2sd,ng))
WRITE (out,170) qout(idu2sd,ng), &
6383 &
'Write out 2D barotropic Stokes u-velocity.'
6384 IF (qout(idv2sd,ng))
WRITE (out,170) qout(idv2sd,ng), &
6386 &
'Write out 2D barotropic Stokes v-velocity.'
6390 IF (qout(idu3rs,ng))
WRITE (out,170) qout(idu3rs,ng), &
6392 &
'Write out 3D total wec u-stress.'
6393 IF (qout(idv3rs,ng))
WRITE (out,170) qout(idv3rs,ng), &
6395 &
'Write out 3D total wec v-stress.'
6396 IF (qout(idu3sd,ng))
WRITE (out,170) qout(idu3sd,ng), &
6398 &
'Write out 3D total wec Stokes u-velocity.'
6399 IF (qout(idv3sd,ng))
WRITE (out,170) qout(idv3sd,ng), &
6401 &
'Write out 3D total wec Stokes v-velocity.'
6402 IF (qout(idw3sd,ng))
WRITE (out,170) qout(idw3sd,ng), &
6404 &
'Write out 3D wec omega Stokes vertical velocity.'
6405 IF (qout(idw3st,ng))
WRITE (out,170) qout(idw3st,ng), &
6407 &
'Write out 3D wec Stokes vertical velocity.'
6410 IF (qout(idwztw,ng))
WRITE (out,170) qout(idwztw,ng), &
6412 &
'Write out wec quasi-static sea level adjustment.'
6413 IF (qout(idwqsp,ng))
WRITE (out,170) qout(idwqsp,ng), &
6415 &
'Write out wec quasi-static sea pressure adjustment.'
6416 IF (qout(idwbeh,ng))
WRITE (out,170) qout(idwbeh,ng), &
6418 &
'Write out wec Bernoulli head sea level adjustment.'
6422 IF (qout(idwamp,ng))
WRITE (out,170) qout(idwamp,ng), &
6424 &
'Write out wave height.'
6427 IF (qout(idwlen,ng))
WRITE (out,170) qout(idwlen,ng), &
6429 &
'Write out waves mean wavelength.'
6432 IF (qout(idwlep,ng))
WRITE (out,170) qout(idwlep,ng), &
6434 &
'Write out waves peak wavelength.'
6437 IF (qout(idwdir,ng))
WRITE (out,170) qout(idwdir,ng), &
6439 &
'Write out waves mean direction.'
6442 IF (qout(idwdip,ng))
WRITE (out,170) qout(idwdip,ng), &
6444 &
'Write out peak waves direction.'
6446#ifdef WAVES_TOP_PERIOD
6447 IF (qout(idwptp,ng))
WRITE (out,170) qout(idwptp,ng), &
6449 &
'Write out wave surface period.'
6451#ifdef WAVES_BOT_PERIOD
6452 IF (qout(idwpbt,ng))
WRITE (out,170) qout(idwpbt,ng), &
6454 &
'Write out wave bottom period.'
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), &
6460 &
'Write out wave bottom orbital velocity.'
6462#if defined WAV_COUPLING || (defined WEC_VF && defined BOTTOM_STREAMING)
6463 IF (qout(idwdif,ng))
WRITE (out,170) qout(idwdif,ng), &
6465 &
'Write out wave dissipation due to bottom friction.'
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), &
6472 &
'Write out wave dissipation due to breaking.'
6473 IF (qout(idwdiw,ng))
WRITE (out,170) qout(idwdiw,ng), &
6475 &
'Write out wave dissipation due to whitecapping.'
6477#ifdef ROLLER_SVENDSEN
6478 IF (qout(idwbrk,ng))
WRITE (out,170) qout(idwbrk,ng), &
6480 &
'Write out percent wave breaking.'
6483 IF (qout(idwdis,ng))
WRITE (out,170) qout(idwdis,ng), &
6485 &
'Write out wave roller dissipation.'
6487#ifdef ROLLER_RENIERS
6488 IF (qout(idwrol,ng))
WRITE (out,170) qout(idwrol,ng), &
6490 &
'Write out wave roller action density.'
6493 IF (qout(idwvds,ng))
WRITE (out,170) qout(idwvds,ng), &
6495 &
'Write out wave directional spread.'
6496 IF (qout(idwvqp,ng))
WRITE (out,170) qout(idwvqp,ng), &
6498 &
'Write out wave spectrum peakedness.'
6501 IF (qout(iduwav,ng))
WRITE (out,170) qout(iduwav,ng), &
6503 &
'Wave-avg surface u-velocity.'
6504 IF (qout(idvwav,ng))
WRITE (out,170) qout(idvwav,ng), &
6506 &
'Wave-avg surface v-velocity.'
6508#if defined SOLVE3D && defined T_PASSIVE
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))))
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))))
6523# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
6524 IF (qout(idpair,ng))
WRITE (out,170) qout(idpair,ng), &
6526 &
'Write out surface air pressure.'
6528# if defined BULK_FLUXES
6529 IF (qout(idtair,ng))
WRITE (out,170) qout(idtair,ng), &
6531 &
'Write out surface air temperature.'
6533# if defined BULK_FLUXES || defined ECOSIM
6534 IF (qout(iduair,ng))
WRITE (out,170) qout(iduair,ng), &
6536 &
'Write out surface U-wind component.'
6537 IF (qout(idvair,ng))
WRITE (out,170) qout(idvair,ng), &
6539 &
'Write out surface V-wind component.'
6540 IF (qout(iduaie,ng))
WRITE (out,170) qout(iduaie,ng), &
6542 &
'Write out surface Eastward U-wind component.'
6543 IF (qout(idvain,ng))
WRITE (out,170) qout(idvain,ng), &
6545 &
'Write out surface Northward V-wind component.'
6547 IF (qout(idtsur(itemp),ng))
WRITE (out,170) &
6548 & qout(idtsur(itemp),ng),
'Qout(idTsur)', &
6549 &
'Write out surface net heat flux.'
6551 IF (qout(idtsur(isalt),ng))
WRITE (out,170) &
6552 & qout(idtsur(isalt),ng),
'Qout(idTsur)', &
6553 &
'Write out surface net salt flux.'
6556 IF (qout(idsrad,ng))
WRITE (out,170) qout(idsrad,ng), &
6558 &
'Write out shortwave radiation flux.'
6560# if defined BULK_FLUXES || defined FRC_COUPLING
6561 IF (qout(idlrad,ng))
WRITE (out,170) qout(idlrad,ng), &
6563 &
'Write out longwave radiation flux.'
6564 IF (qout(idlhea,ng))
WRITE (out,170) qout(idlhea,ng), &
6566 &
'Write out latent heat flux.'
6567 IF (qout(idshea,ng))
WRITE (out,170) qout(idshea,ng), &
6569 &
'Write out sensible heat flux.'
6570# if defined EMINUSP || defined FRC_COUPLING
6571 IF (qout(idempf,ng))
WRITE (out,170) qout(idempf,ng), &
6573 &
'Write out E-P flux.'
6576 IF (qout(idevap,ng))
WRITE (out,170) qout(idevap,ng), &
6578 &
'Write out evaporation rate.'
6579 IF (qout(idrain,ng))
WRITE (out,170) qout(idrain,ng), &
6581 &
'Write out rain rate.'
6584 IF (qout(iddano,ng))
WRITE (out,170) qout(iddano,ng), &
6586 &
'Write out density anomaly.'
6587 IF (qout(idvvis,ng))
WRITE (out,170) qout(idvvis,ng), &
6589 &
'Write out vertical viscosity: AKv.'
6590 IF (qout(idtdif,ng))
WRITE (out,170) qout(idtdif,ng), &
6592 &
'Write out vertical diffusion: AKt(itemp).'
6594 IF (qout(idsdif,ng))
WRITE (out,170) qout(idsdif,ng), &
6596 &
'Write out vertical diffusion: AKt(isalt).'
6599 IF (qout(idhsbl,ng))
WRITE (out,170) qout(idhsbl,ng), &
6601 &
'Write out depth of surface boundary layer.'
6604 IF (qout(idhbbl,ng))
WRITE (out,170) qout(idhbbl,ng), &
6606 &
'Write out depth of bottom boundary layer.'
6608# if defined GLS_MIXING || defined MY25_MIXING
6609 IF (qout(idmtke,ng))
WRITE (out,170) qout(idmtke,ng), &
6611 &
'Write out turbulent kinetic energy.'
6612 IF (qout(idmtls,ng))
WRITE (out,170) qout(idmtls,ng), &
6614 &
'Write out turbulent generic length-scale.'
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
6624 IF (aout(idfsur,ng))
WRITE (out,170) aout(idfsur,ng), &
6626 &
'Write out averaged free-surface.'
6627 IF (aout(idubar,ng))
WRITE (out,170) aout(idubar,ng), &
6629 &
'Write out averaged 2D U-momentum component.'
6630 IF (aout(idvbar,ng))
WRITE (out,170) aout(idvbar,ng), &
6632 &
'Write out averaged 2D V-momentum component.'
6633 IF (aout(idu2de,ng))
WRITE (out,170) aout(idu2de,ng), &
6635 &
'Write out averaged 2D U-eastward at RHO-points.'
6636 IF (aout(idv2dn,ng))
WRITE (out,170) aout(idv2dn,ng), &
6638 &
'Write out averaged 2D V-northward at RHO-points.'
6640 IF (aout(iduvel,ng))
WRITE (out,170) aout(iduvel,ng), &
6642 &
'Write out averaged 3D U-momentum component.'
6643 IF (aout(idvvel,ng))
WRITE (out,170) aout(idvvel,ng), &
6645 &
'Write out averaged 3D V-momentum component.'
6646 IF (aout(idu3de,ng))
WRITE (out,170) aout(idu3de,ng), &
6648 &
'Write out averaged 3D U-eastward at RHO-points.'
6649 IF (aout(idv3dn,ng))
WRITE (out,170) aout(idv3dn,ng), &
6651 &
'Write out averaged 3D V-northward at RHO-points.'
6652 IF (aout(idwvel,ng))
WRITE (out,170) aout(idwvel,ng), &
6654 &
'Write out averaged W-momentum component.'
6655 IF (aout(idovel,ng))
WRITE (out,170) aout(idovel,ng), &
6657 &
'Write out averaged omega vertical velocity.'
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)))
6665 IF (aout(idusms,ng))
WRITE (out,170) aout(idusms,ng), &
6667 &
'Write out averaged surface U-momentum stress.'
6668 IF (aout(idvsms,ng))
WRITE (out,170) aout(idvsms,ng), &
6670 &
'Write out averaged surface V-momentum stress.'
6671 IF (aout(idubms,ng))
WRITE (out,170) aout(idubms,ng), &
6673 &
'Write out averaged bottom U-momentum stress.'
6674 IF (aout(idvbms,ng))
WRITE (out,170) aout(idvbms,ng), &
6676 &
'Write out averaged bottom V-momentum stress.'
6678 IF (aout(idubrs,ng))
WRITE (out,170) aout(idubrs,ng), &
6680 &
'Write out averaged bottom U-current stress.'
6681 IF (aout(idvbrs,ng))
WRITE (out,170) aout(idvbrs,ng), &
6683 &
'Write out averaged bottom V-current stress.'
6684 IF (aout(idubws,ng))
WRITE (out,170) aout(idubws,ng), &
6686 &
'Write out averaged wind-induced, bottom U-wave stress.'
6687 IF (aout(idvbws,ng))
WRITE (out,170) aout(idvbws,ng), &
6689 &
'Write out averaged wind-induced, bottom V-wave stress.'
6690 IF (aout(idubcs,ng))
WRITE (out,170) aout(idubcs,ng), &
6692 &
'Write out averaged max wind+curr bottom U-wave stress.'
6693 IF (aout(idvbcs,ng))
WRITE (out,170) aout(idvbcs,ng), &
6695 &
'Write out averaged max wind+curr bottom V-wave stress.'
6696 IF (aout(iduvwc,ng))
WRITE (out,170) aout(iduvwc,ng), &
6698 &
'Write out averaged max wind+curr bottom UV-wave stress.'
6699 IF (aout(idubot,ng))
WRITE (out,170) aout(idubot,ng), &
6701 &
'Write out averaged bed wave orbital U-velocity.'
6702 IF (aout(idvbot,ng))
WRITE (out,170) aout(idvbot,ng), &
6704 &
'Write out averaged bed wave orbital V-velocity.'
6705 IF (aout(idubur,ng))
WRITE (out,170) aout(idubur,ng), &
6707 &
'Write out averaged bottom U-momentum above bed.'
6708 IF (aout(idvbvr,ng))
WRITE (out,170) aout(idvbvr,ng), &
6710 &
'Write out averaged bottom V-momentum above bed.'
6713 IF (aout(idu2rs,ng))
WRITE (out,170) aout(idu2rs,ng), &
6715 &
'Write out 2D barotropic wec u-stress.'
6716 IF (aout(idv2rs,ng))
WRITE (out,170) aout(idv2rs,ng), &
6718 &
'Write out 2D barotropic wec v-stress.'
6719 IF (aout(idu2sd,ng))
WRITE (out,170) aout(idu2sd,ng), &
6721 &
'Write out 2D barotropic Stokes u-velocity.'
6722 IF (aout(idv2sd,ng))
WRITE (out,170) aout(idv2sd,ng), &
6724 &
'Write out 2D barotropic Stokes v-velocity.'
6728 IF (aout(idu3rs,ng))
WRITE (out,170) aout(idu3rs,ng), &
6730 &
'Write out 3D total wec u-stress.'
6731 IF (aout(idv3rs,ng))
WRITE (out,170) aout(idv3rs,ng), &
6733 &
'Write out 3D total wec v-stress.'
6734 IF (aout(idu3sd,ng))
WRITE (out,170) aout(idu3sd,ng), &
6736 &
'Write out 3D total wec Stokes u-velocity.'
6737 IF (aout(idv3sd,ng))
WRITE (out,170) aout(idv3sd,ng), &
6739 &
'Write out 3D total wec Stokes v-velocity.'
6740 IF (aout(idw3sd,ng))
WRITE (out,170) aout(idw3sd,ng), &
6742 &
'Write out 3D wec omega Stokes vertical velocity.'
6743 IF (aout(idw3st,ng))
WRITE (out,170) aout(idw3st,ng), &
6745 &
'Write out 3D wec Stokes vertical velocity.'
6748 IF (aout(idwztw,ng))
WRITE (out,170) aout(idwztw,ng), &
6750 &
'Write out wec quasi-static sea level adjustment.'
6751 IF (aout(idwqsp,ng))
WRITE (out,170) aout(idwqsp,ng), &
6753 &
'Write out wec quasi-static sea pressure adjustment.'
6754 IF (aout(idwbeh,ng))
WRITE (out,170) aout(idwbeh,ng), &
6756 &
'Write out wec Bernoulli head sea level adjustment.'
6759# if defined SOLVE3D && defined T_PASSIVE
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))))
6768# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
6769 IF (aout(idpair,ng))
WRITE (out,170) aout(idpair,ng), &
6771 &
'Write out averaged surface air pressure.'
6773# if defined BULK_FLUXES
6774 IF (aout(idtair,ng))
WRITE (out,170) aout(idtair,ng), &
6776 &
'Write out averaged surface air temperature.'
6778# if defined BULK_FLUXES || defined ECOSIM
6779 IF (aout(iduair,ng))
WRITE (out,170) aout(iduair,ng), &
6781 &
'Write out averaged surface U-wind component.'
6782 IF (aout(idvair,ng))
WRITE (out,170) aout(idvair,ng), &
6784 &
'Write out averaged surface V-wind component.'
6785 IF (aout(iduaie,ng))
WRITE (out,170) aout(iduaie,ng), &
6787 &
'Write out averaged Eastward surface U-wind component.'
6788 IF (aout(idvain,ng))
WRITE (out,170) aout(idvain,ng), &
6790 &
'Write out averaged Northward surface V-wind component.'
6792 IF (aout(idtsur(itemp),ng))
WRITE (out,170) &
6793 & aout(idtsur(itemp),ng),
'Aout(idTsur)', &
6794 &
'Write out averaged surface net heat flux.'
6796 IF (aout(idtsur(isalt),ng))
WRITE (out,170) &
6797 & aout(idtsur(isalt),ng),
'Aout(idTsur)', &
6798 &
'Write out averaged surface net salt flux.'
6801 IF (aout(idsrad,ng))
WRITE (out,170) aout(idsrad,ng), &
6803 &
'Write out averaged shortwave radiation flux.'
6806 IF (aout(idlrad,ng))
WRITE (out,170) aout(idlrad,ng), &
6808 &
'Write out averaged longwave radiation flux.'
6809 IF (aout(idlhea,ng))
WRITE (out,170) aout(idlhea,ng), &
6811 &
'Write out averaged latent heat flux.'
6812 IF (aout(idshea,ng))
WRITE (out,170) aout(idshea,ng), &
6814 &
'Write out averaged sensible heat flux.'
6816 IF (aout(idevap,ng))
WRITE (out,170) aout(idevap,ng), &
6818 &
'Write out averaged evaporation rate.'
6819 IF (aout(idrain,ng))
WRITE (out,170) aout(idrain,ng), &
6821 &
'Write out averaged rain rate.'
6824 IF (aout(iddano,ng))
WRITE (out,170) aout(iddano,ng), &
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), &
6830 &
'Write out averaged vertical viscosity: AKv.'
6831 IF (aout(idtdif,ng))
WRITE (out,170) aout(idtdif,ng), &
6833 &
'Write out averaged vertical diffusion: AKt(itemp).'
6835 IF (aout(idsdif,ng))
WRITE (out,170) aout(idsdif,ng), &
6837 &
'Write out averaged vertical diffusion: AKt(isalt).'
6841 IF (aout(idhsbl,ng))
WRITE (out,170) aout(idhsbl,ng), &
6843 &
'Write out averaged depth of surface boundary layer.'
6846 IF (aout(idhbbl,ng))
WRITE (out,170) aout(idhbbl,ng), &
6848 &
'Write out averaged depth of bottom boundary layer.'
6851 IF (aout(id2drv,ng))
WRITE (out,170) aout(id2drv,ng), &
6853 &
'Write out averaged 2D relative vorticity.'
6854 IF (aout(id2dpv,ng))
WRITE (out,170) aout(id2dpv,ng), &
6856 &
'Write out averaged 2D potential vorticity.'
6858 IF (aout(id3drv,ng))
WRITE (out,170) aout(id3drv,ng), &
6860 &
'Write out averaged 3D relative vorticity.'
6861 IF (aout(id3dpv,ng))
WRITE (out,170) aout(id3dpv,ng), &
6863 &
'Write out averaged 3D potential vorticity.'
6865 IF (aout(idzzav,ng))
WRITE (out,170) aout(idzzav,ng), &
6867 &
'Write out averaged quadratic <zeta*zeta> term.'
6868 IF (aout(idu2av,ng))
WRITE (out,170) aout(idu2av,ng), &
6870 &
'Write out averaged quadratic <ubar*ubar> term.'
6871 IF (aout(idv2av,ng))
WRITE (out,170) aout(idv2av,ng), &
6873 &
'Write out averaged quadratic <vbar*vbar> term.'
6875 IF (aout(idhuav,ng))
WRITE (out,170) aout(idhuav,ng), &
6877 &
'Write out averaged u-volume flux, Huon.'
6878 IF (aout(idhvav,ng))
WRITE (out,170) aout(idhvav,ng), &
6880 &
'Write out averaged v-volume flux, Hvom.'
6881 IF (aout(iduuav,ng))
WRITE (out,170) aout(iduuav,ng), &
6883 &
'Write out averaged quadratic <u*u> term.'
6884 IF (aout(iduvav,ng))
WRITE (out,170) aout(iduvav,ng), &
6886 &
'Write out averaged quadratic <u*v> term.'
6887 IF (aout(idvvav,ng))
WRITE (out,170) aout(idvvav,ng), &
6889 &
'Write out averaged quadratic <v*v> term.'
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)))
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)))
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)))
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)))
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)))
6921# if defined AVERAGES && defined AVERAGES_DETIDE && \
6922 (defined ssh_tides || defined uv_tides)
6924 IF (aout(idfsud,ng))
WRITE (out,170) aout(idfsud,ng), &
6926 &
'Write out detided free-surface.'
6927 IF (aout(idu2dd,ng))
WRITE (out,170) aout(idu2dd,ng), &
6929 &
'Write out detided 2D U-velocity.'
6930 IF (aout(idv2dd,ng))
WRITE (out,170) aout(idv2dd,ng), &
6932 &
'Write out detided 2D V-velocity.'
6934 IF (aout(idu3dd,ng))
WRITE (out,170) aout(idu3dd,ng), &
6936 &
'Write out detided 3D U-velocity.'
6937 IF (aout(idv3dd,ng))
WRITE (out,170) aout(idv3dd,ng), &
6939 &
'Write out detided 3D V-velocity.'
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)))
6950#ifdef DIAGNOSTICS_UV
6951 IF ((ndia(ng).gt.0).and.any(dout(:,ng)))
THEN
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.'
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.'
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.'
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.'
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.'
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. '
7000 IF (dout(iddu2d(m2fsco),ng).or.dout(iddv2d(m2fsco),ng)) &
7001 &
WRITE (out,170) .true.,
'Dout(M2fsco)', &
7002 &
'Write out 2D Stokes Coriolis.'
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.'
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.'
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.'
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.'
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.'
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.'
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.'
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.'
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.'
7086 IF (dout(iddu3d(m3fsco),ng).or.dout(iddv3d(m3fsco),ng)) &
7087 &
WRITE (out,170) .true.,
'Dout(M3fsco)', &
7088 &
'Write out 3D Stokes Coriolis'
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.'
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.'
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.'
7109#if defined DIAGNOSTICS_TS && defined SOLVE3D
7110 IF (ndia(ng).gt.0)
THEN
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)))
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)))
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)))
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)))
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)))
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)))
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)))
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)))
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)))
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)))
7187# if defined TS_DIF2 || defined TS_DIF4
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)))
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)))
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)))
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)))
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)))
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)))
7233# if defined MIX_GEO_TS || defined MIX_ISO_TS
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)))
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)))
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)))
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)))
7271 WRITE (out,120) extractflag(ng),
'ExtractFlag', &
7272 &
'Field extraction flag to interpolate or decimate.'
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.'
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.'
7293#if defined PIO_LIB && defined DISTRIBUTE
7294 SELECT CASE (pio_method)
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.'
7308 WRITE (out,120) pio_method,
'pio_method', trim(text)
7310 WRITE (out,120) pio_numiotasks,
'pio_NumIOtasks', &
7311 &
'Number of mpi-processors used for I/O.'
7313 WRITE (out,120) pio_stride,
'pio_stride', &
7314 &
'Stride step in the mpi-rank between I/O tasks.'
7316 WRITE (out,120) pio_base,
'pio_base', &
7317 &
'Offset for the first I/O task.'
7319 WRITE (out,120) pio_aggregator,
'pio_aggregator', &
7320 &
'Number of mpi-aggregators for intra-communications.'
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.'
7328 WRITE (out,120) pio_rearranger,
'pio_rearranger', trim(text)
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.'
7336 WRITE (out,120) pio_rearr_comm,
'pio_rearr_comm', trim(text)
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'
7348 WRITE (out,120) pio_rearr_fcd,
'pio_rearr_fcd', trim(text)
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.'
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.'
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.'
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.'
7381 IF (master.and.lwrite)
THEN
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)
7389 WRITE (out,230)
' Output GST Restart File: ', &
7390 & trim(gst(ng)%name)
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)
7399 WRITE (out,230)
' Prefix for History Files: ', &
7400 & trim(his(ng)%head)
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)
7409 WRITE (out,230)
'Prefix for History Extract Files: ', &
7410 & trim(xtr(ng)%head)
7415 IF (ndeftlm(ng).eq.0)
THEN
7416 WRITE (out,230)
' Output Tangent File: ', &
7417 & trim(tlm(ng)%name)
7419 WRITE (out,230)
' Prefix for Tangent Files: ', &
7420 & trim(tlm(ng)%head)
7423# ifdef WEAK_CONSTRAINT
7424 WRITE (out,230)
' Output Impulse Forcing File: ', &
7425 & trim(tlf(ng)%name)
7429 IF (ndefadj(ng).eq.0)
THEN
7430 WRITE (out,230)
' Output Adjoint File: ', &
7431 & trim(adm(ng)%name)
7433 WRITE (out,230)
' Prefix for Adjoint Files: ', &
7434 & trim(adm(ng)%head)
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)
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)
7450 WRITE (out,230)
' Prefix for Averages Files: ', &
7451 & trim(avg(ng)%head)
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)
7460 IF (ndefdia(ng).eq.0)
THEN
7461 WRITE (out,230)
' Output Diagnostics File: ', &
7462 & trim(dia(ng)%name)
7464 WRITE (out,230)
' Prefix for Diagnostics Files: ', &
7465 & trim(dia(ng)%head)
7469 WRITE (out,230)
' Output Stations File: ', &
7470 & trim(sta(ng)%name)
7473 WRITE (out,230)
' Output Floats File: ', &
7474 & trim(flt(ng)%name)
7476# ifdef MODEL_COUPLING
7477 WRITE (out,230)
' Physical parameters File: ', &
7484 IF (.not.find_file(ng, out, fname,
'GRXNAME'))
THEN
7485 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7487 IF (master.and.lwrite)
WRITE (out,230) &
7488 &
' Input History Extract Grid File: ', trim(fname)
7493 IF (.not.find_file(ng, out, fname,
'GRDNAME'))
THEN
7494 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7496 IF (master.and.lwrite)
WRITE (out,230) &
7497 &
' Input Grid File: ', trim(fname)
7500#if !defined CORRELATION
7503 IF (.not.find_file(ng, out, fname,
'NGCNAME'))
THEN
7504 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7506 IF (master.and.lwrite)
WRITE (out,230) &
7507 &
' Nesting grid connectivity File: ', trim(fname)
7514 IF (.not.find_file(ng, out, fname,
'ININAME'))
THEN
7515 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7517 IF (master.and.lwrite)
WRITE (out,230) &
7518 ' Input Nonlinear Initial File: ', trim(fname)
7521# if !defined CORRELATION
7522# if defined TANGENT && \
7524 defined jedi || defined opt_observations || \
7525 defined sanity_check || defined sensitivity_4dvar || \
7528 IF (.not.find_file(ng, out, fname,
'ITLNAME'))
THEN
7529 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7531 IF (master.and.lwrite)
WRITE (out,230) &
7532 &
' Input Tangent Initial File: ', trim(fname)
7535# if defined WEAK_CONSTRAINT && \
7537 defined rbl4dvar_ana_sensitivity || \
7538 defined rbl4dvar_fct_sensitivity || \
7539 defined r_symmetry || \
7542 IF (.not.find_file(ng, out, fname,
'IRPNAME'))
THEN
7543 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7545 IF (master.and.lwrite)
WRITE (out,230) &
7546 &
' Input Representer Initial File: ', trim(fname)
7549# if defined ADJOINT && \
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)
7558 IF (.not.find_file(ng, out, fname,
'IADNAME'))
THEN
7559 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7561 IF (master.and.lwrite)
WRITE (out,230) &
7562 &
' Input Adjoint Initial File: ', trim(fname)
7567#if !defined CORRELATION
7569 IF (luvsrc(ng).or.lwsrc(ng).or.(any(ltracersrc(:,ng))))
THEN
7571 IF (.not.find_file(ng, out, fname,
'SSFNAME'))
THEN
7572 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7574 IF (master.and.lwrite)
WRITE (out,230) &
7575 &
' Input Sources/Sinks File: ', trim(fname)
7579# if defined SSH_TIDES || defined UV_TIDES
7582 IF (.not.find_file(ng, out, fname,
'TIDENAME'))
THEN
7583 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7585 IF (master.and.lwrite)
WRITE (out,230) &
7586 &
' Tidal Forcing File: ', trim(fname)
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)) &
7598 IF (ifile.eq.1)
THEN
7599 IF (master.and.lwrite)
WRITE (out,310) &
7600 &
' Input Forcing File ', i,
': ', trim(fname)
7602 IF (master.and.lwrite)
WRITE (out,
'(37x,a)') trim(fname)
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)) &
7616 IF (ifile.eq.1)
THEN
7617 IF (master.and.lwrite)
WRITE (out,310) &
7618 &
' Input Climatology File ',i,
': ',trim(fname)
7620 IF (master.and.lwrite)
WRITE (out,
'(37x,a)') &
7627# ifndef ANA_NUDGCOEF
7628 IF (lnudgem2clm(ng).or.lnudgem3clm(ng).or. &
7629 & (any(lnudgetclm(:,ng))))
THEN
7631 IF (.not.find_file(ng, out, fname,
'NUDNAME'))
THEN
7632 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7634 IF (master.and.lwrite)
WRITE (out,230) &
7635 &
' Input Nudge Coefficients File: ', trim(fname)
7639# if defined FORWARD_READ && \
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
7646 IF (ifile.eq.1)
THEN
7647 IF (master.and.lwrite)
WRITE (out,230) &
7648 &
' Input Forward State File: ', trim(fname)
7650 WRITE (out,
'(37x,a)') trim(fname)
7655# if defined AD_SENSITIVITY || defined I4DVAR_ANA_SENSITIVITY || \
7656 defined opt_observations || defined sensitivity_4dvar || \
7660 IF (.not.find_file(ng, out, fname,
'ADSNAME'))
THEN
7661 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7663 IF (master.and.lwrite)
WRITE (out,230) &
7664 &
' Input Adjoint Sensitivity File: ', trim(fname)
7669 IF (obcdata(ng))
THEN
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)) &
7677 IF (ifile.eq.1)
THEN
7678 IF (master.and.lwrite)
WRITE (out,310) &
7679 &
' Input Lateral Boundary File ', i,
': ', &
7682 IF (master.and.lwrite)
WRITE (out,
'(37x,a)') &
7691 IF (.not.find_file(ng, out, fname,
'SPOSNAM'))
THEN
7692 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7694 IF (master.and.lwrite)
WRITE (out,230) &
7695 &
' Station positions File: ', trim(fname)
7701 IF (.not.find_file(ng, out, fname,
'APARNAM'))
THEN
7702 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7704 IF (master.and.lwrite)
WRITE (out,230) &
7705 &
' Assimilation Parameters File: ', trim(fname)
7708#if !defined CORRELATION
7711 IF (.not.find_file(ng, out, fname,
'FPOSNAM'))
THEN
7712 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7714 IF (master.and.lwrite)
WRITE (out,230) &
7715 &
' Initial Floats Positions File: ', trim(fname)
7720 IF (.not.find_file(ng, out, fname,
'IPARNAM'))
THEN
7721 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7723 IF (master.and.lwrite)
WRITE (out,230) &
7724 &
' Ice Model Parameters File: ', trim(fname)
7729 IF (.not.find_file(ng, out, fname,
'BPARNAM'))
THEN
7730 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7732 IF (master.and.lwrite)
WRITE (out,230) &
7733 &
' Biology Parameters File: ', trim(fname)
7738 IF (.not.find_file(ng, out, fname,
'VARNAME'))
THEN
7739 IF (founderror(exit_flag, noerror, __line__, myfile))
RETURN
7741 IF (master.and.lwrite)
WRITE (out,230) &
7742 &
'ROMS I/O variables Metadata File: ', trim(fname)
7745 IF (nuser.gt.0)
THEN
7746 IF (master.and.lwrite)
WRITE (out,230) &
7747 &
' Input/Output USER File: ', trim(usrname)
7754 IF (nuser.gt.0)
THEN
7755 IF (master.and.lwrite)
THEN
7758 WRITE (out,250) user(i), i, i
7763#if !defined ANA_TIDES && \
7764 (defined tide_generating_forces || \
7765 defined ssh_tides || defined uv_tides)
7772 CALL tides_date (ng)
7776#if defined WEAK_CONSTRAINT && \
7777 (defined posterior_eofs || defined posterior_error_f || \
7778 defined posterior_error_i)
7786 IF (nouter.gt.1)
THEN
7788 WRITE (out,330)
'Nouter = ', nouter, &
7789 &
'Posterior analysis error available for Nouter=1 only.'
7803 IF (.not.
allocated(runtimeday))
THEN
7804 allocate ( runtimeday(ngrids) )
7806 IF (.not.
allocated(runtimesec))
THEN
7807 allocate ( runtimesec(ngrids) )
7810 runtimesec(ng)=real(ntimes(ng),r8)*dt(ng)
7811 runtimeday(ng)=runtimesec(ng)*sec2day
7814 IF (abs(runtimesec(1)-runtimesec(ng)).ne.0.0_r8)
THEN
7816 WRITE (out,340) 1, runtimesec( 1), runtimeday( 1), &
7817 & ng, runtimesec(ng), runtimeday(ng)
7834 IF (i.gt.nat) itrc=inert(i-nat)
7840 nl_tnu4(itrc,ng)=sqrt(abs(nl_tnu4(itrc,ng)))
7842 ad_tnu4(itrc,ng)=sqrt(abs(ad_tnu4(itrc,ng)))
7844#if defined TANGENT || defined TL_IOMS
7845 tl_tnu4(itrc,ng)=sqrt(abs(tl_tnu4(itrc,ng)))
7850 IF (tnudg(itrc,ng).gt.0.0_r8)
THEN
7851 tnudg(itrc,ng)=1.0_r8/(tnudg(itrc,ng)*86400.0_r8)
7853 tnudg(itrc,ng)=0.0_r8
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))
7875# if defined FOUR_DVAR || defined FORWARD_WRITE
7876 IF (extractflag(ng).ne.2)
THEN
7877 WRITE (out,370) ng, extractflag(ng)
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, &
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, &
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, &
7914# if !(defined PIO_LIB && \
7915 (defined asynchronous_pio || defined asynchronous_scorpio)) && \
7917 & /,1x,
'OCN Communicator : ',i0,
', PET size = ',i0,/, &
7919 & /,1x,
'Input Script : ',a,/, &
7922 & /,1x,
'GIT Root URL : ',a, &
7923 & /,1x,
'GIT Revision : ',a, &
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, &
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, &
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:',/)
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, &
7970 265
FORMAT (/,
' READ_PHYPAR - Invalid input parameter, ',a, &
7972 280
FORMAT (/,
' READ_PHYPAR - Variable index not yet loaded, ', a)
7973 290
FORMAT (/,
' READ_PHYPAR - Invalid dimension parameter, ',a,i0, &
7975 300
FORMAT (/,
' READ_PHYPAR - Invalid dimension parameter, ',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 ', &
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)