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 @ 331

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

nemo_v1_update_005:RB: update headers for the TOP component.

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