/[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.2 - (hide annotations) (download)
Thu Jun 28 20:36:11 2012 UTC (13 years ago) by stephd
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt64a_20121116, ctrb_darwin2_ckpt63o_20120629, ctrb_darwin2_ckpt64e_20130305, ctrb_darwin2_ckpt63s_20120908, ctrb_darwin2_ckpt63r_20120817, ctrb_darwin2_ckpt64c_20130120, ctrb_darwin2_ckpt63p_20120707, ctrb_darwin2_ckpt63q_20120731, ctrb_darwin2_ckpt64b_20121224, ctrb_darwin2_ckpt64d_20130219, ctrb_darwin2_ckpt64_20121012
Changes since 1.1: +17 -0 lines
o add temperature dependencies for mortality (default to no dependence - need to
  change comments in monod_tempfunc to enable)

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

  ViewVC Help
Powered by ViewVC 1.1.22