adding ebend_nucl to UCGM+some further reading
[unres4.git] / source / unres / geometry.f90
index 2d963b3..6895472 100644 (file)
@@ -1,4 +1,4 @@
-      module geometry
+             module geometry
 !-----------------------------------------------------------------------------
       use io_units
       use names
         be1=rad2deg*beta(nres+i,i,nres2+2,i+1)
         alfai=0.0D0
         if (i.gt.2) alfai=rad2deg*alpha(i-2,i-1,i)
-        write (iout,1212) restyp(itype(i,1)),i,dist(i-1,i),&
+        write (iout,1212) restyp(itype(i,1),1),i,dist(i-1,i),&
         alfai,be,dist(nres+i,i),rad2deg*alpha(nres+i,i,nres2+2),be1
       enddo   
  1212 format (a3,'(',i3,')',2(f10.5,2f10.2))
       enddo
       if (lprn) then
       do i=2,nres
-       write (iout,1212) restyp(itype(i,1)),i,vbld(i),&
+       write (iout,1212) restyp(itype(i,1),1),i,vbld(i),&
        rad2deg*theta(i),rad2deg*phi(i),vbld(nres+i),&
        rad2deg*alph(i),rad2deg*omeg(i)
       enddo
       print *,'dv=',dv
       do 10 it=1,1 
         if (it.eq.10) goto 10 
-        open (20,file=restyp(it)//'_distr.sdc',status='unknown')
+        open (20,file=restyp(it,1)//'_distr.sdc',status='unknown')
         call gen_side(it,90.0D0 * deg2rad,al,om,fail)
         close (20)
         goto 10
-        open (20,file=restyp(it)//'_distr1.sdc',status='unknown')
+        open (20,file=restyp(it,1)//'_distr1.sdc',status='unknown')
         do i=0,90
           do j=0,72
             prob(j,i)=0.0D0
        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),i,vbld(i),&
+           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
           iti=itype(i,1)
           if(me.eq.king.or..not.out1file) &
-           write (iout,'(a3,i4,7f10.3)') restyp(iti),i,dist(i,i-1),&
+           write (iout,'(a3,i4,7f10.3)') restyp(iti,1),i,dist(i,i-1),&
            rad2deg*theta(i),rad2deg*phi(i)
         enddo
       endif
         do i=2,nres
           iti=itype(i,1)
           if(me.eq.king.or..not.out1file) &
-           write (iout,'(a3,i4,3f10.5)') restyp(iti),i,xxref(i),&
+           write (iout,'(a3,i4,3f10.5)') restyp(iti,1),i,xxref(i),&
             yyref(i),zzref(i)
         enddo
       endif
       integer :: i,j,ires,nscat
       real(kind=8),dimension(3,20) :: sccor
       real(kind=8) :: sccmj
+!        print *,"I am in sccenter",ires,nscat
       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
 
       write (iout,100)
       do i=1,nres
-        write (iout,110) restyp(itype(i,1)),i,c(1,i),c(2,i),&
+        write (iout,110) restyp(itype(i,1),1),i,c(1,i),c(2,i),&
           c(3,i),c(1,nres+i),c(2,nres+i),c(3,nres+i)
       enddo
   100 format (//'              alpha-carbon coordinates       ',&