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

source: trunk/NEMO/TOP_SRC/PISCES/trcini_pisces.F90 @ 1007

Last change on this file since 1007 was 1007, checked in by cetlod, 16 years ago

Update PISCES modules to take into account the re-organization of TOP initialization phase, see ticket 170

File size: 6.1 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             ! Source Minus Sink variables
20   USE trc
21   USE oce_trc         ! ocean variables
22   USE trp_trc         !
23   USE p4zche 
24   USE lib_mpp
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   trc_ini_pisces   ! called by trcini.F90 module
30
31   !! * Module variables
32   REAL(wp) :: &
33      sco2   =  2.312e-3         , &
34      alka0  =  2.423e-3         , &
35      oxyg0  =  177.6e-6         , &
36      po4    =  2.174e-6         , &
37      bioma0 =  1.000e-8         , &
38      silic1 =  91.65e-6         , &
39      no3    =  31.04e-6 * 7.6
40
41#  include "domzgr_substitute.h90"
42#  include "top_substitute.h90"
43   !!----------------------------------------------------------------------
44   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
45   !! $Id: trcini_pisces.F90 776 2007-12-19 14:10:14Z gm $
46   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
47   !!----------------------------------------------------------------------
48
49CONTAINS
50
51   SUBROUTINE trc_ini_pisces
52      !!----------------------------------------------------------------------
53      !!                   ***  ROUTINE trc_ini_pisces ***
54      !!
55      !! ** Purpose :   Initialisation of the PISCES biochemical model
56      !!----------------------------------------------------------------------
57      INTEGER ::   ji, jj, jk, jn
58      REAL(wp) ::  caralk, bicarb, co3
59
60
61      !!----------------------------------------------------------------------
62
63
64      IF(lwp) WRITE(numout,*)
65      IF(lwp) WRITE(numout,*) ' trc_ini_pisces :   PISCES biochemical model initialisation'
66      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
67
68
69      !                                            ! Time-step
70      rfact   = rdttra(1) * float(ndttrc)          ! ---------
71      rfactr  = 1. / rfact
72      rfact2  = rfact / float(nrdttrc)
73      rfact2r = 1. / rfact2
74
75      IF(lwp) WRITE(numout,*) '    Tracer  time step    rfact  = ', rfact, ' rdt = ', rdt
76      IF(lwp) write(numout,*) '    Biology time step    rfact2 = ', rfact2
77
78
79
80      ! Set biological ratios
81      ! ---------------------
82      rno3   = (16.+2.) / 122.
83      po4r   =   1.e0   / 122.
84      o2nit  =  32.     / 122.
85      rdenit =  97.6    /  16.
86      o2ut   = 140.     / 122.
87
88      CALL p4z_che        ! initialize the chemical constants
89
90      ndayflxtr = 0      !  Initialize a counter for the computation of chemistry
91
92      ! Initialization of tracer concentration in case of  no restart
93      !--------------------------------------------------------------
94      IF( .NOT. lrsttr ) THEN 
95         
96         trn(:,:,:,jpdic) = sco2
97         trn(:,:,:,jpdoc) = bioma0
98         trn(:,:,:,jptal) = alka0
99         trn(:,:,:,jpoxy) = oxyg0
100         trn(:,:,:,jpcal) = bioma0
101         trn(:,:,:,jppo4) = po4 / po4r
102         trn(:,:,:,jppoc) = bioma0
103#  if ! defined key_kriest
104         trn(:,:,:,jpgoc) = bioma0
105         trn(:,:,:,jpbfe) = bioma0 * 5.e-6
106#  else
107         trn(:,:,:,jpnum) = bioma0 / ( 6. * xkr_massp )
108#  endif
109         trn(:,:,:,jpsil) = silic1
110         trn(:,:,:,jpbsi) = bioma0 * 0.15
111         trn(:,:,:,jpdsi) = bioma0 * 5.e-6
112         trn(:,:,:,jpphy) = bioma0
113         trn(:,:,:,jpdia) = bioma0
114         trn(:,:,:,jpzoo) = bioma0
115         trn(:,:,:,jpmes) = bioma0
116         trn(:,:,:,jpfer) = 0.6E-9
117         trn(:,:,:,jpsfe) = bioma0 * 5.e-6
118         trn(:,:,:,jpdfe) = bioma0 * 5.e-6
119         trn(:,:,:,jpnfe) = bioma0 * 5.e-6
120         trn(:,:,:,jpnch) = bioma0 * 12. / 55.
121         trn(:,:,:,jpdch) = bioma0 * 12. / 55.
122         trn(:,:,:,jpno3) = no3
123         trn(:,:,:,jpnh4) = bioma0
124
125         ! Initialization of chemical variables of the carbon cycle
126         ! --------------------------------------------------------
127         DO jk = 1, jpk
128            DO jj = 1, jpj
129               DO ji = 1, jpi
130                  caralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  )
131                  co3    = ( caralk - trn(ji,jj,jk,jpdic) ) *        tmask(ji,jj,jk)   &
132                     &   +                  0.5e-3          * ( 1. - tmask(ji,jj,jk) )
133                  bicarb = ( 2. * trn(ji,jj,jk,jpdic) - caralk )
134                  hi(ji,jj,jk) = ( ak23(ji,jj,jk) * bicarb / co3 ) *        tmask(ji,jj,jk)   &
135                     &         +            1.e-9                  * ( 1. - tmask(ji,jj,jk) )
136               END DO
137            END DO
138         END DO
139         
140      ENDIF
141
142
143
144      ! initialize the half saturation constant for silicate
145      ! ----------------------------------------------------
146      xksi(:,:)    = 2.e-6
147      xksimax(:,:) = xksi(:,:)
148
149      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done'
150      IF(lwp) WRITE(numout,*) ' '
151
152      !
153   END SUBROUTINE trc_ini_pisces
154   
155#else
156   !!----------------------------------------------------------------------
157   !!   Dummy module                            No PISCES biochemical model
158   !!----------------------------------------------------------------------
159CONTAINS
160   SUBROUTINE trc_ini_pisces             ! Empty routine
161   END SUBROUTINE trc_ini_pisces
162#endif
163
164   !!======================================================================
165END MODULE trcini_pisces
Note: See TracBrowser for help on using the repository browser.