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

source: trunk/NEMO/TOP_SRC/PISCES/p4zbio.F90 @ 1289

Last change on this file since 1289 was 1289, checked in by cetlod, 15 years ago

change the computation of xnegtr in PISCEs model, see ticket:318

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 5.6 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      REAL(wp) ::  ztra
62#if defined key_kriest
63      REAL(wp) ::  zcoef1, zcoef2
64#endif
65      CHARACTER (len=25) :: charout
66
67      !!---------------------------------------------------------------------
68
69      !     ASSIGN THE SHEAR RATE THAT IS USED FOR AGGREGATION
70      !     OF PHYTOPLANKTON AND DETRITUS
71
72      xdiss(:,:,:) = 1.
73!!gm the use of nmld should be better here?
74      DO jk = 2, jpkm1
75         DO jj = 1, jpj
76            DO ji = 1, jpi
77               IF( fsdepw(ji,jj,jk+1) > hmld(ji,jj) )   xdiss(ji,jj,jk) = 0.01
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      !                             ! test if tracers concentrations fall below 0.
95      xnegtr(:,:,:) = 1.e0
96      DO jn = jp_pcs0, jp_pcs1
97         DO jk = 1, jpk
98            DO jj = 1, jpj
99               DO ji = 1, jpi
100                  IF( ( trn(ji,jj,jk,jn) + tra(ji,jj,jk,jn) ) < 0.e0 ) THEN
101                     ztra             = ABS(  ( trn(ji,jj,jk,jn) - rtrn ) &
102                                            / ( tra(ji,jj,jk,jn) + rtrn ) )
103                     xnegtr(ji,jj,jk) = MIN( xnegtr(ji,jj,jk),  ztra )
104                  ENDIF
105              END DO
106            END DO
107         END DO
108      END DO
109      !                                ! where at least 1 tracer concentration becomes negative
110      !                                !
111      DO jn = jp_pcs0, jp_pcs1
112         trn(:,:,:,jn) = trn(:,:,:,jn) + xnegtr(:,:,:) * tra(:,:,:,jn)
113      END DO
114
115
116      tra(:,:,:,:) = 0.e0
117
118#if defined key_kriest
119      !
120      zcoef1 = 1.e0 / xkr_massp 
121      zcoef2 = 1.e0 / xkr_massp / 1.1
122      DO jk = 1,jpkm1
123         trn(:,:,jk,jpnum) = MAX(  trn(:,:,jk,jpnum), trn(:,:,jk,jppoc) * zcoef1 / xnumm(jk)  )
124         trn(:,:,jk,jpnum) = MIN(  trn(:,:,jk,jpnum), trn(:,:,jk,jppoc) * zcoef2              )
125      END DO
126#endif
127
128
129# if defined key_trc_dia3d && defined key_kriest
130      trc3d(:,:,:,jp_pcs0_3d + 10) = tra(:,:,:,jpcal) * xnegtr(:,:,:) * 1.e3 * rfact2r
131# endif
132      !
133      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
134         WRITE(charout, FMT="('bio ')")
135         CALL prt_ctl_trc_info(charout)
136         CALL prt_ctl_trc(tab4d=trn, mask=tmask, clinfo=ctrcnm)
137      ENDIF
138      !
139   END SUBROUTINE p4z_bio
140
141#else
142   !!======================================================================
143   !!  Dummy module :                                   No PISCES bio-model
144   !!======================================================================
145CONTAINS
146   SUBROUTINE p4z_bio                         ! Empty routine
147   END SUBROUTINE p4z_bio
148#endif 
149
150   !!======================================================================
151END MODULE  p4zbio
Note: See TracBrowser for help on using the repository browser.