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