root / src / Calc_zmat.f90 @ 12
Historique | Voir | Annoter | Télécharger (33,22 ko)
1 | 1 | pfleura2 | SUBROUTINE Calc_Zmat(na,atome,ind_zmat,val_zmat,x,y,z, & |
---|---|---|---|
2 | 1 | pfleura2 | r_cov, fact) |
3 | 1 | pfleura2 | |
4 | 12 | pfleura2 | !---------------------------------------------------------------------- |
5 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Sup?rieure de Lyon, |
6 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
7 | 12 | pfleura2 | ! Universit? Claude Bernard Lyon 1. All rights reserved. |
8 | 12 | pfleura2 | ! |
9 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
10 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
11 | 12 | pfleura2 | ! |
12 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
13 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
14 | 12 | pfleura2 | ! |
15 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
16 | 12 | pfleura2 | ! |
17 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
18 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
19 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
20 | 12 | pfleura2 | ! or (at your option) any later version. |
21 | 12 | pfleura2 | ! |
22 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
23 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
24 | 12 | pfleura2 | ! |
25 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
26 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
27 | 12 | pfleura2 | ! |
28 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
29 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
30 | 12 | pfleura2 | ! |
31 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
32 | 12 | pfleura2 | ! for commercial licensing opportunities. |
33 | 12 | pfleura2 | !---------------------------------------------------------------------- |
34 | 12 | pfleura2 | |
35 | 1 | pfleura2 | use Path_module, only : Pi,max_Z, NMaxL, Nom, KINT, KREAL |
36 | 8 | pfleura2 | use Io_module, only : IoOut |
37 | 1 | pfleura2 | |
38 | 1 | pfleura2 | IMPLICIT NONE |
39 | 1 | pfleura2 | |
40 | 1 | pfleura2 | ! Number of atoms |
41 | 1 | pfleura2 | integer(KINT), INTENT(IN) :: na |
42 | 1 | pfleura2 | ! Mass number of atoms |
43 | 1 | pfleura2 | INTEGER(KINT), INTENT(IN) :: atome(na) |
44 | 1 | pfleura2 | ! Coordinates |
45 | 1 | pfleura2 | real(KREAL), INTENT(IN) :: x(na),y(na),z(na) |
46 | 1 | pfleura2 | ! Covalent radii |
47 | 1 | pfleura2 | REAL(KREAL), INTENT(IN) :: R_cov(Max_Z) |
48 | 1 | pfleura2 | ! Factor to determine connectivity |
49 | 1 | pfleura2 | REAL(KREAL) :: Fact |
50 | 1 | pfleura2 | ! Zmat index and values |
51 | 1 | pfleura2 | integer(KINT), INTENT(OUT) :: ind_zmat(na,5) |
52 | 1 | pfleura2 | real(KREAL),INTENT(OUT) :: val_zmat(na,3) |
53 | 1 | pfleura2 | |
54 | 1 | pfleura2 | |
55 | 1 | pfleura2 | INTEGER(KINT), ALLOCATABLE :: LIAISONS(:,:) !(na,0:NMaxL |
56 | 1 | pfleura2 | INTEGER(KINT), ALLOCATABLE :: LiaisonsBis(:,:) ! na,0:NMaxL |
57 | 1 | pfleura2 | INTEGER(KINT), ALLOCATABLE :: LieS_CP(:,:),LieS_CF(:,:) ! (na,0:NMaxL) |
58 | 1 | pfleura2 | INTEGER(KINT), ALLOCATABLE :: NbAt3(:,:) !(Na,2) |
59 | 1 | pfleura2 | INTEGER(KINT), ALLOCATABLE :: CycleAt(:) !(Na) |
60 | 1 | pfleura2 | INTEGER(KINT), ALLOCATABLE :: CAFaire(:) ! Na |
61 | 1 | pfleura2 | |
62 | 1 | pfleura2 | Integer(KINT) :: AtTypCycl(Max_Z) |
63 | 1 | pfleura2 | Integer(KINT) :: NbCycle |
64 | 1 | pfleura2 | real(KREAL) :: vx1,vy1,vz1,norm1 |
65 | 1 | pfleura2 | real(KREAL) :: vx2,vy2,vz2,norm2 |
66 | 2 | pfleura2 | real(KREAL) :: val |
67 | 1 | pfleura2 | Logical PasFini,AtTerm,Debug,Bicycle,FLie3,FirstCycle |
68 | 1 | pfleura2 | LOGICAL, ALLOCATABLE :: Former3(:), DejaFait(:) ! Na |
69 | 1 | pfleura2 | Logical FTmp |
70 | 1 | pfleura2 | LOGICAL F1213, F1223,F1323 |
71 | 1 | pfleura2 | |
72 | 1 | pfleura2 | INTEGER(KINT) :: I,J,K, IZM, N1,n2, N3, IL, JL |
73 | 1 | pfleura2 | INTEGER(KINT) :: IdAt0, I3, IAt3, Idx3, I1, I0, IAf |
74 | 1 | pfleura2 | INTEGER(KINT) :: Izm1,Izm2, IZm3,IZm4, VCF, ICat |
75 | 1 | pfleura2 | INTEGER(KINT) :: IOld, IndFin, IdAtL, IndAFaire |
76 | 1 | pfleura2 | INTEGER(KINT) :: IAti, IAtD, IAtv, IIAtDh, IAtDh |
77 | 1 | pfleura2 | INTEGER(KINT) :: IAt0, IAta, IAt, Jat,Idx |
78 | 1 | pfleura2 | INTEGER(KINT) :: ITmp, IAtTmp, NbAt0 |
79 | 1 | pfleura2 | INTEGER(KINT) :: NbLies, ICycle, IMax |
80 | 1 | pfleura2 | REAL(KREAL) :: d,d12, d13,d32 |
81 | 1 | pfleura2 | |
82 | 1 | pfleura2 | INTERFACE |
83 | 1 | pfleura2 | function valid(string) result (isValid) |
84 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
85 | 1 | pfleura2 | logical :: isValid |
86 | 1 | pfleura2 | END function VALID |
87 | 1 | pfleura2 | |
88 | 1 | pfleura2 | FUNCTION angle(v1x,v1y,v1z,norm1,v2x,v2y,v2z,norm2) |
89 | 1 | pfleura2 | use Path_module, only : Pi,KINT, KREAL |
90 | 1 | pfleura2 | real(KREAL) :: v1x,v1y,v1z,norm1 |
91 | 1 | pfleura2 | real(KREAL) :: v2x,v2y,v2z,norm2 |
92 | 1 | pfleura2 | real(KREAL) :: angle |
93 | 1 | pfleura2 | END FUNCTION ANGLE |
94 | 1 | pfleura2 | |
95 | 1 | pfleura2 | |
96 | 1 | pfleura2 | END INTERFACE |
97 | 1 | pfleura2 | |
98 | 1 | pfleura2 | |
99 | 1 | pfleura2 | |
100 | 1 | pfleura2 | debug=valid("Calc_zmat") |
101 | 1 | pfleura2 | if (debug) WRITE(*,*) "========== Entering Calc_zmat ==========" |
102 | 1 | pfleura2 | |
103 | 1 | pfleura2 | FirstCycle=.TRUE. |
104 | 1 | pfleura2 | FTmp=.FALSE. |
105 | 1 | pfleura2 | NbCycle=0 |
106 | 1 | pfleura2 | DO i=1,na |
107 | 1 | pfleura2 | DO J=1,5 |
108 | 1 | pfleura2 | Ind_Zmat(i,J)=0 |
109 | 1 | pfleura2 | END DO |
110 | 1 | pfleura2 | END DO |
111 | 1 | pfleura2 | ALLOCATE(Former3(Na), DejaFait(Na)) |
112 | 1 | pfleura2 | ALLOCATE(CaFaire(Na), CycleAt(Na)) |
113 | 1 | pfleura2 | ALLOCATE(NbAt3(Na,2)) |
114 | 1 | pfleura2 | ALLOCATE(Liaisons(na,0:NMaxL),LiaisonsBis(na,0:NMaxL)) |
115 | 1 | pfleura2 | ALLOCATE(Lies_CP(na,0:NMaxL), Lies_CF(na,0:NMaxL)) |
116 | 1 | pfleura2 | |
117 | 1 | pfleura2 | |
118 | 1 | pfleura2 | WRITE(IOOUT,*) Na |
119 | 1 | pfleura2 | WRITE(IOOUT,*) 'Calc_zmat' |
120 | 1 | pfleura2 | DO I=1,na |
121 | 1 | pfleura2 | WRITE(IOOUT,*) NOM(Atome(I)),X(i),y(i),z(i) |
122 | 1 | pfleura2 | END DO |
123 | 1 | pfleura2 | |
124 | 1 | pfleura2 | if (na.le.2) THEN |
125 | 1 | pfleura2 | WRITE(*,*) "I do not work for less than 2 atoms :-p" |
126 | 1 | pfleura2 | RETURN |
127 | 1 | pfleura2 | END IF |
128 | 1 | pfleura2 | |
129 | 1 | pfleura2 | ! Cas particulier: 3 atomes ou moins... |
130 | 1 | pfleura2 | if (Na.eq.3) THEN |
131 | 1 | pfleura2 | d12=sqrt((x(1)-x(2))**2+(y(1)-y(2))**2+(z(1)-z(2))**2) |
132 | 1 | pfleura2 | d13=sqrt((x(1)-x(3))**2+(y(1)-y(3))**2+(z(1)-z(3))**2) |
133 | 1 | pfleura2 | d32=sqrt((x(3)-x(2))**2+(y(3)-y(2))**2+(z(3)-z(2))**2) |
134 | 1 | pfleura2 | F1213=(d12<=d13) |
135 | 1 | pfleura2 | F1323=(d13<=d32) |
136 | 1 | pfleura2 | F1223=(d12<=d32) |
137 | 1 | pfleura2 | if (debug) THEN |
138 | 1 | pfleura2 | WRITE(*,*) "DEBUG Calc_Zmat 3 atoms" |
139 | 1 | pfleura2 | WRITE(*,*) "d12,d13,d32:",d12,d13,d32 |
140 | 1 | pfleura2 | WRITE(*,*) "F1213,F1323,F1223:",F1213,F1323,F1223 |
141 | 1 | pfleura2 | END IF |
142 | 1 | pfleura2 | if (F1213) THEN |
143 | 1 | pfleura2 | if (F1323) THEN |
144 | 1 | pfleura2 | ind_zmat(1,1)=3 |
145 | 1 | pfleura2 | ind_zmat(2,1)=1 |
146 | 1 | pfleura2 | ind_zmat(2,2)=3 |
147 | 1 | pfleura2 | ind_zmat(3,1)=2 |
148 | 1 | pfleura2 | ind_zmat(3,2)=1 |
149 | 1 | pfleura2 | ind_zmat(3,3)=3 |
150 | 1 | pfleura2 | ELSE |
151 | 1 | pfleura2 | ind_zmat(1,1)=1 |
152 | 1 | pfleura2 | ind_zmat(2,1)=2 |
153 | 1 | pfleura2 | ind_zmat(2,2)=1 |
154 | 1 | pfleura2 | ind_zmat(3,1)=3 |
155 | 1 | pfleura2 | ind_zmat(3,2)=2 |
156 | 1 | pfleura2 | ind_zmat(3,3)=1 |
157 | 1 | pfleura2 | END IF |
158 | 1 | pfleura2 | ELSE |
159 | 1 | pfleura2 | IF (F1223) THEN |
160 | 1 | pfleura2 | ind_zmat(1,1)=2 |
161 | 1 | pfleura2 | ind_zmat(2,1)=1 |
162 | 1 | pfleura2 | ind_zmat(2,2)=2 |
163 | 1 | pfleura2 | ind_zmat(3,1)=3 |
164 | 1 | pfleura2 | ind_zmat(3,2)=1 |
165 | 1 | pfleura2 | ind_zmat(3,3)=2 |
166 | 1 | pfleura2 | ELSE |
167 | 1 | pfleura2 | ind_zmat(1,1)=2 |
168 | 1 | pfleura2 | ind_zmat(2,1)=3 |
169 | 1 | pfleura2 | ind_zmat(2,2)=2 |
170 | 1 | pfleura2 | ind_zmat(3,1)=1 |
171 | 1 | pfleura2 | ind_zmat(3,2)=3 |
172 | 1 | pfleura2 | ind_zmat(3,3)=2 |
173 | 1 | pfleura2 | END IF |
174 | 1 | pfleura2 | END IF |
175 | 1 | pfleura2 | IF (debug) THEN |
176 | 1 | pfleura2 | DO i=1,na |
177 | 1 | pfleura2 | WRITE(*,*) (ind_zmat(i,j),j=1,5) |
178 | 1 | pfleura2 | END DO |
179 | 1 | pfleura2 | END IF |
180 | 1 | pfleura2 | |
181 | 1 | pfleura2 | ! We have ind_zmat, we fill val_zmat |
182 | 1 | pfleura2 | val_zmat(1,1)=0. |
183 | 1 | pfleura2 | val_zmat(1,2)=0. |
184 | 1 | pfleura2 | val_zmat(1,3)=0. |
185 | 1 | pfleura2 | n2=ind_zmat(2,1) |
186 | 1 | pfleura2 | n1=ind_zmat(2,2) |
187 | 1 | pfleura2 | d=sqrt((x(n1)-x(n2))**2+(y(n1)-y(n2))**2+ & |
188 | 1 | pfleura2 | (z(n1)-z(n2))**2) |
189 | 1 | pfleura2 | val_zmat(2,1)=d |
190 | 1 | pfleura2 | val_zmat(2,2)=0. |
191 | 1 | pfleura2 | val_zmat(2,3)=0. |
192 | 1 | pfleura2 | n1=ind_zmat(3,1) |
193 | 1 | pfleura2 | n2=ind_zmat(3,2) |
194 | 1 | pfleura2 | n3=ind_zmat(3,3) |
195 | 1 | pfleura2 | CALL vecteur(n2,n1,x,y,z,vx1,vy1,vz1,norm1) |
196 | 1 | pfleura2 | if (debug) write(*,*) n1,n2,norm1 |
197 | 1 | pfleura2 | val_zmat(3,1)=norm1 |
198 | 1 | pfleura2 | |
199 | 1 | pfleura2 | CALL vecteur(n2,n3,x,y,z,vx2,vy2,vz2,norm2) |
200 | 1 | pfleura2 | val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2) |
201 | 1 | pfleura2 | if (debug) write(*,*) n2,n3,norm2,val |
202 | 1 | pfleura2 | val_zmat(3,2)=val |
203 | 1 | pfleura2 | val_zmat(3,3)=0. |
204 | 1 | pfleura2 | |
205 | 1 | pfleura2 | RETURN |
206 | 1 | pfleura2 | END IF |
207 | 1 | pfleura2 | |
208 | 1 | pfleura2 | |
209 | 1 | pfleura2 | ! Premiere etape : calcul des connectivites |
210 | 1 | pfleura2 | DO I=1,na |
211 | 1 | pfleura2 | DejaFait(I)=.FALSE. |
212 | 1 | pfleura2 | Former3(I)=.False. |
213 | 1 | pfleura2 | Do J=0,NMaxL |
214 | 5 | pfleura2 | Liaisons(I,j)=0 |
215 | 5 | pfleura2 | LiaisonsBis(I,j)=0 |
216 | 1 | pfleura2 | END DO |
217 | 1 | pfleura2 | DO J=1,5 |
218 | 1 | pfleura2 | ind_zmat(I,J)=0 |
219 | 1 | pfleura2 | END DO |
220 | 1 | pfleura2 | END DO |
221 | 1 | pfleura2 | |
222 | 1 | pfleura2 | if (debug) WRITE(IOOUT,*) "Liaisons initialiazed" |
223 | 1 | pfleura2 | ! DO IL=1,na |
224 | 1 | pfleura2 | ! WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL) |
225 | 1 | pfleura2 | ! WRITE(IOOUT,1003) Il,(LIAISONSBis(IL,JL),JL=0,NMaxL) |
226 | 1 | pfleura2 | ! END DO |
227 | 1 | pfleura2 | |
228 | 1 | pfleura2 | Call CalcCnct(na,atome,x,y,z,LIAISONS,r_cov,fact) |
229 | 1 | pfleura2 | |
230 | 1 | pfleura2 | if (debug) THEN |
231 | 1 | pfleura2 | WRITE(IOOUT,*) "Connections calculated" |
232 | 1 | pfleura2 | DO IL=1,na |
233 | 1 | pfleura2 | WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL) |
234 | 1 | pfleura2 | END DO |
235 | 1 | pfleura2 | END IF |
236 | 1 | pfleura2 | |
237 | 1 | pfleura2 | |
238 | 1 | pfleura2 | ! on va maintenant trier ces connectivites en 2 : |
239 | 1 | pfleura2 | ! Lies_CF : vers l'exterieur de la molecule |
240 | 1 | pfleura2 | ! Lies_CP : vers l'interieur de la molecule |
241 | 1 | pfleura2 | ! Pour cela, on procede 'a l'envers' : on regarde les atomes |
242 | 1 | pfleura2 | ! auxquels sont lies les atomes attaches -> on remplit Lies_CF/P |
243 | 1 | pfleura2 | ! et on supprime ces atomes... |
244 | 1 | pfleura2 | |
245 | 1 | pfleura2 | ! v2.0 on copie Liaison dans LiaisonBis. On analyse LiaisonBis |
246 | 1 | pfleura2 | ! tout en modifiant Liaison. Cela evite de fausser l'analyse: un atome |
247 | 1 | pfleura2 | ! qui est lie initialement a 2 atomes (et qui n'est donc pas terminal) |
248 | 1 | pfleura2 | ! peut devenir terminal en milieu de traitement si on annule la liaison |
249 | 1 | pfleura2 | ! qui le liait a un atome terminal situ? avant lui... |
250 | 1 | pfleura2 | ! ex: H2O code dans l'ordre H,O,H. |
251 | 1 | pfleura2 | PasFini=.True. |
252 | 1 | pfleura2 | AtTerm=.True. |
253 | 1 | pfleura2 | DO WHILE (PasFini.AND.AtTerm) |
254 | 1 | pfleura2 | PasFini=.False. |
255 | 1 | pfleura2 | AtTerm=.False. |
256 | 1 | pfleura2 | DO I=1,na |
257 | 1 | pfleura2 | DO J=0,NMaxL |
258 | 1 | pfleura2 | LiaisonsBis(I,J)=Liaisons(I,J) |
259 | 1 | pfleura2 | END DO |
260 | 1 | pfleura2 | END DO |
261 | 1 | pfleura2 | ! DO IL=1,na |
262 | 1 | pfleura2 | ! WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL) |
263 | 1 | pfleura2 | ! WRITE(IOOUT,1003) Il,(LIAISONSBis(IL,JL),JL=0,NMaxL) |
264 | 1 | pfleura2 | ! END DO |
265 | 1 | pfleura2 | ! WRITE(IOOUT,*) "==================================" |
266 | 1 | pfleura2 | |
267 | 1 | pfleura2 | |
268 | 1 | pfleura2 | DO I=1,na |
269 | 1 | pfleura2 | if ((LiaisonsBis(I,0).eq.1).AND.Liaisons(I,0).ne.0) THEN |
270 | 1 | pfleura2 | AtTerm=.True. |
271 | 1 | pfleura2 | ! On enleve cet atome |
272 | 1 | pfleura2 | Liaisons(I,0)=0 |
273 | 1 | pfleura2 | NbLies=Lies_CP(I,0)+1 |
274 | 1 | pfleura2 | Lies_CP(I,NbLies)=Liaisons(I,1) |
275 | 1 | pfleura2 | Lies_CP(I,0)=NbLies |
276 | 1 | pfleura2 | Liaisons(Liaisons(I,1),0)=Liaisons(Liaisons(I,1),0)-1 |
277 | 1 | pfleura2 | |
278 | 1 | pfleura2 | NbLies=Lies_CF(Liaisons(I,1),0)+1 |
279 | 1 | pfleura2 | Lies_CF(Liaisons(I,1),NbLies)=I |
280 | 1 | pfleura2 | Lies_CF(Liaisons(I,1),0)=NbLies |
281 | 1 | pfleura2 | |
282 | 1 | pfleura2 | Call Annul(Liaisons,Liaisons(I,1),I) |
283 | 1 | pfleura2 | |
284 | 1 | pfleura2 | END IF |
285 | 1 | pfleura2 | |
286 | 1 | pfleura2 | if (Liaisons(I,0).ge.1) THEN |
287 | 1 | pfleura2 | PasFini=.TRUE. |
288 | 1 | pfleura2 | END IF |
289 | 1 | pfleura2 | |
290 | 1 | pfleura2 | END DO |
291 | 1 | pfleura2 | if (debug) WRITE(*,*) 'PasFini, AtTerm',PasFini,AtTerm |
292 | 1 | pfleura2 | If (PasFini.AND.(.Not.AtTerm)) THEN |
293 | 1 | pfleura2 | ! Pas d'atomes terminaux lors de l'exploration precedente. |
294 | 1 | pfleura2 | ! On a soit une erreur, soit un cycle. Je ne sais pas encore gerer |
295 | 1 | pfleura2 | ! tous les cas : on affiche un warning |
296 | 1 | pfleura2 | WRITE(*,*) "Je ne trouve pas d'atomes terminaux" |
297 | 1 | pfleura2 | WRITE(*,*) "Possibilite de molecule cyclique" |
298 | 1 | pfleura2 | WRITE(*,*) "Cas en cours de traitement: verifier l'output" |
299 | 1 | pfleura2 | ! On va d'abord voir si on a des atomes li?s a plus de 2 centres. |
300 | 1 | pfleura2 | AtTerm=.TRUE. |
301 | 1 | pfleura2 | Bicycle=.False. |
302 | 1 | pfleura2 | ICycle=0 |
303 | 1 | pfleura2 | IMax=0 |
304 | 1 | pfleura2 | DO I=1,na |
305 | 1 | pfleura2 | if (Liaisons(I,0).gt.2) THEN |
306 | 1 | pfleura2 | ICycle=ICycle+1 |
307 | 1 | pfleura2 | BiCycle=.True. |
308 | 1 | pfleura2 | If (Liaisons(I,0).gt.IMax) Imax=Liaisons(I,0) |
309 | 1 | pfleura2 | Former3(I)=.True. |
310 | 1 | pfleura2 | END IF |
311 | 1 | pfleura2 | END DO |
312 | 1 | pfleura2 | IF (BiCycle) THEN |
313 | 1 | pfleura2 | ! On a des atomes lies a 3 ou plus d'atomes... |
314 | 1 | pfleura2 | ! donc soit des bicycles, soit plusieurs |
315 | 1 | pfleura2 | ! cycles attaches par un sommet... |
316 | 1 | pfleura2 | WRITE(*,*) "On dirait un bicyle... on essaie" |
317 | 1 | pfleura2 | WRITE(*,*) ICycle, "atomes lies a plus de 2 atomes" |
318 | 1 | pfleura2 | WRITe(*,*) "Nb Attaches max:",IMax |
319 | 1 | pfleura2 | ! Plusieurs cas possibles pour un bicycle: |
320 | 1 | pfleura2 | ! 1) 2 cycles relies par un sommet, ICycle=2, IMax=3 |
321 | 1 | pfleura2 | ! 2) 2 cycles relies par une arrete, ICycle=2, Imax=3 |
322 | 1 | pfleura2 | If (Imax.Eq.3) THEN |
323 | 1 | pfleura2 | ! on doit pouvoir traiter celui la... |
324 | 1 | pfleura2 | ! On classe les atomes li?s a trois atomes, par le nombre d'atomes |
325 | 1 | pfleura2 | ! lies a trois atomes |
326 | 1 | pfleura2 | ! auxquels ils sont li?s ... interessant pour les composes asterisques. |
327 | 1 | pfleura2 | I3=0 |
328 | 1 | pfleura2 | FLie3=.False. |
329 | 1 | pfleura2 | DO I=1,Na |
330 | 1 | pfleura2 | If (Liaisons(I,0).EQ.3) THEN |
331 | 1 | pfleura2 | I3=I3+1 |
332 | 1 | pfleura2 | K=0 |
333 | 1 | pfleura2 | DO J=1,Liaisons(I,0) |
334 | 1 | pfleura2 | If (Liaisons(Liaisons(I,J),0).Eq.3) THEN |
335 | 1 | pfleura2 | k=k+1 |
336 | 1 | pfleura2 | FLie3=.True. |
337 | 1 | pfleura2 | END IF |
338 | 1 | pfleura2 | END DO |
339 | 1 | pfleura2 | NbAt3(I3,2)=k |
340 | 1 | pfleura2 | NbAt3(I3,1)=I |
341 | 1 | pfleura2 | END IF |
342 | 1 | pfleura2 | END DO |
343 | 1 | pfleura2 | ! A-t-on deux atomes a 3 lies ensemble ? |
344 | 1 | pfleura2 | IF (FLie3) THEN |
345 | 1 | pfleura2 | ! on les classe pas nb at lies a 3 |
346 | 1 | pfleura2 | IAt3=0 |
347 | 1 | pfleura2 | Idx3=0 |
348 | 1 | pfleura2 | DO I=1,I3 |
349 | 1 | pfleura2 | IF (NbAt3(I,2).ge.Iat3) THEN |
350 | 1 | pfleura2 | IAt3=NbAt3(I,2) |
351 | 1 | pfleura2 | Idx3=NbAt3(I,1) |
352 | 1 | pfleura2 | END IF |
353 | 1 | pfleura2 | END DO |
354 | 1 | pfleura2 | ! On va enlever ces liaisons entre atomes a 3, en les mettant |
355 | 1 | pfleura2 | ! en CF de l'atome 'central' |
356 | 1 | pfleura2 | if (debug) WRITE(*,*) "Atome ",Idx3, & |
357 | 1 | pfleura2 | " retenu, li? a",IAt3," atomes 3" |
358 | 1 | pfleura2 | DO I=1,Liaisons(Idx3,0) |
359 | 1 | pfleura2 | I1=Liaisons(Idx3,I) |
360 | 1 | pfleura2 | If (Liaisons(I1,0).EQ.3) THEN |
361 | 1 | pfleura2 | if (debug) WRITE(*,*) "Traitement ",I1,Idx3 |
362 | 1 | pfleura2 | NbLies=Lies_CF(Idx3,0)+1 |
363 | 1 | pfleura2 | Lies_CF(Idx3,NbLies)=I1 |
364 | 1 | pfleura2 | Lies_CF(Idx3,0)=NbLies |
365 | 1 | pfleura2 | NbLies=Lies_CP(I1,0)+1 |
366 | 1 | pfleura2 | Lies_CP(I1,NbLies)=Idx3 |
367 | 1 | pfleura2 | Call Annul(Liaisons,I1,Idx3) |
368 | 1 | pfleura2 | Call Annul(Liaisons,Idx3,I1) |
369 | 1 | pfleura2 | Liaisons(Idx3,0)=Liaisons(Idx3,0)-1 |
370 | 1 | pfleura2 | Liaisons(I1,0)=Liaisons(I1,0)-1 |
371 | 1 | pfleura2 | END IF |
372 | 1 | pfleura2 | END DO |
373 | 1 | pfleura2 | ELSE |
374 | 1 | pfleura2 | WRITE(*,*) "Aucune liaisons entre deux atomes li?s" |
375 | 1 | pfleura2 | WRITE(*,*) "Pas encore trait?" |
376 | 1 | pfleura2 | STOP |
377 | 1 | pfleura2 | END IF !FLie3=T ? |
378 | 1 | pfleura2 | END IF !Imax=3 ? |
379 | 1 | pfleura2 | ELSE ! BiCyle ? |
380 | 1 | pfleura2 | ! Un seul cycle. Facile :-) |
381 | 1 | pfleura2 | WRITE(*,*) "Un cycle identifie..." |
382 | 1 | pfleura2 | NbCycle=NbCycle+1 |
383 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Considering cycle ',NbCycle |
384 | 1 | pfleura2 | If (NbCycle.ge.2) THEN |
385 | 1 | pfleura2 | ! si ce n'est pas le premier cycle que l'on met, on regarde si parmi les |
386 | 1 | pfleura2 | ! atomes du cycle, l'un d'eux etait avant attache a 3 atomes... |
387 | 1 | pfleura2 | I=1 |
388 | 1 | pfleura2 | DO WHILE (Liaisons(I,0).ne.2) |
389 | 1 | pfleura2 | I=I+1 |
390 | 1 | pfleura2 | END DO |
391 | 1 | pfleura2 | if (debug) WRITE(*,*) "I>2:",I,Former3(I) |
392 | 1 | pfleura2 | FTmp=Former3(I) |
393 | 1 | pfleura2 | I0=I |
394 | 1 | pfleura2 | IOld=I |
395 | 1 | pfleura2 | I1=I |
396 | 1 | pfleura2 | I=Liaisons(I,1) |
397 | 1 | pfleura2 | DO WHILE (.NOT.FTmp) |
398 | 1 | pfleura2 | I1=Liaisons(I,1) |
399 | 1 | pfleura2 | If (I1.Eq.IOld) I1=Liaisons(I,2) |
400 | 1 | pfleura2 | FTmp=Former3(I1) |
401 | 1 | pfleura2 | if (debug) WRITE(*,*) "I,I1,I0,IOld",I,I1,I0, & |
402 | 1 | pfleura2 | IOld,FTmp |
403 | 1 | pfleura2 | IF (I1.eq.I0) FTmp=.TRUE. |
404 | 1 | pfleura2 | if (debug) WRITE(*,*) "I,I1,I0,IOld",I,I1,I0, & |
405 | 1 | pfleura2 | IOld,FTmp |
406 | 1 | pfleura2 | IOld=I |
407 | 1 | pfleura2 | I=I1 |
408 | 1 | pfleura2 | END DO |
409 | 1 | pfleura2 | if (debug) WRITE(*,*) "I,I1,I0,IOld",I,I1,I0, & |
410 | 1 | pfleura2 | IOld,FTmp |
411 | 1 | pfleura2 | IF (Former3(I1)) THEN |
412 | 1 | pfleura2 | ! On a notre atome particulier ... cool :-) |
413 | 1 | pfleura2 | if (debug) WRITE(*,*) "Atome former3",I1 |
414 | 1 | pfleura2 | ITmp=I1 |
415 | 1 | pfleura2 | END IF |
416 | 1 | pfleura2 | END IF ! NbCycle >=2 |
417 | 1 | pfleura2 | IF (.NOT.Ftmp) THEN |
418 | 1 | pfleura2 | if (debug) WRITE(*,*) "Pas trouve de former3" |
419 | 1 | pfleura2 | ! on regarde si il y a un atome particulier.. ie un heteroatome ou autre. |
420 | 1 | pfleura2 | DO I=1,Max_Z |
421 | 1 | pfleura2 | AtTypCycl(I)=0 |
422 | 1 | pfleura2 | END DO |
423 | 1 | pfleura2 | DO I=1,na |
424 | 1 | pfleura2 | if (Liaisons(I,0).eq.2) & |
425 | 1 | pfleura2 | AtTypCycl(Atome(I))=AtTypCycl(Atome(I))+1 |
426 | 1 | pfleura2 | if (debug) WRITE(*,*) I,Atome(I), & |
427 | 1 | pfleura2 | AtTypCycl(Atome(I)), & |
428 | 1 | pfleura2 | Liaisons(I,0) |
429 | 1 | pfleura2 | END DO |
430 | 1 | pfleura2 | Itmp=NmaxL+1 |
431 | 1 | pfleura2 | IAtTmp=0 |
432 | 1 | pfleura2 | DO I=1,Max_Z |
433 | 1 | pfleura2 | If ((AtTypCycl(I).gt.0).and.(AtTypCycl(I).le.Itmp)) & |
434 | 1 | pfleura2 | THEN |
435 | 1 | pfleura2 | Itmp=AtTypCycl(I) |
436 | 1 | pfleura2 | IAtTmp=I |
437 | 1 | pfleura2 | END IF |
438 | 1 | pfleura2 | END DO |
439 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Itmp,IAtTmp:',Itmp,IAtTmp |
440 | 1 | pfleura2 | ! On a le type de l'atome particulier... on va prendre le premier venu |
441 | 1 | pfleura2 | DO I=na,1,-1 |
442 | 1 | pfleura2 | If ((Atome(I).eq.IAtTmp).AND.(Liaisons(I,0).Eq.2)) & |
443 | 1 | pfleura2 | Itmp=I |
444 | 1 | pfleura2 | END DO |
445 | 1 | pfleura2 | END IF |
446 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Atome ',Itmp,'(',IAtTmp,') retenu' |
447 | 1 | pfleura2 | ! On va tricher en enlevant les liaisons de cet atome a la main... |
448 | 1 | pfleura2 | I0=Itmp |
449 | 1 | pfleura2 | I1=Liaisons(I0,1) |
450 | 1 | pfleura2 | DO WHILE (I1.Ne.ITmp) |
451 | 1 | pfleura2 | if (debug) WRITE(*,*) "Going from",I0,"to ",I1 |
452 | 1 | pfleura2 | ! On rajoute ces deux liaisons en CF de Itmp |
453 | 1 | pfleura2 | NbLies=Lies_CF(I0,0)+1 |
454 | 1 | pfleura2 | Lies_CF(I0,NbLies)=Liaisons(I0,1) |
455 | 1 | pfleura2 | Lies_CF(I0,0)=NbLies |
456 | 1 | pfleura2 | ! et les liaisons vers Itmp deviennent des CP pour les autres atomes |
457 | 1 | pfleura2 | NbLies=Lies_CP(I1,0)+1 |
458 | 1 | pfleura2 | Lies_CP(I1,NbLies)=I0 |
459 | 1 | pfleura2 | Lies_CP(I1,0)=NbLies |
460 | 1 | pfleura2 | |
461 | 1 | pfleura2 | Call Annul(Liaisons,I1,I0) |
462 | 1 | pfleura2 | Liaisons(I1,0)=Liaisons(I1,0)-1 |
463 | 1 | pfleura2 | Liaisons(I0,0)=Liaisons(I0,0)-1 |
464 | 1 | pfleura2 | |
465 | 1 | pfleura2 | DO IL=1,na |
466 | 1 | pfleura2 | WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL) |
467 | 1 | pfleura2 | END DO |
468 | 1 | pfleura2 | I0=I1 |
469 | 1 | pfleura2 | I1=Liaisons(I0,1) |
470 | 1 | pfleura2 | |
471 | 1 | pfleura2 | end do |
472 | 1 | pfleura2 | Call Annul(Liaisons,I1,I0) |
473 | 1 | pfleura2 | Liaisons(I1,0)=Liaisons(I1,0)-1 |
474 | 1 | pfleura2 | Liaisons(I0,0)=Liaisons(I0,0)-1 |
475 | 1 | pfleura2 | END IF |
476 | 1 | pfleura2 | END IF |
477 | 1 | pfleura2 | DO IL=1,na |
478 | 1 | pfleura2 | WRITE(IOOUT,1003) Il,(LIAISONS(IL,JL),JL=0,NMaxL) |
479 | 1 | pfleura2 | END DO |
480 | 1 | pfleura2 | ! WRITE(IOOUT,*) "==================================" |
481 | 1 | pfleura2 | ! WRITE(IOOUT,*) "==================================" |
482 | 1 | pfleura2 | END DO |
483 | 1 | pfleura2 | |
484 | 1 | pfleura2 | ! WRITE(IOOUT,*) "==================================" |
485 | 1 | pfleura2 | ! Il ne reste plus que des atomes lies a rien... |
486 | 1 | pfleura2 | ! ce sont les 'centres' de la molecule. On repart |
487 | 1 | pfleura2 | ! d'eux pour construire le reste de la molecule. |
488 | 1 | pfleura2 | |
489 | 1 | pfleura2 | 1003 FORMAT(1X,I4,' - ',15(I5)) |
490 | 1 | pfleura2 | ! Avant de partir, on va classer, pour chaque atome, les atomes CF par |
491 | 1 | pfleura2 | ! nombre de masse decroissant. |
492 | 1 | pfleura2 | DO I=1,na |
493 | 1 | pfleura2 | ! WRITE(*,*) I,Lies_CF(I,0),(Atome(Lies_CF(I,J)),j=1,Lies_CF(I,0)) |
494 | 1 | pfleura2 | DO J=1,Lies_CF(I,0)-1 |
495 | 1 | pfleura2 | DO K=J+1,Lies_CF(I,0) |
496 | 1 | pfleura2 | if (atome(Lies_CF(I,K))>atome(Lies_CF(I,J))) THEN |
497 | 1 | pfleura2 | Itmp=Lies_CF(I,K) |
498 | 1 | pfleura2 | Lies_CF(I,K)=Lies_CF(I,J) |
499 | 1 | pfleura2 | Lies_CF(I,J)=Itmp |
500 | 1 | pfleura2 | END IF |
501 | 1 | pfleura2 | END DO |
502 | 1 | pfleura2 | END DO |
503 | 1 | pfleura2 | ! WRITE(*,*) I,Lies_CF(I,0),(Atome(Lies_CF(I,J)),j=1,Lies_CF(I,0)) |
504 | 1 | pfleura2 | END DO |
505 | 1 | pfleura2 | |
506 | 1 | pfleura2 | IF (Debug) THEN |
507 | 1 | pfleura2 | WRITE(IOOUT,*) 'LIAISONS' |
508 | 1 | pfleura2 | DO I=1,na |
509 | 1 | pfleura2 | WRITE(IOOUT,1003) i,(LIAISONS(I,J),J=0,NMaxL) |
510 | 1 | pfleura2 | END DO |
511 | 1 | pfleura2 | |
512 | 1 | pfleura2 | WRITE(IOOUT,*) 'LIes_CF' |
513 | 1 | pfleura2 | DO I=1,na |
514 | 1 | pfleura2 | WRITE(IOOUT,1003) i,(LIeS_CF(I,J),J=0,NMaxL) |
515 | 1 | pfleura2 | END DO |
516 | 1 | pfleura2 | |
517 | 1 | pfleura2 | WRITE(IOOUT,*) 'LIes_CP' |
518 | 1 | pfleura2 | DO I=1,na |
519 | 1 | pfleura2 | WRITE(IOOUT,1003) i,(LIeS_CP(I,J),J=0,NMaxL) |
520 | 1 | pfleura2 | END DO |
521 | 1 | pfleura2 | END IF |
522 | 1 | pfleura2 | |
523 | 1 | pfleura2 | |
524 | 1 | pfleura2 | ! On compte le nb d'atomes sans atomes CP (centripetes) |
525 | 1 | pfleura2 | NbAt0=0 |
526 | 1 | pfleura2 | DO I=1,na |
527 | 1 | pfleura2 | IF (Lies_CP(I,0).eq.0) THEN |
528 | 1 | pfleura2 | NbAt0=NbAt0+1 |
529 | 1 | pfleura2 | IF (DEBUG) WRITE(*,*) "Center atom",NbAt0,I,Atome(I) |
530 | 1 | pfleura2 | END IF |
531 | 1 | pfleura2 | END DO |
532 | 1 | pfleura2 | |
533 | 1 | pfleura2 | ! On va les traiter tous en construisant les molecules en partant d'eux |
534 | 1 | pfleura2 | ! Le premier atome sans CP est different des autres car il fixe |
535 | 1 | pfleura2 | ! l'origine |
536 | 1 | pfleura2 | |
537 | 1 | pfleura2 | IZm=1 |
538 | 1 | pfleura2 | ! Boucle pour trouver celui qui a le plus d'atomes CF |
539 | 1 | pfleura2 | IdAt0=0 |
540 | 1 | pfleura2 | VCF=0 |
541 | 1 | pfleura2 | DO ICAt=1,na |
542 | 1 | pfleura2 | if ((Lies_CP(ICaT,0).eq.0).AND.(Lies_CF(ICAt,0).gt.VCF)) THEN |
543 | 1 | pfleura2 | IdAt0=ICat |
544 | 1 | pfleura2 | VCF=Lies_CF(ICAt,0) |
545 | 1 | pfleura2 | END IF |
546 | 1 | pfleura2 | END DO |
547 | 1 | pfleura2 | Lies_CP(IdAt0,0)=-1 |
548 | 1 | pfleura2 | |
549 | 1 | pfleura2 | ! WRITE(IOOUT,*) 'Atome 1', IdAt0, Nom(Atome(IdAt0)) |
550 | 1 | pfleura2 | Izm1=IdAt0 |
551 | 1 | pfleura2 | ind_zmat(izm,1)=Izm1 |
552 | 1 | pfleura2 | ind_zmat(izm,2)=0 |
553 | 1 | pfleura2 | ind_zmat(izm,3)=0 |
554 | 1 | pfleura2 | ind_zmat(izm,4)=0 |
555 | 1 | pfleura2 | ind_zmat(izm,5)=0 |
556 | 1 | pfleura2 | val_zmat(izm,1)=0.0 |
557 | 1 | pfleura2 | val_zmat(izm,2)=0.0 |
558 | 1 | pfleura2 | val_zmat(izm,3)=0.0 |
559 | 1 | pfleura2 | DejaFait(Izm1)=.True. |
560 | 1 | pfleura2 | |
561 | 1 | pfleura2 | ! Les atomes CF lies a IdAt0 sont mis en attente pour |
562 | 1 | pfleura2 | ! etre traites |
563 | 1 | pfleura2 | |
564 | 1 | pfleura2 | IndFin=1 |
565 | 1 | pfleura2 | Do iaf=1,Lies_CF(IdAt0,0) |
566 | 1 | pfleura2 | CAfaire(IndFin)=Lies_CF(IdAt0,Iaf) |
567 | 1 | pfleura2 | IndFin=IndFin+1 |
568 | 1 | pfleura2 | END DO |
569 | 1 | pfleura2 | CAfaire(IndFin)=0 |
570 | 1 | pfleura2 | |
571 | 1 | pfleura2 | ! On construit la premiere couche qui est speciale car elle fixe les |
572 | 1 | pfleura2 | ! axes. |
573 | 1 | pfleura2 | ! Plusieurs cas sont possibles suivant le nb d'atomes CF |
574 | 1 | pfleura2 | |
575 | 1 | pfleura2 | IF (Lies_CF(IdAt0,0).ge.3) THEN |
576 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Cas tres simple,',IdAt0, & |
577 | 1 | pfleura2 | ' li? a plus de 3 atomes' |
578 | 1 | pfleura2 | IZm2=Lies_CF(IdAt0,1) |
579 | 1 | pfleura2 | IZm3=Lies_CF(IdAt0,2) |
580 | 1 | pfleura2 | ! WRITE(IOOUT,*) 'Atome 2' , Izm2, Nom(Atome(Izm2)) |
581 | 1 | pfleura2 | ! WRITE(IOOUT,*) 'Atome 3' ,Izm3, Nom(Atome(izm3)) |
582 | 1 | pfleura2 | |
583 | 1 | pfleura2 | Izm=2 |
584 | 1 | pfleura2 | CALL vecteur(IZm1,IZm2,x,y,z,vx1,vy1,vz1,norm1) |
585 | 1 | pfleura2 | ! write(*,11) n1,n2,norm1 |
586 | 1 | pfleura2 | |
587 | 1 | pfleura2 | ind_zmat(izm,1)=izm2 |
588 | 1 | pfleura2 | ind_zmat(izm,2)=izm1 |
589 | 1 | pfleura2 | ind_zmat(izm,3)=0 |
590 | 1 | pfleura2 | ind_zmat(izm,4)=0 |
591 | 1 | pfleura2 | ind_zmat(izm,5)=0 |
592 | 1 | pfleura2 | val_zmat(izm,1)=norm1 |
593 | 1 | pfleura2 | val_zmat(izm,2)=0.0 |
594 | 1 | pfleura2 | val_zmat(izm,3)=0.0 |
595 | 1 | pfleura2 | DejaFait(Izm2)=.TRUE. |
596 | 1 | pfleura2 | |
597 | 1 | pfleura2 | Izm=3 |
598 | 1 | pfleura2 | CALL vecteur(izm1,izm3,x,y,z,vx2,vy2,vz2,norm2) |
599 | 1 | pfleura2 | val=angle(vx1,vy1,vz1,norm1,vx2,vy2,vz2,norm2) |
600 | 1 | pfleura2 | |
601 | 1 | pfleura2 | ! write(*,11) n1,n2,norm1,n3,val |
602 | 1 | pfleura2 | |
603 | 1 | pfleura2 | ind_zmat(izm,1)=izm3 |
604 | 1 | pfleura2 | ind_zmat(izm,2)=izm1 |
605 | 1 | pfleura2 | ind_zmat(izm,3)=izm2 |
606 | 1 | pfleura2 | ind_zmat(izm,4)=0 |
607 | 1 | pfleura2 | ind_zmat(izm,5)=0 |
608 | 1 | pfleura2 | val_zmat(izm,1)=norm2 |
609 | 1 | pfleura2 | val_zmat(izm,2)=val |
610 | 1 | pfleura2 | val_zmat(izm,3)=0.0 |
611 | 1 | pfleura2 | DejaFait(Izm3)=.TRUE. |
612 | 1 | pfleura2 | |
613 | 1 | pfleura2 | DO IdAtl=3,Lies_CF(IdAt0,0) |
614 | 1 | pfleura2 | Izm4= Lies_CF(IdAt0,IdAtl) |
615 | 1 | pfleura2 | ! WRITE(IOOUT,*) 'Atome ',Izm+1,Izm4,Nom(Atome(Izm4)),Izm1, |
616 | 1 | pfleura2 | ! $Izm2,Izm3 |
617 | 1 | pfleura2 | Izm=Izm+1 |
618 | 1 | pfleura2 | Call AddLigne(Izm,Izm4,Izm1,Izm2,Izm3,ind_zmat,val_zmat, & |
619 | 1 | pfleura2 | x,y,z) |
620 | 1 | pfleura2 | DejaFait(Izm4)=.TRUE. |
621 | 1 | pfleura2 | END DO |
622 | 1 | pfleura2 | END IF |
623 | 1 | pfleura2 | |
624 | 1 | pfleura2 | IF (Lies_CF(Izm1,0).eq.2) THEN |
625 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Cas simple,',IdAt0, & |
626 | 1 | pfleura2 | ' li? a 2 atomes' |
627 | 1 | pfleura2 | |
628 | 1 | pfleura2 | IZm2=Lies_CF(IdAt0,1) |
629 | 1 | pfleura2 | IZm3=Lies_CF(IdAt0,2) |
630 | 1 | pfleura2 | Izm=2 |
631 | 1 | pfleura2 | CALL vecteur(IZm1,IZm2,x,y,z,vx1,vy1,vz1,norm1) |
632 | 1 | pfleura2 | ! write(*,11) n1,n2,norm1 |
633 | 1 | pfleura2 | |
634 | 1 | pfleura2 | ind_zmat(izm,1)=izm2 |
635 | 1 | pfleura2 | ind_zmat(izm,2)=izm1 |
636 | 1 | pfleura2 | ind_zmat(izm,3)=0 |
637 | 1 | pfleura2 | ind_zmat(izm,4)=0 |
638 | 1 | pfleura2 | ind_zmat(izm,5)=0 |
639 | 1 | pfleura2 | val_zmat(izm,1)=norm1 |
640 | 1 | pfleura2 | val_zmat(izm,2)=0.0 |
641 | 1 | pfleura2 | val_zmat(izm,3)=0.0 |
642 | 1 | pfleura2 | DejaFait(Izm2)=.TRUE. |
643 | 1 | pfleura2 | |
644 | 1 | pfleura2 | Izm=3 |
645 | 1 | pfleura2 | |
646 | 1 | pfleura2 | CALL vecteur(izm1,izm3,x,y,z,vx2,vy2,vz2,norm2) |
647 | 1 | pfleura2 | val=angle(vx1,vy1,vz1,norm1, & |
648 | 1 | pfleura2 | vx2,vy2,vz2,norm2) |
649 | 1 | pfleura2 | |
650 | 1 | pfleura2 | ! write(*,11) n1,n2,norm1,n3,val |
651 | 1 | pfleura2 | |
652 | 1 | pfleura2 | ind_zmat(izm,1)=izm3 |
653 | 1 | pfleura2 | ind_zmat(izm,2)=izm1 |
654 | 1 | pfleura2 | ind_zmat(izm,3)=izm2 |
655 | 1 | pfleura2 | ind_zmat(izm,4)=0 |
656 | 1 | pfleura2 | ind_zmat(izm,5)=0 |
657 | 1 | pfleura2 | val_zmat(izm,1)=norm2 |
658 | 1 | pfleura2 | val_zmat(izm,2)=val |
659 | 1 | pfleura2 | val_zmat(izm,3)=0.0 |
660 | 1 | pfleura2 | DejaFait(Izm3)=.TRUE. |
661 | 1 | pfleura2 | |
662 | 1 | pfleura2 | END IF |
663 | 1 | pfleura2 | |
664 | 1 | pfleura2 | IF (Lies_CF(Izm1,0).eq.1) THEN |
665 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Cas merdouille,',IdAt0, & |
666 | 1 | pfleura2 | ' li? a 1 atome' |
667 | 1 | pfleura2 | |
668 | 1 | pfleura2 | IZm2=Lies_CF(IdAt0,1) |
669 | 1 | pfleura2 | Izm=2 |
670 | 1 | pfleura2 | CALL vecteur(IZm1,IZm2,x,y,z,vx1,vy1,vz1,norm1) |
671 | 1 | pfleura2 | ! write(*,11) n1,n2,norm1 |
672 | 1 | pfleura2 | |
673 | 1 | pfleura2 | ind_zmat(izm,1)=izm2 |
674 | 1 | pfleura2 | ind_zmat(izm,2)=izm1 |
675 | 1 | pfleura2 | ind_zmat(izm,3)=0 |
676 | 1 | pfleura2 | ind_zmat(izm,4)=0 |
677 | 1 | pfleura2 | ind_zmat(izm,5)=0 |
678 | 1 | pfleura2 | val_zmat(izm,1)=norm1 |
679 | 1 | pfleura2 | val_zmat(izm,2)=0.0 |
680 | 1 | pfleura2 | val_zmat(izm,3)=0.0 |
681 | 1 | pfleura2 | DejaFait(Izm2)=.TRUE. |
682 | 1 | pfleura2 | |
683 | 1 | pfleura2 | ! Pour les autres atomes, on prend les atomes |
684 | 1 | pfleura2 | ! CF lie a l'tome CF lie a At0... en esperant |
685 | 1 | pfleura2 | ! qu'il en a !!! |
686 | 1 | pfleura2 | ! => il faudra voir le cas ou il n'en a pas !!! |
687 | 1 | pfleura2 | ! en attendant on rajoute le test... |
688 | 1 | pfleura2 | IF (Lies_CF(Izm2,0).Eq.0) THEN |
689 | 1 | pfleura2 | WRITE(*,*) "Je n'arrive pas a trouver les premiers" |
690 | 1 | pfleura2 | WRITE(*,*) "atomes pour construire la molecule" |
691 | 1 | pfleura2 | WRITE(*,*) "Atome central li? au plus a 1 atome",Izm1,izm2 |
692 | 1 | pfleura2 | WRITE(*,*) "Et atome 2 li? a rien... moi perdu" |
693 | 1 | pfleura2 | STOP |
694 | 1 | pfleura2 | END IF |
695 | 1 | pfleura2 | |
696 | 1 | pfleura2 | ! On ajoute les atomes lies a cet atome dans la liste a faire |
697 | 1 | pfleura2 | Do iaf=1,Lies_CF(Izm2,0) |
698 | 1 | pfleura2 | CAfaire(IndFin)=Lies_CF(Izm2,Iaf) |
699 | 1 | pfleura2 | IndFin=IndFin+1 |
700 | 1 | pfleura2 | END DO |
701 | 1 | pfleura2 | CAfaire(IndFin)=0 |
702 | 1 | pfleura2 | Izm3= Lies_CF(Izm2,1) |
703 | 1 | pfleura2 | Izm=3 |
704 | 1 | pfleura2 | CALL vecteur(izm2,izm1,x,y,z,vx1,vy1,vz1,norm1) |
705 | 1 | pfleura2 | |
706 | 1 | pfleura2 | CALL vecteur(izm2,izm3,x,y,z,vx2,vy2,vz2,norm2) |
707 | 1 | pfleura2 | val=angle(vx1,vy1,vz1,norm1, & |
708 | 1 | pfleura2 | vx2,vy2,vz2,norm2) |
709 | 1 | pfleura2 | |
710 | 1 | pfleura2 | ! write(*,11) n1,n2,norm1,n3,val |
711 | 1 | pfleura2 | |
712 | 1 | pfleura2 | ind_zmat(izm,1)=izm3 |
713 | 1 | pfleura2 | ind_zmat(izm,2)=izm2 |
714 | 1 | pfleura2 | ind_zmat(izm,3)=izm1 |
715 | 1 | pfleura2 | ind_zmat(izm,4)=0 |
716 | 1 | pfleura2 | ind_zmat(izm,5)=0 |
717 | 1 | pfleura2 | val_zmat(izm,1)=norm1 |
718 | 1 | pfleura2 | val_zmat(izm,2)=val |
719 | 1 | pfleura2 | val_zmat(izm,3)=0.0 |
720 | 1 | pfleura2 | DejaFait(Izm3)=.TRUE. |
721 | 1 | pfleura2 | |
722 | 1 | pfleura2 | ! je pense que ce qui suit est totalement inutile |
723 | 1 | pfleura2 | ! C DO IdAtl=3,Lies_CF(IdAt0,0) |
724 | 1 | pfleura2 | ! C Izm4= Lies_CF(IdAt0,IdAtl) |
725 | 1 | pfleura2 | ! C Izm=Izm+1 |
726 | 1 | pfleura2 | ! C Call AddLigne(Izm,Izm4,Izm1,Izm2,Izm3,ind_zmat,val_zmat |
727 | 1 | pfleura2 | ! C $,x,y,z) |
728 | 1 | pfleura2 | ! C DejaFait(Izm4)=.TRUE. |
729 | 1 | pfleura2 | ! C END DO |
730 | 1 | pfleura2 | END IF |
731 | 1 | pfleura2 | |
732 | 1 | pfleura2 | ! on a cree la premiere couche autour du premier centre |
733 | 1 | pfleura2 | ! reste a finir les autres couches |
734 | 1 | pfleura2 | IndAFaire=1 |
735 | 1 | pfleura2 | if (debug) WRITE(IOOUT,*) "CaFaire:",CaFaire |
736 | 1 | pfleura2 | Do WHILE (Cafaire(IndAFaire).ne.0) |
737 | 1 | pfleura2 | IAt0=Cafaire(IndAfaire) |
738 | 1 | pfleura2 | if (debug) WRITE(*,*) "IndAFaire,IAt0,Lies_CF(IAt0,0)", & |
739 | 1 | pfleura2 | IndAFaire,IAt0,Lies_CF(IAt0,0) |
740 | 1 | pfleura2 | if (Lies_CF(IAt0,0).ge.1) THEN |
741 | 1 | pfleura2 | ! IAt0 est l'atome pour lequel on construit la couche suivante |
742 | 1 | pfleura2 | ! le premier atome lie est particulier car il definit l'orientation |
743 | 1 | pfleura2 | ! de ce fragment |
744 | 1 | pfleura2 | IAti=Lies_CF(IAt0,1) |
745 | 1 | pfleura2 | ! WRITE(IOOUT,*) 'IAti:',IAti |
746 | 1 | pfleura2 | IAtd=IAt0 |
747 | 1 | pfleura2 | ! WRITE(IOOUT,*) 'IAtd:',IAtd |
748 | 1 | pfleura2 | IAtv=Lies_CP(IAt0,1) |
749 | 1 | pfleura2 | ! WRITE(IOOUT,*) 'IAtv:',IAtv |
750 | 1 | pfleura2 | IIAtdh=1 |
751 | 1 | pfleura2 | IAtdh=Lies_CF(IAtv,IIatdh) |
752 | 1 | pfleura2 | DO WHILE (Iatdh.eq.IAt0) |
753 | 1 | pfleura2 | IIatdh=IIatdh+1 |
754 | 1 | pfleura2 | IAtdh=Lies_CF(IAtv,IIatdh) |
755 | 1 | pfleura2 | END DO |
756 | 1 | pfleura2 | IF (IAtdh.eq.0) IAtdh=Lies_CP(IAtv,1) |
757 | 1 | pfleura2 | ! WRITE(IOOUT,*) 'IAtdh:',IAtdh |
758 | 1 | pfleura2 | IF (.NOT.DejaFait(IAti)) THEN |
759 | 1 | pfleura2 | Izm=Izm+1 |
760 | 1 | pfleura2 | if (debug) WRITE(*,*) 'izm,IAti,IAtd,IAtv,IAtdh', & |
761 | 1 | pfleura2 | izm,IAti,IAtd,IAtv,IAtdh |
762 | 1 | pfleura2 | Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh,ind_zmat,val_zmat & |
763 | 1 | pfleura2 | ,x,y,z) |
764 | 1 | pfleura2 | DejaFait(IAti)=.TRUE. |
765 | 1 | pfleura2 | END IF |
766 | 1 | pfleura2 | |
767 | 1 | pfleura2 | CAfaire(IndFin)=Lies_CF(IAt0,1) |
768 | 1 | pfleura2 | IndFin=IndFin+1 |
769 | 1 | pfleura2 | ! Le traitement des autres est plus facile |
770 | 1 | pfleura2 | IAtdh=Lies_CF(IAt0,1) |
771 | 1 | pfleura2 | DO IAta=2,Lies_CF(IAt0,0) |
772 | 1 | pfleura2 | IAtI=Lies_CF(IAt0,IAta) |
773 | 1 | pfleura2 | if (debug) WRITE(*,*) " Problem is here; IndFin:",I |
774 | 1 | pfleura2 | CAfaire(IndFin)=IAtI |
775 | 1 | pfleura2 | IndFin=IndFin+1 |
776 | 1 | pfleura2 | |
777 | 1 | pfleura2 | IF (.NOT.DejaFait(IAti)) THEN |
778 | 1 | pfleura2 | Izm=Izm+1 |
779 | 1 | pfleura2 | Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh,ind_zmat & |
780 | 1 | pfleura2 | ,val_zmat,x,y,z) |
781 | 1 | pfleura2 | DejaFait(IAti)=.TRUE. |
782 | 1 | pfleura2 | END IF |
783 | 1 | pfleura2 | END DO |
784 | 1 | pfleura2 | |
785 | 1 | pfleura2 | CAfaire(IndFin)=0 |
786 | 1 | pfleura2 | END IF |
787 | 1 | pfleura2 | IndAFaire=IndAFaire+1 |
788 | 1 | pfleura2 | END DO |
789 | 1 | pfleura2 | |
790 | 1 | pfleura2 | |
791 | 1 | pfleura2 | ! On a fini de creer la molecule autour du premier atome 'centre' |
792 | 1 | pfleura2 | ! Pour les autres c'est presque id... sauf que les axes sont deja fixes |
793 | 1 | pfleura2 | ! On pourrait imaginer de mettre des atomes fictifs pour redefinir des axes |
794 | 1 | pfleura2 | ! locaux... dans une autre version |
795 | 1 | pfleura2 | ! V2.0 |
796 | 1 | pfleura2 | NbAt0=NbAt0-1 |
797 | 1 | pfleura2 | DO I=1,NbAt0 |
798 | 1 | pfleura2 | ! Boucle pour trouver celui qui a le plus d'atomes CF |
799 | 1 | pfleura2 | |
800 | 1 | pfleura2 | IdAt0=0 |
801 | 1 | pfleura2 | VCF=0 |
802 | 1 | pfleura2 | |
803 | 1 | pfleura2 | DO ICAt=1,na |
804 | 1 | pfleura2 | if ((Lies_CP(ICaT,0).eq.0).AND.(Lies_CF(ICAt,0).gt.VCF)) & |
805 | 1 | pfleura2 | THEN |
806 | 1 | pfleura2 | IdAt0=ICat |
807 | 1 | pfleura2 | VCF=Lies_CF(ICAt,0) |
808 | 1 | pfleura2 | END IF |
809 | 1 | pfleura2 | END DO |
810 | 1 | pfleura2 | Lies_CP(IdAt0,0)=-1 |
811 | 1 | pfleura2 | |
812 | 1 | pfleura2 | IF (debug) WRITE(*,*) 'Adding fragment centered on ',IdAt0, & |
813 | 1 | pfleura2 | LIAISONS(IdAt0,0) |
814 | 1 | pfleura2 | IF (debug) WRITE(*,*) 'Center linked to ',Lies_CF(IdAt0,0), & |
815 | 1 | pfleura2 | ' atoms' |
816 | 1 | pfleura2 | ! if (LIAISONS(IdAt0,0).EQ.0) goto 12345 |
817 | 1 | pfleura2 | |
818 | 1 | pfleura2 | if (debug) THEN |
819 | 1 | pfleura2 | WRITE(IOOUT,*) 'LIAISONS tralala',nbcycle |
820 | 1 | pfleura2 | DO IAt=1,na |
821 | 1 | pfleura2 | WRITE(IOOUT,1003) iat,(LIAISONS(Iat,Jat),Jat=0,NMaxL) |
822 | 1 | pfleura2 | END DO |
823 | 1 | pfleura2 | END IF |
824 | 1 | pfleura2 | |
825 | 1 | pfleura2 | ! Boucle pour voir quel est l'atome du fragment precedent qui est le plus |
826 | 1 | pfleura2 | ! proche de celui ci |
827 | 1 | pfleura2 | ! Rq: si ce sont des cycles lies, il pourrait etre malin de rechercher |
828 | 1 | pfleura2 | ! a quoi il etait lie. |
829 | 1 | pfleura2 | norm2=1.e6 |
830 | 1 | pfleura2 | Idx=0 |
831 | 1 | pfleura2 | DO ICAt=1,Izm |
832 | 1 | pfleura2 | CALL vecteur(Idat0,ind_zmat(icat,1),x,y,z,vx1,vy1,vz1,norm1) |
833 | 1 | pfleura2 | if (norm2.ge.norm1) THEN |
834 | 1 | pfleura2 | norm2=norm1 |
835 | 1 | pfleura2 | Idx=Icat |
836 | 1 | pfleura2 | END IF |
837 | 1 | pfleura2 | END DO |
838 | 1 | pfleura2 | IF (debug) WRITE(*,*) 'Link between fragments ',IdAt0, & |
839 | 1 | pfleura2 | ind_zmat(Idx,1), ' -- Idx=',Idx |
840 | 1 | pfleura2 | |
841 | 1 | pfleura2 | ! on a l'indice... on va rajouter cet atome a la liste ! |
842 | 1 | pfleura2 | izm=izm+1 |
843 | 1 | pfleura2 | n1=ind_zmat(Idx,1) |
844 | 1 | pfleura2 | ! Petit probleme si Idx<=2 |
845 | 1 | pfleura2 | IF (Idx.EQ.1) THEN |
846 | 1 | pfleura2 | ! Pb non negligeable ... |
847 | 1 | pfleura2 | IF (izm.ge.2) THEN |
848 | 1 | pfleura2 | IAtv=ind_zmat(2,1) |
849 | 1 | pfleura2 | IAtdh=ind_zmat(3,1) |
850 | 1 | pfleura2 | ELSE |
851 | 1 | pfleura2 | WRITE(*,*) '2 fragments, le 1er a moins de 2 atomes...' |
852 | 1 | pfleura2 | WRITE(*,*) "J'ai merde... " |
853 | 1 | pfleura2 | STOP |
854 | 1 | pfleura2 | END IF |
855 | 1 | pfleura2 | ELSEIF (Idx.EQ.2) THEN |
856 | 1 | pfleura2 | IAtv=1 |
857 | 1 | pfleura2 | IF (izm.ge.2) THEN |
858 | 1 | pfleura2 | IAtdh=ind_zmat(3,1) |
859 | 1 | pfleura2 | ELSE |
860 | 1 | pfleura2 | WRITE(*,*) '2 fragments, le 1er a moins de 2 atomes...' |
861 | 1 | pfleura2 | WRITE(*,*) "J'ai merde... " |
862 | 1 | pfleura2 | STOP |
863 | 1 | pfleura2 | END IF |
864 | 1 | pfleura2 | ELSE |
865 | 1 | pfleura2 | IAtv=ind_zmat(Idx,2) |
866 | 1 | pfleura2 | IAtdh=ind_zmat(Idx,3) |
867 | 1 | pfleura2 | END IF |
868 | 1 | pfleura2 | |
869 | 1 | pfleura2 | ! WRITE(*,*) "Outchilou IAtv, IAtdh", IAtv, IAtdh,n1 |
870 | 1 | pfleura2 | CALL vecteur(n1,IdAt0,x,y,z,vx1,vy1,vz1,norm1) |
871 | 1 | pfleura2 | CALL vecteur(n1,IAtv,x,y,z,vx2,vy2,vz2,norm2) |
872 | 1 | pfleura2 | val=angle(vx1,vy1,vz1,norm1, & |
873 | 1 | pfleura2 | vx2,vy2,vz2,norm2) |
874 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Angle val:1',IdAt0,n1,IAtv,val |
875 | 1 | pfleura2 | if ((abs(val).LE.10.).OR.(abs(pi-val).le.10.)) THEN |
876 | 1 | pfleura2 | IAtv=IAtdh |
877 | 1 | pfleura2 | ! Ceci pose pb si Idx<=3... a traiter plus tard |
878 | 1 | pfleura2 | IF (Idx.ge.3) THEN |
879 | 1 | pfleura2 | IAtdh=ind_zmat(Idx,4) |
880 | 1 | pfleura2 | ELSE |
881 | 1 | pfleura2 | if (izm.ge.4) THEN |
882 | 1 | pfleura2 | IAtdh=4 |
883 | 1 | pfleura2 | ELSE |
884 | 1 | pfleura2 | WRITE(*,*) 'Pb Angle Val+idx=3+izm<=4' |
885 | 1 | pfleura2 | STOP |
886 | 1 | pfleura2 | END IF |
887 | 1 | pfleura2 | END IF |
888 | 1 | pfleura2 | END IF |
889 | 1 | pfleura2 | Call AddLigne(Izm,IdAt0,ind_zmat(Idx,1),IAtv,IAtdh, & |
890 | 1 | pfleura2 | ind_zmat,val_zmat,x,y,z) |
891 | 1 | pfleura2 | |
892 | 1 | pfleura2 | |
893 | 1 | pfleura2 | IndFin=1 |
894 | 1 | pfleura2 | IAtd=IdAt0 |
895 | 1 | pfleura2 | n1=IAtdh |
896 | 1 | pfleura2 | IAtdh=IAtv |
897 | 1 | pfleura2 | IAtv=ind_zmat(Idx,1) |
898 | 1 | pfleura2 | ! On ajoute les atomes lies a cet atome dans la liste a faire |
899 | 1 | pfleura2 | Do iaf=1,Lies_CF(IdAt0,0) |
900 | 1 | pfleura2 | IatI=Lies_CF(IdAt0,Iaf) |
901 | 1 | pfleura2 | ! We check that this atom is not the one that is the closest to |
902 | 1 | pfleura2 | ! the center atom |
903 | 1 | pfleura2 | if (IAtv.Ne.IAtI) THEN |
904 | 1 | pfleura2 | IF (debug) WRITE(*,*) 'Adding atom',IAtI, & |
905 | 1 | pfleura2 | 'to CAFaire in pos',iaf |
906 | 1 | pfleura2 | CAfaire(IndFin)=IAtI |
907 | 1 | pfleura2 | IndFin=IndFin+1 |
908 | 1 | pfleura2 | ! On les ajoute aussi dans la zmat |
909 | 1 | pfleura2 | If (.NOT.DejaFait(IatI)) THEN |
910 | 1 | pfleura2 | izm=izm+1 |
911 | 1 | pfleura2 | ! WRITE(*,*) "Outchili IAtv, IAtdh,IAtI", IAtv, IAtdh,IAtI |
912 | 1 | pfleura2 | CALL vecteur(IAtI,IAtD,x,y,z,vx1,vy1,vz1,norm1) |
913 | 1 | pfleura2 | CALL vecteur(IAtI,IAtv,x,y,z,vx2,vy2,vz2,norm2) |
914 | 1 | pfleura2 | val=angle(vx1,vy1,vz1,norm1, vx2,vy2,vz2,norm2) |
915 | 1 | pfleura2 | if (debug) WRITE(*,*) 'Angle val:2',IAtI,IAtD,IAtv,val |
916 | 1 | pfleura2 | if ((abs(val).LE.10.).OR.(abs(180.-abs(val)).le.10.)) & |
917 | 1 | pfleura2 | THEN |
918 | 1 | pfleura2 | Call AddLigne(Izm,IAtI,IAtv,IAtdh,n1, & |
919 | 1 | pfleura2 | ind_zmat,val_zmat,x,y,z) |
920 | 1 | pfleura2 | ELSE |
921 | 1 | pfleura2 | |
922 | 1 | pfleura2 | Call AddLigne(Izm,IAtI,IAtD,IAtv,IAtdh, & |
923 | 1 | pfleura2 | ind_zmat,val_zmat,x,y,z) |
924 | 1 | pfleura2 | END IF |
925 | 1 | pfleura2 | END IF |
926 | 1 | pfleura2 | END IF |
927 | 1 | pfleura2 | END DO |
928 | 1 | pfleura2 | CAfaire(IndFin)=0 |
929 | 1 | pfleura2 | |
930 | 1 | pfleura2 | ! On traite le reste de ce fragment !! |
931 | 1 | pfleura2 | IndAFaire=1 |
932 | 1 | pfleura2 | WRITE(IOOUT,*) CaFaire |
933 | 1 | pfleura2 | Do WHILE (Cafaire(IndAFaire).ne.0) |
934 | 1 | pfleura2 | IAt0=Cafaire(IndAfaire) |
935 | 1 | pfleura2 | if (Lies_CF(IAt0,0).ge.1) THEN |
936 | 1 | pfleura2 | ! IAt0 est l'atome pour lequel on construit la couche suivante |
937 | 1 | pfleura2 | ! le premier atome lie est particulier car il definit l'orientation |
938 | 1 | pfleura2 | ! de ce fragment |
939 | 1 | pfleura2 | Itmp=1 |
940 | 1 | pfleura2 | IAti=Lies_CF(IAt0,Itmp) |
941 | 1 | pfleura2 | DO WHILE (DejaFait(IAti).AND.(Itmp.Le.Lies_CF(IAt0,0))) |
942 | 1 | pfleura2 | Itmp=Itmp+1 |
943 | 1 | pfleura2 | IAti=Lies_CF(IAt0,ITmp) |
944 | 1 | pfleura2 | END DO |
945 | 1 | pfleura2 | If (.NOT.DejaFait(Iati)) THEN |
946 | 1 | pfleura2 | IF (debug) WRITE(IOOUT,*) 'IAti:',IAti |
947 | 1 | pfleura2 | IAtd=IAt0 |
948 | 1 | pfleura2 | IF (debug) WRITE(IOOUT,*) 'IAtd:',IAtd |
949 | 1 | pfleura2 | IAtv=Lies_CP(IAt0,1) |
950 | 1 | pfleura2 | IF (debug) WRITE(IOOUT,*) 'IAtv:',IAtv |
951 | 1 | pfleura2 | IIAtdh=1 |
952 | 1 | pfleura2 | IAtdh=Lies_CF(IAtv,IIatdh) |
953 | 1 | pfleura2 | DO WHILE (Iatdh.eq.IAt0) |
954 | 1 | pfleura2 | IIatdh=IIatdh+1 |
955 | 1 | pfleura2 | IAtdh=Lies_CF(IAtv,IIatdh) |
956 | 1 | pfleura2 | END DO |
957 | 1 | pfleura2 | IF (IAtdh.eq.0) IAtdh=Lies_CP(IAtv,1) |
958 | 1 | pfleura2 | IF (debug) WRITE(IOOUT,*) 'IAtdh:',IAtdh |
959 | 1 | pfleura2 | Izm=Izm+1 |
960 | 1 | pfleura2 | Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh, & |
961 | 1 | pfleura2 | ind_zmat,val_zmat,x,y,z) |
962 | 1 | pfleura2 | ! Le traitement des autres est plus facile |
963 | 1 | pfleura2 | IAtdh=Lies_CF(IAt0,ITmp) |
964 | 1 | pfleura2 | DO IAta=ITmp+1,Lies_CF(IAt0,0) |
965 | 1 | pfleura2 | IAtI=Lies_CF(IAt0,IAta) |
966 | 1 | pfleura2 | If (.NOT.DejaFait(IAtI)) THEN |
967 | 1 | pfleura2 | Izm=Izm+1 |
968 | 1 | pfleura2 | Call AddLigne(Izm,IAti,IAtd,IAtv,IAtdh, & |
969 | 1 | pfleura2 | ind_zmat,val_zmat,x,y,z) |
970 | 1 | pfleura2 | END IF |
971 | 1 | pfleura2 | END DO |
972 | 1 | pfleura2 | END IF |
973 | 1 | pfleura2 | |
974 | 1 | pfleura2 | ! On ajoute les atomes lies a cet atome dans la liste a faire |
975 | 1 | pfleura2 | Do iaf=1,Lies_CF(IAt0,0) |
976 | 1 | pfleura2 | CAfaire(IndFin)=Lies_CF(IAt0,Iaf) |
977 | 1 | pfleura2 | IndFin=IndFin+1 |
978 | 1 | pfleura2 | END DO |
979 | 1 | pfleura2 | CAfaire(IndFin)=0 |
980 | 1 | pfleura2 | END IF |
981 | 1 | pfleura2 | IndAFaire=IndAFaire+1 |
982 | 1 | pfleura2 | END DO |
983 | 2 | pfleura2 | !12345 CONTINUE |
984 | 1 | pfleura2 | END DO |
985 | 1 | pfleura2 | |
986 | 1 | pfleura2 | if (debug) THEN |
987 | 1 | pfleura2 | WRITE(*,*) 'ind_zmat' |
988 | 1 | pfleura2 | DO I=1,na |
989 | 1 | pfleura2 | WRITE(*,'(1X,5I5)') (ind_zmat(i,j),j=1,5) |
990 | 1 | pfleura2 | END DO |
991 | 1 | pfleura2 | END IF |
992 | 1 | pfleura2 | |
993 | 1 | pfleura2 | |
994 | 1 | pfleura2 | |
995 | 1 | pfleura2 | if (debug) WRITE(*,*) "====================== Exiting Calc_zmat ===================" |
996 | 1 | pfleura2 | |
997 | 1 | pfleura2 | END SUBROUTINE Calc_Zmat |