DO zmiany czytanie pisanie i cutoff
[unres.git] / source / unres / src_MD-M / energy_p_new_barrier.F
index 38c5306..635a41e 100644 (file)
@@ -296,6 +296,8 @@ C
       energia(17)=estr
       energia(20)=Uconst+Uconst_back
       energia(21)=esccor
+c    Here are the energies showed per procesor if the are more processors 
+c    per molecule then we sum it up in sum_energy subroutine 
 c      print *," Processor",myrank," calls SUM_ENERGY"
       call sum_energy(energia,.true.)
 c      print *," Processor",myrank," left SUM_ENERGY"
@@ -387,14 +389,14 @@ cMS$ATTRIBUTES C ::  proc_proc
 #ifdef SPLITELE
       etot=wsc*evdw+wscp*evdw2+welec*ees+wvdwpp*evdw1
      & +wang*ebe+wtor*etors+wscloc*escloc
-     & +wstrain*ehpb+nss*ebr+wcorr*ecorr+wcorr5*ecorr5
+     & +wstrain*ehpb+wcorr*ecorr+wcorr5*ecorr5
      & +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3
      & +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d
      & +wbond*estr+Uconst+wsccor*esccor
 #else
       etot=wsc*evdw+wscp*evdw2+welec*(ees+evdw1)
      & +wang*ebe+wtor*etors+wscloc*escloc
-     & +wstrain*ehpb+nss*ebr+wcorr*ecorr+wcorr5*ecorr5
+     & +wstrain*ehpb+wcorr*ecorr+wcorr5*ecorr5
      & +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3
      & +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d
      & +wbond*estr+Uconst+wsccor*esccor
@@ -1411,6 +1413,7 @@ C
       include 'COMMON.CALC'
       include 'COMMON.CONTROL'
       logical lprn
+      integer xshift,yshift,zshift
       evdw=0.0D0
 ccccc      energy_dec=.false.
 c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
@@ -1418,6 +1421,11 @@ c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
       lprn=.false.
 c     if (icall.eq.0) lprn=.false.
       ind=0
+C the loop over all 27 posible neigbours (for xshift=0,yshift=0,zshift=0
+C we have the original box)
+      do xshift=-1,1
+      do yshift=-1,1
+      do zshift=-1,1
       do i=iatsc_s,iatsc_e
         itypi=iabs(itype(i))
         if (itypi.eq.ntyp1) cycle
@@ -1425,6 +1433,32 @@ c     if (icall.eq.0) lprn=.false.
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
+C Return atom into box, boxxsize is size of box in x dimension
+  134   continue
+        if (xi.gt.((xshift+0.5d0)*boxxsize)) xi=xi-boxxsize
+        if (xi.lt.((xshift-0.5d0)*boxxsize)) xi=xi+boxxsize
+C Condition for being inside the proper box
+        if ((xi.gt.((xshift+0.5d0)*boxxsize)).or.
+     &       (xi.lt.((xshift-0.5d0)*boxxsize))) then
+        go to 134
+        endif
+  135   continue
+        if (yi.gt.((yshift+0.5d0)*boxysize)) yi=yi-boxysize
+        if (yi.lt.((yshift-0.5d0)*boxysize)) yi=yi+boxysize
+C Condition for being inside the proper box
+        if ((yi.gt.((yshift+0.5d0)*boxysize)).or.
+     &       (yi.lt.((yshift-0.5d0)*boxysize))) then
+        go to 135
+        endif
+  136   continue
+        if (zi.gt.((zshift+0.5d0)*boxzsize)) zi=zi-boxxsize
+        if (zi.lt.((zshift-0.5d0)*boxzsize)) zi=zi+boxxsize
+C Condition for being inside the proper box
+        if ((zi.gt.((zshift+0.5d0)*boxzsize)).or.
+     &       (zi.lt.((zshift-0.5d0)*boxzsize))) then
+        go to 136
+        endif
+
         dxi=dc_norm(1,nres+i)
         dyi=dc_norm(2,nres+i)
         dzi=dc_norm(3,nres+i)
@@ -1465,12 +1499,41 @@ c           chip12=0.0D0
 c           alf1=0.0D0
 c           alf2=0.0D0
 c           alf12=0.0D0
-            xj=c(1,nres+j)-xi
-            yj=c(2,nres+j)-yi
-            zj=c(3,nres+j)-zi
+            xj=c(1,nres+j)
+            yj=c(2,nres+j)
+            zj=c(3,nres+j)
+C Return atom J into box the original box
+  137   continue
+        if (xj.gt.((0.5d0)*boxxsize)) xj=xj-boxxsize
+        if (xj.lt.((-0.5d0)*boxxsize)) xj=xj+boxxsize
+C Condition for being inside the proper box
+        if ((xj.gt.((0.5d0)*boxxsize)).or.
+     &       (xj.lt.((-0.5d0)*boxxsize))) then
+        go to 137
+        endif
+  138   continue
+        if (yj.gt.((0.5d0)*boxysize)) yj=yj-boxysize
+        if (yj.lt.((-0.5d0)*boxysize)) yj=yj+boxysize
+C Condition for being inside the proper box
+        if ((yj.gt.((0.5d0)*boxysize)).or.
+     &       (yj.lt.((-0.5d0)*boxysize))) then
+        go to 138
+        endif
+  139   continue
+        if (zj.gt.((0.5d0)*boxzsize)) zj=zj-boxxsize
+        if (zj.lt.((-0.5d0)*boxzsize)) zj=zj+boxxsize
+C Condition for being inside the proper box
+        if ((zj.gt.((0.5d0)*boxzsize)).or.
+     &       (zj.lt.((-0.5d0)*boxzsize))) then
+        go to 139
+        endif
+
             dxj=dc_norm(1,nres+j)
             dyj=dc_norm(2,nres+j)
             dzj=dc_norm(3,nres+j)
+            xj=xj-xi
+            yj=yj-yi
+            zj=zj-zi
 c            write (iout,*) "dcnorj",dxi*dxi+dyi*dyi+dzi*dzi
 c            write (iout,*) "j",j," dc_norm",
 c     &       dc_norm(1,nres+j),dc_norm(2,nres+j),dc_norm(3,nres+j)
@@ -1534,6 +1597,9 @@ C Calculate angular part of the gradient.
           enddo      ! j
         enddo        ! iint
       enddo          ! i
+      enddo          ! zshift
+      enddo          ! yshift
+      enddo          ! xshift
 c      write (iout,*) "Number of loop steps in EGB:",ind
 cccc      energy_dec=.false.
       return
@@ -2369,7 +2435,11 @@ c        if (i .gt. iatel_s+2) then
         enddo
 c        if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
         if (i.gt. nnt+1 .and. i.lt.nct+1) then
-          iti1 = itortyp(itype(i-1))
+          if (itype(i-1).le.ntyp) then
+            iti1 = itortyp(itype(i-1))
+          else
+            iti1=ntortyp+1
+          endif
         else
           iti1=ntortyp+1
         endif
@@ -2782,6 +2852,7 @@ c 9/27/08 AL Split the interaction loop to ensure load balancing of turn terms
 C
 C Loop over i,i+2 and i,i+3 pairs of the peptide groups
 C
+C 14/01/2014 TURN3,TUNR4 does no go under periodic boundry condition
       do i=iturn3_start,iturn3_end
         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
      &  .or. itype(i+2).eq.ntyp1 .or. itype(i+3).eq.ntyp1) cycle
@@ -2794,6 +2865,31 @@ C
         xmedi=c(1,i)+0.5d0*dxi
         ymedi=c(2,i)+0.5d0*dyi
         zmedi=c(3,i)+0.5d0*dzi
+C Return atom into box, boxxsize is size of box in x dimension
+  184   continue
+        if (xmedi.gt.((0.5d0)*boxxsize)) xmedi=xmedi-boxxsize
+        if (xmedi.lt.((-0.5d0)*boxxsize)) xmedi=xmedi+boxxsize
+C Condition for being inside the proper box
+        if ((xmedi.gt.((0.5d0)*boxxsize)).or.
+     &       (xmedi.lt.((-0.5d0)*boxxsize))) then
+        go to 184
+        endif
+  185   continue
+        if (ymedi.gt.((0.5d0)*boxysize)) ymedi=ymedi-boxysize
+        if (ymedi.lt.((-0.5d0)*boxysize)) ymedi=ymedi+boxysize
+C Condition for being inside the proper box
+        if ((ymedi.gt.((0.5d0)*boxysize)).or.
+     &       (ymedi.lt.((-0.5d0)*boxysize))) then
+        go to 185
+        endif
+  186   continue
+        if (zmedi.gt.((0.5d0)*boxzsize)) zmedi=zmedi-boxxsize
+        if (zmedi.lt.((-0.5d0)*boxzsize)) zmedi=zmedi+boxxsize
+C Condition for being inside the proper box
+        if ((zmedi.gt.((0.5d0)*boxzsize)).or.
+     &       (zmedi.lt.((-0.5d0)*boxzsize))) then
+        go to 186
+        endif
         num_conti=0
         call eelecij(i,i+2,ees,evdw1,eel_loc)
         if (wturn3.gt.0.0d0) call eturn3(i,eello_turn3)
         xmedi=c(1,i)+0.5d0*dxi
         ymedi=c(2,i)+0.5d0*dyi
         zmedi=c(3,i)+0.5d0*dzi
+C Return atom into box, boxxsize is size of box in x dimension
+  194   continue
+        if (xmedi.gt.((0.5d0)*boxxsize)) xmedi=xmedi-boxxsize
+        if (xmedi.lt.((-0.5d0)*boxxsize)) xmedi=xmedi+boxxsize
+C Condition for being inside the proper box
+        if ((xmedi.gt.((0.5d0)*boxxsize)).or.
+     &       (xmedi.lt.((-0.5d0)*boxxsize))) then
+        go to 194
+        endif
+  195   continue
+        if (ymedi.gt.((0.5d0)*boxysize)) ymedi=ymedi-boxysize
+        if (ymedi.lt.((-0.5d0)*boxysize)) ymedi=ymedi+boxysize
+C Condition for being inside the proper box
+        if ((ymedi.gt.((0.5d0)*boxysize)).or.
+     &       (ymedi.lt.((-0.5d0)*boxysize))) then
+        go to 195
+        endif
+  196   continue
+        if (zmedi.gt.((0.5d0)*boxzsize)) zmedi=zmedi-boxxsize
+        if (zmedi.lt.((-0.5d0)*boxzsize)) zmedi=zmedi+boxxsize
+C Condition for being inside the proper box
+        if ((zmedi.gt.((0.5d0)*boxzsize)).or.
+     &       (zmedi.lt.((-0.5d0)*boxzsize))) then
+        go to 196
+        endif
+
         num_conti=num_cont_hb(i)
         call eelecij(i,i+3,ees,evdw1,eel_loc)
         if (wturn4.gt.0.0d0 .and. itype(i+2).ne.ntyp1) 
      &   call eturn4(i,eello_turn4)
         num_cont_hb(i)=num_conti
       enddo   ! i
+C Loop over all neighbouring boxes
+      do xshift=-1,1
+      do yshift=-1,1
+      do zshift=-1,1
 c
 c Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
 c
@@ -2832,6 +2958,32 @@ c
         xmedi=c(1,i)+0.5d0*dxi
         ymedi=c(2,i)+0.5d0*dyi
         zmedi=c(3,i)+0.5d0*dzi
+C Return atom into box, boxxsize is size of box in x dimension
+  164   continue
+        if (xmedi.gt.((xshift+0.5d0)*boxxsize)) xmedi=xmedi-boxxsize
+        if (xmedi.lt.((xshift-0.5d0)*boxxsize)) xmedi=xmedi+boxxsize
+C Condition for being inside the proper box
+        if ((xmedi.gt.((xshift+0.5d0)*boxxsize)).or.
+     &       (xmedi.lt.((xshift-0.5d0)*boxxsize))) then
+        go to 164
+        endif
+  165   continue
+        if (ymedi.gt.((yshift+0.5d0)*boxysize)) ymedi=ymedi-boxysize
+        if (ymedi.lt.((yshift-0.5d0)*boxysize)) ymedi=ymedi+boxysize
+C Condition for being inside the proper box
+        if ((ymedi.gt.((yshift+0.5d0)*boxysize)).or.
+     &       (ymedi.lt.((yshift-0.5d0)*boxysize))) then
+        go to 165
+        endif
+  166   continue
+        if (zmedi.gt.((zshift+0.5d0)*boxzsize)) zmedi=zmedi-boxxsize
+        if (zmedi.lt.((zshift-0.5d0)*boxzsize)) zmedi=zmedi+boxxsize
+C Condition for being inside the proper box
+        if ((zmedi.gt.((zshift+0.5d0)*boxzsize)).or.
+     &       (zmedi.lt.((zshift-0.5d0)*boxzsize))) then
+        go to 166
+        endif
+
 c        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         num_conti=num_cont_hb(i)
         do j=ielstart(i),ielend(i)
@@ -2841,6 +2993,10 @@ c          write (iout,*) i,j,itype(i),itype(j)
         enddo ! j
         num_cont_hb(i)=num_conti
       enddo   ! i
+      enddo   ! zshift
+      enddo   ! yshift
+      enddo   ! xshift
+
 c      write (iout,*) "Number of loop steps in EELEC:",ind
 cd      do i=1,nres
 cd        write (iout,'(i3,3f10.5,5x,3f10.5)') 
@@ -2905,9 +3061,41 @@ c          ind=ind+1
           dx_normj=dc_norm(1,j)
           dy_normj=dc_norm(2,j)
           dz_normj=dc_norm(3,j)
-          xj=c(1,j)+0.5D0*dxj-xmedi
-          yj=c(2,j)+0.5D0*dyj-ymedi
-          zj=c(3,j)+0.5D0*dzj-zmedi
+C          xj=c(1,j)+0.5D0*dxj-xmedi
+C          yj=c(2,j)+0.5D0*dyj-ymedi
+C          zj=c(3,j)+0.5D0*dzj-zmedi
+          xj=c(1,j)+0.5D0*dxj
+          yj=c(2,j)+0.5D0*dyj
+          zj=c(3,j)+0.5D0*dzj
+C        if ((i+3).lt.j) then !this condition keeps for turn3 and turn4 not subject to PBC
+  174   continue
+        if (xj.gt.((0.5d0)*boxxsize)) xj=xj-boxxsize
+        if (xj.lt.((-0.5d0)*boxxsize)) xj=xj+boxxsize
+C Condition for being inside the proper box
+        if ((xj.gt.((0.5d0)*boxxsize)).or.
+     &       (xj.lt.((-0.5d0)*boxxsize))) then
+        go to 174
+        endif
+  175   continue
+        if (yj.gt.((0.5d0)*boxysize)) yj=yj-boxysize
+        if (yj.lt.((-0.5d0)*boxysize)) yj=yj+boxysize
+C Condition for being inside the proper box
+        if ((yj.gt.((0.5d0)*boxysize)).or.
+     &       (yj.lt.((-0.5d0)*boxysize))) then
+        go to 175
+        endif
+  176   continue
+        if (zj.gt.((0.5d0)*boxzsize)) zj=zj-boxxsize
+        if (zj.lt.((-0.5d0)*boxzsize)) zj=zj+boxxsize
+C Condition for being inside the proper box
+        if ((zj.gt.((0.5d0)*boxzsize)).or.
+     &       (zj.lt.((-0.5d0)*boxzsize))) then
+        go to 176
+        endif
+C        endif !endPBC condintion
+        xj=xj-xmedi
+        yj=yj-ymedi
+        zj=zj-zmedi
           rij=xj*xj+yj*yj+zj*zj
           rrmij=1.0D0/rij
           rij=dsqrt(rij)
@@ -2938,7 +3126,9 @@ cd     &      1.0D0/dsqrt(rrmij),evdwij,eesij,
 cd     &      xmedi,ymedi,zmedi,xj,yj,zj
 
           if (energy_dec) then 
-              write (iout,'(a6,2i5,0pf7.3)') 'evdw1',i,j,evdwij
+              write (iout,'(a6,2i5,0pf7.3,2i5,2e11.3)') 
+     &'evdw1',i,j,evdwij
+     &,iteli,itelj,aaa,evdw1
               write (iout,'(a6,2i5,0pf7.3)') 'ees',i,j,eesij
           endif
 
@@ -3270,6 +3460,9 @@ cd          write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
 
           if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
      &            'eelloc',i,j,eel_loc_ij
+           if (eel_loc_ij.ne.0)
+     &      write (iout,'(a4,2i4,8f9.5)')'chuj',
+     &     i,j,a22,muij(1),a23,muij(2),a32,muij(3),a33,muij(4)
 
           eel_loc=eel_loc+eel_loc_ij
 C Partial derivatives in virtual-bond dihedral angles gamma
@@ -3658,8 +3851,9 @@ c        write(iout,*) "iti1",iti1," iti2",iti2," iti3",iti3
         call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
         s3=0.5d0*(pizda(1,1)+pizda(2,2))
         eello_turn4=eello_turn4-(s1+s2+s3)
-        if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
-     &      'eturn4',i,j,-(s1+s2+s3)
+c             write(iout,*)'chujOWO', auxvec(1),b1(1,iti2)
+        if (energy_dec) write (iout,'(a6,2i5,0pf7.3,3f7.3)')
+     &      'eturn4',i,j,-(s1+s2+s3),s1,s2,s3
 cd        write (2,*) 'i,',i,' j',j,'eello_turn4',-(s1+s2+s3),
 cd     &    ' eello_turn4_num',8*eello_turn4_num
 C Derivatives in gamma(i)
       r0_scp=4.5d0
 cd    print '(a)','Enter ESCP'
 cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
+      do xshift=-1,1
+      do yshift=-1,1
+      do zshift=-1,1
       do i=iatscp_s,iatscp_e
         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         zi=0.5D0*(c(3,i)+c(3,i+1))
-
+C Return atom into box, boxxsize is size of box in x dimension
+  134   continue
+        if (xi.gt.((xshift+0.5d0)*boxxsize)) xi=xi-boxxsize
+        if (xi.lt.((xshift-0.5d0)*boxxsize)) xi=xi+boxxsize
+C Condition for being inside the proper box
+        if ((xi.gt.((xshift+0.5d0)*boxxsize)).or.
+     &       (xi.lt.((xshift-0.5d0)*boxxsize))) then
+        go to 134
+        endif
+  135   continue
+        if (yi.gt.((yshift+0.5d0)*boxysize)) yi=yi-boxysize
+        if (yi.lt.((yshift-0.5d0)*boxysize)) yi=yi+boxysize
+C Condition for being inside the proper box
+        if ((yi.gt.((yshift+0.5d0)*boxysize)).or.
+     &       (yi.lt.((yshift-0.5d0)*boxysize))) then
+        go to 135
+        endif
+  136   continue
+        if (zi.gt.((zshift+0.5d0)*boxzsize)) zi=zi-boxxsize
+        if (zi.lt.((zshift-0.5d0)*boxzsize)) zi=zi+boxxsize
+C Condition for being inside the proper box
+        if ((zi.gt.((zshift+0.5d0)*boxzsize)).or.
+     &       (zi.lt.((zshift-0.5d0)*boxzsize))) then
+        go to 136
+        endif
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
@@ -3846,9 +4067,36 @@ c         xj=c(1,nres+j)-xi
 c         yj=c(2,nres+j)-yi
 c         zj=c(3,nres+j)-zi
 C Uncomment following three lines for Ca-p interactions
-          xj=c(1,j)-xi
-          yj=c(2,j)-yi
-          zj=c(3,j)-zi
+          xj=c(1,j)
+          yj=c(2,j)
+          zj=c(3,j)
+  174   continue
+        if (xj.gt.((0.5d0)*boxxsize)) xj=xj-boxxsize
+        if (xj.lt.((-0.5d0)*boxxsize)) xj=xj+boxxsize
+C Condition for being inside the proper box
+        if ((xj.gt.((0.5d0)*boxxsize)).or.
+     &       (xj.lt.((-0.5d0)*boxxsize))) then
+        go to 174
+        endif
+  175   continue
+        if (yj.gt.((0.5d0)*boxysize)) yj=yj-boxysize
+        if (yj.lt.((-0.5d0)*boxysize)) yj=yj+boxysize
+C Condition for being inside the proper box
+        if ((yj.gt.((0.5d0)*boxysize)).or.
+     &       (yj.lt.((-0.5d0)*boxysize))) then
+        go to 175
+        endif
+  176   continue
+        if (zj.gt.((0.5d0)*boxzsize)) zj=zj-boxxsize
+        if (zj.lt.((-0.5d0)*boxzsize)) zj=zj+boxxsize
+C Condition for being inside the proper box
+        if ((zj.gt.((0.5d0)*boxzsize)).or.
+     &       (zj.lt.((-0.5d0)*boxzsize))) then
+        go to 176
+        endif
+          xj=xj-xi
+          yj=yj-yi
+          zj=zj-zi
           rij=xj*xj+yj*yj+zj*zj
           r0ij=r0_scp
           r0ijsq=r0ij*r0ij
@@ -3900,6 +4148,9 @@ cgrad          enddo
 
         enddo ! iint
       enddo ! i
+      enddo !zshift
+      enddo !yshift
+      enddo !xshift
       return
       end
 C-----------------------------------------------------------------------------
       evdw2_14=0.0d0
 cd    print '(a)','Enter ESCP'
 cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
+      do xshift=-1,1
+      do yshift=-1,1
+      do zshift=-1,1
       do i=iatscp_s,iatscp_e
         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         zi=0.5D0*(c(3,i)+c(3,i+1))
-
+C Return atom into box, boxxsize is size of box in x dimension
+  134   continue
+        if (xi.gt.((xshift+0.5d0)*boxxsize)) xi=xi-boxxsize
+        if (xi.lt.((xshift-0.5d0)*boxxsize)) xi=xi+boxxsize
+C Condition for being inside the proper box
+        if ((xi.gt.((xshift+0.5d0)*boxxsize)).or.
+     &       (xi.lt.((xshift-0.5d0)*boxxsize))) then
+        go to 134
+        endif
+  135   continue
+        if (yi.gt.((yshift+0.5d0)*boxysize)) yi=yi-boxysize
+        if (yi.lt.((yshift-0.5d0)*boxysize)) yi=yi+boxysize
+C Condition for being inside the proper box
+        if ((yi.gt.((yshift+0.5d0)*boxysize)).or.
+     &       (yi.lt.((yshift-0.5d0)*boxysize))) then
+        go to 135
+        endif
+  136   continue
+        if (zi.gt.((zshift+0.5d0)*boxzsize)) zi=zi-boxxsize
+        if (zi.lt.((zshift-0.5d0)*boxzsize)) zi=zi+boxxsize
+C Condition for being inside the proper box
+        if ((zi.gt.((zshift+0.5d0)*boxzsize)).or.
+     &       (zi.lt.((zshift-0.5d0)*boxzsize))) then
+        go to 136
+        endif
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
@@ -3942,9 +4220,36 @@ c         xj=c(1,nres+j)-xi
 c         yj=c(2,nres+j)-yi
 c         zj=c(3,nres+j)-zi
 C Uncomment following three lines for Ca-p interactions
-          xj=c(1,j)-xi
-          yj=c(2,j)-yi
-          zj=c(3,j)-zi
+          xj=c(1,j)
+          yj=c(2,j)
+          zj=c(3,j)
+  174   continue
+        if (xj.gt.((0.5d0)*boxxsize)) xj=xj-boxxsize
+        if (xj.lt.((-0.5d0)*boxxsize)) xj=xj+boxxsize
+C Condition for being inside the proper box
+        if ((xj.gt.((0.5d0)*boxxsize)).or.
+     &       (xj.lt.((-0.5d0)*boxxsize))) then
+        go to 174
+        endif
+  175   continue
+        if (yj.gt.((0.5d0)*boxysize)) yj=yj-boxysize
+        if (yj.lt.((-0.5d0)*boxysize)) yj=yj+boxysize
+C Condition for being inside the proper box
+        if ((yj.gt.((0.5d0)*boxysize)).or.
+     &       (yj.lt.((-0.5d0)*boxysize))) then
+        go to 175
+        endif
+  176   continue
+        if (zj.gt.((0.5d0)*boxzsize)) zj=zj-boxxsize
+        if (zj.lt.((-0.5d0)*boxzsize)) zj=zj+boxxsize
+C Condition for being inside the proper box
+        if ((zj.gt.((0.5d0)*boxzsize)).or.
+     &       (zj.lt.((-0.5d0)*boxzsize))) then
+        go to 176
+        endif
+          xj=xj-xi
+          yj=yj-yi
+          zj=zj-zi
           rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
           fac=rrij**expon2
           e1=fac*fac*aad(itypj,iteli)
@@ -3956,8 +4261,9 @@ C Uncomment following three lines for Ca-p interactions
           endif
           evdwij=e1+e2
           evdw2=evdw2+evdwij
-          if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
-     &        'evdw2',i,j,evdwij
+          if (energy_dec) write (iout,'(a6,2i5,0pf7.3,2i3,3e11.3)')
+     &        'evdw2',i,j,evdwij,iteli,itypj,fac,aad(itypj,iteli),
+     &       bad(itypj,iteli)
 C
 C Calculate contributions to the gradient in the virtual-bond and SC vectors.
 C
@@ -4000,6 +4306,9 @@ cgrad          enddo
 
         enddo ! iint
       enddo ! i
+      enddo !zshift
+      enddo !yshift
+      enddo !xshift
       do i=1,nct
         do j=1,3
           gvdwc_scp(j,i)=expon*gvdwc_scp(j,i)
@@ -4155,7 +4464,7 @@ c      dscj_inv=dsc_inv(itypj)
       cosphi=om12-om1*om2
       eij=akcm*deltad*deltad+akth*(deltat1*deltat1+deltat2*deltat2)
      &  +akct*deltad*deltat12
-     &  +v1ss*cosphi+v2ss*cosphi*cosphi+v3ss*cosphi*cosphi*cosphi
+     &  +v1ss*cosphi+v2ss*cosphi*cosphi+v3ss*cosphi*cosphi*cosphi+ebr
 c      write(iout,*) i,j,"rij",rij,"d0cm",d0cm," akcm",akcm," akth",akth,
 c     &  " akct",akct," deltad",deltad," deltat",deltat1,deltat2,
 c     &  " deltat12",deltat12," eij",eij 
       estr=0.0d0
       estr1=0.0d0
       do i=ibondp_start,ibondp_end
-        if (itype(i-1).eq.ntyp1 .or. itype(i).eq.ntyp1) then
-          estr1=estr1+gnmr1(vbld(i),-1.0d0,distchainmax)
-          do j=1,3
-          gradb(j,i-1)=gnmr1prim(vbld(i),-1.0d0,distchainmax)
-     &      *dc(j,i-1)/vbld(i)
-          enddo
-          if (energy_dec) write(iout,*) 
-     &       "estr1",i,gnmr1(vbld(i),-1.0d0,distchainmax)
-        else
+        if (itype(i-1).eq.ntyp1 .and. itype(i).eq.ntyp1) cycle
+c          estr1=estr1+gnmr1(vbld(i),-1.0d0,distchainmax)
+c          do j=1,3
+c          gradb(j,i-1)=gnmr1prim(vbld(i),-1.0d0,distchainmax)
+c     &      *dc(j,i-1)/vbld(i)
+c          enddo
+c          if (energy_dec) write(iout,*) 
+c     &       "estr1",i,gnmr1(vbld(i),-1.0d0,distchainmax)
+c        else
+C       Checking if it involves dummy (NH3+ or COO-) group
+         if (itype(i-1).eq.ntyp1 .or. itype(i).eq.ntyp1) then
+C YES   vbldpDUM is the equlibrium length of spring for Dummy atom
+        diff = vbld(i)-vbldpDUM
+         else
+C NO    vbldp0 is the equlibrium lenght of spring for peptide group
         diff = vbld(i)-vbldp0
-        if (energy_dec) write (iout,*) 
+         endif 
+        if (energy_dec) write (iout,'(a7,i5,4f7.3)') 
      &     "estr bb",i,vbld(i),vbldp0,diff,AKP*diff*diff
         estr=estr+diff*diff
         do j=1,3
           gradb(j,i-1)=AKP*diff*dc(j,i-1)/vbld(i)
         enddo
 c        write (iout,'(i5,3f10.5)') i,(gradb(j,i-1),j=1,3)
-        endif
+c        endif
       enddo
       estr=0.5d0*AKP*estr+estr1
 c
@@ -4363,6 +4679,7 @@ C In following comments this theta will be referred to as t_c.
              bthetk=bthet(k,itype2,ichir21,ichir22)
           endif
          thet_pred_mean=thet_pred_mean+athetk*y(k)+bthetk*z(k)
+c         write(iout,*) 'chuj tu', y(k),z(k)
         enddo
         dthett=thet_pred_mean*ssd
         thet_pred_mean=thet_pred_mean*ss+a0thet(it)
@@ -4399,8 +4716,8 @@ C Derivatives of the "mean" values in gamma1 and gamma2.
      &        E_theta,E_tc)
         endif
         etheta=etheta+ethetai
-        if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
-     &      'ebend',i,ethetai
+        if (energy_dec) write (iout,'(a6,i5,0pf7.3,f7.3,i5)')
+     &      'ebend',i,ethetai,theta(i),itype(i)
         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*E_tc*dthetg1
         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*E_tc*dthetg2
         gloc(nphi+i-2,icg)=wang*(E_theta+E_tc*dthett)
@@ -4421,7 +4738,8 @@ C---------------------------------------------------------------------------
 C Calculate the contributions to both Gaussian lobes.
 C 6/6/97 - Deform the Gaussians using the factor of 1/(1+time)
 C The "polynomial part" of the "standard deviation" of this part of 
-C the distribution.
+C the distributioni.
+        write (iout,*) thetai,thet_pred_mean
         sig=polthet(3,it)
         do j=2,0,-1
           sig=sig*thet_pred_mean+polthet(j,it)
@@ -4451,6 +4769,7 @@ C Following variable is sigma(t_c)**(-2)
         delthe0=thetai-theta0i
         term1=-0.5D0*sigcsq*delthec*delthec
         term2=-0.5D0*sig0inv*delthe0*delthe0
+C        write (iout,*)'term1',term1,term2,sigcsq,delthec,sig0inv,delthe0
 C Following fuzzy logic is to avoid underflows in dexp and subsequent INFs and
 C NaNs in taking the logarithm. We extract the largest exponent which is added
 C to the energy (this being the log of the distribution) at the end of energy
@@ -4478,6 +4797,7 @@ C Contribution of the bending energy from this theta is just the -log of
 C the sum of the contributions from the two lobes and the pre-exponential
 C factor. Simple enough, isn't it?
         ethetai=(-dlog(termexp)-termm+dlog(termpre))
+C       write (iout,*) 'termexp',termexp,termm,termpre,i
 C NOW the derivatives!!!
 C 6/6/97 Take into account the deformation.
         E_theta=(delthec*sigcsq*term1
       logical lprn /.false./, lprn1 /.false./
       etheta=0.0D0
       do i=ithet_start,ithet_end
-        if (itype(i-1).eq.ntyp1) cycle
+        if ((itype(i-1).eq.ntyp1)) cycle
+        if (iabs(itype(i+1)).eq.20) iblock=2
+        if (iabs(itype(i+1)).ne.20) iblock=1
         dethetai=0.0d0
         dephii=0.0d0
         dephii1=0.0d0
         theti2=0.5d0*theta(i)
-        ityp2=ithetyp(iabs(itype(i-1)))
+        ityp2=ithetyp((itype(i-1)))
         do k=1,nntheterm
           coskt(k)=dcos(k*theti2)
           sinkt(k)=dsin(k*theti2)
@@ -4561,7 +4883,8 @@ C
 #else
           phii=phi(i)
 #endif
-          ityp1=ithetyp(iabs(itype(i-2)))
+          ityp1=ithetyp((itype(i-2)))
+C propagation of chirality for glycine type
           do k=1,nsingle
             cosph1(k)=dcos(k*phii)
             sinph1(k)=dsin(k*phii)
@@ -4582,7 +4905,7 @@ C
 #else
           phii1=phi(i+1)
 #endif
-          ityp3=ithetyp(iabs(itype(i)))
+          ityp3=ithetyp((itype(i)))
           do k=1,nsingle
             cosph2(k)=dcos(k*phii1)
             sinph2(k)=dsin(k*phii1)
@@ -4595,7 +4918,7 @@ C
             sinph2(k)=0.0d0
           enddo
         endif  
-        ethetai=aa0thet(ityp1,ityp2,ityp3)
+        ethetai=aa0thet(ityp1,ityp2,ityp3,iblock)
         do k=1,ndouble
           do l=1,k-1
             ccl=cosph1(l)*cosph2(k-l)
         enddo
         endif
         do k=1,ntheterm
-          ethetai=ethetai+aathet(k,ityp1,ityp2,ityp3)*sinkt(k)
-          dethetai=dethetai+0.5d0*k*aathet(k,ityp1,ityp2,ityp3)
+          ethetai=ethetai+aathet(k,ityp1,ityp2,ityp3,iblock)*sinkt(k)
+          dethetai=dethetai+0.5d0*k*aathet(k,ityp1,ityp2,ityp3,iblock)
      &      *coskt(k)
           if (lprn)
-     &    write (iout,*) "k",k," aathet",aathet(k,ityp1,ityp2,ityp3),
+     &    write (iout,*) "k",k,"
+     &     aathet",aathet(k,ityp1,ityp2,ityp3,iblock),
      &     " ethetai",ethetai
         enddo
         if (lprn) then
         endif
         do m=1,ntheterm2
           do k=1,nsingle
-            aux=bbthet(k,m,ityp1,ityp2,ityp3)*cosph1(k)
-     &         +ccthet(k,m,ityp1,ityp2,ityp3)*sinph1(k)
-     &         +ddthet(k,m,ityp1,ityp2,ityp3)*cosph2(k)
-     &         +eethet(k,m,ityp1,ityp2,ityp3)*sinph2(k)
+            aux=bbthet(k,m,ityp1,ityp2,ityp3,iblock)*cosph1(k)
+     &         +ccthet(k,m,ityp1,ityp2,ityp3,iblock)*sinph1(k)
+     &         +ddthet(k,m,ityp1,ityp2,ityp3,iblock)*cosph2(k)
+     &         +eethet(k,m,ityp1,ityp2,ityp3,iblock)*sinph2(k)
             ethetai=ethetai+sinkt(m)*aux
             dethetai=dethetai+0.5d0*m*aux*coskt(m)
             dephii=dephii+k*sinkt(m)*(
-     &          ccthet(k,m,ityp1,ityp2,ityp3)*cosph1(k)-
-     &          bbthet(k,m,ityp1,ityp2,ityp3)*sinph1(k))
+     &          ccthet(k,m,ityp1,ityp2,ityp3,iblock)*cosph1(k)-
+     &          bbthet(k,m,ityp1,ityp2,ityp3,iblock)*sinph1(k))
             dephii1=dephii1+k*sinkt(m)*(
-     &          eethet(k,m,ityp1,ityp2,ityp3)*cosph2(k)-
-     &          ddthet(k,m,ityp1,ityp2,ityp3)*sinph2(k))
+     &          eethet(k,m,ityp1,ityp2,ityp3,iblock)*cosph2(k)-
+     &          ddthet(k,m,ityp1,ityp2,ityp3,iblock)*sinph2(k))
             if (lprn)
      &      write (iout,*) "m",m," k",k," bbthet",
-     &         bbthet(k,m,ityp1,ityp2,ityp3)," ccthet",
-     &         ccthet(k,m,ityp1,ityp2,ityp3)," ddthet",
-     &         ddthet(k,m,ityp1,ityp2,ityp3)," eethet",
-     &         eethet(k,m,ityp1,ityp2,ityp3)," ethetai",ethetai
+     &         bbthet(k,m,ityp1,ityp2,ityp3,iblock)," ccthet",
+     &         ccthet(k,m,ityp1,ityp2,ityp3,iblock)," ddthet",
+     &         ddthet(k,m,ityp1,ityp2,ityp3,iblock)," eethet",
+     &         eethet(k,m,ityp1,ityp2,ityp3,iblock)," ethetai",ethetai
           enddo
         enddo
         if (lprn)
         do m=1,ntheterm3
           do k=2,ndouble
             do l=1,k-1
-              aux=ffthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)+
-     &            ffthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l)+
-     &            ggthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)+
-     &            ggthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)
+              aux=ffthet(l,k,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(l,k)+
+     &            ffthet(k,l,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(k,l)+
+     &            ggthet(l,k,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(l,k)+
+     &            ggthet(k,l,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(k,l)
               ethetai=ethetai+sinkt(m)*aux
               dethetai=dethetai+0.5d0*m*coskt(m)*aux
               dephii=dephii+l*sinkt(m)*(
-     &           -ffthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)-
-     &            ffthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)+
-     &            ggthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)+
-     &            ggthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l))
+     &           -ffthet(l,k,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(l,k)-
+     &            ffthet(k,l,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(k,l)+
+     &            ggthet(l,k,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(l,k)+
+     &            ggthet(k,l,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(k,l))
               dephii1=dephii1+(k-l)*sinkt(m)*(
-     &           -ffthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)+
-     &            ffthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)+
-     &            ggthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)-
-     &            ggthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l))
+     &           -ffthet(l,k,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(l,k)+
+     &            ffthet(k,l,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(k,l)+
+     &            ggthet(l,k,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(l,k)-
+     &            ggthet(k,l,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(k,l))
               if (lprn) then
               write (iout,*) "m",m," k",k," l",l," ffthet",
-     &            ffthet(l,k,m,ityp1,ityp2,ityp3),
-     &            ffthet(k,l,m,ityp1,ityp2,ityp3)," ggthet",
-     &            ggthet(l,k,m,ityp1,ityp2,ityp3),
-     &            ggthet(k,l,m,ityp1,ityp2,ityp3)," ethetai",ethetai
+     &            ffthet(l,k,m,ityp1,ityp2,ityp3,iblock),
+     &            ffthet(k,l,m,ityp1,ityp2,ityp3,iblock)," ggthet",
+     &            ggthet(l,k,m,ityp1,ityp2,ityp3,iblock),
+     &            ggthet(k,l,m,ityp1,ityp2,ityp3,iblock),
+     &            " ethetai",ethetai
               write (iout,*) cosph1ph2(l,k)*sinkt(m),
      &            cosph1ph2(k,l)*sinkt(m),
      &            sinph1ph2(l,k)*sinkt(m),sinph1ph2(k,l)*sinkt(m)
@@ -4695,9 +5020,12 @@ C
           enddo
         enddo
 10      continue
-        if (lprn1) write (iout,'(i2,3f8.1,9h ethetai ,f10.5)') 
+c        lprn1=.true.
+        if (lprn1) 
+     &    write (iout,'(i2,3f8.1,9h ethetai ,f10.5)') 
      &   i,theta(i)*rad2deg,phii*rad2deg,
      &   phii1*rad2deg,ethetai
+c        lprn1=.false.
         etheta=etheta+ethetai
         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*dephii
         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*dephii1
@@ -5040,7 +5368,7 @@ C
         cosfac=dsqrt(cosfac2)
         sinfac2=0.5d0/(1.0d0-costtab(i+1))
         sinfac=dsqrt(sinfac2)
-        it=itype(i)
+        it=iabs(itype(i))
         if (it.eq.10) goto 1
 c
 C  Compute the axes of tghe local cartesian coordinates system; store in
@@ -5058,7 +5386,7 @@ C     &   dc_norm(3,i+nres)
           y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
         enddo
         do j = 1,3
-          z_prime(j) = -uz(j,i-1)
+          z_prime(j) = -uz(j,i-1)*dsign(1.0d0,dfloat(itype(i)))
         enddo     
 c       write (2,*) "i",i
 c       write (2,*) "x_prime",(x_prime(j),j=1,3)
@@ -5080,7 +5408,7 @@ c
         do j = 1,3
           xx = xx + x_prime(j)*dc_norm(j,i+nres)
           yy = yy + y_prime(j)*dc_norm(j,i+nres)
-          zz = zz + dsign(1.0,itype(i))*z_prime(j)*dc_norm(j,i+nres)
+          zz = zz + z_prime(j)*dc_norm(j,i+nres)
         enddo
 
         xxtab(i)=xx
@@ -5098,7 +5426,7 @@ c        write (2,*) "xx",xx," yy",yy," zz",zz
 Cc diagnostics - remove later
         xx1 = dcos(alph(2))
         yy1 = dsin(alph(2))*dcos(omeg(2))
-        zz1 = -dsign(1.0,itype(i))*dsin(alph(2))*dsin(omeg(2))
+        zz1 = -dsign(1.0,dfloat(itype(i)))*dsin(alph(2))*dsin(omeg(2))
         write(2,'(3f8.1,3f9.3,1x,3f9.3)') 
      &    alph(2)*rad2deg,omeg(2)*rad2deg,theta(3)*rad2deg,xx,yy,zz,
      &    xx1,yy1,zz1
@@ -5140,7 +5468,9 @@ c     &   sumene4,
 c     &   dscp1,dscp2,sumene
 c        sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
         escloc = escloc + sumene
-c        write (2,*) "i",i," escloc",sumene,escloc
+c        write (2,*) "i",i," escloc",sumene,escloc,it,itype(i)
+c     & ,zz,xx,yy
+c#define DEBUG
 #ifdef DEBUG
 C
 C This section to check the numerical derivatives of the energy of ith side
@@ -5184,6 +5514,7 @@ C End of diagnostics section.
 C        
 C Compute the gradient of esc
 C
+c        zz=zz*dsign(1.0,dfloat(itype(i)))
         pom_s1=(1.0d0+x(63))/(0.1d0 + dscp1)**2
         pom_s16=6*(1.0d0+x(64))/(0.1d0 + dscp1**6)**2
         pom_s2=(1.0d0+x(65))/(0.1d0 + dscp2)**2
@@ -5208,7 +5539,7 @@ C
      &        +(sumene2x+sumene4x*cost2tab(i+1))*(s2+s2_6)
      &        +(pom1+pom2)*pom_dx
 #ifdef DEBUG
-        write(2,*), "de_dxx = ", de_dxx,de_dxx_num
+        write(2,*), "de_dxx = ", de_dxx,de_dxx_num,itype(i)
 #endif
 C
         sumene1y=x(3) + 2*x(6)*yy + x(9)*xx + x(10)*zz
@@ -5223,7 +5554,7 @@ C
      &        +(sumene2y+sumene4y*cost2tab(i+1))*(s2+s2_6)
      &        +(pom1-pom2)*pom_dy
 #ifdef DEBUG
-        write(2,*), "de_dyy = ", de_dyy,de_dyy_num
+        write(2,*), "de_dyy = ", de_dyy,de_dyy_num,itype(i)
 #endif
 C
         de_dzz =(x(24) +2*x(27)*zz +x(28)*xx +x(30)*yy
      &  +x(60)*xx*yy)*cost2tab(i+1)*(s2+s2_6)
      &  + ( x(14) + 2*x(17)*zz+  x(18)*xx + x(20)*yy)*(s2+s2_6)
 #ifdef DEBUG
-        write(2,*), "de_dzz = ", de_dzz,de_dzz_num
+        write(2,*), "de_dzz = ", de_dzz,de_dzz_num,itype(i)
 #endif
 C
         de_dt =  0.5d0*sumene3*cost2tab(i+1)*(s1+s1_6) 
      &  -0.5d0*sumene4*sint2tab(i+1)*(s2+s2_6)
      &  +pom1*pom_dt1+pom2*pom_dt2
 #ifdef DEBUG
-        write(2,*), "de_dt = ", de_dt,de_dt_num
+        write(2,*), "de_dt = ", de_dt,de_dt_num,itype(i)
 #endif
+c#undef DEBUG
 c 
 C
        cossc=scalar(dc_norm(1,i),dc_norm(1,i+nres))
@@ -5268,13 +5600,16 @@ c     &   (dC_norm(j,i-1),j=1,3)," vbld_inv",vbld_inv(i+1),vbld_inv(i)
          dZZ_Ci1(k)=0.0d0
          dZZ_Ci(k)=0.0d0
          do j=1,3
-           dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1)*dC_norm(j,i+nres)
-           dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1)*dC_norm(j,i+nres)
+           dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1)
+     &     *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
+           dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1)
+     &     *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
          enddo
           
          dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
          dYY_XYZ(k)=vbld_inv(i+nres)*(y_prime(k)-yy*dC_norm(k,i+nres))
-         dZZ_XYZ(k)=vbld_inv(i+nres)*(z_prime(k)-zz*dC_norm(k,i+nres))
+         dZZ_XYZ(k)=vbld_inv(i+nres)*
+     &   (z_prime(k)-zz*dC_norm(k,i+nres))
 c
          dt_dCi(k) = -dt_dCi(k)/sinttab(i+1)
          dt_dCi1(k)= -dt_dCi1(k)/sinttab(i+1)
@@ -5556,8 +5891,12 @@ C Set lprn=.true. for debugging
 c     lprn=.true.
       etors=0.0D0
       do i=iphi_start,iphi_end
-        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1 
-     &       .or. itype(i).eq.ntyp1) cycle
+C ANY TWO ARE DUMMY ATOMS in row CYCLE
+        if (((itype(i-3).eq.ntyp1).and.(itype(i-2).eq.ntyp1)).or.
+     &      ((itype(i-2).eq.ntyp1).and.(itype(i-1).eq.ntyp1))  .or.
+     &      ((itype(i-1).eq.ntyp1).and.(itype(i).eq.ntyp1))) cycle
+C For introducing the NH3+ and COO- group please check the etor_d for reference
+C and guidance
         etors_ii=0.0D0
          if (iabs(itype(i)).eq.20) then
          iblock=2
@@ -5656,9 +5995,13 @@ C Set lprn=.true. for debugging
       lprn=.false.
 c     lprn=.true.
       etors_d=0.0D0
+c      write(iout,*) "a tu??"
       do i=iphid_start,iphid_end
-        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1
-     &      .or. itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+C ANY TWO ARE DUMMY ATOMS in row CYCLE
+        if (((itype(i-3).eq.ntyp1).and.(itype(i-2).eq.ntyp1)).or.
+     &      ((itype(i-2).eq.ntyp1).and.(itype(i-1).eq.ntyp1)).or.
+     &      ((itype(i-1).eq.ntyp1).and.(itype(i).eq.ntyp1))  .or.
+     &      ((itype(i).eq.ntyp1).and.(itype(i+1).eq.ntyp1))) cycle
         itori=itortyp(itype(i-2))
         itori1=itortyp(itype(i-1))
         itori2=itortyp(itype(i))
@@ -5668,9 +6011,20 @@ c     lprn=.true.
         gloci2=0.0D0
         iblock=1
         if (iabs(itype(i+1)).eq.20) iblock=2
+C ADASKO: WHEN PARAMETERS FOR THIS TYPE OF BLOCKING GROUP IS READY UNCOMMENT
+C CHECK WEATHER THERE IS NECCESITY FOR iblock=3 for COO-
+C        if (itype(i+1).eq.ntyp1) iblock=3
+C The problem of NH3+ group can be resolved by adding new parameters please note if there
+C IS or IS NOT need for this
+C IF Yes uncomment below and add to parmread.F appropriate changes and to v1cij and so on
+C        is (itype(i-3).eq.ntyp1) ntblock=2
+C        ntblock is N-terminal blocking group
 
 C Regular cosine and sine terms
         do j=1,ntermd_1(itori,itori1,itori2,iblock)
+C Example of changes for NH3+ blocking group
+C       do j=1,ntermd_1(itori,itori1,itori2,iblock,ntblock)
+C          v1cij=v1c(1,j,itori,itori1,itori2,iblock,ntblock)
           v1cij=v1c(1,j,itori,itori1,itori2,iblock)
           v1sij=v1s(1,j,itori,itori1,itori2,iblock)
           v2cij=v1c(2,j,itori,itori1,itori2,iblock)
@@ -5737,6 +6091,7 @@ c      lprn=.true.
 c      write (iout,*) "EBACK_SC_COR",itau_start,itau_end
       esccor=0.0D0
       do i=itau_start,itau_end
+        if ((itype(i-2).eq.ntyp1).or.(itype(i-1).eq.ntyp1)) cycle
         esccor_ii=0.0D0
         isccori=isccortyp(itype(i-2))
         isccori1=isccortyp(itype(i-1))
@@ -5769,7 +6124,7 @@ c   3 = SC...Ca...Ca...SCi
           esccor=esccor+v1ij*cosphi+v2ij*sinphi
           gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
         enddo
-c      write (iout,*) "EBACK_SC_COR",i,esccor,intertyp
+c      write (iout,*) "EBACK_SC_COR",i,v1ij*cosphi+v2ij*sinphi,intertyp
         gloc_sc(intertyp,i-3,icg)=gloc_sc(intertyp,i-3,icg)+wsccor*gloci
         if (lprn)
      &  write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
@@ -7983,7 +8338,7 @@ c----------------------------------------------------------------------------
       include 'COMMON.GEO'
       logical swap
       double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2),
-     & auxvec1(2),auxvec2(1),auxmat1(2,2)
+     & auxvec1(2),auxvec2(2),auxmat1(2,2)
       logical lprn
       common /kutas/ lprn
 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC