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

source: branches/CMIP5_IPSL/NEMO/TOP_SRC/trcwri.F90 @ 1873

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

Update PISCES diagnostics for AR5

File size: 8.1 KB
Line 
1MODULE trcwri
2   !!===================================================================================
3   !!                       *** MODULE trcwri ***
4   !!    TOP :   Output of passive tracers
5   !!====================================================================================
6   !! History :   1.0  !  2009-05 (C. Ethe)  Original code
7   !!                  !  2010-03 (C. Ethe, R. Seferian ) Add the tracer transport trends
8   !!----------------------------------------------------------------------
9#if defined key_top &&  defined key_iomput
10   !!----------------------------------------------------------------------
11   !!   'key_top' && 'key_iomput'                              TOP models
12   !!----------------------------------------------------------------------
13   !! trc_wri_trc   :  outputs of concentration fields
14   !! trc_wri_trd   :  outputs of transport trends
15   !!----------------------------------------------------------------------
16   USE dom_oce         ! ocean space and time domain variables
17   USE oce_trc
18   USE trp_trc
19   USE trc
20   USE trdmld_trc_oce, ONLY : luttrd
21   USE iom
22#if defined key_off_tra
23   USE oce_trc
24   USE dianam
25#endif
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC trc_wri     
31
32   !! * Substitutions
33#  include "top_substitute.h90"
34   !!----------------------------------------------------------------------
35   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
36   !! $Id: trcdia.F90 1450 2009-05-15 14:12:12Z cetlod $
37   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39
40CONTAINS
41
42   SUBROUTINE trc_wri( kt )
43      !!---------------------------------------------------------------------
44      !!                     ***  ROUTINE trc_wri  ***
45      !!
46      !! ** Purpose :   output passive tracers fields and dynamical trends
47      !!---------------------------------------------------------------------
48      INTEGER, INTENT( in ) :: kt
49      !!---------------------------------------------------------------------
50
51      !
52      CALL iom_setkt  ( kt + ndttrc - 1 )       ! set the passive tracer time step
53      CALL trc_wri_trc( kt              )       ! outputs for tracer concentration
54      CALL trc_wri_trd( kt              )       ! outputs for dynamical trends
55      CALL iom_setkt  ( kt              )       ! set the model time step
56      !
57   END SUBROUTINE trc_wri
58
59   SUBROUTINE trc_wri_trc( kt ) 
60      !!---------------------------------------------------------------------
61      !!                     ***  ROUTINE trc_wri_trc  ***
62      !!
63      !! ** Purpose :   output passive tracers fields
64      !!---------------------------------------------------------------------
65      INTEGER, INTENT( in ) :: kt       ! ocean time-step
66      INTEGER               :: jn
67      CHARACTER (len=20)    :: cltra
68#if defined key_off_tra
69      CHARACTER (len=72) :: clhstnam
70      INTEGER ::   inum = 11            ! temporary logical unit
71#endif
72#if defined key_diaar5  && defined key_pisces
73      INTEGER                      :: ji, jj, jk  ! dummy loop indices
74      REAL(wp), DIMENSION(jpi,jpj) :: zdic        ! DIC content
75      REAL(wp), DIMENSION(jpi,jpj) :: zo2min      ! O2 minimum concentration
76      REAL(wp), DIMENSION(jpi,jpj) :: zdepo2min   ! Depth of O2 minimum concentration
77#endif
78      !!---------------------------------------------------------------------
79 
80#if defined key_off_tra
81      IF( kt == nittrc000 ) THEN
82        ! WRITE root name in date.file for use by postpro
83         IF(lwp) THEN
84            CALL dia_nam( clhstnam, nwritetrc,' ' )
85            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
86            WRITE(inum,*) clhstnam
87            CLOSE(inum)
88         ENDIF
89      ENDIF
90#endif
91      ! write the tracer concentrations in the file
92      ! ---------------------------------------
93      DO jn = 1, jptra
94         cltra = ctrcnm(jn)                   ! short title for tracer
95         CALL iom_put( cltra, trn(:,:,:,jn) )
96      END DO
97#if defined key_diaar5  && defined key_pisces
98      ! DIC content in kg/m2
99      zdic(:,:) = 0.
100      DO jk = 1, jpkm1
101         zdic(:,:) = zdic(:,:) + trn(:,:,jk,jpdic) * fse3t(:,:,jk) * tmask(:,:,jk) * 12. 
102      ENDDO
103      ! Oxygen minimum concentration and depth
104      zo2min   (:,:) = trn(:,:,1,jpoxy) * tmask(:,:,1)
105      zdepo2min(:,:) = fsdepw(:,:,1)    * tmask(:,:,1)
106      DO jk = 2, jpkm1
107         DO jj = 1, jpj               
108            DO ji = 1, jpi 
109               IF( tmask(ji,jj,jk) == 1 ) then
110                  IF( trn(ji,jj,jk,jpoxy) < zo2min(ji,jj) ) then
111                     zo2min   (ji,jj) = trn(ji,jj,jk,jpoxy) 
112                     zdepo2min(ji,jj) = fsdepw(ji,jj,jk)
113                  ENDIF
114               ENDIF
115            END DO
116         END DO
117      END DO
118      !
119      CALL iom_put('INTDIC', zdic       )                              ! DIC content
120      CALL iom_put('O2MIN' , zo2min     )                              ! oxygen minimum concentration
121      CALL iom_put('ZO2MIN', zdepo2min  )                              ! depth of oxygen minimum concentration
122      CALL iom_put('PHYT'  , trn(:,:,:,jpphy) + trn(:,:,:,jpdia) )     ! total phytoplankton
123      CALL iom_put('ZOOT'  , trn(:,:,:,jpzoo) + trn(:,:,:,jpmes) )     ! total zooplankton
124      CALL iom_put('CHLT'  , trn(:,:,:,jpnch) + trn(:,:,:,jpdch) )     ! total chlorophyll
125      CALL iom_put('POCT'  , trn(:,:,:,jppoc) + trn(:,:,:,jpgoc) )     ! total carbon particles
126      CALL iom_put('PFET'  , trn(:,:,:,jpnfe) + trn(:,:,:,jpdfe) )     ! total biogenic iron
127#endif
128      !
129   END SUBROUTINE trc_wri_trc
130
131# if defined key_trc_diatrd
132
133   SUBROUTINE trc_wri_trd( kt )
134      !!----------------------------------------------------------------------
135      !!                     ***  ROUTINE trc_wri_trd  ***
136      !!
137      !! ** Purpose :   output of passive tracer : advection-diffusion trends
138      !!
139      !!----------------------------------------------------------------------
140      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
141      !!
142      CHARACTER (len=3) ::   cltra
143      INTEGER  ::   jn, jl, ikn
144      !!----------------------------------------------------------------------
145
146      DO jn = 1, jptra
147         IF( luttrd(jn) ) THEN
148            ikn = ikeep(jn)
149            DO jl = 1, jpdiatrc
150               IF( jl == jptrc_xad ) WRITE (cltra,"(3a)") 'XAD' ! x advection for tracer
151               IF( jl == jptrc_yad ) WRITE (cltra,"(3a)") 'YAD'  ! y advection for tracer
152               IF( jl == jptrc_zad ) WRITE (cltra,"(3a)") 'ZAD'  ! z advection for tracer
153               IF( jl == jptrc_xdf ) WRITE (cltra,"(3a)") 'XDF'  ! x diffusion for tracer
154               IF( jl == jptrc_ydf ) WRITE (cltra,"(3a)") 'YDF'  ! y diffusion for tracer
155               IF( jl == jptrc_zdf ) WRITE (cltra,"(3a)") 'ZDF'  ! z diffusion for tracer
156# if defined key_trcldf_eiv
157               IF( jl == jptrc_xei ) WRITE (cltra,"(3a)") 'XGV'  ! x gent velocity for tracer
158               IF( jl == jptrc_yei ) WRITE (cltra,"(3a)") 'YGV'  ! y gent velocity for tracer
159               IF( jl == jptrc_zei ) WRITE (cltra,"(3a)") 'ZGV'  ! z gent velocity for tracer
160# endif
161# if defined key_trcdmp
162               IF( jl == jptrc_dmp ) WRITE (cltra,"(3a)") 'DMP'  ! damping
163# endif
164               IF( jl == jptrc_sbc ) WRITE (cltra,"(3a)") 'SBC'  ! surface boundary conditions
165               ! write the trends
166               CALL iom_put( cltra, trtrd(:,:,:,ikn,jl) )
167            END DO
168         END IF
169      END DO
170      !
171   END SUBROUTINE trc_wri_trd
172
173# else
174   SUBROUTINE trc_wri_trd( kt )                      ! Dummy routine
175      INTEGER, INTENT ( in ) ::   kt
176   END SUBROUTINE trc_wri_trd
177#endif
178#else
179   !!----------------------------------------------------------------------
180   !!  Dummy module :                                     No passive tracer
181   !!----------------------------------------------------------------------
182   PUBLIC trc_wri
183CONTAINS
184   SUBROUTINE trc_wri( kt )                     ! Empty routine   
185   INTEGER, INTENT(in) :: kt
186   END SUBROUTINE trc_wri
187#endif
188
189   !!======================================================================
190END MODULE trcwri
Note: See TracBrowser for help on using the repository browser.