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 3584 for branches/2012/dev_LOCEAN_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/sms_pisces.F90 – NEMO

Ignore:
Timestamp:
2012-11-16T17:21:47+01:00 (11 years ago)
Author:
cetlod
Message:

Add in branch 2012/dev_LOCEAN_2012 changes from dev_r3438_LOCEAN15_PISLOB & dev_r3387_LOCEAN6_AGRIF_LIM, see ticket 1000

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_LOCEAN_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/sms_pisces.F90

    r3294 r3584  
    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 ) 
Note: See TracChangeset for help on using the changeset viewer.