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.
trcdia.F90 in branches/DEV_r2006_merge_TRA_TRC/NEMO/TOP_SRC – NEMO

source: branches/DEV_r2006_merge_TRA_TRC/NEMO/TOP_SRC/trcdia.F90 @ 2038

Last change on this file since 2038 was 2038, checked in by cetlod, 14 years ago

Apply the merge to passive tracers, see ticket:693

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 19.6 KB
Line 
1MODULE trcdia
2   !!======================================================================
3   !!                       *** MODULE trcdia ***
4   !! TOP :   Output of passive tracers
5   !!======================================================================
6   !! History :    -   !  1995-01 (M. Levy)  Original code
7   !!              -   !  1998-01 (C. Levy) NETCDF format using ioipsl interface
8   !!              -   !  1999-01 (M.A. Foujols) adapted for passive tracer
9   !!              -   !  1999-09 (M.A. Foujols) split into three parts
10   !!             1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
11   !!                  !  2008-05 (C. Ethe re-organization)
12   !!----------------------------------------------------------------------
13#if defined key_top && ! defined key_iomput
14   !!----------------------------------------------------------------------
15   !!   'key_top'                                                TOP models
16   !!----------------------------------------------------------------------
17   !! trc_dia     : main routine of output passive tracer
18   !! trcdit_wr   : outputs of concentration fields
19   !! trcdii_wr   : outputs of additional 2D/3D diagnostics
20   !! trcdib_wr   : outputs of biological fields
21   !!----------------------------------------------------------------------
22   USE dom_oce         ! ocean space and time domain variables
23   USE oce_trc
24   USE trc
25   USE par_trc
26   USE dianam    ! build name of file (routine)
27   USE in_out_manager  ! I/O manager
28   USE lib_mpp
29   USE ioipsl
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC trc_dia     
35
36   INTEGER  ::   nit5      !: id for tracer output file
37   INTEGER  ::   ndepit5   !: id for depth mesh
38   INTEGER  ::   nhorit5   !: id for horizontal mesh
39   INTEGER  ::   ndimt50   !: number of ocean points in index array
40   INTEGER  ::   ndimt51   !: number of ocean points in index array
41   REAL(wp) ::   zjulian   !: ????   not DOCTOR !
42   INTEGER , DIMENSION (jpij*jpk) ::   ndext50   !: integer arrays for ocean 3D index
43   INTEGER , DIMENSION (jpij)     ::   ndext51   !: integer arrays for ocean surface index
44# if defined key_diatrc
45   INTEGER  ::   nitd      !: id for additional array output file
46   INTEGER  ::   ndepitd   !: id for depth mesh
47   INTEGER  ::   nhoritd   !: id for horizontal mesh
48# endif
49# if defined key_diabio
50   INTEGER  ::   nitb        !:         id.         for additional array output file
51   INTEGER  ::   ndepitb   !:  id for depth mesh
52   INTEGER  ::   nhoritb   !:  id for horizontal mesh
53# endif
54
55   !! * Substitutions
56#  include "top_substitute.h90"
57   !!----------------------------------------------------------------------
58   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
59   !! $Id$
60   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
61   !!----------------------------------------------------------------------
62
63CONTAINS
64
65   SUBROUTINE trc_dia( kt ) 
66      !!---------------------------------------------------------------------
67      !!                     ***  ROUTINE trc_dia  ***
68      !!
69      !! ** Purpose :   output passive tracers fields
70      !!---------------------------------------------------------------------
71      INTEGER, INTENT( in ) :: kt
72      INTEGER               :: kindic
73      !!---------------------------------------------------------------------
74     
75      CALL trcdit_wr( kt, kindic )      ! outputs for tracer concentration
76      CALL trcdii_wr( kt, kindic )      ! outputs for additional arrays
77      CALL trcdib_wr( kt, kindic )      ! outputs for biological trends
78
79      !
80   END SUBROUTINE trc_dia
81
82   SUBROUTINE trcdit_wr( kt, kindic )
83      !!----------------------------------------------------------------------
84      !!                     ***  ROUTINE trcdit_wr  ***
85      !!
86      !! ** Purpose :   Standard output of passive tracer : concentration fields
87      !!
88      !! ** Method  :   At the beginning of the first time step (nit000), define all
89      !!             the NETCDF files and fields for concentration of passive tracer
90      !!
91      !!        At each time step call histdef to compute the mean if necessary
92      !!        Each nwritetrc time step, output the instantaneous or mean fields
93      !!
94      !!        IF kindic <0, output of fields before the model interruption.
95      !!        IF kindic =0, time step loop
96      !!        IF kindic >0, output of fields before the time step loop
97      !!----------------------------------------------------------------------
98      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
99      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
100      !!
101      INTEGER ::   jn
102      LOGICAL ::   ll_print = .FALSE.
103      CHARACTER (len=40) :: clhstnam, clop
104#if defined key_offline
105      INTEGER ::   inum = 11             ! temporary logical unit
106#endif
107      CHARACTER (len=20) :: cltra, cltrau
108      CHARACTER (len=80) :: cltral
109      REAL(wp) :: zsto, zout, zdt
110      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it, itmod
111      !!----------------------------------------------------------------------
112
113      ! Initialisation
114      ! --------------
115
116      ! local variable for debugging
117      ll_print = .FALSE.                  ! change it to true for more control print
118      ll_print = ll_print .AND. lwp
119
120      ! Define frequency of output and means
121      zdt = rdt
122      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
123      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
124      ENDIF
125# if defined key_diainstant
126      zsto = nn_writetrc * rdt
127      clop = "inst("//TRIM(clop)//")"
128# else
129      zsto = zdt
130      clop = "ave("//TRIM(clop)//")"
131# endif
132      zout = nn_writetrc * zdt
133
134      ! Define indices of the horizontal output zoom and vertical limit storage
135      iimi = 1      ;      iima = jpi
136      ijmi = 1      ;      ijma = jpj
137      ipk = jpk
138
139      ! define time axis
140      itmod = kt - nittrc000 + 1
141      it    = kt
142
143      ! Define NETCDF files and fields at beginning of first time step
144      ! --------------------------------------------------------------
145
146      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic
147     
148      IF( kt == nittrc000 ) THEN
149
150         ! Compute julian date from starting date of the run
151         CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )
152         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
153         IF(lwp)WRITE(numout,*)' ' 
154         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         &
155            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   &
156            &                 ,'Julian day : ', zjulian 
157 
158         IF(lwp) WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
159            &                    ' limit storage in depth = ', ipk
160
161#if defined key_offline
162        ! WRITE root name in date.file for use by postpro
163         IF(lwp) THEN
164            CALL dia_nam( clhstnam, nn_writetrc,' ' )
165            CALL ctlopn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, narea )
166            WRITE(inum,*) clhstnam
167            CLOSE(inum)
168         ENDIF
169#endif
170
171         ! Define the NETCDF files for passive tracer concentration
172         CALL dia_nam( clhstnam, nn_writetrc, 'ptrc_T' )
173         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
174
175         ! Horizontal grid : glamt and gphit
176         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,     &
177            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
178            &          nittrc000-ndttrc, zjulian, zdt, nhorit5, nit5 , domain_id=nidom)
179
180         ! Vertical grid for tracer : gdept
181         CALL histvert( nit5, 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepit5)
182
183         ! Index of ocean points in 3D and 2D (surface)
184         CALL wheneq( jpi*jpj*ipk, tmask, 1, 1., ndext50, ndimt50 )
185         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndext51, ndimt51 )
186
187         ! Declare all the output fields as NETCDF variables
188         DO jn = 1, jptra
189            IF( lutsav(jn) ) THEN
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            ENDIF
196         END DO
197
198         ! end netcdf files header
199         CALL histend( nit5 )
200         IF(lwp) WRITE(numout,*)
201         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdit_wr'
202         IF( ll_print )   CALL FLUSH(numout )
203
204      ENDIF
205
206      ! Start writing the tracer concentrations
207      ! ---------------------------------------
208
209      IF( lwp .AND. MOD( itmod, nn_writetrc ) == 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         IF( lutsav(jn) ) CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 )
217      END DO
218
219      ! close the file
220      ! --------------
221      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nit5 )
222      !
223
224   END SUBROUTINE trcdit_wr
225
226#if defined key_diatrc
227
228   SUBROUTINE trcdii_wr( kt, kindic )
229      !!----------------------------------------------------------------------
230      !!                     ***  ROUTINE trcdii_wr  ***
231      !!
232      !! ** Purpose :   output of passive tracer : additional 2D and 3D arrays
233      !!
234      !! ** Method  :   At the beginning of the first time step (nit000), define all
235      !!             the NETCDF files and fields for concentration of passive tracer
236      !!
237      !!        At each time step call histdef to compute the mean if necessary
238      !!        Each nwritedia time step, output the instantaneous or mean fields
239      !!
240      !!        IF kindic <0, output of fields before the model interruption.
241      !!        IF kindic =0, time step loop
242      !!        IF kindic >0, output of fields before the time step loop
243      !!----------------------------------------------------------------------
244      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
245      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
246      !!
247      LOGICAL ::   ll_print = .FALSE.
248      CHARACTER (len=40) ::   clhstnam, clop
249      CHARACTER (len=20) ::   cltra, cltrau
250      CHARACTER (len=80) ::   cltral
251      INTEGER  ::   jl
252      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod
253      REAL(wp) ::   zsto, zout, zdt
254      !!----------------------------------------------------------------------
255
256      ! Initialisation
257      ! --------------
258     
259      ! local variable for debugging
260      ll_print = .FALSE.
261      ll_print = ll_print .AND. lwp
262      !
263      ! Define frequency of output and means
264      zdt = rdt
265      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
266      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
267      ENDIF
268#  if defined key_diainstant
269      zsto = nn_writedia * zdt
270      clop = "inst("//TRIM(clop)//")"
271#  else
272      zsto = zdt
273      clop = "ave("//TRIM(clop)//")"
274#  endif
275      zout = nn_writedia * zdt
276
277      ! Define indices of the horizontal output zoom and vertical limit storage
278      iimi = 1      ;      iima = jpi
279      ijmi = 1      ;      ijma = jpj
280      ipk = jpk
281
282      ! define time axis
283      itmod = kt - nittrc000 + 1
284      it    = kt
285
286      ! 1. Define NETCDF files and fields at beginning of first time step
287      ! -----------------------------------------------------------------
288
289      IF( ll_print ) WRITE(numout,*) 'trcdii_wr kt=', kt, ' kindic ', kindic
290
291      IF( kt == nittrc000 ) THEN
292
293         ! Define the NETCDF files for additional arrays : 2D or 3D
294
295         ! Define the T grid file for tracer auxiliary files
296
297         CALL dia_nam( clhstnam, nn_writedia, 'diad_T' )
298         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam
299
300         ! Define a netcdf FILE for 2d and 3d arrays
301
302         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,             &
303            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         &
304            &          nittrc000-ndttrc, zjulian, zdt, nhoritd, nitd , domain_id=nidom )
305
306         ! Vertical grid for 2d and 3d arrays
307
308         CALL histvert( nitd, 'deptht', 'Vertical T levels','m', ipk, gdept_0, ndepitd)
309
310         ! Declare all the output fields as NETCDF variables
311
312         ! more 3D horizontal arrays
313         DO jl = 1, jpdia3d
314            cltra  = ctrc3d(jl)   ! short title for 3D diagnostic
315            cltral = ctrc3l(jl)   ! long title for 3D diagnostic
316            cltrau = ctrc3u(jl)   ! UNIT for 3D diagnostic
317            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,   &
318               &          ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout )
319         END DO
320
321         ! more 2D horizontal arrays
322         DO jl = 1, jpdia2d
323            cltra  = ctrc2d(jl)    ! short title for 2D diagnostic
324            cltral = ctrc2l(jl)   ! long title for 2D diagnostic
325            cltrau = ctrc2u(jl)   ! UNIT for 2D diagnostic
326            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
327               &          1, 1, 1,  -99, 32, clop, zsto, zout )
328         END DO
329
330         ! TODO: more 2D vertical sections arrays : I or J indice fixed
331
332         ! CLOSE netcdf Files
333         CALL histend( nitd )
334
335         IF(lwp) WRITE(numout,*)
336         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdii_wr'
337         IF( ll_print )   CALL FLUSH(numout )
338         !
339      ENDIF
340
341      ! 2. Start writing data
342      ! ---------------------
343
344      IF( lwp .AND. MOD( itmod, nn_writedia ) == 0 ) THEN
345         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step'
346         WRITE(numout,*) '~~~~~~ '
347      ENDIF
348
349      ! more 3D horizontal arrays
350      DO jl = 1, jpdia3d
351         cltra = ctrc3d(jl)   ! short title for 3D diagnostic
352         CALL histwrite( nitd, cltra, it, trc3d(:,:,:,jl), ndimt50 ,ndext50)
353      END DO
354
355      ! more 2D horizontal arrays
356      DO jl = 1, jpdia2d
357         cltra = ctrc2d(jl)   ! short title for 2D diagnostic
358         CALL histwrite(nitd, cltra, it, trc2d(:,:,jl), ndimt51  ,ndext51)
359      END DO
360
361      ! Closing all files
362      ! -----------------
363      IF( kt == nitend .OR. kindic < 0 )   CALL histclo(nitd)
364      !
365
366   END SUBROUTINE trcdii_wr
367
368# else
369
370   SUBROUTINE trcdii_wr( kt, kindic )                      ! Dummy routine
371      INTEGER, INTENT ( in ) :: kt, kindic
372   END SUBROUTINE trcdii_wr
373
374# endif
375
376# if defined key_diabio
377
378   SUBROUTINE trcdib_wr( kt, kindic )
379      !!----------------------------------------------------------------------
380      !!                     ***  ROUTINE trcdib_wr  ***
381      !!
382      !! ** Purpose :   output of passive tracer : biological fields
383      !!
384      !! ** Method  :   At the beginning of the first time step (nit000), define all
385      !!             the NETCDF files and fields for concentration of passive tracer
386      !!
387      !!        At each time step call histdef to compute the mean if necessary
388      !!        Each nwritebio time step, output the instantaneous or mean fields
389      !!
390      !!        IF kindic <0, output of fields before the model interruption.
391      !!        IF kindic =0, time step loop
392      !!        IF kindic >0, output of fields before the time step loop
393      !!----------------------------------------------------------------------
394      !!
395      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
396      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
397      !!
398      LOGICAL ::   ll_print = .FALSE.
399      CHARACTER (len=40) ::   clhstnam, clop
400      CHARACTER (len=20) ::   cltra, cltrau
401      CHARACTER (len=80) ::   cltral
402      INTEGER  ::   ji, jj, jk, jl
403      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod
404      REAL(wp) ::   zsto, zout, zdt
405      !!----------------------------------------------------------------------
406
407      ! Initialisation
408      ! --------------
409
410     
411      ! local variable for debugging
412      ll_print = .FALSE.
413      ll_print = ll_print .AND. lwp
414
415      ! Define frequency of output and means
416      zdt = rdt
417      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
418      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
419      ENDIF
420#        if defined key_diainstant
421      zsto = nn_writebio * zdt
422      clop = "inst("//TRIM(clop)//")"
423#        else
424      zsto = zdt
425      clop = "ave("//TRIM(clop)//")"
426#        endif
427      zout = nn_writebio * zdt
428
429      ! Define indices of the horizontal output zoom and vertical limit storage
430      iimi = 1      ;      iima = jpi
431      ijmi = 1      ;      ijma = jpj
432      ipk = jpk
433
434      ! define time axis
435      itmod = kt - nittrc000 + 1
436      it    = kt
437
438      ! Define NETCDF files and fields at beginning of first time step
439      ! --------------------------------------------------------------
440
441      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
442
443      IF( kt == nittrc000 ) THEN
444
445         ! Define the NETCDF files for biological trends
446
447         CALL dia_nam(clhstnam,nn_writebio,'biolog')
448         IF(lwp)WRITE(numout,*) " Name of NETCDF file for biological trends ", clhstnam
449         ! Horizontal grid : glamt and gphit
450         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,      &
451            &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
452            &    nittrc000-ndttrc, zjulian, zdt, nhoritb, nitb , domain_id=nidom )
453         ! Vertical grid for biological trends
454         CALL histvert(nitb, 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepitb)
455
456         ! Declare all the output fields as NETCDF variables
457         ! biological trends
458         DO jl = 1, jpdiabio
459            cltra  = ctrbio(jl)   ! short title for biological diagnostic
460            cltral = ctrbil(jl)   ! long title for biological diagnostic
461            cltrau = ctrbiu(jl)   ! UNIT for biological diagnostic
462            CALL histdef( nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
463               &         ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
464         END DO
465
466         ! CLOSE netcdf Files
467          CALL histend( nitb )
468
469         IF(lwp) WRITE(numout,*)
470         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
471         IF(ll_print) CALL FLUSH(numout )
472         !
473      ENDIF
474
475      ! Start writing data
476      ! ------------------
477
478      ! biological trends
479      IF( lwp .AND. MOD( itmod, nn_writebio ) == 0 ) THEN
480         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
481         WRITE(numout,*) '~~~~~~ '
482      ENDIF
483
484      DO jl = 1, jpdiabio
485         cltra = ctrbio(jl)  ! short title for biological diagnostic
486         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jl), ndimt50,ndext50)
487      END DO
488
489      ! Closing all files
490      ! -----------------
491      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nitb )
492      !
493
494   END SUBROUTINE trcdib_wr
495
496# else
497
498   SUBROUTINE trcdib_wr( kt, kindic )                      ! Dummy routine
499      INTEGER, INTENT ( in ) ::   kt, kindic
500   END SUBROUTINE trcdib_wr
501
502# endif 
503
504#else
505   !!----------------------------------------------------------------------
506   !!  Dummy module :                                     No passive tracer
507   !!----------------------------------------------------------------------
508CONTAINS
509   SUBROUTINE trc_dia( kt )                      ! Empty routine   
510      INTEGER, INTENT(in) :: kt
511   END SUBROUTINE trc_dia   
512
513#endif
514
515   !!======================================================================
516END MODULE trcdia
Note: See TracBrowser for help on using the repository browser.