Statistiques
| Révision :

root / src / ConvertBakerInternal_cart.f90

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

1 1 pfleura2
SUBROUTINE ConvertBakerInternal_cart(IntCoord_k,IntCoord,x_k,y_k,z_k,x,y,z,XPrim,XPrimRef)
2 1 pfleura2
3 1 pfleura2
!================================================================
4 1 pfleura2
! Converts the positions in Baker Coordinates to cartesian coordinates
5 1 pfleura2
!================================================================
6 1 pfleura2
!
7 1 pfleura2
! Input:
8 1 pfleura2
!    Incoord_k(NCoord) REAL: Starting internal coordinates
9 1 pfleura2
!    IntCoord(NCoord) REAL: Coordinate to convert to cartesian coordinates
10 1 pfleura2
!    x_k,y_k,z_k(Nat) REAL: Starting cartesian geometry
11 1 pfleura2
!    XPrimRef(NPrim) REAL: Reference values for Primitives coordinates (mainly for dihedral)
12 1 pfleura2
!
13 1 pfleura2
! Output:
14 1 pfleura2
!    x,y,z(Nat) REAL: Cartesian coordinates corresponding to IntCoord
15 1 pfleura2
!    XPrim(NPrim) REAL: Primitives for the cartesian coordinates. (This is a by-product)
16 1 pfleura2
!
17 1 pfleura2
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
18 1 pfleura2
19 1 pfleura2
! BTransInv,UMat should be passed as arguments of this subroutine.
20 1 pfleura2
21 1 pfleura2
22 1 pfleura2
  ! IdxGeom: geometry index.
23 1 pfleura2
  ! Internal coordinates IntCoord(NCoord) is to be converted
24 1 pfleura2
  ! into Cartesian coordinates x(Nat),y(Nat),z(Nat).
25 1 pfleura2
26 12 pfleura2
!----------------------------------------------------------------------
27 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
28 12 pfleura2
!  Centre National de la Recherche Scientifique,
29 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
30 12 pfleura2
!
31 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
32 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
33 12 pfleura2
!
34 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
35 12 pfleura2
!  Contact: optnpath@gmail.com
36 12 pfleura2
!
37 12 pfleura2
! This file is part of "Opt'n Path".
38 12 pfleura2
!
39 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
40 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
41 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
42 12 pfleura2
!  or (at your option) any later version.
43 12 pfleura2
!
44 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
45 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
46 12 pfleura2
!
47 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
48 12 pfleura2
!  GNU Affero General Public License for more details.
49 12 pfleura2
!
50 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
51 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
52 12 pfleura2
!
53 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
54 12 pfleura2
! for commercial licensing opportunities.
55 12 pfleura2
!----------------------------------------------------------------------
56 12 pfleura2
57 8 pfleura2
  use Path_module, only : Nat,AtName,BMat_BakerT,NPrim,&
58 8 pfleura2
       BBT,BBT_inv,BprimT,ScanCoord,Coordinate,&
59 8 pfleura2
       BTransInv_local,Xprimitive_t,&
60 8 pfleura2
       NCoord,UMat_local
61 1 pfleura2
  ! UMat_local is allocated in Calc_baker.f90
62 1 pfleura2
  ! XyzGeomI(NGeomI,3,Nat),BMat_BakerT(3*Nat,NCoord),a0=0.529177249d0
63 1 pfleura2
64 1 pfleura2
  Use Io_Module
65 1 pfleura2
  use VarTypes
66 1 pfleura2
  IMPLICIT NONE
67 1 pfleura2
68 1 pfleura2
  REAL(KREAL), INTENT(OUT) :: x(Nat),y(Nat),z(Nat)
69 1 pfleura2
  REAL(KREAL), INTENT(IN) :: x_k(Nat),y_k(Nat),z_k(Nat)
70 1 pfleura2
  REAL(KREAL), INTENT(IN) :: IntCoord(NCoord)
71 1 pfleura2
  REAL(KREAL), INTENT(INOUT) ::  IntCoord_k(NCoord)
72 1 pfleura2
  REAL(KREAL), INTENT(IN) :: XPrimRef(NPrim)
73 1 pfleura2
  REAL(KREAL), INTENT(OUT) :: XPrim(NPrim)
74 1 pfleura2
75 1 pfleura2
76 1 pfleura2
  ! IdxGeom: geometry index.
77 2 pfleura2
  Integer(KINT) :: I, J, Counter
78 1 pfleura2
  REAL(KREAL) :: normDeltaX_int
79 1 pfleura2
80 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: DeltaX_int(:)  !DeltaX_int(NPrim,3*Nat-6), 3*Nat-6??
81 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: DeltaX_cart(:) !DeltaX_cart(3*Nat)
82 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: Geom(:,:) !(3,Nat)
83 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: X_cart_k(:,:) ! (3,Nat)
84 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: GMat(:,:) !(NPrim,NPrim)
85 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: EigVec(:,:), EigVal(:) ! EigVec(NPrim,NPrim)
86 1 pfleura2
  REAL(KREAL), ALLOCATABLE :: UMat_tmp(:,:)
87 1 pfleura2
88 2 pfleura2
  REAL(KREAL) :: Angle, angle_d
89 1 pfleura2
  REAL(KREAL), PARAMETER :: Crit=1e-08
90 1 pfleura2
91 1 pfleura2
  EXTERNAL Angle, angle_d
92 1 pfleura2
  LOGICAL :: debug, FAIL
93 1 pfleura2
94 1 pfleura2
  INTEGER(KINT), PARAMETER :: NbItMax=50
95 1 pfleura2
96 1 pfleura2
97 1 pfleura2
  INTERFACE
98 1 pfleura2
     function valid(string) result (isValid)
99 1 pfleura2
       CHARACTER(*), intent(in) :: string
100 1 pfleura2
       logical                  :: isValid
101 1 pfleura2
     END function VALID
102 1 pfleura2
103 1 pfleura2
104 1 pfleura2
105 1 pfleura2
     SUBROUTINE Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive,XPrimRef)
106 1 pfleura2
       !
107 1 pfleura2
       ! This subroutine uses the description of a list of Coordinates
108 1 pfleura2
       ! to compute the values of the coordinates for a given geometry.
109 1 pfleura2
       !
110 1 pfleura2
!!!!!!!!!!
111 1 pfleura2
       ! Input:
112 1 pfleura2
       !   Na: INTEGER, Number of atoms
113 1 pfleura2
       !  x,y,z(Na): REAL, cartesian coordinates of the considered geometry
114 1 pfleura2
       ! Coordinate (Pointer(ListCoord)): description of the wanted coordiantes
115 1 pfleura2
       ! NPrim, INTEGER: Number of coordinates to compute
116 1 pfleura2
       !
117 1 pfleura2
       ! Optional: XPrimRef(NPrim) REAL: array that contains coordinates values for
118 1 pfleura2
       ! a former geometry. Useful for Dihedral angles evolution...
119 1 pfleura2
120 1 pfleura2
!!!!!!!!!!!
121 1 pfleura2
       ! Output:
122 1 pfleura2
       ! XPrimimite(NPrim) REAL: array that will contain the values of the coordinates
123 1 pfleura2
       !
124 1 pfleura2
!!!!!!!!!
125 1 pfleura2
126 1 pfleura2
       Use VarTypes
127 1 pfleura2
       Use Io_module
128 1 pfleura2
       Use Path_module, only : pi
129 1 pfleura2
130 1 pfleura2
       IMPLICIT NONE
131 1 pfleura2
132 1 pfleura2
       Type (ListCoord), POINTER :: Coordinate
133 1 pfleura2
       INTEGER(KINT), INTENT(IN) :: Nat,NPrim
134 1 pfleura2
       REAL(KREAL), INTENT(IN) :: x(Nat), y(Nat), z(Nat)
135 1 pfleura2
       REAL(KREAL), INTENT(IN), OPTIONAL :: XPrimRef(NPrim)
136 1 pfleura2
       REAL(KREAL), INTENT(OUT) :: XPrimitive(NPrim)
137 1 pfleura2
138 1 pfleura2
     END SUBROUTINE CALC_XPRIM
139 1 pfleura2
  END INTERFACE
140 1 pfleura2
141 1 pfleura2
142 1 pfleura2
  debug=valid('ConvertBakerInternal_cart')
143 1 pfleura2
  if (debug) WRITE(*,*) '=======Entering ConvertBakerInternal_cart======='
144 1 pfleura2
145 1 pfleura2
  FAIL = .FALSE.
146 1 pfleura2
147 1 pfleura2
!!!!!!
148 1 pfleura2
  ! Allocation phase
149 1 pfleura2
150 1 pfleura2
  ALLOCATE(DeltaX_int(NCoord),DeltaX_cart(3*Nat))
151 1 pfleura2
  ALLOCATE(UMat_tmp(NPrim,NCoord))
152 1 pfleura2
  ALLOCATE(X_cart_k(3,Nat))
153 1 pfleura2
  ALLOCATE(Geom(3,Nat),BprimT(3*Nat,NPrim))
154 1 pfleura2
  ALLOCATE(BBT(NCoord,NCoord))
155 1 pfleura2
  ALLOCATE(BBT_inv(NCoord,NCoord))
156 1 pfleura2
  ALLOCATE(Gmat(NPrim,NPrim))
157 1 pfleura2
  ALLOCATE(EigVal(NPrim),EigVec(NPrim,NPrim))
158 1 pfleura2
159 1 pfleura2
160 1 pfleura2
  if (debug) THEN
161 1 pfleura2
     WRITE(*,*) "Checking purposes...."
162 1 pfleura2
     WRITE(*,*) "Trying ot convert Xint initial (IntCoord)"
163 1 pfleura2
     WRITE(*,'(50(1X,F12.8))') IntCoord(:)
164 1 pfleura2
     WRITE(*,*) "BTransInv_local"
165 1 pfleura2
     DO J=1,3*Nat
166 1 pfleura2
        WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J)
167 1 pfleura2
     END DO
168 1 pfleura2
     WRITE(*,*) "Xint initial (IntCoord_k)"
169 1 pfleura2
     WRITE(*,'(50(1X,F12.8))') IntCoord_k(:)
170 1 pfleura2
     WRITE(*,*) "Cartesian coordinates"
171 1 pfleura2
     WRITE(*,*) Nat
172 1 pfleura2
     WRITE(*,*) 'GeomCart in ConvertBakerInternal_cart'
173 1 pfleura2
     DO I=1,Nat
174 1 pfleura2
        WRITE(*,'(1X,A,I4,3(1X,F12.4))') AtName(I),I,X_k(I),Y_k(i),Z_k(i)
175 1 pfleura2
     END DO
176 1 pfleura2
     WRITE(*,*) "Calculating actual values using x_k,y_k,z_k"
177 1 pfleura2
178 1 pfleura2
!     WRITE(*,*) "First, with Calc_XPrim"
179 1 pfleura2
!     WRITE(*,*) "Coordinate:",associated(Coordinate)
180 1 pfleura2
     Call Calc_Xprim(nat,x_k,y_k,z_k,Coordinate,NPrim,XPrimitive_t,XPrimRef)
181 1 pfleura2
182 1 pfleura2
!      I=0 ! index for the NPrim (NPrim is the number of ! primitive coordinates).
183 1 pfleura2
!      ScanCoord=>Coordinate
184 1 pfleura2
!      DO WHILE (Associated(ScanCoord%next))
185 1 pfleura2
!         I=I+1
186 1 pfleura2
!         SELECT CASE (ScanCoord%Type)
187 1 pfleura2
!         CASE ('BOND')
188 1 pfleura2
!            Print *, I, ':',  ScanCoord%At1, '-', ScanCoord%At2, '=', Xprimitive_t(I)
189 1 pfleura2
!         CASE ('ANGLE')
190 1 pfleura2
!            Print *, I, ':', ScanCoord%At1, '-', ScanCoord%At2,'-',ScanCoord%At3, '=', Xprimitive_t(I)*180./Pi
191 1 pfleura2
!         CASE ('DIHEDRAL')
192 1 pfleura2
!            Print *, I, ':',  ScanCoord%At1, '-',ScanCoord%At2,'-',ScanCoord%At3,'-',&
193 1 pfleura2
!            ScanCoord%At4,'=',Xprimitive_t(I)*180./Pi
194 1 pfleura2
!         END SELECT
195 1 pfleura2
!         ScanCoord => ScanCoord%next
196 1 pfleura2
!      END DO ! matches DO WHILE (Associated(ScanCoord%next))
197 1 pfleura2
198 1 pfleura2
!      WRITE(*,*) "Second with normal proc"
199 1 pfleura2
!      I=0 ! index for the NPrim (NPrim is the number of ! primitive coordinates).
200 1 pfleura2
!      Xprimitive_t=0.d0
201 1 pfleura2
!      ScanCoord=>Coordinate
202 1 pfleura2
!      DO WHILE (Associated(ScanCoord%next))
203 1 pfleura2
!         I=I+1
204 1 pfleura2
!         SELECT CASE (ScanCoord%Type)
205 1 pfleura2
!         CASE ('BOND')
206 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x_k,y_k,z_k,vx2,vy2,vz2,Norm2)
207 1 pfleura2
!            Xprimitive_t(I) = Norm2
208 1 pfleura2
!            Print *, I, ':',  ScanCoord%At1, '-', ScanCoord%At2, '=', Xprimitive_t(I)
209 1 pfleura2
!         CASE ('ANGLE')
210 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At3,x_k,y_k,z_k,vx1,vy1,vz1,Norm1)
211 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x_k,y_k,z_k,vx2,vy2,vz2,Norm2)
212 1 pfleura2
!            Xprimitive_t(I) = angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.
213 1 pfleura2
!            Print *, I, ':', ScanCoord%At1, '-', ScanCoord%At2,'-',ScanCoord%At3, '=', Xprimitive_t(I)*180./Pi
214 1 pfleura2
!         CASE ('DIHEDRAL')
215 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x_k,y_k,z_k,vx1,vy1,vz1,Norm1)
216 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At3,x_k,y_k,z_k,vx2,vy2,vz2,Norm2)
217 1 pfleura2
!            Call vecteur(ScanCoord%At3,ScanCoord%At4,x_k,y_k,z_k,vx3,vy3,vz3,Norm3)
218 2 pfleura2
!            Call produit_vect(vx3,vy3,vz3,vx2,vy2,vz2,vx5,vy5,vz5,norm5)
219 2 pfleura2
!            Call produit_vect(vx1,vy1,vz1,vx2,vy2,vz2,vx4,vy4,vz4,norm4)
220 1 pfleura2
! !!! PFL 28 Feb 2008 Test to be sure that angle does not change by more than Pi
221 1 pfleura2
!            !           Xprimitive_t(I)=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5,vx2,vy2,vz2,norm2)*Pi/180.
222 1 pfleura2
!            DiheTmp= angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
223 1 pfleura2
!                 vx2,vy2,vz2,norm2)
224 1 pfleura2
!            Xprimitive_t(I) = DiheTmp*Pi/180.
225 1 pfleura2
!            ! We treat large dihedral angles differently as +180=-180 mathematically and physically
226 1 pfleura2
!            ! but this causes lots of troubles when converting baker to cart.
227 1 pfleura2
!            ! So we ensure that large dihedral angles always have the same sign
228 1 pfleura2
!            if (abs(ScanCoord%SignDihedral).NE.1) THEN
229 1 pfleura2
!               ScanCoord%SignDihedral=Int(Sign(1.,DiheTmp))
230 1 pfleura2
!            ELSE
231 1 pfleura2
!               If ((abs(DiheTmp).GE.170.D0).AND.(Sign(1.,DiheTmp)*ScanCoord%SignDihedral<0)) THEN
232 1 pfleura2
!                  Xprimitive_t(I) = DiheTmp*Pi/180.+ ScanCoord%SignDihedral*2.*Pi
233 1 pfleura2
!               END IF
234 1 pfleura2
!            END IF
235 1 pfleura2
236 1 pfleura2
!            IF (abs(Xprimitive_t(I)-XPrimRef(I)).GE.Pi) THEN
237 1 pfleura2
!               if ((Xprimitive_t(I)-XPrimRef(I)).GE.Pi) THEN
238 1 pfleura2
!                  Xprimitive_t(I)=Xprimitive_t(I)-2.d0*Pi
239 1 pfleura2
!               ELSE
240 1 pfleura2
!                  Xprimitive_t(I)=Xprimitive_t(I)+2.d0*Pi
241 1 pfleura2
!               END IF
242 1 pfleura2
!            END IF
243 1 pfleura2
244 1 pfleura2
!            Print *, I, ':',  ScanCoord%At1, '-',ScanCoord%At2,'-',ScanCoord%At3,'-',&
245 1 pfleura2
!            ScanCoord%At4,'=',Xprimitive_t(I)*180./Pi
246 1 pfleura2
!         END SELECT
247 1 pfleura2
!         ScanCoord => ScanCoord%next
248 1 pfleura2
!      END DO ! matches DO WHILE (Associated(ScanCoord%next))
249 1 pfleura2
250 1 pfleura2
     IntCoord_k=0.d0
251 1 pfleura2
     DO I=1, NPrim
252 1 pfleura2
        ! Transpose of UMat is needed below, that is why UMat(I,:).
253 1 pfleura2
        IntCoord_k(:)=IntCoord_k(:)+UMat_local(I,:)*Xprimitive_t(I)
254 1 pfleura2
     END DO
255 1 pfleura2
     WRITE(*,*) "Xint (intCoord_k) cooresponding to x_k,y_k,z_k"
256 1 pfleura2
     WRITE(*,'(50(1X,F12.8))') IntCoord_k(:)
257 1 pfleura2
     WRITE(*,*) "UMat_local"
258 1 pfleura2
     DO I=1, NPrim
259 1 pfleura2
        WRITE(*,'(50(1X,F12.8))') UMat_local(I,:)
260 1 pfleura2
     END DO
261 1 pfleura2
262 1 pfleura2
     !     Geom(1,:)=X_k(1:Nat)/a0
263 1 pfleura2
     !     Geom(2,:)=y_k(1:Nat)/a0
264 1 pfleura2
     !     Geom(3,:)=z_k(1:Nat)/a0
265 1 pfleura2
266 1 pfleura2
     Geom(1,:)=X_k(1:Nat)
267 1 pfleura2
     Geom(2,:)=y_k(1:Nat)
268 1 pfleura2
     Geom(3,:)=z_k(1:Nat)
269 1 pfleura2
270 1 pfleura2
     ! Computing B^prim:
271 1 pfleura2
     BprimT=0.d0
272 1 pfleura2
     ScanCoord=>Coordinate
273 1 pfleura2
     I=0
274 1 pfleura2
     DO WHILE (Associated(ScanCoord%next))
275 1 pfleura2
        I=I+1
276 1 pfleura2
        SELECT CASE (ScanCoord%Type)
277 1 pfleura2
        CASE ('BOND')
278 1 pfleura2
           CALL CONSTRAINTS_BONDLENGTH_DER(Nat,ScanCoord%at1,ScanCoord%AT2,Geom,BprimT(1,I))
279 1 pfleura2
        CASE ('ANGLE')
280 1 pfleura2
           CALL CONSTRAINTS_BONDANGLE_DER(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,Geom,BprimT(1,I))
281 1 pfleura2
        CASE ('DIHEDRAL')
282 1 pfleura2
           CALL CONSTRAINTS_TORSION_DER2(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,ScanCoord%At4,Geom,BprimT(1,I))
283 1 pfleura2
        END SELECT
284 1 pfleura2
        ScanCoord => ScanCoord%next
285 1 pfleura2
     END DO
286 1 pfleura2
287 1 pfleura2
     !     if (debug) THEN
288 1 pfleura2
     !        WRITE(*,*) "PFL DBG, I,NPrim,BPrimT",I,NPrim
289 1 pfleura2
     !        DO I=1,NPrim
290 1 pfleura2
     !           WRITE(*,'(50(1X,F12.6))') BPrimT(:,I)
291 1 pfleura2
     !        END DO
292 1 pfleura2
     !     END IF
293 1 pfleura2
294 1 pfleura2
     BMat_BakerT = 0.d0
295 1 pfleura2
     DO I=1,NCoord
296 1 pfleura2
        DO J=1,NPrim
297 1 pfleura2
           !BprimT is transpose of B^prim.
298 1 pfleura2
           !B = UMat^T B^prim, B^T = (B^prim)^T UMat
299 1 pfleura2
           BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat_local(J,I)
300 1 pfleura2
        END DO
301 1 pfleura2
     END DO
302 1 pfleura2
303 1 pfleura2
     BBT = 0.d0
304 1 pfleura2
     DO I=1,NCoord
305 1 pfleura2
        DO J=1,3*Nat   ! BBT(:,I) forms BB^T
306 1 pfleura2
           BBT(:,I) = BBT(:,I) + BMat_BakerT(J,:)*BMat_BakerT(J,I)
307 1 pfleura2
        END DO
308 1 pfleura2
     END DO
309 1 pfleura2
310 1 pfleura2
     BBT_inv = 0.d0
311 1 pfleura2
312 1 pfleura2
     !Print *, 'NCoord=', NCoord
313 1 pfleura2
     !Print *, 'BBT='
314 1 pfleura2
     DO J=1,NCoord
315 1 pfleura2
        ! WRITE(*,'(50(1X,F12.6))') BBT(:,J)
316 1 pfleura2
     END DO
317 1 pfleura2
     !Print *, 'End of BBT'
318 1 pfleura2
     ! GenInv is in Mat_util.f90
319 1 pfleura2
     Call GenInv(NCoord,BBT,BBT_inv,NCoord)
320 1 pfleura2
!     ALLOCATE(V(NCoord,NCoord))
321 1 pfleura2
!     tol = 1e-12
322 1 pfleura2
!     ! BBT is destroyed by GINVSE
323 1 pfleura2
!     Call GINVSE(BBT,NCoord,NCoord,BBT_inv,NCoord,NCoord,NCoord,tol,V,NCoord,FAIL,IOOUT)
324 1 pfleura2
!     DEALLOCATE(V)
325 1 pfleura2
!     IF(Fail) Then
326 1 pfleura2
!        WRITE (*,*) "Failed in generalized inverse, L220, ConvertBaker...f90"
327 1 pfleura2
!        STOP
328 1 pfleura2
!     END IF
329 1 pfleura2
330 1 pfleura2
     !Print *, 'BBT_inv='
331 1 pfleura2
     DO J=1,NCoord
332 1 pfleura2
        ! WRITE(*,'(50(1X,F10.2))') BBT_inv(:,J)
333 1 pfleura2
        ! Print *, BBT_inv(:,J)
334 1 pfleura2
     END DO
335 1 pfleura2
     !Print *, 'End of BBT_inv'
336 1 pfleura2
337 1 pfleura2
     ! Calculation of (B^T)^-1 = (BB^T)^-1B:
338 1 pfleura2
     BTransInv_local = 0.d0
339 1 pfleura2
     DO I=1,3*Nat
340 1 pfleura2
        DO J=1,NCoord
341 1 pfleura2
           BTransInv_local(:,I)=BTransInv_local(:,I)+BBT_inv(:,J)*BMat_BakerT(I,J)
342 1 pfleura2
        END DO
343 1 pfleura2
     END DO
344 1 pfleura2
345 1 pfleura2
     !Print *, 'BMat_BakerT='
346 1 pfleura2
     DO J=1,3*Nat
347 1 pfleura2
        !WRITE(*,'(50(1X,F12.8))') BMat_BakerT(:,J)
348 1 pfleura2
     END DO
349 1 pfleura2
     !Print *, 'End of BMat_BakerT'
350 1 pfleura2
351 1 pfleura2
     WRITE(*,*) "BTransInv_local Trans corresponding to x_k,y_k,z_k"
352 1 pfleura2
     DO J=1,3*Nat
353 1 pfleura2
        WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J)
354 1 pfleura2
     END DO
355 1 pfleura2
356 1 pfleura2
357 1 pfleura2
  END IF
358 1 pfleura2
359 1 pfleura2
  DeltaX_int(:) = IntCoord(:)-IntCoord_k(:)
360 1 pfleura2
361 1 pfleura2
  X_cart_k(1,:) = x_k(:)
362 1 pfleura2
  X_cart_k(2,:) = y_k(:)
363 1 pfleura2
  X_cart_k(3,:) = z_k(:)
364 1 pfleura2
365 1 pfleura2
  normDeltaX_int=0.d0 ! This is to be implemented.
366 1 pfleura2
  DO I=1, NCoord
367 1 pfleura2
     normDeltaX_int=normDeltaX_int+DeltaX_int(I)*DeltaX_int(I)
368 1 pfleura2
  END DO
369 1 pfleura2
  normDeltaX_int = sqrt(normDeltaX_int)
370 1 pfleura2
  ! I just need initial value of normDeltaX_int to be .GT. 1d-11,
371 1 pfleura2
  ! that is why it is initialized to 1.d0
372 1 pfleura2
  !normDeltaX_int = 1.d0
373 1 pfleura2
374 1 pfleura2
  if (debug) WRITE(*,*) "Entering the loop"
375 1 pfleura2
  Counter = 0
376 1 pfleura2
  DO While ((normDeltaX_int .GT. Crit) .AND. (Counter .LT. NbItMax))
377 1 pfleura2
     !DO While (normDeltaX_int .GT. 1d-6)
378 1 pfleura2
     Counter = Counter + 1
379 1 pfleura2
     DeltaX_cart = 0.d0
380 1 pfleura2
!     if (normDeltaX_int.LE.1e-4) THEN
381 1 pfleura2
!        DeltaX_int=DeltaX_int*1e4
382 1 pfleura2
!     END IF
383 1 pfleura2
     DO I=1,NCoord
384 1 pfleura2
        ! below BTransInv_local(I,:) is used because actually we need Transpose of BTransInv_local.
385 1 pfleura2
        DeltaX_cart(:)=DeltaX_cart(:)+BTransInv_local(I,:)*DeltaX_int(I)
386 1 pfleura2
     END DO
387 1 pfleura2
!     if (normDeltaX_int.LE.1e-4) THEN
388 1 pfleura2
!        DeltaX_int=DeltaX_int*1e-4
389 1 pfleura2
!     DeltaX_cart=DeltaX_cart*1e-4
390 1 pfleura2
!     END IF
391 1 pfleura2
392 1 pfleura2
393 1 pfleura2
           if (debug) THEN
394 1 pfleura2
              WRITE(*,*) "Info for iteration:",counter
395 1 pfleura2
              Print *, 'DeltaX_int='
396 1 pfleura2
              WRITE(*,'(50(1X,F12.8))') DeltaX_int
397 1 pfleura2
              Print *, 'DeltaX_cart,norm',sqrt(dot_product(DeltaX_cart,DeltaX_cart))
398 1 pfleura2
              DO J=1,Nat
399 1 pfleura2
              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 1 pfleura2
              END DO
401 1 pfleura2
              Print *, 'BTransInv_local Trans='
402 1 pfleura2
              DO J=1,3*Nat
403 1 pfleura2
                 WRITE(*,'(50(1X,F12.8))') BTransInv_local(:,J)
404 1 pfleura2
              END DO
405 1 pfleura2
              Print *, 'DeltaX_int='
406 1 pfleura2
              WRITE(*,'(50(1X,F12.8))') DeltaX_int
407 1 pfleura2
           END IF
408 1 pfleura2
409 1 pfleura2
     ! Finite precision error correction step:
410 1 pfleura2
!     DO I=1,3*Nat
411 1 pfleura2
!        IF (DeltaX_cart(I) .NE. 0.d0) Then
412 1 pfleura2
!           IF(abs(DeltaX_cart(I)) .LT. 1d-10) Then
413 1 pfleura2
!              !Print *, 'Correcting DeltaX_cart(',I,')=', DeltaX_cart(I)
414 1 pfleura2
!              DeltaX_cart(I) = 0.d0
415 1 pfleura2
!           END IF
416 1 pfleura2
!        END IF
417 1 pfleura2
!     END DO
418 1 pfleura2
419 1 pfleura2
     ! new cartesian coordinates:
420 1 pfleura2
     DO I=1, Nat
421 1 pfleura2
        X_cart_k(1,I) = X_cart_k(1,I) + DeltaX_cart(3*I-2)
422 1 pfleura2
        X_cart_k(2,I) = X_cart_k(2,I) + DeltaX_cart(3*I-1)
423 1 pfleura2
        X_cart_k(3,I) = X_cart_k(3,I) + DeltaX_cart(3*I)
424 1 pfleura2
     END DO
425 1 pfleura2
426 1 pfleura2
     !     Geom(1,:)=X_cart_k(1,1:Nat)/a0
427 1 pfleura2
     !     Geom(2,:)=X_cart_k(2,1:Nat)/a0
428 1 pfleura2
     !     Geom(3,:)=X_cart_k(3,1:Nat)/a0
429 1 pfleura2
     Geom(1,:)=X_cart_k(1,1:Nat)
430 1 pfleura2
     Geom(2,:)=X_cart_k(2,1:Nat)
431 1 pfleura2
     Geom(3,:)=X_cart_k(3,1:Nat)
432 1 pfleura2
433 1 pfleura2
     if (debug) THEN
434 1 pfleura2
     WRITE(*,*) 'GeomCart used to compute BPrim'
435 1 pfleura2
     DO I=1,Nat
436 1 pfleura2
        WRITE(*,'(1X,A,I4,3(1X,F12.4))') AtName(I),I,Geom(1,I),Geom(2,i),Geom(3,i)
437 1 pfleura2
     END DO
438 1 pfleura2
     END IF
439 1 pfleura2
440 1 pfleura2
     ! Computing B^prim:
441 1 pfleura2
     BprimT=0.d0
442 1 pfleura2
     ScanCoord=>Coordinate
443 1 pfleura2
     I=0
444 1 pfleura2
     DO WHILE (Associated(ScanCoord%next))
445 1 pfleura2
        I=I+1
446 1 pfleura2
        SELECT CASE (ScanCoord%Type)
447 1 pfleura2
        CASE ('BOND')
448 1 pfleura2
           CALL CONSTRAINTS_BONDLENGTH_DER(Nat,ScanCoord%at1,ScanCoord%AT2,Geom,BprimT(1,I))
449 1 pfleura2
        CASE ('ANGLE')
450 1 pfleura2
           CALL CONSTRAINTS_BONDANGLE_DER(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,Geom,BprimT(1,I))
451 1 pfleura2
        CASE ('DIHEDRAL')
452 1 pfleura2
           CALL CONSTRAINTS_TORSION_DER2(Nat,ScanCoord%At1,ScanCoord%AT2,ScanCoord%At3,ScanCoord%At4,Geom,BprimT(1,I))
453 1 pfleura2
        END SELECT
454 1 pfleura2
        ScanCoord => ScanCoord%next
455 1 pfleura2
     END DO
456 1 pfleura2
457 1 pfleura2
     if (debug) THEN
458 1 pfleura2
        WRITE(*,*) "Bprim "
459 1 pfleura2
        DO J=1,3*Nat
460 1 pfleura2
           WRITE(*,'(50(1X,F12.6))') BprimT(J,:)
461 1 pfleura2
        END DO
462 1 pfleura2
     END IF
463 1 pfleura2
464 1 pfleura2
465 1 pfleura2
     BMat_BakerT = 0.d0
466 1 pfleura2
     DO I=1,NCoord
467 1 pfleura2
        DO J=1,NPrim
468 1 pfleura2
           !BprimT is transpose of B^prim.
469 1 pfleura2
           !B = UMat^T B^prim, B^T = (B^prim)^T UMat
470 1 pfleura2
           BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat_local(J,I)
471 1 pfleura2
        END DO
472 1 pfleura2
     END DO
473 1 pfleura2
474 1 pfleura2
     ! ADDED FROM HERE:
475 1 pfleura2
     ! We now compute G=B(BT) matrix
476 1 pfleura2
     !IF (IOptt .EQ. 5000) Then
477 1 pfleura2
     !GMat=0.d0
478 1 pfleura2
     !DO I=1,NPrim
479 1 pfleura2
     !  DO J=1,3*Nat
480 1 pfleura2
     !    GMat(:,I)=Gmat(:,I)+BprimT(J,:)*BprimT(J,I) !*1.d0/mass(atome(int(K/3.d0)))
481 1 pfleura2
     !END DO
482 1 pfleura2
     !END DO
483 1 pfleura2
484 1 pfleura2
     ! We diagonalize G
485 1 pfleura2
     !Call Jacobi(GMat,NPrim,EigVal,EigVec,NPrim)
486 1 pfleura2
     !Call Trie(NPrim,EigVal,EigVec,NPrim)
487 1 pfleura2
488 1 pfleura2
     ! We construct the new DzDc(b=baker) matrix
489 1 pfleura2
     ! UMat is nonredundant vector set, i.e. set of eigenvectors of
490 1 pfleura2
     !  BB^T corresponding to eigenvalues > zero.
491 1 pfleura2
492 1 pfleura2
     !UMat=0.d0
493 1 pfleura2
     !UMat_tmp=0.d0
494 1 pfleura2
     !BMat_BakerT = 0.d0
495 1 pfleura2
     !J=0
496 1 pfleura2
     !DO I=1,NPrim
497 1 pfleura2
     !  IF (abs(eigval(I))>=1e-6) THEN
498 1 pfleura2
     !   J=J+1
499 1 pfleura2
     !  DO K=1,NPrim
500 1 pfleura2
     ! BprimT is transpose of B^prim.
501 1 pfleura2
     ! B = UMat^T B^prim, B^T = (B^prim)^T UMat
502 1 pfleura2
     !BMat_BakerT(:,J)=BMat_BakerT(:,J)+BprimT(:,K)*Eigvec(K,I)
503 1 pfleura2
     ! END DO
504 1 pfleura2
     !IF(J .GT. 3*Nat-6) THEN
505 1 pfleura2
     !WRITE(*,*) 'Number of vectors in Eigvec with eigval .GT. &
506 1 pfleura2
     !    1e-6 (=UMat) (=' ,J,') exceeded 3*Nat-6=',3*Nat-6, &
507 1 pfleura2
     !    'Stopping the calculation.'
508 1 pfleura2
     !   STOP
509 1 pfleura2
     !  END IF
510 1 pfleura2
     ! UMat_tmp(:,J) =  Eigvec(:,I)
511 1 pfleura2
     ! END IF
512 1 pfleura2
     !END DO
513 1 pfleura2
514 1 pfleura2
     ! THIS IS TO BE CORRECTED, A special case for debugging C2H3F case:
515 1 pfleura2
     !J=0
516 1 pfleura2
     !DO I=1, 3*Nat-6
517 1 pfleura2
     ! IF ((I .NE. 6) .AND. (I .NE. 7) .AND. (I .NE. 9)) Then
518 1 pfleura2
     !  J=J+1
519 1 pfleura2
     ! Print *, 'J=', J, ' I=', I
520 1 pfleura2
     !UMat(:,J) = UMat_tmp(:,I)
521 1 pfleura2
     !     END IF
522 1 pfleura2
     ! END DO
523 1 pfleura2
     !BMat_BakerT=0.d0
524 1 pfleura2
     !    DO I=1,NCoord
525 1 pfleura2
     !      DO J=1,NPrim
526 1 pfleura2
     ! B = UMat^T B^prim, B^T = (B^prim)^T UMat
527 1 pfleura2
     !       BMat_BakerT(:,I)=BMat_BakerT(:,I)+BprimT(:,J)*UMat(J,I)
528 1 pfleura2
     !    END DO
529 1 pfleura2
     !END DO
530 1 pfleura2
     ! TO BE CORRECTED, ENDS HERE.
531 1 pfleura2
532 1 pfleura2
     !END IF
533 1 pfleura2
     ! END of the new changes.
534 1 pfleura2
535 1 pfleura2
     BBT = 0.d0
536 1 pfleura2
     DO I=1,NCoord
537 1 pfleura2
        DO J=1,3*Nat   ! BBT(:,I) forms BB^T
538 1 pfleura2
           BBT(:,I) = BBT(:,I) + BMat_BakerT(J,:)*BMat_BakerT(J,I)
539 1 pfleura2
        END DO
540 1 pfleura2
     END DO
541 1 pfleura2
542 1 pfleura2
     BBT_inv = 0.d0
543 1 pfleura2
544 1 pfleura2
     !Print *, 'NCoord=', NCoord
545 1 pfleura2
     !Print *, 'BBT='
546 1 pfleura2
     DO J=1,NCoord
547 1 pfleura2
        ! WRITE(*,'(50(1X,F12.6))') BBT(:,J)
548 1 pfleura2
     END DO
549 1 pfleura2
     !Print *, 'End of BBT'
550 1 pfleura2
     ! GenInv is in Mat_util.f90
551 1 pfleura2
     Call GenInv(NCoord,BBT,BBT_inv,NCoord)
552 1 pfleura2
     !     if (debug) THEN
553 1 pfleura2
     !        WRITE(*,*) 'BBT_inv by GenInv'
554 1 pfleura2
     !        DO J=1,NCoord
555 1 pfleura2
     !           WRITE(*,'(50(1X,F12.6))') BBT_inv(:,J)
556 1 pfleura2
     !        END DO
557 1 pfleura2
     !     END IF
558 1 pfleura2
559 1 pfleura2
!    ALLOCATE(V(NCoord,NCoord))
560 1 pfleura2
!    tol = 1e-12
561 1 pfleura2
!    ! BBT is destroyed by GINVSE
562 1 pfleura2
!    Call GINVSE(BBT,NCoord,NCoord,BBT_inv,NCoord,NCoord,NCoord,tol,V,NCoord,FAIL,IOOUT)
563 1 pfleura2
!    DEALLOCATE(V)
564 1 pfleura2
!    IF(Fail) Then
565 1 pfleura2
!       WRITE (*,*) "Failed in generalized inverse, L220, ConvertBaker...f90"
566 1 pfleura2
!       STOP
567 1 pfleura2
!    END IF
568 1 pfleura2
569 1 pfleura2
     !     if (debug) THEN
570 1 pfleura2
     !        WRITE(*,*) 'BBT_inv by Genvse'
571 1 pfleura2
     !        DO J=1,NCoord
572 1 pfleura2
     !           WRITE(*,'(50(1X,F12.6))') BBT_inv(:,J)
573 1 pfleura2
     !        END DO
574 1 pfleura2
     !     END IF
575 1 pfleura2
576 1 pfleura2
     !Print *, 'End of BBT_inv'
577 1 pfleura2
578 1 pfleura2
     ! Calculation of (B^T)^-1 = (BB^T)^-1B:
579 1 pfleura2
     BTransInv_local = 0.d0
580 1 pfleura2
     DO I=1,3*Nat
581 1 pfleura2
        DO J=1,NCoord
582 1 pfleura2
           BTransInv_local(:,I)=BTransInv_local(:,I)+BBT_inv(:,J)*BMat_BakerT(I,J)
583 1 pfleura2
        END DO
584 1 pfleura2
     END DO
585 1 pfleura2
586 1 pfleura2
     !     if (debug) THEN
587 1 pfleura2
     !        Print *, 'BMat_BakerT='
588 1 pfleura2
     !        DO J=1,3*Nat
589 1 pfleura2
     !           WRITE(*,'(50(1X,F12.6))') BMat_BakerT(:,J)
590 1 pfleura2
     !        END DO
591 1 pfleura2
     !        Print *, 'End of BMat_BakerT'
592 1 pfleura2
     !     END IF
593 1 pfleura2
594 1 pfleura2
     !      if (debug) THEN
595 1 pfleura2
     !         Print *, 'BTransInv_local Trans='
596 1 pfleura2
     !         DO J=1,3*Nat
597 1 pfleura2
     !            WRITE(*,'(50(1X,F16.6))') BTransInv_local(:,J)
598 1 pfleura2
     !         END DO
599 1 pfleura2
     !         Print *, 'End of BTransInv_local Trans'
600 1 pfleura2
     !      END IF
601 1 pfleura2
602 1 pfleura2
     ! New cartesian cooordinates:
603 1 pfleura2
     x(:) = X_cart_k(1,:)
604 1 pfleura2
     y(:) = X_cart_k(2,:)
605 1 pfleura2
     z(:) = X_cart_k(3,:)
606 1 pfleura2
607 1 pfleura2
608 1 pfleura2
     Call Calc_Xprim(nat,x,y,z,Coordinate,NPrim,XPrimitive_t,XPrimRef)
609 1 pfleura2
610 1 pfleura2
!      I=0 ! index for the NPrim (NPrim is the number of
611 1 pfleura2
!      ! primitive coordinates).
612 1 pfleura2
!      Xprimitive_t=0.d0
613 1 pfleura2
!      ScanCoord=>Coordinate
614 1 pfleura2
!      DO WHILE (Associated(ScanCoord%next))
615 1 pfleura2
!         I=I+1
616 1 pfleura2
!         SELECT CASE (ScanCoord%Type)
617 1 pfleura2
!         CASE ('BOND')
618 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx2,vy2,vz2,Norm2)
619 1 pfleura2
!            Xprimitive_t(I) = Norm2
620 1 pfleura2
!            !Print *, I, ':',  ScanCoord%At1, '-', ScanCoord%At2, '=', Xprimitive_t(I)
621 1 pfleura2
!         CASE ('ANGLE')
622 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At3,x,y,z,vx1,vy1,vz1,Norm1)
623 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx2,vy2,vz2,Norm2)
624 1 pfleura2
!            Xprimitive_t(I) = angle(vx1,vy1,vz1,Norm1,vx2,vy2,vz2,Norm2)*Pi/180.
625 1 pfleura2
!            !Print *, I, ':', ScanCoord%At1, '-', ScanCoord%At2,'-',ScanCoord%At3, '=', Xprimitive_t(I)*180./Pi
626 1 pfleura2
!         CASE ('DIHEDRAL')
627 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At3,x,y,z,vx2,vy2,vz2,Norm2)
628 1 pfleura2
!            Call vecteur(ScanCoord%At2,ScanCoord%At1,x,y,z,vx1,vy1,vz1,Norm1)
629 1 pfleura2
!            Call vecteur(ScanCoord%At3,ScanCoord%At4,x,y,z,vx3,vy3,vz3,Norm3)
630 2 pfleura2
!            Call produit_vect(vx3,vy3,vz3,vx2,vy2,vz2,vx5,vy5,vz5,norm5)
631 2 pfleura2
!            Call produit_vect(vx1,vy1,vz1,vx2,vy2,vz2,vx4,vy4,vz4,norm4)
632 1 pfleura2
! !!! PFL 28 Feb 2008 Test to be sure that angle does not change by more than Pi
633 1 pfleura2
!            !           Xprimitive_t(I)=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5,vx2,vy2,vz2,norm2)*Pi/180.
634 1 pfleura2
!            DiheTmp=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5,vx2,vy2,vz2,norm2)
635 1 pfleura2
!            Xprimitive_t(I) = DiheTmp*Pi/180.
636 1 pfleura2
!            ! We treat large dihedral angles differently as +180=-180 mathematically and physically
637 1 pfleura2
!            ! but this causes lots of troubles when converting baker to cart.
638 1 pfleura2
!            ! So we ensure that large dihedral angles always have the same sign
639 1 pfleura2
!            if (abs(ScanCoord%SignDihedral).NE.1) THEN
640 1 pfleura2
!               ScanCoord%SignDihedral=Int(Sign(1.d0,DiheTmp))
641 1 pfleura2
!            ELSE
642 1 pfleura2
!               If ((abs(DiheTmp).GE.170.D0).AND.(Sign(1.,DiheTmp)*ScanCoord%SignDihedral<0)) THEN
643 1 pfleura2
!                  Xprimitive_t(I) = DiheTmp*Pi/180.+ ScanCoord%SignDihedral*2.*Pi
644 1 pfleura2
!               END IF
645 1 pfleura2
!            END IF
646 1 pfleura2
647 1 pfleura2
648 1 pfleura2
649 1 pfleura2
!            !Print *, I, ':',  ScanCoord%At1, '-',ScanCoord%At2,'-',ScanCoord%At3,'-',&
650 1 pfleura2
!            !ScanCoord%At4,'=',Xprimitive_t(I)*180./Pi
651 1 pfleura2
!         END SELECT
652 1 pfleura2
!         ScanCoord => ScanCoord%next
653 1 pfleura2
!      END DO ! matches DO WHILE (Associated(ScanCoord%next))
654 1 pfleura2
655 1 pfleura2
     !     if (debug) THEN
656 1 pfleura2
     !        WRITE(*,*) "Xprimitive_t"
657 1 pfleura2
     !        WRITE(*,'(50(1X,F12.6))') Xprimitive_t
658 1 pfleura2
     !     END IF
659 1 pfleura2
660 1 pfleura2
     IntCoord_k=0.d0
661 1 pfleura2
     DO I=1, NPrim
662 1 pfleura2
        ! Transpose of UMat is needed below, that is why UMat(I,:).
663 1 pfleura2
        IntCoord_k(:)=IntCoord_k(:)+UMat_local(I,:)*Xprimitive_t(I)
664 1 pfleura2
     END DO
665 1 pfleura2
666 1 pfleura2
     if (debug) THEN
667 1 pfleura2
        WRITE(*,*) "New Xint (IntCoord_k)"
668 1 pfleura2
        WRITE(*,'(50(1X,F12.8))') IntCoord_k
669 1 pfleura2
        WRITE(*,*) "Target (IntCoord)"
670 1 pfleura2
        WRITE(*,'(50(1X,F12.8))') IntCoord
671 1 pfleura2
672 1 pfleura2
     END IF
673 1 pfleura2
674 1 pfleura2
675 1 pfleura2
     ! Computing DeltaX_int
676 1 pfleura2
677 1 pfleura2
     DeltaX_int(:) = IntCoord(:)-IntCoord_k(:)
678 1 pfleura2
679 1 pfleura2
680 1 pfleura2
681 1 pfleura2
682 1 pfleura2
     ! norm2 of DeltaX_int is being calculated here:
683 1 pfleura2
     normDeltaX_int=0.d0
684 1 pfleura2
     DO I=1, NCoord
685 1 pfleura2
        normDeltaX_int=normDeltaX_int+DeltaX_int(I)*DeltaX_int(I)
686 1 pfleura2
     END DO
687 1 pfleura2
     normDeltaX_int = sqrt(normDeltaX_int)
688 1 pfleura2
689 1 pfleura2
          if (debug) THEN
690 1 pfleura2
             WRITE(*,*) "New Delta_Xint (deltaX_int)"
691 1 pfleura2
             WRITE(*,'(50(1X,F12.6))') DeltaX_int
692 1 pfleura2
             WRITE(*,*) "Norm:",normDeltaX_int
693 1 pfleura2
          END IF
694 1 pfleura2
695 1 pfleura2
     !IF (Counter .GE. 400) THEN
696 1 pfleura2
     !Print *, 'Counter=', Counter, 'normDeltaX_int=', normDeltaX_int
697 1 pfleura2
     !Print *, 'DeltaX_int='
698 1 pfleura2
     !WRITE(*,'(50(1X,F8.2))') DeltaX_int
699 1 pfleura2
     !END IF
700 1 pfleura2
701 1 pfleura2
     IF (Mod(Counter,1).EQ.0) THEN
702 1 pfleura2
        !WRITE(*,*) Nat
703 1 pfleura2
        !WRITE(*,*) 'GeomCart in ConvertBakerInternal_cart'
704 1 pfleura2
        DO I=1,Nat
705 1 pfleura2
           !  WRITE(*,'(1X,A,I4,3(1X,F12.4))') AtName(I),I,X_Cart_k(1:3,I)
706 1 pfleura2
        END DO
707 1 pfleura2
     END IF
708 1 pfleura2
709 1 pfleura2
     !call two_norm(DeltaX_int,normDeltaX_int,3*Nat)
710 1 pfleura2
  END DO !matches DO While (normDeltaX_int .GT. 1d-11)
711 1 pfleura2
712 1 pfleura2
  IF (debug) THEN
713 1 pfleura2
  WRITE(*,*) 'GeomCart in ConvertBakerInternal_cart'
714 1 pfleura2
  DO I=1,Nat
715 1 pfleura2
     WRITE(*,'(1X,A,I4,3(1X,F12.4))') AtName(I),I,X_Cart_k(1:3,I)
716 1 pfleura2
  END DO
717 1 pfleura2
  END IF
718 1 pfleura2
719 1 pfleura2
  if (debug) THEN
720 1 pfleura2
     WRITE(*,*) "Bmat_bakerT"
721 1 pfleura2
     DO J=1,NCoord
722 1 pfleura2
        WRITE(*,'(50(1X,F12.6))') BMat_BakerT(:,J)
723 1 pfleura2
     END DO
724 1 pfleura2
  END IF
725 1 pfleura2
726 1 pfleura2
727 1 pfleura2
728 1 pfleura2
  !IF (IOptt .GE. 2) THEN
729 1 pfleura2
  !   Print  *, 'Counter=', Counter
730 1 pfleura2
  !END IF
731 1 pfleura2
  IF (Counter .GE. NbItMax) Then
732 1 pfleura2
     Print *, 'Counter GE 500, Stopping, normDeltaX_int=', normDeltaX_int
733 1 pfleura2
     STOP
734 1 pfleura2
  END IF
735 1 pfleura2
736 1 pfleura2
737 1 pfleura2
     x(:) = X_cart_k(1,:)
738 1 pfleura2
     y(:) = X_cart_k(2,:)
739 1 pfleura2
     z(:) = X_cart_k(3,:)
740 1 pfleura2
741 1 pfleura2
742 1 pfleura2
!  call CalcRmsd(Nat,x_k,y_k,z_k,x,y,z,MRot,rmsd,.TRUE.,.TRUE.)
743 1 pfleura2
744 1 pfleura2
745 1 pfleura2
  if (debug) WRITE(*,*) "COnverted in ",counter," iterations"
746 1 pfleura2
747 1 pfleura2
  DEALLOCATE(Geom,DeltaX_int,DeltaX_cart)
748 1 pfleura2
  DEALLOCATE(BprimT,BBT,BBT_inv,UMat_tmp)
749 1 pfleura2
  DEALLOCATE(X_cart_k)
750 1 pfleura2
  DEALLOCATE(GMat,EigVal,EigVec)
751 1 pfleura2
752 1 pfleura2
  XPrim=Xprimitive_t
753 1 pfleura2
754 1 pfleura2
  if (debug) WRITE(*,*) '=====ConvertBakerInternal_cart Over====='
755 1 pfleura2
756 1 pfleura2
END SUBROUTINE ConvertBakerInternal_cart