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

Last change on this file since 376 was 352, checked in by opalod, 18 years ago

nemo_v1_update_033 : CT : Switch to IOIPSL-3-0 new library

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