New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 3680 for branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

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

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

Location:
branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES
Files:
13 deleted
7 edited
3 copied

Legend:

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

    r3531 r3680  
    105105            DO ji = 1, jpi 
    106106               zdep    = rfact2 / fse3t(ji,jj,1) 
    107                zwflux  = ( emps(ji,jj) - emp(ji,jj) ) & 
    108                &        * tsn(ji,jj,1,jp_sal) / ( tsn(ji,jj,1,jp_sal) - 6.0 ) / 1000. 
     107    !           zwflux  = ( emps(ji,jj) - emp(ji,jj) ) & 
     108    !           &        * tsn(ji,jj,1,jp_sal) / ( tsn(ji,jj,1,jp_sal) - 6.0 ) / 1000. 
     109               zwflux = 0. 
    109110               zfminus = MIN( 0., -zwflux ) * trn(ji,jj,1,jpfer) * zdep 
    110111               zfplus  = MAX( 0., -zwflux ) * 10E-9 * zdep 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/par_pisces.F90

    r3295 r3680  
    1010   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1111   !!---------------------------------------------------------------------- 
    12    USE par_lobster, ONLY : jp_lobster      !: number of tracers in LOBSTER 
    13    USE par_lobster, ONLY : jp_lobster_2d   !: number of 2D diag in LOBSTER 
    14    USE par_lobster, ONLY : jp_lobster_3d   !: number of 3D diag in LOBSTER 
    15    USE par_lobster, ONLY : jp_lobster_trd  !: number of biological diag in LOBSTER 
    1612 
    1713   IMPLICIT NONE 
    1814 
    19    INTEGER, PUBLIC, PARAMETER ::   jp_lp      = jp_lobster      !: cumulative number of already defined TRC 
    20    INTEGER, PUBLIC, PARAMETER ::   jp_lp_2d   = jp_lobster_2d   !: 
    21    INTEGER, PUBLIC, PARAMETER ::   jp_lp_3d   = jp_lobster_3d   !: 
    22    INTEGER, PUBLIC, PARAMETER ::   jp_lp_trd  = jp_lobster_trd  !: 
     15#if defined key_pisces_reduced 
     16   !!--------------------------------------------------------------------- 
     17   !!   'key_pisces_reduced'   :                                LOBSTER bio-model 
     18   !!--------------------------------------------------------------------- 
     19   LOGICAL, PUBLIC, PARAMETER ::   lk_pisces     = .TRUE.  !: PISCES flag  
     20   LOGICAL, PUBLIC, PARAMETER ::   lk_p4z        = .FALSE. !: p4z flag  
     21   INTEGER, PUBLIC, PARAMETER ::   jp_pisces     =  6      !: number of passive tracers 
     22   INTEGER, PUBLIC, PARAMETER ::   jp_pisces_2d  =  19     !: additional 2d output  
     23   INTEGER, PUBLIC, PARAMETER ::   jp_pisces_3d  =   3     !: additional 3d output  
     24   INTEGER, PUBLIC, PARAMETER ::   jp_pisces_trd =   17    !: number of sms trends for PISCES 
    2325 
    24 #if defined key_pisces  &&  defined key_kriest 
     26   ! assign an index in trc arrays for each LOBSTER prognostic variables 
     27   INTEGER, PUBLIC, PARAMETER ::   jpdet     =  1        !: detritus                    [mmoleN/m3] 
     28   INTEGER, PUBLIC, PARAMETER ::   jpzoo     =  2        !: zooplancton concentration   [mmoleN/m3] 
     29   INTEGER, PUBLIC, PARAMETER ::   jpphy     =  3        !: phytoplancton concentration [mmoleN/m3] 
     30   INTEGER, PUBLIC, PARAMETER ::   jpno3     =  4        !: nitrate concentration       [mmoleN/m3] 
     31   INTEGER, PUBLIC, PARAMETER ::   jpnh4     =  5        !: ammonium concentration      [mmoleN/m3] 
     32   INTEGER, PUBLIC, PARAMETER ::   jpdom     =  6        !: dissolved organic matter    [mmoleN/m3] 
     33 
     34   ! productive layer depth 
     35   INTEGER, PUBLIC, PARAMETER ::   jpkb      = 12        !: first vertical layers where biology is active 
     36   INTEGER, PUBLIC, PARAMETER ::   jpkbm1    = jpkb - 1  !: first vertical layers where biology is active 
     37 
     38#elif defined key_pisces  &&  defined key_kriest 
    2539   !!--------------------------------------------------------------------- 
    2640   !!   'key_pisces' & 'key_kriest'                 PISCES bio-model + ??? 
    2741   !!--------------------------------------------------------------------- 
    2842   LOGICAL, PUBLIC, PARAMETER ::   lk_pisces     = .TRUE.  !: PISCES flag  
     43   LOGICAL, PUBLIC, PARAMETER ::   lk_p4z        = .TRUE. !: p4z flag  
    2944   LOGICAL, PUBLIC, PARAMETER ::   lk_kriest     = .TRUE.  !: Kriest flag  
    3045   INTEGER, PUBLIC, PARAMETER ::   jp_pisces     =  23     !: number of passive tracers 
     
    3651   !    WARNING: be carefull about the order when reading the restart 
    3752        !   !!gm  this warning should be obsolet with IOM 
    38    INTEGER, PUBLIC, PARAMETER ::   jpdic = jp_lp + 1    !: dissolved inoganic carbon concentration  
    39    INTEGER, PUBLIC, PARAMETER ::   jptal = jp_lp + 2    !: total alkalinity  
    40    INTEGER, PUBLIC, PARAMETER ::   jpoxy = jp_lp + 3    !: oxygen carbon concentration  
    41    INTEGER, PUBLIC, PARAMETER ::   jpcal = jp_lp + 4    !: calcite  concentration  
    42    INTEGER, PUBLIC, PARAMETER ::   jppo4 = jp_lp + 5    !: phosphate concentration  
    43    INTEGER, PUBLIC, PARAMETER ::   jppoc = jp_lp + 6    !: small particulate organic phosphate concentration 
    44    INTEGER, PUBLIC, PARAMETER ::   jpsil = jp_lp + 7    !: silicate concentration 
    45    INTEGER, PUBLIC, PARAMETER ::   jpphy = jp_lp + 8    !: phytoplancton concentration  
    46    INTEGER, PUBLIC, PARAMETER ::   jpzoo = jp_lp + 9    !: zooplancton concentration 
    47    INTEGER, PUBLIC, PARAMETER ::   jpdoc = jp_lp + 10    !: dissolved organic carbon concentration  
    48    INTEGER, PUBLIC, PARAMETER ::   jpdia = jp_lp + 11    !: Diatoms Concentration 
    49    INTEGER, PUBLIC, PARAMETER ::   jpmes = jp_lp + 12    !: Mesozooplankton Concentration 
    50    INTEGER, PUBLIC, PARAMETER ::   jpdsi = jp_lp + 13    !: (big) Silicate Concentration 
    51    INTEGER, PUBLIC, PARAMETER ::   jpfer = jp_lp + 14    !: Iron Concentration 
    52    INTEGER, PUBLIC, PARAMETER ::   jpnum = jp_lp + 15    !: Big iron particles Concentration 
    53    INTEGER, PUBLIC, PARAMETER ::   jpsfe = jp_lp + 16    !: number of particulate organic phosphate concentration 
    54    INTEGER, PUBLIC, PARAMETER ::   jpdfe = jp_lp + 17    !: Diatoms iron Concentration 
    55    INTEGER, PUBLIC, PARAMETER ::   jpgsi = jp_lp + 18    !: Diatoms Silicate Concentration 
    56    INTEGER, PUBLIC, PARAMETER ::   jpnfe = jp_lp + 19    !: Nano iron Concentration 
    57    INTEGER, PUBLIC, PARAMETER ::   jpnch = jp_lp + 20    !: Nano Chlorophyll Concentration 
    58    INTEGER, PUBLIC, PARAMETER ::   jpdch = jp_lp + 21    !: Diatoms Chlorophyll Concentration 
    59    INTEGER, PUBLIC, PARAMETER ::   jpno3 = jp_lp + 22    !: Nitrates Concentration 
    60    INTEGER, PUBLIC, PARAMETER ::   jpnh4 = jp_lp + 23    !: Ammonium Concentration 
     53   INTEGER, PUBLIC, PARAMETER ::   jpdic = 1    !: dissolved inoganic carbon concentration  
     54   INTEGER, PUBLIC, PARAMETER ::   jptal = 2    !: total alkalinity  
     55   INTEGER, PUBLIC, PARAMETER ::   jpoxy = 3    !: oxygen carbon concentration  
     56   INTEGER, PUBLIC, PARAMETER ::   jpcal = 4    !: calcite  concentration  
     57   INTEGER, PUBLIC, PARAMETER ::   jppo4 = 5    !: phosphate concentration  
     58   INTEGER, PUBLIC, PARAMETER ::   jppoc = 6    !: small particulate organic phosphate concentration 
     59   INTEGER, PUBLIC, PARAMETER ::   jpsil = 7    !: silicate concentration 
     60   INTEGER, PUBLIC, PARAMETER ::   jpphy = 8    !: phytoplancton concentration  
     61   INTEGER, PUBLIC, PARAMETER ::   jpzoo = 9    !: zooplancton concentration 
     62   INTEGER, PUBLIC, PARAMETER ::   jpdoc = 10    !: dissolved organic carbon concentration  
     63   INTEGER, PUBLIC, PARAMETER ::   jpdia = 11    !: Diatoms Concentration 
     64   INTEGER, PUBLIC, PARAMETER ::   jpmes = 12    !: Mesozooplankton Concentration 
     65   INTEGER, PUBLIC, PARAMETER ::   jpdsi = 13    !: (big) Silicate Concentration 
     66   INTEGER, PUBLIC, PARAMETER ::   jpfer = 14    !: Iron Concentration 
     67   INTEGER, PUBLIC, PARAMETER ::   jpnum = 15    !: Big iron particles Concentration 
     68   INTEGER, PUBLIC, PARAMETER ::   jpsfe = 16    !: number of particulate organic phosphate concentration 
     69   INTEGER, PUBLIC, PARAMETER ::   jpdfe = 17    !: Diatoms iron Concentration 
     70   INTEGER, PUBLIC, PARAMETER ::   jpgsi = 18    !: Diatoms Silicate Concentration 
     71   INTEGER, PUBLIC, PARAMETER ::   jpnfe = 19    !: Nano iron Concentration 
     72   INTEGER, PUBLIC, PARAMETER ::   jpnch = 20    !: Nano Chlorophyll Concentration 
     73   INTEGER, PUBLIC, PARAMETER ::   jpdch = 21    !: Diatoms Chlorophyll Concentration 
     74   INTEGER, PUBLIC, PARAMETER ::   jpno3 = 22    !: Nitrates Concentration 
     75   INTEGER, PUBLIC, PARAMETER ::   jpnh4 = 23    !: Ammonium Concentration 
    6176 
    6277#elif defined key_pisces 
     
    6580   !!--------------------------------------------------------------------- 
    6681   LOGICAL, PUBLIC, PARAMETER ::   lk_pisces     = .TRUE.  !: PISCES flag  
     82   LOGICAL, PUBLIC, PARAMETER ::   lk_p4z        = .TRUE.  !: p4z flag  
    6783   LOGICAL, PUBLIC, PARAMETER ::   lk_kriest     = .FALSE. !: Kriest flag  
    6884   INTEGER, PUBLIC, PARAMETER ::   jp_pisces     = 24      !: number of PISCES passive tracers 
     
    7490   !    WARNING: be carefull about the order when reading the restart 
    7591        !   !!gm  this warning should be obsolet with IOM 
    76    INTEGER, PUBLIC, PARAMETER ::   jpdic = jp_lp + 1    !: dissolved inoganic carbon concentration  
    77    INTEGER, PUBLIC, PARAMETER ::   jptal = jp_lp + 2    !: total alkalinity  
    78    INTEGER, PUBLIC, PARAMETER ::   jpoxy = jp_lp + 3    !: oxygen carbon concentration  
    79    INTEGER, PUBLIC, PARAMETER ::   jpcal = jp_lp + 4    !: calcite  concentration  
    80    INTEGER, PUBLIC, PARAMETER ::   jppo4 = jp_lp + 5    !: phosphate concentration  
    81    INTEGER, PUBLIC, PARAMETER ::   jppoc = jp_lp + 6    !: small particulate organic phosphate concentration 
    82    INTEGER, PUBLIC, PARAMETER ::   jpsil = jp_lp + 7    !: silicate concentration 
    83    INTEGER, PUBLIC, PARAMETER ::   jpphy = jp_lp + 8    !: phytoplancton concentration  
    84    INTEGER, PUBLIC, PARAMETER ::   jpzoo = jp_lp + 9    !: zooplancton concentration 
    85    INTEGER, PUBLIC, PARAMETER ::   jpdoc = jp_lp + 10    !: dissolved organic carbon concentration  
    86    INTEGER, PUBLIC, PARAMETER ::   jpdia = jp_lp + 11    !: Diatoms Concentration 
    87    INTEGER, PUBLIC, PARAMETER ::   jpmes = jp_lp + 12    !: Mesozooplankton Concentration 
    88    INTEGER, PUBLIC, PARAMETER ::   jpdsi = jp_lp + 13    !: (big) Silicate Concentration 
    89    INTEGER, PUBLIC, PARAMETER ::   jpfer = jp_lp + 14    !: Iron Concentration 
    90    INTEGER, PUBLIC, PARAMETER ::   jpbfe = jp_lp + 15    !: Big iron particles Concentration 
    91    INTEGER, PUBLIC, PARAMETER ::   jpgoc = jp_lp + 16    !: big particulate organic phosphate concentration 
    92    INTEGER, PUBLIC, PARAMETER ::   jpsfe = jp_lp + 17    !: Small iron particles Concentration 
    93    INTEGER, PUBLIC, PARAMETER ::   jpdfe = jp_lp + 18    !: Diatoms iron Concentration 
    94    INTEGER, PUBLIC, PARAMETER ::   jpgsi = jp_lp + 19    !: Diatoms Silicate Concentration 
    95    INTEGER, PUBLIC, PARAMETER ::   jpnfe = jp_lp + 20    !: Nano iron Concentration 
    96    INTEGER, PUBLIC, PARAMETER ::   jpnch = jp_lp + 21    !: Nano Chlorophyll Concentration 
    97    INTEGER, PUBLIC, PARAMETER ::   jpdch = jp_lp + 22    !: Diatoms Chlorophyll Concentration 
    98    INTEGER, PUBLIC, PARAMETER ::   jpno3 = jp_lp + 23    !: Nitrates Concentration 
    99    INTEGER, PUBLIC, PARAMETER ::   jpnh4 = jp_lp + 24    !: Ammonium Concentration 
     92   INTEGER, PUBLIC, PARAMETER ::   jpdic = 1    !: dissolved inoganic carbon concentration  
     93   INTEGER, PUBLIC, PARAMETER ::   jptal = 2    !: total alkalinity  
     94   INTEGER, PUBLIC, PARAMETER ::   jpoxy = 3    !: oxygen carbon concentration  
     95   INTEGER, PUBLIC, PARAMETER ::   jpcal = 4    !: calcite  concentration  
     96   INTEGER, PUBLIC, PARAMETER ::   jppo4 = 5    !: phosphate concentration  
     97   INTEGER, PUBLIC, PARAMETER ::   jppoc = 6    !: small particulate organic phosphate concentration 
     98   INTEGER, PUBLIC, PARAMETER ::   jpsil = 7    !: silicate concentration 
     99   INTEGER, PUBLIC, PARAMETER ::   jpphy = 8    !: phytoplancton concentration  
     100   INTEGER, PUBLIC, PARAMETER ::   jpzoo = 9    !: zooplancton concentration 
     101   INTEGER, PUBLIC, PARAMETER ::   jpdoc = 10    !: dissolved organic carbon concentration  
     102   INTEGER, PUBLIC, PARAMETER ::   jpdia = 11    !: Diatoms Concentration 
     103   INTEGER, PUBLIC, PARAMETER ::   jpmes = 12    !: Mesozooplankton Concentration 
     104   INTEGER, PUBLIC, PARAMETER ::   jpdsi = 13    !: (big) Silicate Concentration 
     105   INTEGER, PUBLIC, PARAMETER ::   jpfer = 14    !: Iron Concentration 
     106   INTEGER, PUBLIC, PARAMETER ::   jpbfe = 15    !: Big iron particles Concentration 
     107   INTEGER, PUBLIC, PARAMETER ::   jpgoc = 16    !: big particulate organic phosphate concentration 
     108   INTEGER, PUBLIC, PARAMETER ::   jpsfe = 17    !: Small iron particles Concentration 
     109   INTEGER, PUBLIC, PARAMETER ::   jpdfe = 18    !: Diatoms iron Concentration 
     110   INTEGER, PUBLIC, PARAMETER ::   jpgsi = 19    !: Diatoms Silicate Concentration 
     111   INTEGER, PUBLIC, PARAMETER ::   jpnfe = 20    !: Nano iron Concentration 
     112   INTEGER, PUBLIC, PARAMETER ::   jpnch = 21    !: Nano Chlorophyll Concentration 
     113   INTEGER, PUBLIC, PARAMETER ::   jpdch = 22    !: Diatoms Chlorophyll Concentration 
     114   INTEGER, PUBLIC, PARAMETER ::   jpno3 = 23    !: Nitrates Concentration 
     115   INTEGER, PUBLIC, PARAMETER ::   jpnh4 = 24    !: Ammonium Concentration 
    100116 
    101117#else 
     
    103119   !!   Default                                   No CFC geochemical model 
    104120   !!--------------------------------------------------------------------- 
    105    LOGICAL, PUBLIC, PARAMETER ::   lk_pisces     = .FALSE.  !: CFC flag  
    106    LOGICAL, PUBLIC, PARAMETER ::   lk_kriest     = .FALSE.  !: Kriest flag  
     121   LOGICAL, PUBLIC, PARAMETER ::   lk_pisces     = .FALSE.  !: PISCES flag  
     122   LOGICAL, PUBLIC, PARAMETER ::   lk_p4z        = .FALSE.  !: p4z flag  
    107123   INTEGER, PUBLIC, PARAMETER ::   jp_pisces     =  0       !: No CFC tracers 
    108124   INTEGER, PUBLIC, PARAMETER ::   jp_pisces_2d  =  0       !: No CFC additional 2d output arrays  
     
    112128 
    113129   ! Starting/ending PISCES do-loop indices (N.B. no PISCES : jpl_pcs < jpf_pcs the do-loop are never done) 
    114    INTEGER, PUBLIC, PARAMETER ::   jp_pcs0     = jp_lp + 1                  !: First index of PISCES tracers 
    115    INTEGER, PUBLIC, PARAMETER ::   jp_pcs1     = jp_lp + jp_pisces          !: Last  index of PISCES tracers 
    116    INTEGER, PUBLIC, PARAMETER ::   jp_pcs0_2d  = jp_lp_2d + 1               !: First index of 2D diag 
    117    INTEGER, PUBLIC, PARAMETER ::   jp_pcs1_2d  = jp_lp_2d + jp_pisces_2d    !: Last  index of 2D diag 
    118    INTEGER, PUBLIC, PARAMETER ::   jp_pcs0_3d  = jp_lp_3d + 1               !: First index of 3D diag 
    119    INTEGER, PUBLIC, PARAMETER ::   jp_pcs1_3d  = jp_lp_3d + jp_pisces_3d    !: Last  index of 3d diag 
    120    INTEGER, PUBLIC, PARAMETER ::   jp_pcs0_trd = jp_lp_trd + 1              !: First index of bio diag 
    121    INTEGER, PUBLIC, PARAMETER ::   jp_pcs1_trd = jp_lp_trd + jp_pisces_trd  !: Last  index of bio diag 
     130   INTEGER, PUBLIC, PARAMETER ::   jp_pcs0     = 1                  !: First index of PISCES tracers 
     131   INTEGER, PUBLIC, PARAMETER ::   jp_pcs1     = jp_pisces          !: Last  index of PISCES tracers 
     132   INTEGER, PUBLIC, PARAMETER ::   jp_pcs0_2d  = 1               !: First index of 2D diag 
     133   INTEGER, PUBLIC, PARAMETER ::   jp_pcs1_2d  = jp_pisces_2d    !: Last  index of 2D diag 
     134   INTEGER, PUBLIC, PARAMETER ::   jp_pcs0_3d  = 1               !: First index of 3D diag 
     135   INTEGER, PUBLIC, PARAMETER ::   jp_pcs1_3d  = jp_pisces_3d    !: Last  index of 3d diag 
     136   INTEGER, PUBLIC, PARAMETER ::   jp_pcs0_trd = 1              !: First index of bio diag 
     137   INTEGER, PUBLIC, PARAMETER ::   jp_pcs1_trd = jp_pisces_trd  !: Last  index of bio diag 
    122138 
    123139 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/sms_pisces.F90

    r3294 r3680  
    77   !!             3.2  !  2009-04 (C. Ethe & NEMO team) style 
    88   !!---------------------------------------------------------------------- 
    9 #if defined key_pisces 
     9#if defined key_pisces || defined key_pisces_reduced  
    1010   !!---------------------------------------------------------------------- 
    1111   !!   'key_pisces'                                         PISCES model 
     
    1919   INTEGER ::   numnatp 
    2020 
     21   !!*  Biological fluxes for light : variables shared by pisces & lobster 
     22   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  neln  !: number of T-levels + 1 in the euphotic layer 
     23   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  heup  !: euphotic layer depth 
     24   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  etot  !: par (photosynthetic available radiation) 
     25   ! 
     26   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  xksi  !:  LOBSTER : zooplakton closure 
     27   !                                                       !:  PISCES  : silicon dependant half saturation 
     28 
     29#if defined key_pisces  
    2130   !!*  Time variables 
    2231   INTEGER  ::   nrdttrc           !: ??? 
     
    2736 
    2837   !!*  Biological parameters  
     38   INTEGER  ::   niter1max, niter2max   !: Maximum number of iterations for sinking 
    2939   REAL(wp) ::   rno3              !: ??? 
    3040   REAL(wp) ::   o2ut              !: ??? 
     
    3747   REAL(wp) ::   ferat3            !: ??? 
    3848 
    39    !!* Damping  
    40    LOGICAL  ::   ln_pisdmp         !: relaxation or not of nutrients to a mean value 
    41    INTEGER  ::   nn_pisdmp         !: frequency of relaxation or not of nutrients to a mean value 
    42    LOGICAL  ::   ln_pisclo         !: Restoring or not of nutrients to initial value 
    43                                    !: on close seas 
     49   !!*  diagnostic parameters  
     50   REAL(wp) ::  tpp                !: total primary production 
     51   REAL(wp) ::  t_oce_co2_exp      !: total carbon export 
     52   REAL(wp) ::  t_oce_co2_flx      !: Total ocean carbon flux 
     53   REAL(wp) ::  t_atm_co2_flx      !: global mean of atmospheric pco2 
    4454 
    45    !!*  Biological fluxes for light 
    46    INTEGER , ALLOCATABLE, SAVE,   DIMENSION(:,:)  ::  neln       !: number of T-levels + 1 in the euphotic layer 
    47    REAL(wp), ALLOCATABLE, SAVE,   DIMENSION(:,:)  ::  heup       !: euphotic layer depth 
     55   !!* restoring 
     56   LOGICAL  ::  ln_pisdmp          !: restoring or not of nutrients to a mean value 
     57   INTEGER  ::  nn_pisdmp          !: frequency of relaxation or not of nutrients to a mean value 
     58   LOGICAL  ::  ln_pisclo          !: Restoring or not of nutrients to initial value on closed seas 
     59 
     60   !!* Mass conservation 
     61   LOGICAL  ::  ln_check_mass      !: Flag to check mass conservation 
    4862 
    4963   !!*  Biological fluxes for primary production 
    50    REAL(wp), ALLOCATABLE, SAVE,   DIMENSION(:,:)  ::   xksi       !: ??? 
    5164   REAL(wp), ALLOCATABLE, SAVE,   DIMENSION(:,:)  ::   xksimax    !: ??? 
    5265   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanono3   !: ??? 
     
    6174   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdfe    !: ??? 
    6275   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimsi     !: ??? 
     76   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   biron      !: bioavailable fraction of iron 
    6377 
    6478 
     
    6781   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   nitrfac    !: ?? 
    6882   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xlimbac    !: ?? 
     83   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xlimbacl   !: ?? 
    6984   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xdiss      !: ?? 
    70     REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prodcal    !: Calcite production 
    71     REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   grazing    !: Total zooplankton grazing 
     85   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prodcal    !: Calcite production 
    7286 
    7387   !!* Variable for chemistry of the CO2 cycle 
     
    96110#endif 
    97111 
     112#endif 
    98113   !!---------------------------------------------------------------------- 
    99114   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    111126      !!---------------------------------------------------------------------- 
    112127      ierr(:) = 0 
    113       !*  Biological fluxes for light 
    114       ALLOCATE( neln(jpi,jpj), heup(jpi,jpj),                  STAT=ierr(1) ) 
     128      !*  Biological fluxes for light : shared variables for pisces & lobster 
     129      ALLOCATE( etot(jpi,jpj,jpk), neln(jpi,jpj), heup(jpi,jpj), xksi(jpi,jpj), STAT=ierr(1) ) 
    115130      ! 
     131#if defined key_pisces 
    116132      !*  Biological fluxes for primary production 
    117       ALLOCATE( xksimax(jpi,jpj)     , xksi(jpi,jpj)        ,       & 
     133      ALLOCATE( xksimax(jpi,jpj)     , biron   (jpi,jpj,jpk),       & 
    118134         &      xnanono3(jpi,jpj,jpk), xdiatno3(jpi,jpj,jpk),       & 
    119135         &      xnanonh4(jpi,jpj,jpk), xdiatnh4(jpi,jpj,jpk),       & 
     
    121137         &      xlimnfe (jpi,jpj,jpk), xlimdfe (jpi,jpj,jpk),       & 
    122138         &      xlimsi  (jpi,jpj,jpk), concdfe (jpi,jpj,jpk),       & 
    123          &      concnfe (jpi,jpj,jpk),                          STAT=ierr(2) )  
     139         &      concnfe (jpi,jpj,jpk),                           STAT=ierr(2) )  
    124140         ! 
    125141      !*  SMS for the organic matter 
    126142      ALLOCATE( xfracal (jpi,jpj,jpk), nitrfac(jpi,jpj,jpk),       & 
    127          &      prodcal(jpi,jpj,jpk) , grazing(jpi,jpj,jpk),       & 
    128          &      xlimbac (jpi,jpj,jpk), xdiss  (jpi,jpj,jpk),   STAT=ierr(3) )   
    129          ! 
     143         &      xlimbac (jpi,jpj,jpk), xdiss  (jpi,jpj,jpk),       &  
     144         &      xlimbacl(jpi,jpj,jpk), prodcal(jpi,jpj,jpk),     STAT=ierr(3) ) 
     145 
    130146      !* Variable for chemistry of the CO2 cycle 
    131147      ALLOCATE( akb3(jpi,jpj,jpk)    , ak13  (jpi,jpj,jpk) ,       & 
    132148         &      ak23(jpi,jpj,jpk)    , aksp  (jpi,jpj,jpk) ,       & 
    133149         &      akw3(jpi,jpj,jpk)    , borat (jpi,jpj,jpk) ,       & 
    134          &      hi  (jpi,jpj,jpk)    , excess(jpi,jpj,jpk) ,   STAT=ierr(4) ) 
     150         &      hi  (jpi,jpj,jpk)    , excess(jpi,jpj,jpk) ,     STAT=ierr(4) ) 
    135151         ! 
    136152      !* Temperature dependancy of SMS terms 
    137       ALLOCATE( tgfunc(jpi,jpj,jpk)  , tgfunc2(jpi,jpj,jpk) ,   STAT=ierr(5) ) 
     153      ALLOCATE( tgfunc(jpi,jpj,jpk)  , tgfunc2(jpi,jpj,jpk) ,    STAT=ierr(5) ) 
    138154         ! 
    139155      !* Array used to indicate negative tracer values   
    140       ALLOCATE( xnegtr(jpi,jpj,jpk)  ,                          STAT=ierr(6) ) 
     156      ALLOCATE( xnegtr(jpi,jpj,jpk)  ,                           STAT=ierr(6) ) 
     157#endif 
    141158      ! 
    142159      sms_pisces_alloc = MAXVAL( ierr ) 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90

    r3295 r3680  
    99   !!             1.0  !  2005-03  (O. Aumont, A. El Moussaoui) F90 
    1010   !!             2.0  !  2007-12  (C. Ethe, G. Madec) from trcini.pisces.h90 
    11    !!---------------------------------------------------------------------- 
    12 #if defined key_pisces 
     11   !!             3.5  !  2012-05  (C. Ethe) Merge PISCES-LOBSTER 
     12   !!---------------------------------------------------------------------- 
     13#if defined key_pisces || defined key_pisces_reduced 
    1314   !!---------------------------------------------------------------------- 
    1415   !!   'key_pisces'                                       PISCES bio-model 
     
    2021   USE trc             !  passive tracers common variables  
    2122   USE sms_pisces      !  PISCES Source Minus Sink variables 
    22    USE p4zche          !  Chemical model 
    23    USE p4zsink         !  vertical flux of particulate matter due to sinking 
    24    USE p4zopt          !  optical model 
    25    USE p4zrem          !  Remineralisation of organic matter 
    26    USE p4zflx          !  Gas exchange 
    27    USE p4zsed          !  Sedimentation 
    28    USE p4zlim          !  Co-limitations of differents nutrients 
    29    USE p4zprod         !  Growth rate of the 2 phyto groups 
    30    USE p4zmicro        !  Sources and sinks of microzooplankton 
    31    USE p4zmeso         !  Sources and sinks of mesozooplankton 
    32    USE p4zmort         !  Mortality terms for phytoplankton 
    33    USE p4zlys          !  Calcite saturation 
    34    USE p4zsed          !  Sedimentation 
    3523 
    3624   IMPLICIT NONE 
     
    3927   PUBLIC   trc_ini_pisces   ! called by trcini.F90 module 
    4028 
    41    REAL(wp) :: sco2   =  2.312e-3_wp 
    42    REAL(wp) :: alka0  =  2.423e-3_wp 
    43    REAL(wp) :: oxyg0  =  177.6e-6_wp  
    44    REAL(wp) :: po4    =  2.174e-6_wp  
    45    REAL(wp) :: bioma0 =  1.000e-8_wp   
    46    REAL(wp) :: silic1 =  91.65e-6_wp   
    47    REAL(wp) :: no3    =  31.04e-6_wp * 7.625_wp 
    4829 
    4930#  include "top_substitute.h90" 
     
    6142      !! ** Purpose :   Initialisation of the PISCES biochemical model 
    6243      !!---------------------------------------------------------------------- 
    63       ! 
    64       INTEGER  ::  ji, jj, jk 
     44 
     45      IF( lk_pisces ) THEN  ;   CALL p4z_ini   !  PISCES 
     46      ELSE                  ;   CALL p2z_ini   !  LOBSTER 
     47      ENDIF 
     48 
     49   END SUBROUTINE trc_ini_pisces 
     50 
     51   SUBROUTINE p4z_ini 
     52      !!---------------------------------------------------------------------- 
     53      !!                   ***  ROUTINE p4z_ini *** 
     54      !! 
     55      !! ** Purpose :   Initialisation of the PISCES biochemical model 
     56      !!---------------------------------------------------------------------- 
     57#if defined key_pisces  
     58      ! 
     59      USE p4zsms          ! Main P4Z routine 
     60      USE p4zche          !  Chemical model 
     61      USE p4zsink         !  vertical flux of particulate matter due to sinking 
     62      USE p4zopt          !  optical model 
     63      USE p4zsbc          !  Boundary conditions 
     64      USE p4zfechem       !  Iron chemistry 
     65      USE p4zrem          !  Remineralisation of organic matter 
     66      USE p4zflx          !  Gas exchange 
     67      USE p4zlim          !  Co-limitations of differents nutrients 
     68      USE p4zprod         !  Growth rate of the 2 phyto groups 
     69      USE p4zmicro        !  Sources and sinks of microzooplankton 
     70      USE p4zmeso         !  Sources and sinks of mesozooplankton 
     71      USE p4zmort         !  Mortality terms for phytoplankton 
     72      USE p4zlys          !  Calcite saturation 
     73      ! 
     74      REAL(wp), SAVE :: sco2   =  2.312e-3_wp 
     75      REAL(wp), SAVE :: alka0  =  2.423e-3_wp 
     76      REAL(wp), SAVE :: oxyg0  =  177.6e-6_wp  
     77      REAL(wp), SAVE :: po4    =  2.174e-6_wp  
     78      REAL(wp), SAVE :: bioma0 =  1.000e-8_wp   
     79      REAL(wp), SAVE :: silic1 =  91.65e-6_wp   
     80      REAL(wp), SAVE :: no3    =  31.04e-6_wp * 7.625_wp 
     81      ! 
     82      INTEGER  ::  ji, jj, jk, ierr 
    6583      REAL(wp) ::  zcaralk, zbicarb, zco3 
    6684      REAL(wp) ::  ztmas, ztmas1 
    6785      !!---------------------------------------------------------------------- 
     86 
    6887      IF(lwp) WRITE(numout,*) 
    69       IF(lwp) WRITE(numout,*) ' trc_ini_pisces :   PISCES biochemical model initialisation' 
     88      IF(lwp) WRITE(numout,*) ' p4z_ini :   PISCES biochemical model initialisation' 
    7089      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~' 
    7190 
    72       CALL pisces_alloc()                          ! Allocate PISCES arrays 
    73  
     91                                                 ! Allocate PISCES arrays 
     92      ierr =         sms_pisces_alloc()           
     93      ierr = ierr +  p4z_che_alloc() 
     94      ierr = ierr +  p4z_sink_alloc() 
     95      ierr = ierr +  p4z_opt_alloc() 
     96      ierr = ierr +  p4z_prod_alloc() 
     97      ierr = ierr +  p4z_rem_alloc() 
     98      ierr = ierr +  p4z_flx_alloc() 
     99      ! 
     100      IF( lk_mpp    )   CALL mpp_sum( ierr ) 
     101      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' ) 
     102      ! 
     103 
     104      CALL p4z_sms_init       !  Maint routine 
    74105      !                                            ! Time-step 
    75106      rfact   = rdttrc(1)                          ! --------- 
     
    132163         xksimax(:,:) = xksi(:,:) 
    133164 
    134       ENDIF 
    135  
    136       IF( .NOT. ln_rsttr ) THEN 
    137165         ! Initialization of chemical variables of the carbon cycle 
    138166         ! -------------------------------------------------------- 
     
    159187      CALL p4z_lim_init       !  co-limitations by the various nutrients 
    160188      CALL p4z_prod_init      !  phytoplankton growth rate over the global ocean. 
     189      CALL p4z_sbc_init       !  boundary conditions 
     190      CALL p4z_fechem_init    !  Iron chemistry 
    161191      CALL p4z_rem_init       !  remineralisation 
    162192      CALL p4z_mort_init      !  phytoplankton mortality  
    163193      CALL p4z_micro_init     !  microzooplankton 
    164194      CALL p4z_meso_init      !  mesozooplankton 
    165       CALL p4z_sed_init       !  sedimentation  
    166195      CALL p4z_lys_init       !  calcite saturation 
    167196      CALL p4z_flx_init       !  gas exchange  
     
    172201      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done' 
    173202      IF(lwp) WRITE(numout,*)  
    174       ! 
    175    END SUBROUTINE trc_ini_pisces 
    176  
    177  
    178    SUBROUTINE pisces_alloc 
    179       !!---------------------------------------------------------------------- 
    180       !!                     ***  ROUTINE pisces_alloc *** 
     203#endif 
     204      ! 
     205   END SUBROUTINE p4z_ini 
     206 
     207   SUBROUTINE p2z_ini 
     208      !!---------------------------------------------------------------------- 
     209      !!                   ***  ROUTINE p2z_ini *** 
    181210      !! 
    182       !! ** Purpose :   Allocate all the dynamic arrays of PISCES  
    183       !!---------------------------------------------------------------------- 
    184       ! 
    185       INTEGER :: ierr 
    186       !!---------------------------------------------------------------------- 
    187       ! 
    188       ierr =         sms_pisces_alloc()          ! Start of PISCES-related alloc routines... 
    189       ierr = ierr +  p4z_che_alloc() 
    190       ierr = ierr +  p4z_sink_alloc() 
    191       ierr = ierr +  p4z_opt_alloc() 
    192       ierr = ierr +  p4z_prod_alloc() 
    193       ierr = ierr +  p4z_rem_alloc() 
    194       ierr = ierr +  p4z_sed_alloc() 
    195       ierr = ierr +  p4z_flx_alloc() 
     211      !! ** Purpose :   Initialisation of the LOBSTER biochemical model 
     212      !!---------------------------------------------------------------------- 
     213#if defined key_pisces_reduced  
     214      ! 
     215      USE p2zopt 
     216      USE p2zexp 
     217      USE p2zbio 
     218      USE p2zsed 
     219      ! 
     220      INTEGER  ::  ji, jj, jk, ierr 
     221      !!---------------------------------------------------------------------- 
     222 
     223      IF(lwp) WRITE(numout,*) 
     224      IF(lwp) WRITE(numout,*) ' p2z_ini :   LOBSTER biochemical model initialisation' 
     225      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~' 
     226 
     227      ierr =        sms_pisces_alloc()           
     228      ierr = ierr + p2z_exp_alloc() 
    196229      ! 
    197230      IF( lk_mpp    )   CALL mpp_sum( ierr ) 
    198       IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' ) 
    199       ! 
    200    END SUBROUTINE pisces_alloc 
    201  
     231      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'p2z_ini: unable to allocate LOBSTER arrays' ) 
     232 
     233      ! LOBSTER initialisation for GYRE : init NO3=f(density) by asklod AS Kremeur 2005-07 
     234      ! ---------------------- 
     235      IF( .NOT. ln_rsttr ) THEN             ! in case of  no restart  
     236         trn(:,:,:,jpdet) = 0.1 * tmask(:,:,:) 
     237         trn(:,:,:,jpzoo) = 0.1 * tmask(:,:,:) 
     238         trn(:,:,:,jpnh4) = 0.1 * tmask(:,:,:) 
     239         trn(:,:,:,jpphy) = 0.1 * tmask(:,:,:) 
     240         trn(:,:,:,jpdom) = 1.0 * tmask(:,:,:) 
     241         WHERE( rhd(:,:,:) <= 24.5e-3 )  ;  trn(:,:,:,jpno3 ) = 2._wp * tmask(:,:,:) 
     242         ELSE WHERE                      ;  trn(:,:,:,jpno3) = ( 15.55 * ( rhd(:,:,:) * 1000. ) - 380.11 ) * tmask(:,:,:) 
     243         END WHERE                        
     244      ENDIF 
     245      !                       !  Namelist read 
     246      CALL p2z_opt_init       !  Optics parameters 
     247      CALL p2z_sed_init       !  sedimentation 
     248      CALL p2z_bio_init       !  biology 
     249      CALL p2z_exp_init       !  export  
     250      ! 
     251      IF(lwp) WRITE(numout,*)  
     252      IF(lwp) WRITE(numout,*) 'Initialization of LOBSTER tracers done' 
     253      IF(lwp) WRITE(numout,*)  
     254#endif 
     255      ! 
     256   END SUBROUTINE p2z_ini 
    202257#else 
    203258   !!---------------------------------------------------------------------- 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/trcnam_pisces.F90

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

    r3320 r3680  
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    88   !!---------------------------------------------------------------------- 
    9 #if defined key_pisces 
     9#if defined key_pisces || defined key_pisces_reduced 
    1010   !!---------------------------------------------------------------------- 
    1111   !!   'key_pisces'                                       PISCES bio-model 
     
    1313   !!   trcsms_pisces        :  Time loop of passive tracers sms 
    1414   !!---------------------------------------------------------------------- 
    15    USE oce_trc         !  shared variables between ocean and passive tracers 
    16    USE trc             !  passive tracers common variables  
    17    USE sms_pisces      !  PISCES Source Minus Sink variables 
    18    USE p4zbio          !  Biological model 
    19    USE p4zche          !  Chemical model 
    20    USE p4zlys          !  Calcite saturation 
    21    USE p4zflx          !  Gas exchange 
    22    USE p4zsed          !  Sedimentation 
    23    USE p4zint          !  time interpolation 
    24    USE trdmod_oce      !  Ocean trends variables 
    25    USE trdmod_trc      !  TOP trends variables 
    26    USE sedmodel        !  Sediment model 
    27    USE prtctl_trc      !  print control for debugging 
     15   USE par_pisces 
     16   USE p4zsms 
     17   USE p2zsms 
    2818 
    2919   IMPLICIT NONE 
     
    3121 
    3222   PUBLIC   trc_sms_pisces    ! called in trcsms.F90 
    33  
    34    LOGICAL ::  ln_check_mass = .false.       !: Flag to check mass conservation  
    35  
    36    INTEGER ::  numno3  !: logical unit for NO3 budget 
    37    INTEGER ::  numalk  !: logical unit for talk budget 
    38    INTEGER ::  numsil  !: logical unit for Si budget 
    39  
    4023   !!---------------------------------------------------------------------- 
    4124   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    4629CONTAINS 
    4730 
     31      !!---------------------------------------------------------------------- 
     32      !!                   ***  ROUTINE trc_ini_pisces *** 
     33      !! 
     34      !! ** Purpose :   Initialisation of the PISCES biochemical model 
     35      !!---------------------------------------------------------------------- 
     36 
     37 
    4838   SUBROUTINE trc_sms_pisces( kt ) 
    4939      !!--------------------------------------------------------------------- 
     
    5141      !! 
    5242      !! ** Purpose :   Managment of the call to Biological sources and sinks  
    53       !!              routines of PISCES bio-model 
    54       !! 
    55       !! ** Method  : - at each new day ... 
    56       !!              - several calls of bio and sed ??? 
    57       !!              - ... 
    58       !!--------------------------------------------------------------------- 
    59       ! 
    60       INTEGER, INTENT( in ) ::   kt      ! ocean time-step index       
    61       !! 
    62       INTEGER ::   jnt, jn, jl 
    63       CHARACTER (len=25) :: charout 
    64       REAL(wp), POINTER, DIMENSION(:,:,:,:)  :: ztrdpis 
    65       !!--------------------------------------------------------------------- 
    66       ! 
    67       IF( nn_timing == 1 )  CALL timing_start('trc_sms_pisces') 
    68       ! 
    69       IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL trc_sms_pisces_dmp( kt )  ! Relaxation of some tracers 
    70                                                                    CALL trc_sms_pisces_mass_conserv( kt ) ! Mass conservation checking 
    71       IF( l_trdtrc )  THEN 
    72          CALL wrk_alloc( jpi, jpj, jpk, jp_pisces, ztrdpis )  
    73          DO jn = 1, jp_pisces 
    74             jl = jn + jp_pcs0 - 1 
    75             ztrdpis(:,:,:,jn) = trn(:,:,:,jl) 
    76          ENDDO 
    77       ENDIF 
    78  
    79       IF( ndayflxtr /= nday_year ) THEN      ! New days 
    80          ! 
    81          ndayflxtr = nday_year 
    82  
    83          IF(lwp) write(numout,*) 
    84          IF(lwp) write(numout,*) ' New chemical constants and various rates for biogeochemistry at new day : ', nday_year 
    85          IF(lwp) write(numout,*) '~~~~~~' 
    86  
    87          CALL p4z_che              ! computation of chemical constants 
    88          CALL p4z_int              ! computation of various rates for biogeochemistry 
    89          ! 
    90       ENDIF 
    91  
    92  
    93       DO jnt = 1, nrdttrc          ! Potential time splitting if requested 
    94          ! 
    95          CALL p4z_bio (kt, jnt)    ! Compute soft tissue production (POC) 
    96          CALL p4z_sed (kt, jnt)    ! compute soft tissue remineralisation 
    97          ! 
    98          DO jn = jp_pcs0, jp_pcs1 
    99             trb(:,:,:,jn) = trn(:,:,:,jn) 
    100          ENDDO 
    101          ! 
    102       END DO 
    103  
    104       IF( l_trdtrc )  THEN 
    105          DO jn = 1, jp_pisces 
    106             jl = jn + jp_pcs0 - 1 
    107             ztrdpis(:,:,:,jn) = ( ztrdpis(:,:,:,jn) - trn(:,:,:,jl) ) * rfact2r 
    108          ENDDO 
    109       ENDIF 
    110  
    111       CALL p4z_lys( kt )             ! Compute CaCO3 saturation 
    112       CALL p4z_flx( kt )             ! Compute surface fluxes 
    113  
    114       DO jn = jp_pcs0, jp_pcs1 
    115         CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. ) 
    116         CALL lbc_lnk( trb(:,:,:,jn), 'T', 1. ) 
    117         CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. ) 
    118       END DO 
    119  
    120       IF( l_trdtrc ) THEN 
    121          DO jn = 1, jp_pisces 
    122             jl = jn + jp_pcs0 - 1 
    123              ztrdpis(:,:,:,jn) = ztrdpis(:,:,:,jn) + tra(:,:,:,jl) 
    124              CALL trd_mod_trc( ztrdpis(:,:,:,jn), jn, jptra_trd_sms, kt )   ! save trends 
    125           END DO 
    126           CALL wrk_dealloc( jpi, jpj, jpk, jp_pisces, ztrdpis )  
    127       END IF 
    128  
    129       IF( lk_sed ) THEN  
    130          ! 
    131          CALL sed_model( kt )     !  Main program of Sediment model 
    132          ! 
    133          DO jn = jp_pcs0, jp_pcs1 
    134            CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. ) 
    135          END DO 
    136          ! 
    137       ENDIF 
    138       ! 
    139       IF( nn_timing == 1 )  CALL timing_stop('trc_sms_pisces') 
    140       ! 
    141    END SUBROUTINE trc_sms_pisces 
    142  
    143    SUBROUTINE trc_sms_pisces_dmp( kt ) 
    144       !!---------------------------------------------------------------------- 
    145       !!                    ***  trc_sms_pisces_dmp  *** 
    146       !! 
    147       !! ** purpose  : Relaxation of some tracers 
    148       !!---------------------------------------------------------------------- 
    149       ! 
    150       INTEGER, INTENT( in )  ::     kt ! time step 
    151       ! 
    152       REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. ) 
    153       REAL(wp) ::  po4mean = 2.165     ! mean value of phosphates 
    154       REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate 
    155       REAL(wp) ::  silmean = 91.51     ! mean value of silicate 
    156       ! 
    157       REAL(wp) :: zarea, zalksum, zpo4sum, zno3sum, zsilsum 
    158       !!--------------------------------------------------------------------- 
    159  
    160  
    161       IF(lwp)  WRITE(numout,*) 
    162       IF(lwp)  WRITE(numout,*) ' trc_sms_pisces_dmp : Relaxation of nutrients at time-step kt = ', kt 
    163       IF(lwp)  WRITE(numout,*) 
    164  
    165       IF( cp_cfg == "orca" .AND. .NOT. lk_c1d ) THEN      ! ORCA condiguration (not 1D) ! 
    166          !                                                    ! --------------------------- ! 
    167          ! set total alkalinity, phosphate, nitrate & silicate 
    168          zarea          = 1._wp / glob_sum( cvol(:,:,:) ) * 1e6               
    169  
    170          zalksum = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea 
    171          zpo4sum = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea / 122. 
    172          zno3sum = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea / 7.6 
    173          zsilsum = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea 
    174   
    175          IF(lwp) WRITE(numout,*) '       TALK mean : ', zalksum 
    176          trn(:,:,:,jptal) = trn(:,:,:,jptal) * alkmean / zalksum 
    177  
    178          IF(lwp) WRITE(numout,*) '       PO4  mean : ', zpo4sum 
    179          trn(:,:,:,jppo4) = trn(:,:,:,jppo4) * po4mean / zpo4sum 
    180  
    181          IF(lwp) WRITE(numout,*) '       NO3  mean : ', zno3sum 
    182          trn(:,:,:,jpno3) = trn(:,:,:,jpno3) * no3mean / zno3sum 
    183  
    184          IF(lwp) WRITE(numout,*) '       SiO3 mean : ', zsilsum 
    185          trn(:,:,:,jpsil) = MIN( 400.e-6,trn(:,:,:,jpsil) * silmean / zsilsum ) 
    186          ! 
    187       ENDIF 
    188  
    189    END SUBROUTINE trc_sms_pisces_dmp 
    190  
    191    SUBROUTINE trc_sms_pisces_mass_conserv ( kt ) 
    192       !!---------------------------------------------------------------------- 
    193       !!                  ***  ROUTINE trc_sms_pisces_mass_conserv  *** 
    194       !! 
    195       !! ** Purpose :  Mass conservation check  
     43      !!                routines of PISCES or LOBSTER bio-model 
    19644      !! 
    19745      !!--------------------------------------------------------------------- 
    19846      ! 
    19947      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index       
    200       !! 
    201       REAL(wp) :: zalkbudget, zno3budget, zsilbudget 
     48      !!--------------------------------------------------------------------- 
    20249      ! 
    203       NAMELIST/nampismass/ ln_check_mass 
    204       !!--------------------------------------------------------------------- 
    205  
    206       IF( kt == nittrc000 ) THEN  
    207          REWIND( numnatp )        
    208          READ  ( numnatp, nampismass ) 
    209          IF(lwp) THEN                         ! control print 
    210             WRITE(numout,*) ' ' 
    211             WRITE(numout,*) ' Namelist parameter for mass conservation checking' 
    212             WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    213             WRITE(numout,*) '    Flag to check mass conservation of NO3/Si/TALK ln_check_mass = ', ln_check_mass 
    214          ENDIF 
    215  
    216          IF( ln_check_mass .AND. lwp) THEN      !   Open budget file of NO3, ALK, Si 
    217             CALL ctl_opn( numno3, 'no3.budget' , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    218             CALL ctl_opn( numsil, 'sil.budget' , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    219             CALL ctl_opn( numalk, 'talk.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    220          ENDIF 
     50      IF( lk_p4z ) THEN  ;   CALL p4z_sms( kt )   !  PISCES 
     51      ELSE               ;   CALL p2z_sms( kt )   !  LOBSTER 
    22152      ENDIF 
    222  
    223       IF( ln_check_mass ) THEN      !   Compute the budget of NO3, ALK, Si 
    224          zno3budget = glob_sum( (   trn(:,:,:,jpno3) + trn(:,:,:,jpnh4)  & 
    225             &                     + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  & 
    226             &                     + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  & 
    227             &                     + trn(:,:,:,jppoc) + trn(:,:,:,jpgoc)  & 
    228             &                     + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  )  
    229          !  
    230          zsilbudget = glob_sum( (   trn(:,:,:,jpsil) + trn(:,:,:,jpgsi)  & 
    231             &                     + trn(:,:,:,jpdsi)                     ) * cvol(:,:,:)  ) 
    232          !  
    233          zalkbudget = glob_sum( (   trn(:,:,:,jpno3) * rno3              & 
    234             &                     + trn(:,:,:,jptal)                     & 
    235             &                     + trn(:,:,:,jpcal) * 2.                ) * cvol(:,:,:)  ) 
    236  
    237          IF( lwp ) THEN 
    238             WRITE(numno3,9500) kt,  zno3budget / areatot 
    239             WRITE(numsil,9500) kt,  zsilbudget / areatot 
    240             WRITE(numalk,9500) kt,  zalkbudget / areatot 
    241          ENDIF 
    242        ENDIF 
    243  9500  FORMAT(i10,e18.10)      
    244        ! 
    245    END SUBROUTINE trc_sms_pisces_mass_conserv 
     53      ! 
     54   END SUBROUTINE trc_sms_pisces 
    24655 
    24756#else 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/trcwri_pisces.F90

    r3295 r3680  
    66   !! History :   1.0  !  2009-05 (C. Ethe)  Original code 
    77   !!---------------------------------------------------------------------- 
    8 #if defined key_top && key_pisces && defined key_iomput 
     8#if defined key_top && defined key_iomput && ( defined key_pisces || defined key_pisces_reduced ) 
    99   !!---------------------------------------------------------------------- 
    10    !!   'key_pisces'                                           PISCES model 
     10   !!   'key_pisces or key_pisces_reduced'                     PISCES model 
    1111   !!---------------------------------------------------------------------- 
    1212   !! trc_wri_pisces   :  outputs of concentration fields 
    1313   !!---------------------------------------------------------------------- 
    1414   USE trc         ! passive tracers common variables  
     15   USE sms_pisces  ! PISCES variables 
    1516   USE iom         ! I/O manager 
    1617 
     
    3536      ! write the tracer concentrations in the file 
    3637      ! --------------------------------------- 
    37       DO jn = 1, jptra 
    38          zrfact = 1.0e+6  
    39          IF( jn == jpno3 .OR. jn == jpnh4 ) zrfact = 1.0e+6 / 7.6 
    40          IF( jn == jppo4  )                 zrfact = 1.0e+6 / 122. 
     38#if defined key_pisces_reduced 
     39      DO jn = jp_pcs0, jp_pcs1 
    4140         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer 
    4241         CALL iom_put( cltra, trn(:,:,:,jn) * zrfact ) 
    4342      END DO 
     43#else 
     44      DO jn = jp_pcs0, jp_pcs1 
     45         zrfact = 1.0e+6  
     46         IF( jn == jpno3 .OR. jn == jpnh4 ) zrfact = rno3 * 1.0e+6  
     47         IF( jn == jppo4  )                 zrfact = po4r * 1.0e+6 
     48         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer 
     49         CALL iom_put( cltra, trn(:,:,:,jn) * zrfact ) 
     50      END DO 
     51#endif 
    4452      ! 
    4553   END SUBROUTINE trc_wri_pisces 
Note: See TracChangeset for help on using the changeset viewer.