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

source: branches/UKMO/dev_r5107_kara_mld/NEMOGCM/NEMO/TOP_SRC/PISCES/sms_pisces.F90 @ 5244

Last change on this file since 5244 was 5244, checked in by davestorkey, 9 years ago

UKMO Kara MLD branch: remove svn keyword property and clear keywords.

File size: 9.1 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   REAL(wp) ::   ryyss             !: number of seconds per year
39   REAL(wp) ::   r1_ryyss          !: inverse number of seconds per year
40
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) ::   xkmort            !: ???
52   REAL(wp) ::   ferat3            !: ???
53
54   !!*  diagnostic parameters
55   REAL(wp) ::  tpp                !: total primary production
56   REAL(wp) ::  t_oce_co2_exp      !: total carbon export
57   REAL(wp) ::  t_oce_co2_flx      !: Total ocean carbon flux
58   REAL(wp) ::  t_oce_co2_flx_cum  !: Cumulative Total ocean carbon flux
59   REAL(wp) ::  t_atm_co2_flx      !: global mean of atmospheric pco2
60
61   !!* restoring
62   LOGICAL  ::  ln_pisdmp          !: restoring or not of nutrients to a mean value
63   INTEGER  ::  nn_pisdmp          !: frequency of relaxation or not of nutrients to a mean value
64
65   !!* Mass conservation
66   LOGICAL  ::  ln_check_mass      !: Flag to check mass conservation
67
68   !!*  Biological fluxes for primary production
69   REAL(wp), ALLOCATABLE, SAVE,   DIMENSION(:,:)  ::   xksimax    !: ???
70   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanono3   !: ???
71   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatno3   !: ???
72   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanonh4   !: ???
73   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatnh4   !: ???
74   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanopo4   !: ???
75   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatpo4   !: ???
76   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimphy    !: ???
77   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdia    !: ???
78   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concdfe    !: ???
79   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concnfe    !: ???
80   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimnfe    !: ???
81   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdfe    !: ???
82   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimsi     !: ???
83   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   biron      !: bioavailable fraction of iron
84
85
86   !!*  SMS for the organic matter
87   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xfracal    !: ??
88   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   nitrfac    !: ??
89   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xlimbac    !: ??
90   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xlimbacl   !: ??
91   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xdiss      !: ??
92   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prodcal    !: Calcite production
93
94   !!* Variable for chemistry of the CO2 cycle
95   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   akb3       !: ???
96   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ak13       !: ???
97   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ak23       !: ???
98   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   aksp       !: ???
99   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   akw3       !: ???
100   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   borat      !: ???
101   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hi         !: ???
102   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   excess     !: ???
103
104   !!* Temperature dependancy of SMS terms
105   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tgfunc    !: Temp. dependancy of various biological rates
106   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tgfunc2   !: Temp. dependancy of mesozooplankton rates
107
108   !!* Array used to indicate negative tracer values
109   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xnegtr     !: ???
110
111#if defined key_kriest
112   !!*  Kriest parameter for aggregation
113   REAL(wp) ::   xkr_eta                            !: Sinking  exponent
114   REAL(wp) ::   xkr_zeta                           !:  N content exponent
115   REAL(wp) ::   xkr_ncontent                       !:  N content factor   
116   REAL(wp) ::   xkr_massp                          !:
117   REAL(wp) ::   xkr_mass_min, xkr_mass_max         !:  Minimum, Maximum mass for Aggregates
118#endif
119
120#endif
121   !!----------------------------------------------------------------------
122   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
123   !! $Id$
124   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
125   !!----------------------------------------------------------------------
126CONTAINS
127
128   INTEGER FUNCTION sms_pisces_alloc()
129      !!----------------------------------------------------------------------
130      !!        *** ROUTINE sms_pisces_alloc ***
131      !!----------------------------------------------------------------------
132      USE lib_mpp , ONLY: ctl_warn
133      INTEGER ::   ierr(6)        ! Local variables
134      !!----------------------------------------------------------------------
135      ierr(:) = 0
136      !*  Biological fluxes for light : shared variables for pisces & lobster
137      ALLOCATE( etot(jpi,jpj,jpk), neln(jpi,jpj), heup(jpi,jpj), xksi(jpi,jpj), STAT=ierr(1) )
138      !
139#if defined key_pisces
140      !*  Biological fluxes for primary production
141      ALLOCATE( xksimax(jpi,jpj)     , biron   (jpi,jpj,jpk),       &
142         &      xnanono3(jpi,jpj,jpk), xdiatno3(jpi,jpj,jpk),       &
143         &      xnanonh4(jpi,jpj,jpk), xdiatnh4(jpi,jpj,jpk),       &
144         &      xnanopo4(jpi,jpj,jpk), xdiatpo4(jpi,jpj,jpk),       &
145         &      xlimphy (jpi,jpj,jpk), xlimdia (jpi,jpj,jpk),       &
146         &      xlimnfe (jpi,jpj,jpk), xlimdfe (jpi,jpj,jpk),       &
147         &      xlimsi  (jpi,jpj,jpk), concdfe (jpi,jpj,jpk),       &
148         &      concnfe (jpi,jpj,jpk),                           STAT=ierr(2) ) 
149         !
150      !*  SMS for the organic matter
151      ALLOCATE( xfracal (jpi,jpj,jpk), nitrfac(jpi,jpj,jpk),       &
152         &      xlimbac (jpi,jpj,jpk), xdiss  (jpi,jpj,jpk),       & 
153         &      xlimbacl(jpi,jpj,jpk), prodcal(jpi,jpj,jpk),     STAT=ierr(3) )
154
155      !* Variable for chemistry of the CO2 cycle
156      ALLOCATE( akb3(jpi,jpj,jpk)    , ak13  (jpi,jpj,jpk) ,       &
157         &      ak23(jpi,jpj,jpk)    , aksp  (jpi,jpj,jpk) ,       &
158         &      akw3(jpi,jpj,jpk)    , borat (jpi,jpj,jpk) ,       &
159         &      hi  (jpi,jpj,jpk)    , excess(jpi,jpj,jpk) ,     STAT=ierr(4) )
160         !
161      !* Temperature dependancy of SMS terms
162      ALLOCATE( tgfunc(jpi,jpj,jpk)  , tgfunc2(jpi,jpj,jpk) ,    STAT=ierr(5) )
163         !
164      !* Array used to indicate negative tracer values 
165      ALLOCATE( xnegtr(jpi,jpj,jpk)  ,                           STAT=ierr(6) )
166#endif
167      !
168      sms_pisces_alloc = MAXVAL( ierr )
169      !
170      IF( sms_pisces_alloc /= 0 )   CALL ctl_warn('sms_pisces_alloc: failed to allocate arrays') 
171      !
172   END FUNCTION sms_pisces_alloc
173
174#else
175   !!----------------------------------------------------------------------   
176   !!  Empty module :                                     NO PISCES model
177   !!----------------------------------------------------------------------
178#endif
179   
180   !!======================================================================   
181END MODULE sms_pisces   
Note: See TracBrowser for help on using the repository browser.