New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
trcdit.F90 in trunk/NEMO/TOP_SRC – NEMO

source: trunk/NEMO/TOP_SRC/trcdit.F90 @ 268

Last change on this file since 268 was 268, checked in by opalod, 19 years ago

nemo_v1_update_05:RB+OA: Update and rewritting of part of the TOP component

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 30.9 KB
Line 
1MODULE trcdit
2
3      !!----------------------------------------------------------------------
4      !! * Modules used
5      !! ==============
6   USE oce_trc
7   USE trc
8   USE dianam    ! build name of file (routine)
9   USE in_out_manager  ! I/O manager
10
11   IMPLICIT NONE
12   PRIVATE
13
14   !! * Accessibility
15   PUBLIC trcdit_wr
16   PUBLIC trcdid_wr
17   PUBLIC trcdii_wr
18   PUBLIC trcdib_wr
19
20   !! * Module variables
21   INTEGER            ::  &
22      nit5     ,  &   !!: id for tracer output file
23      ndepit5  ,  &   !!: id for depth mesh
24      nhorit5  ,  &   !!: id for horizontal mesh
25      ndimt50  ,  &   !!: number of ocean points in index array
26      ndimt51         !!: number of ocean points in index array
27   REAL(wp) :: zjulian
28   INTEGER , DIMENSION (jpij*jpk) ::  ndext50 !!: integer arrays for ocean 3D index
29   INTEGER , DIMENSION (jpij)     ::  ndext51 !!: integer arrays for ocean surface index
30#    if defined key_passivetrc && defined key_trc_diaadd
31   INTEGER            :: &
32      nitd     ,  &   !!: id for additional array output file
33      ndepitd  ,  &   !!: id for depth mesh
34      nhoritd         !!: id for horizontal mesh
35#    endif
36#    if defined key_passivetrc && defined key_trc_diatrd
37   INTEGER , DIMENSION (jptra)  :: &
38      nit6    ,   &   !!: id for additional array output file
39      ndepit6 ,   &   !!: id for depth mesh
40      nhorit6         !!: id for horizontal mesh
41#    endif
42#    if defined key_passivetrc && defined key_trc_diabio
43   INTEGER            :: &
44      nitb     ,   &  !!:  id for additional array output FILE
45      ndepitb  ,   &  !!:  id for depth mesh
46      nhoritb  ,   &  !!:  id for horizontal mesh
47#    endif
48
49
50   !! * Substitutions
51#  include "passivetrc_substitute.h90"
52
53CONTAINS
54
55#    if defined key_passivetrc
56
57      SUBROUTINE trcdit_wr(kt,kindic)
58   !!===========================================================================================
59   !!
60   !!                       ROUTINE trcdit_wr
61   !!===========================================================================================
62   !!
63   !! Purpose :
64   !!---------
65   !!          Standard output of passive tracer : concentration fields
66   !!
67   !!
68   !! Method :
69   !! -------
70   !!
71   !!        At the beginning of the first time step (nit000), define all
72   !!        the NETCDF files and fields for concentration of passive tracer
73   !!
74   !!        At each time step call histdef to compute the mean if necessary
75   !!        Each nwritetrc time step, output the instantaneous or mean fields
76   !!
77   !!        IF kindic <0, output of fields before the model interruption.
78   !!        IF kindic =0, time step loop
79   !!        IF kindic >0, output of fields before the time step loop
80   !!
81   !! Input :
82   !! -----
83   !!   argument
84   !!           kt              : time step
85   !!           kindic          : indicator of abnormal termination
86   !!
87   !! EXTERNAL :
88   !! --------
89   !! prihre, hist..., dianam
90   !!
91   !! History:
92   !! --------
93   !!   original  : 95-01  passive tracers  (M. Levy)
94   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
95   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
96   !!   additions : 99-09 (M.A. Foujols) split into three parts
97   !!   05-03 (O. Aumont and A. El Moussaoui) F90
98   !!==================================================================================================!
99
100      !! Modules used
101      USE ioipsl
102
103
104      !! * Arguments
105      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
106
107      !! * Local declarations
108      INTEGER :: jn
109      LOGICAL :: ll_print = .FALSE.
110
111      CHARACTER (len=40) :: clhstnam, clop
112      CHARACTER (len=20) :: cltra, cltrau
113      CHARACTER (len=80) :: cltral
114
115      REAL(wp) :: zsto, zout, zdt
116      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it
117!
118! 0. Initialisation
119! -----------------
120
121! local variable for debugging
122      ll_print = .FALSE.
123      ll_print = ll_print .AND. lwp
124
125! Define frequency of output and means
126
127      zdt = rdt
128#        if defined key_diainstant
129      zsto=nwritetrc*rdt
130      clop='inst(only(x))'
131#        else
132      zsto=zdt
133      clop='ave(only(x))'
134#        endif
135      zout=nwritetrc*zdt
136
137      ! Define indices of the horizontal output zoom and vertical limit storage
138      iimi = 1      ;      iima = jpi
139      ijmi = 1      ;      ijma = jpj
140      ipk = jpk
141
142      ! define time axis
143      it = kt - nit000 + 1
144
145! 1. Define NETCDF files and fields at beginning of first time step
146! -----------------------------------------------------------------
147
148      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic
149      IF(kt == nit000.and.kindic == 1) THEN
150
151! Compute julian date from starting date of the run
152
153         CALL ymds2ju(nyear,nmonth,nday,0.0,zjulian)
154         IF(lwp)WRITE(numout,*)' ' 
155         IF(lwp)WRITE(numout,*)' Date 0 used :',nit000     &
156       &     ,' YEAR ',nyear,' MONTH ',nmonth,' DAY ',nday   &
157       &     ,'Julian day : ',zjulian   
158         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
159                                 ' limit storage in depth = ', ipk
160
161
162! Define the NETCDF files for passive tracer concentration
163
164         CALL dia_nam(clhstnam,nwritetrc,'ptrc_T')
165
166         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
167! Horizontal grid : glamt and gphit
168 
169         CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,     &
170         &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
171         &    0, zjulian, zdt, nhorit5, nit5)
172! Vertical grid for tracer : gdept
173         CALL histvert(nit5, 'deptht', 'Vertical T levels', &
174         &    'm', ipk, gdept, ndepit5)
175
176! Index of ocean points in 3D and 2D (surface)
177         CALL wheneq(jpi*jpj*ipk,tmask,1,1.,ndext50,ndimt50)
178         CALL wheneq(jpi*jpj,tmask,1,1.,ndext51,ndimt51)
179
180! Declare all the output fields as NETCDF variables
181
182! tracer concentrations
183
184         DO jn=1,jptra
185           cltra=ctrcnm(jn)    ! short title for tracer
186           cltral=ctrcnl(jn)   ! long title for tracer
187           cltrau=ctrcun(jn)   ! UNIT for tracer
188           CALL histdef(nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,  &
189         &          ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout) 
190         END DO           
191
192! CLOSE netcdf Files
193         
194         CALL histend(nit5)
195
196         IF(lwp) WRITE(numout,*)
197         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdit_wr'
198         IF(ll_print) CALL FLUSH(numout )
199
200      ENDIF
201
202! SOME diagnostics to DO first time
203
204! 2. Start writing data
205! ---------------------
206
207! tracer concentrations
208
209      IF( lwp .AND. MOD( kt, nwritetrc ) == 0 ) THEN
210         WRITE(numout,*) 'trcdit_wr : write NetCDF passive tracer concentrations at ', kt, 'time-step'
211         WRITE(numout,*) '~~~~~~ '
212      ENDIF
213
214      DO jn=1,jptra
215         cltra=ctrcnm(jn) ! short title for tracer
216         CALL histwrite(nit5, cltra, it, trn(:,:,:,jn), ndimt50,   &
217      &          ndext50)
218      END DO 
219
220! synchronise FILE
221
222      IF( MOD( kt, nwritetrc ) == 0 .OR. kindic < 0 ) THEN
223              CALL histsync(nit5)
224      ENDIF
225
226! 3. Closing all files
227! --------------------
228      IF( kt == nitend .OR. kindic < 0 ) THEN
229          CALL histclo(nit5)
230      ENDIF
231
232END SUBROUTINE trcdit_wr
233
234#    else
235
236! no passive tracers
237
238SUBROUTINE trcdit_wr(kt,kindic)
239     !!! no passive tracers
240     INTEGER, INTENT ( in ) :: kt, kindic
241     WRITE(*,*) 'trcdit_wr: You should not have seen this print! error?', kt, kindic
242END SUBROUTINE trcdit_wr
243
244#    endif
245
246#    if defined key_passivetrc && defined key_trc_diatrd
247
248      SUBROUTINE trcdid_wr(kt,kindic)
249 !!===========================================================================================
250   !!
251   !!                       ROUTINE trcdid_wr
252   !!===========================================================================================
253   !!
254   !! Purpose :
255   !!---------
256   !!          output of opa: passive tracer dynamical trends
257   !!
258   !!
259   !! Method :
260   !! -------
261   !!
262   !!        At the beginning of the first time step (nit000), define all
263   !!        the NETCDF files and fields for dynamical trends of tracers
264   !!
265   !!        At each time step call histdef to compute the mean if necessary
266   !!        Each nwritetrd time step, output the instantaneous or mean fields
267   !!
268   !!        IF kindic <0, output of fields before the model interruption.
269   !!        IF kindic =0, time step loop
270   !!        IF kindic >0, output of fields before the time step loop
271   !!
272   !! Input :
273   !! -----
274   !!   argument
275   !!           kt              : time step
276   !!           kindic          : indicator of abnormal termination
277   !!
278   !! Output :
279   !! ------
280   !!   file
281   !!           "clhstnam" files : one for concentration
282   !!
283   !! History:
284   !! --------
285   !!   original  : 95-01  passive tracers  (M. Levy)
286   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
287   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
288   !!   additions : 99-09 (M.A. Foujols) split into three parts
289   !!   additions : 01-06 (Mehdi B, Elodie K): suppress initialization
290   !!                                          of nit6,nhorit6,ndepit6
291   !!   05-03 (O. Aumont and A. El Moussaoui) F90
292   !!==================================================================================================!
293
294      !! Modules used
295      USE ioipsl
296
297      !! * Arguments
298      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
299
300      INTEGER :: jn, jl
301      LOGICAL :: ll_print = .FALSE.
302
303      CHARACTER (len=40) :: clhstnam, clop
304      CHARACTER (len=20) :: cltra, cltrau
305      CHARACTER (len=80) :: cltral
306      CHARACTER (len=10) :: csuff
307
308      REAL(wp) :: zsto, zout, zdt
309      INTEGER :: iimi, iima, ijmi, ijma, ipk, it
310
311!
312! 0. Initialisation
313! -----------------
314
315! local variable for debugging
316      ll_print = .FALSE.
317      ll_print = ll_print .AND. lwp
318!
319! Define frequency of output and means
320!
321      zdt = rdt
322#        if defined key_diainstant
323      zsto=nwritetrd*rdt
324      clop='inst(only(x))'
325#        else
326      zsto=zdt
327      clop='ave(only(x))'
328#        endif
329      zout=nwritetrd*zdt
330
331      ! Define indices of the horizontal output zoom and vertical limit storage
332      iimi = 1      ;      iima = jpi
333      ijmi = 1      ;      ijma = jpj
334      ipk = jpk
335
336      ! define time axis
337      it = kt - nit000 + 1
338
339! Define the NETCDF files (one per tracer)
340!
341      IF(ll_print)WRITE(numout,*)'trcdid kt=',kt,' kindic ',kindic
342      IF(kt == nit000.and.kindic == 1) THEN
343
344          DO jn=1,jptra
345
346            IF (luttrd(jn)) THEN
347
348! Define the file for dynamical trends - one per each tracer IF required
349
350         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
351                                 ' limit storage in depth = ', ipk
352                csuff='DY_'//ctrcnm(jn)
353                CALL dia_nam(clhstnam,nwritetrd,csuff)
354                IF(lwp)WRITE(numout,*)     &
355                &      " Name of NETCDF file for dynamical trends",   &
356                &      " of tracer number : ",clhstnam
357
358                CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,   &
359                &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
360                &    0, zjulian, rdt, nhorit6(jn),               &
361                &    nit6(jn))
362
363! Vertical grid for tracer trend - one per each tracer IF needed
364                CALL histvert(nit6(jn), 'deptht', 'Vertical T levels',  &
365                &    'm', ipk, gdept, ndepit6(jn)) 
366
367
368            END IF
369          END DO
370
371! Declare all the output fields as NETCDF variables
372
373
374! trends for tracer concentrations
375          DO jn=1,jptra
376            IF (luttrd(jn)) THEN
377                DO jl=1,jpdiatrc
378                  IF (jl.eq.1) THEN
379! short and long title for x advection for tracer
380                      WRITE (cltra,'("XAD_",a)') ctrcnm(jn)
381                      WRITE (cltral,'("X advective trend for ",a)')  &
382                      &      ctrcnl(jn)
383                  END IF
384                  IF (jl.eq.2)  THEN
385! short and long title for y advection for tracer
386                      WRITE (cltra,'("YAD_",a)') ctrcnm(jn)
387                      WRITE (cltral,'("Y advective trend for ",a)')  &
388                      &      ctrcnl(jn)
389                  END IF
390                  IF (jl.eq.3)  THEN
391! short and long title for Z advection for tracer
392                      WRITE (cltra,'("ZAD_",a)') ctrcnm(jn)
393                      WRITE (cltral,'("Z advective trend for ",a)')  &
394                      &      ctrcnl(jn)
395                  END IF
396                  IF (jl.eq.4)  THEN
397! short and long title for X diffusion for tracer
398                      WRITE (cltra,'("XDF_",a)') ctrcnm(jn)
399                      WRITE (cltral,'("X diffusion trend for ",a)')  &
400                      &      ctrcnm(jn)
401                  END IF
402                  IF (jl.eq.5)  THEN
403! short and long title for Y diffusion for tracer
404                      WRITE (cltra,'("YDF_",a)') ctrcnm(jn)
405                      WRITE (cltral,'("Y diffusion trend for ",a)')  &
406                      &      ctrcnm(jn)
407                  END IF
408                  IF (jl.eq.6)  THEN
409! short and long title for Z diffusion for tracer
410                      WRITE (cltra,'("ZDF_",a)') ctrcnm(jn)
411                      WRITE (cltral,'("Z diffusion trend for ",a)')  &
412                      &      ctrcnm(jn)
413                  END IF
414# if defined key_trc_ldfeiv
415                  IF (jl.eq.7) THEN
416! short and long title for x gent velocity for tracer
417                      WRITE (cltra,'("Xgv",a)') ctrcnm(jn)
418                      WRITE (cltral,'("X gent velocity trend for ",a)')  &
419                      &      ctrcnl(jn)
420                  END IF
421                  IF (jl.eq.8)  THEN
422! short and long title for y gent velocity for tracer
423                      WRITE (cltra,'("YGV_",a)') ctrcnm(jn)
424                      WRITE (cltral,'("Y gent velocity trend for ",a)')  &
425                      &i     ctrcnl(jn)
426                  END IF
427                  IF (jl.eq.9)  THEN
428! short and long title for Z gent velocity for tracer
429                      WRITE (cltra,'("ZGV_",a)') ctrcnm(jn)
430                      WRITE (cltral,'("Z gent velocity trend for ",a)')  &
431                      &i     ctrcnl(jn)
432                  END IF
433# endif
434# if defined key_trcdmp
435                  IF (jl.eq.jpdiatrc)  THEN
436! last trends for tracer damping : short and long title
437                      WRITE (cltra,'("TDM_",a)') ctrcnm(jn)
438                      WRITE (cltral,'("Tracer damping trend for ",a)')  &
439                      &      ctrcnl(jn)
440                  END IF
441# endif
442                  cltrau=ctrcun(jn) ! UNIT for tracer /trends
443                  CALL histdef(nit6(jn), cltra, cltral, cltrau, jpi,jpj,  &
444                  &   nhorit6(jn), ipk, 1, ipk,  ndepit6(jn), 32, clop,
445                  &   zsto,zout)
446                END DO
447            END IF
448          END DO
449
450! CLOSE netcdf Files
451
452          DO jn=1,jptra
453             IF (luttrd(jn)) CALL histend(nit6(jn))
454          END DO
455
456         IF(lwp) WRITE(numout,*)
457         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdid'
458         IF(ll_print) CALL FLUSH(numout )
459
460      ENDIF
461
462! SOME diagnostics to DO first time
463
464! 2. Start writing data
465! ---------------------
466
467! trends for tracer concentrations
468
469      IF( lwp .AND. MOD( kt, nwritetrd ) == 0 ) THEN
470         WRITE(numout,*) 'trcdid_wr : write NetCDF dynamical trends at ', kt, 'time-step'
471         WRITE(numout,*) '~~~~~~ '
472      ENDIF
473
474          DO jn=1,jptra
475            IF (luttrd(jn)) THEN
476                DO jl=1,jpdiatrc
477                  IF (jl.eq.1) THEN
478! short title for x advection for tracer
479                      WRITE (cltra,'("XAD_",a)') ctrcnm(jn)
480                  END IF
481                  IF (jl.eq.2)  THEN
482! short title for y advection for tracer
483                      WRITE (cltra,'("YAD_",a)') ctrcnm(jn)
484                  END IF
485                  IF (jl.eq.3)  THEN
486! short title for z advection for tracer
487                      WRITE (cltra,'("ZAD_",a)') ctrcnm(jn)
488                  END IF
489                  IF (jl.eq.4)  THEN
490! short title for x diffusion for tracer
491                      WRITE (cltra,'("XDF_",a)') ctrcnm(jn)
492                  END IF
493                  IF (jl.eq.5)  THEN
494! short title for y diffusion for tracer
495                      WRITE (cltra,'("YDF_",a)') ctrcnm(jn)
496                  END IF
497                  IF (jl.eq.6)  THEN
498! short title for z diffusion for tracer
499                      WRITE (cltra,'("ZDF_",a)') ctrcnm(jn)
500                  END IF
501# if defined key_trc_ldfeiv
502                  IF (jl.eq.7) THEN
503! short for x gent velocity for tracer
504                      WRITE (cltra,'("XGV_",a)') ctrcnm(jn)
505                  END IF
506                  IF (jl.eq.8)  THEN
507! short for y gent velocity for tracer
508                      WRITE (cltra,'("YGV_",a)') ctrcnm(jn)
509                  END IF
510                  IF (jl.eq.9)  THEN
511! short title for Z gent velocity for tracer
512                      WRITE (cltra,'("ZGV_",a)') ctrcnm(jn)
513                  END IF
514# endif
515# if defined key_trcdmp
516                  IF (jl.eq.jpdiatrc) THEN
517! short for x gent velocity for tracer
518                      WRITE (cltra,'("TDM_",a)') ctrcnm(jn)
519                  END IF
520# endif
521
522                  CALL histwrite(nit6(jn), cltra, it, trtrd(:,:,:,jn,jl)  &
523                  &    ,ndimt50, ndext50)
524                END DO
525            END IF
526          END DO
527
528! synchronise FILE
529
530      IF( MOD( kt, nwritetrd ) == 0 .OR. kindic < 0 ) THEN
531          DO jn=1,jptra
532              CALL histsync(nit6(jn))
533          END DO
534      ENDIF
535
536! 3. Closing all files
537! --------------------
538
539      IF( kt == nitend .OR. kindic < 0 ) THEN
540          DO jn=1,jptra
541             CALL histclo(nit6(jn))
542          END DO
543      ENDIF
544
545END SUBROUTINE trcdid_wr
546
547#    else
548
549SUBROUTINE trcdid_wr(kt,kindic)
550     !!! no passive tracers
551     INTEGER, INTENT ( in ) :: kt, kindic
552     WRITE(*,*) 'trcdid_wr: You should not have seen this print! error?', kt, kindic
553END SUBROUTINE trcdid_wr
554
555#    endif
556
557#    if defined key_passivetrc && defined key_trc_diaadd
558
559      SUBROUTINE trcdii_wr(kt,kindic)
560   !!===========================================================================================
561   !!
562   !!                       ROUTINE trcdii_wr
563   !!===========================================================================================
564   !!
565   !! Purpose :
566   !!---------
567   !!          output of passive tracer : additional 2D and 3D arrays
568   !!
569   !!
570   !! Method :
571   !! -------
572   !!
573   !!        At the beginning of the first time step (nit000), define all
574   !!        the NETCDF files and fields for additional arrays
575   !!
576   !!        At each time step call histdef to compute the mean if necessary
577   !!        Each nwritetrc time step, output the instantaneous or mean fields
578   !!
579   !!
580   !!        IF kindic <0, output of fields before the model interruption.
581   !!        IF kindic =0, time step loop
582   !!        IF kindic >0, output of fields before the time step loop
583   !!
584   !! Input :
585   !! -----
586   !!   argument
587   !!           kt              : time step
588   !!           kindic          : indicator of abnormal termination
589   !!
590   !! EXTERNAL :
591   !! --------
592   !! prihre, hist..., dianam
593   !!
594   !! History:
595   !! --------
596   !!   original  : 95-01  passive tracers  (M. Levy)
597   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
598   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
599   !!   additions : 99-09 (M.A. Foujols) split into three parts
600   !!   05-03 (O. Aumont and A. El Moussaoui) F90
601   !!==================================================================================================!
602
603      !! Modules used
604      USE ioipsl
605
606      !! * Arguments
607      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
608
609      INTEGER :: jn
610      LOGICAL :: ll_print = .FALSE.
611
612      CHARACTER (len=40) :: clhstnam, clop
613      CHARACTER (len=20) :: cltra, cltrau
614      CHARACTER (len=80) :: cltral
615
616      REAL(wp) :: zsto, zout, zdt
617      INTEGER :: iimi, iima, ijmi, ijma, ipk, it
618
619!
620! 0. Initialisation
621! -----------------
622
623! local variable for debugging
624      ll_print = .FALSE.
625      ll_print = ll_print .AND. lwp
626!
627! Define frequency of output and means
628!
629      zdt = rdt
630#        if defined key_diainstant
631      zsto=nwriteadd*zdt
632      clop='inst(only(x))'
633#        else
634      zsto=zdt
635      clop='ave(only(x))'
636#        endif
637      zout=nwriteadd*zdt
638
639      ! Define indices of the horizontal output zoom and vertical limit storage
640      iimi = 1      ;      iima = jpi
641      ijmi = 1      ;      ijma = jpj
642      ipk = jpk
643
644      ! define time axis
645      it = kt - nit000 + 1
646
647! 1. Define NETCDF files and fields at beginning of first time step
648! -----------------------------------------------------------------
649
650      IF(ll_print)WRITE(numout,*)'trcdii_wr kt=',kt,' kindic ',kindic
651      IF(kt == nit000.and.kindic == 1) THEN
652
653! Define the NETCDF files for additional arrays : 2D or 3D
654
655! Define the T grid file for tracer auxiliary files
656
657          CALL dia_nam(clhstnam,nwrite,'diad_T')
658          IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
659
660! Define a netcdf FILE for 2d and 3d arrays
661
662          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,     &
663          &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         &
664          &    0, zjulian, zdt, nhoritd, nitd)
665
666! Vertical grid for 2d and 3d arrays
667
668          CALL histvert(nitd, 'deptht', 'Vertical T levels', &
669          &    'm', ipk, gdept, ndepitd)
670
671
672! Declare all the output fields as NETCDF variables
673
674! more 3D horizontal arrays
675
676          DO jn=1,jpdia3d
677            cltra=ctrc3d(jn)    ! short title for 3D diagnostic
678            cltral=ctrc3l(jn)   ! long title for 3D diagnostic
679            cltrau=ctrc3u(jn)   ! UNIT for 3D diagnostic
680            CALL histdef(nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
681            &    ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout)
682          END DO
683
684
685! more 2D horizontal arrays
686
687          DO jn=1,jpdia2d
688            cltra=ctrc2d(jn)    ! short title for 2D diagnostic
689            cltral=ctrc2l(jn)   ! long title for 2D diagnostic
690            cltrau=ctrc2u(jn)   ! UNIT for 2D diagnostic
691            CALL histdef(nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
692            &    1, 1, 1,  -99, 32, clop, zsto, zout)
693          END DO
694
695! TODO: more 2D vertical sections arrays : I or J indice fixed
696
697! CLOSE netcdf Files
698
699          CALL histend(nitd)
700
701         IF(lwp) WRITE(numout,*)
702         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdii_wr'
703         IF(ll_print) CALL FLUSH(numout )
704
705      ENDIF
706
707! 2. Start writing data
708! ---------------------
709
710      IF( lwp .AND. MOD( kt, nwriteadd ) == 0 ) THEN
711         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step'
712         WRITE(numout,*) '~~~~~~ '
713      ENDIF
714
715! more 3D horizontal arrays
716
717          DO jn=1,jpdia3d
718            cltra=ctrc3d(jn) ! short title for 3D diagnostic
719            CALL histwrite(nitd, cltra, it, trc3d(:,:,:,jn), ndimt50  &
720            &   ,ndext50)
721          END DO
722
723! more 2D horizontal arrays
724
725          DO jn=1,jpdia2d
726            cltra=ctrc2d(jn) ! short title for 2D diagnostic
727            CALL histwrite(nitd, cltra, kt, trc2d(:,:,jn), ndimt51    &
728            &   ,ndext51)
729          END DO
730
731! synchronise FILE
732
733      IF( MOD( kt, nwriteadd ) == 0 .OR. kindic < 0 ) THEN
734              CALL histsync(nitd)
735      ENDIF
736
737! 3. Closing all files
738! --------------------
739
740      IF( kt == nitend .OR. kindic < 0 ) THEN
741          CALL histclo(nitd)
742      ENDIF
743
744END SUBROUTINE trcdii_wr
745
746#    else
747
748SUBROUTINE trcdii_wr(kt,kindic)
749     !!! no passive tracers
750     INTEGER, INTENT ( in ) :: kt, kindic
751     WRITE(*,*) 'trcdii_wr: You should not have seen this print! error?', kt, kindic
752END SUBROUTINE trcdii_wr
753
754#    endif
755
756#    if defined key_passivetrc && defined key_trc_diabio
757
758      SUBROUTINE trcdib_wr(kt,kindic)
759 !!===========================================================================================
760   !!
761   !!                       ROUTINE trcdib_wr
762   !!===========================================================================================
763   !!
764   !! Purpose :
765   !!---------
766   !!          Specific output of opa: biological fields
767   !!
768   !!
769   !! Method :
770   !! -------
771   !!
772   !!        At the beginning of the first time step (nit000), define all
773   !!        the NETCDF files and fields for biological fields
774   !!
775   !!        At each time step call histdef to compute the mean if necessary
776   !!        Each nwritetrd time step, output the instantaneous or mean fields
777   !!
778   !!        IF kindic <0, output of fields before the model interruption.
779   !!        IF kindic =0, time step loop
780   !!        IF kindic >0, output of fields before the time step loop
781   !!
782   !! Input :
783   !! -----
784   !!   argument
785   !!           kt              : time step
786   !!           kindic          : indicator of abnormal termination
787   !!
788   !! Output :
789   !! ------
790   !!   file
791   !!           "histname" files : at least one file for each grid
792   !!
793   !! History:
794   !! --------
795   !!   original  : 95-01  passive tracers  (M. Levy)
796   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
797   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
798   !!   additions : 99-09 (M.A. Foujols) split into three parts
799   !!   additions : 01-06 (E Kestenare) assign a parameter to name
800   !!                                          individual tracers
801   !!   additions : 05-03 (O. Aumont and A El Moussaoui) F90
802   !!==================================================================================================!
803
804      !! Modules used
805      USE ioipsl
806
807      !! * Arguments
808      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
809
810      INTEGER :: ji, jj, jk, jn, jl
811      LOGICAL :: ll_print = .FALSE.
812
813      CHARACTER (len=40) :: clhstnam, clop
814      CHARACTER (len=20) :: cltra, cltrau
815      CHARACTER (len=80) :: cltral
816
817      REAL(wp) :: zsto, zout, zdt
818      REAL(wp) :: zsec
819      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it
820
821      REAL(wp) :: ztra,zder
822      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zphy
823
824!
825! 0. Initialisation
826! -----------------
827
828! local variable for debugging
829      ll_print = .FALSE.
830      ll_print = ll_print .AND. lwp
831!
832! Define frequency of output and means
833!
834      zdt = rdt
835#        if defined key_diainstant
836      zsto=nwritebio*zdt
837      clop='inst(only(x))'
838#        else
839      zsto=zdt
840      clop='ave(only(x))'
841#        endif
842      zout=nwritebio*zdt
843
844      ! Define indices of the horizontal output zoom and vertical limit storage      iimi = 1      ;      iima = jpi
845      ijmi = 1      ;      ijma = jpj
846      ipk = jpk
847
848      ! define time axis
849      it = kt - nit000 + 1
850
851! 1. Define NETCDF files and fields at beginning of first time step
852! -----------------------------------------------------------------
853
854      IF(ll_print)WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
855      IF(kt == nit000.and.kindic == 1) THEN
856
857! Define the NETCDF files for biological trends
858
859          CALL dia_nam(clhstnam,nwrite,'biolog')
860          IF(lwp)WRITE(numout,*)        &
861          &      " Name of NETCDF file for biological trends ",clhstnam
862! Horizontal grid : glamt and gphit
863          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,      &
864          &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
865          &    0, zjulian, rdt, nhoritb, nitb)
866! Vertical grid for biological trends
867          CALL histvert(nitb, 'deptht', 'Vertical T levels',  &
868          &    'm', ipk, gdept, ndepitb)
869
870! Declare all the output fields as NETCDF variables
871
872! biological trends
873
874          DO jn=1,jpdiabio
875            cltra=ctrbio(jn)    ! short title for biological diagnostic
876            cltral=ctrbil(jn)   ! long title for biological diagnostic
877            cltrau=ctrbiu(jn)   ! UNIT for biological diagnostic
878            CALL histdef(nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
879            &    ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
880          END DO
881
882! CLOSE netcdf Files
883
884          CALL histend(nitb)
885
886         IF(lwp) WRITE(numout,*)
887         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
888         IF(ll_print) CALL FLUSH(numout )
889
890! SOME diagnostics to DO first time
891
892#        if defined key_trc_npzd || defined key_trc_lobster1
893
894! initial total nitrogen
895
896          trai=0.
897          DO jn=1,jptra
898            DO jk=1,jpk
899              DO jj=1,jpj
900                DO ji=1,jpi
901                  trai=trai+trn(ji,jj,jk,jn)*fse3t(ji,jj,jk)*tmask(ji,jj,jk)
902                END DO
903              END DO
904            END DO
905          END DO
906
907          IF (lwp) then
908              WRITE (numout,*) ' *** total nitrogen =  ',trai,    &
909              &                ' at beginning of run it= ',kt
910          ENDIF
911
912          DO jk=1,jpk
913            DO jj=1,jpj
914              DO ji=1,jpi
915                zphy(ji,jj,jk)=trn(ji,jj,jk,jpphy)
916              END DO
917            END DO
918          END DO
919
920          IF (lwp) then
921              WRITE (numout,*) ' -------'
922              WRITE (numout,*) ' phyto'
923              WRITE (numout,*) ' -------'
924              CALL prizre(zphy,jpi,jpj,jpk,62,2,122,20,1,14,1,0.,numout)
925          ENDIF
926
927#        endif
928
929      ENDIF
930
931! 2. Start writing data
932! ---------------------
933
934! biological trends
935
936      IF( lwp .AND. MOD( kt, nwritebio ) == 0 ) THEN
937         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
938         WRITE(numout,*) '~~~~~~ '
939      ENDIF
940
941
942      DO jn=1,jpdiabio
943         cltra=ctrbio(jn)  ! short title for biological diagnostic
944         CALL histwrite(nitb, cltra, zt, trbio(:,:,:,jn), ndimt50,   &
945         &    ndext50)
946      END DO
947
948#     if defined key_trc_npzd || defined key_trc_lobster1
949
950      IF( MOD(kt-nit000+1,nwritebio) == 0) THEN
951
952! total nitrogen every nwritebio time step
953
954           ztra=0.
955           DO jn=1,jptra
956             DO jk=1,jpk
957               DO jj=1,jpj
958                 DO ji=1,jpi
959                   ztra=ztra+trn(ji,jj,jk,jn)*fse3t(ji,jj,jk)*tmask(ji,jj,jk)
960                 END DO
961               END DO
962             END DO
963           END DO
964
965           zder=(ztra-trai)/trai
966           trai=ztra
967
968           IF (lwp) THEN
969               WRITE (numout,*)
970               WRITE (numout,*) ' *** derive in total nitrogen =  ', zder,' %',' at it= ',kt
971               WRITE (numout,*) ' *** total nitrogen =  ',trai, ' at it= ',kt
972           ENDIF
973
974           zphy(:,:,:)=trn(:,:,:,jpphy)
975
976           IF (lwp) THEN
977               WRITE (numout,*)
978               WRITE (numout,*) ' *** trcdib: at it= ',kt
979               WRITE (numout,*) ' -------'
980               WRITE (numout,*) ' phyto'
981               WRITE (numout,*) ' -------'
982               CALL prizre(zphy,jpi,jpj,jpk,jpj-1,2,jpj-1,20,1,14,1,   &
983               &    0.,numout)
984           ENDIF
985
986       ENDIF
987
988#      endif
989
990! synchronise FILE
991
992      IF( MOD( kt, nwritebio ) == 0 .OR. kindic < 0 ) THEN
993              CALL histsync(nitb)
994      ENDIF
995
996! 3. Closing all files
997! --------------------
998      IF( kt == nitend .OR. kindic < 0 ) THEN
999          CALL histclo(nitb)
1000      ENDIF
1001
1002END SUBROUTINE trcdib_wr
1003
1004#    else
1005
1006SUBROUTINE trcdib_wr(kt,kindic)
1007     !!! no passive tracers
1008     INTEGER, INTENT ( in ) :: kt, kindic
1009     WRITE(*,*) 'trcdib_wr: You should not have seen this print! error?', kt, kindic
1010END SUBROUTINE trcdib_wr
1011
1012#    endif
1013
1014END MODULE trcdit
Note: See TracBrowser for help on using the repository browser.