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

Annotation of /MITgcm_contrib/darwin2/pkg/monod/monod_tempfunc.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_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
2     #include "CPP_OPTIONS.h"
3     #include "PTRACERS_OPTIONS.h"
4     #include "DARWIN_OPTIONS.h"
5    
6     #ifdef ALLOW_PTRACERS
7     #ifdef ALLOW_MONOD
8    
9     c ====================================================================
10     c SUBROUTINE MONOD_TEMPFUNC
11     c ====================================================================
12    
13     SUBROUTINE MONOD_TEMPFUNC(
14     I Tlocal,
15     O phytoTempFunction,
16     #ifndef QUOTA
17     O zooTempFunction,
18     #endif
19     O reminTempFunction,
20     I myThid)
21    
22     implicit none
23     #ifdef QUOTA
24     #include "QUOTA_SIZE.h"
25     #include "QUOTA.h"
26     #else
27     #include "MONOD_SIZE.h"
28     #include "MONOD.h"
29     #endif
30     #include "DARWIN_PARAMS.h"
31    
32     C !INPUT PARAMETERS: ===================================================
33     C myThid :: thread number
34     INTEGER myThid
35     _RL phytoTempFunction(npmax)
36     #ifndef QUOTA
37     _RL zooTempFunction(nzmax)
38     #endif
39     _RL reminTempFunction
40     _RL Tlocal
41    
42     c local
43     _RL Tkel
44     _RL TempAe, Tempref, TempCoeff
45     INTEGER np, nz
46    
47     c TEMP_VERSION 1 used in Follows et al (2007) - without max of 1
48     c TEMP_VERSION 1 used in Dutkiewicz et al (2009), Hickman et al,
49     c Monteiro etal, Barton et al
50     c TEMP_RANGE gives all phyto a specific temperature range
51     c if undefined, then full Eppley/Arrenhius curve used
52     c
53     #if TEMP_VERSION == 1
54     c ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
55     c +++++++++++++++++++ VERSION 1 +++++++++++++++++++++++++++++++++++++++
56     c steph's version 1 (pseudo-Eppley)
57     c plankton growth function (unitless)
58     do np=1, npmax
59     cswd -- this gives Eppley curve only
60     phytoTempFunction(np) =
61     & (phytoTempExp1(np)**Tlocal)
62     #ifdef TEMP_RANGE
63     cswd -- temperature range
64     phytoTempFunction(np) = phytoTempFunction(np) *
65     & (exp(- phytoTempExp2(np)*
66     & (abs(Tlocal - phytoTempOptimum(np)))**
67     & phytoDecayPower(np)))
68     #endif
69     phytoTempFunction(np) = phytoTempFunction(np) - tempnorm
70     phytoTempFunction(np) = phytoTempCoeff(np)*
71     & max(phytoTempFunction(np), 1. _d -10)
72     phytoTempFunction(np) = min(phytoTempFunction(np),1. _d 0)
73     enddo
74     #ifndef QUOTA
75     do nz = 1,nzmax
76     c zooTempFunction(nz) = zooTempCoeff(nz)*EXP(
77     c & zooTempExp(nz)*(Tlocal - zooTempOptimum(nz)))
78     zooTempFunction(nz) = 1.0 _d 0
79     end do
80     #endif
81     reminTempFunction = 1.0 _d 0
82     c ++++++++++++++ END VERSION 1 +++++++++++++++++++++++++++++++++++++++
83     c++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
84     #elif TEMP_VERSION == 2
85     c ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
86     c +++++++++++++++++++ VERSION 2 +++++++++++++++++++++++++++++++++++++++
87     c steph's version 2 (pseudo-Arrenhius)
88     Tkel=273.15 _d 0
89     TempAe=-4000. _d 0
90     Tempref=293.15 _d 0
91     tempnorm= 0. _d 0
92     TempCoeff=0.5882 _d 0
93     do np=1, npmax
94     phytoTempCoeff(np) = TempCoeff
95     cswd -- this gives Arrenhius curve only
96     phytoTempFunction(np) =
97     & exp(TempAe*(1. _d 0/(Tlocal+Tkel) -
98     & 1. _d 0/(Tempref) ) )
99     #ifdef TEMP_RANGE
100     cswd -- temperature range
101     phytoTempFunction(np) = phytoTempFunction(np) *
102     & (exp(- phytoTempExp2(np)*
103     & (abs(Tlocal - phytoTempOptimum(np)))**
104     & phytoDecayPower(np)))
105     #endif
106     phytoTempFunction(np) = phytoTempFunction(np) - tempnorm
107     phytoTempFunction(np) = phytoTempCoeff(np)*
108     & max(phytoTempFunction(np), 1. _d -10)
109     enddo
110     #ifndef QUOTA
111     do nz = 1,nzmax
112     zooTempFunction(nz) =
113     & exp(TempAe*(1/(Tlocal+Tkel) -
114     & 1/(Tempref) ) )
115     zooTempFunction(nz) = zooTempFunction(nz) - tempnorm
116     zooTempFunction(nz) = TempCoeff*
117     & max(zooTempFunction(nz), 1. _d -10)
118     c zooTempFunction(nz) = 1. _d 0
119     end do
120     #endif
121     reminTempFunction = exp(TempAe*(1/(Tlocal+Tkel) -
122     & 1/(Tempref) ) )
123     reminTempFunction = reminTempFunction - tempnorm
124     reminTempFunction = TempCoeff*
125     & max(reminTempFunction, 1. _d -10)
126     c reminTempFunction = 1. _d 0
127     c ++++++++++++++ END VERSION 2 +++++++++++++++++++++++++++++++++++++++
128     c++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
129     #else
130     #error "TEMP_VERSION must be 1 or 2. Define in DARWIN_OPTIONS.h"
131     #endif
132     c
133     c ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
134     c +++++++++++++++++++ NO TEMP LIMITATION +++++++++++++++++++++++++++++
135     #ifdef NOTEMP
136     do np=1, npmax
137     phytoTempFunction(np) = 1.0 _d 0
138     enddo
139     #ifndef QUOTA
140     do nz = 1,nzmax
141     zooTempFunction(nz) = 1.0 _d 0
142     end do
143     #endif
144     reminTempFunction = 1.0 _d 0
145     #endif
146     c +++++++++++++ END NO TEMP LIMITATION +++++++++++++++++++++++++++++
147     c ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
148     c
149    
150     RETURN
151     END
152     #endif /*MONOD*/
153     #endif /*ALLOW_PTRACERS*/
154     c ==================================================================

  ViewVC Help
Powered by ViewVC 1.1.22