ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
fpcurf.f
Go to the documentation of this file.
1  subroutine fpcurf(iopt,x,y,w,m,xb,xe,k,s,nest,tol,maxit,k1,k2,
2  * n,t,c,fp,fpint,z,a,b,g,q,nrdata,ier)
3  implicit none
4 c ..
5 c ..scalar arguments..
6  real*8 xb,xe,s,tol,fp
7  integer iopt,m,k,nest,maxit,k1,k2,n,ier
8 c ..array arguments..
9  real*8 x(m),y(m),w(m),t(nest),c(nest),fpint(nest),
10  * z(nest),a(nest,k1),b(nest,k2),g(nest,k2),q(m,k1)
11  integer nrdata(nest)
12 c ..local scalars..
13  real*8 acc,con1,con4,con9,cos,half,fpart,fpms,fpold,fp0,f1,f2,f3,
14  * one,p,pinv,piv,p1,p2,p3,rn,sin,store,term,wi,xi,yi
15  integer i,ich1,ich3,it,iter,i1,i2,i3,j,k3,l,l0,
16  * mk1,new,nk1,nmax,nmin,nplus,npl1,nrint,n8
17 c ..local arrays..
18  real*8 h(7)
19 c ..function references
20  real*8 abs,fprati
21  integer max0,min0
22 c ..subroutine references..
23 c fpback,fpbspl,fpgivs,fpdisc,fpknot,fprota
24 c ..
25 c set constants
26  one = 0.1e+01
27  con1 = 0.1e0
28  con9 = 0.9e0
29  con4 = 0.4e-01
30  half = 0.5e0
31 cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
32 c part 1: determination of the number of knots and their position c
33 c ************************************************************** c
34 c given a set of knots we compute the least-squares spline sinf(x), c
35 c and the corresponding sum of squared residuals fp=f(p=inf). c
36 c if iopt=-1 sinf(x) is the requested approximation. c
37 c if iopt=0 or iopt=1 we check whether we can accept the knots: c
38 c if fp <=s we will continue with the current set of knots. c
39 c if fp > s we will increase the number of knots and compute the c
40 c corresponding least-squares spline until finally fp<=s. c
41 c the initial choice of knots depends on the value of s and iopt. c
42 c if s=0 we have spline interpolation; in that case the number of c
43 c knots equals nmax = m+k+1. c
44 c if s > 0 and c
45 c iopt=0 we first compute the least-squares polynomial of c
46 c degree k; n = nmin = 2*k+2 c
47 c iopt=1 we start with the set of knots found at the last c
48 c call of the routine, except for the case that s > fp0; then c
49 c we compute directly the least-squares polynomial of degree k. c
50 cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
51 c determine nmin, the number of knots for polynomial approximation.
52  nmin = 2*k1
53  if(iopt.lt.0) go to 60
54 c calculation of acc, the absolute tolerance for the root of f(p)=s.
55  acc = tol*s
56 c determine nmax, the number of knots for spline interpolation.
57  nmax = m+k1
58  if(s.gt.0.) go to 45
59 c if s=0, s(x) is an interpolating spline.
60 c test whether the required storage space exceeds the available one.
61  n = nmax
62  if(nmax.gt.nest) go to 420
63 c find the position of the interior knots in case of interpolation.
64  10 mk1 = m-k1
65  if(mk1.eq.0) go to 60
66  k3 = k/2
67  i = k2
68  j = k3+2
69  if(k3*2.eq.k) go to 30
70  do 20 l=1,mk1
71  t(i) = x(j)
72  i = i+1
73  j = j+1
74  20 continue
75  go to 60
76  30 do 40 l=1,mk1
77  t(i) = (x(j)+x(j-1))*half
78  i = i+1
79  j = j+1
80  40 continue
81  go to 60
82 c if s>0 our initial choice of knots depends on the value of iopt.
83 c if iopt=0 or iopt=1 and s>=fp0, we start computing the least-squares
84 c polynomial of degree k which is a spline without interior knots.
85 c if iopt=1 and fp0>s we start computing the least squares spline
86 c according to the set of knots found at the last call of the routine.
87  45 if(iopt.eq.0) go to 50
88  if(n.eq.nmin) go to 50
89  fp0 = fpint(n)
90  fpold = fpint(n-1)
91  nplus = nrdata(n)
92  if(fp0.gt.s) go to 60
93  50 n = nmin
94  fpold = 0.
95  nplus = 0
96  nrdata(1) = m-2
97 c main loop for the different sets of knots. m is a save upper bound
98 c for the number of trials.
99  60 do 200 iter = 1,m
100  if(n.eq.nmin) ier = -2
101 c find nrint, tne number of knot intervals.
102  nrint = n-nmin+1
103 c find the position of the additional knots which are needed for
104 c the b-spline representation of s(x).
105  nk1 = n-k1
106  i = n
107  do 70 j=1,k1
108  t(j) = xb
109  t(i) = xe
110  i = i-1
111  70 continue
112 c compute the b-spline coefficients of the least-squares spline
113 c sinf(x). the observation matrix a is built up row by row and
114 c reduced to upper triangular form by givens transformations.
115 c at the same time fp=f(p=inf) is computed.
116  fp = 0.
117 c initialize the observation matrix a.
118  do 80 i=1,nk1
119  z(i) = 0.
120  do 80 j=1,k1
121  a(i,j) = 0.
122  80 continue
123  l = k1
124  do 130 it=1,m
125 c fetch the current data point x(it),y(it).
126  xi = x(it)
127  wi = w(it)
128  yi = y(it)*wi
129 c search for knot interval t(l) <= xi < t(l+1).
130  85 if(xi.lt.t(l+1) .or. l.eq.nk1) go to 90
131  l = l+1
132  go to 85
133 c evaluate the (k+1) non-zero b-splines at xi and store them in q.
134  90 call fpbspl(t,n,k,xi,l,h)
135  do 95 i=1,k1
136  q(it,i) = h(i)
137  h(i) = h(i)*wi
138  95 continue
139 c rotate the new row of the observation matrix into triangle.
140  j = l-k1
141  do 110 i=1,k1
142  j = j+1
143  piv = h(i)
144  if(piv.eq.0.) go to 110
145 c calculate the parameters of the givens transformation.
146  call fpgivs(piv,a(j,1),cos,sin)
147 c transformations to right hand side.
148  call fprota(cos,sin,yi,z(j))
149  if(i.eq.k1) go to 120
150  i2 = 1
151  i3 = i+1
152  do 100 i1 = i3,k1
153  i2 = i2+1
154 c transformations to left hand side.
155  call fprota(cos,sin,h(i1),a(j,i2))
156  100 continue
157  110 continue
158 c add contribution of this row to the sum of squares of residual
159 c right hand sides.
160  120 fp = fp+yi**2
161  130 continue
162  if(ier.eq.(-2)) fp0 = fp
163  fpint(n) = fp0
164  fpint(n-1) = fpold
165  nrdata(n) = nplus
166 c backward substitution to obtain the b-spline coefficients.
167  call fpback(a,z,nk1,k1,c,nest)
168 c test whether the approximation sinf(x) is an acceptable solution.
169  if(iopt.lt.0) go to 440
170  fpms = fp-s
171  if(abs(fpms).lt.acc) go to 440
172 c if f(p=inf) < s accept the choice of knots.
173  if(fpms.lt.0.) go to 250
174 c if n = nmax, sinf(x) is an interpolating spline.
175  if(n.eq.nmax) go to 430
176 c increase the number of knots.
177 c if n=nest we cannot increase the number of knots because of
178 c the storage capacity limitation.
179  if(n.eq.nest) go to 420
180 c determine the number of knots nplus we are going to add.
181  if(ier.eq.0) go to 140
182  nplus = 1
183  ier = 0
184  go to 150
185  140 npl1 = nplus*2
186  rn = nplus
187  if(fpold-fp.gt.acc) npl1 = rn*fpms/(fpold-fp)
188  nplus = min0(nplus*2,max0(npl1,nplus/2,1))
189  150 fpold = fp
190 c compute the sum((w(i)*(y(i)-s(x(i))))**2) for each knot interval
191 c t(j+k) <= x(i) <= t(j+k+1) and store it in fpint(j),j=1,2,...nrint.
192  fpart = 0.
193  i = 1
194  l = k2
195  new = 0
196  do 180 it=1,m
197  if(x(it).lt.t(l) .or. l.gt.nk1) go to 160
198  new = 1
199  l = l+1
200  160 term = 0.
201  l0 = l-k2
202  do 170 j=1,k1
203  l0 = l0+1
204  term = term+c(l0)*q(it,j)
205  170 continue
206  term = (w(it)*(term-y(it)))**2
207  fpart = fpart+term
208  if(new.eq.0) go to 180
209  store = term*half
210  fpint(i) = fpart-store
211  i = i+1
212  fpart = store
213  new = 0
214  180 continue
215  fpint(nrint) = fpart
216  do 190 l=1,nplus
217 c add a new knot.
218  call fpknot(x,m,t,n,fpint,nrdata,nrint,nest,1)
219 c if n=nmax we locate the knots as for interpolation.
220  if(n.eq.nmax) go to 10
221 c test whether we cannot further increase the number of knots.
222  if(n.eq.nest) go to 200
223  190 continue
224 c restart the computations with the new set of knots.
225  200 continue
226 c test whether the least-squares kth degree polynomial is a solution
227 c of our approximation problem.
228  250 if(ier.eq.(-2)) go to 440
229 cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
230 c part 2: determination of the smoothing spline sp(x). c
231 c *************************************************** c
232 c we have determined the number of knots and their position. c
233 c we now compute the b-spline coefficients of the smoothing spline c
234 c sp(x). the observation matrix a is extended by the rows of matrix c
235 c b expressing that the kth derivative discontinuities of sp(x) at c
236 c the interior knots t(k+2),...t(n-k-1) must be zero. the corres- c
237 c ponding weights of these additional rows are set to 1/p. c
238 c iteratively we then have to determine the value of p such that c
239 c f(p)=sum((w(i)*(y(i)-sp(x(i))))**2) be = s. we already know that c
240 c the least-squares kth degree polynomial corresponds to p=0, and c
241 c that the least-squares spline corresponds to p=infinity. the c
242 c iteration process which is proposed here, makes use of rational c
243 c interpolation. since f(p) is a convex and strictly decreasing c
244 c function of p, it can be approximated by a rational function c
245 c r(p) = (u*p+v)/(p+w). three values of p(p1,p2,p3) with correspond- c
246 c ing values of f(p) (f1=f(p1)-s,f2=f(p2)-s,f3=f(p3)-s) are used c
247 c to calculate the new value of p such that r(p)=s. convergence is c
248 c guaranteed by taking f1>0 and f3<0. c
249 cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
250 c evaluate the discontinuity jump of the kth derivative of the
251 c b-splines at the knots t(l),l=k+2,...n-k-1 and store in b.
252  call fpdisc(t,n,k2,b,nest)
253 c initial value for p.
254  p1 = 0.
255  f1 = fp0-s
256  p3 = -one
257  f3 = fpms
258  p = 0.
259  do 255 i=1,nk1
260  p = p+a(i,1)
261  255 continue
262  rn = nk1
263  p = rn/p
264  ich1 = 0
265  ich3 = 0
266  n8 = n-nmin
267 c iteration process to find the root of f(p) = s.
268  do 360 iter=1,maxit
269 c the rows of matrix b with weight 1/p are rotated into the
270 c triangularised observation matrix a which is stored in g.
271  pinv = one/p
272  do 260 i=1,nk1
273  c(i) = z(i)
274  g(i,k2) = 0.
275  do 260 j=1,k1
276  g(i,j) = a(i,j)
277  260 continue
278  do 300 it=1,n8
279 c the row of matrix b is rotated into triangle by givens transformation
280  do 270 i=1,k2
281  h(i) = b(it,i)*pinv
282  270 continue
283  yi = 0.
284  do 290 j=it,nk1
285  piv = h(1)
286 c calculate the parameters of the givens transformation.
287  call fpgivs(piv,g(j,1),cos,sin)
288 c transformations to right hand side.
289  call fprota(cos,sin,yi,c(j))
290  if(j.eq.nk1) go to 300
291  i2 = k1
292  if(j.gt.n8) i2 = nk1-j
293  do 280 i=1,i2
294 c transformations to left hand side.
295  i1 = i+1
296  call fprota(cos,sin,h(i1),g(j,i1))
297  h(i) = h(i1)
298  280 continue
299  h(i2+1) = 0.
300  290 continue
301  300 continue
302 c backward substitution to obtain the b-spline coefficients.
303  call fpback(g,c,nk1,k2,c,nest)
304 c computation of f(p).
305  fp = 0.
306  l = k2
307  do 330 it=1,m
308  if(x(it).lt.t(l) .or. l.gt.nk1) go to 310
309  l = l+1
310  310 l0 = l-k2
311  term = 0.
312  do 320 j=1,k1
313  l0 = l0+1
314  term = term+c(l0)*q(it,j)
315  320 continue
316  fp = fp+(w(it)*(term-y(it)))**2
317  330 continue
318 c test whether the approximation sp(x) is an acceptable solution.
319  fpms = fp-s
320  if(abs(fpms).lt.acc) go to 440
321 c test whether the maximal number of iterations is reached.
322  if(iter.eq.maxit) go to 400
323 c carry out one more step of the iteration process.
324  p2 = p
325  f2 = fpms
326  if(ich3.ne.0) go to 340
327  if((f2-f3).gt.acc) go to 335
328 c our initial choice of p is too large.
329  p3 = p2
330  f3 = f2
331  p = p*con4
332  if(p.le.p1) p=p1*con9 + p2*con1
333  go to 360
334  335 if(f2.lt.0.) ich3=1
335  340 if(ich1.ne.0) go to 350
336  if((f1-f2).gt.acc) go to 345
337 c our initial choice of p is too small
338  p1 = p2
339  f1 = f2
340  p = p/con4
341  if(p3.lt.0.) go to 360
342  if(p.ge.p3) p = p2*con1 + p3*con9
343  go to 360
344  345 if(f2.gt.0.) ich1=1
345 c test whether the iteration process proceeds as theoretically
346 c expected.
347  350 if(f2.ge.f1 .or. f2.le.f3) go to 410
348 c find the new value for p.
349  p = fprati(p1,f1,p2,f2,p3,f3)
350  360 continue
351 c error codes and messages.
352  400 ier = 3
353  go to 440
354  410 ier = 2
355  go to 440
356  420 ier = 1
357  go to 440
358  430 ier = -1
359  440 return
360  end
subroutine fpdisc(t, n, k2, b, nest)
Definition: fpdisc.f:1
subroutine fprota(cos, sin, a, b)
Definition: fprota.f:1
subroutine fpknot(x, m, t, n, fpint, nrdata, nrint, nest, istart)
Definition: fpknot.f:1
subroutine fpcurf(iopt, x, y, w, m, xb, xe, k, s, nest, tol, maxit, k1, k2, n, t, c, fp, fpint, z, a, b, g, q, nrdata, ier)
Definition: fpcurf.f:1
real(r8) function p(a, x, xr, xs, yr, ys, psi, psir, F_dia)
subroutine fpback(a, z, n, k, c, nest)
Definition: fpback.f:1
subroutine fpgivs(piv, ww, cos, sin)
Definition: fpgivs.f:1
real *8 function fprati(p1, f1, p2, f2, p3, f3)
Definition: fprati.f:1
subroutine fpbspl(t, n, k, x, l, h)
Definition: fpbspl.f:1