Statistiques
| Révision :

root / src / Calc_baker_allGeomF.f90

Historique | Voir | Annoter | Télécharger (8,61 ko)

1
SUBROUTINE Calc_baker_allGeomF()
2
  !     
3
  ! This subroutine analyses a geometry to construct the baker
4
  ! delocalized internal coordinates
5
  ! v1.0
6
  ! We use only one geometry
7
  !     
8

    
9
!----------------------------------------------------------------------
10
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
11
!  Centre National de la Recherche Scientifique,
12
!  Université Claude Bernard Lyon 1. All rights reserved.
13
!
14
!  This work is registered with the Agency for the Protection of Programs 
15
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
16
!
17
!  Authors: P. Fleurat-Lessard, P. Dayal
18
!  Contact: optnpath@gmail.com
19
!
20
! This file is part of "Opt'n Path".
21
!
22
!  "Opt'n Path" is free software: you can redistribute it and/or modify
23
!  it under the terms of the GNU Affero General Public License as
24
!  published by the Free Software Foundation, either version 3 of the License,
25
!  or (at your option) any later version.
26
!
27
!  "Opt'n Path" is distributed in the hope that it will be useful,
28
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
29
!
30
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
31
!  GNU Affero General Public License for more details.
32
!
33
!  You should have received a copy of the GNU Affero General Public License
34
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
35
!
36
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
37
! for commercial licensing opportunities.
38
!----------------------------------------------------------------------
39
  Use Path_module, only : BMat_BakerT,Nat,NCoord,UMatF, &
40
                          NPrim,BTransInvF,Coordinate, &
41
              ScanCoord,BprimT,BBT,BBT_inv,XprimitiveF, &
42
              NgeomF,XyzGeomF
43
  ! BMat_BakerT(3*Nat,NCoord), NCoord=3*Nat or NFree=3*Nat-6-Symmetry_elimination
44
  ! depending upon the coordinate choice. IntCoordI(NGeomI,NCoord) where 
45
  ! UMatF(NGeomI,NPrim,NCoord), NCoord number of vectors in UMat matrix, i.e. NCoord
46
  ! Baker coordinates. NPrim is the number of primitive internal coordinates.
47
  
48
  Use Io_module
49
  IMPLICIT NONE
50

    
51
  REAL(KREAL), ALLOCATABLE :: Geom(:,:) !(3,Nat)
52
  ! NPrim is the number of primitive coordinates and NCoord is the number
53
  ! of internal coordinates. BMat is actually (NPrim,3*Nat).
54
  REAL(KREAL), ALLOCATABLE :: GMat(:,:) !(NPrim,NPrim)
55
  ! EigVec(..) contains ALL eigevectors of BMat times BprimT, NOT only Baker Coordinate vectors.
56
  REAL(KREAL), ALLOCATABLE :: EigVec(:,:), EigVal(:) ! EigVec(NPrim,NPrim)
57
  REAL(KREAL), ALLOCATABLE :: x(:), y(:), z(:)
58
  REAL(KREAL), ALLOCATABLE :: XPrimRef(:) ! NPrim
59
  INTEGER(KINT) :: IGeom
60
  
61

    
62
  INTEGER(KINT) :: I, J, K
63

    
64

    
65
  LOGICAL :: debug
66
  LOGICAL :: DebugPFL
67

    
68
  INTERFACE
69
     function valid(string) result (isValid)
70
       CHARACTER(*), intent(in) :: string
71
       logical                  :: isValid
72
     END function VALID
73

    
74
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
75
       use Path_module, only :  Pi,KINT, KREAL
76
       real(KREAL) ::  v1x,v1y,v1z,norm1
77
       real(KREAL) ::  v2x,v2y,v2z,norm2
78
       real(KREAL) ::  angle
79
     END FUNCTION ANGLE
80

    
81
     FUNCTION angle_d(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2,v3x,v3y,v3z,norm3)
82
       use Path_module, only :  Pi,KINT, KREAL
83
       real(KREAL) ::  v1x,v1y,v1z,norm1
84
       real(KREAL) ::  v2x,v2y,v2z,norm2
85
       real(KREAL) ::  v3x,v3y,v3z,norm3
86
       real(KREAL) ::  angle_d,ca,sa
87
     END FUNCTION ANGLE_D
88

    
89

    
90

    
91
     SUBROUTINE Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive,XPrimRef)
92
       !     
93
       ! This subroutine uses the description of a list of Coordinates
94
       ! to compute the values of the coordinates for a given geometry.
95
       !
96
!!!!!!!!!!
97
       ! Input:
98
       !   Na: INTEGER, Number of atoms
99
       !  x,y,z(Na): REAL, cartesian coordinates of the considered geometry
100
       ! Coordinate (Pointer(ListCoord)): description of the wanted coordiantes
101
       ! NPrim, INTEGER: Number of coordinates to compute
102
       !
103
       ! Optional: XPrimRef(NPrim) REAL: array that contains coordinates values for
104
       ! a former geometry. Useful for Dihedral angles evolution...
105

    
106
!!!!!!!!!!!
107
       ! Output:
108
       ! XPrimimite(NPrim) REAL: array that will contain the values of the coordinates
109
       !
110
!!!!!!!!!
111

    
112
       Use VarTypes
113
       Use Io_module
114
       Use Path_module, only : pi
115

    
116
       IMPLICIT NONE
117

    
118
       Type (ListCoord), POINTER :: Coordinate
119
       INTEGER(KINT), INTENT(IN) :: Nat,NPrim
120
       REAL(KREAL), INTENT(IN) :: x(Nat), y(Nat), z(Nat)
121
       REAL(KREAL), INTENT(IN), OPTIONAL :: XPrimRef(NPrim) 
122
       REAL(KREAL), INTENT(OUT) :: XPrimitive(NPrim)
123

    
124
     END SUBROUTINE CALC_XPRIM
125
  END INTERFACE
126

    
127

    
128

    
129

    
130
  debug=valid("Calc_baker_allGeomF")
131
  debugPFL=valid("bakerPFL")
132
  if (debug) WRITE(*,*) '============ Entering Calc_baker_allGeomF ============='
133

    
134
  ALLOCATE(Geom(3,Nat),x(Nat),y(Nat),z(Nat))
135
  ALLOCATE(XPrimRef(NPrim))
136
 
137
  ! Now calculating values of all primitive bonds for all final geometries:
138
  DO IGeom=1, NGeomF
139
     x(1:Nat) = XyzGeomF(IGeom,1,1:Nat)
140
     y(1:Nat) = XyzGeomF(IGeom,2,1:Nat)
141
     z(1:Nat) = XyzGeomF(IGeom,3,1:Nat)
142
     XPrimREf=XPrimitiveF(IGeom,:)
143
     Call Calc_XPrim(nat,x,y,z,Coordinate,NPrim,XPrimitiveF(IGeom,:),XPrimRef)
144
  END DO ! matches DO IGeom=1, NGeomF
145
   
146
  ALLOCATE(BprimT(3*Nat,NPrim))
147
  ALLOCATE(Gmat(NPrim,NPrim))
148
  ALLOCATE(EigVal(NPrim),EigVec(NPrim,NPrim))
149
  ALLOCATE(BBT(NCoord,NCoord))
150
  ALLOCATE(BBT_inv(NCoord,NCoord))
151
  BTransInvF = 0.d0
152

    
153
  DO IGeom=1, NGeomF 
154
     Geom(1,:)=XyzGeomF(IGeom,1,1:Nat) ! XyzGeomI(NGeomI,3,Nat)
155
     Geom(2,:)=XyzGeomF(IGeom,2,1:Nat)
156
     Geom(3,:)=XyzGeomF(IGeom,3,1:Nat)
157

    
158
   BprimT=0.d0
159
     ScanCoord=>Coordinate
160
     I=0
161
     DO WHILE (Associated(ScanCoord%next))
162
        I=I+1
163
        SELECT CASE (ScanCoord%Type)
164
        CASE ('BOND') 
165
          CALL CONSTRAINTS_BONDLENGTH_DER(Nat,ScanCoord%at1,ScanCoord%AT2, &
166
               Geom,BprimT(1,I))
167
        CASE ('ANGLE')
168
          CALL CONSTRAINTS_BONDANGLE_DER(Nat,ScanCoord%At1,ScanCoord%AT2, &
169
               ScanCoord%At3,Geom,BprimT(1,I))
170
        CASE ('DIHEDRAL')
171
          CALL CONSTRAINTS_TORSION_DER2(Nat,ScanCoord%At1,ScanCoord%AT2, &
172
               ScanCoord%At3,ScanCoord%At4,Geom,BprimT(1,I))
173
      END SELECT
174
        ScanCoord => ScanCoord%next
175
     END DO
176

    
177
   ! BprimT(3*Nat,NPrim)
178
   ! We now compute G=B(BT) matrix
179
   GMat=0.d0
180
   DO I=1,NPrim
181
    DO J=1,3*Nat
182
           GMat(:,I)=Gmat(:,I)+BprimT(J,:)*BprimT(J,I) !*1.d0/mass(atome(int(K/3.d0)))
183
    END DO
184
   END DO
185
  
186
   ! Diagonalize G
187
   EigVal=0.d0
188
   EigVec=0.d0
189
   Call Jacobi(GMat,NPrim,EigVal,EigVec,NPrim)
190
   Call Trie(NPrim,EigVal,EigVec,NPrim)
191
   DO I=1,NPrim
192
    !WRITE(*,'(1X,"Vector ",I3,": e=",F8.3)') I,EigVal(i)
193
    !WRITE(*,'(20(1X,F8.4))') EigVec(1:min(20,NPrim),I)
194
   END DO
195

    
196
   ! UMatF is nonredundant vector set, i.e. set of eigenvectors of BB^T
197
   !  corresponding to eigenvalues > zero.
198
   ! BMat_BakerT(3*Nat,NCoord), allocated in Path.f90, 
199
   ! NCoord=3*Nat-6
200
   BMat_BakerT = 0.d0
201
   J=0
202
   DO I=1,NPrim
203
    IF (abs(eigval(I))>=1e-6) THEN
204
       J=J+1
205
       DO K=1,NPrim
206
        ! BprimT is transpose of B^prim.
207
        ! B = UMatF^T B^prim, B^T = (B^prim)^T UMatF
208
        BMat_BakerT(:,J)=BMat_BakerT(:,J)+BprimT(:,K)*Eigvec(K,I)
209
       END DO
210
         IF(J .GT. 3*Nat-6) THEN
211
           WRITE(*,*) 'Number of vectors in Eigvec with eigval .GT. 1e-6(=UMatF) (=' &
212
                      ,J,') exceeded 3*Nat-6=',3*Nat-6, &
213
            'Stopping the calculation.'
214
           STOP
215
         END IF
216
         UMatF(IGeom,:,J) =  Eigvec(:,I)
217
    END IF
218
   END DO
219

    
220
!!!!!!!!!!!!!!!!!!!!
221
!
222
! Debug purposes
223
!
224
         if (debugPFL) THEN
225
        UMatF(IGeom,:,:)=0.
226
        DO J=1,3*Nat-6
227
           UMatF(IGeom,J,J)=1.
228
        END DO
229
        END IF
230

    
231
 
232
   !DO I=1, NPrim ! This loop is not needed because we already have IntCoordF
233
             ! from interpolation. 
234
   ! Transpose of UMatF is needed below, that is why UMatF(IGeom,I,:).
235
   ! IntCoordF(IGeom,:) = IntCoordF(IGeom,:) + UMat(IGeom,I,:)*XprimitiveF(IGeom,I)
236
   !END DO
237

    
238
   ! Calculation of BTransInvF starts here:
239
   ! Calculation of BBT(3*Nat-6,3*Nat-6)=BB^T:
240
   ! BMat_BakerT(3*Nat,NCoord) is Transpose of B = UMatF^TB^prim
241
    
242
   BBT = 0.d0
243
   DO I=1, NCoord
244
      DO J=1, 3*Nat
245
       ! BBT(:,I) forms BB^T
246
       BBT(:,I) = BBT(:,I) + BMat_BakerT(J,:)*BMat_BakerT(J,I)
247
    END DO
248
   END DO
249
    
250
   Call GenInv(NCoord,BBT,BBT_inv,NCoord) ! GenInv is in Mat_util.f90
251

    
252
   ! Calculation of (B^T)^-1 = (BB^T)^-1B:
253
   DO I=1, 3*Nat
254
      DO J=1, NCoord
255
        BTransInvF(IGeom,:,I) = BTransInvF(IGeom,:,I) + BBT_inv(:,J)*BMat_BakerT(I,J)
256
      END DO
257
   END DO
258
   
259
  END DO !matches DO IGeom=1, NGeomF
260
  
261
  DEALLOCATE(BBT,BBT_inv,BprimT,GMat,EigVal,EigVec)
262
  DEALLOCATE(Geom,x,y,z,XprimRef)
263
  
264
  IF (debug) WRITE(*,*) "DBG Calc_baker_allGeomF over."
265
END SUBROUTINE Calc_baker_allGeomF