Statistiques
| Révision :

root / src / Hinvup_DFP.f90

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

1
SUBROUTINE Hinvup_DFP(Nfree,ds,dgrad,Hess)
2

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

    
34
  IMPLICIT NONE
35

    
36
  INTEGER, PARAMETER :: KINT=KIND(1)
37
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
38

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

    
75

    
76
  REAL(KREAL), ALLOCATABLE  :: HessOld(:,:) , Wy(:)
77
  REAL(KREAL), ALLOCATABLE  :: Hup(:,:)
78
  REAL(KREAL), ALLOCATABLE  :: Num(:,:), Num2(:,:)
79
  REAL(KREAL) :: Den, Den2,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
  debug=valid("Hinvup_DFP").OR. Valid('HUPDATE')
93

    
94
  if (debug) WRITE(*,*) "=========================== Entering Hinvup_DFP ===================="
95

    
96
  ALLOCATE(HessOld(nfree,nfree), Hup(nfree,nfree), &
97
       Num(nfree,nfree), Num2(nfree,nfree),Wy(Nfree) )
98

    
99

    
100

    
101
  HessOld=Hess
102

    
103
  if (debug) THEN
104
     WRITE(*,*) 'DBG Hinvup_DFP HessOld'
105
     Idx=min(12,Nfree)
106
     DO I=1,NFree
107
        WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx)
108
     END DO
109
     WRITE(*,*) 'DBG Hinvup_DFP ds'
110
     WRITE(*,'(12(1X,F8.4))') ds(1:Idx)
111
     WRITE(*,*) 'DBG Hinvup_DFP dGrad'
112
     WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx)
113
  END IF
114

    
115

    
116

    
117
  NormDS=sqrt(DOT_PRODUCT(DS,DS))
118
  if (NormDS>=1e-6) THEN
119
     IF (debug) WRITE(*,*) 'NormDS=',NormDS
120
     IF (debug) WRITE(*,*) 'DS=',DS
121
     IF (debug) WRITE(*,*) 'DGrad=',DGrad
122
     ! We calculate the denominator (DGrad,DS)
123
     den=DOT_PRODUCT(DGrad,DS)
124

    
125
     if (debug) WRITE(*,*) "(y,s)=(yT)s",den
126

    
127
     ! We calculate Wy
128
     Wy=0
129
     DO I=1,nfree
130
        DO J=1,NFree
131
           Wy(I)=Wy(I)+HessOld(i,j)*DGrad(j)
132
        END DO
133
     END DO
134

    
135
     if (debug) WRITE(*,*) "Wy=",Wy
136

    
137
     ! We calculate Num=s(sT)
138
     Num=0.
139
     DO I=1,Nfree
140
        DO J=1,Nfree
141
           Num(I,J)=ds(i)*Ds(j)
142
        END DO
143
     END DO
144

    
145
     if (debug) THEN
146
        WRITE(*,*) "s(sT)"
147
        DO I=1,NFree
148
           WRITE(*,*) Num(I,:)
149
        END DO
150
     END if
151

    
152
     ! We calculate Num2=Wy(WyT)
153
     Num2=0
154
     Do I=1,NFree
155
        DO J=1,NFree
156
             Num2(I,J)=Wy(i)*Wy(j)
157
        END DO
158
     END DO
159

    
160
     if (debug) THEN
161
        WRITE(*,*) "Wy(WyT)"
162
        DO I=1,NFree
163
           WRITE(*,*) Num2(I,:)
164
        END DO
165
     END if
166

    
167

    
168
! we calculate den=(sT)y
169
     den=DOT_PRODUCT(ds,dgrad)
170

    
171
! we calculate den2=(yT)Wy
172
     den2=DOT_PRODUCT(dgrad,Wy)
173

    
174
     if (debug) THEN
175
        WRITE(*,*) "(sT)y,(yT)Wy ",den,den2
176
     END if
177

    
178

    
179
     !We add everything
180
     Hup=Num/den-Num2/den2
181
     Hess=HessOld+Hup
182

    
183
     if (debug) THEN
184
        WRITE(*,*) 'DBG Hinvup_DFP Hup'
185
        Idx=min(12,Nfree)
186
        DO I=1,NFree
187
           WRITE(*,'(12(1X,F8.4))') Hup(I,1:Idx)
188
        END DO
189
        WRITE(*,*) 'DBG Hinvup_DFP Hess new'
190
        Idx=min(12,Nfree)
191
        DO I=1,NFree
192
           WRITE(*,'(12(1X,F8.4))') Hess(I,1:Idx)
193
        END DO
194
     END IF
195

    
196
  ELSE
197
     Hess=HessOld
198
  END IF
199

    
200
  DEALLOCATE(HessOld, Wy, Hup, Num, Num2 )
201

    
202
  if (debug) WRITE(*,*) "=========================== Hinvup_DFP Over ===================="
203

    
204
END SUBROUTINE Hinvup_DFP