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.
p4zbio.F90 in tags/nemo_v3_1_beta/NEMO/TOP_SRC/PISCES – NEMO

source: tags/nemo_v3_1_beta/NEMO/TOP_SRC/PISCES/p4zbio.F90 @ 5229

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

clean TOP model routines to avoid warning when compiling, see ticket:303

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 5.4 KB
Line 
1MODULE p4zbio
2   !!======================================================================
3   !!                         ***  MODULE p4zbio  ***
4   !! TOP :   PISCES bio-model
5   !!======================================================================
6   !! History :   1.0  !  2004     (O. Aumont) Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!----------------------------------------------------------------------
9#if defined key_pisces
10   !!----------------------------------------------------------------------
11   !!   'key_pisces'                                       PISCES bio-model
12   !!----------------------------------------------------------------------
13   !!   p4z_bio        :   computes the interactions between the different
14   !!                      compartments of PISCES
15   !!----------------------------------------------------------------------
16   USE oce_trc         !
17   USE trc         !
18   USE sms_pisces      !
19   USE p4zsink         !
20   USE p4zopt          !
21   USE p4zlim          !
22   USE p4zprod         !
23   USE p4zmort         !
24   USE p4zmicro        !
25   USE p4zmeso         !
26   USE p4zrem          !
27   USE prtctl_trc
28   
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC  p4z_bio   
33
34   !! * Shared module variables
35   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &  !:
36      xnegtr            ! Array used to indicate negative tracer values
37
38
39   !!* Substitution
40#  include "domzgr_substitute.h90"
41   !!----------------------------------------------------------------------
42   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
43   !! $Id$
44   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
46
47CONTAINS
48
49   SUBROUTINE p4z_bio ( kt, jnt )
50      !!---------------------------------------------------------------------
51      !!                     ***  ROUTINE p4z_bio  ***
52      !!
53      !! ** Purpose :   Ecosystem model in the whole ocean: computes the
54      !!              different interactions between the different compartments
55      !!              of PISCES
56      !!
57      !! ** Method  : - ???
58      !!---------------------------------------------------------------------
59      INTEGER, INTENT(in) :: kt, jnt
60      INTEGER  ::  ji, jj, jk, jn
61#if defined key_kriest
62      REAL(wp) ::  zcoef1, zcoef2
63#endif
64      CHARACTER (len=25) :: charout
65
66      !!---------------------------------------------------------------------
67
68      !     ASSIGN THE SHEAR RATE THAT IS USED FOR AGGREGATION
69      !     OF PHYTOPLANKTON AND DETRITUS
70
71      xdiss(:,:,:) = 0.01
72
73!!gm the use of nmld should be better here?
74      DO jk = 1, jpkm1
75         DO jj = 1, jpj
76            DO ji = 1, jpi
77               IF( fsdepw(ji,jj,jk+1) .le. hmld(ji,jj) )   xdiss(ji,jj,jk) = 1.e0
78            END DO
79         END DO
80      END DO
81
82         
83      CALL p4z_sink ( kt, jnt )     ! vertical flux of particulate organic matter
84      CALL p4z_opt  ( kt, jnt )     ! Optic: PAR in the water column
85      CALL p4z_lim  ( kt, jnt )     ! co-limitations by the various nutrients
86      CALL p4z_prod ( kt, jnt )     ! phytoplankton growth rate over the global ocean.
87      !                             ! (for each element : C, Si, Fe, Chl )
88      CALL p4z_rem  ( kt, jnt )     ! remineralization terms of organic matter+scavenging of Fe
89      CALL p4z_mort ( kt, jnt )     ! phytoplankton mortality
90      !                             ! zooplankton sources/sinks routines
91      CALL p4z_micro( kt, jnt )           ! microzooplankton
92      CALL p4z_meso ( kt, jnt )           ! mesozooplankton
93
94
95      !                                                      ! test if tracers concentrations fall below 0.
96      xnegtr(:,:,:) = 1.e0
97      DO jn = jp_pcs0, jp_pcs1
98         DO jk = 1, jpk
99            DO jj = 1, jpj
100               DO ji = 1, jpi
101                  IF( ( trn(ji,jj,jk,jn) + tra(ji,jj,jk,jn) ) < 0.e0 )    xnegtr(ji,jj,jk) = 0.e0
102               END DO
103            END DO
104         END DO
105      END DO
106      !                                ! where at least 1 tracer concentration becomes negative
107      !                                ! all tracer tendancy are set to zero (i.e. trn = trb)
108      DO jn = jp_pcs0, jp_pcs1
109         trn(:,:,:,jn) = trn(:,:,:,jn) + xnegtr(:,:,:) * tra(:,:,:,jn)
110      END DO
111
112
113      tra(:,:,:,:) = 0.e0
114
115#if defined key_kriest
116      !
117      zcoef1 = 1.e0 / xkr_massp 
118      zcoef2 = 1.e0 / xkr_massp / 1.1
119      DO jk = 1,jpkm1
120         trn(:,:,jk,jpnum) = MAX(  trn(:,:,jk,jpnum), trn(:,:,jk,jppoc) * zcoef1 / xnumm(jk)  )
121         trn(:,:,jk,jpnum) = MIN(  trn(:,:,jk,jpnum), trn(:,:,jk,jppoc) * zcoef2              )
122      END DO
123#endif
124
125
126# if defined key_trc_dia3d && defined key_kriest
127      trc3d(:,:,:,jp_pcs0_3d + 10) = tra(:,:,:,jpcal) * xnegtr(:,:,:) * 1.e3 * rfact2r
128# endif
129      !
130      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
131         WRITE(charout, FMT="('bio ')")
132         CALL prt_ctl_trc_info(charout)
133         CALL prt_ctl_trc(tab4d=trn, mask=tmask, clinfo=ctrcnm)
134      ENDIF
135      !
136   END SUBROUTINE p4z_bio
137
138#else
139   !!======================================================================
140   !!  Dummy module :                                   No PISCES bio-model
141   !!======================================================================
142CONTAINS
143   SUBROUTINE p4z_bio                         ! Empty routine
144   END SUBROUTINE p4z_bio
145#endif 
146
147   !!======================================================================
148END MODULE  p4zbio
Note: See TracBrowser for help on using the repository browser.