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

source: branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC/trcdia.F90 @ 2833

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

Improvment of branch dev_r2787_LOCEAN3_TRA_TRP

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