Statistiques
| Révision :

root / src / Hinvup_BFGS.f90

Historique | Voir | Annoter | Télécharger (5,77 ko)

1
! This program reads an old hessian, old forces, new
2
! forces and updates the hessian matrix inverse
3
! using the BFGS scheme.
4
! 
5
! This routines has been modified so that its input is now:
6
SUBROUTINE Hinvup_BFGS(Nfree,ds,dgrad,Hess)
7

    
8
!----------------------------------------------------------------------
9
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
10
!  Centre National de la Recherche Scientifique,
11
!  Université Claude Bernard Lyon 1. All rights reserved.
12
!
13
!  This work is registered with the Agency for the Protection of Programs 
14
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
15
!
16
!  Authors: P. Fleurat-Lessard, P. Dayal
17
!  Contact: optnpath@gmail.com
18
!
19
! This file is part of "Opt'n Path".
20
!
21
!  "Opt'n Path" is free software: you can redistribute it and/or modify
22
!  it under the terms of the GNU Affero General Public License as
23
!  published by the Free Software Foundation, either version 3 of the License,
24
!  or (at your option) any later version.
25
!
26
!  "Opt'n Path" is distributed in the hope that it will be useful,
27
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
28
!
29
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
30
!  GNU Affero General Public License for more details.
31
!
32
!  You should have received a copy of the GNU Affero General Public License
33
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
34
!
35
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
36
! for commercial licensing opportunities.
37
!----------------------------------------------------------------------
38

    
39
  IMPLICIT NONE
40

    
41
  INTEGER, PARAMETER :: KINT=KIND(1)
42
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
43

    
44
  INTEGER(KINT), INTENT(IN) :: NFREE
45
  REAL(KREAL), INTENT(INOUT) :: Hess(Nfree,Nfree)
46
  REAL(KREAL), INTENT(IN) :: ds(Nfree)
47
  REAL(KREAL), INTENT(IN) :: dGrad(Nfree)
48
  
49
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
50
!
51
! This subroutine updates the inverse of the Hessian
52
! using a BFGS formula.
53
!
54
! input:
55
!  - nfree: number of coordinates
56
!  - ds: GeomOld-Geom (expressed in the optimization coord.)
57
!  - dgrad: GradOld-Grad  (expressed in the optimization coord.)
58
!
59
!  input/output:
60
!  - Hess: old Hessian in input, replaced by updated Hessian on output
61
!
62
!  Notations for the formula:
63
! s=Geom-GeomOld  
64
! y=Grad-GradOld
65
! W= (H)-1 ie the inverse matrix that we are updating
66
! W+=W - [s(yT)W+Wy(sT)]/(y,s)+ {1+[(y,Wy)/(y,s)]}(s(sT))/(y,s)
67
! 
68
!!!!!!!!!!!!!!!!
69
!
70
! Due to the dual properties, this routine is also called to compute
71
! the DFP update for the Hessian
72
!
73
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
74

    
75

    
76
  REAL(KREAL), ALLOCATABLE  :: HessOld(:,:) , Wy(:)
77
  REAL(KREAL), ALLOCATABLE  :: Hup(:,:),ssT(:,:)
78
  REAL(KREAL), ALLOCATABLE  :: HupInt(:)
79
  REAL(KREAL), ALLOCATABLE  :: Num(:,:), Num2(:,:)
80
  REAL(KREAL) :: Den, NormDS
81
  INTEGER(KINT) :: i,j,k, Idx
82

    
83
  LOGICAL debug,valid
84
  EXTERNAL valid
85

    
86
  debug=valid("Hinvup_BFGS")
87

    
88
  if (debug) WRITE(*,*) "=========================== Entering Hinvup_BFGS ===================="
89

    
90
  ALLOCATE(HessOld(nfree,nfree), Hup(nfree,nfree), &
91
       HupInt(nfree),  &
92
       Num(nfree,nfree), Num2(nfree,nfree),Wy(Nfree),ssT(Nfree,nFree) )
93

    
94

    
95

    
96
  HessOld=Hess
97

    
98
  if (debug) THEN
99
     WRITE(*,*) 'DBG Hinvup_BFGS HessOld'
100
     Idx=min(12,Nfree)
101
     DO I=1,NFree
102
        WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx)
103
     END DO
104
     WRITE(*,*) 'DBG Hinvup_BFGS ds'
105
     WRITE(*,'(12(1X,F8.4))') ds(1:Idx)
106
     WRITE(*,*) 'DBG Hinvup_BFGS dGrad'
107
     WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx)
108
  END IF
109

    
110

    
111

    
112
  NormDS=sqrt(DOT_PRODUCT(DS,DS))
113
  if (NormDS>=1e-6) THEN
114
     IF (debug) WRITE(*,*) 'NormDS=',NormDS
115
     IF (debug) WRITE(*,*) 'DS=',DS
116
     IF (debug) WRITE(*,*) 'DGrad=',DGrad
117
     ! We calculate the denominator (DGrad,DS)
118
     den=DOT_PRODUCT(DGrad,DS)
119

    
120
     if (debug) WRITE(*,*) "(y,s)=(yT)s",den
121

    
122
     ! We calculate Wy
123
     Wy=0
124
     DO I=1,nfree
125
        DO J=1,NFree
126
           Wy(I)=Wy(I)+HessOld(i,j)*DGrad(j)
127
        END DO
128
     END DO
129

    
130
     if (debug) WRITE(*,*) "Wy=",Wy
131

    
132
     ! We calculate Num=Wy(sT)
133
     Num=0.
134
     DO I=1,Nfree
135
        DO J=1,Nfree
136
           Num(I,J)=Wy(i)*Ds(j)
137
        END DO
138
     END DO
139

    
140
     if (debug) THEN
141
        WRITE(*,*) "Wy(sT)"
142
        DO I=1,NFree
143
           WRITE(*,*) Num(I,:)
144
        END DO
145
     END if
146

    
147
     ! We calculate Num2=s(yT)
148
     Num2=0
149
     Do I=1,NFree
150
        DO J=1,NFree
151
           Num2(I,J)=Ds(i)*DGrad(j)
152
        END DO
153
     END DO
154

    
155
     if (debug) THEN
156
        WRITE(*,*) "s(yT)"
157
        DO I=1,NFree
158
           WRITE(*,*) Num2(I,:)
159
        END DO
160
     END if
161

    
162

    
163
     ! we add Num2*W to Num
164
     Do I=1,NFree
165
        DO J=1,NFree
166
           DO K=1,NFree
167
              Num(I,J)=Num(I,J)+Num2(I,K)*HessOld(K,J)
168
           END DO
169
        END DO
170
     END DO
171

    
172
     if (debug) THEN
173
        WRITE(*,*) "Num=s(yT)W+Wy(sT)"
174
        DO I=1,NFree
175
           WRITE(*,*) Num(I,:)
176
        END DO
177
     END if
178

    
179

    
180
     ! we calculate ssT
181
     ssT=0.
182
     DO I=1,Nfree
183
        DO J=1,NFree
184
           ssT(I,J)=Ds(I)*Ds(J)
185
        END DO
186
     END DO
187

    
188
     if (debug) THEN
189
        WRITE(*,*) "s(sT)"
190
        DO I=1,NFree
191
           WRITE(*,*) ssT(I,:)
192
        END DO
193
     END if
194

    
195

    
196
     !We add everything
197
     Hup=(1+DOT_PRODUCT(DGRAD,Wy)/Den)*ssT/Den-Num/Den
198
     Hess=HessOld+Hup
199

    
200
     if (debug) THEN
201
        WRITE(*,*) 'DBG Hinvup_BFGS Hup'
202
        Idx=min(12,Nfree)
203
        DO I=1,NFree
204
           WRITE(*,'(12(1X,F8.4))') Hup(I,1:Idx)
205
        END DO
206
        WRITE(*,*) 'DBG Hinvup_BFGS Hess new'
207
        Idx=min(12,Nfree)
208
        DO I=1,NFree
209
           WRITE(*,'(12(1X,F8.4))') Hess(I,1:Idx)
210
        END DO
211
     END IF
212

    
213
  ELSE
214
     Hess=HessOld
215
  END IF
216
  !     WRITE(*,*) 'New hess'
217
  !     DO I=1,nfree
218
  !        WRITE(*,fmt) Hess(i,:)
219
  !     END DO
220

    
221
  DEALLOCATE(HessOld, Wy,ssT, Hup,HupInt, Num, Num2 )
222

    
223
  if (debug) WRITE(*,*) "=========================== Hinvup_BFGS Over ===================="
224

    
225
END SUBROUTINE Hinvup_BFGS