root / src / Hupdate_MS.f90
Historique | Voir | Annoter | Télécharger (4,23 ko)
1 |
SUBROUTINE Hupdate_MS(Nfree,ds,dgrad,Hess) |
---|---|
2 |
|
3 |
! Hessian - or its inverse - update |
4 |
! We use the Murtagh-Sargent update, also called Symmetric Rank 1 |
5 |
! |
6 |
! input: |
7 |
! - nfree: number of coordinates |
8 |
! - ds: GeomOld-Geom (expressed in the optimization coord.) |
9 |
! - dgrad: GradOld-Grad (expressed in the optimization coord.) |
10 |
! |
11 |
! input/output: |
12 |
! - Hess: old Hessian in input, replaced by updated Hessian on output |
13 |
! (or inverse Hessian) |
14 |
! |
15 |
! |
16 |
!!!!!!!!!!!!!!!!!!!!!! |
17 |
! The update formula for the Hessian is: |
18 |
! (following Fletcher, approximate Hessian is denoted by B) |
19 |
! B(k+1)=B+[(y-Bs){(y-Bs)T}]/[{(y-Bs)T}s] |
20 |
! |
21 |
! it is self dual, ie for the inverse Hessian, denote by H: |
22 |
! H(k+1)=H+[(s-Hy){(s-Hy)T}]/[{(s-Hy)T}y] |
23 |
! |
24 |
! |
25 |
! We decompose the computation in two steps: |
26 |
! first we compute the update, and then we add it to Hess to get the |
27 |
! new Hessian. |
28 |
! This allows us to introduce a scaling factor if needed later. |
29 |
! |
30 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
31 |
|
32 |
|
33 |
!---------------------------------------------------------------------- |
34 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
35 |
! Centre National de la Recherche Scientifique, |
36 |
! Université Claude Bernard Lyon 1. All rights reserved. |
37 |
! |
38 |
! This work is registered with the Agency for the Protection of Programs |
39 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
40 |
! |
41 |
! Authors: P. Fleurat-Lessard, P. Dayal |
42 |
! Contact: optnpath@gmail.com |
43 |
! |
44 |
! This file is part of "Opt'n Path". |
45 |
! |
46 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
47 |
! it under the terms of the GNU Affero General Public License as |
48 |
! published by the Free Software Foundation, either version 3 of the License, |
49 |
! or (at your option) any later version. |
50 |
! |
51 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
52 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
53 |
! |
54 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
55 |
! GNU Affero General Public License for more details. |
56 |
! |
57 |
! You should have received a copy of the GNU Affero General Public License |
58 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
59 |
! |
60 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
61 |
! for commercial licensing opportunities. |
62 |
!---------------------------------------------------------------------- |
63 |
|
64 |
IMPLICIT NONE |
65 |
|
66 |
INTEGER, PARAMETER :: KINT=KIND(1) |
67 |
INTEGER, PARAMETER :: KREAL=KIND(1.D0) |
68 |
|
69 |
INTEGER(KINT), INTENT(IN) :: NFREE |
70 |
REAL(KREAL), INTENT(INOUT) :: Hess(Nfree,Nfree) |
71 |
REAL(KREAL), INTENT(IN) :: ds(Nfree) |
72 |
REAL(KREAL), INTENT(IN) :: dGrad(Nfree) |
73 |
|
74 |
|
75 |
REAL(KREAL), ALLOCATABLE :: HessOld(:, :) |
76 |
REAL(KREAL), ALLOCATABLE :: Hup(:,:) |
77 |
REAL(KREAL), ALLOCATABLE :: HupInt(:) |
78 |
REAL(KREAL), ALLOCATABLE :: HS(:), Num(:,:) |
79 |
REAL(KREAL) :: Den, NormDS |
80 |
INTEGER(KINT) :: i,j, idx |
81 |
|
82 |
LOGICAL :: debug |
83 |
|
84 |
interface |
85 |
function valid(string) result (isValid) |
86 |
logical :: isValid |
87 |
character(*), intent(in) :: string |
88 |
end function valid |
89 |
|
90 |
end interface |
91 |
|
92 |
|
93 |
|
94 |
|
95 |
debug=valid("Hupdate").OR.Valid("Hupdate_MS") |
96 |
|
97 |
if (debug) Call Header("Entering Hupdate_MS") |
98 |
|
99 |
ALLOCATE(HessOld(nfree,nfree), & |
100 |
Hup(nfree,nfree), & |
101 |
HupInt(nfree), HS(nfree), & |
102 |
Num(nfree,nfree)) |
103 |
|
104 |
HessOld=Hess |
105 |
|
106 |
if (debug) THEN |
107 |
WRITE(*,*) 'DBG Hupdate HessOld' |
108 |
Idx=min(12,Nfree) |
109 |
DO I=1,NFree |
110 |
WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx) |
111 |
END DO |
112 |
WRITE(*,*) 'DBG Hupdate ds' |
113 |
WRITE(*,'(12(1X,F8.4))') ds(1:Idx) |
114 |
WRITE(*,*) 'DBG Hupdate dGrad' |
115 |
WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx) |
116 |
END IF |
117 |
|
118 |
NormDS=sqrt(DOT_PRODUCT(DS,DS)) |
119 |
if (NormDS>=1e-6) THEN |
120 |
|
121 |
HS=0 |
122 |
DO I=1,nfree |
123 |
DO J=1,nfree |
124 |
HS(I)=HS(I)+HessOld(i,j)*Ds(j) |
125 |
END DO |
126 |
END DO |
127 |
|
128 |
if (debug) WRITE(*,*) "HS:",HS |
129 |
HupInt=DGrad-HS |
130 |
|
131 |
! WE calculate the MS update |
132 |
Num=0. |
133 |
Den=0. |
134 |
DO I=1,nfree |
135 |
DO J=1,nfree |
136 |
Num(I,J)=HUpInt(i)*HupInt(j) |
137 |
END DO |
138 |
Den=Den+Hupint(i)*Ds(i) |
139 |
END DO |
140 |
if (debug) WRITE(*,*) "Den:",Den,1./Den |
141 |
|
142 |
Hup=Num/Den |
143 |
|
144 |
Hess=HessOld+Hup |
145 |
ELSE |
146 |
Hess=HessOld |
147 |
END IF |
148 |
! WRITE(*,*) 'New hess' |
149 |
! DO I=1,nfree |
150 |
! WRITE(*,fmt) Hess(i,:) |
151 |
! END DO |
152 |
|
153 |
DEALLOCATE(HessOld,Hup, HupInt, HS, Num ) |
154 |
|
155 |
if (debug) Call Header("Hupdate_MS Over") |
156 |
|
157 |
END SUBROUTINE Hupdate_MS |