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_medusa.F90 in branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/sms_medusa.F90 @ 7894

Last change on this file since 7894 was 7894, checked in by jpalmier, 7 years ago

JPALM -- 11-04-2017 -- MEDUSA spring tidy-up refreshning session

File size: 23.6 KB
Line 
1MODULE sms_medusa 
2   !!----------------------------------------------------------------------
3   !!                     ***  sms_medusa.F90  *** 
4   !! TOP :   MEDUSA  Source Minus Sink variables
5   !!----------------------------------------------------------------------
6   !! History :    -   !  1999-09 (M. Levy)  original code
7   !!              -   !  2000-12 (O. Aumont, E. Kestenare)  add sediment
8   !!             1.0  !  2005-10 (C. Ethe) F90
9   !!             1.0  !  2005-03  (A-S Kremeur) add fphylab, fzoolab, fdetlab, fdbod
10   !!              -   !  2005-06  (A-S Kremeur) add sedpocb, sedpocn, sedpoca
11   !!             2.0  !  2007-04  (C. Deltel, G. Madec)  Free form and modules
12   !!              -   !  2008-08  (K. Popova) adaptation for MEDUSA
13   !!              -   !  2008-11  (A. Yool) continuing adaptation for MEDUSA
14   !!              -   !  2010-03  (A. Yool) updated for branch inclusion
15   !!              -   !  2011-04  (A. Yool) updated for ROAM project
16   !!----------------------------------------------------------------------
17
18#if defined key_medusa
19   !!----------------------------------------------------------------------
20   !!   'key_medusa'                                         MEDUSA model
21   !!----------------------------------------------------------------------
22   USE par_oce
23   USE par_trc
24
25   IMPLICIT NONE
26   PUBLIC
27
28   !!----------------------------------------------------------------------
29   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
30   !! $Id$
31   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33
34   INTEGER ::   numnatp_ref = -1           !! Logical units for namelist medusa
35   INTEGER ::   numnatp_cfg = -1           !! Logical units for namelist medusa
36   INTEGER ::   numonp      = -1           !! Logical unit for namelist medusa output
37
38!!----------------------------------------------------------------------
39!! Biological parameters
40!!----------------------------------------------------------------------
41!!
42!! Primary production and chl related quantities
43   REAL(wp) ::  xxi       !:  conversion factor from gC to mmolN
44   REAL(wp) ::  xaln      !:  Chl-a specific initial slope of P-I curve for non-diatoms
45   REAL(wp) ::  xald      !:  Chl-a specific initial slope of P-I curve for diatoms
46   INTEGER  ::  jphy      !:  phytoplankton T-dependent growth switch
47   REAL(wp) ::  xvpn      !:  maximum growth rate for non-diatoms
48   REAL(wp) ::  xvpd      !:  maximum growth rate for diatoms
49   REAL(wp) ::  xthetam   !:  maximum Chl to C ratio for non-diatoms     
50   REAL(wp) ::  xthetamd  !:  maximum Chl to C ratio for diatoms   
51   REAL(wp) ::  xq10      !:  specific Q10 value (jphy==2)   
52!!
53!! Diatom silicon parameters
54   REAL(wp) ::  xsin0     !:  minimum diatom Si:N ratio
55   REAL(wp) ::  xnsi0     !:  minimum diatom N:Si ratio
56   REAL(wp) ::  xuif      !:  hypothetical growth ratio at infinite Si:N ratio
57!!
58!! Nutrient limitation
59   INTEGER  ::  jliebig   !:  Liebig nutrient uptake switch
60   REAL(wp) ::  xnln      !:  half-sat constant for DIN uptake by non-diatoms
61   REAL(wp) ::  xnld      !:  half-sat constant for DIN uptake by diatoms
62   REAL(wp) ::  xsld      !:  half-sat constant for Si uptake by diatoms
63   REAL(wp) ::  xfln      !:  half-sat constant for Fe uptake by non-diatoms
64   REAL(wp) ::  xfld      !:  half-sat constant for Fe uptake by diatoms 
65!!
66!! Grazing
67   REAL(wp) ::  xgmi      !:  microzoo maximum growth rate
68   REAL(wp) ::  xgme      !:  mesozoo maximum growth rate
69   REAL(wp) ::  xkmi      !:  microzoo grazing half-sat parameter
70   REAL(wp) ::  xkme      !:  mesozoo grazing half-sat parameter
71   REAL(wp) ::  xphi      !:  micro/mesozoo grazing inefficiency
72   REAL(wp) ::  xbetan    !:  micro/mesozoo N assimilation efficiency
73   REAL(wp) ::  xbetac    !:  micro/mesozoo C assimilation efficiency
74   REAL(wp) ::  xkc       !:  micro/mesozoo net C growth efficiency
75   REAL(wp) ::  xpmipn    !:  grazing preference of microzoo for non-diatoms
76   REAL(wp) ::  xpmid     !:  grazing preference of microzoo for diatoms
77   REAL(wp) ::  xpmepn    !:  grazing preference of mesozoo for non-diatoms
78   REAL(wp) ::  xpmepd    !:  grazing preference of mesozoo for diatoms
79   REAL(wp) ::  xpmezmi   !:  grazing preference of mesozoo for microzoo
80   REAL(wp) ::  xpmed     !:  grazing preference of mesozoo for detritus
81!!
82!! Metabolic losses
83   REAL(wp) ::  xmetapn   !:  non-diatom metabolic loss rate
84   REAL(wp) ::  xmetapd   !:  diatom     metabolic loss rate
85   REAL(wp) ::  xmetazmi  !:  microzoo   metabolic loss rate
86   REAL(wp) ::  xmetazme  !:  mesozoo    metabolic loss rate
87!!
88!! Mortality losses
89   INTEGER  ::  jmpn      !:  non-diatom mortality functional form
90   REAL(wp) ::  xmpn      !:  non-diatom mortality rate
91   REAL(wp) ::  xkphn     !:  non-diatom mortality half-sat constant
92   INTEGER  ::  jmpd      !:  diatom     mortality functional form
93   REAL(wp) ::  xmpd      !:  diatom     mortality rate
94   REAL(wp) ::  xkphd     !:  diatom     mortality half-sat constant
95   INTEGER  ::  jmzmi     !:  microzoo   mortality functional form
96   REAL(wp) ::  xmzmi     !:  microzoo   mortality rate
97   REAL(wp) ::  xkzmi     !:  microzoo   mortality half-sat constant
98   INTEGER  ::  jmzme     !:  mesozoo    mortality functional form
99   REAL(wp) ::  xmzme     !:  mesozoo    mortality rate
100   REAL(wp) ::  xkzme     !:  mesozoo    mortality half-sat constant
101!!
102!! Remineralisation
103   INTEGER  ::  jmd       !:  detritus T-dependent remineralisation switch
104   INTEGER  ::  jsfd      !:  accelerate seafloor detritus remin. switch
105   REAL(wp) ::  xmd       !:  detrital nitrogen remineralisation rate
106   REAL(wp) ::  xmdc      !:  detrital carbon remineralisation rate
107!!
108!! Stochiometric ratios
109   REAL(wp) ::  xthetapn  !:  non-diatom C:N ratio
110   REAL(wp) ::  xthetapd  !:  diatom C:N ratio
111   REAL(wp) ::  xthetazmi !:  microzoo C:N ratio
112   REAL(wp) ::  xthetazme !:  mesozoo C:N ratio
113   REAL(wp) ::  xthetad   !:  detritus C:N ratio
114   REAL(wp) ::  xrfn      !:  phytoplankton Fe:N ratio
115   REAL(wp) ::  xrsn      !:  diatom Si:N ratio (NOT USED HERE; RETAINED FOR LOBSTER)
116!!
117!! Iron parameters
118   INTEGER  ::  jiron     !:  iron scavenging submodel switch
119   REAL(wp) ::  xfe_mass  !:  iron atomic mass
120   REAL(wp) ::  xfe_sol   !:  aeolian iron solubility
121   REAL(wp) ::  xfe_sed   !:  sediment iron input
122   REAL(wp) ::  xLgT      !:  total ligand concentration (umol/m3)
123   REAL(wp) ::  xk_FeL    !:  dissociation constant for (Fe + L)
124   REAL(wp) ::  xk_sc_Fe  !:  scavenging rate of "free" iron
125!!
126!! Gravitational sinking     
127   REAL(wp) ::  vsed      !:  detritus gravitational sinking rate
128   REAL(wp) ::  xhr       !:  coefficient for Martin et al. (1987) remineralisation
129!!
130!! Fast-sinking detritus parameters
131   INTEGER  ::  jexport   !:  fast detritus remineralisation switch
132   INTEGER  ::  jfdfate   !:  fate of fast detritus at seafloor switch
133   INTEGER  ::  jrratio   !:  rain ratio switch
134   INTEGER  ::  jocalccd  !:  CCD switch
135   REAL(wp) ::  xridg_r0  !:  Ridgwell rain ratio coefficient
136   REAL(wp) ::  xfdfrac1  !:  fast-sinking fraction of diatom nat. mort. losses
137   REAL(wp) ::  xfdfrac2  !:  fast-sinking fraction of mesozooplankton mort. losses
138   REAL(wp) ::  xfdfrac3  !:  fast-sinking fraction of diatom silicon grazing losses
139   REAL(wp) ::  xcaco3a   !:  polar (high latitude) CaCO3 fraction
140   REAL(wp) ::  xcaco3b   !:  equatorial (low latitude) CaCO3 fraction
141   REAL(wp) ::  xmassc    !:  organic C mass:mole ratio, C106 H175 O40 N16 P1
142   REAL(wp) ::  xmassca   !:  calcium carbonate mass:mole ratio, CaCO3
143   REAL(wp) ::  xmasssi   !:  biogenic silicon mass:mole ratio, (H2SiO3)n
144   REAL(wp) ::  xprotca   !:  calcium carbonate protection ratio
145   REAL(wp) ::  xprotsi   !:  biogenic silicon protection ratio
146   REAL(wp) ::  xfastc    !:  organic C remineralisation length scale
147   REAL(wp) ::  xfastca   !:  calcium carbonate dissolution length scale
148   REAL(wp) ::  xfastsi   !:  biogenic silicon dissolution length scale
149!!
150!! Benthos parameters
151   INTEGER  ::  jorgben   !:  does   organic detritus go to the benthos?
152   INTEGER  ::  jinorgben !:  does inorganic detritus go to the benthos?
153!!
154   REAL(wp) ::  xsedn     !:  organic   nitrogen sediment remineralisation rate
155   REAL(wp) ::  xsedfe    !:  organic   iron     sediment remineralisation rate
156   REAL(wp) ::  xsedsi    !:  inorganic silicon  sediment dissolution      rate
157   REAL(wp) ::  xsedc     !:  organic   carbon   sediment remineralisation rate
158   REAL(wp) ::  xsedca    !:  inorganic carbon   sediment dissolution      rate
159   REAL(wp) ::  xburial   !:  burial rate of seafloor detritus
160!!
161!! River parameters
162   INTEGER  ::  jriver_n  !:  riverine nitrogen?   0 = no, 1 = conc, 2 = flux
163   INTEGER  ::  jriver_si !:  riverine silicon?    0 = no, 1 = conc, 2 = flux
164   INTEGER  ::  jriver_c  !:  riverine carbon?     0 = no, 1 = conc, 2 = flux
165   INTEGER  ::  jriver_alk!:  riverine alkalinity? 0 = no, 1 = conc, 2 = flux
166   INTEGER  ::  jriver_dep!:  depth river input added to?  1 = surface, >1 possible
167!!
168!! Miscellaneous
169   REAL(wp) ::  xsdiss    !:  diatom frustule dissolution rate
170!!
171!! Additional parameters
172   INTEGER  ::  jpkb      !:  vertical layer for diagnostic of the vertical flux
173!!
174!! UKESM diagnostics
175   INTEGER  ::  jdms         !: include DMS diagnostics ? Jpalm (27-08-2014)
176   INTEGER  ::  jdms_input   !: use instant (0) or diel-average (1) inputs (AXY, 08/07/2015)
177   INTEGER  ::  jdms_model   !: choice of DMS model passed to atmosphere
178!!                              1 = ANDR, 2 = SIMO, 3 = ARAN, 4 = HALL
179!!
180!!
181   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   remdmp   !: depth dependent damping coefficient of passive tracers
182!!
183!! AXY (27/07/10): add in indices for depth horizons (for sinking flux
184!!                 and seafloor iron inputs)
185   INTEGER  ::    i0100, i0150, i0200, i0500, i1000, i1100
186#if defined key_roam
187!!
188!! ROAM carbon, alkalinity and oxygen cycle parameters
189   REAL(wp) ::  xthetaphy    !:  oxygen evolution/consumption by phytoplankton
190   REAL(wp) ::  xthetazoo    !:  oxygen consumption by zooplankton
191   REAL(wp) ::  xthetanit    !:  oxygen consumption by nitrogen remineralisation
192   REAL(wp) ::  xthetarem    !:  oxygen consumption by carbon remineralisation
193   REAL(wp) ::  xo2min       !:  oxygen minimum concentration
194!!
195!! 3D fields of carbonate system parameters
196   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: f3_pH       !: 3D pH
197   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: f3_h2co3    !: 3D carbonic acid
198   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: f3_hco3     !: 3D bicarbonate
199   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: f3_co3      !: 3D carbonate
200   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: f3_omcal    !: 3D omega calcite
201   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: f3_omarg    !: 3D omega aragonite
202!!
203!! 2D fields of calcium carbonate compensation depth
204   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: f2_ccd_cal  !: 2D calcite CCD depth
205   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: f2_ccd_arg  !: 2D aragonite CCD depth
206!!
207!! 2D fields of organic and inorganic material sedimented on the seafloor
208   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_sed_n    !: 2D organic nitrogen   (before)
209   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_sed_n    !: 2D organic nitrogen   (now)
210   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_sed_n    !: 2D organic nitrogen   (after)
211   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_sed_fe   !: 2D organic iron       (before)
212   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_sed_fe   !: 2D organic iron       (now)
213   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_sed_fe   !: 2D organic iron       (after)
214   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_sed_si   !: 2D inorganic silicon  (before)
215   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_sed_si   !: 2D inorganic silicon  (now)
216   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_sed_si   !: 2D inorganic silicon  (after)
217   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_sed_c    !: 2D organic carbon     (before)
218   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_sed_c    !: 2D organic carbon     (now)
219   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_sed_c    !: 2D organic carbon     (after)
220   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_sed_ca   !: 2D inorganic carbon   (before)
221   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_sed_ca   !: 2D inorganic carbon   (now)
222   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_sed_ca   !: 2D inorganic carbon   (after)
223!!
224!! 2D fields of temporally averaged properties for DMS calculations (AXY, 07/07/15)
225   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_dms_chn  !: 2D avg CHN   (before)
226   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_dms_chn  !: 2D avg CHN   (now)
227   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_dms_chn  !: 2D avg CHN   (after)
228   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_dms_chd  !: 2D avg CHD   (before)
229   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_dms_chd  !: 2D avg CHD   (now)
230   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_dms_chd  !: 2D avg CHD   (after)
231   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_dms_mld  !: 2D avg MLD   (before)
232   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_dms_mld  !: 2D avg MLD   (now)
233   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_dms_mld  !: 2D avg MLD   (after)
234   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_dms_qsr  !: 2D avg QSR   (before)
235   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_dms_qsr  !: 2D avg QSR   (now)
236   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_dms_qsr  !: 2D avg QSR   (after)
237   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_dms_din  !: 2D avg DIN   (before)
238   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_dms_din  !: 2D avg DIN   (now)
239   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_dms_din  !: 2D avg DIN   (after)
240!!
241!! 2D fields needing to be knows at first tstp for coupling with atm - UKESM (Jpalm,14-06-2016)
242   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_co2_flx  !: 2D avg fx co2 (before)
243   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_co2_flx  !: 2D avg fx co2 (now)
244   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_co2_flx  !: 2D avg fx co2 (after)
245   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zb_dms_srf  !: 2D avg fx co2 (before)
246   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: zn_dms_srf  !: 2D avg fx co2 (now)
247   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: za_dms_srf  !: 2D avg fx co2 (after)
248
249#endif
250
251!!----------------------------------------------------------------------
252!! CCD parameter
253!!----------------------------------------------------------------------
254!!
255   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ocal_ccd  !: CCD depth
256
257!!----------------------------------------------------------------------
258!! Dust parameters
259!!----------------------------------------------------------------------
260!!
261   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   dust      !: dust parameter 1
262   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   zirondep  !! Fe deposition
263
264!!----------------------------------------------------------------------
265!! River parameters
266!!----------------------------------------------------------------------
267!!
268   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   riv_n      !: riverine N
269   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   riv_si     !: riverine Si
270   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   riv_c      !: riverine C
271   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   riv_alk    !: riverine alkalinity
272   !! AXY (19/07/12): add this to permit river fluxes to be added below top box
273   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   friver_dep !: where river fluxes added
274
275!!----------------------------------------------------------------------
276!! Optical parameters
277!!----------------------------------------------------------------------
278!!
279   REAL(wp) ::   xkr0       !: water coefficient absorption in red      (NAMELIST)
280   REAL(wp) ::   xkg0       !: water coefficient absorption in green    (NAMELIST)
281   REAL(wp) ::   xkrp       !: pigment coefficient absorption in red    (NAMELIST)
282   REAL(wp) ::   xkgp       !: pigment coefficient absorption in green  (NAMELIST)
283   REAL(wp) ::   xlr        !: exposant for pigment absorption in red   (NAMELIST)
284   REAL(wp) ::   xlg        !: exposant for pigment absorption in green (NAMELIST)
285   REAL(wp) ::   rpig       !: chla/chla+phea ratio                     (NAMELIST)
286                                                       
287   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   neln    !: number of levels in the euphotic layer
288   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   xze     !: euphotic layer depth
289   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xpar    !: par (photosynthetic available radiation)
290
291!!----------------------------------------------------------------------
292!! Sediment parameters                               
293!!
294!! AXY (16/01/12): these parameters were originally part of the pre-
295!!                 cursor model on which MEDUSA's code was grounded;
296!!                 they do not relate to the sediment/benthos submodel
297!!                 added as part of the ROAM project; they have only
298!!                 been retained because they are distributed through
299!!                 MEDUSA and require a proper clean-up to purge
300!!----------------------------------------------------------------------
301!!
302   REAL(wp) ::   sedlam       !: time coefficient of POC remineralization in sediments
303   REAL(wp) ::   sedlostpoc   !: ???
304   REAL(wp) ::   areacot      !: ???
305                                                       
306   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: dminl       !: fraction of sinking POC released in sediments
307   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: dmin3       !: fraction of sinking POC released at each level
308                                                       
309   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: sedpocb     !: mass of POC in sediments
310   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: sedpocn     !: mass of POC in sediments
311   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: sedpoca     !: mass of POC in sediments
312                                                       
313   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: fbodf       !: rapid sinking particles
314   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: fbods       !: rapid sinking particles
315   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: fbodn       !: rapid sinking particles
316                                                       
317   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ffln        !:
318   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: fflf        !:
319   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ffls        !:
320
321   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   :: cmask       !: ???
322
323   !!----------------------------------------------------------------------
324   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
325   !! $Id$
326   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
327   !!----------------------------------------------------------------------
328CONTAINS
329
330   INTEGER FUNCTION sms_medusa_alloc()
331      !!----------------------------------------------------------------------
332      !!        *** ROUTINE sms_medusa_alloc ***
333      !!----------------------------------------------------------------------
334      USE lib_mpp , ONLY: ctl_warn
335      INTEGER ::   ierr(8)        ! Local variables
336      !!----------------------------------------------------------------------
337      ierr(:) = 0
338      !
339#if defined key_medusa
340      !* depth-dependent damping coefficient
341      ALLOCATE( remdmp(jpk,jp_medusa),                           STAT=ierr(1) )
342# if defined key_roam
343      !* 2D and 3D fields of carbonate system parameters
344      ALLOCATE( f2_ccd_cal(jpi,jpj)  , f2_ccd_arg(jpi,jpj)  ,       &
345         &      f3_pH(jpi,jpj,jpk)   , f3_h2co3(jpi,jpj,jpk),       &
346         &      f3_hco3(jpi,jpj,jpk) , f3_co3(jpi,jpj,jpk)  ,       &
347         &      f3_omcal(jpi,jpj,jpk), f3_omarg(jpi,jpj,jpk),    STAT=ierr(2) )
348      !* 2D fields of organic and inorganic material sedimented on the seafloor
349      ALLOCATE( zb_sed_n(jpi,jpj)    , zn_sed_n(jpi,jpj)    ,       &
350         &      za_sed_n(jpi,jpj)    ,                              &
351         &      zb_sed_fe(jpi,jpj)   , zn_sed_fe(jpi,jpj)   ,       &
352         &      za_sed_fe(jpi,jpj)   ,                              &
353         &      zb_sed_si(jpi,jpj)   , zn_sed_si(jpi,jpj)   ,       &
354         &      za_sed_si(jpi,jpj)   ,                              &
355         &      zb_sed_c(jpi,jpj)    , zn_sed_c(jpi,jpj)    ,       &
356         &      za_sed_c(jpi,jpj)    ,                              &
357         &      zb_sed_ca(jpi,jpj)   , zn_sed_ca(jpi,jpj)   ,       &
358         &      za_sed_ca(jpi,jpj)   ,                           STAT=ierr(3) )
359      !* 2D fields of temporally averaged properties for DMS calculations (AXY, 07/07/15)
360      ALLOCATE( zb_dms_chn(jpi,jpj)  , zn_dms_chn(jpi,jpj)  ,       &
361         &      za_dms_chn(jpi,jpj)  ,                              &
362         &      zb_dms_chd(jpi,jpj)  , zn_dms_chd(jpi,jpj)  ,       &       
363         &      za_dms_chd(jpi,jpj)  ,                              &
364         &      zb_dms_mld(jpi,jpj)  , zn_dms_mld(jpi,jpj)  ,       &       
365         &      za_dms_mld(jpi,jpj)  ,                              &
366         &      zb_dms_qsr(jpi,jpj)  , zn_dms_qsr(jpi,jpj)  ,       &       
367         &      za_dms_qsr(jpi,jpj)  ,                              &
368         &      zb_dms_din(jpi,jpj)  , zn_dms_din(jpi,jpj)  ,       &       
369         &      za_dms_din(jpi,jpj)  ,                           STAT=ierr(4) )
370      !* 2D fields needing to be knows at first tstp for coupling with atm -
371      !UKESM (Jpalm,14-06-2016)
372      ALLOCATE( zb_co2_flx(jpi,jpj)  , zn_co2_flx(jpi,jpj)  ,       &
373         &      za_co2_flx(jpi,jpj)  ,                              &
374         &      zb_dms_srf(jpi,jpj)  , zn_dms_srf(jpi,jpj)  ,       &           
375         &      za_dms_srf(jpi,jpj)  ,                           STAT=ierr(5) )
376# endif
377      !* 2D fields of miscellaneous parameters
378      ALLOCATE( ocal_ccd(jpi,jpj)    , dust(jpi,jpj)        ,       &
379         &      zirondep(jpi,jpj)                           ,       &
380         &      riv_n(jpi,jpj)                              ,       &
381         &      riv_si(jpi,jpj)      , riv_c(jpi,jpj)       ,       &
382         &      riv_alk(jpi,jpj)     , friver_dep(jpk,jpk)  ,    STAT=ierr(6) )
383      !* 2D and 3D fields of light parameters
384      ALLOCATE( neln(jpi,jpj)        , xze(jpi,jpj)         ,       &
385         &      xpar(jpi,jpj,jpk)    ,                           STAT=ierr(7) )
386      !* 2D and 3D fields of sediment-associated parameters
387      ALLOCATE( dminl(jpi,jpj)       , dmin3(jpi,jpj,jpk)   ,       &
388         &      sedpocb(jpi,jpj)     , sedpocn(jpi,jpj)     ,       &
389         &      sedpoca(jpi,jpj)     , fbodn(jpi,jpj)       ,       &
390         &      fbodf(jpi,jpj)       , fbods(jpi,jpj)       ,       &
391         &      ffln(jpi,jpj,jpk)    , fflf(jpi,jpj,jpk)    ,       &
392         &      ffls(jpi,jpj,jpk)    , cmask(jpi,jpj)       ,    STAT=ierr(8) ) 
393#endif
394      !
395      sms_medusa_alloc = MAXVAL( ierr )
396      !
397      IF( sms_medusa_alloc /= 0 )   CALL ctl_warn('sms_medusa_alloc: failed to allocate arrays')
398      !
399   END FUNCTION sms_medusa_alloc
400
401#else
402   !!----------------------------------------------------------------------
403   !!  Empty module :                                     NO MEDUSA model
404   !!----------------------------------------------------------------------
405#endif
406
407   !!======================================================================
408END MODULE sms_medusa
Note: See TracBrowser for help on using the repository browser.