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.
trcini.pisces.h90 in tags/nemo_v1_04/NEMO/TOP_SRC/SMS – NEMO

source: tags/nemo_v1_04/NEMO/TOP_SRC/SMS/trcini.pisces.h90 @ 280

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

nemo_v1_update_005:RB: update headers for the TOP component.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.1 KB
Line 
1!!-----------------------------------------------------------------
2!!
3!!                     ROUTINE trcini.pisces.h90
4!!                     ************************
5!!
6!!  PURPOSE :
7!!  ---------
8!!     Initialisation of PISCES biological and chemical variables
9!!
10!!   INPUT :
11!!   -----
12!!      common
13!!              all the common defined in opa
14!!
15!!
16!!   OUTPUT :                   : no
17!!   ------
18!!
19!!   EXTERNAL :
20!!   ----------
21!!         p4zche
22!!
23!!   MODIFICATIONS:
24!!   --------------
25!!      original  : 1988-07  E. MAIER-REIMER      MPI HAMBURG
26!!      additions : 1999-10  O. Aumont and C. Le Quere
27!!      additions : 2002     O. Aumont (PISCES)
28!!     03-2005 O. Aumont and A. El Moussaoui F90
29!!---------------------------------------------------------------------
30!!  TOP 1.0,  LOCEAN-IPSL (2005)
31!! $Header$
32!! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
33!!----------------------------------------------------------------------
34!! local declarations
35!! ==================
36      INTEGER :: ichl,iband,mo
37      INTEGER , PARAMETER :: jpmois = 12,      &
38                             jpan   = 1
39
40      REAL(wp) :: xtoto,expide,denitide,ztra
41      REAL(wp) , DIMENSION (jpi,jpj) :: riverdoc,river,ndepo
42      CHARACTER (len=34) :: clname
43
44      INTEGER :: ipi,ipj,ipk,itime
45      INTEGER , DIMENSION (jpmois) :: istep
46      INTEGER , DIMENSION (jpan) :: istep0
47      REAL(wp) :: zsecond, zdate0
48      REAL(wp) , DIMENSION (jpi,jpj) :: zlon,zlat
49      REAL(wp), DIMENSION (jpk) :: zlev
50      INTEGER :: numriv,numdust,numbath,numdep
51
52!! 1. initialization
53!! -----------------
54
55!! computation of the record length for direct access FILE
56!! this length depend of 512 for the t3d machine
57!!
58      rfact = rdttra(1) * float(ndttrc)
59      rfactr = 1./rfact
60      IF(lwp) WRITE(numout,*) ' Tracer time step=',rfact,' rdt=',rdt
61      rfact2= rfact / float(nrdttrc)
62      rfact2r = 1./rfact2
63      IF(lwp) write(numout,*) ' Biology time step=',rfact2
64
65!!    INITIALISE DUST INPUT FROM ATMOSPHERE
66!!    -------------------------------------
67
68       IF (bdustfer) THEN
69         clname='dust.orca.nc'
70       CALL flinopen(clname,mig(1),nlci,mjg(1),nlcj,.false.,ipi,ipj,0        &
71     &      ,zlon,zlat,zlev,itime,istep,zdate0,zsecond,numdust)
72       CALL flinget(numdust,'dust',jpidta,jpjdta,0,jpmois,1,                 &
73     &        12,mig(1),nlci,mjg(1),nlcj,dustmo(1:nlci,1:nlcj,:) )
74       CALL flinclo(numdust)
75
76        ! Extra-halo initialization in MPP
77         IF( lk_mpp ) THEN
78            DO ji = nlci+1, jpi
79               dustmo(ji,:,:) = dustmo(1,:,:)
80            ENDDO
81            DO jj = nlcj+1, jpj
82               dustmo(:,jj,:)=dustmo(:,1,:)
83            ENDDO
84         ENDIF
85       ELSE
86       dustmo(:,:,:)=0.
87       ENDIF
88
89!!    INITIALISE THE NUTRIENT INPUT BY RIVERS
90!!    ---------------------------------------
91
92       IF (briver) THEN
93        clname='river.orca.nc'
94       CALL flinopen(clname,mig(1),nlci,mjg(1),nlcj,.false.,ipi,ipj,0        &
95      &      ,zlon,zlat,zlev,itime,istep0,zdate0,zsecond,numriv)
96       CALL flinget(numriv,'riverdic',jpidta,jpjdta,0,jpan,1,                &
97      &        1,mig(1),nlci,mjg(1),nlcj,river(1:nlci,1:nlcj) )
98       CALL flinget(numriv,'riverdoc',jpidta,jpjdta,0,jpan,1,                &
99      &        1,mig(1),nlci,mjg(1),nlcj,riverdoc(1:nlci,1:nlcj) )
100       CALL flinclo(numriv)
101
102        ! Extra-halo initialization in MPP
103         IF( lk_mpp ) THEN
104            DO ji = nlci+1, jpi
105               river(ji,:) = river(1,:)
106               riverdoc(ji,:) = riverdoc(1,:)
107            ENDDO
108            DO jj = nlcj+1, jpj
109               river(:,jj)=river(:,1)
110               riverdoc(:,jj) = riverdoc(:,1)
111            ENDDO
112         ENDIF
113
114       ELSE
115       river(:,:)=0.
116       riverdoc(:,:)=0.
117       endif
118
119!!    INITIALISE THE N INPUT BY DUST
120!!  ---------------------------------------
121
122       IF (bndepo) THEN
123        clname='ndeposition.orca.nc'
124       CALL flinopen(clname,mig(1),nlci,mjg(1),nlcj,.false.,ipi,ipj,0        &
125     &      ,zlon,zlat,zlev,itime,istep0,zdate0,zsecond,numdep)
126       CALL flinget(numdep,'ndep',jpidta,jpjdta,0,jpan,1,                   &
127     &        1,mig(1),nlci,mjg(1),nlcj,ndepo(1:nlci,1:nlcj) )
128       CALL flinclo(numdep)
129
130        ! Extra-halo initialization in MPP
131         IF( lk_mpp ) THEN
132            DO ji = nlci+1, jpi
133               ndepo(ji,:) = ndepo(1,:)
134            ENDDO
135            DO jj = nlcj+1, jpj
136               ndepo(:,jj)=ndepo(:,1)
137            ENDDO
138         ENDIF
139
140       ELSE
141       ndepo(:,:)=0.
142       ENDIF
143
144!!    Computation of the coastal mask.
145!!    Computation of an island mask to enhance coastal supply
146!!    of iron
147!!    -------------------------------------------------------
148
149       IF (bsedinput) THEN
150        clname='bathy.orca.nc'
151       CALL flinopen(clname,mig(1),nlci,mjg(1),nlcj,.false.,ipi,ipj,ipk      &
152    &      ,zlon,zlat,zlev,itime,istep0,zdate0,zsecond,numbath)
153       CALL flinget(numbath,'bathy',jpidta,jpjdta,jpk,jpan,1,                &
154    &        1,mig(1),nlci,mjg(1),nlcj,cmask(1:nlci,1:nlcj,1:jpk) )
155       CALL flinclo(numbath)
156
157        ! Extra-halo initialization in MPP
158         IF( lk_mpp ) THEN
159            DO ji = nlci+1, jpi
160               cmask(ji,:,:) = cmask(1,:,:)
161            ENDDO
162            DO jj = nlcj+1, jpj
163               cmask(:,jj,:)=cmask(:,1,:)
164            ENDDO
165         ENDIF
166
167         DO jk = 1, jpk
168           DO jj = 1, jpj
169             DO ji = 1, jpi
170               expide=min(8.,(fsdept(ji,jj,jk)/500.)**(-1.5))
171               denitide=-0.9543+0.7662*log(expide)-0.235*log(expide)**2
172               cmask(ji,jj,jk)=cmask(ji,jj,jk)*exp(denitide)/0.6858
173             END DO
174           END DO
175         END DO
176
177       ELSE
178       cmask(:,:,:)=0.
179       ENDIF
180
181!!     Computation of the total atmospheric supply of Si
182!!     -------------------------------------------------
183
184       sumdepsi=0.
185       DO mo=1,12
186         DO jj=2,jpjm1
187           DO ji=2,jpim1
188           sumdepsi=sumdepsi+dustmo(ji,jj,mo)/(12.*rmoss)*8.8        &
189              *0.075/28.1*e1t(ji,jj)*e2t(ji,jj)*tmask(ji,jj,1)
190           END DO
191         END DO
192       END DO
193
194       IF( lk_mpp )   CALL mpp_sum( sumdepsi )  ! sum over the global domain
195
196!!    COMPUTATION OF THE N/P RELEASE DUE TO COASTAL RIVERS
197!!    COMPUTATION OF THE Si RELEASE DUE TO COASTAL RIVERS
198!!    ---------------------------------------------------
199
200       DO jj=1,jpj
201         DO ji=1,jpi
202       cotdep(ji,jj,1)=river(ji,jj)*1E9/(12.*raass                          &
203                       *e1t(ji,jj)*e2t(ji,jj)*fse3t(ji,jj,1)+rtrn)*tmask(ji,jj,1)
204       po4dep(ji,jj,1)=(river(ji,jj)+riverdoc(ji,jj))*1E9                   &
205                       /(31.6*raass*e1t(ji,jj)*e2t(ji,jj)*fse3t(ji,jj,1)+rtrn)   &
206                       *tmask(ji,jj,1)
207       nitdep(ji,jj,1)=7.6*ndepo(ji,jj)*tmask(ji,jj,1)/(14E6*raass          &
208                       *fse3t(ji,jj,1)+rtrn)
209         END DO
210       END DO
211
212      rivpo4input=0.
213      rivalkinput=0.
214      rivnitinput=0.
215       DO jj=2,jpjm1
216         DO ji=2,jpim1
217         rivpo4input=rivpo4input+po4dep(ji,jj,1)*(e1t(ji,jj)*e2t(ji,jj)    &
218                     *fse3t(ji,jj,1))*tmask(ji,jj,1)*raass
219         rivalkinput=rivalkinput+cotdep(ji,jj,1)*(e1t(ji,jj)*e2t(ji,jj)    &
220                     *fse3t(ji,jj,1))*tmask(ji,jj,1)*raass
221         rivnitinput=rivnitinput+nitdep(ji,jj,1)*(e1t(ji,jj)*e2t(ji,jj)    &
222                     *fse3t(ji,jj,1))*tmask(ji,jj,1)*raass
223         END DO
224       END DO
225
226        IF( lk_mpp ) THEN
227          CALL mpp_sum( rivpo4input )  ! sum over the global domain
228          CALL mpp_sum( rivalkinput )  ! sum over the global domain
229          CALL mpp_sum( rivnitinput )  ! sum over the global domain
230        ENDIF
231
232
233!!    Coastal supply of iron
234!!    ----------------------
235
236      DO jk=1,jpkm1
237          ironsed(:,:,jk)=sedfeinput*cmask(:,:,jk)         &
238                            /(fse3t(:,:,jk)*rjjss)
239      END DO
240!!----------------------------------------------------------------------
241!!
242!! Initialize biological variables
243!!
244!!----------------------------------------------------------------------
245
246      spocri = 0.003
247      jkopt = 14
248
249!! Set biological ratios
250!! ---------------------
251
252      rno3   = (16.+2.)/122.
253      po4r   = 1./122.
254      o2ut   = 172./122.
255      o2nit  = 32./122.
256      rdenit = 97.6/16.
257      o2ut   = 140./122.
258
259!!----------------------------------------------------------------------
260!!
261!! Initialize chemical variables
262!!
263!!----------------------------------------------------------------------
264
265!! set pre-industrial atmospheric [co2] (ppm) and o2/n2 ratio
266!! ----------------------------------------------------------
267
268      atcox = 0.20946
269
270!! Set lower/upper limits for temperature and salinity
271!! ---------------------------------------------------
272
273      salchl = 1./1.80655
274      calcon = 1.03E-2
275
276!! Set coefficients for apparent solubility equilibrium
277!!   of calcite (Ingle, 1800, eq. 6)
278!! ----------------------------------------------------
279
280      akcc1 = -34.452
281      akcc2 = -39.866
282      akcc3 = 110.21
283      akcc4 = -7.5752E-6
284
285
286!! Set coefficients for seawater pressure correction
287!! -------------------------------------------------
288
289      devk1  = 24.2
290      devk2  = 16.4
291      devkb  = 27.5
292      devk1t = 0.085
293      devk2t = 0.04
294      devkbt = 0.095
295
296      devkst = 0.23
297      devks  = 35.4
298
299!! Set universal gas constants
300!! ---------------------------
301
302      rgas = 83.143
303      oxyco = 1./22.4144
304
305!! Set boron constants
306!! -------------------
307
308      bor1 = 0.00023
309      bor2 = 1./10.82
310
311!! Set volumetric solubility constants for co2 in ml/l (Weiss, 1974)
312!! -----------------------------------------------------------------
313
314      c00 = -58.0931
315      c01 = 90.5069
316      c02 = 22.2940
317      c03 = 0.027766
318      c04 = -0.025888
319      c05 = 0.0050578
320
321!! Set coeff. for 1. dissoc. of carbonic acid (Edmond and Gieskes, 1970)
322!! ---------------------------------------------------------------------
323
324      c10 = -2307.1266
325      c11 = 2.83655
326      c12 = -1.5529413
327      c13 = -4.0484
328      c14 = -0.20760841
329      c15 = 0.08468345
330      c16 = -0.00654208
331      c17 = -0.001005
332
333!! Set coeff. for 2. dissoc. of carbonic acid (Edmond and Gieskes, 1970)
334!! ---------------------------------------------------------------------
335 
336      c20 = -3351.6106
337      c21 = -9.226508
338      c22 = -0.2005743
339      c23 = -23.9722
340      c24 = -0.106901773
341      c25 = 0.1130822
342      c26 = -0.00846934
343      c27 = -0.001005
344
345!! Set coeff. for 1. dissoc. of boric acid (Edmond and Gieskes, 1970)
346!! ------------------------------------------------------------------
347
348      cb0  = -8966.90
349      cb1  = -2890.53
350      cb2  = -77.942
351      cb3  = 1.728
352      cb4  = -0.0996
353      cb5  = 148.0248
354      cb6  = 137.1942
355      cb7  = 1.62142
356      cb8  = -24.4344
357      cb9  = -25.085
358      cb10 = -0.2474
359      cb11 = 0.053105
360
361!! Set coeff. for dissoc. of water (Dickson and Riley, 1979,
362!!   eq. 7, coefficient cw2 corrected from 0.9415 to 0.09415
363!!   after pers. commun. to B. Bacastow, 1988)
364!! ---------------------------------------------------------
365
366      cw0 = -13847.26
367      cw1 = 148.9652
368      cw2 = -23.6521
369      cw3 = 118.67
370      cw4 = -5.977
371      cw5 = 1.0495
372      cw6 = -0.01615
373
374!! Set volumetric solubility constants for o2 in ml/l (Weiss, 1970)
375!! ----------------------------------------------------------------
376
377      ox0 = -58.3877
378      ox1 = 85.8079
379      ox2 = 23.8439
380      ox3 = -0.034892
381      ox4 = 0.015568
382      ox5 = -0.0019387
383
384!!  FROM THE NEW BIOOPTIC MODEL PROPOSED JM ANDRE, WE READ HERE
385!!  A PRECOMPUTED ARRAY CORRESPONDING TO THE ATTENUATION COEFFICIENT
386
387         open(49,file='kRGB61.txt',form='formatted')
388         do ichl=1,61
389           READ(49,*) xtoto,(xkrgb(iband,ichl),iband = 1,3)
390         end do
391         close(49)
392     
393#if defined key_off_degrad
394
395!! Read volume for degraded regions (DEGINIT)
396!! ------------------------------------------
397
398#    if defined key_vpp
399      CALL READ3S(902,facvol,jpi,jpj,jpk)
400#    else
401      READ (902) facvol
402#    endif
403#endif
404
405
406!!  Call p4zche to initialize the chemical constants
407!!  ------------------------------------------------
408
409      CALL p4zche
410
411      IF(lwp) WRITE(numout,*) ' Initialisation of PISCES done'
Note: See TracBrowser for help on using the repository browser.