##// END OF EJS Templates
lagp.f update 7
rflores -
r1626:cb57cf1f88fc
parent child
Show More
@@ -1,569 +1,569
1 subroutine lagp(plag,wl,r0,dr,nl,nrange)
1 subroutine lagp(plag,wl,r0,dr,nl,nrange)
2 c
2 c
3 c predict lagged product matrix using state parameters stored
3 c predict lagged product matrix using state parameters stored
4 c as cubic b-splines
4 c as cubic b-splines
5 c read weights for numeric integration from a file
5 c read weights for numeric integration from a file
6 c
6 c
7 c faster version - assumes samples taken at half-integer lags, ranges
7 c faster version - assumes samples taken at half-integer lags, ranges
8 c
8 c
9 include 'fitter.h'
9 include 'fitter.h'
10 include 'spline.h'
10 include 'spline.h'
11 include 'bfield.h'
11 include 'bfield.h'
12 integer nl,nrange
12 integer nl,nrange
13 real plag(nl,nrange),taus(nl)
13 real plag(nl,nrange),taus(nl)
14 parameter(nw=1000)
14 parameter(nw=1000)
15 integer ilag(nw)
15 integer ilag(nw)
16 real weight(nw),dtau(nw),drange(nw)
16 real weight(nw),dtau(nw),drange(nw)
17 logical first
17 logical first
18 real store(2*nl,2*nrange,2)
18 real store(2*nl,2*nrange,2)
19
19
20 character(1024) :: fqual_temp
20 character(1024) :: fqual_temp
21 character(:), allocatable :: fqual
21 character(:), allocatable :: fqual
22 character bfmodel_str*8
22 character bfmodel_str*8
23
23
24 data first/.true./
24 data first/.true./
25 c
25 c
26
26
27 c write(*,*) "dens_before: ",dens
27 c write(*,*) "dens_before: ",dens
28 c call exit
28 c call exit
29 c zero out array
29 c zero out array
30 c write(*,*) "Starting lagp"
30 c write(*,*) "Starting lagp"
31 do i=1,nrange
31 do i=1,nrange
32 do j=1,nl
32 do j=1,nl
33 plag(j,i)=0.0
33 plag(j,i)=0.0
34 end do
34 end do
35 end do
35 end do
36
36
37 c
37 c
38 c compute all required acfs
38 c compute all required acfs
39 c
39 c
40 do i=1,2*nrange
40 do i=1,2*nrange
41 ii=(i-1)/2+1
41 ii=(i-1)/2+1
42 alt=r0+float(i-1)*dr*0.5 ! half integer ranges
42 alt=r0+float(i-1)*dr*0.5 ! half integer ranges
43 c write(*,*) "dens_before: ",dens
43 c write(*,*) "dens_before: ",dens
44 c call exit
44 c call exit
45 c write(*,*) "alt: ",alt
45 c write(*,*) "alt: ",alt
46 c write(*,*) "dens: ",dens
46 c write(*,*) "dens: ",dens
47 c write(*,*) "te: ",te
47 c write(*,*) "te: ",te
48 c write(*,*) "ti1: ",ti1
48 c write(*,*) "ti1: ",ti1
49 c write(*,*) "hf: ",hf
49 c write(*,*) "hf: ",hf
50 c write(*,*) "hef: ",hef
50 c write(*,*) "hef: ",hef
51 c call exit
51 c call exit
52 call get_spline(alt,dens,te,ti1,hf,hef)
52 call get_spline(alt,dens,te,ti1,hf,hef)
53 c write(*,*) "dens_after: ",dens
53 c write(*,*) "dens_after: ",dens
54 c call exit
54 c call exit
55 do k=1,nion
55 do k=1,nion
56 ti(k)=ti1
56 ti(k)=ti1
57 end do
57 end do
58 fi(2)=hf
58 fi(2)=hf
59 fi(3)=hef
59 fi(3)=hef
60 fi(1)=1.0-hf-hef
60 fi(1)=1.0-hf-hef
61
61
62 do j=1,2*nl
62 do j=1,2*nl
63 tau=float(j-1)*(dr/1.5e5)*0.5 ! half integer lags
63 tau=float(j-1)*(dr/1.5e5)*0.5 ! half integer lags
64
64
65 c just consider a single azimuth angle for now
65 c just consider a single azimuth angle for now
66
66
67 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
67 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
68 c & alpha_prof(ii)+1.74e-2,dens,bfld_prof(ii),rho)
68 c & alpha_prof(ii)+1.74e-2,dens,bfld_prof(ii),rho)
69 c store(j,i,1)=rho*dens*(100.0/alt)**2
69 c store(j,i,1)=rho*dens*(100.0/alt)**2
70
70
71 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
71 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
72 c & alpha_prof(ii)-1.74e-2,dens,bfld_prof(ii),rho)
72 c & alpha_prof(ii)-1.74e-2,dens,bfld_prof(ii),rho)
73 c store(j,i,2)=rho*dens*(100.0/alt)**2
73 c store(j,i,2)=rho*dens*(100.0/alt)**2
74
74
75 call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
75 call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
76 & alpha_prof(ii),dens,bfld_prof(ii),rho)
76 & alpha_prof(ii),dens,bfld_prof(ii),rho)
77 store(j,i,1)=rho*dens*(100.0/alt)**2
77 store(j,i,1)=rho*dens*(100.0/alt)**2
78 c write(*,*) "store", store(j,i,1)
78 c write(*,*) "store", store(j,i,1)
79 c call exit
79 c call exit
80 end do
80 end do
81 end do
81 end do
82
82
83 c construct lagged products
83 c construct lagged products
84 c
84 c
85 c write(*,*) "before weights"
85 c write(*,*) "before weights"
86 c write(*,*) first
86 c write(*,*) first
87 c write(*,*) "weight before: ",weight
87 c write(*,*) "weight before: ",weight
88 c write(*,*) "BEFORE GET_PATH"
88 c write(*,*) "BEFORE GET_PATH"
89 call get_path(fqual_temp)
89 call get_path(fqual_temp)
90 c write(*,*) "L_BEF: ", fqual_temp, "L_BEF_end"
90 c write(*,*) "L_BEF: ", fqual_temp, "L_BEF_end"
91 fqual = TRIM(fqual_temp)
91 fqual = TRIM(fqual_temp)
92 bfmodel = 'bfmodel/'
92 bfmodel_str = 'bfmodel/'
93 fqual(1:len_trim(fqual)-len_trim(bfmodel))
93 fqual(1:len_trim(fqual)-len_trim(bfmodel_str))
94 fqual = fqual//'weights.dat'
94 fqual = fqual//'weights.dat'
95 c write(*,*) "Final fqual",fqual,"FINAL"
95 c write(*,*) "Final fqual",fqual,"FINAL"
96
96
97 if(first) then
97 if(first) then
98 open(unit=25,file=fqual,
98 open(unit=25,file=fqual,
99 & status='old')
99 & status='old')
100 read (25,*) nwt
100 read (25,*) nwt
101 do i=1,nwt
101 do i=1,nwt
102 read(25,*) weight(i),dtau(i),drange(i),ilag(i)
102 read(25,*) weight(i),dtau(i),drange(i),ilag(i)
103 c write(*,*) "ilag: ",ilag(i)
103 c write(*,*) "ilag: ",ilag(i)
104 end do
104 end do
105 c flush(25)
105 c flush(25)
106 close(25)
106 close(25)
107 c first=.false.
107 c first=.false.
108 end if
108 end if
109
109
110 c write(*,*) "after weights"
110 c write(*,*) "after weights"
111
111
112 c write(*,*) "weight(3): ",weight(3)
112 c write(*,*) "weight(3): ",weight(3)
113 c call exit
113 c call exit
114 c write(*,*) "nl: ",nl,"nrange: ",nrange,"nwt: ",nwt
114 c write(*,*) "nl: ",nl,"nrange: ",nrange,"nwt: ",nwt
115
115
116 do i=1+nl,nrange ! don't worry about redundancy here
116 do i=1+nl,nrange ! don't worry about redundancy here
117
117
118 do j=1,nwt
118 do j=1,nwt
119 c write(*,*) "j: ",j
119 c write(*,*) "j: ",j
120 alt=r0+(float(i-1)+drange(j))*dr
120 alt=r0+(float(i-1)+drange(j))*dr
121 tau=abs(dtau(j)*dr/1.5e5)
121 tau=abs(dtau(j)*dr/1.5e5)
122 lag=ilag(j)+1
122 lag=ilag(j)+1
123 c write(*,*) tau
123 c write(*,*) tau
124
124
125 k=1+2.0*(tau/(dr/1.5e5))
125 k=1+2.0*(tau/(dr/1.5e5))
126 l=1+2.0*(alt-r0)/dr
126 l=1+2.0*(alt-r0)/dr
127
127
128 do m=1,1 ! 2
128 do m=1,1 ! 2
129
129
130 c call exit
130 c call exit
131 c write(*,*) i
131 c write(*,*) i
132 c call exit
132 c call exit
133 c if (i .eq. nrange) then
133 c if (i .eq. nrange) then
134 c if (j .eq. 227) then
134 c if (j .eq. 227) then
135
135
136 c write(*,*) "lag: ",lag
136 c write(*,*) "lag: ",lag
137 c write(*,*) "ilag: ",ilag(j)
137 c write(*,*) "ilag: ",ilag(j)
138 c call exit
138 c call exit
139 c write(*,*) "plag: ",plag(lag,i)
139 c write(*,*) "plag: ",plag(lag,i)
140 c write(*,*) "weight: ",weight
140 c write(*,*) "weight: ",weight
141 c
141 c
142 c write(*,*) "weight: ",weight(j)
142 c write(*,*) "weight: ",weight(j)
143 c write(*,*) "store: ",store(k,l,m)
143 c write(*,*) "store: ",store(k,l,m)
144 c call exit
144 c call exit
145 c end if
145 c end if
146 c end if
146 c end if
147 plag(lag,i)=plag(lag,i)+weight(j)*store(k,l,m)
147 plag(lag,i)=plag(lag,i)+weight(j)*store(k,l,m)
148 c if (i .eq. nrange) then
148 c if (i .eq. nrange) then
149 c write(*,*) "lag: ",lag
149 c write(*,*) "lag: ",lag
150 c write(*,*) "plag: ",plag(lag,i)
150 c write(*,*) "plag: ",plag(lag,i)
151 c write(*,*) "plag: ",plag(lag,i)
151 c write(*,*) "plag: ",plag(lag,i)
152 c call exit
152 c call exit
153 c end if
153 c end if
154 end do
154 end do
155 c write(*,*) "plag: ",plag(lag,i)
155 c write(*,*) "plag: ",plag(lag,i)
156 c write(*,*) "plag: ",plag(12,72)
156 c write(*,*) "plag: ",plag(12,72)
157 c call exit
157 c call exit
158 end do
158 end do
159 c call exit
159 c call exit
160 c write(*,*) "plag: ",plag(12,72)
160 c write(*,*) "plag: ",plag(12,72)
161 end do
161 end do
162 c write(*,*) "plag: ",plag(12,72)
162 c write(*,*) "plag: ",plag(12,72)
163 c call exit
163 c call exit
164 c write(*,*) "End LAGP"
164 c write(*,*) "End LAGP"
165 return
165 return
166 end
166 end
167
167
168 subroutine lagp_old(plag,wl,r0,dr,nl,nrange)
168 subroutine lagp_old(plag,wl,r0,dr,nl,nrange)
169 c
169 c
170 c predict lagged product matrix using state parameters stored
170 c predict lagged product matrix using state parameters stored
171 c as cubic b-splines
171 c as cubic b-splines
172 c read weights for numeric integration from a file
172 c read weights for numeric integration from a file
173 c
173 c
174 c general version - samples can be anywhere
174 c general version - samples can be anywhere
175 c
175 c
176 include 'fitter.h'
176 include 'fitter.h'
177 include 'spline.h'
177 include 'spline.h'
178 include 'bfield.h'
178 include 'bfield.h'
179 integer nl,nrange
179 integer nl,nrange
180 real plag(nl,nrange),taus(nl)
180 real plag(nl,nrange),taus(nl)
181 parameter(nw=1000)
181 parameter(nw=1000)
182 integer ilag(nw)
182 integer ilag(nw)
183 real weight(nw),dtau(nw),drange(nw)
183 real weight(nw),dtau(nw),drange(nw)
184 logical first
184 logical first
185 data first/.true./
185 data first/.true./
186 c
186 c
187
187
188 c zero out array
188 c zero out array
189
189
190 do i=1,nrange
190 do i=1,nrange
191 do j=1,nl
191 do j=1,nl
192 plag(j,i)=0.0
192 plag(j,i)=0.0
193 end do
193 end do
194 end do
194 end do
195
195
196 c
196 c
197 c construct lagged products
197 c construct lagged products
198 c
198 c
199
199
200 if(first) then
200 if(first) then
201 open(unit=25,file='weights.dat',status='old')
201 open(unit=25,file='weights.dat',status='old')
202 read (25,*) nwt
202 read (25,*) nwt
203 do i=1,nwt
203 do i=1,nwt
204 read(25,*) weight(i),dtau(i),drange(i),ilag(i)
204 read(25,*) weight(i),dtau(i),drange(i),ilag(i)
205 end do
205 end do
206 close(25)
206 close(25)
207 first=.false.
207 first=.false.
208 end if
208 end if
209
209
210 c can avoid recalculating splines and/or ACFs when parameters repeat
210 c can avoid recalculating splines and/or ACFs when parameters repeat
211
211
212 altp=-1.0
212 altp=-1.0
213 taup=-1.0
213 taup=-1.0
214
214
215 do i=1+nl,nrange
215 do i=1+nl,nrange
216 do j=1,nwt
216 do j=1,nwt
217 alt=r0+(float(i-1)+drange(j))*dr
217 alt=r0+(float(i-1)+drange(j))*dr
218 ii=(alt-r0)/dr+1
218 ii=(alt-r0)/dr+1
219
219
220 if(alt.ne.altp) then
220 if(alt.ne.altp) then
221 call get_spline(alt,dens,te,ti1,hf,hef)
221 call get_spline(alt,dens,te,ti1,hf,hef)
222
222
223 c write(*,*) alt,dens,te,ti1,hf,hef
223 c write(*,*) alt,dens,te,ti1,hf,hef
224
224
225 do k=1,nion
225 do k=1,nion
226 ti(k)=ti1
226 ti(k)=ti1
227 end do
227 end do
228 fi(2)=hf
228 fi(2)=hf
229 fi(3)=hef
229 fi(3)=hef
230 fi(1)=1.0-hf-hef
230 fi(1)=1.0-hf-hef
231 end if
231 end if
232
232
233 tau=abs(dtau(j)*dr/1.5e5)
233 tau=abs(dtau(j)*dr/1.5e5)
234 lag=ilag(j)+1
234 lag=ilag(j)+1
235
235
236 c write(*,*) i,alpha_prof(i),bfld_prof(i)
236 c write(*,*) i,alpha_prof(i),bfld_prof(i)
237
237
238 if(tau.ne.taup.or.alt.ne.altp) then
238 if(tau.ne.taup.or.alt.ne.altp) then
239
239
240 c two- or three- point Gauss Hermite quadrature rule
240 c two- or three- point Gauss Hermite quadrature rule
241
241
242 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
242 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
243 c & alpha_prof(ii)+1.74e-2,dens,bfld_prof(ii),rho1)
243 c & alpha_prof(ii)+1.74e-2,dens,bfld_prof(ii),rho1)
244
244
245 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
245 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
246 c & alpha_prof(ii)-1.74e-2,dens,bfld_prof(ii),rho2)
246 c & alpha_prof(ii)-1.74e-2,dens,bfld_prof(ii),rho2)
247
247
248 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
248 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
249 c & alpha_prof(ii),dens,bfld_prof(ii),rho1)
249 c & alpha_prof(ii),dens,bfld_prof(ii),rho1)
250
250
251 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
251 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
252 c & alpha_prof(ii)+1.9e-2,dens,bfld_prof(ii),rho2)
252 c & alpha_prof(ii)+1.9e-2,dens,bfld_prof(ii),rho2)
253
253
254 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
254 c call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
255 c & alpha_prof(ii)-1.9e-2,dens,bfld_prof(ii),rho3)
255 c & alpha_prof(ii)-1.9e-2,dens,bfld_prof(ii),rho3)
256
256
257 call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
257 call acf2(wl,tau,te,ti,fi,ven,vin,wi,nion,
258 & alpha_prof(ii),dens,bfld_prof(ii),rho)
258 & alpha_prof(ii),dens,bfld_prof(ii),rho)
259
259
260 c rho=(rho1+rho2)/2.0
260 c rho=(rho1+rho2)/2.0
261 c rho=(rho2+rho3)*0.29541+rho1*1.18164)/1.77246
261 c rho=(rho2+rho3)*0.29541+rho1*1.18164)/1.77246
262
262
263 end if
263 end if
264
264
265 plag(lag,i)=plag(lag,i)+weight(j)*rho*dens*(100.0/alt)**2
265 plag(lag,i)=plag(lag,i)+weight(j)*rho*dens*(100.0/alt)**2
266
266
267 altp=alt
267 altp=alt
268 taup=tau
268 taup=tau
269
269
270 end do
270 end do
271 end do
271 end do
272
272
273 return
273 return
274 end
274 end
275
275
276 function atanh(x)
276 function atanh(x)
277 c
277 c
278 real atanh,x
278 real atanh,x
279 c
279 c
280 atanh=log(sqrt((1.+x)/(1.-x)))
280 atanh=log(sqrt((1.+x)/(1.-x)))
281 return
281 return
282 end
282 end
283
283
284 subroutine get_spline(alt,dens,te,ti,hf,hef)
284 subroutine get_spline(alt,dens,te,ti,hf,hef)
285 c
285 c
286 c routines for handling cubic b-spline interpolation
286 c routines for handling cubic b-spline interpolation
287 c gets values consistent with stored coefficients
287 c gets values consistent with stored coefficients
288 c
288 c
289
289
290 include 'spline.h'
290 include 'spline.h'
291
291
292 c
292 c
293 c bspline values from 200-1500 km in 15-km intervals
293 c bspline values from 200-1500 km in 15-km intervals
294 c must specify five knots above ceiling
294 c must specify five knots above ceiling
295 c note offset ... start accessing splines above bottom two knots
295 c note offset ... start accessing splines above bottom two knots
296 c
296 c
297 c five banks of splines, for Ne, Te, Ti, H+, and He+ versus altitude
297 c five banks of splines, for Ne, Te, Ti, H+, and He+ versus altitude
298 c need to initialize ta somewhere
298 c need to initialize ta somewhere
299 c
299 c
300 c write(*,*) "ta: ",ta
300 c write(*,*) "ta: ",ta
301 c write(*,*) "bcoef(1,1): ",bcoef(1,1)
301 c write(*,*) "bcoef(1,1): ",bcoef(1,1)
302 c write(*,*) "nspline: ",nspline
302 c write(*,*) "nspline: ",nspline
303 c write(*,*) "norder: ",norder
303 c write(*,*) "norder: ",norder
304 c write(*,*) "alt: ",alt
304 c write(*,*) "alt: ",alt
305 dens=bvalue(ta,bcoef(1,1),nspline,norder,alt,0)
305 dens=bvalue(ta,bcoef(1,1),nspline,norder,alt,0)
306 c write(*,*) "dens_inside_get_spline: ",dens
306 c write(*,*) "dens_inside_get_spline: ",dens
307 c write(*,*) dens
307 c write(*,*) dens
308 c call exit
308 c call exit
309 dens=10.0**MAX(dens,2.0)
309 dens=10.0**MAX(dens,2.0)
310 c write(*,*) dens
310 c write(*,*) dens
311 c call exit
311 c call exit
312 te=bvalue(ta,bcoef(1,2),nspline,norder,alt,0)
312 te=bvalue(ta,bcoef(1,2),nspline,norder,alt,0)
313 te=t0+t1*(1.0+tanh(te))/2.0 ! DLH 10/14 was 3500
313 te=t0+t1*(1.0+tanh(te))/2.0 ! DLH 10/14 was 3500
314 c tr=bvalue(ta,bcoef(1,3),nspline,norder,alt,0)
314 c tr=bvalue(ta,bcoef(1,3),nspline,norder,alt,0)
315 c tr=exp(tr)
315 c tr=exp(tr)
316 c ti=te/tr
316 c ti=te/tr
317 ti=bvalue(ta,bcoef(1,3),nspline,norder,alt,0)
317 ti=bvalue(ta,bcoef(1,3),nspline,norder,alt,0)
318 ti=t0+t1*(1.0+tanh(ti))/2.0 ! DLH 10/14 was 3500
318 ti=t0+t1*(1.0+tanh(ti))/2.0 ! DLH 10/14 was 3500
319 hf=bvalue(ta,bcoef(1,4),nspline,norder,alt,0)
319 hf=bvalue(ta,bcoef(1,4),nspline,norder,alt,0)
320 hf=(1.0+tanh(hf))/2.0
320 hf=(1.0+tanh(hf))/2.0
321 hef=bvalue(ta,bcoef(1,5),nspline,norder,alt,0)
321 hef=bvalue(ta,bcoef(1,5),nspline,norder,alt,0)
322 hef=(1.0+tanh(hef))/2.0
322 hef=(1.0+tanh(hef))/2.0
323 return
323 return
324 end
324 end
325
325
326
326
327 real function bvalue ( t, bcoef, n, k, x, jderiv )
327 real function bvalue ( t, bcoef, n, k, x, jderiv )
328 c from * a practical guide to splines * by c. de boor
328 c from * a practical guide to splines * by c. de boor
329 calls interv
329 calls interv
330 c
330 c
331 calculates value at x of jderiv-th derivative of spline from b-repr.
331 calculates value at x of jderiv-th derivative of spline from b-repr.
332 c the spline is taken to be continuous from the right, EXCEPT at the
332 c the spline is taken to be continuous from the right, EXCEPT at the
333 c rightmost knot, where it is taken to be continuous from the left.
333 c rightmost knot, where it is taken to be continuous from the left.
334 c
334 c
335 c****** i n p u t ******
335 c****** i n p u t ******
336 c t, bcoef, n, k......forms the b-representation of the spline f to
336 c t, bcoef, n, k......forms the b-representation of the spline f to
337 c be evaluated. specifically,
337 c be evaluated. specifically,
338 c t.....knot sequence, of length n+k, assumed nondecreasing.
338 c t.....knot sequence, of length n+k, assumed nondecreasing.
339 c bcoef.....b-coefficient sequence, of length n .
339 c bcoef.....b-coefficient sequence, of length n .
340 c n.....length of bcoef and dimension of spline(k,t),
340 c n.....length of bcoef and dimension of spline(k,t),
341 c a s s u m e d positive .
341 c a s s u m e d positive .
342 c k.....order of the spline .
342 c k.....order of the spline .
343 c
343 c
344 c w a r n i n g . . . the restriction k .le. kmax (=20) is imposed
344 c w a r n i n g . . . the restriction k .le. kmax (=20) is imposed
345 c arbitrarily by the dimension statement for aj, dl, dr below,
345 c arbitrarily by the dimension statement for aj, dl, dr below,
346 c but is n o w h e r e c h e c k e d for.
346 c but is n o w h e r e c h e c k e d for.
347 c
347 c
348 c x.....the point at which to evaluate .
348 c x.....the point at which to evaluate .
349 c jderiv.....integer giving the order of the derivative to be evaluated
349 c jderiv.....integer giving the order of the derivative to be evaluated
350 c a s s u m e d to be zero or positive.
350 c a s s u m e d to be zero or positive.
351 c
351 c
352 c****** o u t p u t ******
352 c****** o u t p u t ******
353 c bvalue.....the value of the (jderiv)-th derivative of f at x .
353 c bvalue.....the value of the (jderiv)-th derivative of f at x .
354 c
354 c
355 c****** m e t h o d ******
355 c****** m e t h o d ******
356 c The nontrivial knot interval (t(i),t(i+1)) containing x is lo-
356 c The nontrivial knot interval (t(i),t(i+1)) containing x is lo-
357 c cated with the aid of interv . The k b-coeffs of f relevant for
357 c cated with the aid of interv . The k b-coeffs of f relevant for
358 c this interval are then obtained from bcoef (or taken to be zero if
358 c this interval are then obtained from bcoef (or taken to be zero if
359 c not explicitly available) and are then differenced jderiv times to
359 c not explicitly available) and are then differenced jderiv times to
360 c obtain the b-coeffs of (d**jderiv)f relevant for that interval.
360 c obtain the b-coeffs of (d**jderiv)f relevant for that interval.
361 c Precisely, with j = jderiv, we have from x.(12) of the text that
361 c Precisely, with j = jderiv, we have from x.(12) of the text that
362 c
362 c
363 c (d**j)f = sum ( bcoef(.,j)*b(.,k-j,t) )
363 c (d**j)f = sum ( bcoef(.,j)*b(.,k-j,t) )
364 c
364 c
365 c where
365 c where
366 c / bcoef(.), , j .eq. 0
366 c / bcoef(.), , j .eq. 0
367 c /
367 c /
368 c bcoef(.,j) = / bcoef(.,j-1) - bcoef(.-1,j-1)
368 c bcoef(.,j) = / bcoef(.,j-1) - bcoef(.-1,j-1)
369 c / ----------------------------- , j .gt. 0
369 c / ----------------------------- , j .gt. 0
370 c / (t(.+k-j) - t(.))/(k-j)
370 c / (t(.+k-j) - t(.))/(k-j)
371 c
371 c
372 c Then, we use repeatedly the fact that
372 c Then, we use repeatedly the fact that
373 c
373 c
374 c sum ( a(.)*b(.,m,t)(x) ) = sum ( a(.,x)*b(.,m-1,t)(x) )
374 c sum ( a(.)*b(.,m,t)(x) ) = sum ( a(.,x)*b(.,m-1,t)(x) )
375 c with
375 c with
376 c (x - t(.))*a(.) + (t(.+m-1) - x)*a(.-1)
376 c (x - t(.))*a(.) + (t(.+m-1) - x)*a(.-1)
377 c a(.,x) = ---------------------------------------
377 c a(.,x) = ---------------------------------------
378 c (x - t(.)) + (t(.+m-1) - x)
378 c (x - t(.)) + (t(.+m-1) - x)
379 c
379 c
380 c to write (d**j)f(x) eventually as a linear combination of b-splines
380 c to write (d**j)f(x) eventually as a linear combination of b-splines
381 c of order 1 , and the coefficient for b(i,1,t)(x) must then be the
381 c of order 1 , and the coefficient for b(i,1,t)(x) must then be the
382 c desired number (d**j)f(x). (see x.(17)-(19) of text).
382 c desired number (d**j)f(x). (see x.(17)-(19) of text).
383 c
383 c
384 parameter (kmax = 40)
384 parameter (kmax = 40)
385 integer jderiv,k,n, i,ilo,imk,j,jc,jcmin,jcmax,jj,kmj,km1
385 integer jderiv,k,n, i,ilo,imk,j,jc,jcmin,jcmax,jj,kmj,km1
386 * ,mflag,nmi,jdrvp1
386 * ,mflag,nmi,jdrvp1
387 c integer kmax
387 c integer kmax
388 C real bcoef(n),t(1),x, aj(20),dl(20),dr(20),fkmj
388 C real bcoef(n),t(1),x, aj(20),dl(20),dr(20),fkmj
389 real bcoef(n),x, aj(kmax),dl(kmax),dr(kmax),fkmj
389 real bcoef(n),x, aj(kmax),dl(kmax),dr(kmax),fkmj
390 dimension t(n+k)
390 dimension t(n+k)
391 c former fortran standard made it impossible to specify the length of t
391 c former fortran standard made it impossible to specify the length of t
392 c precisely without the introduction of otherwise superfluous addition-
392 c precisely without the introduction of otherwise superfluous addition-
393 c al arguments.
393 c al arguments.
394 bvalue = 0.
394 bvalue = 0.
395 if (jderiv .ge. k) go to 99
395 if (jderiv .ge. k) go to 99
396 c
396 c
397 c *** Find i s.t. 1 .le. i .lt. n+k and t(i) .lt. t(i+1) and
397 c *** Find i s.t. 1 .le. i .lt. n+k and t(i) .lt. t(i+1) and
398 c t(i) .le. x .lt. t(i+1) . If no such i can be found, x lies
398 c t(i) .le. x .lt. t(i+1) . If no such i can be found, x lies
399 c outside the support of the spline f , hence bvalue = 0.
399 c outside the support of the spline f , hence bvalue = 0.
400 c (The asymmetry in this choice of i makes f rightcontinuous, except
400 c (The asymmetry in this choice of i makes f rightcontinuous, except
401 c at t(n+k) where it is leftcontinuous.)
401 c at t(n+k) where it is leftcontinuous.)
402 call interv ( t, n+k, x, i, mflag )
402 call interv ( t, n+k, x, i, mflag )
403 if (mflag .ne. 0) go to 99
403 if (mflag .ne. 0) go to 99
404 c *** if k = 1 (and jderiv = 0), bvalue = bcoef(i).
404 c *** if k = 1 (and jderiv = 0), bvalue = bcoef(i).
405 km1 = k - 1
405 km1 = k - 1
406 if (km1 .gt. 0) go to 1
406 if (km1 .gt. 0) go to 1
407 bvalue = bcoef(i)
407 bvalue = bcoef(i)
408 go to 99
408 go to 99
409 c
409 c
410 c *** store the k b-spline coefficients relevant for the knot interval
410 c *** store the k b-spline coefficients relevant for the knot interval
411 c (t(i),t(i+1)) in aj(1),...,aj(k) and compute dl(j) = x - t(i+1-j),
411 c (t(i),t(i+1)) in aj(1),...,aj(k) and compute dl(j) = x - t(i+1-j),
412 c dr(j) = t(i+j) - x, j=1,...,k-1 . set any of the aj not obtainable
412 c dr(j) = t(i+j) - x, j=1,...,k-1 . set any of the aj not obtainable
413 c from input to zero. set any t.s not obtainable equal to t(1) or
413 c from input to zero. set any t.s not obtainable equal to t(1) or
414 c to t(n+k) appropriately.
414 c to t(n+k) appropriately.
415 1 jcmin = 1
415 1 jcmin = 1
416 imk = i - k
416 imk = i - k
417 if (imk .ge. 0) go to 8
417 if (imk .ge. 0) go to 8
418 jcmin = 1 - imk
418 jcmin = 1 - imk
419 do 5 j=1,i
419 do 5 j=1,i
420 5 dl(j) = x - t(i+1-j)
420 5 dl(j) = x - t(i+1-j)
421 do 6 j=i,km1
421 do 6 j=i,km1
422 aj(k-j) = 0.
422 aj(k-j) = 0.
423 6 dl(j) = dl(i)
423 6 dl(j) = dl(i)
424 go to 10
424 go to 10
425 8 do 9 j=1,km1
425 8 do 9 j=1,km1
426 9 dl(j) = x - t(i+1-j)
426 9 dl(j) = x - t(i+1-j)
427 c
427 c
428 10 jcmax = k
428 10 jcmax = k
429 nmi = n - i
429 nmi = n - i
430 if (nmi .ge. 0) go to 18
430 if (nmi .ge. 0) go to 18
431 jcmax = k + nmi
431 jcmax = k + nmi
432 do 15 j=1,jcmax
432 do 15 j=1,jcmax
433 15 dr(j) = t(i+j) - x
433 15 dr(j) = t(i+j) - x
434 do 16 j=jcmax,km1
434 do 16 j=jcmax,km1
435 aj(j+1) = 0.
435 aj(j+1) = 0.
436 16 dr(j) = dr(jcmax)
436 16 dr(j) = dr(jcmax)
437 go to 20
437 go to 20
438 18 do 19 j=1,km1
438 18 do 19 j=1,km1
439 19 dr(j) = t(i+j) - x
439 19 dr(j) = t(i+j) - x
440 c
440 c
441 20 do 21 jc=jcmin,jcmax
441 20 do 21 jc=jcmin,jcmax
442 21 aj(jc) = bcoef(imk + jc)
442 21 aj(jc) = bcoef(imk + jc)
443 c
443 c
444 c *** difference the coefficients jderiv times.
444 c *** difference the coefficients jderiv times.
445 if (jderiv .eq. 0) go to 30
445 if (jderiv .eq. 0) go to 30
446 do 23 j=1,jderiv
446 do 23 j=1,jderiv
447 kmj = k-j
447 kmj = k-j
448 fkmj = float(kmj)
448 fkmj = float(kmj)
449 ilo = kmj
449 ilo = kmj
450 do 23 jj=1,kmj
450 do 23 jj=1,kmj
451 aj(jj) = ((aj(jj+1) - aj(jj))/(dl(ilo) + dr(jj)))*fkmj
451 aj(jj) = ((aj(jj+1) - aj(jj))/(dl(ilo) + dr(jj)))*fkmj
452 23 ilo = ilo - 1
452 23 ilo = ilo - 1
453 c
453 c
454 c *** compute value at x in (t(i),t(i+1)) of jderiv-th derivative,
454 c *** compute value at x in (t(i),t(i+1)) of jderiv-th derivative,
455 c given its relevant b-spline coeffs in aj(1),...,aj(k-jderiv).
455 c given its relevant b-spline coeffs in aj(1),...,aj(k-jderiv).
456 30 if (jderiv .eq. km1) go to 39
456 30 if (jderiv .eq. km1) go to 39
457 jdrvp1 = jderiv + 1
457 jdrvp1 = jderiv + 1
458 do 33 j=jdrvp1,km1
458 do 33 j=jdrvp1,km1
459 kmj = k-j
459 kmj = k-j
460 ilo = kmj
460 ilo = kmj
461 do 33 jj=1,kmj
461 do 33 jj=1,kmj
462 aj(jj) = (aj(jj+1)*dl(ilo) + aj(jj)*dr(jj))/(dl(ilo)+dr(jj))
462 aj(jj) = (aj(jj+1)*dl(ilo) + aj(jj)*dr(jj))/(dl(ilo)+dr(jj))
463 33 ilo = ilo - 1
463 33 ilo = ilo - 1
464 39 bvalue = aj(1)
464 39 bvalue = aj(1)
465 c
465 c
466 99 return
466 99 return
467 end
467 end
468 subroutine interv ( xt, lxt, x, left, mflag )
468 subroutine interv ( xt, lxt, x, left, mflag )
469 c from * a practical guide to splines * by C. de Boor
469 c from * a practical guide to splines * by C. de Boor
470 computes left = max( i : xt(i) .lt. xt(lxt) .and. xt(i) .le. x ) .
470 computes left = max( i : xt(i) .lt. xt(lxt) .and. xt(i) .le. x ) .
471 c
471 c
472 c****** i n p u t ******
472 c****** i n p u t ******
473 c xt.....a real sequence, of length lxt , assumed to be nondecreasing
473 c xt.....a real sequence, of length lxt , assumed to be nondecreasing
474 c lxt.....number of terms in the sequence xt .
474 c lxt.....number of terms in the sequence xt .
475 c x.....the point whose location with respect to the sequence xt is
475 c x.....the point whose location with respect to the sequence xt is
476 c to be determined.
476 c to be determined.
477 c
477 c
478 c****** o u t p u t ******
478 c****** o u t p u t ******
479 c left, mflag.....both integers, whose value is
479 c left, mflag.....both integers, whose value is
480 c
480 c
481 c 1 -1 if x .lt. xt(1)
481 c 1 -1 if x .lt. xt(1)
482 c i 0 if xt(i) .le. x .lt. xt(i+1)
482 c i 0 if xt(i) .le. x .lt. xt(i+1)
483 c i 0 if xt(i) .lt. x .eq. xt(i+1) .eq. xt(lxt)
483 c i 0 if xt(i) .lt. x .eq. xt(i+1) .eq. xt(lxt)
484 c i 1 if xt(i) .lt. xt(i+1) .eq. xt(lxt) .lt. x
484 c i 1 if xt(i) .lt. xt(i+1) .eq. xt(lxt) .lt. x
485 c
485 c
486 c In particular, mflag = 0 is the 'usual' case. mflag .ne. 0
486 c In particular, mflag = 0 is the 'usual' case. mflag .ne. 0
487 c indicates that x lies outside the CLOSED interval
487 c indicates that x lies outside the CLOSED interval
488 c xt(1) .le. y .le. xt(lxt) . The asymmetric treatment of the
488 c xt(1) .le. y .le. xt(lxt) . The asymmetric treatment of the
489 c intervals is due to the decision to make all pp functions cont-
489 c intervals is due to the decision to make all pp functions cont-
490 c inuous from the right, but, by returning mflag = 0 even if
490 c inuous from the right, but, by returning mflag = 0 even if
491 C x = xt(lxt), there is the option of having the computed pp function
491 C x = xt(lxt), there is the option of having the computed pp function
492 c continuous from the left at xt(lxt) .
492 c continuous from the left at xt(lxt) .
493 c
493 c
494 c****** m e t h o d ******
494 c****** m e t h o d ******
495 c The program is designed to be efficient in the common situation that
495 c The program is designed to be efficient in the common situation that
496 c it is called repeatedly, with x taken from an increasing or decrea-
496 c it is called repeatedly, with x taken from an increasing or decrea-
497 c sing sequence. This will happen, e.g., when a pp function is to be
497 c sing sequence. This will happen, e.g., when a pp function is to be
498 c graphed. The first guess for left is therefore taken to be the val-
498 c graphed. The first guess for left is therefore taken to be the val-
499 c ue returned at the previous call and stored in the l o c a l varia-
499 c ue returned at the previous call and stored in the l o c a l varia-
500 c ble ilo . A first check ascertains that ilo .lt. lxt (this is nec-
500 c ble ilo . A first check ascertains that ilo .lt. lxt (this is nec-
501 c essary since the present call may have nothing to do with the previ-
501 c essary since the present call may have nothing to do with the previ-
502 c ous call). Then, if xt(ilo) .le. x .lt. xt(ilo+1), we set left =
502 c ous call). Then, if xt(ilo) .le. x .lt. xt(ilo+1), we set left =
503 c ilo and are done after just three comparisons.
503 c ilo and are done after just three comparisons.
504 c Otherwise, we repeatedly double the difference istep = ihi - ilo
504 c Otherwise, we repeatedly double the difference istep = ihi - ilo
505 c while also moving ilo and ihi in the direction of x , until
505 c while also moving ilo and ihi in the direction of x , until
506 c xt(ilo) .le. x .lt. xt(ihi) ,
506 c xt(ilo) .le. x .lt. xt(ihi) ,
507 c after which we use bisection to get, in addition, ilo+1 = ihi .
507 c after which we use bisection to get, in addition, ilo+1 = ihi .
508 c left = ilo is then returned.
508 c left = ilo is then returned.
509 c
509 c
510 integer left,lxt,mflag, ihi,ilo,istep,middle
510 integer left,lxt,mflag, ihi,ilo,istep,middle
511 real x,xt(lxt)
511 real x,xt(lxt)
512 data ilo /1/
512 data ilo /1/
513 save ilo
513 save ilo
514 ihi = ilo + 1
514 ihi = ilo + 1
515 if (ihi .lt. lxt) go to 20
515 if (ihi .lt. lxt) go to 20
516 if (x .ge. xt(lxt)) go to 110
516 if (x .ge. xt(lxt)) go to 110
517 if (lxt .le. 1) go to 90
517 if (lxt .le. 1) go to 90
518 ilo = lxt - 1
518 ilo = lxt - 1
519 ihi = lxt
519 ihi = lxt
520 c
520 c
521 20 if (x .ge. xt(ihi)) go to 40
521 20 if (x .ge. xt(ihi)) go to 40
522 if (x .ge. xt(ilo)) go to 100
522 if (x .ge. xt(ilo)) go to 100
523 c
523 c
524 c **** now x .lt. xt(ilo) . decrease ilo to capture x .
524 c **** now x .lt. xt(ilo) . decrease ilo to capture x .
525 istep = 1
525 istep = 1
526 31 ihi = ilo
526 31 ihi = ilo
527 ilo = ihi - istep
527 ilo = ihi - istep
528 if (ilo .le. 1) go to 35
528 if (ilo .le. 1) go to 35
529 if (x .ge. xt(ilo)) go to 50
529 if (x .ge. xt(ilo)) go to 50
530 istep = istep*2
530 istep = istep*2
531 go to 31
531 go to 31
532 35 ilo = 1
532 35 ilo = 1
533 if (x .lt. xt(1)) go to 90
533 if (x .lt. xt(1)) go to 90
534 go to 50
534 go to 50
535 c **** now x .ge. xt(ihi) . increase ihi to capture x .
535 c **** now x .ge. xt(ihi) . increase ihi to capture x .
536 40 istep = 1
536 40 istep = 1
537 41 ilo = ihi
537 41 ilo = ihi
538 ihi = ilo + istep
538 ihi = ilo + istep
539 if (ihi .ge. lxt) go to 45
539 if (ihi .ge. lxt) go to 45
540 if (x .lt. xt(ihi)) go to 50
540 if (x .lt. xt(ihi)) go to 50
541 istep = istep*2
541 istep = istep*2
542 go to 41
542 go to 41
543 45 if (x .ge. xt(lxt)) go to 110
543 45 if (x .ge. xt(lxt)) go to 110
544 ihi = lxt
544 ihi = lxt
545 c
545 c
546 c **** now xt(ilo) .le. x .lt. xt(ihi) . narrow the interval.
546 c **** now xt(ilo) .le. x .lt. xt(ihi) . narrow the interval.
547 50 middle = (ilo + ihi)/2
547 50 middle = (ilo + ihi)/2
548 if (middle .eq. ilo) go to 100
548 if (middle .eq. ilo) go to 100
549 c note. it is assumed that middle = ilo in case ihi = ilo+1 .
549 c note. it is assumed that middle = ilo in case ihi = ilo+1 .
550 if (x .lt. xt(middle)) go to 53
550 if (x .lt. xt(middle)) go to 53
551 ilo = middle
551 ilo = middle
552 go to 50
552 go to 50
553 53 ihi = middle
553 53 ihi = middle
554 go to 50
554 go to 50
555 c**** set output and return.
555 c**** set output and return.
556 90 mflag = -1
556 90 mflag = -1
557 left = 1
557 left = 1
558 return
558 return
559 100 mflag = 0
559 100 mflag = 0
560 left = ilo
560 left = ilo
561 return
561 return
562 110 mflag = 1
562 110 mflag = 1
563 if (x .eq. xt(lxt)) mflag = 0
563 if (x .eq. xt(lxt)) mflag = 0
564 left = lxt
564 left = lxt
565 111 if (left .eq. 1) return
565 111 if (left .eq. 1) return
566 left = left - 1
566 left = left - 1
567 if (xt(left) .lt. xt(lxt)) return
567 if (xt(left) .lt. xt(lxt)) return
568 go to 111
568 go to 111
569 end
569 end
General Comments 0
You need to be logged in to leave comments. Login now