4
5
6
7
8
9
10
11
12
13
14
15
22
24
26
27 implicit none
28
29
30
31 logical, intent(in) :: Lwrite
32
33 integer, intent(in) :: model, inp, out
34
35
36
37 integer :: Npts, Nval
38 integer :: i, j, igrid, mc, nc, ng, status
39
40 integer, dimension(Ngrids) :: ncount, nentry
41
42 integer, allocatable :: Fcoor(:,:), Fcount(:,:), Ftype(:,:)
43
44 real(r8) :: xfloat, yfloat, zfloat
45
46 real(dp), dimension(nRval) :: Rval
47
48 real(r8), allocatable :: Ft0(:,:), Fx0(:,:), Fy0(:,:), Fz0(:,:)
49 real(r8), allocatable :: Fdt(:,:), Fdx(:,:), Fdy(:,:), Fdz(:,:)
50
51 character (len=1 ), parameter :: blank = ' '
52
53 character (len=35 ) :: frmt
54 character (len=40 ) :: KeyWord
55 character (len=256) :: fname, line
56 character (len=256), dimension(nCval) :: Cval
57
58 character (len=*), parameter :: MyFile = &
59 & __FILE__
60
61
62
63
64
65
66
67
69
70
71
72
73
74 DO WHILE (.true.)
75 READ (inp,
'(a)',
err=20,
END=30) line
77 IF (status.gt.0) THEN
78 SELECT CASE (trim(keyword))
79 CASE ('Lfloats')
81 CASE ('Fprint')
83 CASE ('FRREC')
85 CASE ('FBIONAM')
88 END DO
89 fbionam=trim(adjustl(cval(nval)))
90 CASE ('NFLOATS')
92 CASE ('POS')
95 IF (.not.allocated(fcoor)) THEN
96 allocate ( fcoor(npts,
ngrids) )
98 END IF
99 IF (.not.allocated(fcount)) THEN
100 allocate ( fcount(npts,
ngrids) )
102 END IF
103 IF (.not.allocated(ftype)) THEN
104 allocate ( ftype(npts,
ngrids) )
106 END IF
107 IF (.not.allocated(ft0)) THEN
108 allocate ( ft0(npts,
ngrids) )
110 END IF
111 IF (.not.allocated(fx0)) THEN
112 allocate ( fx0(npts,
ngrids) )
114 END IF
115 IF (.not.allocated(fy0)) THEN
116 allocate ( fy0(npts,
ngrids) )
118 END IF
119 IF (.not.allocated(fz0)) THEN
120 allocate ( fz0(npts,
ngrids) )
122 END IF
123 IF (.not.allocated(fdt)) THEN
124 allocate ( fdt(npts,
ngrids) )
126 END IF
127 IF (.not.allocated(fdx)) THEN
128 allocate ( fdx(npts,
ngrids) )
130 END IF
131 IF (.not.allocated(fdy)) THEN
132 allocate ( fdy(npts,
ngrids) )
134 END IF
135 IF (.not.allocated(fdz)) THEN
136 allocate ( fdz(npts,
ngrids) )
138 END IF
142 DO WHILE (.true.)
143 READ (inp,*,
err=30,
END=30) igrid, &
144 & fcoor(nentry(igrid)+1,igrid), &
145 & ftype(nentry(igrid)+1,igrid), &
146 & fcount(nentry(igrid)+1,igrid), &
147 & ft0(nentry(igrid)+1,igrid), &
148 & fx0(nentry(igrid)+1,igrid), &
149 & fy0(nentry(igrid)+1,igrid), &
150 & fz0(nentry(igrid)+1,igrid), &
151 & fdt(nentry(igrid)+1,igrid), &
152 & fdx(nentry(igrid)+1,igrid), &
153 & fdy(nentry(igrid)+1,igrid), &
154 & fdz(nentry(igrid)+1,igrid)
158 RETURN
159 END IF
160 ncount(igrid)=ncount(igrid)+ &
161 & fcount(nentry(igrid)+1,igrid)
162 nentry(igrid)=nentry(igrid)+1
163 END DO
164 END SELECT
165 END IF
166 END DO
167 20
IF (
master)
WRITE (out,70) line
169 RETURN
170 30 CONTINUE
171
172
173
174
175
179 END IF
180 END DO
181
182
183
184
185
186 IF (
master.and.lwrite)
THEN
189 IF (ncount(ng).ne.
nfloats(ng))
THEN
192 RETURN
193 END IF
194 WRITE (out,90) ng
195 DO i=1,nentry(ng)
196 IF (.not.
spherical.and.(fcoor(i,ng).eq.0))
THEN
197 frmt='(i1,i2,i5,f10.4,2f8.2,f8.2,4f9.3)'
198 ELSE
199 frmt='(i1,i2,i5,f10.4,3f8.2,4f9.3)'
200 END IF
201 WRITE (out,frmt) fcoor(i,ng), ftype(i,ng), fcount(i,ng), &
202 & ft0(i,ng), fx0(i,ng), fy0(i,ng), &
203 & fz0(i,ng), fdt(i,ng), fdx(i,ng), &
204 & fdy(i,ng), fdz(i,ng)
205 END DO
207 & 'Nfloats', &
208 & 'Number of float trajectories to compute.'
209 END IF
210 END DO
211 END IF
212
213# ifdef FLOAT_BIOLOGY
215 IF (.not.
find_file(1, out, fname,
'FBIONAM'))
THEN
217 ELSE
218 IF (
master.and.lwrite)
THEN
219 WRITE (out,120) 'biological floats behavior File: ', &
220 & trim(fname)
221 END IF
222 END IF
223# endif
224
225
226
227
228
229
230
231
232
234 mc=0
235 nc=0
237 DO i=1,nentry(ng)
238 IF (fcount(i,ng).eq.1) THEN
239 nc=nc+1
242 drifter(ng)%Ftype(nc)=ftype(i,ng)
243 IF (fcoor(i,ng).eq.0) THEN
246 ELSE
247 mc=mc+1
251 END IF
252 ELSE IF (fcount(i,ng).gt.1) THEN
253 DO j=1,fcount(i,ng)
254 nc=nc+1
255 IF (fdt(i,ng).gt.0.0_r8) THEN
257 & real(j-1,r8)*fdt(i,ng))* &
260 drifter(ng)%Ftype(nc)=ftype(i,ng)
261 IF (fcoor(i,ng).eq.0) THEN
264 ELSE
265 mc=mc+1
269 END IF
270 ELSE
272 IF (fdz(i,ng).eq.0.0_r8) THEN
274 ELSE
275 IF (fz0(i,ng).gt.0.0_r8) THEN
276 zfloat=fz0(i,ng)+real(j-1,r8)*fdz(i,ng)
278 & zfloat), &
280 ELSE
282 & real(j-1,r8)*fdz(i,ng)
283 END IF
284 END IF
285 drifter(ng)%Ftype(nc)=ftype(i,ng)
286 IF (fcoor(i,ng).eq.0) THEN
287 xfloat=fx0(i,ng)+real(j-1,r8)*fdx(i,ng)
288 yfloat=fy0(i,ng)+real(j-1,r8)*fdy(i,ng)
291 ELSE
292 mc=mc+1
293 drifter(ng)%Flon(mc)=fx0(i,ng)+ &
294 & real(j-1,r8)*fdx(i,ng)
295 drifter(ng)%Flat(mc)=fy0(i,ng)+ &
296 & real(j-1,r8)*fdy(i,ng)
298 END IF
299 END IF
300 END DO
301 END IF
302 END DO
304 END IF
305 END DO
306
307
308
309 IF (allocated(fcoor)) deallocate ( fcoor )
310 IF (allocated(fcount)) deallocate ( fcount )
311 IF (allocated(ftype)) deallocate ( ftype )
312 IF (allocated(ft0)) deallocate ( ft0 )
313 IF (allocated(fx0)) deallocate ( fx0 )
314 IF (allocated(fy0)) deallocate ( fy0 )
315 IF (allocated(fz0)) deallocate ( fz0 )
316 IF (allocated(fdt)) deallocate ( fdt )
317 IF (allocated(fdx)) deallocate ( fdx )
318 IF (allocated(fdy)) deallocate ( fdy )
319 IF (allocated(fdz)) deallocate ( fdz )
320
321 60 FORMAT (/,' READ_FltPar - Error while reading floats', &
322 & ' locations in input script: ',a)
323 70 FORMAT (/,' READ_FltPar - Error while processing line: ',/,a)
324 80 FORMAT (/,' READ_FltPar - Inconsistent number of floats to', &
325 & ' process: ', 2i6,/,18x,'change input script.')
326 90 FORMAT (/,/,' Floats Initial Locations, Grid: ',i2.2, &
327 & /, ' ==================================',/,/, &
328 & 15x,'Ft0',5x,'Fx0',5x,'Fy0',5x,'Fz0', &
329 & 6x,'Fdt',6x,'Fdx',6x,'Fdy',6x,'Fdz',/)
330 100 FORMAT (/,1x,i10,2x,a,t30,a)
331 110 FORMAT (/,' READ_FltPar - Grid ', i2.2, &
332 & ', could not find input file: ', a)
333 120 FORMAT (/,2x,a,a)
334
335 RETURN
integer function decode_line(line_text, keyword, nval, cval, rval)
logical function find_file(ng, out, fname, keyword)
logical, dimension(:), allocatable fprint
integer, dimension(:), allocatable frrec
subroutine, public allocate_floats(ldrifter)
type(t_drifter), dimension(:), allocatable drifter
character(len=256) fbionam
type(t_io), dimension(:), allocatable err
character(len=256) fposnam
integer, dimension(:), allocatable nfloats
integer, dimension(:), allocatable n
real(r8), dimension(:), allocatable dmem
logical, dimension(:), allocatable lfloats
real(dp), parameter day2sec
logical, dimension(:), allocatable ldefflt
logical function, public founderror(flag, noerr, line, routine)