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

source: branches/dev_001_GM/NEMO/TOP_SRC/PISCES/trclsm_pisces.F90 @ 773

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

dev_001_GM - small changes : compilation OK

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