Statistiques
| Révision :

root / src / AlignPartial.f90 @ 6

Historique | Voir | Annoter | Télécharger (5,3 ko)

1
subroutine AlignPartial(na, x,y,z,x2,y2,z2,ListAt,U)
2
  !-----------------------------------------------------------------------
3
  !  This subroutine calculates the least square rmsd of two coordinate
4
  !  sets coord1(3,n) and coord2(3,n) using a method based on quaternion.
5
  !  It then calculate the  rotation matrix U and the centers of coord, and uses
6
  ! them to align the two molecules.
7
  ! This new version does not use all atoms to calculate the RMSD and rotation matrix
8
  ! but only those which are 'true' in ListAt
9
  !-----------------------------------------------------------------------
10
  ! Input parameters:
11
  ! Na        : number of atoms
12
  ! x,y,z     : coordinates of the first geometry
13
  ! x2,y2,z2  : coordinates of the second geometry
14
  ! ListAt    : Logical, T if this atom should be considered in the RMSD calc and 
15
  !             alignment.
16
  ! Debug     : True if additionnal printing is requiered
17
  !
18
  ! output parameters:
19
  ! U         : Real, (3x3) matrix for rotation
20
  ! Rmsd      : Read, the rmsd
21
  ! x2,y2,z2  : coordinates of the second geometry ALIGNED to the first one
22
  !-----------------------------------------------------------------------
23

    
24
  Use VarTypes
25
  IMPLICIT NONE
26

    
27

    
28
  integer(KINT) :: na, NaT
29
  Real(KREAL) ::  x(na),y(Na),z(Na)
30
  Real(KREAL) ::  x2(Na),y2(Na),z2(Na)
31
  Real(KREAL) ::  U(3,3), rmsd
32
  LOGICAL  Debug, ListAt(Na)
33

    
34
  REAL(KREAL) :: Coord1(3,Na), Coord2(3,Na)
35
  Real(KREAL) ::  xc1,yc1,zc1, xc2,yc2,zc2
36

    
37

    
38
  integer(KINT) :: i, j, nd, ia
39
  Real(KREAL) :: x_norm, y_norm, lambda
40
  Real(KREAL) :: Rmatrix(3,3)
41
  Real(KREAL) :: S(4,4), dS(4,4), q(4)
42
  Real(KREAL) :: tmp(3),tmp1(4),tmp2(4),EigVec(4,4), EigVal(4)
43

    
44
  INTERFACE
45
     function valid(string) result (isValid)
46
       CHARACTER(*), intent(in) :: string
47
       logical                  :: isValid
48
     END function VALID
49
  END INTERFACE
50

    
51

    
52
  debug=valid('CalcRmsd').OR.valid('align').OR.valid('alignpartial')
53

    
54
  ! calculate the barycenters, centroidal coordinates, and the norms
55
  x_norm = 0.0d0
56
  y_norm = 0.0d0
57
  xc1=0.
58
  yc1=0.
59
  zc1=0.
60
  xc2=0.
61
  yc2=0.
62
  zc2=0.
63

    
64
  if (debug) THEN
65
     WRITE(*,*) "DBG AlignPartial X2,Y2,Z2 before align"
66
     DO Ia=1,na
67
        WRITE(*,*) x2(ia),y2(ia),z2(ia)
68
     END DO
69
  END IF
70

    
71
  NAt=0
72
  do ia=1,na
73
     IF (listat(ia)) THEN
74
        Nat=NAt+1
75
        xc1=xc1+x(ia)
76
        xc2=xc2+x2(ia)
77
        yc1=yc1+y(ia)
78
        yc2=yc2+y2(ia)
79
        zc1=zc1+z(ia)
80
        zc2=zc2+z2(ia)
81
        !     if (debug) WRITE(*,'(A,I5,4(1X,F10.4))') 'ia...',ia,x(ia),
82
        !     &                        x2(ia),xc1,xc2
83
     END IF
84
  END DO
85

    
86
  if (Nat.EQ.0) THEN
87
     WRITE(*,*) "ERROR, AlignPartial: ListAt is empty :-)"
88
  END IF
89
  xc1=xc1/dble(nat)
90
  yc1=yc1/dble(nat)
91
  zc1=zc1/dble(nat)
92
  xc2=xc2/dble(nat)
93
  yc2=yc2/dble(nat)
94
  zc2=zc2/dble(nat)
95

    
96
  IF (Debug) WRITE(*,*) 'Found :', Nat, ' atoms'
97
  IF (debug) WRITE(*,*) (ListAt(I),I=1,Na)
98
  IF (debug) WRITE(*,'(1X,A,3(1X,F10.4))') 'Center1',xc1,yc1,zc1
99
  IF (debug) WRITE(*,'(1X,A,3(1X,F10.4))') 'Center2',xc2,yc2,zc2
100
  do i=1,na
101
     Coord1(1,i)=x(i)-xc1
102
     Coord1(2,i)=y(i)-yc1
103
     Coord1(3,i)=z(i)-zc1
104
     Coord2(1,i)=x2(i)-xc2
105
     Coord2(2,i)=y2(i)-yc2
106
     Coord2(3,i)=z2(i)-zc2
107
     IF (ListAt(I)) THEN
108
        x_norm=x_norm+Coord1(1,i)**2+Coord1(2,i)**2+Coord1(3,i)**2
109
        y_norm=y_norm+Coord2(1,i)**2+Coord2(2,i)**2+Coord2(3,i)**2
110
     END IF
111
  end do
112

    
113
  ! calculate the R matrix
114
  do i = 1, 3
115
     do j = 1, 3
116
        Rmatrix(i,j)=0.
117
        do ia=1,na
118
           If (ListAt(ia))  Rmatrix(i,j) = Rmatrix(i,j)+Coord1(i,ia)*Coord2(j,ia)
119
        END DO
120
     end do
121
  end do
122

    
123
  IF (debug) THEN
124
     WRITE(*,*) "R matrix"
125
     DO I=1,3
126
        WRITE(*,*) (RMatrix(I,j),j=1,3)
127
     END DO
128
  END IF
129

    
130

    
131
  ! S matrix
132
  S(1, 1) = Rmatrix(1, 1) + Rmatrix(2, 2) + Rmatrix(3, 3)
133
  S(2, 1) = Rmatrix(2, 3) - Rmatrix(3, 2)
134
  S(3, 1) = Rmatrix(3, 1) - Rmatrix(1, 3)
135
  S(4, 1) = Rmatrix(1, 2) - Rmatrix(2, 1)
136

    
137
  S(1, 2) = S(2, 1)
138
  S(2, 2) = Rmatrix(1, 1) - Rmatrix(2, 2) - Rmatrix(3, 3)
139
  S(3, 2) = Rmatrix(1, 2) + Rmatrix(2, 1)
140
  S(4, 2) = Rmatrix(1, 3) + Rmatrix(3, 1)
141

    
142
  S(1, 3) = S(3, 1)
143
  S(2, 3) = S(3, 2)
144
  S(3, 3) =-Rmatrix(1, 1) + Rmatrix(2, 2) - Rmatrix(3, 3)
145
  S(4, 3) = Rmatrix(2, 3) + Rmatrix(3, 2)
146

    
147
  S(1, 4) = S(4, 1)
148
  S(2, 4) = S(4, 2)
149
  S(3, 4) = S(4, 3)
150
  S(4, 4) =-Rmatrix(1, 1) - Rmatrix(2, 2) + Rmatrix(3, 3) 
151

    
152

    
153
  ! PFL : I use my usual Jacobi diagonalisation
154
  ! Calculate eigenvalues and eigenvectors, and 
155
  ! take the maximum eigenvalue lambda and the corresponding eigenvector q.
156

    
157
  IF (debug) THEN
158
     WRITE(*,*) "S matrix"
159
     DO I=1,4
160
        WRITE(*,*) (S(I,j),j=1,4)
161
     END DO
162
  END IF
163

    
164
  Call Jacobi(S,4,EigVal,EigVec,4)
165

    
166
  Call Trie(4,EigVal,EigVec,4)
167

    
168
  Lambda=EigVal(4)
169

    
170
  ! RMS Deviation
171
  rmsd=sqrt(max(0.0d0,((x_norm+y_norm)-2.0d0*lambda))/dble(nat))
172
  if (debug) WRITE(*,*) "AlignPartial rmsd:",rmsd
173
  Call rotation_matrix(EigVec(1,4),U)
174

    
175

    
176
  IF (debug) THEN
177
     WRITE(*,*) "U matrix"
178
     DO I=1,3
179
        WRITE(*,*) (U(I,j),j=1,3)
180
     END DO
181
  END IF
182

    
183
  DO I=1,na
184
     x2(i)=Coord2(1,i)*U(1,1)+Coord2(2,i)*U(2,1) + Coord2(3,i)*U(3,1) +xc1
185
     y2(i)=Coord2(1,i)*U(1,2)+Coord2(2,i)*U(2,2) + Coord2(3,i)*U(3,2) +yc1
186
     z2(i)=Coord2(1,i)*U(1,3)+Coord2(2,i)*U(2,3) + Coord2(3,i)*U(3,3) +zc1
187
  END DO
188

    
189
  if (debug) THEN
190
     WRITE(*,*) "DBG AlignPartial X2,Y2,Z2 after align"
191
     DO Ia=1,na
192
        WRITE(*,*) x2(ia),y2(ia),z2(ia)
193
     END DO
194
  END IF
195

    
196

    
197
END subroutine AlignPartial