Statistiques
| Révision :

root / src / ConvertBakerInternal_cart.f90

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

1
SUBROUTINE ConvertBakerInternal_cart(IntCoord_k,IntCoord,x_k,y_k,z_k,x,y,z,XPrim,XPrimRef)
2

    
3
!================================================================
4
! Converts the positions in Baker Coordinates to cartesian coordinates
5
!================================================================
6
!
7
! Input:
8
!    Incoord_k(NCoord) REAL: Starting internal coordinates
9
!    IntCoord(NCoord) REAL: Coordinate to convert to cartesian coordinates
10
!    x_k,y_k,z_k(Nat) REAL: Starting cartesian geometry
11
!    XPrimRef(NPrim) REAL: Reference values for Primitives coordinates (mainly for dihedral)
12
!
13
! Output:
14
!    x,y,z(Nat) REAL: Cartesian coordinates corresponding to IntCoord
15
!    XPrim(NPrim) REAL: Primitives for the cartesian coordinates. (This is a by-product)
16
!
17
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
18

    
19
! BTransInv,UMat should be passed as arguments of this subroutine.
20

    
21

    
22
  ! IdxGeom: geometry index.
23
  ! Internal coordinates IntCoord(NCoord) is to be converted
24
  ! into Cartesian coordinates x(Nat),y(Nat),z(Nat).
25

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

    
57
  use Path_module, only : Nat,AtName,BMat_BakerT,NPrim,&
58
       BBT,BBT_inv,BprimT,ScanCoord,Coordinate,&
59
       BTransInv_local,Xprimitive_t,&
60
       NCoord,UMat_local
61
  ! UMat_local is allocated in Calc_baker.f90
62
  ! XyzGeomI(NGeomI,3,Nat),BMat_BakerT(3*Nat,NCoord),a0=0.529177249d0
63

    
64
  Use Io_Module
65
  use VarTypes
66
  IMPLICIT NONE
67

    
68
  REAL(KREAL), INTENT(OUT) :: x(Nat),y(Nat),z(Nat)
69
  REAL(KREAL), INTENT(IN) :: x_k(Nat),y_k(Nat),z_k(Nat)
70
  REAL(KREAL), INTENT(IN) :: IntCoord(NCoord)
71
  REAL(KREAL), INTENT(INOUT) ::  IntCoord_k(NCoord)
72
  REAL(KREAL), INTENT(IN) :: XPrimRef(NPrim)
73
  REAL(KREAL), INTENT(OUT) :: XPrim(NPrim)
74

    
75

    
76
  ! IdxGeom: geometry index.
77
  Integer(KINT) :: I, J, Counter
78
  REAL(KREAL) :: normDeltaX_int
79

    
80
  REAL(KREAL), ALLOCATABLE :: DeltaX_int(:)  !DeltaX_int(NPrim,3*Nat-6), 3*Nat-6??
81
  REAL(KREAL), ALLOCATABLE :: DeltaX_cart(:) !DeltaX_cart(3*Nat)
82
  REAL(KREAL), ALLOCATABLE :: Geom(:,:) !(3,Nat)
83
  REAL(KREAL), ALLOCATABLE :: X_cart_k(:,:) ! (3,Nat)
84
  REAL(KREAL), ALLOCATABLE :: GMat(:,:) !(NPrim,NPrim)
85
  REAL(KREAL), ALLOCATABLE :: EigVec(:,:), EigVal(:) ! EigVec(NPrim,NPrim)
86
  REAL(KREAL), ALLOCATABLE :: UMat_tmp(:,:)
87

    
88
  REAL(KREAL) :: Angle, angle_d
89
  REAL(KREAL), PARAMETER :: Crit=1e-08
90

    
91
  EXTERNAL Angle, angle_d
92
  LOGICAL :: debug, FAIL
93

    
94
  INTEGER(KINT), PARAMETER :: NbItMax=50
95

    
96

    
97
  INTERFACE
98
     function valid(string) result (isValid)
99
       CHARACTER(*), intent(in) :: string
100
       logical                  :: isValid
101
     END function VALID
102

    
103

    
104

    
105
     SUBROUTINE Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive,XPrimRef)
106
       !     
107
       ! This subroutine uses the description of a list of Coordinates
108
       ! to compute the values of the coordinates for a given geometry.
109
       !
110
!!!!!!!!!!
111
       ! Input:
112
       !   Na: INTEGER, Number of atoms
113
       !  x,y,z(Na): REAL, cartesian coordinates of the considered geometry
114
       ! Coordinate (Pointer(ListCoord)): description of the wanted coordiantes
115
       ! NPrim, INTEGER: Number of coordinates to compute
116
       !
117
       ! Optional: XPrimRef(NPrim) REAL: array that contains coordinates values for
118
       ! a former geometry. Useful for Dihedral angles evolution...
119

    
120
!!!!!!!!!!!
121
       ! Output:
122
       ! XPrimimite(NPrim) REAL: array that will contain the values of the coordinates
123
       !
124
!!!!!!!!!
125

    
126
       Use VarTypes
127
       Use Io_module
128
       Use Path_module, only : pi
129

    
130
       IMPLICIT NONE
131

    
132
       Type (ListCoord), POINTER :: Coordinate
133
       INTEGER(KINT), INTENT(IN) :: Nat,NPrim
134
       REAL(KREAL), INTENT(IN) :: x(Nat), y(Nat), z(Nat)
135
       REAL(KREAL), INTENT(IN), OPTIONAL :: XPrimRef(NPrim) 
136
       REAL(KREAL), INTENT(OUT) :: XPrimitive(NPrim)
137

    
138
     END SUBROUTINE CALC_XPRIM
139
  END INTERFACE
140

    
141

    
142
  debug=valid('ConvertBakerInternal_cart')
143
  if (debug) WRITE(*,*) '=======Entering ConvertBakerInternal_cart======='
144

    
145
  FAIL = .FALSE.     
146

    
147
!!!!!!
148
  ! Allocation phase
149

    
150
  ALLOCATE(DeltaX_int(NCoord),DeltaX_cart(3*Nat))
151
  ALLOCATE(UMat_tmp(NPrim,NCoord))
152
  ALLOCATE(X_cart_k(3,Nat))
153
  ALLOCATE(Geom(3,Nat),BprimT(3*Nat,NPrim))
154
  ALLOCATE(BBT(NCoord,NCoord))
155
  ALLOCATE(BBT_inv(NCoord,NCoord))
156
  ALLOCATE(Gmat(NPrim,NPrim))
157
  ALLOCATE(EigVal(NPrim),EigVec(NPrim,NPrim))
158

    
159

    
160
  if (debug) THEN
161
     WRITE(*,*) "Checking purposes...."
162
     WRITE(*,*) "Trying ot convert Xint initial (IntCoord)"
163
     WRITE(*,'(50(1X,F12.8))') IntCoord(:)
164
     WRITE(*,*) "BTransInv_local"
165
     DO J=1,3*Nat
166
        WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J)
167
     END DO
168
     WRITE(*,*) "Xint initial (IntCoord_k)"
169
     WRITE(*,'(50(1X,F12.8))') IntCoord_k(:)
170
     WRITE(*,*) "Cartesian coordinates"
171
     WRITE(*,*) Nat
172
     WRITE(*,*) 'GeomCart in ConvertBakerInternal_cart'
173
     DO I=1,Nat
174
        WRITE(*,'(1X,A,I4,3(1X,F12.4))') AtName(I),I,X_k(I),Y_k(i),Z_k(i)
175
     END DO
176
     WRITE(*,*) "Calculating actual values using x_k,y_k,z_k"
177

    
178
!     WRITE(*,*) "First, with Calc_XPrim"
179
!     WRITE(*,*) "Coordinate:",associated(Coordinate)
180
     Call Calc_Xprim(nat,x_k,y_k,z_k,Coordinate,NPrim,XPrimitive_t,XPrimRef)
181

    
182
!      I=0 ! index for the NPrim (NPrim is the number of ! primitive coordinates).
183
!      ScanCoord=>Coordinate
184
!      DO WHILE (Associated(ScanCoord%next))
185
!         I=I+1
186
!         SELECT CASE (ScanCoord%Type)
187
!         CASE ('BOND')
188
!            Print *, I, ':',  ScanCoord%At1, '-', ScanCoord%At2, '=', Xprimitive_t(I)
189
!         CASE ('ANGLE')    
190
!            Print *, I, ':', ScanCoord%At1, '-', ScanCoord%At2,'-',ScanCoord%At3, '=', Xprimitive_t(I)*180./Pi
191
!         CASE ('DIHEDRAL')
192
!            Print *, I, ':',  ScanCoord%At1, '-',ScanCoord%At2,'-',ScanCoord%At3,'-',&
193
!            ScanCoord%At4,'=',Xprimitive_t(I)*180./Pi
194
!         END SELECT
195
!         ScanCoord => ScanCoord%next
196
!      END DO ! matches DO WHILE (Associated(ScanCoord%next))
197

    
198
!      WRITE(*,*) "Second with normal proc"
199
!      I=0 ! index for the NPrim (NPrim is the number of ! primitive coordinates).
200
!      Xprimitive_t=0.d0
201
!      ScanCoord=>Coordinate
202
!      DO WHILE (Associated(ScanCoord%next))
203
!         I=I+1
204
!         SELECT CASE (ScanCoord%Type)
205
!         CASE ('BOND')
206
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x_k,y_k,z_k,vx2,vy2,vz2,Norm2)
207
!            Xprimitive_t(I) = Norm2
208
!            Print *, I, ':',  ScanCoord%At1, '-', ScanCoord%At2, '=', Xprimitive_t(I)
209
!         CASE ('ANGLE')    
210
!            Call vecteur(ScanCoord%At2,ScanCoord%At3,x_k,y_k,z_k,vx1,vy1,vz1,Norm1)
211
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x_k,y_k,z_k,vx2,vy2,vz2,Norm2)
212
!            Xprimitive_t(I) = angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.
213
!            Print *, I, ':', ScanCoord%At1, '-', ScanCoord%At2,'-',ScanCoord%At3, '=', Xprimitive_t(I)*180./Pi
214
!         CASE ('DIHEDRAL')
215
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x_k,y_k,z_k,vx1,vy1,vz1,Norm1)
216
!            Call vecteur(ScanCoord%At2,ScanCoord%At3,x_k,y_k,z_k,vx2,vy2,vz2,Norm2)
217
!            Call vecteur(ScanCoord%At3,ScanCoord%At4,x_k,y_k,z_k,vx3,vy3,vz3,Norm3)
218
!            Call produit_vect(vx3,vy3,vz3,vx2,vy2,vz2,vx5,vy5,vz5,norm5)
219
!            Call produit_vect(vx1,vy1,vz1,vx2,vy2,vz2,vx4,vy4,vz4,norm4)
220
! !!! PFL 28 Feb 2008 Test to be sure that angle does not change by more than Pi
221
!            !           Xprimitive_t(I)=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5,vx2,vy2,vz2,norm2)*Pi/180.
222
!            DiheTmp= angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
223
!                 vx2,vy2,vz2,norm2)
224
!            Xprimitive_t(I) = DiheTmp*Pi/180.
225
!            ! We treat large dihedral angles differently as +180=-180 mathematically and physically
226
!            ! but this causes lots of troubles when converting baker to cart.
227
!            ! So we ensure that large dihedral angles always have the same sign
228
!            if (abs(ScanCoord%SignDihedral).NE.1) THEN
229
!               ScanCoord%SignDihedral=Int(Sign(1.,DiheTmp))
230
!            ELSE
231
!               If ((abs(DiheTmp).GE.170.D0).AND.(Sign(1.,DiheTmp)*ScanCoord%SignDihedral<0)) THEN
232
!                  Xprimitive_t(I) = DiheTmp*Pi/180.+ ScanCoord%SignDihedral*2.*Pi
233
!               END IF
234
!            END IF
235

    
236
!            IF (abs(Xprimitive_t(I)-XPrimRef(I)).GE.Pi) THEN
237
!               if ((Xprimitive_t(I)-XPrimRef(I)).GE.Pi) THEN
238
!                  Xprimitive_t(I)=Xprimitive_t(I)-2.d0*Pi
239
!               ELSE
240
!                  Xprimitive_t(I)=Xprimitive_t(I)+2.d0*Pi
241
!               END IF
242
!            END IF
243

    
244
!            Print *, I, ':',  ScanCoord%At1, '-',ScanCoord%At2,'-',ScanCoord%At3,'-',&
245
!            ScanCoord%At4,'=',Xprimitive_t(I)*180./Pi
246
!         END SELECT
247
!         ScanCoord => ScanCoord%next
248
!      END DO ! matches DO WHILE (Associated(ScanCoord%next))
249

    
250
     IntCoord_k=0.d0
251
     DO I=1, NPrim
252
        ! Transpose of UMat is needed below, that is why UMat(I,:).
253
        IntCoord_k(:)=IntCoord_k(:)+UMat_local(I,:)*Xprimitive_t(I)     
254
     END DO
255
     WRITE(*,*) "Xint (intCoord_k) cooresponding to x_k,y_k,z_k"
256
     WRITE(*,'(50(1X,F12.8))') IntCoord_k(:)
257
     WRITE(*,*) "UMat_local"
258
     DO I=1, NPrim
259
        WRITE(*,'(50(1X,F12.8))') UMat_local(I,:)
260
     END DO
261

    
262
     !     Geom(1,:)=X_k(1:Nat)/a0
263
     !     Geom(2,:)=y_k(1:Nat)/a0
264
     !     Geom(3,:)=z_k(1:Nat)/a0
265

    
266
     Geom(1,:)=X_k(1:Nat)
267
     Geom(2,:)=y_k(1:Nat)
268
     Geom(3,:)=z_k(1:Nat)
269

    
270
     ! Computing B^prim:
271
     BprimT=0.d0
272
     ScanCoord=>Coordinate
273
     I=0
274
     DO WHILE (Associated(ScanCoord%next))
275
        I=I+1
276
        SELECT CASE (ScanCoord%Type)
277
        CASE ('BOND') 
278
           CALL CONSTRAINTS_BONDLENGTH_DER(Nat,ScanCoord%at1,ScanCoord%AT2,Geom,BprimT(1,I))
279
        CASE ('ANGLE')
280
           CALL CONSTRAINTS_BONDANGLE_DER(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,Geom,BprimT(1,I))
281
        CASE ('DIHEDRAL')
282
           CALL CONSTRAINTS_TORSION_DER2(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,ScanCoord%At4,Geom,BprimT(1,I))
283
        END SELECT
284
        ScanCoord => ScanCoord%next
285
     END DO
286

    
287
     !     if (debug) THEN
288
     !        WRITE(*,*) "PFL DBG, I,NPrim,BPrimT",I,NPrim
289
     !        DO I=1,NPrim
290
     !           WRITE(*,'(50(1X,F12.6))') BPrimT(:,I)
291
     !        END DO
292
     !     END IF
293

    
294
     BMat_BakerT = 0.d0
295
     DO I=1,NCoord
296
        DO J=1,NPrim
297
           !BprimT is transpose of B^prim.
298
           !B = UMat^T B^prim, B^T = (B^prim)^T UMat
299
           BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat_local(J,I)
300
        END DO
301
     END DO
302

    
303
     BBT = 0.d0
304
     DO I=1,NCoord
305
        DO J=1,3*Nat   ! BBT(:,I) forms BB^T
306
           BBT(:,I) = BBT(:,I) + BMat_BakerT(J,:)*BMat_BakerT(J,I)
307
        END DO
308
     END DO
309

    
310
     BBT_inv = 0.d0
311

    
312
     !Print *, 'NCoord=', NCoord
313
     !Print *, 'BBT='
314
     DO J=1,NCoord
315
        ! WRITE(*,'(50(1X,F12.6))') BBT(:,J)
316
     END DO
317
     !Print *, 'End of BBT'
318
     ! GenInv is in Mat_util.f90
319
     Call GenInv(NCoord,BBT,BBT_inv,NCoord)
320
!     ALLOCATE(V(NCoord,NCoord))
321
!     tol = 1e-12
322
!     ! BBT is destroyed by GINVSE
323
!     Call GINVSE(BBT,NCoord,NCoord,BBT_inv,NCoord,NCoord,NCoord,tol,V,NCoord,FAIL,IOOUT)
324
!     DEALLOCATE(V)
325
!     IF(Fail) Then
326
!        WRITE (*,*) "Failed in generalized inverse, L220, ConvertBaker...f90"
327
!        STOP
328
!     END IF
329

    
330
     !Print *, 'BBT_inv='
331
     DO J=1,NCoord
332
        ! WRITE(*,'(50(1X,F10.2))') BBT_inv(:,J)
333
        ! Print *, BBT_inv(:,J)
334
     END DO
335
     !Print *, 'End of BBT_inv'
336

    
337
     ! Calculation of (B^T)^-1 = (BB^T)^-1B:
338
     BTransInv_local = 0.d0
339
     DO I=1,3*Nat
340
        DO J=1,NCoord
341
           BTransInv_local(:,I)=BTransInv_local(:,I)+BBT_inv(:,J)*BMat_BakerT(I,J)
342
        END DO
343
     END DO
344

    
345
     !Print *, 'BMat_BakerT='
346
     DO J=1,3*Nat
347
        !WRITE(*,'(50(1X,F12.8))') BMat_BakerT(:,J)
348
     END DO
349
     !Print *, 'End of BMat_BakerT'
350

    
351
     WRITE(*,*) "BTransInv_local Trans corresponding to x_k,y_k,z_k"
352
     DO J=1,3*Nat
353
        WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J)
354
     END DO
355

    
356

    
357
  END IF
358

    
359
  DeltaX_int(:) = IntCoord(:)-IntCoord_k(:)
360

    
361
  X_cart_k(1,:) = x_k(:)
362
  X_cart_k(2,:) = y_k(:)
363
  X_cart_k(3,:) = z_k(:)
364

    
365
  normDeltaX_int=0.d0 ! This is to be implemented.
366
  DO I=1, NCoord
367
     normDeltaX_int=normDeltaX_int+DeltaX_int(I)*DeltaX_int(I)
368
  END DO
369
  normDeltaX_int = sqrt(normDeltaX_int)
370
  ! I just need initial value of normDeltaX_int to be .GT. 1d-11,
371
  ! that is why it is initialized to 1.d0
372
  !normDeltaX_int = 1.d0
373

    
374
  if (debug) WRITE(*,*) "Entering the loop"
375
  Counter = 0
376
  DO While ((normDeltaX_int .GT. Crit) .AND. (Counter .LT. NbItMax))
377
     !DO While (normDeltaX_int .GT. 1d-6)
378
     Counter = Counter + 1       
379
     DeltaX_cart = 0.d0
380
!     if (normDeltaX_int.LE.1e-4) THEN
381
!        DeltaX_int=DeltaX_int*1e4
382
!     END IF 
383
     DO I=1,NCoord
384
        ! below BTransInv_local(I,:) is used because actually we need Transpose of BTransInv_local.
385
        DeltaX_cart(:)=DeltaX_cart(:)+BTransInv_local(I,:)*DeltaX_int(I)
386
     END DO
387
!     if (normDeltaX_int.LE.1e-4) THEN
388
!        DeltaX_int=DeltaX_int*1e-4
389
!     DeltaX_cart=DeltaX_cart*1e-4
390
!     END IF
391

    
392

    
393
           if (debug) THEN
394
              WRITE(*,*) "Info for iteration:",counter
395
              Print *, 'DeltaX_int='
396
              WRITE(*,'(50(1X,F12.8))') DeltaX_int
397
              Print *, 'DeltaX_cart,norm',sqrt(dot_product(DeltaX_cart,DeltaX_cart))
398
              DO J=1,Nat
399
              WRITE(*,'(1X,A4,3(1X,F15.11),3(1X,D25.15))') AtName(J),DeltaX_cart(3*J-2:3*J),DeltaX_cart(3*J-2:3*J)
400
              END DO
401
              Print *, 'BTransInv_local Trans='
402
              DO J=1,3*Nat
403
                 WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J)
404
              END DO
405
              Print *, 'DeltaX_int='
406
              WRITE(*,'(50(1X,F12.8))') DeltaX_int
407
           END IF
408

    
409
     ! Finite precision error correction step:
410
!     DO I=1,3*Nat
411
!        IF (DeltaX_cart(I) .NE. 0.d0) Then
412
!           IF(abs(DeltaX_cart(I)) .LT. 1d-10) Then
413
!              !Print *, 'Correcting DeltaX_cart(',I,')=', DeltaX_cart(I)
414
!              DeltaX_cart(I) = 0.d0
415
!           END IF
416
!        END IF
417
!     END DO
418

    
419
     ! new cartesian coordinates:
420
     DO I=1, Nat
421
        X_cart_k(1,I) = X_cart_k(1,I) + DeltaX_cart(3*I-2)
422
        X_cart_k(2,I) = X_cart_k(2,I) + DeltaX_cart(3*I-1)
423
        X_cart_k(3,I) = X_cart_k(3,I) + DeltaX_cart(3*I)
424
     END DO
425

    
426
     !     Geom(1,:)=X_cart_k(1,1:Nat)/a0
427
     !     Geom(2,:)=X_cart_k(2,1:Nat)/a0
428
     !     Geom(3,:)=X_cart_k(3,1:Nat)/a0
429
     Geom(1,:)=X_cart_k(1,1:Nat)
430
     Geom(2,:)=X_cart_k(2,1:Nat)
431
     Geom(3,:)=X_cart_k(3,1:Nat)
432

    
433
     if (debug) THEN
434
     WRITE(*,*) 'GeomCart used to compute BPrim'
435
     DO I=1,Nat
436
        WRITE(*,'(1X,A,I4,3(1X,F12.4))') AtName(I),I,Geom(1,I),Geom(2,i),Geom(3,i)
437
     END DO
438
     END IF
439

    
440
     ! Computing B^prim:
441
     BprimT=0.d0
442
     ScanCoord=>Coordinate
443
     I=0
444
     DO WHILE (Associated(ScanCoord%next))
445
        I=I+1
446
        SELECT CASE (ScanCoord%Type)
447
        CASE ('BOND') 
448
           CALL CONSTRAINTS_BONDLENGTH_DER(Nat,ScanCoord%at1,ScanCoord%AT2,Geom,BprimT(1,I))
449
        CASE ('ANGLE')
450
           CALL CONSTRAINTS_BONDANGLE_DER(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,Geom,BprimT(1,I))
451
        CASE ('DIHEDRAL')
452
           CALL CONSTRAINTS_TORSION_DER2(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,ScanCoord%At4,Geom,BprimT(1,I))
453
        END SELECT
454
        ScanCoord => ScanCoord%next
455
     END DO
456

    
457
     if (debug) THEN
458
        WRITE(*,*) "Bprim "
459
        DO J=1,3*Nat
460
           WRITE(*,'(50(1X,F12.6))') BprimT(J,:)
461
        END DO
462
     END IF
463

    
464

    
465
     BMat_BakerT = 0.d0
466
     DO I=1,NCoord
467
        DO J=1,NPrim
468
           !BprimT is transpose of B^prim.
469
           !B = UMat^T B^prim, B^T = (B^prim)^T UMat
470
           BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat_local(J,I)
471
        END DO
472
     END DO
473

    
474
     ! ADDED FROM HERE:
475
     ! We now compute G=B(BT) matrix
476
     !IF (IOptt .EQ. 5000) Then
477
     !GMat=0.d0
478
     !DO I=1,NPrim
479
     !  DO J=1,3*Nat
480
     !    GMat(:,I)=Gmat(:,I)+BprimT(J,:)*BprimT(J,I) !*1.d0/mass(atome(int(K/3.d0)))
481
     !END DO
482
     !END DO
483

    
484
     ! We diagonalize G
485
     !Call Jacobi(GMat,NPrim,EigVal,EigVec,NPrim)
486
     !Call Trie(NPrim,EigVal,EigVec,NPrim)
487

    
488
     ! We construct the new DzDc(b=baker) matrix
489
     ! UMat is nonredundant vector set, i.e. set of eigenvectors of
490
     !  BB^T corresponding to eigenvalues > zero.
491

    
492
     !UMat=0.d0
493
     !UMat_tmp=0.d0
494
     !BMat_BakerT = 0.d0
495
     !J=0
496
     !DO I=1,NPrim
497
     !  IF (abs(eigval(I))>=1e-6) THEN
498
     !   J=J+1
499
     !  DO K=1,NPrim
500
     ! BprimT is transpose of B^prim.
501
     ! B = UMat^T B^prim, B^T = (B^prim)^T UMat
502
     !BMat_BakerT(:,J)=BMat_BakerT(:,J)+BprimT(:,K)*Eigvec(K,I)
503
     ! END DO
504
     !IF(J .GT. 3*Nat-6) THEN
505
     !WRITE(*,*) 'Number of vectors in Eigvec with eigval .GT. &
506
     !    1e-6 (=UMat) (=' ,J,') exceeded 3*Nat-6=',3*Nat-6, &
507
     !    'Stopping the calculation.'
508
     !   STOP
509
     !  END IF
510
     ! UMat_tmp(:,J) =  Eigvec(:,I)
511
     ! END IF
512
     !END DO
513

    
514
     ! THIS IS TO BE CORRECTED, A special case for debugging C2H3F case:
515
     !J=0
516
     !DO I=1, 3*Nat-6
517
     ! IF ((I .NE. 6) .AND. (I .NE. 7) .AND. (I .NE. 9)) Then
518
     !  J=J+1
519
     ! Print *, 'J=', J, ' I=', I
520
     !UMat(:,J) = UMat_tmp(:,I)
521
     !     END IF
522
     ! END DO
523
     !BMat_BakerT=0.d0
524
     !    DO I=1,NCoord
525
     !      DO J=1,NPrim
526
     ! B = UMat^T B^prim, B^T = (B^prim)^T UMat
527
     !       BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat(J,I)
528
     !    END DO
529
     !END DO
530
     ! TO BE CORRECTED, ENDS HERE.
531

    
532
     !END IF
533
     ! END of the new changes.
534

    
535
     BBT = 0.d0
536
     DO I=1,NCoord
537
        DO J=1,3*Nat   ! BBT(:,I) forms BB^T
538
           BBT(:,I) = BBT(:,I) + BMat_BakerT(J,:)*BMat_BakerT(J,I)
539
        END DO
540
     END DO
541

    
542
     BBT_inv = 0.d0
543

    
544
     !Print *, 'NCoord=', NCoord
545
     !Print *, 'BBT='
546
     DO J=1,NCoord
547
        ! WRITE(*,'(50(1X,F12.6))') BBT(:,J)
548
     END DO
549
     !Print *, 'End of BBT'
550
     ! GenInv is in Mat_util.f90
551
     Call GenInv(NCoord,BBT,BBT_inv,NCoord)
552
     !     if (debug) THEN
553
     !        WRITE(*,*) 'BBT_inv by GenInv'
554
     !        DO J=1,NCoord
555
     !           WRITE(*,'(50(1X,F12.6))') BBT_inv(:,J)
556
     !        END DO
557
     !     END IF
558

    
559
!    ALLOCATE(V(NCoord,NCoord))
560
!    tol = 1e-12
561
!    ! BBT is destroyed by GINVSE
562
!    Call GINVSE(BBT,NCoord,NCoord,BBT_inv,NCoord,NCoord,NCoord,tol,V,NCoord,FAIL,IOOUT)
563
!    DEALLOCATE(V)
564
!    IF(Fail) Then
565
!       WRITE (*,*) "Failed in generalized inverse, L220, ConvertBaker...f90"
566
!       STOP
567
!    END IF
568

    
569
     !     if (debug) THEN
570
     !        WRITE(*,*) 'BBT_inv by Genvse'
571
     !        DO J=1,NCoord
572
     !           WRITE(*,'(50(1X,F12.6))') BBT_inv(:,J)
573
     !        END DO
574
     !     END IF
575

    
576
     !Print *, 'End of BBT_inv'
577

    
578
     ! Calculation of (B^T)^-1 = (BB^T)^-1B:
579
     BTransInv_local = 0.d0
580
     DO I=1,3*Nat
581
        DO J=1,NCoord
582
           BTransInv_local(:,I)=BTransInv_local(:,I)+BBT_inv(:,J)*BMat_BakerT(I,J)
583
        END DO
584
     END DO
585

    
586
     !     if (debug) THEN
587
     !        Print *, 'BMat_BakerT='
588
     !        DO J=1,3*Nat
589
     !           WRITE(*,'(50(1X,F12.6))') BMat_BakerT(:,J)
590
     !        END DO
591
     !        Print *, 'End of BMat_BakerT'
592
     !     END IF
593

    
594
     !      if (debug) THEN
595
     !         Print *, 'BTransInv_local Trans='
596
     !         DO J=1,3*Nat
597
     !            WRITE(*,'(50(1X,F16.6))') BTransInv_local(:,J)
598
     !         END DO
599
     !         Print *, 'End of BTransInv_local Trans'
600
     !      END IF
601

    
602
     ! New cartesian cooordinates:
603
     x(:) = X_cart_k(1,:)
604
     y(:) = X_cart_k(2,:)
605
     z(:) = X_cart_k(3,:)
606

    
607

    
608
     Call Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive_t,XPrimRef)
609

    
610
!      I=0 ! index for the NPrim (NPrim is the number of 
611
!      ! primitive coordinates).
612
!      Xprimitive_t=0.d0
613
!      ScanCoord=>Coordinate
614
!      DO WHILE (Associated(ScanCoord%next))
615
!         I=I+1
616
!         SELECT CASE (ScanCoord%Type)
617
!         CASE ('BOND')
618
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx2,vy2,vz2,Norm2)
619
!            Xprimitive_t(I) = Norm2
620
!            !Print *, I, ':',  ScanCoord%At1, '-', ScanCoord%At2, '=', Xprimitive_t(I)
621
!         CASE ('ANGLE')    
622
!            Call vecteur(ScanCoord%At2,ScanCoord%At3,x,y,z,vx1,vy1,vz1,Norm1)
623
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx2,vy2,vz2,Norm2)
624
!            Xprimitive_t(I) = angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.
625
!            !Print *, I, ':', ScanCoord%At1, '-', ScanCoord%At2,'-',ScanCoord%At3, '=', Xprimitive_t(I)*180./Pi
626
!         CASE ('DIHEDRAL')
627
!            Call vecteur(ScanCoord%At2,ScanCoord%At3,x,y,z,vx2,vy2,vz2,Norm2)
628
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx1,vy1,vz1,Norm1)
629
!            Call vecteur(ScanCoord%At3,ScanCoord%At4,x,y,z,vx3,vy3,vz3,Norm3)
630
!            Call produit_vect(vx3,vy3,vz3,vx2,vy2,vz2,vx5,vy5,vz5,norm5)
631
!            Call produit_vect(vx1,vy1,vz1,vx2,vy2,vz2,vx4,vy4,vz4,norm4)
632
! !!! PFL 28 Feb 2008 Test to be sure that angle does not change by more than Pi
633
!            !           Xprimitive_t(I)=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5,vx2,vy2,vz2,norm2)*Pi/180.
634
!            DiheTmp=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5,vx2,vy2,vz2,norm2)
635
!            Xprimitive_t(I) = DiheTmp*Pi/180.
636
!            ! We treat large dihedral angles differently as +180=-180 mathematically and physically
637
!            ! but this causes lots of troubles when converting baker to cart.
638
!            ! So we ensure that large dihedral angles always have the same sign
639
!            if (abs(ScanCoord%SignDihedral).NE.1) THEN
640
!               ScanCoord%SignDihedral=Int(Sign(1.d0,DiheTmp))
641
!            ELSE
642
!               If ((abs(DiheTmp).GE.170.D0).AND.(Sign(1.,DiheTmp)*ScanCoord%SignDihedral<0)) THEN
643
!                  Xprimitive_t(I) = DiheTmp*Pi/180.+ ScanCoord%SignDihedral*2.*Pi
644
!               END IF
645
!            END IF
646

    
647

    
648

    
649
!            !Print *, I, ':',  ScanCoord%At1, '-',ScanCoord%At2,'-',ScanCoord%At3,'-',&
650
!            !ScanCoord%At4,'=',Xprimitive_t(I)*180./Pi
651
!         END SELECT
652
!         ScanCoord => ScanCoord%next
653
!      END DO ! matches DO WHILE (Associated(ScanCoord%next))
654

    
655
     !     if (debug) THEN
656
     !        WRITE(*,*) "Xprimitive_t"
657
     !        WRITE(*,'(50(1X,F12.6))') Xprimitive_t
658
     !     END IF
659

    
660
     IntCoord_k=0.d0
661
     DO I=1, NPrim
662
        ! Transpose of UMat is needed below, that is why UMat(I,:).
663
        IntCoord_k(:)=IntCoord_k(:)+UMat_local(I,:)*Xprimitive_t(I)     
664
     END DO
665

    
666
     if (debug) THEN
667
        WRITE(*,*) "New Xint (IntCoord_k)"
668
        WRITE(*,'(50(1X,F12.8))') IntCoord_k
669
        WRITE(*,*) "Target (IntCoord)"
670
        WRITE(*,'(50(1X,F12.8))') IntCoord
671

    
672
     END IF
673

    
674

    
675
     ! Computing DeltaX_int
676

    
677
     DeltaX_int(:) = IntCoord(:)-IntCoord_k(:)
678

    
679

    
680

    
681

    
682
     ! norm2 of DeltaX_int is being calculated here:
683
     normDeltaX_int=0.d0
684
     DO I=1, NCoord
685
        normDeltaX_int=normDeltaX_int+DeltaX_int(I)*DeltaX_int(I)
686
     END DO
687
     normDeltaX_int = sqrt(normDeltaX_int)
688

    
689
          if (debug) THEN
690
             WRITE(*,*) "New Delta_Xint (deltaX_int)"
691
             WRITE(*,'(50(1X,F12.6))') DeltaX_int
692
             WRITE(*,*) "Norm:",normDeltaX_int
693
          END IF
694

    
695
     !IF (Counter .GE. 400) THEN
696
     !Print *, 'Counter=', Counter, 'normDeltaX_int=', normDeltaX_int
697
     !Print *, 'DeltaX_int='
698
     !WRITE(*,'(50(1X,F8.2))') DeltaX_int
699
     !END IF
700

    
701
     IF (Mod(Counter,1).EQ.0) THEN
702
        !WRITE(*,*) Nat
703
        !WRITE(*,*) 'GeomCart in ConvertBakerInternal_cart'
704
        DO I=1,Nat
705
           !  WRITE(*,'(1X,A,I4,3(1X,F12.4))') AtName(I),I,X_Cart_k(1:3,I)
706
        END DO
707
     END IF
708

    
709
     !call two_norm(DeltaX_int,normDeltaX_int,3*Nat)
710
  END DO !matches DO While (normDeltaX_int .GT. 1d-11)
711

    
712
  IF (debug) THEN
713
  WRITE(*,*) 'GeomCart in ConvertBakerInternal_cart'
714
  DO I=1,Nat
715
     WRITE(*,'(1X,A,I4,3(1X,F12.4))') AtName(I),I,X_Cart_k(1:3,I)
716
  END DO
717
  END IF
718

    
719
  if (debug) THEN
720
     WRITE(*,*) "Bmat_bakerT"
721
     DO J=1,NCoord
722
        WRITE(*,'(50(1X,F12.6))') BMat_BakerT(:,J)
723
     END DO
724
  END IF
725

    
726

    
727

    
728
  !IF (IOptt .GE. 2) THEN
729
  !   Print  *, 'Counter=', Counter
730
  !END IF
731
  IF (Counter .GE. NbItMax) Then
732
     Print *, 'Counter GE 500, Stopping, normDeltaX_int=', normDeltaX_int
733
     STOP
734
  END IF
735

    
736

    
737
     x(:) = X_cart_k(1,:)
738
     y(:) = X_cart_k(2,:)
739
     z(:) = X_cart_k(3,:)
740

    
741

    
742
!  call CalcRmsd(Nat,x_k,y_k,z_k,x,y,z,MRot,rmsd,.TRUE.,.TRUE.)
743

    
744

    
745
  if (debug) WRITE(*,*) "COnverted in ",counter," iterations"
746

    
747
  DEALLOCATE(Geom,DeltaX_int,DeltaX_cart)
748
  DEALLOCATE(BprimT,BBT,BBT_inv,UMat_tmp)
749
  DEALLOCATE(X_cart_k)
750
  DEALLOCATE(GMat,EigVal,EigVec)
751

    
752
  XPrim=Xprimitive_t
753

    
754
  if (debug) WRITE(*,*) '=====ConvertBakerInternal_cart Over====='
755

    
756
END SUBROUTINE ConvertBakerInternal_cart