source: minqsn.f@ 6650a56

Last change on this file since 6650a56 was 6650a56, checked in by baerbaer <baerbaer@…>, 14 years ago

Explicitly declare variables.

git-svn-id: svn+ssh://svn.berlios.de/svnroot/repos/smmp/trunk@32 26dc1dd8-5c4e-0410-9ffe-d298b4865968

  • Property mode set to 100644
File size: 10.7 KB
Line 
1! **************************************************************
2!
3! This file contains the subroutines: minqsn,mc11a,mc11e
4!
5! Copyright 2003-2005 Frank Eisenmenger, U.H.E. Hansmann,
6! Shura Hayryan, Chin-Ku
7! Copyright 2007 Frank Eisenmenger, U.H.E. Hansmann,
8! Jan H. Meinke, Sandipan Mohanty
9!
10! **************************************************************
11
12 subroutine minqsn(n,mxn,x,f,g,scal,acur,h,d,w,xa,ga,xb,gb,maxfun,
13 & nfun)
14
15! .............................................................
16! PURPOSE: Quasi-Newton minimizer
17!
18! Unconstrained local minimization of function FUNC
19! vs. N variables by quasi-Newton method using BFGS-
20! formula to update hessian matrix; approximate line
21! searches performed using cubic extra-/interpolation
22! [see Gill P.E., Murray W., Wright M.H., Practical
23! Optimization, Ch. 2.2.5.7, 4.3.2.1 ff.,4.4.2.2.,
24! 4.5.2.1]
25!
26! INPUT: X,F,G - variables, value of FUNC, gradient at START
27! SCAL - factors to reduce(increase) initial step &
28! its lower bound for line searches, diagonal
29! elements of initial hessian matrix
30! MXN - maximal overall number of function calls
31!
32! OUTPUT: X,F,G - variables, value of FUNC, gradient at MINIMUM
33! NFUN - overall number of function calls used
34!
35! ARRAYS: H - approximate hessian matrix in symmetric storage
36! (dimension N(N+1)/2)
37! W,D,XA,XB,GA,GB - dimension N
38!
39! CALLS: MOVE - external to calculate function for current X
40! and its gradients
41! MC11E- solve system H*D=-G for search direction D, where
42! H is given in Cholesky-factorization
43! MC11A- update H using BFGS formula, factorizise new H
44! according to Cholesky (modified to maintain its
45! positive definiteness)
46!
47! PARAMETERS:
48!
49! EPS1 - checks reduction of FUNC during line search
50! ( 0.0001 <= EPS1 < 0.5 )
51! EPS2 - controls accuracy of line search (reduce to increase
52! accuracy; EPS1 < EPS2 <= 0.9 )
53! ACUR - fractional precision for determination of variables
54! (should not be smaller than sqrt of machine accuracy)
55! TINY - prevent division by zero during cubic extrapolation
56! .............................................................
57
58 implicit none
59
60 double precision eps1, eps2, tiny, zero, dff, c, g, scal, h, fa, f
61 double precision xa, x, ga, d, w, dga, di, fmin, gmin, stmin
62 double precision stepub, steplb, acur, step, xb, fb, gb, gl1, gl2
63 double precision si, dgb, sig
64
65 integer izero, ione, mxn, nfun, itr, i, n, n1, i1, j, isfv, maxfun
66 integer ir
67
68
69 parameter ( eps1=0.1d0,
70 & eps2=0.7d0,
71 & tiny=1.d-32,
72
73 & zero=0.d0,
74 & izero=0,
75 & ione=1 )
76
77 dimension x(mxn),g(mxn),scal(mxn),h(mxn*(mxn+1)/2),d(mxn),w(mxn),
78 & xa(mxn),ga(mxn),xb(mxn),gb(mxn)
79
80 nfun=0
81 itr=0
82 dff=0.
83! _______________ hessian to a diagonal matrix depending on scale
84 c=0.
85 do i=1,n
86 c=max(c,abs(g(i)*scal(i)))
87 enddo
88 if (c.le.0.) c=1.
89
90 n1=n+1
91 i1=(n*n1)/2
92 do i=1,i1
93 h(i)=0.
94 enddo
95
96 j=1
97 do i=1,n
98 h(j)=.01*c/scal(i)**2
99 j=j+n1-i
100 enddo
101
102 1 isfv=1 ! Re-start Search from Best Point so far
103
104 fa=f
105 do i=1,n
106 xa(i)=x(i)
107 ga(i)=g(i)
108 enddo
109
110 2 itr=itr+1 ! Start New Line-search from A
111
112! ______________ search direction of the iteration
113 do i=1,n
114 d(i)=-ga(i)
115 enddo
116 call MC11E (h,n,mxn,d,w,n)
117
118 c=0.
119 dga=0.
120 do i=1,n
121 di=d(i)
122 c=max(c,abs(di/scal(i)))
123 dga=dga+ga(i)*di ! directional derivative
124 enddo
125 c=1./c
126
127 if (dga.ge.0.) goto 5 ! search is uphill
128
129 fmin=fa
130 gmin=dga
131 stmin=0.
132
133 stepub=0. ! initial upper and
134 steplb=acur*c ! lower bound on step
135
136! ________________________ initial step of the line search
137 if (dff.gt.0.) then
138 step=min(1.d0,(dff+dff)/(-dga))
139 else
140 step=min(1.d0,c)
141 endif
142
143 3 if (nfun.ge.maxfun) then
144!c write (*,*) ' minfor> exceeded max. number of function calls'
145 return
146 endif
147
148 c=stmin+step ! Step along Search direction A->B
149 do i=1,n
150 xb(i)=xa(i)+c*d(i)
151 enddo
152
153 nfun=nfun+1
154 call MOVE(nfun,n,fb,xb,gb)
155
156 isfv=min(2,isfv)
157
158 if (fb.le.f) then
159 if (fb.eq.f) then
160 gl1=0.
161 gl2=0.
162 do i=1,n
163 si=scal(i)**2
164 gl1=gl1+si*g(i)**2
165 gl2=gl2+si*gb(i)**2
166 enddo
167 if (gl2.ge.gl1) goto 4
168 endif
169! ______________ store function value if it is smallest so far
170 f=fb
171 do i=1,n
172 x(i)=xb(i)
173 g(i)=gb(i)
174 enddo
175
176 isfv=3
177 endif
178
179 4 dgb=0.
180 do i=1,n
181 dgb=dgb+gb(i)*d(i) ! directional derivative at B
182 enddo
183
184 if (fb-fa.le.eps1*c*dga) then ! sufficient reduction of F
185
186 stmin=c
187 fmin=fb
188 gmin=dgb
189
190 stepub=stepub-step ! new upper bound on step
191
192! _______________________________ next step by extrapolation
193 if (stepub.gt.0.) then
194 step=.5*stepub
195 else
196 step=9.*stmin
197 endif
198 c=dga+3.*dgb-4.*(fb-fa)/stmin
199 if (c.gt.0.) step=min(step,stmin*max(1.d0,-dgb/c))
200
201 if (dgb.lt.eps2*dga) goto 3 ! line minimization still not
202 ! accurate enough -> further step
203 isfv=4-isfv
204
205 if (stmin+step.gt.steplb) then ! line minim. complete ->
206 ! update Hessian
207 do i=1,n
208 xa(i)=xb(i)
209 xb(i)=ga(i)
210 d(i)=gb(i)-ga(i)
211 ga(i)=gb(i)
212 enddo
213
214 ir=-n
215 sig=1./dga
216 call MC11A (h,n,mxn,xb,sig,w,ir,ione,zero)
217 ir=-ir
218 sig=1./(stmin*(dgb-dga))
219 call MC11A (h,n,mxn,d,sig,d,ir,izero,zero)
220
221 if (ir.eq.n) then ! Start new line search
222 dff=fa-fb
223 fa=fb
224 goto 2
225 else ! rank of new matrix is deficient
226 write (*,*) ' minfor> rank of hessian < number of variables'
227 return
228 endif
229
230 endif
231
232 else if (step.gt.steplb) then ! insufficient reduction of F:
233 ! new step by cubic interpolation
234 stepub=step ! new upper bound
235
236 c=gmin+dgb-3.*(fb-fmin)/step
237 c=c+gmin-sqrt(c*c-gmin*dgb) !! may be sqrt ( <0 )
238 if (abs(c).lt.tiny) then ! prevent division by zero
239 step=.1*step
240 else
241 step=step*max(.1d0,gmin/c)
242 endif
243 goto 3 ! -> reduced step along search direction
244
245 endif
246
247 5 if (isfv.ge.2) goto 1 ! -> Restart from best point so far
248
249 nfun=nfun+1
250 call MOVE(nfun,n,f,x,g)
251
252 return
253 end
254! ***********************************************
255 subroutine mc11a(a,n,mxn,z,sig,w,ir,mk,eps)
256!
257! CALLS: none
258!
259 implicit none
260
261 double precision sig, ti, w, z, a, v, eps, tim, al, r, b, gm, y
262
263 integer mxn, n, ir, np, ij, mk, i, j, mm
264
265 dimension a(mxn*(mxn+1)/2),z(mxn),w(mxn)
266
267 if (n.gt.1) then
268 if (sig.eq.0..or.ir.eq.0) return
269 np=n+1
270 if (sig.lt.0.) then
271 ti=1./sig
272 ij=1
273 if (mk.eq.0) then
274 do i=1,n
275 w(i)=z(i)
276 enddo
277 do i=1,n
278 if (a(ij).gt.0.) then
279 v=w(i)
280 ti=ti+v**2/a(ij)
281 if (i.lt.n) then
282 do j=i+1,n
283 ij=ij+1
284 w(j)=w(j)-v*a(ij)
285 enddo
286 endif
287 ij=ij+1
288 else
289 w(i)=0.
290 ij=ij+np-i
291 endif
292 enddo
293 else
294 do i=1,n
295 if (a(ij).ne.0.) ti=ti+w(i)**2/a(ij)
296 ij=ij+np-i
297 enddo
298 endif
299 if (ir.le.0) then
300 ti=0.
301 ir=-ir-1
302 else if (ti.gt.0.) then
303 if (eps.ne.0.) then
304 ti=eps/sig
305 else
306 ir=ir-1
307 ti=0.
308 endif
309 else if (mk.le.1) then
310 goto 1
311 endif
312 mm=1
313 tim=ti
314 do i=1,n
315 j=np-i
316 ij=ij-i
317 if (a(ij).ne.0.) tim=ti-w(j)**2/a(ij)
318 w(j)=ti
319 ti=tim
320 enddo
321 goto 2
322 endif
323 1 mm=0
324 tim=1./sig
325 2 ij=1
326 do i=1,n
327 v=z(i)
328 if (a(ij).gt.0.) then
329 al=v/a(ij)
330 if (mm.le.0) then
331 ti=tim+v*al
332 else
333 ti=w(i)
334 endif
335 r=ti/tim
336 a(ij)=a(ij)*r
337 if (r.eq.0..or.i.eq.n) goto 3
338 b=al/ti
339 if (r.gt.4.) then
340 gm=tim/ti
341 do j=i+1,n
342 ij=ij+1
343 y=a(ij)
344 a(ij)=b*z(j)+y*gm
345 z(j)=z(j)-v*y
346 enddo
347 else
348 do j=i+1,n
349 ij=ij+1
350 z(j)=z(j)-v*a(ij)
351 a(ij)=a(ij)+b*z(j)
352 enddo
353 endif
354 tim=ti
355 ij=ij+1
356 else if (ir.gt.0.or.sig.lt.0..or.v.eq.0.) then
357 ti=tim
358 ij=ij+np-i
359 else
360 ir=1-ir
361 a(ij)=v**2/tim
362 if (i.eq.n) return
363 do j=i+1,n
364 ij=ij+1
365 a(ij)=z(j)/v
366 enddo
367 return
368 endif
369 enddo
370 3 if (ir.lt.0) ir=-ir
371 else
372 a(1)=a(1)+sig*z(1)**2
373 ir=1
374 if (a(1).gt.0.) return
375 a(1)=0.
376 ir=0
377 endif
378
379 return
380 end
381! ************************************
382 subroutine mc11e(a,n,mxn,z,w,ir)
383!
384! CALLS: none
385!
386 implicit none
387 double precision w, z, v, a
388
389 integer mxn, ir, n, i, ij, i1, j, np, nip, ii, ip
390
391 dimension a(mxn*(mxn+1)/2),z(mxn),w(mxn)
392
393 if (ir.lt.n) return ! rank of matrix deficient
394
395 w(1)=z(1)
396 if (n.gt.1) then
397 do i=2,n
398 ij=i
399 i1=i-1
400 v=z(i)
401 do j=1,i1
402 v=v-a(ij)*z(j)
403 ij=ij+n-j
404 enddo
405 z(i)=v
406 w(i)=v
407 enddo
408 z(n)=z(n)/a(ij)
409 np=n+1
410 do nip=2,n
411 i=np-nip
412 ii=ij-nip
413 v=z(i)/a(ii)
414 ip=i+1
415 ij=ii
416 do j=ip,n
417 ii=ii+1
418 v=v-a(ii)*z(j)
419 enddo
420 z(i)=v
421 enddo
422 else
423 z(1)=z(1)/a(1)
424 endif
425
426 return
427 end
428
Note: See TracBrowser for help on using the repository browser.