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.
trcdib.F in trunk/NEMO/TOP_SRC/SMS – NEMO

source: trunk/NEMO/TOP_SRC/SMS/trcdib.F @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.4 KB
Line 
1
2CCC $Header$ 
3CCC  TOP 1.0 , LOCEAN-IPSL (2005) 
4C This software is governed by CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
5C ---------------------------------------------------------------------------
6CC $Header$
7CDIR$ LIST
8      SUBROUTINE trcdib(kt,kindic)
9CCC---------------------------------------------------------------------
10CCC
11CCC                       ROUTINE trcdib
12CCC                     ******************
13CCC
14CCC  Purpose :
15CCC  ---------
16CCC     Specific output of opa: biological fields
17CCC
18CCC     If "key_mpp" or "key_fdir, direct access FORMAT
19CCC
20CCC
21CC   Method :
22CC   -------
23CC
24CC At the beginning of the first time step (nit000), define all
25CC the NETCDF files and fields for passive tracer
26CC
27CC      At each time step call histdef to compute the mean if necessary
28CC Each nwrite time step, output the instantaneous or mean fields
29CC
30CC IF kindic <0, output of fields before the model interruption.
31CC      IF kindic =0, time step loop
32CC      IF kindic >0, output of fields before the time step loop
33CC
34CC
35CC
36CC   Input :
37CC   -----
38CC      argument
39CC              kt              : time step
40CC    kindic      : indicator of abnormal termination
41CC      COMMON
42CC            /comcoh/          : orthogonal curvilinear coordinates
43CC                                and scale factors
44CC            /comask/          : masks, bathymetry
45CC            /cottrc/          : passive tracers fields (before,now
46CC                                  ,after)
47CC            /cimcdf/     : NETCDF variables
48CC
49CC   Output :
50CC   ------
51CC      file
52CC              "histname" files: at least one file for each grid
53CC
54CC
55CC   Workspace :
56CC   ---------
57CC      local
58CC              zphy ()         : 3D aray for printing
59CC              ztra            : total nitrogen
60CC              zder            : derive in nitrogen
61CC
62CC
63CC   EXTERNAL :
64CC   --------
65CC prihre, hist..., dianam
66CC
67CC   MODIFICATIONS:
68CC   --------------
69CC      original  : 95-01  passive tracers  (M. Levy)
70CC      additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
71CC      additions : 99-01 (M.A. Foujols) adapted for passive tracer
72CC      additions : 00-12 (E Kestenare) assign a parameter to name
73CC                                      individual tracers
74CC----------------------------------------------------------------------
75CC parameters and commons
76CC ======================
77      USE ioipsl
78      USE oce_trc
79      USE trp_trc
80      USE in_out_manager
81      USE trc
82      USE sms
83      USE dianam
84      IMPLICIT NONE
85CC----------------------------------------------------------------------
86CC local declarations
87CC ==================
88      INTEGER kt, kindic
89
90#    if defined key_passivetrc && key_trc_diabio
91
92      INTEGER ji, jj, jk, jn, jl
93      LOGICAL clp
94C
95      CHARACTER*40 clhstnam
96      CHARACTER*40 clop
97      CHARACTER*20 cltra, cltrau
98      CHARACTER*80 cltral
99
100      REAL zsto,zout
101      INTEGER iimi, iima, ijmi, ijma, ipk
102      REAL zsec
103
104      REAL ztra,zder,zphy(jpi,jpj,jpk)
105C
106CC----------------------------------------------------------------------
107CC statement functions
108CC ===================
109CDIR$ NOLIST
110#include "domzgr_substitute.h90"
111CDIR$ LIST
112CCC---------------------------------------------------------------------
113CCC  OPA8, LODYC (15/11/96)
114CCC---------------------------------------------------------------------
115C
116C 0. Initialisation
117C -----------------
118C
119C local variable for debugging
120      clp=.false.
121      clp=clp.and.lwp
122C
123C Define frequency of output and means
124C
125#        if defined key_diainstant
126      zsto=nwritebio*rdt
127      clop='inst(only(x))'
128#        else
129      zsto=rdt
130      clop='ave(only(x))'
131#        endif
132      zout=nwritebio*rdt
133C
134C Define indexes of the horizontal output zoom
135      iimi=1
136      iima=jpi
137      ijmi=1
138      ijma=jpj
139c ipk limit storage in depth
140      ipk = jpk
141C
142C
143C 1. Define NETCDF files and fields at beginning of first time step
144C -----------------------------------------------------------------
145C
146      IF(clp)WRITE(numout,*)'trcdib kt=',kt,' kindic ',kindic
147      IF (kt.eq.nit000.and.kindic.eq.1) THEN
148C
149C Define the NETCDF files for biological trends
150C
151          CALL dia_nam(clhstnam,nwrite,'biolog')
152          IF(lwp)WRITE(numout,*)
153     $        " Name of NETCDF file for biological trends ",clhstnam
154C Horizontal grid : glamt and gphit
155          WRITE(numout,*)" indexes of zoom = ",
156     $      iimi, iima, ijmi, ijma
157          WRITE(numout,*)" limit storage in depth = ", ipk
158C
159          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,
160     $        iimi, iima-iimi+1, ijmi, ijma-ijmi+1,
161     $        nit000-1, djulian, rdt, nhoritb, nitb)
162C Vertical grid for biological trends
163          CALL histvert(nitb, 'deptht', 'Vertical T levels',
164     $        'm', ipk, gdept, ndepitb)
165C
166C Declare all the output fields as NETCDF variables
167C
168C 
169C biological trends
170C
171          DO jn=1,jpdiabio
172            cltra=ctrbio(jn)    ! short title for biological diagnostic
173            cltral=ctrbil(jn)   ! long title for biological diagnostic
174            cltrau=ctrbiu(jn)   ! UNIT for biological diagnostic
175            CALL histdef(nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,
176     $          ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
177          END DO
178C
179C CLOSE netcdf Files
180C         
181          CALL histend(nitb)
182C
183C SOME diagnostics to DO first time
184C
185
186#        if defined key_trc_npzd || defined key_trc_lobster1
187C
188C initial total nitrogen
189C
190          trai=0.
191          DO jn=1,jptra
192            DO jk=1,jpk
193              DO jj=1,jpj
194                DO ji=1,jpi
195                  trai=trai+trn(ji,jj,jk,jn)*fse3t(ji,jj,jk)*tmask(ji,jj
196     $                ,jk) 
197                END DO
198              END DO
199            END DO
200          END DO
201
202          IF (lwp) then
203              WRITE (numout,*) ' *** total nitrogen =  ',trai,
204     $            ' at beginning of run it= ',kt
205          ENDIF
206C
207          DO jk=1,jpk
208            DO jj=1,jpj
209              DO ji=1,jpi
210                zphy(ji,jj,jk)=trn(ji,jj,jk,jpphy)
211              END DO
212            END DO
213          END DO
214C
215          IF (lwp) then
216              WRITE (numout,*) ' -------'
217              WRITE (numout,*) ' phyto'
218              WRITE (numout,*) ' -------'
219              CALL prizre(zphy,jpi,jpj,jpk,62,2,122,20,1,14,1,0.,numout)
220          ENDIF 
221#        endif
222
223      ELSE
224C
225C
226C 2. Start writing data
227C ---------------------
228C
229C biological trends
230C
231          DO jn=1,jpdiabio
232            cltra=ctrbio(jn)  ! short title for biological diagnostic
233            CALL histwrite(nitb, cltra, kt, trbio(:,:,:,jn), ndimt50,
234     $          ndext50) 
235          END DO 
236#        if defined key_trc_npzd || defined key_trc_lobster1
237
238          IF(mod(kt-nit000+1,nwritebio).eq.0) THEN
239C
240C total nitrogen every nwritebio time step
241C
242              ztra=0.
243              DO jn=1,jptra
244                DO jk=1,jpk
245                  DO jj=1,jpj
246                    DO ji=1,jpi
247                      ztra=ztra+trn(ji,jj,jk,jn)*fse3t(ji,jj,jk)
248     $                    *tmask(ji,jj,jk) 
249                    END DO
250                  END DO
251                END DO
252              END DO
253C
254              zder=(ztra-trai)/trai
255              trai=ztra
256              IF (lwp) THEN
257                  WRITE (numout,*)
258                  WRITE (numout,*) ' *** derive in total nitrogen =  ',
259     $                zder,' %',' at it= ',kt
260                  WRITE (numout,*) ' *** total nitrogen =  ',trai,
261     $                ' at it= ',kt
262              ENDIF
263             
264C
265              DO jk=1,jpk
266                DO jj=1,jpj
267                  DO ji=1,jpi
268                    zphy(ji,jj,jk)=trn(ji,jj,jk,jpphy)
269                  END DO
270                END DO
271              END DO
272C
273              IF(lwp) THEN
274                  WRITE (numout,*)
275                  WRITE (numout,*) ' *** trcdib: at it= ',kt
276                  WRITE (numout,*) ' -------'
277                  WRITE (numout,*) ' phyto'
278                  WRITE (numout,*) ' -------'
279                  CALL prizre(zphy,jpi,jpj,jpk,jpj-1,2,jpj-1,20,1,14,1,
280     $                0.,numout) 
281              ENDIF
282
283          ENDIF 
284
285#        endif
286C
287C synchronise FILE
288C
289          IF(lwp .and. mod( kt, nwritebio ).EQ.0) THEN
290             WRITE(numout,*) '**** trcdib : write NetCDF fields'
291             CALL histsync(nitb)
292         ENDIF
293
294      ENDIF
295C
296C 3. Closing all files
297C --------------------
298      IF (kt.EQ.nitend.OR.kindic.LT.0) THEN
299          CALL histclo(nitb)
300      ENDIF
301
302#    else
303C
304C no passive tracers
305C
306#    endif
307
308C
309C 
310      RETURN
311      END
Note: See TracBrowser for help on using the repository browser.