Statistiques
| Révision :

root / src / Calc_zmat_frag.f90 @ 6

Historique | Voir | Annoter | Télécharger (41,27 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
  Use Path_module, only : max_Z, NMaxL, Nom,MaxFroz, Pi
35
  Use Io_module
36

    
37
  IMPLICIT NONE
38

    
39
  CHARACTER(5) ::  AtName
40
  integer(KINT), INTENT(IN) ::  na,atome(na)
41
  real(KREAL), INTENT(IN)   ::  x(Na),y(Na),z(Na),fact
42
  real(KREAL), INTENT(IN)   ::  r_cov(0:Max_Z)
43

    
44
  INTEGER(KINT), INTENT(OUT) :: ind_zmat(Na,5)
45
  real(KREAL), INTENT(OUT)   :: val_zmat(Na,3)
46

    
47
  INTEGER(KINT) :: idx_zmat(NA)
48
! Frozen contains the indices of frozen atoms
49
! INTEGER(KINT) Frozen(*),NFroz
50
! Number of fragment, Index of the current fragment for loops
51
  INTEGER(KINT) :: NbFrag,IdxFrag
52
! Fragment(I) contains the fragment index to which I belongs
53
! NbAtFrag(j) contains the number of atoms of fragment j
54
  INTEGER(KINT), ALLOCATABLE :: Fragment(:),NbAtFrag(:) !na
55
! FragAt(i,:) lists the atoms of fragment i
56
  INTEGER(KINT), ALLOCATABLE :: FragAt(:,:) !na,na
57
! MaxLFrag(i,1) contains the maximum of links for an atom for fragment i
58
! MaxLFrag(i,2) is the atom that has this number of linked atoms
59
  INTEGER(KINT), ALLOCATABLE :: MaxLFrag(:,:) !na,2
60
! INTEGER(KINT), ALLOCATABLE :: IdxFragAt(:) !na
61
! INTEGER(KINT), ALLOCATABLE :: FrozBlock(:,:) !(na,0:na)
62
! DistFrag contains the distance between a given atom and some other atoms
63
  REAL(KREAL), ALLOCATABLE :: DistFrag(:) !na
64
! FragDist(I) contains the index of the atoms corresponding to DistFrag(I)
65
  INTEGER(KINT), ALLOCATABLE :: FragDist(:) ! na
66

    
67
  INTEGER(KINT) :: IdxCaFaire, IAfaire
68
  INTEGER(KINT), ALLOCATABLE ::  LIAISONS(:,:) ! (Na,0:NMaxL)
69
! INTEGER(KINT), ALLOCATABLE ::  LiaisonsIni(:,:) ! (Na,0:NMaxL)
70
  INTEGER(KINT), ALLOCATABLE :: CAFaire(:) ! (Na)
71

    
72
  real(KREAL) ::  vx1,vy1,vz1,norm1
73
  real(KREAL) ::  vx2,vy2,vz2,norm2
74
  real(KREAL) ::  vx3,vy3,vz3,norm3
75
  real(KREAL) ::  vx4,vy4,vz4,norm4
76
  real(KREAL) ::  vx5,vy5,vz5,norm5
77
  real(KREAL) ::  val,val_d, d12, d13,d23,d
78
  Logical PasFini,Debug, FirstAt, DebugGaussian
79
  LOGICAL, ALLOCATABLE :: DejaFait(:), FCaf(:) !(na)
80
!  Logical, ALLOCATABLE ::  FrozAt(:)    !T if this atom is frozen
81
  LOGICAL F1213, F1223,F1323
82

    
83
  INTEGER(KINT) :: I,J,n0,n1,n2,n3,n4,IAt,IL,JL,IFrag,ITmp, K, KMax
84
  INTEGER(KINT) :: IMax, I3,I1,Ip, IFragFroz
85
  INTEGER(KINT) :: I0, Izm, JAt,Izm0
86
  INTEGER(KINT) :: OrderZmat
87

    
88
  REAL(KREAL) :: sDihe
89

    
90
  INTERFACE
91
     function valid(string) result (isValid)
92
       CHARACTER(*), intent(in) :: string
93
       logical                  :: isValid
94
     END function VALID
95

    
96
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
97
       INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
98
       real(KREAL) ::  v1x,v1y,v1z,norm1
99
       real(KREAL) ::  v2x,v2y,v2z,norm2
100
       real(KREAL) ::  angle
101
     END FUNCTION ANGLE
102

    
103
     FUNCTION SinAngle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
104
       INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
105
       real(KREAL) ::  v1x,v1y,v1z,norm1
106
       real(KREAL) ::  v2x,v2y,v2z,norm2
107
       real(KREAL) ::  SinAngle
108
     END FUNCTION SINANGLE
109

    
110
     FUNCTION angle_d(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2,v3x,v3y,v3z,norm3)
111
       INTEGER, PARAMETER :: KREAL=KIND(1.0D0)
112
       real(KREAL) ::  v1x,v1y,v1z,norm1
113
       real(KREAL) ::  v2x,v2y,v2z,norm2
114
       real(KREAL) ::  v3x,v3y,v3z,norm3
115
       real(KREAL) ::  angle_d,ca,sa
116
     END FUNCTION ANGLE_D
117
  END INTERFACE
118

    
119
  debug=valid("calc_zmat").OR.valid("calc_zmat_frag")
120
  debugGaussian=valid("zmat_gaussian")
121
  
122
  if (debug) WRITE(*,*) "=============================== Entering Calc_zmat_frag ========================"
123
  if (na.le.2) THEN
124
     WRITE(*,*) "I do not work for less than 2 atoms :-p"
125
     RETURN
126
  END IF
127

    
128
  ALLOCATE(FragDist(Na),Fragment(na), NbAtFrag(na),FragAt(na,na))
129
! ALLOCATE(FrozFrag(na,3), IdxFragAt(na), FrozBlock(na,0:na))
130
! ALLOCATE(FrozFrag(na,3))
131
  ALLOCATE(DistFrag(na),Liaisons(na,0:NMaxL))
132
! ALLOCATE(Liaisons(na,0:NMaxL),LiaisonsIni(na,0:NMaxL))
133
! ALLOCATE(CaFaire(na),DejaFait(Na),FCaf(na),FrozAt(na))
134
  ALLOCATE(CaFaire(na+1),DejaFait(Na),FCaf(na))
135

    
136
  if (debug) THEN
137
     WRITE(*,*) "DBG Calc_zmat_frag - Cartesian coordinates"
138
     DO I=1,na
139
        WRITE(*,'(1X,A3,3(1X,F15.8))') Nom(atome(i)),x(i),y(i),z(i)
140
     END DO
141
  END if
142

    
143
  DO I=1,na
144
     DO J=1,5
145
        Ind_Zmat(I,J)=0
146
     END DO
147
  END DO
148
  
149
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
150
!
151
!     Easy case : 3 or less atoms
152
!
153
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
154
  if (Na.eq.3) THEN
155
     d12=sqrt((x(1)-x(2))**2+(y(1)-y(2))**2+(z(1)-z(2))**2)
156
     d13=sqrt((x(1)-x(3))**2+(y(1)-y(3))**2+(z(1)-z(3))**2)
157
     d23=sqrt((x(3)-x(2))**2+(y(3)-y(2))**2+(z(3)-z(2))**2)
158
     F1213=(d12<=d13)
159
     F1323=(d13<=d23)
160
     F1223=(d12<=d23)
161
     if (debug) THEN
162
        WRITE(*,*) "DEBUG Calc_Zmat 3 atoms"
163
        WRITE(*,*) "d12,d13,d23:",d12,d13,d23
164
        WRITE(*,*) "F1213,F1323,F1223:",F1213,F1323,F1223
165
     END IF
166
     OrderZmat=0
167
     if (F1213) orderZmat=OrderZmat+4
168
     if (F1323) orderZmat=OrderZmat+2
169
     if (F1223) orderZmat=OrderZmat+1
170
     if (debug) WRITE(*,*) 'OrderZmat=',OrderZmat
171
     SELECT CASE (OrderZmat)
172
        CASE (0)
173
! F F F ordre 2-3----1 
174
           ind_zmat(1,1)=3
175
           ind_zmat(2,1)=2
176
           ind_zmat(2,2)=3
177
           ind_zmat(3,1)=1
178
           ind_zmat(3,2)=3
179
           ind_zmat(3,3)=2
180
        CASE (2)
181
! F T F ordre 1-3----2
182
           ind_zmat(1,1)=3
183
           ind_zmat(2,1)=1
184
           ind_zmat(2,2)=3
185
           ind_zmat(3,1)=2
186
           ind_zmat(3,2)=3
187
           ind_zmat(3,3)=1
188
        CASE (3)
189
! F T T ordre 2---1-3
190
           ind_zmat(1,1)=1
191
           ind_zmat(2,1)=3
192
           ind_zmat(2,2)=1
193
           ind_zmat(3,1)=2
194
           ind_zmat(3,2)=1
195
           ind_zmat(3,3)=3
196
        CASE (5)
197
! T F T  ordre 1-2----3
198
           ind_zmat(1,1)=2
199
           ind_zmat(2,1)=1
200
           ind_zmat(2,2)=2
201
           ind_zmat(3,1)=3
202
           ind_zmat(3,2)=2
203
           ind_zmat(3,3)=1
204
        CASE (7)
205
! T T T ordre 3----1-2
206
           ind_zmat(1,1)=1
207
           ind_zmat(2,1)=2
208
           ind_zmat(2,2)=1
209
           ind_zmat(3,1)=3
210
           ind_zmat(3,2)=1
211
           ind_zmat(3,3)=2
212
        END SELECT
213

    
214
     IF (debug) THEN
215
        WRITE(*,*) "DBG Calc_zmat_frag - Nat=3 -"
216
        DO i=1,na
217
           WRITE(*,'(1X,A3,5(1X,I5))') Nom(Atome(ind_zmat(i,1))),(ind_zmat(i,j),j=1,5)
218
        END DO
219
     END IF
220

    
221
     ! We have ind_zmat, we fill val_zmat
222
     val_zmat=0.d0
223
     n2=ind_zmat(2,1)
224
     n1=ind_zmat(2,2)
225
     d=sqrt((x(n1)-x(n2))**2+(y(n1)-y(n2))**2+(z(n1)-z(n2))**2)
226
     val_zmat(2,1)=d
227
     n1=ind_zmat(3,1)
228
     n2=ind_zmat(3,2)
229
     n3=ind_zmat(3,3)
230
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
231
     if (debug) write(*,*) n1,n2,norm1
232
     val_zmat(3,1)=norm1
233

    
234
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
235
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
236
     if (debug) write(*,*) n2,n3,norm2,val
237
     val_zmat(3,2)=val
238

    
239
     RETURN
240
  END IF !matches if (Na.eq.3) THEN
241
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
242
!
243
!  End of Easy case : 3 or less atoms
244
!
245
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
246
!
247
! General Case 
248
!
249
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
250
!
251

    
252
! Initialization
253
  DejaFait=.False.
254
  Liaisons=0
255
  ind_zmat=0
256
  val_zmat=0.d0
257

    
258
  if (debug) WRITE(*,*) "Coucou from Calc_zmat_frag.f90; L240"
259
  
260
  if (debug) THEN
261
     WRITE(*,*) "Bonds initialized"
262
     WRITE(*,*) 'Covalent radii used'
263
     DO iat=1,na
264
        i=atome(iat)
265
        WRITE(*,*) Nom(I),Iat,r_cov(i),r_cov(i)*fact
266
     END DO
267
  END IF
268

    
269
1003 FORMAT(1X,I4,' - ',25(I5))
270

    
271
!   First step : connectivity  are calculated
272

    
273
  Call CalcCnct(na,atome,x,y,z,LIAISONS,r_cov,fact)
274

    
275
  if (debug) THEN
276
     WRITE(*,*) "Connections calculated"
277
     DO IL=1,na
278
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
279
     END DO
280
  END IF
281

    
282
  FCaf=.TRUE.
283
  Call Decomp_frag(na,liaisons,FCaf,nbfrag,Fragment,NbAtFrag,FragAt)
284
  
285
  IF (debug) THEN
286
     WRITE(*,*) 'I found ',NbFrag, 'fragments'
287
     WRITE(*,*) (NbAtFrag(I),I=1,NbFrag)
288
     DO I=1,NbFrag
289
        WRITE(*,*) NbAtFrag(I)
290
        WRITE(*,*) 'Fragment ', i
291
        DO J=1,Na
292
           IF (Fragment(J).EQ.I) WRITE(*,'(1X,I3,1X,A5,3(1X,F10.6))') J,Nom(Atome(J)) &
293
                ,X(J),Y(J),Z(J)
294
        END DO
295
        WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
296
     END DO
297
  END IF
298

    
299
 ALLOCATE(MaxLFrag(NbFrag,2))
300

    
301
 MaxLFrag=0
302

    
303
  DO I=1,NbFrag
304
     MaxLFrag(I,1)=Liaisons(FragAt(I,1),0)
305
     MaxLFrag(I,2)=FragAt(I,1)
306

    
307
     DO J=1,NbAtFrag(I)
308
      Iat=FragAt(I,J)
309
        IF (Liaisons(IAt,0).GT.MaxLFrag(I,1)) THEN
310
       MaxLFrag(I,1)=Liaisons(Iat,0)
311
       MaxLFrag(I,2)=Iat
312
    END IF
313
     END DO
314
     IF (debug) WRITE(*,*) 'Frag :',I,', atom ',MaxLFrag(I,2), ' has ',MaxLFrag(I,2),' links'
315
  END DO
316

    
317
  !     We will now build the molecule fragment by fragment
318
  !     We choose the starting fragment with two criteria:
319
  !     1- Number of linked atoms:
320
  !       * >=3 is good as it fully defines the coordinate space
321
  !       * 2 is ok as we can either use a 3rd atom from the same fragment
322
  !       or add a X atom somewhere but this complicates quite a lot the way
323
  !       to treat the conversion from cartesian to zmat latter
324
  !       * 1 is bad...
325
  !     2- Size of the fragment
326
  !     this allows us to deal more easily with cases 1- when number of 
327
  !     directly linked atoms is less than 3
328

    
329
  IFrag=0
330
! I0 is the number of connections of the best fragment
331
  I0=0
332
! I1 is the number of atoms of the best fragment
333
  I1=0
334
  IAt=0
335
  DO I=1,NbFrag
336
    SELECT CASE(MaxLFrag(I,1)-I0)
337
     CASE (1:)
338
        IFrag=I
339
        I0=MaxLFrag(I,1)
340
        I1=NbAtFrag(I)
341
        IAt=MaxLFrag(I,2)
342
     CASE (0)
343
        if (NbAtFrag(I).GT.I1) THEN
344
           IFrag=I
345
           I0=MaxLFrag(I,1)
346
           I1=NbAtFrag(I)
347
           IAt=MaxLFrag(I,2)
348
        END IF
349
     END SELECT
350
  END DO
351

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

    
355
  !     We will build the first fragment in a special way, as it will
356
  !     set the coordinates system
357

    
358
  if (debug) WRITE(*,*) 'Fragment 1, starting with atom:',IAt, &   
359
    'with ',I0,' connections'
360

    
361
  DejaFait=.FALSE.
362
  FCaf=.FALSE.
363
  
364
  izm=0
365
  SELECT CASE (I0)
366
  CASE(3:)
367
     if (debug) WRITE(*,*) 'DBG select case I0 3'
368
     n0=Iat
369

    
370
     ITmp=2
371
     sDihe=0.
372
     n2=IAt
373
     n3=Liaisons(Iat,1)
374
     ! We search for the third atom while making sure that it is not aligned with first two !
375
     DO While ((ITmp.LE.Liaisons(Iat,0)).AND.(sDihe.LE.0.09d0))
376
        n4=Liaisons(Iat,Itmp)
377
        CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
378
        CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
379
        val_d=angle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
380
        sDiHe=abs(sin(val_d*pi/180.d0))
381
        if (debug) Write(*,*) 'Trying n2,n3,n4,sdihe,val_d',n2,n3,n4,sdihe,val_d
382
        Itmp=Itmp+1
383
     END DO
384
     If (debug) WRITE(*,*) 'Itmp,Liaisons',Itmp,Liaisons(Iat,1:NMaxL)
385
     Liaisons(Iat,Itmp-1)=Liaisons(iat,2)
386
     Liaisons(Iat,2)=n4
387
     If (debug) WRITE(*,*) 'Itmp,Liaisons',Itmp,Liaisons(Iat,1:NMaxL)
388

    
389
     if (sDihe.LE.0.09d0) THEN
390
        WRITE(*,*) "PROBLEM !!! All atoms linked to ",n0," are aligned..."
391
    WRITE(*,*) "Surprising as this atom has at least three bonds... For NOW STOP"
392
    STOP
393
     END IF
394

    
395
     CALL produit_vect(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2, &
396
          vx5,vy5,vz5,norm5)
397

    
398

    
399
! We search for the fourth atom while checking that it is not aligned with 1st and 2nd atoms.
400
     Itmp=3
401
     sDiHe=0.
402
! PFL 28 Dec 2007 ->
403
! I had a test on the dihedral angle, but I cannot see why it is important to have
404
! a non planar fragment at the begining... ethylene works and is fully planar
405
! I thus suppress this test
406
!
407
!     DO While ((ITmp.LE.Liaisons(Iat,0)).AND.(sDihe.LE.0.09d0))
408
!        ITmp=ITmp+1
409
        n1=Liaisons(Iat,Itmp)
410
        if (debug) WRITe(*,*) 'trying n1,n2,n3,n4',n1,n2,n3,n4
411
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
412
        ! Is this atom aligned with n2-n3 ?
413
        val_d=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
414
        sDiHe=abs(sin(val_d*pi/180.d0))
415
        if (debug) Write(*,*) 'Angle n3-n2-n1',val_d
416
        if (sDiHe.le.0.09d0) THEN
417
           ! As atoms n2,n3 and n4 are not aligned, we interchange n3 and n4 so that n1,n2 and n3 are not aligned
418
           if (debug) WRITE(*,*) "n3-n2-n1 aligned, we interchange n3 and n4"
419
           n1=n3
420
           n3=n4
421
           n4=n1
422
           n1=Liaisons(Iat,ITmp)
423
           CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)           
424
           CALL vecteur(n2,n4,x,y,z,vx3,vy3,vz3,norm3)           
425
           val_d=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
426
           if (debug) Write(*,*) 'NEW Angle n3-n2-n1',val_d
427
        END IF
428

    
429
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
430
        ! avant de tester l'angle diedre, il faut verifier que ce 4e atome n'est pas
431
        ! aligne avec les 2 premiers. 
432
        ! comme on a deja test? que les 3 premiers ne sont pas alignes,
433
        ! s'il est align? avec les 2 premiers, on peut inverser le role de 2 et 3.
434
        ! On pourrait tout simplier en faisant une bete recherche parmi tous les atomes geles
435
        ! de ce bloc (au moins 4 ?) avec le critere 1) on les range par distance croissante
436
        ! 2) on les scanne tant que l'angle valence n'est pas bon, puis tant que diehedre pas bon
437
        ! on pourrait comme ca faire un tableau avec les atomes ranges d'abord pour le fragment s?lectionn?
438
        ! puis les atomes des autres fragment par distance croissante.
439
        ! les autres fragments ne seraient additonn?s que si l'on ne trouve pas notre bonheur dans le premier bloc
440
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
441

    
442
        CALL produit_vect(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2, &
443
             vx4,vy4,vz4,norm4)
444
        val_d=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
445
             vx2,vy2,vz2,norm2)
446
        sDihe=abs(sin(val_d*pi/180.d0))
447
        if (debug) WRITE(*,*) 'n2,n3,n4,n1, angle_d',n2,n3,n4,n1,val_d
448
!     END DO
449

    
450
     DejaFait(n2)=.TRUE.
451
     DejaFait(n3)=.TRUE.
452
     DejaFait(n4)=.TRUE.
453

    
454
!     if (sDihe.LE.0.09d0) THEN
455
!        !     None of the atoms linked to IAt are good to define the third
456
!        !     direction in space...
457
!        !     We will look at the other atoms
458
!        !     we might improve the search so as to take the atom closest to IAt
459
!        if (debug) WRITE(*,*) "All atoms linked to ",Iat," are in a plane. Looking for other atoms"
460
!        ITmp=0
461
!        DO I=1,NbAtFrag(IFrag)
462
!           JAt=FragAt(IFrag,I)
463
!           if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
464
!              n1=JAt
465
!              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
466
!              CALL produit_vect(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2, &
467
!                   vx4,vy4,vz4,norm4)
468
!              val_d=angle_d(vx4,vy4,vz4,norm4, &
469
!                   vx5,vy5,vz5,norm5, &
470
!                   vx2,vy2,vz2,norm2)
471
!              if (abs(sin(val_d)).GE.0.09D0) THEN
472
!                 ITmp=ITmp+1
473
!                 DistFrag(ITmp)=Norm1
474
!                 FragDist(ITmp)=JAt
475
!              END IF
476
!           END IF
477
!        END DO
478

    
479
!        IF (ITmp.EQ.0) THEN
480
!           !     All dihedral angles between frozen atoms are less than 5?
481
!           !     (or more than 175?). We have to look at other fragments :-(
482
!           DO I=1,NFroz
483
!              Jat=Frozen(I)
484
!              if (.NOT.DejaFait(JAt)) THEN
485
!                 n1=JAt
486
!                 CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
487
!                 CALL produit_vect(vx1,vy1,vz1,norm1, &
488
!                      vx2,vy2,vz2,norm2, &
489
!                      vx4,vy4,vz4,norm4)
490
!                 val_d=angle_d(vx4,vy4,vz4,norm4, &
491
!                      vx5,vy5,vz5,norm5, &
492
!                      vx2,vy2,vz2,norm2)
493
!                 if (abs(sin(val_d)).GE.0.09D0) THEN
494
!                    ITmp=ITmp+1
495
!                    DistFrag(ITmp)=Norm1
496
!                    FragDist(ITmp)=JAt
497
!                 END IF
498
!              END IF
499
!           END DO
500
!           IF (ITmp.EQ.0) THEN
501
!              !     All frozen atoms are in a plane... too bad
502
!              WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
503
!              WRITE(*,*) 'For now, I do not treat this case'
504
!              STOP
505
!           END IF
506
!        END IF
507
!        I1=0
508
!        d=1e9
509
!        DO I=1,ITmp
510
!           IF (DistFrag(I).LE.d) THEN
511
!              d=DistFrag(I)
512
!              I1=FragDist(I)
513
!           END IF
514
!        END DO
515
!     ELSE                !(sDihe.LE.0.09d0)
516
!        I1=FrozBlock(IAt,ITmp)
517
!        if (debug) WRITE(*,*) 'I1,n1:',I1,n1
518
!     END IF                 !(sDihe.LE.0.09d0)
519
!     !     we now have the atom that is closer to the first one and that
520
!     !     forms a non 0/Pi dihedral angle
521
!
522
!  <- PFL 28 Dec 2007
523

    
524
! We construct the begining of the Z-Matrix
525

    
526
     ind_zmat(1,1)=n2
527
     ind_zmat(2,1)=n3
528
     ind_zmat(2,2)=n2
529
     ind_zmat(3,1)=n4
530
     ind_zmat(3,2)=n2
531
     ind_zmat(3,3)=n3
532
     DejaFait(n2)=.TRUE.
533
     DejaFait(n3)=.TRUE.
534
     DejaFait(n4)=.TRUE.
535
     CaFaire(1)=n3
536
     CaFaire(2)=n4
537

    
538
! PFL 28 Dec 2007
539
! We have not selected a fourth atom, so that the following is not needed
540
!     ind_zmat(4,1)=I1
541
!     ind_zmat(4,2)=n2
542
!     ind_zmat(4,3)=n3
543
!     ind_zmat(4,4)=n4
544
!     DejaFait(I1)=.TRUE.
545
!     CaFaire(3)=I1
546
!     CaFaire(4)=0
547
!     IdxCaFaire=4
548
!     izm=4
549
!     FCaf(I1)=.TRUE.
550
!!!!!!!
551
! and replaced by:
552
     CaFaire(3)=0
553
   IdxCaFaire=3
554
   izm=3
555
!
556
! <- PFL 28 Dec 2007
557
   
558
     FCaf(n2)=.TRUE.
559
     FCaf(n3)=.TRUE.
560
   FirstAt=.TRUE.
561
     DO I=3,Liaisons(Iat,0)
562
        IF (.NOT.DejaFait(Liaisons(Iat,I))) THEN
563
           izm=izm+1
564
           !           ind_zmat(izm,1)=Liaisons(Iat,I)
565
           !           ind_zmat(izm,2)=n2
566
           !           ind_zmat(izm,3)=n3
567
           !           ind_zmat(izm,4)=n4
568
           Call add2indzmat(na,izm,Liaisons(Iat,I),n2,n3,n4,ind_zmat,x,y,z)
569
           if (FirstAt) THEN
570
           n4=Liaisons(Iat,I)
571
         FirstAt=.FALSE.
572
       END IF
573
           IF (.NOT.FCaf(Liaisons(Iat,I))) THEN
574
              CaFaire(IdxCaFaire)=Liaisons(Iat,I)
575
              IdxCaFaire=IdxCaFaire+1
576
              CaFaire(IdxCaFaire)=0
577
              FCaf(Liaisons(Iat,I))=.TRUE.
578
           END IF
579
           DejaFait(Liaisons(Iat,I))=.TRUE.
580
        END IF
581
     END DO
582

    
583
     if (debug) THEN
584
        WRITE(*,*) "Ind_zmat 0 - SELECT CASE I0 3: -- izm=",izm
585
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
586
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
587
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
588
        DO I=4,izm
589
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
590
                ind_zmat(I,3), ind_zmat(I,4)
591
        END DO
592
     END IF
593

    
594

    
595
     !     First four atoms (at least) have been put we go on with next parts
596
     !     of this fragment... later
597

    
598

    
599
  CASE(2)
600
     if (debug) WRITE(*,*) 'DBG select case I0 2'
601
   WRITE(*,*) "PFL 28 Dec 2007: No test of alignment here :(  TO DO TO DO TO DO"
602
     ind_zmat(1,1)=IAt
603
     ind_zmat(2,1)=Liaisons(IAt,1)
604
     ind_zmat(2,2)=IAt
605
     ind_zmat(3,1)=Liaisons(IAt,2)
606
     ind_zmat(3,2)=IAt
607
     ind_zmat(3,3)=Liaisons(IAt,1)
608
     DejaFait(IAt)=.TRUE.
609
     DejaFait(Liaisons(Iat,1))=.TRUE.
610
     DejaFait(Liaisons(Iat,2))=.TRUE.
611
     CaFaire(1)=Liaisons(Iat,1)
612
     CaFaire(2)=Liaisons(Iat,2)
613
     FCaf(Liaisons(Iat,1))=.TRUE.
614
     FCaf(Liaisons(Iat,2))=.TRUE.
615

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

    
730
     CaFaire(3)=0
731
     IdxCaFaire=3
732
     izm=3
733

    
734
  CASE(1)
735
     if (debug) WRITE(*,*) 'DBG select case I0 1, NbAtFrag=',NbAtFrag(IFrag)
736
     ind_zmat(1,1)=IAt
737
     ind_zmat(2,1)=Liaisons(IAt,1)
738
     ind_zmat(2,2)=IAt
739
     DejaFait(IAt)=.TRUE.
740
     DejaFait(Liaisons(Iat,1))=.TRUE.
741
     IdxCaFaire=2
742
     CaFaire(1)=Liaisons(Iat,1)
743
     CaFaire(2)=0
744
     FCaf(Liaisons(Iat,1))=.TRUE.
745

    
746
! PFL 28 Dec 2007 ->
747
! We do NOT need a fourth atom. So we will look only for a third atom
748
!
749
!!!!
750
!
751
     !     We search for a third and fourth atoms, first in the FrozBlock atoms
752
     !     It should not be possible to have   (FrozBlock(Iat,0).GT.2) and
753
     !     iat linked to only one atom !       
754

    
755

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

    
760
     ITmp=0
761
     CALL vecteur(Liaisons(Iat,1),IAt,x,y,z,vx2,vy2,vz2,norm2)
762

    
763
! PFL 28 Dec 2007: As MaxL=1 I think that there is at most 2 atoms in this fragment... 
764
! so that the following loop is useless... this should be tested more carefully
765
     DO I=1,NbAtFrag(IFrag)
766
        JAt=FragAt(IFrag,I)
767
        if (.NOT.DejaFait(JAt)) THEN
768
           CALL vecteur(JAt,IAt,x,y,z,vx1,vy1,vz1,norm1)
769
           if (abs(cos(angle(vx1,vy1,vz1,norm1,  &
770
                vx2,vy2,vz2,norm2))).LE.0.996d0) THEN
771
              ITmp=ITmp+1
772
              DistFrag(ITmp)=Norm1
773
              FragDist(ITmp)=JAt
774
           END IF
775
        END IF
776
     END DO
777

    
778
     IF (ITMP.EQ.0) THEN
779
        !     We have no atoms correct in this fragment, we use
780
        !     atoms from other fragments
781
        DO Jat=1,Na
782
! DejaFait(Iat)=.TRUE. so that we do not need to test Jat/=Iat
783
           if (.NOT.DejaFait(JAt)) THEN
784
              CALL vecteur(JAt,IAt,x,y,z,vx1,vy1,vz1,norm1)
785
              if (abs(cos(angle(vx1,vy1,vz1,norm1, &
786
                   vx2,vy2,vz2,norm2))).LE.0.996d0) THEN
787
                 ITmp=ITmp+1
788
                 DistFrag(ITmp)=Norm1
789
                 FragDist(ITmp)=JAt
790
              END IF
791
           END IF
792
        END DO
793
        IF (ITMP.EQ.0) THEN
794
           WRITE(*,*) 'It seems all atoms are aligned'
795
           WRITE(*,*) 'Case non treated for now :-( '
796
           STOP
797
        END IF
798
     END IF
799

    
800
     I1=0
801
     d=1e9
802
! PFL 28 Dec 2007: There exists some F90 intrinsics to find the smallest element of an array.
803
! The following loop should be replaced by it !
804
     DO I=1,ITmp
805
        IF (DistFrag(I).LE.d) THEN
806
           I1=FragDist(I)
807
           d=DistFrag(I)
808
        END IF
809
     END DO
810

    
811
     !     we now have the atom that is closer to the first one and that
812
     !     forms a non 0/Pi valence angle
813
     ind_zmat(3,1)=I1
814
     ind_zmat(3,2)=IAt
815
     ind_zmat(3,3)=Liaisons(Iat,1)
816
     DejaFait(I1)=.TRUE.
817
     CaFaire(2)=I1
818
     FCaf(I1)=.TRUE.
819

    
820

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

    
916
     CaFaire(3)=0
917
   IdxCaFaire=3
918
   
919
  CASE(0)
920
     WRITE(*,*) 'All atoms are separated .. '
921
     WRITE(*,*) 'this case should be treated separately !'
922
     STOP
923
  END SELECT
924

    
925
  if (debug) THEN
926
     WRITE(*,*) 'ind_zmat 1 izm=',izm
927
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
928
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
929
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
930
     DO I=4,izm
931
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
932
             ind_zmat(I,3), ind_zmat(I,4)
933
     END DO
934
  END IF
935

    
936
  DO I=1,izm
937
     Idx_zmat(ind_zmat(I,1))=i
938
  END Do
939

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

    
991
  if (debug) THEN
992
     WRITE(*,*) 'ind_zmat 2, izm=',izm
993
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
994
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
995
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
996
     DO I=4,izm
997
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
998
             ind_zmat(I,3), ind_zmat(I,4)
999
     END DO
1000
  END IF
1001

    
1002
  !     We have finished putting atoms linked to the first one
1003
  ! There should not be any atom left from this fragment. We check:
1004
  !     we will add other atoms of this fragment
1005
  DO I=1,NbAtFrag(IFrag)
1006
     Iat=FragAt(IFrag,I)
1007
     if (debug) WRITE(*,*) "DBG: I,Iat,dejafait",I,Iat,DejaFait(Iat)
1008
     IF (.NOT.DejaFait(Iat)) THEN
1009
           WRITE(*,*) 'Treating atom I,Iat',I,Iat
1010
        
1011
     END IF
1012

    
1013
  END DO
1014

    
1015
  NbAtFrag(Ifrag)=0
1016
  MaxLFrag(IFrag,1)=0
1017
  
1018
  !     we start again with the rest of the molecule...
1019
  ! v 1.01 We add the fragment in the order corresponding to NbAtFrag
1020
  KMax=NbFrag-1
1021

    
1022
  IF (DEBUG) WRITE(*,*) "Adding the ",Kmax," remaining fragments"
1023
  DO K=1, KMax
1024
  IFrag=0
1025
  I0=0
1026
  IAt=0
1027
  I1=0
1028
  DO I=1,NbFrag
1029
    SELECT CASE(MaxLFrag(I,1)-I0)
1030
     CASE (1:)
1031
        IFrag=I
1032
        I0=MaxLFrag(I,1)
1033
        IAt=MaxLFrag(I,2)
1034
        I1=NbAtFrag(I)
1035
     CASE (0)
1036
        if (NbAtFrag(I).GT.I1) THEN
1037
           IFrag=I
1038
           I0=MaxLFrag(I,1)
1039
           IAt=MaxLFrag(I,2)
1040
           I1=NbAtFrag(I)
1041
        END IF
1042
     END SELECT
1043
 
1044
  END DO
1045

    
1046
  if (debug) WRITE(*,'(1X,A,I5,A,I5,A,I5,A,I5)') 'Adding fragment:',IFrag,' with ',I0   &
1047
      ,' max links for atom',IAt,' fragment size',NbAtFrag(IFrag)
1048
    
1049
     MaxLFrag(IFrag,1)=0
1050

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

    
1119
        if (debug) THEN
1120
           WRITE(*,*) 'ind_zmat 4'
1121
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1122
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1123
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1124
           DO Ip=4,izm
1125
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), ind_zmat(Ip,2), &
1126
                   ind_zmat(Ip,3), ind_zmat(Ip,4)
1127
           END DO
1128
        END IF
1129

    
1130
  END DO                    ! Loop on all fragments
1131

    
1132

    
1133
     ! We have ind_zmat. We calculate val_zmat :-)
1134
     if (debug) WRITE(*,*) "Calculating val_zmat"
1135

    
1136
     val_zmat(1,1)=0.d0
1137
     val_zmat(1,2)=0.d0
1138
     val_zmat(1,3)=0.d0
1139
     val_zmat(2,2)=0.d0
1140
     val_zmat(2,3)=0.d0
1141
     val_zmat(3,3)=0.d0
1142

    
1143
     n1=ind_zmat(2,1)
1144
     n2=ind_zmat(2,2)
1145

    
1146
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1147

    
1148
     val_zmat(2,1)=norm1
1149

    
1150

    
1151
     n1=ind_zmat(3,1)
1152
     n2=ind_zmat(3,2)
1153
     n3=ind_zmat(3,3)
1154

    
1155
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1156

    
1157
     val_zmat(3,1)=norm1
1158

    
1159
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
1160
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
1161

    
1162
     val_zmat(3,2)=val
1163

    
1164
     DO i=4,na
1165

    
1166
        n1=ind_zmat(i,1)
1167
        n2=ind_zmat(i,2)
1168
        n3=ind_zmat(i,3)
1169
        n4=ind_zmat(i,4)
1170

    
1171
        if (debug) WRITE(*,*) "Doing i,n1,n2,n3,n4",i,n1,n2,n3,n4
1172
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1173

    
1174
        CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
1175
        val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
1176

    
1177
        CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
1178
        CALL produit_vect(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2, &
1179
             vx4,vy4,vz4,norm4)
1180
        CALL produit_vect(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2, &
1181
             vx5,vy5,vz5,norm5)
1182

    
1183
        val_d=angle_d(vx4,vy4,vz4,norm4, vx5,vy5,vz5,norm5, &
1184
             vx2,vy2,vz2,norm2)
1185

    
1186
        !     write(*,11) n1,n2,norm1,n3,val,n4,val_d
1187
        !11   format (2(1x,i3),1x,f8.4,2(1x,i3,1x,f8.3))
1188

    
1189
        val_zmat(i,1)=norm1
1190
        val_zmat(i,2)=val
1191
        val_zmat(i,3)=val_d
1192

    
1193
     END DO
1194

    
1195
     if (debug) THEN
1196
        WRITE(*,*) 'DBG Cre_Zmat_Frag: ind_zmat'
1197
        DO I=1,na
1198
           WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5)
1199
        END DO
1200

    
1201
        WRITE(*,*) 'DBG Cre_Zmat_Frag: Full zmat'
1202
        DO I=1,na
1203
           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)
1204
        END DO
1205

    
1206
     END IF
1207

    
1208
     if (debugGaussian) THEN
1209
        WRITE(*,*) 'DBG Cre_Zmat_Frag: Gaussian Zmat - START'
1210
        Call zmat_g92(na,atome,ind_zmat,val_zmat)
1211
        WRITE(*,*) 'DBG Cre_Zmat_Frag: Gaussian Zmat - END'
1212
     END IF
1213

    
1214

    
1215
     if (debug) WRITE(*,*) "Deallocate (FragDist,Fragment, NbAtFrag,FragAt)"
1216
     DEALLOCATE(FragDist,Fragment, NbAtFrag,FragAt)
1217
     if (debug) WRITE(*,*) "Deallocate (DistFrag,Liaisons)"
1218
     DEALLOCATE(DistFrag,Liaisons)
1219
     if (debug) WRITE(*,*) "Deallocate(CaFaire,DejaFait)"
1220
     DEALLOCATE(CaFaire,DejaFait,FCaf,MaxLFrag)
1221
 
1222

    
1223

    
1224
     if (debug) WRITE(*,*) "=============================== Exiting Calc_zmat_frag ========================"
1225

    
1226
END SUBROUTINE Calc_Zmat_frag
1227

    
1228
SUBROUTINE zmat_g92(na,atome,ind_zmat,val_zmat)
1229

    
1230
! This subroutine comes for Cart. Slightly modified to be f90
1231

    
1232
  Use Path_module, only : max_Z, NMaxL, Nom,MaxFroz, Pi
1233
  Use Io_module
1234

    
1235
  IMPLICIT NONE
1236

    
1237
  integer(KINT), INTENT(IN) ::  na,atome(na)
1238
  INTEGER(KINT), INTENT(IN) :: ind_zmat(Na,5)
1239
  real(KREAL), INTENT(IN)   :: val_zmat(Na,3)
1240

    
1241
  character(6) :: at1,at2,at3,at4,at5,d,a,dh
1242
  character(SCHARS), ALLOCATABLE :: tab(:) ! 3*na
1243
  character(LCHARS) :: ligne
1244
  
1245
  INTEGER(KINT) :: i,n1,n2,n3,n4
1246

    
1247
  ALLOCATE(tab(3*na))
1248

    
1249
  DO i=1,na
1250
     IF (i .GE. 1)  THEN
1251
        n1=ind_zmat(i,1)
1252
        write(at1,11) nom(atome(n1)),n1
1253
11      format(a2,i3)
1254
        Call ecris_sb(at1,at1)
1255
        write(ligne,4) at1
1256
     END IF
1257
     IF (i .GE. 2)  THEN
1258
        n2=ind_zmat(i,2)
1259
        write(at2,11) nom(atome(n2)),n2
1260
        Call ecris_sb(At2,at2)
1261
        write(d,11) 'R',i-1
1262
        Call ecris_sb(D,d)
1263
        write(ligne,4) at1,at2,d
1264
        write(tab(i-1),12) d,val_zmat(i,1)
1265
12      format(a8,f8.4)
1266
     END IF
1267
     IF (i .GE. 3)  THEN
1268
        n3=ind_zmat(i,3)
1269
        write(at3,11) nom(atome(n3)),n3
1270
        Call ecris_sb(At3,at3)
1271
        write(a,11) 'A',na+i-3
1272
        Call ecris_sb(A,A)
1273
        write(ligne,4) at1,at2,d,at3,a
1274
           write(tab(na+i-3),13) a,val_zmat(i,2)
1275
13         format(a8,f8.3)
1276
        END IF
1277
        IF (i .GE. 4)  THEN
1278
           n4=ind_zmat(i,4)
1279
           write(at4,11) nom(atome(n4)),n4
1280
           Call ecris_sb(At4,at4)
1281
           write(dh,11) 'DH',na+na+i-6
1282
           Call ecris_sb(dh,dh)
1283
           write(ligne,4) at1,at2,d,at3,a,at4,dh
1284
4          format(7a6)
1285
           write(tab(na+na+i-6),13) dh,val_zmat(i,3)
1286
        END IF
1287
        write(IOOUT,*) TRIM(ligne)
1288
     END DO
1289
     
1290
     write(IOOUT,*)
1291
     IF (na .EQ. 2) THEN
1292
        write(IOOUT,*) TRIM(tab(1))
1293
     ELSE
1294
        DO i=1,3*na-6
1295
           write(IOOUT,*) TRIM(tab(i))
1296
        END DO
1297
     END IF
1298
     write(IOOUT,*)
1299

    
1300
     DEALLOCATE(Tab)
1301

    
1302
   END SUBROUTINE zmat_g92
1303

    
1304
   SUBROUTINE ecris_sb(inter1,inter)
1305

    
1306
      character(6) :: inter,inter1
1307

    
1308

    
1309
      k=1
1310
      DO j=1,len(inter)
1311
        IF (inter(j:j) .NE. ' ' ) THEN
1312
         inter1(k:k)=inter(j:j)
1313
         k=k+1
1314
        END IF
1315
      END DO
1316

    
1317
       inter1(k:6)=' '
1318

    
1319
    END SUBROUTINE ecris_sb