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 3680 for branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/trcnam_pisces.F90 – NEMO

Ignore:
Timestamp:
2012-11-27T15:42:24+01:00 (11 years ago)
Author:
rblod
Message:

First commit of the final branch for 2012 (future nemo_3_5), see ticket #1028

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/trcnam_pisces.F90

    r3294 r3680  
    11MODULE trcnam_pisces 
    22   !!====================================================================== 
    3    !!                      ***  MODULE trcnam_lobster  *** 
     3   !!                      ***  MODULE trcnam_pisces  *** 
    44   !! TOP :   initialisation of some run parameters for PISCES bio-model 
    55   !!====================================================================== 
     
    99   !!             2.0  !  2007-12  (C. Ethe, G. Madec) from trcnam.pisces.h90 
    1010   !!---------------------------------------------------------------------- 
    11 #if defined key_pisces 
     11#if defined key_pisces || defined key_pisces_reduced 
    1212   !!---------------------------------------------------------------------- 
    1313   !!   'key_pisces'   :                                   PISCES bio-model 
     
    1919   USE trc             ! TOP variables 
    2020   USE sms_pisces      ! sms trends 
     21   USE trdmod_trc_oce 
    2122   USE iom             ! I/O manager 
    2223 
     
    4849      !! 
    4950      INTEGER :: jl, jn 
    50       TYPE(DIAG), DIMENSION(jp_pisces_2d) :: pisdia2d 
    51       TYPE(DIAG), DIMENSION(jp_pisces_3d) :: pisdia3d 
     51      TYPE(DIAG), DIMENSION(jp_pisces_2d)  :: pisdia2d 
     52      TYPE(DIAG), DIMENSION(jp_pisces_3d)  :: pisdia3d 
     53      TYPE(DIAG), DIMENSION(jp_pisces_trd) :: pisdiabio 
     54      CHARACTER(LEN=20)   ::   clname 
    5255      !! 
    53       NAMELIST/nampisbio/ nrdttrc, wsbio, xkmort, ferat3, wsbio2 
    54 #if defined key_kriest 
    55       NAMELIST/nampiskrp/ xkr_eta, xkr_zeta, xkr_mass_min, xkr_mass_max 
     56      NAMELIST/nampisdia/ pisdia3d, pisdia2d     ! additional diagnostics 
     57#if defined key_pisces_reduced 
     58      NAMELIST/nampisdbi/ pisdiabio 
    5659#endif 
    57       NAMELIST/nampisdia/ pisdia3d, pisdia2d     ! additional diagnostics 
    58       NAMELIST/nampisdmp/ ln_pisdmp, nn_pisdmp, ln_pisclo 
    5960 
    6061      !!---------------------------------------------------------------------- 
    6162 
    6263      IF(lwp) WRITE(numout,*) 
    63       IF(lwp) WRITE(numout,*) ' trc_nam_pisces : read PISCES namelists' 
     64      clname = 'namelist_pisces' 
     65#if defined key_pisces 
     66      IF(lwp) WRITE(numout,*) ' trc_nam_pisces : read PISCES namelist' 
     67#else 
     68      IF(lwp) WRITE(numout,*) ' trc_nam_pisces : read LOBSTER namelist' 
     69#endif 
    6470      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~' 
     71      CALL ctl_opn( numnatp, TRIM( clname ), 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    6572 
    66  
    67       !                               ! Open the namelist file 
    68       !                               ! ---------------------- 
    69       CALL ctl_opn( numnatp, 'namelist_pisces', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    70  
    71       REWIND( numnatp )                     
    72       READ  ( numnatp, nampisbio ) 
    73  
    74       IF(lwp) THEN                         ! control print 
    75          WRITE(numout,*) ' Namelist : nampisbio' 
    76          WRITE(numout,*) '    frequence pour la biologie                nrdttrc   =', nrdttrc 
    77          WRITE(numout,*) '    POC sinking speed                         wsbio     =', wsbio 
    78          WRITE(numout,*) '    half saturation constant for mortality    xkmort    =', xkmort 
    79          WRITE(numout,*) '    Fe/C in zooplankton                       ferat3    =', ferat3 
    80          WRITE(numout,*) '    Big particles sinking speed               wsbio2    =', wsbio2 
    81       ENDIF 
    82  
    83 #if defined key_kriest 
    84  
    85       !                               ! nampiskrp : kriest parameters 
    86       !                               ! ----------------------------- 
    87       xkr_eta      = 0.62         
    88       xkr_zeta     = 1.62         
    89       xkr_mass_min = 0.0002      
    90       xkr_mass_max = 1.       
    91  
    92       REWIND( numnatp )                     ! read natkriest 
    93       READ  ( numnatp, nampiskrp ) 
    94  
    95       IF(lwp) THEN 
    96          WRITE(numout,*) 
    97          WRITE(numout,*) ' Namelist : nampiskrp' 
    98          WRITE(numout,*) '    Sinking  exponent                        xkr_eta      = ', xkr_eta 
    99          WRITE(numout,*) '    N content exponent                       xkr_zeta     = ', xkr_zeta 
    100          WRITE(numout,*) '    Minimum mass for Aggregates              xkr_mass_min = ', xkr_mass_min 
    101          WRITE(numout,*) '    Maximum mass for Aggregates              xkr_mass_max = ', xkr_mass_max 
    102          WRITE(numout,*) 
    103      ENDIF 
    104  
    105  
    106      ! Computation of some variables 
    107      xkr_massp = 5.7E-6 * 7.6 * xkr_mass_min**xkr_zeta 
    108  
    109 #endif 
    11073      ! 
    11174      IF( .NOT.lk_iomput .AND. ln_diatrc ) THEN 
     
    162125      ENDIF 
    163126 
    164       REWIND( numnatp ) 
    165       READ  ( numnatp, nampisdmp ) 
     127#if defined key_pisces_reduced 
    166128 
    167       IF(lwp) THEN                         ! control print 
    168          WRITE(numout,*) 
    169          WRITE(numout,*) ' Namelist : nampisdmp' 
    170          WRITE(numout,*) '    Relaxation of tracer to glodap mean value             ln_pisdmp      =', ln_pisdmp 
    171          WRITE(numout,*) '    Frequency of Relaxation                               nn_pisdmp      =', nn_pisdmp 
    172          WRITE(numout,*) '    Restoring of tracer to initial value  on closed seas  ln_pisclo      =', ln_pisclo 
    173          WRITE(numout,*) ' ' 
    174       ENDIF 
     129      IF( ( .NOT.lk_iomput .AND. ln_diabio ) .OR. lk_trdmld_trc ) THEN 
     130         ! 
     131         ! Namelist nampisdbi 
     132         ! ------------------- 
     133         DO jl = 1, jp_pisces_trd 
     134            IF(     jl <  10 ) THEN   ;   WRITE (pisdiabio(jl)%sname,'("BIO_",I1)') jl      ! short name 
     135            ELSEIF (jl < 100 ) THEN   ;   WRITE (pisdiabio(jl)%sname,'("BIO_",I2)') jl 
     136            ELSE                      ;   WRITE (pisdiabio(jl)%sname,'("BIO_",I3)') jl 
     137            ENDIF 
     138            WRITE(pisdiabio(jl)%lname,'("BIOLOGICAL TREND NUMBER ",I2)') jl                 ! long name 
     139            pisdiabio(jl)%units = 'mmoleN/m3/s '                                            ! units 
     140         END DO 
     141 
     142         REWIND( numnatp ) 
     143         READ  ( numnatp, nampisdbi ) 
     144 
     145         DO jl = 1, jp_pisces_trd 
     146            jn = jp_pcs0_trd + jl - 1 
     147            ctrbio(jl) = pisdiabio(jl)%sname 
     148            ctrbil(jl) = pisdiabio(jl)%lname 
     149            ctrbiu(jl) = pisdiabio(jl)%units 
     150         END DO 
     151 
     152         IF(lwp) THEN                   ! control print 
     153            WRITE(numout,*) 
     154            WRITE(numout,*) ' Namelist : nampisdbi' 
     155            DO jl = 1, jp_pisces_trd 
     156               jn = jp_pcs0_trd + jl - 1 
     157               WRITE(numout,*) '  biological trend No : ', jn, '    short name : ', ctrbio(jn), & 
     158                 &             '  long name  : ', ctrbio(jn), '   unit : ', ctrbio(jn) 
     159            END DO 
     160            WRITE(numout,*) ' ' 
     161         END IF 
     162         ! 
     163      END IF 
     164 
     165#endif 
    175166 
    176167   END SUBROUTINE trc_nam_pisces 
Note: See TracChangeset for help on using the changeset viewer.