Statistiques
| Révision :

root / src / Calc_mixed_frag.f90

Historique | Voir | Annoter | Télécharger (36,11 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

    
13
!----------------------------------------------------------------------
14
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
15
!  Centre National de la Recherche Scientifique,
16
!  Université Claude Bernard Lyon 1. All rights reserved.
17
!
18
!  This work is registered with the Agency for the Protection of Programs 
19
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
20
!
21
!  Authors: P. Fleurat-Lessard, P. Dayal
22
!  Contact: optnpath@gmail.com
23
!
24
! This file is part of "Opt'n Path".
25
!
26
!  "Opt'n Path" is free software: you can redistribute it and/or modify
27
!  it under the terms of the GNU Affero General Public License as
28
!  published by the Free Software Foundation, either version 3 of the License,
29
!  or (at your option) any later version.
30
!
31
!  "Opt'n Path" is distributed in the hope that it will be useful,
32
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
33
!
34
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
35
!  GNU Affero General Public License for more details.
36
!
37
!  You should have received a copy of the GNU Affero General Public License
38
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
39
!
40
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
41
! for commercial licensing opportunities.
42
!----------------------------------------------------------------------
43

    
44
  Use Path_module, only : max_Z, NMaxL, Nom
45
  Use Io_module
46

    
47
  IMPLICIT NONE
48

    
49
! Parameters of the subroutine
50
! na: number of atoms in the system
51
  integer(KINT) ::  na
52
! atome: Mass number of the atoms of the system
53
  integer(KINT) ::  atome(na)
54
! ind_zmat: for "zmat" atoms contains the indices of reference atoms
55
  integer(KINT) ::  ind_zmat(Na,5)
56
  INTEGER(KINT) ::  idx_zmat(NA)
57
  real(KREAL) ::  x(Na),y(Na),z(Na),fact
58
  real(KREAL) ::  val_zmat(Na,3)
59
  real(KREAL) ::  r_cov(0:Max_Z)
60

    
61
  CHARACTER(5) :: AtName
62

    
63
  !     Frozen contains the indices of frozen atoms
64
  INTEGER(KINT) Frozen(*),Cart(*),NFroz,NCart
65
  LOGICAL, ALLOCATABLE :: FCart(:) ! Na
66
  INTEGER(KINT), ALLOCATABLE :: AtCart(:) !Na
67
  INTEGER(KINT), ALLOCATABLE :: FrozDist(:) ! na
68
  INTEGER(KINT) NbFrag,IdxFrag
69
  INTEGER(KINT), ALLOCATABLE :: Fragment(:),NbAtFrag(:) !na
70
  INTEGER(KINT), ALLOCATABLE :: FragAt(:,:) !na,na
71
  INTEGER(KINT), ALLOCATABLE :: FrozFrag(:,:) !na,3
72
  INTEGER(KINT), ALLOCATABLE :: FrozBlock(:,:) !(na,0:na)
73
  REAL(KREAL), ALLOCATABLE :: DistFroz(:) !na
74

    
75
  INTEGER(KINT) :: IdxCaFaire, IAfaire
76
  INTEGER(KINT), ALLOCATABLE ::  LIAISONS(:,:) ! (Na,0:NMaxL)
77
  INTEGER(KINT), ALLOCATABLE ::  LiaisonsBis(:,:) ! (Na,0:NMaxL)
78
  INTEGER(KINT), ALLOCATABLE ::  LiaisonsIni(:,:) ! (Na,0:NMaxL)
79
  INTEGER(KINT), ALLOCATABLE :: CAFaire(:) ! (Na)
80

    
81

    
82
  real(KREAL) ::  vx1,vy1,vz1,norm1
83
  real(KREAL) ::  vx2,vy2,vz2,norm2
84
  real(KREAL) ::  vx3,vy3,vz3,norm3
85
  real(KREAL) ::  vx4,vy4,vz4,norm4
86
  real(KREAL) ::  vx5,vy5,vz5,norm5
87
  real(KREAL) ::  val, val_d, d
88
  Logical Debug,DebugGaussian
89
  LOGICAL, ALLOCATABLE :: DejaFait(:),FCaf(:) !(na)
90
  Logical, ALLOCATABLE ::  FrozAt(:)    !T if this atom is frozen
91

    
92

    
93

    
94
  INTEGER(KINT) :: I, J, n1, n2, n3, n4, IAt, IL, JL, IFrag, ITmp
95
  INTEGER(KINT) :: I3, I1, Ip, IFragFroz, IBeg
96
  INTEGER(KINT) :: I0, Izm, JAt,Izm0,Idx
97

    
98
  REAL(KREAL) :: Pi, Sang
99

    
100
  INTERFACE
101
     function valid(string) result (isValid)
102
       CHARACTER(*), intent(in) :: string
103
       logical                  :: isValid
104
     END function VALID
105

    
106
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
107
       use Path_module, only :  Pi,KINT, KREAL
108
       real(KREAL) ::  v1x,v1y,v1z,norm1
109
       real(KREAL) ::  v2x,v2y,v2z,norm2
110
       real(KREAL) ::  angle
111
     END FUNCTION ANGLE
112

    
113
     FUNCTION SinAngle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
114
       use Path_module, only :  Pi,KINT, KREAL
115
       real(KREAL) ::  v1x,v1y,v1z,norm1
116
       real(KREAL) ::  v2x,v2y,v2z,norm2
117
       real(KREAL) ::  SinAngle
118
     END FUNCTION SINANGLE
119

    
120

    
121
     FUNCTION angle_d(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2,v3x,v3y,v3z,norm3)
122
       use Path_module, only :  Pi,KINT, KREAL
123
       real(KREAL) ::  v1x,v1y,v1z,norm1
124
       real(KREAL) ::  v2x,v2y,v2z,norm2
125
       real(KREAL) ::  v3x,v3y,v3z,norm3 
126
       real(KREAL) ::  angle_d,ca,sa
127
     END FUNCTION ANGLE_D
128

    
129
  END INTERFACE
130

    
131
  Pi=dacos(-1.d0)
132
  debug=valid("calc_mixed_frag")
133
  debugGaussian=valid("zmat_gaussian")
134

    
135
  if (debug) Call Header("Entering Calc_mixed_frag")
136
  if (na.le.2) THEN
137
     WRITE(*,*) "I do not work for less than 2 atoms :-p"
138
     RETURN
139
  END IF
140

    
141
  ALLOCATE(FrozDist(Na),Fragment(na), NbAtFrag(na),FragAt(na,na))
142
  ALLOCATE(FCart(Na),AtCart(Na))
143
  ALLOCATE(FrozFrag(na,3), FrozBlock(na,0:na))
144
  ALLOCATE(DistFroz(na),Liaisons(na,0:NMaxL))
145
  ALLOCATE(LiaisonsBis(na,0:NMaxL),LiaisonsIni(na,0:NMaxL))
146
  ALLOCATE(CaFaire(na+1),DejaFait(Na),FCaf(na),FrozAt(na))
147

    
148
  Ind_Zmat=0
149

    
150
  ! Putting cart+frozen atoms into  cart array
151
  FCart=.FALSE.
152
  NCart=0
153
  Idx=1
154
  DO WHILE (Frozen(Idx).NE.0)
155
     If (Frozen(Idx).LT.0) THEN
156
        DO I=Frozen(Idx-1),abs(Frozen(Idx))
157
           IF (.NOT.FCart(I)) THEN
158
              NCart=NCart+1
159
              AtCart(NCart)=I
160
              FCart(I)=.TRUE.
161
           END IF
162
        END DO
163
     ELSEIF (.NOT.FCart(Frozen(Idx))) THEN
164
        FCart(Frozen(Idx))=.TRUE.
165
        NCart=NCart+1
166
        AtCart(NCart)=Frozen(Idx)
167
     END IF
168
  Idx=Idx+1
169
  END DO
170
  NFroz=NCart
171
  Idx=1
172
  DO WHILE (Cart(Idx).NE.0)
173
     If (Cart(Idx).LT.0) THEN
174
        DO I=Cart(Idx-1),abs(Cart(Idx))
175
           IF (.NOT.FCart(I)) THEN
176
              NCart=NCart+1
177
              AtCart(NCart)=I
178
              FCart(I)=.TRUE.
179
           END IF
180
        END DO
181
     ELSEIF (.NOT.FCart(Cart(Idx))) THEN
182
        FCart(Cart(Idx))=.TRUE.
183
        NCart=NCart+1
184
        AtCart(NCart)=Cart(Idx)
185
     END IF
186
  Idx=Idx+1
187
  END DO
188

    
189
  if (debug) THEN
190
     WRITE(*,'(1X,A,I4,A,I4,A)') "Found ",NFroz," frozen atoms, and a total of ",NCart," atoms described in cartesian coordinates"
191
     WRITE(*,*) "AtCart:",AtCart(1:NCart)
192
  END IF
193

    
194
  DejaFait=.FALSE.
195

    
196
  ! We cheat a lot: we will use ind_zmat et val_zmat to store
197
  ! the cartesian coordinates of the NCart atoms :-p
198
  DO I=1,NCart
199
     Iat=AtCart(I)
200
     ind_zmat(I,1)=Iat
201
     ind_zmat(I,2:5)=-1
202
     val_zmat(I,1)=X(Iat)
203
     val_zmat(I,2)=Y(Iat)
204
     val_zmat(I,3)=Z(Iat)
205
     DejaFait(Iat)=.TRUE.
206
     idx_zmat(Iat)=I
207
  END DO
208

    
209

    
210
  izm=NCart
211

    
212
  ! We now calculate the connections
213
  Liaisons=0
214
  LiaisonsBis=0
215

    
216
  if (debug) THEN
217
     WRITE(*,*) "Liaisons initialized"
218
!     WRITE(*,*) 'Covalent radii used'
219
!     DO iat=1,na
220
!        i=atome(iat)
221
!        WRITE(*,*) Nom(I),Iat,r_cov(i),r_cov(i)*fact
222
!     END DO
223
  END IF
224

    
225
1003 FORMAT(1X,I4,' - ',25(I5))
226

    
227
  Call CalcCnct(na,atome,x,y,z,LIAISONS,r_cov,fact)
228

    
229
  if (debug) THEN
230
     WRITE(*,*) "Connections calculated"
231
     DO IL=1,na
232
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
233
     END DO
234
  END IF
235

    
236
  ! We get rid of bonds between cart atoms
237
  ! the trick is to do this on liaisons while keeping LiaisonsBis ok.
238

    
239
  LiaisonsIni=Liaisons
240
  LiaisonsBis=Liaisons
241

    
242
  DO I=1,NCart
243
     Iat=AtCart(I)
244
     if (debug) WRITE(*,'(20(1X,I3))') I,Iat,  &
245
          (LiaisonsIni(Iat,Itmp),ITmp=0,LiaisonsIni(Iat,0))
246
     DO J=1,LiaisonsIni(Iat,0)
247
        Jat=LiaisonsIni(Iat,J)
248
        IF (FCart(Jat)) THEN
249
           Call Annul(Liaisons,Iat,Jat)
250
           Call Annul(Liaisons,Jat,Iat)
251
           Call Annul(LiaisonsIni,Jat,Iat)
252
           Liaisons(Iat,0)=Liaisons(Iat,0)-1
253
           Liaisons(Jat,0)=Liaisons(Jat,0)-1
254
           LiaisonsIni(Jat,0)=LiaisonsIni(Jat,0)-1
255
        END IF
256
     END DO
257
  END DO
258

    
259
  if (debug) THEN
260
     WRITE(*,*) "Connections omitting bonds between cart atoms"
261
     DO IL=1,na
262
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
263
     END DO
264
  END IF
265

    
266
  ! We decompose the system into fragments, but we omit on purpuse
267
  ! fragments consisting only of frozen atoms
268
  ! Now, frozblock will contain the frozen atom indices in a given fragment
269
  Fragment=0
270
  NbAtFrag=0
271
  FrozBlock=0
272

    
273
  IdxFrag=0
274
  NbFrag=0
275

    
276
 Call Decomp_frag(na,liaisons,.NOT.Fcart,nbfrag,Fragment,NbAtFrag,FragAt)
277

    
278
 ! We compute FrozBlock now
279
  DO IFrag=1,NbFrag
280
     DO I=1,NbAtFrag(IFrag)
281
        Iat=FragAt(IFrag,I)
282
        IF (FCart(Iat)) THEN
283
           FrozBlock(IFrag,0)=FrozBlock(IFrag,0)+1
284
           FrozBlock(IFrag,FrozBlock(IFrag,0))=IAt
285
        END IF
286
     END DO
287
  END DO
288

    
289
  if (debug) THEN
290
     WRITE(*,*) 'I found ',NbFrag, 'fragments with respectively '
291
     WRITE(*,*) (NbAtFrag(I),I=1,NbFrag), 'atoms'
292
     WRITE(*,*) "Fragments atoms are now listed as F in the following"
293
     DO I=1,NbFrag
294
        WRITE(*,*) Na
295
        WRITE(*,*) 'Fragment ', i
296
        DO J=1,Na
297
           AtName=Nom(Atome(J))
298
           IF (Fragment(J).EQ.I) AtName='F'
299
           WRITE(*,'(1X,A5,3(1X,F10.6))') AtName,X(J),Y(J),Z(J)
300
        END DO
301
        !     WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
302
     END DO
303

    
304
     DO I=1,NbFrag
305
        WRITE(*,*) 'Fragment ', i
306
        WRITE(*,'(A,20(1X,I3))') "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
307
        WRITE(*,'(A,20(1X,I3))') "FrozBlock:",(FrozBlock(I,j),j=0,FrozBlock(I,0))
308
     END DO
309
  END IF
310

    
311
  NFroz=0
312
  DO IFrag=1,NbFrag
313
     If (FrozBlock(IFrag,0).NE.0) NFroz=NFroz+1
314
  END DO
315

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

    
318

    
319
  if (debug) THEN
320
     WRITE(*,*) "Connections before adding fragments"
321
     DO IL=1,na
322
        IF (Liaisons(IL,0).NE.0)  WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
323
     END DO
324
  END IF
325

    
326
  ! We will now add the fragments containing non cart atoms.
327
  ! I am not sure that there is a best strategy to add them...
328
  ! so we add them in the order they were created :-(
329
  ! First only block with frozen atoms are added
330
  izm0=-1
331
  IFrag=1
332
  IZm=NCart
333
  FCaf=.FALSE.
334
  DO IFragFroz=1,NFroz
335
     DO WHILE (FrozBlock(IFrag,0).EQ.0)
336
        IFrag=IFrag+1
337
     END DO
338
     ! each atom has at least one frozen atom that will serve as the seed
339
     ! of this fragment.
340
     if (debug) WRITE(*,*) 'Adding fragment :', ifrag,'with',FrozBlock(IFrag,0),' frozen atoms'
341
     IF (FrozBlock(IFrag,0).EQ.1) THEN
342
        ! There is only one frozen atom, easy case ...
343
        Iat=FrozBlock(IFrag,1)
344
        if (debug) WRITE(*,*) 'Only frozen atom of frag',iat
345
        DejaFait(iat)=.TRUE.
346
        IdxCaFaire=2
347
        CaFaire(1)=iat
348
        CaFaire(2)=0
349
        IaFaire=1
350
        FCaf(Iat)=.TRUE.
351
        DO WHILE (CaFaire(IaFaire).NE.0)
352
           n1=CaFaire(IaFaire)
353
           I1=idx_zmat(n1)
354
           n2=ind_zmat(I1,2)
355
           n3=ind_zmat(I1,3)
356

    
357
        if (debug) WRITE(*,1003) n1,(LIAISONS(n1,JL),JL=0,NMaxL)
358
           DO I3=1,Liaisons(n1,0)
359
              IAt=Liaisons(n1,I3)
360
              ! PFL 2007.Apr.16 ->
361
              ! We add ALL atoms linked to n1 to CaFaire
362
              ! But we delete their link to n1
363
!! PFL 2007.Aug.28 ->
364
! re-add the test on FCaf in order not to put the same atom more than once in 
365
! CaFaire array.
366
                 IF (.NOT.FCaf(Iat)) THEN
367
                    CaFaire(IdxCaFaire)=Iat
368
                    IdxCaFaire=IdxCaFaire+1
369
                    CaFaire(IdxCaFaire)=0
370
                    FCaf(Iat)=.TRUE.
371
                 END IF
372
!! <-- PFL 2007.Aug.28
373
              if (debug) WRITE(*,1003) Iat,(LIAISONS(Iat,JL),JL=0,NMaxL)
374
              Call Annul(Liaisons,Iat,n1)
375
              if (debug) WRITE(*,1003) Iat,(LIAISONS(Iat,JL),JL=0,NMaxL)
376
              Liaisons(iat,0)=Liaisons(Iat,0)-1
377
           if (debug) WRITE(*,*) 'Iafaire,n1,DejaFait,idxzmat,n2,n3',IaFaire,n1, &
378
                DejaFait(n1),idx_zmat(n1),n2,3
379
           if (debug) WRITE(*,*) 'Cafaire - 0', &
380
                (CaFaire(J),J=Iafaire,IdxCAfaire)
381

    
382

    
383
              ! <- PFL 2007.Apr.16
384
              IF (.NOT.DejaFait(Iat)) THEN
385
                 ! we add it to the Zmat
386
!                 WRITE(*,*) "coucou"
387
                 call vecteur(n1,iat,x,y,z,vx1,vy1,vz1,norm1)
388
!                 WRITE(*,*) "coucou 2"
389
                 izm=izm+1
390
                 IF (izm.EQ.2) THEN
391
!                 WRITE(*,*) "coucou 3"
392
                    ind_zmat(izm,1)=IAt
393
                    ind_zmat(izm,2)=n1
394
                    ind_zmat(izm,3:5)=0
395
                    if (n2.EQ.-1) n2=Iat
396
                 END IF
397

    
398
!                 WRITE(*,*) "coucou 4"
399
                 if ((izm.GE.3).AND.(n2.EQ.-1)) THEN
400
!                 WRITE(*,*) "coucou 5"
401
!                 WRITE(*,*) "coucou 3 bis"
402
                       ! This atom is defined in cartesian coordinates
403
                       ! and has not been used to put a non cart atom.
404
                       ! we will find the closest atom linked to this one amongst the atoms
405
                       ! already stored in ind_zmat
406
                       d=1e9
407
                       JAt=-1
408
                       DO I=1,NCart
409
                          If (ind_zmat(I,1).NE.n1) THEN
410
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx2,vy2,vz2,norm2)
411
                             SAng=Sinangle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
412
                             ! we take only atoms that are not aligned
413
                             if ((norm2<=d).AND.(SAng.GT.0.09d0)) THEN
414
                                Jat=ind_zmat(I,1)
415
                                d=norm2
416
                             END IF
417
                          END IF
418
                       END DO
419
                       if (JAt.EQ.-1) THEN
420
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
421
                          STOP
422
                       END IF
423
                       n2=JAt
424
                 END IF! izm>=3 and n2.eq.-1
425

    
426
                 IF (izm.eq.3) THEN
427
                    ind_zmat(izm,1)=Iat
428
                    ind_zmat(izm,2)=n1
429
                    ind_zmat(izm,3)=n2
430
                 END IF  ! izm=3
431

    
432
                 IF (izm.GE.4) THEN
433
!                                     WRITE(*,*) "coucou 5 bis"
434
                    IF (n3.EQ.-1) THEN
435
                       ! This atom is defined in cartesian coordinates
436
                       ! and has not been used to put a non cart atom.
437
                       ! we will find the closest atom linked to this one amongst the atoms
438
                       ! already stored in ind_zmat
439
                       call vecteur(n1,n2,x,y,z,vx2,vy2,vz2,norm2)
440
                       d=1e9
441
                       JAt=-1
442
                       DO I=1,NCart
443
                          If ((ind_zmat(I,1).NE.n1).AND.(ind_zmat(I,1).NE.n2)) THEN
444
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx3,vy3,vz3,norm3)
445
                             SAng=Sinangle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
446
                             if (debug) WRITE(*,*) "1-Trying izm,iat,n1,n2,n3,sang,d,norm3", &
447
                                  izm,iat,n1,n2,ind_zmat(I,1),sang,d,norm3
448
                             ! we take only atoms that are not aligned
449
                             if ((norm3<=d).AND.(SAng.GT.0.09d0)) THEN
450
                                Jat=ind_zmat(I,1)
451
                                d=norm3
452
                             END IF
453
                          END IF
454
                       END DO
455
                       if (JAt.EQ.-1) THEN
456
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
457
                          STOP
458
                       END IF
459
                       n3=JAt
460
                    END IF
461
                    !                    ind_zmat(I1,3)=n3
462
                    Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
463
                 END IF ! izm>=4
464
!                 WRITE(*,*) "coucou 6"
465
           if (debug) THEN
466
              WRITE(*,*) 'ind_zmat 0',izm
467
              DO Ip=1,NCart
468
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(ip,1:4)
469
                 END DO
470
              SELECT CASE (NCart)
471
                 CASE (1)
472
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
473
                    if (izm.GE.3) &
474
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
475
                    Ibeg=4
476
                 CASE (2)
477
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
478
                    Ibeg=4
479
                 CASE DEFAULT
480
                    IBeg=NCart+1
481
                 END SELECT
482
              DO Ip=IBeg,izm
483
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
484
                      ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
485
              END DO
486
           END IF
487

    
488
                 idx_zmat(iat)=izm
489
!                 Call Annul(Liaisons,iat,n1)
490
!                 Liaisons(iat,0)=Liaisons(Iat,0)-1
491
                 !                  Call Annul(Liaisons,n1,iat)
492
                 n3=iat
493
                 DejaFait(Iat)=.TRUE.
494
              END IF
495
           END DO
496
           IaFaire=IaFaire+1
497

    
498
           if (debug) THEN
499
              WRITE(*,*) 'ind_zmat 5'
500
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
501
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
502
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
503
              DO Ip=4,izm
504
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
505
                      ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
506
              END DO
507
           END IF
508

    
509
        END Do              ! DO WHILE CaFaire
510

    
511

    
512
     ELSE     ! FrozBlock(I,0)==1
513
        if (debug) WRITE(*,*) 'IFrag=',IFrag,'Frozblock(I,0)>1',Frozblock(IFrag,0)
514
        ! We have many frozen atoms for one fragment. We will have to choose
515
        ! the first one, and then to decide when to swich...
516
        Iat=0
517
        I0=-1
518
        DO I=1,FrozBlock(IFrag,0)
519
           JAt=FrozBlock(IFrag,I)
520
           if (debug) WRITE(*,*) Jat, &
521
                (LiaisonsBis(Jat,Itmp),Itmp=0,LiaisonsBis(Jat,0))
522
           IF (LiaisonsBis(Jat,0).GT.I0) THEN
523
              I0=LiaisonsBis(Jat,0)
524
              Iat=Jat
525
           END IF
526
        END DO
527
        ! Iat is the starting frozen atom
528
        IF (debug) WRITE(*,*) 'Choosing atom ',iat,'as a starting atom for frag',ifrag
529
        DejaFait(iat)=.TRUE.
530
        IdxCaFaire=2
531
        CaFaire(1)=iat
532
        CaFaire(2)=0
533
        IaFaire=1
534
        FCaf(Iat)=.TRUE.
535
        DO WHILE (CaFaire(IaFaire).NE.0)
536
           n1=CaFaire(IaFaire)
537
           I1=idx_zmat(n1)
538
           n2=ind_zmat(I1,2)
539
           n3=ind_zmat(I1,3)
540
           if (debug) WRITE(*,*) 'Iafaire,n1,DejaFait,idxzmat,n2,n3',IaFaire,n1, &
541
                DejaFait(n1),idx_zmat(n1),n2,3
542
           if (debug) WRITE(*,*) 'Cafaire', &
543
                (CaFaire(J),J=Iafaire,IdxCAfaire)
544

    
545

    
546
           DO I3=1,Liaisons(n1,0)
547
              if (debug) WRITE(*,*) "Here, I3=",I3
548
              IAt=Liaisons(n1,I3)
549
              ! PFL 2007.Apr.16 ->
550
              ! We add ALL atoms linked to n1 to CaFaire
551
              ! But we delete their link to n1
552
!! PFL 2007.Aug.28 ->
553
! re-add the test on FCaf in order not to put the same atom more than once in 
554
! CaFaire array.
555
                 IF (.NOT.FCaf(Iat)) THEN
556
                    CaFaire(IdxCaFaire)=Iat
557
                    IdxCaFaire=IdxCaFaire+1
558
                    CaFaire(IdxCaFaire)=0
559
                    FCaf(Iat)=.TRUE.
560
                 END IF
561
!! <-- PFL 2007.Aug.28
562
              Call Annul(Liaisons,Iat,n1)
563
              Liaisons(iat,0)=Liaisons(Iat,0)-1
564
              ! <- PFL 2007.Apr.16
565
              IF (.NOT.DejaFait(Iat)) THEN
566
                 ! we add it to the Zmat
567
                 call vecteur(n1,iat,x,y,z,vx1,vy1,vz1,norm1)
568
                 izm=izm+1
569
                 IF (izm.EQ.2) THEN
570
                    ind_zmat(izm,1)=IAt
571
                    ind_zmat(izm,2)=n1
572
                    ind_zmat(izm,3:5)=0
573
                 ELSE
574
                    IF (n2.EQ.-1) THEN
575
                       ! This atom is defined in cartesian coordinates
576
                       ! and has not been used to put a non cart atom.
577
                       ! we will find the closest atom linked to this one amongst the atoms
578
                       ! already stored in ind_zmat
579
                       d=1e9
580
                       JAt=-1
581
                       DO I=1,NCart
582
                          If (ind_zmat(I,1).NE.n1) THEN
583
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx2,vy2,vz2,norm2)
584
                             SAng=Sinangle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
585
                             ! we take only atoms that are not aligned
586
                             if ((norm2<=d).AND.(SAng.GT.0.09d0)) THEN
587
                                Jat=ind_zmat(I,1)
588
                                d=norm2
589
                             END IF
590
                          END IF
591
                       END DO
592
                       if (JAt.EQ.-1) THEN
593
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
594
                          STOP
595
                       END IF
596
                       n2=JAt
597
                    END IF
598
                    !                    ind_zmat(I1,2)=n2
599
                    if (izm.EQ.3) THEN
600
                       ind_zmat(izm,1)=Iat
601
                       ind_zmat(izm,2)=n1
602
                       ind_zmat(izm,3)=n2
603
                    ELSE
604
                       IF (n3.EQ.-1) THEN
605
                          ! This atom is defined in cartesian coordinates
606
                          ! and has not been used to put a non cart atom.
607
                          ! we will find the closest atom linked to this one amongst the atoms
608
                          ! already stored in ind_zmat
609
                          call vecteur(n1,n2,x,y,z,vx2,vy2,vz2,norm2)
610
                          d=1e9
611
                          JAt=-1
612
                          DO I=1,NCart
613
                             If ((ind_zmat(I,1).NE.n1).AND.(ind_zmat(I,1).NE.n2)) THEN
614
                                call vecteur(n1,ind_zmat(I,1),x,y,z,vx3,vy3,vz3,norm3)
615
                                SAng=Sinangle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
616
                             if (debug) WRITE(*,*) "2-Trying izm,iat,n1,n2,n3,sang,d,norm3", &
617
                                  izm,iat,n1,n2,ind_zmat(I,1),sang,d,norm3
618

    
619
                                ! we take only atoms that are not aligned
620
                                if ((norm3<=d).AND.(SAng.GT.0.09d0)) THEN
621
                                   Jat=ind_zmat(I,1)
622
                                   d=norm3
623
                                END IF
624
                             END IF
625
                          END DO
626
                          if (JAt.EQ.-1) THEN
627
                             WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
628
                             STOP
629
                          END IF
630
                          n3=JAt
631
                       END IF
632
                       !                    ind_zmat(I1,3)=n3
633
                       Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
634
                    END IF
635
                 END IF
636
                 idx_zmat(iat)=izm
637
              !                  Call Annul(Liaisons,n1,iat)
638
                 n3=iat
639
                 DejaFait(Iat)=.TRUE.
640
                 if (debug) WRITE(*,*) "For no reason, I3=",I3
641
              END IF
642
           END DO
643
           IaFaire=IaFaire+1
644

    
645
           if (debug) THEN
646
              WRITE(*,*) 'ind_zmat 6',izm
647
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
648
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
649
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
650
              DO Ip=4,izm
651
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
652
                      ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
653
              END DO
654
           END IF
655

    
656

    
657
        END Do              ! DO WHILE CaFaire
658

    
659

    
660
     END IF  ! FrozBlock(I,0)==1
661

    
662
     IFrag=IFrag+1
663

    
664
  END DO                    ! Loop on all fragments
665

    
666

    
667
  DO IFrag=1,NbFrag
668
     IF (FrozBlock(IFrag,0).EQ.0) THEN
669
        if (debug) WRITE(*,*) 'Adding fragment :', ifrag,'with no frozen atoms'
670
        ! We have no frozen atoms for this fragment. We will have to choose
671
        ! the first atom to put.
672
        ! For now, we do not care of the 'central' atom (ie the one with
673
        ! no CP atoms...)
674
        ! We just take the atom that is the closest to the already placed
675
        ! atoms !
676

    
677
        I0=0
678
        I1=0
679
        d=1e9
680
        DO J=1,izm
681
           Jat=ind_zmat(J,1)
682
           DO I=1,NbAtfrag(IFrag)
683
              IAt=FragAt(IFrag,I)
684
              IF (.NOT.DejaFait(Iat)) THEN
685
                 Call vecteur(Iat,Jat,x,y,z,vx1,vy1,vz1,norm1)
686
                 IF (norm1.LT.d) THEN
687
                    I1=Jat
688
                    I0=Iat
689
                    d=Norm1
690
                 END IF
691
              END IF
692
           END DO
693
        END DO
694

    
695
        Iat=I0
696
        n1=I1
697
        I1=idx_zmat(n1)
698
        n2=ind_zmat(I1,2)
699
        n3=ind_zmat(I1,3)
700

    
701
        IF (debug) WRITE(*,*) Iat,' starting atom for frag',ifrag
702

    
703
        
704
        call vecteur(n1,iat,x,y,z,vx1,vy1,vz1,norm1)
705
        izm=izm+1
706
        IF (izm.EQ.2) THEN
707
           ind_zmat(izm,1)=IAt
708
           ind_zmat(izm,2)=n1
709
           ind_zmat(izm,3:5)=0
710
        ELSE
711
           IF (n2.EQ.-1) THEN
712
! This atom is defined in cartesian coordinates
713
! and has not been used to put a non cart atom.
714
! we will find the closest atom linked to this one amongst the atoms
715
! already stored in ind_zmat
716
              d=1e9
717
              JAt=-1
718
              DO I=1,NCart
719
                 If (ind_zmat(I,1).NE.n1) THEN
720
                    call vecteur(n1,ind_zmat(I,1),x,y,z,vx2,vy2,vz2,norm2)
721
                    SAng=Sinangle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
722
! we take only atoms that are not aligned
723
                    if ((norm2<=d).AND.(SAng.GT.0.09d0)) THEN
724
                       Jat=ind_zmat(I,1)
725
                       d=norm2
726
                    END IF
727
                 END IF
728
              END DO
729
              if (JAt.EQ.-1) THEN
730
                 WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
731
                 STOP
732
              END IF
733
              n2=JAt
734
           END IF
735
!                    ind_zmat(I1,2)=n2
736
        END IF
737
        if (izm.EQ.3) THEN
738
           ind_zmat(izm,1)=Iat
739
           ind_zmat(izm,2)=n1
740
           ind_zmat(izm,3)=n2
741
        ELSE
742
           IF (n3.EQ.-1) THEN
743
! This atom is defined in cartesian coordinates
744
! and has not been used to put a non cart atom.
745
! we will find the closest atom linked to this one amongst the atoms
746
! already stored in ind_zmat
747
              call vecteur(n1,n2,x,y,z,vx2,vy2,vz2,norm2)
748
              d=1e9
749
              JAt=-1
750
              DO I=1,NCart
751
                 If ((ind_zmat(I,1).NE.n1).AND.(ind_zmat(I,1).NE.n2)) THEN
752
                    call vecteur(n1,ind_zmat(I,1),x,y,z,vx3,vy3,vz3,norm3)
753
                    SAng=Sinangle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
754
                             if (debug) WRITE(*,*) "3-Trying izm,iat,n1,n2,n3,sang,d,norm3", &
755
                                  izm,iat,n1,n2,ind_zmat(I,1),sang,d,norm3
756

    
757
! we take only atoms that are not aligned
758
                    if ((norm3<=d).AND.(SAng.GT.0.09d0)) THEN
759
                       Jat=ind_zmat(I,1)
760
                       d=norm3
761
                    END IF
762
                 END IF
763
              END DO
764
              if (JAt.EQ.-1) THEN
765
                 WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
766
                 STOP
767
              END IF
768
              n3=JAt
769
           END IF
770
           !                    ind_zmat(I1,3)=n3
771
           Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
772
        END IF
773
        idx_zmat(iat)=izm
774

    
775

    
776
        DejaFait(iat)=.TRUE.
777
        IdxCaFaire=2
778
        CaFaire(1)=iat
779
        CaFaire(2)=0
780
        IaFaire=1
781
        FCaf(Iat)=.TRUE.
782
        DO WHILE (CaFaire(IaFaire).NE.0)
783
           n1=CaFaire(IaFaire)
784
           if (debug) WRITE(*,*) 'Iafaire,n1',IaFaire,n1, &
785
                DejaFait(n1),idx_zmat(n1)
786
           if (debug) WRITE(*,*) 'Cafaire', &
787
                (CaFaire(J),J=Iafaire,IdxCAfaire)
788
           I1=idx_zmat(n1)
789
           n2=ind_zmat(I1,2)
790
           n3=ind_zmat(I1,3)
791

    
792
           DO I3=1,Liaisons(n1,0)
793
              IAt=Liaisons(n1,I3)
794
              ! PFL 2007.Apr.16 ->
795
              ! We add ALL atoms linked to n1 to CaFaire
796
              ! But we delete their link to n1
797
!! PFL 2007.Aug.28 ->
798
! re-add the test on FCaf in order not to put the same atom more than once in 
799
! CaFaire array.
800
                 IF (.NOT.FCaf(Iat)) THEN
801
                    CaFaire(IdxCaFaire)=Iat
802
                    IdxCaFaire=IdxCaFaire+1
803
                    CaFaire(IdxCaFaire)=0
804
                    FCaf(Iat)=.TRUE.
805
                 END IF
806
!! <-- PFL 2007.Aug.28
807
              Call Annul(Liaisons,Iat,n1)
808
              Liaisons(iat,0)=Liaisons(Iat,0)-1
809
              ! <- PFL 2007.Apr.16
810
              IF (.NOT.DejaFait(Iat)) THEN
811
                 ! we add it to the Zmat
812
                 call vecteur(n1,iat,x,y,z,vx1,vy1,vz1,norm1)
813
                 izm=izm+1
814
                 IF (izm.EQ.2) THEN
815
                    ind_zmat(izm,1)=IAt
816
                    ind_zmat(izm,2)=n1
817
                    ind_zmat(izm,3:5)=0
818
                 ELSE
819
                    IF (n2.EQ.-1) THEN
820
! This atom is defined in cartesian coordinates
821
! and has not been used to put a non cart atom.
822
! we will find the closest atom linked to this one amongst the atoms
823
! already stored in ind_zmat
824
                       d=1e9
825
                       JAt=-1
826
                       DO I=1,NCart
827
                          If (ind_zmat(I,1).NE.n1) THEN
828
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx2,vy2,vz2,norm2)
829
                             SAng=Sinangle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
830
! we take only atoms that are not aligned
831
                             if ((norm2<=d).AND.(SAng.GT.0.09d0)) THEN
832
                                Jat=ind_zmat(I,1)
833
                                d=norm2
834
                             END IF
835
                          END IF
836
                       END DO
837
                       if (JAt.EQ.-1) THEN
838
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
839
                          STOP
840
                       END IF
841
                       n2=JAt
842
                    END IF
843
!                    ind_zmat(I1,2)=n2
844
                 END IF
845
                 if (izm.EQ.3) THEN
846
                    ind_zmat(izm,1)=Iat
847
                    ind_zmat(izm,2)=n1
848
                    ind_zmat(izm,3)=n2
849
                 ELSE
850
                    IF (n3.EQ.-1) THEN
851
! This atom is defined in cartesian coordinates
852
! and has not been used to put a non cart atom.
853
! we will find the closest atom linked to this one amongst the atoms
854
! already stored in ind_zmat
855
                       call vecteur(n1,n2,x,y,z,vx2,vy2,vz2,norm2)
856
                       d=1e9
857
                       JAt=-1
858
                       DO I=1,NCart
859
                          If ((ind_zmat(I,1).NE.n1).AND.(ind_zmat(I,1).NE.n2)) THEN
860
                             call vecteur(n1,ind_zmat(I,1),x,y,z,vx3,vy3,vz3,norm3)
861
                             SAng=Sinangle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
862
                             if (debug) WRITE(*,*) "4-Trying izm,iat,n1,n2,n3,sang,d,norm3", &
863
                                  izm,iat,n1,n2,ind_zmat(I,1),sang,d,norm3
864

    
865
! we take only atoms that are not aligned
866
                             if ((norm3<=d).AND.(SAng.GT.0.09d0)) THEN
867
                                Jat=ind_zmat(I,1)
868
                                d=norm3
869
                             END IF
870
                          END IF
871
                       END DO
872
                       if (JAt.EQ.-1) THEN
873
                          WRITE(*,*) "All cart atoms are aligned. Case non treated for now. Contact PFL"
874
                          STOP
875
                       END IF
876
                       n3=JAt
877
                    END IF
878
!                    ind_zmat(I1,3)=n3
879
                    Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
880
                 END IF
881
                 idx_zmat(iat)=izm
882
                 n3=iat
883
                 DejaFait(Iat)=.TRUE.
884
              END IF
885
           END DO
886
           IaFaire=IaFaire+1
887

    
888
           if (debug) THEN
889
              WRITE(*,*) 'ind_zmat 7',izm
890
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
891
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
892
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
893
              DO Ip=4,izm
894
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
895
                      ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
896
              END DO
897
           END IF
898

    
899

    
900
        END Do              ! DO WHILE CaFaire
901
     END IF                 ! FrozBlock(IFrag,0).EQ.0
902

    
903
  END DO                    ! Loop on all fragments without frozen atoms
904

    
905
  if (debug) THEN
906
     WRITE(*,*) Na+Izm
907
     WRITE(*,*) 'Done... :-(', izm
908
     DO J=1,Na
909
        WRITE(*,'(1X,A5,3(1X,F10.6))') Nom(Atome(J)),X(J),Y(J),Z(J)
910
     END DO
911
     DO I=1,Izm
912
        J=ind_zmat(I,1)
913
        WRITE(*,'(1X,A5,3(1X,F10.6))') 'X ',X(J),Y(J),Z(J)
914
     END DO
915
        IF (izm.NE.Na) THEN
916
           WRITE(*,*) "Atoms not done:"
917
           DO I=1,Na
918
              IF (.NOT.DejaFait(I)) WRITE(*,'(I5)',ADVANCE='NO') I
919
           END DO
920
        END IF
921

    
922
  END IF
923

    
924

    
925
  ! We have ind_zmat. We calculate val_zmat :-)
926
  if (debug) WRITE(*,*) "Calculating val_zmat"
927

    
928
  SELECT CASE (NCart)
929
     CASE (1)
930
        val_zmat(2,2)=0.d0
931
     val_zmat(2,3)=0.d0
932
     val_zmat(3,3)=0.d0
933
     n1=ind_zmat(2,1)
934
     n2=ind_zmat(2,2)
935
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
936
     val_zmat(2,1)=norm1
937

    
938
     n1=ind_zmat(3,1)
939
     n2=ind_zmat(3,2)
940
     n3=ind_zmat(3,3)
941
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
942
     val_zmat(3,1)=norm1
943

    
944
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
945
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
946
     val_zmat(3,2)=val
947
     IBeg=4
948

    
949
     CASE (2)
950
     val_zmat(3,3)=0.d0
951

    
952
     n1=ind_zmat(3,1)
953
     n2=ind_zmat(3,2)
954
     n3=ind_zmat(3,3)
955
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
956
     val_zmat(3,1)=norm1
957

    
958
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
959
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
960
     val_zmat(3,2)=val
961
     IBeg=4
962
  CASE DEFAULT
963
     Ibeg=NCart+1
964
  END SELECT
965

    
966

    
967
  DO i=IBeg,na
968

    
969
     n1=ind_zmat(i,1)
970
     n2=ind_zmat(i,2)
971
     n3=ind_zmat(i,3)
972
     n4=ind_zmat(i,4)
973

    
974
     if (debug) WRITE(*,*) "Doing i,n1,n2,n3,n4",i,n1,n2,n3,n4
975
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
976

    
977
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
978
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
979

    
980
     CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
981
     CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
982
          vx4,vy4,vz4,norm4)
983
     CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, &
984
          vx5,vy5,vz5,norm5)
985

    
986
     val_d=angle_d(vx4,vy4,vz4,norm4, vx5,vy5,vz5,norm5, &
987
          vx2,vy2,vz2,norm2)
988

    
989
     !     write(*,11) n1,n2,norm1,n3,val,n4,val_d
990
!11   format (2(1x,i3),1x,f8.4,2(1x,i3,1x,f8.3))
991

    
992
     val_zmat(i,1)=norm1
993
     val_zmat(i,2)=val
994
     val_zmat(i,3)=val_d
995

    
996
  END DO
997

    
998
  if (debug) THEN
999
     WRITE(*,*) 'DBG Cre_Zmat_Constr: ind_zmat'
1000
     DO I=1,na
1001
        WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5)
1002
     END DO
1003

    
1004
     WRITE(*,*) 'DBG Cre_Zmat_Constr: Full zmat'
1005
     DO I=1,NCart
1006
        WRITE(*,'(1X,I5,3(1X,F11.6))') ind_zmat(i,1),(val_zmat(i,j),j=1,3)
1007
     END DO
1008
     DO I=NCart+1,Na
1009
        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)
1010
     END DO
1011

    
1012
  END IF
1013

    
1014
  if (debug) WRITE(*,*) "Deallocate (FrozDist,Fragment, NbAtFrag,FragAt)"
1015
  DEALLOCATE(FrozDist,Fragment, NbAtFrag,FragAt)
1016
  if (debug) WRITE(*,*) "Deallocate FrozFrag, IdxFragAt, FrozBlock"
1017
!  DEALLOCATE(FrozFrag, IdxFragAt, FrozBlock)
1018
  DEALLOCATE(FrozFrag,FrozBlock)
1019
  if (debug) WRITE(*,*) "Deallocate (DistFroz,Liaisons)"
1020
  DEALLOCATE(DistFroz,Liaisons)
1021
  if (debug) WRITE(*,*) "Deallocate (LiaisonsIni)"
1022
  DEALLOCATE(LiaisonsIni)
1023
  if (debug) WRITE(*,*) "Deallocate(CaFaire,DejaFait,FrozAt)"
1024
  DEALLOCATE(CaFaire,DejaFait,FrozAt)
1025
  if (debug) WRITE(*,*) "Deallocate LiaisonsBis"
1026
  DEALLOCATE(LiaisonsBis)
1027
  if (debug) WRITE(*,*) "Deallocate FCart,AtCart,FCaf"
1028
  DEALLOCATE(FCart,AtCart,FCaf)
1029

    
1030
  if (debugGaussian) THEN
1031
     WRITE(*,*) 'DBG Cre_Zmat_Frag: Gaussian Zmat - START'
1032
     Call WriteMixed_Gaussian(na,atome,NCart,ind_zmat,val_zmat)
1033
     WRITE(*,*) 'DBG Cre_Zmat_Frag: Gaussian Zmat - END'
1034
  END IF
1035

    
1036

    
1037
  if (debug) Call Header("Exiting Calc_mixed_frag")
1038

    
1039
END SUBROUTINE Calc_mixed_frag
1040