root / utils / Xyz2Path.f90 @ 10
Historique | Voir | Annoter | Télécharger (29 ko)
1 | 1 | pfleura2 | program Xyz2Path |
---|---|---|---|
2 | 1 | pfleura2 | ! This programs reads a XYZ file and converts it into distances, |
3 | 1 | pfleura2 | ! valence angle and dihedral angles. |
4 | 1 | pfleura2 | ! It prints them as a function of the irc distance... |
5 | 1 | pfleura2 | !----------------------------------------------- |
6 | 1 | pfleura2 | ! Input: name of the XYZ File |
7 | 1 | pfleura2 | ! it also needs a file call list which has the following structure: |
8 | 1 | pfleura2 | ! one line contains the type of the value you want to follow, it can be |
9 | 1 | pfleura2 | ! b for a Bond distance |
10 | 1 | pfleura2 | ! a for an angle |
11 | 1 | pfleura2 | ! d for a dihedral |
12 | 1 | pfleura2 | ! this descriptor is followed by the number of the atoms involved ! |
13 | 1 | pfleura2 | ! a typical file can be: |
14 | 1 | pfleura2 | ! b 1 2 |
15 | 1 | pfleura2 | ! b 2 3 |
16 | 1 | pfleura2 | ! a 1 2 3 |
17 | 1 | pfleura2 | !---------------------------------------------- |
18 | 1 | pfleura2 | ! Ouput: A files call Scan.dat |
19 | 1 | pfleura2 | ! wich contains in the first lines the input file (as a reminder) |
20 | 1 | pfleura2 | ! and then for each step the wanted values |
21 | 1 | pfleura2 | !------------------------------------------------ |
22 | 1 | pfleura2 | ! Second version also reads the energy (as to be written after E= on |
23 | 1 | pfleura2 | ! the comment line) |
24 | 1 | pfleura2 | !------------------------------------------------ |
25 | 1 | pfleura2 | ! Third version contains a new command: c for Center of Mass |
26 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
27 | 1 | pfleura2 | ! v 3.1 the c command now creates the center of mass... and allows |
28 | 1 | pfleura2 | ! people to do whatever they want with it... |
29 | 1 | pfleura2 | ! Syntax: c NbAt ListAt |
30 | 1 | pfleura2 | |
31 | 1 | pfleura2 | |
32 | 1 | pfleura2 | IMPLICIT NONE |
33 | 1 | pfleura2 | |
34 | 1 | pfleura2 | INCLUDE "Xyz2Path.param" |
35 | 1 | pfleura2 | |
36 | 1 | pfleura2 | character(40) :: f1 |
37 | 1 | pfleura2 | REAL(8) :: geos(3,maxnat), geos1(3,maxnat) |
38 | 1 | pfleura2 | character(33) :: fmt |
39 | 1 | pfleura2 | character(3) :: atoms(maxnat) |
40 | 1 | pfleura2 | character(5) :: Type |
41 | 1 | pfleura2 | Character(120) :: line |
42 | 1 | pfleura2 | INTEGER(4) :: NbPrint |
43 | 1 | pfleura2 | REAL(8) :: AU2PS,Pi |
44 | 1 | pfleura2 | REAL(8) :: Mass(MaxNat), Ener, Conv, Ds, s |
45 | 1 | pfleura2 | INTEGER(4) :: At1,At2,At3,At4,IOOUT,Iat |
46 | 1 | pfleura2 | INTEGER(4) :: IArg, I, NNN, Ng, J |
47 | 1 | pfleura2 | |
48 | 1 | pfleura2 | INTEGER(4) :: Nat,NbDist, NbAngle, NbDie,NbCOM |
49 | 1 | pfleura2 | INTEGER(4) :: At1B(MaxNat),At2B(MaxNat) |
50 | 1 | pfleura2 | INTEGER(4) :: At1A(MaxNat),At2A(MaxNat),At3A(MaxNat) |
51 | 1 | pfleura2 | INTEGER(4) :: At1D(MaxNat),At2D(MaxNat),At3D(MaxNat),At4D(MaxNat) |
52 | 1 | pfleura2 | INTEGER(4) :: AtCom(0:MaxNat,MaxNat) |
53 | 1 | pfleura2 | REAL(8) :: VB(MaxNat),VA(MaxNat),VD(MaxNat),VCOM(MaxNat) |
54 | 1 | pfleura2 | |
55 | 1 | pfleura2 | REAL(8) :: MRot(3,3), Rmsd |
56 | 8 | pfleura2 | LOGICAL FExist,FRot,FAlign,Debug,DebugRMSD |
57 | 1 | pfleura2 | |
58 | 1 | pfleura2 | INTEGER(4) :: ConvertNumAt |
59 | 1 | pfleura2 | external ConvertNumAt |
60 | 1 | pfleura2 | |
61 | 1 | pfleura2 | COMMON /Indices/Nat,NbDist,NbAngle,NbDie,NbCom, At1B,At2B, & |
62 | 1 | pfleura2 | At1A,At2A,At3A,At1D,At2D,At3D,At4D,AtCom |
63 | 1 | pfleura2 | COMMON /Values/VB,VA,VD,VCom |
64 | 1 | pfleura2 | COMMON /Const/AU2ps,Pi |
65 | 1 | pfleura2 | |
66 | 1 | pfleura2 | |
67 | 1 | pfleura2 | |
68 | 1 | pfleura2 | REAL(8) :: MassAt(0:86)=(/0.0D0,1.0078D0, 4.0026D0, & |
69 | 1 | pfleura2 | 7.0160D0, 9.0122D0,11.0093D0, & |
70 | 1 | pfleura2 | 12.0000D0,14.0031D0,15.9949D0,18.9984D0,19.9924D0, & |
71 | 1 | pfleura2 | 22.9898D0,23.9850D0,26.9815D0, & |
72 | 1 | pfleura2 | 27.9769D0,30.9738D0,31.9721D0,34.9688D0,39.9624D0, & |
73 | 1 | pfleura2 | 39.0983D0,40.08D0, & |
74 | 1 | pfleura2 | 44.9559D0, 47.88D0, 50.9415D0, 51.996D0, 54.9380D0, & |
75 | 1 | pfleura2 | 55.847D0, 58.9332D0, 58.69D0, 63.546D0, 65.39D0, & |
76 | 1 | pfleura2 | 69.72D0,72.59D0,74.9216D0,78.96D0,79.904D0,83.80D0, & |
77 | 1 | pfleura2 | 85.4678D0,87.62D0,88.9059D0,91.224D0,92.9064D0, & |
78 | 1 | pfleura2 | 95.94D0,98D0,101.07D0,102.906D0,106.42D0,107.868D0,112.41D0, & |
79 | 1 | pfleura2 | 114.82D0,118.71D0,121.75D0,127.60D0,126.905D0,131.29D0, & |
80 | 1 | pfleura2 | ! 6 'CS','BA', |
81 | 1 | pfleura2 | 132.905D0,137.34D0, & |
82 | 1 | pfleura2 | ! 6 'LA', |
83 | 1 | pfleura2 | ! 'CE','PR','ND','PM','SM','EU','GD', |
84 | 1 | pfleura2 | ! 'TB','DY','HO', 'ER','TM','YB','LU', |
85 | 1 | pfleura2 | 138.91D0, & |
86 | 1 | pfleura2 | 140.12D0, 130.91D0, 144.24D0,147.D0,150.35D0, 151.96D0,157.25D0, & |
87 | 1 | pfleura2 | 158.924D0, 162.50D0, 164.93D0, 167.26D0,168.93D0,173.04D0,174.97D0, & |
88 | 1 | pfleura2 | ! 6 'HF','TA',' W','RE','OS','IR','PT', |
89 | 1 | pfleura2 | ! 'AU','HG', |
90 | 1 | pfleura2 | ! 6 'TL','PB','BI','PO','AT','RN'/ |
91 | 1 | pfleura2 | 178.49D0, 180.95D0, 183.85D0, 186.2D0, 190.2D0, 192.2D0, 195.09D0, & |
92 | 1 | pfleura2 | 196.97D0, 200.59D0, & |
93 | 1 | pfleura2 | 204.37D0, 207.19D0,208.98D0,210.D0,210.D0,222.D0 /) |
94 | 1 | pfleura2 | |
95 | 8 | pfleura2 | Debug=.FALSE. |
96 | 8 | pfleura2 | DebugRMSD=.FALSE. |
97 | 1 | pfleura2 | |
98 | 1 | pfleura2 | AU2PS=1./41341.37 |
99 | 1 | pfleura2 | NbPrint=100 |
100 | 1 | pfleura2 | Pi=dacos(-1.d0) |
101 | 1 | pfleura2 | IOOUT=13 |
102 | 1 | pfleura2 | Conv=1. |
103 | 1 | pfleura2 | FRot=.TRUE. |
104 | 1 | pfleura2 | FAlign=.TRUE. |
105 | 1 | pfleura2 | NbDist=0 |
106 | 1 | pfleura2 | NbAngle=0 |
107 | 1 | pfleura2 | NbDie=0 |
108 | 1 | pfleura2 | |
109 | 1 | pfleura2 | iarg=command_argument_count() |
110 | 1 | pfleura2 | if (iarg.lt.1) then |
111 | 1 | pfleura2 | write(*,*) 'XYZ filename:' |
112 | 1 | pfleura2 | read(*,'(a)') f1 |
113 | 1 | pfleura2 | else |
114 | 1 | pfleura2 | call getarg(1,f1) |
115 | 1 | pfleura2 | endif |
116 | 1 | pfleura2 | |
117 | 1 | pfleura2 | open(13,file='Scan.dat') |
118 | 1 | pfleura2 | |
119 | 1 | pfleura2 | INQUIRE(File='list',Exist=FExist) |
120 | 1 | pfleura2 | if (.NOT.FExist) THEN |
121 | 1 | pfleura2 | WRITE(*,*) "No file 'list', just printing Energy" |
122 | 1 | pfleura2 | END IF |
123 | 1 | pfleura2 | |
124 | 1 | pfleura2 | open(11,file=f1) |
125 | 1 | pfleura2 | call rtraitem(11,nnn,ener,geos1,atoms) |
126 | 1 | pfleura2 | close(11) |
127 | 1 | pfleura2 | |
128 | 1 | pfleura2 | DO I=1,nnn |
129 | 1 | pfleura2 | Iat=ConvertNumAt(atoms(I)) |
130 | 1 | pfleura2 | Mass(I)=MassAt(Iat) |
131 | 1 | pfleura2 | ! write(*,*) I,Atoms(I),Mass(I),geos1(:,I) |
132 | 1 | pfleura2 | END DO |
133 | 1 | pfleura2 | |
134 | 1 | pfleura2 | Nat=nnn |
135 | 1 | pfleura2 | |
136 | 1 | pfleura2 | if (FExist) THEN |
137 | 1 | pfleura2 | open(14,file='list') |
138 | 1 | pfleura2 | Type="d" |
139 | 1 | pfleura2 | DO WHILE (Type.ne."E") |
140 | 1 | pfleura2 | CALL READLINE(14,Type,Line) |
141 | 1 | pfleura2 | ! WRITE(*,*) Line,Type |
142 | 1 | pfleura2 | if (Type.eq."b") THEN |
143 | 1 | pfleura2 | NbDist=NbDist+1 |
144 | 1 | pfleura2 | READ(Line,*) At1,At2 |
145 | 1 | pfleura2 | At1B(NbDist)=At1 |
146 | 1 | pfleura2 | At2B(NbDist)=At2 |
147 | 1 | pfleura2 | WRITE(13,'("# b ",2(A3,I3))') Atoms(At1),At1,Atoms(At2),At2 |
148 | 1 | pfleura2 | WRITE(*,'("# b ",2(A3,I3))') Atoms(At1),At1,Atoms(At2),At2 |
149 | 1 | pfleura2 | END IF |
150 | 1 | pfleura2 | if (Type.eq."a") THEN |
151 | 1 | pfleura2 | NbAngle=NbAngle+1 |
152 | 1 | pfleura2 | READ(Line,*) At1,At2,At3 |
153 | 1 | pfleura2 | At1A(NbAngle)=At1 |
154 | 1 | pfleura2 | At2A(NbAngle)=At2 |
155 | 1 | pfleura2 | At3A(NbAngle)=At3 |
156 | 1 | pfleura2 | WRITE(13,'("# a ",3(A3,I3))') Atoms(At1),At1,Atoms(At2), & |
157 | 1 | pfleura2 | At2, Atoms(At3),At3 |
158 | 1 | pfleura2 | WRITE(*,'("# a ",3(A3,I3))') Atoms(At1),At1,Atoms(At2), & |
159 | 1 | pfleura2 | At2, Atoms(At3),At3 |
160 | 1 | pfleura2 | END IF |
161 | 1 | pfleura2 | if (Type.eq."d") THEN |
162 | 1 | pfleura2 | NbDie=NbDie+1 |
163 | 1 | pfleura2 | READ(Line,*) At1,At2,At3,At4 |
164 | 1 | pfleura2 | At1D(NbDie)=At1 |
165 | 1 | pfleura2 | At2D(NbDie)=At2 |
166 | 1 | pfleura2 | At3D(NbDie)=At3 |
167 | 1 | pfleura2 | At4D(NbDie)=At4 |
168 | 1 | pfleura2 | WRITE(13,'("# d ",4(A3,I3))') Atoms(At1),At1,Atoms(At2),At2, & |
169 | 1 | pfleura2 | Atoms(At3),At3,Atoms(At4),At4 |
170 | 1 | pfleura2 | WRITE(*,'("# d ",4(A3,I3))') Atoms(At1),At1,Atoms(At2),At2, & |
171 | 1 | pfleura2 | Atoms(At3),At3,Atoms(At4),At4 |
172 | 1 | pfleura2 | |
173 | 1 | pfleura2 | END IF |
174 | 1 | pfleura2 | if (Type.eq."c") THEN |
175 | 1 | pfleura2 | NbCOM=NbCOM+1 |
176 | 1 | pfleura2 | READ(Line,*) At1,(AtCom(j,NbCOM),j=1,At1) |
177 | 1 | pfleura2 | AtCom(0,NbCOM)=At1 |
178 | 1 | pfleura2 | Atoms(nat+NbCom)="G" |
179 | 1 | pfleura2 | WRITE(13,'("# c ",I4,20(A3,I3))') At1, & |
180 | 1 | pfleura2 | (Atoms(AtCom(i,NbCoM)),AtCom(i,NbCOM),i=1,At1) |
181 | 1 | pfleura2 | WRITE(*,'("# c ",I4,20(A3,I3))') At1, & |
182 | 1 | pfleura2 | (Atoms(AtCom(i,NbCoM)),AtCom(i,NbCOM),i=1,At1) |
183 | 1 | pfleura2 | END IF |
184 | 1 | pfleura2 | |
185 | 1 | pfleura2 | END DO |
186 | 1 | pfleura2 | END IF |
187 | 1 | pfleura2 | |
188 | 1 | pfleura2 | |
189 | 1 | pfleura2 | |
190 | 1 | pfleura2 | fmt='( (1X,F12.5),1X,F15.6)' |
191 | 1 | pfleura2 | write(fmt(2:4),'(i3)') NbDist+NbAngle+NbDie+1 |
192 | 1 | pfleura2 | ! write(*,*) nat3 |
193 | 1 | pfleura2 | ! write(*,*) 'fmt:',fmt |
194 | 1 | pfleura2 | |
195 | 1 | pfleura2 | ng=1 |
196 | 1 | pfleura2 | |
197 | 1 | pfleura2 | s=0. |
198 | 1 | pfleura2 | |
199 | 1 | pfleura2 | open(11,file=f1) |
200 | 1 | pfleura2 | |
201 | 1 | pfleura2 | 10 call rtraitem(11,nnn,ener,geos,atoms) |
202 | 1 | pfleura2 | ! WRITE(*,*) nnn |
203 | 1 | pfleura2 | if (nnn.gt.0) then |
204 | 1 | pfleura2 | |
205 | 8 | pfleura2 | if (debug) THEN |
206 | 8 | pfleura2 | WRITE(*,*) "Debug ref geom: geos1" |
207 | 8 | pfleura2 | DO I=1,nnn |
208 | 8 | pfleura2 | WRITE(*,'(1X,I5,1X,F5.1,3(1X,F12.6))') I,mass(I),geos1(:,I) |
209 | 8 | pfleura2 | END DO |
210 | 8 | pfleura2 | END IF |
211 | 8 | pfleura2 | |
212 | 8 | pfleura2 | call CalcRmsd(nnn, geos1, geos,MRot,rmsd,FRot,FAlign,debugRMSD) |
213 | 8 | pfleura2 | |
214 | 8 | pfleura2 | if (debug) THEN |
215 | 8 | pfleura2 | WRITE(*,*) "Debug Geos aligned on geos1,rmsd=",rmsd |
216 | 8 | pfleura2 | DO I=1,nnn |
217 | 8 | pfleura2 | WRITE(*,'(1X,I5,1X,F5.1,3(1X,F12.6))') I,mass(I),geos(:,I) |
218 | 8 | pfleura2 | END DO |
219 | 8 | pfleura2 | END IF |
220 | 8 | pfleura2 | |
221 | 1 | pfleura2 | ds=0. |
222 | 1 | pfleura2 | DO I=1,nnn |
223 | 1 | pfleura2 | DO J=1,3 |
224 | 1 | pfleura2 | ds=ds+mass(I)*(geos(J,I)-geos1(J,I))**2 |
225 | 1 | pfleura2 | geos1(J,I)=Geos(J,I) |
226 | 1 | pfleura2 | END DO |
227 | 8 | pfleura2 | if (debug) write(*,*) I,ds |
228 | 1 | pfleura2 | END DO |
229 | 8 | pfleura2 | if (debug) WRITE(*,*) "Debug, ds",sqrt(ds) |
230 | 1 | pfleura2 | s=s+sqrt(ds) |
231 | 1 | pfleura2 | |
232 | 1 | pfleura2 | ! We convert coordinates in a0 into Angstroem |
233 | 1 | pfleura2 | ! write(*,*) "Analyse !" |
234 | 1 | pfleura2 | if (FExist) THEN |
235 | 1 | pfleura2 | Call Analyse(geos) |
236 | 1 | pfleura2 | |
237 | 1 | pfleura2 | write(IOOUT,fmt) s,(VB(j)/Conv,j=1,NbDist), & |
238 | 1 | pfleura2 | (VA(j),j=1,NbAngle), & |
239 | 1 | pfleura2 | (VD(j),j=1,NbDie),ener |
240 | 1 | pfleura2 | write(*,fmt) s,(VB(j)/Conv,j=1,NbDist), & |
241 | 1 | pfleura2 | (VA(j),j=1,NbAngle), & |
242 | 1 | pfleura2 | (VD(j),j=1,NbDie),ener |
243 | 1 | pfleura2 | ELSE |
244 | 1 | pfleura2 | write(IOOUT,fmt) s,ener |
245 | 1 | pfleura2 | write(*,fmt) s,ener |
246 | 1 | pfleura2 | END IF |
247 | 1 | pfleura2 | ng=ng+1 |
248 | 1 | pfleura2 | goto 10 |
249 | 1 | pfleura2 | endif |
250 | 1 | pfleura2 | WRITE(*,*) 'Found ',ng-1,' geometries' |
251 | 1 | pfleura2 | close(11) |
252 | 1 | pfleura2 | end |
253 | 1 | pfleura2 | |
254 | 1 | pfleura2 | !-------------------------------------------------------------- |
255 | 1 | pfleura2 | subroutine rtraitem(ifil,nnn,E,tab,atoms) |
256 | 1 | pfleura2 | ! implicit REAL(8) :: (a-h,o-z) |
257 | 1 | pfleura2 | IMPLICIT NONE |
258 | 1 | pfleura2 | |
259 | 1 | pfleura2 | character(120) :: line |
260 | 1 | pfleura2 | character(3) :: Atoms(*) |
261 | 1 | pfleura2 | INTEGER(4) :: nnn, IFil, Idx, I, J |
262 | 1 | pfleura2 | REAL(8) :: Tab(3,*), E |
263 | 1 | pfleura2 | |
264 | 1 | pfleura2 | |
265 | 1 | pfleura2 | read(ifil,*,err=99,end=99) nnn |
266 | 1 | pfleura2 | read(ifil,'(A)') line |
267 | 1 | pfleura2 | idx=index(line,'E') |
268 | 1 | pfleura2 | ! WRITE(*,*) 'idx,line',idx,line |
269 | 1 | pfleura2 | if (idx/=0) THEN |
270 | 1 | pfleura2 | line=line(idx+2:) |
271 | 1 | pfleura2 | idx=index(line,"=") |
272 | 1 | pfleura2 | if (idx/=0) line=line(idx+1:) |
273 | 1 | pfleura2 | idx=index(line,":") |
274 | 1 | pfleura2 | if (idx/=0) line=line(idx+1:) |
275 | 1 | pfleura2 | read(line,*) E |
276 | 1 | pfleura2 | ELSE |
277 | 1 | pfleura2 | E=0. |
278 | 1 | pfleura2 | END IF |
279 | 1 | pfleura2 | |
280 | 1 | pfleura2 | ! write(*,*) 'coucou',line |
281 | 1 | pfleura2 | do i=1,nnn |
282 | 1 | pfleura2 | read(ifil,'(A)',err=99,end=99) Line |
283 | 1 | pfleura2 | do while (line(1:1)==' ') |
284 | 1 | pfleura2 | line=line(2:) |
285 | 1 | pfleura2 | end do |
286 | 1 | pfleura2 | atoms(i)=line(1:3) |
287 | 1 | pfleura2 | ! write(*,*) 'coucou atoms',atoms(i) |
288 | 1 | pfleura2 | do while (line(1:1).ne.' ') |
289 | 1 | pfleura2 | line=line(2:) |
290 | 1 | pfleura2 | end do |
291 | 1 | pfleura2 | ! WRITE(*,*) 'coucou2:',i,line |
292 | 1 | pfleura2 | read(line,*) (tab(j,i),j=1,3) |
293 | 1 | pfleura2 | end do |
294 | 1 | pfleura2 | ! WRITE(*,*) 'coucou:',nnn,tab(1,1) |
295 | 1 | pfleura2 | return |
296 | 1 | pfleura2 | 99 nnn=0 |
297 | 1 | pfleura2 | ! WRITE(*,*) 'Erreur lecture',ifil,nnn |
298 | 1 | pfleura2 | return |
299 | 1 | pfleura2 | end |
300 | 1 | pfleura2 | |
301 | 1 | pfleura2 | !-------------------------------------------------------------- |
302 | 1 | pfleura2 | |
303 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
304 | 1 | pfleura2 | ! READLINE |
305 | 1 | pfleura2 | ! This subroutine reads a line for a file, and converts |
306 | 1 | pfleura2 | ! the first field into a character variable, and the rest into 4 integers |
307 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
308 | 1 | pfleura2 | |
309 | 1 | pfleura2 | SUBROUTINE READLINE(IOIN,Type,Line) |
310 | 1 | pfleura2 | |
311 | 1 | pfleura2 | IMPLICIT NONE |
312 | 1 | pfleura2 | CHARACTER(5) :: Type |
313 | 1 | pfleura2 | CHARACTER(120) :: LINE |
314 | 1 | pfleura2 | INTEGER(4) :: i,IOIN |
315 | 1 | pfleura2 | READ(IOIN,'(A120)',ERR=999,END=999) LINE |
316 | 1 | pfleura2 | ! WRITE(*,*) Line |
317 | 1 | pfleura2 | DO WHILE (LINE(1:1).eq.' ') |
318 | 1 | pfleura2 | LINE=LINE(2:) |
319 | 1 | pfleura2 | END DO |
320 | 1 | pfleura2 | |
321 | 1 | pfleura2 | i=1 |
322 | 1 | pfleura2 | DO WHILE (LINE(i:i).ne.' ') |
323 | 1 | pfleura2 | i=i+1 |
324 | 1 | pfleura2 | END DO |
325 | 1 | pfleura2 | |
326 | 1 | pfleura2 | if (i.ge.6) THEN |
327 | 1 | pfleura2 | WRITE(*,*) 'Pb with READLINE:',LINE |
328 | 1 | pfleura2 | GOTO 999 |
329 | 1 | pfleura2 | END IF |
330 | 1 | pfleura2 | Type=LINE(1:i-1) |
331 | 1 | pfleura2 | LINE=LINE(i:120) // " 0 0 0 0" |
332 | 1 | pfleura2 | |
333 | 1 | pfleura2 | RETURN |
334 | 1 | pfleura2 | 999 Type="E" |
335 | 1 | pfleura2 | END |
336 | 1 | pfleura2 | |
337 | 1 | pfleura2 | |
338 | 1 | pfleura2 | |
339 | 1 | pfleura2 | SUBROUTINE Analyse(geos) |
340 | 1 | pfleura2 | |
341 | 1 | pfleura2 | IMPLICIT NONE |
342 | 1 | pfleura2 | INCLUDE "Xyz2Path.param" |
343 | 1 | pfleura2 | |
344 | 1 | pfleura2 | REAL(8) :: geos(3,maxnat) |
345 | 1 | pfleura2 | REAL(8) :: AU2PS,Pi |
346 | 1 | pfleura2 | INTEGER(4) :: i,j,k |
347 | 1 | pfleura2 | REAL(8) :: V1x,V1y,V1z,V2x,V2y,V2z,V3x,V3y,V3z |
348 | 1 | pfleura2 | REAL(8) :: d1,d2,ca,sa |
349 | 1 | pfleura2 | REAL(8) :: V4x,v4y,v4z,v5x,v5y,v5z |
350 | 1 | pfleura2 | REAL(8) :: COG(3) |
351 | 1 | pfleura2 | LOGICAL :: Debug=.FALSE. |
352 | 1 | pfleura2 | INTEGER(4) :: Nat,NbDist, NbAngle, NbDie,NbCOM |
353 | 1 | pfleura2 | INTEGER(4) :: At1B(MaxNat),At2B(MaxNat) |
354 | 1 | pfleura2 | INTEGER(4) :: At1A(MaxNat),At2A(MaxNat),At3A(MaxNat) |
355 | 1 | pfleura2 | INTEGER(4) :: At1D(MaxNat),At2D(MaxNat),At3D(MaxNat),At4D(MaxNat) |
356 | 1 | pfleura2 | INTEGER(4) :: AtCom(0:MaxNat,MaxNat) |
357 | 1 | pfleura2 | REAL(8) :: VB(MaxNat),VA(MaxNat),VD(MaxNat),VCOM(MaxNat) |
358 | 1 | pfleura2 | |
359 | 1 | pfleura2 | COMMON /Indices/Nat,NbDist,NbAngle,NbDie,NbCom, & |
360 | 1 | pfleura2 | At1B,At2B,At1A,At2A,At3A,At1D,At2D,At3D,At4D,AtCom |
361 | 1 | pfleura2 | COMMON /Values/VB,VA,VD,VCom |
362 | 1 | pfleura2 | COMMON /Const/AU2ps,Pi |
363 | 1 | pfleura2 | |
364 | 1 | pfleura2 | if (debug) THEN |
365 | 1 | pfleura2 | DO I=1,Nat |
366 | 1 | pfleura2 | WRITE(*,'(1X,I3,3(1X,F15.6))') i,(geos(j,i),j=1,3) |
367 | 1 | pfleura2 | END DO |
368 | 1 | pfleura2 | END IF |
369 | 1 | pfleura2 | |
370 | 1 | pfleura2 | ! First, we create the Centre of Mass atoms |
371 | 1 | pfleura2 | DO i=1,NbCOM |
372 | 1 | pfleura2 | COG(1)=0. |
373 | 1 | pfleura2 | COG(2)=0. |
374 | 1 | pfleura2 | COG(3)=0. |
375 | 1 | pfleura2 | DO j=1,AtCOm(0,i) |
376 | 1 | pfleura2 | DO k=1,3 |
377 | 1 | pfleura2 | COG(k)=COG(k)+geos(k,AtCom(j,i)) |
378 | 1 | pfleura2 | END DO |
379 | 1 | pfleura2 | END DO |
380 | 1 | pfleura2 | DO k=1,3 |
381 | 1 | pfleura2 | COG(k)=COG(k)/AtCOM(0,i) |
382 | 1 | pfleura2 | geos(k,Nat+i)=COG(k) |
383 | 1 | pfleura2 | END DO |
384 | 1 | pfleura2 | END DO |
385 | 1 | pfleura2 | |
386 | 1 | pfleura2 | |
387 | 1 | pfleura2 | DO i=1,NbDist |
388 | 1 | pfleura2 | VB(i)=sqrt((geos(1,At1B(i))-geos(1,At2B(i)))**2+ & |
389 | 1 | pfleura2 | (geos(2,At1B(i))-geos(2,At2B(i)))**2+ & |
390 | 1 | pfleura2 | (geos(3,At1B(i))-geos(3,At2B(i)))**2) |
391 | 1 | pfleura2 | END DO |
392 | 1 | pfleura2 | DO i=1,NbAngle |
393 | 1 | pfleura2 | v1x=geos(1,At1A(i))-geos(1,At2A(i)) |
394 | 1 | pfleura2 | v1y=geos(2,At1A(i))-geos(2,At2A(i)) |
395 | 1 | pfleura2 | v1z=geos(3,At1A(i))-geos(3,At2A(i)) |
396 | 1 | pfleura2 | d1=sqrt(v1x**2+v1y**2+v1z**2) |
397 | 1 | pfleura2 | v2x=geos(1,At3A(i))-geos(1,At2A(i)) |
398 | 1 | pfleura2 | v2y=geos(2,At3A(i))-geos(2,At2A(i)) |
399 | 1 | pfleura2 | v2z=geos(3,At3A(i))-geos(3,At2A(i)) |
400 | 1 | pfleura2 | d2=sqrt(v2x**2+v2y**2+v2z**2) |
401 | 1 | pfleura2 | VA(i)=acos((v1x*v2x+v1y*v2y+v1z*v2z)/(d1*d2))*180./Pi |
402 | 1 | pfleura2 | END DO |
403 | 1 | pfleura2 | DO i=1,NbDie |
404 | 1 | pfleura2 | ! WRITE(*,*) At1D(i),At2D(i),At3D(i),At4D(i) |
405 | 1 | pfleura2 | ! WRITE(*,*) geos(1,At1D(i)),geos(2,At1D(i)),geos(3,At1D(i)) |
406 | 1 | pfleura2 | ! WRITE(*,*) geos(1,At2D(i)),geos(2,At2D(i)),geos(3,At2D(i)) |
407 | 1 | pfleura2 | v1x=geos(1,At1D(i))-geos(1,At2D(i)) |
408 | 1 | pfleura2 | v1y=geos(2,At1D(i))-geos(2,At2D(i)) |
409 | 1 | pfleura2 | v1z=geos(3,At1D(i))-geos(3,At2D(i)) |
410 | 1 | pfleura2 | v2x=geos(1,At3D(i))-geos(1,At2D(i)) |
411 | 1 | pfleura2 | v2y=geos(2,At3D(i))-geos(2,At2D(i)) |
412 | 1 | pfleura2 | v2z=geos(3,At3D(i))-geos(3,At2D(i)) |
413 | 1 | pfleura2 | v3x=geos(1,At4D(i))-geos(1,At3D(i)) |
414 | 1 | pfleura2 | v3y=geos(2,At4D(i))-geos(2,At3D(i)) |
415 | 1 | pfleura2 | v3z=geos(3,At4D(i))-geos(3,At3D(i)) |
416 | 1 | pfleura2 | |
417 | 1 | pfleura2 | v4x=v1y*v2z-v1z*v2y |
418 | 1 | pfleura2 | v4y=v1z*v2x-v1x*v2z |
419 | 1 | pfleura2 | v4z=v1x*v2y-v1y*v2x |
420 | 1 | pfleura2 | d1=sqrt(v4x**2+v4y**2+v4z**2) |
421 | 1 | pfleura2 | v5x=-v2y*v3z+v2z*v3y |
422 | 1 | pfleura2 | v5y=-v2z*v3x+v2x*v3z |
423 | 1 | pfleura2 | v5z=-v2x*v3y+v2y*v3x |
424 | 1 | pfleura2 | d2=sqrt(v5x**2+v5y**2+v5z**2) |
425 | 1 | pfleura2 | ca=(v4x*v5x+v4y*v5y+v4z*v5z)/(d1*d2) |
426 | 1 | pfleura2 | sa=v1x*v5x+v1y*v5y+v1z*v5z |
427 | 1 | pfleura2 | VD(i)=acos(ca)*180./Pi |
428 | 1 | pfleura2 | if (sa<0.) VD(i)=-VD(i) |
429 | 1 | pfleura2 | ! WRITE(*,*) "Dihe",v5x,v5y,v5z,v4x,v4y,v4z,d1,d2, |
430 | 1 | pfleura2 | ! &(v4x*v5x+v4y*v5y+v4z*v5z)/(d1*d2),pi |
431 | 1 | pfleura2 | !!!!!!!!! Another solution, more elegant ? |
432 | 1 | pfleura2 | ! norm2=sqrt(v2x**2+v2y**2+v2z**2) |
433 | 1 | pfleura2 | ! sa=(v4x*(v5y*v2z-v5z*v2y) |
434 | 1 | pfleura2 | ! * -v4y*(v5x*v2z-v5z*v2x) |
435 | 1 | pfleura2 | ! * +v4z*(v5x*v2y-v5y*v2x)) |
436 | 1 | pfleura2 | ! * /(d1*norm2*d2) |
437 | 1 | pfleura2 | ! angle_d=datan2(sa,ca)*180./Pi |
438 | 1 | pfleura2 | ! WRITE(*,*) sa,ca,angle_d,d1,d2,norm2 |
439 | 1 | pfleura2 | ! WRITE(*,*) VD(i),angle_d |
440 | 1 | pfleura2 | END DO |
441 | 1 | pfleura2 | |
442 | 1 | pfleura2 | END SUBROUTINE Analyse |
443 | 1 | pfleura2 | |
444 | 1 | pfleura2 | !C================================================================ |
445 | 1 | pfleura2 | !C Convertit un nom d'atome (2 lettres) en nombre de masse (entier) |
446 | 1 | pfleura2 | !C cette fonction a ete modifiee pour pouvoir convertir un nom |
447 | 1 | pfleura2 | !C d'atome avec un numero a la fin... |
448 | 1 | pfleura2 | !C================================================================ |
449 | 1 | pfleura2 | |
450 | 1 | pfleura2 | FUNCTION ConvertNumAt(ATOM) |
451 | 1 | pfleura2 | |
452 | 1 | pfleura2 | |
453 | 1 | pfleura2 | IMPLICIT NONE |
454 | 1 | pfleura2 | |
455 | 1 | pfleura2 | INTEGER(4) :: I,Long,ConvertNumAt,IC |
456 | 1 | pfleura2 | character(2) :: ATOM,L_Atom |
457 | 1 | pfleura2 | character(3) :: ATOME |
458 | 1 | pfleura2 | INTEGER(4), PARAMETER :: Max_Z=86 |
459 | 1 | pfleura2 | |
460 | 1 | pfleura2 | |
461 | 1 | pfleura2 | CHARACTER(2) :: Nom(0:max_Z)=(/ ' X',' H', 'HE', & |
462 | 1 | pfleura2 | 'LI','BE', ' B',' C',' N',' O',' F','NE', & |
463 | 1 | pfleura2 | 'NA','MG', 'AL','SI',' P',' S','CL','AR', & |
464 | 1 | pfleura2 | ' K','CA', & |
465 | 1 | pfleura2 | 'SC','TI',' V','CR','MN','FE','CO','NI','CU','ZN', & |
466 | 1 | pfleura2 | 'GA','GE','AS','SE','BR','KR', & |
467 | 1 | pfleura2 | 'RB','SR', & |
468 | 1 | pfleura2 | ' Y','ZR','NB','MO','TC','RU','RH','PD','AG','CD', & |
469 | 1 | pfleura2 | 'IN','SN','SB','TE',' I','XE', & |
470 | 1 | pfleura2 | 'CS','BA', & |
471 | 1 | pfleura2 | 'LA', & |
472 | 1 | pfleura2 | 'CE','PR','ND','PM','SM','EU','GD','TB','DY','HO', & |
473 | 1 | pfleura2 | 'ER','TM','YB','LU', & |
474 | 1 | pfleura2 | 'HF','TA',' W','RE','OS','IR','PT','AU','HG', & |
475 | 1 | pfleura2 | 'TL','PB','BI','PO','AT','RN'/) |
476 | 1 | pfleura2 | |
477 | 1 | pfleura2 | |
478 | 1 | pfleura2 | !C Verifie qu'il n'y a que des lettres et des espaces dans ATOM |
479 | 1 | pfleura2 | ! WRITE(*,*) 'DBG CNVNUMAT, ATOM:',ATOM |
480 | 1 | pfleura2 | |
481 | 1 | pfleura2 | L_atom=Atom |
482 | 1 | pfleura2 | IF (ATOM(1:1).LT.'A') L_ATOM(1:1)=' ' |
483 | 1 | pfleura2 | IC=Ichar(ATOM(1:1)) |
484 | 1 | pfleura2 | IF ((ic.le.123).AND.(ic.ge.97)) L_ATOM(1:1)=CHAr(IC-32) |
485 | 1 | pfleura2 | IF (ATOM(2:2).LT.'A') L_ATOM(2:2)=' ' |
486 | 1 | pfleura2 | IC=Ichar(ATOM(2:2)) |
487 | 1 | pfleura2 | IF ((ic.le.123).AND.(ic.ge.97)) L_ATOM(2:2)=CHAr(IC-32) |
488 | 1 | pfleura2 | !C Justifie le nom sur la droite (et non sur la gauche comme souvent...) |
489 | 1 | pfleura2 | Long=INDEX(L_ATOM,' ')-1 |
490 | 1 | pfleura2 | ATOME=' ' // L_ATOM |
491 | 1 | pfleura2 | IF (Long.EQ.1) L_ATOM=ATOME(1:2) |
492 | 1 | pfleura2 | ! WRITE(*,*) 'DBG CNVNUMAT, L_ATOM:',L_ATOM |
493 | 1 | pfleura2 | I=max_Z |
494 | 1 | pfleura2 | DO WHILE ((nom(I).NE.L_ATOM) .AND. (I.GT.0)) |
495 | 1 | pfleura2 | I=I-1 |
496 | 1 | pfleura2 | END DO |
497 | 1 | pfleura2 | ConvertNumAT=I |
498 | 1 | pfleura2 | END |
499 | 1 | pfleura2 | ! This subroutine calculates RMSD using quaternions. |
500 | 1 | pfleura2 | ! It is based on the F90 routine bu E. Coutsias |
501 | 1 | pfleura2 | ! http://www.math.unm.edu/~vageli/homepage.html |
502 | 1 | pfleura2 | ! I (PFL) have just translated it, and I have changed the diagonalization |
503 | 1 | pfleura2 | ! subroutine. |
504 | 1 | pfleura2 | ! I also made some changes to make it suitable for Cart package. |
505 | 1 | pfleura2 | !---------------------------------------------------------------------- |
506 | 1 | pfleura2 | !---------------------------------------------------------------------- |
507 | 1 | pfleura2 | ! Copyright (C) 2004, 2005 Chaok Seok, Evangelos Coutsias and Ken Dill |
508 | 1 | pfleura2 | ! UCSF, Univeristy of New Mexico, Seoul National University |
509 | 1 | pfleura2 | ! Witten by Chaok Seok and Evangelos Coutsias 2004. |
510 | 1 | pfleura2 | |
511 | 1 | pfleura2 | ! This library is free software; you can redistribute it and/or |
512 | 1 | pfleura2 | ! modify it under the terms of the GNU Lesser General Public |
513 | 1 | pfleura2 | ! License as published by the Free Software Foundation; either |
514 | 1 | pfleura2 | ! version 2.1 of the License, or (at your option) any later version. |
515 | 1 | pfleura2 | ! |
516 | 1 | pfleura2 | |
517 | 1 | pfleura2 | ! This library is distributed in the hope that it will be useful, |
518 | 1 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
519 | 1 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
520 | 1 | pfleura2 | ! Lesser General Public License for more details. |
521 | 1 | pfleura2 | ! |
522 | 1 | pfleura2 | |
523 | 1 | pfleura2 | ! You should have received a copy of the GNU Lesser General Public |
524 | 1 | pfleura2 | ! License along with this library; if not, write to the Free Software |
525 | 1 | pfleura2 | ! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA |
526 | 1 | pfleura2 | !---------------------------------------------------------------------------- |
527 | 1 | pfleura2 | |
528 | 1 | pfleura2 | subroutine CalcRmsd(na, geom,geom2,U,rmsd,FRot,FAlign,debug) |
529 | 1 | pfleura2 | !----------------------------------------------------------------------- |
530 | 1 | pfleura2 | ! This subroutine calculates the least square rmsd of two coordinate |
531 | 1 | pfleura2 | ! sets coord1(3,n) and coord2(3,n) using a method based on quaternion. |
532 | 1 | pfleura2 | ! It then calculate the rotation matrix U and the centers of coord, and uses |
533 | 1 | pfleura2 | ! them to align the two molecules. |
534 | 1 | pfleura2 | !----------------------------------------------------------------------- |
535 | 1 | pfleura2 | |
536 | 1 | pfleura2 | |
537 | 1 | pfleura2 | IMPLICIT NONE |
538 | 1 | pfleura2 | |
539 | 1 | pfleura2 | INCLUDE "Xyz2Path.param" |
540 | 1 | pfleura2 | |
541 | 1 | pfleura2 | INTEGER(4) :: IOIN, IOOUT, IOSCRN, IOPRNT, IOTAMP |
542 | 1 | pfleura2 | COMMON/IODEFS/IOIN,IOOUT,IOSCRN,IOPRNT,IOTAMP |
543 | 1 | pfleura2 | |
544 | 1 | pfleura2 | INTEGER(4) :: na |
545 | 1 | pfleura2 | REAL(8) :: geom(3,MaxNAt), Geom2(3,MaxNAt) |
546 | 1 | pfleura2 | REAL(8) :: U(3,3), rmsd |
547 | 1 | pfleura2 | LOGICAL FRot,FAlign,Debug |
548 | 1 | pfleura2 | |
549 | 1 | pfleura2 | REAL(8) :: Coord1(3,MaxNAt), Coord2(3,MaxNAt) |
550 | 1 | pfleura2 | REAL(8) :: xc1,yc1,zc1, xc2,yc2,zc2 |
551 | 1 | pfleura2 | |
552 | 1 | pfleura2 | |
553 | 1 | pfleura2 | INTEGER(4) :: i, j, ia |
554 | 1 | pfleura2 | REAL(8) :: x_norm, y_norm, lambda |
555 | 1 | pfleura2 | REAL(8) :: Rmatrix(3,3) |
556 | 1 | pfleura2 | REAL(8) :: S(4,4) |
557 | 1 | pfleura2 | REAL(8) :: EigVec(4,4), EigVal(4) |
558 | 1 | pfleura2 | |
559 | 1 | pfleura2 | |
560 | 1 | pfleura2 | |
561 | 1 | pfleura2 | ! calculate the barycenters, centroidal coordinates, and the norms |
562 | 1 | pfleura2 | x_norm = 0.0d0 |
563 | 1 | pfleura2 | y_norm = 0.0d0 |
564 | 1 | pfleura2 | xc1=0. |
565 | 1 | pfleura2 | yc1=0. |
566 | 1 | pfleura2 | zc1=0. |
567 | 1 | pfleura2 | xc2=0. |
568 | 1 | pfleura2 | yc2=0. |
569 | 1 | pfleura2 | zc2=0. |
570 | 1 | pfleura2 | do ia=1,na |
571 | 1 | pfleura2 | xc1=xc1+geom(1,ia) |
572 | 1 | pfleura2 | xc2=xc2+geom2(1,ia) |
573 | 1 | pfleura2 | yc1=yc1+geom(2,ia) |
574 | 1 | pfleura2 | yc2=yc2+geom2(2,ia) |
575 | 1 | pfleura2 | zc1=zc1+geom(3,ia) |
576 | 1 | pfleura2 | zc2=zc2+geom2(3,ia) |
577 | 1 | pfleura2 | ! if (debug) WRITE(*,'(A,I5,4(1X,F10.4))') 'ia...',ia,x(ia), |
578 | 1 | pfleura2 | ! & x2(ia),xc1,xc2 |
579 | 1 | pfleura2 | END DO |
580 | 1 | pfleura2 | xc1=xc1/dble(na) |
581 | 1 | pfleura2 | yc1=yc1/dble(na) |
582 | 1 | pfleura2 | zc1=zc1/dble(na) |
583 | 1 | pfleura2 | xc2=xc2/dble(na) |
584 | 1 | pfleura2 | yc2=yc2/dble(na) |
585 | 1 | pfleura2 | zc2=zc2/dble(na) |
586 | 1 | pfleura2 | |
587 | 1 | pfleura2 | IF (debug) WRITE(*,'(1X,A,3(1X,F10.4))') 'Center1',xc1,yc1,zc1 |
588 | 1 | pfleura2 | IF (debug) WRITE(*,'(1X,A,3(1X,F10.4))') 'Center2',xc2,yc2,zc2 |
589 | 1 | pfleura2 | do i=1,na |
590 | 1 | pfleura2 | Coord1(1,i)=geom(1,i)-xc1 |
591 | 1 | pfleura2 | Coord1(2,i)=geom(2,i)-yc1 |
592 | 1 | pfleura2 | Coord1(3,i)=geom(3,i)-zc1 |
593 | 1 | pfleura2 | Coord2(1,i)=geom2(1,i)-xc2 |
594 | 1 | pfleura2 | Coord2(2,i)=geom2(2,i)-yc2 |
595 | 1 | pfleura2 | Coord2(3,i)=geom2(3,i)-zc2 |
596 | 1 | pfleura2 | x_norm=x_norm+Coord1(1,i)**2+Coord1(2,i)**2+Coord1(3,i)**2 |
597 | 1 | pfleura2 | y_norm=y_norm+Coord2(1,i)**2+Coord2(2,i)**2+Coord2(3,i)**2 |
598 | 1 | pfleura2 | end do |
599 | 1 | pfleura2 | |
600 | 1 | pfleura2 | IF (debug) THEN |
601 | 1 | pfleura2 | WRITE(*,*) "R matrix" |
602 | 1 | pfleura2 | DO I=1,3 |
603 | 1 | pfleura2 | WRITE(*,*) (RMatrix(I,j),j=1,3) |
604 | 1 | pfleura2 | END DO |
605 | 1 | pfleura2 | END IF |
606 | 1 | pfleura2 | |
607 | 1 | pfleura2 | ! calculate the R matrix |
608 | 1 | pfleura2 | do i = 1, 3 |
609 | 1 | pfleura2 | do j = 1, 3 |
610 | 1 | pfleura2 | Rmatrix(i,j)=0. |
611 | 1 | pfleura2 | do ia=1,na |
612 | 1 | pfleura2 | Rmatrix(i,j) = Rmatrix(i,j)+Coord1(i,ia)*Coord2(j,ia) |
613 | 1 | pfleura2 | END DO |
614 | 1 | pfleura2 | end do |
615 | 1 | pfleura2 | end do |
616 | 1 | pfleura2 | |
617 | 1 | pfleura2 | IF (debug) THEN |
618 | 1 | pfleura2 | WRITE(*,*) "R matrix" |
619 | 1 | pfleura2 | DO I=1,3 |
620 | 1 | pfleura2 | WRITE(*,*) (RMatrix(I,j),j=1,3) |
621 | 1 | pfleura2 | END DO |
622 | 1 | pfleura2 | END IF |
623 | 1 | pfleura2 | |
624 | 1 | pfleura2 | |
625 | 1 | pfleura2 | ! S matrix |
626 | 1 | pfleura2 | S(1, 1) = Rmatrix(1, 1) + Rmatrix(2, 2) + Rmatrix(3, 3) |
627 | 1 | pfleura2 | S(2, 1) = Rmatrix(2, 3) - Rmatrix(3, 2) |
628 | 1 | pfleura2 | S(3, 1) = Rmatrix(3, 1) - Rmatrix(1, 3) |
629 | 1 | pfleura2 | S(4, 1) = Rmatrix(1, 2) - Rmatrix(2, 1) |
630 | 1 | pfleura2 | |
631 | 1 | pfleura2 | S(1, 2) = S(2, 1) |
632 | 1 | pfleura2 | S(2, 2) = Rmatrix(1, 1) - Rmatrix(2, 2) - Rmatrix(3, 3) |
633 | 1 | pfleura2 | S(3, 2) = Rmatrix(1, 2) + Rmatrix(2, 1) |
634 | 1 | pfleura2 | S(4, 2) = Rmatrix(1, 3) + Rmatrix(3, 1) |
635 | 1 | pfleura2 | |
636 | 1 | pfleura2 | S(1, 3) = S(3, 1) |
637 | 1 | pfleura2 | S(2, 3) = S(3, 2) |
638 | 1 | pfleura2 | S(3, 3) =-Rmatrix(1, 1) + Rmatrix(2, 2) - Rmatrix(3, 3) |
639 | 1 | pfleura2 | S(4, 3) = Rmatrix(2, 3) + Rmatrix(3, 2) |
640 | 1 | pfleura2 | |
641 | 1 | pfleura2 | S(1, 4) = S(4, 1) |
642 | 1 | pfleura2 | S(2, 4) = S(4, 2) |
643 | 1 | pfleura2 | S(3, 4) = S(4, 3) |
644 | 1 | pfleura2 | S(4, 4) =-Rmatrix(1, 1) - Rmatrix(2, 2) + Rmatrix(3, 3) |
645 | 1 | pfleura2 | |
646 | 1 | pfleura2 | |
647 | 1 | pfleura2 | ! PFL : I use my usual Jacobi diagonalisation |
648 | 1 | pfleura2 | ! Calculate eigenvalues and eigenvectors, and |
649 | 1 | pfleura2 | ! take the maximum eigenvalue lambda and the corresponding eigenvector q. |
650 | 1 | pfleura2 | |
651 | 1 | pfleura2 | IF (debug) THEN |
652 | 1 | pfleura2 | WRITE(*,*) "S matrix" |
653 | 1 | pfleura2 | DO I=1,4 |
654 | 1 | pfleura2 | WRITE(*,*) (S(I,j),j=1,4) |
655 | 1 | pfleura2 | END DO |
656 | 1 | pfleura2 | END IF |
657 | 1 | pfleura2 | |
658 | 1 | pfleura2 | Call Jacobi(S,4,EigVal,EigVec,4) |
659 | 1 | pfleura2 | |
660 | 1 | pfleura2 | Call Trie(4,EigVal,EigVec,4) |
661 | 1 | pfleura2 | |
662 | 1 | pfleura2 | Lambda=EigVal(4) |
663 | 1 | pfleura2 | |
664 | 1 | pfleura2 | ! RMS Deviation |
665 | 1 | pfleura2 | rmsd=sqrt(max(0.0d0,((x_norm+y_norm)-2.0d0*lambda))/dble(na)) |
666 | 1 | pfleura2 | |
667 | 1 | pfleura2 | if (FRot.OR.FAlign) Call rotation_matrix(EigVec(1,4),U) |
668 | 1 | pfleura2 | IF (FAlign) THEN |
669 | 1 | pfleura2 | DO I=1,na |
670 | 1 | pfleura2 | geom2(1,i)=Coord2(1,i)*U(1,1)+Coord2(2,i)*U(2,1)+Coord2(3,i)*U(3,1) +xc1 |
671 | 1 | pfleura2 | geom2(2,i)=Coord2(1,i)*U(1,2)+Coord2(2,i)*U(2,2)+Coord2(3,i)*U(3,2) +yc1 |
672 | 1 | pfleura2 | geom2(3,i)=Coord2(1,i)*U(1,3)+Coord2(2,i)*U(2,3)+Coord2(3,i)*U(3,3) +zc1 |
673 | 1 | pfleura2 | END DO |
674 | 1 | pfleura2 | END IF |
675 | 1 | pfleura2 | |
676 | 1 | pfleura2 | END |
677 | 1 | pfleura2 | |
678 | 1 | pfleura2 | |
679 | 1 | pfleura2 | !----------------------------------------------------------------------- |
680 | 1 | pfleura2 | subroutine rotation_matrix(q, U) |
681 | 1 | pfleura2 | !----------------------------------------------------------------------- |
682 | 1 | pfleura2 | ! This subroutine constructs rotation matrix U from quaternion q. |
683 | 1 | pfleura2 | !----------------------------------------------------------------------- |
684 | 1 | pfleura2 | ! This subroutine calculates RMSD using quaternions. |
685 | 1 | pfleura2 | ! It is based on the F90 routine bu E. Coutsias |
686 | 1 | pfleura2 | ! http://www.math.unm.edu/~vageli/homepage.html |
687 | 1 | pfleura2 | ! I (PFL) have just translated it, and I have changed the diagonalization |
688 | 1 | pfleura2 | ! subroutine. |
689 | 1 | pfleura2 | ! I also made some changes to make it suitable for Cart package. |
690 | 1 | pfleura2 | !---------------------------------------------------------------------- |
691 | 1 | pfleura2 | !---------------------------------------------------------------------- |
692 | 1 | pfleura2 | ! Copyright (C) 2004, 2005 Chaok Seok, Evangelos Coutsias and Ken Dill |
693 | 1 | pfleura2 | ! UCSF, Univeristy of New Mexico, Seoul National University |
694 | 1 | pfleura2 | ! Witten by Chaok Seok and Evangelos Coutsias 2004. |
695 | 1 | pfleura2 | |
696 | 1 | pfleura2 | ! This library is free software; you can redistribute it and/or |
697 | 1 | pfleura2 | ! modify it under the terms of the GNU Lesser General Public |
698 | 1 | pfleura2 | ! License as published by the Free Software Foundation; either |
699 | 1 | pfleura2 | ! version 2.1 of the License, or (at your option) any later version. |
700 | 1 | pfleura2 | ! |
701 | 1 | pfleura2 | |
702 | 1 | pfleura2 | ! This library is distributed in the hope that it will be useful, |
703 | 1 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
704 | 1 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
705 | 1 | pfleura2 | ! Lesser General Public License for more details. |
706 | 1 | pfleura2 | ! |
707 | 1 | pfleura2 | |
708 | 1 | pfleura2 | ! You should have received a copy of the GNU Lesser General Public |
709 | 1 | pfleura2 | ! License along with this library; if not, write to the Free Software |
710 | 1 | pfleura2 | ! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA |
711 | 1 | pfleura2 | !---------------------------------------------------------------------------- |
712 | 1 | pfleura2 | |
713 | 1 | pfleura2 | REAL(8) :: q(4) |
714 | 1 | pfleura2 | REAL(8) :: U(3,3) |
715 | 1 | pfleura2 | REAL(8) :: q0,q1,q2,q3,b0,b1,b2,b3,q00,q01,q02,q03 |
716 | 1 | pfleura2 | REAL(8) :: q11,q12,q13,q22,q23,q33 |
717 | 1 | pfleura2 | |
718 | 1 | pfleura2 | q0 = q(1) |
719 | 1 | pfleura2 | q1 = q(2) |
720 | 1 | pfleura2 | q2 = q(3) |
721 | 1 | pfleura2 | q3 = q(4) |
722 | 1 | pfleura2 | |
723 | 1 | pfleura2 | b0 = 2.0d0*q0 |
724 | 1 | pfleura2 | b1 = 2.0d0*q1 |
725 | 1 | pfleura2 | b2 = 2.0d0*q2 |
726 | 1 | pfleura2 | b3 = 2.0d0*q3 |
727 | 1 | pfleura2 | |
728 | 1 | pfleura2 | q00 = b0*q0-1.0d0 |
729 | 1 | pfleura2 | q01 = b0*q1 |
730 | 1 | pfleura2 | q02 = b0*q2 |
731 | 1 | pfleura2 | q03 = b0*q3 |
732 | 1 | pfleura2 | |
733 | 1 | pfleura2 | q11 = b1*q1 |
734 | 1 | pfleura2 | q12 = b1*q2 |
735 | 1 | pfleura2 | q13 = b1*q3 |
736 | 1 | pfleura2 | |
737 | 1 | pfleura2 | q22 = b2*q2 |
738 | 1 | pfleura2 | q23 = b2*q3 |
739 | 1 | pfleura2 | |
740 | 1 | pfleura2 | q33 = b3*q3 |
741 | 1 | pfleura2 | |
742 | 1 | pfleura2 | U(1,1) = q00+q11 |
743 | 1 | pfleura2 | U(1,2) = q12-q03 |
744 | 1 | pfleura2 | U(1,3) = q13+q02 |
745 | 1 | pfleura2 | |
746 | 1 | pfleura2 | U(2,1) = q12+q03 |
747 | 1 | pfleura2 | U(2,2) = q00+q22 |
748 | 1 | pfleura2 | U(2,3) = q23-q01 |
749 | 1 | pfleura2 | |
750 | 1 | pfleura2 | U(3,1) = q13-q02 |
751 | 1 | pfleura2 | U(3,2) = q23+q01 |
752 | 1 | pfleura2 | U(3,3) = q00+q33 |
753 | 1 | pfleura2 | |
754 | 1 | pfleura2 | end |
755 | 1 | pfleura2 | |
756 | 1 | pfleura2 | !c============================================================ |
757 | 1 | pfleura2 | !c |
758 | 1 | pfleura2 | !c ++ diagonalisation par jacobi |
759 | 1 | pfleura2 | !c vecteur propre i : V(i,i) |
760 | 1 | pfleura2 | !c valeur propre i : D(i) |
761 | 1 | pfleura2 | !c |
762 | 1 | pfleura2 | !c============================================================ |
763 | 1 | pfleura2 | !c |
764 | 1 | pfleura2 | SUBROUTINE JACOBI(A,N,D,V,max_N) |
765 | 1 | pfleura2 | IMPLICIT REAL(8) (A-H,O-Z) |
766 | 1 | pfleura2 | parameter (max_it=500) |
767 | 1 | pfleura2 | DIMENSION A(max_N,max_N),B(max_N),Z(max_N) |
768 | 1 | pfleura2 | DIMENSION V(max_N,max_N),D(max_N) |
769 | 1 | pfleura2 | |
770 | 1 | pfleura2 | |
771 | 1 | pfleura2 | DO 12 IP=1,N |
772 | 1 | pfleura2 | DO 11 IQ=1,N |
773 | 1 | pfleura2 | V(IP,IQ)=0. |
774 | 1 | pfleura2 | 11 CONTINUE |
775 | 1 | pfleura2 | V(IP,IP)=1. |
776 | 1 | pfleura2 | 12 CONTINUE |
777 | 1 | pfleura2 | DO 13 IP=1,N |
778 | 1 | pfleura2 | B(IP)=A(IP,IP) |
779 | 1 | pfleura2 | D(IP)=B(IP) |
780 | 1 | pfleura2 | Z(IP)=0. |
781 | 1 | pfleura2 | 13 CONTINUE |
782 | 1 | pfleura2 | NROT=0 |
783 | 1 | pfleura2 | DO 24 I=1,max_it |
784 | 1 | pfleura2 | SM=0. |
785 | 1 | pfleura2 | DO 15 IP=1,N-1 |
786 | 1 | pfleura2 | DO 14 IQ=IP+1,N |
787 | 1 | pfleura2 | SM=SM+ABS(A(IP,IQ)) |
788 | 1 | pfleura2 | 14 CONTINUE |
789 | 1 | pfleura2 | 15 CONTINUE |
790 | 1 | pfleura2 | IF(SM.EQ.0.)RETURN |
791 | 1 | pfleura2 | IF(I.LT.4)THEN |
792 | 1 | pfleura2 | TRESH=0.2*SM/N**2 |
793 | 1 | pfleura2 | ELSE |
794 | 1 | pfleura2 | TRESH=0. |
795 | 1 | pfleura2 | ENDIF |
796 | 1 | pfleura2 | DO 22 IP=1,N-1 |
797 | 1 | pfleura2 | DO 21 IQ=IP+1,N |
798 | 1 | pfleura2 | G=100.*ABS(A(IP,IQ)) |
799 | 1 | pfleura2 | IF((I.GT.4).AND.(ABS(D(IP))+G.EQ.ABS(D(IP))) & |
800 | 1 | pfleura2 | .AND.(ABS(D(IQ))+G.EQ.ABS(D(IQ))))THEN |
801 | 1 | pfleura2 | A(IP,IQ)=0. |
802 | 1 | pfleura2 | ELSE IF(ABS(A(IP,IQ)).GT.TRESH)THEN |
803 | 1 | pfleura2 | H=D(IQ)-D(IP) |
804 | 1 | pfleura2 | IF(ABS(H)+G.EQ.ABS(H))THEN |
805 | 1 | pfleura2 | T=A(IP,IQ)/H |
806 | 1 | pfleura2 | ELSE |
807 | 1 | pfleura2 | THETA=0.5*H/A(IP,IQ) |
808 | 1 | pfleura2 | T=1./(ABS(THETA)+SQRT(1.+THETA**2)) |
809 | 1 | pfleura2 | IF(THETA.LT.0.)T=-T |
810 | 1 | pfleura2 | ENDIF |
811 | 1 | pfleura2 | C=1./SQRT(1+T**2) |
812 | 1 | pfleura2 | S=T*C |
813 | 1 | pfleura2 | TAU=S/(1.+C) |
814 | 1 | pfleura2 | H=T*A(IP,IQ) |
815 | 1 | pfleura2 | Z(IP)=Z(IP)-H |
816 | 1 | pfleura2 | Z(IQ)=Z(IQ)+H |
817 | 1 | pfleura2 | D(IP)=D(IP)-H |
818 | 1 | pfleura2 | D(IQ)=D(IQ)+H |
819 | 1 | pfleura2 | A(IP,IQ)=0. |
820 | 1 | pfleura2 | DO 16 J=1,IP-1 |
821 | 1 | pfleura2 | G=A(J,IP) |
822 | 1 | pfleura2 | H=A(J,IQ) |
823 | 1 | pfleura2 | A(J,IP)=G-S*(H+G*TAU) |
824 | 1 | pfleura2 | A(J,IQ)=H+S*(G-H*TAU) |
825 | 1 | pfleura2 | 16 CONTINUE |
826 | 1 | pfleura2 | DO 17 J=IP+1,IQ-1 |
827 | 1 | pfleura2 | G=A(IP,J) |
828 | 1 | pfleura2 | H=A(J,IQ) |
829 | 1 | pfleura2 | A(IP,J)=G-S*(H+G*TAU) |
830 | 1 | pfleura2 | A(J,IQ)=H+S*(G-H*TAU) |
831 | 1 | pfleura2 | 17 CONTINUE |
832 | 1 | pfleura2 | DO 18 J=IQ+1,N |
833 | 1 | pfleura2 | G=A(IP,J) |
834 | 1 | pfleura2 | H=A(IQ,J) |
835 | 1 | pfleura2 | A(IP,J)=G-S*(H+G*TAU) |
836 | 1 | pfleura2 | A(IQ,J)=H+S*(G-H*TAU) |
837 | 1 | pfleura2 | 18 CONTINUE |
838 | 1 | pfleura2 | DO 19 J=1,N |
839 | 1 | pfleura2 | G=V(J,IP) |
840 | 1 | pfleura2 | H=V(J,IQ) |
841 | 1 | pfleura2 | V(J,IP)=G-S*(H+G*TAU) |
842 | 1 | pfleura2 | V(J,IQ)=H+S*(G-H*TAU) |
843 | 1 | pfleura2 | 19 CONTINUE |
844 | 1 | pfleura2 | NROT=NROT+1 |
845 | 1 | pfleura2 | ENDIF |
846 | 1 | pfleura2 | 21 CONTINUE |
847 | 1 | pfleura2 | 22 CONTINUE |
848 | 1 | pfleura2 | DO 23 IP=1,N |
849 | 1 | pfleura2 | B(IP)=B(IP)+Z(IP) |
850 | 1 | pfleura2 | D(IP)=B(IP) |
851 | 1 | pfleura2 | Z(IP)=0. |
852 | 1 | pfleura2 | 23 CONTINUE |
853 | 1 | pfleura2 | 24 CONTINUE |
854 | 1 | pfleura2 | write(6,*) max_it,' iterations should never happen' |
855 | 1 | pfleura2 | STOP |
856 | 1 | pfleura2 | RETURN |
857 | 1 | pfleura2 | END |
858 | 1 | pfleura2 | ! |
859 | 1 | pfleura2 | !============================================================ |
860 | 1 | pfleura2 | !c |
861 | 1 | pfleura2 | !c ++ trie des vecteur dans l'ordre croissant |
862 | 1 | pfleura2 | !c |
863 | 1 | pfleura2 | !c============================================================ |
864 | 1 | pfleura2 | !c |
865 | 1 | pfleura2 | SUBROUTINE trie(nb_niv,ene,psi,max_niv) |
866 | 1 | pfleura2 | integer(4) :: i,j,k,nb_niv,max_niv |
867 | 1 | pfleura2 | REAL(8) :: ene(max_niv),psi(max_niv,max_niv) |
868 | 1 | pfleura2 | REAL(8) :: a |
869 | 1 | pfleura2 | |
870 | 1 | pfleura2 | DO i=1,nb_niv |
871 | 1 | pfleura2 | DO j=i+1,nb_niv |
872 | 1 | pfleura2 | IF (ene(i) .GT. ene(j)) THEN |
873 | 1 | pfleura2 | !c permutation |
874 | 1 | pfleura2 | a=ene(i) |
875 | 1 | pfleura2 | ene(i)=ene(j) |
876 | 1 | pfleura2 | ene(j)=a |
877 | 1 | pfleura2 | DO k=1,nb_niv |
878 | 1 | pfleura2 | a=psi(k,i) |
879 | 1 | pfleura2 | psi(k,i)=psi(k,j) |
880 | 1 | pfleura2 | psi(k,j)=a |
881 | 1 | pfleura2 | END DO |
882 | 1 | pfleura2 | END IF |
883 | 1 | pfleura2 | END DO |
884 | 1 | pfleura2 | END DO |
885 | 1 | pfleura2 | |
886 | 1 | pfleura2 | END SUBROUTINE trie |