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