source: minqsn.f

Last change on this file was 38d77eb, checked in by baerbaer <baerbaer@…>, 14 years ago

Redirected standard out to logString.

SMMP produced a lot of log messages. This became an issue when run in massively
parallel environments. I replaced all writes to standard out to a write to logString.
The next step is to pass this string to a function that writes the messages to a log
file according to their importance and the chosen log level.

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

  • Property mode set to 100644
File size: 10.8 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 character(255) logString
69
70 parameter ( eps1=0.1d0,
71 & eps2=0.7d0,
72 & tiny=1.d-32,
73
74 & zero=0.d0,
75 & izero=0,
76 & ione=1 )
77
78 dimension x(mxn),g(mxn),scal(mxn),h(mxn*(mxn+1)/2),d(mxn),w(mxn),
79 & xa(mxn),ga(mxn),xb(mxn),gb(mxn)
80
81 nfun=0
82 itr=0
83 dff=0.
84! _______________ hessian to a diagonal matrix depending on scale
85 c=0.
86 do i=1,n
87 c=max(c,abs(g(i)*scal(i)))
88 enddo
89 if (c.le.0.) c=1.
90
91 n1=n+1
92 i1=(n*n1)/2
93 do i=1,i1
94 h(i)=0.
95 enddo
96
97 j=1
98 do i=1,n
99 h(j)=.01*c/scal(i)**2
100 j=j+n1-i
101 enddo
102
103 1 isfv=1 ! Re-start Search from Best Point so far
104
105 fa=f
106 do i=1,n
107 xa(i)=x(i)
108 ga(i)=g(i)
109 enddo
110
111 2 itr=itr+1 ! Start New Line-search from A
112
113! ______________ search direction of the iteration
114 do i=1,n
115 d(i)=-ga(i)
116 enddo
117 call MC11E (h,n,mxn,d,w,n)
118
119 c=0.
120 dga=0.
121 do i=1,n
122 di=d(i)
123 c=max(c,abs(di/scal(i)))
124 dga=dga+ga(i)*di ! directional derivative
125 enddo
126 c=1./c
127
128 if (dga.ge.0.) goto 5 ! search is uphill
129
130 fmin=fa
131 gmin=dga
132 stmin=0.
133
134 stepub=0. ! initial upper and
135 steplb=acur*c ! lower bound on step
136
137! ________________________ initial step of the line search
138 if (dff.gt.0.) then
139 step=min(1.d0,(dff+dff)/(-dga))
140 else
141 step=min(1.d0,c)
142 endif
143
144 3 if (nfun.ge.maxfun) then
145!c write (logString, *) ' minfor> exceeded max. number of function calls'
146 return
147 endif
148
149 c=stmin+step ! Step along Search direction A->B
150 do i=1,n
151 xb(i)=xa(i)+c*d(i)
152 enddo
153
154 nfun=nfun+1
155 call MOVE(nfun,n,fb,xb,gb)
156
157 isfv=min(2,isfv)
158
159 if (fb.le.f) then
160 if (fb.eq.f) then
161 gl1=0.
162 gl2=0.
163 do i=1,n
164 si=scal(i)**2
165 gl1=gl1+si*g(i)**2
166 gl2=gl2+si*gb(i)**2
167 enddo
168 if (gl2.ge.gl1) goto 4
169 endif
170! ______________ store function value if it is smallest so far
171 f=fb
172 do i=1,n
173 x(i)=xb(i)
174 g(i)=gb(i)
175 enddo
176
177 isfv=3
178 endif
179
180 4 dgb=0.
181 do i=1,n
182 dgb=dgb+gb(i)*d(i) ! directional derivative at B
183 enddo
184
185 if (fb-fa.le.eps1*c*dga) then ! sufficient reduction of F
186
187 stmin=c
188 fmin=fb
189 gmin=dgb
190
191 stepub=stepub-step ! new upper bound on step
192
193! _______________________________ next step by extrapolation
194 if (stepub.gt.0.) then
195 step=.5*stepub
196 else
197 step=9.*stmin
198 endif
199 c=dga+3.*dgb-4.*(fb-fa)/stmin
200 if (c.gt.0.) step=min(step,stmin*max(1.d0,-dgb/c))
201
202 if (dgb.lt.eps2*dga) goto 3 ! line minimization still not
203 ! accurate enough -> further step
204 isfv=4-isfv
205
206 if (stmin+step.gt.steplb) then ! line minim. complete ->
207 ! update Hessian
208 do i=1,n
209 xa(i)=xb(i)
210 xb(i)=ga(i)
211 d(i)=gb(i)-ga(i)
212 ga(i)=gb(i)
213 enddo
214
215 ir=-n
216 sig=1./dga
217 call MC11A (h,n,mxn,xb,sig,w,ir,ione,zero)
218 ir=-ir
219 sig=1./(stmin*(dgb-dga))
220 call MC11A (h,n,mxn,d,sig,d,ir,izero,zero)
221
222 if (ir.eq.n) then ! Start new line search
223 dff=fa-fb
224 fa=fb
225 goto 2
226 else ! rank of new matrix is deficient
227 write (logString, *)
228 & ' minfor> rank of hessian < number of variables'
229 return
230 endif
231
232 endif
233
234 else if (step.gt.steplb) then ! insufficient reduction of F:
235 ! new step by cubic interpolation
236 stepub=step ! new upper bound
237
238 c=gmin+dgb-3.*(fb-fmin)/step
239 c=c+gmin-sqrt(c*c-gmin*dgb) !! may be sqrt ( <0 )
240 if (abs(c).lt.tiny) then ! prevent division by zero
241 step=.1*step
242 else
243 step=step*max(.1d0,gmin/c)
244 endif
245 goto 3 ! -> reduced step along search direction
246
247 endif
248
249 5 if (isfv.ge.2) goto 1 ! -> Restart from best point so far
250
251 nfun=nfun+1
252 call MOVE(nfun,n,f,x,g)
253
254 return
255 end
256! ***********************************************
257 subroutine mc11a(a,n,mxn,z,sig,w,ir,mk,eps)
258!
259! CALLS: none
260!
261 implicit none
262
263 double precision sig, ti, w, z, a, v, eps, tim, al, r, b, gm, y
264
265 integer mxn, n, ir, np, ij, mk, i, j, mm
266
267 dimension a(mxn*(mxn+1)/2),z(mxn),w(mxn)
268
269 if (n.gt.1) then
270 if (sig.eq.0..or.ir.eq.0) return
271 np=n+1
272 if (sig.lt.0.) then
273 ti=1./sig
274 ij=1
275 if (mk.eq.0) then
276 do i=1,n
277 w(i)=z(i)
278 enddo
279 do i=1,n
280 if (a(ij).gt.0.) then
281 v=w(i)
282 ti=ti+v**2/a(ij)
283 if (i.lt.n) then
284 do j=i+1,n
285 ij=ij+1
286 w(j)=w(j)-v*a(ij)
287 enddo
288 endif
289 ij=ij+1
290 else
291 w(i)=0.
292 ij=ij+np-i
293 endif
294 enddo
295 else
296 do i=1,n
297 if (a(ij).ne.0.) ti=ti+w(i)**2/a(ij)
298 ij=ij+np-i
299 enddo
300 endif
301 if (ir.le.0) then
302 ti=0.
303 ir=-ir-1
304 else if (ti.gt.0.) then
305 if (eps.ne.0.) then
306 ti=eps/sig
307 else
308 ir=ir-1
309 ti=0.
310 endif
311 else if (mk.le.1) then
312 goto 1
313 endif
314 mm=1
315 tim=ti
316 do i=1,n
317 j=np-i
318 ij=ij-i
319 if (a(ij).ne.0.) tim=ti-w(j)**2/a(ij)
320 w(j)=ti
321 ti=tim
322 enddo
323 goto 2
324 endif
325 1 mm=0
326 tim=1./sig
327 2 ij=1
328 do i=1,n
329 v=z(i)
330 if (a(ij).gt.0.) then
331 al=v/a(ij)
332 if (mm.le.0) then
333 ti=tim+v*al
334 else
335 ti=w(i)
336 endif
337 r=ti/tim
338 a(ij)=a(ij)*r
339 if (r.eq.0..or.i.eq.n) goto 3
340 b=al/ti
341 if (r.gt.4.) then
342 gm=tim/ti
343 do j=i+1,n
344 ij=ij+1
345 y=a(ij)
346 a(ij)=b*z(j)+y*gm
347 z(j)=z(j)-v*y
348 enddo
349 else
350 do j=i+1,n
351 ij=ij+1
352 z(j)=z(j)-v*a(ij)
353 a(ij)=a(ij)+b*z(j)
354 enddo
355 endif
356 tim=ti
357 ij=ij+1
358 else if (ir.gt.0.or.sig.lt.0..or.v.eq.0.) then
359 ti=tim
360 ij=ij+np-i
361 else
362 ir=1-ir
363 a(ij)=v**2/tim
364 if (i.eq.n) return
365 do j=i+1,n
366 ij=ij+1
367 a(ij)=z(j)/v
368 enddo
369 return
370 endif
371 enddo
372 3 if (ir.lt.0) ir=-ir
373 else
374 a(1)=a(1)+sig*z(1)**2
375 ir=1
376 if (a(1).gt.0.) return
377 a(1)=0.
378 ir=0
379 endif
380
381 return
382 end
383! ************************************
384 subroutine mc11e(a,n,mxn,z,w,ir)
385!
386! CALLS: none
387!
388 implicit none
389 double precision w, z, v, a
390
391 integer mxn, ir, n, i, ij, i1, j, np, nip, ii, ip
392
393 dimension a(mxn*(mxn+1)/2),z(mxn),w(mxn)
394
395 if (ir.lt.n) return ! rank of matrix deficient
396
397 w(1)=z(1)
398 if (n.gt.1) then
399 do i=2,n
400 ij=i
401 i1=i-1
402 v=z(i)
403 do j=1,i1
404 v=v-a(ij)*z(j)
405 ij=ij+n-j
406 enddo
407 z(i)=v
408 w(i)=v
409 enddo
410 z(n)=z(n)/a(ij)
411 np=n+1
412 do nip=2,n
413 i=np-nip
414 ii=ij-nip
415 v=z(i)/a(ii)
416 ip=i+1
417 ij=ii
418 do j=ip,n
419 ii=ii+1
420 v=v-a(ii)*z(j)
421 enddo
422 z(i)=v
423 enddo
424 else
425 z(1)=z(1)/a(1)
426 endif
427
428 return
429 end
430
Note: See TracBrowser for help on using the repository browser.