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 branches/DEV_r1879_FCM/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/DEV_r1879_FCM/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zbio.F90 @ 2007

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

update branches/DEV_r1879_FCM/NEMOGCM/NEMO with tags/nemo_v3_2_1/NEMO

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 5.5 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   USE iom
29 
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC  p4z_bio   
34
35   !! * Shared module variables
36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &  !:
37      xnegtr            ! Array used to indicate negative tracer values
38
39
40   !!* Substitution
41#  include "top_substitute.h90"
42   !!----------------------------------------------------------------------
43   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
44   !! $Id$
45   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
46   !!----------------------------------------------------------------------
47
48CONTAINS
49
50   SUBROUTINE p4z_bio ( kt, jnt )
51      !!---------------------------------------------------------------------
52      !!                     ***  ROUTINE p4z_bio  ***
53      !!
54      !! ** Purpose :   Ecosystem model in the whole ocean: computes the
55      !!              different interactions between the different compartments
56      !!              of PISCES
57      !!
58      !! ** Method  : - ???
59      !!---------------------------------------------------------------------
60      INTEGER, INTENT(in) :: kt, jnt
61      INTEGER  ::  ji, jj, jk, jn
62      REAL(wp) ::  ztra
63#if defined key_kriest
64      REAL(wp) ::  zcoef1, zcoef2
65#endif
66      CHARACTER (len=25) :: charout
67
68      !!---------------------------------------------------------------------
69
70      !     ASSIGN THE SHEAR RATE THAT IS USED FOR AGGREGATION
71      !     OF PHYTOPLANKTON AND DETRITUS
72
73      xdiss(:,:,:) = 1.
74!!gm the use of nmld should be better here?
75      DO jk = 2, jpkm1
76         DO jj = 1, jpj
77            DO ji = 1, jpi
78               IF( fsdepw(ji,jj,jk+1) > hmld(ji,jj) )   xdiss(ji,jj,jk) = 0.01
79            END DO
80         END DO
81      END DO
82
83         
84      CALL p4z_sink ( kt, jnt )     ! vertical flux of particulate organic matter
85      CALL p4z_opt  ( kt, jnt )     ! Optic: PAR in the water column
86      CALL p4z_lim  ( kt, jnt )     ! co-limitations by the various nutrients
87      CALL p4z_prod ( kt, jnt )     ! phytoplankton growth rate over the global ocean.
88      !                             ! (for each element : C, Si, Fe, Chl )
89      CALL p4z_rem  ( kt, jnt )     ! remineralization terms of organic matter+scavenging of Fe
90      CALL p4z_mort ( kt, jnt )     ! phytoplankton mortality
91      !                             ! zooplankton sources/sinks routines
92      CALL p4z_micro( kt, jnt )           ! microzooplankton
93      CALL p4z_meso ( kt, jnt )           ! mesozooplankton
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 ) THEN
102                     ztra             = ABS(  ( trn(ji,jj,jk,jn) - rtrn ) &
103                                            / ( tra(ji,jj,jk,jn) + rtrn ) )
104                     xnegtr(ji,jj,jk) = MIN( xnegtr(ji,jj,jk),  ztra )
105                  ENDIF
106              END DO
107            END DO
108         END DO
109      END DO
110      !                                ! where at least 1 tracer concentration becomes negative
111      !                                !
112      DO jn = jp_pcs0, jp_pcs1
113         trn(:,:,:,jn) = trn(:,:,:,jn) + xnegtr(:,:,:) * tra(:,:,:,jn)
114      END DO
115
116
117      tra(:,:,:,:) = 0.e0
118
119#if defined key_kriest
120      !
121      zcoef1 = 1.e0 / xkr_massp 
122      zcoef2 = 1.e0 / xkr_massp / 1.1
123      DO jk = 1,jpkm1
124         trn(:,:,jk,jpnum) = MAX(  trn(:,:,jk,jpnum), trn(:,:,jk,jppoc) * zcoef1 / xnumm(jk)  )
125         trn(:,:,jk,jpnum) = MIN(  trn(:,:,jk,jpnum), trn(:,:,jk,jppoc) * zcoef2              )
126      END DO
127#endif
128
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.