ROMS
Loading...
Searching...
No Matches
red_tide_mod.h
Go to the documentation of this file.
1 MODULE mod_biology
2!
3!git $Id$
4!================================================== Hernan G. Arango ===
5! Copyright (c) 2002-2025 The ROMS Group !
6! Licensed under a MIT/X style license !
7! See License_ROMS.md !
8!=======================================================================
9! !
10! Parameters for Powell et al. (2006) ecosystem model with iron !
11! limitation: !
12! !
13! AttS Mean light diffuse attenuation coefficient in the !
14! sediment (1/m) !
15! AttW Mean light diffuse attenuation coefficient in the !
16! water column (1/m) !
17! DIN_Cdepth Constant Dissolved Inorganic Nutrient concentration !
18! below of growth crical depth (millimole/m3) !
19! Dg Mean depth (m) of sediment over which cysts are able !
20! to germinate and contribute to the bloom !
21! E_dark Light level for germination under dark conditions !
22! (watt/m2) !
23! E_light Light level for germination under "light" conditions !
24! (Watt/m2) !
25! Gmax Maximum growth rate at optimal temperature and salinty !
26! (1/day) !
27! G_eff Growth efficiency (m2/Watts/day) !
28! G_r Maintanenance respiration rate (1/day) !
29! Kn Half-saturation constant for nutrient limited growth !
30! (millimoles/m3) !
31! Mor_a Mortality rate equation, Q10 amplitude term (1/day) !
32! Mor_b Mortality rate equation, Q10 intercept term (1/day) !
33! Mor_Q10 Mortality rate equation, Q10 reaction rate base !
34! Mor_T0 Mortality rate equation, Q10 background temperature (C)!
35! Tmin_growth Coldest temperature limit used to compute temperature- !
36! dependent growth factor from cubic polynomial fit !
37! based on available data (Celsius) !
38! srad_Cdepth Averaged solar shortwave radiation used to compute !
39! critical depth in the growth function (Watts/m2) !
40! wDino Dinoflagellate (Alexandrium Fundyense) vertical !
41! swimming rate (positive; m/day) !
42! !
43!=======================================================================
44!
45 USE mod_param
46!
47 implicit none
48!
49! Set biological tracer identification indices.
50!
51 integer, allocatable :: idbio(:) ! Biological tracers
52 integer :: idasrf ! Averaged shortwave radiation
53 integer :: idcyst ! Bottom cyst concentration
54 integer :: idodin ! Dissolved Inorganic Nutrient
55 integer :: idino ! Dinoflagellate concentration
56!
57! Biological parameters.
58!
59 integer, allocatable :: bioiter(:)
60
61
62 real(r8), allocatable :: atts(:) ! 1/m
63 real(r8), allocatable :: attw(:) ! 1/m
64 real(r8), allocatable :: din_cdepth(:) ! millimoles/m3
65 real(r8), allocatable :: dg(:) ! m
66 real(r8), allocatable :: e_dark(:) ! Watts/m2
67 real(r8), allocatable :: e_light(:) ! Watts/m2
68 real(r8), allocatable :: gmax(:) ! 1/day
69 real(r8), allocatable :: g_eff(:) ! m2/Watts/day
70 real(r8), allocatable :: g_r(:) ! 1/day
71 real(r8), allocatable :: kn(:) ! millimoles/m3
72 real(r8), allocatable :: mor_a(:) ! 1/day
73 real(r8), allocatable :: mor_b(:) ! 1/day
74 real(r8), allocatable :: mor_q10(:) ! nondimensional
75 real(r8), allocatable :: mor_t0(:) ! Celsius
76 real(r8), allocatable :: tmin_growth(:) ! Celsius
77 real(r8), allocatable :: srad_cdepth(:) ! Watts/m2
78 real(r8), allocatable :: wdino(:) ! m/day
79!
80! Mid-day of each month (YearDay = 0 for Jan 1, 00:00:00).
81!
82 real(dp), dimension(12) :: month_midday = &
83 & (/ 15.5_dp, 45.0_dp, 74.5_dp, 105.0_dp, &
84 & 135.5_dp, 166.0_dp, 196.5_dp, 227.5_dp, &
85 & 258.0_dp, 288.5_dp, 319.0_dp, 349.5_dp /)
86!
87! Monthly median germination potential.
88!
89 real(r8), dimension(12) :: gp = &
90 & (/ 21.90_r8, 11.25_r8, 78.0_r8, 85.0_r8, &
91 & 96.8_r8, 93.0_r8, 60.0_r8, 50.0_r8, &
92 & 10.0_r8, 11.5_r8, 17.0_r8, 34.5_r8 /)
93!
94! Normalized montly mean germination potential.
95!
96 real(r8), dimension(12) :: gpn
97!
98 CONTAINS
99!
100 SUBROUTINE initialize_biology
101!
102!=======================================================================
103! !
104! This routine sets several variables needed by the biology model. !
105! It allocates and assigns biological tracers indices. !
106! !
107!=======================================================================
108!
109! Local variable declarations
110!
111 integer :: i, ic
112
113 real(r8) :: gpmax
114!
115!-----------------------------------------------------------------------
116! Set number of biological tracers.
117!-----------------------------------------------------------------------
118!
119 nbt=1
120!
121!-----------------------------------------------------------------------
122! Allocate various module variables.
123!-----------------------------------------------------------------------
124!
125 IF (.not.allocated(bioiter)) THEN
126 allocate ( bioiter(ngrids) )
127 dmem(1)=dmem(1)+real(ngrids,r8)
128 END IF
129
130 IF (.not.allocated(atts)) THEN
131 allocate ( atts(ngrids) )
132 dmem(1)=dmem(1)+real(ngrids,r8)
133 END IF
134
135 IF (.not.allocated(attw)) THEN
136 allocate ( attw(ngrids) )
137 dmem(1)=dmem(1)+real(ngrids,r8)
138 END IF
139
140 IF (.not.allocated(din_cdepth)) THEN
141 allocate ( din_cdepth(ngrids) )
142 dmem(1)=dmem(1)+real(ngrids,r8)
143 END IF
144
145 IF (.not.allocated(dg)) THEN
146 allocate ( dg(ngrids) )
147 dmem(1)=dmem(1)+real(ngrids,r8)
148 END IF
149
150 IF (.not.allocated(e_dark)) THEN
151 allocate ( e_dark(ngrids) )
152 dmem(1)=dmem(1)+real(ngrids,r8)
153 END IF
154
155 IF (.not.allocated(e_light)) THEN
156 allocate ( e_light(ngrids) )
157 dmem(1)=dmem(1)+real(ngrids,r8)
158 END IF
159
160 IF (.not.allocated(gmax)) THEN
161 allocate ( gmax(ngrids) )
162 dmem(1)=dmem(1)+real(ngrids,r8)
163 END IF
164
165 IF (.not.allocated(g_eff)) THEN
166 allocate ( g_eff(ngrids) )
167 dmem(1)=dmem(1)+real(ngrids,r8)
168 END IF
169
170 IF (.not.allocated(g_r)) THEN
171 allocate ( g_r(ngrids) )
172 dmem(1)=dmem(1)+real(ngrids,r8)
173 END IF
174
175 IF (.not.allocated(kn)) THEN
176 allocate ( kn(ngrids) )
177 dmem(1)=dmem(1)+real(ngrids,r8)
178 END IF
179
180 IF (.not.allocated(tmin_growth)) THEN
181 allocate ( tmin_growth(ngrids) )
182 dmem(1)=dmem(1)+real(ngrids,r8)
183 END IF
184
185 IF (.not.allocated(srad_cdepth)) THEN
186 allocate ( srad_cdepth(ngrids) )
187 dmem(1)=dmem(1)+real(ngrids,r8)
188 END IF
189
190 IF (.not.allocated(wdino)) THEN
191 allocate ( wdino(ngrids) )
192 dmem(1)=dmem(1)+real(ngrids,r8)
193 END IF
194
195 IF (.not.allocated(mor_a)) THEN
196 allocate ( mor_a(ngrids) )
197 dmem(1)=dmem(1)+real(ngrids,r8)
198 END IF
199
200 IF (.not.allocated(mor_b)) THEN
201 allocate ( mor_b(ngrids) )
202 dmem(1)=dmem(1)+real(ngrids,r8)
203 END IF
204
205 IF (.not.allocated(mor_q10)) THEN
206 allocate ( mor_q10(ngrids) )
207 dmem(1)=dmem(1)+real(ngrids,r8)
208 END IF
209
210 IF (.not.allocated(mor_t0)) THEN
211 allocate ( mor_t0(ngrids) )
212 dmem(1)=dmem(1)+real(ngrids,r8)
213 END IF
214
215#ifdef TANGENT
216 IF (.not.allocated(tl_wdino)) THEN
217 allocate ( tl_wdino(ngrids) )
218 dmem(1)=dmem(1)+real(ngrids,r8)
219 END IF
220#endif
221
222#ifdef ADJOINT
223 IF (.not.allocated(ad_wdino)) THEN
224 allocate ( ad_wdino(ngrids) )
225 dmem(1)=dmem(1)+real(ngrids,r8)
226 END IF
227#endif
228!
229! Allocate biological tracer vector.
230!
231 IF (.not.allocated(idbio)) THEN
232 allocate ( idbio(nbt) )
233 dmem(1)=dmem(1)+real(ngrids,r8)
234 END IF
235!
236!-----------------------------------------------------------------------
237! Initialize tracer identification indices.
238!-----------------------------------------------------------------------
239!
240 ic=nat+npt+ncs+nns
241 DO i=1,nbt
242 idbio(i)=ic+i
243 END DO
244 idino=ic+1
245!
246! Compute normalized montly germination poterntial.
247!
248 gpmax=maxval(gp)
249 DO i=1,12
250 gpn(i)=gp(i)/gpmax
251 END DO
252!
253 RETURN
254 END SUBROUTINE initialize_biology
255
256 END MODULE mod_biology
real(r8), dimension(:), allocatable mor_t0
integer idodin
real(dp), dimension(12) month_midday
integer, dimension(:), allocatable bioiter
Definition ecosim_mod.h:343
real(r8), dimension(:), allocatable e_dark
real(r8), dimension(:), allocatable srad_cdepth
real(r8), dimension(:), allocatable din_cdepth
real(r8), dimension(:), allocatable wdino
real(r8), dimension(:), allocatable mor_q10
real(r8), dimension(12) gp
real(r8), dimension(:), allocatable dg
real(r8), dimension(:), allocatable g_eff
real(r8), dimension(:), allocatable mor_b
real(r8), dimension(:), allocatable e_light
real(r8), dimension(:), allocatable mor_a
integer idino
real(r8), dimension(:), allocatable attw
real(r8), dimension(:), allocatable atts
real(r8), dimension(:), allocatable g_r
real(r8), dimension(:), allocatable kn
subroutine initialize_biology
Definition ecosim_mod.h:499
real(r8), dimension(:), allocatable tmin_growth
real(r8), dimension(12) gpn
integer idcyst
real(r8), dimension(:), allocatable gmax
integer idasrf
integer nat
Definition mod_param.F:499
real(r8), dimension(:), allocatable dmem
Definition mod_param.F:137
integer ncs
Definition mod_param.F:525
integer nbt
Definition mod_param.F:509
integer ngrids
Definition mod_param.F:113
integer nns
Definition mod_param.F:529
integer npt
Definition mod_param.F:505