root / src / Hupdate_MS.f90 @ 7
Historique | Voir | Annoter | Télécharger (2,99 ko)
1 |
! Hessian - or its inverse - update |
---|---|
2 |
! We use the Murtagh-Sargent update, also called Symmetric Rank 1 |
3 |
! |
4 |
! input: |
5 |
! - nfree: number of coordinates |
6 |
! - ds: GeomOld-Geom (expressed in the optimization coord.) |
7 |
! - dgrad: GradOld-Grad (expressed in the optimization coord.) |
8 |
! |
9 |
! input/output: |
10 |
! - Hess: old Hessian in input, replaced by updated Hessian on output |
11 |
! (or inverse Hessian) |
12 |
! |
13 |
! |
14 |
!!!!!!!!!!!!!!!!!!!!!! |
15 |
! The update formula for the Hessian is: |
16 |
! (following Fletcher, approximate Hessian is denoted by B) |
17 |
! B(k+1)=B+[(y-Bs){(y-Bs)T}]/[{(y-Bs)T}s] |
18 |
! |
19 |
! it is self dual, ie for the inverse Hessian, denote by H: |
20 |
! H(k+1)=H+[(s-Hy){(s-Hy)T}]/[{(s-Hy)T}y] |
21 |
! |
22 |
! |
23 |
! We decompose the computation in two steps: |
24 |
! first we compute the update, and then we add it to Hess to get the |
25 |
! new Hessian. |
26 |
! This allows us to introduce a scaling factor if needed later. |
27 |
! |
28 |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
29 |
|
30 |
SUBROUTINE Hupdate_MS(Nfree,ds,dgrad,Hess) |
31 |
|
32 |
IMPLICIT NONE |
33 |
|
34 |
INTEGER, PARAMETER :: KINT=KIND(1) |
35 |
INTEGER, PARAMETER :: KREAL=KIND(1.D0) |
36 |
|
37 |
INTEGER(KINT), INTENT(IN) :: NFREE |
38 |
REAL(KREAL), INTENT(INOUT) :: Hess(Nfree,Nfree) |
39 |
REAL(KREAL), INTENT(IN) :: ds(Nfree) |
40 |
REAL(KREAL), INTENT(IN) :: dGrad(Nfree) |
41 |
|
42 |
|
43 |
REAL(KREAL), ALLOCATABLE :: HessOld(:,:) , HupMS(:,:) |
44 |
REAL(KREAL), ALLOCATABLE :: Hup(:,:) |
45 |
REAL(KREAL), ALLOCATABLE :: HupInt(:) |
46 |
REAL(KREAL), ALLOCATABLE :: HS(:), Num(:,:) |
47 |
REAL(KREAL) :: Phi, Num3, Den, Den2,NormDS |
48 |
CHARACTER(120) :: fmt,fmt2,Line |
49 |
INTEGER(KINT) :: i,j, idx |
50 |
|
51 |
LOGICAL :: debug |
52 |
|
53 |
interface |
54 |
function valid(string) result (isValid) |
55 |
logical :: isValid |
56 |
character(*), intent(in) :: string |
57 |
end function valid |
58 |
|
59 |
end interface |
60 |
|
61 |
|
62 |
|
63 |
|
64 |
debug=valid("Hupdate").OR.Valid("Hupdate_MS") |
65 |
|
66 |
if (debug) Call Header("Entering Hupdate_MS") |
67 |
|
68 |
ALLOCATE(HessOld(nfree,nfree), & |
69 |
Hup(nfree,nfree), & |
70 |
HupInt(nfree), HS(nfree), & |
71 |
Num(nfree,nfree)) |
72 |
|
73 |
HessOld=Hess |
74 |
|
75 |
if (debug) THEN |
76 |
WRITE(*,*) 'DBG Hupdate HessOld' |
77 |
Idx=min(12,Nfree) |
78 |
DO I=1,NFree |
79 |
WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx) |
80 |
END DO |
81 |
WRITE(*,*) 'DBG Hupdate ds' |
82 |
WRITE(*,'(12(1X,F8.4))') ds(1:Idx) |
83 |
WRITE(*,*) 'DBG Hupdate dGrad' |
84 |
WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx) |
85 |
END IF |
86 |
|
87 |
NormDS=sqrt(DOT_PRODUCT(DS,DS)) |
88 |
if (NormDS>=1e-6) THEN |
89 |
|
90 |
HS=0 |
91 |
DO I=1,nfree |
92 |
DO J=1,nfree |
93 |
HS(I)=HS(I)+HessOld(i,j)*Ds(j) |
94 |
END DO |
95 |
END DO |
96 |
|
97 |
if (debug) WRITE(*,*) "HS:",HS |
98 |
HupInt=DGrad-HS |
99 |
|
100 |
! WE calculate the MS update |
101 |
Num=0. |
102 |
Den=0. |
103 |
DO I=1,nfree |
104 |
DO J=1,nfree |
105 |
Num(I,J)=HUpInt(i)*HupInt(j) |
106 |
END DO |
107 |
Den=Den+Hupint(i)*Ds(i) |
108 |
END DO |
109 |
if (debug) WRITE(*,*) "Den:",Den,1./Den |
110 |
|
111 |
Hup=Num/Den |
112 |
|
113 |
Hess=HessOld+Hup |
114 |
ELSE |
115 |
Hess=HessOld |
116 |
END IF |
117 |
! WRITE(*,*) 'New hess' |
118 |
! DO I=1,nfree |
119 |
! WRITE(*,fmt) Hess(i,:) |
120 |
! END DO |
121 |
|
122 |
DEALLOCATE(HessOld,Hup, HupInt, HS, Num ) |
123 |
|
124 |
if (debug) Call Header("Hupdate_MS Over") |
125 |
|
126 |
END SUBROUTINE Hupdate_MS |