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

source: trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zbio.F90 @ 2715

Last change on this file since 2715 was 2715, checked in by rblod, 13 years ago

First attempt to put dynamic allocation on the trunk

  • Property svn:keywords set to Id
File size: 5.3 KB
RevLine 
[935]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         !
[1119]17   USE trc         !
[1073]18   USE sms_pisces      !
[935]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
[1457]28   USE iom
29 
[935]30   IMPLICIT NONE
31   PRIVATE
32
[1073]33   PUBLIC  p4z_bio   
[935]34
35   !!* Substitution
[1800]36#  include "top_substitute.h90"
[935]37   !!----------------------------------------------------------------------
[2528]38   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[1152]39   !! $Id$
[2528]40   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[935]41   !!----------------------------------------------------------------------
42
43CONTAINS
44
45   SUBROUTINE p4z_bio ( kt, jnt )
46      !!---------------------------------------------------------------------
47      !!                     ***  ROUTINE p4z_bio  ***
48      !!
49      !! ** Purpose :   Ecosystem model in the whole ocean: computes the
50      !!              different interactions between the different compartments
51      !!              of PISCES
52      !!
53      !! ** Method  : - ???
54      !!---------------------------------------------------------------------
55      INTEGER, INTENT(in) :: kt, jnt
56      INTEGER  ::  ji, jj, jk, jn
[1289]57      REAL(wp) ::  ztra
[935]58#if defined key_kriest
59      REAL(wp) ::  zcoef1, zcoef2
60#endif
61      CHARACTER (len=25) :: charout
62
63      !!---------------------------------------------------------------------
64
65      !     ASSIGN THE SHEAR RATE THAT IS USED FOR AGGREGATION
66      !     OF PHYTOPLANKTON AND DETRITUS
67
[1289]68      xdiss(:,:,:) = 1.
[935]69!!gm the use of nmld should be better here?
[1289]70      DO jk = 2, jpkm1
[935]71         DO jj = 1, jpj
72            DO ji = 1, jpi
[1289]73               IF( fsdepw(ji,jj,jk+1) > hmld(ji,jj) )   xdiss(ji,jj,jk) = 0.01
[935]74            END DO
75         END DO
76      END DO
77
78         
79      CALL p4z_sink ( kt, jnt )     ! vertical flux of particulate organic matter
80      CALL p4z_opt  ( kt, jnt )     ! Optic: PAR in the water column
[2528]81      CALL p4z_lim  ( kt      )     ! co-limitations by the various nutrients
[935]82      CALL p4z_prod ( kt, jnt )     ! phytoplankton growth rate over the global ocean.
83      !                             ! (for each element : C, Si, Fe, Chl )
[2528]84      CALL p4z_rem  ( kt      )     ! remineralization terms of organic matter+scavenging of Fe
85      CALL p4z_mort ( kt      )     ! phytoplankton mortality
[935]86      !                             ! zooplankton sources/sinks routines
[2528]87      CALL p4z_micro( kt      )           ! microzooplankton
[935]88      CALL p4z_meso ( kt, jnt )           ! mesozooplankton
89
[1289]90      !                             ! test if tracers concentrations fall below 0.
[935]91      xnegtr(:,:,:) = 1.e0
92      DO jn = jp_pcs0, jp_pcs1
93         DO jk = 1, jpk
94            DO jj = 1, jpj
95               DO ji = 1, jpi
[1289]96                  IF( ( trn(ji,jj,jk,jn) + tra(ji,jj,jk,jn) ) < 0.e0 ) THEN
97                     ztra             = ABS(  ( trn(ji,jj,jk,jn) - rtrn ) &
98                                            / ( tra(ji,jj,jk,jn) + rtrn ) )
99                     xnegtr(ji,jj,jk) = MIN( xnegtr(ji,jj,jk),  ztra )
100                  ENDIF
101              END DO
[935]102            END DO
103         END DO
104      END DO
105      !                                ! where at least 1 tracer concentration becomes negative
[1289]106      !                                !
[935]107      DO jn = jp_pcs0, jp_pcs1
108         trn(:,:,:,jn) = trn(:,:,:,jn) + xnegtr(:,:,:) * tra(:,:,:,jn)
109      END DO
110
111
112      tra(:,:,:,:) = 0.e0
113
114#if defined key_kriest
115      !
116      zcoef1 = 1.e0 / xkr_massp 
117      zcoef2 = 1.e0 / xkr_massp / 1.1
118      DO jk = 1,jpkm1
119         trn(:,:,jk,jpnum) = MAX(  trn(:,:,jk,jpnum), trn(:,:,jk,jppoc) * zcoef1 / xnumm(jk)  )
120         trn(:,:,jk,jpnum) = MIN(  trn(:,:,jk,jpnum), trn(:,:,jk,jppoc) * zcoef2              )
121      END DO
122#endif
123
124      !
125      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
126         WRITE(charout, FMT="('bio ')")
127         CALL prt_ctl_trc_info(charout)
128         CALL prt_ctl_trc(tab4d=trn, mask=tmask, clinfo=ctrcnm)
129      ENDIF
130      !
131   END SUBROUTINE p4z_bio
132
133#else
134   !!======================================================================
135   !!  Dummy module :                                   No PISCES bio-model
136   !!======================================================================
137CONTAINS
138   SUBROUTINE p4z_bio                         ! Empty routine
139   END SUBROUTINE p4z_bio
140#endif 
141
142   !!======================================================================
143END MODULE  p4zbio
Note: See TracBrowser for help on using the repository browser.