Statistiques
| Révision :

root / src / Hinvup_BFGS.f90 @ 6

Historique | Voir | Annoter | Télécharger (4,51 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
  IMPLICIT NONE
9

    
10
  INTEGER, PARAMETER :: KINT=KIND(1)
11
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
12

    
13
  INTEGER(KINT), INTENT(IN) :: NFREE
14
  REAL(KREAL), INTENT(INOUT) :: Hess(Nfree,Nfree)
15
  REAL(KREAL), INTENT(IN) :: ds(Nfree)
16
  REAL(KREAL), INTENT(IN) :: dGrad(Nfree)
17
  
18
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
19
!
20
! This subroutine updates the inverse of the Hessian
21
! using a BFGS formula.
22
!
23
! input:
24
!  - nfree: number of coordinates
25
!  - ds: GeomOld-Geom (expressed in the optimization coord.)
26
!  - dgrad: GradOld-Grad  (expressed in the optimization coord.)
27
!
28
!  input/output:
29
!  - Hess: old Hessian in input, replaced by updated Hessian on output
30
!
31
!  Notations for the formula:
32
! s=Geom-GeomOld  
33
! y=Grad-GradOld
34
! W= (H)-1 ie the inverse matrix that we are updating
35
! W+=W - [s(yT)W+Wy(sT)]/(y,s)+ {1+[(y,Wy)/(y,s)]}(s(sT))/(y,s)
36
! 
37
!!!!!!!!!!!!!!!!
38
!
39
! Due to the dual properties, this routine is also called to compute
40
! the DFP update for the Hessian
41
!
42
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
43

    
44

    
45
  REAL(KREAL), ALLOCATABLE  :: HessOld(:,:) , Wy(:)
46
  REAL(KREAL), ALLOCATABLE  :: Hup(:,:),ssT(:,:)
47
  REAL(KREAL), ALLOCATABLE  :: HupInt(:)
48
  REAL(KREAL), ALLOCATABLE  :: Num(:,:), Num2(:,:)
49
  REAL(KREAL) :: Phi, Num3, Den, Den2,NormDS
50
  CHARACTER(120) :: fmt,fmt2,Line
51
  INTEGER(KINT) :: i,j,k, Idx
52

    
53
  LOGICAL debug,valid
54
  EXTERNAL valid
55

    
56
  debug=valid("Hinvup_BFGS")
57

    
58
  if (debug) WRITE(*,*) "=========================== Entering Hinvup_BFGS ===================="
59

    
60
  ALLOCATE(HessOld(nfree,nfree), Hup(nfree,nfree), &
61
       HupInt(nfree),  &
62
       Num(nfree,nfree), Num2(nfree,nfree),Wy(Nfree),ssT(Nfree,nFree) )
63

    
64

    
65

    
66
  HessOld=Hess
67

    
68
  if (debug) THEN
69
     WRITE(*,*) 'DBG Hinvup_BFGS HessOld'
70
     Idx=min(12,Nfree)
71
     DO I=1,NFree
72
        WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx)
73
     END DO
74
     WRITE(*,*) 'DBG Hinvup_BFGS ds'
75
     WRITE(*,'(12(1X,F8.4))') ds(1:Idx)
76
     WRITE(*,*) 'DBG Hinvup_BFGS dGrad'
77
     WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx)
78
  END IF
79

    
80

    
81

    
82
  NormDS=sqrt(DOT_PRODUCT(DS,DS))
83
  if (NormDS>=1e-6) THEN
84
     IF (debug) WRITE(*,*) 'NormDS=',NormDS
85
     IF (debug) WRITE(*,*) 'DS=',DS
86
     IF (debug) WRITE(*,*) 'DGrad=',DGrad
87
     ! We calculate the denominator (DGrad,DS)
88
     den=DOT_PRODUCT(DGrad,DS)
89

    
90
     if (debug) WRITE(*,*) "(y,s)=(yT)s",den
91

    
92
     ! We calculate Wy
93
     Wy=0
94
     DO I=1,nfree
95
        DO J=1,NFree
96
           Wy(I)=Wy(I)+HessOld(i,j)*DGrad(j)
97
        END DO
98
     END DO
99

    
100
     if (debug) WRITE(*,*) "Wy=",Wy
101

    
102
     ! We calculate Num=Wy(sT)
103
     Num=0.
104
     DO I=1,Nfree
105
        DO J=1,Nfree
106
           Num(I,J)=Wy(i)*Ds(j)
107
        END DO
108
     END DO
109

    
110
     if (debug) THEN
111
        WRITE(*,*) "Wy(sT)"
112
        DO I=1,NFree
113
           WRITE(*,*) Num(I,:)
114
        END DO
115
     END if
116

    
117
     ! We calculate Num2=s(yT)
118
     Num2=0
119
     Do I=1,NFree
120
        DO J=1,NFree
121
           Num2(I,J)=Ds(i)*DGrad(j)
122
        END DO
123
     END DO
124

    
125
     if (debug) THEN
126
        WRITE(*,*) "s(yT)"
127
        DO I=1,NFree
128
           WRITE(*,*) Num2(I,:)
129
        END DO
130
     END if
131

    
132

    
133
     ! we add Num2*W to Num
134
     Do I=1,NFree
135
        DO J=1,NFree
136
           DO K=1,NFree
137
              Num(I,J)=Num(I,J)+Num2(I,K)*HessOld(K,J)
138
           END DO
139
        END DO
140
     END DO
141

    
142
     if (debug) THEN
143
        WRITE(*,*) "Num=s(yT)W+Wy(sT)"
144
        DO I=1,NFree
145
           WRITE(*,*) Num(I,:)
146
        END DO
147
     END if
148

    
149

    
150
     ! we calculate ssT
151
     ssT=0.
152
     DO I=1,Nfree
153
        DO J=1,NFree
154
           ssT(I,J)=Ds(I)*Ds(J)
155
        END DO
156
     END DO
157

    
158
     if (debug) THEN
159
        WRITE(*,*) "s(sT)"
160
        DO I=1,NFree
161
           WRITE(*,*) ssT(I,:)
162
        END DO
163
     END if
164

    
165

    
166
     !We add everything
167
     Hup=(1+DOT_PRODUCT(DGRAD,Wy)/Den)*ssT/Den-Num/Den
168
     Hess=HessOld+Hup
169

    
170
     if (debug) THEN
171
        WRITE(*,*) 'DBG Hinvup_BFGS Hup'
172
        Idx=min(12,Nfree)
173
        DO I=1,NFree
174
           WRITE(*,'(12(1X,F8.4))') Hup(I,1:Idx)
175
        END DO
176
        WRITE(*,*) 'DBG Hinvup_BFGS Hess new'
177
        Idx=min(12,Nfree)
178
        DO I=1,NFree
179
           WRITE(*,'(12(1X,F8.4))') Hess(I,1:Idx)
180
        END DO
181
     END IF
182

    
183
  ELSE
184
     Hess=HessOld
185
  END IF
186
  !     WRITE(*,*) 'New hess'
187
  !     DO I=1,nfree
188
  !        WRITE(*,fmt) Hess(i,:)
189
  !     END DO
190

    
191
  DEALLOCATE(HessOld, Wy,ssT, Hup,HupInt, Num, Num2 )
192

    
193
  if (debug) WRITE(*,*) "=========================== Hinvup_BFGS Over ===================="
194

    
195
END SUBROUTINE Hinvup_BFGS