Statistiques
| Révision :

root / src / Hupdate_Bofill.f90 @ 2

Historique | Voir | Annoter | Télécharger (3,08 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
  IMPLICIT NONE
15

    
16
  INTEGER, PARAMETER :: KINT=KIND(1)
17
  INTEGER, PARAMETER :: KREAL=KIND(1.D0)
18

    
19
  INTEGER(KINT), INTENT(IN) :: NFREE
20
  REAL(KREAL), INTENT(INOUT) :: Hess(Nfree,Nfree)
21
  REAL(KREAL), INTENT(IN) :: ds(Nfree)
22
  REAL(KREAL), INTENT(IN) :: dGrad(Nfree)
23

    
24

    
25
  REAL(KREAL), ALLOCATABLE  :: HessOld(:,:) , HupMS(:,:)
26
  REAL(KREAL), ALLOCATABLE  :: HupPSB(:,:), Hup(:,:)
27
  REAL(KREAL), ALLOCATABLE  :: HupInt(:)
28
  REAL(KREAL), ALLOCATABLE  :: HS(:), Num(:,:), Num2(:,:)
29
  REAL(KREAL) :: Phi, Num3, Den, Den2,NormDS
30
  CHARACTER(120) :: fmt,fmt2,Line
31
  INTEGER(KINT) :: i,j, idx
32

    
33
  LOGICAL debug,valid
34
  EXTERNAL valid
35

    
36
  debug=valid("Hupdate").OR.Valid("Hupdate_bofill")
37

    
38
  if (debug) WRITE(*,*) "=========================== Entering Hupdate_Bofill ===================="
39

    
40
  ALLOCATE(HessOld(nfree,nfree), HupMS(nfree,nfree),  &
41
       HupPSB(nfree,nfree), Hup(nfree,nfree), &
42
       HupInt(nfree), HS(nfree),  &
43
       Num(nfree,nfree), Num2(nfree,nfree) )
44

    
45
  HessOld=Hess
46

    
47
  if (debug) THEN
48
     WRITE(*,*) 'DBG Hupdate HessOld'
49
     Idx=min(12,Nfree)
50
     DO I=1,NFree
51
        WRITE(*,'(12(1X,F8.4))') HessOld(I,1:Idx)
52
     END DO
53
     WRITE(*,*) 'DBG Hupdate ds'
54
     WRITE(*,'(12(1X,F8.4))') ds(1:Idx)
55
     WRITE(*,*) 'DBG Hupdate dGrad'
56
     WRITE(*,'(12(1X,F8.4))') dGrad(1:Idx)
57
  END IF
58

    
59
  NormDS=sqrt(DOT_PRODUCT(DS,DS))
60
  if (NormDS>=1e-6) THEN
61

    
62
     HS=0
63
     DO I=1,nfree
64
        DO J=1,nfree
65
           HS(I)=HS(I)+HessOld(i,j)*Ds(j)
66
        END DO
67
     END DO
68
     HupInt=DGrad-HS
69

    
70
     ! WE calculate the MS update
71
     Num=0.
72
     Den=0.
73
     DO I=1,nfree
74
        DO J=1,nfree
75
           Num(I,J)=HUpInt(i)*HupInt(j)
76
        END DO
77
        Den=Den+Hupint(i)*Ds(i)
78
     END DO
79

    
80
     HupMS=Num/Den
81

    
82
     ! Now we calculate the PSB update
83
     Num=0
84
     Num2=0
85
     Num3=0
86
     Den=0
87
     DO I=1,nfree
88
        DO J=1,nfree
89
           Num(I,J)=HUpInt(i)*Ds(j)+Ds(i)*HupInt(j)
90
           Num2(I,J)=DS(i)*DS(j)
91
        END DO
92
        Den=Den+Ds(i)*Ds(i)
93
        Num3=Num3+DS(i)*HupInt(i)
94
     END DO
95
     HupPSB=Num/Den-Num3*Num2/(Den)**2
96

    
97
     ! We calculate Phi
98
     Den2=0.
99
     Do I=1,nfree
100
        Den2=Den2+HupInt(i)*HupInt(i)
101
     END DO
102
     Phi=Num3**2/(Den*Den2)
103

    
104
     Hup=Phi*HupMS+(1-Phi)*HupPSB
105

    
106
     Hess=HessOld+Hup
107
  ELSE
108
     Hess=HessOld
109
  END IF
110
  !     WRITE(*,*) 'New hess'
111
  !     DO I=1,nfree
112
  !        WRITE(*,fmt) Hess(i,:)
113
  !     END DO
114

    
115
  DEALLOCATE(HessOld, HupMS, HupPSB, Hup, &
116
       HupInt, HS, Num, Num2 )
117

    
118
  if (debug) WRITE(*,*) "=========================== Hupdate Over ===================="
119

    
120
END SUBROUTINE Hupdate_Bofill