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 trunk/NEMOGCM/NEMO/TOP_SRC – NEMO

source: trunk/NEMOGCM/NEMO/TOP_SRC/trcdia.F90 @ 2567

Last change on this file since 2567 was 2567, checked in by cetlod, 13 years ago

rename nwritedia to nn_writedia, see ticket #791

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