Statistiques
| Révision :

root / src / Hinvup_DFP.f90 @ 1

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

1 1 pfleura2
SUBROUTINE Hinvup_DFP(Nfree,ds,dgrad,Hess)
2 1 pfleura2
3 1 pfleura2
  IMPLICIT NONE
4 1 pfleura2
5 1 pfleura2
  INTEGER, PARAMETER :: KINT=KIND(1)
6 1 pfleura2
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
7 1 pfleura2
8 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: NFREE
9 1 pfleura2
  REAL(KREAL), INTENT(INOUT) :: Hess(Nfree,Nfree)
10 1 pfleura2
  REAL(KREAL), INTENT(IN) :: ds(Nfree)
11 1 pfleura2
  REAL(KREAL), INTENT(IN) :: dGrad(Nfree)
12 1 pfleura2
13 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
14 1 pfleura2
!
15 1 pfleura2
! This subroutine updates the inverse of the Hessian
16 1 pfleura2
! using a DFP formula.
17 1 pfleura2
!
18 1 pfleura2
! input:
19 1 pfleura2
!  - nfree: number of coordinates
20 1 pfleura2
!  - ds: GeomOld-Geom (expressed in the optimization coord.)
21 1 pfleura2
!  - dgrad: GradOld-Grad  (expressed in the optimization coord.)
22 1 pfleura2
!
23 1 pfleura2
!  input/output:
24 1 pfleura2
!  - Hess: old Hessian in input, replaced by updated Hessian on output
25 1 pfleura2
!
26 1 pfleura2
!  Notations for the formula:
27 1 pfleura2
! s=Geom-GeomOld
28 1 pfleura2
! y=Grad-GradOld
29 1 pfleura2
! W= (H)-1 ie the inverse matrix that we are updating
30 1 pfleura2
! W+=W + s(sT)/(s,y)-[Wy(yT)W]/(y,Wy)
31 1 pfleura2
!
32 1 pfleura2
! We decompose the computation in two steps:
33 1 pfleura2
! first we compute the update, and then we add it to Hess to get the
34 1 pfleura2
! new Hessian.
35 1 pfleura2
! This allows us to introduce a scaling factor if needed later.
36 1 pfleura2
!
37 1 pfleura2
!!!!!!!!!!!!!!!!
38 1 pfleura2
!
39 1 pfleura2
! Due to the dual properties, this routine is also called to compute
40 1 pfleura2
! the BFGS update for the Hessian
41 1 pfleura2
!
42 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
43 1 pfleura2
44 1 pfleura2
45 1 pfleura2
  REAL(KREAL), ALLOCATABLE  :: HessOld(:,:) , Wy(:)
46 1 pfleura2
  REAL(KREAL), ALLOCATABLE  :: Hup(:,:)
47 1 pfleura2
  REAL(KREAL), ALLOCATABLE  :: Num(:,:), Num2(:,:)
48 1 pfleura2
  REAL(KREAL) :: Den, Den2,NormDS
49 1 pfleura2
  INTEGER(KINT) :: i,j,k, Idx
50 1 pfleura2
51 1 pfleura2
  LOGICAL :: debug
52 1 pfleura2
53 1 pfleura2
  interface
54 1 pfleura2
     function valid(string) result (isValid)
55 1 pfleura2
       logical                  :: isValid
56 1 pfleura2
       character(*), intent(in) :: string
57 1 pfleura2
     end function valid
58 1 pfleura2
59 1 pfleura2
  end interface
60 1 pfleura2
61 1 pfleura2
  debug=valid("Hinvup_DFP").OR. Valid('HUPDATE')
62 1 pfleura2
63 1 pfleura2
  if (debug) WRITE(*,*) "=========================== Entering Hinvup_DFP ===================="
64 1 pfleura2
65 1 pfleura2
  ALLOCATE(HessOld(nfree,nfree), Hup(nfree,nfree), &
66 1 pfleura2
       Num(nfree,nfree), Num2(nfree,nfree),Wy(Nfree) )
67 1 pfleura2
68 1 pfleura2
69 1 pfleura2
70 1 pfleura2
  HessOld=Hess
71 1 pfleura2
72 1 pfleura2
  if (debug) THEN
73 1 pfleura2
     WRITE(*,*) 'DBG Hinvup_DFP HessOld'
74 1 pfleura2
     Idx=min(12,Nfree)
75 1 pfleura2
     DO I=1,NFree
76 1 pfleura2
        WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx)
77 1 pfleura2
     END DO
78 1 pfleura2
     WRITE(*,*) 'DBG Hinvup_DFP ds'
79 1 pfleura2
     WRITE(*,'(12(1X,F8.4))') ds(1:Idx)
80 1 pfleura2
     WRITE(*,*) 'DBG Hinvup_DFP dGrad'
81 1 pfleura2
     WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx)
82 1 pfleura2
  END IF
83 1 pfleura2
84 1 pfleura2
85 1 pfleura2
86 1 pfleura2
  NormDS=sqrt(DOT_PRODUCT(DS,DS))
87 1 pfleura2
  if (NormDS>=1e-6) THEN
88 1 pfleura2
     IF (debug) WRITE(*,*) 'NormDS=',NormDS
89 1 pfleura2
     IF (debug) WRITE(*,*) 'DS=',DS
90 1 pfleura2
     IF (debug) WRITE(*,*) 'DGrad=',DGrad
91 1 pfleura2
     ! We calculate the denominator (DGrad,DS)
92 1 pfleura2
     den=DOT_PRODUCT(DGrad,DS)
93 1 pfleura2
94 1 pfleura2
     if (debug) WRITE(*,*) "(y,s)=(yT)s",den
95 1 pfleura2
96 1 pfleura2
     ! We calculate Wy
97 1 pfleura2
     Wy=0
98 1 pfleura2
     DO I=1,nfree
99 1 pfleura2
        DO J=1,NFree
100 1 pfleura2
           Wy(I)=Wy(I)+HessOld(i,j)*DGrad(j)
101 1 pfleura2
        END DO
102 1 pfleura2
     END DO
103 1 pfleura2
104 1 pfleura2
     if (debug) WRITE(*,*) "Wy=",Wy
105 1 pfleura2
106 1 pfleura2
     ! We calculate Num=s(sT)
107 1 pfleura2
     Num=0.
108 1 pfleura2
     DO I=1,Nfree
109 1 pfleura2
        DO J=1,Nfree
110 1 pfleura2
           Num(I,J)=ds(i)*Ds(j)
111 1 pfleura2
        END DO
112 1 pfleura2
     END DO
113 1 pfleura2
114 1 pfleura2
     if (debug) THEN
115 1 pfleura2
        WRITE(*,*) "s(sT)"
116 1 pfleura2
        DO I=1,NFree
117 1 pfleura2
           WRITE(*,*) Num(I,:)
118 1 pfleura2
        END DO
119 1 pfleura2
     END if
120 1 pfleura2
121 1 pfleura2
     ! We calculate Num2=Wy(WyT)
122 1 pfleura2
     Num2=0
123 1 pfleura2
     Do I=1,NFree
124 1 pfleura2
        DO J=1,NFree
125 1 pfleura2
             Num2(I,J)=Wy(i)*Wy(j)
126 1 pfleura2
        END DO
127 1 pfleura2
     END DO
128 1 pfleura2
129 1 pfleura2
     if (debug) THEN
130 1 pfleura2
        WRITE(*,*) "Wy(WyT)"
131 1 pfleura2
        DO I=1,NFree
132 1 pfleura2
           WRITE(*,*) Num2(I,:)
133 1 pfleura2
        END DO
134 1 pfleura2
     END if
135 1 pfleura2
136 1 pfleura2
137 1 pfleura2
! we calculate den=(sT)y
138 1 pfleura2
     den=DOT_PRODUCT(ds,dgrad)
139 1 pfleura2
140 1 pfleura2
! we calculate den2=(yT)Wy
141 1 pfleura2
     den2=DOT_PRODUCT(dgrad,Wy)
142 1 pfleura2
143 1 pfleura2
     if (debug) THEN
144 1 pfleura2
        WRITE(*,*) "(sT)y,(yT)Wy ",den,den2
145 1 pfleura2
     END if
146 1 pfleura2
147 1 pfleura2
148 1 pfleura2
     !We add everything
149 1 pfleura2
     Hup=Num/den-Num2/den2
150 1 pfleura2
     Hess=HessOld+Hup
151 1 pfleura2
152 1 pfleura2
     if (debug) THEN
153 1 pfleura2
        WRITE(*,*) 'DBG Hinvup_DFP Hup'
154 1 pfleura2
        Idx=min(12,Nfree)
155 1 pfleura2
        DO I=1,NFree
156 1 pfleura2
           WRITE(*,'(12(1X,F8.4))') Hup(I,1:Idx)
157 1 pfleura2
        END DO
158 1 pfleura2
        WRITE(*,*) 'DBG Hinvup_DFP Hess new'
159 1 pfleura2
        Idx=min(12,Nfree)
160 1 pfleura2
        DO I=1,NFree
161 1 pfleura2
           WRITE(*,'(12(1X,F8.4))') Hess(I,1:Idx)
162 1 pfleura2
        END DO
163 1 pfleura2
     END IF
164 1 pfleura2
165 1 pfleura2
  ELSE
166 1 pfleura2
     Hess=HessOld
167 1 pfleura2
  END IF
168 1 pfleura2
169 1 pfleura2
  DEALLOCATE(HessOld, Wy, Hup, Num, Num2 )
170 1 pfleura2
171 1 pfleura2
  if (debug) WRITE(*,*) "=========================== Hinvup_DFP Over ===================="
172 1 pfleura2
173 1 pfleura2
END SUBROUTINE Hinvup_DFP