Statistiques
| Révision :

root / src / Hinvup_DFP.f90 @ 8

Historique | Voir | Annoter | Télécharger (4,01 ko)

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

    
3
  IMPLICIT NONE
4

    
5
  INTEGER, PARAMETER :: KINT=KIND(1)
6
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
7

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

    
44

    
45
  REAL(KREAL), ALLOCATABLE  :: HessOld(:,:) , Wy(:)
46
  REAL(KREAL), ALLOCATABLE  :: Hup(:,:)
47
  REAL(KREAL), ALLOCATABLE  :: Num(:,:), Num2(:,:)
48
  REAL(KREAL) :: Den, Den2,NormDS
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
  debug=valid("Hinvup_DFP").OR. Valid('HUPDATE')
62

    
63
  if (debug) WRITE(*,*) "=========================== Entering Hinvup_DFP ===================="
64

    
65
  ALLOCATE(HessOld(nfree,nfree), Hup(nfree,nfree), &
66
       Num(nfree,nfree), Num2(nfree,nfree),Wy(Nfree) )
67

    
68

    
69

    
70
  HessOld=Hess
71

    
72
  if (debug) THEN
73
     WRITE(*,*) 'DBG Hinvup_DFP HessOld'
74
     Idx=min(12,Nfree)
75
     DO I=1,NFree
76
        WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx)
77
     END DO
78
     WRITE(*,*) 'DBG Hinvup_DFP ds'
79
     WRITE(*,'(12(1X,F8.4))') ds(1:Idx)
80
     WRITE(*,*) 'DBG Hinvup_DFP dGrad'
81
     WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx)
82
  END IF
83

    
84

    
85

    
86
  NormDS=sqrt(DOT_PRODUCT(DS,DS))
87
  if (NormDS>=1e-6) THEN
88
     IF (debug) WRITE(*,*) 'NormDS=',NormDS
89
     IF (debug) WRITE(*,*) 'DS=',DS
90
     IF (debug) WRITE(*,*) 'DGrad=',DGrad
91
     ! We calculate the denominator (DGrad,DS)
92
     den=DOT_PRODUCT(DGrad,DS)
93

    
94
     if (debug) WRITE(*,*) "(y,s)=(yT)s",den
95

    
96
     ! We calculate Wy
97
     Wy=0
98
     DO I=1,nfree
99
        DO J=1,NFree
100
           Wy(I)=Wy(I)+HessOld(i,j)*DGrad(j)
101
        END DO
102
     END DO
103

    
104
     if (debug) WRITE(*,*) "Wy=",Wy
105

    
106
     ! We calculate Num=s(sT)
107
     Num=0.
108
     DO I=1,Nfree
109
        DO J=1,Nfree
110
           Num(I,J)=ds(i)*Ds(j)
111
        END DO
112
     END DO
113

    
114
     if (debug) THEN
115
        WRITE(*,*) "s(sT)"
116
        DO I=1,NFree
117
           WRITE(*,*) Num(I,:)
118
        END DO
119
     END if
120

    
121
     ! We calculate Num2=Wy(WyT)
122
     Num2=0
123
     Do I=1,NFree
124
        DO J=1,NFree
125
             Num2(I,J)=Wy(i)*Wy(j)
126
        END DO
127
     END DO
128

    
129
     if (debug) THEN
130
        WRITE(*,*) "Wy(WyT)"
131
        DO I=1,NFree
132
           WRITE(*,*) Num2(I,:)
133
        END DO
134
     END if
135

    
136

    
137
! we calculate den=(sT)y
138
     den=DOT_PRODUCT(ds,dgrad)
139

    
140
! we calculate den2=(yT)Wy
141
     den2=DOT_PRODUCT(dgrad,Wy)
142

    
143
     if (debug) THEN
144
        WRITE(*,*) "(sT)y,(yT)Wy ",den,den2
145
     END if
146

    
147

    
148
     !We add everything
149
     Hup=Num/den-Num2/den2
150
     Hess=HessOld+Hup
151

    
152
     if (debug) THEN
153
        WRITE(*,*) 'DBG Hinvup_DFP Hup'
154
        Idx=min(12,Nfree)
155
        DO I=1,NFree
156
           WRITE(*,'(12(1X,F8.4))') Hup(I,1:Idx)
157
        END DO
158
        WRITE(*,*) 'DBG Hinvup_DFP Hess new'
159
        Idx=min(12,Nfree)
160
        DO I=1,NFree
161
           WRITE(*,'(12(1X,F8.4))') Hess(I,1:Idx)
162
        END DO
163
     END IF
164

    
165
  ELSE
166
     Hess=HessOld
167
  END IF
168

    
169
  DEALLOCATE(HessOld, Wy, Hup, Num, Num2 )
170

    
171
  if (debug) WRITE(*,*) "=========================== Hinvup_DFP Over ===================="
172

    
173
END SUBROUTINE Hinvup_DFP