Statistiques
| Révision :

root / src / Hupdate_Bofill.f90

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

1
! This program reads an old hessian, old forces, new forces
2
! and print the updated hessian and old coordinates.
3
! Instead of the Murtagh-Sargent update, we use the Bofill update
4
! which is an average of Murtagh-Sargent and Powell-symmetryc-Broyden
5
! cf JCP 1999, vol 111 (19), p 8773
6

    
7
! This subroutine slightly differs from previous ones as
8
! it is written with the Gradient as input and not the forces
9
! Using the relation F=-Grad, one can easily go from older
10
! versions to this one (which more closely mimics the JCP article)
11

    
12
SUBROUTINE Hupdate_Bofill(Nfree,ds,dgrad,Hess)
13

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

    
45
  IMPLICIT NONE
46

    
47
  INTEGER, PARAMETER :: KINT=KIND(1)
48
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
49

    
50
  INTEGER(KINT), INTENT(IN) :: NFREE
51
  REAL(KREAL), INTENT(INOUT) :: Hess(Nfree,Nfree)
52
  REAL(KREAL), INTENT(IN) :: ds(Nfree)
53
  REAL(KREAL), INTENT(IN) :: dGrad(Nfree)
54

    
55

    
56
  REAL(KREAL), ALLOCATABLE  :: HessOld(:,:) , HupMS(:,:)
57
  REAL(KREAL), ALLOCATABLE  :: HupPSB(:,:), Hup(:,:)
58
  REAL(KREAL), ALLOCATABLE  :: HupInt(:)
59
  REAL(KREAL), ALLOCATABLE  :: HS(:), Num(:,:), Num2(:,:)
60
  REAL(KREAL) :: Phi, Num3, Den, Den2,NormDS
61
  INTEGER(KINT) :: i,j, idx
62

    
63
  LOGICAL debug,valid
64
  EXTERNAL valid
65

    
66
  debug=valid("Hupdate").OR.Valid("Hupdate_bofill")
67

    
68
  if (debug) WRITE(*,*) "=========================== Entering Hupdate_Bofill ===================="
69

    
70
  ALLOCATE(HessOld(nfree,nfree), HupMS(nfree,nfree),  &
71
       HupPSB(nfree,nfree), Hup(nfree,nfree), &
72
       HupInt(nfree), HS(nfree),  &
73
       Num(nfree,nfree), Num2(nfree,nfree) )
74

    
75
  HessOld=Hess
76

    
77
  if (debug) THEN
78
     WRITE(*,*) 'DBG Hupdate HessOld'
79
     Idx=min(12,Nfree)
80
     DO I=1,NFree
81
        WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx)
82
     END DO
83
     WRITE(*,*) 'DBG Hupdate ds'
84
     WRITE(*,'(12(1X,F8.4))') ds(1:Idx)
85
     WRITE(*,*) 'DBG Hupdate dGrad'
86
     WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx)
87
  END IF
88

    
89
  NormDS=sqrt(DOT_PRODUCT(DS,DS))
90
  if (NormDS>=1e-6) THEN
91

    
92
     HS=0
93
     DO I=1,nfree
94
        DO J=1,nfree
95
           HS(I)=HS(I)+HessOld(i,j)*Ds(j)
96
        END DO
97
     END DO
98
     HupInt=DGrad-HS
99

    
100
     ! WE calculate the MS update
101
     Num=0.
102
     Den=0.
103
     DO I=1,nfree
104
        DO J=1,nfree
105
           Num(I,J)=HUpInt(i)*HupInt(j)
106
        END DO
107
        Den=Den+Hupint(i)*Ds(i)
108
     END DO
109

    
110
     HupMS=Num/Den
111

    
112
     ! Now we calculate the PSB update
113
     Num=0
114
     Num2=0
115
     Num3=0
116
     Den=0
117
     DO I=1,nfree
118
        DO J=1,nfree
119
           Num(I,J)=HUpInt(i)*Ds(j)+Ds(i)*HupInt(j)
120
           Num2(I,J)=DS(i)*DS(j)
121
        END DO
122
        Den=Den+Ds(i)*Ds(i)
123
        Num3=Num3+DS(i)*HupInt(i)
124
     END DO
125
     HupPSB=Num/Den-Num3*Num2/(Den)**2
126

    
127
     ! We calculate Phi
128
     Den2=0.
129
     Do I=1,nfree
130
        Den2=Den2+HupInt(i)*HupInt(i)
131
     END DO
132
     Phi=Num3**2/(Den*Den2)
133

    
134
     Hup=Phi*HupMS+(1-Phi)*HupPSB
135

    
136
     Hess=HessOld+Hup
137
  ELSE
138
     Hess=HessOld
139
  END IF
140
  !     WRITE(*,*) 'New hess'
141
  !     DO I=1,nfree
142
  !        WRITE(*,fmt) Hess(i,:)
143
  !     END DO
144

    
145
  DEALLOCATE(HessOld, HupMS, HupPSB, Hup, &
146
       HupInt, HS, Num, Num2 )
147

    
148
  if (debug) WRITE(*,*) "=========================== Hupdate Over ===================="
149

    
150
END SUBROUTINE Hupdate_Bofill