root / src / CalcRmsd.f90 @ 2
Historique | Voir | Annoter | Télécharger (6,88 ko)
1 |
|
---|---|
2 |
! This subroutine calculates RMSD (Root mean square deviation) using quaternions. |
3 |
! It is baNatsed on the F90 routine bu E. Coutsias |
4 |
! http://www.math.unm.edu/~vageli/homepage.html |
5 |
! I (PFL) have just translated it, and I have changed the diagonalization |
6 |
! subroutine. |
7 |
! I also made some changes to make it suitable for Cart package. |
8 |
!---------------------------------------------------------------------- |
9 |
!---------------------------------------------------------------------- |
10 |
! Copyright (C) 2004, 2005 Chaok Seok, Evangelos Coutsias and Ken Dill |
11 |
! UCSF, Univeristy of New Mexico, Seoul National University |
12 |
! Witten by Chaok Seok and Evangelos Coutsias 2004. |
13 |
|
14 |
! This library is free software; you can redistribute it and/or |
15 |
! modify it under the terms of the GNU Lesser General Public |
16 |
! License as published by the Free Software Foundation; either |
17 |
! version 2.1 of the License, or (at your option) any later version. |
18 |
! |
19 |
|
20 |
! This library is distributed in the hope that it will be useful, |
21 |
! but WITHOUT ANY WARRANTY; without even the implied warranty of |
22 |
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
23 |
! Lesser General Public License for more details. |
24 |
! |
25 |
|
26 |
! You should have received a copy of the GNU Lesser General Public |
27 |
! License along with this library; if not, write to the Free Software |
28 |
! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA |
29 |
!---------------------------------------------------------------------------- |
30 |
|
31 |
subroutine CalcRmsd(Nat,x0,y0,z0, x2,y2,z2,U,rmsd,FRot,FAlign) |
32 |
!----------------------------------------------------------------------- |
33 |
! This subroutine calculates the least square rmsd of two coordinate |
34 |
! sets coord1(3,n) and coord2(3,n) using a method based on quaternion. |
35 |
! It then calculate the rotation matrix U and the centers of coord, and uses |
36 |
! them to align the two molecules. |
37 |
! x0(Nat), y0(Nat), z0(Nat) are the coordinates of the reference geometry. |
38 |
! x2(Nat), y2(Nat), z2(Nat) are the coordinates of the geometry which is to |
39 |
! be aligned with the reference geometry. |
40 |
! The rotation matrix U has INTENT(OUT) in subroutine rotation_matrix(...), |
41 |
! which is called in this CalcRmsd(...). |
42 |
! rmsd: the root mean square deviation and calculated in this subroutine |
43 |
! CalcRmsd(...). |
44 |
! FRot: if .TRUE. the rotation matrix is calculated. This is the matrix that rotates |
45 |
! the first molecule onto the second one. |
46 |
! FAlgin: if .TRUE. then the second molecule is aligned on the first one. |
47 |
!----------------------------------------------------------------------- |
48 |
|
49 |
use VarTypes |
50 |
|
51 |
IMPLICIT NONE |
52 |
|
53 |
INTEGER(KINT) :: Nat |
54 |
real(KREAL) :: x0(Nat),y0(Nat),z0(Nat) |
55 |
real(KREAL) :: x2(Nat),y2(Nat),z2(Nat) |
56 |
real(KREAL) :: U(3,3), rmsd |
57 |
LOGICAL FRot,FAlign,Debug |
58 |
|
59 |
REAL(KREAL) :: Coord1(3,Nat), Coord2(3,Nat) |
60 |
real(KREAL) :: x0c1,y0c1,z0c1, xc2,yc2,zc2 |
61 |
|
62 |
|
63 |
INTEGER(KINT) :: i, j, nd, ia |
64 |
real(KREAL) :: x_norm, y_norm, lambda |
65 |
real(KREAL) :: Rmatrix(3,3) |
66 |
real(KREAL) :: S(4,4), dS(4,4), q(4) |
67 |
real(KREAL) :: tmp(3),tmp1(4),tmp2(4),EigVec(4,4), EigVal(4) |
68 |
|
69 |
INTERFACE |
70 |
function valid(string) result (isValid) |
71 |
CHARACTER(*), intent(in) :: string |
72 |
logical :: isValid |
73 |
END function VALID |
74 |
END INTERFACE |
75 |
|
76 |
|
77 |
debug=valid('CalcRmsd').OR.valid('align').OR.valid('alignpartial') |
78 |
|
79 |
! calculate the barycenters, centroidal coordinates, and the norms |
80 |
x_norm = 0.0d0 |
81 |
y_norm = 0.0d0 |
82 |
x0c1=0. |
83 |
y0c1=0. |
84 |
z0c1=0. |
85 |
xc2=0. |
86 |
yc2=0. |
87 |
zc2=0. |
88 |
do ia=1,Nat |
89 |
x0c1=x0c1+x0(ia) |
90 |
xc2=xc2+x2(ia) |
91 |
y0c1=y0c1+y0(ia) |
92 |
yc2=yc2+y2(ia) |
93 |
z0c1=z0c1+z0(ia) |
94 |
zc2=zc2+z2(ia) |
95 |
! if (debug) WRITE(*,'(A,I5,4(1X,F10.4))') 'ia...',ia,x0(ia), |
96 |
! & x2(ia),x0c1,xc2 |
97 |
END DO |
98 |
x0c1=x0c1/dble(Nat) |
99 |
y0c1=y0c1/dble(Nat) |
100 |
z0c1=z0c1/dble(Nat) |
101 |
xc2=xc2/dble(Nat) |
102 |
yc2=yc2/dble(Nat) |
103 |
zc2=zc2/dble(Nat) |
104 |
|
105 |
IF (debug) WRITE(*,'(1X,A,3(1X,F10.4))') 'Center1',x0c1,y0c1,z0c1 |
106 |
IF (debug) WRITE(*,'(1X,A,3(1X,F10.4))') 'Center2',xc2,yc2,zc2 |
107 |
do i=1,Nat |
108 |
Coord1(1,i)=x0(i)-x0c1 |
109 |
Coord1(2,i)=y0(i)-y0c1 |
110 |
Coord1(3,i)=z0(i)-z0c1 |
111 |
Coord2(1,i)=x2(i)-xc2 |
112 |
Coord2(2,i)=y2(i)-yc2 |
113 |
Coord2(3,i)=z2(i)-zc2 |
114 |
x_norm=x_norm+Coord1(1,i)**2+Coord1(2,i)**2+Coord1(3,i)**2 |
115 |
y_norm=y_norm+Coord2(1,i)**2+Coord2(2,i)**2+Coord2(3,i)**2 |
116 |
end do |
117 |
|
118 |
IF (debug) THEN |
119 |
WRITE(*,*) "R matrix" |
120 |
DO I=1,3 |
121 |
WRITE(*,*) (RMatrix(I,j),j=1,3) |
122 |
END DO |
123 |
END IF |
124 |
|
125 |
! calculate the R matrix |
126 |
do i = 1, 3 |
127 |
do j = 1, 3 |
128 |
Rmatrix(i,j)=0. |
129 |
do ia=1,Nat |
130 |
Rmatrix(i,j) = Rmatrix(i,j)+Coord1(i,ia)*Coord2(j,ia) |
131 |
END DO |
132 |
end do |
133 |
end do |
134 |
|
135 |
IF (debug) THEN |
136 |
WRITE(*,*) "R matrix" |
137 |
DO I=1,3 |
138 |
WRITE(*,*) (RMatrix(I,j),j=1,3) |
139 |
END DO |
140 |
END IF |
141 |
|
142 |
|
143 |
! S matrix |
144 |
S(1, 1) = Rmatrix(1, 1) + Rmatrix(2, 2) + Rmatrix(3, 3) |
145 |
S(2, 1) = Rmatrix(2, 3) - Rmatrix(3, 2) |
146 |
S(3, 1) = Rmatrix(3, 1) - Rmatrix(1, 3) |
147 |
S(4, 1) = Rmatrix(1, 2) - Rmatrix(2, 1) |
148 |
|
149 |
S(1, 2) = S(2, 1) |
150 |
S(2, 2) = Rmatrix(1, 1) - Rmatrix(2, 2) - Rmatrix(3, 3) |
151 |
S(3, 2) = Rmatrix(1, 2) + Rmatrix(2, 1) |
152 |
S(4, 2) = Rmatrix(1, 3) + Rmatrix(3, 1) |
153 |
|
154 |
S(1, 3) = S(3, 1) |
155 |
S(2, 3) = S(3, 2) |
156 |
S(3, 3) =-Rmatrix(1, 1) + Rmatrix(2, 2) - Rmatrix(3, 3) |
157 |
S(4, 3) = Rmatrix(2, 3) + Rmatrix(3, 2) |
158 |
|
159 |
S(1, 4) = S(4, 1) |
160 |
S(2, 4) = S(4, 2) |
161 |
S(3, 4) = S(4, 3) |
162 |
S(4, 4) =-Rmatrix(1, 1) - Rmatrix(2, 2) + Rmatrix(3, 3) |
163 |
|
164 |
|
165 |
! PFL : I use my usual Jacobi diagonalisation |
166 |
! Calculate eigenvalues and eigenvectors, and |
167 |
! take the maximum eigenvalue lambda and the corresponding eigenvector q. |
168 |
|
169 |
IF (debug) THEN |
170 |
WRITE(*,*) "S matrix" |
171 |
DO I=1,4 |
172 |
WRITE(*,*) (S(I,j),j=1,4) |
173 |
END DO |
174 |
END IF |
175 |
|
176 |
Call Jacobi(S,4,EigVal,EigVec,4) |
177 |
|
178 |
Call Trie(4,EigVal,EigVec,4) |
179 |
|
180 |
Lambda=EigVal(4) |
181 |
|
182 |
! RMS Deviation |
183 |
rmsd=sqrt(max(0.0d0,((x_norm+y_norm)-2.0d0*lambda))/dble(Nat)) |
184 |
! The subroutine rotation_matrix(...) constructs rotation matrix U as output |
185 |
! from the input quaternion EigVec(1,4). |
186 |
if (FRot.OR.FAlign) Call rotation_matrix(EigVec(1,4),U) |
187 |
IF (FAlign) THEN |
188 |
DO I=1,Nat |
189 |
x2(i)=Coord2(1,i)*U(1,1)+Coord2(2,i)*U(2,1) & |
190 |
+Coord2(3,i)*U(3,1) +x0c1 |
191 |
y2(i)=Coord2(1,i)*U(1,2)+Coord2(2,i)*U(2,2) & |
192 |
+Coord2(3,i)*U(3,2) +y0c1 |
193 |
z2(i)=Coord2(1,i)*U(1,3)+Coord2(2,i)*U(2,3) & |
194 |
+Coord2(3,i)*U(3,3) +z0c1 |
195 |
END DO |
196 |
END IF |
197 |
|
198 |
END |