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.
Changeset 763 for branches/dev_001_GM/NEMO/TOP_SRC/SMS/trclsm.lobster1.h90 – NEMO

Ignore:
Timestamp:
2007-12-13T14:52:50+01:00 (16 years ago)
Author:
gm
Message:

dev_001_GM - Style only addition in TOP F90 h90 routines

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_001_GM/NEMO/TOP_SRC/SMS/trclsm.lobster1.h90

    r719 r763  
    1 !!---------------------------------------------------------------------- 
    2 !!                    ***  trclsm.lobster1.h90 *** 
    3 !!---------------------------------------------------------------------- 
     1   !!---------------------------------------------------------------------- 
     2   !!                     ***  trclsm.lobster1.h90  ***   
     3   !! TOP :   Definition some run parameter for LOBSTER biological model 
     4   !!---------------------------------------------------------------------- 
     5   !! History :    -  !  1999-10 (M.A. Foujols, M. Levy) original code 
     6   !!              -  !  2000-12 (O. Aumont, E. Kestenare) add sediments 
     7   !!             1.0 !  2003-08 (C. Ethe)  Original code 
     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 
    416CONTAINS 
    517 
    618   SUBROUTINE trc_lsm 
    719      !!---------------------------------------------------------------------- 
    8       !!                        trclsm.lobster1.h 
    9       !!                     ********************** 
     20      !!                     ***  trc_lsm  ***   
    1021      !! 
    11       !!  PURPOSE : 
    12       !!  --------- 
    13       !!     READS the specific NAMELIST for LOBSTER1 model 
     22      !! ** Purpose :   read LOBSTER namelist 
    1423      !! 
    15       !!   WORKSPACE :                : no 
    16       !!   --------- 
     24      !! ** input   :   file 'namelist.trc.sms' containing the following 
     25      !!             namelist: natbio, natopt, and natdbi ("key_trc_diabio") 
     26      !!---------------------------------------------------------------------- 
     27      CHARACTER (len=32) :: clname 
    1728      !! 
    18       !!   MODIFICATIONS: 
    19       !!   -------------- 
    20       !!      original  : 99-10 (M.A. Foujols, M. Levy) passive tracer 
    21       !!      additions : 00-12 (O. Aumont, E. Kestenare) add sediments 
    22       !! ---------------------------------------------------------------------- 
    23       !! local declarations 
    24       !! ================== 
    25       CHARACTER (len=32) :: clname 
    26  
    27       !!--------------------------------------------------------------------- 
    28       !!  TOP 1.0 , LOCEAN-IPSL (2005)  
    29    !! $Header$  
    30    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    31       !!--------------------------------------------------------------------- 
    32  
    33       ! 0. initializations 
    34       ! ------------------ 
    35      NAMELIST/natbio/apmin,azmin,anmin,admin,   & 
    36       &   redf,reddom,slopet,toptp,psinut,akno3,aknh4,rcchl,        & 
    37       &   rgamma,toptgz,tmaxgz,rgz,             & 
    38       &   rppz,taus,aks,filmax,rpnaz,rdnaz,eggzoo,tauzn,   & 
    39       &   tmmaxp,tmminp,tmmaxz,tmminz,anumin,afdmin,taudn,   & 
    40       &   vsed,tmumax,aki,tmaxr,tminr, taunn, taudomn,xhr,   & 
    41       &   sedlam, sedlostpoc,  & 
    42       &    fphylab,fzoolab,fdetlab,fdbod 
    43       NAMELIST/natopt/xkg0,xkr0,xkgp,xkrp,xlg,xlr,rpig 
     29      NAMELIST/natbio/ apmin, azmin, anmin, admin,                       & 
     30         &   redf, reddom, slopet, toptp, psinut, akno3, aknh4, rcchl,   & 
     31         &   rgamma, toptgz, tmaxgz, rgz,                                & 
     32         &   rppz, taus, aks, filmax, rpnaz, rdnaz, eggzoo, tauzn,       & 
     33         &   tmmaxp, tmminp, tmmaxz, tmminz, anumin, afdmin, taudn,      & 
     34         &   vsed, tmumax, aki, tmaxr, tminr, taunn, taudomn, xhr,       & 
     35         &   sedlam, sedlostpoc,                                         & 
     36         &   fphylab, fzoolab, fdetlab, fdbod 
     37      NAMELIST/natopt/ xkg0, xkr0, xkgp, xkrp, xlg, xlr, rpig 
    4438#if defined key_trc_diabio 
    4539      INTEGER :: ji 
    4640      NAMELIST/natdbi/ctrbio,ctrbil,ctrbiu,nwritebio 
    4741#endif 
    48  
    49       IF(lwp) THEN 
    50          WRITE(numout,*) ' ' 
    51          WRITE(numout,*) ' ROUTINE trclsm' 
    52          WRITE(numout,*) ' **************' 
    53          WRITE(numout,*) ' ' 
    54          WRITE(numout,*) ' namelist for lobster1 model' 
    55          WRITE(numout,*) ' ***************************' 
    56          WRITE(numout,*) ' ' 
    57       ENDIF 
    58  
    59  
     42      !!---------------------------------------------------------------------- 
     43 
     44      IF(lwp) WRITE(numout,*) 
     45      IF(lwp) WRITE(numout,*) ' trc_lsm : read LOBSTER 1 namelists' 
     46      IF(lwp) WRITE(numout,*) ' ~~~~~~~' 
     47 
     48      !                               ! Open the namelist file 
     49      !                               ! ---------------------- 
    6050      clname ='namelist.trc.sms' 
    6151      CALL ctlopn( numnat, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL',   & 
    6252         &           1, numout, .FALSE., 1 ) 
    6353 
    64       ! 1.4 namelist natbio : biological parameters 
    65       ! ------------------------------------------- 
    66  
    67       apmin = 0. 
     54      !                               ! natbio : biological parameters 
     55      !                               ! ------------------------------ 
     56      apmin = 0.                           ! default values 
    6857      azmin = 0. 
    6958      anmin = 0. 
     
    111100      fdbod = 0. 
    112101 
    113       READ(numnat,natbio) 
     102      REWIND( numnat )                     ! read natbio 
     103      READ  ( numnat, natbio ) 
    114104 
    115105      IF(lwp) THEN 
    116           WRITE(numout,*) 'natbio' 
    117           WRITE(numout,*) ' ' 
    118           WRITE(numout,*)     & 
    119           &   ' minimum phytoplancton concentration  apmin =', apmin 
    120           WRITE(numout,*)     & 
    121           &   ' minimum zooplancton   concentration  azmin =', azmin 
    122           WRITE(numout,*)     & 
    123           &   ' minimum nutrients     concentration  anmin =', anmin 
    124           WRITE(numout,*)     & 
    125           &   ' minimum detritus      concentration  admin =', admin 
    126           WRITE(numout,*)     & 
    127           &   ' redfield ratio  c:n                   redf =', redf 
    128           WRITE(numout,*)     & 
    129           &   ' van t hoff coefficient              slopet =', slopet 
    130           WRITE(numout,*)     & 
    131           &   ' optimal photosynthesis temperature   toptp =', toptp 
    132           WRITE(numout,*)     & 
    133           &   ' inhibition of no3 uptake by nh4      psinut =', psinut 
    134           WRITE(numout,*)     & 
    135           &   ' half-saturation nutrient for no3 uptake   akno3 =', akno3 
    136           WRITE(numout,*)     & 
    137           &   ' half-saturation nutrient for nh4 uptake   aknh4 =', aknh4 
    138           WRITE(numout,*)     & 
    139           &   ' carbone/chlorophyl ratio             rcchl =', rcchl 
    140           WRITE(numout,*)     & 
    141           &   ' phytoplankton exudation fraction    rgamma =', rgamma 
    142           WRITE(numout,*)     & 
    143           &   ' optimal temperature for zoo growth  toptgz =', toptgz 
    144           WRITE(numout,*)     & 
    145           &   ' maximal temperature for zoo growth  tmaxgz =', tmaxgz 
    146           WRITE(numout,*)     & 
    147           &   ' widtht of zoo temperature FUNCTION     rgz =', rgz 
    148           WRITE(numout,*)     & 
    149           &   ' zoo preference for phyto              rppz =', rppz 
    150           WRITE(numout,*)     & 
    151           &   ' maximal zoo grazing rate              taus =',86400*taus 
    152           WRITE(numout,*)     & 
    153           &   ' half saturation constant for zoo food  aks =', aks 
    154           WRITE(numout,*)     & 
    155           &   ' maximal mass clearance rate for zoo filmax =', filmax 
    156           WRITE(numout,*)     & 
    157           &   ' non-assimilated phyto by zoo         rpnaz =', rpnaz 
    158           WRITE(numout,*)     & 
    159           &   ' non-assimilated detritus by zoo      rdnaz =', rdnaz 
    160           WRITE(numout,*)     & 
    161           &   ' minimum  for zoo concentration      eggzoo =', eggzoo 
    162           WRITE(numout,*)     & 
    163           &   ' zoo specific excretion rate          tauzn =',86400   & 
    164           &   *tauzn 
    165           WRITE(numout,*)     & 
    166           &   ' maximal phyto mortality rate        tmmaxp =',86400   & 
    167           &   *tmmaxp 
    168           WRITE(numout,*)     & 
    169           &   ' minimal phyto mortality rate        tmminp =',86400   & 
    170           &   *tmminp 
    171           WRITE(numout,*)     & 
    172           &   ' maximal zoo mortality rate          tmmaxz =',86400   & 
    173           &   *tmmaxz 
    174           WRITE(numout,*)     & 
    175           &   ' minimal zoo mortality rate          tmminz =',86400   & 
    176           &   *tmminz 
    177           WRITE(numout,*)     & 
    178           &   ' nutrient threshold for phyto mort   anumin =', anumin 
    179           WRITE(numout,*)     & 
    180           &   ' food threshold for zoo mort         afdmin =', afdmin 
    181           WRITE(numout,*)     & 
    182           &   ' detrital breakdown rate              taudn =',86400   & 
    183           &   *taudn 
    184           WRITE(numout,*)     & 
    185           &   ' detritus sedimentation speed          vsed =',86400*vsed 
    186           WRITE(numout,*)     & 
    187           &   ' phyto max growth rate               tmumax =',86400   & 
    188           &   *tmumax 
    189           WRITE(numout,*)     & 
    190           &   ' light hlaf saturation constant         aki =', aki 
    191           WRITE(numout,*)     & 
    192           &   ' maximum damping for d z or p         tmaxr =', tmaxr 
    193           WRITE(numout,*)     & 
    194           &   ' damping-remineralisation rate        tminr =', tminr 
    195           WRITE(numout,*)     &  
    196           &   ' nitrification rate                   taunn =', taunn 
    197           WRITE(numout,*)     &  
    198           &   ' dom remineralisation rate          taudomn =', taudomn 
    199           WRITE(numout,*)     &  
    200           &   ' coeff for martin''s remineralistion    xhr =', xhr 
    201           WRITE(numout,*)     &  
    202           &   ' time coeff of POC in sediments      sedlam =', sedlam 
    203           WRITE(numout,*)     & 
    204           &   ' Sediment geol loss for POC  sedlostpoc =', sedlostpoc 
    205           WRITE(numout,*)     & 
    206           & ' NH4 fraction of phytoplankton exsudation fphylab =', fphylab 
    207           WRITE(numout,*)     & 
    208           & ' NH4 fraction of zooplankton excretion fzoolab =', fzoolab 
    209           WRITE(numout,*)     & 
    210           & ' NH4 fraction of detritus dissolution  fdetlab =', fdetlab 
    211           WRITE(numout,*)     & 
    212           & ' Zooplankton mortality fraction that goes to detritus fdbod =', fdbod 
     106          WRITE(numout,*) ' Namelist natbio' 
     107          WRITE(numout,*) '    minimum phytoplancton concentration                  apmin     =', apmin 
     108          WRITE(numout,*) '    minimum zooplancton   concentration                  azmin     =', azmin 
     109          WRITE(numout,*) '    minimum nutrients     concentration                  anmin     =', anmin 
     110          WRITE(numout,*) '    minimum detritus      concentration                  admin     =', admin 
     111          WRITE(numout,*) '    redfield ratio  c:n                                  redf      =', redf 
     112          WRITE(numout,*) '    van t hoff coefficient                               slopet    =', slopet 
     113          WRITE(numout,*) '    optimal photosynthesis temperature                   toptp     =', toptp 
     114          WRITE(numout,*) '    inhibition of no3 uptake by nh4                      psinut    =', psinut 
     115          WRITE(numout,*) '    half-saturation nutrient for no3 uptake              akno3     =', akno3 
     116          WRITE(numout,*) '    half-saturation nutrient for nh4 uptake              aknh4     =', aknh4 
     117          WRITE(numout,*) '    carbone/chlorophyl ratio                             rcchl     =', rcchl 
     118          WRITE(numout,*) '    phytoplankton exudation fraction                     rgamma    =', rgamma 
     119          WRITE(numout,*) '    optimal temperature for zoo growth                   toptgz    =', toptgz 
     120          WRITE(numout,*) '    maximal temperature for zoo growth                   tmaxgz    =', tmaxgz 
     121          WRITE(numout,*) '    widtht of zoo temperature FUNCTION                   rgz       =', rgz 
     122          WRITE(numout,*) '    zoo preference for phyto                             rppz      =', rppz 
     123          WRITE(numout,*) '    maximal zoo grazing rate                             taus      =', 86400 * taus, ' d' 
     124          WRITE(numout,*) '    half saturation constant for zoo food                aks       =', aks 
     125          WRITE(numout,*) '    maximal mass clearance rate for zoo                  filmax    =', filmax 
     126          WRITE(numout,*) '    non-assimilated phyto by zoo                         rpnaz     =', rpnaz 
     127          WRITE(numout,*) '    non-assimilated detritus by zoo                      rdnaz     =', rdnaz 
     128          WRITE(numout,*) '    minimum  for zoo concentration                       eggzoo    =', eggzoo 
     129          WRITE(numout,*) '    zoo specific excretion rate                          tauzn     =', 86400 * tauzn 
     130          WRITE(numout,*) '    maximal phyto mortality rate                         tmmaxp    =', 86400 * tmmaxp 
     131          WRITE(numout,*) '    minimal phyto mortality rate                         tmminp    =', 86400 * tmminp 
     132          WRITE(numout,*) '    maximal zoo mortality rate                           tmmaxz    =', 86400 * tmmaxz 
     133          WRITE(numout,*) '    minimal zoo mortality rate                           tmminz    =', 86400 * tmminz 
     134          WRITE(numout,*) '    nutrient threshold for phyto mort                    anumin    =', anumin 
     135          WRITE(numout,*) '    food threshold for zoo mort                          afdmin    =', afdmin 
     136          WRITE(numout,*) '    detrital breakdown rate                              taudn     =', 86400 * taudn , ' d' 
     137          WRITE(numout,*) '    detritus sedimentation speed                         vsed      =', 86400 * vsed  , ' d' 
     138          WRITE(numout,*) '    phyto max growth rate                                tmumax    =', 86400 * tmumax, ' d' 
     139          WRITE(numout,*) '    light hlaf saturation constant                       aki       =', aki 
     140          WRITE(numout,*) '    maximum damping for d z or p                         tmaxr     =', tmaxr 
     141          WRITE(numout,*) '    damping-remineralisation rate                        tminr     =', tminr 
     142          WRITE(numout,*) '    nitrification rate                                   taunn     =', taunn 
     143          WRITE(numout,*) '    dom remineralisation rate                            taudomn   =', taudomn 
     144          WRITE(numout,*) '    coeff for martin''s remineralistion                  xhr       =', xhr 
     145          WRITE(numout,*) '    time coeff of POC in sediments                       sedlam    =', sedlam 
     146          WRITE(numout,*) '    Sediment geol loss for POC                           sedlostpoc=', sedlostpoc 
     147          WRITE(numout,*) '    NH4 fraction of phytoplankton exsudation             fphylab   =', fphylab 
     148          WRITE(numout,*) '    NH4 fraction of zooplankton excretion                fzoolab   =', fzoolab 
     149          WRITE(numout,*) '    NH4 fraction of detritus dissolution                 fdetlab   =', fdetlab 
     150          WRITE(numout,*) '    Zooplankton mortality fraction that goes to detritus fdbod     =', fdbod 
    213151      ENDIF 
    214152 
    215       ! 1.5 namelist natopt : parameters for optic 
    216       ! ------------------------------------------ 
    217  
    218       xkg0  = 0. 
     153      !                               ! natopt : optical parameters 
     154      !                               ! --------------------------- 
     155      xkg0  = 0.                           ! default values 
    219156      xkr0  = 0. 
    220157      xkgp  = 0. 
     
    224161      rpig  = 0. 
    225162 
    226       READ(numnat,natopt) 
     163      REWIND( numnat )                     ! read natopt 
     164      READ  ( numnat, natopt )        
     165 
     166      IF(lwp) THEN                         ! control print 
     167         WRITE(numout,*) 
     168         WRITE(numout,*) ' Namelist natopt' 
     169         WRITE(numout,*) '    green   water absorption coeff                       xkg0  = ', xkg0 
     170         WRITE(numout,*) '    red water absorption coeff                           xkr0  = ', xkr0 
     171         WRITE(numout,*) '    pigment red absorption coeff                         xkrp  = ', xkrp 
     172         WRITE(numout,*) '    pigment green absorption coeff                       xkgp  = ', xkgp 
     173         WRITE(numout,*) '    green chl exposant                                   xlg   = ', xlg 
     174         WRITE(numout,*) '    red   chl exposant                                   xlr   = ', xlr 
     175         WRITE(numout,*) '    chla/chla+phea ratio                                 rpig  = ', rpig 
     176      ENDIF 
     177 
     178#if defined key_trc_diabio 
     179 
     180      !                               ! natdbi : bio diagnostics 
     181      !                               ! ------------------------ 
     182      nwritebio = 10                     ! default values 
     183      DO ji = 1, jpdiabio 
     184         IF(     ji <  10 ) THEN   ;   WRITE (ctrbio(ji),'("BIO_",I1)') ji      ! short name 
     185         ELSEIF (ji < 100 ) THEN   ;   WRITE (ctrbio(ji),'("BIO_",I2)') ji    
     186         ELSE                      ;   WRITE (ctrbio(ji),'("BIO_",I3)') ji 
     187         ENDIF 
     188         WRITE(ctrbil(ji),'("BIOLOGICAL TREND NUMBER ",I2)') ji                 ! long name 
     189         ctrbiu(ji) = 'mmoleN/m3/s '                                            ! units 
     190      END DO 
     191 
     192      REWIND( numnat )                     ! read natdbi 
     193      READ  ( numnat, natdbi )   
    227194 
    228195      IF(lwp) THEN 
    229          WRITE(numout,*) 'natopt' 
    230          WRITE(numout,*) ' ' 
    231          WRITE(numout,*) ' green   water absorption coeff  xkg0  = ',xkg0 
    232          WRITE(numout,*) ' red water absorption coeff      xkr0  = ',xkr0 
    233          WRITE(numout,*) ' pigment red absorption coeff    xkrp  = ',xkrp 
    234          WRITE(numout,*) ' pigment green absorption coeff  xkgp  = ',xkgp 
    235          WRITE(numout,*) ' green chl exposant              xlg   = ',xlg 
    236          WRITE(numout,*) ' red   chl exposant              xlr   = ',xlr 
    237          WRITE(numout,*) ' chla/chla+phea ratio            rpig  = ',rpig 
    238          WRITE(numout,*) ' ' 
    239  
    240       ENDIF 
    241  
    242 #if defined key_trc_diabio 
    243  
    244       ! NAMELIST : natdbi  
    245  
    246       ! default name for biological trends : short and long name, units 
    247  
    248       DO ji=1,jpdiabio 
    249          IF (ji < 10) THEN  
    250             WRITE (ctrbio(ji),'("BIO_",I1)') ji 
    251          ELSE IF (ji < 100) THEN 
    252             WRITE (ctrbio(ji),'("BIO_",I2)') ji 
    253          ELSE 
    254             WRITE (ctrbio(ji),'("BIO_",I3)') ji 
    255          ENDIF 
    256          WRITE (ctrbil(ji),'("BIOLOGICAL TREND NUMBER ",I2)') ji 
    257          ctrbiu(ji)='mmoleN/m3/s ' 
    258       END DO 
    259  
    260       nwritebio = 10 
    261  
    262       READ(numnat,natdbi) 
    263  
    264       IF(lwp) THEN 
    265          WRITE(numout,*) 'natdbi' 
    266          WRITE(numout,*) ' ' 
    267          WRITE(numout,*)      & 
    268             &   ' frequency of outputs for biological outputs = '    & 
    269             &   ,nwritebio 
    270          WRITE(numout,*) ' ' 
    271          DO ji=1,jpdiabio 
    272             WRITE(numout,*)     & 
    273                &   'name of biological trend number :',ji,' : ',ctrbio(ji)   
    274             WRITE(numout,*) ctrbil(ji)   
    275             WRITE(numout,*) ' in unit = ',ctrbiu(ji) 
     196         WRITE(numout,*) 
     197         WRITE(numout,*) ' Namelist natdbi' 
     198         WRITE(numout,*) '    frequency of outputs for biological outputs  nwritebio = ', nwritebio 
     199         DO ji = 1, jpdiabio 
     200            WRITE(numout,*) '     name of biological trend No :',ji,' : ',ctrbio(ji), ctrbil(ji), ' in ', ctrbiu(ji) 
    276201         END DO 
    277202      END IF 
    278203#endif 
    279  
     204      ! 
    280205   END SUBROUTINE trc_lsm 
Note: See TracChangeset for help on using the changeset viewer.