root / src / ZmatBuild.f90
Historique | Voir | Annoter | Télécharger (32,92 ko)
1 |
SUBROUTINE ZmatBuild(na,atome,ind_zmat,val_zmat,x,y,z,izm, & |
---|---|
2 |
Liaisons, LIes_CP,LIes_CF,ListAt,DejaFait,debug) |
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 |
! 12.06.06 |
13 |
! Small modification: there was an inconsistency: izm was increased |
14 |
! after the atom was added to ind_zmat for the three first atoms, |
15 |
! but before for all others. Now, it starts at zero and it |
16 |
! is increased before the atom is added to ind_zmat |
17 |
!---------------------------------------------------------------------- |
18 |
! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
19 |
! Centre National de la Recherche Scientifique, |
20 |
! Université Claude Bernard Lyon 1. All rights reserved. |
21 |
! |
22 |
! This work is registered with the Agency for the Protection of Programs |
23 |
! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
24 |
! |
25 |
! Authors: P. Fleurat-Lessard, P. Dayal |
26 |
! Contact: optnpath@gmail.com |
27 |
! |
28 |
! This file is part of "Opt'n Path". |
29 |
! |
30 |
! "Opt'n Path" is free software: you can redistribute it and/or modify |
31 |
! it under the terms of the GNU Affero General Public License as |
32 |
! published by the Free Software Foundation, either version 3 of the License, |
33 |
! or (at your option) any later version. |
34 |
! |
35 |
! "Opt'n Path" is distributed in the hope that it will be useful, |
36 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
37 |
! |
38 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
39 |
! GNU Affero General Public License for more details. |
40 |
! |
41 |
! You should have received a copy of the GNU Affero General Public License |
42 |
! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
43 |
! |
44 |
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
45 |
! for commercial licensing opportunities. |
46 |
!---------------------------------------------------------------------- |
47 |
|
48 |
use Path_module, only : Nat, NMaxL, KINT, KREAL,Pi |
49 |
use Io_module |
50 |
|
51 |
IMPLICIT NONE |
52 |
|
53 |
INTEGER(KINT) :: Izm,I,IAf,IAt,IAt0,J,Jat |
54 |
INTEGER(KINT) :: n1, NMaxCF, NMinCP, VCF |
55 |
INTEGER(KINT) :: IAta,IAtd,IAtDh,IAti,IAtv,ICat |
56 |
INTEGER(KINT) :: ICP0, IdAt0, IdAtl |
57 |
INTEGER(KINT) :: Idx, IIat, IIatDh, IndAFaire, IndFin |
58 |
INTEGER(KINT) :: IdxAt0 |
59 |
INTEGER(KINT) :: ITmp, IZm0, IZm1, IZm2, IZm3, IZm4, IzmTmp |
60 |
integer(KINT) :: na, atome(NAt), ind_zmat(NAt, 5) |
61 |
real(KREAL) :: x(NAt), y(NAt), z(NAt) |
62 |
real(KREAL) :: val_zmat(NAt,3) |
63 |
! ListAt contains the indices of frozen atoms |
64 |
LOGICAL ListAT(NAt), FFirst |
65 |
INTEGER(KINT) :: Natreat |
66 |
|
67 |
real(KREAL) :: dist |
68 |
INTEGER(KINT) :: LIAISONS(NAt, 0:NMaxL) |
69 |
INTEGER(KINT) :: CAFaire(NAt) |
70 |
INTEGER(KINT) :: LieS_CP(NAt,0:NMaxL),LieS_CF(NAt,0:NMaxL) |
71 |
INTEGER(KINT) :: AtCP0(NAt),NbAt0,NbAt0r |
72 |
Integer(KINT) :: NbCycle |
73 |
real(KREAL) :: vx1,vy1,vz1,norm1 |
74 |
real(KREAL) :: vx2,vy2,vz2,norm2 |
75 |
real(KREAL) :: val |
76 |
Logical Debug, Done |
77 |
Logical DejaFait(NAt) |
78 |
|
79 |
|
80 |
INTERFACE |
81 |
FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2) |
82 |
use Path_module, only : Pi,KINT, KREAL |
83 |
real(KREAL) :: v1x,v1y,v1z,norm1 |
84 |
real(KREAL) :: v2x,v2y,v2z,norm2 |
85 |
real(KREAL) :: angle |
86 |
END FUNCTION ANGLE |
87 |
END INTERFACE |
88 |
|
89 |
|
90 |
|
91 |
|
92 |
|
93 |
! As we may have to treat only partial molecules, it may happen |
94 |
! that there are no central atoms... so we first check this by looking |
95 |
! for the least number of CP atoms |
96 |
FFirst=.TRUE. |
97 |
NMinCP=na |
98 |
NMaxCF=-1 |
99 |
NAtreat=0 |
100 |
Izm0=Izm+1 |
101 |
|
102 |
DO I=1,na |
103 |
if (DEBUG) WRITE(*,*) "DBG ZmatBuild i,listat",i,listAt(i) |
104 |
IF (ListAt(I).AND.(.NOT.(DejaFait(I)))) THEN |
105 |
IF (Lies_CP(I,0).lt.NMinCP) NMinCP=Lies_CP(I,0) |
106 |
IF (Lies_CF(I,0).gt.NMaxCF) NMaxCF=Lies_CF(I,0) |
107 |
NATreat=NATreat+1 |
108 |
END IF |
109 |
END DO |
110 |
if (debug) WRITE(*,*) 'NMinCP=',NMinCP |
111 |
if (debug) WRITE(*,*) 'NMaxCF=',NMaxCF |
112 |
if (debug) WRITE(*,*) 'NATreat=',NAtreat |
113 |
|
114 |
|
115 |
IF (Debug) THEN |
116 |
WRITE(*,*) '------------------ Zmat Build -------------------' |
117 |
WRITE(*,*) 'LIAISONS' |
118 |
DO I=1,na |
119 |
WRITE(*,1003) i,(LIAISONS(I,J),J=0,NMaxL) |
120 |
END DO |
121 |
|
122 |
WRITE(*,*) 'LIes_CF' |
123 |
DO I=1,na |
124 |
WRITE(*,1003) i,(LIeS_CF(I,J),J=0,NMaxL) |
125 |
END DO |
126 |
|
127 |
WRITE(*,*) 'LIes_CP' |
128 |
DO I=1,na |
129 |
WRITE(*,1003) i,(LIeS_CP(I,J),J=0,NMaxL) |
130 |
END DO |
131 |
WRITE(*,*) '-- Zmat Build : only _To treat_ atoms------------' |
132 |
WRITE(*,*) 'LIAISONS' |
133 |
DO I=1,na |
134 |
IF (ListAt(I).AND.(.NOT.DejaFait(I))) & |
135 |
WRITE(*,1003) i,(LIAISONS(I,J),J=0,NMaxL) |
136 |
END DO |
137 |
|
138 |
WRITE(*,*) 'LIes_CF' |
139 |
DO I=1,na |
140 |
IF (ListAt(I).AND.(.NOT.DejaFait(I))) & |
141 |
WRITE(*,1003) i,(LIeS_CF(I,J),J=0,NMaxL) |
142 |
END DO |
143 |
|
144 |
WRITE(*,*) 'LIes_CP' |
145 |
DO I=1,na |
146 |
IF (ListAt(I).AND.(.NOT.DejaFait(I))) & |
147 |
WRITE(*,1003) i,(LIeS_CP(I,J),J=0,NMaxL) |
148 |
END DO |
149 |
|
150 |
END IF |
151 |
|
152 |
|
153 |
if (NAtreat.EQ.0) THEN |
154 |
WRITE(*,*) "Foutage de gueule : NAtTreat=0" |
155 |
RETURN |
156 |
END IF |
157 |
|
158 |
if (debug) THEN |
159 |
WRITE(*,*) 'DBG ZmatBuil, izm=',izm |
160 |
DO I=1,na |
161 |
WRITE(*,'(1X,I5,1X,L4,1X,L4,12(1X,I4))') i,ListAt(I) & |
162 |
,DejaFait(I), & |
163 |
(Liaisons(I,J),J=0,Liaisons(I,0)) |
164 |
END DO |
165 |
END IF |
166 |
|
167 |
!!! atraiter NMaxCF=0 :que des atomes separes... |
168 |
! mais faut-il reellement faire un cas a part ? |
169 |
|
170 |
! On compte le nb d'atomes sans atomes CP (centripetes) |
171 |
NbAt0=0 |
172 |
DO I=1,na |
173 |
IF (ListAt(I).AND.(.NOT.DejaFait(I)).AND. & |
174 |
(Lies_CP(I,0).eq.NMinCP)) THEN |
175 |
NbAt0=NbAt0+1 |
176 |
AtCP0(NbAt0)=I |
177 |
IF (DEBUG) WRITE(*,*) "Center atom",NbAt0,I,Atome(I) |
178 |
END IF |
179 |
END DO |
180 |
AtCP0(NbAt0+1)=0 |
181 |
NbAt0r=NbAt0 |
182 |
|
183 |
IF (Debug) WRITE(*,*) 'DBG ZmatBuld - NCP0,AtCP0 ',NbAt0, & |
184 |
(AtCP0(i),i=1,NbAt0) |
185 |
|
186 |
! On va les traiter tous en construisant les molecules en partant d'eux |
187 |
! Le premier atome sans CP est different des autres car il fixe |
188 |
! l'origine |
189 |
|
190 |
!First atom |
191 |
IF (Izm==0) THEN |
192 |
FFirst=.FALSE. |
193 |
if (debug) WRITE(*,*) 'DBG ZmatBuil - Treating Izm=1' |
194 |
! IZm=1 |
195 |
! Boucle pour trouver celui qui a le plus d'atomes CF |
196 |
IdAt0=0 |
197 |
VCF=-1 |
198 |
DO I=1,NbAt0 |
199 |
! WRITE(*,*) 'DBG ZmatB',I,AtCP0(I) |
200 |
if (AtCP0(I).NE.0) THEN |
201 |
ICat=AtCP0(I) |
202 |
if (Lies_CF(ICAt,0).gt.VCF) THEN |
203 |
IdAt0=ICat |
204 |
IdxAt0=I |
205 |
VCF=Lies_CF(ICAt,0) |
206 |
END IF |
207 |
END IF |
208 |
END DO |
209 |
|
210 |
! IF (debug) WRITE(*,*) 'DBG ZmatBuil - VCF, IdxAt0,IdAt0', |
211 |
! & VCF, IdxAt0,IdAt0 |
212 |
! all atoms with NMinCP CP links do not have CF links... not a good choice to start |
213 |
! building the molecule(s) around them... we increase NMinCP |
214 |
AtCP0(IdxAt0)=0 |
215 |
NbAt0r=NbAt0r-1 |
216 |
|
217 |
! WRITE(IOOUT,*) 'Atome 1', IdAt0, Nom(Atome(IdAt0)) |
218 |
Izm1=IdAt0 |
219 |
Izm=Izm+1 |
220 |
|
221 |
ind_zmat(izm,1)=Izm1 |
222 |
ind_zmat(izm,2)=0 |
223 |
ind_zmat(izm,3)=0 |
224 |
ind_zmat(izm,4)=0 |
225 |
ind_zmat(izm,5)=0 |
226 |
val_zmat(izm,1)=0.0 |
227 |
val_zmat(izm,2)=0.0 |
228 |
val_zmat(izm,3)=0.0 |
229 |
DejaFait(Izm1)=.True. |
230 |
|
231 |
END IF ! end of izm==1 test |
232 |
|
233 |
! On construit la premiere couche qui est speciale car elle fixe les |
234 |
! axes. |
235 |
! Plusieurs cas sont possibles suivant le nb d'atomes CF |
236 |
IdAt0=ind_zmat(1,1) |
237 |
Izm1=IdAt0 |
238 |
|
239 |
!Second atom |
240 |
IF ((izm==1).AND.(NAtreat.ge.2)) THEN |
241 |
Done=.FALSE. |
242 |
if (debug) WRITE(*,*) 'DBG ZmatBuil - Treating Izm=2' |
243 |
! Two cases: 1) We are constructing the first fragment: FIzm1=.T. |
244 |
! 2) We are constructing the second fragment: FIzm1=.F. |
245 |
! in this case, we select one CP0 atom to start with |
246 |
IF (FFirst) THEN |
247 |
FFirst=.FALSE. |
248 |
! This is the first atom to be dealt with |
249 |
! We look for a CP0 |
250 |
If (NbAt0r.ge.1) THEN |
251 |
IdAt0=0 |
252 |
VCF=-1 |
253 |
WRITE(*,*) 'DBG ZBuild Izm=2:AtCP0',(AtCP0(I),I=1,NbAt0) |
254 |
DO I=1,NbAt0 |
255 |
if (AtCP0(I).NE.0) THEN |
256 |
ICat=AtCP0(I) |
257 |
if (Lies_CF(I,0).gt.VCF) THEN |
258 |
Izm2=ICat |
259 |
IdxAt0=I |
260 |
VCF=Lies_CF(ICAt,0) |
261 |
END IF |
262 |
END IF |
263 |
END DO |
264 |
WRITE(*,*) 'DBG ZBuild Izm=2:izm2,IdxAt0,VCF,AtCP0(1)', & |
265 |
izm2,IdxAt0,VCF,AtCP0(1) |
266 |
NbAt0r=NbAt0r-1 |
267 |
Done=.TRUE. |
268 |
END IF |
269 |
|
270 |
! If we do not have a CP0 available the other tests are identical |
271 |
! for cases 1 and 2... |
272 |
END IF |
273 |
IF (.NOT.DONE) THEN |
274 |
IF (Lies_CF(IdAt0,0).ge.1) THEN |
275 |
IZm2=Lies_CF(IdAt0,1) |
276 |
WRITE(*,*) 'DBG ZBuild Lies_CF(IdAt0,0).ge.1', & |
277 |
Lies_CF(IdAt0,0),izm2 |
278 |
ELSE |
279 |
! First atom is not linked to anything... we look for the second CP0 atom |
280 |
! if we have one.. |
281 |
If (NbAt0r.ge.1) THEN |
282 |
IdAt0=0 |
283 |
VCF=-1 |
284 |
IF (DEBUG) WRITE(*,*) 'DBG ZBuild Izm=2:AtCP0', & |
285 |
(AtCP0(I),I=1,NbAt0) |
286 |
DO I=1,NbAt0 |
287 |
if (AtCP0(I).NE.0) THEN |
288 |
ICat=AtCP0(I) |
289 |
if (Lies_CF(I,0).gt.VCF) THEN |
290 |
Izm2=ICat |
291 |
IdxAt0=I |
292 |
VCF=Lies_CF(ICAt,0) |
293 |
END IF |
294 |
END IF |
295 |
END DO |
296 |
IF (DEBUG) WRITE(*,*) 'DBG ZBuild Izm=2:izm2,IdxAt0,VCF,AtCP0(1)', & |
297 |
izm2,IdxAt0,VCF,AtCP0(1) |
298 |
NbAt0r=NbAt0r-1 |
299 |
ELSE |
300 |
! we do not have another CP0 atom... but we know that there |
301 |
! is at least two atoms... we look for the closest atom to Izm1 |
302 |
Izm2=0 |
303 |
Dist=1.D99 |
304 |
DO I=1,Na |
305 |
IF (ListAt(I).AND.(.NOT.Dejafait(I))) THEN |
306 |
CALL vecteur(IZm1,I,x,y,z,vx1,vy1,vz1,norm1) |
307 |
if (Norm1.lt.Dist) IZm2=I |
308 |
END IF |
309 |
END DO |
310 |
END IF |
311 |
END IF |
312 |
END IF |
313 |
CALL vecteur(IZm1,IZm2,x,y,z,vx1,vy1,vz1,norm1) |
314 |
|
315 |
Izm=Izm+1 |
316 |
|
317 |
ind_zmat(izm,1)=izm2 |
318 |
ind_zmat(izm,2)=izm1 |
319 |
ind_zmat(izm,3)=0 |
320 |
ind_zmat(izm,4)=0 |
321 |
ind_zmat(izm,5)=0 |
322 |
val_zmat(izm,1)=norm1 |
323 |
val_zmat(izm,2)=0.0 |
324 |
val_zmat(izm,3)=0.0 |
325 |
DejaFait(Izm2)=.TRUE. |
326 |
|
327 |
END IF ! end of izm==2 test |
328 |
|
329 |
Izm1=ind_zmat(1,1) |
330 |
Izm2=ind_zmat(2,1) |
331 |
|
332 |
! Third atom |
333 |
|
334 |
IF ((Izm==2).AND.(NAtreat.ge.3)) THEN |
335 |
Done=.FALSE. |
336 |
if (debug) WRITE(*,*) 'DBG ZmatBuil - Treating Izm=3',FFirst |
337 |
! Two cases: 1) We are constructing the first fragment: FIzm1=.T. |
338 |
! 2) We are constructing the second fragment: FIzm1=.F. |
339 |
! in this case, we select one CP0 atom to start with |
340 |
IF (FFirst) THEN |
341 |
FFirst=.FALSE. |
342 |
! This is the first atom to be dealt with |
343 |
! We look for a CP0 |
344 |
If (NbAt0r.ge.1) THEN |
345 |
IdAt0=0 |
346 |
VCF=-1 |
347 |
DO I=1,NbAt0 |
348 |
if (AtCP0(I).NE.0) THEN |
349 |
ICat=AtCP0(I) |
350 |
if (Lies_CF(I,0).gt.VCF) THEN |
351 |
Izm3=ICat |
352 |
IdxAt0=I |
353 |
VCF=Lies_CF(ICAt,0) |
354 |
END IF |
355 |
END IF |
356 |
END DO |
357 |
NbAt0r=NbAt0r-1 |
358 |
Done=.TRUE. |
359 |
END IF |
360 |
! If we do not have a CP0 available the other tests are identical |
361 |
! for cases 1 and 2... |
362 |
END IF |
363 |
IF (.NOT.Done) THEN |
364 |
WRITE(*,*) 'DBG ZmatBuild: Done false for izm=3' |
365 |
IF (Lies_CF(izm1,0).ge.2) THEN |
366 |
! easiest case: the first atom is linked to at least 2 atoms. |
367 |
WRITE(*,*) 'DBG ZmtB-izm3:Lies_CF(izm1,0)>=2 ' |
368 |
I=1 |
369 |
DO WHILE ((.NOT.ListAt(Lies_CF(izm1,I))) & |
370 |
.OR.(DejaFait(Lies_CF(izm1,I)))) |
371 |
I=I+1 |
372 |
END DO |
373 |
izm3=Lies_CF(Izm1,I) |
374 |
Done=.TRUE. |
375 |
ELSEIF (Lies_CF(Izm2,0).ge.1) THEN |
376 |
! a bit more complex: first atom is linked to one atom (Izm2) |
377 |
! but luckily 2nd atom is linked to at least one atom |
378 |
I=1 |
379 |
DO WHILE ((.NOT.ListAt(Lies_CF(izm2,I))) & |
380 |
.OR.(DejaFait(Lies_CF(izm2,I))).AND.(I.le.Lies_CF(Izm2,0))) |
381 |
I=I+1 |
382 |
END DO |
383 |
IF (I.LE.Lies_CF(Izm2,0)) THEN |
384 |
Izm3=Lies_CF(izm2,I) |
385 |
WRITE(*,*) 'DBG ZmtB-izm3:Lies_CF(izm2,0)>=1 and ok ' |
386 |
! We exchange Izm1 and Izm2 because the logical order is Izm3 linked |
387 |
! to Izm2 and not to Izm1 as is the default later |
388 |
IzmTmp=Izm2 |
389 |
Izm2=Izm1 |
390 |
Izm1=IzmTmp |
391 |
Done=.TRUE. |
392 |
END IF |
393 |
END IF |
394 |
IF (.NOT.Done) THEN |
395 |
! None of the first two atoms has links to a third atom... |
396 |
! we take it from the CP0 if possible... |
397 |
If (NbAt0r.ge.1) THEN |
398 |
WRITE(*,*) 'DBG ZmatB izm=3',NbAt0r |
399 |
IdAt0=0 |
400 |
VCF=-1 |
401 |
DO I=1,NbAt0 |
402 |
if (AtCP0(I).NE.0) THEN |
403 |
ICat=AtCP0(I) |
404 |
if (Lies_CF(I,0).gt.VCF) THEN |
405 |
Izm3=ICat |
406 |
IdxAt0=I |
407 |
VCF=Lies_CF(ICAt,0) |
408 |
END IF |
409 |
END IF |
410 |
END DO |
411 |
NbAt0r=NbAt0r-1 |
412 |
WRITE(*,*) 'DBG ZmatB izm=3',NbAt0r,Izm3 |
413 |
ELSE |
414 |
! Or the atom closest to 1 |
415 |
Izm3=0 |
416 |
Dist=1.D99 |
417 |
DO I=1,Na |
418 |
IF (ListAt(I).AND.(.NOT.Dejafait(I))) THEN |
419 |
CALL vecteur(IZm1,I,x,y,z,vx1,vy1,vz1,norm1) |
420 |
if (Norm1.lt.Dist) IZm3=I |
421 |
END IF |
422 |
END DO |
423 |
END IF |
424 |
END IF |
425 |
END IF |
426 |
|
427 |
CALL vecteur(IZm1,IZm2,x,y,z,vx1,vy1,vz1,norm1) |
428 |
CALL vecteur(izm1,izm3,x,y,z,vx2,vy2,vz2,norm2) |
429 |
val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2) |
430 |
|
431 |
! write(*,11) n1,n2,norm1,n3,val |
432 |
|
433 |
Izm=Izm+1 |
434 |
|
435 |
ind_zmat(izm,1)=izm3 |
436 |
ind_zmat(izm,2)=izm1 |
437 |
ind_zmat(izm,3)=izm2 |
438 |
ind_zmat(izm,4)=0 |
439 |
ind_zmat(izm,5)=0 |
440 |
val_zmat(izm,1)=norm2 |
441 |
val_zmat(izm,2)=val |
442 |
val_zmat(izm,3)=0.0 |
443 |
DejaFait(Izm3)=.TRUE. |
444 |
|
445 |
END IF ! end of test izm=3 |
446 |
|
447 |
! We add all atoms CF atoms linked to the already present atoms in the zmat to |
448 |
! the "to do" list: |
449 |
! Les atomes CF lies a IdAt0 sont mis en attente pour |
450 |
! etre traites |
451 |
|
452 |
! For 'historical' reasons, the first atom links have to be dealt with |
453 |
! in a special way... now ! |
454 |
|
455 |
if (Izm.ge.NaTreat) Return |
456 |
|
457 |
|
458 |
WRITE(*,*) 'DBG ZmatBuild Izm0',Izm0 |
459 |
|
460 |
if (debug) THEN |
461 |
WRITE(*,*) 'ind_zmat' |
462 |
DO I=1,na |
463 |
WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5) |
464 |
END DO |
465 |
END IF |
466 |
|
467 |
IF (FFIrst) GOTO 9753 |
468 |
|
469 |
I=Ind_zmat(Izm0,1) |
470 |
DO IdAtl=1,Lies_CF(I,0) |
471 |
Izm4= Lies_CF(I,IdAtl) |
472 |
! WRITE(IOOUT,*) 'Atome ',Izm+1,Izm4,Nom(Atome(Izm4)),Izm1, |
473 |
! $Izm2,Izm3 |
474 |
IF (ListAt(Izm4).AND.(.NOT.DejaFait(Izm4))) THEN |
475 |
Izm=Izm+1 |
476 |
Call AddLigne(Izm,Izm4,Izm1,Izm2,Izm3,ind_zmat,val_zmat, & |
477 |
x,y,z) |
478 |
DejaFait(Izm4)=.TRUE. |
479 |
END IF |
480 |
END DO |
481 |
! END IF |
482 |
|
483 |
if (debug) THEN |
484 |
WRITE(*,*) 'ind_zmat' |
485 |
DO I=1,na |
486 |
WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5) |
487 |
END DO |
488 |
END IF |
489 |
|
490 |
if (Izm.ge.NaTreat) Return |
491 |
|
492 |
IndFin=1 |
493 |
DO I=Izm0,Izm |
494 |
Iat=ind_zmat(I,1) |
495 |
! Do iaf=1,Lies_CF(Iat,0) |
496 |
!! if (ListAt(Lies_CF(IAt,iaf)).AND. |
497 |
!! & (.NOT.DejaFait(Lies_CF(IAt,iaf)))) THEN |
498 |
! if (ListAt(Lies_CF(IAt,iaf))) THEN |
499 |
! CAfaire(IndFin)=Lies_CF(IAt,Iaf) |
500 |
CaFaire(IndFin)=Iat |
501 |
IndFin=IndFin+1 |
502 |
! END IF |
503 |
! END DO |
504 |
END DO |
505 |
CAfaire(IndFin)=0 |
506 |
|
507 |
if (debug) WRITE(IOOUT,*) "CaFaire:",CaFaire |
508 |
|
509 |
if (debug) WRITE(*,*) 'DBG ZmatBuil - Treating Izm=4' |
510 |
|
511 |
! on a cree la premiere couche autour du premier centre |
512 |
! reste a finir les autres couches |
513 |
IndAFaire=1 |
514 |
if (debug) WRITE(IOOUT,*) "CaFaire:",CaFaire |
515 |
Do WHILE (Cafaire(IndAFaire).ne.0) |
516 |
IAt0=Cafaire(IndAfaire) |
517 |
if (debug) WRITE(*,*) "IndAFaire,IAt0,Lies_CF(IAt0,0)", & |
518 |
IndAFaire,IAt0,Lies_CF(IAt0,0) |
519 |
if (Lies_CF(IAt0,0).ge.1) THEN |
520 |
! IAt0 est l'atome pour lequel on construit la couche suivante |
521 |
! le premier atome lie est particulier car il definit l'orientation |
522 |
! de ce fragment |
523 |
IAti=Lies_CF(IAt0,1) |
524 |
WRITE(IOOUT,*) 'IAti:',IAti |
525 |
IAtd=IAt0 |
526 |
WRITE(IOOUT,*) 'IAtd:',IAtd |
527 |
IAtv=Lies_CP(IAt0,1) |
528 |
WRITE(IOOUT,*) 'IAtv:',IAtv |
529 |
IIAtdh=1 |
530 |
IAtdh=Lies_CF(IAtv,IIatdh) |
531 |
DO WHILE (Iatdh.eq.IAt0) |
532 |
IIatdh=IIatdh+1 |
533 |
IAtdh=Lies_CF(IAtv,IIatdh) |
534 |
END DO |
535 |
IF (IAtdh.eq.0) IAtdh=Lies_CP(IAtv,1) |
536 |
WRITE(IOOUT,*) 'IAtdh:',IAtdh |
537 |
IF (ListAt(IAti).AND.(.NOT.DejaFait(IAti))) THEN |
538 |
Izm=Izm+1 |
539 |
if (debug) WRITE(*,*) 'izm,IAti,IAtd,IAtv,IAtdh', & |
540 |
izm,IAti,IAtd,IAtv,IAtdh |
541 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh, & |
542 |
ind_zmat,val_zmat ,x,y,z) |
543 |
DejaFait(IAti)=.TRUE. |
544 |
END IF |
545 |
|
546 |
CAfaire(IndFin)=Lies_CF(IAt0,1) |
547 |
IndFin=IndFin+1 |
548 |
! Le traitement des autres est plus facile |
549 |
IAtdh=Lies_CF(IAt0,1) |
550 |
DO IAta=2,Lies_CF(IAt0,0) |
551 |
IAtI=Lies_CF(IAt0,IAta) |
552 |
CAfaire(IndFin)=IAtI |
553 |
IndFin=IndFin+1 |
554 |
|
555 |
IF (ListAt(IAti).AND.(.NOT.DejaFait(IAti))) THEN |
556 |
Izm=Izm+1 |
557 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh,ind_zmat & |
558 |
,val_zmat,x,y,z) |
559 |
DejaFait(IAti)=.TRUE. |
560 |
END IF |
561 |
END DO |
562 |
CAfaire(IndFin)=0 |
563 |
END IF |
564 |
IndAFaire=IndAFaire+1 |
565 |
if (debug) WRITE(IOOUT,*) "IndAfaire,CaFaire:",IndAfaire, & |
566 |
CaFaire |
567 |
END DO |
568 |
|
569 |
IndFin=1 |
570 |
DO I=1,Izm0 |
571 |
Iat=ind_zmat(I,1) |
572 |
! Do iaf=1,Lies_CF(Iat,0) |
573 |
if (ListAt(IAt).AND. & |
574 |
(.NOT.DejaFait(IAt))) THEN |
575 |
! if (ListAt(Lies_CF(IAt,iaf))) THEN |
576 |
! CAfaire(IndFin)=Lies_CF(IAt,Iaf) |
577 |
CaFaire(IndFin)=Iat |
578 |
IndFin=IndFin+1 |
579 |
END IF |
580 |
! END DO |
581 |
END DO |
582 |
CAfaire(IndFin)=0 |
583 |
|
584 |
if (debug) WRITE(IOOUT,*) "CaFaire:",CaFaire |
585 |
|
586 |
if (debug) WRITE(*,*) 'DBG ZmatBuil - Treating Izm=4' |
587 |
|
588 |
! on a cree la premiere couche autour du premier centre |
589 |
! reste a finir les autres couches |
590 |
IndAFaire=1 |
591 |
if (debug) WRITE(IOOUT,*) "CaFaire:",CaFaire |
592 |
Do WHILE (Cafaire(IndAFaire).ne.0) |
593 |
IAt0=Cafaire(IndAfaire) |
594 |
if (debug) WRITE(*,*) "IndAFaire,IAt0,Lies_CF(IAt0,0)", & |
595 |
IndAFaire,IAt0,Lies_CF(IAt0,0) |
596 |
if (Lies_CF(IAt0,0).ge.1) THEN |
597 |
! IAt0 est l'atome pour lequel on construit la couche suivante |
598 |
! le premier atome lie est particulier car il definit l'orientation |
599 |
! de ce fragment |
600 |
IAti=Lies_CF(IAt0,1) |
601 |
WRITE(IOOUT,*) 'IAti:',IAti |
602 |
IAtd=IAt0 |
603 |
WRITE(IOOUT,*) 'IAtd:',IAtd |
604 |
IAtv=Lies_CP(IAt0,1) |
605 |
WRITE(IOOUT,*) 'IAtv:',IAtv |
606 |
IIAtdh=1 |
607 |
IAtdh=Lies_CF(IAtv,IIatdh) |
608 |
DO WHILE (Iatdh.eq.IAt0) |
609 |
IIatdh=IIatdh+1 |
610 |
IAtdh=Lies_CF(IAtv,IIatdh) |
611 |
END DO |
612 |
IF (IAtdh.eq.0) IAtdh=Lies_CP(IAtv,1) |
613 |
WRITE(IOOUT,*) 'IAtdh:',IAtdh |
614 |
IF (ListAt(IAti).AND.(.NOT.DejaFait(IAti))) THEN |
615 |
Izm=Izm+1 |
616 |
if (debug) WRITE(*,*) 'izm,IAti,IAtd,IAtv,IAtdh', & |
617 |
izm,IAti,IAtd,IAtv,IAtdh |
618 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh, & |
619 |
ind_zmat,val_zmat ,x,y,z) |
620 |
DejaFait(IAti)=.TRUE. |
621 |
END IF |
622 |
|
623 |
CAfaire(IndFin)=Lies_CF(IAt0,1) |
624 |
IndFin=IndFin+1 |
625 |
! Le traitement des autres est plus facile |
626 |
IAtdh=Lies_CF(IAt0,1) |
627 |
DO IAta=2,Lies_CF(IAt0,0) |
628 |
IAtI=Lies_CF(IAt0,IAta) |
629 |
CAfaire(IndFin)=IAtI |
630 |
IndFin=IndFin+1 |
631 |
|
632 |
IF (ListAt(IAti).AND.(.NOT.DejaFait(IAti))) THEN |
633 |
Izm=Izm+1 |
634 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh,ind_zmat & |
635 |
,val_zmat,x,y,z) |
636 |
DejaFait(IAti)=.TRUE. |
637 |
END IF |
638 |
END DO |
639 |
CAfaire(IndFin)=0 |
640 |
END IF |
641 |
IndAFaire=IndAFaire+1 |
642 |
if (debug) WRITE(IOOUT,*) "IndAfaire,CaFaire:",IndAfaire, & |
643 |
CaFaire |
644 |
END DO |
645 |
|
646 |
|
647 |
! On a fini de creer la molecule autour du premier atome 'centre' |
648 |
! Pour les autres c'est presque id... sauf que les axes sont deja fixes |
649 |
! On pourrait imaginer de mettre des atomes fictifs pour redefinir des axes |
650 |
! locaux... dans une autre version |
651 |
! V2.0 |
652 |
9753 FFirst=.FALSE. |
653 |
if (debug) THEN |
654 |
WRITE(*,*) 'NbAt0r',NbAt0r,AtCP0 |
655 |
END IF |
656 |
DO I=1,NbAt0r |
657 |
! Boucle pour trouver celui qui a le plus d'atomes CF |
658 |
IdAt0=0 |
659 |
VCF=-1 |
660 |
DO ICP0=1,NbAt0 |
661 |
if (AtCP0(ICP0).NE.0) THEN |
662 |
ICat=AtCP0(ICP0) |
663 |
if (Lies_CF(ICAt,0).gt.VCF) THEN |
664 |
IdAt0=ICat |
665 |
IdxAt0=ICP0 |
666 |
VCF=Lies_CF(ICAt,0) |
667 |
END IF |
668 |
END IF |
669 |
END DO |
670 |
AtCP0(IdxAt0)=0 |
671 |
|
672 |
IF (debug) WRITE(*,*) 'Adding fragment centered on ',IdAt0, & |
673 |
LIAISONS(IdAt0,0) |
674 |
IF (debug) WRITE(*,*) 'Center linked to ',Lies_CF(IdAt0,0), & |
675 |
' atoms' |
676 |
! if (LIAISONS(IdAt0,0).EQ.0) goto 12345 |
677 |
|
678 |
if (debug) THEN |
679 |
WRITE(IOOUT,*) 'LIAISONS tralala',nbcycle |
680 |
DO IAt=1,na |
681 |
WRITE(IOOUT,1003) iat,(LIAISONS(Iat,Jat),Jat=0,NMaxL) |
682 |
END DO |
683 |
END IF |
684 |
1003 FORMAT(1X,I5,' - ',12(I5)) |
685 |
! Boucle pour voir quel est l'atome du fragment precedent qui est le plus |
686 |
! proche de celui ci |
687 |
! Rq: si ce sont des cycles lies, il pourrait etre malin de rechercher |
688 |
! a quoi il etait lie. |
689 |
norm2=1.e6 |
690 |
Idx=0 |
691 |
DO ICAt=1,Izm |
692 |
CALL vecteur(Idat0,ind_zmat(icat,1),x,y,z,vx1,vy1,vz1 & |
693 |
,norm1) |
694 |
if (norm2.ge.norm1) THEN |
695 |
norm2=norm1 |
696 |
Idx=Icat |
697 |
END IF |
698 |
END DO |
699 |
IF (debug) WRITE(*,*) 'Link between fragments ',IdAt0, & |
700 |
ind_zmat(Idx,1), ' -- Idx=',Idx |
701 |
|
702 |
! Despite the fact that this atom has officialy no CP atom |
703 |
! we add one into its list; the one just found |
704 |
Lies_CP(IdAt0,0)=Lies_CP(IdAt0,0)+1 |
705 |
Lies_CP(Idat0,Lies_CP(IdAt0,0))= ind_zmat(Idx,1) |
706 |
Lies_CP(Idat0,Lies_CP(IdAt0,0)+1)=0 |
707 |
|
708 |
|
709 |
! on a l'indice... on va rajouter cet atome a la liste ! |
710 |
izm=izm+1 |
711 |
n1=ind_zmat(Idx,1) |
712 |
! Petit probleme si Idx<=2 |
713 |
IF (Idx.EQ.1) THEN |
714 |
! Pb non negligeable ... |
715 |
IF (izm.ge.2) THEN |
716 |
IAtv=ind_zmat(2,1) |
717 |
IAtdh=ind_zmat(3,1) |
718 |
ELSE |
719 |
WRITE(*,*) '2 frag, le 1er a moins de 2 atomes..' |
720 |
WRITE(*,*) "J'ai merde... " |
721 |
STOP |
722 |
END IF |
723 |
ELSEIF (Idx.EQ.2) THEN |
724 |
IAtv=1 |
725 |
IF (izm.ge.2) THEN |
726 |
IAtdh=ind_zmat(3,1) |
727 |
ELSE |
728 |
WRITE(*,*) '2 frag, le 1er a moins de 2 atomes...' |
729 |
WRITE(*,*) "J'ai merde... " |
730 |
STOP |
731 |
END IF |
732 |
ELSE |
733 |
IAtv=ind_zmat(Idx,2) |
734 |
IAtdh=ind_zmat(Idx,3) |
735 |
END IF |
736 |
|
737 |
! WRITE(*,*) "Outchilou IAtv, IAtdh", IAtv, IAtdh,n1 |
738 |
CALL vecteur(n1,IdAt0,x,y,z,vx1,vy1,vz1,norm1) |
739 |
CALL vecteur(n1,IAtv,x,y,z,vx2,vy2,vz2,norm2) |
740 |
val=angle(vx1,vy1,vz1,norm1, & |
741 |
vx2,vy2,vz2,norm2) |
742 |
if (debug) WRITE(*,*) 'Angle val:1',IdAt0,n1,IAtv,val |
743 |
if ((abs(val).LE.10.).OR.(abs(pi-val).le.10.)) THEN |
744 |
IAtv=IAtdh |
745 |
! Ceci pose pb si Idx<=3... a traiter plus tard |
746 |
IF (Idx.ge.3) THEN |
747 |
IAtdh=ind_zmat(Idx,4) |
748 |
ELSE |
749 |
if (izm.ge.4) THEN |
750 |
IAtdh=4 |
751 |
ELSE |
752 |
WRITE(*,*) 'Pb Angle Val+idx=3+izm<=4' |
753 |
STOP |
754 |
END IF |
755 |
END IF |
756 |
END IF |
757 |
Call AddLigne(Izm,IdAt0,ind_zmat(Idx,1),IAtv,IAtdh, & |
758 |
ind_zmat,val_zmat,x,y,z) |
759 |
DejaFait(IdAt0)=.TRUE. |
760 |
|
761 |
IndFin=1 |
762 |
IAtd=IdAt0 |
763 |
n1=IAtdh |
764 |
IAtdh=IAtv |
765 |
IAtv=ind_zmat(Idx,1) |
766 |
! On ajoute les atomes lies a cet atome dans la liste a faire |
767 |
Do iaf=1,Lies_CF(IdAt0,0) |
768 |
IatI=Lies_CF(IdAt0,Iaf) |
769 |
! We check that this atom is not the one that is the closest to |
770 |
! the center atom |
771 |
if (IAtv.Ne.IAtI) THEN |
772 |
IF (debug) WRITE(*,*) 'Adding atom',IAtI, & |
773 |
'to CAFaire in pos',iaf |
774 |
CAfaire(IndFin)=IAtI |
775 |
IndFin=IndFin+1 |
776 |
! On les ajoute aussi dans la zmat |
777 |
If (ListAt(IAtI).AND.(.NOT.DejaFait(IatI))) THEN |
778 |
izm=izm+1 |
779 |
WRITE(*,*) "Outchili IAtv, IAtdh,IAtI", IAtv, IAtdh,IAtI |
780 |
CALL vecteur(IAtI,IAtD,x,y,z,vx1,vy1,vz1,norm1) |
781 |
CALL vecteur(IAtI,IAtv,x,y,z,vx2,vy2,vz2,norm2) |
782 |
val=angle(vx1,vy1,vz1,norm1, vx2,vy2,vz2,norm2) |
783 |
if (debug) & |
784 |
WRITE(*,*) 'Angle val:2',IAtI,IAtD,IAtv,val |
785 |
if ((abs(val).LE.10.).OR. & |
786 |
(abs(180.-abs(val)).le.10.)) THEN |
787 |
Call AddLigne(Izm,IAtI,IAtv,IAtdh,n1, & |
788 |
ind_zmat,val_zmat,x,y,z) |
789 |
DejaFait(Iati)=.TRUE. |
790 |
ELSE |
791 |
Call AddLigne(Izm,IAtI,IAtD,IAtv,IAtdh, & |
792 |
ind_zmat,val_zmat,x,y,z) |
793 |
DejaFait(Iati)=.TRUE. |
794 |
END IF |
795 |
END IF |
796 |
END IF |
797 |
END DO |
798 |
CAfaire(IndFin)=0 |
799 |
|
800 |
! On traite le reste de ce fragment !! |
801 |
IndAFaire=1 |
802 |
WRITE(IOOUT,*) CaFaire |
803 |
Do WHILE (Cafaire(IndAFaire).ne.0) |
804 |
IAt0=Cafaire(IndAfaire) |
805 |
if (Lies_CF(IAt0,0).ge.1) THEN |
806 |
! IAt0 est l'atome pour lequel on construit la couche suivante |
807 |
! le premier atome lie est particulier car il definit l'orientation |
808 |
! de ce fragment |
809 |
Itmp=1 |
810 |
IAti=Lies_CF(IAt0,Itmp) |
811 |
DO WHILE (DejaFait(IAti).AND. & |
812 |
(Itmp.Le.Lies_CF(IAt0,0))) |
813 |
Itmp=Itmp+1 |
814 |
IAti=Lies_CF(IAt0,ITmp) |
815 |
END DO |
816 |
If (ListAt(IAtI).AND.(.NOT.DejaFait(IatI))) THEN |
817 |
IF (debug) WRITE(IOOUT,*) 'IAti:',IAti |
818 |
IAtd=IAt0 |
819 |
IF (debug) WRITE(IOOUT,*) 'IAtd:',IAtd |
820 |
IAtv=Lies_CP(IAt0,1) |
821 |
IF (debug) WRITE(IOOUT,*) 'IAtv:',IAtv |
822 |
IIAtdh=1 |
823 |
IAtdh=Lies_CF(IAtv,IIatdh) |
824 |
DO WHILE (Iatdh.eq.IAt0) |
825 |
IIatdh=IIatdh+1 |
826 |
IAtdh=Lies_CF(IAtv,IIatdh) |
827 |
END DO |
828 |
IF (IAtdh.eq.0) IAtdh=Lies_CP(IAtv,1) |
829 |
IF (debug) WRITE(IOOUT,*) 'IAtdh:',IAtdh |
830 |
Izm=Izm+1 |
831 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh, & |
832 |
ind_zmat,val_zmat,x,y,z) |
833 |
DejaFait(Iati)=.TRUE. |
834 |
! Le traitement des autres est plus facile |
835 |
IAtdh=Lies_CF(IAt0,ITmp) |
836 |
DO IAta=ITmp+1,Lies_CF(IAt0,0) |
837 |
IAtI=Lies_CF(IAt0,IAta) |
838 |
If (ListAt(IAtI).AND.(.NOT.DejaFait(IatI))) & |
839 |
THEN |
840 |
Izm=Izm+1 |
841 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh, & |
842 |
ind_zmat,val_zmat,x,y,z) |
843 |
DejaFait(Iati)=.TRUE. |
844 |
END IF |
845 |
END DO |
846 |
END IF |
847 |
|
848 |
! On ajoute les atomes lies a cet atome dans la liste a faire |
849 |
Do iaf=1,Lies_CF(IAt0,0) |
850 |
CAfaire(IndFin)=Lies_CF(IAt0,Iaf) |
851 |
IndFin=IndFin+1 |
852 |
END DO |
853 |
CAfaire(IndFin)=0 |
854 |
END IF |
855 |
IndAFaire=IndAFaire+1 |
856 |
END DO |
857 |
!12345 CONTINUE |
858 |
END DO |
859 |
|
860 |
WRITE(*,*) 'TOTOTOTOTOTOTOTOT' |
861 |
|
862 |
if (debug) THEN |
863 |
WRITE(*,*) 'ind_zmat' |
864 |
DO I=1,na |
865 |
WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5) |
866 |
END DO |
867 |
END IF |
868 |
|
869 |
IndFin=1 |
870 |
DO I=1,Izm0 |
871 |
Iat=ind_zmat(I,1) |
872 |
Do iaf=1,Lies_CF(Iat,0) |
873 |
IIat=Lies_CF(Iat,iaf) |
874 |
if (ListAt(iIAt).AND. & |
875 |
(.NOT.DejaFait(iIAt))) THEN |
876 |
IAti=IIat |
877 |
WRITE(IOOUT,*) 'IAti:',IAti |
878 |
IAtd=IAt0 |
879 |
WRITE(IOOUT,*) 'IAtd:',IAtd |
880 |
IAtv=Lies_CP(IAt0,1) |
881 |
WRITE(IOOUT,*) 'IAtv:',IAtv |
882 |
IIAtdh=1 |
883 |
IAtdh=Lies_CF(IAtv,IIatdh) |
884 |
DO WHILE (Iatdh.eq.IAt0) |
885 |
IIatdh=IIatdh+1 |
886 |
IAtdh=Lies_CF(IAtv,IIatdh) |
887 |
END DO |
888 |
IF (IAtdh.eq.0) IAtdh=Lies_CP(IAtv,1) |
889 |
WRITE(IOOUT,*) 'IAtdh:',IAtdh |
890 |
IF (ListAt(IAti).AND.(.NOT.DejaFait(IAti))) THEN |
891 |
Izm=Izm+1 |
892 |
if (debug) WRITE(*,*) 'izm,IAti,IAtd,IAtv,IAtdh', & |
893 |
izm,IAti,IAtd,IAtv,IAtdh |
894 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh, & |
895 |
ind_zmat,val_zmat ,x,y,z) |
896 |
DejaFait(IAti)=.TRUE. |
897 |
CaFaire(IndFin)=iIat |
898 |
IndFin=IndFin+1 |
899 |
END IF |
900 |
END IF |
901 |
END DO |
902 |
END DO |
903 |
CAfaire(IndFin)=0 |
904 |
|
905 |
if (debug) WRITE(IOOUT,*) "CaFaire:",CaFaire |
906 |
|
907 |
if (debug) WRITE(*,*) 'DBG ZmatBuil - Toto' |
908 |
if (debug) THEN |
909 |
WRITE(*,*) 'ind_zmat' |
910 |
DO I=1,na |
911 |
WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5) |
912 |
END DO |
913 |
END IF |
914 |
|
915 |
! on a cree la premiere couche autour du premier centre |
916 |
! reste a finir les autres couches |
917 |
IndAFaire=1 |
918 |
if (debug) WRITE(IOOUT,*) "CaFaire:",CaFaire |
919 |
Do WHILE (Cafaire(IndAFaire).ne.0) |
920 |
IAt0=Cafaire(IndAfaire) |
921 |
if (debug) WRITE(*,*) "IndAFaire,IAt0,Lies_CF(IAt0,0)", & |
922 |
IndAFaire,IAt0,Lies_CF(IAt0,0) |
923 |
if (Lies_CF(IAt0,0).ge.1) THEN |
924 |
! IAt0 est l'atome pour lequel on construit la couche suivante |
925 |
! le premier atome lie est particulier car il definit l'orientation |
926 |
! de ce fragment |
927 |
IAti=Lies_CF(IAt0,1) |
928 |
WRITE(IOOUT,*) 'IAti:',IAti |
929 |
IAtd=IAt0 |
930 |
WRITE(IOOUT,*) 'IAtd:',IAtd |
931 |
IAtv=Lies_CP(IAt0,1) |
932 |
WRITE(IOOUT,*) 'IAtv:',IAtv |
933 |
IIAtdh=1 |
934 |
IAtdh=Lies_CF(IAtv,IIatdh) |
935 |
DO WHILE (Iatdh.eq.IAt0) |
936 |
IIatdh=IIatdh+1 |
937 |
IAtdh=Lies_CF(IAtv,IIatdh) |
938 |
END DO |
939 |
IF (IAtdh.eq.0) IAtdh=Lies_CP(IAtv,1) |
940 |
WRITE(IOOUT,*) 'IAtdh:',IAtdh |
941 |
IF (ListAt(IAti).AND.(.NOT.DejaFait(IAti))) THEN |
942 |
Izm=Izm+1 |
943 |
if (debug) WRITE(*,*) 'izm,IAti,IAtd,IAtv,IAtdh', & |
944 |
izm,IAti,IAtd,IAtv,IAtdh |
945 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh, & |
946 |
ind_zmat,val_zmat ,x,y,z) |
947 |
DejaFait(IAti)=.TRUE. |
948 |
END IF |
949 |
|
950 |
CAfaire(IndFin)=Lies_CF(IAt0,1) |
951 |
IndFin=IndFin+1 |
952 |
! Le traitement des autres est plus facile |
953 |
IAtdh=Lies_CF(IAt0,1) |
954 |
DO IAta=2,Lies_CF(IAt0,0) |
955 |
IAtI=Lies_CF(IAt0,IAta) |
956 |
CAfaire(IndFin)=IAtI |
957 |
IndFin=IndFin+1 |
958 |
|
959 |
IF (ListAt(IAti).AND.(.NOT.DejaFait(IAti))) THEN |
960 |
IF (debug) & |
961 |
WRITE(*,*) 'DBG ZmatBuil Toto adding',Iati,Izm |
962 |
Izm=Izm+1 |
963 |
Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh,ind_zmat & |
964 |
,val_zmat,x,y,z) |
965 |
DejaFait(IAti)=.TRUE. |
966 |
END IF |
967 |
END DO |
968 |
CAfaire(IndFin)=0 |
969 |
END IF |
970 |
IndAFaire=IndAFaire+1 |
971 |
if (debug) WRITE(IOOUT,*) "Toto IndAfaire,CaFaire:",IndAfaire, & |
972 |
CaFaire |
973 |
END DO |
974 |
|
975 |
|
976 |
if (debug) THEN |
977 |
WRITE(*,*) 'ind_zmat' |
978 |
DO I=1,na |
979 |
WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5) |
980 |
END DO |
981 |
END IF |
982 |
|
983 |
END |