ROMS
Loading...
Searching...
No Matches
oyster_floats.h
Go to the documentation of this file.
1#undef GROWTH_ONLY
2
4!
5!git $Id$
6!================================================== Hernan G. Arango ===
7! Copyright (c) 2002-2025 The ROMS Group Diego A. Narvaez !
8! Licensed under a MIT/X style license !
9! See License_ROMS.md !
10!=======================================================================
11! !
12! This routine sets behavior for Lagrangian particles that simulates !
13! planktonic larvae. The planktonic behavior is based on the model !
14! of Dekshenieks et al. (1993; 1996; 1997). It calculates the size !
15! (length) and development of oyster larvae. Results about this model !
16! can be found in Narvaez et al. 2012 a,b (in review) !
17! !
18! The governing equation are: !
19! !
20! d(Lsize)/d(t) = growth(food,Lsize) * Gfactor(T,S) * turb_ef !
21! !
22! w_bio = TS * SW - (1 - TS) * SR !
23! !
24! where !
25! !
26! turbef = m * turb + c, for turbidity < 0.1 g/l !
27! or !
28! turbef = b * EXP(-beta*(turb-turb0)), for turbidity > 0.1 g/l !
29! !
30! TS = c * DS + d, for increasing salinity gradient DS !
31! or !
32! TS = -e * DS + f, for decreasing salinity gradient DS !
33! !
34! SR = 2.665 * EXP(0.0058*(Lsize-220)) !
35! !
36! TS: fraction of active larvae: fractional swimming time !
37! SW: larval swimming rate (mm/s) !
38! SR: larval sinking rate (mm/s) !
39! DS: salinity change rate (1/s) !
40! !
41! References: !
42! !
43! Dekshenieks, M.M., E.E. Hofmann, and E.N. Powell, 1993: !
44! Environmental effect on the growth and development of !
45! Eastern oyster, Crassostrea virginica (Gmelin, 1791), !
46! larvae: A modeling study, J. Shelfish Res, 12, 241-254. !
47! !
48! Dekshenieks, M.M., E.E. Hofmann, J.M. Klinck, and E.N. !
49! Powell, 1996: Modeling the vertical distribution of !
50! oyster larvae in response to environmental conditions, !
51! Mar. Ecol. Prog. Ser., 136, 97-110. !
52! !
53! Dekshenicks, M.M., E.E. Hofmann, J.M. Klinck, and E.N. !
54! Powell, 1997: A modeling study of the effect of size- !
55! and depth_dependent predation on larval survival, J. !
56! Plankton Res., 19, (11), 1583-1598. !
57! !
58! Narvaez, D.A, J.M. Klinck, E.N. Powell, E.E. Hofmann, J. Wilkin !
59! and D. B. Haidvogel. Modeling the dispersal of Eastern !
60! oyster (Crassostrea virginica) larvae in Delaware Bay, J. Mar. !
61! Res., in review. !
62! !
63! Narvaez, D.A, J.M. Klinck, E.N. Powell, E.E. Hofmann, J. Wilkin !
64! and D. B. Haidvogel. Circulation and behavior controls on !
65! dispersal of Eastern oyster (Crassostrea virginica) larvae in !
66! Delaware Bay, J. Mar. Res., in review. !
67! !
68!=======================================================================
69!
70 implicit none
71!
72 PRIVATE
73 PUBLIC :: biology_floats
74!
75 CONTAINS
76!
77!***********************************************************************
78 SUBROUTINE biology_floats (ng, Lstr, Lend, Predictor, my_thread)
79!***********************************************************************
80!
81 USE mod_param
82 USE mod_floats
83 USE mod_stepping
84!
85! Imported variable declarations.
86!
87 integer, intent(in) :: ng, lstr, lend
88
89 logical, intent(in) :: predictor
90#ifdef ASSUMED_SHAPE
91 logical, intent(in) :: my_thread(lstr:)
92#else
93 logical, intent(in) :: my_thread(lstr:lend)
94#endif
95!
96! Local variable declarations.
97!
98 character (len=*), parameter :: myfile = &
99 & __FILE__
100!
101#ifdef PROFILE
102 CALL wclock_on (ng, inlm, 10, __line__, myfile)
103#endif
104 CALL oyster_floats_tile (ng, lstr, lend, &
105 & nfm3(ng), nfm2(ng), nfm1(ng), nf(ng), &
106 & nfp1(ng), &
107 & predictor, my_thread, &
108 & drifter(ng) % bounded, &
109 & drifter(ng) % Tinfo, &
110 & drifter(ng) % track)
111#ifdef PROFILE
112 CALL wclock_off (ng, inlm, 10, __line__, myfile)
113#endif
114!
115 RETURN
116 END SUBROUTINE biology_floats
117!
118!***********************************************************************
119 SUBROUTINE oyster_floats_tile (ng, Lstr, Lend, &
120 & nfm3, nfm2, nfm1, nf, nfp1, &
121 & Predictor, my_thread, bounded, &
122 & Tinfo, track)
123!***********************************************************************
124!
125 USE mod_param
126 USE mod_parallel
127 USE mod_behavior
128#ifdef BIOLOGY
129 USE mod_biology
130#endif
131 USE mod_floats
132 USE mod_grid
133 USE mod_iounits
134 USE mod_scalars
135!
136! Imported variable declarations.
137!
138 integer, intent(in) :: ng, Lstr, Lend
139 integer, intent(in) :: nfm3, nfm2, nfm1, nf, nfp1
140 logical, intent(in) :: Predictor
141!
142#ifdef ASSUMED_SHAPE
143 logical, intent(in) :: bounded(:)
144 logical, intent(in) :: my_thread(Lstr:)
145
146 real(r8), intent(in) :: Tinfo(0:,:)
147 real(r8), intent(inout) :: track(:,0:,:)
148#else
149 logical, intent(in) :: bounded(Nfloats(ng))
150 logical, intent(in) :: my_thread(Lstr:Lend)
151
152 real(r8), intent(in) :: Tinfo(0:izrhs,Nfloats(ng))
153 real(r8), intent(inout) :: track(NFV(ng),0:NFT,Nfloats(ng))
154#endif
155!
156! Local variable declarations.
157!
158 integer :: i, i1, i2, j1, j2, l
159
160 real(r8) :: dsalt, temp, salt
161 real(r8) :: Lfood, Lturb, Lsize, LsizeNew
162 real(r8) :: Grate, Gfactor, turb_ef
163 real(r8) :: SwimRate, SwimTime, SwimTimeNew
164 real(r8) :: bottom, brhs, sink, w_bio
165 real(r8) :: cff1, cff2, cff3, cff4
166 real(r8) :: p1, p2, q1, q2
167 real(r8) :: my_food, my_salt, my_size, my_temp
168 real(r8) :: oGfactor_DS, oGfactor_DT
169 real(r8) :: oGrate_DF, oGrate_DL
170 real(r8) :: oswim_DL, oswim_DT
171 real(r8) :: HalfDT
172!
173!-----------------------------------------------------4-----------------
174! Estimate larval growth, as length (um), based on food, salinity,
175! temperature and turbidity. Then, estimate swimming time (s),
176! larvae sinking velocity (m/s) and larvae vertical velocity (m/s).
177!-----------------------------------------------------------------------
178!
179! Compute look tables inverse axis increments to avoid repetitive
180! divisions.
181!
182 ograte_df=1.0_r8/grate_df
183 ograte_dl=1.0_r8/grate_dl
184
185 ogfactor_ds=1.0_r8/gfactor_ds
186 ogfactor_dt=1.0_r8/gfactor_dt
187
188 oswim_dt=1.0_r8/swim_dt
189 oswim_dl=1.0_r8/swim_dl
190!
191! Assign predictor/corrector weights.
192!
193 IF (predictor) THEN
194 cff1=8.0_r8/3.0_r8
195 cff2=4.0_r8/3.0_r8
196 ELSE
197 cff1=9.0_r8/8.0_r8
198 cff2=1.0_r8/8.0_r8
199 cff3=3.0_r8/8.0_r8
200 cff4=6.0_r8/8.0_r8
201 END IF
202!
203! Compute biological behavior fields.
204!
205 halfdt=0.5_r8*dt(ng)
206
207 DO l=lstr,lend
208 IF (my_thread(l).and.bounded(l)) THEN
209!
210! If newly relased float, initialize biological behavior fields. Note
211! that since we need temperature and salinity, we need to initialize
212! their values to all time levels. Otherwise, we will have a parallel
213! bug.
214!
215 IF (time(ng)-halfdt.le.tinfo(itstr,l).and. &
216 & time(ng)+halfdt.gt.tinfo(itstr,l)) THEN
217 temp=track(iftvar(itemp),nfp1,l)
218 salt=track(iftvar(isalt),nfp1,l)
219 DO i=0,nft
220 track(isizf,i,l)=larvae_size0(ng)
221 track(iswim,i,l)=0.5_r8*(swim_tmin(ng)+swim_tmax(ng))
222 track(iftvar(itemp),i,l)=temp
223 track(iftvar(isalt),i,l)=salt
224 END DO
225 END IF
226!
227! Get temperature, salinity, larvae size (length), swimming time, and
228! food supply. For now, assume constant food and turbidity. This
229! can be changed in the future with spatial and temporal variability
230! for food and/or turbidity. If this is the case, we need to have
231! something like:
232!
233! IF (Predictor) THEN
234! Lfood=track(ifood,nf,l)
235! Lturb=track(iturb,nf,l)
236! ...
237! ELSE
238! Lfood=track(ifood,nfp1,l)
239! Lturb=track(iturb,nfp1,l)
240! ...
241! END IF
242!
243! The food variability may be from data, ecosystem model, or analytical
244! functions. Similarly, the turbidity may be from data, sediment model,
245! or analytical functions.
246!
247 temp=track(iftvar(itemp),nfp1,l)
248 salt=track(iftvar(isalt),nfp1,l)
249 dsalt=track(iftvar(isalt),nfp1,l)- &
250 & track(iftvar(isalt),nf ,l)
251 IF (predictor) THEN
252 lsize=track(isizf,nf,l)
253 swimtime=track(iswim,nf,l)
254 lfood=food_supply(ng)
255 lturb=turb_ambi(ng)
256 ELSE
257 lsize=track(isizf,nfp1,l)
258 swimtime=track(iswim,nfp1,l)
259 lfood=food_supply(ng)
260 lturb=turb_ambi(ng)
261 END IF
262!
263! Determine larval growth rate (um/day) contribution as function of
264! food supply (mg_Carbon/l) and larval size (um). Linearly interpolate
265! growth rate from the look table of food concentration versus larval
266! size. Notice that extrapolation is suppresed by bounding "Lfood" and
267! "Lsize" to the range values in the look table.
268!
269 my_food=min(max(grate_f0,lfood), &
270 & grate_f0+grate_df*real(grate_im-1,r8))
271 my_size=min(max(grate_l0,lsize), &
272 & grate_l0+grate_dl*real(grate_jm-1,r8))
273
274 i1=int(1.0_r8+(my_food-grate_f0)*ograte_df)
275 i2=min(i1+1,grate_im)
276 j1=int(1.0_r8+(my_size-grate_l0)*ograte_dl)
277 j2=min(j1+1,grate_jm)
278
279 p2=(my_food-(grate_f0+real(i1-1,r8)*grate_df))*ograte_df
280 q2=(my_size-(grate_l0+real(j1-1,r8)*grate_dl))*ograte_dl
281 p1=1.0_r8-p2
282 q1=1.0_r8-q2
283
284 grate=p1*q1*grate_table(i1,j1)+ &
285 & p2*q1*grate_table(i2,j1)+ &
286 & p1*q2*grate_table(i1,j2)+ &
287 & p2*q2*grate_table(i2,j2)
288!
289! Determine larval growth rate factor (nondimensional) as function of
290! salinity and temperature (Celsius). Linearly interpolate growth rate
291! factor from the look table of salinity versus temperature. Notice
292! that extrapolation is suppresed by bounding "salt" and "temp" to the
293! range values in the look table.
294!
295 IF (temp.lt.gfactor_t0) THEN
296 gfactor=0.0_r8
297 ELSE
298 my_salt=min(max(gfactor_s0,salt), &
299 & gfactor_s0+gfactor_ds*real(gfactor_im-1,r8))
300 my_temp=min(max(gfactor_t0,temp), &
301 & gfactor_t0+gfactor_dt*real(gfactor_jm-1,r8))
302
303 i1=int(1.0_r8+(my_salt-gfactor_s0)*ogfactor_ds)
304 i2=min(i1+1,gfactor_im)
305 j1=int(1.0_r8+(my_temp-gfactor_t0)*ogfactor_dt)
306 j2=min(j1+1,gfactor_jm)
307
308 p2=(my_salt-(gfactor_s0+real(i1-1,r8)*gfactor_ds))* &
309 & ogfactor_ds
310 q2=(my_temp-(gfactor_t0+real(j1-1,r8)*gfactor_dt))* &
311 & ogfactor_dt
312 p1=1.0_r8-p2
313 q1=1.0_r8-q2
314
315 gfactor=p1*q1*gfactor_table(i1,j1)+ &
316 & p2*q1*gfactor_table(i2,j1)+ &
317 & p1*q2*gfactor_table(i1,j2)+ &
318 & p2*q2*gfactor_table(i2,j2)
319 END IF
320!
321! Determine turbidity effect (linear or exponential) on larval growth.
322! Then, compute new larvae size (um) as function of growth rate (um/s)
323! which is loaded in track(ibrhs,:,:).
324!
325 IF (lsize.gt.turb_size(ng)) THEN
326 IF (lturb.gt.turb_crit(ng)) THEN
327 turb_ef=turb_base(ng)* &
328 & exp(-turb_rate(ng)*(lturb-turb_mean(ng)))
329 ELSE
330 turb_ef=turb_slop(ng)*lturb+turb_axis(ng)
331 END IF
332 track(ibrhs,nfp1,l)=grate*gfactor*turb_ef*sec2day
333 ELSE
334 track(ibrhs,nfp1,l)=larvae_gr0(ng)*gfactor*sec2day
335 END IF
336 IF (predictor) THEN
337 track(isizf,nfp1,l)=track(isizf,nfm3,l)+ &
338 & dt(ng)*(cff1*track(ibrhs,nf ,l)- &
339 & cff2*track(ibrhs,nfm1,l)+ &
340 & cff1*track(ibrhs,nfm2,l))
341 ELSE
342 track(isizf,nfp1,l)=cff1*track(isizf,nf ,l)- &
343 & cff2*track(isizf,nfm2,l)+ &
344 & dt(ng)*(cff3*track(ibrhs,nfp1,l)+ &
345 & cff4*track(ibrhs,nf ,l)- &
346 & cff3*track(ibrhs,nfm1,l))
347 END IF
348 lsize=track(isizf,nfp1,l)
349!
350! Estimate the fraction of time that the larvae spend swimming.
351!
352 IF (abs(dsalt).lt.0.00001_r8) THEN
353 dsalt=0.0_r8
354 END IF
355 IF (dsalt.gt.0.0_r8) THEN
356 swimtimenew=min(swimtime+dsalt*slope_sinc(ng),swim_tmax(ng))
357 ELSE
358 swimtimenew=max(swimtime+dsalt*slope_sdec(ng),swim_tmin(ng))
359 END IF
360!
361! Compute swim behavior as function of larval size and temperature.
362! Linearly interpolate swimming rate (mm/s) from the look table of
363! larval size (um) versus temperature (Celsius). Notice that
364! extrapolation is suppresed by bounding "Lsize" and "temp" to
365! the range values in the look table.
366!
367 IF ((temp.lt.swim_t0).or.(lsize.lt.swim_l0)) THEN
368 swimrate=0.0_r8
369 ELSE
370 my_size=min(max(swim_l0,lsize), &
371 & swim_l0+swim_dl*real(swim_im-1,r8))
372 my_temp=min(max(swim_t0,temp), &
373 & swim_t0+swim_dt*real(swim_jm-1,r8))
374
375 i1=int(1.0_r8+(my_size-swim_l0)*oswim_dl)
376 i2=min(i1+1,swim_im)
377 j1=int(1.0_r8+(my_temp-swim_t0)*oswim_dt)
378 j2=min(j1+1,swim_jm)
379
380 p2=(my_size-(swim_l0+real(i1-1,r8)*swim_dl))*oswim_dl
381 q2=(my_temp-(swim_t0+real(j1-1,r8)*swim_dt))*oswim_dt
382 p1=1.0_r8-p2
383 q1=1.0_r8-q2
384
385 swimrate=p1*q1*swim_table(i1,j1)+ &
386 & p2*q1*swim_table(i2,j1)+ &
387 & p1*q2*swim_table(i1,j2)+ &
388 & p2*q2*swim_table(i2,j2)
389
390 swimrate=swimrate*0.001_r8 ! convert from mm/s to m/s
391 END IF
392!
393! Compute larvae sinking velocity (m/s).
394!
395 sink=sink_base(ng)*(exp(sink_rate(ng)*(lsize-sink_size(ng))))
396
397 sink=sink*0.001_r8 ! convert from mm/s to m/s
398!
399! Compute larvae vertical velocity (m/s).
400!
401#ifdef GROWTH_ONLY
402 w_bio=0.0_r8
403#else
404 w_bio=swimtime*swimrate-(1.0_r8-swimtime)*sink
405#endif
406!
407! Load behavior into track array. Apply settlement condition: larvae
408! greater or equal than SETTLE_SIZE, settle on the bottom.
409!
410 IF (track(isizf,nfp1,l).lt.settle_size(ng)) THEN
411 track(iwbio,nfp1,l)=w_bio
412 track(iwsin,nfp1,l)=sink
413 track(iswim,nfp1,l)=swimtimenew
414 ELSE
415 i1=min(max(0,int(track(ixgrd,nfp1,l))),lm(ng)+1)
416 i2=min(i1+1,lm(ng)+1)
417 j1=min(max(0,int(track(iygrd,nfp1,l))),mm(ng)+1)
418 j2=min(j1+1,mm(ng)+1)
419
420 p2=real(i2-i1,r8)*(track(ixgrd,nfp1,l)-real(i1,r8))
421 q2=real(j2-j1,r8)*(track(iygrd,nfp1,l)-real(j1,r8))
422 p1=1.0_r8-p2
423 q1=1.0_r8-q2
424
425 bottom=p1*q1*grid(ng)%h(i1,j1)+ &
426 & p2*q1*grid(ng)%h(i2,j1)+ &
427 & p1*q2*grid(ng)%h(i1,j2)+ &
428 & p2*q2*grid(ng)%h(i2,j2)
429
430 track(idpth,nfp1,l)=-bottom
431 track(isizf,nfp1,l)=track(isizf,nf,l)
432 track(iwbio,nfp1,l)=0.0_r8
433 track(iwsin,nfp1,l)=0.0_r8
434 track(iswim,nfp1,l)=0.0_r8
435 END IF
436!
437! If newly relased float, set vertical migration fields for all time
438! levels.
439!
440 IF (time(ng)-halfdt.le.tinfo(itstr,l).and. &
441 & time(ng)+halfdt.gt.tinfo(itstr,l)) THEN
442 brhs=track(ibrhs,nfp1,l)
443 sink=track(iwsin,nfp1,l)
444 w_bio=track(iwbio,nfp1,l)
445 DO i=0,nft
446 track(ibrhs,i,l)=brhs
447 track(iwsin,i,l)=sink
448 track(iwbio,i,l)=w_bio
449 END DO
450 END IF
451
452 END IF
453 END DO
454!
455 RETURN
456 END SUBROUTINE oyster_floats_tile
457
458 END MODULE biology_floats_mod
subroutine oyster_floats_tile(ng, lstr, lend, nfm3, nfm2, nfm1, nf, nfp1, predictor, my_thread, bounded, tinfo, track)
subroutine, public biology_floats(ng, lstr, lend, predictor, my_thread)
real(r8), dimension(:), allocatable food_supply
real(r8), dimension(:), allocatable turb_base
real(r8), dimension(:), allocatable larvae_gr0
real(r8), dimension(:), allocatable turb_crit
real(r8), dimension(:), allocatable turb_rate
real(r8), dimension(:), allocatable swim_tmin
real(r8), dimension(:,:), allocatable swim_table
real(r8), dimension(:), allocatable sink_size
real(r8), dimension(:), allocatable slope_sinc
real(r8), dimension(:), allocatable turb_slop
real(r8), dimension(:), allocatable turb_mean
real(r8), dimension(:), allocatable settle_size
real(r8), dimension(:), allocatable swim_tmax
real(r8), dimension(:), allocatable larvae_size0
real(r8), dimension(:,:), allocatable grate_table
real(r8), dimension(:), allocatable turb_ambi
real(r8), dimension(:), allocatable turb_axis
real(r8), dimension(:), allocatable slope_sdec
real(r8), dimension(:), allocatable sink_rate
real(r8), dimension(:), allocatable turb_size
real(r8), dimension(:,:), allocatable gfactor_table
real(r8), dimension(:), allocatable sink_base
integer, parameter ibrhs
Definition mod_floats.F:99
integer, parameter idpth
Definition mod_floats.F:86
integer, parameter iwbio
Definition mod_floats.F:101
integer, parameter isizf
Definition mod_floats.F:98
integer, parameter iygrd
Definition mod_floats.F:82
integer, dimension(:), allocatable iftvar
Definition mod_floats.F:116
integer, parameter iswim
Definition mod_floats.F:100
integer, parameter itstr
Definition mod_floats.F:80
integer, parameter ixgrd
Definition mod_floats.F:81
type(t_drifter), dimension(:), allocatable drifter
Definition mod_floats.F:67
integer, parameter iwsin
Definition mod_floats.F:102
type(t_grid), dimension(:), allocatable grid
Definition mod_grid.F:365
integer, parameter inlm
Definition mod_param.F:662
integer, dimension(:), allocatable lm
Definition mod_param.F:455
integer, dimension(:), allocatable mm
Definition mod_param.F:456
real(dp), dimension(:), allocatable dt
real(dp), parameter sec2day
integer isalt
integer itemp
real(dp), dimension(:), allocatable time
integer, dimension(:), allocatable nfm2
integer, dimension(:), allocatable nfm1
integer, dimension(:), allocatable nf
integer, dimension(:), allocatable nfm3
integer, dimension(:), allocatable nfp1
recursive subroutine wclock_off(ng, model, region, line, routine)
Definition timers.F:148
recursive subroutine wclock_on(ng, model, region, line, routine)
Definition timers.F:3