intoduction of constant velocity for spring
[unres.git] / source / unres / src_MD-M / int_to_cart.f
1        subroutine int_to_cart
2 c--------------------------------------------------------------         
3 c  This subroutine converts the energy derivatives from internal 
4 c  coordinates to cartesian coordinates
5 c-------------------------------------------------------------
6       implicit real*8 (a-h,o-z)
7       include 'DIMENSIONS'
8       include 'COMMON.VAR'
9       include 'COMMON.CHAIN'
10       include 'COMMON.DERIV'
11       include 'COMMON.GEO'
12       include 'COMMON.LOCAL'
13       include 'COMMON.INTERACT'
14       include 'COMMON.MD'
15       include 'COMMON.IOUNITS'
16       include 'COMMON.SCCOR' 
17       include 'COMMON.CONTROL'
18 c   calculating dE/ddc1     
19 C       print *,"wchodze22",ialph(2,1) 
20        if (nres.lt.3) go to 18
21        do j=1,3
22          gcart(j,1)=gcart(j,1)+gloc(1,icg)*dphi(j,1,4)
23      &     +gloc(nres-2,icg)*dtheta(j,1,3)       
24          if(itype(2).ne.10) then
25           gcart(j,1)=gcart(j,1)+gloc(ialph(2,1),icg)*dalpha(j,1,2)+
26      &    gloc(ialph(2,1)+nside,icg)*domega(j,1,2)              
27         endif
28        enddo
29 C       print *,"wchodze22",ialph(2,1)
30 c     Calculating the remainder of dE/ddc2
31        do j=1,3
32          gcart(j,2)=gcart(j,2)+gloc(1,icg)*dphi(j,2,4)+
33      &   gloc(nres-2,icg)*dtheta(j,2,3)+gloc(nres-1,icg)*dtheta(j,1,4)
34         if(itype(2).ne.10) then
35           gcart(j,2)=gcart(j,2)+gloc(ialph(2,1),icg)*dalpha(j,2,2)+
36      &    gloc(ialph(2,1)+nside,icg)*domega(j,2,2)
37         endif
38         if(itype(3).ne.10) then
39           gcart(j,2)=gcart(j,2)+gloc(ialph(3,1),icg)*dalpha(j,1,3)+
40      &    gloc(ialph(3,1)+nside,icg)*domega(j,1,3)
41         endif
42         if(nres.gt.4) then
43           gcart(j,2)=gcart(j,2)+gloc(2,icg)*dphi(j,1,5)
44         endif                   
45        enddo
46 C       print *,"wchodze22",ialph(2,1)
47 c  If there are only five residues       
48        if(nres.eq.5) then
49          do j=1,3
50            gcart(j,3)=gcart(j,3)+gloc(1,icg)*dphi(j,3,4)+gloc(2,icg)*
51      &     dphi(j,2,5)+gloc(nres-1,icg)*dtheta(j,2,4)+gloc(nres,icg)*
52      &     dtheta(j,1,5)
53          if(itype(3).ne.10) then
54            gcart(j,3)=gcart(j,3)+gloc(ialph(3,1),icg)*
55      &     dalpha(j,2,3)+gloc(ialph(3,1)+nside,icg)*domega(j,2,3)
56          endif
57          if(itype(4).ne.10) then
58            gcart(j,3)=gcart(j,3)+gloc(ialph(4,1),icg)*
59      &     dalpha(j,1,4)+gloc(ialph(4,1)+nside,icg)*domega(j,1,4)
60          endif
61         enddo
62        endif
63 c    If there are more than five residues
64       if(nres.gt.5) then                           
65 C       print *,"wchodze22",ialph(2,1)
66         do i=3,nres-3
67 C        print *,i,ialph(i,1)+nside
68          do j=1,3
69           gcart(j,i)=gcart(j,i)+gloc(i-2,icg)*dphi(j,3,i+1)
70      &    +gloc(i-1,icg)*dphi(j,2,i+2)+
71      &    gloc(i,icg)*dphi(j,1,i+3)+gloc(nres+i-4,icg)*dtheta(j,2,i+1)+
72      &    gloc(nres+i-3,icg)*dtheta(j,1,i+2)
73           if((itype(i).ne.10).and.(itype(i).ne.ntyp1)) then
74            gcart(j,i)=gcart(j,i)+gloc(ialph(i,1),icg)*dalpha(j,2,i)+
75      &     gloc(ialph(i,1)+nside,icg)*domega(j,2,i)
76           endif
77           if((itype(i+1).ne.10).and.(itype(i+1).ne.ntyp1)) then
78            gcart(j,i)=gcart(j,i)+gloc(ialph(i+1,1),icg)*dalpha(j,1,i+1)
79      &     +gloc(ialph(i+1,1)+nside,icg)*domega(j,1,i+1)
80           endif
81          enddo
82         enddo
83       endif     
84 C       print *,"wchodze22",ialph(2,1)
85
86 c  Setting dE/ddnres-2       
87       if(nres.gt.5) then
88          do j=1,3
89            gcart(j,nres-2)=gcart(j,nres-2)+gloc(nres-4,icg)*
90      &     dphi(j,3,nres-1)+gloc(nres-3,icg)*dphi(j,2,nres)
91      &     +gloc(2*nres-6,icg)*
92      &     dtheta(j,2,nres-1)+gloc(2*nres-5,icg)*dtheta(j,1,nres)
93           if(itype(nres-2).ne.10) then
94               gcart(j,nres-2)=gcart(j,nres-2)+gloc(ialph(nres-2,1),icg)*
95      &        dalpha(j,2,nres-2)+gloc(ialph(nres-2,1)+nside,icg)*
96      &        domega(j,2,nres-2)
97           endif
98           if(itype(nres-1).ne.10) then
99              gcart(j,nres-2)=gcart(j,nres-2)+gloc(ialph(nres-1,1),icg)*
100      &       dalpha(j,1,nres-1)+gloc(ialph(nres-1,1)+nside,icg)*
101      &       domega(j,1,nres-1)
102           endif
103          enddo
104       endif 
105 c  Settind dE/ddnres-1       
106        do j=1,3
107         gcart(j,nres-1)=gcart(j,nres-1)+gloc(nres-3,icg)*dphi(j,3,nres)+
108      &  gloc(2*nres-5,icg)*dtheta(j,2,nres)
109         if(itype(nres-1).ne.10) then
110           gcart(j,nres-1)=gcart(j,nres-1)+gloc(ialph(nres-1,1),icg)*
111      &    dalpha(j,2,nres-1)+gloc(ialph(nres-1,1)+nside,icg)*
112      &    domega(j,2,nres-1)
113         endif
114         enddo
115 c   The side-chain vector derivatives
116         do i=2,nres-1
117          if(itype(i).ne.10 .and. itype(i).ne.ntyp1) then        
118             do j=1,3    
119               gxcart(j,i)=gxcart(j,i)+gloc(ialph(i,1),icg)*dalpha(j,3,i)
120      &        +gloc(ialph(i,1)+nside,icg)*domega(j,3,i)
121             enddo
122          endif      
123        enddo                                                                                                                                                    
124 c----------------------------------------------------------------------
125 C INTERTYP=1 SC...Ca...Ca...Ca
126 C INTERTYP=2 Ca...Ca...Ca...SC
127 C INTERTYP=3 SC...Ca...Ca...SC
128 c   calculating dE/ddc1      
129   18   continue
130 c       do i=1,nres
131 c       gloc(i,icg)=0.0D0
132 c          write (iout,*) "poczotkoawy",i,gloc_sc(1,i,icg)
133 c       enddo
134 C       print *,"tu dochodze??"
135        if (nres.lt.2) return
136        if ((nres.lt.3).and.(itype(1).eq.10)) return
137        if ((itype(1).ne.10).and.(itype(1).ne.ntyp1)) then
138         do j=1,3
139 cc Derviative was calculated for oposite vector of side chain therefore
140 c there is "-" sign before gloc_sc
141          gxcart(j,1)=gxcart(j,1)-gloc_sc(1,0,icg)*
142      &     dtauangle(j,1,1,3)
143          gcart(j,1)=gcart(j,1)+gloc_sc(1,0,icg)*
144      &     dtauangle(j,1,2,3)
145           if ((itype(2).ne.10).and.(itype(2).ne.ntyp1)) then
146          gxcart(j,1)= gxcart(j,1)
147      &               -gloc_sc(3,0,icg)*dtauangle(j,3,1,3)
148          gcart(j,1)=gcart(j,1)+gloc_sc(3,0,icg)*
149      &       dtauangle(j,3,2,3)
150           endif
151        enddo
152        endif
153          if ((nres.ge.3).and.(itype(3).ne.10).and.(itype(3).ne.ntyp1))
154      & then
155          do j=1,3
156          gcart(j,1)=gcart(j,1)+gloc_sc(2,1,icg)*dtauangle(j,2,1,4)
157          enddo
158          endif
159 c   As potetnial DO NOT depend on omicron anlge their derivative is
160 c   ommited 
161 c     &     +gloc_sc(intertyp,nres-2,icg)*dtheta(j,1,3)  
162
163 c     Calculating the remainder of dE/ddc2
164        do j=1,3
165          if((itype(2).ne.10).and.(itype(2).ne.ntyp1)) then
166            if (itype(1).ne.10) gxcart(j,2)=gxcart(j,2)+
167      &                         gloc_sc(3,0,icg)*dtauangle(j,3,3,3)
168         if ((itype(3).ne.10).and.(nres.ge.3).and.(itype(3).ne.ntyp1))
169      &   then
170            gxcart(j,2)=gxcart(j,2)-gloc_sc(3,1,icg)*dtauangle(j,3,1,4)
171 cc                  the   - above is due to different vector direction
172            gcart(j,2)=gcart(j,2)+gloc_sc(3,1,icg)*dtauangle(j,3,2,4)
173           endif
174           if (nres.gt.3) then
175            gxcart(j,2)=gxcart(j,2)-gloc_sc(1,1,icg)*dtauangle(j,1,1,4)
176 cc                  the   - above is due to different vector direction
177            gcart(j,2)=gcart(j,2)+gloc_sc(1,1,icg)*dtauangle(j,1,2,4)
178 c          write(iout,*) gloc_sc(1,1,icg),dtauangle(j,1,2,4),"gcart"
179 c           write(iout,*) gloc_sc(1,1,icg),dtauangle(j,1,1,4),"gx"
180           endif
181          endif
182          if ((itype(1).ne.10).and.(itype(1).ne.ntyp1)) then
183           gcart(j,2)=gcart(j,2)+gloc_sc(1,0,icg)*dtauangle(j,1,3,3)
184 c           write(iout,*)  gloc_sc(1,0,icg),dtauangle(j,1,3,3)
185         endif
186          if ((itype(3).ne.10).and.(nres.ge.3)) then
187           gcart(j,2)=gcart(j,2)+gloc_sc(2,1,icg)*dtauangle(j,2,2,4)
188 c           write(iout,*) gloc_sc(2,1,icg),dtauangle(j,2,2,4)
189          endif
190          if ((itype(4).ne.10).and.(nres.ge.4)) then
191           gcart(j,2)=gcart(j,2)+gloc_sc(2,2,icg)*dtauangle(j,2,1,5)
192 c           write(iout,*) gloc_sc(2,2,icg),dtauangle(j,2,1,5)
193          endif
194
195 c      write(iout,*) gcart(j,2),itype(2),itype(1),itype(3), "gcart2"
196        enddo
197 c    If there are more than five residues
198       if(nres.ge.5) then                        
199         do i=3,nres-2
200          do j=1,3
201 c          write(iout,*) "before", gcart(j,i)
202           if ((itype(i).ne.10).and.(itype(i).ne.ntyp1)) then
203           gxcart(j,i)=gxcart(j,i)+gloc_sc(2,i-2,icg)
204      &    *dtauangle(j,2,3,i+1)
205      &    -gloc_sc(1,i-1,icg)*dtauangle(j,1,1,i+2)
206           gcart(j,i)=gcart(j,i)+gloc_sc(1,i-1,icg)
207      &    *dtauangle(j,1,2,i+2)
208 c                   write(iout,*) "new",j,i,
209 c     &  gcart(j,i),gloc_sc(1,i-1,icg),dtauangle(j,1,2,i+2)
210           if (itype(i-1).ne.10) then
211            gxcart(j,i)=gxcart(j,i)+gloc_sc(3,i-2,icg)
212      &*dtauangle(j,3,3,i+1)
213           endif
214           if (itype(i+1).ne.10) then
215            gxcart(j,i)=gxcart(j,i)-gloc_sc(3,i-1,icg)
216      &*dtauangle(j,3,1,i+2)
217            gcart(j,i)=gcart(j,i)+gloc_sc(3,i-1,icg)
218      &*dtauangle(j,3,2,i+2)
219           endif
220           endif
221           if (itype(i-1).ne.10) then
222            gcart(j,i)=gcart(j,i)+gloc_sc(1,i-2,icg)*
223      &     dtauangle(j,1,3,i+1)
224           endif
225           if (itype(i+1).ne.10) then
226            gcart(j,i)=gcart(j,i)+gloc_sc(2,i-1,icg)*
227      &     dtauangle(j,2,2,i+2)
228 c          write(iout,*) "numer",i,gloc_sc(2,i-1,icg),
229 c     &    dtauangle(j,2,2,i+2)
230           endif
231           if (itype(i+2).ne.10) then
232            gcart(j,i)=gcart(j,i)+gloc_sc(2,i,icg)*
233      &     dtauangle(j,2,1,i+3)
234           endif
235          enddo
236         enddo
237       endif     
238 c  Setting dE/ddnres-1       
239       if(nres.ge.4) then
240          do j=1,3
241          if ((itype(nres-1).ne.10).and.(itype(nres-1).ne.ntyp1)) then
242          gxcart(j,nres-1)=gxcart(j,nres-1)+gloc_sc(2,nres-3,icg)
243      &    *dtauangle(j,2,3,nres)
244 c          write (iout,*) "gxcart(nres-1)", gloc_sc(2,nres-3,icg),
245 c     &     dtauangle(j,2,3,nres), gxcart(j,nres-1)
246          if (itype(nres-2).ne.10) then
247         gxcart(j,nres-1)=gxcart(j,nres-1)+gloc_sc(3,nres-3,icg)
248      &    *dtauangle(j,3,3,nres)
249           endif
250          if ((itype(nres).ne.10).and.(itype(nres).ne.ntyp1)) then
251         gxcart(j,nres-1)=gxcart(j,nres-1)-gloc_sc(3,nres-2,icg)
252      &    *dtauangle(j,3,1,nres+1)
253         gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(3,nres-2,icg)
254      &    *dtauangle(j,3,2,nres+1)
255           endif
256          endif
257          if ((itype(nres-2).ne.10).and.(itype(nres-2).ne.ntyp1)) then
258             gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(1,nres-3,icg)*
259      &   dtauangle(j,1,3,nres)
260          endif
261           if ((itype(nres).ne.10).and.(itype(nres).ne.ntyp1)) then
262             gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(2,nres-2,icg)*
263      &     dtauangle(j,2,2,nres+1)
264 c           write (iout,*) "gcart(nres-1)", gloc_sc(2,nres-2,icg),
265 c     &     dtauangle(j,2,2,nres+1), itype(nres-1),itype(nres)
266            endif
267          enddo
268       endif
269 c  Settind dE/ddnres       
270        if ((nres.ge.3).and.(itype(nres).ne.10).and.
271      &    (itype(nres).ne.ntyp1))then
272        do j=1,3
273         gxcart(j,nres)=gxcart(j,nres)+gloc_sc(3,nres-2,icg)
274      & *dtauangle(j,3,3,nres+1)+gloc_sc(2,nres-2,icg)
275      & *dtauangle(j,2,3,nres+1)
276         enddo
277        endif
278 c   The side-chain vector derivatives
279 C      if (SELFGUIDE.gt.0) then
280 C      do j=1,3
281 C       gcart(j,afmbeg)=gcart(j,afmbeg)+gcart(j,afmend)
282 C       gcart(j,afmbeg)=0.0d0
283 C       gcart(j,afmend)=0.0d0
284 C      enddo
285 C      endif
286       return
287       end       
288         
289