adding ebend_nucl to UCGM+some further reading
[unres4.git] / source / unres / geometry.f90
index 8542f52..6895472 100644 (file)
        endif
       endif
       do i=1,nres-1
+       if (molnum(i).ne.1) cycle
 !in wham      do i=1,nres
         iti=itype(i,1)
         if ((dist(i,i+1).lt.2.0D0 .or. dist(i,i+1).gt.5.0D0).and.&
           di=dist(i,nres+i)
 !#ifndef WHAM_RUN
 ! 10/03/12 Adam: Correction for zero SC-SC bond length
+          
           if (itype(i,1).ne.10 .and. itype(i,1).ne.ntyp1 .and. di.eq.0.0d0) &
-           di=dsc(itype(i,1))
+           di=dsc(itype(i,molnum(i)))
           vbld(i+nres)=di
           if (itype(i,1).ne.10) then
             vbld_inv(i+nres)=1.0d0/di
             alph(i)=alpha(nres+i,i,nres2+2)
             omeg(i)=beta(nres+i,i,nres2+2,i+1)
           endif
+          if (iti.ne.0) then
           if(me.eq.king.or..not.out1file)then
            if (lprn) &
            write (iout,'(a3,i4,7f10.3)') restyp(iti,1),i,vbld(i),&
            rad2deg*theta(i),rad2deg*phi(i),dsc(iti),vbld(nres+i),&
            rad2deg*alph(i),rad2deg*omeg(i)
           endif
+          else
+          if(me.eq.king.or..not.out1file)then
+           if (lprn) &
+           write (iout,'(a3,i4,7f10.3)') restyp(iti,1),i,vbld(i),&
+           rad2deg*theta(i),rad2deg*phi(i),dsc(iti+1),vbld(nres+i),&
+           rad2deg*alph(i),rad2deg*omeg(i)
+          endif
+          endif
         enddo
       else if (lprn) then
         do i=2,nres
       do j=1,3
         sccmj=0.0D0
         do i=1,nscat
-          sccmj=sccmj+sccor(j,i) 
+          sccmj=sccmj+sccor(j,i)
+          print *,"insccent", ires,sccor(j,i) 
         enddo
         dc(j,ires)=sccmj/nscat
       enddo