update new files
[unres.git] / source / maxlik / src-Fmatch_safe / 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 "DIMENSIONS.ZSCOPT"
9       include 'COMMON.VAR'
10       include 'COMMON.CHAIN'
11       include 'COMMON.DERIV'
12       include 'COMMON.GEO'
13       include 'COMMON.LOCAL'
14       include 'COMMON.INTERACT'
15       include 'COMMON.MD'
16       include 'COMMON.IOUNITS'
17       include 'COMMON.SCCOR' 
18       include 'COMMON.CONTROL'
19       include "COMMON.ENERGIES"
20 c   calculating dE/ddc1     
21 C       print *,"wchodze22",ialph(2,1) 
22        if (nres.lt.3) go to 18
23        do j=1,3
24          gcart(j,1)=gcart(j,1)+gloc(1,icg)*dphi(j,1,4)
25      &     +gloc(nres-2,icg)*dtheta(j,1,3) 
26          do k=1,n_ene
27            gcompon(k,j,1)=gcompon(k,j,1)+gloc_compon(k,1)*dphi(j,1,4)
28      &     +gloc_compon(k,nres-2)*dtheta(j,1,3)
29          enddo
30          if(itype(2).ne.10) then
31            gcart(j,1)=gcart(j,1)+gloc(ialph(2,1),icg)*dalpha(j,1,2)+
32      &     gloc(ialph(2,1)+nside,icg)*domega(j,1,2)        
33            do k=1,n_ene
34              gcompon(k,j,1)=gcompon(k,j,1)
35      &         +gloc_compon(k,ialph(2,1))*dalpha(j,1,2)
36      &         +gloc_compon(k,ialph(2,1)+nside)*domega(j,1,2)
37            enddo
38          endif
39        enddo
40 C       print *,"wchodze22",ialph(2,1)
41 c     Calculating the remainder of dE/ddc2
42        do j=1,3
43          gcart(j,2)=gcart(j,2)+gloc(1,icg)*dphi(j,2,4)+
44      &   gloc(nres-2,icg)*dtheta(j,2,3)+gloc(nres-1,icg)*dtheta(j,1,4)
45          do k=1,n_ene
46            gcompon(k,j,2)=gcompon(k,j,2)
47      &       +gloc_compon(k,1)*dphi(j,2,4)
48      &       +gloc_compon(k,nres-2)*dtheta(j,2,3)
49      &       +gloc_compon(k,nres-1)*dtheta(j,1,4)
50          enddo
51         if(itype(2).ne.10) then
52           gcart(j,2)=gcart(j,2)+gloc(ialph(2,1),icg)*dalpha(j,2,2)+
53      &    gloc(ialph(2,1)+nside,icg)*domega(j,2,2)
54           do k=1,n_ene
55             gcompon(k,j,2)=gcompon(k,j,2)
56      &        +gloc_compon(k,ialph(2,1))*dalpha(j,2,2)+
57      &         gloc_compon(k,ialph(2,1)+nside)*domega(j,2,2)
58
59           enddo
60         endif
61         if(itype(3).ne.10) then
62           gcart(j,2)=gcart(j,2)+gloc(ialph(3,1),icg)*dalpha(j,1,3)+
63      &    gloc(ialph(3,1)+nside,icg)*domega(j,1,3)
64           do k=1,n_ene
65             gcompon(k,j,2)=gcompon(k,j,2)
66      &        +gloc_compon(k,ialph(3,1))*dalpha(j,1,3)+
67      &         gloc_compon(k,ialph(3,1)+nside)*domega(j,1,3)
68           enddo
69         endif
70         if(nres.gt.4) then
71           gcart(j,2)=gcart(j,2)+gloc(2,icg)*dphi(j,1,5)
72           do k=1,n_ene
73             gcompon(k,j,2)=gcompon(k,j,2)+gloc_compon(k,2)*dphi(j,1,5)
74           enddo
75         endif                   
76        enddo
77 C       print *,"wchodze22",ialph(2,1)
78 c  If there are only five residues       
79        if(nres.eq.5) then
80          do j=1,3
81            gcart(j,3)=gcart(j,3)+gloc(1,icg)*dphi(j,3,4)+gloc(2,icg)*
82      &     dphi(j,2,5)+gloc(nres-1,icg)*dtheta(j,2,4)+gloc(nres,icg)*
83      &     dtheta(j,1,5)
84            do k=1,n_ene
85              gcompon(k,j,3)=gcompon(k,j,3)+gloc_compon(k,1)*dphi(j,3,4)+
86      &         gloc_compon(k,2)*dphi(j,2,5)
87      &           +gloc_compon(k,nres-1)*dtheta(j,2,4)
88      &           +gloc_compon(k,nres)*dtheta(j,1,5)
89            enddo
90          if(itype(3).ne.10) then
91            gcart(j,3)=gcart(j,3)+gloc(ialph(3,1),icg)*
92      &     dalpha(j,2,3)+gloc(ialph(3,1)+nside,icg)*domega(j,2,3)
93            do k=1,n_ene
94              gcompon(k,j,3)=gcompon(k,j,3)
95      &          +gloc_compon(k,ialph(3,1))*dalpha(j,2,3)
96      &          +gloc_compon(k,ialph(3,1)+nside)*domega(j,2,3)
97            enddo
98          endif
99          if(itype(4).ne.10) then
100            gcart(j,3)=gcart(j,3)+gloc(ialph(4,1),icg)*
101      &     dalpha(j,1,4)+gloc(ialph(4,1)+nside,icg)*domega(j,1,4)
102            do k=1,n_ene
103              gcompon(k,j,3)=gcompon(k,j,3)
104      &         +gloc_compon(k,ialph(4,1))*dalpha(j,1,4)
105      &         +gloc_compon(k,ialph(4,1)+nside)*domega(j,1,4)
106            enddo
107          endif
108         enddo
109        endif
110 c    If there are more than five residues
111       if(nres.gt.5) then
112 C       print *,"wchodze22",ialph(2,1)
113         do i=3,nres-3
114 C        print *,i,ialph(i,1)+nside
115          do j=1,3
116           gcart(j,i)=gcart(j,i)+gloc(i-2,icg)*dphi(j,3,i+1)
117      &    +gloc(i-1,icg)*dphi(j,2,i+2)+
118      &    gloc(i,icg)*dphi(j,1,i+3)+gloc(nres+i-4,icg)*dtheta(j,2,i+1)+
119      &    gloc(nres+i-3,icg)*dtheta(j,1,i+2)
120           do k=1,n_ene
121             gcompon(k,j,i)=gcompon(k,j,i)
122      &        +gloc_compon(k,i-2)*dphi(j,3,i+1)
123      &        +gloc_compon(k,i-1)*dphi(j,2,i+2)+
124      &         gloc_compon(k,i)*dphi(j,1,i+3)
125      &        +gloc_compon(k,nres+i-4)*dtheta(j,2,i+1)+
126      &         gloc_compon(k,nres+i-3)*dtheta(j,1,i+2)
127           enddo
128           if((itype(i).ne.10).and.(itype(i).ne.ntyp1)) then
129            gcart(j,i)=gcart(j,i)+gloc(ialph(i,1),icg)*dalpha(j,2,i)+
130      &     gloc(ialph(i,1)+nside,icg)*domega(j,2,i)
131            do k=1,n_ene
132              gcompon(k,j,i)=gcompon(k,j,i)
133      &         +gloc_compon(k,ialph(i,1))*dalpha(j,2,i)+
134      &          gloc_compon(k,ialph(i,1)+nside)*domega(j,2,i)
135            enddo
136           endif
137           if((itype(i+1).ne.10).and.(itype(i+1).ne.ntyp1)) then
138            gcart(j,i)=gcart(j,i)+gloc(ialph(i+1,1),icg)*dalpha(j,1,i+1)
139      &     +gloc(ialph(i+1,1)+nside,icg)*domega(j,1,i+1)
140            do k=1,n_ene
141              gcompon(k,j,i)=gcompon(k,j,i)
142      &         +gloc_compon(k,ialph(i+1,1))*dalpha(j,1,i+1)
143      &         +gloc_compon(k,ialph(i+1,1)+nside)*domega(j,1,i+1)
144            enddo
145           endif
146          enddo
147         enddo
148       endif
149 C       print *,"wchodze22",ialph(2,1)
150
151 c  Setting dE/ddnres-2       
152       if(nres.gt.5) then
153          do j=1,3
154            gcart(j,nres-2)=gcart(j,nres-2)+gloc(nres-4,icg)*
155      &     dphi(j,3,nres-1)+gloc(nres-3,icg)*dphi(j,2,nres)
156      &     +gloc(2*nres-6,icg)*
157      &     dtheta(j,2,nres-1)+gloc(2*nres-5,icg)*dtheta(j,1,nres)
158            do k=1,n_ene
159              gcompon(k,j,nres-2)=gcompon(k,j,nres-2)
160      &          +gloc_compon(k,nres-4)*dphi(j,3,nres-1)
161      &          +gloc_compon(k,nres-3)*dphi(j,2,nres)
162      &          +gloc_compon(k,2*nres-6)*dtheta(j,2,nres-1)
163      &          +gloc_compon(k,2*nres-5)*dtheta(j,1,nres)
164            enddo
165           if(itype(nres-2).ne.10) then
166               gcart(j,nres-2)=gcart(j,nres-2)+gloc(ialph(nres-2,1),icg)*
167      &        dalpha(j,2,nres-2)+gloc(ialph(nres-2,1)+nside,icg)*
168      &        domega(j,2,nres-2)
169               do k=1,n_ene
170                 gcompon(k,j,nres-2)=gcompon(k,j,nres-2)+
171      &            gloc_compon(k,ialph(nres-2,1))*dalpha(j,2,nres-2)
172      &          +gloc_compon(k,ialph(nres-2,1)+nside)*domega(j,2,nres-2)
173               enddo
174           endif
175           if(itype(nres-1).ne.10) then
176              gcart(j,nres-2)=gcart(j,nres-2)+gloc(ialph(nres-1,1),icg)*
177      &       dalpha(j,1,nres-1)+gloc(ialph(nres-1,1)+nside,icg)*
178      &       domega(j,1,nres-1)
179              do k=1,n_ene
180                gcompon(k,j,nres-2)=gcompon(k,j,nres-2)
181      &           +gloc_compon(k,ialph(nres-1,1))*dalpha(j,1,nres-1)
182      &          +gloc_compon(k,ialph(nres-1,1)+nside)*domega(j,1,nres-1)
183              enddo
184           endif
185          enddo
186       endif 
187 c  Settind dE/ddnres-1       
188        do j=1,3
189         gcart(j,nres-1)=gcart(j,nres-1)+gloc(nres-3,icg)*dphi(j,3,nres)+
190      &  gloc(2*nres-5,icg)*dtheta(j,2,nres)
191         do k=1,n_ene
192           gcompon(k,j,nres-1)=gcompon(k,j,nres-1)
193      &      +gloc_compon(k,nres-3)*dphi(j,3,nres)
194      &      +gloc_compon(k,2*nres-5)*dtheta(j,2,nres)
195         enddo
196         if(itype(nres-1).ne.10) then
197           gcart(j,nres-1)=gcart(j,nres-1)+gloc(ialph(nres-1,1),icg)*
198      &    dalpha(j,2,nres-1)+gloc(ialph(nres-1,1)+nside,icg)*
199      &    domega(j,2,nres-1)
200           do k=1,n_ene
201             gcompon(k,j,nres-1)=gcompon(k,j,nres-1)
202      &        +gloc_compon(k,ialph(nres-1,1))*dalpha(j,2,nres-1)
203      &        +gloc_compon(k,ialph(nres-1,1)+nside)*domega(j,2,nres-1)
204           enddo
205         endif
206         enddo
207 c   The side-chain vector derivatives
208         do i=2,nres-1
209          if(itype(i).ne.10 .and. itype(i).ne.ntyp1) then
210             do j=1,3
211               gxcart(j,i)=gxcart(j,i)+gloc(ialph(i,1),icg)*dalpha(j,3,i)
212      &        +gloc(ialph(i,1)+nside,icg)*domega(j,3,i)
213               do k=1,n_ene
214                 gcomponx(k,j,i)=gcomponx(k,j,i)
215      &            +gloc_compon(k,ialph(i,1))*dalpha(j,3,i)
216      &            +gloc_compon(k,ialph(i,1)+nside)*domega(j,3,i)
217               enddo
218             enddo
219          endif
220        enddo
221   18   continue
222 #ifdef SCCORR
223 c----------------------------------------------------------------------
224 C INTERTYP=1 SC...Ca...Ca...Ca
225 C INTERTYP=2 Ca...Ca...Ca...SC
226 C INTERTYP=3 SC...Ca...Ca...SC
227 c   calculating dE/ddc1      
228 c       do i=1,nres
229 c       gloc(i,icg)=0.0D0
230 c          write (iout,*) "poczotkoawy",i,gloc_sc(1,i,icg)
231 c       enddo
232 C       print *,"tu dochodze??"
233        if (nres.lt.2) return
234        if ((nres.lt.3).and.(itype(1).eq.10)) return
235        if ((itype(1).ne.10).and.(itype(1).ne.ntyp1)) then
236         do j=1,3
237 cc Derviative was calculated for oposite vector of side chain therefore
238 c there is "-" sign before gloc_sc
239          gxcart(j,1)=gxcart(j,1)-gloc_sc(1,0,icg)*
240      &     dtauangle(j,1,1,3)
241          gcomponx(19,j,1)=gcomponx(19,j,1)-gloc_sc(1,0,icg)*
242      &     dtauangle(j,1,1,3)
243          gcart(j,1)=gcart(j,1)+gloc_sc(1,0,icg)*
244      &     dtauangle(j,1,2,3)
245          gcompon(19,j,1)=gcompon(19,j,1)+gloc_sc(1,0,icg)*
246      &     dtauangle(j,1,2,3)
247           if ((itype(2).ne.10).and.(itype(2).ne.ntyp1)) then
248          gxcart(j,1)= gxcart(j,1)
249      &               -gloc_sc(3,0,icg)*dtauangle(j,3,1,3)
250          gcomponx(19,j,1)=gcomponx(19,j,1)
251      &               -gloc_sc(3,0,icg)*dtauangle(j,3,1,3)
252          gcart(j,1)=gcart(j,1)+gloc_sc(3,0,icg)*
253      &       dtauangle(j,3,2,3)
254          gcompon(19,j,1)=gcompon(19,j,1)+gloc_sc(3,0,icg)*
255      &       dtauangle(j,3,2,3)
256           endif
257        enddo
258        endif
259          if ((nres.ge.3).and.(itype(3).ne.10).and.(itype(3).ne.ntyp1))
260      & then
261          do j=1,3
262          gcart(j,1)=gcart(j,1)+gloc_sc(2,1,icg)*dtauangle(j,2,1,4)
263          gcompon(19,j,1)=gcompon(19,j,1)
264      &     +gloc_sc(2,1,icg)*dtauangle(j,2,1,4)
265          enddo
266          endif
267 c   As potetnial DO NOT depend on omicron anlge their derivative is
268 c   ommited 
269 c     &     +gloc_sc(intertyp,nres-2,icg)*dtheta(j,1,3)  
270
271 c     Calculating the remainder of dE/ddc2
272        do j=1,3
273          if((itype(2).ne.10).and.(itype(2).ne.ntyp1)) then
274            if (itype(1).ne.10) then
275              gxcart(j,2)=gxcart(j,2)+
276      &                         gloc_sc(3,0,icg)*dtauangle(j,3,3,3)
277              gcomponx(19,j,2)=gcomponx(19,j,2)+
278      &                         gloc_sc(3,0,icg)*dtauangle(j,3,3,3)
279            endif
280         if ((itype(3).ne.10).and.(nres.ge.3).and.(itype(3).ne.ntyp1))
281      &   then
282            gxcart(j,2)=gxcart(j,2)-gloc_sc(3,1,icg)*dtauangle(j,3,1,4)
283            gcomponx(19,j,2)=gcomponx(19,j,2)
284      &       -gloc_sc(3,1,icg)*dtauangle(j,3,1,4)
285 cc                  the   - above is due to different vector direction
286            gcart(j,2)=gcart(j,2)+gloc_sc(3,1,icg)*dtauangle(j,3,2,4)
287            gcompon(19,j,2)=gcompon(19,j,2)
288      &       +gloc_sc(3,1,icg)*dtauangle(j,3,2,4)
289           endif
290           if (nres.gt.3) then
291            gxcart(j,2)=gxcart(j,2)-gloc_sc(1,1,icg)*dtauangle(j,1,1,4)
292            gcomponx(19,j,2)=gcomponx(19,j,2)
293      &       -gloc_sc(1,1,icg)*dtauangle(j,1,1,4)
294 cc                  the   - above is due to different vector direction
295            gcart(j,2)=gcart(j,2)+gloc_sc(1,1,icg)*dtauangle(j,1,2,4)
296            gcompon(19,j,2)=gcompon(19,j,2)
297      &        +gloc_sc(1,1,icg)*dtauangle(j,1,2,4)
298 c          write(iout,*) gloc_sc(1,1,icg),dtauangle(j,1,2,4),"gcart"
299 c           write(iout,*) gloc_sc(1,1,icg),dtauangle(j,1,1,4),"gx"
300           endif
301          endif
302          if ((itype(1).ne.10).and.(itype(1).ne.ntyp1)) then
303           gcart(j,2)=gcart(j,2)+gloc_sc(1,0,icg)*dtauangle(j,1,3,3)
304           gcompon(19,j,2)=gcompon(19,j,2)
305      &       +gloc_sc(1,0,icg)*dtauangle(j,1,3,3)
306 c           write(iout,*)  gloc_sc(1,0,icg),dtauangle(j,1,3,3)
307         endif
308          if ((itype(3).ne.10).and.(nres.ge.3)) then
309           gcart(j,2)=gcart(j,2)+gloc_sc(2,1,icg)*dtauangle(j,2,2,4)
310           gcompon(19,j,2)=gcompon(19,j,2)
311      &       +gloc_sc(2,1,icg)*dtauangle(j,2,2,4)
312 c           write(iout,*) gloc_sc(2,1,icg),dtauangle(j,2,2,4)
313          endif
314          if ((itype(4).ne.10).and.(nres.ge.4)) then
315           gcart(j,2)=gcart(j,2)+gloc_sc(2,2,icg)*dtauangle(j,2,1,5)
316           gcompon(19,j,2)=gcompon(19,j,2)
317      &        +gloc_sc(2,2,icg)*dtauangle(j,2,1,5)
318 c           write(iout,*) gloc_sc(2,2,icg),dtauangle(j,2,1,5)
319          endif
320
321 c      write(iout,*) gcart(j,2),itype(2),itype(1),itype(3), "gcart2"
322        enddo
323 c    If there are more than five residues
324       if(nres.ge.5) then                        
325         do i=3,nres-2
326          do j=1,3
327 c          write(iout,*) "before", gcart(j,i)
328           if ((itype(i).ne.10).and.(itype(i).ne.ntyp1)) then
329           gxcart(j,i)=gxcart(j,i)+gloc_sc(2,i-2,icg)
330      &    *dtauangle(j,2,3,i+1)
331      &    -gloc_sc(1,i-1,icg)*dtauangle(j,1,1,i+2)
332           gcomponx(19,j,i)=gcomponx(19,j,i)+gloc_sc(2,i-2,icg)
333      &    *dtauangle(j,2,3,i+1)
334      &    -gloc_sc(1,i-1,icg)*dtauangle(j,1,1,i+2)
335           gcart(j,i)=gcart(j,i)+gloc_sc(1,i-1,icg)
336      &    *dtauangle(j,1,2,i+2)
337           gcompon(19,j,i)=gcompon(19,j,i)+gloc_sc(1,i-1,icg)
338      &    *dtauangle(j,1,2,i+2)
339 c                   write(iout,*) "new",j,i,
340 c     &  gcart(j,i),gloc_sc(1,i-1,icg),dtauangle(j,1,2,i+2)
341           if (itype(i-1).ne.10) then
342            gxcart(j,i)=gxcart(j,i)+gloc_sc(3,i-2,icg)
343      &*dtauangle(j,3,3,i+1)
344            gcomponx(19,j,i)=gcomponx(19,j,i)+gloc_sc(3,i-2,icg)
345      &*dtauangle(j,3,3,i+1)
346           endif
347           if (itype(i+1).ne.10) then
348            gxcart(j,i)=gxcart(j,i)-gloc_sc(3,i-1,icg)
349      &*dtauangle(j,3,1,i+2)
350            gcomponx(19,j,i)=gcomponx(19,j,i)-gloc_sc(3,i-1,icg)
351      &*dtauangle(j,3,1,i+2)
352            gcart(j,i)=gcart(j,i)+gloc_sc(3,i-1,icg)
353      &*dtauangle(j,3,2,i+2)
354            gcompon(19,j,i)=gcompon(19,j,i)+gloc_sc(3,i-1,icg)
355      &*dtauangle(j,3,2,i+2)
356           endif
357           endif
358           if (itype(i-1).ne.10) then
359            gcart(j,i)=gcart(j,i)+gloc_sc(1,i-2,icg)*
360      &     dtauangle(j,1,3,i+1)
361            gcompon(19,j,i)=gcompon(19,j,i)+gloc_sc(1,i-2,icg)*
362      &     dtauangle(j,1,3,i+1)
363           endif
364           if (itype(i+1).ne.10) then
365            gcart(j,i)=gcart(j,i)+gloc_sc(2,i-1,icg)*
366      &     dtauangle(j,2,2,i+2)
367            gcompon(19,j,i)= gcompon(19,j,i)+gloc_sc(2,i-1,icg)*
368      &     dtauangle(j,2,2,i+2)
369 c          write(iout,*) "numer",i,gloc_sc(2,i-1,icg),
370 c     &    dtauangle(j,2,2,i+2)
371           endif
372           if (itype(i+2).ne.10) then
373            gcart(j,i)=gcart(j,i)+gloc_sc(2,i,icg)*
374      &     dtauangle(j,2,1,i+3)
375            gcompon(19,j,i)=gcompon(19,j,i)+gloc_sc(2,i,icg)*
376      &     dtauangle(j,2,1,i+3)
377           endif
378          enddo
379         enddo
380       endif     
381 c  Setting dE/ddnres-1       
382       if(nres.ge.4) then
383          do j=1,3
384          if ((itype(nres-1).ne.10).and.(itype(nres-1).ne.ntyp1)) then
385          gxcart(j,nres-1)=gxcart(j,nres-1)+gloc_sc(2,nres-3,icg)
386      &    *dtauangle(j,2,3,nres)
387          gcomponx(19,j,nres-1)=gcomponx(19,j,nres-1)
388      &     +gloc_sc(2,nres-3,icg)*dtauangle(j,2,3,nres)
389 c          write (iout,*) "gxcart(nres-1)", gloc_sc(2,nres-3,icg),
390 c     &     dtauangle(j,2,3,nres), gxcart(j,nres-1)
391          if (itype(nres-2).ne.10) then
392         gxcart(j,nres-1)=gxcart(j,nres-1)+gloc_sc(3,nres-3,icg)
393      &    *dtauangle(j,3,3,nres)
394         gcomponx(19,j,nres-1)=gcomponx(19,j,nres-1)
395      &    +gloc_sc(3,nres-3,icg)*dtauangle(j,3,3,nres)
396           endif
397          if ((itype(nres).ne.10).and.(itype(nres).ne.ntyp1)) then
398         gxcart(j,nres-1)=gxcart(j,nres-1)-gloc_sc(3,nres-2,icg)
399      &    *dtauangle(j,3,1,nres+1)
400         gcomponx(19,j,nres-1)=gcomponx(19,j,nres-1)
401      &    -gloc_sc(3,nres-2,icg)*dtauangle(j,3,1,nres+1)
402         gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(3,nres-2,icg)
403      &    *dtauangle(j,3,2,nres+1)
404         gcompon(19,j,nres-1)=gcompon(19,j,nres-1)+gloc_sc(3,nres-2,icg)
405      &    *dtauangle(j,3,2,nres+1)
406           endif
407          endif
408          if ((itype(nres-2).ne.10).and.(itype(nres-2).ne.ntyp1)) then
409             gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(1,nres-3,icg)*
410      &   dtauangle(j,1,3,nres)
411             gcompon(19,j,nres-1)=gcompon(19,j,nres-1)
412      &        +gloc_sc(1,nres-3,icg)*dtauangle(j,1,3,nres)
413          endif
414           if ((itype(nres).ne.10).and.(itype(nres).ne.ntyp1)) then
415             gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(2,nres-2,icg)*
416      &     dtauangle(j,2,2,nres+1)
417             gcompon(19,j,nres-1)=gcompon(19,j,nres-1)
418      &        +gloc_sc(2,nres-2,icg)*dtauangle(j,2,2,nres+1)
419 c           write (iout,*) "gcart(nres-1)", gloc_sc(2,nres-2,icg),
420 c     &     dtauangle(j,2,2,nres+1), itype(nres-1),itype(nres)
421            endif
422          enddo
423       endif
424 c  Settind dE/ddnres       
425        if ((nres.ge.3).and.(itype(nres).ne.10).and.
426      &    (itype(nres).ne.ntyp1))then
427        do j=1,3
428         gxcart(j,nres)=gxcart(j,nres)+gloc_sc(3,nres-2,icg)
429      & *dtauangle(j,3,3,nres+1)+gloc_sc(2,nres-2,icg)
430      & *dtauangle(j,2,3,nres+1)
431         gcomponx(19,j,nres)=gcomponx(19,j,nres)+gloc_sc(2,nres-2,icg)
432      & *dtauangle(j,2,3,nres+1) 
433         enddo
434        endif
435 c   The side-chain vector derivatives
436 C      if (SELFGUIDE.gt.0) then
437 C      do j=1,3
438 C       gcart(j,afmbeg)=gcart(j,afmbeg)+gcart(j,afmend)
439 C       gcart(j,afmbeg)=0.0d0
440 C       gcart(j,afmend)=0.0d0
441 C      enddo
442 C      endif
443 #endif
444       return
445       end       
446         
447