Statistiques
| Révision :

root / src / Calc_mixed_frag.f90 @ 4

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

1
SUBROUTINE Calc_mixed_frag(na,atome,ind_zmat,val_zmat,x,y,z, &
2
     r_cov,fact,frozen,cart,ncart)
3

    
4
  !     
5
  !     This second version enables the user to freeze some atoms
6
  !     the frozen atoms indices are listed in the frozen array.
7
  !     
8
  !     The idea is surely too stupid to work all the time... but here it is
9
  !     we first construct the zmat using only the frozen atoms, and then
10
  !     we add the other atoms on top of the first ones...
11
  !     
12
  Use Path_module, only : max_Z, NMaxL, Nom,MaxFroz
13
  Use Io_module
14

    
15
  IMPLICIT NONE
16

    
17
  CHARACTER(5) :: AtName
18
  integer(KINT) ::  na,atome(na),ind_zmat(Na,5)
19
  INTEGER(KINT) ::  idx_zmat(NA)
20
  real(KREAL) ::  x(Na),y(Na),z(Na),fact
21
  real(KREAL) ::  val_zmat(Na,3)
22
  real(KREAL) ::  r_cov(0:Max_Z)
23

    
24
  !     Frozen contains the indices of frozen atoms
25
  INTEGER(KINT) Frozen(*),Cart(*),NFroz,NCart
26
  LOGICAL, ALLOCATABLE :: FCart(:) ! Na
27
  INTEGER(KINT), ALLOCATABLE :: AtCart(:) !Na
28
  INTEGER(KINT), ALLOCATABLE :: FrozDist(:) ! na
29
  INTEGER(KINT) NbFrag,IdxFrag
30
  INTEGER(KINT), ALLOCATABLE :: Fragment(:),NbAtFrag(:) !na
31
  INTEGER(KINT), ALLOCATABLE :: FragAt(:,:) !na,na
32
  INTEGER(KINT), ALLOCATABLE :: FrozFrag(:,:) !na,3
33
  !  INTEGER(KINT), ALLOCATABLE :: IdxFragAt(:) !na
34
  INTEGER(KINT), ALLOCATABLE :: FrozBlock(:,:) !(na,0:na)
35
  REAL(KREAL), ALLOCATABLE :: DistFroz(:) !na
36

    
37
  INTEGER(KINT) :: IdxCaFaire, IAfaire
38
  INTEGER(KINT), ALLOCATABLE ::  LIAISONS(:,:) ! (Na,0:NMaxL)
39
  INTEGER(KINT), ALLOCATABLE ::  LiaisonsBis(:,:) ! (Na,0:NMaxL)
40
  INTEGER(KINT), ALLOCATABLE ::  LiaisonsIni(:,:) ! (Na,0:NMaxL)
41
  INTEGER(KINT), ALLOCATABLE :: CAFaire(:) ! (Na)
42

    
43

    
44
  real(KREAL) ::  vx1,vy1,vz1,norm1
45
  real(KREAL) ::  vx2,vy2,vz2,norm2
46
  real(KREAL) ::  vx3,vy3,vz3,norm3
47
  real(KREAL) ::  vx4,vy4,vz4,norm4
48
  real(KREAL) ::  vx5,vy5,vz5,norm5
49
  real(KREAL) ::  val,val_d, d12, d13,d23,d
50
  Logical PasFini,Debug
51
  LOGICAL, ALLOCATABLE :: DejaFait(:),FCaf(:) !(na)
52
  Logical, ALLOCATABLE ::  FrozAt(:)    !T if this atom is frozen
53
  LOGICAL F1213, F1223,F1323
54

    
55

    
56
  INTEGER(KINT) :: I,J,n0,n1,n2,n3,n4,IAt,IL,JL,IFrag,ITmp, K, KMax
57
  INTEGER(KINT) :: IMax, I3,I1,Ip, IFragFroz,IBeg
58
  INTEGER(KINT) :: I0, Izm, JAt,Izm0,Idx
59

    
60
  REAL(KREAL) :: sDihe, Pi, Sang
61

    
62
  INTERFACE
63
     function valid(string) result (isValid)
64
       CHARACTER(*), intent(in) :: string
65
       logical                  :: isValid
66
     END function VALID
67

    
68
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
69
       use Path_module, only :  Pi,KINT, KREAL
70
       real(KREAL) ::  v1x,v1y,v1z,norm1
71
       real(KREAL) ::  v2x,v2y,v2z,norm2
72
       real(KREAL) ::  angle
73
     END FUNCTION ANGLE
74

    
75
     FUNCTION SinAngle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
76
       use Path_module, only :  Pi,KINT, KREAL
77
       real(KREAL) ::  v1x,v1y,v1z,norm1
78
       real(KREAL) ::  v2x,v2y,v2z,norm2
79
       real(KREAL) ::  SinAngle
80
     END FUNCTION SINANGLE
81

    
82

    
83
     FUNCTION angle_d(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2,v3x,v3y,v3z,norm3)
84
       use Path_module, only :  Pi,KINT, KREAL
85
       real(KREAL) ::  v1x,v1y,v1z,norm1
86
       real(KREAL) ::  v2x,v2y,v2z,norm2
87
       real(KREAL) ::  v3x,v3y,v3z,norm3 
88
       real(KREAL) ::  angle_d,ca,sa
89
     END FUNCTION ANGLE_D
90

    
91
  END INTERFACE
92

    
93
  Pi=dacos(-1.d0)
94
  debug=valid("calc_mixed_frag")
95
  if (debug) Call Header("Entering Calc_mixed_frag")
96
  if (na.le.2) THEN
97
     WRITE(*,*) "I do not work for less than 2 atoms :-p"
98
     RETURN
99
  END IF
100

    
101
  ALLOCATE(FrozDist(Na),Fragment(na), NbAtFrag(na),FragAt(na,na))
102
  ALLOCATE(FCart(Na),AtCart(Na))
103
  ALLOCATE(FrozFrag(na,3), FrozBlock(na,0:na))
104
  ALLOCATE(DistFroz(na),Liaisons(na,0:NMaxL))
105
  ALLOCATE(LiaisonsBis(na,0:NMaxL),LiaisonsIni(na,0:NMaxL))
106
  ALLOCATE(CaFaire(na+1),DejaFait(Na),FCaf(na),FrozAt(na))
107

    
108
  Ind_Zmat=0
109

    
110
  ! Putting cart+frozen atoms into  cart array
111
  FCart=.FALSE.
112
  NCart=0
113
  Idx=1
114
  DO WHILE (Frozen(Idx).NE.0)
115
     If (Frozen(Idx).LT.0) THEN
116
        DO I=Frozen(Idx-1),abs(Frozen(Idx))
117
           IF (.NOT.FCart(I)) THEN
118
              NCart=NCart+1
119
              AtCart(NCart)=I
120
              FCart(I)=.TRUE.
121
           END IF
122
        END DO
123
     ELSEIF (.NOT.FCart(Frozen(Idx))) THEN
124
        FCart(Frozen(Idx))=.TRUE.
125
        NCart=NCart+1
126
        AtCart(NCart)=Frozen(Idx)
127
     END IF
128
  Idx=Idx+1
129
  END DO
130
  NFroz=NCart
131
  Idx=1
132
  DO WHILE (Cart(Idx).NE.0)
133
     If (Cart(Idx).LT.0) THEN
134
        DO I=Cart(Idx-1),abs(Cart(Idx))
135
           IF (.NOT.FCart(I)) THEN
136
              NCart=NCart+1
137
              AtCart(NCart)=I
138
              FCart(I)=.TRUE.
139
           END IF
140
        END DO
141
     ELSEIF (.NOT.FCart(Cart(Idx))) THEN
142
        FCart(Cart(Idx))=.TRUE.
143
        NCart=NCart+1
144
        AtCart(NCart)=Cart(Idx)
145
     END IF
146
  Idx=Idx+1
147
  END DO
148

    
149
  if (debug) THEN
150
     WRITE(*,'(1X,A,I4,A,I4,A)') "Found ",NFroz," frozen atoms, and a total of ",NCart," atoms described in cartesian coordinates"
151
     WRITE(*,*) "AtCart:",AtCart(1:NCart)
152
  END IF
153

    
154
  DejaFait=.FALSE.
155

    
156
  ! We cheat a lot: we will use ind_zmat et val_zmat to store
157
  ! the cartesian coordinates of the NCart atoms :-p
158
  DO I=1,NCart
159
     Iat=AtCart(I)
160
     ind_zmat(I,1)=Iat
161
     ind_zmat(I,2:5)=-1
162
     val_zmat(I,1)=X(Iat)
163
     val_zmat(I,2)=Y(Iat)
164
     val_zmat(I,3)=Z(Iat)
165
     DejaFait(Iat)=.TRUE.
166
     idx_zmat(Iat)=I
167
  END DO
168

    
169

    
170
  izm=NCart
171

    
172
  ! We now calculate the connections
173
  Liaisons=0
174
  LiaisonsBis=0
175

    
176
  if (debug) THEN
177
     WRITE(*,*) "Liaisons initialized"
178
!     WRITE(*,*) 'Covalent radii used'
179
!     DO iat=1,na
180
!        i=atome(iat)
181
!        WRITE(*,*) Nom(I),Iat,r_cov(i),r_cov(i)*fact
182
!     END DO
183
  END IF
184

    
185
1003 FORMAT(1X,I4,' - ',25(I5))
186

    
187
  Call CalcCnct(na,atome,x,y,z,LIAISONS,r_cov,fact)
188

    
189
  if (debug) THEN
190
     WRITE(*,*) "Connections calculated"
191
     DO IL=1,na
192
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
193
     END DO
194
  END IF
195

    
196
  ! We get rid of bonds between cart atoms
197
  ! the trick is to do this on liaisons while keeping LiaisonsBis ok.
198

    
199
  LiaisonsIni=Liaisons
200
  LiaisonsBis=Liaisons
201

    
202
  DO I=1,NCart
203
     Iat=AtCart(I)
204
     if (debug) WRITE(*,'(20(1X,I3))') I,Iat,  &
205
          (LiaisonsIni(Iat,Itmp),ITmp=0,LiaisonsIni(Iat,0))
206
     DO J=1,LiaisonsIni(Iat,0)
207
        Jat=LiaisonsIni(Iat,J)
208
        IF (FCart(Jat)) THEN
209
           Call Annul(Liaisons,Iat,Jat)
210
           Call Annul(Liaisons,Jat,Iat)
211
           Call Annul(LiaisonsIni,Jat,Iat)
212
           Liaisons(Iat,0)=Liaisons(Iat,0)-1
213
           Liaisons(Jat,0)=Liaisons(Jat,0)-1
214
           LiaisonsIni(Jat,0)=LiaisonsIni(Jat,0)-1
215
        END IF
216
     END DO
217
  END DO
218

    
219
  if (debug) THEN
220
     WRITE(*,*) "Connections omitting bonds between cart atoms"
221
     DO IL=1,na
222
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
223
     END DO
224
  END IF
225

    
226
  ! We decompose the system into fragments, but we omit on purpuse
227
  ! fragments consisting only of frozen atoms
228
  ! Now, frozblock will contain the frozen atom indices in a given fragment
229
  Fragment=0
230
  NbAtFrag=0
231
  FrozBlock=0
232

    
233
  IdxFrag=0
234
  NbFrag=0
235

    
236
 Call Decomp_frag(na,liaisons,.NOT.Fcart,nbfrag,Fragment,NbAtFrag,FragAt)
237

    
238
 ! We compute FrozBlock now
239
  DO IFrag=1,NbFrag
240
     DO I=1,NbAtFrag(IFrag)
241
        Iat=FragAt(IFrag,I)
242
        IF (FCart(Iat)) THEN
243
           FrozBlock(IFrag,0)=FrozBlock(IFrag,0)+1
244
           FrozBlock(IFrag,FrozBlock(IFrag,0))=IAt
245
        END IF
246
     END DO
247
  END DO
248

    
249
  if (debug) THEN
250
     WRITE(*,*) 'I found ',NbFrag, 'fragments with respectively '
251
     WRITE(*,*) (NbAtFrag(I),I=1,NbFrag), 'atoms'
252
     WRITE(*,*) "Fragments atoms are now listed as F in the following"
253
     DO I=1,NbFrag
254
        WRITE(*,*) Na
255
        WRITE(*,*) 'Fragment ', i
256
        DO J=1,Na
257
           AtName=Nom(Atome(J))
258
           IF (Fragment(J).EQ.I) AtName='F'
259
           WRITE(*,'(1X,A5,3(1X,F10.6))') AtName,X(J),Y(J),Z(J)
260
        END DO
261
        !     WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
262
     END DO
263

    
264
     DO I=1,NbFrag
265
        WRITE(*,*) 'Fragment ', i
266
        WRITE(*,'(A,20(1X,I3))') "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
267
        WRITE(*,'(A,20(1X,I3))') "FrozBlock:",(FrozBlock(I,j),j=0,FrozBlock(I,0))
268
     END DO
269
  END IF
270

    
271
  NFroz=0
272
  DO IFrag=1,NbFrag
273
     If (FrozBlock(IFrag,0).NE.0) NFroz=NFroz+1
274
  END DO
275

    
276
  IF (DEBUG) WRITE(*,'(1X,A,I4,A,I4,A)') "Found ",NFroz," fragment(s) with cart atoms, out of",NbFrag," fragment(s)"
277

    
278

    
279
  if (debug) THEN
280
     WRITE(*,*) "Connections before adding fragments"
281
     DO IL=1,na
282
        IF (Liaisons(IL,0).NE.0)  WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
283
     END DO
284
  END IF
285

    
286
  ! We will now add the fragments containing non cart atoms.
287
  ! I am not sure that there is a best strategy to add them...
288
  ! so we add them in the order they were created :-(
289
  ! First only block with frozen atoms are added
290
  izm0=-1
291
  IFrag=1
292
  IZm=NCart
293
  FCaf=.FALSE.
294
  DO IFragFroz=1,NFroz
295
     DO WHILE (FrozBlock(IFrag,0).EQ.0)
296
        IFrag=IFrag+1
297
     END DO
298
     ! each atom has at least one frozen atom that will serve as the seed
299
     ! of this fragment.
300
     if (debug) WRITE(*,*) 'Adding fragment :', ifrag,'with',FrozBlock(IFrag,0),' frozen atoms'
301
     IF (FrozBlock(IFrag,0).EQ.1) THEN
302
        ! There is only one frozen atom, easy case ...
303
        Iat=FrozBlock(IFrag,1)
304
        if (debug) WRITE(*,*) 'Only frozen atom of frag',iat
305
        DejaFait(iat)=.TRUE.
306
        IdxCaFaire=2
307
        CaFaire(1)=iat
308
        CaFaire(2)=0
309
        IaFaire=1
310
        FCaf(Iat)=.TRUE.
311
        DO WHILE (CaFaire(IaFaire).NE.0)
312
           n1=CaFaire(IaFaire)
313
           I1=idx_zmat(n1)
314
           n2=ind_zmat(I1,2)
315
           n3=ind_zmat(I1,3)
316

    
317
        if (debug) WRITE(*,1003) n1,(LIAISONS(n1,JL),JL=0,NMaxL)
318
           DO I3=1,Liaisons(n1,0)
319
              IAt=Liaisons(n1,I3)
320
              ! PFL 2007.Apr.16 ->
321
              ! We add ALL atoms linked to n1 to CaFaire
322
              ! But we delete their link to n1
323
!! PFL 2007.Aug.28 ->
324
! re-add the test on FCaf in order not to put the same atom more than once in 
325
! CaFaire array.
326
                 IF (.NOT.FCaf(Iat)) THEN
327
                    CaFaire(IdxCaFaire)=Iat
328
                    IdxCaFaire=IdxCaFaire+1
329
                    CaFaire(IdxCaFaire)=0
330
                    FCaf(Iat)=.TRUE.
331
                 END IF
332
!! <-- PFL 2007.Aug.28
333
              if (debug) WRITE(*,1003) Iat,(LIAISONS(Iat,JL),JL=0,NMaxL)
334
              Call Annul(Liaisons,Iat,n1)
335
              if (debug) WRITE(*,1003) Iat,(LIAISONS(Iat,JL),JL=0,NMaxL)
336
              Liaisons(iat,0)=Liaisons(Iat,0)-1
337
           if (debug) WRITE(*,*) 'Iafaire,n1,DejaFait,idxzmat,n2,n3',IaFaire,n1, &
338
                DejaFait(n1),idx_zmat(n1),n2,3
339
           if (debug) WRITE(*,*) 'Cafaire - 0', &
340
                (CaFaire(J),J=Iafaire,IdxCAfaire)
341

    
342

    
343
              ! <- PFL 2007.Apr.16
344
              IF (.NOT.DejaFait(Iat)) THEN
345
                 ! we add it to the Zmat
346
!                 WRITE(*,*) "coucou"
347
                 call vecteur(n1,iat,x,y,z,vx1,vy1,vz1,norm1)
348
!                 WRITE(*,*) "coucou 2"
349
                 izm=izm+1
350
                 IF (izm.EQ.2) THEN
351
!                 WRITE(*,*) "coucou 3"
352
                    ind_zmat(izm,1)=IAt
353
                    ind_zmat(izm,2)=n1
354
                    ind_zmat(izm,3:5)=0
355
                    if (n2.EQ.-1) n2=Iat
356
                 END IF
357

    
358
!                 WRITE(*,*) "coucou 4"
359
                 if ((izm.GE.3).AND.(n2.EQ.-1)) THEN
360
!                 WRITE(*,*) "coucou 5"
361
!                 WRITE(*,*) "coucou 3 bis"
362
                       ! This atom is defined in cartesian coordinates
363
                       ! and has not been used to put a non cart atom.
364
                       ! we will find the closest atom linked to this one amongst the atoms
365
                       ! already stored in ind_zmat
366
                       d=1e9
367
                       JAt=-1
368
                       DO I=1,NCart
369
                          If (ind_zmat(I,1).NE.n1) THEN
370
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx2,vy2,vz2,norm2)
371
                             SAng=Sinangle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
372
                             ! we take only atoms that are not aligned
373
                             if ((norm2<=d).AND.(SAng.GT.0.09d0)) THEN
374
                                Jat=ind_zmat(I,1)
375
                                d=norm2
376
                             END IF
377
                          END IF
378
                       END DO
379
                       if (JAt.EQ.-1) THEN
380
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
381
                          STOP
382
                       END IF
383
                       n2=JAt
384
                 END IF! izm>=3 and n2.eq.-1
385

    
386
                 IF (izm.eq.3) THEN
387
                    ind_zmat(izm,1)=Iat
388
                    ind_zmat(izm,2)=n1
389
                    ind_zmat(izm,3)=n2
390
                 END IF  ! izm=3
391

    
392
                 IF (izm.GE.4) THEN
393
!                                     WRITE(*,*) "coucou 5 bis"
394
                    IF (n3.EQ.-1) THEN
395
                       ! This atom is defined in cartesian coordinates
396
                       ! and has not been used to put a non cart atom.
397
                       ! we will find the closest atom linked to this one amongst the atoms
398
                       ! already stored in ind_zmat
399
                       call vecteur(n1,n2,x,y,z,vx2,vy2,vz2,norm2)
400
                       d=1e9
401
                       JAt=-1
402
                       DO I=1,NCart
403
                          If ((ind_zmat(I,1).NE.n1).AND.(ind_zmat(I,1).NE.n2)) THEN
404
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx3,vy3,vz3,norm3)
405
                             SAng=Sinangle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
406
                             if (debug) WRITE(*,*) "1-Trying izm,iat,n1,n2,n3,sang,d,norm3", &
407
                                  izm,iat,n1,n2,ind_zmat(I,1),sang,d,norm3
408
                             ! we take only atoms that are not aligned
409
                             if ((norm3<=d).AND.(SAng.GT.0.09d0)) THEN
410
                                Jat=ind_zmat(I,1)
411
                                d=norm3
412
                             END IF
413
                          END IF
414
                       END DO
415
                       if (JAt.EQ.-1) THEN
416
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
417
                          STOP
418
                       END IF
419
                       n3=JAt
420
                    END IF
421
                    !                    ind_zmat(I1,3)=n3
422
                    Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
423
                 END IF ! izm>=4
424
!                 WRITE(*,*) "coucou 6"
425
           if (debug) THEN
426
              WRITE(*,*) 'ind_zmat 0',izm
427
              DO Ip=1,NCart
428
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(ip,1:4)
429
                 END DO
430
              SELECT CASE (NCart)
431
                 CASE (1)
432
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
433
                    if (izm.GE.3) &
434
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
435
                    Ibeg=4
436
                 CASE (2)
437
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
438
                    Ibeg=4
439
                 CASE DEFAULT
440
                    IBeg=NCart+1
441
                 END SELECT
442
              DO Ip=IBeg,izm
443
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
444
                      ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
445
              END DO
446
           END IF
447

    
448
                 idx_zmat(iat)=izm
449
!                 Call Annul(Liaisons,iat,n1)
450
!                 Liaisons(iat,0)=Liaisons(Iat,0)-1
451
                 !                  Call Annul(Liaisons,n1,iat)
452
                 n3=iat
453
                 DejaFait(Iat)=.TRUE.
454
              END IF
455
           END DO
456
           IaFaire=IaFaire+1
457

    
458
           if (debug) THEN
459
              WRITE(*,*) 'ind_zmat 5'
460
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
461
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
462
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
463
              DO Ip=4,izm
464
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
465
                      ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
466
              END DO
467
           END IF
468

    
469
        END Do              ! DO WHILE CaFaire
470

    
471

    
472
     ELSE     ! FrozBlock(I,0)==1
473
        if (debug) WRITE(*,*) 'IFrag=',IFrag,'Frozblock(I,0)>1',Frozblock(IFrag,0)
474
        ! We have many frozen atoms for one fragment. We will have to choose
475
        ! the first one, and then to decide when to swich...
476
        Iat=0
477
        I0=-1
478
        DO I=1,FrozBlock(IFrag,0)
479
           JAt=FrozBlock(IFrag,I)
480
           if (debug) WRITE(*,*) Jat, &
481
                (LiaisonsBis(Jat,Itmp),Itmp=0,LiaisonsBis(Jat,0))
482
           IF (LiaisonsBis(Jat,0).GT.I0) THEN
483
              I0=LiaisonsBis(Jat,0)
484
              Iat=Jat
485
           END IF
486
        END DO
487
        ! Iat is the starting frozen atom
488
        IF (debug) WRITE(*,*) 'Choosing atom ',iat,'as a starting atom for frag',ifrag
489
        DejaFait(iat)=.TRUE.
490
        IdxCaFaire=2
491
        CaFaire(1)=iat
492
        CaFaire(2)=0
493
        IaFaire=1
494
        FCaf(Iat)=.TRUE.
495
        DO WHILE (CaFaire(IaFaire).NE.0)
496
           n1=CaFaire(IaFaire)
497
           I1=idx_zmat(n1)
498
           n2=ind_zmat(I1,2)
499
           n3=ind_zmat(I1,3)
500
           if (debug) WRITE(*,*) 'Iafaire,n1,DejaFait,idxzmat,n2,n3',IaFaire,n1, &
501
                DejaFait(n1),idx_zmat(n1),n2,3
502
           if (debug) WRITE(*,*) 'Cafaire', &
503
                (CaFaire(J),J=Iafaire,IdxCAfaire)
504

    
505

    
506
           DO I3=1,Liaisons(n1,0)
507
              if (debug) WRITE(*,*) "Here, I3=",I3
508
              IAt=Liaisons(n1,I3)
509
              ! PFL 2007.Apr.16 ->
510
              ! We add ALL atoms linked to n1 to CaFaire
511
              ! But we delete their link to n1
512
!! PFL 2007.Aug.28 ->
513
! re-add the test on FCaf in order not to put the same atom more than once in 
514
! CaFaire array.
515
                 IF (.NOT.FCaf(Iat)) THEN
516
                    CaFaire(IdxCaFaire)=Iat
517
                    IdxCaFaire=IdxCaFaire+1
518
                    CaFaire(IdxCaFaire)=0
519
                    FCaf(Iat)=.TRUE.
520
                 END IF
521
!! <-- PFL 2007.Aug.28
522
              Call Annul(Liaisons,Iat,n1)
523
              Liaisons(iat,0)=Liaisons(Iat,0)-1
524
              ! <- PFL 2007.Apr.16
525
              IF (.NOT.DejaFait(Iat)) THEN
526
                 ! we add it to the Zmat
527
                 call vecteur(n1,iat,x,y,z,vx1,vy1,vz1,norm1)
528
                 izm=izm+1
529
                 IF (izm.EQ.2) THEN
530
                    ind_zmat(izm,1)=IAt
531
                    ind_zmat(izm,2)=n1
532
                    ind_zmat(izm,3:5)=0
533
                 ELSE
534
                    IF (n2.EQ.-1) THEN
535
                       ! This atom is defined in cartesian coordinates
536
                       ! and has not been used to put a non cart atom.
537
                       ! we will find the closest atom linked to this one amongst the atoms
538
                       ! already stored in ind_zmat
539
                       d=1e9
540
                       JAt=-1
541
                       DO I=1,NCart
542
                          If (ind_zmat(I,1).NE.n1) THEN
543
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx2,vy2,vz2,norm2)
544
                             SAng=Sinangle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
545
                             ! we take only atoms that are not aligned
546
                             if ((norm2<=d).AND.(SAng.GT.0.09d0)) THEN
547
                                Jat=ind_zmat(I,1)
548
                                d=norm2
549
                             END IF
550
                          END IF
551
                       END DO
552
                       if (JAt.EQ.-1) THEN
553
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
554
                          STOP
555
                       END IF
556
                       n2=JAt
557
                    END IF
558
                    !                    ind_zmat(I1,2)=n2
559
                    if (izm.EQ.3) THEN
560
                       ind_zmat(izm,1)=Iat
561
                       ind_zmat(izm,2)=n1
562
                       ind_zmat(izm,3)=n2
563
                    ELSE
564
                       IF (n3.EQ.-1) THEN
565
                          ! This atom is defined in cartesian coordinates
566
                          ! and has not been used to put a non cart atom.
567
                          ! we will find the closest atom linked to this one amongst the atoms
568
                          ! already stored in ind_zmat
569
                          call vecteur(n1,n2,x,y,z,vx2,vy2,vz2,norm2)
570
                          d=1e9
571
                          JAt=-1
572
                          DO I=1,NCart
573
                             If ((ind_zmat(I,1).NE.n1).AND.(ind_zmat(I,1).NE.n2)) THEN
574
                                call vecteur(n1,ind_zmat(I,1),x,y,z,vx3,vy3,vz3,norm3)
575
                                SAng=Sinangle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
576
                             if (debug) WRITE(*,*) "2-Trying izm,iat,n1,n2,n3,sang,d,norm3", &
577
                                  izm,iat,n1,n2,ind_zmat(I,1),sang,d,norm3
578

    
579
                                ! we take only atoms that are not aligned
580
                                if ((norm3<=d).AND.(SAng.GT.0.09d0)) THEN
581
                                   Jat=ind_zmat(I,1)
582
                                   d=norm3
583
                                END IF
584
                             END IF
585
                          END DO
586
                          if (JAt.EQ.-1) THEN
587
                             WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
588
                             STOP
589
                          END IF
590
                          n3=JAt
591
                       END IF
592
                       !                    ind_zmat(I1,3)=n3
593
                       Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
594
                    END IF
595
                 END IF
596
                 idx_zmat(iat)=izm
597
              !                  Call Annul(Liaisons,n1,iat)
598
                 n3=iat
599
                 DejaFait(Iat)=.TRUE.
600
                 if (debug) WRITE(*,*) "For no reason, I3=",I3
601
              END IF
602
           END DO
603
           IaFaire=IaFaire+1
604

    
605
           if (debug) THEN
606
              WRITE(*,*) 'ind_zmat 6',izm
607
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
608
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
609
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
610
              DO Ip=4,izm
611
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
612
                      ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
613
              END DO
614
           END IF
615

    
616

    
617
        END Do              ! DO WHILE CaFaire
618

    
619

    
620
     END IF  ! FrozBlock(I,0)==1
621

    
622
     IFrag=IFrag+1
623

    
624
  END DO                    ! Loop on all fragments
625

    
626

    
627
  DO IFrag=1,NbFrag
628
     IF (FrozBlock(IFrag,0).EQ.0) THEN
629
        if (debug) WRITE(*,*) 'Adding fragment :', ifrag,'with no frozen atoms'
630
        ! We have no frozen atoms for this fragment. We will have to choose
631
        ! the first atom to put.
632
        ! For now, we do not care of the 'central' atom (ie the one with
633
        ! no CP atoms...)
634
        ! We just take the atom that is the closest to the already placed
635
        ! atoms !
636

    
637
        I0=0
638
        I1=0
639
        d=1e9
640
        DO J=1,izm
641
           Jat=ind_zmat(J,1)
642
           DO I=1,NbAtfrag(IFrag)
643
              IAt=FragAt(IFrag,I)
644
              IF (.NOT.DejaFait(Iat)) THEN
645
                 Call vecteur(Iat,Jat,x,y,z,vx1,vy1,vz1,norm1)
646
                 IF (norm1.LT.d) THEN
647
                    I1=Jat
648
                    I0=Iat
649
                    d=Norm1
650
                 END IF
651
              END IF
652
           END DO
653
        END DO
654

    
655
        Iat=I0
656
        n1=I1
657
        I1=idx_zmat(n1)
658
        n2=ind_zmat(I1,2)
659
        n3=ind_zmat(I1,3)
660

    
661
        IF (debug) WRITE(*,*) Iat,' starting atom for frag',ifrag
662

    
663
        
664
        call vecteur(n1,iat,x,y,z,vx1,vy1,vz1,norm1)
665
        izm=izm+1
666
        IF (izm.EQ.2) THEN
667
           ind_zmat(izm,1)=IAt
668
           ind_zmat(izm,2)=n1
669
           ind_zmat(izm,3:5)=0
670
        ELSE
671
           IF (n2.EQ.-1) THEN
672
! This atom is defined in cartesian coordinates
673
! and has not been used to put a non cart atom.
674
! we will find the closest atom linked to this one amongst the atoms
675
! already stored in ind_zmat
676
              d=1e9
677
              JAt=-1
678
              DO I=1,NCart
679
                 If (ind_zmat(I,1).NE.n1) THEN
680
                    call vecteur(n1,ind_zmat(I,1),x,y,z,vx2,vy2,vz2,norm2)
681
                    SAng=Sinangle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
682
! we take only atoms that are not aligned
683
                    if ((norm2<=d).AND.(SAng.GT.0.09d0)) THEN
684
                       Jat=ind_zmat(I,1)
685
                       d=norm2
686
                    END IF
687
                 END IF
688
              END DO
689
              if (JAt.EQ.-1) THEN
690
                 WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
691
                 STOP
692
              END IF
693
              n2=JAt
694
           END IF
695
!                    ind_zmat(I1,2)=n2
696
        END IF
697
        if (izm.EQ.3) THEN
698
           ind_zmat(izm,1)=Iat
699
           ind_zmat(izm,2)=n1
700
           ind_zmat(izm,3)=n2
701
        ELSE
702
           IF (n3.EQ.-1) THEN
703
! This atom is defined in cartesian coordinates
704
! and has not been used to put a non cart atom.
705
! we will find the closest atom linked to this one amongst the atoms
706
! already stored in ind_zmat
707
              call vecteur(n1,n2,x,y,z,vx2,vy2,vz2,norm2)
708
              d=1e9
709
              JAt=-1
710
              DO I=1,NCart
711
                 If ((ind_zmat(I,1).NE.n1).AND.(ind_zmat(I,1).NE.n2)) THEN
712
                    call vecteur(n1,ind_zmat(I,1),x,y,z,vx3,vy3,vz3,norm3)
713
                    SAng=Sinangle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
714
                             if (debug) WRITE(*,*) "3-Trying izm,iat,n1,n2,n3,sang,d,norm3", &
715
                                  izm,iat,n1,n2,ind_zmat(I,1),sang,d,norm3
716

    
717
! we take only atoms that are not aligned
718
                    if ((norm3<=d).AND.(SAng.GT.0.09d0)) THEN
719
                       Jat=ind_zmat(I,1)
720
                       d=norm3
721
                    END IF
722
                 END IF
723
              END DO
724
              if (JAt.EQ.-1) THEN
725
                 WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
726
                 STOP
727
              END IF
728
              n3=JAt
729
           END IF
730
           !                    ind_zmat(I1,3)=n3
731
           Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
732
        END IF
733
        idx_zmat(iat)=izm
734

    
735

    
736
        DejaFait(iat)=.TRUE.
737
        IdxCaFaire=2
738
        CaFaire(1)=iat
739
        CaFaire(2)=0
740
        IaFaire=1
741
        FCaf(Iat)=.TRUE.
742
        DO WHILE (CaFaire(IaFaire).NE.0)
743
           n1=CaFaire(IaFaire)
744
           if (debug) WRITE(*,*) 'Iafaire,n1',IaFaire,n1, &
745
                DejaFait(n1),idx_zmat(n1)
746
           if (debug) WRITE(*,*) 'Cafaire', &
747
                (CaFaire(J),J=Iafaire,IdxCAfaire)
748
           I1=idx_zmat(n1)
749
           n2=ind_zmat(I1,2)
750
           n3=ind_zmat(I1,3)
751

    
752
           DO I3=1,Liaisons(n1,0)
753
              IAt=Liaisons(n1,I3)
754
              ! PFL 2007.Apr.16 ->
755
              ! We add ALL atoms linked to n1 to CaFaire
756
              ! But we delete their link to n1
757
!! PFL 2007.Aug.28 ->
758
! re-add the test on FCaf in order not to put the same atom more than once in 
759
! CaFaire array.
760
                 IF (.NOT.FCaf(Iat)) THEN
761
                    CaFaire(IdxCaFaire)=Iat
762
                    IdxCaFaire=IdxCaFaire+1
763
                    CaFaire(IdxCaFaire)=0
764
                    FCaf(Iat)=.TRUE.
765
                 END IF
766
!! <-- PFL 2007.Aug.28
767
              Call Annul(Liaisons,Iat,n1)
768
              Liaisons(iat,0)=Liaisons(Iat,0)-1
769
              ! <- PFL 2007.Apr.16
770
              IF (.NOT.DejaFait(Iat)) THEN
771
                 ! we add it to the Zmat
772
                 call vecteur(n1,iat,x,y,z,vx1,vy1,vz1,norm1)
773
                 izm=izm+1
774
                 IF (izm.EQ.2) THEN
775
                    ind_zmat(izm,1)=IAt
776
                    ind_zmat(izm,2)=n1
777
                    ind_zmat(izm,3:5)=0
778
                 ELSE
779
                    IF (n2.EQ.-1) THEN
780
! This atom is defined in cartesian coordinates
781
! and has not been used to put a non cart atom.
782
! we will find the closest atom linked to this one amongst the atoms
783
! already stored in ind_zmat
784
                       d=1e9
785
                       JAt=-1
786
                       DO I=1,NCart
787
                          If (ind_zmat(I,1).NE.n1) THEN
788
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx2,vy2,vz2,norm2)
789
                             SAng=Sinangle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
790
! we take only atoms that are not aligned
791
                             if ((norm2<=d).AND.(SAng.GT.0.09d0)) THEN
792
                                Jat=ind_zmat(I,1)
793
                                d=norm2
794
                             END IF
795
                          END IF
796
                       END DO
797
                       if (JAt.EQ.-1) THEN
798
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
799
                          STOP
800
                       END IF
801
                       n2=JAt
802
                    END IF
803
!                    ind_zmat(I1,2)=n2
804
                 END IF
805
                 if (izm.EQ.3) THEN
806
                    ind_zmat(izm,1)=Iat
807
                    ind_zmat(izm,2)=n1
808
                    ind_zmat(izm,3)=n2
809
                 ELSE
810
                    IF (n3.EQ.-1) THEN
811
! This atom is defined in cartesian coordinates
812
! and has not been used to put a non cart atom.
813
! we will find the closest atom linked to this one amongst the atoms
814
! already stored in ind_zmat
815
                       call vecteur(n1,n2,x,y,z,vx2,vy2,vz2,norm2)
816
                       d=1e9
817
                       JAt=-1
818
                       DO I=1,NCart
819
                          If ((ind_zmat(I,1).NE.n1).AND.(ind_zmat(I,1).NE.n2)) THEN
820
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx3,vy3,vz3,norm3)
821
                             SAng=Sinangle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
822
                             if (debug) WRITE(*,*) "4-Trying izm,iat,n1,n2,n3,sang,d,norm3", &
823
                                  izm,iat,n1,n2,ind_zmat(I,1),sang,d,norm3
824

    
825
! we take only atoms that are not aligned
826
                             if ((norm3<=d).AND.(SAng.GT.0.09d0)) THEN
827
                                Jat=ind_zmat(I,1)
828
                                d=norm3
829
                             END IF
830
                          END IF
831
                       END DO
832
                       if (JAt.EQ.-1) THEN
833
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
834
                          STOP
835
                       END IF
836
                       n3=JAt
837
                    END IF
838
!                    ind_zmat(I1,3)=n3
839
                    Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
840
                 END IF
841
                 idx_zmat(iat)=izm
842
                 n3=iat
843
                 DejaFait(Iat)=.TRUE.
844
              END IF
845
           END DO
846
           IaFaire=IaFaire+1
847

    
848
           if (debug) THEN
849
              WRITE(*,*) 'ind_zmat 7',izm
850
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
851
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
852
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
853
              DO Ip=4,izm
854
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
855
                      ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
856
              END DO
857
           END IF
858

    
859

    
860
        END Do              ! DO WHILE CaFaire
861
     END IF                 ! FrozBlock(IFrag,0).EQ.0
862

    
863
  END DO                    ! Loop on all fragments without frozen atoms
864

    
865
  if (debug) THEN
866
     WRITE(*,*) Na+Izm
867
     WRITE(*,*) 'Done... :-(', izm
868
     DO J=1,Na
869
        WRITE(*,'(1X,A5,3(1X,F10.6))') Nom(Atome(J)),X(J),Y(J),Z(J)
870
     END DO
871
     DO I=1,Izm
872
        J=ind_zmat(I,1)
873
        WRITE(*,'(1X,A5,3(1X,F10.6))') 'X ',X(J),Y(J),Z(J)
874
     END DO
875
        IF (izm.NE.Na) THEN
876
           WRITE(*,*) "Atoms not done:"
877
           DO I=1,Na
878
              IF (.NOT.DejaFait(I)) WRITE(*,'(I5)',ADVANCE='NO') I
879
           END DO
880
        END IF
881

    
882
  END IF
883

    
884

    
885
  ! We have ind_zmat. We calculate val_zmat :-)
886
  if (debug) WRITE(*,*) "Calculating val_zmat"
887

    
888
  SELECT CASE (NCart)
889
     CASE (1)
890
        val_zmat(2,2)=0.d0
891
     val_zmat(2,3)=0.d0
892
     val_zmat(3,3)=0.d0
893
     n1=ind_zmat(2,1)
894
     n2=ind_zmat(2,2)
895
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
896
     val_zmat(2,1)=norm1
897

    
898
     n1=ind_zmat(3,1)
899
     n2=ind_zmat(3,2)
900
     n3=ind_zmat(3,3)
901
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
902
     val_zmat(3,1)=norm1
903

    
904
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
905
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
906
     val_zmat(3,2)=val
907
     IBeg=4
908

    
909
     CASE (2)
910
     val_zmat(3,3)=0.d0
911

    
912
     n1=ind_zmat(3,1)
913
     n2=ind_zmat(3,2)
914
     n3=ind_zmat(3,3)
915
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
916
     val_zmat(3,1)=norm1
917

    
918
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
919
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
920
     val_zmat(3,2)=val
921
     IBeg=4
922
  CASE DEFAULT
923
     Ibeg=NCart+1
924
  END SELECT
925

    
926

    
927
  DO i=IBeg,na
928

    
929
     n1=ind_zmat(i,1)
930
     n2=ind_zmat(i,2)
931
     n3=ind_zmat(i,3)
932
     n4=ind_zmat(i,4)
933

    
934
     if (debug) WRITE(*,*) "Doing i,n1,n2,n3,n4",i,n1,n2,n3,n4
935
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
936

    
937
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
938
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
939

    
940
     CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
941
     CALL produit_vect(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2, &
942
          vx4,vy4,vz4,norm4)
943
     CALL produit_vect(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2, &
944
          vx5,vy5,vz5,norm5)
945

    
946
     val_d=angle_d(vx4,vy4,vz4,norm4, vx5,vy5,vz5,norm5, &
947
          vx2,vy2,vz2,norm2)
948

    
949
     !     write(*,11) n1,n2,norm1,n3,val,n4,val_d
950
!11   format (2(1x,i3),1x,f8.4,2(1x,i3,1x,f8.3))
951

    
952
     val_zmat(i,1)=norm1
953
     val_zmat(i,2)=val
954
     val_zmat(i,3)=val_d
955

    
956
  END DO
957

    
958
  if (debug) THEN
959
     WRITE(*,*) 'DBG Cre_Zmat_Constr: ind_zmat'
960
     DO I=1,na
961
        WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5)
962
     END DO
963

    
964
     WRITE(*,*) 'DBG Cre_Zmat_Constr: Full zmat'
965
     DO I=1,NCart
966
        WRITE(*,'(1X,I5,3(1X,F11.6))') ind_zmat(i,1),(val_zmat(i,j),j=1,3)
967
     END DO
968
     DO I=NCart+1,Na
969
        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)
970
     END DO
971

    
972
  END IF
973

    
974
  if (debug) WRITE(*,*) "Deallocate (FrozDist,Fragment, NbAtFrag,FragAt)"
975
  DEALLOCATE(FrozDist,Fragment, NbAtFrag,FragAt)
976
  if (debug) WRITE(*,*) "Deallocate FrozFrag, IdxFragAt, FrozBlock"
977
!  DEALLOCATE(FrozFrag, IdxFragAt, FrozBlock)
978
  DEALLOCATE(FrozFrag,FrozBlock)
979
  if (debug) WRITE(*,*) "Deallocate (DistFroz,Liaisons)"
980
  DEALLOCATE(DistFroz,Liaisons)
981
  if (debug) WRITE(*,*) "Deallocate (LiaisonsIni)"
982
  DEALLOCATE(LiaisonsIni)
983
  if (debug) WRITE(*,*) "Deallocate(CaFaire,DejaFait,FrozAt)"
984
  DEALLOCATE(CaFaire,DejaFait,FrozAt)
985
  if (debug) WRITE(*,*) "Deallocate LiaisonsBis"
986
  DEALLOCATE(LiaisonsBis)
987
  if (debug) WRITE(*,*) "Deallocate FCart,AtCart,FCaf"
988
  DEALLOCATE(FCart,AtCart,FCaf)
989

    
990
  if (debug) Call Header("Exiting Calc_mixed_frag")
991

    
992
END SUBROUTINE Calc_mixed_frag
993