Statistiques
| Révision :

root / src / Calc_zmat_constr_frag.f90 @ 2

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

1
SUBROUTINE Calc_Zmat_const_frag(na,atome,ind_zmat,val_zmat,x,y,z, &
2
     r_cov,fact,frozen)
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

    
18
  CHARACTER(5) :: AtName
19
  integer(KINT) :: na,atome(na),ind_zmat(Na,5)
20
  INTEGER(KINT) :: idx_zmat(NA)
21
  real(KREAL) ::  x(Na),y(Na),z(Na),fact
22
  real(KREAL) ::  val_zmat(Na,3)
23
  real(KREAL) :: r_cov(0:Max_Z)
24
  !     Frozen contains the indices of frozen atoms
25
  INTEGER(KINT) :: Frozen(*),NFroz
26
  INTEGER(KINT), ALLOCATABLE :: FrozDist(:) ! na
27
  INTEGER(KINT) :: NbFrag,IdxFrag
28
  INTEGER(KINT), ALLOCATABLE :: Fragment(:),NbAtFrag(:) !na
29
  INTEGER(KINT), ALLOCATABLE :: FragAt(:,:) !na,na
30
  INTEGER(KINT), ALLOCATABLE :: FrozFrag(:,:) !na,3
31
  !  INTEGER(KINT), ALLOCATABLE :: IdxFragAt(:) !na
32
  INTEGER(KINT), ALLOCATABLE :: FrozBlock(:,:) !(na,0:na)
33
  REAL(KREAL), ALLOCATABLE :: DistFroz(:) !na
34

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

    
41

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

    
53

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

    
58
  REAL(KREAL) :: sDihe, Pi
59

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

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

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

    
80

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

    
89
  END INTERFACE
90

    
91

    
92

    
93
  Pi=dacos(-1.d0)
94
  debug=valid("calc_zmat_constr").OR.valid("calc_zmat_contr_frag")
95

    
96
  if (debug) WRITE(*,*) "=============================== Entering Calc_zmat_contr_frag ========================"
97
  if (na.le.2) THEN
98
     WRITE(*,*) "I do not work for less than 2 atoms :-p"
99
     RETURN
100
  END IF
101

    
102
  ALLOCATE(FrozDist(Na),Fragment(na), NbAtFrag(na),FragAt(na,na))
103
  !  ALLOCATE(FrozFrag(na,3), IdxFragAt(na), FrozBlock(na,0:na))
104
  ALLOCATE(FrozFrag(na,3), FrozBlock(na,0:na))
105
  ALLOCATE(DistFroz(na),Liaisons(na,0:NMaxL))
106
  ALLOCATE(LiaisonsBis(na,0:NMaxL),LiaisonsIni(na,0:NMaxL))
107
  ALLOCATE(CaFaire(na),DejaFait(Na),FCaf(na),FrozAt(na))
108

    
109
  DO i=1,na
110
     DO J=1,5
111
        Ind_Zmat(i,J)=0
112
     END DO
113
  END DO
114

    
115
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
116
!
117
!     Easy case : 3 or less atoms
118
!
119
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
120
  if (Na.eq.3) THEN
121
     d12=sqrt((x(1)-x(2))**2+(y(1)-y(2))**2+(z(1)-z(2))**2)
122
     d13=sqrt((x(1)-x(3))**2+(y(1)-y(3))**2+(z(1)-z(3))**2)
123
     d23=sqrt((x(3)-x(2))**2+(y(3)-y(2))**2+(z(3)-z(2))**2)
124
     F1213=(d12<=d13)
125
     F1323=(d13<=d23)
126
     F1223=(d12<=d23)
127
     if (debug) THEN
128
        WRITE(*,*) "DEBUG Calc_Zmat 3 atoms"
129
        WRITE(*,*) "d12,d13,d23:",d12,d13,d23
130
        WRITE(*,*) "F1213,F1323,F1223:",F1213,F1323,F1223
131
     END IF
132
     if (F1213) THEN
133
        if (F1323) THEN
134
           ind_zmat(1,1)=3
135
           ind_zmat(2,1)=1
136
           ind_zmat(2,2)=3
137
           ind_zmat(3,1)=2
138
           ind_zmat(3,2)=1
139
           ind_zmat(3,3)=3
140
        ELSE
141
           ind_zmat(1,1)=1
142
           ind_zmat(2,1)=2
143
           ind_zmat(2,2)=1
144
           ind_zmat(3,1)=3
145
           ind_zmat(3,2)=2
146
           ind_zmat(3,3)=1
147
        END IF
148
     ELSE
149
        IF (F1223) THEN
150
           ind_zmat(1,1)=2
151
           ind_zmat(2,1)=1
152
           ind_zmat(2,2)=2
153
           ind_zmat(3,1)=3
154
           ind_zmat(3,2)=1
155
           ind_zmat(3,3)=2
156
        ELSE
157
           ind_zmat(1,1)=2
158
           ind_zmat(2,1)=3
159
           ind_zmat(2,2)=2
160
           ind_zmat(3,1)=1
161
           ind_zmat(3,2)=3
162
           ind_zmat(3,3)=2
163
        END IF
164
     END IF
165
     IF (debug) THEN
166
        DO i=1,na
167
           WRITE(*,'(1X,5(1X,I5))') (ind_zmat(i,j),j=1,5)
168
        END DO
169
     END IF
170

    
171
     !     We have ind_zmat, we fill val_zmat
172
     val_zmat(1,1)=0.
173
     val_zmat(1,2)=0.
174
     val_zmat(1,3)=0.
175
     n2=ind_zmat(2,1)
176
     n1=ind_zmat(2,2)
177
     d=sqrt((x(n1)-x(n2))**2+(y(n1)-y(n2))**2+(z(n1)-z(n2))**2)
178
     val_zmat(2,1)=d
179
     val_zmat(2,2)=0.
180
     val_zmat(2,3)=0.
181
     n1=ind_zmat(3,1)
182
     n2=ind_zmat(3,2)
183
     n3=ind_zmat(3,3)
184
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
185
     if (debug) write(*,*) n1,n2,norm1
186
     val_zmat(3,1)=norm1
187

    
188
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
189
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
190
     if (debug) write(*,*) n2,n3,norm2,val
191
     val_zmat(3,2)=val
192
     val_zmat(3,3)=0.
193

    
194
     RETURN
195
  END IF
196
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
197
!
198
!  End of   Easy case : 3 or less atoms
199
!
200
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
201
!
202
! General Case 
203
!
204
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
205
!
206
! 1 - Frozen Atoms
207

    
208
! Initialization
209
  DejaFait=.False.
210
  FrozAt=.False.
211
  Liaisons=0
212
  LiaisonsBis=0
213
  ind_zmat=0
214
  val_zmat=0.d0
215

    
216
  NFroz=0
217
  I=1
218
  DO WHILE (Frozen(I).NE.0)
219
     If (Frozen(I).LT.0) THEN
220
        DO J=Frozen(I-1),abs(Frozen(I))
221
           IF (.NOT.FrozAt(J)) THEN
222
              NFroz=NFroz+1
223
              FrozAt(J)=.TRUE.
224
           END IF
225
        END DO
226
     ELSEIF (.NOT.FrozAt(Frozen(I))) THEN
227
        FrozAt(Frozen(I))=.TRUE.
228
        NFroz=NFroz+1
229
     END IF
230
  I=I+1
231
  END DO
232

    
233
  if (debug) WRITE(*,*) 'DGB zmtc NFroz=', NFroz
234
  if (debug) WRITE(*,*) 'DGB zmtc FrozAt=',(FrozAt(I),I=1,na)
235

    
236
  if (debug) THEN
237
     WRITE(*,*) "Liaisons initialized"
238
     WRITE(*,*) 'Covalent radii used'
239
     DO iat=1,na
240
        i=atome(iat)
241
        WRITE(*,*) Nom(I),Iat,r_cov(i),r_cov(i)*fact
242
     END DO
243
  END IF
244

    
245
1003 FORMAT(1X,I4,' - ',25(I5))
246
  !     DO IL=1,na
247
  !     WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
248
  !     WRITE(IOOUT,1003) Il,(LIAISONSBis(IL,JL),JL=0,NMaxL)
249
  !     END DO
250
!   First step : connectivity  are calculated
251

    
252
  Call CalcCnct(na,atome,x,y,z,LIAISONS,r_cov,fact)
253

    
254
  if (debug) THEN
255
     WRITE(*,*) "Connections calculated"
256
     DO IL=1,na
257
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
258
     END DO
259
  END IF
260

    
261
  FCaf=.TRUE.
262
  Call Decomp_frag(na,liaisons,FCaf,nbfrag,Fragment,NbAtFrag,FragAt)
263

    
264
  IF (debug) THEN
265
     WRITE(*,*) 'I found ',NbFrag, 'fragments'
266
     WRITE(*,'(20(1X,I4))') (NbAtFrag(I),I=1,NbFrag)
267
     DO I=1,NbFrag
268
        WRITE(*,*) NbAtFrag(I)
269
        WRITE(*,*) 'Fragment ', i
270
        DO J=1,Na
271
           IF (Fragment(J).EQ.I)   THEN                
272
		        if (FrozAt(J))    THEN   
273
                   WRITE(*,'(1X,I3,"f",1X,A5,3(1X,F10.6))') J,Nom(Atome(J)) &
274
                        ,X(J),Y(J),Z(J)
275
               ELSE
276
                    WRITE(*,'(1X,I3,2X,A5,3(1X,F10.6))') J,Nom(Atome(J)) &
277
                      ,X(J),Y(J),Z(J)
278
                END IF
279
		   END IF
280
        END DO
281
        WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
282
     END DO
283
  END IF
284

    
285

    
286
! First, we decompose the connectivity into Frozen atoms and non frozen atoms
287
  DO I=1,na
288
     LiaisonsBis(I,0)=0
289
     DO J=1,Liaisons(I,0)
290
        IF (FrozAt(Liaisons(I,J))) THEN
291
           LiaisonsBis(I,0)=LiaisonsBis(I,0)+1
292
           LiaisonsBis(I,LiaisonsBis(I,0))=Liaisons(I,J)
293
        END IF
294
     END DO
295
     IMax=LiaisonsBis(I,0)+1
296
     LiaisonsBis(I,Imax)=0
297
     DO J=1,Liaisons(I,0)
298
        IF (.NOT.FrozAt(Liaisons(I,J))) THEN
299
           LiaisonsBis(I,IMax)=LiaisonsBis(I,Imax)+1
300
           LiaisonsBis(I,LiaisonsBis(I,Imax)+Imax)=Liaisons(I,J)
301
        END IF
302
     END DO
303
  END DO
304

    
305
  if (debug) THEN
306
     WRITE(*,*) "Liaisons and LiaisonsBis"
307
     DO I=1,Na
308
        WRITE(*,'(1X,I3," -",I3,":",15(1X,I3))') I, &
309
             (Liaisons(I,J),J=0,NMaxL)
310
        WRITE(*,'(1X,I3," +",I3,":",15(1X,I3))') I, &
311
             (LiaisonsBis(I,J),J=0,NMaxL)
312
     END DO
313
  END IF
314

    
315
! Now, for each frozen atom, we count the length of the frozen block
316
! FrozBlock(I,0) contains the number of frozen atoms forming a frozen
317
!                fragment containing atom I
318
! FrozBlock(I,:) is the list of the frozen atoms of this fragment.
319
  Do I=1,na
320
     FrozBlock(I,0)=-1
321
  END DO
322
  DO I=1,na
323
     IF (FrozAt(I).AND.(FrozBlock(I,0).EQ.-1)) THEN
324
        if (debug) WRITE(*,*) 'Treating atom ',I
325
        FrozBlock(I,0)=1
326
        FrozBlock(I,1)=I
327
        DO J=1,na
328
           DejaFait(J)=.FALSE.
329
        END DO
330
        DejaFait(I)=.TRUE.
331
        DO J=1,LiaisonsBis(I,0)
332
           CaFaire(J)=LiaisonsBis(I,J)
333
        END DO
334
        IdxCaFaire=LiaisonsBis(I,0)+1
335
        CaFaire(IdxCaFaire)=0
336
        IAfaire=1
337
        FCaf=DejaFait
338
        DO WHILE (CaFaire(IAfaire).NE.0)
339
           Iat=CaFaire(IAFAire)
340
           if (debug) WRITE(*,*) 'IaFaire; Iat:', IaFaire, Iat, DejaFait(Iat)
341
           IF (.NOT.DejaFait(Iat)) THEN
342
              FrozBlock(I,0)=FrozBlock(I,0)+1
343
              FrozBlock(I,FrozBlock(I,0))=Iat
344
              DO J=1,LiaisonsBis(Iat,0)
345
                 IF ((.NOT.DejaFait(LiaisonsBis(Iat,J))).AND.(.NOT.FCaf(LiaisonsBis(Iat,J)))) THEN
346
                    CaFaire(IdxCaFaire)=LiaisonsBis(Iat,J)
347
                    IdxCaFaire=IdxCaFaire+1
348
                    CaFaire(IdxCaFaire)=0
349
                    FCaf(LiaisonsBis(Iat,J))=.TRUE.
350
                 END IF
351
              END DO
352
              !     WRITE(*,*) 'liaisonbis(Iat,0),FrozBlick(I,0)',&
353
              !                      LiaisonsBis(Iat,0), FrozBlock(I,0)
354
           END IF
355
           DejaFait(Iat)=.TRUE.
356
           IaFaire=IaFaire+1
357
        END DO
358
        if (debug) WRITE(*,*) 'I,FrozBlock(0),IaFaire',I,FrozBlock(I,0),IaFaire
359
        if (debug) WRITE(*,*) 'FrozBlock:',FrozBlock(I,1:FrozBlock(I,0))
360
        !        FrozBlock(I,1)=I
361
        !        DO J=2,IaFaire
362
        !           FrozBlock(I,J)=CaFaire(J-1)
363
        !        END DO
364
        !     We copy this block into all frozen atoms that belongs to it
365
        DO J=2,Frozblock(I,0)
366
           Iat=FrozBlock(I,J)
367
           DO K=0,FrozBlock(I,0)
368
              FrozBlock(Iat,K)=FrozBlock(I,K)
369
           END DO
370
        END DO
371
     ELSE
372
        IF (.NOT.FrozAt(I))      FrozBlock(I,0)=0
373
     END IF
374
  END DO
375

    
376
  if (debug) THEN
377
     WRITE(*,*) "FrozBlock"
378
     DO I=1,Na
379
        If (FrozAt(I))  WRITE(*,'(1X,I3," -",I3,":",15(1X,I3))') I, &
380
             (FrozBlock(I,J),J=0,FrozBlock(I,0))
381
     END DO
382
  END IF
383

    
384
  DO I=1,NbFrag
385
     FrozFrag(I,1)=0
386
     FrozFrag(I,2)=0
387
     DO J=1,NbAtFrag(I)
388
        IF (FrozAt(FragAt(I,J))) THEN
389
           FrozFrag(I,1)=FrozFrag(I,1)+1
390
           IF (FrozBlock(FragAt(I,J),0).GE.FrozFrag(I,2))  &
391
                FrozFrag(I,2)=FrozBlock(FragAt(I,J),0)
392
           if (FrozFrag(I,3).LE.LiaisonsBis(FragAt(I,J),0))& 
393
                FrozFrag(I,3)=LiaisonsBis(FragAt(I,J),0)
394
        END IF
395
     END DO
396
     IF (debug) WRITE(*,*) 'Frag :',I,FrozFrag(I,1), &
397
          ' frozen atoms,max linked:'  &
398
          ,FrozFrag(I,2),' with at most',FrozFrag(I,3),' frozen'
399
  END DO
400

    
401
  !     We will now build the molecule fragment by fragment
402
  !     First the frozen atoms, then the rest of the fragment
403
  !     We choose the starting fragment with two criteria:
404
  !     1- Number of linked frozen atoms:
405
  !       * >=3 is good as it fully defines the coordinate space
406
  !       * 2 is ok as we can either use a 3rd atom from the same fragment
407
  !       or add a X atom somewhere but this complicates quite a lot the way
408
  !       to treat the conversion from cartesian to zmat latter
409
  !       * 1 is bad...
410
  !     2- Max number of linked frozen atoms
411
  !     this allows us to deal more easily with cases 1- when number of 
412
  !     directly linked frozen atoms is less than 3
413

    
414
  IFrag=0
415
  I0=0
416
  I1=0
417
  DO I=1,NbFrag
418
     SELECT CASE(FrozFrag(I,3)-I0)
419
     CASE (1:)
420
        IFrag=I
421
        I0=FrozFrag(I,3)
422
        I1=FrozFrag(I,2)
423
     CASE (0)
424
        if (FrozFrag(I,2).GT.I1) THEN
425
           IFrag=I
426
           I0=FrozFrag(I,3)
427
           I1=FrozFrag(I,2)
428
        END IF
429
     END SELECT
430
  END DO
431

    
432
  if (debug) WRITE(*,'(1X,A,I5,A,I5,A,I5,A)') 'Starting with fragment:',IFrag,' with ',I0,' frozen linked and overall',I1,' linked'
433

    
434
  !     We will build the first fragment in a special way, as it will
435
  !     set the coordinates system
436
  !     We look for the frozen atom that is linked to the maximum frozen atom,
437
  !     and belongs to the longer fragment
438
  I0=0
439
  I1=0
440
  DO I=1,NbAtFrag(IFrag)
441
     IF (FrozAt(FragAt(IFrag,I))) THEN
442
        SELECT CASE(LiaisonsBis(FragAt(IFrag,I),0)-I0)
443
        CASE (1:) 
444
           IAt=FragAt(IFrag,I)
445
           I0=LiaisonsBis(IAt,0)
446
           I1=FrozBlock(IAt,0)
447
        CASE (0)
448
           IF (FrozBlock(FragAt(IFrag,I),0).GT.I1) THEN
449
              IAt=FragAt(IFrag,I)
450
              I0=LiaisonsBis(Iat,0)
451
              I1=FrozBlock(Iat,0)
452
           END IF
453
        END SELECT
454
     END IF
455
     if (debug) WRITE(*,*) 'DBG: I,FragAt(IFrag,I),IAt,I0,I1',I,FragAt(IFrag,I),IAt,I0,I1
456
  END DO
457

    
458
  if (debug) WRITE(*,*) 'Fragment 1, starting with atom:',IAt,I0,I1
459

    
460
  DO I=1,na
461
     DejaFait(I)=.FALSE.
462
     FCaf(I)=.FALSE.
463
  END DO
464

    
465
  izm=0
466
  SELECT CASE (I0)
467
  CASE(3:)
468
     if (debug) WRITE(*,*) 'DBG select case I0 3'
469
     n0=Iat
470
     !     We search for the fourth atom while making sure that the dihedral angle
471
     !     is not 0 or Pi
472
     ITmp=2
473
     sDihe=0.
474
     n2=IAt
475
     n3=LiaisonsBis(Iat,1)
476
     ! We search for the third atom while making sure that it is not aligned with first two !
477
     DO While ((ITmp.LE.LiaisonsBis(Iat,0)).AND.(sDihe.LE.0.09d0))
478
        n4=LiaisonsBis(Iat,Itmp)
479
        CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
480
        CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
481
        val_d=angle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
482
        sDiHe=abs(sin(val_d*pi/180.d0))
483
        if (debug) Write(*,*) 'Trying n2,n3,n4,sdihe,val_d',n2,n3,n4,sdihe,val_d
484
        Itmp=Itmp+1
485
     END DO
486
     If (debug) WRITE(*,*) 'Itmp,LiaisonsBis',Itmp,LiaisonsBis(Iat,1:NMaxL)
487
     LiaisonsBis(Iat,Itmp-1)=LiaisonsBis(iat,2)
488
     LiaisonsBis(Iat,2)=n4
489
     If (debug) WRITE(*,*) 'Itmp,LiaisonsBis',Itmp,LiaisonsBis(Iat,1:NMaxL)
490

    
491
     if (sDihe.LE.0.09d0) THEN
492
        WRITE(*,*) "Dans le caca car tous les atoms de ce block sont align?s!"
493
     END IF
494

    
495
     CALL produit_vect(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2, &
496
          vx5,vy5,vz5,norm5)
497

    
498

    
499
     Itmp=2
500
     sDiHe=0.
501

    
502
     DO While ((ITmp.LT.LiaisonsBis(Iat,0)).AND.(sDihe.LE.0.09d0))
503
        ITmp=ITmp+1
504
        n1=LiaisonsBis(Iat,Itmp)
505
        if (debug) WRITe(*,*) 'trying n1,n2,n3,n4',n1,n2,n3,n4
506
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
507
        ! Is this atom aligned with n2-n3 ?
508
        val_d=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
509
        sDiHe=abs(sin(val_d*pi/180.d0))
510
        if (debug) Write(*,*) 'Angle n3-n2-n1',val_d
511
        if (sDiHe.le.0.09d0) THEN
512
           ! As atoms n2,n3 and n4 are not aligned, we interchange n3 and n4 so that n1,n2 and n3 are not aligned
513
           if (debug) WRITE(*,*) "n3-n2-n1 aligned, we interchange n3 and n4"
514
           n1=n3
515
           n3=n4
516
           n4=n1
517
           n1=LiaisonsBis(Iat,ITmp)
518
           CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)           
519
           CALL vecteur(n2,n4,x,y,z,vx3,vy3,vz3,norm3)           
520
           val_d=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
521
           if (debug) Write(*,*) 'NEW Angle n3-n2-n1',val_d
522
        END IF
523

    
524
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
525
        ! avant de tester l'angle diedre, il faut verifier que ce 4e atome n'est pas
526
        ! aligne avec les 2 premiers. 
527
        ! comme on a deja test? que les 3 premiers ne sont pas alignes,
528
        ! s'il est align? avec les 2 premiers, on peut inverser le role de 2 et 3.
529
        ! On pourrait tout simplier en faisant une bete recherche parmi tous les atomes geles
530
        ! de ce bloc (au moins 4 ?) avec le critere 1) on les range par distance croissante
531
        ! 2) on les scanne tant que l'angle valence n'est pas bon, puis tant que diehedre pas bon
532
        ! on pourrait comme ca faire un tableau avec les atomes ranges d'abord pour le fragment s?lectionn?
533
        ! puis les atomes des autres fragment par distance croissante.
534
        ! les autres fragments ne seraient additonn?s que si l'on ne trouve pas notre bonheur dans le premier bloc
535
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
536

    
537
        CALL produit_vect(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2, &
538
             vx4,vy4,vz4,norm4)
539
        val_d=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
540
             vx2,vy2,vz2,norm2)
541
        sDihe=abs(sin(val_d*pi/180.d0))
542
        if (debug) WRITE(*,*) 'n2,n3,n4,n1, angle_d',n2,n3,n4,n1,val_d
543
     END DO
544

    
545
     DejaFait(n2)=.TRUE.
546
     DejaFait(n3)=.TRUE.
547
     DejaFait(n4)=.TRUE.
548

    
549
     if (sDihe.LE.0.09d0) THEN
550
        !     None of the frozen atoms linked to IAt are good to define the third
551
        !     direction in space...
552
        !     We will look at the other frozen atoms
553
        !     we might improve the search so as to take the atom closest to IAt
554
        if (debug) WRITE(*,*) "All atoms linked to ",Iat," are in a plane. Looking for other frozen atoms"
555
        ITmp=0
556
        DO I=1,NbAtFrag(IFrag)
557
           JAt=FragAt(IFrag,I)
558
           if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
559
              n1=JAt
560
              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
561
              CALL produit_vect(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2, &
562
                   vx4,vy4,vz4,norm4)
563
              val_d=angle_d(vx4,vy4,vz4,norm4, &
564
                   vx5,vy5,vz5,norm5, &
565
                   vx2,vy2,vz2,norm2)
566
              if (abs(sin(val_d)).GE.0.09D0) THEN
567
                 ITmp=ITmp+1
568
                 DistFroz(ITmp)=Norm1
569
                 FrozDist(ITmp)=JAt
570
              END IF
571
           END IF
572
        END DO
573
        IF (ITmp.EQ.0) THEN
574
           !     All dihedral angles between frozen atoms are less than 5?
575
           !     (or more than 175?). We have to look at other fragments :-(
576
           DO I=1,NFroz
577
              Jat=Frozen(I)
578
              if (.NOT.DejaFait(JAt)) THEN
579
                 n1=JAt
580
                 CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
581
                 CALL produit_vect(vx1,vy1,vz1,norm1, &
582
                      vx2,vy2,vz2,norm2, &
583
                      vx4,vy4,vz4,norm4)
584
                 val_d=angle_d(vx4,vy4,vz4,norm4, &
585
                      vx5,vy5,vz5,norm5, &
586
                      vx2,vy2,vz2,norm2)
587
                 if (abs(sin(val_d)).GE.0.09D0) THEN
588
                    ITmp=ITmp+1
589
                    DistFroz(ITmp)=Norm1
590
                    FrozDist(ITmp)=JAt
591
                 END IF
592
              END IF
593
           END DO
594
           IF (ITmp.EQ.0) THEN
595
              !     All frozen atoms are in a plane... too bad
596
              WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
597
              WRITE(*,*) 'For now, I do not treat this case'
598
              STOP
599
           END IF
600
        END IF
601
        I1=0
602
        d=1e9
603
        DO I=1,ITmp
604
           IF (DistFroz(I).LE.d) THEN
605
              d=DistFroz(I)
606
              I1=FrozDist(I)
607
           END IF
608
        END DO
609
     ELSE                !(sDihe.LE.0.09d0)
610
        I1=FrozBlock(IAt,ITmp)
611
        if (debug) WRITE(*,*) 'I1,n1:',I1,n1
612
     END IF                 !(sDihe.LE.0.09d0)
613
     !     we now have the atom that is closer to the first one and that
614
     !     forms a non 0/Pi dihedral angle
615

    
616
     ind_zmat(1,1)=n2
617
     ind_zmat(2,1)=n3
618
     ind_zmat(2,2)=n2
619
     ind_zmat(3,1)=n4
620
     ind_zmat(3,2)=n2
621
     ind_zmat(3,3)=n3
622
     DejaFait(n2)=.TRUE.
623
     DejaFait(n3)=.TRUE.
624
     DejaFait(n4)=.TRUE.
625
     CaFaire(1)=n3
626
     CaFaire(2)=n4
627

    
628
     ind_zmat(4,1)=I1
629
     ind_zmat(4,2)=n2
630
     ind_zmat(4,3)=n3
631
     ind_zmat(4,4)=n4
632
     DejaFait(I1)=.TRUE.
633
     CaFaire(3)=I1
634
     CaFaire(4)=0
635
     IdxCaFaire=4
636

    
637
     FCaf(n2)=.TRUE.
638
     FCaf(n3)=.TRUE.
639
     FCaf(I1)=.TRUE.
640
     izm=4
641
     DO I=3,LiaisonsBis(Iat,0)
642
        IF (.NOT.DejaFait(LiaisonsBis(Iat,I))) THEN
643
           izm=izm+1
644
           !           ind_zmat(izm,1)=LiaisonsBis(Iat,I)
645
           !           ind_zmat(izm,2)=n2
646
           !           ind_zmat(izm,3)=n3
647
           !           ind_zmat(izm,4)=n4
648
           Call add2indzmat(na,izm,LiaisonsBis(Iat,I),n2,n3,n4,ind_zmat,x,y,z)
649
           IF (.NOT.FCaf(LiaisonsBis(Iat,I))) THEN
650
              CaFaire(IdxCaFaire)=LiaisonsBis(Iat,I)
651
              IdxCaFaire=IdxCaFaire+1
652
              CaFaire(IdxCaFaire)=0
653
              FCaf(LiaisonsBis(Iat,I))=.TRUE.
654
           END IF
655
           DejaFait(LiaisonsBis(Iat,I))=.TRUE.
656
        END IF
657
     END DO
658

    
659
     if (debug) THEN
660
        WRITE(*,*) "Ind_zmat 0 - SELECT CASE I0 3: -- izm=",izm
661
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
662
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
663
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
664
        DO I=4,izm
665
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
666
                ind_zmat(I,3), ind_zmat(I,4)
667
        END DO
668
     END IF
669

    
670

    
671
     !     First four atoms (at least) have been put we go on with next parts
672
     !     of this fragment... later
673

    
674

    
675
  CASE(2)
676
     if (debug) WRITE(*,*) 'DBG select case I0 2'
677
     if (debug) WRITE(*,*) 'ATTENTION For now, case with only 3 frozen atoms non treated'
678
     ind_zmat(1,1)=IAt
679
     ind_zmat(2,1)=liaisonsBis(IAt,1)
680
     ind_zmat(2,2)=IAt
681
     ind_zmat(3,1)=LiaisonsBis(IAt,2)
682
     ind_zmat(3,2)=IAt
683
     ind_zmat(3,3)=LiaisonsBis(IAt,1)
684
     DejaFait(IAt)=.TRUE.
685
     DejaFait(LiaisonsBis(Iat,1))=.TRUE.
686
     DejaFait(LiaisonsBis(Iat,2))=.TRUE.
687
     CaFaire(1)=LiaisonsBis(Iat,1)
688
     CaFaire(2)=LiaisonsBis(Iat,2)
689
     FCaf(LiaisonsBis(Iat,1))=.TRUE.
690
     FCaf(LiaisonsBis(Iat,2))=.TRUE.
691

    
692
     !     We search for a fourth atom, first in the FrozBlock atoms
693
     ITmp=2
694
     sDihe=0.
695
     n2=IAt
696
     n3=LiaisonsBis(Iat,1)
697
     n4=LiaisonsBis(Iat,2)
698
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
699
     CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
700
     CALL produit_vect(vx3,vy3,vz3,norm3, &
701
          vx2,vy2,vz2,norm2, &
702
          vx5,vy5,vz5,norm5)
703

    
704
     DO While ((ITmp.LE.FrozBlock(Iat,0)).AND.(sDihe.LE.0.09d0))
705
        ITmp=ITmp+1
706
        n1=FrozBlock(Iat,Itmp)
707
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
708
        CALL produit_vect(vx1,vy1,vz1,norm1, &
709
             vx2,vy2,vz2,norm2, &
710
             vx4,vy4,vz4,norm4)
711
        val_d=angle_d(vx4,vy4,vz4,norm4,  &
712
             vx5,vy5,vz5,norm5,           &
713
             vx2,vy2,vz2,norm2)
714
        sDihe=abs(sin(val_d))
715
     END DO
716
     IF (debug) WRITE(*,*) 'DBG 4th atom, ITmp, sDihe',ITmp, sDihe
717
     if (sDihe.LE.0.09d0) THEN
718
        !     None of the frozen atoms linked to IAt are good to define the third
719
        !     direction in space...
720
        !     We will look at the other frozen atoms
721
        !     we might improve the search so as to take the atom closest to IAt
722
        ITmp=0
723
        DO I=1,NbAtFrag(IFrag)
724
           JAt=FragAt(IFrag,I)
725
           if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
726
              n1=JAt
727
              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
728
              CALL produit_vect(vx1,vy1,vz1,norm1,  &
729
                   vx2,vy2,vz2,norm2,               &
730
                   vx4,vy4,vz4,norm4)
731
              val_d=angle_d(vx4,vy4,vz4,norm4,    &
732
                   vx5,vy5,vz5,norm5,              &
733
                   vx2,vy2,vz2,norm2)
734
              if (abs(sin(val_d)).GE.0.09D0) THEN
735
                 ITmp=ITmp+1
736
                 DistFroz(ITmp)=Norm1
737
                 FrozDist(ITmp)=JAt
738
              END IF
739
           END IF
740
        END DO
741
        IF (ITmp.EQ.0) THEN
742
           !     All dihedral angles between frozen atoms are less than 5?
743
           !     (or more than 175?). We have to look at other fragments :-(
744
           DO I=1,NFroz
745
              Jat=Frozen(I)
746
              if (.NOT.DejaFait(JAt)) THEN
747
                 n1=JAt
748
                 CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
749
                 CALL produit_vect(vx1,vy1,vz1,norm1,   &
750
                      vx2,vy2,vz2,norm2,                 &
751
                      vx4,vy4,vz4,norm4)
752
                 val_d=angle_d(vx4,vy4,vz4,norm4,       &
753
                      vx5,vy5,vz5,norm5,                 &
754
                      vx2,vy2,vz2,norm2)
755
                 if (abs(sin(val_d)).GE.0.09D0) THEN
756
                    ITmp=ITmp+1
757
                    DistFroz(ITmp)=Norm1
758
                    FrozDist(ITmp)=JAt
759
                 END IF
760
              END IF
761
           END DO
762
           IF (ITmp.EQ.0) THEN
763
              !     All frozen atoms are in a plane... too bad
764
              WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
765
              WRITE(*,*) 'For now, I do not treat this case'
766
              STOP
767
           END IF
768
        END IF
769
        I1=0
770
        d=1e9
771
        DO I=1,ITmp
772
           IF (DistFroz(I).LE.d) THEN
773
              d=DistFroz(I)
774
              I1=FrozDist(I)
775
           END IF
776
        END DO
777
     ELSE                   !(sDihe.LE.0.09d0)
778
        I1=FrozBlock(IAt,ITmp)
779
     END IF                 !(sDihe.LE.0.09d0)
780
     !     we now have the atom that is closer to the first one and that
781
     !     forms a non 0/Pi dihedral angle
782
     !     ind_zmat(4,1)=I1
783
     !     ind_zmat(4,2)=IAt
784
     !     ind_zmat(4,3)=LiaisonsBis(Iat,1)
785
     !     ind_zmat(4,4)=LiaisonsBis(Iat,2)
786
     n3=LiaisonsBis(Iat,1)
787
     n4=LiaisonsBis(Iat,2)
788
     Call add2indzmat(na,4,I1,Iat,n3,n4,ind_zmat,x,y,z)
789
     LiaisonsBis(Iat,1)=n3
790
     LiaisonsBis(Iat,2)=n4
791
     DejaFait(I1)=.TRUE.
792
     CaFaire(3)=I1
793
     CaFaire(4)=0
794
     IdxCaFaire=4
795
     izm=4
796
     FCaf(I1)=.TRUE.
797

    
798
  CASE(1)
799
     if (debug) WRITE(*,*) 'DBG select case I0 1'
800
     ind_zmat(1,1)=IAt
801
     ind_zmat(2,1)=liaisonsBis(IAt,1)
802
     ind_zmat(2,2)=IAt
803
     DejaFait(IAt)=.TRUE.
804
     DejaFait(LiaisonsBis(Iat,1))=.TRUE.
805
     IdxCaFaire=2
806
     CaFaire(1)=LiaisonsBis(Iat,1)
807
     CaFaire(2)=0
808
     FCaf(LiaisonsBis(Iat,1))=.TRUE.
809

    
810
     !     We search for a third and fourth atoms, first in the FrozBlock atoms
811
     !     It should not be possible to have   (FrozBlock(Iat,0).GT.2) and
812
     !     iat linked to only one atom !       
813

    
814
     IF (FrozBlock(Iat,0).GT.2) THEN
815
        WRITE(*,*) 'I found some inconsistancy: IAt linked to 1'
816
        WRITE(*,*) 'Atom only, but belongs to a frozblock of at '
817
        WRITE(*,*) 'least 3 atoms. IAt, FrozBlock'
818
        WRITE(*,*) Iat,(FrozBlock(IAt,J),J=0,FrozBlock(Iat,0))
819
        STOP
820
     END IF
821

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

    
826
     ITmp=0
827
     CALL vecteur(LiaisonsBis(Iat,1),IAt,x,y,z,vx2,vy2,vz2,norm2)
828

    
829
     DO I=1,NbAtFrag(IFrag)
830
        JAt=FragAt(IFrag,I)
831
        if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
832
           CALL vecteur(JAt,IAt,x,y,z,vx1,vy1,vz1,norm1)
833
           if (abs(cos(angle(vx1,vy1,vz1,norm1,  &
834
                vx2,vy2,vz2,norm2))).LE.0.996d0) THEN
835
              ITmp=ITmp+1
836
              DistFroz(ITmp)=Norm1
837
              FrozDist(ITmp)=JAt
838
           END IF
839
        END IF
840
     END DO
841

    
842
     IF (ITMP.EQ.0) THEN
843
        !     We have no frozen atoms correct in this fragment, we use
844
        !     atoms from other fragments
845
        DO I=1,NFroz
846
           Jat=Frozen(I)
847
           if (.NOT.DejaFait(JAt)) THEN
848
              CALL vecteur(JAt,IAt,x,y,z,vx1,vy1,vz1,norm1)
849
              if (abs(cos(angle(vx1,vy1,vz1,norm1, &
850
                   vx2,vy2,vz2,norm2))).LE.0.996d0) THEN
851
                 ITmp=ITmp+1
852
                 DistFroz(ITmp)=Norm1
853
                 FrozDist(ITmp)=JAt
854
              END IF
855
           END IF
856
        END DO
857
        IF (ITMP.EQ.0) THEN
858
           WRITE(*,*) 'It seems all frozen atoms are aligned'
859
           WRITE(*,*) 'Case non treated for now :-( '
860
           STOP
861
        END IF
862
     END IF
863

    
864
     I1=0
865
     d=1e9
866
     DO I=1,ITmp
867
        IF (DistFroz(I).LE.d) THEN
868
           I1=FrozDist(I)
869
           d=DistFroz(I)
870
        END IF
871
     END DO
872

    
873
     !     we now have the atom that is closer to the first one and that
874
     !     forms a non 0/Pi valence angle
875
     ind_zmat(3,1)=I1
876
     ind_zmat(3,2)=IAt
877
     ind_zmat(3,3)=LiaisonsBis(Iat,1)
878
     DejaFait(I1)=.TRUE.
879
     CaFaire(2)=I1
880
     FCaf(I1)=.TRUE.
881

    
882

    
883
     !     we search for a fourth atom !
884
     !     We search for a fourth atom, first in the FrozBlock atoms
885
     ITmp=2
886
     sDihe=0.
887
     n2=IAt
888
     n3=LiaisonsBis(Iat,1)
889
     n4=I1
890
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
891
     CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
892
     CALL produit_vect(vx3,vy3,vz3,norm3,  &
893
          vx2,vy2,vz2,norm2,    &
894
          vx5,vy5,vz5,norm5)
895

    
896
     !     We will look at the other frozen atoms
897
     !     we might improve the search so as to take the atom closest to IAt
898
     ITmp=0
899
     DO I=1,NbAtFrag(IFrag)
900
        JAt=FragAt(IFrag,I)
901
        if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
902
           n1=JAt
903
           CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
904
           CALL produit_vect(vx1,vy1,vz1,norm1, &
905
                vx2,vy2,vz2,norm2, &
906
                vx4,vy4,vz4,norm4)
907
           val_d=angle_d(vx4,vy4,vz4,norm4,  &
908
                vx5,vy5,vz5,norm5,   &
909
                vx2,vy2,vz2,norm2)
910
           if (abs(sin(val_d)).GE.0.09D0) THEN
911
              ITmp=ITmp+1
912
              DistFroz(ITmp)=Norm1
913
              FrozDist(ITmp)=JAt
914
           END IF
915
        END IF
916
     END DO
917
     IF (ITmp.EQ.0) THEN
918
        !     All dihedral angles between frozen atoms are less than 5?
919
        !     (or more than 175?). We have to look at other fragments :-(
920
        DO I=1,NFroz
921
           Jat=Frozen(I)
922
           if (.NOT.DejaFait(JAt)) THEN
923
              n1=JAt
924
              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
925
              CALL produit_vect(vx1,vy1,vz1,norm1,  &
926
                   vx2,vy2,vz2,norm2, &
927
                   vx4,vy4,vz4,norm4)
928
              val_d=angle_d(vx4,vy4,vz4,norm4,   &
929
                   vx5,vy5,vz5,norm5,           &
930
                   vx2,vy2,vz2,norm2)
931
              if (abs(sin(val_d)).GE.0.09D0) THEN
932
                 ITmp=ITmp+1
933
                 DistFroz(ITmp)=Norm1
934
                 FrozDist(ITmp)=JAt
935
              END IF
936
           END IF
937
        END DO
938
        IF (ITmp.EQ.0) THEN
939
           !     All frozen atoms are in a plane... too bad
940
           WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
941
           WRITE(*,*) 'For now, I do not treat this case'
942
           STOP
943
        END IF
944
     END IF                 ! ITmp.EQ.0 after scaning fragment
945
     I1=0
946
     d=1e9
947
     DO I=1,ITmp
948
        IF (DistFroz(I).LE.d) THEN
949
           d=DistFroz(I)
950
           I1=FrozDist(I)
951
        END IF
952
     END DO
953

    
954
     !     we now have the atom that is closer to the first one and that
955
     !     forms a non 0/Pi dihedral angle
956
     !     ind_zmat(4,1)=I1
957
     !     ind_zmat(4,2)=IAt
958
     !     ind_zmat(4,3)=ind_zmat(2,1)
959
     !     ind_zmat(4,4)=ind_zmat(3,1)
960
     n3=ind_zmat(2,1)
961
     n4=ind_zmat(3,1)
962
     Call add2indzmat(na,4,I1,IAt,n3,n4,ind_zmat,x,y,z)
963
     ind_zmat(2,1)=n3
964
     ind_zmat(3,1)=n4
965
     DejaFait(I1)=.TRUE.
966
     CaFaire(3)=I1
967
     CaFaire(4)=0
968
     IdxCaFaire=4
969
     izm=4
970
     FCaf(I1)=.TRUE.
971

    
972
  CASE(0)
973
     WRITE(*,*) 'All frozen atoms are separated .. '
974
     WRITE(*,*) 'this case should be treated separately !'
975
     STOP
976
  END SELECT
977

    
978
  if (debug) THEN
979
     WRITE(*,*) 'ind_zmat 1'
980
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
981
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
982
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
983
     DO I=4,izm
984
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
985
             ind_zmat(I,3), ind_zmat(I,4)
986
     END DO
987
  END IF
988

    
989
  DO I=1,izm
990
     Idx_zmat(ind_zmat(I,1))=i
991
  END Do
992

    
993
  !     at least first four (frozen) atoms of this fragment done...
994
  !     we empty the 'cafaire' array before pursuing
995
  IAFaire=1
996
  DO WHILE (CaFaire(IaFaire).NE.0)
997
     n1=CaFaire(IaFaire)
998
     n2=ind_zmat(idx_zmat(N1),2)
999
     if (idx_zmat(N1).EQ.2) THEN
1000
        !     We have a (small) problem: we have to add atoms linked to the 2nd
1001
        !     atom of the zmat. This is a pb because we do not know
1002
        !     which atom to use to define the dihedral angle
1003
        !     we take the third atom of the zmat
1004
        n3=ind_zmat(3,1)
1005
     ELSE
1006
        n3=ind_zmat(idx_zmat(n1),3)
1007
     END IF
1008
     IF (LiaisonsBis(n1,0).GE.1) THEN
1009
        IAt=LiaisonsBis(n1,1)
1010
        if (.NOT.DejaFait(Iat)) THEN
1011
           izm=izm+1
1012
           if (debug) WRITE(*,*) ">0< Adding atom ",Iat,"position izm=",izm
1013
           !           ind_zmat(izm,1)=iat
1014
           !           ind_zmat(izm,2)=n1
1015
           !           ind_zmat(izm,3)=n2
1016
           !           ind_zmat(izm,4)=n3
1017
           Call add2indzmat(na,izm,iat,n1,n2,n3,ind_zmat,x,y,z)
1018
           Idx_zmat(iat)=izm
1019
           n3=iat
1020
           IF (.NOT.FCaf(Iat)) THEN
1021
              CaFaire(IdxCaFaire)=iat
1022
              IdxCaFaire=IdxCaFaire+1
1023
              CaFaire(IdxCaFaire)=0
1024
              FCaf(Iat)=.TRUE.
1025
           END IF
1026
           DejaFait(iat)=.TRUE.
1027
        END IF
1028
     END IF
1029
     DO I=2,LiaisonsBis(n1,0)
1030
        IAt=LiaisonsBis(n1,I)
1031
! PFL 29.Aug.2008 ->
1032
! We dissociate the test on 'DejaFait' that indicates that this atom
1033
! has already been put in the Zmat
1034
! from the test on FCaf that indicates that this atom has been put in the
1035
! 'CAFaire' list that deals with identifying its connectivity.
1036
! Those two test might differ for a frozen atom linked to non frozen atoms.
1037
        IF (.NOT.DejaFait(Iat)) THEN
1038
           izm=izm+1
1039
           if (debug) WRITE(*,*) ">1< Adding atom ",Iat,"position izm=",izm
1040
           !           ind_zmat(izm,1)=iat
1041
           !           ind_zmat(izm,2)=n1
1042
           !           ind_zmat(izm,3)=n2
1043
           !           ind_zmat(izm,4)=n3
1044
           Call add2indzmat(na,izm,iat,n1,n2,n3,ind_zmat,x,y,z)
1045
           idx_zmat(iat)=izm
1046
           DejaFait(iat)=.TRUE.
1047
        END IF
1048
        IF (.NOT.FCaf(Iat)) THEN
1049
           CaFaire(IdxCaFaire)=iat
1050
           IdxCaFaire=IdxCaFaire+1
1051
           CaFaire(IdxCaFaire)=0
1052
           FCaf(Iat)=.TRUE.
1053
        END IF
1054
! <- PFL 29.Aug.2008
1055
     END DO
1056
     IaFaire=IaFaire+1
1057
  END Do                    ! DO WHILE CaFaire
1058

    
1059
  if (debug) THEN
1060
     WRITE(*,*) 'ind_zmat 2, izm=',izm
1061
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1062
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1063
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1064
     DO I=4,izm
1065
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
1066
             ind_zmat(I,3), ind_zmat(I,4)
1067
     END DO
1068
  END IF
1069

    
1070
  !     We have finished putting atoms linked to the first one
1071
  !     we will add other frozen atoms of this fragment
1072
  DO I=1,NbAtFrag(IFrag)
1073
     Iat=FragAt(IFrag,I)
1074
     if (debug) WRITE(*,*) "DBG: I,Iat,Frozat,dejafait,frozbloc",I,Iat,FrozAt(Iat), DejaFait(Iat),FrozBlock(Iat,0)
1075
     IF (FrozAt(Iat).AND.(.NOT.DejaFait(Iat))) THEN
1076
        !     in order to have the zmat as connected as possible,
1077
        !     we look if this atom belongs to a frozblock
1078
        if (debug) WRITE(*,*) 'Treating atom I,Iat, FrozBlock ',I,Iat, FrozBlock(Iat,0)
1079
        IF (FrozBlock(Iat,0).EQ.1) THEN
1080
           !     it is a lonely atom :-)
1081
           d=1e9
1082
           DO J=1,izm
1083
              Call vecteur(iat,ind_zmat(j,1),x,y,z,vx1,vy1,vz1,norm1)
1084
              if (norm1.le.d) THEN
1085
                 Jat=j
1086
                 d=norm1
1087
              END IF
1088
           END DO
1089
           n2=ind_zmat(jat,1)
1090
           SELECT CASE(jat)
1091
           CASE (1)
1092
              n3=ind_zmat(2,1)
1093
              n4=ind_zmat(3,1)
1094
           CASE (2)
1095
              n3=ind_zmat(1,1)
1096
              n4=ind_zmat(3,1)
1097
           CASE DEFAULT
1098
              n3=ind_zmat(jAt,2)
1099
              n4=ind_zmat(jat,3)
1100
           END SELECT
1101
           izm=izm+1
1102
           !           ind_zmat(izm,1)=iat
1103
           !           ind_zmat(izm,2)=n2
1104
           !           ind_zmat(izm,3)=n3
1105
           !           ind_zmat(izm,4)=n4
1106
           Call add2indzmat(na,izm,iat,n2,n3,n4,ind_zmat,x,y,z)
1107
           DejaFait(iat)=.TRUE.
1108
           idx_zmat(iat)=iat
1109
        ELSE        !(FrozBlock(Iat,0).EQ.1)
1110
           !     we have a group of atoms
1111
           !     We search for the atom of the group with the most links
1112
           ITmp=-1
1113
           DO J=1,FrozBlock(Iat,0)
1114
              Jat=FrozBlock(Iat,J)
1115
              IF ((.NOT.DejaFait(Jat)).AND.  &
1116
                   (LiaisonsBis(Jat,0).GT.ITMP)) THEN
1117
                 JL=Jat
1118
                 ITmp=LiaisonsBis(Jat,0)
1119
              END IF
1120
           END DO
1121
           if (debug) WRITE(*,*) 'JL,ITmp:',JL,ITmp
1122
           Iat=JL
1123
           d=1e9
1124
           DO J=1,izm
1125
              Call vecteur(iat,ind_zmat(j,1),x,y,z, vx1,vy1,vz1,norm1)
1126
              if (norm1.le.d) THEN
1127
                 Jat=j
1128
                 d=norm1
1129
              END IF
1130
           END DO
1131
           if (debug) WRITE(*,*) 'Jat,d:',Jat,d
1132
           n2=ind_zmat(jat,1)
1133
           SELECT CASE(jat)
1134
           CASE (1)
1135
              n3=ind_zmat(2,1)
1136
              n4=ind_zmat(3,1)
1137
           CASE (2)
1138
              n3=ind_zmat(1,1)
1139
              n4=ind_zmat(3,1)
1140
           CASE DEFAULT
1141
              n3=ind_zmat(jAt,2)
1142
              n4=ind_zmat(jat,3)
1143
           END SELECT
1144
           izm=izm+1
1145
           !           ind_zmat(izm,1)=iat
1146
           !           ind_zmat(izm,2)=n2
1147
           !           ind_zmat(izm,3)=n3
1148
           !           ind_zmat(izm,4)=n4
1149
           Call add2indzmat(na,izm,iat,n2,n3,n4,ind_zmat,x,y,z)
1150
           idx_zmat(iat)=izm
1151
           DejaFait(iat)=.TRUE.
1152
           IdxCaFaire=2
1153
           CaFaire(1)=iat
1154
           CaFaire(2)=0
1155
           FCaf(Iat)=.TRUE.
1156

    
1157
           if (debug) WRITE(*,*) izm,iat,n2,n3,n4
1158

    
1159
           IaFaire=1
1160
           DO WHILE (CaFaire(IaFaire).NE.0)
1161
              n1=CaFaire(IaFaire)
1162
              n2=ind_zmat(idx_zmat(N1),2)
1163
              if (debug) WRITE(*,*) 'DBG Cafaire, Iafaire,n1,n2',Iafaire,n1,n2
1164
              if (idx_zmat(N1).EQ.2) THEN
1165
                 !     We have a (small) problem: we have to add atoms linked to the 2nd
1166
                 !     atom of the zmat. This is a pb because we do not know
1167
                 !     which atom to use to define the dihedral angle
1168
                 !     we take the third atom of the zmat
1169
                 n3=ind_zmat(3,1)
1170
              ELSE
1171
                 n3=ind_zmat(idx_zmat(n1),3)
1172
              END IF
1173
              if (debug) WRITe(*,*) 'DBG :n3,liaisonBis',n3,LiaisonsBis(n1,0)
1174
              DO I3=1,LiaisonsBis(n1,0)
1175
! PFL 29.Aug.2008 ->
1176
! We dissociate the test on 'DejaFait' that indicates that this atom
1177
! has already been put in the Zmat
1178
! from the test on FCaf that indicates that this atom has been put in the
1179
! 'CAFaire' list that deals with identifying its connectivity.
1180
! Those two test might differ for a frozen atom linked to non frozen atoms.
1181
                 IAt=LiaisonsBis(n1,I3)
1182
                 if (.NOT.DejaFait(Iat)) THEN
1183
                    izm=izm+1
1184
                    !                 ind_zmat(izm,1)=iat
1185
                    !                 ind_zmat(izm,2)=n1
1186
                    !                 ind_zmat(izm,3)=n2
1187
                    !                 ind_zmat(izm,4)=n3
1188
                    Call add2indzmat(na,izm,iat,n1,n2,n3,ind_zmat,x,y,z)
1189
                    idx_zmat(iat)=izm
1190
                    if (I3.EQ.1) n3=ind_zmat(izm,1)
1191
                    DejaFait(Iat)=.TRUE.
1192
                 END IF
1193
                 If (.NOT.FCaf(Iat)) THEN
1194
                    CaFaire(IdxCaFaire)=iat
1195
                    IdxCaFaire=IdxCaFaire+1
1196
                    CaFaire(IdxCaFaire)=0
1197
                    FCaf(Iat)=.TRUE.
1198
                 END IF
1199
! <- PFL 29.Aug.2008
1200
              END DO
1201
              IaFaire=IaFaire+1
1202
           END Do           ! DO WHILE CaFaire
1203
        END IF
1204
     END IF
1205
     if (debug) THEN
1206
        WRITE(*,*) 'ind_zmat 3'
1207
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1208
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1209
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1210
        DO Ip=4,izm
1211
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), ind_zmat(Ip,2),  &
1212
                ind_zmat(Ip,3), ind_zmat(Ip,4)
1213
        END DO
1214
     END IF
1215

    
1216
  END DO
1217

    
1218
  FrozFrag(IFrag,1)=-1
1219
  FrozFrag(IFrag,2)=-1
1220
  FrozFrag(IFrag,3)=-1
1221

    
1222
  !     we start again with the rest of the molecule...
1223
  ! v 1.01 We add the fragment in the order corresponding to FrozFrag
1224
  KMax=0
1225
  DO I=1,NbFrag
1226
     IF (FrozFrag(I,1).NE.0) KMax=KMax+1
1227
  END DO
1228

    
1229
  IF (DEBUG) WRITE(*,*) "Adding the",Kmax,"fragments with frozen atoms"
1230
  DO K=1, KMax-1
1231
     IFrag=0
1232
     I0=0
1233
     I1=0
1234
     DO I=1,NbFrag
1235
        SELECT CASE(FrozFrag(I,3)-I0)
1236
        CASE (1:)
1237
           IFrag=I
1238
           I0=FrozFrag(I,3)
1239
           I1=FrozFrag(I,2)
1240
        CASE (0)
1241
           if (FrozFrag(I,2).GT.I1) THEN
1242
              IFrag=I
1243
              I0=FrozFrag(I,3)
1244
              I1=FrozFrag(I,2)
1245
           END IF
1246
        END SELECT
1247
     END DO
1248

    
1249
     FrozFrag(IFrag,1)=-1
1250
     FrozFrag(IFrag,2)=-1
1251
     FrozFrag(IFrag,3)=-1
1252

    
1253
     if (debug) WRITE(*,*) "Adding Fragment ",IFrag,K
1254

    
1255
     DO I=1,NbAtFrag(IFrag)
1256
        Iat=FragAt(IFrag,I)
1257
        IF (FrozAt(Iat).AND.(.NOT.DejaFait(Iat))) THEN
1258
           !     in order to have the zmat as connected as possible,
1259
           !     we look if this atom belongs to a frozblock
1260
           IF (FrozBlock(Iat,0).EQ.1) THEN
1261
              !     it is a lonely atom :-)
1262
              if (debug) write(*,*) "DBG 4: Lonely atom",Iat
1263
              d=1e9
1264
              DO J=1,izm
1265
                 Call vecteur(iat,ind_zmat(j,1),x,y,z,vx1,vy1,vz1,norm1)
1266
                 if (norm1.le.d) THEN
1267
                    Jat=j
1268
                    d=norm1
1269
                 END IF
1270
              END DO
1271
              n2=ind_zmat(jat,1)
1272
              SELECT CASE(jat)
1273
              CASE (1)
1274
                 n3=ind_zmat(2,1)
1275
                 n4=ind_zmat(3,1)
1276
              CASE (2)
1277
                 n3=ind_zmat(1,1)
1278
                 n4=ind_zmat(3,1)
1279
              CASE DEFAULT
1280
                 n3=ind_zmat(jAt,2)
1281
                 n4=ind_zmat(jat,3)
1282
              END SELECT
1283
              izm=izm+1
1284
              !              ind_zmat(izm,1)=iat
1285
              !              ind_zmat(izm,2)=n2
1286
              !              ind_zmat(izm,3)=n3
1287
              !              ind_zmat(izm,4)=n4
1288
              Call add2indzmat(na,izm,iat,n2,n3,n4,ind_zmat,x,y,z)
1289
              idx_zmat(iat)=izm
1290
              DejaFait(iat)=.TRUE.
1291
           ELSE
1292
              !     we have a group of atoms
1293
              !     We search for the atom of the group with the most links
1294
              if (debug) write(*,*) "DBG 4b: ",Iat," belong to frozblock",FrozBlock(Iat,0)
1295
              ITmp=-1
1296
              DO J=1,FrozBlock(Iat,0)
1297
                 Jat=FrozBlock(Iat,J)
1298
                 IF ((.NOT.DejaFait(Jat)).AND.         &
1299
                      (LiaisonsBis(Jat,0).GT.ITMP)) THEN
1300
                    JL=Jat
1301
                    ITmp=LiaisonsBis(Jat,0)
1302
                 END IF
1303
              END DO
1304
              Iat=JL
1305
              d=1e9
1306
              DO J=1,izm
1307
                 Call vecteur(iat,ind_zmat(j,1),x,y,z,vx1,vy1,vz1,norm1)
1308
                 if (norm1.le.d) THEN
1309
                    Jat=j
1310
                    d=norm1
1311
                 END IF
1312
              END DO
1313
              n2=ind_zmat(jat,1)
1314
              SELECT CASE(jat)
1315
              CASE (1)
1316
                 n3=ind_zmat(2,1)
1317
                 n4=ind_zmat(3,1)
1318
              CASE (2)
1319
                 n3=ind_zmat(1,1)
1320
                 n4=ind_zmat(3,1)
1321
              CASE DEFAULT
1322
                 n3=ind_zmat(jAt,2)
1323
                 n4=ind_zmat(jat,3)
1324
              END SELECT
1325
              izm=izm+1
1326
              !              ind_zmat(izm,1)=iat
1327
              !              ind_zmat(izm,2)=n2
1328
              !              ind_zmat(izm,3)=n3
1329
              !              ind_zmat(izm,4)=n4
1330
              Call add2indzmat(na,izm,Iat,n2,n3,n4,ind_zmat,x,y,z)
1331
              idx_zmat(iat)=izm
1332
              DejaFait(iat)=.TRUE.
1333
              IdxCaFaire=2
1334
              CaFaire(1)=iat
1335
              CaFaire(2)=0
1336
              FCaf(Iat)=.TRUE.
1337
              IaFaire=1
1338
              DO WHILE (CaFaire(IaFaire).NE.0)
1339
                 n1=CaFaire(IaFaire)
1340
                 n2=ind_zmat(idx_zmat(N1),2)
1341
                 if (idx_zmat(N1).EQ.2) THEN
1342
                    !     We have a (small) problem: we have to add atoms linked to the 2nd
1343
                    !     atom of the zmat. This is a pb because we do not know
1344
                    !     which atom to use to define the dihedral angle
1345
                    !     we take the third atom of the zmat
1346
                    n3=ind_zmat(3,1)
1347
                 ELSE
1348
                    n3=ind_zmat(idx_zmat(n1),3)
1349
                 END IF
1350
                 DO I3=1,LiaisonsBis(n1,0)
1351
                    IAt=LiaisonsBis(n1,I3)
1352
! PFL 29.Aug.2008 ->
1353
! We dissociate the test on 'DejaFait' that indicates that this atom
1354
! has already been put in the Zmat
1355
! from the test on FCaf that indicates that this atom has been put in the
1356
! 'CAFaire' list that deals with identifying its connectivity.
1357
! Those two test might differ for a frozen atom linked to non frozen atoms.
1358
                    IF (.NOT.DejaFait(Iat)) THEN
1359
                       izm=izm+1
1360
                       Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1361
                       idx_zmat(iat)=izm
1362
                       n3=iat
1363
                       DejaFait(Iat)=.TRUE.
1364
                    END IF
1365
                    IF (.NOT.FCaf(Iat)) THEN
1366
                       CaFaire(IdxCaFaire)=iat
1367
                       IdxCaFaire=IdxCaFaire+1
1368
                       CaFaire(IdxCaFaire)=0
1369
                       FCaf(Iat)=.TRUE.
1370
                    END IF
1371
! <- PFL 29.Aug.2008
1372
                 END DO
1373
                 IaFaire=IaFaire+1
1374
              END Do              ! DO WHILE CaFaire
1375
           END IF
1376
        END IF
1377

    
1378
        if (debug) THEN
1379
           WRITE(*,*) 'ind_zmat 4'
1380
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1381
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1382
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1383
           DO Ip=4,izm
1384
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), ind_zmat(Ip,2), &
1385
                   ind_zmat(Ip,3), ind_zmat(Ip,4)
1386
           END DO
1387
        END IF
1388

    
1389
     END DO ! loop on atoms of fragment IFrag
1390
  END DO                    ! Loop on all fragments
1391

    
1392
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1393
!
1394
!        General case
1395
!
1396
! 2 - we have all frozen atoms done... now comes the non frozen atoms
1397
! and we should fragment the fragments !
1398
!
1399
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1400

    
1401
! First, we get rid of bonds between frozen atoms
1402
! the trick is to do this on liaisons while keeping LiaisonsBis ok.
1403

    
1404
  if (debug) THEN
1405
     WRITE(*,*) 'Frozen',NFroz
1406
     WRITE(*,'(20(1X,I3))') (Frozen(I),I=1,NFroz)
1407
  END IF
1408

    
1409
  DO I=1,na
1410
     DO J=0,NMAxL
1411
        LiaisonsIni(I,J)=LiaisonsBis(I,J)
1412
     END DO
1413
! PFL 29.Aug.2008 -> 
1414
! We re-initialize FCaf in order to add frozen atoms that are connected
1415
! to non frozen atoms
1416
     FCaf(I)=.FALSE.
1417
! <- 29.Aug.2008
1418
  END DO
1419

    
1420
  DO I=1,Na
1421
     IF (FrozAt(I)) THEN
1422
        Iat=I
1423
        if (debug) WRITE(*,'(20(1X,I3))') I,Iat,  &
1424
             (LiaisonsIni(Iat,Itmp),ITmp=0,LiaisonsIni(Iat,0))
1425
        DO J=1,LiaisonsIni(Iat,0)
1426
           Jat=LiaisonsIni(Iat,J)
1427
           Call Annul(Liaisons,Iat,Jat)
1428
           Call Annul(Liaisons,Jat,Iat)
1429
           Call Annul(LiaisonsIni,Jat,Iat)
1430
           Liaisons(Iat,0)=Liaisons(Iat,0)-1
1431
           Liaisons(Jat,0)=Liaisons(Jat,0)-1
1432
           LiaisonsIni(Jat,0)=LiaisonsIni(Jat,0)-1
1433
        END DO
1434
     END IF
1435
  END DO
1436

    
1437
  if (debug) THEN
1438
     WRITE(*,*) "Connections calculees"
1439
     DO IL=1,na
1440
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
1441
     END DO
1442
  END IF
1443

    
1444

    
1445

    
1446
  ! We re-decompose the system into fragments, but we omit on purpuse
1447
  ! fragments consisting only of frozen atoms
1448
  ! Now, frozblock will contain the frozen atom indices in a given fragment
1449

    
1450
  DO I=1,na
1451
     Fragment(I)=0 
1452
     NbAtFrag(I)=0
1453
     FrozBlock(I,0)=0
1454
  END DO
1455
  IdxFrag=0
1456
  NbFrag=0
1457

    
1458
  DO I=1,na
1459
     IdxCAfaire=1
1460
     CaFaire(IdxCaFaire)=0
1461

    
1462
     if (debug) WRITE(*,*) 'Treating atom I, fragment(I)',I,Fragment(I)
1463
     IF (.NOT.FrozAt(I).OR.(Liaisons(I,0).NE.0)) THEN 
1464
        IF (Fragment(I).EQ.0) THEN
1465
           IdxFrag=IdxFrag+1
1466
           NbFrag=NbFrag+1
1467
           IFrag=IdxFrag
1468
           Fragment(I)=IFrag
1469
           NbAtFrag(IFrag)=NbAtFrag(IFrag)+1
1470
           FragAt(IFrag,NbAtFrag(IFrag))=I
1471
        ELSE  ! fragment(I).EQ.0
1472
           IFrag=Fragment(I)
1473
        END IF     ! fragment(I).EQ.0
1474
        DO J=1,Liaisons(I,0)
1475
           Iat=Liaisons(I,J)
1476
           IF ((Fragment(Iat).NE.0).AND.(Fragment(Iat).NE.IFrag)) THEN
1477
              WRITE(*,*) 'Error : Atoms ',I,' and ',Iat
1478
              WRITE(*,*) 'are linked, but belongs to fragments ',IFrag,' and ',Fragment(Iat)
1479
              STOP
1480
           END IF
1481
           IF (Fragment(Iat).EQ.0) THEN
1482
              IF (.NOT.FCaf(IAt)) THEN
1483
                 CaFaire(IdxCaFaire)=Iat
1484
                 IdxCAfaire=IdxCAFaire+1
1485
                 FCaf(IAt)=.TRUE.
1486
              END IF
1487
              Fragment(Iat)=IFrag
1488
              NbAtFrag(IFrag)=NbAtFrag(IFrag)+1
1489
              FragAt(IFrag,NbAtFrag(IFrag))=Iat
1490
           END IF
1491
        END DO
1492
        CaFaire(IdxCaFaire)=0
1493

    
1494
        If (debug) WRITE(*,'(1X,A,1000I4)') 'Cafaire:',CaFaire(1:IdxCaFaire)
1495
        If (debug) WRITE(*,*) 'IFrag=',IFrag
1496

    
1497
        IAfaire=1
1498
        DO WHILE (CaFaire(IAfaire).NE.0)
1499
           Iat=CaFaire(IaFaire)
1500
           IF (.NOT.FrozAt(Iat).OR.(Liaisons(Iat,0).NE.0)) THEN 
1501
              if (debug) WRITE(*,*) 'Cafaire treating ',Iat
1502
              IF (Fragment(Iat).EQ.0) THEN
1503
                 WRITE(*,*) 'Error: Atom ',Iat,' does not belong to any fragment !'
1504
                 STOP
1505
              END IF
1506

    
1507
              DO J=1,Liaisons(Iat,0)
1508
                 Jat=Liaisons(Iat,J)
1509
                 IF ((Fragment(Jat).NE.0).AND.(Fragment(Jat).NE.IFrag)) THEN
1510
                    WRITE(*,*) 'Error: Atoms ',Iat,' and ',Liaisons(Iat,J)
1511
                    WRITE(*,*) 'are linked, but belongs to fragments ',IFrag,' and ',Fragment(Liaisons(Iat,J))
1512
                    STOP
1513
                 END IF
1514
                 IF (Fragment(Jat).EQ.0) THEN
1515
                    IF (.NOT.FCaf(Liaisons(Iat,J))) THEN
1516
                       CaFaire(IdxCaFaire)=Liaisons(Iat,J)
1517
                       IdxCAfaire=IdxCAFaire+1
1518
                       FCaf(Liaisons(Iat,J))=.TRUE.
1519
                    END IF
1520
                    Fragment(Jat)=IFrag
1521
                    NbAtFrag(IFrag)=NbAtFrag(IFrag)+1
1522
                    FragAt(IFrag,NbAtFrag(IFrag))=Jat
1523
                 END IF
1524
              END DO
1525
              CaFaire(IdxCaFaire)=0
1526
              If (debug) WRITE(*,*) 'IAfaire, IdxCaFaire,Cafaire :',IAfaire,IdxCafaire,' == ',CaFaire(IaFaire+1:IdxCaFaire)
1527
              IAFaire=IAFaire+1
1528
           END IF
1529
        END DO
1530
     END IF
1531
  END DO
1532

    
1533
  ! We compute FrozBlock now
1534
  DO IFrag=1,NbFrag
1535
     DO I=1,NbAtFrag(IFrag)
1536
        Iat=FragAt(IFrag,I)
1537
        IF (FrozAt(Iat)) THEN
1538
           FrozBlock(IFrag,0)=FrozBlock(IFrag,0)+1
1539
           FrozBlock(IFrag,FrozBlock(IFrag,0))=IAt
1540
        END IF
1541
     END DO
1542
  END DO
1543

    
1544

    
1545
  if (debug) THEN
1546
     WRITE(*,*) 'I found ',NbFrag, 'fragments with respectively '
1547
     WRITE(*,*) (NbAtFrag(I),I=1,NbFrag), 'atoms'
1548
     WRITE(*,*) "Fragments atoms are now listed as F in the following"
1549
     DO I=1,NbFrag
1550
        WRITE(*,*) Na
1551
        WRITE(*,*) 'Fragment ', i
1552
        DO J=1,Na
1553
           AtName=Nom(Atome(J))
1554
           IF (Fragment(J).EQ.I) AtName='F'
1555
           WRITE(*,'(1X,A5,3(1X,F10.6))') AtName,X(J),Y(J),Z(J)
1556
        END DO
1557
        !     WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
1558
     END DO
1559

    
1560
     DO I=1,NbFrag
1561
        WRITE(*,*) 'Fragment ', i
1562
        WRITE(*,'(A,20(1X,I3))') "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
1563
        WRITE(*,'(A,20(1X,I3))') "FrozBlock:",(FrozBlock(I,j),j=0,FrozBlock(I,0))
1564
     END DO
1565
  END IF
1566

    
1567

    
1568
  NFroz=0
1569
  DO IFrag=1,NbFrag
1570
     If (FrozBlock(IFrag,0).NE.0) NFroz=NFroz+1
1571
  END DO
1572

    
1573
  IF (DEBUG) WRITE(*,'(1X,A,I4,A,I4,A)') "Found ",NFroz," fragmenst with frozen atoms, out of",NbFrag," fragments"
1574

    
1575
  ! We will now add the fragments containing non frozen atoms.
1576
  ! I am not sure that there is a best strategy to add them...
1577
  ! so we add them in the order they were created :-(
1578
  ! First only block with frozen atoms are added
1579
  izm0=-1
1580
  IFrag=1
1581
  FCaf=.FALSE.
1582

    
1583
  DO IFragFroz=1,NFroz
1584
     DO WHILE (FrozBlock(IFrag,0).EQ.0)
1585
        IFrag=IFrag+1
1586
     END DO
1587
     ! each atom has at least one frozen atom that will serve as the seed
1588
     ! of this fragment.
1589
     if (debug) WRITE(*,*) 'Adding fragment :', ifrag,'with',FrozBlock(IFrag,0),' frozen atoms'
1590
     IF (FrozBlock(IFrag,0).EQ.1) THEN
1591
        ! There is only one frozen atom, easy case ...
1592
        Iat=FrozBlock(IFrag,1)
1593
        if (debug) WRITE(*,*) 'Only frozen atom of frag',iat
1594
        DejaFait(iat)=.TRUE.
1595
        IdxCaFaire=2
1596
        CaFaire(1)=iat
1597
        CaFaire(2)=0
1598
        FCaf(Iat)=.TRUE.
1599
        IaFaire=1
1600
        DO WHILE (CaFaire(IaFaire).NE.0)
1601
           n1=CaFaire(IaFaire)
1602
           SELECT CASE(idx_zmat(n1))
1603
           CASE (1)
1604
              n2=ind_zmat(2,1)
1605
              n3=ind_zmat(3,1)
1606
           CASE (2)
1607
              n2=ind_zmat(1,1)
1608
              n3=ind_zmat(3,1)
1609
           CASE (3:)
1610
              n2=ind_zmat(idx_zmat(n1),2)
1611
              n3=ind_zmat(idx_zmat(n1),3)
1612
           END SELECT
1613

    
1614
           DO I3=1,Liaisons(n1,0)
1615
              IAt=Liaisons(n1,I3)
1616
              ! PFL 2007.Apr.16 ->
1617
              ! We add ALL atoms linked to n1 to CaFaire
1618
              ! But we delete their link to n1
1619
              IF (.NOT.FCaf(Iat)) THEN
1620
                 CaFaire(IdxCaFaire)=Iat
1621
                 IdxCaFaire=IdxCaFaire+1
1622
                 CaFaire(IdxCaFaire)=0
1623
              END IF
1624
              Call Annul(Liaisons,Iat,n1)
1625
              Liaisons(iat,0)=Liaisons(Iat,0)-1
1626
              ! <- PFL 2007.Apr.16
1627
              IF (.NOT.DejaFait(Iat)) THEN
1628
                 ! we add it to the Zmat
1629
                 izm=izm+1
1630
                 !              ind_zmat(izm,1)=iat
1631
                 !              ind_zmat(izm,2)=n1
1632
                 !              ind_zmat(izm,3)=n2
1633
                 !              ind_zmat(izm,4)=n3
1634
                 Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1635
                 idx_zmat(iat)=izm
1636
                 !                  Call Annul(Liaisons,n1,iat)
1637
                 n3=iat
1638
                 DejaFait(Iat)=.TRUE.
1639
              END IF
1640
           END DO
1641
              IaFaire=IaFaire+1
1642

    
1643
              if (debug) THEN
1644
                 WRITE(*,*) 'ind_zmat 5'
1645
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1646
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1647
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1648
                 DO Ip=4,izm
1649
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
1650
                         ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
1651
                 END DO
1652
              END IF
1653
              
1654
           END Do              ! DO WHILE CaFaire
1655

    
1656

    
1657
        ELSE     ! FrozBlock(I,0)==1
1658
           if (debug) WRITE(*,*) 'IFrag=',IFrag,'Frozblock(I,0)/=1',Frozblock(IFrag,0)
1659
           ! We have many frozen atoms for one fragment. We will have to choose
1660
           ! the first one, and then to decide when to swich...
1661
           Iat=0
1662
           I0=-1
1663
           DO I=1,FrozBlock(IFrag,0)
1664
              JAt=FrozBlock(IFrag,I)
1665
              if (debug) WRITE(*,*) Jat, &
1666
                   (LiaisonsBis(Jat,Itmp),Itmp=0,LiaisonsBis(Jat,0))
1667
              IF (LiaisonsBis(Jat,0).GT.I0) THEN
1668
                 I0=LiaisonsBis(Jat,0)
1669
                 Iat=Jat
1670
              END IF
1671
           END DO
1672
           ! Iat is the starting frozen atom
1673
           IF (debug) WRITE(*,*) 'Choosing atom ',iat,'as a starting atom for frag',ifrag
1674
           DejaFait(iat)=.TRUE.
1675
           IdxCaFaire=2
1676
           CaFaire(1)=iat
1677
           CaFaire(2)=0
1678
           IaFaire=1
1679
           FCaf(Iat)=.TRUE.
1680
           DO WHILE (CaFaire(IaFaire).NE.0)
1681
              n1=CaFaire(IaFaire)
1682
              if (debug) WRITE(*,*) 'Iafaire,n1,dejafait,idx_zmat', &
1683
                   IaFaire,n1,    DejaFait(n1),idx_zmat(n1)
1684
              if (debug) WRITE(*,*) 'Cafaire', &
1685
                   (CaFaire(J),J=Iafaire,IdxCAfaire)
1686
              SELECT CASE(idx_zmat(n1))
1687
              CASE (1)
1688
                 n2=ind_zmat(2,1)
1689
                 n3=ind_zmat(3,1)
1690
              CASE (2)
1691
                 n2=ind_zmat(1,1)
1692
                 n3=ind_zmat(3,1)
1693
              CASE (3:)
1694
                 n2=ind_zmat(idx_zmat(n1),2)
1695
                 n3=ind_zmat(idx_zmat(n1),3)
1696
              END SELECT
1697

    
1698
              if (debug) WRITE(*,*) "DBG n1,Liaisons(n1,0)",n1,Liaisons(n1,0)
1699
              DO I3=1,Liaisons(n1,0)
1700
                 IAt=Liaisons(n1,I3)                 
1701
                 if (debug) WRITE(*,*) "DBG I3,Iat",I3,Iat
1702
                 ! PFL 2007.Apr.16 ->
1703
                 ! We add ALL atoms linked to n1 to CaFaire
1704
                 ! But we delete their link to n1
1705
!! PFL 2007.Aug.28 ->
1706
! re-add the test on FCaf in order not to put the same atom more than once in 
1707
! CaFaire array.
1708
                 IF (.NOT.FCaf(Iat)) THEN
1709
                    CaFaire(IdxCaFaire)=Iat
1710
                    IdxCaFaire=IdxCaFaire+1
1711
                    CaFaire(IdxCaFaire)=0
1712
                    FCaf(Iat)=.TRUE.
1713
                    if (debug) WRITE(*,*) 'Adding ',iat,' to CaFaire. I3=',I3,'IdxCafaire=',IdxCafaire
1714
                    if (debug) WRITE(*,*) 'Cafaire',(CaFaire(J),J=Iafaire,IdxCAfaire)
1715

    
1716
                 END IF
1717
!! <-- PFL 2007.Aug.28
1718

    
1719
                 Call Annul(Liaisons,Iat,n1)
1720
                 Liaisons(iat,0)=Liaisons(Iat,0)-1
1721
                 ! <- PFL 2007.Apr.16
1722
                 IF (.NOT.DejaFait(Iat)) THEN
1723
                    izm=izm+1
1724
                    !                 ind_zmat(izm,1)=iat
1725
                    !                 ind_zmat(izm,2)=n1
1726
                    !                 ind_zmat(izm,3)=n2
1727
                    !                 ind_zmat(izm,4)=n3
1728
                    Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1729
                    idx_zmat(iat)=izm
1730
                    !                  Call Annul(Liaisons,n1,iat)
1731

    
1732
                    n3=iat
1733
                    DejaFait(Iat)=.TRUE.
1734
                 END IF
1735
              END DO
1736

    
1737
              if (debug) WRITE(*,*) 'I3,n1,Liaisons(n1,:)', &
1738
                   I3,n1,(Liaisons(n1,J),J=0,Liaisons(n1,0))
1739

    
1740

    
1741
              if (debug.AND.(izm.GT.izm0)) THEN
1742
                 WRITE(*,*) 'ind_zmat 6, izm=',izm
1743
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1744
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1745
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2),  &
1746
                      ind_zmat(3,3)
1747
                 DO Ip=4,izm
1748
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), &
1749
                         ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
1750
                 END DO
1751
                 izm0=izm
1752
              END IF
1753

    
1754
              IaFaire=IaFaire+1
1755

    
1756

    
1757
           END Do              ! DO WHILE CaFaire
1758

    
1759
        END IF  ! FrozBlock(I,0)==1
1760

    
1761
        IFrag=IFrag+1
1762
     END DO                    ! Loop on all fragments
1763

    
1764

    
1765
     DO IFrag=1,NbFrag
1766
        IF (FrozBlock(IFrag,0).EQ.0) THEN
1767
           if (debug) WRITE(*,*) 'Adding fragment :', ifrag,'with no frozen atoms'
1768
           ! We have no frozen atoms for this fragment. We will have to choose
1769
           ! the first atom to put.
1770
           ! For now, we do not care of the 'central' atom (ie the one with
1771
           ! no CP atoms...)
1772
           ! We just take the atom that is the closest to the already placed
1773
           ! atoms !
1774

    
1775

    
1776
           I0=0
1777
           I1=0
1778
           d=1e9
1779
           DO J=1,izm
1780
              Jat=ind_zmat(J,1)
1781
              DO I=1,NbAtfrag(IFrag)
1782
                 IAt=FragAt(IFrag,I)
1783
                 IF (.NOT.DejaFait(Iat)) THEN
1784
                    Call vecteur(Iat,Jat,x,y,z,vx1,vy1,vz1,norm1)
1785
                    IF (norm1.LT.d) THEN
1786
                       I1=Jat
1787
                       I0=Iat
1788
                       d=Norm1
1789
                    END IF
1790
                 END IF
1791
              END DO
1792
           END DO
1793

    
1794
           Iat=I0
1795
           n1=I1
1796

    
1797
           IF (debug) WRITE(*,*) Iat,' starting atom for frag',ifrag
1798

    
1799

    
1800
           SELECT CASE(idx_zmat(n1))
1801
           CASE (1)
1802
              n2=ind_zmat(2,1)
1803
              n3=ind_zmat(3,1)
1804
           CASE (2)
1805
              n2=ind_zmat(1,1)
1806
              n3=ind_zmat(3,1)
1807
           CASE (3:)
1808
              n2=ind_zmat(idx_zmat(n1),2)
1809
              n3=ind_zmat(idx_zmat(n1),3)
1810
           END SELECT
1811

    
1812
           izm=izm+1
1813
           !        ind_zmat(izm,1)=iat
1814
           !        ind_zmat(izm,2)=n1
1815
           !        ind_zmat(izm,3)=n2
1816
           !        ind_zmat(izm,4)=n3
1817
           Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1818
           idx_zmat(iat)=izm
1819

    
1820

    
1821
           DejaFait(iat)=.TRUE.
1822
           IdxCaFaire=2
1823
           CaFaire(1)=iat
1824
           CaFaire(2)=0
1825
           IaFaire=1
1826
           FCaf(Iat)=.TRUE.
1827
           DO WHILE (CaFaire(IaFaire).NE.0)
1828
              n1=CaFaire(IaFaire)
1829
              if (debug) WRITE(*,*) 'Iafaire,n1',IaFaire,n1, &
1830
                   DejaFait(n1),idx_zmat(n1)
1831
              if (debug) WRITE(*,*) 'Cafaire', &
1832
                   (CaFaire(J),J=Iafaire,IdxCAfaire)
1833
              SELECT CASE(idx_zmat(n1))
1834
              CASE (1)
1835
                 n2=ind_zmat(2,1)
1836
                 n3=ind_zmat(3,1)
1837
              CASE (2)
1838
                 n2=ind_zmat(1,1)
1839
                 n3=ind_zmat(3,1)
1840
              CASE (3:)
1841
                 n2=ind_zmat(idx_zmat(n1),2)
1842
                 n3=ind_zmat(idx_zmat(n1),3)
1843
              END SELECT
1844

    
1845

    
1846
              DO I3=1,Liaisons(n1,0)
1847
                 IAt=Liaisons(n1,I3)
1848
                 ! PFL 2007.Apr.16 ->
1849
                 ! We add ALL atoms linked to n1 to CaFaire
1850
                 ! But we delete their link to n1
1851
!! PFL 2007.Aug.28 ->
1852
! re-add the test on FCaf in order not to put the same atom more than once in 
1853
! CaFaire array.
1854
                 IF (.NOT.FCaf(Iat)) THEN
1855
                    CaFaire(IdxCaFaire)=Iat
1856
                    IdxCaFaire=IdxCaFaire+1
1857
                    CaFaire(IdxCaFaire)=0
1858
                    FCaf(Iat)=.TRUE.
1859
                 END IF
1860
!! <-- PFL 2007.Aug.28
1861

    
1862
                 Call Annul(Liaisons,Iat,n1)
1863
                 Liaisons(iat,0)=Liaisons(Iat,0)-1
1864
                 if (debug) WRITE(*,*) 'Adding ',iat,' to CaFaire. I3=',I3
1865
                 if (debug) WRITE(*,*) 'Cafaire',(CaFaire(J),J=Iafaire,IdxCAfaire)
1866

    
1867
                 ! <- PFL 2007.Apr.16
1868
                 IF (.NOT.DejaFait(Liaisons(n1,i3))) THEN
1869
                    IAt=Liaisons(n1,I3)
1870
                    izm=izm+1
1871
                    !                 ind_zmat(izm,1)=iat
1872
                    !                 ind_zmat(izm,2)=n1
1873
                    !                 ind_zmat(izm,3)=n2
1874
                    !                 ind_zmat(izm,4)=n3
1875
                    Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1876
                    idx_zmat(iat)=izm
1877

    
1878
                    n3=iat
1879
                    DejaFait(Iat)=.TRUE.
1880
                 END IF
1881

    
1882
              if (debug) WRITE(*,*) 'I3,n1,Liaisons(n1,:)', &
1883
                   I3,n1,(Liaisons(n1,J),J=0,Liaisons(n1,0))
1884
              END DO
1885
              IaFaire=IaFaire+1
1886

    
1887
              if (debug) THEN
1888
                 WRITE(*,*) 'ind_zmat 7', izm
1889
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1890
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1891
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2),ind_zmat(3,3)
1892
                 DO Ip=4,izm
1893
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), &
1894
                         ind_zmat(Ip,2),  &
1895
                         ind_zmat(Ip,3), ind_zmat(Ip,4)
1896
                 END DO
1897
              END IF
1898

    
1899
           END Do              ! DO WHILE CaFaire
1900
        END IF                 ! FrozBlock(IFrag,0).EQ.0
1901

    
1902
     END DO                    ! Loop on all fragments without frozen atoms
1903

    
1904
     if (debug) THEN
1905
        WRITE(*,*) Na+Izm
1906
        WRITE(*,*) 'Done... ', izm
1907
        DO J=1,Na
1908
           WRITE(*,'(1X,A5,3(1X,F10.6))') Nom(Atome(J)),X(J),Y(J),Z(J)
1909
        END DO
1910
        DO I=1,Izm
1911
           J=ind_zmat(I,1)
1912
           WRITE(*,'(1X,A5,3(1X,F10.6))') 'X ',X(J),Y(J),Z(J)
1913
        END DO
1914
        IF (izm.NE.Na) THEN
1915
           WRITE(*,*) "Atoms not done:"
1916
           DO I=1,Na
1917
              IF (.NOT.DejaFait(I)) WRITE(*,'(I5)',ADVANCE='NO') I
1918
           END DO
1919
        END IF
1920
     END IF
1921

    
1922

    
1923
     ! We have ind_zmat. We calculate val_zmat :-)
1924
     if (debug) WRITE(*,*) "Calculating val_zmat"
1925

    
1926
     val_zmat(1,1)=0.d0
1927
     val_zmat(1,2)=0.d0
1928
     val_zmat(1,3)=0.d0
1929
     val_zmat(2,2)=0.d0
1930
     val_zmat(2,3)=0.d0
1931
     val_zmat(3,3)=0.d0
1932

    
1933
     n1=ind_zmat(2,1)
1934
     n2=ind_zmat(2,2)
1935

    
1936
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1937

    
1938
     val_zmat(2,1)=norm1
1939

    
1940

    
1941
     n1=ind_zmat(3,1)
1942
     n2=ind_zmat(3,2)
1943
     n3=ind_zmat(3,3)
1944

    
1945
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1946

    
1947
     val_zmat(3,1)=norm1
1948

    
1949
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
1950
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
1951

    
1952
     val_zmat(3,2)=val
1953

    
1954
     DO i=4,na
1955

    
1956
        n1=ind_zmat(i,1)
1957
        n2=ind_zmat(i,2)
1958
        n3=ind_zmat(i,3)
1959
        n4=ind_zmat(i,4)
1960

    
1961
        if (debug) WRITE(*,*) "Doing i,n1,n2,n3,n4",i,n1,n2,n3,n4
1962
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1963

    
1964
        CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
1965
        val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
1966

    
1967
        CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
1968
        CALL produit_vect(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2, &
1969
             vx4,vy4,vz4,norm4)
1970
        CALL produit_vect(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2, &
1971
             vx5,vy5,vz5,norm5)
1972

    
1973
        val_d=angle_d(vx4,vy4,vz4,norm4, vx5,vy5,vz5,norm5, &
1974
             vx2,vy2,vz2,norm2)
1975

    
1976
        !     write(*,11) n1,n2,norm1,n3,val,n4,val_d
1977
        !11   format (2(1x,i3),1x,f8.4,2(1x,i3,1x,f8.3))
1978

    
1979
        val_zmat(i,1)=norm1
1980
        val_zmat(i,2)=val
1981
        val_zmat(i,3)=val_d
1982

    
1983
     END DO
1984

    
1985
     if (debug) THEN
1986
        WRITE(*,*) 'DBG Cre_Zmat_Constr: ind_zmat'
1987
        DO I=1,na
1988
           WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5)
1989
        END DO
1990

    
1991
        WRITE(*,*) 'DBG Cre_Zmat_Constr: Full zmat'
1992
        DO I=1,na
1993
           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)
1994
        END DO
1995

    
1996
     END IF
1997

    
1998
     if (debug) WRITE(*,*) "Deallocate (FrozDist,Fragment, NbAtFrag,FragAt)"
1999
     DEALLOCATE(FrozDist,Fragment, NbAtFrag,FragAt)
2000
     if (debug) WRITE(*,*) "Deallocate FrozFrag, IdxFragAt, FrozBlock"
2001
     !  DEALLOCATE(FrozFrag, IdxFragAt, FrozBlock)
2002
     DEALLOCATE(FrozFrag,FrozBlock)
2003
     if (debug) WRITE(*,*) "Deallocate (DistFroz,Liaisons)"
2004
     DEALLOCATE(DistFroz,Liaisons)
2005
     if (debug) WRITE(*,*) "Deallocate (LiaisonsIni)"
2006
     DEALLOCATE(LiaisonsIni)
2007
     if (debug) WRITE(*,*) "Deallocate(CaFaire,DejaFait,FrozAt)"
2008
     DEALLOCATE(CaFaire,DejaFait,FrozAt)
2009
     if (debug) WRITE(*,*) "Deallocate (LiaisonsBis"
2010
     DEALLOCATE(LiaisonsBis)
2011

    
2012

    
2013
     if (debug) WRITE(*,*) "=============================== Exiting Calc_zmat_contr_frag ========================"
2014

    
2015
   END SUBROUTINE Calc_Zmat_const_frag
2016

    
2017