/[MITgcm]/MITgcm_contrib/darwin2/pkg/quota/geider98.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/quota/geider98.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_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_ckpt63e_20111107, ctrb_darwin2_ckpt63b_20110830, ctrb_darwin2_ckpt63j_20120217, ctrb_darwin2_ckpt63g_20111220, ctrb_darwin2_ckpt63a_20110804, ctrb_darwin2_ckpt63h_20111230, ctrb_darwin2_ckpt63d_20111107, ctrb_darwin2_ckpt63_20110728, ctrb_darwin2_baseline, ctrb_darwin2_ckpt63n_20120604, ctrb_darwin2_ckpt63k_20120317, ctrb_darwin2_ckpt62z_20110622
darwin2 initial checkin

1 jahn 1.1 C $Header$
2     C $Name$
3    
4     #include "CPP_OPTIONS.h"
5     #include "PTRACERS_OPTIONS.h"
6     #include "DARWIN_OPTIONS.h"
7     c
8     #ifdef ALLOW_PTRACERS
9     #ifdef ALLOW_DARWIN
10     #ifdef GEIDER
11     #ifdef DYNCHL
12     c
13     c ====================================================================
14     c SUBROUTINE GEIDER98
15     c ====================================================================
16     SUBROUTINE GEIDER98(
17     I PARlocal,
18     I biomass,
19     I qlimit,
20     #ifdef FQUOTA
21     I felimit,
22     #endif
23     I up_inorg,
24     I photo_Tempfunction,
25     O dchldt, ! chlorophyll synthesis rate
26     I myThid)
27     IMPLICIT NONE
28    
29     #ifdef ALLOW_QUOTA
30     #include "QUOTA_SIZE.h"
31     #include "QUOTA.h"
32     #else
33     #include "MONOD_SIZE.h"
34     #include "MONOD.h"
35     #endif
36     c
37     INTEGER myThid
38     INTEGER ii,jp
39     c
40     _RL PARlocal
41     _RL biomass(iomax,npmax)
42     _RL qlimit(npmax)
43     _RL felimit(npmax)
44     _RL alpha_fe
45     _RL up_inorg(iimax,npmax)
46     _RL N_uptake(npmax)
47     _RL photo_Tempfunction
48     c
49     _RL dchldt(npmax)
50     c
51     _RL E0
52     _RL C_biomass
53     _RL chl
54     _RL VCref
55     c
56     _RL Chl2C
57     _RL PCmax
58     _RL PCPhot(npmax)
59     _RL rhochl
60     _RL chlsynth(npmax)
61     _RL VCmax
62     _RL VCN
63     c
64     c Geider, MacIntyre and Kana (1998) photosynthesis model
65     c adapted for multiple nutrients following Moore et al (2002)
66     c
67     E0 = PARlocal ! muEin m^-2 s^-1
68     do jp=1,npmax
69     #ifdef FQUOTA
70     alpha_fe = alphachl(jp) * felimit(jp)
71     #else
72     alpha_fe = alphachl(jp)
73     #endif
74     if (autotrophy(jp).gt.0. _d 0) then
75     C_biomass = biomass(iCarb,jp) ! mmol C m^-3
76     chl = biomass(iChlo,jp) ! mg Chl m^-3
77     c
78     c N uptake is sum of NO3, NO2 and NH4 uptake
79     VCN = 0.0 _d 0
80     do ii=2,iimax
81     if (ii.eq.iNO3.or.ii.eq.iNO2.or.ii.eq.iNH4) then
82     VCN = VCN + up_inorg(ii,jp) ! mmol N (mmol C)^-1 s^-1
83     endif
84     enddo
85     c
86     c-----------------------------------------------------------------
87     if (E0.gt.1. _d -1 .and.
88     & vmaxi(iDIC,jp).gt.0. _d 0 .and.
89     & C_biomass.gt.0. _d 0 .and.
90     & chl.gt.0. _d 0) then
91     Chl2C = chl / C_biomass ! mg chl (mmol C)^-1
92     c
93     PCmax = vmaxi(iDIC,jp) ! s^-1
94     & * qlimit(jp)
95     & * photo_Tempfunction
96     c
97     if (PCmax.gt.0. _d 0.and.alpha_fe.gt.0. _d 0) then
98     PCPhot(jp) = PCmax ! s^-1
99     & *(1-exp(-alpha_fe*Chl2C*E0/PCmax))
100     c
101     rhochl = Chl2Nmax * PCPhot(jp) ! mg chl (mmol N)^-1
102     & /(alphachl(jp)*Chl2C*E0)
103     chlsynth(jp) = rhochl * VCN * C_biomass ! mg chl m^-3 s^-1
104     else
105     PCPhot(jp) = 0. _d 0 ! s^-1
106     chlsynth(jp) = 0. _d 0 ! mg chl m^-3 s^-1
107     endif
108     c
109     else ! else if insufficient light, max phot=0 or C biomass=0...
110     PCPhot(jp) = 0. _d 0 ! s^-1
111     chlsynth(jp) = 0. _d 0 ! mg chl m^-3 s^-1
112     endif
113     c-----------------------------------------------------------------
114     ! for passing back to quota_plankton
115     up_inorg(iDIC,jp) = PCPhot(jp) - biosynth*VCN ! s^-1
116     dchldt(jp) = chlsynth(jp) ! mg chl m^-3 s^-1
117     else ! else if jp is a heterotroph
118     up_inorg(iDIC,jp) = 0. _d 0 ! s^-1
119     dchldt(jp) = 0. _d 0 ! mg chl m^-3 s^-1
120     c-----------------------------------------------------------------
121     endif
122     enddo
123    
124     RETURN
125     END
126     c
127     #endif /*DYNCHL*/
128     #endif /*GEIDER*/
129     #endif /*ALLOW_DARWIN*/
130     #endif /*ALLOW_PTRACERS*/
131     C ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22