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.
trcini_pisces.F90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

  • Property svn:keywords set to Id
File size: 5.9 KB
Line 
1MODULE trcini_pisces
2   !!======================================================================
3   !!                         ***  MODULE trcini_pisces  ***
4   !! TOP :   initialisation of the PISCES biochemical model
5   !!======================================================================
6   !! History :    -   !  1988-07  (E. Maier-Reiner) Original code
7   !!              -   !  1999-10  (O. Aumont, C. Le Quere)
8   !!              -   !  2002     (O. Aumont)  PISCES
9   !!             1.0  !  2005-03  (O. Aumont, A. El Moussaoui) F90
10   !!             2.0  !  2007-12  (C. Ethe, G. Madec) from trcini.pisces.h90
11   !!----------------------------------------------------------------------
12#if defined key_pisces
13   !!----------------------------------------------------------------------
14   !!   'key_pisces'                                       PISCES bio-model
15   !!----------------------------------------------------------------------
16   !! trc_ini_pisces   : PISCES biochemical model initialisation
17   !!----------------------------------------------------------------------
18   USE par_trc         ! TOP parameters
19   USE sms_pisces      ! Source Minus Sink variables
20   USE trc
21   USE oce_trc         ! ocean variables
22   USE p4zche 
23   USE lib_mpp
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   trc_ini_pisces   ! called by trcini.F90 module
29
30   !! * Module variables
31   REAL(wp) :: &
32      sco2   =  2.312e-3         , &
33      alka0  =  2.423e-3         , &
34      oxyg0  =  177.6e-6         , &
35      po4    =  2.174e-6         , &
36      bioma0 =  1.000e-8         , &
37      silic1 =  91.65e-6         , &
38      no3    =  31.04e-6 * 7.6
39
40#  include "top_substitute.h90"
41   !!----------------------------------------------------------------------
42   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
43   !! $Id$
44   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
46
47CONTAINS
48
49   SUBROUTINE trc_ini_pisces
50      !!----------------------------------------------------------------------
51      !!                   ***  ROUTINE trc_ini_pisces ***
52      !!
53      !! ** Purpose :   Initialisation of the PISCES biochemical model
54      !!----------------------------------------------------------------------
55
56
57      !  Control consitency
58      CALL trc_ctl_pisces
59
60
61      IF(lwp) WRITE(numout,*)
62      IF(lwp) WRITE(numout,*) ' trc_ini_pisces :   PISCES biochemical model initialisation'
63      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
64
65      !                                            ! Time-step
66      rfact   = rdttra(1) * float(nn_dttrc)          ! ---------
67      rfactr  = 1. / rfact
68      rfact2  = rfact / float(nrdttrc)
69      rfact2r = 1. / rfact2
70
71      IF(lwp) WRITE(numout,*) '    Tracer  time step    rfact  = ', rfact, ' rdt = ', rdt
72      IF(lwp) write(numout,*) '    Biology time step    rfact2 = ', rfact2
73
74
75
76      ! Set biological ratios
77      ! ---------------------
78      rno3   = (16.+2.) / 122.
79      po4r   =   1.e0   / 122.
80      o2nit  =  32.     / 122.
81      rdenit =  97.6    /  16.
82      o2ut   = 140.     / 122.
83
84      CALL p4z_che        ! initialize the chemical constants
85
86      ndayflxtr = 0      !  Initialize a counter for the computation of chemistry
87
88      ! Initialization of tracer concentration in case of  no restart
89      !--------------------------------------------------------------
90      IF( .NOT. ln_rsttr ) THEN 
91         
92         trn(:,:,:,jpdic) = sco2
93         trn(:,:,:,jpdoc) = bioma0
94         trn(:,:,:,jptal) = alka0
95         trn(:,:,:,jpoxy) = oxyg0
96         trn(:,:,:,jpcal) = bioma0
97         trn(:,:,:,jppo4) = po4 / po4r
98         trn(:,:,:,jppoc) = bioma0
99#  if ! defined key_kriest
100         trn(:,:,:,jpgoc) = bioma0
101         trn(:,:,:,jpbfe) = bioma0 * 5.e-6
102#  else
103         trn(:,:,:,jpnum) = bioma0 / ( 6. * xkr_massp )
104#  endif
105         trn(:,:,:,jpsil) = silic1
106         trn(:,:,:,jpbsi) = bioma0 * 0.15
107         trn(:,:,:,jpdsi) = bioma0 * 5.e-6
108         trn(:,:,:,jpphy) = bioma0
109         trn(:,:,:,jpdia) = bioma0
110         trn(:,:,:,jpzoo) = bioma0
111         trn(:,:,:,jpmes) = bioma0
112         trn(:,:,:,jpfer) = 0.6E-9
113         trn(:,:,:,jpsfe) = bioma0 * 5.e-6
114         trn(:,:,:,jpdfe) = bioma0 * 5.e-6
115         trn(:,:,:,jpnfe) = bioma0 * 5.e-6
116         trn(:,:,:,jpnch) = bioma0 * 12. / 55.
117         trn(:,:,:,jpdch) = bioma0 * 12. / 55.
118         trn(:,:,:,jpno3) = no3
119         trn(:,:,:,jpnh4) = bioma0
120
121         ! initialize the half saturation constant for silicate
122         ! ----------------------------------------------------
123         xksi(:,:)    = 2.e-6
124         xksimax(:,:) = xksi(:,:)
125
126      ENDIF
127
128      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done'
129      IF(lwp) WRITE(numout,*) ' '
130
131      !
132   END SUBROUTINE trc_ini_pisces
133 
134   SUBROUTINE trc_ctl_pisces
135      !!----------------------------------------------------------------------
136      !!                     ***  ROUTINE trc_ctl_pisces  ***
137      !!
138      !! ** Purpose :   control the cpp options, namelist and files
139      !!----------------------------------------------------------------------
140
141      IF(lwp) WRITE(numout,*)
142      IF(lwp) WRITE(numout,*) ' use PISCES biological model '
143
144   ! Check number of tracers
145   ! -----------------------
146#if  defined key_kriest
147      IF( jp_pisces /= 23) CALL ctl_stop( ' PISCES must have 23 passive tracers. Change jp_pisces in par_pisces.F90' )
148#else
149      IF( jp_pisces /= 24) CALL ctl_stop( ' PISCES must have 24 passive tracers. Change jp_pisces in par_pisces.F90' )
150#endif
151
152   END SUBROUTINE trc_ctl_pisces
153 
154#else
155   !!----------------------------------------------------------------------
156   !!   Dummy module                            No PISCES biochemical model
157   !!----------------------------------------------------------------------
158CONTAINS
159   SUBROUTINE trc_ini_pisces             ! Empty routine
160   END SUBROUTINE trc_ini_pisces
161#endif
162
163   !!======================================================================
164END MODULE trcini_pisces
Note: See TracBrowser for help on using the repository browser.