dfa & multichain cluster
[unres.git] / source / unres / src-HCD-5D / gen_rand_conf.F
index 3e662cc..ea009b6 100644 (file)
@@ -144,6 +144,7 @@ C Check for SC-SC overlaps.
 cd    print *,'nnt=',nnt,' nct=',nct
       do j=nnt,i-1
         itj=iabs(itype(j))
+        if (itj.eq.ntyp1) cycle
         if (j.lt.i-1 .or. ipot.ne.4) then
           rcomp=sigmaii(iti,itj)
         else 
@@ -281,7 +282,7 @@ c-------------------------------------------------------------------------
       double precision eig_limit /1.0D-8/
       double precision Big /10.0D0/
       double precision vec(3,3)
-      logical lprint,fail,lcheck
+      logical lprint,fail,lcheck,lprn /.false./
       lcheck=.false.
       lprint=.false.
       fail=.false.
@@ -514,10 +515,12 @@ C
       endif
       if (box(1,2).lt.-MaxBoxLen .or. box(2,2).gt.MaxBoxLen) then
 #ifdef MPI
+        if (lprn) then
         write (iout,'(a,i4,a)') 'CG Processor:',me,': bad sampling box.'
         write (*,'(a,i4,a)') 'CG Processor:',me,': bad sampling box.'
+        endif
 #else
-c        write (iout,'(a)') 'Bad sampling box.'
+        if (lprn) write (iout,'(a)') 'Bad sampling box.'
 #endif
         fail=.true.
         return
@@ -780,7 +783,7 @@ c     overlapping residues left, or false otherwise (success)
       call overlap_sc_list(ioverlap,ioverlap_last)
       if (ioverlap_last.gt.0) then
         write (iout,*) '#OVERLAPing residues ',ioverlap_last
-        write (iout,'(20i4)') (ioverlap(k),k=1,ioverlap_last)
+        write (iout,'(18i5)') (ioverlap(k),k=1,ioverlap_last)
         had_overlaps=.true.
       endif
 
@@ -796,13 +799,16 @@ c     overlapping residues left, or false otherwise (success)
             fail=.true.
             do while (fail.and.nsi.le.maxsi)
               call gen_side(iti,theta(i+1),alph(i),omeg(i),fail)
+              call sc_coord_rebuild(i)
               nsi=nsi+1
             enddo
             if(fail) goto 999
           endif
         enddo
 
-        call chainbuild_extconf
+c        write (iout,*) "before chaincuild overlap_sc_list: dc0",dc(:,0)
+c        call chainbuild_extconf
+c        write (iout,*) "after chaincuild overlap_sc_list: dc0",dc(:,0)
         call overlap_sc_list(ioverlap,ioverlap_last)
         write (iout,*) 'Overlaping residues ',ioverlap_last,
      &           (ioverlap(j),j=1,ioverlap_last)
@@ -846,11 +852,14 @@ c     overlapping residues left, or false otherwise (success)
       data redfac /0.5D0/
 
       write (iout,*) "overlap_sc_list"
+c      write(iout,*) "iatsc_s",iatsc_s," iatsc_e",iatsc_e
+      write(iout,*) "nnt",nnt," nct",nct
       ioverlap_last=0
 C Check for SC-SC overlaps and mark residues
 c      print *,'>>overlap_sc nnt=',nnt,' nct=',nct
       ind=0
-      do i=iatsc_s,iatsc_e
+c      do i=iatsc_s,iatsc_e
+      do i=nnt,nct
         itypi=iabs(itype(i))
         itypi1=iabs(itype(i+1))
         if (itypi.eq.ntyp1) cycle
@@ -862,12 +871,13 @@ c      print *,'>>overlap_sc nnt=',nnt,' nct=',nct
         dzi=dc_norm(3,nres+i)
         dsci_inv=dsc_inv(itypi)
 c
-       do iint=1,nint_gr(i)
-         do j=istart(i,iint),iend(i,iint)
+c        do iint=1,nint_gr(i)
+c          do j=istart(i,iint),iend(i,iint)
+          do j=i+1,nct
             ind=ind+1
             itypj=iabs(itype(j))
             if (itypj.eq.ntyp1) cycle
-c            write (iout,*) "i,j",i,j," itypi,itypj",itypi,itypj
+c           write (iout,*) "i,j",i,j," itypi,itypj",itypi,itypj
             dscj_inv=dsc_inv(itypj)
             sig0ij=sigma(itypi,itypj)
             chi1=chi(itypi,itypj)
@@ -879,13 +889,13 @@ c            write (iout,*) "i,j",i,j," itypi,itypj",itypi,itypj
             alf1=alp(itypi)   
             alf2=alp(itypj)   
             alf12=0.5D0*(alf1+alf2)
-          if (j.gt.i+1) then
-           rcomp=sigmaii(itypi,itypj)
-          else 
-           rcomp=sigma(itypi,itypj)
-          endif
-c         print '(2(a3,2i3),a3,2f10.5)',
-c     &        ' i=',i,iti,' j=',j,itj,' d=',dist(nres+i,nres+j)
+            if (j.gt.i+1) then
+              rcomp=sigmaii(itypi,itypj)
+            else 
+              rcomp=sigma(itypi,itypj)
+            endif
+c            write (iout,'(2(a3,2i5),a3,2f10.5)'),
+c     &        ' i=',i,itypi,' j=',j,itypj,' d=',dist(nres+i,nres+j)
 c     &        ,rcomp
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
@@ -896,30 +906,36 @@ c     &        ,rcomp
             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
             rij=dsqrt(rrij)
             call sc_angular
+c            write (iout,*) "dxj",dxj," dyj",dyj," dzj",dzj
+c            write (iout,*) "erij",erij
+c            write (iout,*) "om1",om1," om2",om2," om12",om12,
+c     &       " faceps1",faceps1," eps1",eps1
+c            write (iout,*) "sigsq",sigsq
             sigsq=1.0D0/sigsq
             sig=sig0ij*dsqrt(sigsq)
             rij_shift=1.0D0/rij-sig+sig0ij
-
-ct          if ( 1.0/rij .lt. redfac*rcomp .or. 
-ct     &       rij_shift.le.0.0D0 ) then
-c           write (iout,'(a,i3,a,i3,a,f10.5,a,3f10.5)')
-c     &     'overlap SC-SC: i=',i,' j=',j,
-c     &     ' dist=',dist(nres+i,nres+j),' rcomp=',
-c     &     rcomp,1.0/rij,rij_shift
-            if ( rij_shift.le.0.0D0 ) then
-          ioverlap_last=ioverlap_last+1
-          ioverlap(ioverlap_last)=i         
-          do k=1,ioverlap_last-1
-           if (ioverlap(k).eq.i) ioverlap_last=ioverlap_last-1
+c            write (iout,*) "rij",1.0d0/rij," rij_shift",rij_shift,
+c     &       " sig",sig," sig0ij",sig0ij
+c            if ( rij_shift.le.0.0D0 ) then
+            if ( rij_shift/sig0ij.le.0.1D0 ) then
+c              write (iout,*) "overlap",i,j
+              write (iout,'(a,i5,a,i5,a,f10.5,a,3f10.5)')
+     &         'overlap SC-SC: i=',i,' j=',j,
+     &         ' dist=',dist(nres+i,nres+j),' rcomp=',
+     &         rcomp,1.0/rij,rij_shift
+              ioverlap_last=ioverlap_last+1
+              ioverlap(ioverlap_last)=i         
+              do k=1,ioverlap_last-1
+                if (ioverlap(k).eq.i) ioverlap_last=ioverlap_last-1
+              enddo
+              ioverlap_last=ioverlap_last+1
+              ioverlap(ioverlap_last)=j         
+              do k=1,ioverlap_last-1
+                if (ioverlap(k).eq.j) ioverlap_last=ioverlap_last-1
+              enddo 
+            endif
           enddo
-          ioverlap_last=ioverlap_last+1
-          ioverlap(ioverlap_last)=j         
-          do k=1,ioverlap_last-1
-           if (ioverlap(k).eq.j) ioverlap_last=ioverlap_last-1
-          enddo 
-         endif
-        enddo
-       enddo
+c        enddo
       enddo
       return
       end