Ticket #687: def_info.F

File def_info.F, 119.1 KB (added by m.hadfield, 9 years ago)
Line 
1#include "cppdefs.h"
2 SUBROUTINE def_info (ng, model, ncid, ncname, DimIDs)
3!
4!svn $Id$
5!================================================== Hernan G. Arango ===
6! Copyright (c) 2002-2015 The ROMS/TOMS Group !
7! Licensed under a MIT/X style license !
8! See License_ROMS.txt !
9!=======================================================================
10! !
11! This routine defines information variables in requested NetCDF !
12! file. !
13! !
14! On Input: !
15! !
16! ng Nested grid number (integer). !
17! model Calling model identifier (integer). !
18! ncid NetCDF file ID (integer). !
19! ncname NetCDF file name (character). !
20! DimIDs NetCDF dimensions IDs (integer vector): !
21! DimIDs( 1) => XI-dimension at RHO-points. !
22! DimIDs( 2) => XI-dimension at U-points. !
23! DimIDs( 3) => XI-dimension at V-points. !
24! DimIDs( 4) => XI-dimension at PSI-points. !
25! DimIDs( 5) => ETA-dimension at RHO-points. !
26! DimIDs( 6) => ETA-dimension at U-points. !
27! DimIDs( 7) => ETA-dimension at V-points. !
28! DimIDs( 8) => ETA-dimension at PSI-points. !
29! DimIDs( 9) => S-dimension at RHO-points. !
30! DimIDs(10) => S-dimension at W-points. !
31! DimIDs(11) => Number of tracers dimension. !
32! DimIDs(12) => Unlimited time record dimension. !
33! DimIDs(13) => Number of stations dimension. !
34! DimIDs(14) => Boundary dimension. !
35! DimIDs(15) => Number of floats dimension. !
36! DimIDs(16) => Number sediment bed layers dimension. !
37! DimIDs(17) => Dimension 2D water RHO-points. !
38! DimIDs(18) => Dimension 2D water U-points. !
39! DimIDs(19) => Dimension 2D water V-points. !
40! DimIDs(20) => Dimension 3D water RHO-points. !
41! DimIDs(21) => Dimension 3D water U-points. !
42! DimIDs(23) => Dimension 3D water W-points. !
43! DimIDs(24) => Dimension sediment bed water points. !
44! DimIDs(25) => Number of EcoSim phytoplankton groups. !
45! DimIDs(26) => Number of EcoSim bateria groups. !
46! DimIDs(27) => Number of EcoSim DOM groups. !
47! DimIDs(28) => Number of EcoSim fecal groups. !
48! DimIDs(29) => Number of state variables. !
49! DimIDs(30) => Number of 3D variables time levels (2). !
50! DimIDs(31) => Number of 2D variables time levels (3). !
51! DimIDs(32) => Number of sediment tracers. !
52! !
53! On Output: !
54! !
55! exit_flag Error flag (integer) stored in MOD_SCALARS !
56! ioerror NetCDF return code (integer) stored in MOD_IOUNITS !
57! !
58!=======================================================================
59!
60 USE mod_param
61 USE mod_parallel
62#ifdef FOUR_DVAR
63 USE mod_fourdvar
64#endif
65 USE mod_grid
66 USE mod_iounits
67 USE mod_ncparam
68 USE mod_netcdf
69 USE mod_scalars
70 USE mod_strings
71!
72 USE def_var_mod, ONLY : def_var
73#if !defined PARALLEL_IO && defined DISTRIBUTE
74 USE distribute_mod, ONLY : mp_bcasti
75#endif
76 USE strings_mod, ONLY : join_string
77!
78 implicit none
79!
80! Imported variable declarations.
81!
82 integer, intent(in) :: ng, model, ncid
83 integer, intent(in) :: DimIDs(32)
84 character (*), intent(in) :: ncname
85!
86! Local variable declarations.
87!
88 integer, parameter :: Natt = 25
89
90 integer :: brydim, i, ie, is, j, lstr, varid
91 integer :: srdim, stadim, status, swdim, trcdim, usrdim
92#ifdef SEDIMENT
93 integer :: seddim
94#endif
95#ifdef FOUR_DVAR
96 integer :: statedim
97#endif
98#if defined BIOLOGY && defined ECOSIM
99 integer :: bacdim, domdim, fecdim, phydim
100
101 integer :: biodim(2)
102#endif
103#if !defined PARALLEL_IO && defined DISTRIBUTE
104 integer :: ibuffer(2)
105#endif
106 integer :: p2dgrd(2), tbrydim(2)
107 integer :: t2dgrd(3), u2dgrd(3), v2dgrd(3)
108
109 integer :: def_dim
110
111 real(r8) :: Aval(6)
112
113 character (len=11 ) :: frcatt
114 character (len=50 ) :: tiling
115 character (len=80 ) :: type
116 character (len=120) :: Vinfo(Natt)
117#ifdef FOUR_DVAR
118 character (len=512) :: state_vector
119#endif
120#ifdef BIOLOGY
121 character (len=512) :: bio_file
122#endif
123 character (len=1024) :: string
124!
125!-----------------------------------------------------------------------
126! Set dimension variables.
127!-----------------------------------------------------------------------
128!
129 p2dgrd(1)=DimIDs(4)
130 p2dgrd(2)=DimIDs(8)
131 t2dgrd(1)=DimIDs(1)
132 t2dgrd(2)=DimIDs(5)
133 u2dgrd(1)=DimIDs(2)
134 u2dgrd(2)=DimIDs(6)
135 v2dgrd(1)=DimIDs(3)
136 v2dgrd(2)=DimIDs(7)
137 srdim=DimIDs(9)
138 swdim=DimIDs(10)
139 trcdim=DimIDs(11)
140#ifdef SEDIMENT
141 seddim=DimIDs(32)
142#endif
143 stadim=DimIDs(13)
144 brydim=DimIDs(14)
145#ifdef FOUR_DVAR
146 statedim=DimIDs(29)
147#endif
148 tbrydim(1)=DimIDs(11)
149 tbrydim(2)=DimIDs(14)
150#if defined ECOSIM && defined SOLVE3D
151 phydim=DimIDs(25)
152 bacdim=DimIDs(26)
153 domdim=DimIDs(27)
154 fecdim=DimIDs(28)
155 biodim(1)=phydim
156 biodim(2)=fecdim
157#endif
158!
159! Set dimension for generic user parameters.
160!
161 IF ((Nuser.gt.0).and.(ncid.ne.GST(ng)%ncid)) THEN
162 status=def_dim(ng, model, ncid, ncname, 'Nuser', 25, usrdim)
163 IF (exit_flag.ne.NoError) RETURN
164 END IF
165!
166! Initialize local information variable arrays.
167!
168 DO i=1,Natt
169 DO j=1,LEN(Vinfo(1))
170 Vinfo(i)(j:j)=' '
171 END DO
172 END DO
173 DO i=1,6
174 Aval(i)=0.0_r8
175 END DO
176!
177!-----------------------------------------------------------------------
178! Define global attributes.
179!-----------------------------------------------------------------------
180!
181 IF (OutThread) THEN
182!
183! Define history global attribute.
184!
185 IF (LEN_TRIM(date_str).gt.0) THEN
186 WRITE (history,'(a,1x,a,", ",a)') 'ROMS/TOMS, Version', &
187 & TRIM( version), &
188 & TRIM(date_str)
189 ELSE
190 WRITE (history,'(a,1x,a)') 'ROMS/TOMS, Version', &
191 & TRIM(version)
192 END IF
193!
194! Set tile decomposition global attribute.
195!
196 WRITE (tiling,10) NtileI(ng), NtileJ(ng)
197!
198! Define file name global attribute.
199!
200 IF (exit_flag.eq.NoError) THEN
201 status=nf90_put_att(ncid, nf90_global, 'file', &
202 & TRIM(ncname))
203 IF (status.ne.nf90_noerr) THEN
204 IF (Master) WRITE (stdout,20) 'file', TRIM(ncname)
205 exit_flag=3
206 ioerror=status
207 END IF
208 END IF
209
210#ifndef DEBUGGING
211!
212! Define NetCDF format type.
213!
214 IF (exit_flag.eq.NoError) THEN
215# ifdef HDF5
216 status=nf90_put_att(ncid, nf90_global, 'format', &
217 & 'netCDF-4/HDF5 file')
218# else
219 status=nf90_put_att(ncid, nf90_global, 'format', &
220 & 'netCDF-3 64bit offset file')
221# endif
222 IF (status.ne.nf90_noerr) THEN
223 IF (Master) WRITE (stdout,20) 'format', TRIM(ncname)
224 exit_flag=3
225 ioerror=status
226 END IF
227 END IF
228
229#endif
230!
231! Define file climate and forecast metadata convention global
232! attribute.
233!
234 type='CF-1.4'
235 IF (exit_flag.eq.NoError) THEN
236 status=nf90_put_att(ncid, nf90_global, 'Conventions', &
237 & TRIM(type))
238 IF (status.ne.nf90_noerr) THEN
239 IF (Master) WRITE (stdout,20) 'Conventions', TRIM(ncname)
240 exit_flag=3
241 ioerror=status
242 END IF
243 END IF
244!
245! Define file type global attribute.
246!
247 IF (ncid.eq.ADM(ng)%ncid) THEN
248 type='ROMS/TOMS adjoint history file'
249 ELSE IF (ncid.eq.AVG(ng)%ncid) THEN
250#if defined AD_AVERAGES && defined ADJOINT
251 type='ROMS/TOMS adjoint model averages file'
252#elif defined RP_AVERAGES && defined TL_IOMS
253 type='ROMS/TOMS representer model averages file'
254#elif defined TL_AVERAGES && defined TANGENT
255 type='ROMS/TOMS tangent linear model averages file'
256#else
257 type='ROMS/TOMS nonlinear model averages file'
258#endif
259 ELSE IF (ncid.eq.DIA(ng)%ncid) THEN
260 type='ROMS/TOMS diagnostics file'
261 ELSE IF (ncid.eq.FLT(ng)%ncid) THEN
262 type='ROMS/TOMS floats file'
263 ELSE IF (ncid.eq.ERR(ng)%ncid) THEN
264 type='ROMS/TOMS posterior analysis error covariance matrix'
265 ELSE IF (ncid.eq.GST(ng)%ncid) THEN
266 type='ROMS/TOMS GST check pointing restart file'
267 ELSE IF (ncid.eq.HSS(ng)%ncid) THEN
268 type='ROMS/TOMS 4DVAR Hessian eigenvectors file'
269 ELSE IF (ncid.eq.HIS(ng)%ncid) THEN
270 type='ROMS/TOMS history file'
271 ELSE IF (ncid.eq.ITL(ng)%ncid) THEN
272 type='ROMS/TOMS tangent linear model initial file'
273 ELSE IF (ncid.eq.LCZ(ng)%ncid) THEN
274 type='ROMS/TOMS 4DVAR Lanczos vectors file'
275 ELSE IF (ncid.eq.NRM(1,ng)%ncid) THEN
276 type='ROMS/TOMS initial conditions error covariance norm file'
277 ELSE IF (ncid.eq.NRM(2,ng)%ncid) THEN
278 type='ROMS/TOMS model error covariance norm file'
279 ELSE IF (ncid.eq.NRM(3,ng)%ncid) THEN
280 type='ROMS/TOMS boundary conditions error covariance norm file'
281 ELSE IF (ncid.eq.NRM(4,ng)%ncid) THEN
282 type='ROMS/TOMS surface forcing error covariance norm file'
283 ELSE IF (ncid.eq.RST(ng)%ncid) THEN
284 type='ROMS/TOMS restart file'
285 ELSE IF (ncid.eq.STA(ng)%ncid) THEN
286 type='ROMS/TOMS station file'
287 ELSE IF (ncid.eq.TLF(ng)%ncid) THEN
288 type='ROMS/TOMS tangent linear impulse forcing file'
289 ELSE IF (ncid.eq.TLM(ng)%ncid) THEN
290 type='ROMS/TOMS tangent linear history file'
291 END IF
292 IF (exit_flag.eq.NoError) THEN
293 status=nf90_put_att(ncid, nf90_global, 'type', &
294 & TRIM(type))
295 IF (status.ne.nf90_noerr) THEN
296 IF (Master) WRITE (stdout,20) 'type', TRIM(ncname)
297 exit_flag=3
298 ioerror=status
299 END IF
300 END IF
301
302#ifdef FOUR_DVAR
303!
304! Set state vector variables.
305!
306 is=1
307 state_vector=' '
308 DO i=1,NstateVar(ng)
309 lstr=LEN_TRIM(Vname(1,idSvar(i)))
310 ie=is+lstr
311 state_vector(is:ie)=TRIM(Vname(1,idSvar(i)))//', '
312 is=ie+2
313 END DO
314#endif
315!
316! Define other global attributes to NetCDF file.
317!
318 IF (exit_flag.eq.NoError) THEN
319 status=nf90_put_att(ncid, nf90_global, 'title', &
320 & TRIM(title))
321 IF (status.ne.nf90_noerr) THEN
322 IF (Master) WRITE (stdout,20) 'title', TRIM(ncname)
323 exit_flag=3
324 ioerror=status
325 END IF
326 END IF
327
328#ifdef FOUR_DVAR
329 IF (exit_flag.eq.NoError) THEN
330 lstr=LEN_TRIM(state_vector)-1
331 status=nf90_put_att(ncid, nf90_global, 'state_vector', &
332 & state_vector(1:lstr))
333 IF (status.ne.nf90_noerr) THEN
334 IF (Master) WRITE (stdout,20) 'state_vector', TRIM(ncname)
335 exit_flag=3
336 ioerror=status
337 END IF
338 END IF
339#endif
340
341#ifdef PROPAGATOR
342 IF (exit_flag.eq.NoError) THEN
343 status=nf90_put_att(ncid, nf90_global, 'gst_file', &
344 & TRIM(GST(ng)%name))
345 IF (status.ne.nf90_noerr) THEN
346 IF (Master) WRITE (stdout,20) 'gst_file', TRIM(ncname)
347 exit_flag=3
348 ioerror=status
349 END IF
350 END IF
351#endif
352
353 IF (exit_flag.eq.NoError) THEN
354 status=nf90_put_att(ncid, nf90_global, 'rst_file', &
355 & TRIM(RST(ng)%name))
356 IF (status.ne.nf90_noerr) THEN
357 IF (Master) WRITE (stdout,20) 'rst_file', TRIM(ncname)
358 exit_flag=3
359 ioerror=status
360 END IF
361 END IF
362
363 IF (exit_flag.eq.NoError) THEN
364 IF (LdefHIS(ng)) THEN
365 IF (ndefHIS(ng).gt.0) THEN
366 status=nf90_put_att(ncid, nf90_global, 'his_base', &
367 & TRIM(HIS(ng)%base))
368 ELSE
369 status=nf90_put_att(ncid, nf90_global, 'his_file', &
370 & TRIM(HIS(ng)%name))
371 END IF
372 IF (status.ne.nf90_noerr) THEN
373 IF (Master) WRITE (stdout,20) 'his_file', TRIM(ncname)
374 exit_flag=3
375 ioerror=status
376 END IF
377 END IF
378 END IF
379
380#if defined AVERAGES || \
381 (defined AD_AVERAGES && defined ADJOINT) || \
382 (defined RP_AVERAGES && defined TL_IOMS) || \
383 (defined TL_AVERAGES && defined TANGENT)
384 IF (exit_flag.eq.NoError) THEN
385 IF (ndefAVG(ng).gt.0) THEN
386 status=nf90_put_att(ncid, nf90_global, 'avg_base', &
387 & TRIM(AVG(ng)%base))
388 ELSE
389 status=nf90_put_att(ncid, nf90_global, 'avg_file', &
390 & TRIM(AVG(ng)%name))
391 END IF
392 IF (status.ne.nf90_noerr) THEN
393 IF (Master) WRITE (stdout,20) 'avg_file', TRIM(ncname)
394 exit_flag=3
395 ioerror=status
396 END IF
397 END IF
398#endif
399
400#ifdef DIAGNOSTICS
401 IF (exit_flag.eq.NoError) THEN
402 IF (ndefDIA(ng).gt.0) THEN
403 status=nf90_put_att(ncid,nf90_global, 'dia_base', &
404 & TRIM(DIA(ng)%base))
405 ELSE
406 status=nf90_put_att(ncid, nf90_global, 'dia_file', &
407 & TRIM(DIA(ng)%name))
408 END IF
409 IF (status.ne.nf90_noerr) THEN
410 IF (Master) WRITE (stdout,20) 'dia_file', TRIM(ncname)
411 exit_flag=3
412 ioerror=status
413 END IF
414 END IF
415#endif
416
417#if defined WEAK_CONSTRAINT && \
418 (defined POSTERIOR_ERROR_F || defined POSTERIOR_ERROR_I)
419 IF (exit_flag.eq.NoError) THEN
420 status=nf90_put_att(ncid, nf90_global, 'err_file', &
421 & TRIM(ERR(ng)%name))
422 IF (status.ne.nf90_noerr) THEN
423 IF (Master) WRITE (stdout,20) 'err_file', TRIM(ncname)
424 exit_flag=3
425 ioerror=status
426 END IF
427 END IF
428#endif
429
430#ifdef STATIONS
431 IF (exit_flag.eq.NoError) THEN
432 status=nf90_put_att(ncid, nf90_global, 'sta_file', &
433 & TRIM(STA(ng)%name))
434 IF (status.ne.nf90_noerr) THEN
435 IF (Master) WRITE (stdout,20) 'sta_file', TRIM(ncname)
436 exit_flag=3
437 ioerror=status
438 END IF
439 END IF
440#endif
441
442#ifdef FLOATS
443 IF (exit_flag.eq.NoError) THEN
444 status=nf90_put_att(ncid, nf90_global, 'flt_file', &
445 & TRIM(FLT(ng)%name))
446 IF (status.ne.nf90_noerr) THEN
447 IF (Master) WRITE (stdout,20) 'flt_file', TRIM(ncname)
448 exit_flag=3
449 ioerror=status
450 END IF
451 END IF
452#endif
453
454#ifndef ANA_GRID
455 IF (exit_flag.eq.NoError) THEN
456 status=nf90_put_att(ncid, nf90_global, 'grd_file', &
457 & TRIM(GRD(ng)%name))
458 IF (status.ne.nf90_noerr) THEN
459 IF (Master) WRITE (stdout,20) 'grd_file', TRIM(ncname)
460 exit_flag=3
461 ioerror=status
462 END IF
463 END IF
464#endif
465
466#ifdef INI_FILE
467# ifdef NONLINEAR
468 IF (exit_flag.eq.NoError) THEN
469 status=nf90_put_att(ncid, nf90_global, 'ini_file', &
470 & TRIM(INI(ng)%name))
471 IF (status.ne.nf90_noerr) THEN
472 IF (Master) WRITE (stdout,20) 'ini_file', TRIM(ncname)
473 exit_flag=3
474 ioerror=status
475 END IF
476 END IF
477# endif
478
479# ifdef TANGENT
480 IF (exit_flag.eq.NoError) THEN
481 status=nf90_put_att(ncid,nf90_global, 'itl_file', &
482 & TRIM(ITL(ng)%name))
483 IF (status.ne.nf90_noerr) THEN
484 IF (Master) WRITE (stdout,20) 'itl_file', TRIM(ncname)
485 exit_flag=3
486 ioerror=status
487 END IF
488 END IF
489# endif
490
491# if defined ADJOINT && \
492 !(defined AD_SENSITIVITY || defined FOUR_DVAR || \
493 defined IS4DVAR_SENSITIVITY || defined OPT_OBSERVATIONS || \
494 defined SENSITIVITY_4DVAR || defined SO_SEMI || \
495 defined STOCHASTIC_OPT )
496 IF (exit_flag.eq.NoError) THEN
497 status=nf90_put_att(ncid, nf90_global, 'iad_file', &
498 & TRIM(IAD(ng)%name))
499 IF (status.ne.nf90_noerr) THEN
500 IF (Master) WRITE (stdout,20) 'iad_file', TRIM(ncname)
501 exit_flag=3
502 ioerror=status
503 END IF
504 END IF
505# endif
506#endif
507
508#if defined IS4DVAR || defined OPT_OBSERVATIONS || \
509 defined WEAK_CONSTRAINT
510 IF (exit_flag.eq.NoError) THEN
511 status=nf90_put_att(ncid, nf90_global, 'nrm_file', &
512 & TRIM(NRM(1,ng)%name))
513 IF (status.ne.nf90_noerr) THEN
514 IF (Master) WRITE (stdout,20) 'nrm_file', TRIM(ncname)
515 exit_flag=3
516 ioerror=status
517 END IF
518 END IF
519#endif
520
521#ifdef WEAK_CONSTRAINT
522 IF (exit_flag.eq.NoError) THEN
523 status=nf90_put_att(ncid, nf90_global, 'tlf_file', &
524 & TRIM(TLF(ng)%name))
525 IF (status.ne.nf90_noerr) THEN
526 IF (Master) WRITE (stdout,20) 'tlf_file', TRIM(ncname)
527 exit_flag=3
528 ioerror=status
529 END IF
530 END IF
531#endif
532
533#ifdef FOUR_DVAR
534 IF (exit_flag.eq.NoError) THEN
535 status=nf90_put_att(ncid, nf90_global, 'obs_file', &
536 & TRIM(OBS(ng)%name))
537 IF (status.ne.nf90_noerr) THEN
538 IF (Master) WRITE (stdout,20) 'obs_file', TRIM(ncname)
539 exit_flag=3
540 ioerror=status
541 END IF
542 END IF
543#endif
544
545#ifdef FRC_FILE
546 IF (exit_flag.eq.NoError) THEN
547 DO i=1,nFfiles(ng)
548 CALL join_string (FRC(i,ng)%files, FRC(i,ng)%Nfiles, &
549 & string, lstr)
550 WRITE (frcatt,30) i
551 status=nf90_put_att(ncid, nf90_global, frcatt, &
552 & string(1:lstr))
553 IF (status.ne.nf90_noerr) THEN
554 IF (Master) WRITE (stdout,20) TRIM(frcatt), TRIM(ncname)
555 exit_flag=3
556 ioerror=status
557 EXIT
558 END IF
559 END DO
560 END IF
561#endif
562
563 IF (ObcData(ng)) THEN
564 IF (exit_flag.eq.NoError) THEN
565 CALL join_string (BRY(ng)%files, BRY(ng)%Nfiles, &
566 & string, lstr)
567 status=nf90_put_att(ncid, nf90_global, 'bry_file', &
568 & string(1:lstr))
569 IF (status.ne.nf90_noerr) THEN
570 IF (Master) WRITE (stdout,20) 'bry_file', TRIM(ncname)
571 exit_flag=3
572 ioerror=status
573 END IF
574 END IF
575 END IF
576
577#if !(defined ANA_SSH || defined ANA_M2CLIMA || \
578 defined ANA_M3CLIMA || defined ANA_TCLIMA)
579 IF (Lclimatology(ng)) THEN
580 IF (exit_flag.eq.NoError) THEN
581 CALL join_string (CLM(ng)%files, CLM(ng)%Nfiles, &
582 & string,lstr)
583 status=nf90_put_att(ncid, nf90_global, 'clm_file', &
584 & string(1:lstr))
585 IF (status.ne.nf90_noerr) THEN
586 IF (Master) WRITE (stdout,20) 'clm_file', TRIM(ncname)
587 exit_flag=3
588 ioerror=status
589 END IF
590 END IF
591 END IF
592#endif
593
594#ifndef ANA_NUDGCOEF
595 IF (Lnudging(ng)) THEN
596 IF (exit_flag.eq.NoError) THEN
597 status=nf90_put_att(ncid, nf90_global, 'nud_file', &
598 & TRIM(NUD(ng)%name))
599 IF (status.ne.nf90_noerr) THEN
600 IF (Master) WRITE (stdout,20) 'nud_file', TRIM(ncname)
601 exit_flag=3
602 ioerror=status
603 END IF
604 END IF
605 END IF
606#endif
607
608#ifdef FORWARD_READ
609 IF (exit_flag.eq.NoError) THEN
610 status=nf90_put_att(ncid, nf90_global, 'fwd_file', &
611 & TRIM(FWD(ng)%name))
612 IF (status.ne.nf90_noerr) THEN
613 IF (Master) WRITE (stdout,20) 'fwd_file', TRIM(ncname)
614 exit_flag=3
615 ioerror=status
616 END IF
617 END IF
618#endif
619
620#if defined AD_SENSITIVITY || defined IS4DVAR_SENSITIVITY || \
621 defined OPT_OBSERVATIONS || defined SENSITIVITY_4DVAR || \
622 defined SO_SEMI
623 IF (exit_flag.eq.NoError) THEN
624 status=nf90_put_att(ncid, nf90_global, 'ads_file', &
625 & TRIM(ADS(ng)%name))
626 IF (status.ne.nf90_noerr) THEN
627 IF (Master) WRITE (stdout,20) 'ads_file', TRIM(ncname)
628 exit_flag=3
629 ioerror=status
630 END IF
631 END IF
632#endif
633
634#if !defined DEBUGGING && defined DISTRIBUTE
635 IF (exit_flag.eq.NoError) THEN
636 status=nf90_put_att(ncid, nf90_global, 'script_file', &
637 & TRIM(Iname))
638 IF (status.ne.nf90_noerr) THEN
639 IF (Master) WRITE (stdout,20) 'script_file', TRIM(ncname)
640 exit_flag=3
641 ioerror=status
642 END IF
643 END IF
644#endif
645
646#ifdef FOUR_DVAR
647 IF (exit_flag.eq.NoError) THEN
648 status=nf90_put_att(ncid, nf90_global, 'apar_file', &
649 & TRIM(aparnam))
650 IF (status.ne.nf90_noerr) THEN
651 IF (Master) WRITE (stdout,20) 'apar_file', TRIM(ncname)
652 exit_flag=3
653 ioerror=status
654 END IF
655 END IF
656#endif
657
658#ifdef BIOLOGY
659 IF (exit_flag.eq.NoError) THEN
660 status=nf90_put_att(ncid, nf90_global, 'bpar_file', &
661 & TRIM(bparnam))
662 IF (status.ne.nf90_noerr) THEN
663 IF (Master) WRITE (stdout,20) 'bpar_file', TRIM(ncname)
664 exit_flag=3
665 ioerror=status
666 END IF
667 END IF
668#endif
669
670#ifdef FLOATS
671 IF (exit_flag.eq.NoError) THEN
672 status=nf90_put_att(ncid, nf90_global, 'fpos_file', &
673 & TRIM(fposnam))
674 IF (status.ne.nf90_noerr) THEN
675 IF (Master) WRITE (stdout,20) 'fpos_file', TRIM(ncname)
676 exit_flag=3
677 ioerror=status
678 END IF
679 END IF
680#endif
681
682#ifdef STATIONS
683 IF (exit_flag.eq.NoError) THEN
684 status=nf90_put_att(ncid, nf90_global, 'spos_file', &
685 & TRIM(sposnam))
686 IF (status.ne.nf90_noerr) THEN
687 IF (Master) WRITE (stdout,20) 'spos_file', TRIM(ncname)
688 exit_flag=3
689 ioerror=status
690 END IF
691 END IF
692#endif
693
694#ifndef DEBUGGING
695!
696! NLM Lateral boundary conditions.
697!
698 IF (exit_flag.eq.NoError) THEN
699 CALL lbc_putatt (ng, ncid, ncname, 'NLM_LBC', LBC, status)
700 IF (status.ne.nf90_noerr) THEN
701 IF (Master) WRITE (stdout,20) 'NLM_LBC', TRIM(ncname)
702 exit_flag=3
703 ioerror=status
704 END IF
705 END IF
706
707# if defined ADJOINT || defined TANGENT || defined TL_IOMS
708!
709! Adjoint-based lateral boundary conditions.
710!
711 IF (exit_flag.eq.NoError) THEN
712 CALL lbc_putatt (ng, ncid, ncname, 'ADM_LBC', ad_LBC, status)
713 IF (status.ne.nf90_noerr) THEN
714 IF (Master) WRITE (stdout,20) 'ADM_LBC', TRIM(ncname)
715 exit_flag=3
716 ioerror=status
717 END IF
718 END IF
719# endif
720#endif
721!
722! SVN repository information.
723!
724 IF (exit_flag.eq.NoError) THEN
725 status=nf90_put_att(ncid, nf90_global, 'svn_url', &
726 & TRIM(svn_url))
727 IF (status.ne.nf90_noerr) THEN
728 IF (Master) WRITE (stdout,20) 'svn_url', TRIM(ncname)
729 exit_flag=3
730 ioerror=status
731 END IF
732 END IF
733
734#if !defined DEBUGGING && defined SVN_REV
735 IF (exit_flag.eq.NoError) THEN
736 status=nf90_put_att(ncid, nf90_global, 'svn_rev', &
737 & TRIM(svn_rev))
738 IF (status.ne.nf90_noerr) THEN
739 IF (Master) WRITE (stdout,20) 'svn_rev', TRIM(ncname)
740 exit_flag=3
741 ioerror=status
742 END IF
743 END IF
744#endif
745#ifndef DEBUGGING
746!
747! Local root directory, cpp header directory and file, and analytical
748! directory
749!
750# ifdef ROOT_DIR
751 IF (exit_flag.eq.NoError) THEN
752 status=nf90_put_att(ncid, nf90_global, 'code_dir', &
753 & TRIM(Rdir))
754 IF (status.ne.nf90_noerr) THEN
755 IF (Master) WRITE (stdout,20) 'code_dir', TRIM(ncname)
756 exit_flag=3
757 ioerror=status
758 END IF
759 END IF
760# endif
761
762# ifdef HEADER_DIR
763 IF (exit_flag.eq.NoError) THEN
764 status=nf90_put_att(ncid, nf90_global, 'header_dir', &
765 & TRIM(Hdir))
766 IF (status.ne.nf90_noerr) THEN
767 IF (Master) WRITE (stdout,20) 'header_dir', TRIM(ncname)
768 exit_flag=3
769 ioerror=status
770 END IF
771 END IF
772# endif
773
774# ifdef ROMS_HEADER
775 IF (exit_flag.eq.NoError) THEN
776 status=nf90_put_att(ncid, nf90_global, 'header_file', &
777 & TRIM(Hfile))
778 IF (status.ne.nf90_noerr) THEN
779 IF (Master) WRITE (stdout,20) 'header_file', TRIM(ncname)
780 exit_flag=3
781 ioerror=status
782 END IF
783 END IF
784# endif
785#endif
786#ifndef DEBUGGING
787!
788! Attributes describing platform and compiler
789!
790 IF (exit_flag.eq.NoError) THEN
791 status=nf90_put_att(ncid, nf90_global, 'os', &
792 & TRIM(my_os))
793 IF (status.ne.nf90_noerr) THEN
794 IF (Master) WRITE (stdout,20) 'os', TRIM(ncname)
795 exit_flag=3
796 ioerror=status
797 END IF
798 END IF
799
800 IF (exit_flag.eq.NoError) THEN
801 status=nf90_put_att(ncid, nf90_global, 'cpu', &
802 & TRIM(my_cpu))
803 IF (status.ne.nf90_noerr) THEN
804 IF (Master) WRITE (stdout,20) 'cpu', TRIM(ncname)
805 exit_flag=3
806 ioerror=status
807 END IF
808 END IF
809
810 IF (exit_flag.eq.NoError) THEN
811 status=nf90_put_att(ncid, nf90_global, 'compiler_system', &
812 & TRIM(my_fort))
813 IF (status.ne.nf90_noerr) THEN
814 IF (Master) WRITE (stdout,20) 'compiler_system', &
815 & TRIM(ncname)
816 exit_flag=3
817 ioerror=status
818 END IF
819 END IF
820
821 IF (exit_flag.eq.NoError) THEN
822 status=nf90_put_att(ncid, nf90_global, 'compiler_command', &
823 & TRIM(my_fc))
824 IF (status.ne.nf90_noerr) THEN
825 IF (Master) WRITE (stdout,20) 'compiler_command', &
826 & TRIM(ncname)
827 exit_flag=3
828 ioerror=status
829 END IF
830 END IF
831
832 IF (exit_flag.eq.NoError) THEN
833 status=nf90_put_att(ncid, nf90_global, 'compiler_flags', &
834 & TRIM(my_fflags))
835 IF (status.ne.nf90_noerr) THEN
836 IF (Master) WRITE (stdout,20) 'compiler_flags', TRIM(ncname)
837 exit_flag=3
838 ioerror=status
839 END IF
840 END IF
841!
842! Tiling and history attributes.
843!
844 IF (exit_flag.eq.NoError) THEN
845 status=nf90_put_att(ncid, nf90_global, 'tiling', &
846 & TRIM(tiling))
847 IF (status.ne.nf90_noerr) THEN
848 IF (Master) WRITE (stdout,20) 'tiling', TRIM(ncname)
849 exit_flag=3
850 ioerror=status
851 END IF
852 END IF
853
854 IF (exit_flag.eq.NoError) THEN
855 status=nf90_put_att(ncid, nf90_global, 'history', &
856 & TRIM(history))
857 IF (status.ne.nf90_noerr) THEN
858 IF (Master) WRITE (stdout,20) 'history', TRIM(ncname)
859 exit_flag=3
860 ioerror=status
861 END IF
862 END IF
863!
864! Analytical header files used.
865!
866 IF (exit_flag.eq.NoError) THEN
867 CALL join_string (ANANAME, SIZE(ANANAME), string, lstr)
868 IF (lstr.gt.0) THEN
869 status=nf90_put_att(ncid, nf90_global, 'ana_file', &
870 & string(1:lstr))
871 IF (status.ne.nf90_noerr) THEN
872 IF (Master) WRITE (stdout,20) 'ana_file', TRIM(ncname)
873 exit_flag=3
874 ioerror=status
875 END IF
876 END IF
877 END IF
878#endif
879
880#ifdef BIOLOGY
881!
882! Biology model header file used.
883!
884 IF (exit_flag.eq.NoError) THEN
885 DO i=1,512
886 bio_file(i:i)='-'
887 END DO
888 status=nf90_put_att(ncid, nf90_global, 'bio_file', &
889 & bio_file)
890 IF (status.ne.nf90_noerr) THEN
891 IF (Master) WRITE (stdout,20) 'bio_file', TRIM(ncname)
892 exit_flag=3
893 ioerror=status
894 END IF
895 END IF
896#endif
897
898#ifndef DEBUGGING
899!
900! Activated CPP options.
901!
902 IF (exit_flag.eq.NoError) THEN
903 lstr=LEN_TRIM(Coptions)-1
904 status=nf90_put_att(ncid, nf90_global, 'CPP_options', &
905 & TRIM(Coptions(1:lstr)))
906 IF (status.ne.nf90_noerr) THEN
907 IF (Master) WRITE (stdout,20) 'CPP_options', TRIM(ncname)
908 exit_flag=3
909 ioerror=status
910 END IF
911 END IF
912#endif
913 END IF
914
915#if !defined PARALLEL_IO && defined DISTRIBUTE
916 ibuffer(1)=exit_flag
917 ibuffer(2)=ioerror
918 CALL mp_bcasti (ng, model, ibuffer)
919 exit_flag=ibuffer(1)
920 ioerror=ibuffer(2)
921#endif
922 IF (exit_flag.ne.NoError) RETURN
923
924#ifdef PROPAGATOR
925!
926! Avoid writing other information variables if GST check pointing
927! NetCDF file.
928!
929 IF (ncid.eq.GST(ng)%ncid) RETURN
930#endif
931!
932!-----------------------------------------------------------------------
933! Define running parameters.
934!-----------------------------------------------------------------------
935!
936! Time stepping parameters.
937!
938 Vinfo( 1)='ntimes'
939 Vinfo( 2)='number of long time-steps'
940 status=def_var(ng, model, ncid, varid, nf90_int, &
941 & 1, (/0/), Aval, Vinfo, ncname, &
942 & SetParAccess = .FALSE.)
943 IF (exit_flag.ne.NoError) RETURN
944
945 Vinfo( 1)='ndtfast'
946 Vinfo( 2)='number of short time-steps'
947 status=def_var(ng, model, ncid, varid, nf90_int, &
948 & 1, (/0/), Aval, Vinfo, ncname, &
949 & SetParAccess = .FALSE.)
950 IF (exit_flag.ne.NoError) RETURN
951
952 Vinfo( 1)='dt'
953 Vinfo( 2)='size of long time-steps'
954 Vinfo( 3)='second'
955 status=def_var(ng, model, ncid, varid, NF_TYPE, &
956 & 1, (/0/), Aval, Vinfo, ncname, &
957 & SetParAccess = .FALSE.)
958 IF (exit_flag.ne.NoError) RETURN
959
960 Vinfo( 1)='dtfast'
961 Vinfo( 2)='size of short time-steps'
962 Vinfo( 3)='second'
963 status=def_var(ng, model, ncid, varid, NF_TYPE, &
964 & 1, (/0/), Aval, Vinfo, ncname, &
965 & SetParAccess = .FALSE.)
966 IF (exit_flag.ne.NoError) RETURN
967
968 Vinfo( 1)='dstart'
969 Vinfo( 2)='time stamp assigned to model initilization'
970 IF (INT(time_ref).eq.-2) THEN
971 Vinfo( 3)='days since 1968-05-23 00:00:00 GMT'
972 Vinfo( 4)='gregorian'
973 ELSE IF (INT(time_ref).eq.-1) THEN
974 Vinfo( 3)='days since 0001-01-01 00:00:00'
975 Vinfo( 4)='360_day'
976 ELSE IF (INT(time_ref).eq.0) THEN
977 Vinfo( 3)='days since 0001-01-01 00:00:00'
978 Vinfo( 4)='julian'
979 ELSE IF (time_ref.gt.0.0_r8) THEN
980 WRITE (Vinfo( 3),'(a,1x,a)') 'days since', TRIM(r_text)
981 END IF
982 status=def_var(ng, model, ncid, varid, NF_TYPE, &
983 & 1, (/0/), Aval, Vinfo, ncname, &
984 & SetParAccess = .FALSE.)
985 IF (exit_flag.ne.NoError) RETURN
986
987#if defined HDF5 && defined DEFLATE
988 Vinfo( 1)='shuffle'
989 Vinfo( 2)='NetCDF-4/HDF5 file format shuffle filer flag'
990 status=def_var(ng, model, ncid, varid, nf90_int, &
991 & 1, (/0/), Aval, Vinfo, ncname, &
992 & SetParAccess = .FALSE.)
993 IF (exit_flag.ne.NoError) RETURN
994
995 Vinfo( 1)='deflate'
996 Vinfo( 2)='NetCDF-4/HDF5 file format deflate filer flag'
997 status=def_var(ng, model, ncid, varid, nf90_int, &
998 & 1, (/0/), Aval, Vinfo, ncname, &
999 & SetParAccess = .FALSE.)
1000 IF (exit_flag.ne.NoError) RETURN
1001
1002 Vinfo( 1)='deflate_level'
1003 Vinfo( 2)='NetCDF-4/HDF5 file format deflate level parameter'
1004 status=def_var(ng, model, ncid, varid, nf90_int, &
1005 & 1, (/0/), Aval, Vinfo, ncname, &
1006 & SetParAccess = .FALSE.)
1007 IF (exit_flag.ne.NoError) RETURN
1008#endif
1009
1010 Vinfo( 1)='nHIS'
1011 Vinfo( 2)='number of time-steps between history records'
1012 status=def_var(ng, model, ncid, varid, nf90_int, &
1013 & 1, (/0/), Aval, Vinfo, ncname, &
1014 & SetParAccess = .FALSE.)
1015 IF (exit_flag.ne.NoError) RETURN
1016
1017 Vinfo( 1)='ndefHIS'
1018 Vinfo( 2)= &
1019 & 'number of time-steps between the creation of history files'
1020 status=def_var(ng, model, ncid, varid, nf90_int, &
1021 & 1, (/0/), Aval, Vinfo, ncname, &
1022 & SetParAccess = .FALSE.)
1023 IF (exit_flag.ne.NoError) RETURN
1024
1025 Vinfo( 1)='nRST'
1026 Vinfo( 2)='number of time-steps between restart records'
1027 IF (LcycleRST(ng)) THEN
1028 Vinfo(13)='only latest two records are maintained'
1029 END IF
1030 status=def_var(ng, model, ncid, varid, nf90_int, &
1031 & 1, (/0/), Aval, Vinfo, ncname, &
1032 & SetParAccess = .FALSE.)
1033 IF (exit_flag.ne.NoError) RETURN
1034
1035#if defined AVERAGES || \
1036 (defined AD_AVERAGES && defined ADJOINT) || \
1037 (defined RP_AVERAGES && defined TL_IOMS) || \
1038 (defined TL_AVERAGES && defined TANGENT)
1039 Vinfo( 1)='ntsAVG'
1040 Vinfo( 2)= &
1041 & 'starting time-step for accumulation of time-averaged fields'
1042 status=def_var(ng, model, ncid, varid, nf90_int, &
1043 & 1, (/0/), Aval, Vinfo, ncname, &
1044 & SetParAccess = .FALSE.)
1045 IF (exit_flag.ne.NoError) RETURN
1046
1047 Vinfo( 1)='nAVG'
1048 Vinfo( 2)='number of time-steps between time-averaged records'
1049 status=def_var(ng, model, ncid, varid, nf90_int, &
1050 & 1, (/0/), Aval, Vinfo, ncname, &
1051 & SetParAccess = .FALSE.)
1052 IF (exit_flag.ne.NoError) RETURN
1053
1054 Vinfo( 1)='ndefAVG'
1055 Vinfo( 2)= &
1056 & 'number of time-steps between the creation of average files'
1057 status=def_var(ng, model, ncid, varid, nf90_int, &
1058 & 1, (/0/), Aval, Vinfo, ncname, &
1059 & SetParAccess = .FALSE.)
1060 IF (exit_flag.ne.NoError) RETURN
1061#endif
1062
1063#ifdef ADJOINT
1064 Vinfo( 1)='nADJ'
1065 Vinfo( 2)='number of time-steps between adjoint history records'
1066 status=def_var(ng, model, ncid, varid, nf90_int, &
1067 & 1, (/0/), Aval, Vinfo, ncname, &
1068 & SetParAccess = .FALSE.)
1069 IF (exit_flag.ne.NoError) RETURN
1070
1071 Vinfo( 1)='ndefADJ'
1072 Vinfo( 2)= &
1073 & 'number of time-steps between the creation of adjoint files'
1074 status=def_var(ng, model, ncid, varid, nf90_int, &
1075 & 1, (/0/), Aval, Vinfo, ncname, &
1076 & SetParAccess = .FALSE.)
1077 IF (exit_flag.ne.NoError) RETURN
1078#endif
1079
1080#ifdef TANGENT
1081 Vinfo( 1)='nTLM'
1082 Vinfo( 2)='number of time-steps between tangent history records'
1083 status=def_var(ng, model, ncid, varid, nf90_int, &
1084 & 1, (/0/), Aval, Vinfo, ncname, &
1085 & SetParAccess = .FALSE.)
1086 IF (exit_flag.ne.NoError) RETURN
1087
1088 Vinfo( 1)='ndefTLM'
1089 Vinfo( 2)= &
1090 & 'number of time-steps between the creation of tanget files'
1091 status=def_var(ng, model, ncid, varid, nf90_int, &
1092 & 1, (/0/), Aval, Vinfo, ncname, &
1093 & SetParAccess = .FALSE.)
1094 IF (exit_flag.ne.NoError) RETURN
1095#endif
1096
1097#ifdef ADJUST_BOUNDARY
1098 Vinfo( 1)='nOBC'
1099 Vinfo( 2)= &
1100 & 'number of time-steps between 4DVAR open boundary adjustment'
1101 status=def_var(ng, model, ncid, varid, nf90_int, &
1102 & 1, (/0/), Aval, Vinfo, ncname, &
1103 & SetParAccess = .FALSE.)
1104 IF (exit_flag.ne.NoError) RETURN
1105#endif
1106
1107#if defined ADJUST_STFLUX || defined ADJUST_WSTRESS
1108 Vinfo( 1)='nSFF'
1109 Vinfo( 2)= &
1110 & 'number of time-steps between 4DVAR surface forcing adjustment'
1111 status=def_var(ng, model, ncid, varid, nf90_int, &
1112 & 1, (/0/), Aval, Vinfo, ncname, &
1113 & SetParAccess = .FALSE.)
1114 IF (exit_flag.ne.NoError) RETURN
1115#endif
1116
1117#ifdef PROPAGATOR
1118 Vinfo( 1)='LmultiGST'
1119 Vinfo( 2)='Switch to write one GST eigenvector per file'
1120 Vinfo( 9)='.FALSE.'
1121 Vinfo(10)='.TRUE.'
1122 status=def_var(ng, model, ncid, varid, nf90_int, &
1123 & 1, (/0/), Aval, Vinfo, ncname, &
1124 & SetParAccess = .FALSE.)
1125 IF (exit_flag.ne.NoError) RETURN
1126
1127 Vinfo( 1)='LrstGST'
1128 Vinfo( 2)='Switch to restart GST analysis'
1129 Vinfo( 9)='.FALSE.'
1130 Vinfo(10)='.TRUE.'
1131 status=def_var(ng, model, ncid, varid, nf90_int, &
1132 & 1, (/0/), Aval, Vinfo, ncname, &
1133 & SetParAccess = .FALSE.)
1134 IF (exit_flag.ne.NoError) RETURN
1135
1136 Vinfo( 1)='MaxIterGST'
1137 Vinfo( 2)='maximum number of GST algorithm iterations'
1138 status=def_var(ng, model, ncid, varid, nf90_int, &
1139 & 1, (/0/), Aval, Vinfo, ncname, &
1140 & SetParAccess = .FALSE.)
1141 IF (exit_flag.ne.NoError) RETURN
1142
1143 Vinfo( 1)='nGST'
1144 Vinfo( 2)='number GST iterations between check pointing'
1145 status=def_var(ng, model, ncid, varid, nf90_int, &
1146 & 1, (/0/), Aval, Vinfo, ncname, &
1147 & SetParAccess = .FALSE.)
1148 IF (exit_flag.ne.NoError) RETURN
1149
1150 Vinfo( 1)='NEV'
1151 Vinfo( 2)='number Ritz eigenvalues'
1152 status=def_var(ng, model, ncid, varid, nf90_int, &
1153 & 1, (/0/), Aval, Vinfo, ncname, &
1154 & SetParAccess = .FALSE.)
1155 IF (exit_flag.ne.NoError) RETURN
1156
1157 Vinfo( 1)='NCV'
1158 Vinfo( 2)='number Ritz eigenvectors generated'
1159 status=def_var(ng, model, ncid, varid, nf90_int, &
1160 & 1, (/0/), Aval, Vinfo, ncname, &
1161 & SetParAccess = .FALSE.)
1162 IF (exit_flag.ne.NoError) RETURN
1163
1164 Vinfo( 1)='Ritz_tol'
1165 Vinfo( 2)='relative accuracy of Ritz values'
1166 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1167 & 1, (/0/), Aval, Vinfo, ncname, &
1168 & SetParAccess = .FALSE.)
1169 IF (exit_flag.ne.NoError) RETURN
1170#endif
1171
1172#ifdef DIAGNOSTICS
1173 Vinfo( 1)='ntsDIA'
1174 Vinfo( 2)= &
1175 & 'starting time-step for accumulation of diagnostic fields'
1176 status=def_var(ng, model, ncid, varid, nf90_int, &
1177 & 1, (/0/), Aval, Vinfo, ncname, &
1178 & SetParAccess = .FALSE.)
1179 IF (exit_flag.ne.NoError) RETURN
1180
1181 Vinfo( 1)='nDIA'
1182 Vinfo( 2)='number of time-steps between diagnostic records'
1183 status=def_var(ng, model, ncid, varid, nf90_int, &
1184 & 1, (/0/), Aval, Vinfo, ncname, &
1185 & SetParAccess = .FALSE.)
1186 IF (exit_flag.ne.NoError) RETURN
1187
1188 Vinfo( 1)='ndefDIA'
1189 Vinfo( 2)= &
1190 & 'number of time-steps between the creation of diagnostic files'
1191 status=def_var(ng, model, ncid, varid, nf90_int, &
1192 & 1, (/0/), Aval, Vinfo, ncname, &
1193 & SetParAccess = .FALSE.)
1194 IF (exit_flag.ne.NoError) RETURN
1195#endif
1196
1197#ifdef STATIONS
1198 Vinfo( 1)='nSTA'
1199 Vinfo( 2)='number of time-steps between stations records'
1200 status=def_var(ng, model, ncid, varid, nf90_int, &
1201 & 1, (/0/), Aval, Vinfo, ncname, &
1202 & SetParAccess = .FALSE.)
1203 IF (exit_flag.ne.NoError) RETURN
1204#endif
1205
1206#ifdef FOUR_DVAR
1207 Vinfo( 1)='Nouter'
1208 Vinfo( 2)='number of minimization outer loops'
1209 status=def_var(ng, model, ncid, varid, nf90_int, &
1210 & 1, (/0/), Aval, Vinfo, ncname, &
1211 & SetParAccess = .FALSE.)
1212 IF (exit_flag.ne.NoError) RETURN
1213
1214 Vinfo( 1)='Ninner'
1215 Vinfo( 2)='number of minimization inner loops'
1216 status=def_var(ng, model, ncid, varid, nf90_int, &
1217 & 1, (/0/), Aval, Vinfo, ncname, &
1218 & SetParAccess = .FALSE.)
1219 IF (exit_flag.ne.NoError) RETURN
1220#endif
1221
1222#if defined POWER_LAW && defined SOLVE3D
1223!
1224! Power-law shape filter parameters for time-averaging of barotropic
1225! fields.
1226!
1227 Vinfo( 1)='Falpha'
1228 Vinfo( 2)='Power-law shape barotropic filter parameter'
1229 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1230 & 1, (/0/), Aval, Vinfo, ncname, &
1231 & SetParAccess = .FALSE.)
1232 IF (exit_flag.ne.NoError) RETURN
1233
1234 Vinfo( 1)='Fbeta'
1235 Vinfo( 2)='Power-law shape barotropic filter parameter'
1236 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1237 & 1, (/0/), Aval, Vinfo, ncname, &
1238 & SetParAccess = .FALSE.)
1239 IF (exit_flag.ne.NoError) RETURN
1240
1241 Vinfo( 1)='Fgamma'
1242 Vinfo( 2)='Power-law shape barotropic filter parameter'
1243 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1244 & 1, (/0/), Aval, Vinfo, ncname, &
1245 & SetParAccess = .FALSE.)
1246 IF (exit_flag.ne.NoError) RETURN
1247#endif
1248!
1249! Horizontal mixing coefficients.
1250!
1251#if defined SOLVE3D && defined TS_DIF2
1252 Vinfo( 1)='nl_tnu2'
1253 Vinfo( 2)='nonlinear model Laplacian mixing coefficient '// &
1254 & 'for tracers'
1255 Vinfo( 3)='meter2 second-1'
1256 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1257 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1258 & SetParAccess = .FALSE.)
1259 IF (exit_flag.ne.NoError) RETURN
1260
1261# ifdef ADJOINT
1262 Vinfo( 1)='ad_tnu2'
1263 Vinfo( 2)='adjoint model Laplacian mixing coefficient '// &
1264 & 'for tracers'
1265 Vinfo( 3)='meter2 second-1'
1266 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1267 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1268 & SetParAccess = .FALSE.)
1269 IF (exit_flag.ne.NoError) RETURN
1270# endif
1271
1272# if defined TANGENT || defined TL_IOMS
1273 Vinfo( 1)='tl_tnu2'
1274 Vinfo( 2)='tangent linear model Laplacian mixing coefficient '// &
1275 & 'for tracers'
1276 Vinfo( 3)='meter2 second-1'
1277 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1278 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1279 & SetParAccess = .FALSE.)
1280 IF (exit_flag.ne.NoError) RETURN
1281# endif
1282#endif
1283
1284#if defined SOLVE3D && defined TS_DIF4
1285 Vinfo( 1)='nl_tnu4'
1286 Vinfo( 2)='nonlinear model biharmonic mixing coefficient '// &
1287 & 'for tracers'
1288 Vinfo( 3)='meter4 second-1'
1289 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1290 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1291 & SetParAccess = .FALSE.)
1292 IF (exit_flag.ne.NoError) RETURN
1293
1294# ifdef ADJOINT
1295 Vinfo( 1)='ad_tnu4'
1296 Vinfo( 2)='adjoint model biharmonic mixing coefficient '// &
1297 & 'for tracers'
1298 Vinfo( 3)='meter4 second-1'
1299 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1300 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1301 & SetParAccess = .FALSE.)
1302 IF (exit_flag.ne.NoError) RETURN
1303# endif
1304
1305# if defined TANGENT || defined TL_IOMS
1306 Vinfo( 1)='tl_tnu4'
1307 Vinfo( 2)='tangent linear model biharmonic mixing coefficient '// &
1308 & 'for tracers'
1309 Vinfo( 3)='meter4 second-1'
1310 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1311 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1312 & SetParAccess = .FALSE.)
1313 IF (exit_flag.ne.NoError) RETURN
1314# endif
1315#endif
1316
1317#ifdef UV_VIS2
1318 Vinfo( 1)='nl_visc2'
1319 Vinfo( 2)='nonlinear model Laplacian mixing coefficient '// &
1320 & 'for momentum'
1321 Vinfo( 3)='meter2 second-1'
1322 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1323 & 1, (/0/), Aval, Vinfo, ncname, &
1324 & SetParAccess = .FALSE.)
1325 IF (exit_flag.ne.NoError) RETURN
1326
1327# ifdef ADJOINT
1328 Vinfo( 1)='ad_visc2'
1329 Vinfo( 2)='adjoint model Laplacian mixing coefficient '// &
1330 & 'for momentum'
1331 Vinfo( 3)='meter2 second-1'
1332 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1333 & 1, (/0/), Aval, Vinfo, ncname, &
1334 & SetParAccess = .FALSE.)
1335 IF (exit_flag.ne.NoError) RETURN
1336# endif
1337
1338# if defined TANGENT || defined TL_IOMS
1339 Vinfo( 1)='tl_visc2'
1340 Vinfo( 2)='tangent linear model Laplacian mixing coefficient '// &
1341 & 'for momentum'
1342 Vinfo( 3)='meter2 second-1'
1343 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1344 & 1, (/0/), Aval, Vinfo, ncname, &
1345 & SetParAccess = .FALSE.)
1346 IF (exit_flag.ne.NoError) RETURN
1347# endif
1348#endif
1349
1350#ifdef UV_VIS4
1351 Vinfo( 1)='nl_visc4'
1352 Vinfo( 2)='nonlinear model biharmonic mixing coefficient '// &
1353 & 'for momentum'
1354 Vinfo( 3)='meter4 second-1'
1355 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1356 & 1, (/0/), Aval, Vinfo, ncname, &
1357 & SetParAccess = .FALSE.)
1358 IF (exit_flag.ne.NoError) RETURN
1359
1360# ifdef ADJOINT
1361 Vinfo( 1)='ad_visc4'
1362 Vinfo( 2)='adjoint model biharmonic mixing coefficient '// &
1363 & 'for momentum'
1364 Vinfo( 3)='meter4 second-1'
1365 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1366 & 1, (/0/), Aval, Vinfo, ncname, &
1367 & SetParAccess = .FALSE.)
1368 IF (exit_flag.ne.NoError) RETURN
1369# endif
1370
1371# if defined TANGENT || defined TL_IOMS
1372 Vinfo( 1)='tl_visc4'
1373 Vinfo( 2)='tangent linear model biharmonic mixing coefficient '// &
1374 & 'for momentum'
1375 Vinfo( 3)='meter4 second-1'
1376 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1377 & 1, (/0/), Aval, Vinfo, ncname, &
1378 & SetParAccess = .FALSE.)
1379 IF (exit_flag.ne.NoError) RETURN
1380# endif
1381#endif
1382
1383#if defined SOLVE3D && (defined MY25_MIXING || defined GLS_MIXING)
1384# ifdef TKE_DIF2
1385 Vinfo( 1)='tkenu2'
1386 Vinfo( 2)='harmonic mixing coefficient for turbulent energy'
1387 Vinfo( 3)='meter2 second-1'
1388 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1389 & 1, (/0/), Aval, Vinfo, ncname, &
1390 & SetParAccess = .FALSE.)
1391 IF (exit_flag.ne.NoError) RETURN
1392# endif
1393# ifdef TKE_DIF4
1394 Vinfo( 1)='tkenu4'
1395 Vinfo( 2)='biharmonic mixing coefficient for turbulent energy'
1396 Vinfo( 3)='meter4 second-1'
1397 status=def_var(ng, model, ncid,varid, NF_TYPE, &
1398 & 1, (/0/), Aval, Vinfo, ncname, &
1399 & SetParAccess = .FALSE.)
1400 IF (exit_flag.ne.NoError) RETURN
1401# endif
1402#endif
1403#if defined UV_VIS2 || defined UV_VIS4
1404 Vinfo( 1)='LuvSponge'
1405 Vinfo( 2)='horizontal viscosity sponge activation switch'
1406 Vinfo( 9)='.FALSE.'
1407 Vinfo(10)='.TRUE.'
1408 status=def_var(ng, model, ncid, varid, nf90_int, &
1409 & 1, (/0/), Aval, Vinfo, ncname, &
1410 & SetParAccess = .FALSE.)
1411 IF (exit_flag.ne.NoError) RETURN
1412#endif
1413#if (defined TS_DIF2 || defined TS_DIF4) && defined SOLVE3D
1414 Vinfo( 1)='LtracerSponge'
1415 Vinfo( 2)='horizontal diffusivity sponge activation switch'
1416 Vinfo( 9)='.FALSE.'
1417 Vinfo(10)='.TRUE.'
1418 status=def_var(ng, model, ncid, varid, nf90_int, &
1419 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1420 & SetParAccess = .FALSE.)
1421 IF (exit_flag.ne.NoError) RETURN
1422#endif
1423#ifdef SOLVE3D
1424!
1425! Background vertical mixing coefficients.
1426!
1427 Vinfo( 1)='Akt_bak'
1428 Vinfo( 2)='background vertical mixing coefficient for tracers'
1429 Vinfo( 3)='meter2 second-1'
1430 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1431 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1432 & SetParAccess = .FALSE.)
1433 IF (exit_flag.ne.NoError) RETURN
1434
1435 Vinfo( 1)='Akv_bak'
1436 Vinfo( 2)='background vertical mixing coefficient for momentum'
1437 Vinfo( 3)='meter2 second-1'
1438 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1439 & 1, (/0/), Aval, Vinfo, ncname, &
1440 & SetParAccess = .FALSE.)
1441 IF (exit_flag.ne.NoError) RETURN
1442
1443# if defined MY25_MIXING || defined GLS_MIXING
1444 Vinfo( 1)='Akk_bak'
1445 Vinfo( 2)= &
1446 & 'background vertical mixing coefficient for turbulent energy'
1447 Vinfo( 3)='meter2 second-1'
1448 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1449 & 1, (/0/), Aval, Vinfo, ncname, &
1450 & SetParAccess = .FALSE.)
1451 IF (exit_flag.ne.NoError) RETURN
1452
1453 Vinfo( 1)='Akp_bak'
1454 Vinfo( 2)= &
1455 & 'background vertical mixing coefficient for length scale'
1456 Vinfo( 3)='meter2 second-1'
1457 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1458 & 1, (/0/), Aval, Vinfo, ncname, &
1459 & SetParAccess = .FALSE.)
1460 IF (exit_flag.ne.NoError) RETURN
1461# endif
1462
1463# ifdef FORWARD_MIXING
1464!
1465! Basic state vertical mixing scale used in adjoint-based applications.
1466!
1467# ifdef ADJOINT
1468 Vinfo( 1)='ad_Akt_fac'
1469 Vinfo( 2)='adjoint model basic state vertical mixing '// &
1470 & 'scale for tracers'
1471 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1472 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1473 & SetParAccess = .FALSE.)
1474 IF (exit_flag.ne.NoError) RETURN
1475# endif
1476
1477# if defined TANGENT || defined TL_IOMS
1478 Vinfo( 1)='tl_Akt_fac'
1479 Vinfo( 2)='tangent linear model basic state vertical mixing '// &
1480 & 'scale for tracers'
1481 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1482 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1483 & SetParAccess = .FALSE.)
1484 IF (exit_flag.ne.NoError) RETURN
1485# endif
1486
1487# ifdef ADJOINT
1488 Vinfo( 1)='ad_Akv_fac'
1489 Vinfo( 2)='adjoint model basic state vertical mixing '// &
1490 & 'scale for momentum'
1491 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1492 & 1, (/0/), Aval, Vinfo, ncname, &
1493 & SetParAccess = .FALSE.)
1494 IF (exit_flag.ne.NoError) RETURN
1495# endif
1496
1497# if defined TANGENT || defined TL_IOMS
1498 Vinfo( 1)='tl_Akv_fac'
1499 Vinfo( 2)='tangent linear model basic state vertical mixing '// &
1500 & 'scale for momentum'
1501 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1502 & 1, (/0/), Aval, Vinfo, ncname, &
1503 & SetParAccess = .FALSE.)
1504 IF (exit_flag.ne.NoError) RETURN
1505# endif
1506# endif
1507#endif
1508!
1509! Drag coefficients.
1510!
1511 Vinfo( 1)='rdrg'
1512 Vinfo( 2)='linear drag coefficient'
1513 Vinfo( 3)='meter second-1'
1514 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1515 & 1, (/0/), Aval, Vinfo, ncname, &
1516 & SetParAccess = .FALSE.)
1517 IF (exit_flag.ne.NoError) RETURN
1518
1519 Vinfo( 1)='rdrg2'
1520 Vinfo( 2)='quadratic drag coefficient'
1521 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1522 & 1, (/0/), Aval, Vinfo ,ncname, &
1523 & SetParAccess = .FALSE.)
1524 IF (exit_flag.ne.NoError) RETURN
1525
1526#ifdef SOLVE3D
1527 Vinfo( 1)='Zob'
1528 Vinfo( 2)='bottom roughness'
1529 Vinfo( 3)='meter'
1530 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1531 & 1, (/0/), Aval, Vinfo, ncname, &
1532 & SetParAccess = .FALSE.)
1533 IF (exit_flag.ne.NoError) RETURN
1534
1535 Vinfo( 1)='Zos'
1536 Vinfo( 2)='surface roughness'
1537 Vinfo( 3)='meter'
1538 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1539 & 1, (/0/), Aval, Vinfo, ncname, &
1540 & SetParAccess = .FALSE.)
1541 IF (exit_flag.ne.NoError) RETURN
1542#endif
1543#if defined SOLVE3D && defined GLS_MIXING
1544!
1545! Generic length-scale parameters.
1546!
1547 Vinfo( 1)='gls_p'
1548 Vinfo( 2)='stability exponent'
1549 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1550 & 1, (/0/), Aval, Vinfo, ncname, &
1551 & SetParAccess = .FALSE.)
1552 IF (exit_flag.ne.NoError) RETURN
1553
1554 Vinfo( 1)='gls_m'
1555 Vinfo( 2)='turbulent kinetic energy exponent'
1556 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1557 & 1, (/0/), Aval, Vinfo, ncname, &
1558 & SetParAccess = .FALSE.)
1559 IF (exit_flag.ne.NoError) RETURN
1560
1561 Vinfo( 1)='gls_n'
1562 Vinfo( 2)='turbulent length scale exponent'
1563 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1564 & 1, (/0/), Aval, Vinfo, ncname, &
1565 & SetParAccess = .FALSE.)
1566 IF (exit_flag.ne.NoError) RETURN
1567
1568 Vinfo( 1)='gls_cmu0'
1569 Vinfo( 2)='stability coefficient'
1570 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1571 & 1, (/0/), Aval, Vinfo, ncname, &
1572 & SetParAccess = .FALSE.)
1573 IF (exit_flag.ne.NoError) RETURN
1574
1575 Vinfo( 1)='gls_c1'
1576 Vinfo( 2)='shear production coefficient'
1577 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1578 & 1, (/0/), Aval, Vinfo, ncname, &
1579 & SetParAccess = .FALSE.)
1580 IF (exit_flag.ne.NoError) RETURN
1581
1582 Vinfo( 1)='gls_c2'
1583 Vinfo( 2)='dissipation coefficient'
1584 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1585 & 1, (/0/), Aval, Vinfo, ncname, &
1586 & SetParAccess = .FALSE.)
1587 IF (exit_flag.ne.NoError) RETURN
1588
1589 Vinfo( 1)='gls_c3m'
1590 Vinfo( 2)='buoyancy production coefficient (minus)'
1591 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1592 & 1, (/0/), Aval, Vinfo, ncname, &
1593 & SetParAccess = .FALSE.)
1594 IF (exit_flag.ne.NoError) RETURN
1595
1596 Vinfo( 1)='gls_c3p'
1597 Vinfo( 2)='buoyancy production coefficient (plus)'
1598 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1599 & 1, (/0/), Aval, Vinfo, ncname, &
1600 & SetParAccess = .FALSE.)
1601 IF (exit_flag.ne.NoError) RETURN
1602
1603 Vinfo( 1)='gls_sigk'
1604 Vinfo( 2)='constant Schmidt number for TKE'
1605 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1606 & 1, (/0/), Aval, Vinfo, ncname, &
1607 & SetParAccess = .FALSE.)
1608 IF (exit_flag.ne.NoError) RETURN
1609
1610 Vinfo( 1)='gls_sigp'
1611 Vinfo( 2)='constant Schmidt number for PSI'
1612 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1613 & 1, (/0/), Aval, Vinfo, ncname, &
1614 & SetParAccess = .FALSE.)
1615 IF (exit_flag.ne.NoError) RETURN
1616
1617 Vinfo( 1)='gls_Kmin'
1618 Vinfo( 2)='minimum value of specific turbulent kinetic energy'
1619 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1620 & 1, (/0/), Aval, Vinfo, ncname, &
1621 & SetParAccess = .FALSE.)
1622 IF (exit_flag.ne.NoError) RETURN
1623
1624 Vinfo( 1)='gls_Pmin'
1625 Vinfo( 2)='minimum Value of dissipation'
1626 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1627 & 1, (/0/), Aval, Vinfo, ncname, &
1628 & SetParAccess = .FALSE.)
1629 IF (exit_flag.ne.NoError) RETURN
1630
1631 Vinfo( 1)='Charnok_alpha'
1632 Vinfo( 2)='Charnok factor for surface roughness'
1633 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1634 & 1, (/0/), Aval, Vinfo, ncname, &
1635 & SetParAccess = .FALSE.)
1636 IF (exit_flag.ne.NoError) RETURN
1637
1638 Vinfo( 1)='Zos_hsig_alpha'
1639 Vinfo( 2)='wave amplitude factor for surface roughness'
1640 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1641 & 1, (/0/), Aval, Vinfo, ncname, &
1642 & SetParAccess = .FALSE.)
1643 IF (exit_flag.ne.NoError) RETURN
1644
1645 Vinfo( 1)='sz_alpha'
1646 Vinfo( 2)='surface flux from wave dissipation'
1647 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1648 & 1, (/0/), Aval, Vinfo, ncname, &
1649 & SetParAccess = .FALSE.)
1650 IF (exit_flag.ne.NoError) RETURN
1651
1652 Vinfo( 1)='CrgBan_cw'
1653 Vinfo( 2)='surface flux due to Craig and Banner wave breaking'
1654 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1655 & 1, (/0/), Aval, Vinfo, ncname, &
1656 & SetParAccess = .FALSE.)
1657 IF (exit_flag.ne.NoError) RETURN
1658
1659#endif
1660!
1661! Nudging inverse time scales used in various tasks.
1662!
1663 Vinfo( 1)='Znudg'
1664 Vinfo( 2)='free-surface nudging/relaxation inverse time scale'
1665 Vinfo( 3)='day-1'
1666 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1667 & 1, (/0/), Aval, Vinfo, ncname, &
1668 & SetParAccess = .FALSE.)
1669 IF (exit_flag.ne.NoError) RETURN
1670
1671 Vinfo( 1)='M2nudg'
1672 Vinfo( 2)='2D momentum nudging/relaxation inverse time scale'
1673 Vinfo( 3)='day-1'
1674 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1675 & 1, (/0/), Aval, Vinfo, ncname, &
1676 & SetParAccess = .FALSE.)
1677 IF (exit_flag.ne.NoError) RETURN
1678
1679#ifdef SOLVE3D
1680 Vinfo( 1)='M3nudg'
1681 Vinfo( 2)='3D momentum nudging/relaxation inverse time scale'
1682 Vinfo( 3)='day-1'
1683 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1684 & 1, (/0/), Aval, Vinfo, ncname, &
1685 & SetParAccess = .FALSE.)
1686 IF (exit_flag.ne.NoError) RETURN
1687
1688 Vinfo( 1)='Tnudg'
1689 Vinfo( 2)='Tracers nudging/relaxation inverse time scale'
1690 Vinfo( 3)='day-1'
1691 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1692 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1693 & SetParAccess = .FALSE.)
1694 IF (exit_flag.ne.NoError) RETURN
1695#endif
1696
1697#ifndef DEBUGGING
1698!
1699! Open boundary nudging, inverse time scales.
1700!
1701 IF (NudgingCoeff(ng)) THEN
1702 Vinfo( 1)='FSobc_in'
1703 Vinfo( 2)='free-surface inflow, nudging inverse time scale'
1704 Vinfo( 3)='second-1'
1705 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1706 & 1, (/brydim/), Aval, Vinfo, ncname, &
1707 & SetParAccess = .FALSE.)
1708 IF (exit_flag.ne.NoError) RETURN
1709
1710 Vinfo( 1)='FSobc_out'
1711 Vinfo( 2)='free-surface outflow, nudging inverse time scale'
1712 Vinfo( 3)='second-1'
1713 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1714 & 1, (/brydim/), Aval, Vinfo, ncname, &
1715 & SetParAccess = .FALSE.)
1716 IF (exit_flag.ne.NoError) RETURN
1717
1718 Vinfo( 1)='M2obc_in'
1719 Vinfo( 2)='2D momentum inflow, nudging inverse time scale'
1720 Vinfo( 3)='second-1'
1721 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1722 & 1, (/brydim/), Aval, Vinfo, ncname, &
1723 & SetParAccess = .FALSE.)
1724 IF (exit_flag.ne.NoError) RETURN
1725
1726 Vinfo( 1)='M2obc_out'
1727 Vinfo( 2)='2D momentum outflow, nudging inverse time scale'
1728 Vinfo( 3)='second-1'
1729 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1730 & 1, (/brydim/), Aval, Vinfo, ncname, &
1731 & SetParAccess = .FALSE.)
1732 IF (exit_flag.ne.NoError) RETURN
1733
1734# ifdef SOLVE3D
1735 Vinfo( 1)='Tobc_in'
1736 Vinfo( 2)='tracers inflow, nudging inverse time scale'
1737 Vinfo( 3)='second-1'
1738 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1739 & 2, tbrydim, Aval, Vinfo, ncname, &
1740 & SetParAccess = .FALSE.)
1741 IF (exit_flag.ne.NoError) RETURN
1742
1743 Vinfo( 1)='Tobc_out'
1744 Vinfo( 2)='tracers outflow, nudging inverse time scale'
1745 Vinfo( 3)='second-1'
1746 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1747 & 2, tbrydim, Aval, Vinfo, ncname, &
1748 & SetParAccess = .FALSE.)
1749 IF (exit_flag.ne.NoError) RETURN
1750
1751 Vinfo( 1)='M3obc_in'
1752 Vinfo( 2)='3D momentum inflow, nudging inverse time scale'
1753 Vinfo( 3)='second-1'
1754 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1755 & 1, (/brydim/), Aval, Vinfo, ncname, &
1756 & SetParAccess = .FALSE.)
1757 IF (exit_flag.ne.NoError) RETURN
1758
1759 Vinfo( 1)='M3obc_out'
1760 Vinfo( 2)='3D momentum outflow, nudging inverse time scale'
1761 Vinfo( 3)='second-1'
1762 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1763 & 1, (/brydim/), Aval, Vinfo, ncname, &
1764 & SetParAccess = .FALSE.)
1765 IF (exit_flag.ne.NoError) RETURN
1766# endif
1767 END IF
1768#endif
1769!
1770! Equation of State parameters.
1771!
1772 Vinfo( 1)='rho0'
1773 Vinfo( 2)='mean density used in Boussinesq approximation'
1774 Vinfo( 3)='kilogram meter-3'
1775 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1776 & 1, (/0/), Aval, Vinfo, ncname, &
1777 & SetParAccess = .FALSE.)
1778 IF (exit_flag.ne.NoError) RETURN
1779
1780#if defined SOLVE3D && defined PROPAGATOR
1781 Vinfo( 1)='bvf_bak'
1782 Vinfo( 2)='background Brunt-Vaisala frequency'
1783 Vinfo( 3)='second-2'
1784 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1785 & 1, (/0/), Aval, Vinfo, ncname, &
1786 & SetParAccess = .FALSE.)
1787 IF (exit_flag.ne.NoError) RETURN
1788#endif
1789
1790#if defined SOLVE3D && \
1791 (!defined NONLIN_EOS || defined FOUR_DVAR || defined PROPAGATOR)
1792 Vinfo( 1)='R0'
1793 Vinfo( 2)='background density used in linear equation of state'
1794 Vinfo( 3)='kilogram meter-3'
1795 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1796 & 1, (/0/), Aval, Vinfo, ncname, &
1797 & SetParAccess = .FALSE.)
1798 IF (exit_flag.ne.NoError) RETURN
1799
1800 Vinfo( 1)='Tcoef'
1801 Vinfo( 2)='thermal expansion coefficient'
1802 Vinfo( 3)='Celsius-1'
1803 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1804 & 1, (/0/), Aval, Vinfo, ncname, &
1805 & SetParAccess = .FALSE.)
1806 IF (exit_flag.ne.NoError) RETURN
1807
1808 Vinfo( 1)='Scoef'
1809 Vinfo( 2)='Saline contraction coefficient'
1810 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1811 & 1, (/0/), Aval, Vinfo, ncname, &
1812 & SetParAccess = .FALSE.)
1813 IF (exit_flag.ne.NoError) RETURN
1814#endif
1815#ifdef SOLVE3D
1816!
1817! Various parameters.
1818!
1819# ifdef BODYFORCE
1820 Vinfo( 1)='levsfrc'
1821 Vinfo( 2)='shallowest level for body-force stress'
1822 status=def_var(ng, model, ncid, varid, nf90_int, &
1823 & 1, (/0/), Aval, Vinfo, ncname, &
1824 & SetParAccess = .FALSE.)
1825 IF (exit_flag.ne.NoError) RETURN
1826
1827 Vinfo( 1)='levbfrc'
1828 Vinfo( 2)='deepest level for body-force stress'
1829 status=def_var(ng, model, ncid, varid, nf90_int, &
1830 & 1, (/0/), Aval, Vinfo, ncname, &
1831 & SetParAccess = .FALSE.)
1832 IF (exit_flag.ne.NoError) RETURN
1833# endif
1834#endif
1835!
1836! Slipperiness parameters.
1837!
1838 Vinfo( 1)='gamma2'
1839 Vinfo( 2)='slipperiness parameter'
1840 status=def_var(ng, model, ncid, varid, NF_TYPE, &
1841 & 1, (/0/), Aval, Vinfo, ncname, &
1842 & SetParAccess = .FALSE.)
1843 IF (exit_flag.ne.NoError) RETURN
1844!
1845! Logical switches to activate horizontal momentum transport
1846! point Sources/Sinks (like river runoff transport) and mass point
1847! Sources/Sinks (like volume vertical influx).
1848!
1849 Vinfo( 1)='LuvSrc'
1850 Vinfo( 2)='momentum point sources and sink activation switch'
1851 Vinfo( 9)='.FALSE.'
1852 Vinfo(10)='.TRUE.'
1853 status=def_var(ng, model, ncid, varid, nf90_int, &
1854 & 1, (/0/), Aval, Vinfo, ncname, &
1855 & SetParAccess = .FALSE.)
1856 IF (exit_flag.ne.NoError) RETURN
1857
1858 Vinfo( 1)='LwSrc'
1859 Vinfo( 2)='mass point sources and sink activation switch'
1860 Vinfo( 9)='.FALSE.'
1861 Vinfo(10)='.TRUE.'
1862 status=def_var(ng, model, ncid, varid, nf90_int, &
1863 & 1, (/0/), Aval, Vinfo, ncname, &
1864 & SetParAccess = .FALSE.)
1865 IF (exit_flag.ne.NoError) RETURN
1866
1867#ifdef SOLVE3D
1868!
1869! Logical switches indicating which tracer variables are processed
1870! during point Sources/Sinks.
1871!
1872 Vinfo( 1)='LtracerSrc'
1873 Vinfo( 2)='tracer point sources and sink activation switch'
1874 Vinfo( 9)='.FALSE.'
1875 Vinfo(10)='.TRUE.'
1876 status=def_var(ng, model, ncid, varid, nf90_int, &
1877 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1878 & SetParAccess = .FALSE.)
1879 IF (exit_flag.ne.NoError) RETURN
1880#endif
1881!
1882! Logical switches to process climatology fields.
1883!
1884 Vinfo( 1)='LsshCLM'
1885 Vinfo( 2)='sea surface height climatology processing switch'
1886 Vinfo( 9)='.FALSE.'
1887 Vinfo(10)='.TRUE.'
1888 status=def_var(ng, model, ncid, varid, nf90_int, &
1889 & 1, (/0/), Aval, Vinfo, ncname, &
1890 & SetParAccess = .FALSE.)
1891 IF (exit_flag.ne.NoError) RETURN
1892
1893 Vinfo( 1)='Lm2CLM'
1894 Vinfo( 2)='2D momentum climatology processing switch'
1895 Vinfo( 9)='.FALSE.'
1896 Vinfo(10)='.TRUE.'
1897 status=def_var(ng, model, ncid, varid, nf90_int, &
1898 & 1, (/0/), Aval, Vinfo, ncname, &
1899 & SetParAccess = .FALSE.)
1900 IF (exit_flag.ne.NoError) RETURN
1901
1902#ifdef SOLVE3D
1903 Vinfo( 1)='Lm3CLM'
1904 Vinfo( 2)='3D momentum climatology processing switch'
1905 Vinfo( 9)='.FALSE.'
1906 Vinfo(10)='.TRUE.'
1907 status=def_var(ng, model, ncid, varid, nf90_int, &
1908 & 1, (/0/), Aval, Vinfo, ncname, &
1909 & SetParAccess = .FALSE.)
1910 IF (exit_flag.ne.NoError) RETURN
1911
1912 Vinfo( 1)='LtracerCLM'
1913 Vinfo( 2)='tracer climatology processing switch'
1914 Vinfo( 9)='.FALSE.'
1915 Vinfo(10)='.TRUE.'
1916 status=def_var(ng, model, ncid, varid, nf90_int, &
1917 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1918 & SetParAccess = .FALSE.)
1919 IF (exit_flag.ne.NoError) RETURN
1920#endif
1921!
1922! Logical switches for nudging of climatology fields.
1923!
1924 Vinfo( 1)='LnudgeM2CLM'
1925 Vinfo( 2)='2D momentum climatology nudging activation switch'
1926 Vinfo( 9)='.FALSE.'
1927 Vinfo(10)='.TRUE.'
1928 status=def_var(ng, model, ncid, varid, nf90_int, &
1929 & 1, (/0/), Aval, Vinfo, ncname, &
1930 & SetParAccess = .FALSE.)
1931 IF (exit_flag.ne.NoError) RETURN
1932#ifdef SOLVE3D
1933!
1934 Vinfo( 1)='LnudgeM3CLM'
1935 Vinfo( 2)='3D momentum climatology nudging activation switch'
1936 Vinfo( 9)='.FALSE.'
1937 Vinfo(10)='.TRUE.'
1938 status=def_var(ng, model, ncid, varid, nf90_int, &
1939 & 1, (/0/), Aval, Vinfo, ncname, &
1940 & SetParAccess = .FALSE.)
1941 IF (exit_flag.ne.NoError) RETURN
1942!
1943 Vinfo( 1)='LnudgeTCLM'
1944 Vinfo( 2)='tracer climatology nudging activation switch'
1945 Vinfo( 9)='.FALSE.'
1946 Vinfo(10)='.TRUE.'
1947 status=def_var(ng, model, ncid, varid, nf90_int, &
1948 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1949 & SetParAccess = .FALSE.)
1950 IF (exit_flag.ne.NoError) RETURN
1951#endif
1952#ifdef FOUR_DVAR
1953!
1954! 4DVAR assimilation parameters.
1955!
1956# ifdef ADJUST_STFLUX
1957 Vinfo( 1)='Lstflux'
1958 Vinfo( 2)='surface tracer fluxes adjustment switch'
1959 Vinfo( 9)='.FALSE.'
1960 Vinfo(10)='.TRUE.'
1961 status=def_var(ng, model, ncid, varid, nf90_int, &
1962 & 1, (/trcdim/), Aval, Vinfo, ncname, &
1963 & SetParAccess = .FALSE.)
1964 IF (exit_flag.ne.NoError) RETURN
1965# endif
1966# ifdef ADJUST_BOUNDARY
1967 Vinfo( 1)='Lobc'
1968 Vinfo( 2)='open boundary conditions adjustment switch'
1969 Vinfo( 9)='.FALSE.'
1970 Vinfo(10)='.TRUE.'
1971 status=def_var(ng, model, ncid, varid, nf90_int, &
1972 & 2, (/brydim, statedim/), Aval, Vinfo, ncname, &
1973 & SetParAccess = .FALSE.)
1974 IF (exit_flag.ne.NoError) RETURN
1975# endif
1976# ifndef IS4DVAR_SENSITIVITY
1977 Vinfo( 1)='LhessianEV'
1978 Vinfo( 2)='switch to compute Hessian eigenvectors'
1979 Vinfo( 9)='.FALSE.'
1980 Vinfo(10)='.TRUE.'
1981 status=def_var(ng, model, ncid, varid, nf90_int, &
1982 & 1, (/0/), Aval, Vinfo, ncname, &
1983 & SetParAccess = .FALSE.)
1984 IF (exit_flag.ne.NoError) RETURN
1985
1986# ifdef WEAK_CONSTRAINT
1987 Vinfo( 1)='LhotStart'
1988 Vinfo( 2)='switch for hot start of subsequent outer loops'
1989 Vinfo( 9)='.FALSE.'
1990 Vinfo(10)='.TRUE.'
1991 status=def_var(ng, model, ncid, varid, nf90_int, &
1992 & 1, (/0/), Aval, Vinfo, ncname, &
1993 & SetParAccess = .FALSE.)
1994 IF (exit_flag.ne.NoError) RETURN
1995# endif
1996
1997 Vinfo( 1)='Lprecond'
1998 Vinfo( 2)='switch for conjugate gradient preconditioning'
1999 Vinfo( 9)='.FALSE.'
2000 Vinfo(10)='.TRUE.'
2001 status=def_var(ng, model, ncid, varid, nf90_int, &
2002 & 1, (/0/), Aval, Vinfo, ncname, &
2003 & SetParAccess = .FALSE.)
2004 IF (exit_flag.ne.NoError) RETURN
2005
2006 Vinfo( 1)='Lritz'
2007 Vinfo( 2)='switch for Ritz limited-memory preconditioning'
2008 Vinfo( 9)='.FALSE.'
2009 Vinfo(10)='.TRUE.'
2010 status=def_var(ng, model, ncid, varid, nf90_int, &
2011 & 1, (/0/), Aval, Vinfo, ncname, &
2012 & SetParAccess = .FALSE.)
2013 IF (exit_flag.ne.NoError) RETURN
2014
2015# ifdef WEAK_CONSTRAINT
2016 IF (Lprecond.and.(NritzEV.gt.0)) THEN
2017 Vinfo( 1)='NritzEV'
2018 Vinfo( 2)='number of preconditioning eigenpairs to use'
2019 status=def_var(ng, model, ncid, varid, nf90_int, &
2020 & 1, (/0/), Aval, Vinfo, ncname, &
2021 & SetParAccess = .FALSE.)
2022 IF (exit_flag.ne.NoError) RETURN
2023 END IF
2024# endif
2025# endif
2026# if defined POSTERIOR_EOFS && defined WEAK_CONSTRAINT
2027 Vinfo( 1)='NpostI'
2028 Vinfo( 2)='number of Lanczos iterations in posterior analysis'
2029 status=def_var(ng, model, ncid, varid, nf90_int, &
2030 & 1, (/0/), Aval, Vinfo, ncname, &
2031 & SetParAccess = .FALSE.)
2032 IF (exit_flag.ne.NoError) RETURN
2033# endif
2034# ifndef IS4DVAR_SENSITIVITY
2035 Vinfo( 1)='GradErr'
2036 Vinfo( 2)='Upper bound on relative error of the gradient'
2037 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2038 & 1, (/0/), Aval, Vinfo, ncname, &
2039 & SetParAccess = .FALSE.)
2040 IF (exit_flag.ne.NoError) RETURN
2041
2042 Vinfo( 1)='HevecErr'
2043 Vinfo( 2)='Accuracy required for Hessian eigenvectors'
2044 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2045 & 1, (/0/), Aval, Vinfo, ncname, &
2046 & SetParAccess = .FALSE.)
2047 IF (exit_flag.ne.NoError) RETURN
2048# endif
2049
2050 Vinfo( 1)='Nmethod'
2051 Vinfo( 2)='background error covariance normalization method'
2052 Vinfo( 9)='exact'
2053 Vinfo(10)='randomization'
2054 status=def_var(ng, model, ncid, varid, nf90_int, &
2055 & 1, (/0/), Aval, Vinfo, ncname, &
2056 & SetParAccess = .FALSE.)
2057 IF (exit_flag.ne.NoError) RETURN
2058
2059 Vinfo( 1)='Rscheme'
2060 Vinfo( 2)='Random number generation scheme'
2061 Vinfo( 9)='intrisic_randon_number'
2062 Vinfo(10)='Gaussian_distributed_deviates'
2063 status=def_var(ng, model, ncid, varid, nf90_int, &
2064 & 1, (/0/), Aval, Vinfo, ncname, &
2065 & SetParAccess = .FALSE.)
2066 IF (exit_flag.ne.NoError) RETURN
2067
2068 Vinfo( 1)='Nrandom'
2069 Vinfo( 2)='number of randomization iterations'
2070 status=def_var(ng, model, ncid, varid, nf90_int, &
2071 & 1, (/0/), Aval, Vinfo, ncname, &
2072 & SetParAccess = .FALSE.)
2073 IF (exit_flag.ne.NoError) RETURN
2074
2075 Vinfo( 1)='Hgamma'
2076 Vinfo( 2)='initial conditions error covariance '// &
2077 & 'horizontal convolution time-step stability factor'
2078 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2079 & 1, (/0/), Aval, Vinfo, ncname, &
2080 & SetParAccess = .FALSE.)
2081 IF (exit_flag.ne.NoError) RETURN
2082
2083# ifdef WEAK_CONSTRAINT
2084 Vinfo( 1)='HgammaM'
2085 Vinfo( 2)='model error covariance '// &
2086 & 'horizontal convolution time-step stability factor'
2087 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2088 & 1, (/0/), Aval, Vinfo, ncname, &
2089 & SetParAccess = .FALSE.)
2090 IF (exit_flag.ne.NoError) RETURN
2091# endif
2092
2093# ifdef ADJUST_BOUNDARY
2094 Vinfo( 1)='HgammaB'
2095 Vinfo( 2)='open boundary conditions error covariance '// &
2096 & 'horizontal convolution time-step stability factor'
2097 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2098 & 1, (/0/), Aval, Vinfo, ncname, &
2099 & SetParAccess = .FALSE.)
2100 IF (exit_flag.ne.NoError) RETURN
2101# endif
2102
2103# ifdef ADJUST_STFLUX
2104 Vinfo( 1)='HgammaF'
2105 Vinfo( 2)='surface forcing error covariance '// &
2106 & 'horizontal convolution time-step stability factor'
2107 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2108 & 1, (/0/), Aval, Vinfo, ncname, &
2109 & SetParAccess = .FALSE.)
2110 IF (exit_flag.ne.NoError) RETURN
2111# endif
2112
2113# ifdef SOLVE3D
2114 Vinfo( 1)='Vgamma'
2115 Vinfo( 2)='initial conditions error covariance '// &
2116 & 'vertical convolution time-step stability factor'
2117 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2118 & 1, (/0/), Aval, Vinfo, ncname, &
2119 & SetParAccess = .FALSE.)
2120 IF (exit_flag.ne.NoError) RETURN
2121
2122# ifdef WEAK_CONSTRAINT
2123 Vinfo( 1)='VgammaM'
2124 Vinfo( 2)='model error covariance '// &
2125 & 'vertical convolution time-step stability factor'
2126 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2127 & 1, (/0/), Aval, Vinfo, ncname, &
2128 & SetParAccess = .FALSE.)
2129 IF (exit_flag.ne.NoError) RETURN
2130# endif
2131
2132# ifdef ADJUST_BOUNDARY
2133 Vinfo( 1)='VgammaB'
2134 Vinfo( 2)='open boundary conditions error covariance '// &
2135 & 'vertical convolution time-step stability factor'
2136 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2137 & 1, (/0/), Aval, Vinfo, ncname, &
2138 & SetParAccess = .FALSE.)
2139 IF (exit_flag.ne.NoError) RETURN
2140# endif
2141# endif
2142
2143 Vinfo( 1)='Hdecay'
2144 Vinfo( 2)='initial conditions error covariance '// &
2145 & 'horizontal decorrelation scale'
2146 Vinfo( 3)='meter'
2147 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2148 & 1, (/statedim/), Aval, Vinfo, ncname, &
2149 & SetParAccess = .FALSE.)
2150 IF (exit_flag.ne.NoError) RETURN
2151
2152# ifdef SOLVE3D
2153 Vinfo( 1)='Vdecay'
2154 Vinfo( 2)='initial conditions error covariance '// &
2155 & 'vertical decorrelation scale'
2156 Vinfo( 3)='meter'
2157 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2158 & 1, (/statedim/), Aval, Vinfo, ncname, &
2159 & SetParAccess = .FALSE.)
2160 IF (exit_flag.ne.NoError) RETURN
2161# endif
2162
2163 IF (NSA.eq.2) THEN
2164 Vinfo( 1)='HdecayM'
2165 Vinfo( 2)='model error covariance ' // &
2166 & 'horizontal decorrelation scale'
2167 Vinfo( 3)='meter'
2168 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2169 & 1, (/statedim/), Aval, Vinfo, ncname, &
2170 & SetParAccess = .FALSE.)
2171 IF (exit_flag.ne.NoError) RETURN
2172
2173# ifdef SOLVE3D
2174 Vinfo( 1)='VdecayM'
2175 Vinfo( 2)='model error covariance '// &
2176 & 'vertical decorrelation scale'
2177 Vinfo( 3)='meter'
2178 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2179 & 1, (/statedim/), Aval, Vinfo, ncname, &
2180 & SetParAccess = .FALSE.)
2181 IF (exit_flag.ne.NoError) RETURN
2182# endif
2183 END IF
2184
2185# ifdef ADJUST_BOUNDARY
2186 Vinfo( 1)='HdecayB'
2187 Vinfo( 2)='open boundary conditions error covariance '// &
2188 & 'horizontal decorrelation scale'
2189 Vinfo( 3)='meter'
2190 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2191 & 2, (/statedim, brydim/), Aval, Vinfo, ncname, &
2192 & SetParAccess = .FALSE.)
2193 IF (exit_flag.ne.NoError) RETURN
2194
2195# ifdef SOLVE3D
2196 Vinfo( 1)='VdecayB'
2197 Vinfo( 2)='open boundary conditions error covariance '// &
2198 & 'vertical decorrelation scale'
2199 Vinfo( 3)='meter'
2200 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2201 & 2, (/statedim, brydim/), Aval, Vinfo, ncname, &
2202 & SetParAccess = .FALSE.)
2203 IF (exit_flag.ne.NoError) RETURN
2204# endif
2205# endif
2206
2207# ifdef RPM_RELAXATION
2208 Vinfo( 1)='tl_M2diff'
2209 Vinfo( 2)='RPM 2D momentum diffusive relaxation coefficient'
2210 Vinfo( 3)='meter2 second-1'
2211 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2212 & 1, (/0/), Aval, Vinfo, ncname, &
2213 & SetParAccess = .FALSE.)
2214 IF (exit_flag.ne.NoError) RETURN
2215
2216# ifdef SOLVE3D
2217 Vinfo( 1)='tl_M3diff'
2218 Vinfo( 2)='RPM 3D momentum diffusive relaxation coefficient'
2219 Vinfo( 3)='meter2 second-1'
2220 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2221 & 1, (/0/), Aval, Vinfo, ncname, &
2222 & SetParAccess = .FALSE.)
2223 IF (exit_flag.ne.NoError) RETURN
2224
2225 Vinfo( 1)='tl_Tdiff'
2226 Vinfo( 2)='RPM tracers diffusive relaxation coefficients'
2227 Vinfo( 3)='meter2 second-1'
2228 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2229 & 1, (/trcdim/), Aval, Vinfo, ncname, &
2230 & SetParAccess = .FALSE.)
2231 IF (exit_flag.ne.NoError) RETURN
2232# endif
2233# endif
2234
2235# ifdef BALANCE_OPERATOR
2236# ifdef ZETA_ELLIPTIC
2237 Vinfo( 1)='Nbico'
2238 Vinfo( 2)='number of iterations in SSH elliptic equation'
2239 status=def_var(ng, model, ncid, varid, nf90_int, &
2240 & 1, (/0/), Aval, Vinfo, ncname, &
2241 & SetParAccess = .FALSE.)
2242 IF (exit_flag.ne.NoError) RETURN
2243# endif
2244
2245 Vinfo( 1)='Lbalance'
2246 Vinfo( 2)='switches for state variables included as '// &
2247 'constraint in the error covariance balance operator'
2248 Vinfo( 9)='.FALSE.'
2249 Vinfo(10)='.TRUE.'
2250 status=def_var(ng, model, ncid, varid, nf90_int, &
2251 & 1, (/statedim/), Aval, Vinfo, ncname, &
2252 & SetParAccess = .FALSE.)
2253 IF (exit_flag.ne.NoError) RETURN
2254
2255 Vinfo( 1)='LNM_flag'
2256 Vinfo( 2)='balance operator level of no motion flag'
2257 Vinfo( 9)='integrate from bottom to surface,'
2258 Vinfo(10)='integrate from LNM_depth to surface'
2259 status=def_var(ng, model, ncid, varid, nf90_int, &
2260 & 1, (/0/), Aval, Vinfo, ncname, &
2261 & SetParAccess = .FALSE.)
2262 IF (exit_flag.ne.NoError) RETURN
2263
2264 Vinfo( 1)='LNM_depth'
2265 Vinfo( 2)='balance operator level of no motion depth'
2266 Vinfo( 3)='meter'
2267 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2268 & 1, (/0/), Aval, Vinfo, ncname, &
2269 & SetParAccess = .FALSE.)
2270 IF (exit_flag.ne.NoError) RETURN
2271
2272 Vinfo( 1)='dTdz_min'
2273 Vinfo( 2)='minimum dT/dz value used in balaced salinity'
2274 Vinfo( 3)='Celsius meter-1'
2275 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2276 & 1, (/0/), Aval, Vinfo, ncname, &
2277 & SetParAccess = .FALSE.)
2278 IF (exit_flag.ne.NoError) RETURN
2279
2280 Vinfo( 1)='ml_depth'
2281 Vinfo( 2)='mixed layer depth used in balanced salinity'
2282 Vinfo( 3)='meter'
2283 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2284 & 1, (/0/), Aval, Vinfo, ncname, &
2285 & SetParAccess = .FALSE.)
2286 IF (exit_flag.ne.NoError) RETURN
2287# endif
2288#endif
2289
2290#if defined AD_SENSITIVITY || defined IS4DVAR_SENSITIVITY || \
2291 defined OPT_OBSERVATIONS || defined SENSITIVITY_4DVAR || \
2292 defined SO_SEMI
2293!
2294! Adjoint sensitivity parameters.
2295!
2296 Vinfo( 1)='Lzeta'
2297 Vinfo( 2)='adjoint sensitivity on free-surface'
2298 Vinfo( 9)='off'
2299 Vinfo(10)='on'
2300 status=def_var(ng, model, ncid, varid, nf90_int, &
2301 & 1, (/0/), Aval, Vinfo, ncname, &
2302 & SetParAccess = .FALSE.)
2303 IF (exit_flag.ne.NoError) RETURN
2304
2305 Vinfo( 1)='Lubar'
2306 Vinfo( 2)='adjoint sensitivity on 2D U-momentum'
2307 Vinfo( 9)='off'
2308 Vinfo(10)='on'
2309 status=def_var(ng, model, ncid, varid, nf90_int, &
2310 & 1, (/0/), Aval, Vinfo, ncname, &
2311 & SetParAccess = .FALSE.)
2312 IF (exit_flag.ne.NoError) RETURN
2313
2314 Vinfo( 1)='Lvbar'
2315 Vinfo( 2)='adjoint sensitivity on 2D V-momentum'
2316 Vinfo( 9)='off'
2317 Vinfo(10)='on'
2318 status=def_var(ng, model, ncid, varid, nf90_int, &
2319 & 1, (/0/), Aval, Vinfo, ncname, &
2320 & SetParAccess = .FALSE.)
2321 IF (exit_flag.ne.NoError) RETURN
2322
2323# ifdef SOLVE3D
2324 Vinfo( 1)='Luvel'
2325 Vinfo( 2)='adjoint sensitivity on 3D U-momentum'
2326 Vinfo( 9)='off'
2327 Vinfo(10)='on'
2328 status=def_var(ng, model, ncid, varid, nf90_int, &
2329 & 1, (/0/), Aval, Vinfo, ncname, &
2330 & SetParAccess = .FALSE.)
2331 IF (exit_flag.ne.NoError) RETURN
2332
2333 Vinfo( 1)='Lvvel'
2334 Vinfo( 2)='adjoint sensitivity on 3D V-momentum'
2335 Vinfo( 9)='off'
2336 Vinfo(10)='on'
2337 status=def_var(ng, model, ncid, varid, nf90_int, &
2338 & 1, (/0/), Aval, Vinfo, ncname, &
2339 & SetParAccess = .FALSE.)
2340 IF (exit_flag.ne.NoError) RETURN
2341
2342 Vinfo( 1)='Ltracer'
2343 Vinfo( 2)='adjoint sensitivity on tracer variables'
2344 Vinfo( 9)='off'
2345 Vinfo(10)='on'
2346 status=def_var(ng, model, ncid, varid, nf90_int, &
2347 & 1, (/trcdim/), Aval, Vinfo, ncname, &
2348 & SetParAccess = .FALSE.)
2349 IF (exit_flag.ne.NoError) RETURN
2350
2351 Vinfo( 1)='KstrS'
2352 Vinfo( 2)='deepest level for adjoint sensitivity analysis'
2353 status=def_var(ng, model, ncid, varid, nf90_int, &
2354 & 1, (/0/), Aval, Vinfo, ncname, &
2355 & SetParAccess = .FALSE.)
2356 IF (exit_flag.ne.NoError) RETURN
2357
2358 Vinfo( 1)='KendS'
2359 Vinfo( 2)='shallowest level for adjoint sensitivity analysis'
2360 status=def_var(ng, model, ncid, varid, nf90_int, &
2361 & 1, (/0/), Aval, Vinfo, ncname, &
2362 & SetParAccess = .FALSE.)
2363 IF (exit_flag.ne.NoError) RETURN
2364# endif
2365#endif
2366
2367#if defined FORCING_SV || defined SO_SEMI || defined STOCHASTIC_OPT
2368!
2369! Singular Forcing Vectors or Stochastic Optimals state switches.
2370!
2371 Vinfo( 1)='Fzeta'
2372# ifdef FORCING_SV
2373 Vinfo( 2)='forcing singular vectors for free-surface'
2374# else
2375 Vinfo( 2)='stochastic optimals for free-surface'
2376# endif
2377 Vinfo( 9)='off'
2378 Vinfo(10)='on'
2379 status=def_var(ng, model, ncid, varid, nf90_int, &
2380 & 1, (/0/), Aval, Vinfo, ncname, &
2381 & SetParAccess = .FALSE.)
2382 IF (exit_flag.ne.NoError) RETURN
2383
2384# ifndef SOLVE3D
2385 Vinfo( 1)='Fubar'
2386# ifdef FORCING_SV
2387 Vinfo( 2)='forcing singular vectors for 2D U-momentum'
2388# else
2389 Vinfo( 2)='stochastic optimals for 2D U-momentum'
2390# endif
2391 Vinfo( 9)='off'
2392 Vinfo(10)='on'
2393 status=def_var(ng, model, ncid, varid, nf90_int, &
2394 & 1, (/0/), Aval, Vinfo, ncname, &
2395 & SetParAccess = .FALSE.)
2396 IF (exit_flag.ne.NoError) RETURN
2397
2398 Vinfo( 1)='Fvbar'
2399# ifdef FORCING_SV
2400 Vinfo( 2)='forcing singular vectors for 2D V-momentum'
2401# else
2402 Vinfo( 2)='stochastic optimals for 2D V-momentum'
2403# endif
2404 Vinfo( 9)='off'
2405 Vinfo(10)='on'
2406 status=def_var(ng, model, ncid, varid, nf90_int, &
2407 & 1, (/0/), Aval, Vinfo, ncname, &
2408 & SetParAccess = .FALSE.)
2409 IF (exit_flag.ne.NoError) RETURN
2410
2411# else
2412
2413 Vinfo( 1)='Fuvel'
2414# ifdef FORCING_SV
2415 Vinfo( 2)='forcing singular vectors for 3D U-momentum'
2416# else
2417 Vinfo( 2)='stochastic optimals for 3D U-momentum'
2418# endif
2419 Vinfo( 9)='off'
2420 Vinfo(10)='on'
2421 status=def_var(ng, model, ncid, varid, nf90_int, &
2422 & 1, (/0/), Aval, Vinfo, ncname, &
2423 & SetParAccess = .FALSE.)
2424 IF (exit_flag.ne.NoError) RETURN
2425
2426 Vinfo( 1)='Fvvel'
2427# ifdef FORCING_SV
2428 Vinfo( 2)='forcing singular vectors for 3D V-momentum'
2429# else
2430 Vinfo( 2)='stochastic optimals for 3D V-momentum'
2431# endif
2432 Vinfo( 9)='off'
2433 Vinfo(10)='on'
2434 status=def_var(ng, model, ncid, varid, nf90_int, &
2435 & 1, (/0/), Aval, Vinfo, ncname, &
2436 & SetParAccess = .FALSE.)
2437 IF (exit_flag.ne.NoError) RETURN
2438
2439 Vinfo( 1)='Ftracer'
2440# ifdef FORCING_SV
2441 Vinfo( 2)='forcing singular vectors for tracer variables'
2442# else
2443 Vinfo( 2)='stochastic optimals for tracer variables'
2444# endif
2445 Vinfo( 9)='off'
2446 Vinfo(10)='on'
2447 status=def_var(ng, model, ncid, varid, nf90_int, &
2448 & 1, (/trcdim/), Aval, Vinfo, ncname, &
2449 & SetParAccess = .FALSE.)
2450 IF (exit_flag.ne.NoError) RETURN
2451# endif
2452
2453 Vinfo( 1)='Fsustr'
2454# ifdef FORCING_SV
2455 Vinfo( 2)='forcing singular vectors for surface U-stress'
2456# else
2457 Vinfo( 2)='stochastic optimals for surface U-stress'
2458# endif
2459 Vinfo( 9)='off'
2460 Vinfo(10)='on'
2461 status=def_var(ng, model, ncid, varid, nf90_int, &
2462 & 1, (/0/), Aval, Vinfo, ncname, &
2463 & SetParAccess = .FALSE.)
2464 IF (exit_flag.ne.NoError) RETURN
2465
2466 Vinfo( 1)='Fsvstr'
2467# ifdef FORCING_SV
2468 Vinfo( 2)='forcing singular vectors for surface V-stress'
2469# else
2470 Vinfo( 2)='stochastic optimals for surface V-stress'
2471# endif
2472 Vinfo( 9)='off'
2473 Vinfo(10)='on'
2474 status=def_var(ng, model, ncid, varid, nf90_int, &
2475 & 1, (/0/), Aval, Vinfo, ncname, &
2476 & SetParAccess = .FALSE.)
2477 IF (exit_flag.ne.NoError) RETURN
2478
2479# ifdef SOLVE3D
2480 Vinfo( 1)='Fstflx'
2481# ifdef FORCING_SV
2482 Vinfo( 2)='forcing singular vectors for surface tracer flux'
2483# else
2484 Vinfo( 2)='stochastic optimals for surface tracer flux'
2485# endif
2486 Vinfo( 9)='off'
2487 Vinfo(10)='on'
2488 status=def_var(ng, model, ncid, varid, nf90_int, &
2489 & 1, (/trcdim/), Aval, Vinfo, ncname, &
2490 & SetParAccess = .FALSE.)
2491 IF (exit_flag.ne.NoError) RETURN
2492# endif
2493#endif
2494
2495#ifdef SO_SEMI
2496!
2497! Define Stochatic optimals parameters.
2498!
2499# ifndef SO_SEMI_WHITE
2500 Vinfo( 1)='SO_decay'
2501 Vinfo( 2)='red noise stochastic optimals time decorrelation'
2502 Vinfo( 3)='day'
2503 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2504 & 1, (/0/), Aval, Vinfo, ncname, &
2505 & SetParAccess = .FALSE.)
2506 IF (exit_flag.ne.NoError) RETURN
2507# endif
2508
2509 Vinfo( 1)='SO_trace'
2510 Vinfo( 2)='trace of stochastic optimals matrix'
2511 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2512 & 1, (/0/), Aval, Vinfo, ncname, &
2513 & SetParAccess = .FALSE.)
2514 IF (exit_flag.ne.NoError) RETURN
2515
2516 Vinfo( 1)='SOsdev_zeta'
2517 Vinfo( 2)='stochastic optimals scale, free-surface'
2518 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2519 & 1, (/0/), Aval, Vinfo, ncname, &
2520 & SetParAccess = .FALSE.)
2521 IF (exit_flag.ne.NoError) RETURN
2522
2523# ifndef SOLVE3D
2524 Vinfo( 1)='SOsdev_ubar'
2525 Vinfo( 2)='stochastic optimals scale, 2D U-momentum'
2526 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2527 & 1, (/0/), Aval, Vinfo, ncname, &
2528 & SetParAccess = .FALSE.)
2529 IF (exit_flag.ne.NoError) RETURN
2530
2531 Vinfo( 1)='SOsdev_vbar'
2532 Vinfo( 2)='stochastic optimals scale, 2D V-momentum'
2533 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2534 & 1, (/0/), Aval, Vinfo, ncname, &
2535 & SetParAccess = .FALSE.)
2536 IF (exit_flag.ne.NoError) RETURN
2537
2538# else
2539
2540 Vinfo( 1)='SOsdev_uvel'
2541 Vinfo( 2)='stochastic optimals scale, 3D U-momentum'
2542 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2543 & 1, (/0/), Aval, Vinfo, ncname, &
2544 & SetParAccess = .FALSE.)
2545 IF (exit_flag.ne.NoError) RETURN
2546
2547 Vinfo( 1)='SOsdev_vvel'
2548 Vinfo( 2)='stochastic optimals scale, 3D V-momentum'
2549 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2550 & 1, (/0/), Aval, Vinfo, ncname, &
2551 & SetParAccess = .FALSE.)
2552 IF (exit_flag.ne.NoError) RETURN
2553
2554 Vinfo( 1)='SOsdev_tracer'
2555 Vinfo( 2)='stochastic optimals scale, tracer variables'
2556 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2557 & 1, (/trcdim/), Aval, Vinfo, ncname, &
2558 & SetParAccess = .FALSE.)
2559 IF (exit_flag.ne.NoError) RETURN
2560# endif
2561
2562 Vinfo( 1)='SOsdev_sustr'
2563 Vinfo( 2)='stochastic optimals scale, surface U-stress'
2564 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2565 & 1, (/0/), Aval, Vinfo, ncname, &
2566 & SetParAccess = .FALSE.)
2567 IF (exit_flag.ne.NoError) RETURN
2568
2569 Vinfo( 1)='SOsdev_svstr'
2570 Vinfo( 2)='stochastic optimals scale, surface V-stress'
2571 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2572 & 1, (/0/), Aval, Vinfo, ncname, &
2573 & SetParAccess = .FALSE.)
2574 IF (exit_flag.ne.NoError) RETURN
2575
2576# ifdef SOLVE3D
2577 Vinfo( 1)='SOsdev_stflx'
2578 Vinfo( 2)='stochastic optimals scale, surface tracer flux'
2579 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2580 & 1, (/trcdim/), Aval, Vinfo, ncname, &
2581 & SetParAccess = .FALSE.)
2582 IF (exit_flag.ne.NoError) RETURN
2583# endif
2584#endif
2585
2586#if defined BIOLOGY && defined SOLVE3D
2587# if defined BIO_FENNEL
2588# include <fennel_def.h>
2589# elif defined ECOSIM
2590# include <ecosim_def.h>
2591# elif defined NEMURO
2592# include <nemuro_def.h>
2593# elif defined NPZD_FRANKS
2594# include <npzd_Franks_def.h>
2595# elif defined NPZD_IRON
2596# include <npzd_iron_def.h>
2597# elif defined NPZD_POWELL
2598# include <npzd_Powell_def.h>
2599# endif
2600#endif
2601
2602#if defined FLOATS && defined FLOAT_BIOLOGY
2603# if defined FLOAT_OYSTER
2604# include <oyster_floats_def.h>
2605# endif
2606#endif
2607
2608#ifdef SEDIMENT
2609# include <sediment_def.h>
2610#endif
2611!
2612!-----------------------------------------------------------------------
2613! Define grid variables.
2614!-----------------------------------------------------------------------
2615!
2616! Grid type switch: Spherical or Cartesian. Writing characters in
2617! parallel I/O is extremely inefficient. It is better to write
2618! this as an integer switch: 0=Cartesian, 1=spherical.
2619!
2620 Vinfo( 1)='spherical'
2621 Vinfo( 2)='grid type logical switch'
2622 Vinfo( 9)='Cartesian'
2623 Vinfo(10)='spherical'
2624 status=def_var(ng, model, ncid, varid, nf90_int, &
2625 & 1, (/0/), Aval, Vinfo, ncname, &
2626 & SetParAccess = .FALSE.)
2627 IF (exit_flag.ne.NoError) RETURN
2628!
2629! Domain Length.
2630!
2631 Vinfo( 1)='xl'
2632 Vinfo( 2)='domain length in the XI-direction'
2633 Vinfo( 3)='meter'
2634 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2635 & 1, (/0/), Aval, Vinfo, ncname, &
2636 & SetParAccess = .FALSE.)
2637 IF (exit_flag.ne.NoError) RETURN
2638
2639 Vinfo( 1)='el'
2640 Vinfo( 2)='domain length in the ETA-direction'
2641 Vinfo( 3)='meter'
2642 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2643 & 1, (/0/), Aval, Vinfo, ncname, &
2644 & SetParAccess = .FALSE.)
2645 IF (exit_flag.ne.NoError) RETURN
2646#ifdef SOLVE3D
2647!
2648! S-coordinate parameters.
2649!
2650 Vinfo( 1)='Vtransform'
2651 Vinfo( 2)='vertical terrain-following transformation equation'
2652 status=def_var(ng, model, ncid, varid, nf90_int, &
2653 & 1, (/0/), Aval, Vinfo, ncname, &
2654 & SetParAccess = .FALSE.)
2655 IF (exit_flag.ne.NoError) RETURN
2656
2657 Vinfo( 1)='Vstretching'
2658 Vinfo( 2)='vertical terrain-following stretching function'
2659 status=def_var(ng, model, ncid, varid, nf90_int, &
2660 & 1, (/0/), Aval, Vinfo, ncname, &
2661 & SetParAccess = .FALSE.)
2662 IF (exit_flag.ne.NoError) RETURN
2663
2664 Vinfo( 1)='theta_s'
2665 Vinfo( 2)='S-coordinate surface control parameter'
2666 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2667 & 1, (/0/), Aval, Vinfo, ncname, &
2668 & SetParAccess = .FALSE.)
2669 IF (exit_flag.ne.NoError) RETURN
2670
2671 Vinfo( 1)='theta_b'
2672 Vinfo( 2)='S-coordinate bottom control parameter'
2673 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2674 & 1, (/0/), Aval, Vinfo, ncname, &
2675 & SetParAccess = .FALSE.)
2676 IF (exit_flag.ne.NoError) RETURN
2677
2678 Vinfo( 1)='Tcline'
2679 Vinfo( 2)='S-coordinate surface/bottom layer width'
2680 Vinfo( 3)='meter'
2681 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2682 & 1, (/0/), Aval, Vinfo, ncname, &
2683 & SetParAccess = .FALSE.)
2684 IF (exit_flag.ne.NoError) RETURN
2685
2686 Vinfo( 1)='hc'
2687 Vinfo( 2)='S-coordinate parameter, critical depth'
2688 Vinfo( 3)='meter'
2689 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2690 & 1, (/0/), Aval, Vinfo, ncname, &
2691 & SetParAccess = .FALSE.)
2692 IF (exit_flag.ne.NoError) RETURN
2693!
2694! S-coordinate non-dimensional independent variable at RHO-points.
2695!
2696 Vinfo( 1)='s_rho'
2697 Vinfo( 2)='S-coordinate at RHO-points'
2698 Vinfo( 5)='valid_min'
2699 Vinfo( 6)='valid_max'
2700 Vinfo(14)='s_rho, scalar'
2701 IF (Vtransform(ng).eq.1) THEN
2702 Vinfo(21)='ocean_s_coordinate_g1'
2703 ELSE IF (Vtransform(ng).eq.2) THEN
2704 Vinfo(21)='ocean_s_coordinate_g2'
2705 END IF
2706# if defined SEDIMENT && defined SED_MORPH
2707 Vinfo(23)='s: s_rho C: Cs_r eta: zeta depth: bath depth_c: hc'
2708# else
2709 Vinfo(23)='s: s_rho C: Cs_r eta: zeta depth: h depth_c: hc'
2710# endif
2711 vinfo(25)='up'
2712 Aval(2)=-1.0_r8
2713 Aval(3)=0.0_r8
2714 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2715 & 1, (/srdim/), Aval, Vinfo, ncname, &
2716 & SetParAccess = .FALSE.)
2717 IF (exit_flag.ne.NoError) RETURN
2718!
2719! S-coordinate non-dimensional independent variable at W-points.
2720!
2721 Vinfo( 1)='s_w'
2722 Vinfo( 2)='S-coordinate at W-points'
2723 Vinfo( 5)='valid_min'
2724 Vinfo( 6)='valid_max'
2725 Vinfo(14)='s_w, scalar'
2726 Vinfo(21)='ocean_s_coordinate'
2727 IF (Vtransform(ng).eq.1) THEN
2728 Vinfo(21)='ocean_s_coordinate_g1'
2729 ELSE IF (Vtransform(ng).eq.2) THEN
2730 Vinfo(21)='ocean_s_coordinate_g2'
2731 END IF
2732# if defined SEDIMENT && defined SED_MORPH
2733 Vinfo(23)='s: s_w C: Cs_w eta: zeta depth: bath depth_c: hc'
2734# else
2735 Vinfo(23)='s: s_w C: Cs_w eta: zeta depth: h depth_c: hc'
2736# endif
2737 vinfo(25)='up'
2738 Aval(2)=-1.0_r8
2739 Aval(3)=0.0_r8
2740 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2741 & 1, (/swdim/), Aval, Vinfo, ncname, &
2742 & SetParAccess = .FALSE.)
2743 IF (exit_flag.ne.NoError) RETURN
2744!
2745! S-coordinate non-dimensional stretching curves at RHO-points.
2746!
2747 Vinfo( 1)='Cs_r'
2748 Vinfo( 2)='S-coordinate stretching curves at RHO-points'
2749 Vinfo( 5)='valid_min'
2750 Vinfo( 6)='valid_max'
2751 Vinfo(14)='Cs_r, scalar'
2752 Aval(2)=-1.0_r8
2753 Aval(3)=0.0_r8
2754 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2755 & 1, (/srdim/), Aval, Vinfo, ncname, &
2756 & SetParAccess = .FALSE.)
2757 IF (exit_flag.ne.NoError) RETURN
2758!
2759! S-coordinate non-dimensional stretching curves at W-points.
2760!
2761 Vinfo( 1)='Cs_w'
2762 Vinfo( 2)='S-coordinate stretching curves at W-points'
2763 Vinfo( 5)='valid_min'
2764 Vinfo( 6)='valid_max'
2765 Vinfo(14)='Cs_w, scalar'
2766 Aval(2)=-1.0_r8
2767 Aval(3)=0.0_r8
2768 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2769 & 1, (/swdim/), Aval, Vinfo, ncname, &
2770 & SetParAccess = .FALSE.)
2771 IF (exit_flag.ne.NoError) RETURN
2772#endif
2773!
2774! User generic parameters.
2775!
2776 IF (Nuser.gt.0) THEN
2777 Vinfo( 1)='user'
2778 Vinfo( 2)='user generic parameters'
2779 Vinfo(14)='user, scalar'
2780 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2781 & 1, (/usrdim/), Aval, Vinfo, ncname, &
2782 & SetParAccess = .FALSE.)
2783 IF (exit_flag.ne.NoError) RETURN
2784 END IF
2785#ifdef STATIONS
2786!
2787! Station positions.
2788!
2789 IF (ncid.eq.STA(ng)%ncid) THEN
2790 Vinfo( 1)='Ipos'
2791 Vinfo( 2)='stations I-direction positions'
2792 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2793 & 1, (/stadim/), Aval, Vinfo, ncname, &
2794 & SetParAccess = .FALSE.)
2795 IF (exit_flag.ne.NoError) RETURN
2796
2797 Vinfo( 1)='Jpos'
2798 Vinfo( 2)='stations J-direction positions'
2799 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2800 & 1, (/stadim/), Aval, Vinfo, ncname, &
2801 & SetParAccess = .FALSE.)
2802 IF (exit_flag.ne.NoError) RETURN
2803 END IF
2804#endif
2805#ifdef NO_WRITE_GRID
2806 IF (ncid.eq.STA(ng)%ncid) THEN
2807#else
2808 IF (ncid.ne.FLT(ng)%ncid) THEN
2809#endif
2810#if !(defined SED_MORPH && defined SEDIMENT)
2811!
2812! Bathymetry.
2813!
2814 Vinfo( 1)='h'
2815 Vinfo( 2)='bathymetry at RHO-points'
2816 Vinfo( 3)='meter'
2817 Vinfo(14)='bath, scalar'
2818 Vinfo(22)='coordinates'
2819 Aval(5)=REAL(r2dvar,r8)
2820 IF (ncid.eq.STA(ng)%ncid) THEN
2821 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2822 & 1, (/stadim/), Aval, Vinfo, ncname)
2823 IF (exit_flag.ne.NoError) RETURN
2824 ELSE
2825 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2826 & 2, t2dgrd, Aval, Vinfo, ncname)
2827 IF (exit_flag.ne.NoError) RETURN
2828 END IF
2829#endif
2830!
2831! Coriolis Parameter.
2832!
2833 IF (ncid.ne.STA(ng)%ncid) THEN
2834 Vinfo( 1)='f'
2835 Vinfo( 2)='Coriolis parameter at RHO-points'
2836 Vinfo( 3)='second-1'
2837 Vinfo(14)='coriolis, scalar'
2838 Vinfo(22)='coordinates'
2839 Aval(5)=REAL(r2dvar,r8)
2840 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2841 & 2, t2dgrd, Aval, Vinfo, ncname)
2842 IF (exit_flag.ne.NoError) RETURN
2843 END IF
2844!
2845! Curvilinear coordinate metrics.
2846!
2847 IF (ncid.ne.STA(ng)%ncid) THEN
2848 Vinfo( 1)='pm'
2849 Vinfo( 2)='curvilinear coordinate metric in XI'
2850 Vinfo( 3)='meter-1'
2851 Vinfo(14)='pm, scalar'
2852 Vinfo(22)='coordinates'
2853 Aval(5)=REAL(r2dvar,r8)
2854 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2855 & 2, t2dgrd, Aval, Vinfo, ncname)
2856 IF (exit_flag.ne.NoError) RETURN
2857
2858 Vinfo( 1)='pn'
2859 Vinfo( 2)='curvilinear coordinate metric in ETA'
2860 Vinfo( 3)='meter-1'
2861 Vinfo(14)='pn, scalar'
2862 Vinfo(22)='coordinates'
2863 Aval(5)=REAL(r2dvar,r8)
2864 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2865 & 2, t2dgrd, Aval, Vinfo, ncname)
2866 IF (exit_flag.ne.NoError) RETURN
2867 END IF
2868!
2869! Grid coordinates of RHO-points.
2870!
2871 IF (spherical) THEN
2872 Vinfo( 1)='lon_rho'
2873 Vinfo( 2)='longitude of RHO-points'
2874 Vinfo( 3)='degree_east'
2875 Vinfo(14)='lon_rho, scalar'
2876 Vinfo(21)='longitude'
2877 IF (ncid.eq.STA(ng)%ncid) THEN
2878 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2879 & 1, (/stadim/), Aval, Vinfo, ncname)
2880 IF (exit_flag.ne.NoError) RETURN
2881 ELSE
2882 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2883 & 2, t2dgrd, Aval, Vinfo, ncname)
2884 IF (exit_flag.ne.NoError) RETURN
2885 END IF
2886
2887 Vinfo( 1)='lat_rho'
2888 Vinfo( 2)='latitude of RHO-points'
2889 Vinfo( 3)='degree_north'
2890 Vinfo(14)='lat_rho, scalar'
2891 Vinfo(21)='latitude'
2892 IF (ncid.eq.STA(ng)%ncid) THEN
2893 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2894 & 1, (/stadim/), Aval, Vinfo, ncname)
2895 IF (exit_flag.ne.NoError) RETURN
2896 ELSE
2897 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2898 & 2, t2dgrd, Aval, Vinfo, ncname)
2899 IF (exit_flag.ne.NoError) RETURN
2900 END IF
2901 ELSE
2902 Vinfo( 1)='x_rho'
2903 Vinfo( 2)='x-locations of RHO-points'
2904 Vinfo( 3)='meter'
2905 Vinfo(14)='x_rho, scalar'
2906 IF (ncid.eq.STA(ng)%ncid) THEN
2907 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2908 & 1, (/stadim/), Aval, Vinfo, ncname)
2909 IF (exit_flag.ne.NoError) RETURN
2910 ELSE
2911 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2912 & 2, t2dgrd, Aval, Vinfo, ncname)
2913 IF (exit_flag.ne.NoError) RETURN
2914 END IF
2915
2916 Vinfo( 1)='y_rho'
2917 Vinfo( 2)='y-locations of RHO-points'
2918 Vinfo( 3)='meter'
2919 Vinfo(14)='y_rho, scalar'
2920 IF (ncid.eq.STA(ng)%ncid) THEN
2921 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2922 & 1, (/stadim/), Aval, Vinfo, ncname)
2923 IF (exit_flag.ne.NoError) RETURN
2924 ELSE
2925 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2926 & 2, t2dgrd, Aval, Vinfo, ncname)
2927 IF (exit_flag.ne.NoError) RETURN
2928 END IF
2929 END IF
2930!
2931! Grid coordinates of U-points.
2932!
2933 IF (spherical) THEN
2934 Vinfo( 1)='lon_u'
2935 Vinfo( 2)='longitude of U-points'
2936 Vinfo( 3)='degree_east'
2937 Vinfo(14)='lon_u, scalar'
2938 Vinfo(21)='longitude'
2939 IF (ncid.ne.STA(ng)%ncid) THEN
2940 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2941 & 2, u2dgrd, Aval, Vinfo, ncname)
2942 IF (exit_flag.ne.NoError) RETURN
2943 END IF
2944
2945 Vinfo( 1)='lat_u'
2946 Vinfo( 2)='latitude of U-points'
2947 Vinfo( 3)='degree_north'
2948 Vinfo(14)='lat_u, scalar'
2949 Vinfo(21)='latitude'
2950 IF (ncid.ne.STA(ng)%ncid) THEN
2951 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2952 & 2, u2dgrd, Aval, Vinfo, ncname)
2953 IF (exit_flag.ne.NoError) RETURN
2954 END IF
2955 ELSE
2956 Vinfo( 1)='x_u'
2957 Vinfo( 2)='x-locations of U-points'
2958 Vinfo( 3)='meter'
2959 Vinfo(14)='x_u, scalar'
2960 IF (ncid.ne.STA(ng)%ncid) THEN
2961 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2962 & 2, u2dgrd, Aval, Vinfo, ncname)
2963 IF (exit_flag.ne.NoError) RETURN
2964 END IF
2965
2966 Vinfo( 1)='y_u'
2967 Vinfo( 2)='y-locations of U-points'
2968 Vinfo( 3)='meter'
2969 Vinfo(14)='y_u, scalar'
2970 IF (ncid.ne.STA(ng)%ncid) THEN
2971 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2972 & 2, u2dgrd, Aval, Vinfo, ncname)
2973 IF (exit_flag.ne.NoError) RETURN
2974 END IF
2975 END IF
2976!
2977! Grid coordinates of V-points.
2978!
2979 IF (spherical) THEN
2980 Vinfo( 1)='lon_v'
2981 Vinfo( 2)='longitude of V-points'
2982 Vinfo( 3)='degree_east'
2983 Vinfo(14)='lon_v, scalar'
2984 Vinfo(21)='longitude'
2985 IF (ncid.ne.STA(ng)%ncid) THEN
2986 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2987 & 2, v2dgrd, Aval, Vinfo, ncname)
2988 IF (exit_flag.ne.NoError) RETURN
2989 END IF
2990
2991 Vinfo( 1)='lat_v'
2992 Vinfo( 2)='latitude of V-points'
2993 Vinfo( 3)='degree_north'
2994 Vinfo(14)='lat_v, scalar'
2995 Vinfo(21)='latitude'
2996 IF (ncid.ne.STA(ng)%ncid) THEN
2997 status=def_var(ng, model, ncid, varid, NF_TYPE, &
2998 & 2, v2dgrd, Aval, Vinfo, ncname)
2999 IF (exit_flag.ne.NoError) RETURN
3000 END IF
3001 ELSE
3002 Vinfo( 1)='x_v'
3003 Vinfo( 2)='x-locations of V-points'
3004 Vinfo( 3)='meter'
3005 Vinfo(14)='x_v, scalar'
3006 IF (ncid.ne.STA(ng)%ncid) THEN
3007 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3008 & 2, v2dgrd, Aval, Vinfo, ncname)
3009 IF (exit_flag.ne.NoError) RETURN
3010 END IF
3011
3012 Vinfo( 1)='y_v'
3013 Vinfo( 2)='y-locations of V-points'
3014 Vinfo( 3)='meter'
3015 Vinfo(14)='y_v, scalar'
3016 IF (ncid.ne.STA(ng)%ncid) THEN
3017 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3018 & 2, v2dgrd, Aval, Vinfo, ncname)
3019 IF (exit_flag.ne.NoError) RETURN
3020 END IF
3021 END IF
3022!
3023! Grid coordinates of PSI-points.
3024!
3025 IF (spherical) THEN
3026 Vinfo( 1)='lon_psi'
3027 Vinfo( 2)='longitude of PSI-points'
3028 Vinfo( 3)='degree_east'
3029 Vinfo(14)='lon_psi, scalar'
3030 Vinfo(21)='longitude'
3031 IF (ncid.ne.STA(ng)%ncid) THEN
3032 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3033 & 2, p2dgrd, Aval, Vinfo, ncname)
3034 IF (exit_flag.ne.NoError) RETURN
3035 END IF
3036
3037 Vinfo( 1)='lat_psi'
3038 Vinfo( 2)='latitude of PSI-points'
3039 Vinfo( 3)='degree_north'
3040 Vinfo(14)='lat_psi, scalar'
3041 Vinfo(21)='latitude'
3042 IF (ncid.ne.STA(ng)%ncid) THEN
3043 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3044 & 2, p2dgrd, Aval, Vinfo, ncname)
3045 IF (exit_flag.ne.NoError) RETURN
3046 END IF
3047 ELSE
3048 Vinfo( 1)='x_psi'
3049 Vinfo( 2)='x-locations of PSI-points'
3050 Vinfo( 3)='meter'
3051 Vinfo(14)='x_psi, scalar'
3052 IF (ncid.ne.STA(ng)%ncid) THEN
3053 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3054 & 2, p2dgrd, Aval, Vinfo, ncname)
3055 IF (exit_flag.ne.NoError) RETURN
3056 END IF
3057
3058 Vinfo( 1)='y_psi'
3059 Vinfo( 2)='y-locations of PSI-points'
3060 Vinfo( 3)='meter'
3061 Vinfo(14)='y_psi, scalar'
3062 IF (ncid.ne.STA(ng)%ncid) THEN
3063 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3064 & 2, p2dgrd, Aval, Vinfo, ncname)
3065 IF (exit_flag.ne.NoError) RETURN
3066 END IF
3067 END IF
3068#ifdef CURVGRID
3069!
3070! Angle between XI-axis and EAST at RHO-points.
3071!
3072 Vinfo( 1)='angle'
3073 Vinfo( 2)='angle between XI-axis and EAST'
3074 Vinfo( 3)='radians'
3075 Vinfo(14)='angle, scalar'
3076 Vinfo(22)='coordinates'
3077 Aval(5)=REAL(r2dvar,r8)
3078 IF (ncid.eq.STA(ng)%ncid) THEN
3079 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3080 & 1, (/stadim/), Aval, Vinfo, ncname)
3081 IF (exit_flag.ne.NoError) RETURN
3082 ELSE
3083 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3084 & 2, t2dgrd, Aval, Vinfo, ncname)
3085 IF (exit_flag.ne.NoError) RETURN
3086 END IF
3087#endif
3088#ifdef MASKING
3089!
3090! Masking fields at RHO-, U-, V-points, and PSI-points.
3091!
3092 IF (ncid.ne.STA(ng)%ncid) THEN
3093 Vinfo( 1)='mask_rho'
3094 Vinfo( 2)='mask on RHO-points'
3095 Vinfo( 9)='land'
3096 Vinfo(10)='water'
3097 Vinfo(22)='coordinates'
3098 Aval(5)=REAL(r2dvar,r8)
3099 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3100 & 2, t2dgrd, Aval, Vinfo, ncname)
3101 IF (exit_flag.ne.NoError) RETURN
3102
3103 Vinfo( 1)='mask_u'
3104 Vinfo( 2)='mask on U-points'
3105 Vinfo( 9)='land'
3106 Vinfo(10)='water'
3107 Vinfo(22)='coordinates'
3108 Aval(5)=REAL(u2dvar,r8)
3109 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3110 & 2, u2dgrd, Aval, Vinfo, ncname)
3111 IF (exit_flag.ne.NoError) RETURN
3112
3113 Vinfo( 1)='mask_v'
3114 Vinfo( 2)='mask on V-points'
3115 Vinfo( 9)='land'
3116 Vinfo(10)='water'
3117 Vinfo(22)='coordinates'
3118 Aval(5)=REAL(v2dvar,r8)
3119 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3120 & 2, v2dgrd, Aval, Vinfo, ncname)
3121 IF (exit_flag.ne.NoError) RETURN
3122
3123 Vinfo( 1)='mask_psi'
3124 Vinfo( 2)='mask on psi-points'
3125 Vinfo( 9)='land'
3126 Vinfo(10)='water'
3127 Vinfo(22)='coordinates'
3128 Aval(5)=REAL(p2dvar,r8)
3129 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3130 & 2, p2dgrd, Aval, Vinfo, ncname)
3131 IF (exit_flag.ne.NoError) RETURN
3132 END IF
3133#endif
3134#if defined AD_SENSITIVITY || defined IS4DVAR_SENSITIVITY || \
3135 defined OPT_OBSERVATIONS || defined SENSITIVITY_4DVAR || \
3136 defined SO_SEMI
3137!
3138! Adjoint sensitivity spatial scope mask at RHO-, U-, and V-points.
3139!
3140 IF (ncid.ne.STA(ng)%ncid) THEN
3141 Vinfo( 1)='scope_rho'
3142 Vinfo( 2)='adjoint sensitivity spatial scope on RHO-points'
3143 Vinfo( 9)='inactive'
3144 Vinfo(10)='active'
3145 Vinfo(22)='coordinates'
3146 Aval(5)=REAL(r2dvar,r8)
3147 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3148 & 2, t2dgrd, Aval, Vinfo, ncname)
3149 IF (exit_flag.ne.NoError) RETURN
3150
3151 Vinfo( 1)='scope_u'
3152 Vinfo( 2)='adjoint sensitivity spatial scope on U-points'
3153 Vinfo( 9)='inactive'
3154 Vinfo(10)='active'
3155 Vinfo(22)='coordinates'
3156 Aval(5)=REAL(u2dvar,r8)
3157 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3158 & 2, u2dgrd, Aval, Vinfo, ncname)
3159 IF (exit_flag.ne.NoError) RETURN
3160
3161 Vinfo( 1)='scope_v'
3162 Vinfo( 2)='adjoint sensitivity spatial scope on V-points'
3163 Vinfo( 9)='inactive'
3164 Vinfo(10)='active'
3165 Vinfo(22)='coordinates'
3166 Aval(5)=REAL(v2dvar,r8)
3167 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3168 & 2, v2dgrd, Aval, Vinfo, ncname)
3169 IF (exit_flag.ne.NoError) RETURN
3170 END IF
3171#endif
3172#ifdef UV_DRAG_GRID
3173!
3174! Spatially varying bottom friction parameter.
3175!
3176 IF (ncid.ne.STA(ng)%ncid) THEN
3177# ifdef UV_LOGDRAG
3178 Vinfo( 1)=Vname(1,idZoBL)
3179 Vinfo( 2)=Vname(2,idZoBL)
3180 Vinfo( 3)=Vname(3,idZoBL)
3181 Vinfo(14)=Vname(4,idZoBL)
3182 Vinfo(22)='coordinates'
3183 Aval(5)=REAL(r2dvar,r8)
3184 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3185 & 2, t2dgrd, Aval, Vinfo, ncname)
3186 IF (exit_flag.ne.NoError) RETURN
3187# endif
3188# ifdef UV_LDRAG
3189 Vinfo( 1)=Vname(1,idragL)
3190 Vinfo( 2)=Vname(2,idragL)
3191 Vinfo( 3)=Vname(3,idragL)
3192 Vinfo(14)=Vname(4,idragL)
3193 Vinfo(22)='coordinates'
3194 Aval(5)=REAL(r2dvar,r8)
3195 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3196 & 2, t2dgrd, Aval, Vinfo, ncname)
3197 IF (exit_flag.ne.NoError) RETURN
3198# endif
3199# ifdef UV_QDRAG
3200 Vinfo( 1)=Vname(1,idragQ)
3201 Vinfo( 2)=Vname(2,idragQ)
3202 Vinfo( 3)=Vname(3,idragQ)
3203 Vinfo(14)=Vname(4,idragQ)
3204 Vinfo(22)='coordinates'
3205 Aval(5)=REAL(r2dvar,r8)
3206 status=def_var(ng, model, ncid, varid, NF_TYPE, &
3207 & 2, t2dgrd, Aval, Vinfo, ncname)
3208 IF (exit_flag.ne.NoError) RETURN
3209# endif
3210 END IF
3211#endif
3212 END IF
3213
3214 10 FORMAT (i3.3,'x',i3.3)
3215 20 FORMAT (/,' DEF_INFO - error while creating global attribute: ', &
3216 & a,/,12x,a)
3217 30 FORMAT ('frc_file_',i2.2)
3218
3219 RETURN
3220 END SUBROUTINE def_info