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.
trclsm.pisces.h90 in branches/dev_001_GM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/dev_001_GM/NEMO/TOP_SRC/PISCES/trclsm.pisces.h90 @ 764

Last change on this file since 764 was 764, checked in by gm, 16 years ago

dev_001_GM - create new directory and move files only

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 12.4 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                     ***  trclsm.pisces.h90  *** 
3   !! TOP :   Definition some run parameter for PISCES biological model
4   !!----------------------------------------------------------------------
5   !! History :    -  !  1999-10 (M.A. Foujols, M. Levy) original code
6   !!              -  !  2000-01 (L. Bopp) hamocc3, p3zd
7   !!             1.0 !  2003-08 (C. Ethe)  module F90
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
12   !! $Id $
13   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
14   !!----------------------------------------------------------------------
15
16CONTAINS
17
18   SUBROUTINE trc_lsm
19      !!----------------------------------------------------------------------
20      !!                     ***  trc_lsm  *** 
21      !!
22      !! ** Purpose :   read PISCES namelist
23      !!
24      !! ** input   :   file 'namelist.trc.sms' containing the following
25      !!             namelist: natext, natbio, natsms
26      !!                       natkriest ("key_trc_kriest")
27      !!----------------------------------------------------------------------
28      CHARACTER (len=32) ::   clname
29      !!
30      NAMELIST/natext/ atcco2
31      NAMELIST/natbio/ caco3r, kdca, nca, part,                               &
32         &             dispo0,conc0,oxymin,grosip, nrdttrc,                   &
33         &             pislope, excret,wsbio,wchl,wchld,resrat,mprat,mzrat,   &
34         &             grazrat,xprefc,xprefp,unass,xkgraz,xkmort,xksi1,       &
35         &             xksi2,xremip,xremik,xsirem,xkdoc1,xkdoc2,              &
36         &             excret2,resrat2,mprat2,mpratm,mzrat2,grazrat2,         &
37         &             xprefz, xprefpoc, unass2, xkgraz2, xlam1,              &
38         &             ferat3,conc1,conc2,conc3,concnnh4,concdnh4,            &
39         &             nitrif,epsher,epsher2,pislope2,wsbio2,sigma1,          &
40         &             sigma2, zprefc, zprefp, zprefd,fecnm,fecdm,            &
41         &             chlcnm,chlcdm, sedfeinput
42      NAMELIST/natsms/bdustfer, briver, bndepo, bsedinput
43#if defined key_trc_kriest
44      NAMELIST/natkriest/ xkr_eta  , xkr_zeta , xkr_sfact, xkr_mass_min, xkr_mass_max,   &
45         &                xkr_dnano, xkr_ddiat, xkr_dmeso, xkr_daggr   , xkr_stick
46#endif
47      !!----------------------------------------------------------------------
48
49
50      IF(lwp) WRITE(numout,*)
51      IF(lwp) WRITE(numout,*) ' trc_lsm : read PISCES namelists'
52      IF(lwp) WRITE(numout,*) ' ~~~~~~~'
53
54
55      !                               ! Open the namelist file
56      !                               ! ----------------------
57      clname ='namelist.trc.sms'
58      CALL ctlopn( numnat, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL',   &
59         &           1, numout, .FALSE., 1 )
60
61      !                               ! natext : Atmospheric parameters
62      !                               ! -------------------- ----------
63      REWIND( numnat )                     ! read natext
64      READ  ( numnat, natext )
65
66      IF(lwp) THEN                         ! control print
67         WRITE(numout,*)
68         WRITE(numout,*) ' Namelist : natext'
69         WRITE(numout,*) '    atmospheric pCO2                         atcco2 = ',atcco2
70      ENDIF
71
72
73      !                               ! natbio : biological parameters
74      !                               ! ------------------------------
75      REWIND( numnat )                     ! read natbio
76      READ  ( numnat, natbio )
77
78      IF(lwp) THEN                         ! control print
79         WRITE(numout,*) ' Namelist : natbio'
80         WRITE(numout,*) '    mean rainratio                            caco3r    =', caco3r
81         WRITE(numout,*) '    diss. rate constant calcite (per month)   kdca      =', kdca
82         WRITE(numout,*) '    order of reaction for calcite dissolution nca       =', nca
83         WRITE(numout,*) '    part of calcite not dissolved in guts     part      =', part
84         WRITE(numout,*) '    mean Si/C ratio                           grosip    =', grosip
85         WRITE(numout,*) '    Calcite dissolution half saturation       dispo0    =', dispo0
86         WRITE(numout,*) '    Phosphate half saturation                 conc0     =', conc0
87         WRITE(numout,*) '    frequence pour la biologie                nrdttrc   =', nrdttrc
88         WRITE(numout,*) '    P-I slope                                 pislope   =', pislope
89         WRITE(numout,*) '    excretion ratio of phytoplankton          excret    =', excret
90         WRITE(numout,*) '    POC sinking speed                         wsbio     =', wsbio
91         WRITE(numout,*) '    quadratic mortality of phytoplankton      wchl      =', wchl
92         WRITE(numout,*) '    maximum quadratic mortality of diatoms    wchld     =', wchld
93         WRITE(numout,*) '    exsudation rate of zooplankton            resrat    =', resrat
94         WRITE(numout,*) '    phytoplankton mortality rate              mprat     =', mprat
95         WRITE(numout,*) '    zooplankton mortality rate                mzrat     =', mzrat
96         WRITE(numout,*) '    zoo preference for phyto                  xprefc    =', xprefc
97         WRITE(numout,*) '    zoo preference for POC                    xprefp    =', xprefp
98         WRITE(numout,*) '    maximal zoo grazing rate                  grazrat   =', grazrat
99         WRITE(numout,*) '    non assimilated fraction of phyto by zoo  unass     =', unass
100         WRITE(numout,*) '    half sturation constant for grazing       xkgraz    =', xkgraz
101         WRITE(numout,*) '    half saturation constant for mortality    xkmort    =', xkmort
102         WRITE(numout,*) '    half saturation constant for Si uptake    xksi1     =', xksi1
103         WRITE(numout,*) '    half saturation constant for Si/C         xksi2     =', xksi2
104         WRITE(numout,*) '    remineralisation rate of POC              xremip    =', xremip
105         WRITE(numout,*) '    remineralization rate of DOC              xremik    =', xremik
106         WRITE(numout,*) '    remineralization rate of Si               xsirem    =', xsirem
107         WRITE(numout,*) '    1st half-sat. of DOC remineralization     xkdoc1    =', xkdoc1
108         WRITE(numout,*) '    2nd half-sat. of DOC remineralization     xkdoc2    =', xkdoc2
109         WRITE(numout,*) '    excretion ratio of diatoms                excret2   =', excret2
110         WRITE(numout,*) '    exsudation rate of mesozooplankton        resrat2   =', resrat2
111         WRITE(numout,*) '    Diatoms mortality rate                    mprat2    =', mprat2
112         WRITE(numout,*) '    Phytoplankton minimum mortality rate      mpratm    =', mpratm
113         WRITE(numout,*) '    mesozooplankton mortality rate            mzrat2    =', mzrat2
114         WRITE(numout,*) '    zoo preference for zoo                    xprefz    =', xprefz
115         WRITE(numout,*) '    zoo preference for poc                    xprefpoc  =', xprefpoc
116         WRITE(numout,*) '    maximal mesozoo grazing rate              grazrat2  =', grazrat2
117         WRITE(numout,*) '    non assimilated fraction of P by mesozoo  unass2    =', unass2
118         WRITE(numout,*) '    Efficicency of Mesozoo growth             epsher2   =', epsher2
119         WRITE(numout,*) '    Efficiency of microzoo growth             epsher    =', epsher
120         WRITE(numout,*) '    half sturation constant for grazing 2     xkgraz2   =', xkgraz2
121         WRITE(numout,*) '    Maximum aggregation rate for diatoms      wchld     =', wchld
122         WRITE(numout,*) '    scavenging rate of Iron                   xlam1     =', xlam1
123         WRITE(numout,*) '    Fe/C in zooplankton                       ferat3    =', ferat3
124         WRITE(numout,*) '    Phosphate half saturation for diatoms     conc1     =', conc1
125         WRITE(numout,*) '    Iron half saturation for phyto            conc2     =', conc2
126         WRITE(numout,*) '    Iron half saturation for diatoms          conc3     =', conc3
127         WRITE(numout,*) '    NH4 half saturation for phyto             concnnh4  =', concnnh4
128         WRITE(numout,*) '    NH4 half saturation for diatoms           concdnh4  =', concdnh4
129         WRITE(numout,*) '    NH4 nitrification rate                    nitrif    =', nitrif
130         WRITE(numout,*) '    P-I slope  for diatoms                    pislope2  =', pislope2
131         WRITE(numout,*) '    Big particles sinking speed               wsbio2    =', wsbio2
132         WRITE(numout,*) '    Fraction of microzoo excretion as DOM     sigma1    =', sigma1
133         WRITE(numout,*) '    Fraction of mesozoo excretion as DOM      sigma2    =', sigma2
134         WRITE(numout,*) '    Microzoo preference for POM               zprefc    =', zprefc
135         WRITE(numout,*) '    Microzoo preference for Nanophyto         zprefp    =', zprefp
136         WRITE(numout,*) '    Microzoo preference for Diatoms           zprefd    =', zprefd
137         WRITE(numout,*) '    Minimum Chl/C in nanophytoplankton        chlcnm    =', chlcnm
138         WRITE(numout,*) '    Minimum Chl/C in diatoms                  chlcdm    =', chlcdm
139         WRITE(numout,*) '    Maximum Fe/C in nanophytoplankton         fecnm     =', fecnm
140         WRITE(numout,*) '    Minimum Fe/C in diatoms                   fecdm     =', fecdm
141         WRITE(numout,*) '    Coastal release of Iron                   sedfeinput=', sedfeinput
142      ENDIF
143
144      !                               ! natsms : SMS parameters
145      !                               ! -----------------------
146      REWIND( numnat )                     ! read natsms
147      READ  ( numnat, natsms )
148      IF(lwp) THEN
149         WRITE(numout,*) ' '
150         WRITE(numout,*) ' Namelist : natsms'
151         WRITE(numout,*) '    Dust input from the atmosphere           bdustfer  = ', bdustfer
152         WRITE(numout,*) '    River input of nutrients                 briver    = ', briver
153         WRITE(numout,*) '    Atmospheric deposition of N              bndepo    = ', bndepo
154         WRITE(numout,*) '    Fe input from sediments                  bsedinput = ', bsedinput
155      ENDIF
156
157#if defined key_trc_kriest
158
159      !                               ! natkriest : kriest parameters
160      !                               ! -----------------------------
161      REWIND( numnat )                     ! read natkriest
162      READ  ( numnat, natkriest )
163
164      IF(lwp) THEN
165         WRITE(numout,*)
166         WRITE(numout,*) ' Namelist : natkriest'
167         WRITE(numout,*) '    Sinking  exponent                        xkr_eta      = ', xkr_eta
168         WRITE(numout,*) '    N content exponent                       xkr_zeta     = ', xkr_zeta
169         WRITE(numout,*) '    Sinking factor                           xkr_sfact    = ', xkr_sfact
170         WRITE(numout,*) '    Stickiness                               xkr_stick    = ', xkr_stick
171         WRITE(numout,*) '    Minimum mass for Aggregates              xkr_mass_min = ', xkr_mass_min
172         WRITE(numout,*) '    Maximum mass for Aggregates              xkr_mass_max = ', xkr_mass_max
173         WRITE(numout,*) '    Size of particles in nano pool           xkr_dnano    = ', xkr_dnano
174         WRITE(numout,*) '    Size of particles in diatoms pool        xkr_ddiat    = ', xkr_ddiat
175         WRITE(numout,*) '    Size of particles in mesozoo pool        xkr_dmeso    = ', xkr_dmeso
176         WRITE(numout,*) '    Size of particles in aggregates pool     xkr_daggr    = ', xkr_daggr
177     ENDIF
178
179
180     ! Computation of some variables
181     xkr_massp = 5.7E-6 * 7.6 * xkr_mass_min**xkr_zeta
182     
183     ! max and min vertical particle speed
184     xkr_wsbio_min = xkr_sfact * xkr_mass_min**xkr_eta
185     xkr_wsbio_max = xkr_sfact * xkr_mass_max**xkr_eta
186     WRITE(numout,*) ' max and min vertical particle speed ', xkr_wsbio_min, xkr_wsbio_max
187     
188     !
189     !    effect of the sizes of the different living pools on particle numbers
190     !    nano = 2um-20um -> mean size=6.32 um -> ws=2.596 -> xnum=xnnano=2.337
191     !    diat and microzoo = 10um-200um -> 44.7 -> 8.732 -> xnum=xndiat=3.718
192     !    mesozoo = 200um-2mm -> 632.45 -> 45.14 -> xnum=xnmeso=7.147
193     !    aggregates = 200um-10mm -> 1414 -> 74.34 -> xnum=xnaggr=9.877
194     !    doc aggregates = 1um
195     ! ----------------------------------------------------------
196
197     xkr_nnano = 1. / ( xkr_massp * xkr_dnano )
198     xkr_ndiat = 1. / ( xkr_massp * xkr_ddiat )
199     xkr_nmeso = 1. / ( xkr_massp * xkr_dmeso )
200     xkr_naggr = 1. / ( xkr_massp * xkr_daggr )
201   
202#endif
203      !
204   END SUBROUTINE trc_lsm
Note: See TracBrowser for help on using the repository browser.