87 integer,
intent(in) :: ng, lstr, lend
89 logical,
intent(in) :: predictor
91 logical,
intent(in) :: my_thread(lstr:)
93 logical,
intent(in) :: my_thread(lstr:lend)
98 character (len=*),
parameter :: myfile = &
107 & predictor, my_thread, &
120 & nfm3, nfm2, nfm1, nf, nfp1, &
121 & Predictor, my_thread, bounded, &
138 integer,
intent(in) :: ng, Lstr, Lend
139 integer,
intent(in) :: nfm3, nfm2, nfm1, nf, nfp1
140 logical,
intent(in) :: Predictor
143 logical,
intent(in) :: bounded(:)
144 logical,
intent(in) :: my_thread(Lstr:)
146 real(r8),
intent(in) :: Tinfo(0:,:)
147 real(r8),
intent(inout) :: track(:,0:,:)
149 logical,
intent(in) :: bounded(Nfloats(ng))
150 logical,
intent(in) :: my_thread(Lstr:Lend)
152 real(r8),
intent(in) :: Tinfo(0:izrhs,Nfloats(ng))
153 real(r8),
intent(inout) :: track(NFV(ng),0:NFT,Nfloats(ng))
158 integer :: i, i1, i2, j1, j2, l
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
208 IF (my_thread(l).and.bounded(l))
THEN
215 IF (
time(ng)-halfdt.le.tinfo(
itstr,l).and. &
216 &
time(ng)+halfdt.gt.tinfo(
itstr,l))
THEN
252 lsize=track(
isizf,nf,l)
253 swimtime=track(
iswim,nf,l)
257 lsize=track(
isizf,nfp1,l)
258 swimtime=track(
iswim,nfp1,l)
274 i1=int(1.0_r8+(my_food-
grate_f0)*ograte_df)
276 j1=int(1.0_r8+(my_size-
grate_l0)*ograte_dl)
303 i1=int(1.0_r8+(my_salt-
gfactor_s0)*ogfactor_ds)
305 j1=int(1.0_r8+(my_temp-
gfactor_t0)*ogfactor_dt)
338 &
dt(ng)*(cff1*track(
ibrhs,nf ,l)- &
339 & cff2*track(
ibrhs,nfm1,l)+ &
340 & cff1*track(
ibrhs,nfm2,l))
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))
348 lsize=track(
isizf,nfp1,l)
352 IF (abs(dsalt).lt.0.00001_r8)
THEN
355 IF (dsalt.gt.0.0_r8)
THEN
370 my_size=min(max(
swim_l0,lsize), &
372 my_temp=min(max(
swim_t0,temp), &
375 i1=int(1.0_r8+(my_size-
swim_l0)*oswim_dl)
377 j1=int(1.0_r8+(my_temp-
swim_t0)*oswim_dt)
390 swimrate=swimrate*0.001_r8
404 w_bio=swimtime*swimrate-(1.0_r8-swimtime)*sink
411 track(
iwbio,nfp1,l)=w_bio
412 track(
iwsin,nfp1,l)=sink
413 track(
iswim,nfp1,l)=swimtimenew
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)
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))
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)
430 track(
idpth,nfp1,l)=-bottom
432 track(
iwbio,nfp1,l)=0.0_r8
433 track(
iwsin,nfp1,l)=0.0_r8
434 track(
iswim,nfp1,l)=0.0_r8
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)
446 track(
ibrhs,i,l)=brhs
447 track(
iwsin,i,l)=sink
448 track(
iwbio,i,l)=w_bio
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, dimension(:), allocatable iftvar
type(t_drifter), dimension(:), allocatable drifter
type(t_grid), dimension(:), allocatable grid
integer, dimension(:), allocatable lm
integer, dimension(:), allocatable mm
real(dp), dimension(:), allocatable dt
real(dp), parameter sec2day
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)
recursive subroutine wclock_on(ng, model, region, line, routine)