Statistiques
| Révision :

root / src / CalcHess.f90

Historique | Voir | Annoter | Télécharger (5,79 ko)

1 1 pfleura2
      subroutine CalcHess (nfree,geom, hess,Igeom,Iopt)
2 1 pfleura2
3 1 pfleura2
! This routine calculate the Hessian (or its inverse) numerically using Egrad.
4 1 pfleura2
! It should be general and should work with any combination of Coord and Prog
5 1 pfleura2
! however, it has not been tested with Prog different from 'test'
6 1 pfleura2
7 1 pfleura2
! It comes mostly from the hess.f subroutine of the IRC package.
8 1 pfleura2
9 12 pfleura2
!----------------------------------------------------------------------
10 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
11 12 pfleura2
!  Centre National de la Recherche Scientifique,
12 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
13 12 pfleura2
!
14 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
15 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
16 12 pfleura2
!
17 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
18 12 pfleura2
!  Contact: optnpath@gmail.com
19 12 pfleura2
!
20 12 pfleura2
! This file is part of "Opt'n Path".
21 12 pfleura2
!
22 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
23 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
24 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
25 12 pfleura2
!  or (at your option) any later version.
26 12 pfleura2
!
27 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
28 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
29 12 pfleura2
!
30 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
31 12 pfleura2
!  GNU Affero General Public License for more details.
32 12 pfleura2
!
33 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
34 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
35 12 pfleura2
!
36 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
37 12 pfleura2
! for commercial licensing opportunities.
38 12 pfleura2
!----------------------------------------------------------------------
39 1 pfleura2
40 12 pfleura2
  use Path_module, only : Nat,Hinv
41 1 pfleura2
42 1 pfleura2
  use Io_module
43 1 pfleura2
!
44 1 pfleura2
      IMPLICIT NONE
45 1 pfleura2
46 1 pfleura2
!!!!!!!!!!! Parameters
47 1 pfleura2
  ! NFree==NCoord: Number of the degrees of freedom
48 1 pfleura2
  ! IGeom: index of the geometry.
49 1 pfleura2
  ! Iopt: step in the optimization process
50 1 pfleura2
  INTEGER(KINT), INTENT (IN) :: NFree, IGeom, IOpt
51 1 pfleura2
! Geometry at which Hessian is calculated (or its inverse)
52 1 pfleura2
   REAL(KREAL), INTENT(IN) :: Geom(Nfree)
53 1 pfleura2
! Hessian in compacted form
54 1 pfleura2
      REAL(KREAL), INTENT(OUT) ::  Hess(Nfree,Nfree)
55 1 pfleura2
!
56 1 pfleura2
! Parameters used to calculate the Hessian
57 1 pfleura2
! numerically with increasing accuray
58 1 pfleura2
      INTEGER(KINT), DIMENSION(6,0:3), PARAMETER :: IECOEF  &
59 1 pfleura2
      = RESHAPE(SOURCE=(/           &
60 1 pfleura2
          -1,1,0,0,0,0,             &
61 1 pfleura2
          -1,1,0,0,0,0,             &
62 1 pfleura2
          1,-8,8,-1,0,0,            &
63 1 pfleura2
          -1,9,-45,45,-9,1          &
64 1 pfleura2
       /), SHAPE=(/6,4/))
65 1 pfleura2
66 1 pfleura2
      INTEGER(KINT), DIMENSION(6,0:3), PARAMETER :: ISCOEF   &
67 1 pfleura2
      = RESHAPE(SOURCE=(/    &
68 1 pfleura2
         0,1,0,0,0,0,         &
69 1 pfleura2
          -1,1,0,0,0,0,       &
70 1 pfleura2
          -2,-1,1,2,0,0,      &
71 1 pfleura2
           -3,-2,-1,1,2,3     &
72 1 pfleura2
         /),SHAPE=(/6,4/))
73 1 pfleura2
      INTEGER(KINT), DIMENSION(0:3), PARAMETER :: NbDiv = (/1,2,12,60/)
74 1 pfleura2
      INTEGER(KINT), DIMENSION(0:3), PARAMETER :: NbCoef = (/2,2,4,6/)
75 1 pfleura2
76 1 pfleura2
77 1 pfleura2
      INTEGER(KINT), PARAMETER :: HessAcc=2
78 1 pfleura2
      REAL(KREAL), PARAMETER :: StepHess=0.01d0
79 1 pfleura2
! ======================================================================
80 1 pfleura2
      logical           :: debug
81 1 pfleura2
82 1 pfleura2
      REAL(KREAL) :: Ener
83 2 pfleura2
      INTEGER(KINT) :: I, J, IAT, IConst
84 1 pfleura2
85 2 pfleura2
       REAL(KREAL), ALLOCATABLE :: Temp2(:, :)
86 1 pfleura2
87 1 pfleura2
88 1 pfleura2
       REAL(KREAL), ALLOCATABLE :: Value(:), ValueOld(:), GradTMP(:)
89 1 pfleura2
       REAL(KREAL), ALLOCATABLE :: RTmp1(:,:), RTmp3(:,:)  ! Nat,3
90 1 pfleura2
       REAL(KREAL), ALLOCATABLE :: RTmp2(:)  ! NFree
91 1 pfleura2
! ======================================================================
92 1 pfleura2
93 1 pfleura2
  INTERFACE
94 1 pfleura2
     function valid(string) result (isValid)
95 1 pfleura2
       CHARACTER(*), intent(in) :: string
96 1 pfleura2
       logical                  :: isValid
97 1 pfleura2
     END function VALID
98 1 pfleura2
  END INTERFACE
99 1 pfleura2
100 1 pfleura2
! ======================================================================
101 1 pfleura2
102 1 pfleura2
      hess=0.d0
103 1 pfleura2
104 1 pfleura2
      debug=valid('CALCHESS').OR.valid('hess')
105 1 pfleura2
106 1 pfleura2
      if (debug) THEN
107 1 pfleura2
         WRITE(*,*) 'Entering CalcHess'
108 1 pfleura2
         WRITE(*,*) 'StepHess=',StepHess
109 1 pfleura2
         WRITE(*,*) "HessAcc=",HessAcc
110 1 pfleura2
      END IF
111 1 pfleura2
112 1 pfleura2
      allocate(Value(Nfree), ValueOld(Nfree), GradTmp(Nfree))
113 1 pfleura2
      ALLOCATE(RTmp1(Nat,3),RTmp3(Nat,3),RTmp2(NFree))
114 1 pfleura2
      allocate(temp2(Nfree,Nfree))
115 1 pfleura2
116 1 pfleura2
      RTmp1=0.d0
117 1 pfleura2
      RTmp3=0.d0
118 1 pfleura2
      RTmp2=Geom
119 1 pfleura2
120 1 pfleura2
!     Now, we calculate the second derivatives for the active variables
121 1 pfleura2
      Value=Geom
122 1 pfleura2
      ValueOld=Geom
123 1 pfleura2
124 1 pfleura2
      Do IConst=1,Nfree
125 1 pfleura2
            DO I=1,NbCoef(HessAcc)
126 1 pfleura2
               Value(IConst)=valueOld(IConst)+StepHess*ISCOEF(I,HessAcc)
127 1 pfleura2
!     We 'propagate this new value in the Zmatrix'
128 1 pfleura2
               call egrad(ener,value,gradtmp,NFree,IGeom,Iopt,RTmp1,RTmp2,RTmp3,.FALSE.)
129 1 pfleura2
               Hess(1:Nfree,IConst)= Hess(1:Nfree,IConst)+   &
130 1 pfleura2
                    gradtmp(1:Nfree)*IECOEF(I,HessAcc)
131 1 pfleura2
            end do
132 1 pfleura2
         END DO
133 1 pfleura2
        deallocate(Value, ValueOld, GradTmp)
134 1 pfleura2
135 1 pfleura2
        HESS=Hess/(NbDiv(HessAcc)*StepHess)
136 1 pfleura2
137 1 pfleura2
         if (debug) then
138 1 pfleura2
            WRITE(*,*) 'Non symmetrized hessian'
139 1 pfleura2
            DO iat=1,Nfree
140 1 pfleura2
               WRITE(*,'(15(1X,F12.5))') Hess(iat,1:Nfree)
141 1 pfleura2
            END DO
142 1 pfleura2
         END if
143 1 pfleura2
144 1 pfleura2
         DO i=1,Nfree
145 1 pfleura2
           Temp2(i,i)=Hess(i,i)
146 1 pfleura2
           DO j=i+1,Nfree
147 1 pfleura2
             Temp2(i,j)=0.5*(Hess(i,j)+Hess(j,i))
148 1 pfleura2
             Temp2(j,i)=Temp2(i,j)
149 1 pfleura2
           END DO
150 1 pfleura2
         END DO
151 1 pfleura2
152 1 pfleura2
         Hess=Hess-Temp2
153 1 pfleura2
154 1 pfleura2
         if (debug) then
155 1 pfleura2
            WRITE(*,*) 'Symmetrized hessian'
156 1 pfleura2
            DO iat=1,Nfree
157 1 pfleura2
               WRITE(*,'(15(1X,F12.5))') Temp2(iat,1:Nfree)
158 1 pfleura2
            END DO
159 1 pfleura2
160 1 pfleura2
            WRITE(*,*) 'Difference between non-syma and Symmetrized hessian'
161 1 pfleura2
            DO iat=1,Nfree
162 1 pfleura2
               WRITE(*,'(15(1X,F12.5))') Hess(iat,1:Nfree)
163 1 pfleura2
            END DO
164 1 pfleura2
         end if
165 1 pfleura2
166 1 pfleura2
! We calculate inverse of the Hessian only if HInv=T
167 1 pfleura2
168 1 pfleura2
         Hess=Temp2
169 1 pfleura2
      if (Hinv) then
170 1 pfleura2
        call Geninv(Nfree,Hess,Temp2,NFree)
171 1 pfleura2
        Hess=Temp2
172 1 pfleura2
      end if
173 1 pfleura2
174 1 pfleura2
      deallocate(RTmp1,RTmp2,RTmp3,Temp2)
175 1 pfleura2
176 1 pfleura2
! ======================================================================
177 1 pfleura2
      end subroutine CalcHess