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.
sedini.F90 in NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/SED/sedini.F90 @ 15127

Last change on this file since 15127 was 15127, checked in by cetlod, 2 years ago

dev_PISCO : merge with trunk@15119

  • Property svn:keywords set to Id
File size: 30.9 KB
Line 
1MODULE sedini
2   !!======================================================================
3   !!              ***  MODULE  sedini  ***
4   !! Sediment : define sediment variables
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   sed_ini    : initialization, namelist read, and parameters control
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE sed     ! sediment global variable
12   USE sedarr
13   USE sedadv
14   USE trcdmp_sed
15   USE trcdta
16   USE iom
17   USE lib_mpp         ! distribued memory computing library
18
19
20   IMPLICIT NONE
21   PRIVATE
22
23   !! Module variables
24   REAL(wp), PUBLIC :: sedmask 
25
26   REAL(wp)    ::  &
27      sedzmin = 0.3    ,  &  !: Minimum vertical spacing
28      sedhmax = 10.0   ,  &  !: Maximum depth of the sediment
29      sedkth  = 5.0    ,  &  !: Default parameters
30      sedacr  = 3.0          !: Default parameters
31     
32   REAL(wp)    ::  &
33      porsurf =  0.95  ,  &  !: Porosity at the surface
34      porinf  =  0.75  ,  &  !: Porosity at infinite depth
35      rhox    =  2.0         !: Vertical length scale of porosity variation
36
37   REAL(wp)    ::  &
38      rcopal  =   40.  ,  &  !: reactivity for si    [l.mol-1.an-1]
39      dcoef   =  8.e-6       !: diffusion coefficient (*por)   [cm**2/s]
40
41   REAL(wp), PUBLIC    ::  &
42      redO2    =  133.  ,  &  !: Redfield coef for Oxygen
43      redNo3   =   16.  ,  &  !: Redfield coef for Nitrate
44      redPo4   =    1.  ,  &  !: Redfield coef for Phosphate
45      redC     =  122.  ,  &  !: Redfield coef for Carbon
46      redfep   =  0.175 ,  &  !: Ratio for iron bound phosphorus
47      rcorgl   =   50.  ,  &  !: reactivity for POC/O2 [l.mol-1.an-1]   
48      rcorgs   =   0.5  ,  &  !: reactivity of the semi-labile component
49      rcorgr   =   1E-4 ,  &  !: reactivity of the refractory component
50      rcnh4    =   10E6 ,  &  !: reactivity for O2/NH4 [l.mol-1.an-1] 
51      rch2s    =   1.E5 ,  &  !: reactivity for O2/ODU [l.mol-1.an-1]
52      rcfe2    =   5.E8 ,  &  !: reactivity for O2/Fe2+ [l.mol-1.an-1]
53      rcfeh2s  =   1.E4 ,  &  !: Reactivity for FEOH/H2S [l.mol-1.an-1]
54      rcfeso   =   3.E5 ,  &  !: Reactivity for FES/O2 [l.mol-1.an-1]
55      rcfesp   =   5E-6 ,  &  !: Precipitation of FeS [mol/l-1.an-1]
56      rcfesd   =   1E-3 ,  &  !: Dissolution of FeS [an-1]
57      xksedo2  =   5E-6 ,  &  !: half-sturation constant for oxic remin.
58      xksedno3 =   5E-6 ,  &  !: half-saturation constant for denitrification
59      xksedfeo =   0.6  ,  & !: half-saturation constant for iron remin
60      xksedso4 =   2E-3       !: half-saturation constant for SO4 remin
61
62   REAL(wp)    ::  &
63      rccal   = 1000.,      & !: reactivity for calcite         [l.mol-1.an-1]
64      rcligc  = 1.E-4         !: L/C ratio in POC
65
66   REAL(wp), PUBLIC    ::  dbiot   = 15. , &  !: coefficient for bioturbation    [cm**2.(n-1)]
67      dbtbzsc =  10.0  ,    &  !: Vertical scale of variation. If no variation, mixed layer in the sed [cm]
68      xirrzsc = 2.0            !: Vertical scale of irrigation variation.
69   REAL(wp)    ::  &
70      ryear = 365. * 24. * 3600. !:  1 year converted in second
71
72   REAL(wp), DIMENSION(jpwat), PUBLIC  :: diff1
73   DATA diff1/ 1.104E-5, 9.78E-6, 3.58E-6, 9.8E-6, 9.73E-6, 5.0E-6, 3.31E-6, 4.81E-6, 4.81E-6, 4.81E-6, 4.59E-6 /
74
75
76   REAL(wp), DIMENSION(jpwat), PUBLIC  :: diff2
77   DATA diff2/ 4.47E-7, 3.89E-7, 1.77E-7, 3.89E-7, 3.06E-7, 2.5E-7, 1.5E-7, 2.51E-7, 2.51E-7, 2.51E-7, 1.74E-7 /
78
79   !! *  Routine accessibility
80   PUBLIC sed_ini          ! routine called by opa.F90
81
82   !! * Substitutions
83#  include "do_loop_substitute.h90"
84   !! $Id$
85CONTAINS
86
87
88   SUBROUTINE sed_ini
89      !!----------------------------------------------------------------------
90      !!                   ***  ROUTINE sed_ini  ***
91      !!
92      !! ** Purpose :  Initialization of sediment module
93      !!               - Reading namelist
94      !!               - Read the deepest water layer thickness
95      !!                 ( using as mask ) in Netcdf file
96      !!               - Convert unity if necessary
97      !!               - sets initial sediment composition
98      !!                 ( only clay or reading restart file )
99      !!               - sets sediment grid, porosity and others constants
100      !!
101      !!   History :
102      !!        !  04-10  (N. Emprin, M. Gehlen )  Original code
103      !!        !  06-07  (C. Ethe)  Re-organization
104      !!----------------------------------------------------------------------
105      INTEGER :: ji, jj, js, jn, jk, ikt, ierr
106      !!----------------------------------------------------------------------
107
108      ! Reading namelist.sed variables
109      !---------------------------------------
110
111      CALL ctl_opn( numsed, 'sediment.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
112
113      IF (lwp) THEN
114         WRITE(numsed,*)
115         WRITE(numsed,*) '                 PISCES framework'
116         WRITE(numsed,*) '                 SEDIMENT model'
117         WRITE(numsed,*) '                version 3.0  (2018) '
118         WRITE(numsed,*)
119         WRITE(numsed,*)
120      ENDIF
121
122      IF(lwp) WRITE(numsed,*) ' sed_ini : Initialization of sediment module  '
123      IF(lwp) WRITE(numsed,*) ' '
124
125      ! Read sediment Namelist
126      !-------------------------
127      CALL sed_ini_nam
128
129      ! Allocate SEDIMENT arrays
130      ierr =        sed_alloc()
131      ierr = ierr + sed_adv_alloc() 
132      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'sed_ini: unable to allocate sediment model arrays' )
133
134      ! Determination of sediments number of points and allocate global variables
135      epkbot(:,:) = 0.
136      gdepbot(:,:) = 0.
137      DO_2D( 1, 1, 1, 1 )
138         ikt = mbkt(ji,jj) 
139         IF( tmask(ji,jj,ikt) == 1 ) epkbot(ji,jj) = e3t_0(ji,jj,ikt)
140         gdepbot(ji,jj) = gdepw_0(ji,jj,ikt+1)
141      END_2D
142
143      ! computation of total number of ocean points
144      !--------------------------------------------
145      sedmask = 0.
146      IF ( COUNT( epkbot(:,:) > 0. ) == 0 ) THEN
147          sedmask = 0.
148      ELSE
149          sedmask = 1.
150      ENDIF
151      jpoce  = MAX( COUNT( epkbot(:,:) > 0. ) , 1 )
152
153      ! Allocate memory size of global variables
154      ALLOCATE( pwcp (jpoce,jpksed,jpwat) )  ;  ALLOCATE( pwcp_dta  (jpoce,jpwat) )
155      ALLOCATE( pwcpa(jpoce,jpksed,jpwat) )  ;  ALLOCATE( solcpa(jpoce,jpksed,jpsol) )
156      ALLOCATE( solcp(jpoce,jpksed,jpsol) )  ;  ALLOCATE( rainrm_dta(jpoce,jpsol) )
157      ALLOCATE( rainrm(jpoce,jpsol) )        ;  ALLOCATE( rainrg(jpoce,jpsol) )        ;  ALLOCATE( raintg(jpoce) ) 
158      ALLOCATE( dzdep(jpoce) )               ;  ALLOCATE( iarroce(jpoce) )             ;  ALLOCATE( dzkbot(jpoce) )
159      ALLOCATE( zkbot(jpoce) )               ;  ALLOCATE( db(jpoce,jpksed) )
160      ALLOCATE( temp(jpoce) )                ;  ALLOCATE( salt(jpoce) ) 
161      ALLOCATE( diff(jpoce,jpksed,jpwat ) )  ;  ALLOCATE( irrig(jpoce, jpksed) )
162      ALLOCATE( wacc(jpoce) )                ;  ALLOCATE( fecratio(jpoce) )
163      ALLOCATE( densSW(jpoce) )   ;   ALLOCATE( saturco3(jpoce,jpksed) ) 
164      ALLOCATE( hipor(jpoce,jpksed) )        ;  ALLOCATE( co3por(jpoce,jpksed) )
165      ALLOCATE( dz3d(jpoce,jpksed) )         ;  ALLOCATE( volw3d(jpoce,jpksed) )       ;  ALLOCATE( vols3d(jpoce,jpksed) )
166      ALLOCATE( rearatpom(jpoce, jpksed) )   ;  ALLOCATE( volc(jpoce,jpksed,jpsol) )
167      ALLOCATE( Jacobian(jpoce, jpvode*jpksed, jpvode*jpksed) )
168      ALLOCATE( radsfe2(jpksed) )            ;  ALLOCATE( radsnh4(jpksed) )
169      ALLOCATE( wacc1(jpoce) )
170
171      ! Initialization of global variables
172      pwcp  (:,:,:) = 0.   ;  pwcp_dta  (:,:) = 0. 
173      pwcpa (:,:,:) = 0.   ;  solcpa(:,:,:) = 0.
174      solcp (:,:,:) = 0.   ;  rainrm_dta(:,:) = 0.
175      rainrm(:,:  ) = 0.   ;  rainrg(:,:  ) = 0.  ; raintg    (:  ) = 0. 
176      dzdep (:    ) = 0.   ;  iarroce(:   ) = 0   ; dzkbot    (:  ) = 0.
177      temp  (:    ) = 0.   ;  salt   (:   ) = 0.  ; zkbot     (:  ) = 0.
178      densSW (:   ) = 0.   ;  db     (:,:) = 0. 
179      hipor (:,:  ) = 0.   ;  co3por (:,: ) = 0.  ; irrig     (:,:) = 0. 
180      dz3d  (:,:  ) = 0.   ;  volw3d (:,: ) = 0.  ; vols3d    (:,:) = 0. 
181      fecratio(:)   = 1E-5 ;  rearatpom(:,:) = 0. 
182      radsfe2(:)    = 1.0  ;  radsnh4(:)    = 1.0
183
184      ! Chemical variables     
185      ALLOCATE( akbs  (jpoce) )  ;  ALLOCATE( ak1s   (jpoce) )  ;  ALLOCATE( ak2s  (jpoce) ) ;  ALLOCATE( akws  (jpoce) )     
186      ALLOCATE( ak1ps (jpoce) )  ;  ALLOCATE( ak2ps  (jpoce) )  ;  ALLOCATE( ak3ps (jpoce) ) ;  ALLOCATE( aksis (jpoce) )   
187      ALLOCATE( aksps (jpoce) )  ;  ALLOCATE( ak12s  (jpoce) )  ;  ALLOCATE( ak12ps(jpoce) ) ;  ALLOCATE( ak123ps(jpoce) )   
188      ALLOCATE( borats(jpoce) )  ;  ALLOCATE( calcon2(jpoce) )  ;  ALLOCATE( sieqs (jpoce) ) 
189      ALLOCATE( aks3s(jpoce) )   ;  ALLOCATE( akf3s(jpoce) )    ;  ALLOCATE( sulfats(jpoce) )
190      ALLOCATE( fluorids(jpoce) ) ; ALLOCATE( akh2s(jpoce) )    ;  ALLOCATE( aknh3(jpoce) )
191
192      akbs  (:) = 0. ;   ak1s   (:) = 0. ;  ak2s  (:) = 0. ;   akws   (:) = 0.
193      ak1ps (:) = 0. ;   ak2ps  (:) = 0. ;  ak3ps (:) = 0. ;   aksis  (:) = 0.
194      aksps (:) = 0. ;   ak12s  (:) = 0. ;  ak12ps(:) = 0. ;   ak123ps(:) = 0.
195      borats(:) = 0. ;   calcon2(:) = 0. ;  sieqs (:) = 0. ;   akh2s  (:) = 0.
196      aks3s(:)  = 0. ;   akf3s(:)   = 0. ;  sulfats(:) = 0. ;  fluorids(:) = 0.
197      aknh3(:)  = 0.
198
199      ! Mass balance calculation 
200      ALLOCATE( fromsed(jpoce, jpsol+jpads) ) ; ALLOCATE( tosed(jpoce, jpsol+jpads) )
201
202      fromsed(:,:) = 0.    ;   tosed(:,:) = 0.
203
204      ! Initialization of sediment geometry
205      !------------------------------------
206      CALL sed_ini_geom
207
208      ! Offline specific mode
209      ! ---------------------
210      ln_sediment_offline = .FALSE.
211
212      ! Vertical profile of of the adsorption factor for adsorbed species
213      ! -----------------------------------------------------------------
214      radsfe2(:) = 1.0 / ( 1.0 + adsfe2 * por1(:) / por(:) )
215      radsnh4(:) = 1.0 / ( 1.0 + adsnh4 * por1(:) / por(:) )
216
217      ! Initialization of the array for non linear solving
218      ! --------------------------------------------------
219
220      ALLOCATE( jarr(jpvode*jpksed,2) )
221      ALLOCATE( jsvode(jpvode), isvode(jptrased) )
222      jsvode(1) = jwoxy ; jsvode(2) = jwno3 ; jsvode(3) = jwnh4
223      jsvode(4) = jwh2s ; jsvode(5) = jwso4 ; jsvode(6) = jwfe2
224      jsvode(7) = jpwat+jsfeo ; jsvode(8) = jpwat+jsfes
225      isvode(jwoxy) = 1 ; isvode(jwno3) = 2 ; isvode(jwnh4) = 3
226      isvode(jwh2s) = 4 ; isvode(jwso4) = 5 ; isvode(jwfe2) = 6
227      isvode(jpwat+jsfeo) = 7 ; isvode(jpwat+jsfes) = 8
228      DO js = 1, jpvode
229         DO jk = 1, jpksed
230            jn = (jk-1) * jpvode + js
231            jarr(jn,1) = jk
232            jarr(jn,2) = jsvode(js)
233         END DO
234      END DO
235
236      ALLOCATE( stepros(jpoce) )
237
238#if defined key_sed_off
239      ln_sediment_offline = .TRUE.
240      IF (lwp) write(numsed,*) 'Sediment module is run in offline mode'
241      IF (lwp) write(numsed,*) 'key_sed_off is activated at compilation time'
242      IF (lwp) write(numsed,*) 'ln_sed_2way is forced to false'
243      IF (lwp) write(numsed,*) '--------------------------------------------'
244      ln_sed_2way = .FALSE.
245#endif
246      ! Initialisation of tracer damping
247      ! --------------------------------
248      IF (ln_sediment_offline) THEN
249         CALL trc_dmp_sed_ini
250      ENDIF
251
252   END SUBROUTINE sed_ini
253
254   SUBROUTINE sed_ini_geom
255      !!----------------------------------------------------------------------
256      !!                   ***  ROUTINE sed_ini_geom  ***
257      !!
258      !! ** Purpose :  Initialization of sediment geometry
259      !!               - Read the deepest water layer thickness
260      !!                 ( using as mask ) in Netcdf file
261      !!               - sets sediment grid, porosity and molecular weight
262      !!                 and others constants
263      !!
264      !!   History :
265      !!        !  06-07  (C. Ethe)  Original
266      !!----------------------------------------------------------------------
267      !! * Modules used
268      !! * local declarations
269      INTEGER  :: ji, jj, jk, jn
270      REAL(wp) :: za0, za1, zt, zw, zsum, zsur, zprof, zprofw
271      REAL(wp) :: ztmp1, ztmp2
272      !----------------------------------------------------------
273
274      IF(lwp) WRITE(numsed,*) ' sed_ini_geom : Initialization of sediment geometry '
275      IF(lwp) WRITE(numsed,*) ' '
276
277      ! Computation of 1D array of sediments points
278      indoce = 0
279      DO_2D( 1, 1, 1, 1 )
280         IF (  epkbot(ji,jj) > 0. ) THEN
281            indoce          = indoce + 1
282            iarroce(indoce) = (jj - 1) * jpi + ji
283         ENDIF
284      END_2D
285
286      IF ( indoce .EQ. 0 ) THEN
287         indoce = 1
288         iarroce(indoce) = 1
289      ENDIF
290
291      IF( indoce .NE. jpoce ) THEN
292         CALL ctl_stop( 'STOP', 'sed_ini: number of ocean points indoce doesn''t match  number of point' )
293      ELSE
294         IF (lwp) WRITE(numsed,*) ' '
295         IF (lwp) WRITE(numsed,*) ' total number of ocean points jpoce =  ',jpoce
296         IF (lwp) WRITE(numsed,*) ' '
297      ENDIF
298
299      ! initialization of dzkbot in [cm]
300      !------------------------------------------------   
301      CALL pack_arr ( jpoce, dzkbot(1:jpoce), epkbot(1:jpi,1:jpj), iarroce(1:jpoce) )
302      dzkbot(1:jpoce) = dzkbot(1:jpoce) * 1.e+2 
303      CALL pack_arr ( jpoce, zkbot(1:jpoce), gdepbot(1:jpi,1:jpj), iarroce(1:jpoce) )
304
305      ! Geometry and  constants
306      ! sediment layer thickness [cm]
307      ! (1st layer= diffusive layer = pur water)
308      !------------------------------------------
309      za1  = (  sedzmin - sedhmax / FLOAT(jpksed-1)  )                                                      &
310         & / ( TANH((1-sedkth)/sedacr) - sedacr/FLOAT(jpksed-1) * (  LOG( COSH( (jpksed - sedkth) / sedacr) )      &
311         &                                                   - LOG( COSH( ( 1  - sedkth) / sedacr) )  )  )
312      za0  = sedzmin - za1 * TANH( (1-sedkth) / sedacr )
313      zsur = - za0 - za1 * sedacr * LOG( COSH( (1-sedkth) / sedacr )  )
314
315      dz(1)       = 0.1
316      profsedw(1) = 0.0
317      profsed(1)  = -dz(1) / 2.
318      DO jk = 2, jpksed
319         zw = REAL( jk , wp )
320         zt = REAL( jk , wp ) - 0.5_wp
321         profsed(jk)  = ( zsur + za0 * zt + za1 * sedacr * LOG ( COSH( (zt-sedkth) / sedacr ) )  ) 
322         profsedw(jk) = ( zsur + za0 * zw + za1 * sedacr * LOG ( COSH( (zw-sedkth) / sedacr ) )  )
323         dz(jk) = profsedw(jk) - profsedw(jk-1)
324      END DO
325
326      DO ji = 1, jpoce
327         dz3d(ji,:) = dz(:)
328      END DO
329
330      !  Porosity profile [0]
331      !---------------------
332      por(1) = 1.0
333      DO jk = 2, jpksed
334         por(jk) = porinf + ( porsurf-porinf) * exp(-rhox * (profsed(jk) ) )
335      END DO
336 
337      ! inverse of  Porosity profile
338      !-----------------------------
339      por1(:) = 1. - por(:)
340
341      ! Volumes of pore water and solid fractions (vector and array)
342      !     WARNING : volw(1) and vols(1) are sublayer volums
343      volw(:) = dz(:) * por(:)
344      vols(:) = dz(:) * por1(:)
345
346      ! temporary new value for dz3d(:,1)
347      dz3d(1:jpoce,1) = dzkbot(1:jpoce)
348
349      ! WARNING : volw3d(:,1) and vols3d(:,1) are deepest water column volums
350      DO jk = 1, jpksed
351         volw3d(1:jpoce,jk) = dz3d(1:jpoce,jk) * por (jk)
352         vols3d(1:jpoce,jk) = dz3d(1:jpoce,jk) * por1(jk)
353      ENDDO
354
355      ! Back to the old sublayer vlaue for dz3d(:,1)
356      dz3d(1:jpoce,1) = dz(1)
357
358      !---------------------------------------------
359      ! Molecular weight [g/mol] for solid species
360      !---------------------------------------------
361
362      ! opal=sio2*0.4(h20)=28+2*16+0.4*(2+16)
363      !---------------------------------------
364      mol_wgt(jsopal) = 28. + 2. * 16. + 0.4 * ( 2. + 16. ) 
365
366      !  clay
367      !  some kind of Illit (according to Pape)
368      !  K0.58(Al 1.38 Fe(III)0.37Fe(II)0.04Mg0.34)[(OH)2|(Si3.41Al0.59)O10]
369      !--------------------------------------------------------------------
370      mol_wgt(jsclay) = 0.58 * 39. + 1.38 * 27. + ( 0.37 + 0.04 ) * 56.+ &
371         &              0.34 * 24. + 2. * ( 16. + 1. ) + 3.41 * 38. +    &
372         &              0.59 * 27. + 10. * 16.
373
374      mol_wgt(jsfeo)  = 55.0 + 3.0 * ( 16.0 + 1.0)
375
376      mol_wgt(jsfes)  = 55.0 + 32.0
377
378      ! for chemistry Poc : C(122)H(244)O(86)N(16)P(1)
379      ! But den sity of Poc is an Hydrated material (= POC + 30H2O)
380      ! So C(122)H(355)O(120)N(16)P(1)
381      !------------------------------------------------------------
382      mol_wgt(jspoc) = ( 122. * 12. + 355. + 120. * 16.+ &
383         &                16. * 14. + 31. ) / 122.
384      mol_wgt(jspos) = mol_wgt(jspoc)
385      mol_wgt(jspor) = mol_wgt(jspoc)
386
387      ! CaCO3
388      !---------
389      mol_wgt(jscal) = 40. + 12. + 3. * 16.
390
391      ! Density of solid material in sediment [g/cm**3]
392      !------------------------------------------------
393      denssol = 2.6
394
395      ! Accumulation rate from Burwicz et al. (2011). This is used to
396      ! compute the flux of clays and minerals
397      ! --------------------------------------------------------------
398      DO ji = 1, jpoce
399!          ztmp1 = 0.117 / ( 1.0 + ( zkbot(ji) / 200.)**3 )
400          ztmp1 = 0.
401          ztmp2 = 0.006 / ( 1.0 + ( zkbot(ji) / 4000.)**10 )
402          wacc(ji) = ztmp2+ztmp1 
403      END DO
404
405
406      ! Initialization of time step as function of porosity [cm**2/s]
407      !------------------------------------------------------------------
408   END SUBROUTINE sed_ini_geom
409
410   SUBROUTINE sed_ini_nam
411      !!----------------------------------------------------------------------
412      !!                   ***  ROUTINE sed_ini_nam  ***
413      !!
414      !! ** Purpose :  Initialization of sediment geometry
415      !!               - Reading namelist and defines constants variables
416      !!
417      !!   History :
418      !!        !  06-07  (C. Ethe)  Original
419      !!----------------------------------------------------------------------
420
421      INTEGER ::   numnamsed_ref = -1           !! Logical units for namelist sediment
422      INTEGER ::   numnamsed_cfg = -1           !! Logical units for namelist sediment
423      INTEGER :: ios                 ! Local integer output status for namelist read
424      CHARACTER(LEN=20)   ::   clname
425
426      TYPE PSED
427         CHARACTER(len = 20)  :: snamesed   !: short name
428         CHARACTER(len = 80 ) :: lnamesed   !: long name
429         CHARACTER(len = 20 ) :: unitsed    !: unit
430      END TYPE PSED
431
432      TYPE(PSED) , DIMENSION(jpsol     ) :: sedsol
433      TYPE(PSED) , DIMENSION(jpwat     ) :: sedwat
434      TYPE(PSED) , DIMENSION(jpdia3dsed) :: seddiag3d
435      TYPE(PSED) , DIMENSION(jpdia2dsed) :: seddiag2d
436
437      NAMELIST/nam_run/ln_sed_2way
438      NAMELIST/nam_geom/jpksed, sedzmin, sedhmax, sedkth, sedacr, porsurf, porinf, rhox
439      NAMELIST/nam_trased/sedsol, sedwat
440      NAMELIST/nam_diased/seddiag3d, seddiag2d
441      NAMELIST/nam_inorg/rcopal, dcoef, rccal, ratligc, rcligc
442      NAMELIST/nam_poc/redO2, redNo3, redPo4, redC, redfep, rcorgl, rcorgs,  &
443         &             rcorgr, rcnh4, rch2s, rcfe2, rcfeh2s, rcfeso, rcfesp, &
444         &             rcfesd, xksedo2, xksedno3, xksedfeo, xksedso4
445      NAMELIST/nam_btb/dbiot, ln_btbz, dbtbzsc, adsnh4, adsfe2, ln_irrig, xirrzsc
446      NAMELIST/nam_rst/ln_rst_sed, cn_sedrst_indir, cn_sedrst_outdir, cn_sedrst_in, cn_sedrst_out
447
448      INTEGER :: ji, jn, jn1
449      !-------------------------------------------------------
450
451      IF(lwp) WRITE(numsed,*) ' sed_ini_nam : Read namelists '
452      IF(lwp) WRITE(numsed,*) ' '
453
454      ! ryear = 1 year converted in second
455      !------------------------------------
456      IF (lwp) THEN
457         WRITE(numsed,*) ' '
458         WRITE(numsed,*) 'number of seconds in one year : ryear = ', ryear
459         WRITE(numsed,*) ' '     
460      ENDIF
461
462      ! Reading namelist.sed variables
463      !---------------------------------
464      clname = 'namelist_sediment'
465      IF(lwp) WRITE(numsed,*) ' sed_ini_nam : read SEDIMENT namelist'
466      IF(lwp) WRITE(numsed,*) ' ~~~~~~~~~~~~~~'
467      CALL ctl_opn( numnamsed_ref, TRIM( clname )//'_ref', 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
468      CALL ctl_opn( numnamsed_cfg, TRIM( clname )//'_cfg', 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
469
470      nitsed000 = nittrc000
471      nitsedend = nitend
472      ! Namelist nam_run
473      REWIND( numnamsed_ref )              ! Namelist nam_run in reference namelist : Pisces variables
474      READ  ( numnamsed_ref, nam_run, IOSTAT = ios, ERR = 901)
475901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_run in reference namelist' )
476
477      REWIND( numnamsed_cfg )              ! Namelist nam_run in reference namelist : Pisces variables
478      READ  ( numnamsed_cfg, nam_run, IOSTAT = ios, ERR = 902)
479902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_run in configuration namelist' )
480
481      IF (lwp) THEN
482         WRITE(numsed,*) ' namelist nam_run'
483         WRITE(numsed,*) ' 2-way coupling between PISCES and Sed ln_sed_2way = ', ln_sed_2way
484      ENDIF
485
486      IF ( ln_p5z .AND. ln_sed_2way ) CALL ctl_stop( '2 ways coupling with sediment cannot be activated with PISCES-QUOTA' )
487
488      REWIND( numnamsed_ref )              ! Namelist nam_geom in reference namelist : Pisces variables
489      READ  ( numnamsed_ref, nam_geom, IOSTAT = ios, ERR = 903)
490903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_geom in reference namelist' )
491
492      REWIND( numnamsed_cfg )              ! Namelist nam_geom in reference namelist : Pisces variables
493      READ  ( numnamsed_cfg, nam_geom, IOSTAT = ios, ERR = 904)
494904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_geom in configuration namelist' )
495
496      IF (lwp) THEN
497         WRITE(numsed,*) ' namelist nam_geom'
498         WRITE(numsed,*) ' Number of vertical layers            jpksed  = ', jpksed
499         WRITE(numsed,*) ' Minimum vertical spacing             sedzmin = ', sedzmin
500         WRITE(numsed,*) ' Maximum depth of the sediment        sedhmax = ', sedhmax
501         WRITE(numsed,*) ' Default parameter                    sedkth  = ', sedkth
502         WRITE(numsed,*) ' Default parameter                    sedacr  = ', sedacr
503         WRITE(numsed,*) ' Sediment porosity at the surface     porsurf = ', porsurf
504         WRITE(numsed,*) ' Sediment porosity at infinite depth  porinf  = ', porinf
505         WRITE(numsed,*) ' Length scale of porosity variation   rhox    = ', rhox
506      ENDIF
507
508      jpksedm1  = jpksed - 1
509      dtsed = rDt_trc
510
511      REWIND( numnamsed_ref )              ! Namelist nam_trased in reference namelist : Pisces variables
512      READ  ( numnamsed_ref, nam_trased, IOSTAT = ios, ERR = 905)
513905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_trased in reference namelist' )
514
515      REWIND( numnamsed_cfg )              ! Namelist nam_trased in reference namelist : Pisces variables
516      READ  ( numnamsed_cfg, nam_trased, IOSTAT = ios, ERR = 906)
517906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_trased in configuration namelist' )
518
519      DO jn = 1, jpsol
520         sedtrcd(jn) = sedsol(jn)%snamesed
521         sedtrcl(jn) = sedsol(jn)%lnamesed
522         sedtrcu(jn) = sedsol(jn)%unitsed
523      END DO
524
525      DO jn = 1, jpwat
526         jn1 = jn + jpsol
527         sedtrcd(jn1) = sedwat(jn)%snamesed
528         sedtrcl(jn1) = sedwat(jn)%lnamesed
529         sedtrcu(jn1) = sedwat(jn)%unitsed
530      END DO
531
532      IF (lwp) THEN
533         WRITE(numsed,*) ' namelist nam_trased'
534         WRITE(numsed,*) ' '
535         DO jn = 1, jptrased
536            WRITE(numsed,*) 'name of 3d output sediment field number :',jn,' : ',TRIM(sedtrcd(jn))
537            WRITE(numsed,*) 'long name ', TRIM(sedtrcl(jn))
538            WRITE(numsed,*) ' in unit = ', TRIM(sedtrcu(jn))
539            WRITE(numsed,*) ' '
540         END DO
541         WRITE(numsed,*) ' '
542      ENDIF
543
544      REWIND( numnamsed_ref )              ! Namelist nam_diased in reference namelist : Pisces variables
545      READ  ( numnamsed_ref, nam_diased, IOSTAT = ios, ERR = 907)
546907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diased in reference namelist' )
547
548      REWIND( numnamsed_cfg )              ! Namelist nam_diased in reference namelist : Pisces variables
549      READ  ( numnamsed_cfg, nam_diased, IOSTAT = ios, ERR = 908)
550908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diased in configuration namelist' )
551     
552      DO jn = 1, jpdia3dsed
553         seddia3d(jn) = seddiag3d(jn)%snamesed
554         seddia3l(jn) = seddiag3d(jn)%lnamesed
555         seddia3u(jn) = seddiag3d(jn)%unitsed
556      END DO
557
558      DO jn = 1, jpdia2dsed
559         seddia2d(jn) = seddiag2d(jn)%snamesed
560         seddia2l(jn) = seddiag2d(jn)%lnamesed
561         seddia2u(jn) = seddiag2d(jn)%unitsed
562      END DO
563
564      IF (lwp) THEN
565         WRITE(numsed,*) ' namelist nam_diased'
566         WRITE(numsed,*) ' '
567         DO jn = 1, jpdia3dsed
568            WRITE(numsed,*) 'name of 3D output diag number :',jn, ' : ', TRIM(seddia3d(jn))
569            WRITE(numsed,*) 'long name ', TRIM(seddia3l(jn))
570            WRITE(numsed,*) ' in unit = ',TRIM(seddia3u(jn))
571            WRITE(numsed,*) ' '
572         END DO
573
574         DO jn = 1, jpdia2dsed
575            WRITE(numsed,*) 'name of 2D output diag number :',jn, ' : ', TRIM(seddia2d(jn))
576            WRITE(numsed,*) 'long name ', TRIM(seddia2l(jn))
577            WRITE(numsed,*) ' in unit = ',TRIM(seddia2u(jn))
578            WRITE(numsed,*) ' '
579         END DO
580
581         WRITE(numsed,*) ' '
582      ENDIF
583
584      ! Inorganic chemistry parameters
585      !----------------------------------
586      REWIND( numnamsed_ref )              ! Namelist nam_inorg in reference namelist : Pisces variables
587      READ  ( numnamsed_ref, nam_inorg, IOSTAT = ios, ERR = 909)
588909   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_inorg in reference namelist' )
589
590      REWIND( numnamsed_cfg )              ! Namelist nam_inorg in reference namelist : Pisces variables
591      READ  ( numnamsed_cfg, nam_inorg, IOSTAT = ios, ERR = 910)
592910   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_inorg in configuration namelist' )
593
594      IF (lwp) THEN
595         WRITE(numsed,*) ' namelist nam_inorg'
596         WRITE(numsed,*) ' reactivity for Si      rcopal  = ', rcopal
597         WRITE(numsed,*) ' diff. coef for por.    dcoef   = ', dcoef
598         WRITE(numsed,*) ' reactivity for calcite rccal   = ', rccal
599         WRITE(numsed,*) ' L/C ratio in POC       ratligc = ', ratligc
600         WRITE(numsed,*) ' reactivity for ligands rcligc  = ', rcligc
601         WRITE(numsed,*) ' '
602      ENDIF
603
604      ! Unity conversion to get saturation conc. psat in [mol.l-1]
605      ! and reactivity rc in  [l.mol-1.s-1]
606      !----------------------------------------------------------
607      reac_sil   = rcopal / ryear     
608      reac_ligc  = rcligc / ryear
609
610      ! Additional parameter linked to POC/O2/No3/Po4
611      !----------------------------------------------
612      REWIND( numnamsed_ref )              ! Namelist nam_poc in reference namelist : Pisces variables
613      READ  ( numnamsed_ref, nam_poc, IOSTAT = ios, ERR = 911)
614911   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_poc in reference namelist' )
615
616      REWIND( numnamsed_cfg )              ! Namelist nam_poc in reference namelist : Pisces variables
617      READ  ( numnamsed_cfg, nam_poc, IOSTAT = ios, ERR = 912)
618912   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_poc in configuration namelist' )
619
620      IF (lwp) THEN
621         WRITE(numsed,*) ' namelist nam_poc'
622         WRITE(numsed,*) ' Redfield coef for oxy            redO2    = ', redO2
623         WRITE(numsed,*) ' Redfield coef for no3            redNo3   = ', redNo3
624         WRITE(numsed,*) ' Redfield coef for po4            redPo4   = ', redPo4
625         WRITE(numsed,*) ' Redfield coef for carbon         redC     = ', redC
626         WRITE(numsed,*) ' Ration for iron bound P          redfep   = ', redfep
627         WRITE(numsed,*) ' reactivity for labile POC        rcorgl   = ', rcorgl
628         WRITE(numsed,*) ' reactivity for semi-refract. POC rcorgs   = ', rcorgs
629         WRITE(numsed,*) ' reactivity for refractory POC    rcorgr   = ', rcorgr
630         WRITE(numsed,*) ' reactivity for NH4               rcnh4    = ', rcnh4
631         WRITE(numsed,*) ' reactivity for H2S               rch2s    = ', rch2s
632         WRITE(numsed,*) ' reactivity for Fe2+              rcfe2    = ', rcfe2
633         WRITE(numsed,*) ' reactivity for FeOH/H2S          rcfeh2s  = ', rcfeh2s
634         WRITE(numsed,*) ' reactivity for FeS/O2            rcfeso   = ', rcfeso
635         WRITE(numsed,*) ' Precipitation of FeS             rcfesp   = ', rcfesp
636         WRITE(numsed,*) ' Dissolution of FeS               rcfesd   = ', rcfesd
637         WRITE(numsed,*) ' Half-sat. cste for oxic remin    xksedo2  = ', xksedo2
638         WRITE(numsed,*) ' Half-sat. cste for denit.        xksedno3 = ', xksedno3
639         WRITE(numsed,*) ' Half-sat. cste for iron remin    xksedfeo = ', xksedfeo
640         WRITE(numsed,*) ' Half-sat. cste for SO4 remin     xksedso4 = ', xksedso4
641         WRITE(numsed,*) ' '
642      ENDIF
643
644
645      so2ut  = redO2    / redC
646      srno3  = redNo3   / redC
647      spo4r  = redPo4   / redC
648      srDnit = ( (redO2 + 32. ) * 0.8 - redNo3 - redNo3 * 0.6 ) / redC
649      ! reactivity rc in  [l.mol-1.s-1]
650      reac_pocl  = rcorgl / ryear
651      reac_pocs  = rcorgs / ryear
652      reac_pocr  = rcorgr / ryear
653      reac_nh4   = rcnh4  / ryear
654      reac_h2s   = rch2s  / ryear
655      reac_fe2   = rcfe2  / ryear
656      reac_feh2s = rcfeh2s/ ryear
657      reac_feso  = rcfeso / ryear
658      reac_fesp  = rcfesp / ryear
659      reac_fesd  = rcfesd / ryear
660
661
662      ! reactivity rc in  [l.mol-1.s-1]     
663      reac_cal = rccal / ryear
664
665      ! Bioturbation parameter
666      !------------------------
667      REWIND( numnamsed_ref )              ! Namelist nam_btb in reference namelist : Pisces variables
668      READ  ( numnamsed_ref, nam_btb, IOSTAT = ios, ERR = 913)
669913   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_btb in reference namelist' )
670
671      REWIND( numnamsed_cfg )              ! Namelist nam_btb in reference namelist : Pisces variables
672      READ  ( numnamsed_cfg, nam_btb, IOSTAT = ios, ERR = 914)
673914   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_btb in configuration namelist' )
674
675      IF (lwp) THEN
676         WRITE(numsed,*) ' namelist nam_btb ' 
677         WRITE(numsed,*) ' coefficient for bioturbation      dbiot    = ', dbiot
678         WRITE(numsed,*) ' Depth varying bioturbation        ln_btbz  = ', ln_btbz
679         WRITE(numsed,*) ' coefficient for btb attenuation   dbtbzsc  = ', dbtbzsc
680         WRITE(numsed,*) ' Adsorption coefficient of NH4     adsnh4   = ', adsnh4
681         WRITE(numsed,*) ' Adsorption coefficient of Fe2     adsfe2   = ', adsfe2
682         WRITE(numsed,*) ' Bioirrigation in sediment         ln_irrig = ', ln_irrig
683         WRITE(numsed,*) ' coefficient for irrig attenuation xirrzsc  = ', xirrzsc
684         WRITE(numsed,*) ' '
685      ENDIF
686
687      ! Initial value (t=0) for sediment pore water and solid components
688      !----------------------------------------------------------------
689      REWIND( numnamsed_ref )              ! Namelist nam_rst in reference namelist : Pisces variables
690      READ  ( numnamsed_ref, nam_rst, IOSTAT = ios, ERR = 915)
691915   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_rst in reference namelist' )
692
693      REWIND( numnamsed_cfg )              ! Namelist nam_rst in reference namelist : Pisces variables
694      READ  ( numnamsed_cfg, nam_rst, IOSTAT = ios, ERR = 916)
695916   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_rst in configuration namelist' )
696
697      IF (lwp) THEN
698         WRITE(numsed,*) ' namelist  nam_rst ' 
699         WRITE(numsed,*) '  boolean term for restart (T or F) ln_rst_sed = ', ln_rst_sed 
700         WRITE(numsed,*) ' '
701      ENDIF
702
703      CLOSE( numnamsed_cfg )
704      CLOSE( numnamsed_ref )
705
706   END SUBROUTINE sed_ini_nam
707
708END MODULE sedini
Note: See TracBrowser for help on using the repository browser.