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.
sms_pisces.F90 in branches/CNRS/dev_r6270_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/CNRS/dev_r6270_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/sms_pisces.F90 @ 8003

Last change on this file since 8003 was 8003, checked in by aumont, 7 years ago

modification in the code to remove unnecessary parts such as kriest and non iomput options

  • Property svn:keywords set to Id
File size: 8.8 KB
Line 
1MODULE sms_pisces   
2   !!----------------------------------------------------------------------
3   !!                     ***  sms_pisces.F90  *** 
4   !! TOP :   PISCES Source Minus Sink variables
5   !!----------------------------------------------------------------------
6   !! History :   1.0  !  2000-02 (O. Aumont) original code
7   !!             3.2  !  2009-04 (C. Ethe & NEMO team) style
8   !!             3.6  !  2015-05  (O. Aumont) PISCES quota
9   !!----------------------------------------------------------------------
10#if defined key_pisces || defined key_pisces_reduced || defined key_pisces_quota 
11   !!----------------------------------------------------------------------
12   !!   'key_pisces*'                                         PISCES model
13   !!----------------------------------------------------------------------
14   USE par_oce
15   USE par_trc
16
17   IMPLICIT NONE
18   PUBLIC
19
20   INTEGER ::   numnatp_ref = -1           !! Logical units for namelist pisces
21   INTEGER ::   numnatp_cfg = -1           !! Logical units for namelist pisces
22   INTEGER ::   numonp      = -1           !! Logical unit for namelist pisces output
23
24   !!*  Biological fluxes for light : variables shared by pisces & lobster
25   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  neln    !: number of T-levels + 1 in the euphotic layer
26   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  heup    !: euphotic layer depth
27   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  heup_01 !: Absolute euphotic layer depth
28   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  etot    !: par (photosynthetic available radiation)
29   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  xksi    !:  LOBSTER : zooplakton closure
30   !                                                         !:  PISCES  : silicon dependant half saturation
31
32#if defined key_pisces || defined key_pisces_quota 
33   !!*  Time variables
34   INTEGER  ::   nrdttrc           !: ???
35   INTEGER  ::   ndayflxtr         !: ???
36   REAL(wp) ::   rfact , rfactr    !: ???
37   REAL(wp) ::   rfact2, rfact2r   !: ???
38   REAL(wp) ::   xstep             !: Time step duration for biology
39   REAL(wp) ::   ryyss             !: number of seconds per year
40   REAL(wp) ::   r1_ryyss          !: inverse number of seconds per year
41
42   !!*  Biological parameters
43   INTEGER  ::   niter1max, niter2max   !: Maximum number of iterations for sinking
44   REAL(wp) ::   rno3              !: ???
45   REAL(wp) ::   o2ut              !: ???
46   REAL(wp) ::   po4r              !: ???
47   REAL(wp) ::   rdenit            !: ???
48   REAL(wp) ::   rdenita           !: ???
49   REAL(wp) ::   o2nit             !: ???
50   REAL(wp) ::   wsbio, wsbio2     !: ???
51   REAL(wp) ::   wsbio2max         !: ???
52   REAL(wp) ::   wsbio2scale       !: ???
53   REAL(wp) ::   xkmort            !: ???
54   REAL(wp) ::   ferat3            !: ???
55#if defined key_ligand
56   REAL(wp) ::   wfep              !: ???
57   REAL(wp) ::   ldocp           !: ???
58   REAL(wp) ::   ldocz           !: ???
59   REAL(wp) ::   lthet           !: ???
60#endif
61
62
63   !!*  diagnostic parameters
64   REAL(wp) ::  tpp                !: total primary production
65   REAL(wp) ::  t_oce_co2_exp      !: total carbon export
66   REAL(wp) ::  t_oce_co2_flx      !: Total ocean carbon flux
67   REAL(wp) ::  t_oce_co2_flx_cum  !: Cumulative Total ocean carbon flux
68   REAL(wp) ::  t_atm_co2_flx      !: global mean of atmospheric pco2
69
70   !!* restoring
71   LOGICAL  ::  ln_pisdmp          !: restoring or not of nutrients to a mean value
72   INTEGER  ::  nn_pisdmp          !: frequency of relaxation or not of nutrients to a mean value
73
74   !!* Mass conservation
75   LOGICAL  ::  ln_check_mass      !: Flag to check mass conservation
76
77   !!*  Biological fluxes for primary production
78   REAL(wp), ALLOCATABLE, SAVE,   DIMENSION(:,:)  ::   xksimax    !: ???
79   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   biron      !: bioavailable fraction of iron
80#if defined key_ligand
81   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   plig       !: proportion of iron organically complexed
82#endif
83
84   !!*  SMS for the organic matter
85   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xfracal    !: ??
86   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   nitrfac    !: ??
87   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   orem       !: ??
88   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xdiss      !: ??
89   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prodcal    !: Calcite production
90   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prodpoc    !: Calcite production
91   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   conspoc    !: Calcite production
92   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prodgoc    !: Calcite production
93   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   consgoc    !: Calcite production
94
95
96   !!* Variable for chemistry of the CO2 cycle
97   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ak13       !: ???
98   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ak23       !: ???
99   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   aksp       !: ???
100   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hi         !: ???
101   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   excess     !: ???
102   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   aphscale   !:
103
104
105   !!* Temperature dependancy of SMS terms
106   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tgfunc    !: Temp. dependancy of various biological rates
107   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tgfunc2   !: Temp. dependancy of mesozooplankton rates
108
109#endif
110
111# if defined key_pisces_quota
112   !!*  Biological parameters
113   REAL(wp) ::   no3rat3           !: ???
114   REAL(wp) ::   po4rat3           !: ???
115
116   !!*  SMS for the organic matter
117   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sizen      !: size of diatoms
118   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sizep      !: size of diatoms
119   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sized      !: size of diatoms
120
121#endif
122   !!----------------------------------------------------------------------
123   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
124   !! $Id$
125   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
126   !!----------------------------------------------------------------------
127CONTAINS
128
129   INTEGER FUNCTION sms_pisces_alloc()
130      !!----------------------------------------------------------------------
131      !!        *** ROUTINE sms_pisces_alloc ***
132      !!----------------------------------------------------------------------
133      USE lib_mpp , ONLY: ctl_warn
134#if defined key_pisces_quota
135      INTEGER ::   ierr(6)        ! Local variables
136#else
137      INTEGER ::   ierr(5)        ! Local variables
138#endif
139      !!----------------------------------------------------------------------
140      ierr(:) = 0
141      !*  Biological fluxes for light : shared variables for pisces & lobster
142      ALLOCATE( etot(jpi,jpj,jpk), neln(jpi,jpj), heup(jpi,jpj),    &
143      &         heup_01(jpi,jpj), xksi(jpi,jpj), STAT=ierr(1) )
144      !
145#if defined key_pisces || defined key_pisces_quota
146      !*  Biological fluxes for primary production
147      ALLOCATE( xksimax(jpi,jpj)     , biron   (jpi,jpj,jpk),       &
148#if defined key_ligand
149      &         plig(jpi,jpj,jpk)    ,                              &
150#endif
151         &      STAT=ierr(2) )
152         !
153      !*  SMS for the organic matter
154      ALLOCATE( xfracal (jpi,jpj,jpk), nitrfac (jpi,jpj,jpk),      &
155         &      orem    (jpi,jpj,jpk),                             &
156         &      prodcal(jpi,jpj,jpk),  xdiss   (jpi,jpj,jpk),      & 
157         &      prodpoc(jpi,jpj,jpk) , conspoc(jpi,jpj,jpk),       &
158         &      prodgoc(jpi,jpj,jpk) , consgoc(jpi,jpj,jpk),     STAT=ierr(3) )
159
160      !* Variable for chemistry of the CO2 cycle
161      ALLOCATE( ak13  (jpi,jpj,jpk) ,                              &
162         &      ak23(jpi,jpj,jpk)    , aksp  (jpi,jpj,jpk) ,       &
163         &      hi  (jpi,jpj,jpk)    , excess(jpi,jpj,jpk) ,       &
164         &      aphscale(jpi,jpj,jpk),                           STAT=ierr(4) )
165         !
166      !* Temperature dependancy of SMS terms
167      ALLOCATE( tgfunc(jpi,jpj,jpk)  , tgfunc2(jpi,jpj,jpk) ,    STAT=ierr(5) )
168         !
169#endif
170#if defined key_pisces_quota
171      !*  Size of phytoplankton cells
172      ALLOCATE( sizen   (jpi,jpj,jpk), sizep   (jpi,jpj,jpk),      &
173         &      sized   (jpi,jpj,jpk), STAT=ierr(6) )
174         !
175#endif
176
177      !
178      sms_pisces_alloc = MAXVAL( ierr )
179      !
180      IF( sms_pisces_alloc /= 0 )   CALL ctl_warn('sms_pisces_alloc: failed to allocate arrays') 
181      !
182   END FUNCTION sms_pisces_alloc
183
184#else
185   !!----------------------------------------------------------------------   
186   !!  Empty module :                                     NO PISCES model
187   !!----------------------------------------------------------------------
188#endif
189   
190   !!======================================================================   
191END MODULE sms_pisces   
Note: See TracBrowser for help on using the repository browser.