/[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.3 - (hide annotations) (download)
Tue May 19 14:32:43 2015 UTC (10 years, 2 months ago) by benw
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt65w_20160512, ctrb_darwin2_ckpt66g_20170424, ctrb_darwin2_ckpt66k_20171025, ctrb_darwin2_ckpt66n_20180118, ctrb_darwin2_ckpt65v_20160409, ctrb_darwin2_ckpt65s_20160114, ctrb_darwin2_ckpt66d_20170214, ctrb_darwin2_ckpt65m_20150615, ctrb_darwin2_ckpt65q_20151118, ctrb_darwin2_ckpt65o_20150914, ctrb_darwin2_ckpt65p_20151023, ctrb_darwin2_ckpt65z_20160929, ctrb_darwin2_ckpt65n_20150729, ctrb_darwin2_ckpt66h_20170602, ctrb_darwin2_ckpt65x_20160612, ctrb_darwin2_ckpt66f_20170407, ctrb_darwin2_ckpt66a_20161020, ctrb_darwin2_ckpt66b_20161219, ctrb_darwin2_ckpt66j_20170815, ctrb_darwin2_ckpt65y_20160801, ctrb_darwin2_ckpt66c_20170121, ctrb_darwin2_ckpt65t_20160221, ctrb_darwin2_ckpt66o_20180209, ctrb_darwin2_ckpt66e_20170314, ctrb_darwin2_ckpt65u_20160315, ctrb_darwin2_ckpt65r_20151221, ctrb_darwin2_ckpt66i_20170718, ctrb_darwin2_ckpt66l_20171025, ctrb_darwin2_ckpt66m_20171213, HEAD
Changes since 1.2: +7 -10 lines
Ben Ward - some superficial structural changes allowing runs with no pfts
         - more significant structural and parameter changes to follow later

1 benw 1.3 C $Header: /u/gcmpack/MITgcm_contrib/darwin2/pkg/quota/geider98.F,v 1.2 2012/07/02 09:44:24 benw Exp $
2 benw 1.2 C $Name: $
3 jahn 1.1
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 benw 1.2 #ifdef QUOTA_DIAG_LIMIT
24     O Ilim,
25     #endif
26 jahn 1.1 I up_inorg,
27 benw 1.2 O PP,
28 jahn 1.1 I photo_Tempfunction,
29     O dchldt, ! chlorophyll synthesis rate
30     I myThid)
31     IMPLICIT NONE
32    
33     #ifdef ALLOW_QUOTA
34     #include "QUOTA_SIZE.h"
35     #include "QUOTA.h"
36     #else
37     #include "MONOD_SIZE.h"
38     #include "MONOD.h"
39     #endif
40     c
41     INTEGER myThid
42     INTEGER ii,jp
43     c
44     _RL PARlocal
45     _RL biomass(iomax,npmax)
46     _RL qlimit(npmax)
47     _RL felimit(npmax)
48     _RL alpha_fe
49     _RL up_inorg(iimax,npmax)
50     _RL photo_Tempfunction
51     c
52     _RL dchldt(npmax)
53     c
54     _RL E0
55     _RL C_biomass
56     _RL chl
57     c
58     _RL Chl2C
59     _RL PCmax
60     _RL PCPhot(npmax)
61     _RL rhochl
62     _RL chlsynth(npmax)
63     _RL VCN
64 benw 1.2 _RL PP
65     #ifdef QUOTA_DIAG_LIMIT
66     _RL Ilim(npmax)
67     #endif
68 jahn 1.1 c
69     c Geider, MacIntyre and Kana (1998) photosynthesis model
70     c adapted for multiple nutrients following Moore et al (2002)
71     c
72     E0 = PARlocal ! muEin m^-2 s^-1
73 benw 1.2 PP = 0.0 _d 0
74 jahn 1.1 do jp=1,npmax
75     #ifdef FQUOTA
76     alpha_fe = alphachl(jp) * felimit(jp)
77     #else
78     alpha_fe = alphachl(jp)
79     #endif
80     if (autotrophy(jp).gt.0. _d 0) then
81     C_biomass = biomass(iCarb,jp) ! mmol C m^-3
82     chl = biomass(iChlo,jp) ! mg Chl m^-3
83     c
84     c N uptake is sum of NO3, NO2 and NH4 uptake
85     VCN = 0.0 _d 0
86     do ii=2,iimax
87     if (ii.eq.iNO3.or.ii.eq.iNO2.or.ii.eq.iNH4) then
88     VCN = VCN + up_inorg(ii,jp) ! mmol N (mmol C)^-1 s^-1
89     endif
90     enddo
91     c
92     c-----------------------------------------------------------------
93     if (E0.gt.1. _d -1 .and.
94     & vmaxi(iDIC,jp).gt.0. _d 0 .and.
95     & C_biomass.gt.0. _d 0 .and.
96     & chl.gt.0. _d 0) then
97     Chl2C = chl / C_biomass ! mg chl (mmol C)^-1
98     c
99     PCmax = vmaxi(iDIC,jp) ! s^-1
100     & * qlimit(jp)
101     & * photo_Tempfunction
102     c
103     if (PCmax.gt.0. _d 0.and.alpha_fe.gt.0. _d 0) then
104     PCPhot(jp) = PCmax ! s^-1
105 benw 1.3 & *(1. _d 0 - exp(-alpha_fe*Chl2C*E0/PCmax))
106 jahn 1.1 c
107     rhochl = Chl2Nmax * PCPhot(jp) ! mg chl (mmol N)^-1
108     & /(alphachl(jp)*Chl2C*E0)
109     chlsynth(jp) = rhochl * VCN * C_biomass ! mg chl m^-3 s^-1
110     else
111     PCPhot(jp) = 0. _d 0 ! s^-1
112     chlsynth(jp) = 0. _d 0 ! mg chl m^-3 s^-1
113     endif
114     c
115     else ! else if insufficient light, max phot=0 or C biomass=0...
116     PCPhot(jp) = 0. _d 0 ! s^-1
117     chlsynth(jp) = 0. _d 0 ! mg chl m^-3 s^-1
118     endif
119     c-----------------------------------------------------------------
120     ! for passing back to quota_plankton
121 benw 1.2 PP = PP + PCPhot(jp) * C_biomass
122 jahn 1.1 up_inorg(iDIC,jp) = PCPhot(jp) - biosynth*VCN ! s^-1
123     dchldt(jp) = chlsynth(jp) ! mg chl m^-3 s^-1
124     else ! else if jp is a heterotroph
125     up_inorg(iDIC,jp) = 0. _d 0 ! s^-1
126     dchldt(jp) = 0. _d 0 ! mg chl m^-3 s^-1
127     c-----------------------------------------------------------------
128     endif
129 benw 1.3 #ifdef QUOTA_DIAG_LIMIT
130     Ilim(jp) = 1. _d 0 - exp(-alphachl(jp)*1.59*E0/vmaxi(iDIC,jp))
131     #endif
132     ! print*,"vmax",PP,PCPhot(jp),biomass(iCarb,jp),
133     ! & E0,vmaxi(iDIC,jp),chl,C_biomass
134 jahn 1.1 enddo
135    
136     RETURN
137     END
138     c
139     #endif /*DYNCHL*/
140     #endif /*GEIDER*/
141     #endif /*ALLOW_DARWIN*/
142     #endif /*ALLOW_PTRACERS*/
143     C ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22