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

source: branches/2012/dev_LOCEAN_UKMO_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/sms_pisces.F90 @ 3653

Last change on this file since 3653 was 3653, checked in by cetlod, 11 years ago

commit the changes from LOCEAN & UKMO merge, see ticket #1021

  • Property svn:keywords set to Id
File size: 8.4 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
20
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 
30   !!*  Time variables
31   INTEGER  ::   nrdttrc           !: ???
32   INTEGER  ::   ndayflxtr         !: ???
33   REAL(wp) ::   rfact , rfactr    !: ???
34   REAL(wp) ::   rfact2, rfact2r   !: ???
35   REAL(wp) ::   xstep             !: Time step duration for biology
36
37   !!*  Biological parameters
38   INTEGER  ::   niter1max, niter2max   !: Maximum number of iterations for sinking
39   REAL(wp) ::   rno3              !: ???
40   REAL(wp) ::   o2ut              !: ???
41   REAL(wp) ::   po4r              !: ???
42   REAL(wp) ::   rdenit            !: ???
43   REAL(wp) ::   rdenita           !: ???
44   REAL(wp) ::   o2nit             !: ???
45   REAL(wp) ::   wsbio, wsbio2     !: ???
46   REAL(wp) ::   xkmort            !: ???
47   REAL(wp) ::   ferat3            !: ???
48
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
54
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
62
63   !!*  Biological fluxes for primary production
64   REAL(wp), ALLOCATABLE, SAVE,   DIMENSION(:,:)  ::   xksimax    !: ???
65   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanono3   !: ???
66   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatno3   !: ???
67   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanonh4   !: ???
68   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatnh4   !: ???
69   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimphy    !: ???
70   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdia    !: ???
71   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concdfe    !: ???
72   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concnfe    !: ???
73   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimnfe    !: ???
74   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdfe    !: ???
75   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimsi     !: ???
76   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   biron      !: bioavailable fraction of iron
77
78
79   !!*  SMS for the organic matter
80   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xfracal    !: ??
81   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   nitrfac    !: ??
82   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xlimbac    !: ??
83   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xlimbacl   !: ??
84   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xdiss      !: ??
85   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   prodcal    !: Calcite production
86
87   !!* Variable for chemistry of the CO2 cycle
88   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   akb3       !: ???
89   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ak13       !: ???
90   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ak23       !: ???
91   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   aksp       !: ???
92   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   akw3       !: ???
93   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   borat      !: ???
94   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hi         !: ???
95   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   excess     !: ???
96
97   !!* Temperature dependancy of SMS terms
98   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tgfunc    !: Temp. dependancy of various biological rates
99   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tgfunc2   !: Temp. dependancy of mesozooplankton rates
100
101   !!* Array used to indicate negative tracer values
102   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xnegtr     !: ???
103
104#if defined key_kriest
105   !!*  Kriest parameter for aggregation
106   REAL(wp) ::   xkr_eta                            !: ???
107   REAL(wp) ::   xkr_zeta                           !: ???
108   REAL(wp) ::   xkr_massp                          !: ???
109   REAL(wp) ::   xkr_mass_min, xkr_mass_max         !: ???
110#endif
111
112#endif
113   !!----------------------------------------------------------------------
114   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
115   !! $Id$
116   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
117   !!----------------------------------------------------------------------
118CONTAINS
119
120   INTEGER FUNCTION sms_pisces_alloc()
121      !!----------------------------------------------------------------------
122      !!        *** ROUTINE sms_pisces_alloc ***
123      !!----------------------------------------------------------------------
124      USE lib_mpp , ONLY: ctl_warn
125      INTEGER ::   ierr(6)        ! Local variables
126      !!----------------------------------------------------------------------
127      ierr(:) = 0
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) )
130      !
131#if defined key_pisces
132      !*  Biological fluxes for primary production
133      ALLOCATE( xksimax(jpi,jpj)     , biron   (jpi,jpj,jpk),       &
134         &      xnanono3(jpi,jpj,jpk), xdiatno3(jpi,jpj,jpk),       &
135         &      xnanonh4(jpi,jpj,jpk), xdiatnh4(jpi,jpj,jpk),       &
136         &      xlimphy (jpi,jpj,jpk), xlimdia (jpi,jpj,jpk),       &
137         &      xlimnfe (jpi,jpj,jpk), xlimdfe (jpi,jpj,jpk),       &
138         &      xlimsi  (jpi,jpj,jpk), concdfe (jpi,jpj,jpk),       &
139         &      concnfe (jpi,jpj,jpk),                           STAT=ierr(2) ) 
140         !
141      !*  SMS for the organic matter
142      ALLOCATE( xfracal (jpi,jpj,jpk), nitrfac(jpi,jpj,jpk),       &
143         &      xlimbac (jpi,jpj,jpk), xdiss  (jpi,jpj,jpk),       & 
144         &      xlimbacl(jpi,jpj,jpk), prodcal(jpi,jpj,jpk),     STAT=ierr(3) )
145
146      !* Variable for chemistry of the CO2 cycle
147      ALLOCATE( akb3(jpi,jpj,jpk)    , ak13  (jpi,jpj,jpk) ,       &
148         &      ak23(jpi,jpj,jpk)    , aksp  (jpi,jpj,jpk) ,       &
149         &      akw3(jpi,jpj,jpk)    , borat (jpi,jpj,jpk) ,       &
150         &      hi  (jpi,jpj,jpk)    , excess(jpi,jpj,jpk) ,     STAT=ierr(4) )
151         !
152      !* Temperature dependancy of SMS terms
153      ALLOCATE( tgfunc(jpi,jpj,jpk)  , tgfunc2(jpi,jpj,jpk) ,    STAT=ierr(5) )
154         !
155      !* Array used to indicate negative tracer values 
156      ALLOCATE( xnegtr(jpi,jpj,jpk)  ,                           STAT=ierr(6) )
157#endif
158      !
159      sms_pisces_alloc = MAXVAL( ierr )
160      !
161      IF( sms_pisces_alloc /= 0 )   CALL ctl_warn('sms_pisces_alloc: failed to allocate arrays') 
162      !
163   END FUNCTION sms_pisces_alloc
164
165#else
166   !!----------------------------------------------------------------------   
167   !!  Empty module :                                     NO PISCES model
168   !!----------------------------------------------------------------------
169#endif
170   
171   !!======================================================================   
172END MODULE sms_pisces   
Note: See TracBrowser for help on using the repository browser.