Statistiques
| Révision :

root / src / Calc_zmat_constr_frag.f90

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

    
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

    
50
  CHARACTER(5) :: AtName
51
  integer(KINT) :: na,atome(na),ind_zmat(Na,5)
52
  INTEGER(KINT) :: idx_zmat(NA)
53
  real(KREAL) ::  x(Na),y(Na),z(Na),fact
54
  real(KREAL) ::  val_zmat(Na,3)
55
  real(KREAL) :: r_cov(0:Max_Z)
56
  !     Frozen contains the indices of frozen atoms
57
  INTEGER(KINT) :: Frozen(*),NFroz
58
  INTEGER(KINT), ALLOCATABLE :: FrozDist(:) ! na
59
  INTEGER(KINT) :: NbFrag,IdxFrag
60
  INTEGER(KINT), ALLOCATABLE :: Fragment(:),NbAtFrag(:) !na
61
  INTEGER(KINT), ALLOCATABLE :: FragAt(:,:) !na,na
62
  INTEGER(KINT), ALLOCATABLE :: FrozFrag(:,:) !na,3
63
  !  INTEGER(KINT), ALLOCATABLE :: IdxFragAt(:) !na
64
  INTEGER(KINT), ALLOCATABLE :: FrozBlock(:,:) !(na,0:na)
65
  REAL(KREAL), ALLOCATABLE :: DistFroz(:) !na
66

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

    
73

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

    
85

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

    
90
  REAL(KREAL), PARAMETER :: LocalNCart=0.d0
91
  REAL(KREAL) :: sDihe, Pi
92

    
93
  INTERFACE
94
     function valid(string) result (isValid)
95
       CHARACTER(*), intent(in) :: string
96
       logical                  :: isValid
97
     END function VALID
98

    
99
     FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2)
100
       use Path_module, only :  Pi,KINT, KREAL
101
       real(KREAL) ::  v1x,v1y,v1z,norm1
102
       real(KREAL) ::  v2x,v2y,v2z,norm2
103
       real(KREAL) ::  angle
104
     END FUNCTION ANGLE
105

    
106
     FUNCTION SinAngle(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) ::  SinAngle
111
     END FUNCTION SINANGLE
112

    
113

    
114
     FUNCTION angle_d(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2,v3x,v3y,v3z,norm3)
115
       use Path_module, only :  Pi,KINT, KREAL
116
       real(KREAL) ::  v1x,v1y,v1z,norm1
117
       real(KREAL) ::  v2x,v2y,v2z,norm2
118
       real(KREAL) ::  v3x,v3y,v3z,norm3
119
       real(KREAL) ::  angle_d,ca,sa
120
     END FUNCTION ANGLE_D
121

    
122
  END INTERFACE
123

    
124

    
125

    
126
  Pi=dacos(-1.d0)
127
  debug=valid("calc_zmat_constr").OR.valid("calc_zmat_contr_frag")
128
  debugGaussian=valid("zmat_gaussian")
129

    
130
  if (debug) WRITE(*,*) "=============================== Entering Calc_zmat_contr_frag ========================"
131
  if (na.le.2) THEN
132
     WRITE(*,*) "I do not work for less than 2 atoms :-p"
133
     RETURN
134
  END IF
135

    
136
  ALLOCATE(FrozDist(Na),Fragment(na), NbAtFrag(na),FragAt(na,na))
137
  !  ALLOCATE(FrozFrag(na,3), IdxFragAt(na), FrozBlock(na,0:na))
138
  ALLOCATE(FrozFrag(na,3), FrozBlock(na,0:na))
139
  ALLOCATE(DistFroz(na),Liaisons(na,0:NMaxL))
140
  ALLOCATE(LiaisonsBis(na,0:NMaxL),LiaisonsIni(na,0:NMaxL))
141
  ALLOCATE(CaFaire(na),DejaFait(Na),FCaf(na),FrozAt(na))
142

    
143
  DO i=1,na
144
     DO J=1,5
145
        Ind_Zmat(i,J)=0
146
     END DO
147
  END DO
148

    
149
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
150
!
151
!     Easy case : 3 or less atoms
152
!
153
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
154
  if (Na.eq.3) THEN
155
     d12=sqrt((x(1)-x(2))**2+(y(1)-y(2))**2+(z(1)-z(2))**2)
156
     d13=sqrt((x(1)-x(3))**2+(y(1)-y(3))**2+(z(1)-z(3))**2)
157
     d23=sqrt((x(3)-x(2))**2+(y(3)-y(2))**2+(z(3)-z(2))**2)
158
     F1213=(d12<=d13)
159
     F1323=(d13<=d23)
160
     F1223=(d12<=d23)
161
     if (debug) THEN
162
        WRITE(*,*) "DEBUG Calc_Zmat 3 atoms"
163
        WRITE(*,*) "d12,d13,d23:",d12,d13,d23
164
        WRITE(*,*) "F1213,F1323,F1223:",F1213,F1323,F1223
165
     END IF
166
     if (F1213) THEN
167
        if (F1323) THEN
168
           ind_zmat(1,1)=3
169
           ind_zmat(2,1)=1
170
           ind_zmat(2,2)=3
171
           ind_zmat(3,1)=2
172
           ind_zmat(3,2)=1
173
           ind_zmat(3,3)=3
174
        ELSE
175
           ind_zmat(1,1)=1
176
           ind_zmat(2,1)=2
177
           ind_zmat(2,2)=1
178
           ind_zmat(3,1)=3
179
           ind_zmat(3,2)=2
180
           ind_zmat(3,3)=1
181
        END IF
182
     ELSE
183
        IF (F1223) THEN
184
           ind_zmat(1,1)=2
185
           ind_zmat(2,1)=1
186
           ind_zmat(2,2)=2
187
           ind_zmat(3,1)=3
188
           ind_zmat(3,2)=1
189
           ind_zmat(3,3)=2
190
        ELSE
191
           ind_zmat(1,1)=2
192
           ind_zmat(2,1)=3
193
           ind_zmat(2,2)=2
194
           ind_zmat(3,1)=1
195
           ind_zmat(3,2)=3
196
           ind_zmat(3,3)=2
197
        END IF
198
     END IF
199
     IF (debug) THEN
200
        DO i=1,na
201
           WRITE(*,'(1X,5(1X,I5))') (ind_zmat(i,j),j=1,5)
202
        END DO
203
     END IF
204

    
205
     !     We have ind_zmat, we fill val_zmat
206
     val_zmat(1,1)=0.
207
     val_zmat(1,2)=0.
208
     val_zmat(1,3)=0.
209
     n2=ind_zmat(2,1)
210
     n1=ind_zmat(2,2)
211
     d=sqrt((x(n1)-x(n2))**2+(y(n1)-y(n2))**2+(z(n1)-z(n2))**2)
212
     val_zmat(2,1)=d
213
     val_zmat(2,2)=0.
214
     val_zmat(2,3)=0.
215
     n1=ind_zmat(3,1)
216
     n2=ind_zmat(3,2)
217
     n3=ind_zmat(3,3)
218
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
219
     if (debug) write(*,*) n1,n2,norm1
220
     val_zmat(3,1)=norm1
221

    
222
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
223
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
224
     if (debug) write(*,*) n2,n3,norm2,val
225
     val_zmat(3,2)=val
226
     val_zmat(3,3)=0.
227

    
228
     RETURN
229
  END IF
230
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
231
!
232
!  End of   Easy case : 3 or less atoms
233
!
234
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
235
!
236
! General Case 
237
!
238
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
239
!
240
! 1 - Frozen Atoms
241

    
242
! Initialization
243
  DejaFait=.False.
244
  FrozAt=.False.
245
  Liaisons=0
246
  LiaisonsBis=0
247
  ind_zmat=0
248
  val_zmat=0.d0
249

    
250
  NFroz=0
251
  I=1
252
  DO WHILE (Frozen(I).NE.0)
253
     If (Frozen(I).LT.0) THEN
254
        DO J=Frozen(I-1),abs(Frozen(I))
255
           IF (.NOT.FrozAt(J)) THEN
256
              NFroz=NFroz+1
257
              FrozAt(J)=.TRUE.
258
           END IF
259
        END DO
260
     ELSEIF (.NOT.FrozAt(Frozen(I))) THEN
261
        FrozAt(Frozen(I))=.TRUE.
262
        NFroz=NFroz+1
263
     END IF
264
  I=I+1
265
  END DO
266

    
267
  if (debug) WRITE(*,*) 'DGB zmtc NFroz=', NFroz
268
  if (debug) WRITE(*,*) 'DGB zmtc FrozAt=',(FrozAt(I),I=1,na)
269

    
270
  if (debug) THEN
271
     WRITE(*,*) "Liaisons initialized"
272
     WRITE(*,*) 'Covalent radii used'
273
     DO iat=1,na
274
        i=atome(iat)
275
        WRITE(*,*) Nom(I),Iat,r_cov(i),r_cov(i)*fact
276
     END DO
277
  END IF
278

    
279
1003 FORMAT(1X,I4,' - ',25(I5))
280
  !     DO IL=1,na
281
  !     WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
282
  !     WRITE(IOOUT,1003) Il,(LIAISONSBis(IL,JL),JL=0,NMaxL)
283
  !     END DO
284
!   First step : connectivity  are calculated
285

    
286
  Call CalcCnct(na,atome,x,y,z,LIAISONS,r_cov,fact)
287

    
288
  if (debug) THEN
289
     WRITE(*,*) "Connections calculated"
290
     DO IL=1,na
291
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
292
     END DO
293
  END IF
294

    
295
  FCaf=.TRUE.
296
  Call Decomp_frag(na,liaisons,FCaf,nbfrag,Fragment,NbAtFrag,FragAt)
297

    
298
  IF (debug) THEN
299
     WRITE(*,*) 'I found ',NbFrag, 'fragments'
300
     WRITE(*,'(20(1X,I4))') (NbAtFrag(I),I=1,NbFrag)
301
     DO I=1,NbFrag
302
        WRITE(*,*) NbAtFrag(I)
303
        WRITE(*,*) 'Fragment ', i
304
        DO J=1,Na
305
           IF (Fragment(J).EQ.I)   THEN                
306
            if (FrozAt(J))    THEN   
307
                   WRITE(*,'(1X,I3,"f",1X,A5,3(1X,F10.6))') J,Nom(Atome(J)) &
308
                        ,X(J),Y(J),Z(J)
309
               ELSE
310
                    WRITE(*,'(1X,I3,2X,A5,3(1X,F10.6))') J,Nom(Atome(J)) &
311
                      ,X(J),Y(J),Z(J)
312
                END IF
313
       END IF
314
        END DO
315
        WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
316
     END DO
317
  END IF
318

    
319

    
320
! First, we decompose the connectivity into Frozen atoms and non frozen atoms
321
  DO I=1,na
322
     LiaisonsBis(I,0)=0
323
     DO J=1,Liaisons(I,0)
324
        IF (FrozAt(Liaisons(I,J))) THEN
325
           LiaisonsBis(I,0)=LiaisonsBis(I,0)+1
326
           LiaisonsBis(I,LiaisonsBis(I,0))=Liaisons(I,J)
327
        END IF
328
     END DO
329
     IMax=LiaisonsBis(I,0)+1
330
     LiaisonsBis(I,Imax)=0
331
     DO J=1,Liaisons(I,0)
332
        IF (.NOT.FrozAt(Liaisons(I,J))) THEN
333
           LiaisonsBis(I,IMax)=LiaisonsBis(I,Imax)+1
334
           LiaisonsBis(I,LiaisonsBis(I,Imax)+Imax)=Liaisons(I,J)
335
        END IF
336
     END DO
337
  END DO
338

    
339
  if (debug) THEN
340
     WRITE(*,*) "Liaisons and LiaisonsBis"
341
     DO I=1,Na
342
        WRITE(*,'(1X,I3," -",I3,":",15(1X,I3))') I, &
343
             (Liaisons(I,J),J=0,NMaxL)
344
        WRITE(*,'(1X,I3," +",I3,":",15(1X,I3))') I, &
345
             (LiaisonsBis(I,J),J=0,NMaxL)
346
     END DO
347
  END IF
348

    
349
! Now, for each frozen atom, we count the length of the frozen block
350
! FrozBlock(I,0) contains the number of frozen atoms forming a frozen
351
!                fragment containing atom I
352
! FrozBlock(I,:) is the list of the frozen atoms of this fragment.
353
  Do I=1,na
354
     FrozBlock(I,0)=-1
355
  END DO
356
  DO I=1,na
357
     IF (FrozAt(I).AND.(FrozBlock(I,0).EQ.-1)) THEN
358
        if (debug) WRITE(*,*) 'Treating atom ',I
359
        FrozBlock(I,0)=1
360
        FrozBlock(I,1)=I
361
        DO J=1,na
362
           DejaFait(J)=.FALSE.
363
        END DO
364
        DejaFait(I)=.TRUE.
365
        DO J=1,LiaisonsBis(I,0)
366
           CaFaire(J)=LiaisonsBis(I,J)
367
        END DO
368
        IdxCaFaire=LiaisonsBis(I,0)+1
369
        CaFaire(IdxCaFaire)=0
370
        IAfaire=1
371
        FCaf=DejaFait
372
        DO WHILE (CaFaire(IAfaire).NE.0)
373
           Iat=CaFaire(IAFAire)
374
           if (debug) WRITE(*,*) 'IaFaire; Iat:', IaFaire, Iat, DejaFait(Iat)
375
           IF (.NOT.DejaFait(Iat)) THEN
376
              FrozBlock(I,0)=FrozBlock(I,0)+1
377
              FrozBlock(I,FrozBlock(I,0))=Iat
378
              DO J=1,LiaisonsBis(Iat,0)
379
                 IF ((.NOT.DejaFait(LiaisonsBis(Iat,J))).AND.(.NOT.FCaf(LiaisonsBis(Iat,J)))) THEN
380
                    CaFaire(IdxCaFaire)=LiaisonsBis(Iat,J)
381
                    IdxCaFaire=IdxCaFaire+1
382
                    CaFaire(IdxCaFaire)=0
383
                    FCaf(LiaisonsBis(Iat,J))=.TRUE.
384
                 END IF
385
              END DO
386
              !     WRITE(*,*) 'liaisonbis(Iat,0),FrozBlick(I,0)',&
387
              !                      LiaisonsBis(Iat,0), FrozBlock(I,0)
388
           END IF
389
           DejaFait(Iat)=.TRUE.
390
           IaFaire=IaFaire+1
391
        END DO
392
        if (debug) WRITE(*,*) 'I,FrozBlock(0),IaFaire',I,FrozBlock(I,0),IaFaire
393
        if (debug) WRITE(*,*) 'FrozBlock:',FrozBlock(I,1:FrozBlock(I,0))
394
        !        FrozBlock(I,1)=I
395
        !        DO J=2,IaFaire
396
        !           FrozBlock(I,J)=CaFaire(J-1)
397
        !        END DO
398
        !     We copy this block into all frozen atoms that belongs to it
399
        DO J=2,Frozblock(I,0)
400
           Iat=FrozBlock(I,J)
401
           DO K=0,FrozBlock(I,0)
402
              FrozBlock(Iat,K)=FrozBlock(I,K)
403
           END DO
404
        END DO
405
     ELSE
406
        IF (.NOT.FrozAt(I))      FrozBlock(I,0)=0
407
     END IF
408
  END DO
409

    
410
  if (debug) THEN
411
     WRITE(*,*) "FrozBlock"
412
     DO I=1,Na
413
        If (FrozAt(I))  WRITE(*,'(1X,I3," -",I3,":",15(1X,I3))') I, &
414
             (FrozBlock(I,J),J=0,FrozBlock(I,0))
415
     END DO
416
  END IF
417

    
418
  DO I=1,NbFrag
419
     FrozFrag(I,1)=0
420
     FrozFrag(I,2)=0
421
     DO J=1,NbAtFrag(I)
422
        IF (FrozAt(FragAt(I,J))) THEN
423
           FrozFrag(I,1)=FrozFrag(I,1)+1
424
           IF (FrozBlock(FragAt(I,J),0).GE.FrozFrag(I,2))  &
425
                FrozFrag(I,2)=FrozBlock(FragAt(I,J),0)
426
           if (FrozFrag(I,3).LE.LiaisonsBis(FragAt(I,J),0))& 
427
                FrozFrag(I,3)=LiaisonsBis(FragAt(I,J),0)
428
        END IF
429
     END DO
430
     IF (debug) WRITE(*,*) 'Frag :',I,FrozFrag(I,1), &
431
          ' frozen atoms,max linked:'  &
432
          ,FrozFrag(I,2),' with at most',FrozFrag(I,3),' frozen'
433
  END DO
434

    
435
  !     We will now build the molecule fragment by fragment
436
  !     First the frozen atoms, then the rest of the fragment
437
  !     We choose the starting fragment with two criteria:
438
  !     1- Number of linked frozen atoms:
439
  !       * >=3 is good as it fully defines the coordinate space
440
  !       * 2 is ok as we can either use a 3rd atom from the same fragment
441
  !       or add a X atom somewhere but this complicates quite a lot the way
442
  !       to treat the conversion from cartesian to zmat latter
443
  !       * 1 is bad...
444
  !     2- Max number of linked frozen atoms
445
  !     this allows us to deal more easily with cases 1- when number of 
446
  !     directly linked frozen atoms is less than 3
447

    
448
  IFrag=0
449
  I0=0
450
  I1=0
451
  DO I=1,NbFrag
452
     SELECT CASE(FrozFrag(I,3)-I0)
453
     CASE (1:)
454
        IFrag=I
455
        I0=FrozFrag(I,3)
456
        I1=FrozFrag(I,2)
457
     CASE (0)
458
        if (FrozFrag(I,2).GT.I1) THEN
459
           IFrag=I
460
           I0=FrozFrag(I,3)
461
           I1=FrozFrag(I,2)
462
        END IF
463
     END SELECT
464
  END DO
465

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

    
468
  !     We will build the first fragment in a special way, as it will
469
  !     set the coordinates system
470
  !     We look for the frozen atom that is linked to the maximum frozen atom,
471
  !     and belongs to the longer fragment
472
  I0=0
473
  I1=0
474
  DO I=1,NbAtFrag(IFrag)
475
     IF (FrozAt(FragAt(IFrag,I))) THEN
476
        SELECT CASE(LiaisonsBis(FragAt(IFrag,I),0)-I0)
477
        CASE (1:) 
478
           IAt=FragAt(IFrag,I)
479
           I0=LiaisonsBis(IAt,0)
480
           I1=FrozBlock(IAt,0)
481
        CASE (0)
482
           IF (FrozBlock(FragAt(IFrag,I),0).GT.I1) THEN
483
              IAt=FragAt(IFrag,I)
484
              I0=LiaisonsBis(Iat,0)
485
              I1=FrozBlock(Iat,0)
486
           END IF
487
        END SELECT
488
     END IF
489
     if (debug) WRITE(*,*) 'DBG: I,FragAt(IFrag,I),IAt,I0,I1',I,FragAt(IFrag,I),IAt,I0,I1
490
  END DO
491

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

    
494
  DO I=1,na
495
     DejaFait(I)=.FALSE.
496
     FCaf(I)=.FALSE.
497
  END DO
498

    
499
  izm=0
500
  SELECT CASE (I0)
501
  CASE(3:)
502
     if (debug) WRITE(*,*) 'DBG select case I0 3'
503
     n0=Iat
504
     !     We search for the fourth atom while making sure that the dihedral angle
505
     !     is not 0 or Pi
506
     ITmp=2
507
     sDihe=0.
508
     n2=IAt
509
     n3=LiaisonsBis(Iat,1)
510
     ! We search for the third atom while making sure that it is not aligned with first two !
511
     DO While ((ITmp.LE.LiaisonsBis(Iat,0)).AND.(sDihe.LE.0.09d0))
512
        n4=LiaisonsBis(Iat,Itmp)
513
        CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
514
        CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
515
        val_d=angle(vx3,vy3,vz3,norm3,vx2,vy2,vz2,norm2)
516
        sDiHe=abs(sin(val_d*pi/180.d0))
517
        if (debug) Write(*,*) 'Trying n2,n3,n4,sdihe,val_d',n2,n3,n4,sdihe,val_d
518
        Itmp=Itmp+1
519
     END DO
520
     If (debug) WRITE(*,*) 'Itmp,LiaisonsBis',Itmp,LiaisonsBis(Iat,1:NMaxL)
521
     LiaisonsBis(Iat,Itmp-1)=LiaisonsBis(iat,2)
522
     LiaisonsBis(Iat,2)=n4
523
     If (debug) WRITE(*,*) 'Itmp,LiaisonsBis',Itmp,LiaisonsBis(Iat,1:NMaxL)
524

    
525
     if (sDihe.LE.0.09d0) THEN
526
        WRITE(*,*) "Dans le caca car tous les atoms de ce block sont align?s!"
527
     END IF
528

    
529
     CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, &
530
          vx5,vy5,vz5,norm5)
531

    
532

    
533
     Itmp=2
534
     sDiHe=0.
535

    
536
     DO While ((ITmp.LT.LiaisonsBis(Iat,0)).AND.(sDihe.LE.0.09d0))
537
        ITmp=ITmp+1
538
        n1=LiaisonsBis(Iat,Itmp)
539
        if (debug) WRITe(*,*) 'trying n1,n2,n3,n4',n1,n2,n3,n4
540
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
541
        ! Is this atom aligned with n2-n3 ?
542
        val_d=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
543
        sDiHe=abs(sin(val_d*pi/180.d0))
544
        if (debug) Write(*,*) 'Angle n3-n2-n1',val_d
545
        if (sDiHe.le.0.09d0) THEN
546
           ! As atoms n2,n3 and n4 are not aligned, we interchange n3 and n4 so that n1,n2 and n3 are not aligned
547
           if (debug) WRITE(*,*) "n3-n2-n1 aligned, we interchange n3 and n4"
548
           n1=n3
549
           n3=n4
550
           n4=n1
551
           n1=LiaisonsBis(Iat,ITmp)
552
           CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)           
553
           CALL vecteur(n2,n4,x,y,z,vx3,vy3,vz3,norm3)           
554
           val_d=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
555
           if (debug) Write(*,*) 'NEW Angle n3-n2-n1',val_d
556
        END IF
557

    
558
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
559
        ! avant de tester l'angle diedre, il faut verifier que ce 4e atome n'est pas
560
        ! aligne avec les 2 premiers. 
561
        ! comme on a deja test? que les 3 premiers ne sont pas alignes,
562
        ! s'il est align? avec les 2 premiers, on peut inverser le role de 2 et 3.
563
        ! On pourrait tout simplier en faisant une bete recherche parmi tous les atomes geles
564
        ! de ce bloc (au moins 4 ?) avec le critere 1) on les range par distance croissante
565
        ! 2) on les scanne tant que l'angle valence n'est pas bon, puis tant que diehedre pas bon
566
        ! on pourrait comme ca faire un tableau avec les atomes ranges d'abord pour le fragment s?lectionn?
567
        ! puis les atomes des autres fragment par distance croissante.
568
        ! les autres fragments ne seraient additonn?s que si l'on ne trouve pas notre bonheur dans le premier bloc
569
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
570

    
571
        CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
572
             vx4,vy4,vz4,norm4)
573
        val_d=angle_d(vx4,vy4,vz4,norm4,vx5,vy5,vz5,norm5, &
574
             vx2,vy2,vz2,norm2)
575
        sDihe=abs(sin(val_d*pi/180.d0))
576
        if (debug) WRITE(*,*) 'n2,n3,n4,n1, angle_d',n2,n3,n4,n1,val_d
577
     END DO
578

    
579
     DejaFait(n2)=.TRUE.
580
     DejaFait(n3)=.TRUE.
581
     DejaFait(n4)=.TRUE.
582

    
583
     if (sDihe.LE.0.09d0) THEN
584
        !     None of the frozen atoms linked to IAt are good to define the third
585
        !     direction in space...
586
        !     We will look at the other frozen atoms
587
        !     we might improve the search so as to take the atom closest to IAt
588
        if (debug) WRITE(*,*) "All atoms linked to ",Iat," are in a plane. Looking for other frozen atoms"
589
        ITmp=0
590
        DO I=1,NbAtFrag(IFrag)
591
           JAt=FragAt(IFrag,I)
592
           if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
593
              n1=JAt
594
              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
595
              CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
596
                   vx4,vy4,vz4,norm4)
597
              val_d=angle_d(vx4,vy4,vz4,norm4, &
598
                   vx5,vy5,vz5,norm5, &
599
                   vx2,vy2,vz2,norm2)
600
              if (abs(sin(val_d)).GE.0.09D0) THEN
601
                 ITmp=ITmp+1
602
                 DistFroz(ITmp)=Norm1
603
                 FrozDist(ITmp)=JAt
604
              END IF
605
           END IF
606
        END DO
607
        IF (ITmp.EQ.0) THEN
608
           !     All dihedral angles between frozen atoms are less than 5?
609
           !     (or more than 175?). We have to look at other fragments :-(
610
           DO I=1,NFroz
611
              Jat=Frozen(I)
612
              if (.NOT.DejaFait(JAt)) THEN
613
                 n1=JAt
614
                 CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
615
                 CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
616
                      vx4,vy4,vz4,norm4)
617
                 val_d=angle_d(vx4,vy4,vz4,norm4, &
618
                      vx5,vy5,vz5,norm5, &
619
                      vx2,vy2,vz2,norm2)
620
                 if (abs(sin(val_d)).GE.0.09D0) THEN
621
                    ITmp=ITmp+1
622
                    DistFroz(ITmp)=Norm1
623
                    FrozDist(ITmp)=JAt
624
                 END IF
625
              END IF
626
           END DO
627
           IF (ITmp.EQ.0) THEN
628
              !     All frozen atoms are in a plane... too bad
629
              WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
630
              WRITE(*,*) 'For now, I do not treat this case'
631
              STOP
632
           END IF
633
        END IF
634
        I1=0
635
        d=1e9
636
        DO I=1,ITmp
637
           IF (DistFroz(I).LE.d) THEN
638
              d=DistFroz(I)
639
              I1=FrozDist(I)
640
           END IF
641
        END DO
642
     ELSE                !(sDihe.LE.0.09d0)
643
        I1=FrozBlock(IAt,ITmp)
644
        if (debug) WRITE(*,*) 'I1,n1:',I1,n1
645
     END IF                 !(sDihe.LE.0.09d0)
646
     !     we now have the atom that is closer to the first one and that
647
     !     forms a non 0/Pi dihedral angle
648

    
649
     ind_zmat(1,1)=n2
650
     ind_zmat(2,1)=n3
651
     ind_zmat(2,2)=n2
652
     ind_zmat(3,1)=n4
653
     ind_zmat(3,2)=n2
654
     ind_zmat(3,3)=n3
655
     DejaFait(n2)=.TRUE.
656
     DejaFait(n3)=.TRUE.
657
     DejaFait(n4)=.TRUE.
658
     CaFaire(1)=n3
659
     CaFaire(2)=n4
660

    
661
     ind_zmat(4,1)=I1
662
     ind_zmat(4,2)=n2
663
     ind_zmat(4,3)=n3
664
     ind_zmat(4,4)=n4
665
     DejaFait(I1)=.TRUE.
666
     CaFaire(3)=I1
667
     CaFaire(4)=0
668
     IdxCaFaire=4
669

    
670
     FCaf(n2)=.TRUE.
671
     FCaf(n3)=.TRUE.
672
     FCaf(I1)=.TRUE.
673
     izm=4
674
     DO I=3,LiaisonsBis(Iat,0)
675
        IF (.NOT.DejaFait(LiaisonsBis(Iat,I))) THEN
676
           izm=izm+1
677
           !           ind_zmat(izm,1)=LiaisonsBis(Iat,I)
678
           !           ind_zmat(izm,2)=n2
679
           !           ind_zmat(izm,3)=n3
680
           !           ind_zmat(izm,4)=n4
681
           Call add2indzmat(na,izm,LiaisonsBis(Iat,I),n2,n3,n4,ind_zmat,x,y,z)
682
           IF (.NOT.FCaf(LiaisonsBis(Iat,I))) THEN
683
              CaFaire(IdxCaFaire)=LiaisonsBis(Iat,I)
684
              IdxCaFaire=IdxCaFaire+1
685
              CaFaire(IdxCaFaire)=0
686
              FCaf(LiaisonsBis(Iat,I))=.TRUE.
687
           END IF
688
           DejaFait(LiaisonsBis(Iat,I))=.TRUE.
689
        END IF
690
     END DO
691

    
692
     if (debug) THEN
693
        WRITE(*,*) "Ind_zmat 0 - SELECT CASE I0 3: -- izm=",izm
694
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
695
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
696
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
697
        DO I=4,izm
698
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
699
                ind_zmat(I,3), ind_zmat(I,4)
700
        END DO
701
     END IF
702

    
703

    
704
     !     First four atoms (at least) have been put we go on with next parts
705
     !     of this fragment... later
706

    
707

    
708
  CASE(2)
709
     if (debug) WRITE(*,*) 'DBG select case I0 2'
710
     if (debug) WRITE(*,*) 'ATTENTION For now, case with only 3 frozen atoms non treated'
711
     ind_zmat(1,1)=IAt
712
     ind_zmat(2,1)=liaisonsBis(IAt,1)
713
     ind_zmat(2,2)=IAt
714
     ind_zmat(3,1)=LiaisonsBis(IAt,2)
715
     ind_zmat(3,2)=IAt
716
     ind_zmat(3,3)=LiaisonsBis(IAt,1)
717
     DejaFait(IAt)=.TRUE.
718
     DejaFait(LiaisonsBis(Iat,1))=.TRUE.
719
     DejaFait(LiaisonsBis(Iat,2))=.TRUE.
720
     CaFaire(1)=LiaisonsBis(Iat,1)
721
     CaFaire(2)=LiaisonsBis(Iat,2)
722
     FCaf(LiaisonsBis(Iat,1))=.TRUE.
723
     FCaf(LiaisonsBis(Iat,2))=.TRUE.
724

    
725
     !     We search for a fourth atom, first in the FrozBlock atoms
726
     ITmp=2
727
     sDihe=0.
728
     n2=IAt
729
     n3=LiaisonsBis(Iat,1)
730
     n4=LiaisonsBis(Iat,2)
731
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
732
     CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
733
     CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, &
734
          vx5,vy5,vz5,norm5)
735

    
736
     DO While ((ITmp.LE.FrozBlock(Iat,0)).AND.(sDihe.LE.0.09d0))
737
        ITmp=ITmp+1
738
        n1=FrozBlock(Iat,Itmp)
739
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
740
        CALL produit_vect(vx1,vy1,vz1, vx2,vy2,vz2, &
741
             vx4,vy4,vz4,norm4)
742
        val_d=angle_d(vx4,vy4,vz4,norm4,  &
743
             vx5,vy5,vz5,norm5,           &
744
             vx2,vy2,vz2,norm2)
745
        sDihe=abs(sin(val_d))
746
     END DO
747
     IF (debug) WRITE(*,*) 'DBG 4th atom, ITmp, sDihe',ITmp, sDihe
748
     if (sDihe.LE.0.09d0) THEN
749
        !     None of the frozen atoms linked to IAt are good to define the third
750
        !     direction in space...
751
        !     We will look at the other frozen atoms
752
        !     we might improve the search so as to take the atom closest to IAt
753
        ITmp=0
754
        DO I=1,NbAtFrag(IFrag)
755
           JAt=FragAt(IFrag,I)
756
           if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
757
              n1=JAt
758
              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
759
              CALL produit_vect(vx1,vy1,vz1, vx2,vy2,vz2,   &
760
                   vx4,vy4,vz4,norm4)
761
              val_d=angle_d(vx4,vy4,vz4,norm4,    &
762
                   vx5,vy5,vz5,norm5,              &
763
                   vx2,vy2,vz2,norm2)
764
              if (abs(sin(val_d)).GE.0.09D0) THEN
765
                 ITmp=ITmp+1
766
                 DistFroz(ITmp)=Norm1
767
                 FrozDist(ITmp)=JAt
768
              END IF
769
           END IF
770
        END DO
771
        IF (ITmp.EQ.0) THEN
772
           !     All dihedral angles between frozen atoms are less than 5?
773
           !     (or more than 175?). We have to look at other fragments :-(
774
           DO I=1,NFroz
775
              Jat=Frozen(I)
776
              if (.NOT.DejaFait(JAt)) THEN
777
                 n1=JAt
778
                 CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
779
                 CALL produit_vect(vx1,vy1,vz1, vx2,vy2,vz2,   &
780
                      vx4,vy4,vz4,norm4)
781
                 val_d=angle_d(vx4,vy4,vz4,norm4,       &
782
                      vx5,vy5,vz5,norm5,                 &
783
                      vx2,vy2,vz2,norm2)
784
                 if (abs(sin(val_d)).GE.0.09D0) THEN
785
                    ITmp=ITmp+1
786
                    DistFroz(ITmp)=Norm1
787
                    FrozDist(ITmp)=JAt
788
                 END IF
789
              END IF
790
           END DO
791
           IF (ITmp.EQ.0) THEN
792
              !     All frozen atoms are in a plane... too bad
793
              WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
794
              WRITE(*,*) 'For now, I do not treat this case'
795
              STOP
796
           END IF
797
        END IF
798
        I1=0
799
        d=1e9
800
        DO I=1,ITmp
801
           IF (DistFroz(I).LE.d) THEN
802
              d=DistFroz(I)
803
              I1=FrozDist(I)
804
           END IF
805
        END DO
806
     ELSE                   !(sDihe.LE.0.09d0)
807
        I1=FrozBlock(IAt,ITmp)
808
     END IF                 !(sDihe.LE.0.09d0)
809
     !     we now have the atom that is closer to the first one and that
810
     !     forms a non 0/Pi dihedral angle
811
     !     ind_zmat(4,1)=I1
812
     !     ind_zmat(4,2)=IAt
813
     !     ind_zmat(4,3)=LiaisonsBis(Iat,1)
814
     !     ind_zmat(4,4)=LiaisonsBis(Iat,2)
815
     n3=LiaisonsBis(Iat,1)
816
     n4=LiaisonsBis(Iat,2)
817
     Call add2indzmat(na,4,I1,Iat,n3,n4,ind_zmat,x,y,z)
818
     LiaisonsBis(Iat,1)=n3
819
     LiaisonsBis(Iat,2)=n4
820
     DejaFait(I1)=.TRUE.
821
     CaFaire(3)=I1
822
     CaFaire(4)=0
823
     IdxCaFaire=4
824
     izm=4
825
     FCaf(I1)=.TRUE.
826

    
827
  CASE(1)
828
     if (debug) WRITE(*,*) 'DBG select case I0 1'
829
     ind_zmat(1,1)=IAt
830
     ind_zmat(2,1)=liaisonsBis(IAt,1)
831
     ind_zmat(2,2)=IAt
832
     DejaFait(IAt)=.TRUE.
833
     DejaFait(LiaisonsBis(Iat,1))=.TRUE.
834
     IdxCaFaire=2
835
     CaFaire(1)=LiaisonsBis(Iat,1)
836
     CaFaire(2)=0
837
     FCaf(LiaisonsBis(Iat,1))=.TRUE.
838

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

    
843
     IF (FrozBlock(Iat,0).GT.2) THEN
844
        WRITE(*,*) 'I found some inconsistancy: IAt linked to 1'
845
        WRITE(*,*) 'Atom only, but belongs to a frozblock of at '
846
        WRITE(*,*) 'least 3 atoms. IAt, FrozBlock'
847
        WRITE(*,*) Iat,(FrozBlock(IAt,J),J=0,FrozBlock(Iat,0))
848
        STOP
849
     END IF
850

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

    
855
     ITmp=0
856
     CALL vecteur(LiaisonsBis(Iat,1),IAt,x,y,z,vx2,vy2,vz2,norm2)
857

    
858
     DO I=1,NbAtFrag(IFrag)
859
        JAt=FragAt(IFrag,I)
860
        if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
861
           CALL vecteur(JAt,IAt,x,y,z,vx1,vy1,vz1,norm1)
862
           if (abs(cos(angle(vx1,vy1,vz1,norm1,  &
863
                vx2,vy2,vz2,norm2))).LE.0.996d0) THEN
864
              ITmp=ITmp+1
865
              DistFroz(ITmp)=Norm1
866
              FrozDist(ITmp)=JAt
867
           END IF
868
        END IF
869
     END DO
870

    
871
     IF (ITMP.EQ.0) THEN
872
        !     We have no frozen atoms correct in this fragment, we use
873
        !     atoms from other fragments
874
        DO I=1,NFroz
875
           Jat=Frozen(I)
876
           if (.NOT.DejaFait(JAt)) THEN
877
              CALL vecteur(JAt,IAt,x,y,z,vx1,vy1,vz1,norm1)
878
              if (abs(cos(angle(vx1,vy1,vz1,norm1, &
879
                   vx2,vy2,vz2,norm2))).LE.0.996d0) THEN
880
                 ITmp=ITmp+1
881
                 DistFroz(ITmp)=Norm1
882
                 FrozDist(ITmp)=JAt
883
              END IF
884
           END IF
885
        END DO
886
        IF (ITMP.EQ.0) THEN
887
           WRITE(*,*) 'It seems all frozen atoms are aligned'
888
           WRITE(*,*) 'Case non treated for now :-( '
889
           STOP
890
        END IF
891
     END IF
892

    
893
     I1=0
894
     d=1e9
895
     DO I=1,ITmp
896
        IF (DistFroz(I).LE.d) THEN
897
           I1=FrozDist(I)
898
           d=DistFroz(I)
899
        END IF
900
     END DO
901

    
902
     !     we now have the atom that is closer to the first one and that
903
     !     forms a non 0/Pi valence angle
904
     ind_zmat(3,1)=I1
905
     ind_zmat(3,2)=IAt
906
     ind_zmat(3,3)=LiaisonsBis(Iat,1)
907
     DejaFait(I1)=.TRUE.
908
     CaFaire(2)=I1
909
     FCaf(I1)=.TRUE.
910

    
911

    
912
     !     we search for a fourth atom !
913
     !     We search for a fourth atom, first in the FrozBlock atoms
914
     ITmp=2
915
     sDihe=0.
916
     n2=IAt
917
     n3=LiaisonsBis(Iat,1)
918
     n4=I1
919
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
920
     CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
921
     CALL produit_vect(vx3,vy3,vz3, vx2,vy2,vz2,  &
922
          vx5,vy5,vz5,norm5)
923

    
924
     !     We will look at the other frozen atoms
925
     !     we might improve the search so as to take the atom closest to IAt
926
     ITmp=0
927
     DO I=1,NbAtFrag(IFrag)
928
        JAt=FragAt(IFrag,I)
929
        if (FrozAt(Jat).AND.(.NOT.DejaFait(JAt))) THEN
930
           n1=JAt
931
           CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
932
           CALL produit_vect(vx1,vy1,vz1, vx2,vy2,vz2, &
933
                vx4,vy4,vz4,norm4)
934
           val_d=angle_d(vx4,vy4,vz4,norm4,  &
935
                vx5,vy5,vz5,norm5,   &
936
                vx2,vy2,vz2,norm2)
937
           if (abs(sin(val_d)).GE.0.09D0) THEN
938
              ITmp=ITmp+1
939
              DistFroz(ITmp)=Norm1
940
              FrozDist(ITmp)=JAt
941
           END IF
942
        END IF
943
     END DO
944
     IF (ITmp.EQ.0) THEN
945
        !     All dihedral angles between frozen atoms are less than 5?
946
        !     (or more than 175?). We have to look at other fragments :-(
947
        DO I=1,NFroz
948
           Jat=Frozen(I)
949
           if (.NOT.DejaFait(JAt)) THEN
950
              n1=JAt
951
              CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
952
              CALL produit_vect(vx1,vy1,vz1, vx2,vy2,vz2, &
953
                   vx4,vy4,vz4,norm4)
954
              val_d=angle_d(vx4,vy4,vz4,norm4,   &
955
                   vx5,vy5,vz5,norm5,           &
956
                   vx2,vy2,vz2,norm2)
957
              if (abs(sin(val_d)).GE.0.09D0) THEN
958
                 ITmp=ITmp+1
959
                 DistFroz(ITmp)=Norm1
960
                 FrozDist(ITmp)=JAt
961
              END IF
962
           END IF
963
        END DO
964
        IF (ITmp.EQ.0) THEN
965
           !     All frozen atoms are in a plane... too bad
966
           WRITE(*,*) 'ERROR: It seems that all frozen atoms are in a plane'
967
           WRITE(*,*) 'For now, I do not treat this case'
968
           STOP
969
        END IF
970
     END IF                 ! ITmp.EQ.0 after scaning fragment
971
     I1=0
972
     d=1e9
973
     DO I=1,ITmp
974
        IF (DistFroz(I).LE.d) THEN
975
           d=DistFroz(I)
976
           I1=FrozDist(I)
977
        END IF
978
     END DO
979

    
980
     !     we now have the atom that is closer to the first one and that
981
     !     forms a non 0/Pi dihedral angle
982
     !     ind_zmat(4,1)=I1
983
     !     ind_zmat(4,2)=IAt
984
     !     ind_zmat(4,3)=ind_zmat(2,1)
985
     !     ind_zmat(4,4)=ind_zmat(3,1)
986
     n3=ind_zmat(2,1)
987
     n4=ind_zmat(3,1)
988
     Call add2indzmat(na,4,I1,IAt,n3,n4,ind_zmat,x,y,z)
989
     ind_zmat(2,1)=n3
990
     ind_zmat(3,1)=n4
991
     DejaFait(I1)=.TRUE.
992
     CaFaire(3)=I1
993
     CaFaire(4)=0
994
     IdxCaFaire=4
995
     izm=4
996
     FCaf(I1)=.TRUE.
997

    
998
  CASE(0)
999
     WRITE(*,*) 'All frozen atoms are separated .. '
1000
     WRITE(*,*) 'this case should be treated separately !'
1001
     STOP
1002
  END SELECT
1003

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

    
1015
  DO I=1,izm
1016
     Idx_zmat(ind_zmat(I,1))=i
1017
  END Do
1018

    
1019
  !     at least first four (frozen) atoms of this fragment done...
1020
  !     we empty the 'cafaire' array before pursuing
1021
  IAFaire=1
1022
  DO WHILE (CaFaire(IaFaire).NE.0)
1023
     n1=CaFaire(IaFaire)
1024
     n2=ind_zmat(idx_zmat(N1),2)
1025
     if (idx_zmat(N1).EQ.2) THEN
1026
        !     We have a (small) problem: we have to add atoms linked to the 2nd
1027
        !     atom of the zmat. This is a pb because we do not know
1028
        !     which atom to use to define the dihedral angle
1029
        !     we take the third atom of the zmat
1030
        n3=ind_zmat(3,1)
1031
     ELSE
1032
        n3=ind_zmat(idx_zmat(n1),3)
1033
     END IF
1034
     IF (LiaisonsBis(n1,0).GE.1) THEN
1035
        IAt=LiaisonsBis(n1,1)
1036
        if (.NOT.DejaFait(Iat)) THEN
1037
           izm=izm+1
1038
           if (debug) WRITE(*,*) ">0< Adding atom ",Iat,"position izm=",izm
1039
           !           ind_zmat(izm,1)=iat
1040
           !           ind_zmat(izm,2)=n1
1041
           !           ind_zmat(izm,3)=n2
1042
           !           ind_zmat(izm,4)=n3
1043
           Call add2indzmat(na,izm,iat,n1,n2,n3,ind_zmat,x,y,z)
1044
           Idx_zmat(iat)=izm
1045
           n3=iat
1046
           IF (.NOT.FCaf(Iat)) THEN
1047
              CaFaire(IdxCaFaire)=iat
1048
              IdxCaFaire=IdxCaFaire+1
1049
              CaFaire(IdxCaFaire)=0
1050
              FCaf(Iat)=.TRUE.
1051
           END IF
1052
           DejaFait(iat)=.TRUE.
1053
        END IF
1054
     END IF
1055
     DO I=2,LiaisonsBis(n1,0)
1056
        IAt=LiaisonsBis(n1,I)
1057
! PFL 29.Aug.2008 ->
1058
! We dissociate the test on 'DejaFait' that indicates that this atom
1059
! has already been put in the Zmat
1060
! from the test on FCaf that indicates that this atom has been put in the
1061
! 'CAFaire' list that deals with identifying its connectivity.
1062
! Those two test might differ for a frozen atom linked to non frozen atoms.
1063
        IF (.NOT.DejaFait(Iat)) THEN
1064
           izm=izm+1
1065
           if (debug) WRITE(*,*) ">1< Adding atom ",Iat,"position izm=",izm
1066
           !           ind_zmat(izm,1)=iat
1067
           !           ind_zmat(izm,2)=n1
1068
           !           ind_zmat(izm,3)=n2
1069
           !           ind_zmat(izm,4)=n3
1070
           Call add2indzmat(na,izm,iat,n1,n2,n3,ind_zmat,x,y,z)
1071
           idx_zmat(iat)=izm
1072
           DejaFait(iat)=.TRUE.
1073
        END IF
1074
        IF (.NOT.FCaf(Iat)) THEN
1075
           CaFaire(IdxCaFaire)=iat
1076
           IdxCaFaire=IdxCaFaire+1
1077
           CaFaire(IdxCaFaire)=0
1078
           FCaf(Iat)=.TRUE.
1079
        END IF
1080
! <- PFL 29.Aug.2008
1081
     END DO
1082
     IaFaire=IaFaire+1
1083
  END Do                    ! DO WHILE CaFaire
1084

    
1085
  if (debug) THEN
1086
     WRITE(*,*) 'ind_zmat 2, izm=',izm
1087
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1088
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1089
     WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1090
     DO I=4,izm
1091
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(I,1), ind_zmat(I,2),  &
1092
             ind_zmat(I,3), ind_zmat(I,4)
1093
     END DO
1094
  END IF
1095

    
1096
  !     We have finished putting atoms linked to the first one
1097
  !     we will add other frozen atoms of this fragment
1098
  DO I=1,NbAtFrag(IFrag)
1099
     Iat=FragAt(IFrag,I)
1100
     if (debug) WRITE(*,*) "DBG: I,Iat,Frozat,dejafait,frozbloc",I,Iat,FrozAt(Iat), DejaFait(Iat),FrozBlock(Iat,0)
1101
     IF (FrozAt(Iat).AND.(.NOT.DejaFait(Iat))) THEN
1102
        !     in order to have the zmat as connected as possible,
1103
        !     we look if this atom belongs to a frozblock
1104
        if (debug) WRITE(*,*) 'Treating atom I,Iat, FrozBlock ',I,Iat, FrozBlock(Iat,0)
1105
        IF (FrozBlock(Iat,0).EQ.1) THEN
1106
           !     it is a lonely atom :-)
1107
           d=1e9
1108
           DO J=1,izm
1109
              Call vecteur(iat,ind_zmat(j,1),x,y,z,vx1,vy1,vz1,norm1)
1110
              if (norm1.le.d) THEN
1111
                 Jat=j
1112
                 d=norm1
1113
              END IF
1114
           END DO
1115
           n2=ind_zmat(jat,1)
1116
           SELECT CASE(jat)
1117
           CASE (1)
1118
              n3=ind_zmat(2,1)
1119
              n4=ind_zmat(3,1)
1120
           CASE (2)
1121
              n3=ind_zmat(1,1)
1122
              n4=ind_zmat(3,1)
1123
           CASE DEFAULT
1124
              n3=ind_zmat(jAt,2)
1125
              n4=ind_zmat(jat,3)
1126
           END SELECT
1127
           izm=izm+1
1128
           !           ind_zmat(izm,1)=iat
1129
           !           ind_zmat(izm,2)=n2
1130
           !           ind_zmat(izm,3)=n3
1131
           !           ind_zmat(izm,4)=n4
1132
           Call add2indzmat(na,izm,iat,n2,n3,n4,ind_zmat,x,y,z)
1133
           DejaFait(iat)=.TRUE.
1134
           idx_zmat(iat)=iat
1135
        ELSE        !(FrozBlock(Iat,0).EQ.1)
1136
           !     we have a group of atoms
1137
           !     We search for the atom of the group with the most links
1138
           ITmp=-1
1139
           DO J=1,FrozBlock(Iat,0)
1140
              Jat=FrozBlock(Iat,J)
1141
              IF ((.NOT.DejaFait(Jat)).AND.  &
1142
                   (LiaisonsBis(Jat,0).GT.ITMP)) THEN
1143
                 JL=Jat
1144
                 ITmp=LiaisonsBis(Jat,0)
1145
              END IF
1146
           END DO
1147
           if (debug) WRITE(*,*) 'JL,ITmp:',JL,ITmp
1148
           Iat=JL
1149
           d=1e9
1150
           DO J=1,izm
1151
              Call vecteur(iat,ind_zmat(j,1),x,y,z, vx1,vy1,vz1,norm1)
1152
              if (norm1.le.d) THEN
1153
                 Jat=j
1154
                 d=norm1
1155
              END IF
1156
           END DO
1157
           if (debug) WRITE(*,*) 'Jat,d:',Jat,d
1158
           n2=ind_zmat(jat,1)
1159
           SELECT CASE(jat)
1160
           CASE (1)
1161
              n3=ind_zmat(2,1)
1162
              n4=ind_zmat(3,1)
1163
           CASE (2)
1164
              n3=ind_zmat(1,1)
1165
              n4=ind_zmat(3,1)
1166
           CASE DEFAULT
1167
              n3=ind_zmat(jAt,2)
1168
              n4=ind_zmat(jat,3)
1169
           END SELECT
1170
           izm=izm+1
1171
           !           ind_zmat(izm,1)=iat
1172
           !           ind_zmat(izm,2)=n2
1173
           !           ind_zmat(izm,3)=n3
1174
           !           ind_zmat(izm,4)=n4
1175
           Call add2indzmat(na,izm,iat,n2,n3,n4,ind_zmat,x,y,z)
1176
           idx_zmat(iat)=izm
1177
           DejaFait(iat)=.TRUE.
1178
           IdxCaFaire=2
1179
           CaFaire(1)=iat
1180
           CaFaire(2)=0
1181
           FCaf(Iat)=.TRUE.
1182

    
1183
           if (debug) WRITE(*,*) izm,iat,n2,n3,n4
1184

    
1185
           IaFaire=1
1186
           DO WHILE (CaFaire(IaFaire).NE.0)
1187
              n1=CaFaire(IaFaire)
1188
              n2=ind_zmat(idx_zmat(N1),2)
1189
              if (debug) WRITE(*,*) 'DBG Cafaire, Iafaire,n1,n2',Iafaire,n1,n2
1190
              if (idx_zmat(N1).EQ.2) THEN
1191
                 !     We have a (small) problem: we have to add atoms linked to the 2nd
1192
                 !     atom of the zmat. This is a pb because we do not know
1193
                 !     which atom to use to define the dihedral angle
1194
                 !     we take the third atom of the zmat
1195
                 n3=ind_zmat(3,1)
1196
              ELSE
1197
                 n3=ind_zmat(idx_zmat(n1),3)
1198
              END IF
1199
              if (debug) WRITe(*,*) 'DBG :n3,liaisonBis',n3,LiaisonsBis(n1,0)
1200
              DO I3=1,LiaisonsBis(n1,0)
1201
! PFL 29.Aug.2008 ->
1202
! We dissociate the test on 'DejaFait' that indicates that this atom
1203
! has already been put in the Zmat
1204
! from the test on FCaf that indicates that this atom has been put in the
1205
! 'CAFaire' list that deals with identifying its connectivity.
1206
! Those two test might differ for a frozen atom linked to non frozen atoms.
1207
                 IAt=LiaisonsBis(n1,I3)
1208
                 if (.NOT.DejaFait(Iat)) THEN
1209
                    izm=izm+1
1210
                    !                 ind_zmat(izm,1)=iat
1211
                    !                 ind_zmat(izm,2)=n1
1212
                    !                 ind_zmat(izm,3)=n2
1213
                    !                 ind_zmat(izm,4)=n3
1214
                    Call add2indzmat(na,izm,iat,n1,n2,n3,ind_zmat,x,y,z)
1215
                    idx_zmat(iat)=izm
1216
                    if (I3.EQ.1) n3=ind_zmat(izm,1)
1217
                    DejaFait(Iat)=.TRUE.
1218
                 END IF
1219
                 If (.NOT.FCaf(Iat)) THEN
1220
                    CaFaire(IdxCaFaire)=iat
1221
                    IdxCaFaire=IdxCaFaire+1
1222
                    CaFaire(IdxCaFaire)=0
1223
                    FCaf(Iat)=.TRUE.
1224
                 END IF
1225
! <- PFL 29.Aug.2008
1226
              END DO
1227
              IaFaire=IaFaire+1
1228
           END Do           ! DO WHILE CaFaire
1229
        END IF
1230
     END IF
1231
     if (debug) THEN
1232
        WRITE(*,*) 'ind_zmat 3'
1233
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1234
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1235
        WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1236
        DO Ip=4,izm
1237
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), ind_zmat(Ip,2),  &
1238
                ind_zmat(Ip,3), ind_zmat(Ip,4)
1239
        END DO
1240
     END IF
1241

    
1242
  END DO
1243

    
1244
  FrozFrag(IFrag,1)=-1
1245
  FrozFrag(IFrag,2)=-1
1246
  FrozFrag(IFrag,3)=-1
1247

    
1248
  !     we start again with the rest of the molecule...
1249
  ! v 1.01 We add the fragment in the order corresponding to FrozFrag
1250
  KMax=0
1251
  DO I=1,NbFrag
1252
     IF (FrozFrag(I,1).NE.0) KMax=KMax+1
1253
  END DO
1254

    
1255
  IF (DEBUG) WRITE(*,*) "Adding the",Kmax,"fragments with frozen atoms"
1256
  DO K=1, KMax-1
1257
     IFrag=0
1258
     I0=0
1259
     I1=0
1260
     DO I=1,NbFrag
1261
        SELECT CASE(FrozFrag(I,3)-I0)
1262
        CASE (1:)
1263
           IFrag=I
1264
           I0=FrozFrag(I,3)
1265
           I1=FrozFrag(I,2)
1266
        CASE (0)
1267
           if (FrozFrag(I,2).GT.I1) THEN
1268
              IFrag=I
1269
              I0=FrozFrag(I,3)
1270
              I1=FrozFrag(I,2)
1271
           END IF
1272
        END SELECT
1273
     END DO
1274

    
1275
     FrozFrag(IFrag,1)=-1
1276
     FrozFrag(IFrag,2)=-1
1277
     FrozFrag(IFrag,3)=-1
1278

    
1279
     if (debug) WRITE(*,*) "Adding Fragment ",IFrag,K
1280

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

    
1404
        if (debug) THEN
1405
           WRITE(*,*) 'ind_zmat 4'
1406
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1407
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1408
           WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1409
           DO Ip=4,izm
1410
              WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), ind_zmat(Ip,2), &
1411
                   ind_zmat(Ip,3), ind_zmat(Ip,4)
1412
           END DO
1413
        END IF
1414

    
1415
     END DO ! loop on atoms of fragment IFrag
1416
  END DO                    ! Loop on all fragments
1417

    
1418
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1419
!
1420
!        General case
1421
!
1422
! 2 - we have all frozen atoms done... now comes the non frozen atoms
1423
! and we should fragment the fragments !
1424
!
1425
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1426

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

    
1430
  if (debug) THEN
1431
     WRITE(*,*) 'Frozen',NFroz
1432
     WRITE(*,'(20(1X,I3))') (Frozen(I),I=1,NFroz)
1433
  END IF
1434

    
1435
  DO I=1,na
1436
     DO J=0,NMAxL
1437
        LiaisonsIni(I,J)=LiaisonsBis(I,J)
1438
     END DO
1439
! PFL 29.Aug.2008 -> 
1440
! We re-initialize FCaf in order to add frozen atoms that are connected
1441
! to non frozen atoms
1442
     FCaf(I)=.FALSE.
1443
! <- 29.Aug.2008
1444
  END DO
1445

    
1446
  DO I=1,Na
1447
     IF (FrozAt(I)) THEN
1448
        Iat=I
1449
        if (debug) WRITE(*,'(20(1X,I3))') I,Iat,  &
1450
             (LiaisonsIni(Iat,Itmp),ITmp=0,LiaisonsIni(Iat,0))
1451
        DO J=1,LiaisonsIni(Iat,0)
1452
           Jat=LiaisonsIni(Iat,J)
1453
           Call Annul(Liaisons,Iat,Jat)
1454
           Call Annul(Liaisons,Jat,Iat)
1455
           Call Annul(LiaisonsIni,Jat,Iat)
1456
           Liaisons(Iat,0)=Liaisons(Iat,0)-1
1457
           Liaisons(Jat,0)=Liaisons(Jat,0)-1
1458
           LiaisonsIni(Jat,0)=LiaisonsIni(Jat,0)-1
1459
        END DO
1460
     END IF
1461
  END DO
1462

    
1463
  if (debug) THEN
1464
     WRITE(*,*) "Connections calculees"
1465
     DO IL=1,na
1466
        WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL)
1467
     END DO
1468
  END IF
1469

    
1470

    
1471

    
1472
  ! We re-decompose the system into fragments, but we omit on purpuse
1473
  ! fragments consisting only of frozen atoms
1474
  ! Now, frozblock will contain the frozen atom indices in a given fragment
1475

    
1476
  DO I=1,na
1477
     Fragment(I)=0 
1478
     NbAtFrag(I)=0
1479
     FrozBlock(I,0)=0
1480
  END DO
1481
  IdxFrag=0
1482
  NbFrag=0
1483

    
1484
  DO I=1,na
1485
     IdxCAfaire=1
1486
     CaFaire(IdxCaFaire)=0
1487

    
1488
     if (debug) WRITE(*,*) 'Treating atom I, fragment(I)',I,Fragment(I)
1489
     IF (.NOT.FrozAt(I).OR.(Liaisons(I,0).NE.0)) THEN 
1490
        IF (Fragment(I).EQ.0) THEN
1491
           IdxFrag=IdxFrag+1
1492
           NbFrag=NbFrag+1
1493
           IFrag=IdxFrag
1494
           Fragment(I)=IFrag
1495
           NbAtFrag(IFrag)=NbAtFrag(IFrag)+1
1496
           FragAt(IFrag,NbAtFrag(IFrag))=I
1497
        ELSE  ! fragment(I).EQ.0
1498
           IFrag=Fragment(I)
1499
        END IF     ! fragment(I).EQ.0
1500
        DO J=1,Liaisons(I,0)
1501
           Iat=Liaisons(I,J)
1502
           IF ((Fragment(Iat).NE.0).AND.(Fragment(Iat).NE.IFrag)) THEN
1503
              WRITE(*,*) 'Error : Atoms ',I,' and ',Iat
1504
              WRITE(*,*) 'are linked, but belongs to fragments ',IFrag,' and ',Fragment(Iat)
1505
              STOP
1506
           END IF
1507
           IF (Fragment(Iat).EQ.0) THEN
1508
              IF (.NOT.FCaf(IAt)) THEN
1509
                 CaFaire(IdxCaFaire)=Iat
1510
                 IdxCAfaire=IdxCAFaire+1
1511
                 FCaf(IAt)=.TRUE.
1512
              END IF
1513
              Fragment(Iat)=IFrag
1514
              NbAtFrag(IFrag)=NbAtFrag(IFrag)+1
1515
              FragAt(IFrag,NbAtFrag(IFrag))=Iat
1516
           END IF
1517
        END DO
1518
        CaFaire(IdxCaFaire)=0
1519

    
1520
        If (debug) WRITE(*,'(1X,A,1000I4)') 'Cafaire:',CaFaire(1:IdxCaFaire)
1521
        If (debug) WRITE(*,*) 'IFrag=',IFrag
1522

    
1523
        IAfaire=1
1524
        DO WHILE (CaFaire(IAfaire).NE.0)
1525
           Iat=CaFaire(IaFaire)
1526
           IF (.NOT.FrozAt(Iat).OR.(Liaisons(Iat,0).NE.0)) THEN 
1527
              if (debug) WRITE(*,*) 'Cafaire treating ',Iat
1528
              IF (Fragment(Iat).EQ.0) THEN
1529
                 WRITE(*,*) 'Error: Atom ',Iat,' does not belong to any fragment !'
1530
                 STOP
1531
              END IF
1532

    
1533
              DO J=1,Liaisons(Iat,0)
1534
                 Jat=Liaisons(Iat,J)
1535
                 IF ((Fragment(Jat).NE.0).AND.(Fragment(Jat).NE.IFrag)) THEN
1536
                    WRITE(*,*) 'Error: Atoms ',Iat,' and ',Liaisons(Iat,J)
1537
                    WRITE(*,*) 'are linked, but belongs to fragments ',IFrag,' and ',Fragment(Liaisons(Iat,J))
1538
                    STOP
1539
                 END IF
1540
                 IF (Fragment(Jat).EQ.0) THEN
1541
                    IF (.NOT.FCaf(Liaisons(Iat,J))) THEN
1542
                       CaFaire(IdxCaFaire)=Liaisons(Iat,J)
1543
                       IdxCAfaire=IdxCAFaire+1
1544
                       FCaf(Liaisons(Iat,J))=.TRUE.
1545
                    END IF
1546
                    Fragment(Jat)=IFrag
1547
                    NbAtFrag(IFrag)=NbAtFrag(IFrag)+1
1548
                    FragAt(IFrag,NbAtFrag(IFrag))=Jat
1549
                 END IF
1550
              END DO
1551
              CaFaire(IdxCaFaire)=0
1552
              If (debug) WRITE(*,*) 'IAfaire, IdxCaFaire,Cafaire :',IAfaire,IdxCafaire,' == ',CaFaire(IaFaire+1:IdxCaFaire)
1553
              IAFaire=IAFaire+1
1554
           END IF
1555
        END DO
1556
     END IF
1557
  END DO
1558

    
1559
  ! We compute FrozBlock now
1560
  DO IFrag=1,NbFrag
1561
     DO I=1,NbAtFrag(IFrag)
1562
        Iat=FragAt(IFrag,I)
1563
        IF (FrozAt(Iat)) THEN
1564
           FrozBlock(IFrag,0)=FrozBlock(IFrag,0)+1
1565
           FrozBlock(IFrag,FrozBlock(IFrag,0))=IAt
1566
        END IF
1567
     END DO
1568
  END DO
1569

    
1570

    
1571
  if (debug) THEN
1572
     WRITE(*,*) 'I found ',NbFrag, 'fragments with respectively '
1573
     WRITE(*,*) (NbAtFrag(I),I=1,NbFrag), 'atoms'
1574
     WRITE(*,*) "Fragments atoms are now listed as F in the following"
1575
     DO I=1,NbFrag
1576
        WRITE(*,*) Na
1577
        WRITE(*,*) 'Fragment ', i
1578
        DO J=1,Na
1579
           AtName=Nom(Atome(J))
1580
           IF (Fragment(J).EQ.I) AtName='F'
1581
           WRITE(*,'(1X,A5,3(1X,F10.6))') AtName,X(J),Y(J),Z(J)
1582
        END DO
1583
        !     WRITE(*,*) "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
1584
     END DO
1585

    
1586
     DO I=1,NbFrag
1587
        WRITE(*,*) 'Fragment ', i
1588
        WRITE(*,'(A,20(1X,I3))') "FragAt:",(FragAt(I,j),j=1,NbAtFrag(I))
1589
        WRITE(*,'(A,20(1X,I3))') "FrozBlock:",(FrozBlock(I,j),j=0,FrozBlock(I,0))
1590
     END DO
1591
  END IF
1592

    
1593

    
1594
  NFroz=0
1595
  DO IFrag=1,NbFrag
1596
     If (FrozBlock(IFrag,0).NE.0) NFroz=NFroz+1
1597
  END DO
1598

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

    
1601
  ! We will now add the fragments containing non frozen atoms.
1602
  ! I am not sure that there is a best strategy to add them...
1603
  ! so we add them in the order they were created :-(
1604
  ! First only block with frozen atoms are added
1605
  izm0=-1
1606
  IFrag=1
1607
  FCaf=.FALSE.
1608

    
1609
  DO IFragFroz=1,NFroz
1610
     DO WHILE (FrozBlock(IFrag,0).EQ.0)
1611
        IFrag=IFrag+1
1612
     END DO
1613
     ! each atom has at least one frozen atom that will serve as the seed
1614
     ! of this fragment.
1615
     if (debug) WRITE(*,*) 'Adding fragment :', ifrag,'with',FrozBlock(IFrag,0),' frozen atoms'
1616
     IF (FrozBlock(IFrag,0).EQ.1) THEN
1617
        ! There is only one frozen atom, easy case ...
1618
        Iat=FrozBlock(IFrag,1)
1619
        if (debug) WRITE(*,*) 'Only frozen atom of frag',iat
1620
        DejaFait(iat)=.TRUE.
1621
        IdxCaFaire=2
1622
        CaFaire(1)=iat
1623
        CaFaire(2)=0
1624
        FCaf(Iat)=.TRUE.
1625
        IaFaire=1
1626
        DO WHILE (CaFaire(IaFaire).NE.0)
1627
           n1=CaFaire(IaFaire)
1628
           SELECT CASE(idx_zmat(n1))
1629
           CASE (1)
1630
              n2=ind_zmat(2,1)
1631
              n3=ind_zmat(3,1)
1632
           CASE (2)
1633
              n2=ind_zmat(1,1)
1634
              n3=ind_zmat(3,1)
1635
           CASE (3:)
1636
              n2=ind_zmat(idx_zmat(n1),2)
1637
              n3=ind_zmat(idx_zmat(n1),3)
1638
           END SELECT
1639

    
1640
           DO I3=1,Liaisons(n1,0)
1641
              IAt=Liaisons(n1,I3)
1642
              ! PFL 2007.Apr.16 ->
1643
              ! We add ALL atoms linked to n1 to CaFaire
1644
              ! But we delete their link to n1
1645
              IF (.NOT.FCaf(Iat)) THEN
1646
                 CaFaire(IdxCaFaire)=Iat
1647
                 IdxCaFaire=IdxCaFaire+1
1648
                 CaFaire(IdxCaFaire)=0
1649
              END IF
1650
              Call Annul(Liaisons,Iat,n1)
1651
              Liaisons(iat,0)=Liaisons(Iat,0)-1
1652
              ! <- PFL 2007.Apr.16
1653
              IF (.NOT.DejaFait(Iat)) THEN
1654
                 ! we add it to the Zmat
1655
                 izm=izm+1
1656
                 !              ind_zmat(izm,1)=iat
1657
                 !              ind_zmat(izm,2)=n1
1658
                 !              ind_zmat(izm,3)=n2
1659
                 !              ind_zmat(izm,4)=n3
1660
                 Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1661
                 idx_zmat(iat)=izm
1662
                 !                  Call Annul(Liaisons,n1,iat)
1663
                 n3=iat
1664
                 DejaFait(Iat)=.TRUE.
1665
              END IF
1666
           END DO
1667
              IaFaire=IaFaire+1
1668

    
1669
              if (debug) THEN
1670
                 WRITE(*,*) 'ind_zmat 5'
1671
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1672
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1673
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2), ind_zmat(3,3)
1674
                 DO Ip=4,izm
1675
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1),  &
1676
                         ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
1677
                 END DO
1678
              END IF
1679
              
1680
           END Do              ! DO WHILE CaFaire
1681

    
1682

    
1683
        ELSE     ! FrozBlock(I,0)==1
1684
           if (debug) WRITE(*,*) 'IFrag=',IFrag,'Frozblock(I,0)/=1',Frozblock(IFrag,0)
1685
           ! We have many frozen atoms for one fragment. We will have to choose
1686
           ! the first one, and then to decide when to swich...
1687
           Iat=0
1688
           I0=-1
1689
           DO I=1,FrozBlock(IFrag,0)
1690
              JAt=FrozBlock(IFrag,I)
1691
              if (debug) WRITE(*,*) Jat, &
1692
                   (LiaisonsBis(Jat,Itmp),Itmp=0,LiaisonsBis(Jat,0))
1693
              IF (LiaisonsBis(Jat,0).GT.I0) THEN
1694
                 I0=LiaisonsBis(Jat,0)
1695
                 Iat=Jat
1696
              END IF
1697
           END DO
1698
           ! Iat is the starting frozen atom
1699
           IF (debug) WRITE(*,*) 'Choosing atom ',iat,'as a starting atom for frag',ifrag
1700
           DejaFait(iat)=.TRUE.
1701
           IdxCaFaire=2
1702
           CaFaire(1)=iat
1703
           CaFaire(2)=0
1704
           IaFaire=1
1705
           FCaf(Iat)=.TRUE.
1706
           DO WHILE (CaFaire(IaFaire).NE.0)
1707
              n1=CaFaire(IaFaire)
1708
              if (debug) WRITE(*,*) 'Iafaire,n1,dejafait,idx_zmat', &
1709
                   IaFaire,n1,    DejaFait(n1),idx_zmat(n1)
1710
              if (debug) WRITE(*,*) 'Cafaire', &
1711
                   (CaFaire(J),J=Iafaire,IdxCAfaire)
1712
              SELECT CASE(idx_zmat(n1))
1713
              CASE (1)
1714
                 n2=ind_zmat(2,1)
1715
                 n3=ind_zmat(3,1)
1716
              CASE (2)
1717
                 n2=ind_zmat(1,1)
1718
                 n3=ind_zmat(3,1)
1719
              CASE (3:)
1720
                 n2=ind_zmat(idx_zmat(n1),2)
1721
                 n3=ind_zmat(idx_zmat(n1),3)
1722
              END SELECT
1723

    
1724
              if (debug) WRITE(*,*) "DBG n1,Liaisons(n1,0)",n1,Liaisons(n1,0)
1725
              DO I3=1,Liaisons(n1,0)
1726
                 IAt=Liaisons(n1,I3)                 
1727
                 if (debug) WRITE(*,*) "DBG I3,Iat",I3,Iat
1728
                 ! PFL 2007.Apr.16 ->
1729
                 ! We add ALL atoms linked to n1 to CaFaire
1730
                 ! But we delete their link to n1
1731
!! PFL 2007.Aug.28 ->
1732
! re-add the test on FCaf in order not to put the same atom more than once in 
1733
! CaFaire array.
1734
                 IF (.NOT.FCaf(Iat)) THEN
1735
                    CaFaire(IdxCaFaire)=Iat
1736
                    IdxCaFaire=IdxCaFaire+1
1737
                    CaFaire(IdxCaFaire)=0
1738
                    FCaf(Iat)=.TRUE.
1739
                    if (debug) WRITE(*,*) 'Adding ',iat,' to CaFaire. I3=',I3,'IdxCafaire=',IdxCafaire
1740
                    if (debug) WRITE(*,*) 'Cafaire',(CaFaire(J),J=Iafaire,IdxCAfaire)
1741

    
1742
                 END IF
1743
!! <-- PFL 2007.Aug.28
1744

    
1745
                 Call Annul(Liaisons,Iat,n1)
1746
                 Liaisons(iat,0)=Liaisons(Iat,0)-1
1747
                 ! <- PFL 2007.Apr.16
1748
                 IF (.NOT.DejaFait(Iat)) THEN
1749
                    izm=izm+1
1750
                    !                 ind_zmat(izm,1)=iat
1751
                    !                 ind_zmat(izm,2)=n1
1752
                    !                 ind_zmat(izm,3)=n2
1753
                    !                 ind_zmat(izm,4)=n3
1754
                    Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1755
                    idx_zmat(iat)=izm
1756
                    !                  Call Annul(Liaisons,n1,iat)
1757

    
1758
                    n3=iat
1759
                    DejaFait(Iat)=.TRUE.
1760
                 END IF
1761
              END DO
1762

    
1763
              if (debug) WRITE(*,*) 'I3,n1,Liaisons(n1,:)', &
1764
                   I3,n1,(Liaisons(n1,J),J=0,Liaisons(n1,0))
1765

    
1766

    
1767
              if (debug.AND.(izm.GT.izm0)) THEN
1768
                 WRITE(*,*) 'ind_zmat 6, izm=',izm
1769
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1770
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1771
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2),  &
1772
                      ind_zmat(3,3)
1773
                 DO Ip=4,izm
1774
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), &
1775
                         ind_zmat(Ip,2),ind_zmat(Ip,3), ind_zmat(Ip,4)
1776
                 END DO
1777
                 izm0=izm
1778
              END IF
1779

    
1780
              IaFaire=IaFaire+1
1781

    
1782

    
1783
           END Do              ! DO WHILE CaFaire
1784

    
1785
        END IF  ! FrozBlock(I,0)==1
1786

    
1787
        IFrag=IFrag+1
1788
     END DO                    ! Loop on all fragments
1789

    
1790

    
1791
     DO IFrag=1,NbFrag
1792
        IF (FrozBlock(IFrag,0).EQ.0) THEN
1793
           if (debug) WRITE(*,*) 'Adding fragment :', ifrag,'with no frozen atoms'
1794
           ! We have no frozen atoms for this fragment. We will have to choose
1795
           ! the first atom to put.
1796
           ! For now, we do not care of the 'central' atom (ie the one with
1797
           ! no CP atoms...)
1798
           ! We just take the atom that is the closest to the already placed
1799
           ! atoms !
1800

    
1801

    
1802
           I0=0
1803
           I1=0
1804
           d=1e9
1805
           DO J=1,izm
1806
              Jat=ind_zmat(J,1)
1807
              DO I=1,NbAtfrag(IFrag)
1808
                 IAt=FragAt(IFrag,I)
1809
                 IF (.NOT.DejaFait(Iat)) THEN
1810
                    Call vecteur(Iat,Jat,x,y,z,vx1,vy1,vz1,norm1)
1811
                    IF (norm1.LT.d) THEN
1812
                       I1=Jat
1813
                       I0=Iat
1814
                       d=Norm1
1815
                    END IF
1816
                 END IF
1817
              END DO
1818
           END DO
1819

    
1820
           Iat=I0
1821
           n1=I1
1822

    
1823
           IF (debug) WRITE(*,*) Iat,' starting atom for frag',ifrag
1824

    
1825

    
1826
           SELECT CASE(idx_zmat(n1))
1827
           CASE (1)
1828
              n2=ind_zmat(2,1)
1829
              n3=ind_zmat(3,1)
1830
           CASE (2)
1831
              n2=ind_zmat(1,1)
1832
              n3=ind_zmat(3,1)
1833
           CASE (3:)
1834
              n2=ind_zmat(idx_zmat(n1),2)
1835
              n3=ind_zmat(idx_zmat(n1),3)
1836
           END SELECT
1837

    
1838
           izm=izm+1
1839
           !        ind_zmat(izm,1)=iat
1840
           !        ind_zmat(izm,2)=n1
1841
           !        ind_zmat(izm,3)=n2
1842
           !        ind_zmat(izm,4)=n3
1843
           Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1844
           idx_zmat(iat)=izm
1845

    
1846

    
1847
           DejaFait(iat)=.TRUE.
1848
           IdxCaFaire=2
1849
           CaFaire(1)=iat
1850
           CaFaire(2)=0
1851
           IaFaire=1
1852
           FCaf(Iat)=.TRUE.
1853
           DO WHILE (CaFaire(IaFaire).NE.0)
1854
              n1=CaFaire(IaFaire)
1855
              if (debug) WRITE(*,*) 'Iafaire,n1',IaFaire,n1, &
1856
                   DejaFait(n1),idx_zmat(n1)
1857
              if (debug) WRITE(*,*) 'Cafaire', &
1858
                   (CaFaire(J),J=Iafaire,IdxCAfaire)
1859
              SELECT CASE(idx_zmat(n1))
1860
              CASE (1)
1861
                 n2=ind_zmat(2,1)
1862
                 n3=ind_zmat(3,1)
1863
              CASE (2)
1864
                 n2=ind_zmat(1,1)
1865
                 n3=ind_zmat(3,1)
1866
              CASE (3:)
1867
                 n2=ind_zmat(idx_zmat(n1),2)
1868
                 n3=ind_zmat(idx_zmat(n1),3)
1869
              END SELECT
1870

    
1871

    
1872
              DO I3=1,Liaisons(n1,0)
1873
                 IAt=Liaisons(n1,I3)
1874
                 ! PFL 2007.Apr.16 ->
1875
                 ! We add ALL atoms linked to n1 to CaFaire
1876
                 ! But we delete their link to n1
1877
!! PFL 2007.Aug.28 ->
1878
! re-add the test on FCaf in order not to put the same atom more than once in 
1879
! CaFaire array.
1880
                 IF (.NOT.FCaf(Iat)) THEN
1881
                    CaFaire(IdxCaFaire)=Iat
1882
                    IdxCaFaire=IdxCaFaire+1
1883
                    CaFaire(IdxCaFaire)=0
1884
                    FCaf(Iat)=.TRUE.
1885
                 END IF
1886
!! <-- PFL 2007.Aug.28
1887

    
1888
                 Call Annul(Liaisons,Iat,n1)
1889
                 Liaisons(iat,0)=Liaisons(Iat,0)-1
1890
                 if (debug) WRITE(*,*) 'Adding ',iat,' to CaFaire. I3=',I3
1891
                 if (debug) WRITE(*,*) 'Cafaire',(CaFaire(J),J=Iafaire,IdxCAfaire)
1892

    
1893
                 ! <- PFL 2007.Apr.16
1894
                 IF (.NOT.DejaFait(Liaisons(n1,i3))) THEN
1895
                    IAt=Liaisons(n1,I3)
1896
                    izm=izm+1
1897
                    !                 ind_zmat(izm,1)=iat
1898
                    !                 ind_zmat(izm,2)=n1
1899
                    !                 ind_zmat(izm,3)=n2
1900
                    !                 ind_zmat(izm,4)=n3
1901
                    Call add2indzmat(na,izm,Iat,n1,n2,n3,ind_zmat,x,y,z)
1902
                    idx_zmat(iat)=izm
1903

    
1904
                    n3=iat
1905
                    DejaFait(Iat)=.TRUE.
1906
                 END IF
1907

    
1908
              if (debug) WRITE(*,*) 'I3,n1,Liaisons(n1,:)', &
1909
                   I3,n1,(Liaisons(n1,J),J=0,Liaisons(n1,0))
1910
              END DO
1911
              IaFaire=IaFaire+1
1912

    
1913
              if (debug) THEN
1914
                 WRITE(*,*) 'ind_zmat 7', izm
1915
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(1,1)
1916
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(2,1), ind_zmat(2,2)
1917
                 WRITE(*,'(1X,4(1X,I5))') ind_zmat(3,1), ind_zmat(3,2),ind_zmat(3,3)
1918
                 DO Ip=4,izm
1919
                    WRITE(*,'(1X,4(1X,I5))') ind_zmat(Ip,1), &
1920
                         ind_zmat(Ip,2),  &
1921
                         ind_zmat(Ip,3), ind_zmat(Ip,4)
1922
                 END DO
1923
              END IF
1924

    
1925
           END Do              ! DO WHILE CaFaire
1926
        END IF                 ! FrozBlock(IFrag,0).EQ.0
1927

    
1928
     END DO                    ! Loop on all fragments without frozen atoms
1929

    
1930
     if (debug) THEN
1931
        WRITE(*,*) Na+Izm
1932
        WRITE(*,*) 'Done... ', izm
1933
        DO J=1,Na
1934
           WRITE(*,'(1X,A5,3(1X,F10.6))') Nom(Atome(J)),X(J),Y(J),Z(J)
1935
        END DO
1936
        DO I=1,Izm
1937
           J=ind_zmat(I,1)
1938
           WRITE(*,'(1X,A5,3(1X,F10.6))') 'X ',X(J),Y(J),Z(J)
1939
        END DO
1940
        IF (izm.NE.Na) THEN
1941
           WRITE(*,*) "Atoms not done:"
1942
           DO I=1,Na
1943
              IF (.NOT.DejaFait(I)) WRITE(*,'(I5)',ADVANCE='NO') I
1944
           END DO
1945
        END IF
1946
     END IF
1947

    
1948

    
1949
     ! We have ind_zmat. We calculate val_zmat :-)
1950
     if (debug) WRITE(*,*) "Calculating val_zmat"
1951

    
1952
     val_zmat(1,1)=0.d0
1953
     val_zmat(1,2)=0.d0
1954
     val_zmat(1,3)=0.d0
1955
     val_zmat(2,2)=0.d0
1956
     val_zmat(2,3)=0.d0
1957
     val_zmat(3,3)=0.d0
1958

    
1959
     n1=ind_zmat(2,1)
1960
     n2=ind_zmat(2,2)
1961

    
1962
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1963

    
1964
     val_zmat(2,1)=norm1
1965

    
1966

    
1967
     n1=ind_zmat(3,1)
1968
     n2=ind_zmat(3,2)
1969
     n3=ind_zmat(3,3)
1970

    
1971
     CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1972

    
1973
     val_zmat(3,1)=norm1
1974

    
1975
     CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
1976
     val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
1977

    
1978
     val_zmat(3,2)=val
1979

    
1980
     DO i=4,na
1981

    
1982
        n1=ind_zmat(i,1)
1983
        n2=ind_zmat(i,2)
1984
        n3=ind_zmat(i,3)
1985
        n4=ind_zmat(i,4)
1986

    
1987
        if (debug) WRITE(*,*) "Doing i,n1,n2,n3,n4",i,n1,n2,n3,n4
1988
        CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1)
1989

    
1990
        CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2)
1991
        val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2)
1992

    
1993
        CALL vecteur(n3,n4,x,y,z,vx3,vy3,vz3,norm3)
1994
        CALL produit_vect(vx1,vy1,vz1,vx2,vy2,vz2, &
1995
             vx4,vy4,vz4,norm4)
1996
        CALL produit_vect(vx3,vy3,vz3,vx2,vy2,vz2, &
1997
             vx5,vy5,vz5,norm5)
1998

    
1999
        val_d=angle_d(vx4,vy4,vz4,norm4, vx5,vy5,vz5,norm5, &
2000
             vx2,vy2,vz2,norm2)
2001

    
2002
        !     write(*,11) n1,n2,norm1,n3,val,n4,val_d
2003
        !11   format (2(1x,i3),1x,f8.4,2(1x,i3,1x,f8.3))
2004

    
2005
        val_zmat(i,1)=norm1
2006
        val_zmat(i,2)=val
2007
        val_zmat(i,3)=val_d
2008

    
2009
     END DO
2010

    
2011
     if (debug) THEN
2012
        WRITE(*,*) 'DBG Cre_Zmat_Constr: ind_zmat'
2013
        DO I=1,na
2014
           WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5)
2015
        END DO
2016

    
2017
        WRITE(*,*) 'DBG Cre_Zmat_Constr: Full zmat'
2018
        DO I=1,na
2019
           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)
2020
        END DO
2021

    
2022
     END IF
2023

    
2024
     if (debug) WRITE(*,*) "Deallocate (FrozDist,Fragment, NbAtFrag,FragAt)"
2025
     DEALLOCATE(FrozDist,Fragment, NbAtFrag,FragAt)
2026
     if (debug) WRITE(*,*) "Deallocate FrozFrag, IdxFragAt, FrozBlock"
2027
     !  DEALLOCATE(FrozFrag, IdxFragAt, FrozBlock)
2028
     DEALLOCATE(FrozFrag,FrozBlock)
2029
     if (debug) WRITE(*,*) "Deallocate (DistFroz,Liaisons)"
2030
     DEALLOCATE(DistFroz,Liaisons)
2031
     if (debug) WRITE(*,*) "Deallocate (LiaisonsIni)"
2032
     DEALLOCATE(LiaisonsIni)
2033
     if (debug) WRITE(*,*) "Deallocate(CaFaire,DejaFait,FrozAt)"
2034
     DEALLOCATE(CaFaire,DejaFait,FrozAt)
2035
     if (debug) WRITE(*,*) "Deallocate (LiaisonsBis"
2036
     DEALLOCATE(LiaisonsBis)
2037

    
2038
     if (debugGaussian) THEN
2039
        WRITE(*,*) 'DBG Cre_Zmat_Constr_Frag: Gaussian Zmat - START'
2040
        Call WriteMixed_Gaussian(na,atome,LocalNCart,ind_zmat,val_zmat)
2041
        WRITE(*,*) 'DBG Cre_Zmat_Constr_Frag: Gaussian Zmat - END'
2042
     END IF
2043

    
2044

    
2045

    
2046
     if (debug) WRITE(*,*) "=============================== Exiting Calc_zmat_contr_frag ========================"
2047

    
2048
   END SUBROUTINE Calc_Zmat_const_frag
2049

    
2050