Statistiques
| Révision :

root / src / Calc_baker.f90 @ 10

Historique | Voir | Annoter | Télécharger (40,75 ko)

1 1 pfleura2
SUBROUTINE Calc_baker(atome,r_cov,fact,frozen,IGeomRef)
2 1 pfleura2
  !
3 1 pfleura2
  ! This subroutine analyses a geometry to construct the baker
4 1 pfleura2
  ! delocalized internal coordinates
5 1 pfleura2
  ! v1.0
6 1 pfleura2
  ! We use only one geometry
7 1 pfleura2
  !
8 8 pfleura2
  Use Path_module, only : max_Z,NMaxL,Pi,Massat,BMat_BakerT, &
9 1 pfleura2
       Nat,NCoord,XyzGeomI,NGeomI,NGeomF,UMat,NPrim,BTransInv, &
10 1 pfleura2
       IntCoordI,Coordinate,CurrentCoord,ScanCoord,BprimT,BBT, &
11 8 pfleura2
       BBT_inv,Xprimitive,XPrimitiveF,UMat_local, &
12 1 pfleura2
       BTransInv_local, UMatF,BTransInvF,      &
13 1 pfleura2
       indzmat, dzdc,renum,order,OrderInv
14 1 pfleura2
  ! BMat_BakerT(3*Nat,NCoord), NCoord=3*Nat or NFree=3*Nat-6-Symmetry_elimination
15 1 pfleura2
  ! depending upon the coordinate choice. IntCoordI(NGeomI,NCoord) where
16 1 pfleura2
  ! UMat(NPrim,NCoord), NCoord number of vectors in UMat matrix, i.e. NCoord
17 1 pfleura2
  ! Baker coordinates. NPrim is the number of primitive internal coordinates.
18 1 pfleura2
19 1 pfleura2
  Use Io_module
20 1 pfleura2
  IMPLICIT NONE
21 1 pfleura2
22 1 pfleura2
  ! IGeom: Geometry index, IGeomRef: Reference Geometry.
23 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: atome(Nat),IGeomRef
24 1 pfleura2
  REAL(KREAL), INTENT(IN) :: fact
25 1 pfleura2
  REAL(KREAL), INTENT(IN)  :: r_cov(0:Max_Z)
26 1 pfleura2
  ! Frozen contains the indices of frozen atoms
27 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: Frozen(*)
28 1 pfleura2
29 1 pfleura2
  INTEGER(KINT), ALLOCATABLE :: LIAISONS(:,:) ! (Nat,0:NMaxL)
30 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: Geom(:,:) !(3,Nat)
31 1 pfleura2
  ! NPrim is the number of primitive coordinates and NCoord is the number
32 1 pfleura2
  ! of internal coordinates. BMat is actually (NPrim,3*Nat).
33 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: GMat(:,:) !(NPrim,NPrim)
34 1 pfleura2
  ! EigVec(..) contains ALL eigevectors of BMat times BprimT, NOT only Baker Coordinate vectors.
35 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: EigVec(:,:), EigVal(:) ! EigVec(NPrim,NPrim)
36 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: x(:), y(:), z(:)
37 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: x_refGeom(:), y_refGeom(:), z_refGeom(:)
38 1 pfleura2
  !REAL(KREAL), ALLOCATABLE :: V(:,:) ! (3*Nat,3*Nat)
39 1 pfleura2
  !REAL(KREAL), ALLOCATABLE :: P(:) ! Used in Baker Coordinates: Matrix Inversion
40 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: UMat_tmp(:,:)
41 1 pfleura2
  INTEGER(KINT) :: NbBonds, NbAngles, NbDihedrals, IGeom
42 1 pfleura2
43 2 pfleura2
  real(KREAL) :: vx, vy, vz, Norm
44 1 pfleura2
  real(KREAL) :: vx1,vy1,vz1,norm1
45 1 pfleura2
  real(KREAL) :: vx2,vy2,vz2,norm2
46 1 pfleura2
  real(KREAL) :: vx3,vy3,vz3,norm3
47 1 pfleura2
  real(KREAL) :: vx4,vy4,vz4,norm4
48 1 pfleura2
  real(KREAL) :: vx5,vy5,vz5,norm5
49 1 pfleura2
50 2 pfleura2
  INTEGER(KINT) :: I, J, IAt, K
51 2 pfleura2
  INTEGER(KINT) :: Kat, Lat, L
52 1 pfleura2
53 1 pfleura2
  REAL(KREAL) :: sAngleIatIKat, sAngleIIatLat
54 1 pfleura2
55 2 pfleura2
  LOGICAL :: debug, bond, AddPrimitiveCoord
56 1 pfleura2
57 1 pfleura2
  INTERFACE
58 1 pfleura2
     function valid(string) result (isValid)
59 1 pfleura2
       CHARACTER(*), intent(in) :: string
60 1 pfleura2
       logical                  :: isValid
61 1 pfleura2
     END function VALID
62 1 pfleura2
63 1 pfleura2
64 1 pfleura2
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
65 1 pfleura2
       use Path_module, only :  Pi,KINT, KREAL
66 1 pfleura2
       real(KREAL) ::  v1x,v1y,v1z,norm1
67 1 pfleura2
       real(KREAL) ::  v2x,v2y,v2z,norm2
68 1 pfleura2
       real(KREAL) ::  angle
69 1 pfleura2
     END FUNCTION ANGLE
70 1 pfleura2
71 1 pfleura2
72 1 pfleura2
73 1 pfleura2
     FUNCTION angle_d(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2,v3x,v3y,v3z,norm3)
74 1 pfleura2
       use Path_module, only :  Pi,KINT, KREAL
75 1 pfleura2
       real(KREAL) ::  v1x,v1y,v1z,norm1
76 1 pfleura2
       real(KREAL) ::  v2x,v2y,v2z,norm2
77 1 pfleura2
       real(KREAL) ::  v3x,v3y,v3z,norm3
78 1 pfleura2
       real(KREAL) ::  angle_d,ca,sa
79 1 pfleura2
     END FUNCTION ANGLE_D
80 1 pfleura2
81 1 pfleura2
82 1 pfleura2
83 7 pfleura2
84 1 pfleura2
     SUBROUTINE Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive,XPrimRef)
85 1 pfleura2
       !
86 1 pfleura2
       ! This subroutine uses the description of a list of Coordinates
87 1 pfleura2
       ! to compute the values of the coordinates for a given geometry.
88 1 pfleura2
       !
89 1 pfleura2
!!!!!!!!!!
90 1 pfleura2
       ! Input:
91 1 pfleura2
       !   Na: INTEGER, Number of atoms
92 1 pfleura2
       !  x,y,z(Na): REAL, cartesian coordinates of the considered geometry
93 1 pfleura2
       ! Coordinate (Pointer(ListCoord)): description of the wanted coordiantes
94 1 pfleura2
       ! NPrim, INTEGER: Number of coordinates to compute
95 1 pfleura2
       !
96 1 pfleura2
       ! Optional: XPrimRef(NPrim) REAL: array that contains coordinates values for
97 1 pfleura2
       ! a former geometry. Useful for Dihedral angles evolution...
98 1 pfleura2
99 1 pfleura2
!!!!!!!!!!!
100 1 pfleura2
       ! Output:
101 1 pfleura2
       ! XPrimimite(NPrim) REAL: array that will contain the values of the coordinates
102 1 pfleura2
       !
103 1 pfleura2
!!!!!!!!!
104 1 pfleura2
105 1 pfleura2
       Use VarTypes
106 1 pfleura2
       Use Io_module
107 1 pfleura2
       Use Path_module, only : pi
108 1 pfleura2
109 1 pfleura2
       IMPLICIT NONE
110 1 pfleura2
111 1 pfleura2
       Type (ListCoord), POINTER :: Coordinate
112 1 pfleura2
       INTEGER(KINT), INTENT(IN) :: Nat,NPrim
113 1 pfleura2
       REAL(KREAL), INTENT(IN) :: x(Nat), y(Nat), z(Nat)
114 1 pfleura2
       REAL(KREAL), INTENT(IN), OPTIONAL :: XPrimRef(NPrim)
115 1 pfleura2
       REAL(KREAL), INTENT(OUT) :: XPrimitive(NPrim)
116 1 pfleura2
117 1 pfleura2
     END SUBROUTINE CALC_XPRIM
118 1 pfleura2
  END INTERFACE
119 1 pfleura2
120 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
121 7 pfleura2
  !
122 1 pfleura2
!!!!!!!! PFL Debug
123 7 pfleura2
  !
124 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
125 1 pfleura2
  INTEGER(KINT) :: I1,I2,I3,I4
126 1 pfleura2
  LOGICAL :: debugPFL
127 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: val_zmat(:,:)
128 1 pfleura2
  INTEGER(KINT), ALLOCATABLE :: indzmat0(:,:)
129 1 pfleura2
130 1 pfleura2
131 1 pfleura2
  debug=valid("Calc_baker")
132 1 pfleura2
  debugPFL=valid("BakerPFL")
133 1 pfleura2
134 7 pfleura2
  if (debug) Call Header(" Entering Cal_baker ")
135 7 pfleura2
136 1 pfleura2
  IF (Nat.le.2) THEN
137 1 pfleura2
     WRITE(*,*) "I do not work for less than 2 atoms :-p"
138 1 pfleura2
     RETURN
139 1 pfleura2
  END IF
140 1 pfleura2
141 1 pfleura2
  IF (debug) THEN
142 1 pfleura2
     WRITE(*,*) "DBG Calc_baker, geom"
143 1 pfleura2
     DO I=1,Nat
144 1 pfleura2
        WRITE(*,'(1X,I5,":",I3,3(1X,F15.3))') I,atome(I),XyzGeomI(IGeomRef,1:3,I)
145 1 pfleura2
     END DO
146 1 pfleura2
  END IF
147 1 pfleura2
148 1 pfleura2
149 1 pfleura2
150 1 pfleura2
151 1 pfleura2
  ! we construct the list of bonds, valence angles and dihedral angles using this connectivity
152 1 pfleura2
  ALLOCATE(Coordinate)
153 1 pfleura2
  NULLIFY(Coordinate%next)
154 1 pfleura2
  NbBonds=0
155 1 pfleura2
  NbAngles=0
156 1 pfleura2
  NbDihedrals=0
157 1 pfleura2
158 1 pfleura2
  CurrentCoord => Coordinate
159 1 pfleura2
160 1 pfleura2
  ALLOCATE(Liaisons(Nat,0:NMaxL),Geom(3,Nat),x(Nat),y(Nat),z(Nat))
161 1 pfleura2
  ALLOCATE(x_refGeom(Nat),y_refGeom(Nat),z_refGeom(Nat))
162 1 pfleura2
163 1 pfleura2
  x_refGeom(1:Nat) = XyzGeomI(IGeomRef,1,1:Nat)
164 1 pfleura2
  y_refGeom(1:Nat) = XyzGeomI(IGeomRef,2,1:Nat)
165 1 pfleura2
  z_refGeom(1:Nat) = XyzGeomI(IGeomRef,3,1:Nat)
166 1 pfleura2
167 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
168 7 pfleura2
  !
169 7 pfleura2
  !   PFL Debug
170 7 pfleura2
  !
171 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
172 7 pfleura2
  if (debugPFL) THEN
173 7 pfleura2
     WRITE(*,*) "DBG PFL Calc_BAKER - Calculating Zmat"
174 1 pfleura2
     if (.not.ALLOCATED(indzmat)) THEN
175 1 pfleura2
        ALLOCATE(indzmat(Nat,5))
176 1 pfleura2
     END IF
177 1 pfleura2
     IF (.NOT.ALLOCATED(DzDc)) THEN
178 1 pfleura2
        ALLOCATE(DzDc(3,nat,3,Nat))
179 1 pfleura2
     END IF
180 1 pfleura2
     IF (.NOT.ALLOCATED(Val_zmat)) THEN
181 1 pfleura2
        ALLOCATE(val_zmat(nat,3))
182 1 pfleura2
     END IF
183 1 pfleura2
     IF (.NOT.ALLOCATED(indzmat0)) THEN
184 1 pfleura2
        ALLOCATE(indzmat0(nat,5))
185 1 pfleura2
     END IF
186 7 pfleura2
     ! We construct a Zmat
187 7 pfleura2
     IF (Frozen(1).NE.0) THEN
188 7 pfleura2
        Renum=.TRUE.
189 1 pfleura2
!!! remplcaer indzmat par indzmat0 puis renumerotation
190 7 pfleura2
        call Calc_zmat_const_frag(Nat,atome,IndZmat0,val_zmat, &
191 1 pfleura2
             x_refGeom,y_refGeom,z_refGeom, &
192 7 pfleura2
             r_cov,fact,frozen)
193 7 pfleura2
     ELSE
194 7 pfleura2
        !no zmat... we create our own
195 7 pfleura2
        call Calc_zmat_frag(Nat,atome,IndZmat0,val_zmat, &
196 1 pfleura2
             x_refGeom,y_refGeom,z_refGeom, &
197 7 pfleura2
             r_cov,fact)
198 7 pfleura2
     END IF
199 1 pfleura2
200 7 pfleura2
     DO I=1,Nat
201 7 pfleura2
        Order(IndZmat0(I,1))=I
202 7 pfleura2
        OrderInv(I)=IndZmat0(I,1)
203 7 pfleura2
     END DO
204 7 pfleura2
     IndZmat(1,1)=Order(IndZmat0(1,1))
205 7 pfleura2
     IndZmat(2,1)=Order(IndZmat0(2,1))
206 7 pfleura2
     IndZmat(2,2)=Order(IndZmat0(2,2))
207 7 pfleura2
     IndZmat(3,1)=Order(IndZmat0(3,1))
208 7 pfleura2
     IndZmat(3,2)=Order(IndZmat0(3,2))
209 7 pfleura2
     IndZmat(3,3)=Order(IndZmat0(3,3))
210 7 pfleura2
     DO I=4,Nat
211 7 pfleura2
        DO J=1,4
212 7 pfleura2
           IndZmat(I,J)=Order(IndZmat0(I,J))
213 1 pfleura2
        END DO
214 7 pfleura2
     end do
215 1 pfleura2
216 1 pfleura2
217 7 pfleura2
     WRITE(*,*) "DBG PFL CalcBaker, IndZmat0"
218 7 pfleura2
     DO I=1,Nat
219 7 pfleura2
        WRITE(*,*) I, indZmat0(I,:)
220 7 pfleura2
     end do
221 1 pfleura2
222 7 pfleura2
     WRITE(*,*) "DBG PFL CalcBaker, IndZmat"
223 7 pfleura2
     DO I=1,Nat
224 7 pfleura2
        WRITE(*,*) I, indZmat(I,:)
225 7 pfleura2
     end do
226 1 pfleura2
227 1 pfleura2
228 1 pfleura2
     DO I=1,Nat
229 1 pfleura2
        I1=indzmat0(I,1)
230 1 pfleura2
        I2=indzmat0(I,2)
231 1 pfleura2
        I3=indzmat0(I,3)
232 1 pfleura2
        I4=indzmat0(I,4)
233 7 pfleura2
        ! Adding BOND between at1 and at2
234 7 pfleura2
        WRITE(*,*)  "DBG Indzmat",I,I1,I2,I3,I4
235 7 pfleura2
        if (I2.NE.0) THEN
236 1 pfleura2
           NbBonds=NbBonds+1
237 7 pfleura2
           ! values of the coordinate (bond) is calculated for the reference geometry
238 7 pfleura2
           ! whereas the coordinates (bonds) (CurrentCoord%At1, CurrentCoord%At2, etc.)
239 7 pfleura2
           ! are determined using all geometries. vecteur is defined in bib_oper.f
240 7 pfleura2
           Call vecteur(I1,I2,x_refGeom,y_refGeom,z_refGeom,vx2,vy2,vz2,Norm2)
241 7 pfleura2
           !                  CurrentCoord%value=Norm2
242 7 pfleura2
           WRITE(*,'(1X,A,I5,A,2(1X,F12.6))') "Bond",NbBonds," Norm2,val_zmat",Norm2,val_zmat(I,1)
243 7 pfleura2
           CurrentCoord%value=val_zmat(I,1)
244 7 pfleura2
           CurrentCoord%SignDihedral = 0
245 7 pfleura2
           CurrentCoord%At1=I1
246 7 pfleura2
           CurrentCoord%At2=I2
247 7 pfleura2
           CurrentCoord%Type="BOND"
248 7 pfleura2
           IF (.NOT.ASSOCIATED(CurrentCoord%next)) THEN
249 7 pfleura2
              ALLOCATE(CurrentCoord%next)
250 7 pfleura2
              NULLIFY(CurrentCoord%next%next)
251 7 pfleura2
           END IF
252 7 pfleura2
           CurrentCoord => CurrentCoord%next
253 1 pfleura2
        END IF !IE.NE.0
254 7 pfleura2
        if (I3.NE.0) THEN
255 1 pfleura2
256 7 pfleura2
           NbAngles=NbAngles+1
257 7 pfleura2
           ! values of the coordinate (bond) is calculated for the reference geometry
258 7 pfleura2
           ! whereas the coordinates (bonds) (CurrentCoord%At1, CurrentCoord%At2, etc.) are
259 7 pfleura2
           ! determined using all geometries.
260 7 pfleura2
           Call vecteur(i2,I3,x_refGeom,y_refGeom,z_refGeom,vx1,vy1,vz1,Norm1)
261 7 pfleura2
           Call vecteur(i2,I1,x_refGeom,y_refGeom,z_refGeom,vx2,vy2,vz2,Norm2)
262 7 pfleura2
           !                       CurrentCoord%value=angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.
263 7 pfleura2
           WRITE(*,'(1X,A,I5,A,2(1X,F12.6))') "Angle",NbAngles," angle,val_zmat", &
264 7 pfleura2
                angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2),val_zmat(I,2)
265 7 pfleura2
           CurrentCoord%value=val_zmat(I,2)*Pi/180.
266 7 pfleura2
           CurrentCoord%SignDihedral = 0
267 7 pfleura2
           CurrentCoord%At1=I1
268 7 pfleura2
           CurrentCoord%At2=I2
269 7 pfleura2
           CurrentCoord%At3=I3
270 7 pfleura2
           CurrentCoord%Type="ANGLE"
271 7 pfleura2
           IF (.NOT.ASSOCIATED(CurrentCoord%next)) THEN
272 7 pfleura2
              ALLOCATE(CurrentCoord%next)
273 7 pfleura2
              NULLIFY(CurrentCoord%next%next)
274 7 pfleura2
           END IF
275 7 pfleura2
           CurrentCoord => CurrentCoord%next
276 7 pfleura2
        END IF ! matches IF (I3.NE.0)
277 7 pfleura2
        if (I4.NE.0) THEN
278 7 pfleura2
           NbDihedrals=NbDihedrals+1
279 7 pfleura2
           Call vecteur(I2,I1,x_refGeom,y_refGeom,z_refGeom,vx1,vy1,vz1,Norm1)
280 7 pfleura2
           Call vecteur(I2,I3,x_refGeom,y_refGeom,z_refGeom,vx2,vy2,vz2,Norm2)
281 7 pfleura2
           Call vecteur(I3,I4,x_refGeom,y_refGeom,z_refGeom,vx3,vy3,vz3,Norm3)
282 7 pfleura2
           CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
283 7 pfleura2
                vx4,vy4,vz4,norm4)
284 7 pfleura2
           CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, &
285 7 pfleura2
                vx5,vy5,vz5,norm5)
286 7 pfleura2
           !                       CurrentCoord%value=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
287 7 pfleura2
           !                            vx2,vy2,vz2,norm2)*Pi/180.
288 7 pfleura2
           WRITE(*,'(1X,A,I5,A,2(1X,F12.6))') "Dihedral",NbDihedrals,    &
289 7 pfleura2
                " angle_d,val_zmat", &
290 7 pfleura2
                angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
291 7 pfleura2
                vx2,vy2,vz2,norm2) &
292 7 pfleura2
                ,val_zmat(I,3)
293 1 pfleura2
294 7 pfleura2
           CurrentCoord%value = val_zmat(I,3)*Pi/180.
295 7 pfleura2
           CurrentCoord%SignDihedral = int(sign(1.D0,val_zmat(I,3)))
296 7 pfleura2
           CurrentCoord%At1=I1
297 7 pfleura2
           CurrentCoord%At2=I2
298 7 pfleura2
           CurrentCoord%At3=I3
299 7 pfleura2
           CurrentCoord%At4=I4
300 7 pfleura2
           CurrentCoord%Type="DIHEDRAL"
301 7 pfleura2
           IF (.NOT.ASSOCIATED(CurrentCoord%next)) THEN
302 7 pfleura2
              ALLOCATE(CurrentCoord%next)
303 7 pfleura2
              NULLIFY(CurrentCoord%next%next)
304 7 pfleura2
           END IF
305 7 pfleura2
           CurrentCoord => CurrentCoord%next
306 7 pfleura2
        END IF ! matches IF (I4.NE.0)
307 7 pfleura2
     END DO ! matches DO I=1,Nat
308 7 pfleura2
     deallocate(indzmat0)
309 1 pfleura2
310 1 pfleura2
  ELSE !! if (debugPFL)
311 1 pfleura2
312 7 pfleura2
     DO IGeom=1, NGeomI
313 7 pfleura2
        !IGeom=1 ! need when using only first geometry.
314 7 pfleura2
        x(1:Nat) = XyzGeomI(IGeom,1,1:Nat)
315 7 pfleura2
        y(1:Nat) = XyzGeomI(IGeom,2,1:Nat)
316 7 pfleura2
        z(1:Nat) = XyzGeomI(IGeom,3,1:Nat)
317 1 pfleura2
318 7 pfleura2
        ! First step: we calculate the connectivity
319 7 pfleura2
        Liaisons=0
320 1 pfleura2
321 7 pfleura2
        Call CalcCnct(Nat,atome,x,y,z,LIAISONS,r_cov,fact)
322 1 pfleura2
323 7 pfleura2
        IF (debug) THEN
324 7 pfleura2
           WRITE(*,*) 'Connectivity done'
325 7 pfleura2
           DO I=1,Nat
326 7 pfleura2
              WRITE(*,'(1X,I5,":",I3,"=",15I4)') I,(Liaisons(I,J),J=0,NMaxL)
327 7 pfleura2
              WRITE(*,'(1X,I5,":",I3,"=",15I4)') I,(Liaisons(I,:))
328 7 pfleura2
           END DO
329 7 pfleura2
           DO I=1,Nat
330 7 pfleura2
              WRITE(*,'(1X,I5,":",I3," r_cov=",F15.6)') I,atome(I),r_cov(atome(I))
331 7 pfleura2
           END DO
332 7 pfleura2
        END IF
333 7 pfleura2
334 1 pfleura2
        DO I=1,Nat
335 7 pfleura2
           IF (Liaisons(I,0).NE.0) THEN
336 7 pfleura2
              DO J=1,Liaisons(I,0)
337 7 pfleura2
                 ! We add the bond
338 7 pfleura2
                 Iat=Liaisons(I,J)
339 7 pfleura2
                 IF (Iat.GT.I) THEN
340 7 pfleura2
                    ! Checking the uniqueness of bond.
341 1 pfleura2
                    ! Duplicate bonds should not be added.
342 1 pfleura2
                    AddPrimitiveCoord=.True.
343 1 pfleura2
                    ScanCoord=>Coordinate
344 1 pfleura2
                    DO WHILE (Associated(ScanCoord%next))
345 7 pfleura2
                       IF (ScanCoord%Type .EQ. 'BOND') THEN
346 1 pfleura2
                          IF (ScanCoord%At1 .EQ. Iat) THEN
347 1 pfleura2
                             IF (ScanCoord%At2 .EQ. I) THEN
348 7 pfleura2
                                AddPrimitiveCoord=.False.
349 1 pfleura2
                             END IF
350 1 pfleura2
                          END IF
351 1 pfleura2
                       END IF
352 1 pfleura2
                       ScanCoord => ScanCoord%next
353 7 pfleura2
                    END DO
354 1 pfleura2
355 7 pfleura2
                    IF (AddPrimitiveCoord) THEN
356 7 pfleura2
                       NbBonds=NbBonds+1
357 1 pfleura2
                       ! values of the coordinate (bond) is calculated for the reference geometry
358 7 pfleura2
                       ! whereas the coordinates (bonds) (CurrentCoord%At1, CurrentCoord%At2, etc.)
359 7 pfleura2
                       ! are determined using all geometries. vecteur is defined in bib_oper.f
360 7 pfleura2
                       Call vecteur(I,Iat,x_refGeom,y_refGeom,z_refGeom,vx2,vy2,vz2,Norm2)
361 7 pfleura2
                       CurrentCoord%value=Norm2
362 1 pfleura2
                       CurrentCoord%SignDihedral = 0
363 1 pfleura2
                       CurrentCoord%At1=Iat
364 1 pfleura2
                       CurrentCoord%At2=I
365 7 pfleura2
                       CurrentCoord%Type="BOND"
366 1 pfleura2
                       IF (.NOT.ASSOCIATED(CurrentCoord%next)) THEN
367 1 pfleura2
                          ALLOCATE(CurrentCoord%next)
368 1 pfleura2
                          NULLIFY(CurrentCoord%next%next)
369 1 pfleura2
                       END IF
370 1 pfleura2
                       CurrentCoord => CurrentCoord%next
371 1 pfleura2
                    END IF ! matches IF (AddPrimitiveCoord) THEN
372 7 pfleura2
                 END IF ! matches IF (Iat.GT.I) THEN
373 1 pfleura2
374 7 pfleura2
                 !           Call Annul(Liaisons,IAt,I,Nat,NMaxL)
375 7 pfleura2
                 !           Liaisons(Iat,0)=Liaisons(Iat,0)-1
376 7 pfleura2
377 7 pfleura2
                 ! We add the valence angles
378 7 pfleura2
                 DO K=J+1,Liaisons(I,0)
379 7 pfleura2
                    Kat=Liaisons(I,K)
380 7 pfleura2
                    IF (Kat.GT.I) THEN
381 1 pfleura2
                       ! Checking the uniqueness of valence angle.
382 7 pfleura2
                       ! Duplicate bonds should not be added.
383 1 pfleura2
                       AddPrimitiveCoord=.True.
384 1 pfleura2
                       ScanCoord=>Coordinate
385 1 pfleura2
                       DO WHILE (Associated(ScanCoord%next))
386 1 pfleura2
                          IF (ScanCoord%Type .EQ. 'ANGLE') THEN
387 1 pfleura2
                             IF (ScanCoord%At1 .EQ. Iat) THEN
388 1 pfleura2
                                IF (ScanCoord%At2 .EQ. I) THEN
389 1 pfleura2
                                   IF (ScanCoord%At3 .EQ. Kat) THEN
390 1 pfleura2
                                      AddPrimitiveCoord=.False.
391 1 pfleura2
                                   END IF
392 1 pfleura2
                                END IF
393 1 pfleura2
                             END IF
394 1 pfleura2
                          END IF
395 1 pfleura2
                          ScanCoord => ScanCoord%next
396 7 pfleura2
                       END DO ! matches DO WHILE (Associated(ScanCoord%next))
397 1 pfleura2
398 7 pfleura2
                       IF (AddPrimitiveCoord) THEN
399 7 pfleura2
                          IF (debug) WRITE(*,*) "Adding angle:",Iat,I,Kat
400 1 pfleura2
                          NbAngles=NbAngles+1
401 1 pfleura2
                          ! values of the coordinate (bond) is calculated for the reference geometry
402 7 pfleura2
                          ! whereas the coordinates (bonds) (CurrentCoord%At1, CurrentCoord%At2, etc.) are
403 7 pfleura2
                          ! determined using all geometries.
404 1 pfleura2
                          Call vecteur(i,kat,x_refGeom,y_refGeom,z_refGeom,vx1,vy1,vz1,Norm1)
405 1 pfleura2
                          Call vecteur(i,Iat,x_refGeom,y_refGeom,z_refGeom,vx2,vy2,vz2,Norm2)
406 1 pfleura2
                          CurrentCoord%value=angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.
407 7 pfleura2
                          CurrentCoord%SignDihedral = 0
408 7 pfleura2
                          sAngleIatIKat=abs(sin(angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.))
409 1 pfleura2
                          CurrentCoord%At1=Iat
410 1 pfleura2
                          CurrentCoord%At2=I
411 1 pfleura2
                          CurrentCoord%At3=KAt
412 1 pfleura2
                          CurrentCoord%Type="ANGLE"
413 1 pfleura2
                          IF (.NOT.ASSOCIATED(CurrentCoord%next)) THEN
414 1 pfleura2
                             ALLOCATE(CurrentCoord%next)
415 1 pfleura2
                             NULLIFY(CurrentCoord%next%next)
416 1 pfleura2
                          END IF
417 1 pfleura2
                          CurrentCoord => CurrentCoord%next
418 7 pfleura2
                       END IF ! matches IF (AddPrimitiveCoord) THEN
419 7 pfleura2
                    ELSE ! matches IF (Kat.GT.I) THEN
420 7 pfleura2
                       ! Kat is less than I. If there is a bond between I and Kat, then this angle
421 7 pfleura2
                       ! has already been taken into account.
422 7 pfleura2
                       if (debug) WRITE(*,*) "Testing angle:",Iat,I,Kat
423 7 pfleura2
                       Bond=.FALSE.
424 7 pfleura2
                       DO L=1,Liaisons(Iat,0)
425 7 pfleura2
                          IF (Liaisons(Iat,L).EQ.Kat) Bond=.TRUE.
426 7 pfleura2
                       END DO
427 7 pfleura2
                       IF (.NOT.Bond) THEN
428 7 pfleura2
                          IF (debug) WRITE(*,*) "Not Bond Adding angle:",Iat,I,Kat
429 1 pfleura2
430 7 pfleura2
                          ! Checking the uniqueness of valence angle.
431 7 pfleura2
                          ! Duplicate bonds should not be added.
432 7 pfleura2
                          AddPrimitiveCoord=.True.
433 7 pfleura2
                          ScanCoord=>Coordinate
434 7 pfleura2
                          DO WHILE (Associated(ScanCoord%next))
435 7 pfleura2
                             IF (ScanCoord%Type .EQ. 'ANGLE') THEN
436 7 pfleura2
                                IF (ScanCoord%At1 .EQ. Iat) THEN
437 7 pfleura2
                                   IF (ScanCoord%At2 .EQ. I) THEN
438 7 pfleura2
                                      IF (ScanCoord%At3 .EQ. Kat) THEN
439 7 pfleura2
                                         AddPrimitiveCoord=.False.
440 7 pfleura2
                                      END IF
441 7 pfleura2
                                   END IF
442 7 pfleura2
                                END IF
443 7 pfleura2
                             END IF
444 7 pfleura2
                             ScanCoord => ScanCoord%next
445 7 pfleura2
                          END DO
446 7 pfleura2
447 7 pfleura2
                          IF (AddPrimitiveCoord) THEN
448 7 pfleura2
                             NbAngles=NbAngles+1
449 7 pfleura2
                             ! values of the coordinate (bond) is calculated for the reference geometry
450 7 pfleura2
                             ! whereas the coordinates (bonds) (CurrentCoord%At1, CurrentCoord%At2, etc.)
451 7 pfleura2
                             ! are determined using all geometries.
452 7 pfleura2
                             Call vecteur(i,kat,x_refGeom,y_refGeom,z_refGeom,vx1,vy1,vz1,Norm1)
453 7 pfleura2
                             Call vecteur(i,Iat,x_refGeom,y_refGeom,z_refGeom,vx2,vy2,vz2,Norm2)
454 7 pfleura2
                             CurrentCoord%value=angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.
455 7 pfleura2
                             CurrentCoord%SignDihedral = 0
456 7 pfleura2
                             CurrentCoord%At1=Iat
457 7 pfleura2
                             CurrentCoord%At2=I
458 7 pfleura2
                             CurrentCoord%At3=KAt
459 7 pfleura2
                             CurrentCoord%Type="ANGLE"
460 7 pfleura2
                             IF (.NOT.ASSOCIATED(CurrentCoord%next)) THEN
461 7 pfleura2
                                ALLOCATE(CurrentCoord%next)
462 7 pfleura2
                                NULLIFY(CurrentCoord%next%next)
463 7 pfleura2
                             END IF
464 7 pfleura2
                             CurrentCoord => CurrentCoord%next
465 7 pfleura2
                          END IF  ! matches IF (AddPrimitiveCoord) THEN
466 7 pfleura2
                       END IF ! matches IF (.NOT.Bond) THEN
467 7 pfleura2
                    END IF ! matches IF (Kat.GT.I) THEN, after else
468 7 pfleura2
                 END DO ! matches DO K=J+1,Liaisons(I,0)
469 7 pfleura2
              END DO ! matches DO J=1,Liaisons(I,0)
470 7 pfleura2
           END IF ! matches IF (Liaisons(I,0).NE.0) THEN
471 7 pfleura2
472 7 pfleura2
           ! We add dihedral angles. We do not concentrate on necessary angles, ie those that are
473 7 pfleura2
           ! needed to build the molecule. Instead we collect all of them, and the choice of the best
474 7 pfleura2
           ! ones will be done when diagonalizing the Baker matrix.
475 7 pfleura2
           IF (Liaisons(I,0).GE.3) Then
476 7 pfleura2
              DO J=1,Liaisons(I,0)
477 7 pfleura2
                 Iat=Liaisons(I,J)
478 7 pfleura2
                 ! values of the coordinate (bond) is calculated for the reference geometry
479 7 pfleura2
                 ! whereas the coordinates (bonds) (CurrentCoord%At1, CurrentCoord%At2, etc.) are
480 7 pfleura2
                 ! determined using all geometries.
481 7 pfleura2
                 Call vecteur(Iat,i,x_refGeom,y_refGeom,z_refGeom,vx2,vy2,vz2,Norm2)
482 7 pfleura2
483 7 pfleura2
                 DO K=J+1,Liaisons(I,0)
484 7 pfleura2
                    Kat=Liaisons(I,K)
485 7 pfleura2
                    Call vecteur(i,kat,x_refGeom,y_refGeom,z_refGeom,vx1,vy1,vz1,Norm1)
486 7 pfleura2
                    sAngleIatIKat=abs(sin(angle(vx1,vy1,vz1,Norm1,-vx2,-vy2,-vz2,Norm2)*Pi/180.))
487 7 pfleura2
488 7 pfleura2
                    DO L=K+1,Liaisons(I,0)
489 7 pfleura2
                       Lat=Liaisons(I,L)
490 7 pfleura2
                       if (debug) WRITE(*,*) "0-Dihe Kat,I,Iat:",Kat,I,Iat,angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)
491 7 pfleura2
                       Call vecteur(iat,lat,x_refGeom,y_refGeom,z_refGeom,vx3,vy3,vz3,Norm3)
492 7 pfleura2
                       sAngleIIatLat=abs(sin(angle(vx3,vy3,vz3,Norm3,vx2,vy2,vz2,Norm2)*Pi/180.))
493 7 pfleura2
                       if (debug) WRITE(*,*) "0-Dihe I,Iat,Lat:",angle(vx3,vy3,vz3,Norm3,vx2,vy2,vz2,Norm2)
494 7 pfleura2
                       IF ((sAngleIatIKat.ge.0.01d0).AND.(sAngleIIatLat.ge.0.01d0)) THEN
495 7 pfleura2
                          if (debug) WRITE(*,*) "Adding dihedral:",Kat,I,Iat,Lat
496 7 pfleura2
497 7 pfleura2
                          ! Checking for the uniqueness of valence angle.
498 7 pfleura2
                          ! Duplicate bonds should not be added.
499 7 pfleura2
                          AddPrimitiveCoord=.True.
500 7 pfleura2
                          ScanCoord=>Coordinate
501 7 pfleura2
                          DO WHILE (Associated(ScanCoord%next))
502 7 pfleura2
                             IF (ScanCoord%Type .EQ. 'DIHEDRAL') THEN
503 7 pfleura2
                                IF (ScanCoord%At1 .EQ. Kat) THEN
504 7 pfleura2
                                   IF (ScanCoord%At2 .EQ. I) THEN
505 7 pfleura2
                                      IF (ScanCoord%At3 .EQ. Iat) THEN
506 7 pfleura2
                                         IF (ScanCoord%At4 .EQ. Lat) THEN
507 7 pfleura2
                                            AddPrimitiveCoord=.False.
508 7 pfleura2
                                         END IF
509 7 pfleura2
                                      END IF
510 7 pfleura2
                                   END IF
511 7 pfleura2
                                END IF
512 7 pfleura2
                             END IF
513 7 pfleura2
                             ScanCoord => ScanCoord%next
514 7 pfleura2
                          END DO ! matches DO WHILE (Associated(ScanCoord%next))
515 7 pfleura2
516 7 pfleura2
                          ! IF (AddPrimitiveCoord) THEN
517 7 pfleura2
                          !   NbDihedrals=NbDihedrals+1
518 7 pfleura2
                          !  CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, &
519 7 pfleura2
                          !      vx5,vy5,vz5,norm5)
520 7 pfleura2
                          !CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
521 7 pfleura2
                          !    vx4,vy4,vz4,norm4)
522 7 pfleura2
                          !         CurrentCoord%value=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
523 7 pfleura2
                          !             vx2,vy2,vz2,norm2)*Pi/180.
524 7 pfleura2
                          !          CurrentCoord%SignDihedral = 0
525 7 pfleura2
                          !       CurrentCoord%At1=Kat
526 7 pfleura2
                          !      CurrentCoord%At2=I
527 7 pfleura2
                          !     CurrentCoord%At3=IAt
528 7 pfleura2
                          !    CurrentCoord%At4=LAt
529 7 pfleura2
                          !WRITE(*,'(1X,":(dihed 1)",I5," - ",I5," - ",I5," - ",I5," = ",F15.6)') &
530 7 pfleura2
                          !        ScanCoord%At1,ScanCoord%At2,ScanCoord%At3,ScanCoord%At4,ScanCoord%Value*180./Pi
531 7 pfleura2
                          !         CurrentCoord%Type="DIHEDRAL"
532 7 pfleura2
                          !        IF (.NOT.ASSOCIATED(CurrentCoord%next)) THEN
533 7 pfleura2
                          !          ALLOCATE(CurrentCoord%next)
534 7 pfleura2
                          !         NULLIFY(CurrentCoord%next%next)
535 7 pfleura2
                          !     END IF
536 7 pfleura2
                          !    CurrentCoord => CurrentCoord%next
537 7 pfleura2
                          !END IF ! matches IF (AddPrimitiveCoord) THEN
538 7 pfleura2
539 7 pfleura2
                       END IF ! matches IF ((sAngleIatIKat.ge.0.01d0).AND.(sAngleIIatLat.ge.0.01d0)) THEN
540 7 pfleura2
                    END DO ! matches DO L=K+1,Liaisons(I,0)
541 7 pfleura2
                 END DO ! matches DO K=J+1,Liaisons(I,0)
542 7 pfleura2
              END DO ! matches DO J=1,Liaisons(I,0)
543 7 pfleura2
           END IF !matches  IF (Liaisons(I,0).GE.3) Then
544 7 pfleura2
545 7 pfleura2
           ! we now add other dihedrals
546 1 pfleura2
           DO J=1,Liaisons(I,0)
547 1 pfleura2
              Iat=Liaisons(I,J)
548 7 pfleura2
              If (Iat.LE.I) Cycle
549 1 pfleura2
              ! values of the coordinate (bond) is calculated for the reference geometry
550 1 pfleura2
              ! whereas the coordinates (bonds) (CurrentCoord%At1, CurrentCoord%At2, etc.) are
551 1 pfleura2
              ! determined using all geometries.
552 1 pfleura2
              Call vecteur(Iat,i,x_refGeom,y_refGeom,z_refGeom,vx2,vy2,vz2,Norm2)
553 1 pfleura2
554 7 pfleura2
              DO K=1,Liaisons(I,0)
555 7 pfleura2
                 IF (Liaisons(I,K).EQ.Iat) Cycle
556 1 pfleura2
                 Kat=Liaisons(I,K)
557 1 pfleura2
                 Call vecteur(i,kat,x_refGeom,y_refGeom,z_refGeom,vx1,vy1,vz1,Norm1)
558 1 pfleura2
                 sAngleIatIKat=abs(sin(angle(vx1,vy1,vz1,Norm1,-vx2,-vy2,-vz2,Norm2)*Pi/180.))
559 1 pfleura2
560 7 pfleura2
                 DO L=1,Liaisons(Iat,0)
561 7 pfleura2
                    Lat=Liaisons(Iat,L)
562 7 pfleura2
                    IF (Lat.eq.I) Cycle
563 7 pfleura2
564 7 pfleura2
                    if (debug) WRITE(*,*) "Dihe Kat,I,Iat:",angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2),sAngleIatIKat
565 7 pfleura2
                    Call vecteur(iat,lat,x_refGeom,y_refGeom,z_refGeom,vx,vy,vz,Norm)
566 7 pfleura2
567 7 pfleura2
                    sAngleIIatLat=abs(sin(angle(vx,vy,vz,Norm,vx2,vy2,vz2,Norm2)*Pi/180.))
568 7 pfleura2
                    if (debug) WRITE(*,*) "Dihe I,Iat,Lat:",angle(vx,vy,vz,Norm,vx2,vy2,vz2,Norm2)
569 7 pfleura2
                    ! we add the dihedral angle Kat-I-Iat-Lat
570 7 pfleura2
                    if (debug) WRITE(*,*) "Trying dihedral:",Kat,I,Iat,Lat,sAngleIatIKat,sAngleIIatLat
571 7 pfleura2
                    IF ((Lat.NE.Kat).AND.(Lat.Ne.I).AND.(sAngleIatIKat.ge.0.01d0) &
572 7 pfleura2
                         .AND.(sAngleIIatLat.ge.0.01d0)) THEN
573 1 pfleura2
                       if (debug) WRITE(*,*) "Adding dihedral:",Kat,I,Iat,Lat
574 1 pfleura2
575 1 pfleura2
                       ! Checking for the uniqueness of valence angle.
576 1 pfleura2
                       ! Duplicate bonds should not be added.
577 1 pfleura2
                       AddPrimitiveCoord=.True.
578 1 pfleura2
                       ScanCoord=>Coordinate
579 1 pfleura2
                       DO WHILE (Associated(ScanCoord%next))
580 1 pfleura2
                          IF (ScanCoord%Type .EQ. 'DIHEDRAL') THEN
581 1 pfleura2
                             IF (ScanCoord%At1 .EQ. Kat) THEN
582 1 pfleura2
                                IF (ScanCoord%At2 .EQ. I) THEN
583 1 pfleura2
                                   IF (ScanCoord%At3 .EQ. Iat) THEN
584 1 pfleura2
                                      IF (ScanCoord%At4 .EQ. Lat) THEN
585 1 pfleura2
                                         AddPrimitiveCoord=.False.
586 1 pfleura2
                                      END IF
587 1 pfleura2
                                   END IF
588 1 pfleura2
                                END IF
589 1 pfleura2
                             END IF
590 1 pfleura2
                          END IF
591 1 pfleura2
                          ScanCoord => ScanCoord%next
592 7 pfleura2
                       END DO
593 1 pfleura2
594 7 pfleura2
                       IF (AddPrimitiveCoord) THEN
595 7 pfleura2
                          NbDihedrals=NbDihedrals+1
596 7 pfleura2
                          Call vecteur(iat,lat,x_refGeom,y_refGeom,z_refGeom,vx3,vy3,vz3,Norm3)
597 7 pfleura2
                          CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, &
598 7 pfleura2
                               vx5,vy5,vz5,norm5)
599 7 pfleura2
                          CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
600 7 pfleura2
                               vx4,vy4,vz4,norm4)
601 7 pfleura2
                          CurrentCoord%value=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
602 7 pfleura2
                               vx2,vy2,vz2,norm2)*Pi/180.
603 7 pfleura2
                          CurrentCoord%At1=Kat
604 7 pfleura2
                          CurrentCoord%At2=I
605 7 pfleura2
                          CurrentCoord%At3=IAt
606 7 pfleura2
                          CurrentCoord%At4=LAt
607 7 pfleura2
                          CurrentCoord%Type="DIHEDRAL"
608 7 pfleura2
                          CurrentCoord%SignDihedral=int(sign(1.d0,angle_d(vx4,vy4,vz4,norm4,   &
609 7 pfleura2
                               vx5,vy5,vz5,norm5, vx2,vy2,vz2,norm2)))
610 7 pfleura2
                          WRITE(*,'(1X,":(dihed 2)",I5," - ",I5," - ",I5," - ",I5," = ",F15.6)') ScanCoord%At1,&
611 7 pfleura2
                               ScanCoord%At2, ScanCoord%At3,ScanCoord%At4,ScanCoord%Value*180./Pi
612 7 pfleura2
                          IF (.NOT.ASSOCIATED(CurrentCoord%next)) THEN
613 7 pfleura2
                             ALLOCATE(CurrentCoord%next)
614 7 pfleura2
                             NULLIFY(CurrentCoord%next%next)
615 7 pfleura2
                          END IF
616 7 pfleura2
                          CurrentCoord => CurrentCoord%next
617 7 pfleura2
                       END IF ! matches IF (AddPrimitiveCoord) THEN
618 7 pfleura2
                    END IF ! matches IF ((Lat.NE.Kat).AND.(Lat.Ne.I).AND.(sAngleIatIKat.ge.0.01d0) .....
619 7 pfleura2
                 END DO ! matches DO L=1,Liaisons(Iat,0)
620 7 pfleura2
              END DO ! matches DO K=1,Liaisons(I,0)
621 1 pfleura2
           END DO ! matches DO J=1,Liaisons(I,0)
622 7 pfleura2
        END DO ! end of loop over all atoms, DO I=1, Nat
623 7 pfleura2
     END DO ! matches DO IGeom=1, NGeomI
624 1 pfleura2
625 1 pfleura2
626 1 pfleura2
627 7 pfleura2
  END IF ! if (debugPFL)
628 1 pfleura2
  DEALLOCATE(Liaisons)
629 1 pfleura2
630 1 pfleura2
  WRITE(*,*) "I have found"
631 1 pfleura2
  WRITE(*,*) NbBonds, " bonds"
632 1 pfleura2
  WRITE(*,*) NbAngles, " angles"
633 1 pfleura2
  WRITE(*,*) NbDihedrals, " dihedrals"
634 1 pfleura2
635 1 pfleura2
  WRITE(*,*) 'All in all...'
636 1 pfleura2
  ScanCoord=>Coordinate
637 1 pfleura2
  I=0
638 1 pfleura2
  DO WHILE (Associated(ScanCoord%next))
639 1 pfleura2
     I=I+1
640 1 pfleura2
     SELECT CASE (ScanCoord%Type)
641 1 pfleura2
     CASE ('BOND')
642 1 pfleura2
        !WRITE(IOOUT,'(1X,I3,":",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1,ScanCoord%At2,ScanCoord%Value
643 1 pfleura2
        WRITE(*,'(1X,I3,":(bond )",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1,ScanCoord%At2,ScanCoord%Value
644 1 pfleura2
     CASE ('ANGLE')
645 1 pfleura2
        !WRITE(IOOUT,'(1X,I3,":",I5," - ",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1, &
646 1 pfleura2
        !    ScanCoord%At2, ScanCoord%At3,ScanCoord%Value*180./Pi
647 1 pfleura2
        WRITE(*,'(1X,I3,":(angle)",I5," - ",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1, &
648 1 pfleura2
             ScanCoord%At2, ScanCoord%At3,ScanCoord%Value*180./Pi
649 1 pfleura2
     CASE ('DIHEDRAL')
650 1 pfleura2
        !WRITE(IOOUT,'(1X,I3,":",I5," - ",I5," - ",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1,&
651 1 pfleura2
        !    ScanCoord%At2, ScanCoord%At3,ScanCoord%At4,ScanCoord%Value*180./Pi
652 1 pfleura2
        WRITE(*,'(1X,I3,":(dihed)",I5," - ",I5," - ",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1,&
653 1 pfleura2
             ScanCoord%At2, ScanCoord%At3,ScanCoord%At4,ScanCoord%Value*180./Pi
654 1 pfleura2
     END SELECT
655 1 pfleura2
     ScanCoord => ScanCoord%next
656 1 pfleura2
  END DO
657 1 pfleura2
658 1 pfleura2
  ! NPrim is the number of primitive coordinates.
659 1 pfleura2
  NPrim=NbBonds+NbAngles+NbDihedrals
660 1 pfleura2
661 1 pfleura2
  ! Now calculating values of all primitive bonds for all geometries:
662 1 pfleura2
  ALLOCATE(Xprimitive(NgeomI,NPrim),XPrimitiveF(NGeomF,NPrim))
663 1 pfleura2
  ALLOCATE(UMatF(NGeomF,NPrim,NCoord))
664 1 pfleura2
  ALLOCATE(BTransInvF(NGeomF,NCoord,3*Nat))
665 1 pfleura2
666 7 pfleura2
  ! We calculate the Primitive values for the first geometry, this plays a special role
667 7 pfleura2
  ! as it will serve as a reference for other geometries !
668 1 pfleura2
669 1 pfleura2
  x(1:Nat) = XyzGeomI(1,1,1:Nat)
670 1 pfleura2
  y(1:Nat) = XyzGeomI(1,2,1:Nat)
671 1 pfleura2
  z(1:Nat) = XyzGeomI(1,3,1:Nat)
672 1 pfleura2
673 1 pfleura2
  Call Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive(1,:))
674 1 pfleura2
675 1 pfleura2
  DO IGeom=2, NGeomI
676 1 pfleura2
677 7 pfleura2
     x(1:Nat) = XyzGeomI(IGeom,1,1:Nat)
678 7 pfleura2
     y(1:Nat) = XyzGeomI(IGeom,2,1:Nat)
679 7 pfleura2
     z(1:Nat) = XyzGeomI(IGeom,3,1:Nat)
680 1 pfleura2
681 7 pfleura2
     Call Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive(IGeom,:),Xprimitive(1,:))
682 1 pfleura2
683 7 pfleura2
     !      ScanCoord=>Coordinate
684 7 pfleura2
     !      I=0 ! index for the NPrim (NPrim is the number of primitive coordinates).
685 7 pfleura2
     !      DO WHILE (Associated(ScanCoord%next))
686 7 pfleura2
     !         I=I+1
687 7 pfleura2
     !         SELECT CASE (ScanCoord%Type)
688 7 pfleura2
     !         CASE ('BOND')
689 7 pfleura2
     !            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx2,vy2,vz2,Norm2)
690 7 pfleura2
     !            Xprimitive(IGeom,I) = Norm2
691 7 pfleura2
     !         CASE ('ANGLE')
692 7 pfleura2
     !            Call vecteur(ScanCoord%At2,ScanCoord%At3,x,y,z,vx1,vy1,vz1,Norm1)
693 7 pfleura2
     !            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx2,vy2,vz2,Norm2)
694 7 pfleura2
     !            Xprimitive(IGeom,I) = angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.
695 7 pfleura2
     !         CASE ('DIHEDRAL')
696 1 pfleura2
697 1 pfleura2
698 7 pfleura2
     !            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx1,vy1,vz1,Norm1)
699 7 pfleura2
     !            Call vecteur(ScanCoord%At2,ScanCoord%At3,x,y,z,vx2,vy2,vz2,Norm2)
700 7 pfleura2
     !            Call vecteur(ScanCoord%At3,ScanCoord%At4,x,y,z,vx3,vy3,vz3,Norm3)
701 7 pfleura2
     !            Call produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
702 7 pfleura2
     !                 vx4,vy4,vz4,norm4)
703 7 pfleura2
     !            Call produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, &
704 7 pfleura2
     !                 vx5,vy5,vz5,norm5)
705 1 pfleura2
706 7 pfleura2
     !                  DiheTmp= angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
707 7 pfleura2
     !                          vx2,vy2,vz2,norm2)
708 7 pfleura2
     !                  Xprimitive(IGeom,I) = DiheTmp*Pi/180.
709 7 pfleura2
     ! ! We treat large dihedral angles differently as +180=-180 mathematically and physically
710 7 pfleura2
     ! ! but this causes lots of troubles when converting baker to cart.
711 7 pfleura2
     ! ! So we ensure that large dihedral angles always have the same sign
712 7 pfleura2
     !                     if (abs(ScanCoord%SignDihedral).NE.1) THEN
713 7 pfleura2
     !                         ScanCoord%SignDihedral=Int(Sign(1.D0,DiheTmp))
714 7 pfleura2
     !                     ELSE
715 7 pfleura2
     !                         If ((abs(DiheTmp).GE.170.D0).AND.(Sign(1.,DiheTmp)*ScanCoord%SignDihedral<0)) THEN
716 7 pfleura2
     !                           Xprimitive(IGeom,I) = DiheTmp*Pi/180.+ ScanCoord%SignDihedral*2.*Pi
717 7 pfleura2
     !                        END IF
718 7 pfleura2
     !                   END IF
719 7 pfleura2
     ! ! Another test... will all this be consistent ???
720 7 pfleura2
     ! ! We want the shortest path, so we check that the change in dihedral angles is less than Pi:
721 7 pfleura2
     !                   IF (IGeom.GT.1) THEN
722 7 pfleura2
     !                      IF (abs(Xprimitive(IGeom,I)-XPrimitive(IGeom-1,I)).GE.Pi) THEN
723 7 pfleura2
     !                         if ((Xprimitive(IGeom,I)-XPrimitive(IGeom-1,I)).GE.Pi) THEN
724 7 pfleura2
     !                            Xprimitive(IGeom,I)=Xprimitive(IGeom,I)-2.d0*Pi
725 7 pfleura2
     !                         ELSE
726 7 pfleura2
     !                            Xprimitive(IGeom,I)=Xprimitive(IGeom,I)+2.d0*Pi
727 7 pfleura2
     !                         END IF
728 7 pfleura2
     !                      END IF
729 7 pfleura2
     !                   END IF
730 7 pfleura2
     !         END SELECT
731 7 pfleura2
     !         ScanCoord => ScanCoord%next
732 7 pfleura2
     !      END DO ! matches DO WHILE (Associated(ScanCoord%next))
733 1 pfleura2
  END DO ! matches DO IGeom=1, NGeomI
734 1 pfleura2
735 1 pfleura2
  IF (debug) THEN
736 1 pfleura2
     WRITE(*,*) "DBG Calc_Baker Xprimitives for all geometries"
737 7 pfleura2
     DO IGeom=1, NGeomI
738 7 pfleura2
        WRITE(*,*) "Geometry ",IGeom
739 7 pfleura2
        ScanCoord=>Coordinate
740 7 pfleura2
        I=0 ! index for the NPrim (NPrim is the number of primitive coordinates).
741 7 pfleura2
        DO WHILE (Associated(ScanCoord%next))
742 7 pfleura2
           I=I+1
743 7 pfleura2
           SELECT CASE (ScanCoord%Type)
744 7 pfleura2
           CASE ('BOND')
745 7 pfleura2
              WRITE(*,'(1X,I3,":",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1,ScanCoord%At2,Xprimitive(IGeom,I)
746 7 pfleura2
           CASE ('ANGLE')
747 7 pfleura2
              WRITE(*,'(1X,I3,":",I5," - ",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1, &
748 7 pfleura2
                   ScanCoord%At2, ScanCoord%At3,Xprimitive(IGeom,I)*180./Pi
749 7 pfleura2
           CASE ('DIHEDRAL')
750 7 pfleura2
              WRITE(*,'(1X,I3,":",I5," - ",I5," - ",I5," - ",I5," = ",F15.6)') I,ScanCoord%At1,&
751 7 pfleura2
                   ScanCoord%At2, ScanCoord%At3,ScanCoord%At4,Xprimitive(IGeom,I)*180./Pi
752 7 pfleura2
           END SELECT
753 7 pfleura2
           ScanCoord => ScanCoord%next
754 7 pfleura2
        END DO ! matches DO WHILE (Associated(ScanCoord%next))
755 7 pfleura2
     END DO ! matches DO IGeom=1, NGeomI
756 1 pfleura2
  END IF
757 1 pfleura2
  ! Here reference geometry is assigned to Geom. Earlier x,y,z(Nat) were assigned from XyzGeomI(...)
758 1 pfleura2
  ! before the call of this (Calc_baker) subroutine and passed to this subroutine as arguments of the
759 1 pfleura2
  ! subroutine.
760 7 pfleura2
  ! PFL 19 Feb 2008 ->
761 7 pfleura2
  ! In order to reproduce the B matrix in the Baker article, one has
762 7 pfleura2
  ! to divide Geom by a0.
763 7 pfleura2
  ! However, this is inconsitent with our way of storing geometries
764 7 pfleura2
  ! so we do not do it !
765 1 pfleura2
766 1 pfleura2
  Geom(1,:)=XyzGeomI(IGeomRef,1,1:Nat) ! XyzGeomI(NGeomI,3,Nat)
767 1 pfleura2
  Geom(2,:)=XyzGeomI(IGeomRef,2,1:Nat)
768 1 pfleura2
  Geom(3,:)=XyzGeomI(IGeomRef,3,1:Nat)
769 1 pfleura2
770 7 pfleura2
  ! <- PFL 19 Feb 2008
771 1 pfleura2
772 1 pfleura2
  ! We now have to compute dq/dx...
773 1 pfleura2
  ALLOCATE(BprimT(3*Nat,NPrim))
774 1 pfleura2
  BprimT=0.d0
775 1 pfleura2
776 1 pfleura2
  ScanCoord=>Coordinate
777 1 pfleura2
  I=0
778 1 pfleura2
  DO WHILE (Associated(ScanCoord%next))
779 1 pfleura2
     I=I+1
780 1 pfleura2
     SELECT CASE (ScanCoord%Type)
781 1 pfleura2
     CASE ('BOND')
782 1 pfleura2
        CALL CONSTRAINTS_BONDLENGTH_DER(Nat,ScanCoord%at1,ScanCoord%AT2, &
783 1 pfleura2
             Geom,BprimT(1,I))
784 1 pfleura2
     CASE ('ANGLE')
785 1 pfleura2
        CALL CONSTRAINTS_BONDANGLE_DER(Nat,ScanCoord%At1,ScanCoord%AT2, &
786 1 pfleura2
             ScanCoord%At3,Geom,BprimT(1,I))
787 1 pfleura2
     CASE ('DIHEDRAL')
788 1 pfleura2
        CALL CONSTRAINTS_TORSION_DER2(Nat,ScanCoord%At1,ScanCoord%AT2, &
789 1 pfleura2
             ScanCoord%At3,ScanCoord%At4,Geom,BprimT(1,I))
790 7 pfleura2
        !        CALL CONSTRAINTS_TORSION_DER(Nat,ScanCoord%At1,ScanCoord%AT2, &
791 7 pfleura2
        !             ScanCoord%At3,ScanCoord%At4,Geom,BprimT(1,I))
792 1 pfleura2
793 1 pfleura2
     END SELECT
794 1 pfleura2
     ScanCoord => ScanCoord%next
795 1 pfleura2
  END DO
796 1 pfleura2
797 1 pfleura2
798 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
799 7 pfleura2
  !
800 7 pfleura2
  !   PFL Debug
801 7 pfleura2
  !
802 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
803 1 pfleura2
804 7 pfleura2
  if (debugPFL) THEN
805 7 pfleura2
     WRITe(*,*) "DBG PFL Calc_Baker ====="
806 1 pfleura2
     DzDc=0.d0
807 1 pfleura2
     WRITE(*,*) "PFL DBG, DzdC"
808 7 pfleura2
     do I=1,Nat
809 7 pfleura2
        Geom(1,i)=XyzGeomI(IGeomRef,1,orderInv(i)) ! XyzGeomI(NGeomI,3,Nat)
810 7 pfleura2
        Geom(2,i)=XyzGeomI(IGeomRef,2,OrderInv(i))
811 7 pfleura2
        Geom(3,i)=XyzGeomI(IGeomRef,3,OrderInv(i))
812 7 pfleura2
        WRITE(*,*) I,OrderInv(I),Geom(:,I)
813 7 pfleura2
     end do
814 1 pfleura2
     CALL CalcBMat_int (nat, Geom, indzmat, dzdc, massat,atome)
815 1 pfleura2
816 1 pfleura2
     WRITE(*,*) "PFL DBG, BPrimT"
817 1 pfleura2
     DO I=1,NPrim
818 1 pfleura2
        WRITE(*,'(50(1X,F12.6))') BPrimT(:,I)
819 1 pfleura2
     END DO
820 7 pfleura2
     WRITe(*,*) "DBG PFL Calc_Baker ====="
821 7 pfleura2
  END IF
822 1 pfleura2
823 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
824 7 pfleura2
  !
825 7 pfleura2
  !   PFL Debug
826 7 pfleura2
  !
827 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
828 1 pfleura2
829 1 pfleura2
  DEALLOCATE(Geom)
830 1 pfleura2
831 1 pfleura2
  ! BprimT(3*Nat,NPrim)
832 1 pfleura2
  ! We now compute G=B(BT) matrix
833 1 pfleura2
  ALLOCATE(Gmat(NPrim,NPrim))
834 1 pfleura2
  GMat=0.d0
835 1 pfleura2
  DO I=1,NPrim
836 1 pfleura2
     DO J=1,3*Nat
837 1 pfleura2
        GMat(:,I)=Gmat(:,I)+BprimT(J,:)*BprimT(J,I) !*1.d0/mass(atome(int(K/3.d0)))
838 1 pfleura2
     END DO
839 1 pfleura2
  END DO
840 1 pfleura2
841 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
842 7 pfleura2
  !
843 7 pfleura2
  !   PFL Debug --->
844 7 pfleura2
  !
845 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
846 7 pfleura2
  if (debugPFL) THEN
847 7 pfleura2
     GMat=0.d0
848 7 pfleura2
     DO I=1,NPrim
849 1 pfleura2
        GMat(I,I)=1.
850 7 pfleura2
     END DO
851 7 pfleura2
  END IF
852 1 pfleura2
853 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
854 7 pfleura2
  !
855 7 pfleura2
  !  <--- PFL Debug
856 7 pfleura2
  !
857 1 pfleura2
!!!!!!!!!!!!!!!!!!!!
858 1 pfleura2
859 1 pfleura2
  !DO I=1,NPrim
860 1 pfleura2
  !  WRITE(*,'(20(1X,F6.3))') GMat(1:min(20,NPrim),I)
861 1 pfleura2
  !END DO
862 1 pfleura2
863 1 pfleura2
  ! We diagonalize G
864 1 pfleura2
  ALLOCATE(EigVal(NPrim),EigVec(NPrim,NPrim))
865 1 pfleura2
  Call Jacobi(GMat,NPrim,EigVal,EigVec,NPrim)
866 1 pfleura2
  Call Trie(NPrim,EigVal,EigVec,NPrim)
867 1 pfleura2
  DO I=1,NPrim
868 1 pfleura2
     WRITE(*,'(1X,"Vector ",I3,": e=",F8.3)') I,EigVal(i)
869 1 pfleura2
     WRITE(*,'(20(1X,F8.4))') EigVec(1:min(20,NPrim),I)
870 1 pfleura2
  END DO
871 1 pfleura2
872 1 pfleura2
  !DO I=1,NPrim
873 1 pfleura2
  ! WRITE(*,'(1X,"Vector ",I3,(20(F8.3)))') I,EigVec(1:min(20,NPrim),I)
874 1 pfleura2
  ! END DO
875 1 pfleura2
876 1 pfleura2
  !DO I=1,NPrim
877 1 pfleura2
  !  WRITE(*,'(1X,"Vector ",I3,F8.3,F8.3,F8.3,F8.3,F8.3,F8.3,F8.3,F8.3,F8.3,F8.3,F8.3,F8.3,&
878 1 pfleura2
  ! F8.3,F8.3,F8.3,F8.3,F8.3)') I,EigVec(1,I),EigVec(4,I),EigVec(6,I),EigVec(14,I),EigVec(16,I),&
879 1 pfleura2
  !EigVec(2,I),EigVec(3,I),EigVec(5,I),EigVec(12,I),EigVec(13,I),EigVec(15,I),EigVec(7,I),&
880 7 pfleura2
  !EigVec(8,I),EigVec(9,I),EigVec(10,I),EigVec(11,I),EigVec(17,I)
881 1 pfleura2
  !END DO
882 1 pfleura2
883 1 pfleura2
  ! We construct the new DzDc(b=baker) matrix
884 1 pfleura2
  ! UMat is nonredundant vector set, i.e. set of eigenvectors of BB^T corresponding
885 1 pfleura2
  ! to eigenvalues > zero.
886 1 pfleura2
  ALLOCATE(UMat(NPrim,NCoord))
887 1 pfleura2
  ALLOCATE(UMat_local(NPrim,NCoord))
888 1 pfleura2
  ALLOCATE(UMat_tmp(NPrim,3*Nat-6))
889 1 pfleura2
  ! BMat_BakerT(3*Nat,NCoord), allocated in Path.f90,
890 1 pfleura2
  ! NCoord=3*Nat-6
891 1 pfleura2
  BMat_BakerT = 0.d0
892 1 pfleura2
  J=0
893 1 pfleura2
  UMat=0.d0
894 1 pfleura2
  UMat_tmp=0.d0
895 1 pfleura2
  DO I=1,NPrim
896 1 pfleura2
     IF (abs(eigval(I))>=1e-6) THEN
897 1 pfleura2
        J=J+1
898 1 pfleura2
        DO K=1,NPrim
899 1 pfleura2
           !DzDcb(:,J)=DzDcb(:,J)+Eigvec(K,I)*BprimT(:,K) ! original
900 1 pfleura2
           ! BprimT is transpose of B^prim.
901 1 pfleura2
           ! B = UMat^T B^prim, B^T = (B^prim)^T UMat
902 1 pfleura2
           BMat_BakerT(:,J)=BMat_BakerT(:,J)+BprimT(:,K)*Eigvec(K,I)
903 1 pfleura2
           !Dzdcb(:,J)=DzDcb(:,J)+Eigvec(K,:)*BprimT(I,K)
904 1 pfleura2
        END DO
905 1 pfleura2
        IF(J .GT. 3*Nat-6) THEN
906 1 pfleura2
           WRITE(*,*) 'Number of vectors in Eigvec with eigval .GT. 1e-6(=UMat) (=' &
907 1 pfleura2
                ,J,') exceeded 3*Nat-6=',3*Nat-6, &
908 1 pfleura2
                'Stopping the calculation.'
909 1 pfleura2
           STOP
910 1 pfleura2
        END IF
911 1 pfleura2
        UMat_tmp(:,J) =  Eigvec(:,I)
912 1 pfleura2
     END IF
913 1 pfleura2
  END DO
914 1 pfleura2
915 1 pfleura2
  if (debug) THEN
916 1 pfleura2
     WRITE(*,*) "DBG Calc_Baker: UMat"
917 1 pfleura2
     DO I=1,3*Nat-6
918 1 pfleura2
        WRITE(*,'(50(1X,F12.8))') UMat_tmp(:,I)
919 1 pfleura2
     END DO
920 1 pfleura2
  END IF
921 1 pfleura2
922 1 pfleura2
  ! THIS IS TO BE CORRECTED:
923 1 pfleura2
  UMat = UMat_tmp
924 1 pfleura2
  !J=0
925 1 pfleura2
  !DO I=1, 3*Nat-6
926 1 pfleura2
  !  IF ((I .NE. 6) .AND. (I .NE. 7) .AND. (I .NE. 9)) Then
927 1 pfleura2
  !   J=J+1
928 1 pfleura2
  !  Print *, 'J=', J, ' I=', I
929 1 pfleura2
  ! UMat(:,J) = UMat_tmp(:,I)
930 1 pfleura2
  !END IF
931 1 pfleura2
  !END DO
932 1 pfleura2
  ! BMat_BakerT=0.d0
933 1 pfleura2
  !DO I=1,NCoord
934 1 pfleura2
  !  DO J=1,NPrim
935 1 pfleura2
  ! B = UMat^T B^prim, B^T = (B^prim)^T UMat
936 1 pfleura2
  !   BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat(J,I)
937 1 pfleura2
  !    END DO
938 1 pfleura2
  !END DO
939 1 pfleura2
  ! TO BE CORRECTED, ENDS HERE.
940 1 pfleura2
941 1 pfleura2
  IntCoordI=0.d0
942 1 pfleura2
  DO IGeom=1, NGeomI
943 1 pfleura2
     DO I=1, NPrim
944 1 pfleura2
        ! Transpose of UMat is needed below, that is why UMat(I,:).
945 1 pfleura2
        IntCoordI(IGeom,:) = IntCoordI(IGeom,:) + UMat(I,:)*Xprimitive(IGeom,I)
946 1 pfleura2
     END DO
947 1 pfleura2
  END DO
948 1 pfleura2
949 1 pfleura2
  if (debug) THEN
950 1 pfleura2
     WRITE(*,*) "DBG Calc_Baker IntCoordI"
951 1 pfleura2
     DO IGeom=1, NGeomI
952 1 pfleura2
        WRITE(*,'(1X,I5,":",30(1X,F10.6))') IGeom,IntCoordI(IGeom,:)
953 1 pfleura2
     END DO
954 1 pfleura2
  END IF
955 1 pfleura2
956 1 pfleura2
957 1 pfleura2
  ! the following might be used to get rid of some coordinates that
958 1 pfleura2
  ! do not respect the symmetry of the problem.
959 1 pfleura2
960 1 pfleura2
  ! ! We look at the group symmetry of the molecule. Nothing complicate here
961 1 pfleura2
  ! ! we just look for planar symmetry.
962 1 pfleura2
  ! ! We first place it into the standard orientation
963 1 pfleura2
  !   Call Std_ori(Nat,x,y,z,a,b,c,massat)
964 1 pfleura2
965 1 pfleura2
  ! ! Is the molecule planar
966 1 pfleura2
  !   DO I=1,Nat
967 1 pfleura2
  !      WRITE(*,*) nom(atome(i)),x(i),y(i),z(i)
968 1 pfleura2
  !      END DO
969 1 pfleura2
  DEALLOCATE(BprimT,GMat,EigVal,EigVec) ! BprimT is B^prim^T
970 1 pfleura2
  ! Calculation of BTransInv starts here:
971 1 pfleura2
  ! Calculation of BBT(3*Nat-6,3*Nat-6)=BB^T:
972 1 pfleura2
  ! BMat_BakerT(3*Nat,NCoord) is Transpose of B = UMat^TB^prim
973 1 pfleura2
  ALLOCATE(BBT(NCoord,NCoord))
974 1 pfleura2
  BBT = 0.d0
975 1 pfleura2
  DO I=1, NCoord
976 1 pfleura2
     DO J=1, 3*Nat
977 1 pfleura2
        ! BBT(:,I) forms BB^T
978 1 pfleura2
        BBT(:,I) = BBT(:,I) + BMat_BakerT(J,:)*BMat_BakerT(J,I)
979 1 pfleura2
     END DO
980 1 pfleura2
  END DO
981 1 pfleura2
982 1 pfleura2
  !ALLOCATE(V(3*Nat,3*Nat))
983 1 pfleura2
  !Call GINVSE(BBT,3*Nat,3*Nat,BBT_inv,3*Nat,3*Nat,3*Nat,1e-6,V,3*Nat,FAIL,NOUT)
984 1 pfleura2
  !DEALLOCATE(V)
985 1 pfleura2
  ALLOCATE(BBT_inv(NCoord,NCoord))
986 1 pfleura2
  ! GenInv is in Mat_util.f90
987 1 pfleura2
  Call GenInv(NCoord,BBT,BBT_inv,NCoord)
988 1 pfleura2
989 1 pfleura2
  ! Calculation of (B^T)^-1 = (BB^T)^-1B:
990 1 pfleura2
  !ALLOCATE(BTransInv(3*Nat-6,3*Nat))    ! allocated in Path.f90
991 1 pfleura2
  BTransInv = 0.d0
992 1 pfleura2
  DO I=1, 3*Nat
993 1 pfleura2
     DO J=1, NCoord
994 1 pfleura2
        BTransInv(:,I) = BTransInv(:,I) + BBT_inv(:,J)*BMat_BakerT(I,J)
995 1 pfleura2
     END DO
996 1 pfleura2
  END DO
997 1 pfleura2
  BTransInv_local = BTransInv
998 1 pfleura2
  UMat_local = UMat
999 1 pfleura2
  DEALLOCATE(BBT,BBT_inv,UMat_tmp)
1000 1 pfleura2
  DEALLOCATE(x_refGeom,y_refGeom,z_refGeom,x,y,z)
1001 1 pfleura2
  IF (debug) WRITE(*,*) "DBG Calc_baker over."
1002 1 pfleura2
END SUBROUTINE Calc_baker