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 9169 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

Ignore:
Timestamp:
2017-12-26T17:32:56+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: all SRC: finalize the removal of useless warning when reading namelist_cfg + remove all nn_closea + nn_msh replaced by a logical

Location:
branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zfechem.F90

    r9125 r9169  
    77   !!             3.6  !  2015-05  (O. Aumont) PISCES quota 
    88   !!---------------------------------------------------------------------- 
    9    !!   p4z_fechem       :  Compute remineralization/scavenging of iron 
    10    !!   p4z_fechem_init  :  Initialisation of parameters for remineralisation 
    11    !!   p4z_fechem_alloc :  Allocate remineralisation variables 
     9   !!   p4z_fechem       : Compute remineralization/scavenging of iron 
     10   !!   p4z_fechem_init  : Initialisation of parameters for remineralisation 
     11   !!   p4z_fechem_alloc : Allocate remineralisation variables 
    1212   !!---------------------------------------------------------------------- 
    13    USE oce_trc         !  shared variables between ocean and passive tracers 
    14    USE trc             !  passive tracers common variables  
    15    USE sms_pisces      !  PISCES Source Minus Sink variables 
    16    USE p4zche          !  chemical model 
    17    USE p4zsbc          !  Boundary conditions from sediments 
    18    USE prtctl_trc      !  print control for debugging 
    19    USE iom             !  I/O manager 
     13   USE oce_trc         ! shared variables between ocean and passive tracers 
     14   USE trc             ! passive tracers common variables  
     15   USE sms_pisces      ! PISCES Source Minus Sink variables 
     16   USE p4zche          ! chemical model 
     17   USE p4zsbc          ! Boundary conditions from sediments 
     18   USE prtctl_trc      ! print control for debugging 
     19   USE iom             ! I/O manager 
    2020 
    2121   IMPLICIT NONE 
    2222   PRIVATE 
    2323 
    24    PUBLIC   p4z_fechem      ! called in p4zbio.F90 
    25    PUBLIC   p4z_fechem_init ! called in trcsms_pisces.F90 
    26  
    27    !! * Shared module variables 
    28    LOGICAL          ::  ln_fechem    !: boolean for complex iron chemistry following Tagliabue and voelker 
    29    LOGICAL          ::  ln_ligvar    !: boolean for variable ligand concentration following Tagliabue and voelker 
    30    LOGICAL          ::  ln_fecolloid !: boolean for variable colloidal fraction 
    31    REAL(wp), PUBLIC ::  xlam1        !: scavenging rate of Iron  
    32    REAL(wp), PUBLIC ::  xlamdust     !: scavenging rate of Iron by dust  
    33    REAL(wp), PUBLIC ::  ligand       !: ligand concentration in the ocean  
    34    REAL(wp), PUBLIC ::  kfep         !: rate constant for nanoparticle formation 
    35  
    36    REAL(wp) :: kl1, kl2, kb1, kb2, ks, kpr, spd, con, kth 
     24   PUBLIC   p4z_fechem        ! called in p4zbio.F90 
     25   PUBLIC   p4z_fechem_init   ! called in trcsms_pisces.F90 
     26 
     27   LOGICAL          ::   ln_fechem    !: boolean for complex iron chemistry following Tagliabue and voelker 
     28   LOGICAL          ::   ln_ligvar    !: boolean for variable ligand concentration following Tagliabue and voelker 
     29   LOGICAL          ::   ln_fecolloid !: boolean for variable colloidal fraction 
     30   REAL(wp), PUBLIC ::   xlam1        !: scavenging rate of Iron  
     31   REAL(wp), PUBLIC ::   xlamdust     !: scavenging rate of Iron by dust  
     32   REAL(wp), PUBLIC ::   ligand       !: ligand concentration in the ocean  
     33   REAL(wp), PUBLIC ::   kfep         !: rate constant for nanoparticle formation 
     34 
     35   REAL(wp) :: kl1, kl2, kb1, kb2, ks, kpr, spd, con, kth      !!gm  <<<== DOCTOR names SVP !!! 
    3736 
    3837   !!---------------------------------------------------------------------- 
     
    5655      !!                    and one particulate form (ln_fechem) 
    5756      !!--------------------------------------------------------------------- 
    58       ! 
    59       INTEGER, INTENT(in) ::   kt, knt ! ocean time step 
     57      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step 
    6058      ! 
    6159      INTEGER  ::   ji, jj, jk, jic, jn 
     
    6765      REAL(wp) ::   zzFeL1, zzFeL2, zzFe2, zzFeP, zzFe3, zzstrn2 
    6866      REAL(wp) ::   zrum, zcodel, zargu, zlight 
    69       REAL(wp) :: zkox, zkph1, zkph2, zph, zionic, ztligand 
    70       REAL(wp) :: za, zb, zc, zkappa1, zkappa2, za0, za1, za2 
    71       REAL(wp) :: zxs, zfunc, zp, zq, zd, zr, zphi, zfff, zp3, zq2 
    72       REAL(wp) :: ztfe, zoxy, zhplus 
    73       REAL(wp) :: zaggliga, zaggligb 
    74       REAL(wp) :: dissol, zligco 
     67      REAL(wp) ::   zkox, zkph1, zkph2, zph, zionic, ztligand 
     68      REAL(wp) ::   za, zb, zc, zkappa1, zkappa2, za0, za1, za2 
     69      REAL(wp) ::   zxs, zfunc, zp, zq, zd, zr, zphi, zfff, zp3, zq2 
     70      REAL(wp) ::   ztfe, zoxy, zhplus 
     71      REAL(wp) ::   zaggliga, zaggligb 
     72      REAL(wp) ::   dissol, zligco 
    7573      CHARACTER (len=25) :: charout 
    76       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zTL1, zFe3, ztotlig, precip, zFeL1 
    77       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zFeL2, zTL2, zFe2, zFeP 
    78       REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zstrn, zstrn2 
     74      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zTL1, zFe3, ztotlig, precip, zFeL1 
     75      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zFeL2, zTL2, zFe2, zFeP 
     76      REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) ::   zstrn, zstrn2 
    7977      !!--------------------------------------------------------------------- 
    8078      ! 
     
    384382      NAMELIST/nampisfer/ ln_fechem, ln_ligvar, ln_fecolloid, xlam1, xlamdust, ligand, kfep  
    385383      !!---------------------------------------------------------------------- 
    386  
    387       REWIND( numnatp_ref )              ! Namelist nampisfer in reference namelist : Pisces iron chemistry 
     384      ! 
     385      IF(lwp) THEN 
     386         WRITE(numout,*) 
     387         WRITE(numout,*) 'p4z_rem_init : Initialization of iron chemistry parameters' 
     388         WRITE(numout,*) '~~~~~~~~~~~~' 
     389      ENDIF 
     390      ! 
     391      REWIND( numnatp_ref )            ! Namelist nampisfer in reference namelist : Pisces iron chemistry 
    388392      READ  ( numnatp_ref, nampisfer, IOSTAT = ios, ERR = 901) 
    389 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisfer in reference namelist', lwp ) 
    390  
    391       REWIND( numnatp_cfg )              ! Namelist nampisfer in configuration namelist : Pisces iron chemistry 
     393901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisfer in reference namelist', lwp ) 
     394      REWIND( numnatp_cfg )            ! Namelist nampisfer in configuration namelist : Pisces iron chemistry 
    392395      READ  ( numnatp_cfg, nampisfer, IOSTAT = ios, ERR = 902 ) 
    393 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampisfer in configuration namelist', lwp ) 
    394       IF(lwm) WRITE ( numonp, nampisfer ) 
    395  
    396       IF(lwp) THEN                         ! control print 
    397          WRITE(numout,*) ' ' 
    398          WRITE(numout,*) ' Namelist parameters for Iron chemistry, nampisfer' 
    399          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    400          WRITE(numout,*) '    enable complex iron chemistry scheme      ln_fechem    =', ln_fechem 
    401          WRITE(numout,*) '    variable concentration of ligand          ln_ligvar    =', ln_ligvar 
    402          WRITE(numout,*) '    Variable colloidal fraction of Fe3+       ln_fecolloid =', ln_fecolloid 
    403          WRITE(numout,*) '    scavenging rate of Iron                   xlam1        =', xlam1 
    404          WRITE(numout,*) '    scavenging rate of Iron by dust           xlamdust     =', xlamdust 
    405          WRITE(numout,*) '    ligand concentration in the ocean         ligand       =', ligand 
    406          WRITE(numout,*) '    rate constant for nanoparticle formation  kfep         =', kfep 
    407       ENDIF 
    408       ! 
    409       IF( ln_fechem ) THEN 
    410          ! initialization of some constants used by the complexe chemistry scheme 
    411          ! ---------------------------------------------------------------------- 
     396902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisfer in configuration namelist', lwp ) 
     397      IF(lwm) WRITE( numonp, nampisfer ) 
     398 
     399      IF(lwp) THEN                     ! control print 
     400         WRITE(numout,*) '   Namelist : nampisfer' 
     401         WRITE(numout,*) '      enable complex iron chemistry scheme      ln_fechem    =', ln_fechem 
     402         WRITE(numout,*) '      variable concentration of ligand          ln_ligvar    =', ln_ligvar 
     403         WRITE(numout,*) '      Variable colloidal fraction of Fe3+       ln_fecolloid =', ln_fecolloid 
     404         WRITE(numout,*) '      scavenging rate of Iron                   xlam1        =', xlam1 
     405         WRITE(numout,*) '      scavenging rate of Iron by dust           xlamdust     =', xlamdust 
     406         WRITE(numout,*) '      ligand concentration in the ocean         ligand       =', ligand 
     407         WRITE(numout,*) '      rate constant for nanoparticle formation  kfep         =', kfep 
     408      ENDIF 
     409      ! 
     410      IF( ln_fechem ) THEN             ! set some constants used by the complexe chemistry scheme 
     411         ! 
    412412         spd = 3600. * 24. 
    413413         con = 1.E9 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zflx.F90

    r9125 r9169  
    44   !! TOP :   PISCES CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE 
    55   !!====================================================================== 
    6    !! History :    -   !  1988-07  (E. MAIER-REIMER) Original code 
    7    !!              -   !  1998     (O. Aumont) additions 
    8    !!              -   !  1999     (C. Le Quere) modifications 
    9    !!             1.0  !  2004     (O. Aumont) modifications 
    10    !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    11    !!                  !  2011-02  (J. Simeon, J. Orr) Include total atm P correction  
     6   !! History :   -   !  1988-07  (E. MAIER-REIMER) Original code 
     7   !!             -   !  1998     (O. Aumont) additions 
     8   !!             -   !  1999     (C. Le Quere) modifications 
     9   !!            1.0  !  2004     (O. Aumont) modifications 
     10   !!            2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
     11   !!                 !  2011-02  (J. Simeon, J. Orr) Include total atm P correction  
    1212   !!---------------------------------------------------------------------- 
    1313   !!   p4z_flx       :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE 
     
    1515   !!   p4z_patm      :   Read sfc atm pressure [atm] for each grid cell 
    1616   !!---------------------------------------------------------------------- 
    17    USE oce_trc                      !  shared variables between ocean and passive tracers  
    18    USE trc                          !  passive tracers common variables 
    19    USE sms_pisces                   !  PISCES Source Minus Sink variables 
    20    USE p4zche                       !  Chemical model 
    21    USE prtctl_trc                   !  print control for debugging 
    22    USE iom                          !  I/O manager 
    23    USE fldread                      !  read input fields 
     17   USE oce_trc        !  shared variables between ocean and passive tracers  
     18   USE trc            !  passive tracers common variables 
     19   USE sms_pisces     !  PISCES Source Minus Sink variables 
     20   USE p4zche         !  Chemical model 
     21   USE prtctl_trc     !  print control for debugging 
     22   USE iom            !  I/O manager 
     23   USE fldread        !  read input fields 
    2424 
    2525   IMPLICIT NONE 
     
    3030   PUBLIC   p4z_flx_alloc   
    3131 
    32    !                               !!** Namelist  nampisext  ** 
    33    REAL(wp)          ::  atcco2     !: pre-industrial atmospheric [co2] (ppm)     
    34    LOGICAL           ::  ln_co2int  !: flag to read in a file and interpolate atmospheric pco2 or not 
    35    CHARACTER(len=34) ::  clname     !: filename of pco2 values 
    36    INTEGER           ::  nn_offset  !: Offset model-data start year (default = 0)  
     32   !                                 !!** Namelist  nampisext  ** 
     33   REAL(wp)          ::   atcco2      !: pre-industrial atmospheric [co2] (ppm)   
     34   LOGICAL           ::   ln_co2int   !: flag to read in a file and interpolate atmospheric pco2 or not 
     35   CHARACTER(len=34) ::   clname      !: filename of pco2 values 
     36   INTEGER           ::   nn_offset   !: Offset model-data start year (default = 0)  
    3737 
    3838   !!  Variables related to reading atmospheric CO2 time history     
    39    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) :: atcco2h, years 
    40    INTEGER  :: nmaxrec, numco2 
    41  
    42    !                               !!* nampisatm namelist (Atmospheric PRessure) * 
     39   INTEGER                                   ::   nmaxrec, numco2   ! 
     40   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   atcco2h, years    ! 
     41 
     42   !                                  !!* nampisatm namelist (Atmospheric PRessure) * 
    4343   LOGICAL, PUBLIC ::   ln_presatm     !: ref. pressure: global mean Patm (F) or a constant (F) 
    4444   LOGICAL, PUBLIC ::   ln_presatmco2  !: accounting for spatial atm CO2 in the compuation of carbon flux (T) or not (F) 
    4545 
    46    REAL(wp) , ALLOCATABLE, SAVE, DIMENSION(:,:) ::  patm      ! atmospheric pressure at kt                 [N/m2] 
    47    TYPE(FLD), ALLOCATABLE,       DIMENSION(:)   ::  sf_patm   ! structure of input fields (file informations, fields read) 
    48    TYPE(FLD), ALLOCATABLE,       DIMENSION(:)   ::  sf_atmco2 ! structure of input fields (file informations, fields read) 
    49  
    50    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: satmco2   !: atmospheric pco2  
    51  
    52    REAL(wp) ::  xconv  = 0.01_wp / 3600._wp !: coefficients for conversion  
     46   REAL(wp) , ALLOCATABLE, SAVE, DIMENSION(:,:) ::   patm      ! atmospheric pressure at kt                 [N/m2] 
     47   TYPE(FLD), ALLOCATABLE,       DIMENSION(:)   ::   sf_patm   ! structure of input fields (file informations, fields read) 
     48   TYPE(FLD), ALLOCATABLE,       DIMENSION(:)   ::   sf_atmco2 ! structure of input fields (file informations, fields read) 
     49 
     50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  satmco2   !: atmospheric pco2  
     51 
     52   REAL(wp) ::   xconv  = 0.01_wp / 3600._wp  !: coefficients for conversion  
    5353 
    5454   !!---------------------------------------------------------------------- 
     
    7070      !!              - Add option for time-interpolation of atcco2.txt   
    7171      !!--------------------------------------------------------------------- 
    72       ! 
    7372      INTEGER, INTENT(in) ::   kt, knt   ! 
    7473      ! 
     
    7978      REAL(wp) ::   zph, zdic, zsch_o2, zsch_co2 
    8079      REAL(wp) ::   zyr_dec, zdco2dt 
    81       CHARACTER (len=25) :: charout 
    82       REAL(wp), DIMENSION(jpi,jpj) :: zkgco2, zkgo2, zh2co3, zoflx,  zpco2atm   
    83       REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zw2d 
     80      CHARACTER (len=25) ::   charout 
     81      REAL(wp), DIMENSION(jpi,jpj) ::   zkgco2, zkgo2, zh2co3, zoflx,  zpco2atm   
     82      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zw2d 
    8483      !!--------------------------------------------------------------------- 
    8584      ! 
    8685      IF( ln_timing )   CALL timing_start('p4z_flx') 
    8786      ! 
    88  
    8987      ! SURFACE CHEMISTRY (PCO2 AND [H+] IN 
    9088      !     SURFACE LAYER); THE RESULT OF THIS CALCULATION 
    9189      !     IS USED TO COMPUTE AIR-SEA FLUX OF CO2 
    9290 
    93       IF( kt /= nit000 .AND. .NOT.l_co2cpl .AND. knt == 1 ) CALL p4z_patm( kt )    ! Get sea-level pressure (E&K [1981] climatology) for use in flux calcs 
     91      IF( kt /= nit000 .AND. .NOT.l_co2cpl .AND. knt == 1 )   CALL p4z_patm( kt )   ! Get sea-level pressure (E&K [1981] climatology) for use in flux calcs 
    9492 
    9593      IF( ln_co2int .AND. .NOT.ln_presatmco2 .AND. .NOT.l_co2cpl ) THEN  
     
    226224      !! ** Method  :   Read the nampisext namelist and check the parameters 
    227225      !!      called at the first timestep (nittrc000) 
     226      !! 
    228227      !! ** input   :   Namelist nampisext 
    229228      !!---------------------------------------------------------------------- 
    230       INTEGER ::   jm 
    231       INTEGER ::   ios   ! Local integer  
    232       ! 
     229      INTEGER ::   jm, ios   ! Local integer  
     230      !! 
    233231      NAMELIST/nampisext/ln_co2int, atcco2, clname, nn_offset 
    234232      !!---------------------------------------------------------------------- 
    235       ! 
    236  
     233      IF(lwp) THEN 
     234         WRITE(numout,*) 
     235         WRITE(numout,*) ' p4z_flx_init : atmospheric conditions for air-sea flux calculation' 
     236         WRITE(numout,*) ' ~~~~~~~~~~~~' 
     237      ENDIF 
     238      ! 
    237239      REWIND( numnatp_ref )              ! Namelist nampisext in reference namelist : Pisces atm. conditions 
    238240      READ  ( numnatp_ref, nampisext, IOSTAT = ios, ERR = 901) 
    239 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisext in reference namelist', lwp ) 
    240  
     241901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisext in reference namelist', lwp ) 
    241242      REWIND( numnatp_cfg )              ! Namelist nampisext in configuration namelist : Pisces atm. conditions 
    242243      READ  ( numnatp_cfg, nampisext, IOSTAT = ios, ERR = 902 ) 
    243 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampisext in configuration namelist', lwp ) 
     244902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisext in configuration namelist', lwp ) 
    244245      IF(lwm) WRITE ( numonp, nampisext ) 
    245246      ! 
    246247      IF(lwp) THEN                         ! control print 
    247          WRITE(numout,*) ' ' 
    248          WRITE(numout,*) ' Namelist parameters for air-sea exchange, nampisext' 
    249          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    250          WRITE(numout,*) '    Choice for reading in the atm pCO2 file or constant value, ln_co2int =', ln_co2int 
    251          WRITE(numout,*) ' ' 
    252       ENDIF 
     248         WRITE(numout,*) '   Namelist : nampisext --- parameters for air-sea exchange' 
     249         WRITE(numout,*) '      reading in the atm pCO2 file or constant value   ln_co2int =', ln_co2int 
     250      ENDIF 
     251 
     252!!gm  BUG !!!   ===>>>  ln_presatm and ln_presatmco2 are used below, but read in namelist  
     253!!gm                    at the end of the routine via a CALL to CALL p4z_patm( nit000 ) 
     254 
    253255     IF( .NOT.ln_co2int .AND. .NOT.ln_presatmco2 ) THEN 
    254256         IF(lwp) THEN                         ! control print 
    255             WRITE(numout,*) '    Constant Atmospheric pCO2 value  atcco2    =', atcco2 
    256             WRITE(numout,*) ' ' 
     257            WRITE(numout,*) '         Constant Atmospheric pCO2 value               atcco2    =', atcco2 
    257258         ENDIF 
    258259         satmco2(:,:)  = atcco2      ! Initialisation of atmospheric pco2 
    259260      ELSEIF( ln_co2int .AND. .NOT.ln_presatmco2 ) THEN 
    260261         IF(lwp)  THEN 
    261             WRITE(numout,*) '    Atmospheric pCO2 value  from file clname      =', TRIM( clname ) 
    262             WRITE(numout,*) '    Offset model-data start year      nn_offset   =', nn_offset 
    263             WRITE(numout,*) ' ' 
     262            WRITE(numout,*) '         Constant Atmospheric pCO2 value               atcco2    =', atcco2 
     263            WRITE(numout,*) '         Atmospheric pCO2 value  from file             clname    =', TRIM( clname ) 
     264            WRITE(numout,*) '         Offset model-data start year                  nn_offset =', nn_offset 
    264265         ENDIF 
    265266         CALL ctl_opn( numco2, TRIM( clname) , 'OLD', 'FORMATTED', 'SEQUENTIAL', -1 , numout, lwp ) 
     
    270271         END DO 
    271272 100     nmaxrec = jm - 1  
    272          ALLOCATE( years  (nmaxrec) )     ;      years  (:) = 0._wp 
    273          ALLOCATE( atcco2h(nmaxrec) )     ;      atcco2h(:) = 0._wp 
    274  
     273         ALLOCATE( years  (nmaxrec) )   ;   years  (:) = 0._wp 
     274         ALLOCATE( atcco2h(nmaxrec) )   ;   atcco2h(:) = 0._wp 
     275         ! 
    275276         REWIND(numco2) 
    276277         DO jm = 1, nmaxrec          ! get  xCO2 data 
     
    282283         IF(lwp)  THEN 
    283284            WRITE(numout,*) '    Spatialized Atmospheric pCO2 from an external file' 
    284             WRITE(numout,*) ' ' 
    285285         ENDIF 
    286286      ELSE 
    287287         IF(lwp)  THEN 
    288288            WRITE(numout,*) '    Spatialized Atmospheric pCO2 from an external file' 
    289             WRITE(numout,*) ' ' 
    290289         ENDIF 
    291290      ENDIF 
     
    304303      !!                  ***  ROUTINE p4z_atm  *** 
    305304      !! 
    306       !! ** Purpose :   Read and interpolate the external atmospheric sea-levl pressure 
     305      !! ** Purpose :   Read and interpolate the external atmospheric sea-level pressure 
    307306      !! ** Method  :   Read the files and interpolate the appropriate variables 
    308307      !! 
    309308      !!---------------------------------------------------------------------- 
    310       INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    311       ! 
    312       INTEGER            ::  ierr 
    313       INTEGER            ::  ios      ! Local integer output status for namelist read 
    314       CHARACTER(len=100) ::  cn_dir   ! Root directory for location of ssr files 
    315       TYPE(FLD_N)        ::  sn_patm  ! informations about the fields to be read 
    316       TYPE(FLD_N)        ::  sn_atmco2 ! informations about the fields to be read 
     309      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     310      ! 
     311      INTEGER            ::   ierr, ios   ! Local integer 
     312      CHARACTER(len=100) ::   cn_dir      ! Root directory for location of ssr files 
     313      TYPE(FLD_N)        ::   sn_patm     ! informations about the fields to be read 
     314      TYPE(FLD_N)        ::   sn_atmco2   ! informations about the fields to be read 
    317315      !! 
    318316      NAMELIST/nampisatm/ ln_presatm, ln_presatmco2, sn_patm, sn_atmco2, cn_dir 
    319317      !!---------------------------------------------------------------------- 
    320  
    321       !                                         ! ----------------------- ! 
    322       IF( kt == nit000 ) THEN                   ! First call kt=nittrc000 ! 
    323  
     318      ! 
     319      IF( kt == nit000 ) THEN    !==  First call kt=nittrc000  ==! 
     320         ! 
     321         IF(lwp) THEN 
     322            WRITE(numout,*) 
     323            WRITE(numout,*) ' p4z_patm : sea-level atmospheric pressure' 
     324            WRITE(numout,*) ' ~~~~~~~~' 
     325         ENDIF 
     326         ! 
    324327         REWIND( numnatp_ref )              ! Namelist nampisatm in reference namelist : Pisces atm. sea level pressure file 
    325328         READ  ( numnatp_ref, nampisatm, IOSTAT = ios, ERR = 901) 
    326329901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisatm in reference namelist', lwp ) 
    327  
    328330         REWIND( numnatp_cfg )              ! Namelist nampisatm in configuration namelist : Pisces atm. sea level pressure file  
    329331         READ  ( numnatp_cfg, nampisatm, IOSTAT = ios, ERR = 902 ) 
    330 902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisatm in configuration namelist', lwp ) 
     332902      IF( ios >  0 )  CALL ctl_nam ( ios , 'nampisatm in configuration namelist', lwp ) 
    331333         IF(lwm) WRITE ( numonp, nampisatm ) 
    332334         ! 
    333335         ! 
    334336         IF(lwp) THEN                                 !* control print 
    335             WRITE(numout,*) 
    336             WRITE(numout,*) '   Namelist nampisatm : Atmospheric Pressure as external forcing' 
    337             WRITE(numout,*) '      constant atmopsheric pressure (F) or from a file (T)  ln_presatm = ', ln_presatm 
    338             WRITE(numout,*) '      spatial atmopsheric CO2 for flux calcs  ln_presatmco2 = ', ln_presatmco2 
    339             WRITE(numout,*) 
     337            WRITE(numout,*) '   Namelist : nampisatm --- Atmospheric Pressure as external forcing' 
     338            WRITE(numout,*) '      constant atmopsheric pressure (F) or from a file (T)  ln_presatm    = ', ln_presatm 
     339            WRITE(numout,*) '      spatial atmopsheric CO2 for flux calcs                ln_presatmco2 = ', ln_presatmco2 
    340340         ENDIF 
    341341         ! 
     
    358358         ENDIF 
    359359         ! 
    360          IF( .NOT.ln_presatm )   patm(:,:) = 1.e0    ! Initialize patm if no reading from a file 
     360         IF( .NOT.ln_presatm )   patm(:,:) = 1._wp    ! Initialize patm if no reading from a file 
    361361         ! 
    362362      ENDIF 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zligand.F90

    r9124 r9169  
    66   !! History :   3.6  !  2016-03  (O. Aumont, A. Tagliabue) Quota model and reorganization 
    77   !!---------------------------------------------------------------------- 
    8    !!   p4z_ligand       :  Compute remineralization/dissolution of organic ligands 
    9    !!   p4z_ligand_init  :  Initialisation of parameters for remineralisation 
     8   !!   p4z_ligand     :  Compute remineralization/dissolution of organic ligands 
     9   !!   p4z_ligand_init:  Initialisation of parameters for remineralisation 
    1010   !!---------------------------------------------------------------------- 
    11    USE oce_trc         !  shared variables between ocean and passive tracers 
    12    USE trc             !  passive tracers common variables  
    13    USE sms_pisces      !  PISCES Source Minus Sink variables 
    14    USE prtctl_trc      !  print control for debugging 
     11   USE oce_trc         ! shared variables between ocean and passive tracers 
     12   USE trc             ! passive tracers common variables  
     13   USE sms_pisces      ! PISCES Source Minus Sink variables 
     14   USE prtctl_trc      ! print control for debugging 
    1515 
    1616   IMPLICIT NONE 
     
    2020   PUBLIC   p4z_ligand_init    ! called in trcsms_pisces.F90 
    2121 
    22    !! * Shared module variables 
    2322   REAL(wp), PUBLIC ::  rlgw     !: lifetime (years) of weak ligands 
    2423   REAL(wp), PUBLIC ::  rlgs     !: lifetime (years) of strong ligands 
     
    3938      !! 
    4039      !! ** Purpose :   Compute remineralization/scavenging of organic ligands 
    41       !! 
    42       !! ** Method  : - ??? 
    4340      !!--------------------------------------------------------------------- 
    44       ! 
    4541      INTEGER, INTENT(in) ::   kt, knt ! ocean time step 
    4642      ! 
    4743      INTEGER  ::   ji, jj, jk 
    4844      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw, zrfepa, zfepr 
    49       CHARACTER (len=25) :: charout 
     45      CHARACTER (len=25) ::   charout 
    5046      !!--------------------------------------------------------------------- 
    5147      ! 
    5248      IF( ln_timing )   CALL timing_start('p4z_ligand') 
    5349      ! 
    54       ! ------------------------------------------------------------------ 
    55       ! Remineralization of iron ligands 
    56       ! ------------------------------------------------------------------ 
    5750      DO jk = 1, jpkm1 
    5851         DO jj = 1, jpj 
    5952            DO ji = 1, jpi 
     53               ! 
     54               ! ------------------------------------------------------------------ 
     55               ! Remineralization of iron ligands 
     56               ! ------------------------------------------------------------------ 
    6057               ! production from remineralisation of organic matter 
    6158               zlgwp  = orem(ji,jj,jk) * rlig 
     
    6865               zlgwpr = prlgw * xstep * etot(ji,jj,jk) * trb(ji,jj,jk,jplgw) * (1. - fr_i(ji,jj)) 
    6966               tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) + zlgwp - zlgwr - zlgwpr 
    70             END DO 
    71          END DO 
    72       END DO 
    73  
    74       ! ---------------------------------------------------------- 
    75       ! Dissolution of nanoparticle Fe 
    76       ! ---------------------------------------------------------- 
    77       DO jk = 1, jpkm1 
    78          DO jj = 1, jpj 
    79             DO ji = 1, jpi 
     67               ! 
     68               ! ---------------------------------------------------------- 
     69               ! Dissolution of nanoparticle Fe 
     70               ! ---------------------------------------------------------- 
    8071               ! dissolution rate is maximal in the presence of light and  
    8172               ! lower in the aphotici zone 
     
    8677               tra(ji,jj,jk,jpfep) = tra(ji,jj,jk,jpfep) - zfepr 
    8778               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zfepr 
     79               ! 
    8880            END DO 
    8981         END DO 
    9082      END DO 
    91  
     83      ! 
    9284      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
    9385         WRITE(charout, FMT="('ligand1')") 
    9486         CALL prt_ctl_trc_info(charout) 
    9587         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    96        ENDIF 
     88      ENDIF 
    9789      ! 
    9890      IF( ln_timing )   CALL timing_stop('p4z_ligand') 
     
    108100      !! 
    109101      !! ** Method  :   Read the nampislig namelist and check the parameters 
    110       !!      called at the first timestep 
    111102      !! 
    112103      !! ** input   :   Namelist nampislig 
    113       !! 
    114104      !!---------------------------------------------------------------------- 
    115105      INTEGER ::   ios   ! Local integer  
     
    117107      NAMELIST/nampislig/ rlgw, prlgw, rlgs, rfep, rlig 
    118108      !!---------------------------------------------------------------------- 
    119  
     109      ! 
     110      IF(lwp) THEN 
     111         WRITE(numout,*) 
     112         WRITE(numout,*) 'p4z_ligand_init : remineralization/scavenging of organic ligands' 
     113         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
     114      ENDIF 
    120115      REWIND( numnatp_ref )              ! Namelist nampislig in reference namelist : Pisces remineralization 
    121116      READ  ( numnatp_ref, nampislig, IOSTAT = ios, ERR = 901) 
    122 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampislig in reference namelist', lwp ) 
    123  
     117901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampislig in reference namelist', lwp ) 
    124118      REWIND( numnatp_cfg )              ! Namelist nampislig in configuration namelist : Pisces remineralization 
    125119      READ  ( numnatp_cfg, nampislig, IOSTAT = ios, ERR = 902 ) 
    126 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampislig in configuration namelist', lwp ) 
     120902   IF( ios >  0 )  CALL ctl_nam ( ios , 'nampislig in configuration namelist', lwp ) 
    127121      IF(lwm) WRITE ( numonp, nampislig ) 
    128  
     122      ! 
    129123      IF(lwp) THEN                         ! control print 
    130          WRITE(numout,*) ' ' 
    131          WRITE(numout,*) ' Namelist parameters for ligands, nampislig' 
    132          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    133          WRITE(numout,*) '    Dissolution rate of FeP                        rfep =', rfep 
    134          WRITE(numout,*) '    Lifetime (years) of weak ligands               rlgw =', rlgw 
    135          WRITE(numout,*) '    Remin ligand production per unit C             rlig =', rlig 
    136          WRITE(numout,*) '    Photolysis of weak ligand                     prlgw =', prlgw 
    137          WRITE(numout,*) '    Lifetime (years) of strong ligands             rlgs =', rlgs 
     124         WRITE(numout,*) '   Namelist : nampislig' 
     125         WRITE(numout,*) '      Dissolution rate of FeP                      rfep  =', rfep 
     126         WRITE(numout,*) '      Lifetime (years) of weak ligands             rlgw  =', rlgw 
     127         WRITE(numout,*) '      Remin ligand production per unit C           rlig  =', rlig 
     128         WRITE(numout,*) '      Photolysis of weak ligand                    prlgw =', prlgw 
     129         WRITE(numout,*) '      Lifetime (years) of strong ligands           rlgs  =', rlgs 
    138130      ENDIF 
    139131      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zlim.F90

    r9124 r9169  
    215215      ! 
    216216      IF( lk_iomput .AND. knt == nrdttrc ) THEN        ! save output diagnostics 
    217         IF( iom_use( "xfracal" ) ) CALL iom_put( "xfracal", xfracal(:,:,:) * tmask(:,:,:) )  ! euphotic layer deptht 
    218         IF( iom_use( "LNnut"   ) ) CALL iom_put( "LNnut"  , xlimphy(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
    219         IF( iom_use( "LDnut"   ) ) CALL iom_put( "LDnut"  , xlimdia(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
    220         IF( iom_use( "LNFe"    ) ) CALL iom_put( "LNFe"   , xlimnfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    221         IF( iom_use( "LDFe"    ) ) CALL iom_put( "LDFe"   , xlimdfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     217        IF( iom_use( "xfracal" ) )   CALL iom_put( "xfracal", xfracal(:,:,:) * tmask(:,:,:) )  ! euphotic layer deptht 
     218        IF( iom_use( "LNnut"   ) )   CALL iom_put( "LNnut"  , xlimphy(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
     219        IF( iom_use( "LDnut"   ) )   CALL iom_put( "LDnut"  , xlimdia(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
     220        IF( iom_use( "LNFe"    ) )   CALL iom_put( "LNFe"   , xlimnfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     221        IF( iom_use( "LDFe"    ) )   CALL iom_put( "LDFe"   , xlimdfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    222222      ENDIF 
    223223      ! 
     
    246246      !!---------------------------------------------------------------------- 
    247247      ! 
     248      IF(lwp) THEN 
     249         WRITE(numout,*) 
     250         WRITE(numout,*) 'p4z_lim_init : initialization of nutrient limitations' 
     251         WRITE(numout,*) '~~~~~~~~~~~~' 
     252      ENDIF 
     253      ! 
    248254      REWIND( numnatp_ref )              ! Namelist nampislim in reference namelist : Pisces nutrient limitation parameters 
    249255      READ  ( numnatp_ref, namp4zlim, IOSTAT = ios, ERR = 901) 
    250 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namp4zlim in reference namelist', lwp ) 
    251       ! 
     256901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zlim in reference namelist', lwp ) 
    252257      REWIND( numnatp_cfg )              ! Namelist nampislim in configuration namelist : Pisces nutrient limitation parameters  
    253258      READ  ( numnatp_cfg, namp4zlim, IOSTAT = ios, ERR = 902 ) 
    254 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namp4zlim in configuration namelist', lwp ) 
    255       IF(lwm) WRITE ( numonp, namp4zlim ) 
     259902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zlim in configuration namelist', lwp ) 
     260      IF(lwm) WRITE( numonp, namp4zlim ) 
    256261      ! 
    257262      IF(lwp) THEN                         ! control print 
    258          WRITE(numout,*) ' ' 
    259          WRITE(numout,*) ' Namelist parameters for nutrient limitations, namp4zlim' 
    260          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    261          WRITE(numout,*) '    mean rainratio                           caco3r    = ', caco3r 
    262          WRITE(numout,*) '    NO3 half saturation of nanophyto         concnno3  = ', concnno3 
    263          WRITE(numout,*) '    NO3 half saturation of diatoms           concdno3  = ', concdno3 
    264          WRITE(numout,*) '    NH4 half saturation for phyto            concnnh4  = ', concnnh4 
    265          WRITE(numout,*) '    NH4 half saturation for diatoms          concdnh4  = ', concdnh4 
    266          WRITE(numout,*) '    half saturation constant for Si uptake   xksi1     = ', xksi1 
    267          WRITE(numout,*) '    half saturation constant for Si/C        xksi2     = ', xksi2 
    268          WRITE(numout,*) '    half-sat. of DOC remineralization        xkdoc     = ', xkdoc 
    269          WRITE(numout,*) '    Iron half saturation for nanophyto       concnfer  = ', concnfer 
    270          WRITE(numout,*) '    Iron half saturation for diatoms         concdfer  = ', concdfer 
    271          WRITE(numout,*) '    size ratio for nanophytoplankton         xsizern   = ', xsizern 
    272          WRITE(numout,*) '    size ratio for diatoms                   xsizerd   = ', xsizerd 
    273          WRITE(numout,*) '    NO3 half saturation of bacteria          concbno3  = ', concbno3 
    274          WRITE(numout,*) '    NH4 half saturation for bacteria         concbnh4  = ', concbnh4 
    275          WRITE(numout,*) '    Minimum size criteria for diatoms        xsizedia  = ', xsizedia 
    276          WRITE(numout,*) '    Minimum size criteria for nanophyto      xsizephy  = ', xsizephy 
    277          WRITE(numout,*) '    Fe half saturation for bacteria          concbfe   = ', concbfe 
    278          WRITE(numout,*) '    halk saturation constant for anoxia       oxymin   =' , oxymin 
    279          WRITE(numout,*) '    optimal Fe quota for nano.               qnfelim   = ', qnfelim 
    280          WRITE(numout,*) '    Optimal Fe quota for diatoms             qdfelim   = ', qdfelim 
     263         WRITE(numout,*) '   Namelist : namp4zlim' 
     264         WRITE(numout,*) '      mean rainratio                           caco3r    = ', caco3r 
     265         WRITE(numout,*) '      NO3 half saturation of nanophyto         concnno3  = ', concnno3 
     266         WRITE(numout,*) '      NO3 half saturation of diatoms           concdno3  = ', concdno3 
     267         WRITE(numout,*) '      NH4 half saturation for phyto            concnnh4  = ', concnnh4 
     268         WRITE(numout,*) '      NH4 half saturation for diatoms          concdnh4  = ', concdnh4 
     269         WRITE(numout,*) '      half saturation constant for Si uptake   xksi1     = ', xksi1 
     270         WRITE(numout,*) '      half saturation constant for Si/C        xksi2     = ', xksi2 
     271         WRITE(numout,*) '      half-sat. of DOC remineralization        xkdoc     = ', xkdoc 
     272         WRITE(numout,*) '      Iron half saturation for nanophyto       concnfer  = ', concnfer 
     273         WRITE(numout,*) '      Iron half saturation for diatoms         concdfer  = ', concdfer 
     274         WRITE(numout,*) '      size ratio for nanophytoplankton         xsizern   = ', xsizern 
     275         WRITE(numout,*) '      size ratio for diatoms                   xsizerd   = ', xsizerd 
     276         WRITE(numout,*) '      NO3 half saturation of bacteria          concbno3  = ', concbno3 
     277         WRITE(numout,*) '      NH4 half saturation for bacteria         concbnh4  = ', concbnh4 
     278         WRITE(numout,*) '      Minimum size criteria for diatoms        xsizedia  = ', xsizedia 
     279         WRITE(numout,*) '      Minimum size criteria for nanophyto      xsizephy  = ', xsizephy 
     280         WRITE(numout,*) '      Fe half saturation for bacteria          concbfe   = ', concbfe 
     281         WRITE(numout,*) '      halk saturation constant for anoxia       oxymin   =' , oxymin 
     282         WRITE(numout,*) '      optimal Fe quota for nano.               qnfelim   = ', qnfelim 
     283         WRITE(numout,*) '      Optimal Fe quota for diatoms             qdfelim   = ', qdfelim 
    281284      ENDIF 
    282285      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zlys.F90

    r9125 r9169  
    2929   PUBLIC   p4z_lys_init    ! called in trcsms_pisces.F90 
    3030 
    31    !! * Shared module variables 
    32    REAL(wp), PUBLIC :: kdca !: diss. rate constant calcite 
    33    REAL(wp), PUBLIC :: nca  !: order of reaction for calcite dissolution 
     31   REAL(wp), PUBLIC ::   kdca   !: diss. rate constant calcite 
     32   REAL(wp), PUBLIC ::   nca    !: order of reaction for calcite dissolution 
    3433 
    35    !! * Module variables 
    36    REAL(wp) :: calcon = 1.03E-2           !: mean calcite concentration [Ca2+] in sea water [mole/kg solution] 
     34   INTEGER  ::   rmtss              ! number of seconds per month  
     35   REAL(wp) ::   calcon = 1.03E-2   ! mean calcite concentration [Ca2+] in sea water [mole/kg solution] 
    3736  
    38    INTEGER  :: rmtss                      !: number of seconds per month  
    39  
    4037   !!---------------------------------------------------------------------- 
    4138   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    5653      !! ** Method  : - ??? 
    5754      !!--------------------------------------------------------------------- 
     55      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step and ??? 
    5856      ! 
    59       INTEGER, INTENT(in) ::   kt, knt ! ocean time step 
    6057      INTEGER  ::   ji, jj, jk, jn 
    6158      REAL(wp) ::   zdispot, zfact, zcalcon 
    6259      REAL(wp) ::   zomegaca, zexcess, zexcess0 
    63       CHARACTER (len=25) :: charout 
    64       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zco3, zcaldiss, zhinit, zhi, zco3sat 
     60      CHARACTER (len=25) ::   charout 
     61      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zco3, zcaldiss, zhinit, zhi, zco3sat 
    6562      !!--------------------------------------------------------------------- 
    6663      ! 
     
    6966      zco3    (:,:,:) = 0. 
    7067      zcaldiss(:,:,:) = 0. 
    71       zhinit(:,:,:)   = hi(:,:,:) * 1000. / ( rhop(:,:,:) + rtrn ) 
     68      zhinit  (:,:,:) = hi(:,:,:) * 1000. / ( rhop(:,:,:) + rtrn ) 
     69      ! 
    7270      !     ------------------------------------------- 
    7371      !     COMPUTE [CO3--] and [H+] CONCENTRATIONS 
    7472      !     ------------------------------------------- 
    7573 
    76       CALL solve_at_general(zhinit, zhi) 
     74      CALL solve_at_general( zhinit, zhi ) 
    7775 
    7876      DO jk = 1, jpkm1 
     
    8078            DO ji = 1, jpi 
    8179               zco3(ji,jj,jk) = trb(ji,jj,jk,jpdic) * ak13(ji,jj,jk) * ak23(ji,jj,jk) / (zhi(ji,jj,jk)**2   & 
    82                &                + ak13(ji,jj,jk) * zhi(ji,jj,jk) + ak13(ji,jj,jk) * ak23(ji,jj,jk) + rtrn ) 
    83                hi(ji,jj,jk)  = zhi(ji,jj,jk) * rhop(ji,jj,jk) / 1000. 
     80                  &             + ak13(ji,jj,jk) * zhi(ji,jj,jk) + ak13(ji,jj,jk) * ak23(ji,jj,jk) + rtrn ) 
     81               hi  (ji,jj,jk) = zhi(ji,jj,jk) * rhop(ji,jj,jk) / 1000. 
    8482            END DO 
    8583         END DO 
     
    158156      NAMELIST/nampiscal/ kdca, nca 
    159157      !!---------------------------------------------------------------------- 
     158      IF(lwp) THEN 
     159         WRITE(numout,*) 
     160         WRITE(numout,*) 'p4z_lys_init : initialization of CaCO3 dissolution' 
     161         WRITE(numout,*) '~~~~~~~~~~~~' 
     162      ENDIF 
    160163      ! 
    161164      REWIND( numnatp_ref )              ! Namelist nampiscal in reference namelist : Pisces CaCO3 dissolution 
    162165      READ  ( numnatp_ref, nampiscal, IOSTAT = ios, ERR = 901) 
    163 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampiscal in reference namelist', lwp ) 
    164       ! 
     166901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampiscal in reference namelist', lwp ) 
    165167      REWIND( numnatp_cfg )              ! Namelist nampiscal in configuration namelist : Pisces CaCO3 dissolution 
    166168      READ  ( numnatp_cfg, nampiscal, IOSTAT = ios, ERR = 902 ) 
    167 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampiscal in configuration namelist', lwp ) 
    168       IF(lwm) WRITE ( numonp, nampiscal ) 
     169902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampiscal in configuration namelist', lwp ) 
     170      IF(lwm) WRITE( numonp, nampiscal ) 
    169171      ! 
    170172      IF(lwp) THEN                         ! control print 
    171          WRITE(numout,*) ' ' 
    172          WRITE(numout,*) ' Namelist parameters for CaCO3 dissolution, nampiscal' 
    173          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    174          WRITE(numout,*) '    diss. rate constant calcite (per month)   kdca      =', kdca 
    175          WRITE(numout,*) '    order of reaction for calcite dissolution nca       =', nca 
     173         WRITE(numout,*) '   Namelist : nampiscal' 
     174         WRITE(numout,*) '      diss. rate constant calcite (per month)        kdca =', kdca 
     175         WRITE(numout,*) '      order of reaction for calcite dissolution      nca  =', nca 
    176176      ENDIF 
    177177      ! 
     
    180180      ! 
    181181   END SUBROUTINE p4z_lys_init 
     182 
    182183   !!====================================================================== 
    183184END MODULE p4zlys 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmeso.F90

    r9125 r9169  
    88   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Quota model for iron 
    99   !!---------------------------------------------------------------------- 
    10    !!   p4z_meso       :   Compute the sources/sinks for mesozooplankton 
    11    !!   p4z_meso_init  :   Initialization of the parameters for mesozooplankton 
    12    !!---------------------------------------------------------------------- 
    13    USE oce_trc         !  shared variables between ocean and passive tracers 
    14    USE trc             !  passive tracers common variables  
    15    USE sms_pisces      !  PISCES Source Minus Sink variables 
    16    USE p4zprod         !  production 
    17    USE prtctl_trc      !  print control for debugging 
    18    USE iom             !  I/O manager 
     10   !!   p4z_meso       : Compute the sources/sinks for mesozooplankton 
     11   !!   p4z_meso_init  : Initialization of the parameters for mesozooplankton 
     12   !!---------------------------------------------------------------------- 
     13   USE oce_trc         ! shared variables between ocean and passive tracers 
     14   USE trc             ! passive tracers common variables  
     15   USE sms_pisces      ! PISCES Source Minus Sink variables 
     16   USE p4zprod         ! production 
     17   USE prtctl_trc      ! print control for debugging 
     18   USE iom             ! I/O manager 
    1919 
    2020   IMPLICIT NONE 
     
    2424   PUBLIC   p4z_meso_init         ! called in trcsms_pisces.F90 
    2525 
    26    !! * Shared module variables 
    2726   REAL(wp), PUBLIC ::  part2        !: part of calcite not dissolved in mesozoo guts 
    2827   REAL(wp), PUBLIC ::  xprefc       !: mesozoo preference for POC  
     
    4948   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    5049   !!---------------------------------------------------------------------- 
    51  
    5250CONTAINS 
    5351 
     
    6058      !! ** Method  : - ??? 
    6159      !!--------------------------------------------------------------------- 
    62       INTEGER, INTENT(in) ::   kt, knt ! ocean time step 
     60      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step and ??? 
     61      ! 
    6362      INTEGER  :: ji, jj, jk 
    6463      REAL(wp) :: zcompadi, zcompaph, zcompapoc, zcompaz, zcompam 
     
    7372      CHARACTER (len=25) :: charout 
    7473      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing 
    75       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d 
    76  
     74      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zw3d 
    7775      !!--------------------------------------------------------------------- 
    7876      ! 
     
    122120 
    123121               !  Mesozooplankton flux feeding on GOC 
    124                !  ---------------------------------- 
    125122               !  ---------------------------------- 
    126123               zgrazffeg = grazflux  * xstep * wsbio4(ji,jj,jk)      & 
     
    253250      !! 
    254251      !! ** input   :   Namelist nampismes 
    255       !! 
    256252      !!---------------------------------------------------------------------- 
    257253      INTEGER ::   ios   ! Local integer 
     
    262258      !!---------------------------------------------------------------------- 
    263259      ! 
     260      IF(lwp) THEN 
     261         WRITE(numout,*)  
     262         WRITE(numout,*) 'p4z_meso_init : Initialization of mesozooplankton parameters' 
     263         WRITE(numout,*) '~~~~~~~~~~~~~' 
     264      ENDIF 
     265      ! 
    264266      REWIND( numnatp_ref )              ! Namelist nampismes in reference namelist : Pisces mesozooplankton 
    265267      READ  ( numnatp_ref, namp4zmes, IOSTAT = ios, ERR = 901) 
    266 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namp4zmes in reference namelist', lwp ) 
    267       ! 
     268901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zmes in reference namelist', lwp ) 
    268269      REWIND( numnatp_cfg )              ! Namelist nampismes in configuration namelist : Pisces mesozooplankton 
    269270      READ  ( numnatp_cfg, namp4zmes, IOSTAT = ios, ERR = 902 ) 
    270 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namp4zmes in configuration namelist', lwp ) 
    271       IF(lwm) WRITE ( numonp, namp4zmes ) 
     271902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zmes in configuration namelist', lwp ) 
     272      IF(lwm) WRITE( numonp, namp4zmes ) 
    272273      ! 
    273274      IF(lwp) THEN                         ! control print 
    274          WRITE(numout,*) ' '  
    275          WRITE(numout,*) ' Namelist parameters for mesozooplankton, namp4zmes' 
    276          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    277          WRITE(numout,*) '    part of calcite not dissolved in mesozoo guts  part2        =', part2 
    278          WRITE(numout,*) '    mesozoo preference for phyto                   xprefc       =', xprefc 
    279          WRITE(numout,*) '    mesozoo preference for POC                     xprefp       =', xprefp 
    280          WRITE(numout,*) '    mesozoo preference for zoo                     xprefz       =', xprefz 
    281          WRITE(numout,*) '    mesozoo preference for poc                     xprefpoc     =', xprefpoc 
    282          WRITE(numout,*) '    microzoo feeding threshold  for mesozoo        xthresh2zoo  =', xthresh2zoo 
    283          WRITE(numout,*) '    diatoms feeding threshold  for mesozoo         xthresh2dia  =', xthresh2dia 
    284          WRITE(numout,*) '    nanophyto feeding threshold for mesozoo        xthresh2phy  =', xthresh2phy 
    285          WRITE(numout,*) '    poc feeding threshold for mesozoo              xthresh2poc  =', xthresh2poc 
    286          WRITE(numout,*) '    feeding threshold for mesozooplankton          xthresh2     =', xthresh2 
    287          WRITE(numout,*) '    exsudation rate of mesozooplankton             resrat2      =', resrat2 
    288          WRITE(numout,*) '    mesozooplankton mortality rate                 mzrat2       =', mzrat2 
    289          WRITE(numout,*) '    maximal mesozoo grazing rate                   grazrat2     =', grazrat2 
    290          WRITE(numout,*) '    mesozoo flux feeding rate                      grazflux     =', grazflux 
    291          WRITE(numout,*) '    non assimilated fraction of P by mesozoo       unass2       =', unass2 
    292          WRITE(numout,*) '    Efficicency of Mesozoo growth                  epsher2      =', epsher2 
    293          WRITE(numout,*) '    Fraction of mesozoo excretion as DOM           sigma2       =', sigma2 
    294          WRITE(numout,*) '    half sturation constant for grazing 2          xkgraz2      =', xkgraz2 
     275         WRITE(numout,*) '   Namelist : namp4zmes' 
     276         WRITE(numout,*) '      part of calcite not dissolved in mesozoo guts  part2        =', part2 
     277         WRITE(numout,*) '      mesozoo preference for phyto                   xprefc       =', xprefc 
     278         WRITE(numout,*) '      mesozoo preference for POC                     xprefp       =', xprefp 
     279         WRITE(numout,*) '      mesozoo preference for zoo                     xprefz       =', xprefz 
     280         WRITE(numout,*) '      mesozoo preference for poc                     xprefpoc     =', xprefpoc 
     281         WRITE(numout,*) '      microzoo feeding threshold  for mesozoo        xthresh2zoo  =', xthresh2zoo 
     282         WRITE(numout,*) '      diatoms feeding threshold  for mesozoo         xthresh2dia  =', xthresh2dia 
     283         WRITE(numout,*) '      nanophyto feeding threshold for mesozoo        xthresh2phy  =', xthresh2phy 
     284         WRITE(numout,*) '      poc feeding threshold for mesozoo              xthresh2poc  =', xthresh2poc 
     285         WRITE(numout,*) '      feeding threshold for mesozooplankton          xthresh2     =', xthresh2 
     286         WRITE(numout,*) '      exsudation rate of mesozooplankton             resrat2      =', resrat2 
     287         WRITE(numout,*) '      mesozooplankton mortality rate                 mzrat2       =', mzrat2 
     288         WRITE(numout,*) '      maximal mesozoo grazing rate                   grazrat2     =', grazrat2 
     289         WRITE(numout,*) '      mesozoo flux feeding rate                      grazflux     =', grazflux 
     290         WRITE(numout,*) '      non assimilated fraction of P by mesozoo       unass2       =', unass2 
     291         WRITE(numout,*) '      Efficicency of Mesozoo growth                  epsher2      =', epsher2 
     292         WRITE(numout,*) '      Fraction of mesozoo excretion as DOM           sigma2       =', sigma2 
     293         WRITE(numout,*) '      half sturation constant for grazing 2          xkgraz2      =', xkgraz2 
    295294      ENDIF 
    296295      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmicro.F90

    r9125 r9169  
    88   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Quota model for iron 
    99   !!---------------------------------------------------------------------- 
    10    !!   p4z_micro       :  Compute the sources/sinks for microzooplankton 
    11    !!   p4z_micro_init  :  Initialize and read the appropriate namelist 
    12    !!---------------------------------------------------------------------- 
    13    USE oce_trc         !  shared variables between ocean and passive tracers 
    14    USE trc             !  passive tracers common variables  
    15    USE sms_pisces      !  PISCES Source Minus Sink variables 
    16    USE p4zlim          !  Co-limitations 
    17    USE p4zprod         !  production 
    18    USE iom             !  I/O manager 
    19    USE prtctl_trc      !  print control for debugging 
     10   !!   p4z_micro      : Compute the sources/sinks for microzooplankton 
     11   !!   p4z_micro_init : Initialize and read the appropriate namelist 
     12   !!---------------------------------------------------------------------- 
     13   USE oce_trc         ! shared variables between ocean and passive tracers 
     14   USE trc             ! passive tracers common variables  
     15   USE sms_pisces      ! PISCES Source Minus Sink variables 
     16   USE p4zlim          ! Co-limitations 
     17   USE p4zprod         ! production 
     18   USE iom             ! I/O manager 
     19   USE prtctl_trc      ! print control for debugging 
    2020 
    2121   IMPLICIT NONE 
     
    2525   PUBLIC   p4z_micro_init    ! called in trcsms_pisces.F90 
    2626 
    27    !! * Shared module variables 
    28    REAL(wp), PUBLIC ::  part        !: part of calcite not dissolved in microzoo guts 
    29    REAL(wp), PUBLIC ::  xpref2c     !: microzoo preference for POC  
    30    REAL(wp), PUBLIC ::  xpref2p     !: microzoo preference for nanophyto 
    31    REAL(wp), PUBLIC ::  xpref2d     !: microzoo preference for diatoms 
    32    REAL(wp), PUBLIC ::  xthreshdia  !: diatoms feeding threshold for microzooplankton  
    33    REAL(wp), PUBLIC ::  xthreshphy  !: nanophyto threshold for microzooplankton  
    34    REAL(wp), PUBLIC ::  xthreshpoc  !: poc threshold for microzooplankton  
    35    REAL(wp), PUBLIC ::  xthresh     !: feeding threshold for microzooplankton  
    36    REAL(wp), PUBLIC ::  resrat      !: exsudation rate of microzooplankton 
    37    REAL(wp), PUBLIC ::  mzrat       !: microzooplankton mortality rate  
    38    REAL(wp), PUBLIC ::  grazrat     !: maximal microzoo grazing rate 
    39    REAL(wp), PUBLIC ::  xkgraz      !: non assimilated fraction of P by microzoo  
    40    REAL(wp), PUBLIC ::  unass       !: Efficicency of microzoo growth  
    41    REAL(wp), PUBLIC ::  sigma1      !: Fraction of microzoo excretion as DOM  
    42    REAL(wp), PUBLIC ::  epsher      !: half sturation constant for grazing 1  
     27   REAL(wp), PUBLIC ::   part        !: part of calcite not dissolved in microzoo guts 
     28   REAL(wp), PUBLIC ::   xpref2c     !: microzoo preference for POC  
     29   REAL(wp), PUBLIC ::   xpref2p     !: microzoo preference for nanophyto 
     30   REAL(wp), PUBLIC ::   xpref2d     !: microzoo preference for diatoms 
     31   REAL(wp), PUBLIC ::   xthreshdia  !: diatoms feeding threshold for microzooplankton  
     32   REAL(wp), PUBLIC ::   xthreshphy  !: nanophyto threshold for microzooplankton  
     33   REAL(wp), PUBLIC ::   xthreshpoc  !: poc threshold for microzooplankton  
     34   REAL(wp), PUBLIC ::   xthresh     !: feeding threshold for microzooplankton  
     35   REAL(wp), PUBLIC ::   resrat      !: exsudation rate of microzooplankton 
     36   REAL(wp), PUBLIC ::   mzrat       !: microzooplankton mortality rate  
     37   REAL(wp), PUBLIC ::   grazrat     !: maximal microzoo grazing rate 
     38   REAL(wp), PUBLIC ::   xkgraz      !: non assimilated fraction of P by microzoo  
     39   REAL(wp), PUBLIC ::   unass       !: Efficicency of microzoo growth  
     40   REAL(wp), PUBLIC ::   sigma1      !: Fraction of microzoo excretion as DOM  
     41   REAL(wp), PUBLIC ::   epsher      !: half sturation constant for grazing 1  
    4342 
    4443   !!---------------------------------------------------------------------- 
     
    5756      !! ** Method  : - ??? 
    5857      !!--------------------------------------------------------------------- 
    59       INTEGER, INTENT(in) ::  kt  ! ocean time step 
    60       INTEGER, INTENT(in) ::  knt  
     58      INTEGER, INTENT(in) ::   kt    ! ocean time step 
     59      INTEGER, INTENT(in) ::   knt   ! ???  
    6160      ! 
    6261      INTEGER  :: ji, jj, jk 
     
    185184      ENDIF 
    186185      ! 
    187       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     186      IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
    188187         WRITE(charout, FMT="('micro')") 
    189188         CALL prt_ctl_trc_info(charout) 
     
    215214      !!---------------------------------------------------------------------- 
    216215      ! 
     216      IF(lwp) THEN 
     217         WRITE(numout,*)  
     218         WRITE(numout,*) 'p4z_micro_init : Initialization of microzooplankton parameters' 
     219         WRITE(numout,*) '~~~~~~~~~~~~~~' 
     220      ENDIF 
     221      ! 
    217222      REWIND( numnatp_ref )              ! Namelist nampiszoo in reference namelist : Pisces microzooplankton 
    218223      READ  ( numnatp_ref, namp4zzoo, IOSTAT = ios, ERR = 901) 
    219 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namp4zzoo in reference namelist', lwp ) 
    220       ! 
     224901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zzoo in reference namelist', lwp ) 
    221225      REWIND( numnatp_cfg )              ! Namelist nampiszoo in configuration namelist : Pisces microzooplankton 
    222226      READ  ( numnatp_cfg, namp4zzoo, IOSTAT = ios, ERR = 902 ) 
    223 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namp4zzoo in configuration namelist', lwp ) 
    224       IF(lwm) WRITE ( numonp, namp4zzoo ) 
     227902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zzoo in configuration namelist', lwp ) 
     228      IF(lwm) WRITE( numonp, namp4zzoo ) 
    225229      ! 
    226230      IF(lwp) THEN                         ! control print 
    227          WRITE(numout,*) ' ' 
    228          WRITE(numout,*) ' Namelist parameters for microzooplankton, namp4zzoo' 
    229          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    230          WRITE(numout,*) '    part of calcite not dissolved in microzoo guts  part        =', part 
    231          WRITE(numout,*) '    microzoo preference for POC                     xpref2c     =', xpref2c 
    232          WRITE(numout,*) '    microzoo preference for nano                    xpref2p     =', xpref2p 
    233          WRITE(numout,*) '    microzoo preference for diatoms                 xpref2d     =', xpref2d 
    234          WRITE(numout,*) '    diatoms feeding threshold  for microzoo         xthreshdia  =', xthreshdia 
    235          WRITE(numout,*) '    nanophyto feeding threshold for microzoo        xthreshphy  =', xthreshphy 
    236          WRITE(numout,*) '    poc feeding threshold for microzoo              xthreshpoc  =', xthreshpoc 
    237          WRITE(numout,*) '    feeding threshold for microzooplankton          xthresh     =', xthresh 
    238          WRITE(numout,*) '    exsudation rate of microzooplankton             resrat      =', resrat 
    239          WRITE(numout,*) '    microzooplankton mortality rate                 mzrat       =', mzrat 
    240          WRITE(numout,*) '    maximal microzoo grazing rate                   grazrat     =', grazrat 
    241          WRITE(numout,*) '    non assimilated fraction of P by microzoo       unass       =', unass 
    242          WRITE(numout,*) '    Efficicency of microzoo growth                  epsher      =', epsher 
    243          WRITE(numout,*) '    Fraction of microzoo excretion as DOM           sigma1      =', sigma1 
    244          WRITE(numout,*) '    half sturation constant for grazing 1           xkgraz      =', xkgraz 
     231         WRITE(numout,*) '   Namelist : namp4zzoo' 
     232         WRITE(numout,*) '      part of calcite not dissolved in microzoo guts  part        =', part 
     233         WRITE(numout,*) '      microzoo preference for POC                     xpref2c     =', xpref2c 
     234         WRITE(numout,*) '      microzoo preference for nano                    xpref2p     =', xpref2p 
     235         WRITE(numout,*) '      microzoo preference for diatoms                 xpref2d     =', xpref2d 
     236         WRITE(numout,*) '      diatoms feeding threshold  for microzoo         xthreshdia  =', xthreshdia 
     237         WRITE(numout,*) '      nanophyto feeding threshold for microzoo        xthreshphy  =', xthreshphy 
     238         WRITE(numout,*) '      poc feeding threshold for microzoo              xthreshpoc  =', xthreshpoc 
     239         WRITE(numout,*) '      feeding threshold for microzooplankton          xthresh     =', xthresh 
     240         WRITE(numout,*) '      exsudation rate of microzooplankton             resrat      =', resrat 
     241         WRITE(numout,*) '      microzooplankton mortality rate                 mzrat       =', mzrat 
     242         WRITE(numout,*) '      maximal microzoo grazing rate                   grazrat     =', grazrat 
     243         WRITE(numout,*) '      non assimilated fraction of P by microzoo       unass       =', unass 
     244         WRITE(numout,*) '      Efficicency of microzoo growth                  epsher      =', epsher 
     245         WRITE(numout,*) '      Fraction of microzoo excretion as DOM           sigma1      =', sigma1 
     246         WRITE(numout,*) '      half sturation constant for grazing 1           xkgraz      =', xkgraz 
    245247      ENDIF 
    246248      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmort.F90

    r9124 r9169  
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    88   !!---------------------------------------------------------------------- 
    9    !!   p4z_mort       :   Compute the mortality terms for phytoplankton 
    10    !!   p4z_mort_init  :   Initialize the mortality params for phytoplankton 
    11    !!---------------------------------------------------------------------- 
    12    USE oce_trc         !  shared variables between ocean and passive tracers 
    13    USE trc             !  passive tracers common variables  
    14    USE sms_pisces      !  PISCES Source Minus Sink variables 
    15    USE p4zprod         !  Primary productivity  
    16    USE p4zlim          !  Phytoplankton limitation terms 
    17    USE prtctl_trc      !  print control for debugging 
     9   !!   p4z_mort       : Compute the mortality terms for phytoplankton 
     10   !!   p4z_mort_init  : Initialize the mortality params for phytoplankton 
     11   !!---------------------------------------------------------------------- 
     12   USE oce_trc         ! shared variables between ocean and passive tracers 
     13   USE trc             ! passive tracers common variables  
     14   USE sms_pisces      ! PISCES Source Minus Sink variables 
     15   USE p4zprod         ! Primary productivity  
     16   USE p4zlim          ! Phytoplankton limitation terms 
     17   USE prtctl_trc      ! print control for debugging 
    1818 
    1919   IMPLICIT NONE 
     
    2323   PUBLIC   p4z_mort_init     
    2424 
    25    !! * Shared module variables 
    26    REAL(wp), PUBLIC :: wchl    !: 
    27    REAL(wp), PUBLIC :: wchld   !: 
    28    REAL(wp), PUBLIC :: wchldm  !: 
    29    REAL(wp), PUBLIC :: mprat   !: 
    30    REAL(wp), PUBLIC :: mprat2  !: 
     25   REAL(wp), PUBLIC ::   wchl     !: 
     26   REAL(wp), PUBLIC ::   wchld    !: 
     27   REAL(wp), PUBLIC ::   wchldm   !: 
     28   REAL(wp), PUBLIC ::   mprat    !: 
     29   REAL(wp), PUBLIC ::   mprat2   !: 
    3130 
    3231   !!---------------------------------------------------------------------- 
     
    3534   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    3635   !!---------------------------------------------------------------------- 
    37  
    3836CONTAINS 
    3937 
     
    4947      INTEGER, INTENT(in) ::   kt ! ocean time step 
    5048      !!--------------------------------------------------------------------- 
    51  
     49      ! 
    5250      CALL p4z_nano            ! nanophytoplankton 
    53  
     51      ! 
    5452      CALL p4z_diat            ! diatoms 
    55  
     53      ! 
    5654   END SUBROUTINE p4z_mort 
    5755 
     
    6563      !! ** Method  : - ??? 
    6664      !!--------------------------------------------------------------------- 
    67       INTEGER  :: ji, jj, jk 
    68       REAL(wp) :: zsizerat, zcompaph 
    69       REAL(wp) :: zfactfe, zfactch, zprcaca, zfracal 
    70       REAL(wp) :: ztortp , zrespp , zmortp  
    71       CHARACTER (len=25) :: charout 
     65      INTEGER  ::   ji, jj, jk 
     66      REAL(wp) ::   zsizerat, zcompaph 
     67      REAL(wp) ::   zfactfe, zfactch, zprcaca, zfracal 
     68      REAL(wp) ::   ztortp , zrespp , zmortp  
     69      CHARACTER (len=25) ::   charout 
    7270      !!--------------------------------------------------------------------- 
    7371      ! 
    7472      IF( ln_timing )   CALL timing_start('p4z_nano') 
    7573      ! 
    76       prodcal(:,:,:) = 0.  !: calcite production variable set to zero 
     74      prodcal(:,:,:) = 0._wp   ! calcite production variable set to zero 
    7775      DO jk = 1, jpkm1 
    7876         DO jj = 1, jpj 
     
    139137      !! ** Method  : - ??? 
    140138      !!--------------------------------------------------------------------- 
    141       INTEGER  ::  ji, jj, jk 
    142       REAL(wp) ::  zfactfe,zfactsi,zfactch, zcompadi 
    143       REAL(wp) ::  zrespp2, ztortp2, zmortp2 
    144       REAL(wp) ::  zlim2, zlim1 
    145       CHARACTER (len=25) :: charout 
     139      INTEGER  ::   ji, jj, jk 
     140      REAL(wp) ::   zfactfe,zfactsi,zfactch, zcompadi 
     141      REAL(wp) ::   zrespp2, ztortp2, zmortp2 
     142      REAL(wp) ::   zlim2, zlim1 
     143      CHARACTER (len=25) ::   charout 
    146144      !!--------------------------------------------------------------------- 
    147145      ! 
    148146      IF( ln_timing )   CALL timing_start('p4z_diat') 
    149147      ! 
    150  
    151148      !    Aggregation term for diatoms is increased in case of nutrient 
    152149      !    stress as observed in reality. The stressed cells become more 
     
    196193      END DO 
    197194      ! 
    198       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     195      IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
    199196         WRITE(charout, FMT="('diat')") 
    200197         CALL prt_ctl_trc_info(charout) 
     
    214211      !! 
    215212      !! ** Method  :   Read the nampismort namelist and check the parameters 
    216       !!      called at the first timestep 
     213      !!              called at the first timestep 
    217214      !! 
    218215      !! ** input   :   Namelist nampismort 
     
    224221      !!---------------------------------------------------------------------- 
    225222      ! 
     223      IF(lwp) THEN 
     224         WRITE(numout,*)  
     225         WRITE(numout,*) 'p4z_mort_init : Initialization of phytoplankton mortality parameters' 
     226         WRITE(numout,*) '~~~~~~~~~~~~~' 
     227      ENDIF 
     228      ! 
    226229      REWIND( numnatp_ref )              ! Namelist nampismort in reference namelist : Pisces phytoplankton 
    227230      READ  ( numnatp_ref, namp4zmort, IOSTAT = ios, ERR = 901) 
    228 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namp4zmort in reference namelist', lwp ) 
    229       ! 
     231901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zmort in reference namelist', lwp ) 
    230232      REWIND( numnatp_cfg )              ! Namelist nampismort in configuration namelist : Pisces phytoplankton 
    231233      READ  ( numnatp_cfg, namp4zmort, IOSTAT = ios, ERR = 902 ) 
    232 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namp4zmort in configuration namelist', lwp ) 
    233       IF(lwm) WRITE ( numonp, namp4zmort ) 
     234902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zmort in configuration namelist', lwp ) 
     235      IF(lwm) WRITE( numonp, namp4zmort ) 
    234236      ! 
    235237      IF(lwp) THEN                         ! control print 
    236          WRITE(numout,*) ' ' 
    237          WRITE(numout,*) ' Namelist parameters for phytoplankton mortality, namp4zmort' 
    238          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    239          WRITE(numout,*) '    quadratic mortality of phytoplankton      wchl      =', wchl 
    240          WRITE(numout,*) '    maximum quadratic mortality of diatoms    wchld     =', wchld 
    241          WRITE(numout,*) '    maximum quadratic mortality of diatoms    wchldm    =', wchldm 
    242          WRITE(numout,*) '    phytoplankton mortality rate              mprat     =', mprat 
    243          WRITE(numout,*) '    Diatoms mortality rate                    mprat2    =', mprat2 
     238         WRITE(numout,*) '   Namelist : namp4zmort' 
     239         WRITE(numout,*) '      quadratic mortality of phytoplankton        wchl   =', wchl 
     240         WRITE(numout,*) '      maximum quadratic mortality of diatoms      wchld  =', wchld 
     241         WRITE(numout,*) '      maximum quadratic mortality of diatoms      wchldm =', wchldm 
     242         WRITE(numout,*) '      phytoplankton mortality rate                mprat  =', mprat 
     243         WRITE(numout,*) '      Diatoms mortality rate                      mprat2 =', mprat2 
    244244      ENDIF 
    245245      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zopt.F90

    r9125 r9169  
    44   !! TOP - PISCES : Compute the light availability in the water column 
    55   !!====================================================================== 
    6    !! History :   1.0  !  2004     (O. Aumont) Original code 
    7    !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    8    !!             3.2  !  2009-04  (C. Ethe, G. Madec)  optimisation 
    9    !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Improve light availability of nano & diat 
     6   !! History :  1.0  !  2004     (O. Aumont) Original code 
     7   !!            2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
     8   !!            3.2  !  2009-04  (C. Ethe, G. Madec)  optimisation 
     9   !!            3.4  !  2011-06  (O. Aumont, C. Ethe) Improve light availability of nano & diat 
    1010   !!---------------------------------------------------------------------- 
    1111   !!   p4z_opt       : light availability in the water column 
     
    1515   USE sms_pisces     ! Source Minus Sink of PISCES 
    1616   USE iom            ! I/O manager 
    17    USE fldread         !  time interpolation 
    18    USE prtctl_trc      !  print control for debugging 
     17   USE fldread        !  time interpolation 
     18   USE prtctl_trc     !  print control for debugging 
    1919 
    2020   IMPLICIT NONE 
     
    2727   !! * Shared module variables 
    2828 
    29    LOGICAL  :: ln_varpar   !: boolean for variable PAR fraction 
    30    REAL(wp) :: parlux      !: Fraction of shortwave as PAR 
    31    REAL(wp) :: xparsw                 !: parlux/3 
    32    REAL(wp) :: xsi0r                 !: 1. /rn_si0 
     29   LOGICAL  ::   ln_varpar   ! boolean for variable PAR fraction 
     30   REAL(wp) ::   parlux      ! Fraction of shortwave as PAR 
     31   REAL(wp) ::   xparsw      ! parlux/3 
     32   REAL(wp) ::   xsi0r       ! 1. /rn_si0 
    3333 
    3434   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_par      ! structure of input par 
    3535   INTEGER , PARAMETER :: nbtimes = 366  !: maximum number of times record in a file 
    3636   INTEGER  :: ntimes_par                ! number of time steps in a file 
    37    REAL(wp), ALLOCATABLE, SAVE,   DIMENSION(:,:) :: par_varsw    !: PAR fraction of shortwave 
    38    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ekb, ekg, ekr  !: wavelength (Red-Green-Blue) 
     37   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   par_varsw      ! PAR fraction of shortwave 
     38   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ekb, ekg, ekr  ! wavelength (Red-Green-Blue) 
    3939 
    4040   INTEGER  ::   nksrp   ! levels below which the light cannot penetrate ( depth larger than 391 m) 
    4141 
    42    REAL(wp), DIMENSION(3,61) ::   xkrgb   !: tabulated attenuation coefficients for RGB absorption 
     42   REAL(wp), DIMENSION(3,61) ::   xkrgb   ! tabulated attenuation coefficients for RGB absorption 
    4343    
    4444   !!---------------------------------------------------------------------- 
     
    7070      !!--------------------------------------------------------------------- 
    7171      ! 
    72       IF( ln_timing )  CALL timing_start('p4z_opt') 
    73       ! 
    74       ! Allocate temporary workspace 
    75       IF( ln_p5z ) ALLOCATE( zetmp5(jpi,jpj) ) 
    76  
    77       IF( knt == 1 .AND. ln_varpar ) CALL p4z_opt_sbc( kt ) 
     72      IF( ln_timing )   CALL timing_start('p4z_opt') 
     73      IF( ln_p5z    )   ALLOCATE( zetmp5(jpi,jpj) ) 
     74 
     75      IF( knt == 1 .AND. ln_varpar )   CALL p4z_opt_sbc( kt ) 
    7876 
    7977      !     Initialisation of variables used to compute PAR 
     
    8482      ! 
    8583      !                                        !* attenuation coef. function of Chlorophyll and wavelength (Red-Green-Blue) 
    86                                                !  -------------------------------------------------------- 
    87                     zchl3d(:,:,:) = trb(:,:,:,jpnch) + trb(:,:,:,jpdch) 
    88       IF( ln_p5z )  zchl3d(:,:,:) = zchl3d(:,:,:) + trb(:,:,:,jppch) 
     84      !                                        !  -------------------------------------------------------- 
     85                     zchl3d(:,:,:) = trb(:,:,:,jpnch) + trb(:,:,:,jpdch) 
     86      IF( ln_p5z )   zchl3d(:,:,:) = zchl3d(:,:,:)    + trb(:,:,:,jppch) 
    8987      ! 
    9088      DO jk = 1, jpkm1    
     
    105103      IF( l_trcdm2dc ) THEN                     !  diurnal cycle 
    106104         ! 
    107          zqsr_corr(:,:) = qsr_mean(:,:) / ( 1. - fr_i(:,:) + rtrn ) 
     105         zqsr_corr(:,:) = qsr_mean(:,:) / ( 1.-fr_i(:,:) + rtrn ) 
    108106         ! 
    109107         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3, pqsr100 = zqsr100 )  
     
    120118         ENDIF 
    121119         ! 
    122          zqsr_corr(:,:) = qsr(:,:) / ( 1. - fr_i(:,:) + rtrn ) 
     120         zqsr_corr(:,:) = qsr(:,:) / ( 1.-fr_i(:,:) + rtrn ) 
    123121         ! 
    124122         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3 )  
     
    130128      ELSE 
    131129         ! 
    132          zqsr_corr(:,:) = qsr(:,:) / ( 1. - fr_i(:,:) + rtrn ) 
     130         zqsr_corr(:,:) = qsr(:,:) / ( 1.-fr_i(:,:) + rtrn ) 
    133131         ! 
    134132         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3, pqsr100 = zqsr100  )  
     
    240238      ENDIF 
    241239      ! 
    242       IF( ln_p5z ) DEALLOCATE( zetmp5 ) 
    243       ! 
    244       IF( ln_timing )  CALL timing_stop('p4z_opt') 
     240      IF( ln_p5z    )   DEALLOCATE( zetmp5 ) 
     241      IF( ln_timing )   CALL timing_stop('p4z_opt') 
    245242      ! 
    246243   END SUBROUTINE p4z_opt 
     
    255252      !! 
    256253      !!---------------------------------------------------------------------- 
    257       !! * arguments 
    258       INTEGER, INTENT(in)                                       ::  kt            !   ocean time-step 
    259       REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in)              ::  pqsr          !   shortwave 
    260       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout)           ::  pe1 , pe2 , pe3   !  PAR ( R-G-B) 
    261       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout), OPTIONAL ::  pe0   
    262       REAL(wp), DIMENSION(jpi,jpj)    , INTENT(out)  , OPTIONAL  ::  pqsr100   
    263       !! * local variables 
     254      INTEGER                         , INTENT(in)              ::   kt                ! ocean time-step 
     255      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in   )           ::   pqsr              ! shortwave 
     256      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout)           ::   pe1 , pe2 , pe3   ! PAR ( R-G-B) 
     257      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout), OPTIONAL ::   pe0               ! 
     258      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(  out), OPTIONAL ::   pqsr100           ! 
     259      ! 
    264260      INTEGER    ::   ji, jj, jk     ! dummy loop indices 
    265       REAL(wp), DIMENSION(jpi,jpj)     ::  zqsr          !  shortwave 
     261      REAL(wp), DIMENSION(jpi,jpj) ::  zqsr   ! shortwave 
    266262      !!---------------------------------------------------------------------- 
    267263 
     
    272268       
    273269      !  Light at the euphotic depth  
    274       IF( PRESENT( pqsr100 ) )  pqsr100(:,:) = 0.01 * 3. * zqsr(:,:) 
     270      IF( PRESENT( pqsr100 ) )   pqsr100(:,:) = 0.01 * 3. * zqsr(:,:) 
    275271 
    276272      IF( PRESENT( pe0 ) ) THEN     !  W-level 
     
    285281               DO ji = 1, jpi 
    286282                  pe0(ji,jj,jk) = pe0(ji,jj,jk-1) * EXP( -e3t_n(ji,jj,jk-1) * xsi0r ) 
    287                   pe1(ji,jj,jk) = pe1(ji,jj,jk-1) * EXP( -ekb(ji,jj,jk-1 ) ) 
    288                   pe2(ji,jj,jk) = pe2(ji,jj,jk-1) * EXP( -ekg(ji,jj,jk-1 ) ) 
    289                   pe3(ji,jj,jk) = pe3(ji,jj,jk-1) * EXP( -ekr(ji,jj,jk-1 ) ) 
     283                  pe1(ji,jj,jk) = pe1(ji,jj,jk-1) * EXP( -ekb  (ji,jj,jk-1 )        ) 
     284                  pe2(ji,jj,jk) = pe2(ji,jj,jk-1) * EXP( -ekg  (ji,jj,jk-1 )        ) 
     285                  pe3(ji,jj,jk) = pe3(ji,jj,jk-1) * EXP( -ekr  (ji,jj,jk-1 )        ) 
    290286               END DO 
    291287              ! 
     
    327323      !! 
    328324      !!---------------------------------------------------------------------- 
    329       INTEGER ,                INTENT(in) ::   kt     ! ocean time step 
     325      INTEGER, INTENT(in) ::   kt   ! ocean time step 
    330326      ! 
    331327      INTEGER  :: ji,jj 
     
    357353      !! ** Input   :   external ascii and netcdf files 
    358354      !!---------------------------------------------------------------------- 
    359       INTEGER :: numpar 
    360       INTEGER :: ierr 
    361       INTEGER :: ios                 ! Local integer output status for namelist read 
    362       REAL(wp), DIMENSION(nbtimes) :: zsteps                 ! times records 
     355      INTEGER :: numpar, ierr, ios   ! Local integer  
     356      REAL(wp), DIMENSION(nbtimes) ::   zsteps   ! times records 
    363357      ! 
    364358      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files 
     
    367361      NAMELIST/nampisopt/cn_dir, sn_par, ln_varpar, parlux 
    368362      !!---------------------------------------------------------------------- 
    369  
     363      IF(lwp) THEN 
     364         WRITE(numout,*) 
     365         WRITE(numout,*) 'p4z_opt_init : ' 
     366         WRITE(numout,*) '~~~~~~~~~~~~ ' 
     367      ENDIF 
    370368      REWIND( numnatp_ref )              ! Namelist nampisopt in reference namelist : Pisces attenuation coef. and PAR 
    371369      READ  ( numnatp_ref, nampisopt, IOSTAT = ios, ERR = 901) 
    372 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisopt in reference namelist', lwp ) 
    373  
     370901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisopt in reference namelist', lwp ) 
    374371      REWIND( numnatp_cfg )              ! Namelist nampisopt in configuration namelist : Pisces attenuation coef. and PAR 
    375372      READ  ( numnatp_cfg, nampisopt, IOSTAT = ios, ERR = 902 ) 
    376 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisopt in configuration namelist', lwp ) 
     373902   IF( ios >  0 )  CALL ctl_nam ( ios , 'nampisopt in configuration namelist', lwp ) 
    377374      IF(lwm) WRITE ( numonp, nampisopt ) 
    378375 
    379376      IF(lwp) THEN 
    380          WRITE(numout,*) ' ' 
    381          WRITE(numout,*) ' namelist : nampisopt ' 
    382          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~ ' 
    383          WRITE(numout,*) '    PAR as a variable fraction of SW     ln_varpar      = ', ln_varpar 
    384          WRITE(numout,*) '    Default value for the PAR fraction   parlux         = ', parlux 
     377         WRITE(numout,*) '   Namelist : nampisopt ' 
     378         WRITE(numout,*) '      PAR as a variable fraction of SW     ln_varpar      = ', ln_varpar 
     379         WRITE(numout,*) '      Default value for the PAR fraction   parlux         = ', parlux 
    385380      ENDIF 
    386381      ! 
     
    391386      ! ---------------------------------------- 
    392387      IF( ln_varpar ) THEN 
    393          IF(lwp) WRITE(numout,*) '    initialize variable par fraction ' 
    394          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     388         IF(lwp) WRITE(numout,*) 
     389         IF(lwp) WRITE(numout,*) '   ==>>>   initialize variable par fraction (ln_varpar=T)' 
    395390         ! 
    396391         ALLOCATE( par_varsw(jpi,jpj) ) 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zpoc.F90

    r9125 r9169  
    2323   PUBLIC   p4z_poc         ! called in p4zbio.F90 
    2424   PUBLIC   p4z_poc_init    ! called in trcsms_pisces.F90 
    25    PUBLIC   alngam 
    26    PUBLIC   gamain 
    27  
    28    !! * Shared module variables 
    29    REAL(wp), PUBLIC ::  xremip     !: remineralisation rate of DOC 
    30    REAL(wp), PUBLIC ::  xremipc    !: remineralisation rate of DOC 
    31    REAL(wp), PUBLIC ::  xremipn    !: remineralisation rate of DON 
    32    REAL(wp), PUBLIC ::  xremipp    !: remineralisation rate of DOP 
    33    INTEGER , PUBLIC ::  jcpoc      !: number of lability classes 
    34    REAL(wp), PUBLIC ::  rshape     !: shape factor of the gamma distribution 
    35  
    36    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::   alphan, reminp 
    37    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: alphap 
     25   PUBLIC   alngam          ! 
     26   PUBLIC   gamain          ! 
     27 
     28   REAL(wp), PUBLIC ::   xremip     !: remineralisation rate of DOC 
     29   REAL(wp), PUBLIC ::   xremipc    !: remineralisation rate of DOC 
     30   REAL(wp), PUBLIC ::   xremipn    !: remineralisation rate of DON 
     31   REAL(wp), PUBLIC ::   xremipp    !: remineralisation rate of DOP 
     32   INTEGER , PUBLIC ::   jcpoc      !: number of lability classes 
     33   REAL(wp), PUBLIC ::   rshape     !: shape factor of the gamma distribution 
     34 
     35   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   alphan, reminp   !: 
     36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   alphap           !: 
    3837 
    3938 
     
    5352      !! ** Method  : - ??? 
    5453      !!--------------------------------------------------------------------- 
    55       ! 
    56       INTEGER, INTENT(in) ::   kt, knt ! ocean time step 
     54      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step and ??? 
    5755      ! 
    5856      INTEGER  ::   ji, jj, jk, jn 
     
    187185      END DO 
    188186 
    189       IF( ln_p4z ) THEN   ;  zremigoc(:,:,:) = MIN( xremip , ztremint(:,:,:) ) 
    190       ELSE                ;  zremigoc(:,:,:) = MIN( xremipc, ztremint(:,:,:) ) 
     187      IF( ln_p4z ) THEN   ;   zremigoc(:,:,:) = MIN( xremip , ztremint(:,:,:) ) 
     188      ELSE                ;   zremigoc(:,:,:) = MIN( xremipc, ztremint(:,:,:) ) 
    191189      ENDIF 
    192190 
     
    260258     ! ------------------------------------------------------------------- 
    261259     ! 
    262      totprod(:,:) = 0. 
     260     totprod (:,:) = 0. 
    263261     totthick(:,:) = 0. 
    264      totcons(:,:) = 0. 
     262     totcons (:,:) = 0. 
    265263     ! intregrated production and consumption of POC in the mixed layer 
    266264     ! ---------------------------------------------------------------- 
     
    396394      END DO 
    397395 
    398      IF( ln_p4z ) THEN   ;  zremipoc(:,:,:) = MIN( xremip , ztremint(:,:,:) ) 
    399      ELSE                ;  zremipoc(:,:,:) = MIN( xremipc, ztremint(:,:,:) ) 
     396     IF( ln_p4z ) THEN   ;   zremipoc(:,:,:) = MIN( xremip , ztremint(:,:,:) ) 
     397     ELSE                ;   zremipoc(:,:,:) = MIN( xremipc, ztremint(:,:,:) ) 
    400398     ENDIF 
    401399 
     
    473471      !! 
    474472      !! ** Method  :   Read the nampispoc namelist and check the parameters 
    475       !!      called at the first timestep 
     473      !!              called at the first timestep 
    476474      !! 
    477475      !! ** input   :   Namelist nampispoc 
    478       !! 
    479476      !!---------------------------------------------------------------------- 
     477      INTEGER ::   jn            ! dummy loop index 
    480478      INTEGER ::   ios, ifault   ! Local integer 
    481       INTEGER ::   jn 
    482       REAL(wp) :: remindelta, reminup, remindown 
     479      REAL(wp)::   remindelta, reminup, remindown 
    483480      !! 
    484481      NAMELIST/nampispoc/ xremip , jcpoc  , rshape,  & 
    485482         &                xremipc, xremipn, xremipp 
    486483      !!---------------------------------------------------------------------- 
    487  
     484      ! 
     485      IF(lwp) THEN 
     486         WRITE(numout,*) 
     487         WRITE(numout,*) 'p4z_poc_init : Initialization of remineralization parameters' 
     488         WRITE(numout,*) '~~~~~~~~~~~~' 
     489      ENDIF 
     490      ! 
    488491      REWIND( numnatp_ref )              ! Namelist nampisrem in reference namelist : Pisces remineralization 
    489492      READ  ( numnatp_ref, nampispoc, IOSTAT = ios, ERR = 901) 
    490 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampispoc in reference namelist', lwp ) 
    491  
     493901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampispoc in reference namelist', lwp ) 
    492494      REWIND( numnatp_cfg )              ! Namelist nampisrem in configuration namelist : Pisces remineralization 
    493495      READ  ( numnatp_cfg, nampispoc, IOSTAT = ios, ERR = 902 ) 
    494 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampispoc in configuration namelist', lwp ) 
    495       IF(lwm) WRITE ( numonp, nampispoc ) 
     496902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampispoc in configuration namelist', lwp ) 
     497      IF(lwm) WRITE( numonp, nampispoc ) 
    496498 
    497499      IF(lwp) THEN                         ! control print 
    498          WRITE(numout,*) ' ' 
    499          WRITE(numout,*) ' Namelist parameters for remineralization, nampispoc' 
    500          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     500         WRITE(numout,*) '   Namelist : nampispoc' 
    501501         IF( ln_p4z ) THEN 
    502             WRITE(numout,*) '    remineralisation rate of POC              xremip    =', xremip 
     502            WRITE(numout,*) '      remineralisation rate of POC              xremip    =', xremip 
    503503         ELSE 
    504             WRITE(numout,*) '    remineralisation rate of POC              xremipc   =', xremipc 
    505             WRITE(numout,*) '    remineralisation rate of PON              xremipn   =', xremipn 
    506             WRITE(numout,*) '    remineralisation rate of POP              xremipp   =', xremipp 
     504            WRITE(numout,*) '      remineralisation rate of POC              xremipc   =', xremipc 
     505            WRITE(numout,*) '      remineralisation rate of PON              xremipn   =', xremipn 
     506            WRITE(numout,*) '      remineralisation rate of POP              xremipp   =', xremipp 
    507507         ENDIF 
    508          WRITE(numout,*) '    Number of lability classes for POC        jcpoc     =', jcpoc 
    509          WRITE(numout,*) '    Shape factor of the gamma distribution    rshape    =', rshape 
     508         WRITE(numout,*) '      Number of lability classes for POC        jcpoc     =', jcpoc 
     509         WRITE(numout,*) '      Shape factor of the gamma distribution    rshape    =', rshape 
    510510      ENDIF 
    511511      ! 
     
    513513      ! --------------------------------------- 
    514514      ! 
    515       ALLOCATE( alphan(jcpoc), reminp(jcpoc) ) 
    516       ALLOCATE( alphap(jpi,jpj,jpk,jcpoc) ) 
     515      ALLOCATE( alphan(jcpoc) , reminp(jcpoc) , alphap(jpi,jpj,jpk,jcpoc) ) 
    517516      ! 
    518517      IF (jcpoc > 1) THEN 
     
    551550   END SUBROUTINE p4z_poc_init 
    552551 
     552 
    553553   REAL FUNCTION alngam( xvalue, ifault ) 
    554  
    555 !*****************************************************************************80 
    556 ! 
    557 !! ALNGAM computes the logarithm of the gamma function. 
    558 ! 
    559 !  Modified: 
    560 ! 
    561 !    13 January 2008 
    562 ! 
    563 !  Author: 
    564 ! 
    565 !    Allan Macleod 
    566 !    FORTRAN90 version by John Burkardt 
    567 ! 
    568 !  Reference: 
    569 ! 
    570 !    Allan Macleod, 
    571 !    Algorithm AS 245, 
    572 !    A Robust and Reliable Algorithm for the Logarithm of the Gamma Function, 
    573 !    Applied Statistics, 
    574 !    Volume 38, Number 2, 1989, pages 397-402. 
    575 ! 
    576 !  Parameters: 
    577 ! 
    578 !    Input, real ( kind = 8 ) XVALUE, the argument of the Gamma function. 
    579 ! 
    580 !    Output, integer ( kind = 4 ) IFAULT, error flag. 
    581 !    0, no error occurred. 
    582 !    1, XVALUE is less than or equal to 0. 
    583 !    2, XVALUE is too big. 
    584 ! 
    585 !    Output, real ( kind = 8 ) ALNGAM, the logarithm of the gamma function of X. 
    586 ! 
     554      !*****************************************************************************80 
     555      ! 
     556      !! ALNGAM computes the logarithm of the gamma function. 
     557      ! 
     558      !  Modified:    13 January 2008 
     559      ! 
     560      !  Author  :    Allan Macleod 
     561      !               FORTRAN90 version by John Burkardt 
     562      ! 
     563      !  Reference: 
     564      !    Allan Macleod, Algorithm AS 245, 
     565      !    A Robust and Reliable Algorithm for the Logarithm of the Gamma Function, 
     566      !    Applied Statistics, 
     567      !    Volume 38, Number 2, 1989, pages 397-402. 
     568      ! 
     569      !  Parameters: 
     570      ! 
     571      !    Input, real ( kind = 8 ) XVALUE, the argument of the Gamma function. 
     572      ! 
     573      !    Output, integer ( kind = 4 ) IFAULT, error flag. 
     574      !    0, no error occurred. 
     575      !    1, XVALUE is less than or equal to 0. 
     576      !    2, XVALUE is too big. 
     577      ! 
     578      !    Output, real ( kind = 8 ) ALNGAM, the logarithm of the gamma function of X. 
     579      !*****************************************************************************80 
    587580  implicit none 
    588581 
     
    746739   END FUNCTION alngam 
    747740 
     741 
    748742   REAL FUNCTION gamain( x, p, ifault ) 
    749  
    750743!*****************************************************************************80 
    751744! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zprod.F90

    r9125 r9169  
    88   !!             3.4  !  2011-05  (O. Aumont, C. Ethe) New parameterization of light limitation 
    99   !!---------------------------------------------------------------------- 
    10    !!   p4z_prod       :   Compute the growth Rate of the two phytoplanktons groups 
    11    !!   p4z_prod_init  :   Initialization of the parameters for growth 
    12    !!   p4z_prod_alloc :   Allocate variables for growth 
     10   !!   p4z_prod       : Compute the growth Rate of the two phytoplanktons groups 
     11   !!   p4z_prod_init  : Initialization of the parameters for growth 
     12   !!   p4z_prod_alloc : Allocate variables for growth 
    1313   !!---------------------------------------------------------------------- 
    14    USE oce_trc         !  shared variables between ocean and passive tracers 
    15    USE trc             !  passive tracers common variables  
    16    USE sms_pisces      !  PISCES Source Minus Sink variables 
    17    USE p4zlim          !  Co-limitations of differents nutrients 
    18    USE prtctl_trc      !  print control for debugging 
    19    USE iom             !  I/O manager 
     14   USE oce_trc         ! shared variables between ocean and passive tracers 
     15   USE trc             ! passive tracers common variables  
     16   USE sms_pisces      ! PISCES Source Minus Sink variables 
     17   USE p4zlim          ! Co-limitations of differents nutrients 
     18   USE prtctl_trc      ! print control for debugging 
     19   USE iom             ! I/O manager 
    2020 
    2121   IMPLICIT NONE 
     
    2626   PUBLIC   p4z_prod_alloc 
    2727 
    28    !! * Shared module variables 
    29    LOGICAL , PUBLIC ::  ln_newprod      !: 
    30    REAL(wp), PUBLIC ::  pislopen         !: 
    31    REAL(wp), PUBLIC ::  pisloped        !: 
    32    REAL(wp), PUBLIC ::  xadap           !: 
    33    REAL(wp), PUBLIC ::  excretn          !: 
    34    REAL(wp), PUBLIC ::  excretd         !: 
    35    REAL(wp), PUBLIC ::  bresp           !: 
    36    REAL(wp), PUBLIC ::  chlcnm          !: 
    37    REAL(wp), PUBLIC ::  chlcdm          !: 
    38    REAL(wp), PUBLIC ::  chlcmin         !: 
    39    REAL(wp), PUBLIC ::  fecnm           !: 
    40    REAL(wp), PUBLIC ::  fecdm           !: 
    41    REAL(wp), PUBLIC ::  grosip          !: 
     28   LOGICAL , PUBLIC ::   ln_newprod   !: 
     29   REAL(wp), PUBLIC ::   pislopen     !: 
     30   REAL(wp), PUBLIC ::   pisloped     !: 
     31   REAL(wp), PUBLIC ::   xadap        !: 
     32   REAL(wp), PUBLIC ::   excretn      !: 
     33   REAL(wp), PUBLIC ::   excretd      !: 
     34   REAL(wp), PUBLIC ::   bresp        !: 
     35   REAL(wp), PUBLIC ::   chlcnm       !: 
     36   REAL(wp), PUBLIC ::   chlcdm       !: 
     37   REAL(wp), PUBLIC ::   chlcmin      !: 
     38   REAL(wp), PUBLIC ::   fecnm        !: 
     39   REAL(wp), PUBLIC ::   fecdm        !: 
     40   REAL(wp), PUBLIC ::   grosip       !: 
    4241 
    4342   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prmax    !: optimal production = f(temperature) 
     
    4544   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   quotad   !: proxy of N quota in diatomee 
    4645    
    47    REAL(wp) :: r1_rday                !: 1 / rday 
    48    REAL(wp) :: texcretn               !: 1 - excretn  
    49    REAL(wp) :: texcretd               !: 1 - excretd         
     46   REAL(wp) ::   r1_rday    ! 1 / rday 
     47   REAL(wp) ::   texcretn   ! 1 - excretn  
     48   REAL(wp) ::   texcretd   ! 1 - excretd         
    5049 
    5150   !!---------------------------------------------------------------------- 
     
    6564      !! ** Method  : - ??? 
    6665      !!--------------------------------------------------------------------- 
    67       INTEGER, INTENT(in) :: kt, knt 
     66      INTEGER, INTENT(in) ::   kt, knt   ! 
    6867      ! 
    6968      INTEGER  ::   ji, jj, jk 
     
    475474         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    476475     ENDIF 
    477      ! 
    478      IF( ln_timing )  CALL timing_stop('p4z_prod') 
    479      ! 
     476      ! 
     477      IF( ln_timing )  CALL timing_stop('p4z_prod') 
     478      ! 
    480479   END SUBROUTINE p4z_prod 
    481480 
     
    492491      !! ** input   :   Namelist nampisprod 
    493492      !!---------------------------------------------------------------------- 
    494       INTEGER :: ios                 ! Local integer output status for namelist read 
     493      INTEGER ::   ios   ! Local integer 
    495494      ! 
    496495      NAMELIST/namp4zprod/ pislopen, pisloped, xadap, ln_newprod, bresp, excretn, excretd,  & 
    497496         &                 chlcnm, chlcdm, chlcmin, fecnm, fecdm, grosip 
    498497      !!---------------------------------------------------------------------- 
    499  
     498      ! 
     499      IF(lwp) THEN                         ! control print 
     500         WRITE(numout,*) 
     501         WRITE(numout,*) 'p4z_prod_init : phytoplankton growth' 
     502         WRITE(numout,*) '~~~~~~~~~~~~~' 
     503      ENDIF 
     504      ! 
    500505      REWIND( numnatp_ref )              ! Namelist nampisprod in reference namelist : Pisces phytoplankton production 
    501506      READ  ( numnatp_ref, namp4zprod, IOSTAT = ios, ERR = 901) 
    502 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namp4zprod in reference namelist', lwp ) 
    503  
     507901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zprod in reference namelist', lwp ) 
    504508      REWIND( numnatp_cfg )              ! Namelist nampisprod in configuration namelist : Pisces phytoplankton production 
    505509      READ  ( numnatp_cfg, namp4zprod, IOSTAT = ios, ERR = 902 ) 
    506 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namp4zprod in configuration namelist', lwp ) 
    507       IF(lwm) WRITE ( numonp, namp4zprod ) 
     510902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zprod in configuration namelist', lwp ) 
     511      IF(lwm) WRITE( numonp, namp4zprod ) 
    508512 
    509513      IF(lwp) THEN                         ! control print 
    510          WRITE(numout,*) ' ' 
    511          WRITE(numout,*) ' Namelist parameters for phytoplankton growth, namp4zprod' 
    512          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    513          WRITE(numout,*) '    Enable new parame. of production (T/F)   ln_newprod    =', ln_newprod 
    514          WRITE(numout,*) '    mean Si/C ratio                           grosip       =', grosip 
    515          WRITE(numout,*) '    P-I slope                                 pislopen     =', pislopen 
    516          WRITE(numout,*) '    Acclimation factor to low light           xadap        =', xadap 
    517          WRITE(numout,*) '    excretion ratio of nanophytoplankton      excretn      =', excretn 
    518          WRITE(numout,*) '    excretion ratio of diatoms                excretd      =', excretd 
     514         WRITE(numout,*) '   Namelist : namp4zprod' 
     515         WRITE(numout,*) '      Enable new parame. of production (T/F)   ln_newprod    =', ln_newprod 
     516         WRITE(numout,*) '      mean Si/C ratio                           grosip       =', grosip 
     517         WRITE(numout,*) '      P-I slope                                 pislopen     =', pislopen 
     518         WRITE(numout,*) '      Acclimation factor to low light           xadap        =', xadap 
     519         WRITE(numout,*) '      excretion ratio of nanophytoplankton      excretn      =', excretn 
     520         WRITE(numout,*) '      excretion ratio of diatoms                excretd      =', excretd 
    519521         IF( ln_newprod )  THEN 
    520             WRITE(numout,*) '    basal respiration in phytoplankton        bresp        =', bresp 
    521             WRITE(numout,*) '    Maximum Chl/C in phytoplankton            chlcmin      =', chlcmin 
     522            WRITE(numout,*) '      basal respiration in phytoplankton        bresp        =', bresp 
     523            WRITE(numout,*) '      Maximum Chl/C in phytoplankton            chlcmin      =', chlcmin 
    522524         ENDIF 
    523          WRITE(numout,*) '    P-I slope  for diatoms                    pisloped     =', pisloped 
    524          WRITE(numout,*) '    Minimum Chl/C in nanophytoplankton        chlcnm       =', chlcnm 
    525          WRITE(numout,*) '    Minimum Chl/C in diatoms                  chlcdm       =', chlcdm 
    526          WRITE(numout,*) '    Maximum Fe/C in nanophytoplankton         fecnm        =', fecnm 
    527          WRITE(numout,*) '    Minimum Fe/C in diatoms                   fecdm        =', fecdm 
     525         WRITE(numout,*) '      P-I slope  for diatoms                    pisloped     =', pisloped 
     526         WRITE(numout,*) '      Minimum Chl/C in nanophytoplankton        chlcnm       =', chlcnm 
     527         WRITE(numout,*) '      Minimum Chl/C in diatoms                  chlcdm       =', chlcdm 
     528         WRITE(numout,*) '      Maximum Fe/C in nanophytoplankton         fecnm        =', fecnm 
     529         WRITE(numout,*) '      Minimum Fe/C in diatoms                   fecdm        =', fecdm 
    528530      ENDIF 
    529531      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zrem.F90

    r9125 r9169  
    2929   PUBLIC   p4z_rem_alloc 
    3030 
    31    !! * Shared module variables 
    32    REAL(wp), PUBLIC ::  xremikc    !: remineralisation rate of DOC  
    33    REAL(wp), PUBLIC ::  xremikn    !: remineralisation rate of DON  
    34    REAL(wp), PUBLIC ::  xremikp    !: remineralisation rate of DOP  
    35    REAL(wp), PUBLIC ::  xremik     !: remineralisation rate of POC  
    36    REAL(wp), PUBLIC ::  nitrif     !: NH4 nitrification rate  
    37    REAL(wp), PUBLIC ::  xsirem     !: remineralisation rate of POC  
    38    REAL(wp), PUBLIC ::  xsiremlab  !: fast remineralisation rate of POC  
    39    REAL(wp), PUBLIC ::  xsilab     !: fraction of labile biogenic silica  
    40    REAL(wp), PUBLIC ::  feratb     !: Fe/C quota in bacteria 
    41    REAL(wp), PUBLIC ::  xkferb     !: Half-saturation constant for bacteria Fe/C 
    42  
    43    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitr     !: denitrification array 
     31   REAL(wp), PUBLIC ::   xremikc    !: remineralisation rate of DOC  
     32   REAL(wp), PUBLIC ::   xremikn    !: remineralisation rate of DON  
     33   REAL(wp), PUBLIC ::   xremikp    !: remineralisation rate of DOP  
     34   REAL(wp), PUBLIC ::   xremik     !: remineralisation rate of POC  
     35   REAL(wp), PUBLIC ::   nitrif     !: NH4 nitrification rate  
     36   REAL(wp), PUBLIC ::   xsirem     !: remineralisation rate of POC  
     37   REAL(wp), PUBLIC ::   xsiremlab  !: fast remineralisation rate of POC  
     38   REAL(wp), PUBLIC ::   xsilab     !: fraction of labile biogenic silica  
     39   REAL(wp), PUBLIC ::   feratb     !: Fe/C quota in bacteria 
     40   REAL(wp), PUBLIC ::   xkferb     !: Half-saturation constant for bacteria Fe/C 
     41 
     42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitr   !: denitrification array 
    4443 
    4544   !!---------------------------------------------------------------------- 
     
    303302      INTEGER :: ios                 ! Local integer output status for namelist read 
    304303      !!---------------------------------------------------------------------- 
    305  
     304      ! 
     305      IF(lwp) THEN 
     306         WRITE(numout,*) 
     307         WRITE(numout,*) 'p4z_rem_init : Initialization of remineralization parameters' 
     308         WRITE(numout,*) '~~~~~~~~~~~~' 
     309      ENDIF 
     310      ! 
    306311      REWIND( numnatp_ref )              ! Namelist nampisrem in reference namelist : Pisces remineralization 
    307312      READ  ( numnatp_ref, nampisrem, IOSTAT = ios, ERR = 901) 
    308 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisrem in reference namelist', lwp ) 
    309  
     313901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisrem in reference namelist', lwp ) 
    310314      REWIND( numnatp_cfg )              ! Namelist nampisrem in configuration namelist : Pisces remineralization 
    311315      READ  ( numnatp_cfg, nampisrem, IOSTAT = ios, ERR = 902 ) 
    312 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampisrem in configuration namelist', lwp ) 
    313       IF(lwm) WRITE ( numonp, nampisrem ) 
     316902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisrem in configuration namelist', lwp ) 
     317      IF(lwm) WRITE( numonp, nampisrem ) 
    314318 
    315319      IF(lwp) THEN                         ! control print 
    316          WRITE(numout,*) ' ' 
    317          WRITE(numout,*) ' Namelist parameters for remineralization, nampisrem' 
    318          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     320         WRITE(numout,*) '   Namelist parameters for remineralization, nampisrem' 
    319321         IF( ln_p4z ) THEN 
    320             WRITE(numout,*) '    remineralization rate of DOC              xremik    =', xremik 
     322            WRITE(numout,*) '      remineralization rate of DOC              xremik    =', xremik 
    321323         ELSE 
    322             WRITE(numout,*) '    remineralization rate of DOC              xremikc   =', xremikc 
    323             WRITE(numout,*) '    remineralization rate of DON              xremikn   =', xremikn 
    324             WRITE(numout,*) '    remineralization rate of DOP              xremikp   =', xremikp 
     324            WRITE(numout,*) '      remineralization rate of DOC              xremikc   =', xremikc 
     325            WRITE(numout,*) '      remineralization rate of DON              xremikn   =', xremikn 
     326            WRITE(numout,*) '      remineralization rate of DOP              xremikp   =', xremikp 
    325327         ENDIF 
    326          WRITE(numout,*) '    remineralization rate of Si               xsirem    =', xsirem 
    327          WRITE(numout,*) '    fast remineralization rate of Si          xsiremlab =', xsiremlab 
    328          WRITE(numout,*) '    fraction of labile biogenic silica        xsilab    =', xsilab 
    329          WRITE(numout,*) '    NH4 nitrification rate                    nitrif    =', nitrif 
    330          WRITE(numout,*) '    Bacterial Fe/C ratio                      feratb    =', feratb 
    331          WRITE(numout,*) '    Half-saturation constant for bact. Fe/C   xkferb    =', xkferb 
     328         WRITE(numout,*) '      remineralization rate of Si               xsirem    =', xsirem 
     329         WRITE(numout,*) '      fast remineralization rate of Si          xsiremlab =', xsiremlab 
     330         WRITE(numout,*) '      fraction of labile biogenic silica        xsilab    =', xsilab 
     331         WRITE(numout,*) '      NH4 nitrification rate                    nitrif    =', nitrif 
     332         WRITE(numout,*) '      Bacterial Fe/C ratio                      feratb    =', feratb 
     333         WRITE(numout,*) '      Half-saturation constant for bact. Fe/C   xkferb    =', xkferb 
    332334      ENDIF 
    333335      ! 
    334       denitr  (:,:,:) = 0._wp 
     336      denitr(:,:,:) = 0._wp 
    335337      ! 
    336338   END SUBROUTINE p4z_rem_init 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsbc.F90

    r9124 r9169  
    2121   PUBLIC   p4z_sbc_init    
    2222 
    23    LOGICAL , PUBLIC  :: ln_dust     !: boolean for dust input from the atmosphere 
    24    LOGICAL , PUBLIC  :: ln_solub    !: boolean for variable solubility of atmospheric iron 
    25    LOGICAL , PUBLIC  :: ln_river    !: boolean for river input of nutrients 
    26    LOGICAL , PUBLIC  :: ln_ndepo    !: boolean for atmospheric deposition of N 
    27    LOGICAL , PUBLIC  :: ln_ironsed  !: boolean for Fe input from sediments 
    28    LOGICAL , PUBLIC  :: ln_hydrofe  !: boolean for Fe input from hydrothermal vents 
    29    LOGICAL , PUBLIC  :: ln_ironice  !: boolean for Fe input from sea ice 
    30    REAL(wp), PUBLIC  :: sedfeinput  !: Coastal release of Iron 
    31    REAL(wp), PUBLIC  :: dustsolub   !: Solubility of the dust 
    32    REAL(wp), PUBLIC  :: mfrac       !: Mineral Content of the dust 
    33    REAL(wp), PUBLIC  :: icefeinput  !: Iron concentration in sea ice 
    34    REAL(wp), PUBLIC  :: wdust       !: Sinking speed of the dust  
    35    REAL(wp), PUBLIC  :: nitrfix     !: Nitrogen fixation rate    
    36    REAL(wp), PUBLIC  :: diazolight  !: Nitrogen fixation sensitivty to light  
    37    REAL(wp), PUBLIC  :: concfediaz  !: Fe half-saturation Cste for diazotrophs  
    38    REAL(wp)          :: hratio      !: Fe:3He ratio assumed for vent iron supply 
    39    REAL(wp), PUBLIC  :: fep_rats    !: Fep/Fer ratio from sed  sources 
    40    REAL(wp), PUBLIC  :: fep_rath    !: Fep/Fer ratio from hydro sources 
    41    REAL(wp), PUBLIC  :: lgw_rath    !: Weak ligand ratio from hydro sources 
    42  
    43  
    44    LOGICAL , PUBLIC  :: ll_sbc 
    45  
    46    LOGICAL  ::  ll_solub 
     23   LOGICAL , PUBLIC ::   ln_dust      !: boolean for dust input from the atmosphere 
     24   LOGICAL , PUBLIC ::   ln_solub     !: boolean for variable solubility of atmospheric iron 
     25   LOGICAL , PUBLIC ::   ln_river     !: boolean for river input of nutrients 
     26   LOGICAL , PUBLIC ::   ln_ndepo     !: boolean for atmospheric deposition of N 
     27   LOGICAL , PUBLIC ::   ln_ironsed   !: boolean for Fe input from sediments 
     28   LOGICAL , PUBLIC ::   ln_hydrofe   !: boolean for Fe input from hydrothermal vents 
     29   LOGICAL , PUBLIC ::   ln_ironice   !: boolean for Fe input from sea ice 
     30   REAL(wp), PUBLIC ::   sedfeinput   !: Coastal release of Iron 
     31   REAL(wp), PUBLIC ::   dustsolub    !: Solubility of the dust 
     32   REAL(wp), PUBLIC ::   mfrac        !: Mineral Content of the dust 
     33   REAL(wp), PUBLIC ::   icefeinput   !: Iron concentration in sea ice 
     34   REAL(wp), PUBLIC ::   wdust        !: Sinking speed of the dust  
     35   REAL(wp), PUBLIC ::   nitrfix      !: Nitrogen fixation rate    
     36   REAL(wp), PUBLIC ::   diazolight   !: Nitrogen fixation sensitivty to light  
     37   REAL(wp), PUBLIC ::   concfediaz   !: Fe half-saturation Cste for diazotrophs  
     38   REAL(wp)         ::   hratio       !: Fe:3He ratio assumed for vent iron supply 
     39   REAL(wp), PUBLIC ::   fep_rats     !: Fep/Fer ratio from sed  sources 
     40   REAL(wp), PUBLIC ::   fep_rath     !: Fep/Fer ratio from hydro sources 
     41   REAL(wp), PUBLIC ::   lgw_rath     !: Weak ligand ratio from hydro sources 
     42 
     43   LOGICAL , PUBLIC ::   ll_sbc 
     44   LOGICAL          ::   ll_solub 
    4745 
    4846   INTEGER , PARAMETER  :: jpriv  = 7   !: Maximum number of river input fields 
     
    5553   INTEGER , PARAMETER  :: jr_dsi = 7   !: index of dissolved silicate 
    5654 
    57  
    5855   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_dust      ! structure of input dust 
    59    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_solub      ! structure of input dust 
    60    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_river  ! structure of input riverdic 
     56   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_solub     ! structure of input dust 
     57   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_river     ! structure of input riverdic 
    6158   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ndepo     ! structure of input nitrogen deposition 
    6259   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ironsed   ! structure of input iron from sediment 
    6360   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_hydrofe   ! structure of input iron from hydrothermal vents 
    6461 
    65    INTEGER , PARAMETER :: nbtimes = 365  !: maximum number of times record in a file 
    66    INTEGER  :: ntimes_dust, ntimes_riv, ntimes_ndep       ! number of time steps in a file 
    67    INTEGER  :: ntimes_solub, ntimes_hydro                 ! number of time steps in a file 
    68  
    69    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: dust, solub       !: dust fields 
    70    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdic, rivalk    !: river input fields 
    71    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdin, rivdip    !: river input fields 
    72    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdon, rivdop    !: river input fields 
    73    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdoc    !: river input fields 
    74    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdsi    !: river input fields 
    75    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: nitdep    !: atmospheric N deposition  
    76    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ironsed   !: Coastal supply of iron 
    77    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: hydrofe   !: Hydrothermal vent supply of iron 
    78  
    79    REAL(wp), PUBLIC :: sumdepsi, rivalkinput, rivdicinput, nitdepinput 
    80    REAL(wp), PUBLIC :: rivdininput, rivdipinput, rivdsiinput 
     62   INTEGER , PARAMETER ::   nbtimes = 365                          ! maximum number of times record in a file 
     63   INTEGER             ::   ntimes_dust, ntimes_riv, ntimes_ndep   ! number of time steps in a file 
     64   INTEGER             ::   ntimes_solub, ntimes_hydro             ! number of time steps in a file 
     65 
     66   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   dust  , solub    !: dust fields 
     67   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdic, rivalk   !: river input fields 
     68   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdin, rivdip   !: river input fields 
     69   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdon, rivdop   !: river input fields 
     70   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdoc           !: river input fields 
     71   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdsi           !: river input fields 
     72   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nitdep           !: atmospheric N deposition  
     73   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ironsed          !: Coastal supply of iron 
     74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hydrofe          !: Hydrothermal vent supply of iron 
     75 
     76   REAL(wp), PUBLIC ::   rivalkinput, rivdicinput, nitdepinput, sumdepsi 
     77   REAL(wp), PUBLIC ::   rivdininput, rivdipinput, rivdsiinput 
    8178 
    8279   !! * Substitutions 
     
    10097      !! 
    10198      !!---------------------------------------------------------------------- 
    102       !! * arguments 
    103       INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    104  
    105       !! * local declarations 
    106       INTEGER  :: ji,jj  
    107       REAL(wp) :: zcoef, zyyss 
     99      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     100      ! 
     101      INTEGER  ::   ji, jj  
     102      REAL(wp) ::   zcoef, zyyss 
    108103      !!--------------------------------------------------------------------- 
    109104      ! 
    110       IF( ln_timing )  CALL timing_start('p4z_sbc') 
     105      IF( ln_timing )   CALL timing_start('p4z_sbc') 
    111106      ! 
    112107      ! Compute dust at nit000 or only if there is more than 1 time record in dust file 
     
    114109         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_dust > 1 ) ) THEN 
    115110            CALL fld_read( kt, 1, sf_dust ) 
    116             IF( nn_ice_tr == -1 .AND. .NOT. ln_ironice ) THEN 
    117                dust(:,:) = sf_dust(1)%fnow(:,:,1) 
    118             ELSE 
    119                dust(:,:) = sf_dust(1)%fnow(:,:,1) * ( 1.0 - fr_i(:,:) ) 
     111            IF( nn_ice_tr == -1 .AND. .NOT.ln_ironice ) THEN   ;   dust(:,:) = sf_dust(1)%fnow(:,:,1) 
     112            ELSE                                               ;   dust(:,:) = sf_dust(1)%fnow(:,:,1) * ( 1.-fr_i(:,:) ) 
    120113            ENDIF 
    121114         ENDIF 
    122115      ENDIF 
    123  
     116      ! 
    124117      IF( ll_solub ) THEN 
    125118         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_solub > 1 ) ) THEN 
     
    205198      !! 
    206199      !!---------------------------------------------------------------------- 
    207       ! 
    208200      INTEGER  :: ji, jj, jk, jm, ifpr 
    209201      INTEGER  :: ii0, ii1, ij0, ij1 
     
    224216      TYPE(FLD_N) ::   sn_riverdoc, sn_riverdic, sn_riverdsi   ! informations about the fields to be read 
    225217      TYPE(FLD_N) ::   sn_riverdin, sn_riverdon, sn_riverdip, sn_riverdop 
    226       ! 
     218      !! 
    227219      NAMELIST/nampissbc/cn_dir, sn_dust, sn_solub, sn_riverdic, sn_riverdoc, sn_riverdin, sn_riverdon,     & 
    228220        &                sn_riverdip, sn_riverdop, sn_riverdsi, sn_ndepo, sn_ironsed, sn_hydrofe, & 
     
    232224      !!---------------------------------------------------------------------- 
    233225      ! 
     226      IF(lwp) THEN 
     227         WRITE(numout,*) 
     228         WRITE(numout,*) 'p4z_sbc_init : initialization of the external sources of nutrients ' 
     229         WRITE(numout,*) '~~~~~~~~~~~~ ' 
     230      ENDIF 
    234231      !                            !* set file information 
    235232      REWIND( numnatp_ref )              ! Namelist nampissbc in reference namelist : Pisces external sources of nutrients 
    236233      READ  ( numnatp_ref, nampissbc, IOSTAT = ios, ERR = 901) 
    237 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampissbc in reference namelist', lwp ) 
    238  
     234901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampissbc in reference namelist', lwp ) 
    239235      REWIND( numnatp_cfg )              ! Namelist nampissbc in configuration namelist : Pisces external sources of nutrients 
    240236      READ  ( numnatp_cfg, nampissbc, IOSTAT = ios, ERR = 902 ) 
    241 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampissbc in configuration namelist', lwp ) 
     237902   IF( ios >  0 )  CALL ctl_nam ( ios , 'nampissbc in configuration namelist', lwp ) 
    242238      IF(lwm) WRITE ( numonp, nampissbc ) 
    243239 
    244       IF ( ( nn_ice_tr >= 0 ) .AND. ln_ironice ) THEN 
     240      IF(lwp) THEN 
     241         WRITE(numout,*) '   Namelist : nampissbc ' 
     242         WRITE(numout,*) '      dust input from the atmosphere           ln_dust     = ', ln_dust 
     243         WRITE(numout,*) '      Variable solubility of iron input        ln_solub    = ', ln_solub 
     244         WRITE(numout,*) '      river input of nutrients                 ln_river    = ', ln_river 
     245         WRITE(numout,*) '      atmospheric deposition of n              ln_ndepo    = ', ln_ndepo 
     246         WRITE(numout,*) '      Fe input from sediments                  ln_ironsed  = ', ln_ironsed 
     247         WRITE(numout,*) '      Fe input from seaice                     ln_ironice  = ', ln_ironice 
     248         WRITE(numout,*) '      fe input from hydrothermal vents         ln_hydrofe  = ', ln_hydrofe 
     249         WRITE(numout,*) '      coastal release of iron                  sedfeinput  = ', sedfeinput 
     250         WRITE(numout,*) '      solubility of the dust                   dustsolub   = ', dustsolub 
     251         WRITE(numout,*) '      Mineral Fe content of the dust           mfrac       = ', mfrac 
     252         WRITE(numout,*) '      Iron concentration in sea ice            icefeinput  = ', icefeinput 
     253         WRITE(numout,*) '      sinking speed of the dust                wdust       = ', wdust 
     254         WRITE(numout,*) '      nitrogen fixation rate                   nitrfix     = ', nitrfix 
     255         WRITE(numout,*) '      nitrogen fixation sensitivty to light    diazolight  = ', diazolight 
     256         WRITE(numout,*) '      Fe half-saturation cste for diazotrophs  concfediaz  = ', concfediaz 
     257         WRITE(numout,*) '      Fe to 3He ratio assumed for vent iron supply hratio  = ', hratio 
     258         IF( ln_ligand ) THEN 
     259            WRITE(numout,*) '      Fep/Fer ratio from sed sources            fep_rats   = ', fep_rats 
     260            WRITE(numout,*) '      Fep/Fer ratio from sed hydro sources      fep_rath   = ', fep_rath 
     261            WRITE(numout,*) '      Weak ligand ratio from sed hydro sources  lgw_rath   = ', lgw_rath 
     262         ENDIF 
     263      END IF 
     264 
     265      IF( nn_ice_tr >= 0 .AND. ln_ironice ) THEN 
    245266         IF(lwp) THEN 
    246             WRITE(numout,*) ' ln_ironice incompatible with nn_ice_tr = ', nn_ice_tr 
    247             WRITE(numout,*) ' Specify your sea ice iron concentration in nampisice instead ' 
    248             WRITE(numout,*) ' ln_ironice is forced to .FALSE. ' 
    249             ln_ironice = .FALSE. 
    250          ENDIF 
    251       ENDIF 
    252  
    253       IF(lwp) THEN 
    254          WRITE(numout,*) ' ' 
    255          WRITE(numout,*) ' namelist : nampissbc ' 
    256          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~ ' 
    257          WRITE(numout,*) '    dust input from the atmosphere           ln_dust     = ', ln_dust 
    258          WRITE(numout,*) '    Variable solubility of iron input        ln_solub    = ', ln_solub 
    259          WRITE(numout,*) '    river input of nutrients                 ln_river    = ', ln_river 
    260          WRITE(numout,*) '    atmospheric deposition of n              ln_ndepo    = ', ln_ndepo 
    261          WRITE(numout,*) '    Fe input from sediments                  ln_ironsed  = ', ln_ironsed 
    262          WRITE(numout,*) '    Fe input from seaice                     ln_ironice  = ', ln_ironice 
    263          WRITE(numout,*) '    fe input from hydrothermal vents         ln_hydrofe  = ', ln_hydrofe 
    264          WRITE(numout,*) '    coastal release of iron                  sedfeinput  = ', sedfeinput 
    265          WRITE(numout,*) '    solubility of the dust                   dustsolub   = ', dustsolub 
    266          WRITE(numout,*) '    Mineral Fe content of the dust           mfrac       = ', mfrac 
    267          WRITE(numout,*) '    Iron concentration in sea ice            icefeinput  = ', icefeinput 
    268          WRITE(numout,*) '    sinking speed of the dust                wdust       = ', wdust 
    269          WRITE(numout,*) '    nitrogen fixation rate                   nitrfix     = ', nitrfix 
    270          WRITE(numout,*) '    nitrogen fixation sensitivty to light    diazolight  = ', diazolight 
    271          WRITE(numout,*) '    fe half-saturation cste for diazotrophs  concfediaz  = ', concfediaz 
    272          WRITE(numout,*) '    Fe to 3He ratio assumed for vent iron supply hratio  = ', hratio 
    273          IF( ln_ligand ) THEN 
    274             WRITE(numout,*) '    Fep/Fer ratio from sed sources            fep_rats   = ', fep_rats 
    275             WRITE(numout,*) '    Fep/Fer ratio from sed hydro sources      fep_rath   = ', fep_rath 
    276             WRITE(numout,*) '    Weak ligand ratio from sed hydro sources  lgw_rath   = ', lgw_rath 
    277          ENDIF 
    278       END IF 
    279  
    280       IF( ln_dust .OR. ln_river .OR. ln_ndepo ) THEN  ;  ll_sbc = .TRUE. 
    281       ELSE                                            ;  ll_sbc = .FALSE. 
    282       ENDIF 
    283  
    284       IF( ln_dust .AND. ln_solub ) THEN               ;  ll_solub = .TRUE. 
    285       ELSE                                            ;  ll_solub = .FALSE. 
     267            WRITE(numout,*) '   ==>>>   ln_ironice incompatible with nn_ice_tr = ', nn_ice_tr 
     268            WRITE(numout,*) '           Specify your sea ice iron concentration in nampisice instead ' 
     269            WRITE(numout,*) '           ln_ironice is forced to .FALSE. ' 
     270         ENDIF 
     271         ln_ironice = .FALSE. 
     272      ENDIF 
     273 
     274      IF( ln_dust .OR. ln_river .OR. ln_ndepo ) THEN   ;   ll_sbc = .TRUE. 
     275      ELSE                                             ;   ll_sbc = .FALSE. 
     276      ENDIF 
     277 
     278      IF( ln_dust .AND. ln_solub ) THEN                ;   ll_solub = .TRUE. 
     279      ELSE                                             ;   ll_solub = .FALSE. 
    286280      ENDIF 
    287281 
     
    322316            DO jm = 1, ntimes_dust 
    323317               sumdepsi = sumdepsi + glob_sum( zdust(:,:,jm) * e1e2t(:,:) * tmask(:,:,1) * ztimes_dust ) 
    324             ENDDO 
     318            END DO 
    325319            sumdepsi = sumdepsi / ( nyear_len(1) * rday ) * 12. * 8.8 * 0.075 * mfrac / 28.1  
    326320            DEALLOCATE( zdust) 
     
    335329      IF( ll_solub ) THEN 
    336330         ! 
    337          IF(lwp) WRITE(numout,*) '    initialize variable solubility of Fe ' 
    338          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' 
     331         IF(lwp) WRITE(numout,*) 
     332         IF(lwp) WRITE(numout,*) '   ==>>>   ll_solub=T , initialize variable solubility of Fe ' 
    339333         ! 
    340334         ALLOCATE( solub(jpi,jpj) )    ! allocation 
     
    356350      IF( ln_river ) THEN 
    357351         ! 
    358          slf_river(jr_dic) = sn_riverdic  ;  slf_river(jr_doc) = sn_riverdoc  ;  slf_river(jr_din) = sn_riverdin  
    359          slf_river(jr_don) = sn_riverdon  ;  slf_river(jr_dip) = sn_riverdip  ;  slf_river(jr_dop) = sn_riverdop 
     352         slf_river(jr_dic) = sn_riverdic   ;   slf_river(jr_doc) = sn_riverdoc   ;   slf_river(jr_din) = sn_riverdin  
     353         slf_river(jr_don) = sn_riverdon   ;   slf_river(jr_dip) = sn_riverdip   ;   slf_river(jr_dop) = sn_riverdop 
    360354         slf_river(jr_dsi) = sn_riverdsi   
    361355         ! 
     
    363357         IF( ln_p5z )  ALLOCATE( rivdon(jpi,jpj), rivdop(jpi,jpj), rivdoc(jpi,jpj) ) 
    364358         ! 
    365          ALLOCATE( sf_river(jpriv), rivinput(jpriv), STAT=ierr1 )           !* allocate and fill sf_river (forcing structure) with sn_river_ 
    366          rivinput(:) = 0.0 
     359         ALLOCATE( sf_river(jpriv), rivinput(jpriv), STAT=ierr1 )    !* allocate and fill sf_river (forcing structure) with sn_river_ 
     360         rivinput(:) = 0._wp 
    367361 
    368362         IF( ierr1 > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_irver structure' ) 
     
    409403      IF( ln_ndepo ) THEN 
    410404         ! 
    411          IF(lwp) WRITE(numout,*) '    initialize the nutrient input by dust from ndeposition.orca.nc' 
    412          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     405         IF(lwp) WRITE(numout,*) 
     406         IF(lwp) WRITE(numout,*) '   ==>>>   ln_ndepo=T , initialize the nutrient input by dust from NetCDF file' 
    413407         ! 
    414408         ALLOCATE( nitdep(jpi,jpj) )    ! allocation 
     
    446440      IF( ln_ironsed ) THEN      
    447441         ! 
    448          IF(lwp) WRITE(numout,*) '    computation of an island mask to enhance coastal supply of iron' 
    449          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     442         IF(lwp) WRITE(numout,*) 
     443         IF(lwp) WRITE(numout,*) '   ==>>>   ln_ironsed=T , computation of an island mask to enhance coastal supply of iron' 
    450444         ! 
    451445         ALLOCATE( ironsed(jpi,jpj,jpk) )    ! allocation 
     
    458452         ik50 = 5        !  last level where depth less than 50 m 
    459453         DO jk = jpkm1, 1, -1 
    460             IF( gdept_1d(jk) > 50. )  ik50 = jk - 1 
     454            IF( gdept_1d(jk) > 50. )   ik50 = jk - 1 
    461455         END DO 
    462          IF (lwp) WRITE(numout,*) 
    463          IF (lwp) WRITE(numout,*) ' Level corresponding to 50m depth ',  ik50,' ', gdept_1d(ik50+1) 
    464          IF (lwp) WRITE(numout,*) 
     456         IF(lwp) WRITE(numout,*) 
     457         IF(lwp) WRITE(numout,*) ' Level corresponding to 50m depth ',  ik50,' ', gdept_1d(ik50+1) 
    465458         DO jk = 1, ik50 
    466459            DO jj = 2, jpjm1 
     
    499492      IF( ln_hydrofe ) THEN 
    500493         ! 
    501          IF(lwp) WRITE(numout,*) '    Input of iron from hydrothermal vents ' 
    502          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     494         IF(lwp) WRITE(numout,*) 
     495         IF(lwp) WRITE(numout,*) '   ==>>>   ln_hydrofe=T , Input of iron from hydrothermal vents' 
    503496         ! 
    504497         ALLOCATE( hydrofe(jpi,jpj,jpk) )    ! allocation 
     
    521514         WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    522515         WRITE(numout,*) '    N Supply   : ', rivdininput*rno3*1E3/1E12*14.,' TgN/yr' 
    523          WRITE(numout,*) '    Si Supply  : ', rivdsiinput*1E3/1E12*28.1,' TgSi/yr' 
     516         WRITE(numout,*) '    Si Supply  : ', rivdsiinput*1E3/1E12*28.1    ,' TgSi/yr' 
    524517         WRITE(numout,*) '    P Supply   : ', rivdipinput*1E3*po4r/1E12*31.,' TgP/yr' 
    525          WRITE(numout,*) '    Alk Supply : ', rivalkinput*1E3/1E12,' Teq/yr' 
    526          WRITE(numout,*) '    DIC Supply : ', rivdicinput*1E3*12./1E12,'TgC/yr' 
     518         WRITE(numout,*) '    Alk Supply : ', rivalkinput*1E3/1E12         ,' Teq/yr' 
     519         WRITE(numout,*) '    DIC Supply : ', rivdicinput*1E3*12./1E12     ,' TgC/yr' 
    527520         WRITE(numout,*)  
    528521         WRITE(numout,*) '    Total input of elements from atmospheric supply' 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90

    r9125 r9169  
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    88   !!---------------------------------------------------------------------- 
    9    !!   p4zsms         : Time loop of passive tracers sms 
     9   !!   p4z_sms        : Time loop of passive tracers sms 
    1010   !!---------------------------------------------------------------------- 
    11    USE oce_trc         !  shared variables between ocean and passive tracers 
    12    USE trc             !  passive tracers common variables  
    13    USE trcdta 
    14    USE sms_pisces      !  PISCES Source Minus Sink variables 
    15    USE p4zbio          !  Biological model 
    16    USE p4zche          !  Chemical model 
    17    USE p4zlys          !  Calcite saturation 
    18    USE p4zflx          !  Gas exchange 
    19    USE p4zsbc          !  External source of nutrients 
    20    USE p4zsed          !  Sedimentation 
    21    USE p4zint          !  time interpolation 
    22    USE p4zrem          !  remineralisation 
    23    USE iom             !  I/O manager 
    24    USE trd_oce         !  Ocean trends variables 
    25    USE trdtrc          !  TOP trends variables 
    26    USE sedmodel        !  Sediment model 
    27    USE prtctl_trc      !  print control for debugging 
     11   USE oce_trc         ! shared variables between ocean and passive tracers 
     12   USE trc             ! passive tracers common variables  
     13   USE trcdta          !  
     14   USE sms_pisces      ! PISCES Source Minus Sink variables 
     15   USE p4zbio          ! Biological model 
     16   USE p4zche          ! Chemical model 
     17   USE p4zlys          ! Calcite saturation 
     18   USE p4zflx          ! Gas exchange 
     19   USE p4zsbc          ! External source of nutrients 
     20   USE p4zsed          ! Sedimentation 
     21   USE p4zint          ! time interpolation 
     22   USE p4zrem          ! remineralisation 
     23   USE iom             ! I/O manager 
     24   USE trd_oce         ! Ocean trends variables 
     25   USE trdtrc          ! TOP trends variables 
     26   USE sedmodel        ! Sediment model 
     27   USE prtctl_trc      ! print control for debugging 
    2828 
    2929   IMPLICIT NONE 
     
    3333   PUBLIC   p4z_sms        ! called in p4zsms.F90 
    3434 
    35    REAL(wp) :: alkbudget, no3budget, silbudget, ferbudget, po4budget 
    36    REAL(wp) :: xfact1, xfact2, xfact3 
    37    INTEGER ::  numco2, numnut, numnit  !: logical unit for co2 budget 
    38  
    39    !!* Array used to indicate negative tracer values 
    40    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xnegtr     !: ??? 
     35   INTEGER ::    numco2, numnut, numnit      ! logical unit for co2 budget 
     36   REAL(wp) ::   alkbudget, no3budget, silbudget, ferbudget, po4budget 
     37   REAL(wp) ::   xfact1, xfact2, xfact3 
     38 
     39   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xnegtr     ! Array used to indicate negative tracer values 
    4140 
    4241   !!---------------------------------------------------------------------- 
     
    4544   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4645   !!---------------------------------------------------------------------- 
    47  
    4846CONTAINS 
    4947 
     
    197195      NAMELIST/nampismass/ ln_check_mass 
    198196      !!---------------------------------------------------------------------- 
     197      ! 
     198      IF(lwp) THEN 
     199         WRITE(numout,*) 
     200         WRITE(numout,*) 'p4z_sms_init : PISCES initialization' 
     201         WRITE(numout,*) '~~~~~~~~~~~~' 
     202      ENDIF 
    199203 
    200204      REWIND( numnatp_ref )              ! Namelist nampisbio in reference namelist : Pisces variables 
    201205      READ  ( numnatp_ref, nampisbio, IOSTAT = ios, ERR = 901) 
    202 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisbio in reference namelist', lwp ) 
    203  
     206901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisbio in reference namelist', lwp ) 
    204207      REWIND( numnatp_cfg )              ! Namelist nampisbio in configuration namelist : Pisces variables 
    205208      READ  ( numnatp_cfg, nampisbio, IOSTAT = ios, ERR = 902 ) 
    206 902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampisbio in configuration namelist', lwp ) 
    207       IF(lwm) WRITE ( numonp, nampisbio ) 
    208  
     209902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisbio in configuration namelist', lwp ) 
     210      IF(lwm) WRITE( numonp, nampisbio ) 
     211      ! 
    209212      IF(lwp) THEN                         ! control print 
    210          WRITE(numout,*) ' Namelist : nampisbio' 
    211          WRITE(numout,*) '    frequence pour la biologie                nrdttrc    =', nrdttrc 
    212          WRITE(numout,*) '    POC sinking speed                         wsbio      =', wsbio 
    213          WRITE(numout,*) '    half saturation constant for mortality    xkmort     =', xkmort  
     213         WRITE(numout,*) '   Namelist : nampisbio' 
     214         WRITE(numout,*) '      frequency for the biology                 nrdttrc     =', nrdttrc 
     215         WRITE(numout,*) '      POC sinking speed                         wsbio       =', wsbio 
     216         WRITE(numout,*) '      half saturation constant for mortality    xkmort      =', xkmort  
    214217         IF( ln_p5z ) THEN 
    215             WRITE(numout,*) '    N/C in zooplankton                        no3rat3    =', no3rat3 
    216             WRITE(numout,*) '    P/C in zooplankton                        po4rat3    =', po4rat3 
    217          ENDIF 
    218          WRITE(numout,*) '    Fe/C in zooplankton                       ferat3     =', ferat3 
    219          WRITE(numout,*) '    Big particles sinking speed               wsbio2     =', wsbio2 
    220          WRITE(numout,*) '    Big particles maximum sinking speed       wsbio2max  =', wsbio2max 
    221          WRITE(numout,*) '    Big particles sinking speed length scale  wsbio2scale =', wsbio2scale 
    222          WRITE(numout,*) '    Maximum number of iterations for POC      niter1max =', niter1max 
    223          WRITE(numout,*) '    Maximum number of iterations for GOC      niter2max =', niter2max 
     218            WRITE(numout,*) '      N/C in zooplankton                        no3rat3     =', no3rat3 
     219            WRITE(numout,*) '      P/C in zooplankton                        po4rat3     =', po4rat3 
     220         ENDIF 
     221         WRITE(numout,*) '      Fe/C in zooplankton                       ferat3      =', ferat3 
     222         WRITE(numout,*) '      Big particles sinking speed               wsbio2      =', wsbio2 
     223         WRITE(numout,*) '      Big particles maximum sinking speed       wsbio2max   =', wsbio2max 
     224         WRITE(numout,*) '      Big particles sinking speed length scale  wsbio2scale =', wsbio2scale 
     225         WRITE(numout,*) '      Maximum number of iterations for POC      niter1max  =', niter1max 
     226         WRITE(numout,*) '      Maximum number of iterations for GOC      niter2max  =', niter2max 
    224227         IF( ln_ligand ) THEN 
    225             WRITE(numout,*) '    FeP sinking speed                             wfep   =', wfep 
     228            WRITE(numout,*) '      FeP sinking speed                              wfep   =', wfep 
    226229            IF( ln_p4z ) THEN 
    227               WRITE(numout,*) '    Phyto ligand production per unit doc          ldocp  =', ldocp 
    228               WRITE(numout,*) '    Zoo ligand production per unit doc            ldocz  =', ldocz 
    229               WRITE(numout,*) '    Proportional loss of ligands due to Fe uptake lthet  =', lthet 
     230               WRITE(numout,*) '      Phyto ligand production per unit doc           ldocp  =', ldocp 
     231               WRITE(numout,*) '      Zoo ligand production per unit doc             ldocz  =', ldocz 
     232               WRITE(numout,*) '      Proportional loss of ligands due to Fe uptake lthet  =', lthet 
    230233            ENDIF 
    231234         ENDIF 
     
    235238      REWIND( numnatp_ref )              ! Namelist nampisdmp in reference namelist : Pisces damping 
    236239      READ  ( numnatp_ref, nampisdmp, IOSTAT = ios, ERR = 905) 
    237 905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisdmp in reference namelist', lwp ) 
    238  
     240905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisdmp in reference namelist', lwp ) 
    239241      REWIND( numnatp_cfg )              ! Namelist nampisdmp in configuration namelist : Pisces damping 
    240242      READ  ( numnatp_cfg, nampisdmp, IOSTAT = ios, ERR = 906 ) 
    241 906   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampisdmp in configuration namelist', lwp ) 
    242       IF(lwm) WRITE ( numonp, nampisdmp ) 
    243  
     243906   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisdmp in configuration namelist', lwp ) 
     244      IF(lwm) WRITE( numonp, nampisdmp ) 
     245      ! 
    244246      IF(lwp) THEN                         ! control print 
    245247         WRITE(numout,*) 
    246          WRITE(numout,*) ' Namelist : nampisdmp' 
    247          WRITE(numout,*) '    Relaxation of tracer to glodap mean value             ln_pisdmp      =', ln_pisdmp 
    248          WRITE(numout,*) '    Frequency of Relaxation                               nn_pisdmp      =', nn_pisdmp 
    249          WRITE(numout,*) ' ' 
     248         WRITE(numout,*) '   Namelist : nampisdmp --- relaxation to GLODAP' 
     249         WRITE(numout,*) '      Relaxation of tracer to glodap mean value   ln_pisdmp =', ln_pisdmp 
     250         WRITE(numout,*) '      Frequency of Relaxation                     nn_pisdmp =', nn_pisdmp 
    250251      ENDIF 
    251252 
    252253      REWIND( numnatp_ref )              ! Namelist nampismass in reference namelist : Pisces mass conservation check 
    253254      READ  ( numnatp_ref, nampismass, IOSTAT = ios, ERR = 907) 
    254 907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismass in reference namelist', lwp ) 
    255  
     255907   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampismass in reference namelist', lwp ) 
    256256      REWIND( numnatp_cfg )              ! Namelist nampismass in configuration namelist : Pisces mass conservation check  
    257257      READ  ( numnatp_cfg, nampismass, IOSTAT = ios, ERR = 908 ) 
    258 908   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampismass in configuration namelist', lwp ) 
    259       IF(lwm) WRITE ( numonp, nampismass ) 
     258908   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampismass in configuration namelist', lwp ) 
     259      IF(lwm) WRITE( numonp, nampismass ) 
    260260 
    261261      IF(lwp) THEN                         ! control print 
    262          WRITE(numout,*) ' ' 
    263          WRITE(numout,*) ' Namelist parameter for mass conservation checking' 
    264          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    265          WRITE(numout,*) '    Flag to check mass conservation of NO3/Si/TALK ln_check_mass = ', ln_check_mass 
     262         WRITE(numout,*) 
     263         WRITE(numout,*) '   Namelist : nampismass  --- mass conservation checking' 
     264         WRITE(numout,*) '      Flag to check mass conservation of NO3/Si/TALK   ln_check_mass = ', ln_check_mass 
    266265      ENDIF 
    267266      ! 
Note: See TracChangeset for help on using the changeset viewer.