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 trunk/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/sms_pisces.F90 @ 4528

Last change on this file since 4528 was 4148, checked in by cetlod, 10 years ago

merge in trunk changes between r3853 and r3940 and commit the changes, see ticket #1169

  • Property svn:keywords set to Id
File size: 8.7 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   !!----------------------------------------------------------------------
9#if defined key_pisces || defined key_pisces_reduced 
10   !!----------------------------------------------------------------------
11   !!   'key_pisces'                                         PISCES model
12   !!----------------------------------------------------------------------
13   USE par_oce
14   USE par_trc
15
16   IMPLICIT NONE
17   PUBLIC
18
19   INTEGER ::   numnatp_ref = -1           !! Logical units for namelist pisces
20   INTEGER ::   numnatp_cfg = -1           !! Logical units for namelist pisces
21   INTEGER ::   numonp      = -1           !! Logical unit for namelist pisces output
22
23   !!*  Biological fluxes for light : variables shared by pisces & lobster
24   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  neln  !: number of T-levels + 1 in the euphotic layer
25   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  heup  !: euphotic layer depth
26   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  etot  !: par (photosynthetic available radiation)
27   !
28   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  xksi  !:  LOBSTER : zooplakton closure
29   !                                                       !:  PISCES  : silicon dependant half saturation
30
31#if defined key_pisces 
32   !!*  Time variables
33   INTEGER  ::   nrdttrc           !: ???
34   INTEGER  ::   ndayflxtr         !: ???
35   REAL(wp) ::   rfact , rfactr    !: ???
36   REAL(wp) ::   rfact2, rfact2r   !: ???
37   REAL(wp) ::   xstep             !: Time step duration for biology
38
39   !!*  Biological parameters
40   INTEGER  ::   niter1max, niter2max   !: Maximum number of iterations for sinking
41   REAL(wp) ::   rno3              !: ???
42   REAL(wp) ::   o2ut              !: ???
43   REAL(wp) ::   po4r              !: ???
44   REAL(wp) ::   rdenit            !: ???
45   REAL(wp) ::   rdenita           !: ???
46   REAL(wp) ::   o2nit             !: ???
47   REAL(wp) ::   wsbio, wsbio2     !: ???
48   REAL(wp) ::   xkmort            !: ???
49   REAL(wp) ::   ferat3            !: ???
50
51   !!*  diagnostic parameters
52   REAL(wp) ::  tpp                !: total primary production
53   REAL(wp) ::  t_oce_co2_exp      !: total carbon export
54   REAL(wp) ::  t_oce_co2_flx      !: Total ocean carbon flux
55   REAL(wp) ::  t_atm_co2_flx      !: global mean of atmospheric pco2
56
57   !!* restoring
58   LOGICAL  ::  ln_pisdmp          !: restoring or not of nutrients to a mean value
59   INTEGER  ::  nn_pisdmp          !: frequency of relaxation or not of nutrients to a mean value
60
61   !!* Mass conservation
62   LOGICAL  ::  ln_check_mass      !: Flag to check mass conservation
63
64   !!*  Biological fluxes for primary production
65   REAL(wp), ALLOCATABLE, SAVE,   DIMENSION(:,:)  ::   xksimax    !: ???
66   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanono3   !: ???
67   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatno3   !: ???
68   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanonh4   !: ???
69   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatnh4   !: ???
70   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimphy    !: ???
71   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdia    !: ???
72   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concdfe    !: ???
73   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concnfe    !: ???
74   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimnfe    !: ???
75   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdfe    !: ???
76   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimsi     !: ???
77   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   biron      !: bioavailable fraction of iron
78
79
80   !!*  SMS for the organic matter
81   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xfracal    !: ??
82   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   nitrfac    !: ??
83   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xlimbac    !: ??
84   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xlimbacl   !: ??
85   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xdiss      !: ??
86   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prodcal    !: Calcite production
87
88   !!* Variable for chemistry of the CO2 cycle
89   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   akb3       !: ???
90   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ak13       !: ???
91   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ak23       !: ???
92   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   aksp       !: ???
93   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   akw3       !: ???
94   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   borat      !: ???
95   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hi         !: ???
96   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   excess     !: ???
97
98   !!* Temperature dependancy of SMS terms
99   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tgfunc    !: Temp. dependancy of various biological rates
100   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tgfunc2   !: Temp. dependancy of mesozooplankton rates
101
102   !!* Array used to indicate negative tracer values
103   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xnegtr     !: ???
104
105#if defined key_kriest
106   !!*  Kriest parameter for aggregation
107   REAL(wp) ::   xkr_eta                            !: Sinking  exponent
108   REAL(wp) ::   xkr_zeta                           !:  N content exponent
109   REAL(wp) ::   xkr_ncontent                       !:  N content factor   
110   REAL(wp) ::   xkr_massp                          !:
111   REAL(wp) ::   xkr_mass_min, xkr_mass_max         !:  Minimum, Maximum mass for Aggregates
112#endif
113
114#endif
115   !!----------------------------------------------------------------------
116   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
117   !! $Id$
118   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
119   !!----------------------------------------------------------------------
120CONTAINS
121
122   INTEGER FUNCTION sms_pisces_alloc()
123      !!----------------------------------------------------------------------
124      !!        *** ROUTINE sms_pisces_alloc ***
125      !!----------------------------------------------------------------------
126      USE lib_mpp , ONLY: ctl_warn
127      INTEGER ::   ierr(6)        ! Local variables
128      !!----------------------------------------------------------------------
129      ierr(:) = 0
130      !*  Biological fluxes for light : shared variables for pisces & lobster
131      ALLOCATE( etot(jpi,jpj,jpk), neln(jpi,jpj), heup(jpi,jpj), xksi(jpi,jpj), STAT=ierr(1) )
132      !
133#if defined key_pisces
134      !*  Biological fluxes for primary production
135      ALLOCATE( xksimax(jpi,jpj)     , biron   (jpi,jpj,jpk),       &
136         &      xnanono3(jpi,jpj,jpk), xdiatno3(jpi,jpj,jpk),       &
137         &      xnanonh4(jpi,jpj,jpk), xdiatnh4(jpi,jpj,jpk),       &
138         &      xlimphy (jpi,jpj,jpk), xlimdia (jpi,jpj,jpk),       &
139         &      xlimnfe (jpi,jpj,jpk), xlimdfe (jpi,jpj,jpk),       &
140         &      xlimsi  (jpi,jpj,jpk), concdfe (jpi,jpj,jpk),       &
141         &      concnfe (jpi,jpj,jpk),                           STAT=ierr(2) ) 
142         !
143      !*  SMS for the organic matter
144      ALLOCATE( xfracal (jpi,jpj,jpk), nitrfac(jpi,jpj,jpk),       &
145         &      xlimbac (jpi,jpj,jpk), xdiss  (jpi,jpj,jpk),       & 
146         &      xlimbacl(jpi,jpj,jpk), prodcal(jpi,jpj,jpk),     STAT=ierr(3) )
147
148      !* Variable for chemistry of the CO2 cycle
149      ALLOCATE( akb3(jpi,jpj,jpk)    , ak13  (jpi,jpj,jpk) ,       &
150         &      ak23(jpi,jpj,jpk)    , aksp  (jpi,jpj,jpk) ,       &
151         &      akw3(jpi,jpj,jpk)    , borat (jpi,jpj,jpk) ,       &
152         &      hi  (jpi,jpj,jpk)    , excess(jpi,jpj,jpk) ,     STAT=ierr(4) )
153         !
154      !* Temperature dependancy of SMS terms
155      ALLOCATE( tgfunc(jpi,jpj,jpk)  , tgfunc2(jpi,jpj,jpk) ,    STAT=ierr(5) )
156         !
157      !* Array used to indicate negative tracer values 
158      ALLOCATE( xnegtr(jpi,jpj,jpk)  ,                           STAT=ierr(6) )
159#endif
160      !
161      sms_pisces_alloc = MAXVAL( ierr )
162      !
163      IF( sms_pisces_alloc /= 0 )   CALL ctl_warn('sms_pisces_alloc: failed to allocate arrays') 
164      !
165   END FUNCTION sms_pisces_alloc
166
167#else
168   !!----------------------------------------------------------------------   
169   !!  Empty module :                                     NO PISCES model
170   !!----------------------------------------------------------------------
171#endif
172   
173   !!======================================================================   
174END MODULE sms_pisces   
Note: See TracBrowser for help on using the repository browser.