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

Last change on this file since 6140 was 6140, checked in by timgraham, 8 years ago

Merge of branches/2015/dev_merge_2015 back into trunk. Merge excludes NEMOGCM/TOOLS/OBSTOOLS/ for now due to issues with the change of file type. Will sort these manually with further commits.

Branch merged as follows:
In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
Small conflicts due to bug fixes applied to trunk since the dev_merge_2015 was copied. Bug fixes were applied to the branch as well so these were easy to resolve.
Branch committed at this stage

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2015/dev_merge_2015
to merge the branch into the trunk and then commit - no conflicts at this stage.

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