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.
p4zopt.F in trunk/NEMO/TOP_SRC/SMS – NEMO

source: trunk/NEMO/TOP_SRC/SMS/p4zopt.F @ 491

Last change on this file since 491 was 341, checked in by opalod, 19 years ago

nemo_v1_update_028 : CT : add missing headers

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 5.0 KB
Line 
1
2CCC $Header$ 
3CCC  TOP 1.0 , LOCEAN-IPSL (2005) 
4C This software is governed by CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
5C ---------------------------------------------------------------------------
6CDIR$ LIST
7      SUBROUTINE p4zopt
8#if defined key_passivetrc && defined key_trc_pisces
9CCC---------------------------------------------------------------------
10CCC
11CCC             ROUTINE p4zopt : PISCES MODEL
12CCC             *****************************
13CCC
14CCC  PURPOSE :
15CCC  ---------
16CCC         Compute the light availability in the water column
17CCC         depending on the depth and the chlorophyll concentration
18CCC
19CC   INPUT :
20CC   -----
21CC      argument
22CC              None
23CC      common
24CC              all the common defined in opa
25CC
26CC
27CC   OUTPUT :                   : no
28CC   ------
29CC
30CC   MODIFICATIONS:
31CC   --------------
32CC      original  : O. Aumont (2004)
33CC----------------------------------------------------------------------
34CC parameters and commons
35CC ======================
36CDIR$ NOLIST
37      USE oce_trc
38      USE trp_trc
39      USE sms
40      IMPLICIT NONE
41#include "domzgr_substitute.h90"
42CDIR$ LIST
43CC----------------------------------------------------------------------
44CC local declarations
45CC ==================
46      INTEGER ji, jj, jk, mrgb
47      REAL xchl,ekg(jpi,jpj,jpk),ekr(jpi,jpj,jpk)
48      REAL ekb(jpi,jpj,jpk)
49      REAL parlux,e1(jpi,jpj,jpk),e2(jpi,jpj,jpk),e3(jpi,jpj,jpk)
50      REAL zdepmoy(jpi,jpj)
51      REAL etmp(jpi,jpj)
52      REAL zrlight,zblight,zglight
53C
54C     Initialisation of variables used to compute PAR
55C     -----------------------------------------------
56C
57        e1     = 0.
58        e2     = 0.
59        e3     = 0.
60        etot   = 0.
61        parlux = 0.43/3.
62
63        DO jk=1,jpkm1
64          DO jj=1,jpj
65            DO ji=1,jpi
66C
67C     Separation in three light bands: red, green, blue
68C     -------------------------------------------------
69C
70        xchl=(trn(ji,jj,jk,jpnch)+trn(ji,jj,jk,jpdch)+rtrn)*1.E6
71        xchl=max(0.03,xchl)
72        xchl=min(10.,xchl)
73                                                                               
74        mrgb = int(41+20.*log10(xchl)+rtrn)
75                                                                               
76        ekb(ji,jj,jk)=xkrgb(1,mrgb)
77        ekg(ji,jj,jk)=xkrgb(2,mrgb)
78        ekr(ji,jj,jk)=xkrgb(3,mrgb)
79C
80            END DO
81          END DO
82        END DO
83C
84          DO jj = 1,jpj
85            DO ji = 1,jpi
86C
87C     Separation in three light bands: red, green, blue
88C     -------------------------------------------------
89C
90        zblight=0.5*ekb(ji,jj,1)*fse3t(ji,jj,1)
91        zglight=0.5*ekg(ji,jj,1)*fse3t(ji,jj,1)
92        zrlight=0.5*ekr(ji,jj,1)*fse3t(ji,jj,1)
93C
94        e1(ji,jj,1) = parlux*qsr(ji,jj)*exp(-zblight)
95        e2(ji,jj,1) = parlux*qsr(ji,jj)*exp(-zglight)
96        e3(ji,jj,1) = parlux*qsr(ji,jj)*exp(-zrlight)
97C
98            END DO
99          END DO
100                                                                               
101                                                                               
102        DO jk = 2,jpkm1
103          DO jj = 1,jpj
104            DO ji = 1,jpi
105C
106C     Separation in three light bands: red, green, blue
107C     -------------------------------------------------
108C
109        zblight=0.5*(ekb(ji,jj,jk-1)*fse3t(ji,jj,jk-1)
110     &    +ekb(ji,jj,jk)*fse3t(ji,jj,jk))
111        zglight=0.5*(ekg(ji,jj,jk-1)*fse3t(ji,jj,jk-1)
112     &    +ekg(ji,jj,jk)*fse3t(ji,jj,jk))
113        zrlight=0.5*(ekr(ji,jj,jk-1)*fse3t(ji,jj,jk-1)
114     &    +ekr(ji,jj,jk)*fse3t(ji,jj,jk))
115C
116        e1(ji,jj,jk) = e1(ji,jj,jk-1)*exp(-zblight)
117        e2(ji,jj,jk) = e2(ji,jj,jk-1)*exp(-zglight)
118        e3(ji,jj,jk) = e3(ji,jj,jk-1)*exp(-zrlight)
119C
120            END DO
121          END DO
122        END DO
123C
124        etot(:,:,:) = e1(:,:,:)+e2(:,:,:)+e3(:,:,:)
125C   
126C     Computation of the euphotic depth
127C     ---------------------------------
128C   
129        zmeu(:,:) = 300.
130
131        DO jk = 2,jpkm1
132          DO jj = 1,jpj
133            DO ji = 1,jpi
134        IF (etot(ji,jj,jk).GE.0.0043*qsr(ji,jj)) THEN
135           zmeu(ji,jj) = fsdepw(ji,jj,jk+1)
136        ENDIF
137            END DO
138          END DO
139        END DO
140C
141        zmeu(:,:)=min(300.,zmeu(:,:))
142C
143C    Computation of the mean light over the mixed layer depth
144C    --------------------------------------------------------
145C
146        zdepmoy  = 0
147        etmp  = 0.
148        emoy  = 0.
149
150        DO jk = 1,jpkm1
151          DO jj = 1,jpj
152            DO ji = 1,jpi
153         if (fsdepw(ji,jj,jk+1).le.hmld(ji,jj)) then
154       etmp(ji,jj) = etmp(ji,jj)+etot(ji,jj,jk)*fse3t(ji,jj,jk)
155       zdepmoy(ji,jj)=zdepmoy(ji,jj)+fse3t(ji,jj,jk)
156         endif
157            END DO
158          END DO
159        END DO
160
161        emoy(:,:,:) = etot(:,:,:)
162
163        DO jk = 1,jpkm1
164          DO jj = 1,jpj
165            DO ji = 1,jpi
166        IF (fsdepw(ji,jj,jk+1).LE.hmld(ji,jj)) THEN
167          emoy(ji,jj,jk) = etmp(ji,jj)/(zdepmoy(ji,jj)+rtrn)
168        ENDIF
169            END DO
170          END DO
171        END DO
172
173#   if defined key_trc_diaadd
174        trc2d(:,:,11) = zmeu(:,:)
175#    endif
176C
177#endif
178      RETURN
179      END
Note: See TracBrowser for help on using the repository browser.