Merge branch 'prerelease-3.2.1'
[unres.git] / source / cluster / wham / src / main_clust.F
index 4b6478a..5a61e8d 100644 (file)
@@ -34,8 +34,9 @@ C
       DIMENSION NN(maxconf),DISNN(maxconf)
       LOGICAL FLAG(maxconf)
       integer i,j,k,l,m,n,len,lev,idum,ii,ind,ioffset,jj,icut,ncon,
-     & it,ncon_work,ind1,ilen
+     & it,ncon_work,ind1,ilen,is,ie
       double precision t1,t2,tcpu,difconf
+      real diss_(maxdist)
       
       double precision varia(maxvar)
       double precision hrtime,mintime,sectime
@@ -75,6 +76,12 @@ c      if (refstr) call read_ref_structure(*30)
 
       print *,'MAIN: nnt=',nnt,' nct=',nct
 
+      if (nclust.gt.0) then
+        PRINTANG(1)=.TRUE.
+        PRINTPDB(1)=outpdb
+        printmol2(1)=outmol2
+        ncut=0
+      else
       DO I=1,NCUT
         PRINTANG(I)=.FALSE.
         PRINTPDB(I)=0
@@ -86,12 +93,21 @@ c      if (refstr) call read_ref_structure(*30)
           printmol2(i)=outmol2
         ENDIF
       ENDDO
+      endif
+      if (ncut.gt.0) then
       write (iout,*) 'Number of cutoffs:',NCUT
       write (iout,*) 'Cutoff values:'
       DO ICUT=1,NCUT
         WRITE(IOUT,'(8HRCUTOFF(,I2,2H)=,F8.1,2i2)')ICUT,RCUTOFF(ICUT),
      &    printpdb(icut),printmol2(icut)
       ENDDO
+      else if (nclust.gt.0) then
+      write (iout,'("Number of clusters requested",i5)') nclust
+      else
+      if (me.eq.Master)
+     & write (iout,*) "ERROR: Either nclust or ncut must be >0"
+      stop
+      endif
       DO I=1,NRES-3  
         MULT(I)=1
       ENDDO
@@ -146,7 +162,11 @@ C
           if (ind.ge.indstart(me) .and. ind.le.indend(me)) then
 #endif
           ind1=ind1+1
+#ifdef MPI
+          DISS_(IND1)=DIFCONF(I,J)
+#else
           DISS(IND1)=DIFCONF(I,J)
+#endif
 c          write (iout,'(2i4,i10,f10.5)') i,j,ind,DISS(IND)
 #ifdef MPI
           endif
@@ -160,7 +180,7 @@ c          write (iout,'(2i4,i10,f10.5)') i,j,ind,DISS(IND)
       PRINT '(a)','End of distance computation'
 
 #ifdef MPI
-      call MPI_Gatherv(diss(1),scount(me),MPI_REAL,diss(1),
+      call MPI_Gatherv(diss_(1),scount(me),MPI_REAL,diss(1),
      &     scount(0),idispl(0),MPI_REAL,Master,MPI_COMM_WORLD, IERROR)
       if (me.eq.master) then
 #endif
@@ -238,29 +258,39 @@ C
       CALL HCASS(N,IA,IB,CRIT,LEV,ICLASS,HVALS,IORDER,CRITVAL,HEIGHT)
 c      CALL HCDEN(LEV,IORDER,HEIGHT,CRITVAL)
 
+c 3/3/16 AL: added explicit number of cluters
+      if (nclust.gt.0) then
+        is=nclust-1
+        ie=nclust-1
+        icut=1
+      else
+        is=1
+        ie=lev-1
+      endif
       do i=1,maxgr
         licz(i)=0
       enddo
       icut=1
-      i=1
-      NGR=i+1
+      i=is
+      NGR=is+1
       do j=1,n
         licz(iclass(j,i))=licz(iclass(j,i))+1
         nconf(iclass(j,i),licz(iclass(j,i)))=j
 c        write (iout,*) i,j,iclass(j,i),licz(iclass(j,i)),
 c     &    nconf(iclass(j,i),licz(iclass(j,i)))
       enddo        
-      do i=1,lev-1
-
+c      do i=1,lev-1
+      do i=is,ie
          idum=lev-i
          DO L=1,LEV
             IF (HEIGHT(L).EQ.IDUM) GOTO 190
          ENDDO
  190     IDUM=L
-         write(IOUT,*) "i+1",i+1," idum",idum," critval",CRITVAL(IDUM),
-     &    " icut",icut," cutoff",rcutoff(icut)
-         IF (CRITVAL(IDUM).LT. RCUTOFF(ICUT)) THEN
-          WRITE (iout,'(/a,f10.5)') 'AT CUTOFF:',rcutoff(icut)
+c         write(IOUT,*) "i+1",i+1," idum",idum," critval",CRITVAL(IDUM),
+c     &    " icut",icut," cutoff",rcutoff(icut)
+         IF (nclust.gt.0.or.CRITVAL(IDUM).LT. RCUTOFF(ICUT)) THEN
+         if (nclust.le.0) 
+     &    WRITE (iout,'(/a,f10.5)') 'AT CUTOFF:',rcutoff(icut)
           write (iout,'(a,f8.2)') 'Maximum distance found:',
      &              CRITVAL(IDUM)
           CALL SRTCLUST(ICUT,ncon_work,iT)
@@ -273,9 +303,10 @@ c     &    nconf(iclass(j,i),licz(iclass(j,i)))
          do l=1,maxgr
           licz(l)=0
          enddo
+         ii=i-is+1
          do j=1,n
-          licz(iclass(j,i))=licz(iclass(j,i))+1
-          nconf(iclass(j,i),licz(iclass(j,i)))=j
+          licz(iclass(j,ii))=licz(iclass(j,ii))+1
+          nconf(iclass(j,ii),licz(iclass(j,ii)))=j
 c        write (iout,*) i,j,iclass(j,i),licz(iclass(j,i)),
 c     &    nconf(iclass(j,i),licz(iclass(j,i)))
 cd          print *,j,iclass(j,i),
@@ -301,17 +332,17 @@ C
 C
       close(icbase,status="delete")
 #ifdef MPI
-      call MPI_Finalize(MPI_COMM_WORLD,IERROR)
+      call MPI_Finalize(IERROR)
 #endif
       stop '********** Program terminated normally.'
    20 write (iout,*) "Error reading coordinates"
 #ifdef MPI
-      call MPI_Finalize(MPI_COMM_WORLD,IERROR)
+      call MPI_Finalize(IERROR)
 #endif
       stop
    30 write (iout,*) "Error reading reference structure"
 #ifdef MPI
-      call MPI_Finalize(MPI_COMM_WORLD,IERROR)
+      call MPI_Finalize(IERROR)
 #endif
       stop
       end