/[MITgcm]/MITgcm_contrib/darwin2/pkg/monod/monod_check_chl.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/monod/monod_check_chl.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Wed Apr 13 18:56:25 2011 UTC (14 years, 3 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt63l_20120405, ctrb_darwin2_ckpt62v_20110413, ctrb_darwin2_ckpt63f_20111201, ctrb_darwin2_ckpt64a_20121116, ctrb_darwin2_ckpt62y_20110526, ctrb_darwin2_ckpt62x_20110513, ctrb_darwin2_ckpt62w_20110426, ctrb_darwin2_ckpt63o_20120629, ctrb_darwin2_ckpt63c_20111011, ctrb_darwin2_ckpt63i_20120124, ctrb_darwin2_ckpt63m_20120506, ctrb_darwin2_ckpt63s_20120908, ctrb_darwin2_ckpt63e_20111107, ctrb_darwin2_ckpt63b_20110830, ctrb_darwin2_ckpt63j_20120217, ctrb_darwin2_ckpt63r_20120817, ctrb_darwin2_ckpt63g_20111220, ctrb_darwin2_ckpt64c_20130120, ctrb_darwin2_ckpt63a_20110804, ctrb_darwin2_ckpt63h_20111230, ctrb_darwin2_ckpt63p_20120707, ctrb_darwin2_ckpt63d_20111107, ctrb_darwin2_ckpt63q_20120731, ctrb_darwin2_ckpt63_20110728, ctrb_darwin2_ckpt64b_20121224, ctrb_darwin2_ckpt64_20121012, ctrb_darwin2_baseline, ctrb_darwin2_ckpt63n_20120604, ctrb_darwin2_ckpt63k_20120317, ctrb_darwin2_ckpt62z_20110622
darwin2 initial checkin

1 jahn 1.1
2     #include "CPP_OPTIONS.h"
3     #include "DARWIN_OPTIONS.h"
4    
5     #ifdef ALLOW_PTRACERS
6     #ifdef ALLOW_MONOD
7    
8     c ==========================================================
9     c SUBROUTINE MONOD_CHECK_CHL()
10     c initialize Chl is not set and check that not too much or too little
11     c --- steph spring 2010
12     c ==========================================================
13     c
14     SUBROUTINE MONOD_CHECK_CHL(myThid)
15    
16     IMPLICIT NONE
17    
18     #include "SIZE.h"
19     #include "GRID.h"
20     #include "DYNVARS.h"
21     #include "EEPARAMS.h"
22     #include "PARAMS.h"
23     #include "PTRACERS_SIZE.h"
24     #include "PTRACERS_PARAMS.h"
25     #include "PTRACERS_FIELDS.h"
26     #include "MONOD_SIZE.h"
27     #include "MONOD.h"
28     #include "DARWIN_IO.h"
29     #ifdef OASIM
30     #include "SPECTRAL_SIZE.h"
31     #include "SPECTRAL.h"
32     #endif
33    
34    
35     C !INPUT PARAMETERS: ===================================================
36     C myThid :: thread number
37     INTEGER myThid
38    
39     C !LOCAL VARIABLES:
40     C === Local variables ===
41     C msgBuf - Informational/error meesage buffer
42     CHARACTER*(MAX_LEN_MBUF) msgBuf
43     INTEGER IniUnit1, IniUnit2
44    
45     INTEGER bi, bj, k, i, j, iPAR
46    
47     INTEGER np
48    
49     INTEGER ilam
50    
51     _RL phytmp, chltmp, chl2ctmp, pcm
52     _RL PARlocal, lite
53     _RL atten
54     CEOP
55    
56     #ifdef DYNAMIC_CHL
57    
58     WRITE(msgBuf,'(A)')
59     & '// ======================================================='
60     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
61     & SQUEEZE_RIGHT, myThid )
62     WRITE(msgBuf,'(A)') '// Darwin check Chl >>> START <<<'
63     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
64     & SQUEEZE_RIGHT, myThid )
65     WRITE(msgBuf,'(A)')
66     & '// ======================================================='
67     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
68     & SQUEEZE_RIGHT, myThid )
69    
70     call DARWIN_FIELDS_LOAD(0,0. _d 0,myThid)
71    
72     c check Chl fields are reasonable
73     DO bj = myByLo(myThid), myByHi(myThid)
74     DO bi = myBxLo(myThid), myBxHi(myThid)
75     DO j=1-Oly,sNy+Oly
76     DO i=1-Olx,sNx+Olx
77     atten= 0. _d 0
78     #if defined(WAVEBANDS) && defined(OASIM)
79     c if spectral use wavebands to give a single surface PAR
80     lite= 0. _d 0
81     DO ilam=1,tlam
82     lite=lite+WtouEins(ilam)*(oasim_ed(i,j,ilam,bi,bj)+
83     & oasim_es(i,j,ilam,bi,bj))
84     ENDDO
85     #else
86     lite=sur_par(i,j,bi,bj)
87     #endif
88    
89     DO k=1,nR
90     if (HFacC(i,j,k,bi,bj).gt.0. _d 0) then
91     DO np=1,npmax
92     chltmp=Ptracer(i,j,k,bi,bj,iChl+np-1)
93     phytmp=Ptracer(i,j,k,bi,bj,iPhy+np-1)
94     c if initialized to zero, set to balanced growth
95     c with no nutrient or temperature limitation
96     c (Eq. A15 Geider et al 1997)
97     if (chltmp.eq.0. _d 0) then
98     atten= atten + (k0 )*5. _d -1*drF(k)
99     if (k.gt.1)then
100     atten = atten + (k0)*5. _d -1*drF(k-1)
101     endif
102     PARlocal = lite*exp(-atten)
103     pcm=pcmax(np) !*limit(np)*phytoTempFunction(np)
104     chl2ctmp=chl2cmax(np)/
105     & (1+(chl2cmax(np)*alphachl(np)*PARlocal)/
106     & (2*pcm))
107     Ptracer(i,j,k,bi,bj,iChl+np-1)=
108     & phytmp*R_PC(np)*chl2ctmp
109     endif
110     c check not too high or too low
111     Ptracer(i,j,k,bi,bj,iChl+np-1)=
112     & max(Ptracer(i,j,k,bi,bj,iChl+np-1),
113     & phytmp*R_PC(np)*chl2cmin(np))
114     Ptracer(i,j,k,bi,bj,iChl+np-1)=
115     & min(Ptracer(i,j,k,bi,bj,iChl+np-1),
116     & phytmp*R_PC(np)*chl2cmax(np))
117     if (k.eq.1.and.i.eq.1.and.j.eq.1) print*,'initial Chl',
118     & Ptracer(i,j,k,bi,bj,iChl+np-1), phytmp
119     ENDDO
120     endif
121     ENDDO
122     ENDDO
123     ENDDO
124     ENDDO
125     ENDDO
126    
127     #endif
128    
129     WRITE(msgBuf,'(A)')
130     & '// ======================================================='
131     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
132     & SQUEEZE_RIGHT, myThid )
133     WRITE(msgBuf,'(A)') '// Darwin check chl >>> END <<<'
134     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
135     & SQUEEZE_RIGHT, myThid )
136     WRITE(msgBuf,'(A)')
137     & '// ======================================================='
138     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
139     & SQUEEZE_RIGHT, myThid )
140    
141    
142     RETURN
143     END
144     #endif /*MONOD*/
145     #endif /*ALLOW_PTRACERS*/
146     c ==========================================================
147    

  ViewVC Help
Powered by ViewVC 1.1.22