Statistiques
| Révision :

root / src / Calc_zmat_frag.f90

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

1
SUBROUTINE Calc_Zmat_frag(na,atome,ind_zmat,val_zmat,x,y,z,r_cov,fact)
2

    
3
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4
!
5
!   Goal: to compute a viable Z-Matrix starting from the 
6
!         cartesian coordinates of the atoms
7
!
8
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
9
!
10
! Input:
11
!  na    : Number or atoms 
12
! atome  : Mass number of the atoms (H=1, He=2,...)
13
! x,y,z  : cartesian coordinates of the atoms
14
! r_cov  : array containing the covalent radii of the atoms
15
!  fact  : multiplicative factor used to determine if two atoms are linked.
16
!          see CalcCnct for more details.
17
!
18
! Output:
19
! ind_zmat : INTEGER(na,5) contains the indices of the Z-matrix
20
! val_zmat : REAL(na,3)    contains the values of the Z-matrix
21
!
22
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
23
! History
24
!
25
! v1.0 written for Cart a long time ago. Does not use fragment analysis, but was quite good !
26
!
27
! v2.0 12/2007
28
! Comes from Calc_zmat_constr_frag, based on a fragment analysis of the 
29
! system under study.
30
! It should be more flexible and robust.
31
!
32
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
33

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

    
65
  Use Path_module, only : max_Z, NMaxL, Nom, Pi
66
  Use Io_module
67

    
68
  IMPLICIT NONE
69

    
70
  integer(KINT), INTENT(IN) ::  na,atome(na)
71
  real(KREAL), INTENT(IN)   ::  x(Na),y(Na),z(Na),fact
72
  real(KREAL), INTENT(IN)   ::  r_cov(0:Max_Z)
73

    
74
  INTEGER(KINT), INTENT(OUT) :: ind_zmat(Na,5)
75
  real(KREAL), INTENT(OUT)   :: val_zmat(Na,3)
76

    
77
  INTEGER(KINT) :: idx_zmat(NA)
78
! Frozen contains the indices of frozen atoms
79
! INTEGER(KINT) Frozen(*),NFroz
80
! Number of fragment, Index of the current fragment for loops
81
  INTEGER(KINT) :: NbFrag
82
! Fragment(I) contains the fragment index to which I belongs
83
! NbAtFrag(j) contains the number of atoms of fragment j
84
  INTEGER(KINT), ALLOCATABLE :: Fragment(:),NbAtFrag(:) !na
85
! FragAt(i,:) lists the atoms of fragment i
86
  INTEGER(KINT), ALLOCATABLE :: FragAt(:,:) !na,na
87
! MaxLFrag(i,1) contains the maximum of links for an atom for fragment i
88
! MaxLFrag(i,2) is the atom that has this number of linked atoms
89
  INTEGER(KINT), ALLOCATABLE :: MaxLFrag(:,:) !na,2
90
! INTEGER(KINT), ALLOCATABLE :: IdxFragAt(:) !na
91
! INTEGER(KINT), ALLOCATABLE :: FrozBlock(:,:) !(na,0:na)
92
! DistFrag contains the distance between a given atom and some other atoms
93
  REAL(KREAL), ALLOCATABLE :: DistFrag(:) !na
94
! FragDist(I) contains the index of the atoms corresponding to DistFrag(I)
95
  INTEGER(KINT), ALLOCATABLE :: FragDist(:) ! na
96

    
97
  INTEGER(KINT) :: IdxCaFaire, IAfaire
98
  INTEGER(KINT), ALLOCATABLE ::  LIAISONS(:,:) ! (Na,0:NMaxL)
99
! INTEGER(KINT), ALLOCATABLE ::  LiaisonsIni(:,:) ! (Na,0:NMaxL)
100
  INTEGER(KINT), ALLOCATABLE :: CAFaire(:) ! (Na)
101

    
102
  real(KREAL) ::  vx1,vy1,vz1,norm1
103
  real(KREAL) ::  vx2,vy2,vz2,norm2
104
  real(KREAL) ::  vx3,vy3,vz3,norm3
105
  real(KREAL) ::  vx4,vy4,vz4,norm4
106
  real(KREAL) ::  vx5,vy5,vz5,norm5
107
  real(KREAL) ::  val,val_d, d12, d13,d23,d
108
  Logical Debug, FirstAt, DebugGaussian
109
  LOGICAL, ALLOCATABLE :: DejaFait(:), FCaf(:) !(na)
110
!  Logical, ALLOCATABLE ::  FrozAt(:)    !T if this atom is frozen
111
  LOGICAL F1213, F1223,F1323
112

    
113
  INTEGER(KINT) :: I,J,n0,n1,n2,n3,n4,IAt,IL,JL,IFrag,ITmp, K, KMax
114
  INTEGER(KINT) :: I3, I1, Ip
115
  INTEGER(KINT) :: I0, Izm, JAt
116
  INTEGER(KINT) :: OrderZmat
117

    
118
  REAL(KREAL) :: sDihe
119
  REAL(KREAL), PARAMETER :: LocalNCart=0.d0
120

    
121
  INTERFACE
122
     function valid(string) result (isValid)
123
       CHARACTER(*), intent(in) :: string
124
       logical                  :: isValid
125
     END function VALID
126

    
127
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
128
       INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
129
       real(KREAL) ::  v1x,v1y,v1z,norm1
130
       real(KREAL) ::  v2x,v2y,v2z,norm2
131
       real(KREAL) ::  angle
132
     END FUNCTION ANGLE
133

    
134
     FUNCTION SinAngle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
135
       INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
136
       real(KREAL) ::  v1x,v1y,v1z,norm1
137
       real(KREAL) ::  v2x,v2y,v2z,norm2
138
       real(KREAL) ::  SinAngle
139
     END FUNCTION SINANGLE
140

    
141
     FUNCTION angle_d(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2,v3x,v3y,v3z,norm3)
142
       INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
143
       real(KREAL) ::  v1x,v1y,v1z,norm1
144
       real(KREAL) ::  v2x,v2y,v2z,norm2
145
       real(KREAL) ::  v3x,v3y,v3z,norm3
146
       real(KREAL) ::  angle_d,ca,sa
147
     END FUNCTION ANGLE_D
148
  END INTERFACE
149

    
150
  debug=valid("calc_zmat").OR.valid("calc_zmat_frag")
151
  debugGaussian=valid("zmat_gaussian")
152
  
153
  if (debug) WRITE(*,*) "=============================== Entering Calc_zmat_frag ========================"
154
  if (na.le.2) THEN
155
     WRITE(*,*) "I do not work for less than 2 atoms :-p"
156
     RETURN
157
  END IF
158

    
159
  ALLOCATE(FragDist(Na),Fragment(na), NbAtFrag(na),FragAt(na,na))
160
! ALLOCATE(FrozFrag(na,3), IdxFragAt(na), FrozBlock(na,0:na))
161
! ALLOCATE(FrozFrag(na,3))
162
  ALLOCATE(DistFrag(na),Liaisons(na,0:NMaxL))
163
! ALLOCATE(Liaisons(na,0:NMaxL),LiaisonsIni(na,0:NMaxL))
164
! ALLOCATE(CaFaire(na),DejaFait(Na),FCaf(na),FrozAt(na))
165
  ALLOCATE(CaFaire(na+1),DejaFait(Na),FCaf(na))
166

    
167
  if (debug) THEN
168
     WRITE(*,*) "DBG Calc_zmat_frag - Cartesian coordinates"
169
     DO I=1,na
170
        WRITE(*,'(1X,A3,3(1X,F15.8))') Nom(atome(i)),x(i),y(i),z(i)
171
     END DO
172
  END if
173

    
174
  DO I=1,na
175
     DO J=1,5
176
        Ind_Zmat(I,J)=0
177
     END DO
178
  END DO
179
  
180
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
181
!
182
!     Easy case : 3 or less atoms
183
!
184
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
185
  if (Na.eq.3) THEN
186
     d12=sqrt((x(1)-x(2))**2+(y(1)-y(2))**2+(z(1)-z(2))**2)
187
     d13=sqrt((x(1)-x(3))**2+(y(1)-y(3))**2+(z(1)-z(3))**2)
188
     d23=sqrt((x(3)-x(2))**2+(y(3)-y(2))**2+(z(3)-z(2))**2)
189
     F1213=(d12<=d13)
190
     F1323=(d13<=d23)
191
     F1223=(d12<=d23)
192
     if (debug) THEN
193
        WRITE(*,*) "DEBUG Calc_Zmat 3 atoms"
194
        WRITE(*,*) "d12,d13,d23:",d12,d13,d23
195
        WRITE(*,*) "F1213,F1323,F1223:",F1213,F1323,F1223
196
     END IF
197
     OrderZmat=0
198
     if (F1213) orderZmat=OrderZmat+4
199
     if (F1323) orderZmat=OrderZmat+2
200
     if (F1223) orderZmat=OrderZmat+1
201
     if (debug) WRITE(*,*) 'OrderZmat=',OrderZmat
202
     SELECT CASE (OrderZmat)
203
        CASE (0)
204
! F F F ordre 2-3----1 
205
           ind_zmat(1,1)=3
206
           ind_zmat(2,1)=2
207
           ind_zmat(2,2)=3
208
           ind_zmat(3,1)=1
209
           ind_zmat(3,2)=3
210
           ind_zmat(3,3)=2
211
        CASE (2)
212
! F T F ordre 1-3----2
213
           ind_zmat(1,1)=3
214
           ind_zmat(2,1)=1
215
           ind_zmat(2,2)=3
216
           ind_zmat(3,1)=2
217
           ind_zmat(3,2)=3
218
           ind_zmat(3,3)=1
219
        CASE (3)
220
! F T T ordre 2---1-3
221
           ind_zmat(1,1)=1
222
           ind_zmat(2,1)=3
223
           ind_zmat(2,2)=1
224
           ind_zmat(3,1)=2
225
           ind_zmat(3,2)=1
226
           ind_zmat(3,3)=3
227
        CASE (5)
228
! T F T  ordre 1-2----3
229
           ind_zmat(1,1)=2
230
           ind_zmat(2,1)=1
231
           ind_zmat(2,2)=2
232
           ind_zmat(3,1)=3
233
           ind_zmat(3,2)=2
234
           ind_zmat(3,3)=1
235
        CASE (7)
236
! T T T ordre 3----1-2
237
           ind_zmat(1,1)=1
238
           ind_zmat(2,1)=2
239
           ind_zmat(2,2)=1
240
           ind_zmat(3,1)=3
241
           ind_zmat(3,2)=1
242
           ind_zmat(3,3)=2
243
        END SELECT
244

    
245
     IF (debug) THEN
246
        WRITE(*,*) "DBG Calc_zmat_frag - Nat=3 -"
247
        DO i=1,na
248
           WRITE(*,'(1X,A3,5(1X,I5))') Nom(Atome(ind_zmat(i,1))),(ind_zmat(i,j),j=1,5)
249
        END DO
250
     END IF
251

    
252
     ! We have ind_zmat, we fill val_zmat
253
     val_zmat=0.d0
254
     n2=ind_zmat(2,1)
255
     n1=ind_zmat(2,2)
256
     d=sqrt((x(n1)-x(n2))**2+(y(n1)-y(n2))**2+(z(n1)-z(n2))**2)
257
     val_zmat(2,1)=d
258
     n1=ind_zmat(3,1)
259
     n2=ind_zmat(3,2)
260
     n3=ind_zmat(3,3)
261
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
262
     if (debug) write(*,*) n1,n2,norm1
263
     val_zmat(3,1)=norm1
264

    
265
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
266
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
267
     if (debug) write(*,*) n2,n3,norm2,val
268
     val_zmat(3,2)=val
269

    
270
     RETURN
271
  END IF !matches if (Na.eq.3) THEN
272
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
273
!
274
!  End of Easy case : 3 or less atoms
275
!
276
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
277
!
278
! General Case 
279
!
280
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
281
!
282

    
283
! Initialization
284
  DejaFait=.False.
285
  Liaisons=0
286
  ind_zmat=0
287
  val_zmat=0.d0
288

    
289
  if (debug) WRITE(*,*) "Coucou from Calc_zmat_frag.f90; L240"
290
  
291
  if (debug) THEN
292
     WRITE(*,*) "Bonds initialized"
293
     WRITE(*,*) 'Covalent radii used'
294
     DO iat=1,na
295
        i=atome(iat)
296
        WRITE(*,*) Nom(I),Iat,r_cov(i),r_cov(i)*fact
297
     END DO
298
  END IF
299

    
300
1003 FORMAT(1X,I4,' - ',25(I5))
301

    
302
!   First step : connectivity  are calculated
303

    
304
  Call CalcCnct(na,atome,x,y,z,LIAISONS,r_cov,fact)
305

    
306
  if (debug) THEN
307
     WRITE(*,*) "Connections calculated"
308
     DO IL=1,na
309
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
310
     END DO
311
  END IF
312

    
313
  FCaf=.TRUE.
314
  Call Decomp_frag(na,liaisons,FCaf,nbfrag,Fragment,NbAtFrag,FragAt)
315
  
316
  IF (debug) THEN
317
     WRITE(*,*) 'I found ',NbFrag, 'fragments'
318
     WRITE(*,*) (NbAtFrag(I),I=1,NbFrag)
319
     DO I=1,NbFrag
320
        WRITE(*,*) NbAtFrag(I)
321
        WRITE(*,*) 'Fragment ', i
322
        DO J=1,Na
323
           IF (Fragment(J).EQ.I) WRITE(*,'(1X,I3,1X,A5,3(1X,F10.6))') J,Nom(Atome(J)) &
324
                ,X(J),Y(J),Z(J)
325
        END DO
326
        WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
327
     END DO
328
  END IF
329

    
330
 ALLOCATE(MaxLFrag(NbFrag,2))
331

    
332
 MaxLFrag=0
333

    
334
  DO I=1,NbFrag
335
     MaxLFrag(I,1)=Liaisons(FragAt(I,1),0)
336
     MaxLFrag(I,2)=FragAt(I,1)
337

    
338
     DO J=1,NbAtFrag(I)
339
      Iat=FragAt(I,J)
340
        IF (Liaisons(IAt,0).GT.MaxLFrag(I,1)) THEN
341
       MaxLFrag(I,1)=Liaisons(Iat,0)
342
       MaxLFrag(I,2)=Iat
343
    END IF
344
     END DO
345
     IF (debug) WRITE(*,*) 'Frag :',I,', atom ',MaxLFrag(I,2), ' has ',MaxLFrag(I,2),' links'
346
  END DO
347

    
348
  !     We will now build the molecule fragment by fragment
349
  !     We choose the starting fragment with two criteria:
350
  !     1- Number of linked atoms:
351
  !       * >=3 is good as it fully defines the coordinate space
352
  !       * 2 is ok as we can either use a 3rd atom from the same fragment
353
  !       or add a X atom somewhere but this complicates quite a lot the way
354
  !       to treat the conversion from cartesian to zmat latter
355
  !       * 1 is bad...
356
  !     2- Size of the fragment
357
  !     this allows us to deal more easily with cases 1- when number of 
358
  !     directly linked atoms is less than 3
359

    
360
  IFrag=0
361
! I0 is the number of connections of the best fragment
362
  I0=0
363
! I1 is the number of atoms of the best fragment
364
  I1=0
365
  IAt=0
366
  DO I=1,NbFrag
367
    SELECT CASE(MaxLFrag(I,1)-I0)
368
     CASE (1:)
369
        IFrag=I
370
        I0=MaxLFrag(I,1)
371
        I1=NbAtFrag(I)
372
        IAt=MaxLFrag(I,2)
373
     CASE (0)
374
        if (NbAtFrag(I).GT.I1) THEN
375
           IFrag=I
376
           I0=MaxLFrag(I,1)
377
           I1=NbAtFrag(I)
378
           IAt=MaxLFrag(I,2)
379
        END IF
380
     END SELECT
381
  END DO
382

    
383
  if (debug) WRITE(*,'(1X,A,I5,A,I5,A,I5,A,I5)') 'Starting with fragment:',IFrag,' with ',I0   &
384
      ,' max links for atom',IAt,' fragment size',NbAtFrag(IFrag)
385

    
386
  !     We will build the first fragment in a special way, as it will
387
  !     set the coordinates system
388

    
389
  if (debug) WRITE(*,*) 'Fragment 1, starting with atom:',IAt, &   
390
    'with ',I0,' connections'
391

    
392
  DejaFait=.FALSE.
393
  FCaf=.FALSE.
394
  
395
  izm=0
396
  SELECT CASE (I0)
397
  CASE(3:)
398
     if (debug) WRITE(*,*) 'DBG select case I0 3'
399
     n0=Iat
400

    
401
     ITmp=2
402
     sDihe=0.
403
     n2=IAt
404
     n3=Liaisons(Iat,1)
405
     ! We search for the third atom while making sure that it is not aligned with first two !
406
     DO While ((ITmp.LE.Liaisons(Iat,0)).AND.(sDihe.LE.0.09d0))
407
        n4=Liaisons(Iat,Itmp)
408
        CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
409
        CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
410
        val_d=angle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
411
        sDiHe=abs(sin(val_d*pi/180.d0))
412
        if (debug) Write(*,*) 'Trying n2,n3,n4,sdihe,val_d',n2,n3,n4,sdihe,val_d
413
        Itmp=Itmp+1
414
     END DO
415
     If (debug) WRITE(*,*) 'Itmp,Liaisons',Itmp,Liaisons(Iat,1:NMaxL)
416
     Liaisons(Iat,Itmp-1)=Liaisons(iat,2)
417
     Liaisons(Iat,2)=n4
418
     If (debug) WRITE(*,*) 'Itmp,Liaisons',Itmp,Liaisons(Iat,1:NMaxL)
419

    
420
     if (sDihe.LE.0.09d0) THEN
421
        WRITE(*,*) "PROBLEM !!! All atoms linked to ",n0," are aligned..."
422
    WRITE(*,*) "Surprising as this atom has at least three bonds... For NOW STOP"
423
    STOP
424
     END IF
425

    
426
     CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2,  vx5,vy5,vz5,norm5)
427

    
428

    
429
! We search for the fourth atom while checking that it is not aligned with 1st and 2nd atoms.
430
     Itmp=3
431
     sDiHe=0.
432
! PFL 28 Dec 2007 ->
433
! I had a test on the dihedral angle, but I cannot see why it is important to have
434
! a non planar fragment at the begining... ethylene works and is fully planar
435
! I thus suppress this test
436
!
437
!     DO While ((ITmp.LE.Liaisons(Iat,0)).AND.(sDihe.LE.0.09d0))
438
!        ITmp=ITmp+1
439
        n1=Liaisons(Iat,Itmp)
440
        if (debug) WRITe(*,*) 'trying n1,n2,n3,n4',n1,n2,n3,n4
441
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
442
        ! Is this atom aligned with n2-n3 ?
443
        val_d=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
444
        sDiHe=abs(sin(val_d*pi/180.d0))
445
        if (debug) Write(*,*) 'Angle n3-n2-n1',val_d
446
        if (sDiHe.le.0.09d0) THEN
447
           ! As atoms n2,n3 and n4 are not aligned, we interchange n3 and n4 so that n1,n2 and n3 are not aligned
448
           if (debug) WRITE(*,*) "n3-n2-n1 aligned, we interchange n3 and n4"
449
           n1=n3
450
           n3=n4
451
           n4=n1
452
           n1=Liaisons(Iat,ITmp)
453
           CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)           
454
           CALL vecteur(n2,n4,x,y,z,vx3,vy3,vz3,norm3)           
455
           val_d=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
456
           if (debug) Write(*,*) 'NEW Angle n3-n2-n1',val_d
457
        END IF
458

    
459
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
460
        ! avant de tester l'angle diedre, il faut verifier que ce 4e atome n'est pas
461
        ! aligne avec les 2 premiers. 
462
        ! comme on a deja test? que les 3 premiers ne sont pas alignes,
463
        ! s'il est align? avec les 2 premiers, on peut inverser le role de 2 et 3.
464
        ! On pourrait tout simplier en faisant une bete recherche parmi tous les atomes geles
465
        ! de ce bloc (au moins 4 ?) avec le critere 1) on les range par distance croissante
466
        ! 2) on les scanne tant que l'angle valence n'est pas bon, puis tant que diehedre pas bon
467
        ! on pourrait comme ca faire un tableau avec les atomes ranges d'abord pour le fragment s?lectionn?
468
        ! puis les atomes des autres fragment par distance croissante.
469
        ! les autres fragments ne seraient additonn?s que si l'on ne trouve pas notre bonheur dans le premier bloc
470
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
471

    
472
        CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, vx4,vy4,vz4,norm4)
473
        val_d=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
474
             vx2,vy2,vz2,norm2)
475
        sDihe=abs(sin(val_d*pi/180.d0))
476
        if (debug) WRITE(*,*) 'n2,n3,n4,n1, angle_d',n2,n3,n4,n1,val_d
477
!     END DO
478

    
479
     DejaFait(n2)=.TRUE.
480
     DejaFait(n3)=.TRUE.
481
     DejaFait(n4)=.TRUE.
482

    
483
!     if (sDihe.LE.0.09d0) THEN
484
!        !     None of the atoms linked to IAt are good to define the third
485
!        !     direction in space...
486
!        !     We will look at the other atoms
487
!        !     we might improve the search so as to take the atom closest to IAt
488
!        if (debug) WRITE(*,*) "All atoms linked to ",Iat," are in a plane. Looking for other atoms"
489
!        ITmp=0
490
!        DO I=1,NbAtFrag(IFrag)
491
!           JAt=FragAt(IFrag,I)
492
!           if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
493
!              n1=JAt
494
!              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
495
!              CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2,vx4,vy4,vz4,norm4)
496
!              val_d=angle_d(vx4,vy4,vz4,norm4, &
497
!                   vx5,vy5,vz5,norm5, &
498
!                   vx2,vy2,vz2,norm2)
499
!              if (abs(sin(val_d)).GE.0.09D0) THEN
500
!                 ITmp=ITmp+1
501
!                 DistFrag(ITmp)=Norm1
502
!                 FragDist(ITmp)=JAt
503
!              END IF
504
!           END IF
505
!        END DO
506

    
507
!        IF (ITmp.EQ.0) THEN
508
!           !     All dihedral angles between frozen atoms are less than 5?
509
!           !     (or more than 175?). We have to look at other fragments :-(
510
!           DO I=1,NFroz
511
!              Jat=Frozen(I)
512
!              if (.NOT.DejaFait(JAt)) THEN
513
!                 n1=JAt
514
!                 CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
515
!                 CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2,vx4,vy4,vz4,norm4)
516
!                 val_d=angle_d(vx4,vy4,vz4,norm4, &
517
!                      vx5,vy5,vz5,norm5, &
518
!                      vx2,vy2,vz2,norm2)
519
!                 if (abs(sin(val_d)).GE.0.09D0) THEN
520
!                    ITmp=ITmp+1
521
!                    DistFrag(ITmp)=Norm1
522
!                    FragDist(ITmp)=JAt
523
!                 END IF
524
!              END IF
525
!           END DO
526
!           IF (ITmp.EQ.0) THEN
527
!              !     All frozen atoms are in a plane... too bad
528
!              WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
529
!              WRITE(*,*) 'For now, I do not treat this case'
530
!              STOP
531
!           END IF
532
!        END IF
533
!        I1=0
534
!        d=1e9
535
!        DO I=1,ITmp
536
!           IF (DistFrag(I).LE.d) THEN
537
!              d=DistFrag(I)
538
!              I1=FragDist(I)
539
!           END IF
540
!        END DO
541
!     ELSE                !(sDihe.LE.0.09d0)
542
!        I1=FrozBlock(IAt,ITmp)
543
!        if (debug) WRITE(*,*) 'I1,n1:',I1,n1
544
!     END IF                 !(sDihe.LE.0.09d0)
545
!     !     we now have the atom that is closer to the first one and that
546
!     !     forms a non 0/Pi dihedral angle
547
!
548
!  <- PFL 28 Dec 2007
549

    
550
! We construct the begining of the Z-Matrix
551

    
552
     ind_zmat(1,1)=n2
553
     ind_zmat(2,1)=n3
554
     ind_zmat(2,2)=n2
555
     ind_zmat(3,1)=n4
556
     ind_zmat(3,2)=n2
557
     ind_zmat(3,3)=n3
558
     DejaFait(n2)=.TRUE.
559
     DejaFait(n3)=.TRUE.
560
     DejaFait(n4)=.TRUE.
561
     CaFaire(1)=n3
562
     CaFaire(2)=n4
563

    
564
! PFL 28 Dec 2007
565
! We have not selected a fourth atom, so that the following is not needed
566
!     ind_zmat(4,1)=I1
567
!     ind_zmat(4,2)=n2
568
!     ind_zmat(4,3)=n3
569
!     ind_zmat(4,4)=n4
570
!     DejaFait(I1)=.TRUE.
571
!     CaFaire(3)=I1
572
!     CaFaire(4)=0
573
!     IdxCaFaire=4
574
!     izm=4
575
!     FCaf(I1)=.TRUE.
576
!!!!!!!
577
! and replaced by:
578
     CaFaire(3)=0
579
   IdxCaFaire=3
580
   izm=3
581
!
582
! <- PFL 28 Dec 2007
583
   
584
     FCaf(n2)=.TRUE.
585
     FCaf(n3)=.TRUE.
586
   FirstAt=.TRUE.
587
     DO I=3,Liaisons(Iat,0)
588
        IF (.NOT.DejaFait(Liaisons(Iat,I))) THEN
589
           izm=izm+1
590
           !           ind_zmat(izm,1)=Liaisons(Iat,I)
591
           !           ind_zmat(izm,2)=n2
592
           !           ind_zmat(izm,3)=n3
593
           !           ind_zmat(izm,4)=n4
594
           Call add2indzmat(na,izm,Liaisons(Iat,I),n2,n3,n4,ind_zmat,x,y,z)
595
           if (FirstAt) THEN
596
           n4=Liaisons(Iat,I)
597
         FirstAt=.FALSE.
598
       END IF
599
           IF (.NOT.FCaf(Liaisons(Iat,I))) THEN
600
              CaFaire(IdxCaFaire)=Liaisons(Iat,I)
601
              IdxCaFaire=IdxCaFaire+1
602
              CaFaire(IdxCaFaire)=0
603
              FCaf(Liaisons(Iat,I))=.TRUE.
604
           END IF
605
           DejaFait(Liaisons(Iat,I))=.TRUE.
606
        END IF
607
     END DO
608

    
609
     if (debug) THEN
610
        WRITE(*,*) "Ind_zmat 0 - SELECT CASE I0 3: -- izm=",izm
611
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
612
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
613
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
614
        DO I=4,izm
615
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
616
                ind_zmat(I,3), ind_zmat(I,4)
617
        END DO
618
     END IF
619

    
620

    
621
     !     First four atoms (at least) have been put we go on with next parts
622
     !     of this fragment... later
623

    
624

    
625
  CASE(2)
626
     if (debug) WRITE(*,*) 'DBG select case I0 2'
627
   WRITE(*,*) "PFL 28 Dec 2007: No test of alignment here :(  TO DO TO DO TO DO"
628
     ind_zmat(1,1)=IAt
629
     ind_zmat(2,1)=Liaisons(IAt,1)
630
     ind_zmat(2,2)=IAt
631
     ind_zmat(3,1)=Liaisons(IAt,2)
632
     ind_zmat(3,2)=IAt
633
     ind_zmat(3,3)=Liaisons(IAt,1)
634
     DejaFait(IAt)=.TRUE.
635
     DejaFait(Liaisons(Iat,1))=.TRUE.
636
     DejaFait(Liaisons(Iat,2))=.TRUE.
637
     CaFaire(1)=Liaisons(Iat,1)
638
     CaFaire(2)=Liaisons(Iat,2)
639
     FCaf(Liaisons(Iat,1))=.TRUE.
640
     FCaf(Liaisons(Iat,2))=.TRUE.
641

    
642
! PFL 28 Dec 2007 ->
643
! We do NOT need a fourth atom !!! The third direction in space is defined by the cross
644
! product of the first two directions
645
!
646
! the following is thus commented
647
!
648
!     !     We search for a fourth atom, first in the FrozBlock atoms
649
!     ITmp=2
650
!     sDihe=0.
651
!     n2=IAt
652
!     n3=Liaisons(Iat,1)
653
!     n4=Liaisons(Iat,2)
654
!     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
655
!     CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
656
!     CALL produit_vect(vx3,vy3,vz3, vx2,vy2,vz2, vx5,vy5,vz5,norm5)
657
!
658
!     DO While ((ITmp.LE.FrozBlock(Iat,0)).AND.(sDihe.LE.0.09d0))
659
!        ITmp=ITmp+1
660
!        n1=FrozBlock(Iat,Itmp)
661
!        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
662
!        CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, vx4,vy4,vz4,norm4)
663
!        val_d=angle_d(vx4,vy4,vz4,norm4,  &
664
!             vx5,vy5,vz5,norm5,           &
665
!             vx2,vy2,vz2,norm2)
666
!        sDihe=abs(sin(val_d))
667
!     END DO
668
!     IF (debug) WRITE(*,*) 'DBG 4th atom, ITmp, sDihe',ITmp, sDihe
669
!     if (sDihe.LE.0.09d0) THEN
670
!        !     None of the frozen atoms linked to IAt are good to define the third
671
!        !     direction in space...
672
!        !     We will look at the other frozen atoms
673
!        !     we might improve the search so as to take the atom closest to IAt
674
!        ITmp=0
675
!        DO I=1,NbAtFrag(IFrag)
676
!           JAt=FragAt(IFrag,I)
677
!           if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
678
!              n1=JAt
679
!              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
680
!              CALL produit_vect(vx1,vy1,vz1, vx2,vy2,vz2, vx4,vy4,vz4,norm4)
681
!              val_d=angle_d(vx4,vy4,vz4,norm4,    &
682
!                   vx5,vy5,vz5,norm5,              &
683
!                   vx2,vy2,vz2,norm2)
684
!              if (abs(sin(val_d)).GE.0.09D0) THEN
685
!                 ITmp=ITmp+1
686
!                 DistFrag(ITmp)=Norm1
687
!                 FragDist(ITmp)=JAt
688
!              END IF
689
!           END IF
690
!        END DO
691
!        IF (ITmp.EQ.0) THEN
692
!           !     All dihedral angles between frozen atoms are less than 5?
693
!           !     (or more than 175?). We have to look at other fragments :-(
694
!           DO I=1,NFroz
695
!              Jat=Frozen(I)
696
!              if (.NOT.DejaFait(JAt)) THEN
697
!                 n1=JAt
698
!                 CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
699
!                 CALL produit_vect(vx1,vy1,vz1, vx2,vy2,vz2, vx4,vy4,vz4,norm4)
700
!                 val_d=angle_d(vx4,vy4,vz4,norm4,       &
701
!                      vx5,vy5,vz5,norm5,                 &
702
!                      vx2,vy2,vz2,norm2)
703
!                 if (abs(sin(val_d)).GE.0.09D0) THEN
704
!                    ITmp=ITmp+1
705
!                    DistFrag(ITmp)=Norm1
706
!                    FragDist(ITmp)=JAt
707
!                 END IF
708
!              END IF
709
!           END DO
710
!           IF (ITmp.EQ.0) THEN
711
!              !     All frozen atoms are in a plane... too bad
712
!              WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
713
!              WRITE(*,*) 'For now, I do not treat this case'
714
!              STOP
715
!           END IF
716
!        END IF
717
!        I1=0
718
!        d=1e9
719
!        DO I=1,ITmp
720
!           IF (DistFrag(I).LE.d) THEN
721
!              d=DistFrag(I)
722
!              I1=FragDist(I)
723
!           END IF
724
!        END DO
725
!     ELSE                   !(sDihe.LE.0.09d0)
726
!        I1=FrozBlock(IAt,ITmp)
727
!     END IF                 !(sDihe.LE.0.09d0)
728
!     !     we now have the atom that is closer to the first one and that
729
!     !     forms a non 0/Pi dihedral angle
730
!     !     ind_zmat(4,1)=I1
731
!     !     ind_zmat(4,2)=IAt
732
!     !     ind_zmat(4,3)=Liaisons(Iat,1)
733
!     !     ind_zmat(4,4)=Liaisons(Iat,2)
734
!     n3=Liaisons(Iat,1)
735
!     n4=Liaisons(Iat,2)
736
!     Call add2indzmat(na,4,I1,Iat,n3,n4,ind_zmat,x,y,z)
737
!     Liaisons(Iat,1)=n3
738
!     Liaisons(Iat,2)=n4
739
!     DejaFait(I1)=.TRUE.
740
!     CaFaire(3)=I1
741
!     CaFaire(4)=0
742
!     IdxCaFaire=4
743
!     izm=4
744
!     FCaf(I1)=.TRUE.
745
!
746
!!!!!! <- PFL 28 Dec 2007
747

    
748
     CaFaire(3)=0
749
     IdxCaFaire=3
750
     izm=3
751

    
752
  CASE(1)
753
     if (debug) WRITE(*,*) 'DBG select case I0 1, NbAtFrag=',NbAtFrag(IFrag)
754
     ind_zmat(1,1)=IAt
755
     ind_zmat(2,1)=Liaisons(IAt,1)
756
     ind_zmat(2,2)=IAt
757
     DejaFait(IAt)=.TRUE.
758
     DejaFait(Liaisons(Iat,1))=.TRUE.
759
     IdxCaFaire=2
760
     CaFaire(1)=Liaisons(Iat,1)
761
     CaFaire(2)=0
762
     FCaf(Liaisons(Iat,1))=.TRUE.
763

    
764
! PFL 28 Dec 2007 ->
765
! We do NOT need a fourth atom. So we will look only for a third atom
766
!
767
!!!!
768
!
769
     !     We search for a third and fourth atoms, first in the FrozBlock atoms
770
     !     It should not be possible to have   (FrozBlock(Iat,0).GT.2) and
771
     !     iat linked to only one atom !       
772

    
773

    
774
     !     we calculate the distances between Iat and all other frozen
775
     !     atoms of this fragment, and store only those for which 
776
     !     valence angles are not too close to 0/Pi. (limit:5?)
777

    
778
     ITmp=0
779
     CALL vecteur(Liaisons(Iat,1),IAt,x,y,z,vx2,vy2,vz2,norm2)
780

    
781
! PFL 28 Dec 2007: As MaxL=1 I think that there is at most 2 atoms in this fragment... 
782
! so that the following loop is useless... this should be tested more carefully
783
     DO I=1,NbAtFrag(IFrag)
784
        JAt=FragAt(IFrag,I)
785
        if (.NOT.DejaFait(JAt)) THEN
786
           CALL vecteur(JAt,IAt,x,y,z,vx1,vy1,vz1,norm1)
787
           if (abs(cos(angle(vx1,vy1,vz1,norm1,  &
788
                vx2,vy2,vz2,norm2))).LE.0.996d0) THEN
789
              ITmp=ITmp+1
790
              DistFrag(ITmp)=Norm1
791
              FragDist(ITmp)=JAt
792
           END IF
793
        END IF
794
     END DO
795

    
796
     IF (ITMP.EQ.0) THEN
797
        !     We have no atoms correct in this fragment, we use
798
        !     atoms from other fragments
799
        DO Jat=1,Na
800
! DejaFait(Iat)=.TRUE. so that we do not need to test Jat/=Iat
801
           if (.NOT.DejaFait(JAt)) THEN
802
              CALL vecteur(JAt,IAt,x,y,z,vx1,vy1,vz1,norm1)
803
              if (abs(cos(angle(vx1,vy1,vz1,norm1, &
804
                   vx2,vy2,vz2,norm2))).LE.0.996d0) THEN
805
                 ITmp=ITmp+1
806
                 DistFrag(ITmp)=Norm1
807
                 FragDist(ITmp)=JAt
808
              END IF
809
           END IF
810
        END DO
811
        IF (ITMP.EQ.0) THEN
812
           WRITE(*,*) 'It seems all atoms are aligned'
813
           WRITE(*,*) 'Case non treated for now :-( '
814
           STOP
815
        END IF
816
     END IF
817

    
818
     I1=0
819
     d=1e9
820
! PFL 28 Dec 2007: There exists some F90 intrinsics to find the smallest element of an array.
821
! The following loop should be replaced by it !
822
     DO I=1,ITmp
823
        IF (DistFrag(I).LE.d) THEN
824
           I1=FragDist(I)
825
           d=DistFrag(I)
826
        END IF
827
     END DO
828

    
829
     !     we now have the atom that is closer to the first one and that
830
     !     forms a non 0/Pi valence angle
831
     ind_zmat(3,1)=I1
832
     ind_zmat(3,2)=IAt
833
     ind_zmat(3,3)=Liaisons(Iat,1)
834
     DejaFait(I1)=.TRUE.
835
     CaFaire(2)=I1
836
     FCaf(I1)=.TRUE.
837

    
838

    
839
! PFL 28 Dec 2007 ->
840
! We do NOT need a fourth atom so that the following is suppressed
841
!
842
!     !     we search for a fourth atom !
843
!     !     We search for a fourth atom, first in the FrozBlock atoms
844
!     ITmp=2
845
!     sDihe=0.
846
!     n2=IAt
847
!     n3=Liaisons(Iat,1)
848
!     n4=I1
849
!     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
850
!     CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
851
!     CALL produit_vect(vx3,vy3,vz3, vx2,vy2,vz2,vx5,vy5,vz5,norm5)
852
!
853
!     !     We will look at the other frozen atoms
854
!     !     we might improve the search so as to take the atom closest to IAt
855
!     ITmp=0
856
!     DO I=1,NbAtFrag(IFrag)
857
!        JAt=FragAt(IFrag,I)
858
!        if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
859
!           n1=JAt
860
!           CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
861
!           CALL produit_vect(vx1,vy1,vz1, vx2,vy2,vz2, vx4,vy4,vz4,norm4)
862
!           val_d=angle_d(vx4,vy4,vz4,norm4,  &
863
!                vx5,vy5,vz5,norm5,   &
864
!                vx2,vy2,vz2,norm2)
865
!           if (abs(sin(val_d)).GE.0.09D0) THEN
866
!              ITmp=ITmp+1
867
!              DistFrag(ITmp)=Norm1
868
!              FragDist(ITmp)=JAt
869
!           END IF
870
!        END IF
871
!     END DO
872
!     IF (ITmp.EQ.0) THEN
873
!        !     All dihedral angles between frozen atoms are less than 5?
874
!        !     (or more than 175?). We have to look at other fragments :-(
875
!        DO I=1,NFroz
876
!           Jat=Frozen(I)
877
!           if (.NOT.DejaFait(JAt)) THEN
878
!              n1=JAt
879
!              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
880
!              CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, vx4,vy4,vz4,norm4)
881
!              val_d=angle_d(vx4,vy4,vz4,norm4,   &
882
!                   vx5,vy5,vz5,norm5,           &
883
!                   vx2,vy2,vz2,norm2)
884
!              if (abs(sin(val_d)).GE.0.09D0) THEN
885
!                 ITmp=ITmp+1
886
!                 DistFrag(ITmp)=Norm1
887
!                 FragDist(ITmp)=JAt
888
!              END IF
889
!           END IF
890
!       END DO
891
!        IF (ITmp.EQ.0) THEN
892
!           !     All frozen atoms are in a plane... too bad
893
!           WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
894
!           WRITE(*,*) 'For now, I do not treat this case'
895
!           STOP
896
!        END IF
897
!     END IF                 ! ITmp.EQ.0 after scaning fragment
898
!     I1=0
899
!     d=1e9
900
!     DO I=1,ITmp
901
!        IF (DistFrag(I).LE.d) THEN
902
!           d=DistFrag(I)
903
!           I1=FragDist(I)
904
!        END IF
905
!     END DO
906
!
907
!     !     we now have the atom that is closer to the first one and that
908
!     !     forms a non 0/Pi dihedral angle
909
!     !     ind_zmat(4,1)=I1
910
!     !     ind_zmat(4,2)=IAt
911
!     !     ind_zmat(4,3)=ind_zmat(2,1)
912
!     !     ind_zmat(4,4)=ind_zmat(3,1)
913
!     n3=ind_zmat(2,1)
914
!     n4=ind_zmat(3,1)
915
!     Call add2indzmat(na,4,I1,IAt,n3,n4,ind_zmat,x,y,z)
916
!     ind_zmat(2,1)=n3
917
!     ind_zmat(3,1)=n4
918
!     DejaFait(I1)=.TRUE.
919
!     CaFaire(3)=I1
920
!     CaFaire(4)=0
921
!     IdxCaFaire=4
922
!     izm=4
923
!     FCaf(I1)=.TRUE.
924
!!!!!!!!!!!
925
!
926
! <- PFL 28 Dec 2007
927

    
928
     CaFaire(3)=0
929
   IdxCaFaire=3
930
   
931
  CASE(0)
932
     WRITE(*,*) 'All atoms are separated .. '
933
     WRITE(*,*) 'this case should be treated separately !'
934
     STOP
935
  END SELECT
936

    
937
  if (debug) THEN
938
     WRITE(*,*) 'ind_zmat 1 izm=',izm
939
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
940
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
941
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
942
     DO I=4,izm
943
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
944
             ind_zmat(I,3), ind_zmat(I,4)
945
     END DO
946
  END IF
947

    
948
  DO I=1,izm
949
     Idx_zmat(ind_zmat(I,1))=i
950
  END Do
951

    
952
  !     at least first three atoms of this fragment done...
953
  !     we empty the 'cafaire' array before going on
954
  IAFaire=1
955
  DO WHILE (CaFaire(IaFaire).NE.0)
956
     n1=CaFaire(IaFaire)
957
     n2=ind_zmat(idx_zmat(N1),2)
958
     if (idx_zmat(N1).EQ.2) THEN
959
        !     We have a (small) problem: we have to add atoms linked to the 2nd
960
        !     atom of the zmat. This is a pb because we do not know
961
        !     which atom to use to define the dihedral angle
962
        !     we take the third atom of the zmat
963
        n3=ind_zmat(3,1)
964
     ELSE
965
        n3=ind_zmat(idx_zmat(n1),3)
966
     END IF
967
   
968
   FirstAt=.TRUE.
969
     DO I=1,Liaisons(n1,0)
970
        IAt=Liaisons(n1,I)
971
! PFL 29.Aug.2008 ->
972
! We dissociate the test on 'DejaFait' that indicates that this atom
973
! has already been put in the Zmat
974
! from the test on FCaf that indicates that this atom has been put in the
975
! 'CAFaire' list that deals with identifying its connectivity.
976
! Those two test might differ in some cases.
977
        IF (.NOT.DejaFait(Iat)) THEN
978
           izm=izm+1
979
           if (debug) WRITE(*,*) ">1< Adding atom ",Iat,"position izm=",izm
980
           !           ind_zmat(izm,1)=iat
981
           !           ind_zmat(izm,2)=n1
982
           !           ind_zmat(izm,3)=n2
983
           !           ind_zmat(izm,4)=n3
984
           Call add2indzmat(na,izm,iat,n1,n2,n3,ind_zmat,x,y,z)
985
       if (FirstAt) THEN
986
          n3=Iat
987
        FirstAt=.FALSE.
988
           END IF
989
           idx_zmat(iat)=izm
990
           DejaFait(iat)=.TRUE.
991
        END IF
992
        IF (.NOT.FCaf(Iat)) THEN
993
           CaFaire(IdxCaFaire)=iat
994
           IdxCaFaire=IdxCaFaire+1
995
           CaFaire(IdxCaFaire)=0
996
           FCaf(Iat)=.TRUE.
997
        END IF
998
! <- PFL 29.Aug.2008
999
     END DO
1000
     IaFaire=IaFaire+1
1001
  END Do                    ! DO WHILE CaFaire
1002

    
1003
  if (debug) THEN
1004
     WRITE(*,*) 'ind_zmat 2, izm=',izm
1005
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1006
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1007
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1008
     DO I=4,izm
1009
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
1010
             ind_zmat(I,3), ind_zmat(I,4)
1011
     END DO
1012
  END IF
1013

    
1014
  !     We have finished putting atoms linked to the first one
1015
  ! There should not be any atom left from this fragment. We check:
1016
  !     we will add other atoms of this fragment
1017
  DO I=1,NbAtFrag(IFrag)
1018
     Iat=FragAt(IFrag,I)
1019
     if (debug) WRITE(*,*) "DBG: I,Iat,dejafait",I,Iat,DejaFait(Iat)
1020
     IF (.NOT.DejaFait(Iat)) THEN
1021
           WRITE(*,*) 'Treating atom I,Iat',I,Iat
1022
        
1023
     END IF
1024

    
1025
  END DO
1026

    
1027
  NbAtFrag(Ifrag)=0
1028
  MaxLFrag(IFrag,1)=0
1029
  
1030
  !     we start again with the rest of the molecule...
1031
  ! v 1.01 We add the fragment in the order corresponding to NbAtFrag
1032
  KMax=NbFrag-1
1033

    
1034
  IF (DEBUG) WRITE(*,*) "Adding the ",Kmax," remaining fragments"
1035
  DO K=1, KMax
1036
  IFrag=0
1037
  I0=0
1038
  IAt=0
1039
  I1=0
1040
  DO I=1,NbFrag
1041
    SELECT CASE(MaxLFrag(I,1)-I0)
1042
     CASE (1:)
1043
        IFrag=I
1044
        I0=MaxLFrag(I,1)
1045
        IAt=MaxLFrag(I,2)
1046
        I1=NbAtFrag(I)
1047
     CASE (0)
1048
        if (NbAtFrag(I).GT.I1) THEN
1049
           IFrag=I
1050
           I0=MaxLFrag(I,1)
1051
           IAt=MaxLFrag(I,2)
1052
           I1=NbAtFrag(I)
1053
        END IF
1054
     END SELECT
1055
 
1056
  END DO
1057

    
1058
  if (debug) WRITE(*,'(1X,A,I5,A,I5,A,I5,A,I5)') 'Adding fragment:',IFrag,' with ',I0   &
1059
      ,' max links for atom',IAt,' fragment size',NbAtFrag(IFrag)
1060
    
1061
     MaxLFrag(IFrag,1)=0
1062

    
1063
! We search for the closest atoms of the previous fragments to the atom with max links
1064
  d=1e9
1065
  DO J=1,izm
1066
    Call vecteur(iat,ind_zmat(j,1),x,y,z,vx1,vy1,vz1,norm1)
1067
    if (norm1.le.d) THEN
1068
      Jat=j
1069
      d=norm1
1070
    END IF
1071
  END DO
1072
  n2=ind_zmat(jat,1)
1073
  SELECT CASE(jat)
1074
        CASE (1)
1075
     n3=ind_zmat(2,1)
1076
     n4=ind_zmat(3,1)
1077
    CASE (2)
1078
     n3=ind_zmat(1,1)
1079
     n4=ind_zmat(3,1)
1080
    CASE DEFAULT
1081
     n3=ind_zmat(jAt,2)
1082
     n4=ind_zmat(jat,3)
1083
  END SELECT
1084
  izm=izm+1
1085
  Call add2indzmat(na,izm,iat,n2,n3,n4,ind_zmat,x,y,z)
1086
    idx_zmat(iat)=izm
1087
    DejaFait(iat)=.TRUE.
1088
  IdxCaFaire=2
1089
    CaFaire(1)=iat
1090
              CaFaire(2)=0
1091
              FCaf(Iat)=.TRUE.
1092
              IaFaire=1
1093
              DO WHILE (CaFaire(IaFaire).NE.0)
1094
                 n1=CaFaire(IaFaire)
1095
                 n2=ind_zmat(idx_zmat(N1),2)
1096
                 if (idx_zmat(N1).EQ.2) THEN
1097
                    !     We have a (small) problem: we have to add atoms linked to the 2nd
1098
                    !     atom of the zmat. This is a pb because we do not know
1099
                    !     which atom to use to define the dihedral angle
1100
                    !     we take the third atom of the zmat
1101
                    n3=ind_zmat(3,1)
1102
                 ELSE
1103
                    n3=ind_zmat(idx_zmat(n1),3)
1104
                 END IF
1105
                 DO I3=1,Liaisons(n1,0)
1106
                    IAt=Liaisons(n1,I3)
1107
! PFL 29.Aug.2008 ->
1108
! We dissociate the test on 'DejaFait' that indicates that this atom
1109
! has already been put in the Zmat
1110
! from the test on FCaf that indicates that this atom has been put in the
1111
! 'CAFaire' list that deals with identifying its connectivity.
1112
! Those two test might differ for a frozen atom linked to non frozen atoms.
1113
                    IF (.NOT.DejaFait(Iat)) THEN
1114
                       izm=izm+1
1115
                       Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1116
                       idx_zmat(iat)=izm
1117
                       n3=iat
1118
                       DejaFait(Iat)=.TRUE.
1119
                    END IF
1120
                    IF (.NOT.FCaf(Iat)) THEN
1121
                       CaFaire(IdxCaFaire)=iat
1122
                       IdxCaFaire=IdxCaFaire+1
1123
                       CaFaire(IdxCaFaire)=0
1124
                       FCaf(Iat)=.TRUE.
1125
                    END IF
1126
! <- PFL 29.Aug.2008
1127
                 END DO
1128
                 IaFaire=IaFaire+1
1129
              END Do              ! DO WHILE CaFaire
1130

    
1131
        if (debug) THEN
1132
           WRITE(*,*) 'ind_zmat 4'
1133
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1134
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1135
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1136
           DO Ip=4,izm
1137
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), ind_zmat(Ip,2), &
1138
                   ind_zmat(Ip,3), ind_zmat(Ip,4)
1139
           END DO
1140
        END IF
1141

    
1142
  END DO                    ! Loop on all fragments
1143

    
1144

    
1145
     ! We have ind_zmat. We calculate val_zmat :-)
1146
     if (debug) WRITE(*,*) "Calculating val_zmat"
1147

    
1148
     val_zmat(1,1)=0.d0
1149
     val_zmat(1,2)=0.d0
1150
     val_zmat(1,3)=0.d0
1151
     val_zmat(2,2)=0.d0
1152
     val_zmat(2,3)=0.d0
1153
     val_zmat(3,3)=0.d0
1154

    
1155
     n1=ind_zmat(2,1)
1156
     n2=ind_zmat(2,2)
1157

    
1158
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1159

    
1160
     val_zmat(2,1)=norm1
1161

    
1162

    
1163
     n1=ind_zmat(3,1)
1164
     n2=ind_zmat(3,2)
1165
     n3=ind_zmat(3,3)
1166

    
1167
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1168

    
1169
     val_zmat(3,1)=norm1
1170

    
1171
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
1172
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
1173

    
1174
     val_zmat(3,2)=val
1175

    
1176
     DO i=4,na
1177

    
1178
        n1=ind_zmat(i,1)
1179
        n2=ind_zmat(i,2)
1180
        n3=ind_zmat(i,3)
1181
        n4=ind_zmat(i,4)
1182

    
1183
        if (debug) WRITE(*,*) "Doing i,n1,n2,n3,n4",i,n1,n2,n3,n4
1184
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1185

    
1186
        CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
1187
        val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
1188

    
1189
        CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
1190
        CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2,vx4,vy4,vz4,norm4)
1191
        CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2,vx5,vy5,vz5,norm5)
1192

    
1193
        val_d=angle_d(vx4,vy4,vz4,norm4, vx5,vy5,vz5,norm5, &
1194
             vx2,vy2,vz2,norm2)
1195

    
1196
        !     write(*,11) n1,n2,norm1,n3,val,n4,val_d
1197
        !11   format (2(1x,i3),1x,f8.4,2(1x,i3,1x,f8.3))
1198

    
1199
        val_zmat(i,1)=norm1
1200
        val_zmat(i,2)=val
1201
        val_zmat(i,3)=val_d
1202

    
1203
     END DO
1204

    
1205
     if (debug) THEN
1206
        WRITE(*,*) 'DBG Cre_Zmat_Frag: ind_zmat'
1207
        DO I=1,na
1208
           WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5)
1209
        END DO
1210

    
1211
        WRITE(*,*) 'DBG Cre_Zmat_Frag: Full zmat'
1212
        DO I=1,na
1213
           WRITE(*,'(1X,I5,1X,I5,F8.4,2(1X,I5,1X,F7.2))') ind_zmat(i,1),(ind_zmat(i,j+1),val_zmat(i,j),j=1,3)
1214
        END DO
1215

    
1216
     END IF
1217

    
1218
     if (debugGaussian) THEN
1219
        WRITE(*,*) 'DBG Cre_Zmat_Frag: Gaussian Zmat - START'
1220
        Call WriteMixed_Gaussian(na,atome,LocalNCart,ind_zmat,val_zmat)
1221
        WRITE(*,*) 'DBG Cre_Zmat_Frag: Gaussian Zmat - END'
1222
     END IF
1223

    
1224

    
1225
     if (debug) WRITE(*,*) "Deallocate (FragDist,Fragment, NbAtFrag,FragAt)"
1226
     DEALLOCATE(FragDist,Fragment, NbAtFrag,FragAt)
1227
     if (debug) WRITE(*,*) "Deallocate (DistFrag,Liaisons)"
1228
     DEALLOCATE(DistFrag,Liaisons)
1229
     if (debug) WRITE(*,*) "Deallocate(CaFaire,DejaFait)"
1230
     DEALLOCATE(CaFaire,DejaFait,FCaf,MaxLFrag)
1231
 
1232

    
1233

    
1234
     if (debug) WRITE(*,*) "=============================== Exiting Calc_zmat_frag ========================"
1235

    
1236
END SUBROUTINE Calc_Zmat_frag
1237