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