added source code
[unres.git] / source / wham / src / fitsq.f
1       subroutine fitsq(rms,x,y,nn,t,b,non_conv)
2       implicit real*8 (a-h,o-z)
3       include 'COMMON.IOUNITS'
4 c  x and y are the vectors of coordinates (dimensioned (3,n)) of the two
5 c  structures to be superimposed.  nn is 3*n, where n is the number of  
6 c  points.   t and b are respectively the translation vector and the    
7 c  rotation matrix that transforms the second set of coordinates to the 
8 c  frame of the first set.                                              
9 c  eta =  machine-specific variable                                     
10                                                                         
11       dimension x(3*nn),y(3*nn),t(3)                                          
12       dimension b(3,3),q(3,3),r(3,3),v(3),xav(3),yav(3),e(3),c(3,3)     
13       logical non_conv
14       eta = z00100000                                                   
15 c     small=25.0*rmdcon(3)                                              
16 c     small=25.0*eta                                                    
17 c     small=25.0*10.e-10                                                
18 c the following is a very lenient value for 'small'                     
19       small = 0.0001D0                                                  
20       non_conv=.false.
21       fn=nn                                                             
22       do 10 i=1,3                                                       
23       xav(i)=0.0D0                                                      
24       yav(i)=0.0D0                                                      
25       do 10 j=1,3                                                       
26    10 b(j,i)=0.0D0                                                      
27       nc=0                                                              
28 c                                                                       
29       do 30 n=1,nn                                                      
30       do 20 i=1,3                                                       
31 crc      write(iout,*)'x = ',x(nc+i),'  y = ',y(nc+i)                           
32       xav(i)=xav(i)+x(nc+i)/fn                                          
33    20 yav(i)=yav(i)+y(nc+i)/fn                                          
34    30 nc=nc+3                                                           
35 c                                                                       
36       do i=1,3
37         t(i)=yav(i)-xav(i)
38       enddo
39
40       rms=0.0d0
41       do n=1,nn
42         do i=1,3
43           rms=rms+(y(3*(n-1)+i)-x(3*(n-1)+i)-t(i))**2
44         enddo
45       enddo
46       rms=dabs(rms/fn)
47
48 c     write(iout,*)'xav = ',(xav(j),j=1,3)                                    
49 c     write(iout,*)'yav = ',(yav(j),j=1,3)                                    
50 c     write(iout,*)'t   = ',(t(j),j=1,3)
51 c     write(iout,*)'rms=',rms
52       if (rms.lt.small) return
53                                                                         
54                                                                         
55       nc=0                                                              
56       rms=0.0D0                                                         
57       do 50 n=1,nn                                                      
58       do 40 i=1,3                                                       
59       rms=rms+((x(nc+i)-xav(i))**2+(y(nc+i)-yav(i))**2)/fn              
60       do 40 j=1,3                                                       
61       b(j,i)=b(j,i)+(x(nc+i)-xav(i))*(y(nc+j)-yav(j))/fn                
62    40 c(j,i)=b(j,i)                                                     
63    50 nc=nc+3                                                           
64       call sivade(b,q,r,d,non_conv)
65       sn3=dsign(1.0d0,d)                                                   
66       do 120 i=1,3                                                      
67       do 120 j=1,3                                                      
68   120 b(j,i)=-q(j,1)*r(i,1)-q(j,2)*r(i,2)-sn3*q(j,3)*r(i,3)             
69       call mvvad(b,xav,yav,t)                                           
70       do 130 i=1,3                                                      
71       do 130 j=1,3                                                      
72       rms=rms+2.0*c(j,i)*b(j,i)                                         
73   130 b(j,i)=-b(j,i)                                                    
74       if (dabs(rms).gt.small) go to 140                                  
75 *     write (6,301)                                                     
76       return                                                            
77   140 if (rms.gt.0.0d0) go to 150                                         
78 c     write (iout,303) rms                                                 
79       rms=0.0d0
80 *     stop                                                              
81 c 150 write (iout,302) dsqrt(rms)                                           
82   150 continue
83       return                                                            
84   301 format (5x,'rms deviation negligible')                            
85   302 format (5x,'rms deviation ',f14.6)                                
86   303 format (//,5x,'negative ms deviation - ',f14.6)                   
87       end                                                               
88       subroutine sivade(x,q,r,dt,non_conv)
89       implicit real*8(a-h,o-z)
90 c  computes q,e and r such that q(t)xr = diag(e)                        
91       dimension x(3,3),q(3,3),r(3,3),e(3)                               
92       dimension h(3,3),p(3,3),u(3,3),d(3)                               
93       logical non_conv
94       eta = z00100000                                                   
95       nit = 0
96       small=25.0*10.e-10                                                
97 c     small=25.0*eta                                                    
98 c     small=2.0*rmdcon(3)                                               
99       xnrm=0.0d0                                                          
100       do 20 i=1,3                                                       
101       do 10 j=1,3                                                       
102       xnrm=xnrm+x(j,i)*x(j,i)                                           
103       u(j,i)=0.0d0                                                        
104       r(j,i)=0.0d0                                                        
105    10 h(j,i)=0.0d0                                                        
106       u(i,i)=1.0                                                        
107    20 r(i,i)=1.0                                                        
108       xnrm=dsqrt(xnrm)                                                   
109       do 110 n=1,2                                                      
110       xmax=0.0d0                                                          
111       do 30 j=n,3                                                       
112    30 if (dabs(x(j,n)).gt.xmax) xmax=dabs(x(j,n))                         
113       a=0.0d0                                                             
114       do 40 j=n,3                                                       
115       h(j,n)=x(j,n)/xmax                                                
116    40 a=a+h(j,n)*h(j,n)                                                 
117       a=dsqrt(a)                                                         
118       den=a*(a+dabs(h(n,n)))                                             
119       d(n)=1.0/den                                                      
120       h(n,n)=h(n,n)+dsign(a,h(n,n))                                      
121       do 70 i=n,3                                                       
122       s=0.0d0                                                             
123       do 50 j=n,3                                                       
124    50 s=s+h(j,n)*x(j,i)                                                 
125       s=d(n)*s                                                          
126       do 60 j=n,3                                                       
127    60 x(j,i)=x(j,i)-s*h(j,n)                                            
128    70 continue                                                          
129       if (n.gt.1) go to 110                                             
130       xmax=dmax1(dabs(x(1,2)),dabs(x(1,3)))                               
131       h(2,3)=x(1,2)/xmax                                                
132       h(3,3)=x(1,3)/xmax                                                
133       a=dsqrt(h(2,3)*h(2,3)+h(3,3)*h(3,3))                               
134       den=a*(a+dabs(h(2,3)))                                             
135       d(3)=1.0/den                                                      
136       h(2,3)=h(2,3)+sign(a,h(2,3))                                      
137       do 100 i=1,3                                                      
138       s=0.0d0                                                             
139       do 80 j=2,3                                                       
140    80 s=s+h(j,3)*x(i,j)                                                 
141       s=d(3)*s                                                          
142       do 90 j=2,3                                                       
143    90 x(i,j)=x(i,j)-s*h(j,3)                                            
144   100 continue                                                          
145   110 continue                                                          
146       do 130 i=1,3                                                      
147       do 120 j=1,3                                                      
148   120 p(j,i)=-d(1)*h(j,1)*h(i,1)                                        
149   130 p(i,i)=1.0+p(i,i)                                                 
150       do 140 i=2,3                                                      
151       do 140 j=2,3                                                      
152       u(j,i)=u(j,i)-d(2)*h(j,2)*h(i,2)                                  
153   140 r(j,i)=r(j,i)-d(3)*h(j,3)*h(i,3)                                  
154       call mmmul(p,u,q)                                                 
155   150 np=1                                                              
156       nq=1                                                              
157       nit=nit+1
158       if (nit.gt.10000) then
159         print '(a)','!!!! Over 10000 iterations in SIVADE!!!!!'
160         non_conv=.true.
161         return
162       endif
163       if (dabs(x(2,3)).gt.small*(dabs(x(2,2))+abs(x(3,3)))) go to 160     
164       x(2,3)=0.0d0                                                        
165       nq=nq+1                                                           
166   160 if (dabs(x(1,2)).gt.small*(dabs(x(1,1))+dabs(x(2,2)))) go to 180     
167       x(1,2)=0.0d0                                                        
168       if (x(2,3).ne.0.0d0) go to 170                                      
169       nq=nq+1                                                           
170       go to 180                                                         
171   170 np=np+1                                                           
172   180 if (nq.eq.3) go to 310                                            
173       npq=4-np-nq                                                       
174       if (np.gt.npq) go to 230                                          
175       n0=0                                                              
176       do 220 n=np,npq                                                   
177       nn=n+np-1                                                         
178       if (dabs(x(nn,nn)).gt.small*xnrm) go to 220                        
179       x(nn,nn)=0.0d0                                                      
180       if (x(nn,nn+1).eq.0.0d0) go to 220                                  
181       n0=n0+1                                                           
182       go to (190,210,220),nn                                            
183   190 do 200 j=2,3                                                      
184   200 call givns(x,q,1,j)                                               
185       go to 220                                                         
186   210 call givns(x,q,2,3)                                               
187   220 continue                                                          
188       if (n0.ne.0) go to 150                                            
189   230 nn=3-nq                                                           
190       a=x(nn,nn)*x(nn,nn)                                               
191       if (nn.gt.1) a=a+x(nn-1,nn)*x(nn-1,nn)                            
192       b=x(nn+1,nn+1)*x(nn+1,nn+1)+x(nn,nn+1)*x(nn,nn+1)                 
193       c=x(nn,nn)*x(nn,nn+1)                                             
194       dd=0.5*(a-b)                                                      
195       xn2=c*c                                                           
196       rt=b-xn2/(dd+sign(dsqrt(dd*dd+xn2),dd))                            
197       y=x(np,np)*x(np,np)-rt                                            
198       z=x(np,np)*x(np,np+1)                                             
199       do 300 n=np,nn                                                    
200       if (dabs(y).lt.dabs(z)) go to 240                                   
201       t=z/y                                                             
202       c=1.0/dsqrt(1.0d0+t*t)                                               
203       s=c*t                                                             
204       go to 250                                                         
205   240 t=y/z                                                             
206       s=1.0/dsqrt(1.0d0+t*t)                                               
207       c=s*t                                                             
208   250 do 260 j=1,3                                                      
209       v=x(j,n)                                                          
210       w=x(j,n+1)                                                        
211       x(j,n)=c*v+s*w                                                    
212       x(j,n+1)=-s*v+c*w                                                 
213       a=r(j,n)                                                          
214       b=r(j,n+1)                                                        
215       r(j,n)=c*a+s*b                                                    
216   260 r(j,n+1)=-s*a+c*b                                                 
217       y=x(n,n)                                                          
218       z=x(n+1,n)                                                        
219       if (dabs(y).lt.dabs(z)) go to 270                                   
220       t=z/y                                                             
221       c=1.0/dsqrt(1.0+t*t)                                               
222       s=c*t                                                             
223       go to 280                                                         
224   270 t=y/z                                                             
225       s=1.0/dsqrt(1.0+t*t)                                               
226       c=s*t                                                             
227   280 do 290 j=1,3                                                      
228       v=x(n,j)                                                          
229       w=x(n+1,j)                                                        
230       a=q(j,n)                                                          
231       b=q(j,n+1)                                                        
232       x(n,j)=c*v+s*w                                                    
233       x(n+1,j)=-s*v+c*w                                                 
234       q(j,n)=c*a+s*b                                                    
235   290 q(j,n+1)=-s*a+c*b                                                 
236       if (n.ge.nn) go to 300                                            
237       y=x(n,n+1)                                                        
238       z=x(n,n+2)                                                        
239   300 continue                                                          
240       go to 150                                                         
241   310 do 320 i=1,3                                                      
242   320 e(i)=x(i,i)                                                       
243       nit=0
244   330 n0=0                                                              
245       nit=nit+1
246       if (nit.gt.10000) then
247         print '(a)','!!!! Over 10000 iterations in SIVADE!!!!!'
248         non_conv=.true.
249         return
250       endif
251       do 360 i=1,3                                                      
252       if (e(i).ge.0.0d0) go to 350                                        
253       e(i)=-e(i)                                                        
254       do 340 j=1,3                                                      
255   340 q(j,i)=-q(j,i)                                                    
256   350 if (i.eq.1) go to 360                                             
257       if (dabs(e(i)).lt.dabs(e(i-1))) go to 360                           
258       call switch(i,1,q,r,e)                                            
259       n0=n0+1                                                           
260   360 continue                                                          
261       if (n0.ne.0) go to 330                                            
262       if (dabs(e(3)).gt.small*xnrm) go to 370                            
263       e(3)=0.0d0                                                          
264       if (dabs(e(2)).gt.small*xnrm) go to 370                            
265       e(2)=0.0d0                                                          
266   370 dt=det(q(1,1),q(1,2),q(1,3))*det(r(1,1),r(1,2),r(1,3))            
267 *     write (1,501) (e(i),i=1,3)                                        
268       return                                                            
269   501 format (/,5x,'singular values - ',3e15.5)                         
270       end                                                               
271       subroutine givns(a,b,m,n)                                         
272       implicit real*8 (a-h,o-z)
273       dimension a(3,3),b(3,3)                                           
274       if (dabs(a(m,n)).lt.dabs(a(n,n))) go to 10                          
275       t=a(n,n)/a(m,n)                                                   
276       s=1.0/dsqrt(1.0+t*t)                                               
277       c=s*t                                                             
278       go to 20                                                          
279    10 t=a(m,n)/a(n,n)                                                   
280       c=1.0/dsqrt(1.0+t*t)                                               
281       s=c*t                                                             
282    20 do 30 j=1,3                                                       
283       v=a(m,j)                                                          
284       w=a(n,j)                                                          
285       x=b(j,m)                                                          
286       y=b(j,n)                                                          
287       a(m,j)=c*v-s*w                                                    
288       a(n,j)=s*v+c*w                                                    
289       b(j,m)=c*x-s*y                                                    
290    30 b(j,n)=s*x+c*y                                                    
291       return                                                            
292       end                                                               
293       subroutine switch(n,m,u,v,d)                                      
294       implicit real*8 (a-h,o-z)
295       dimension u(3,3),v(3,3),d(3)                                      
296       do 10 i=1,3                                                       
297       tem=u(i,n)                                                        
298       u(i,n)=u(i,n-1)                                                   
299       u(i,n-1)=tem                                                      
300       if (m.eq.0) go to 10                                              
301       tem=v(i,n)                                                        
302       v(i,n)=v(i,n-1)                                                   
303       v(i,n-1)=tem                                                      
304    10 continue                                                          
305       tem=d(n)                                                          
306       d(n)=d(n-1)                                                       
307       d(n-1)=tem                                                        
308       return                                                            
309       end                                                               
310       subroutine mvvad(b,xav,yav,t)                                     
311       implicit real*8 (a-h,o-z)
312       dimension b(3,3),xav(3),yav(3),t(3)                               
313 c     dimension a(3,3),b(3),c(3),d(3)                                   
314 c     do 10 j=1,3                                                       
315 c     d(j)=c(j)                                                         
316 c     do 10 i=1,3                                                       
317 c  10 d(j)=d(j)+a(j,i)*b(i)                                             
318       do 10 j=1,3                                                       
319       t(j)=yav(j)                                                       
320       do 10 i=1,3                                                       
321    10 t(j)=t(j)+b(j,i)*xav(i)                                           
322       return                                                            
323       end                                                               
324       double precision function det (a,b,c)
325       implicit real*8 (a-h,o-z)
326       dimension a(3),b(3),c(3)                                          
327       det=a(1)*(b(2)*c(3)-b(3)*c(2))+a(2)*(b(3)*c(1)-b(1)*c(3))         
328      1  +a(3)*(b(1)*c(2)-b(2)*c(1))                                     
329       return                                                            
330       end                                                               
331       subroutine mmmul(a,b,c)                                           
332       implicit real*8 (a-h,o-z)
333       dimension a(3,3),b(3,3),c(3,3)                                    
334       do 10 i=1,3                                                       
335       do 10 j=1,3                                                       
336       c(i,j)=0.0d0                                                        
337       do 10 k=1,3                                                       
338    10 c(i,j)=c(i,j)+a(i,k)*b(k,j)                                       
339       return                                                            
340       end                                                               
341       subroutine matvec(uvec,tmat,pvec,nback)                           
342       implicit real*8 (a-h,o-z)
343       real*8 tmat(3,3),uvec(3,nback), pvec(3,nback)                     
344 c                                                                       
345       do 2 j=1,nback                                                    
346          do 1 i=1,3                                                     
347          uvec(i,j) = 0.0d0                                                
348          do 1 k=1,3                                                     
349     1    uvec(i,j)=uvec(i,j)+tmat(i,k)*pvec(k,j)                        
350     2 continue                                                          
351       return                                                            
352       end