the first working version of multichain homology
[unres.git] / source / cluster / wham / src-M / main_clust.F
index f01f859..a3f8094 100644 (file)
@@ -29,12 +29,12 @@ C
       INTEGER IA(maxconf),IB(maxconf)
       INTEGER ICLASS(maxconf,maxconf-1),HVALS(maxconf-1)
       INTEGER IORDER(maxconf-1),HEIGHT(maxconf-1)
-      integer nn,ndis
-      real*4 DISNN
+      integer nn,ndis,scount_buf
+      real*4 DISNN, diss_buf(maxdist)
       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
+     & it,ncon_work,ind1,kkk, ijk
       double precision t1,t2,tcpu,difconf
       
       double precision varia(maxvar)
@@ -122,7 +122,7 @@ c      call flush(iout)
       ndis=ncon_work*(ncon_work-1)/2
       call work_partition(.true.,ndis)
 #endif
-
+      write(iout,*) "AFTET wort_part",NCON_work
       DO I=1,NCON_work
         ICC(I)=I
       ENDDO
@@ -132,6 +132,8 @@ C
 C CALCULATE DISTANCES
 C
       call daread_ccoords(1,ncon_work)
+      write (iout,*) "AM I HERE"
+      call flush(iout)
       ind1=0
       DO I=1,NCON_work-1
         if (mod(i,100).eq.0) print *,'Calculating RMS i=',i
@@ -140,9 +142,10 @@ C
             c(l,k)=allcart(l,k,i)
           enddo 
         enddo
+        kkk=1
         do k=1,nres
           do l=1,3
-            cref(l,k)=c(l,k)
+            cref(l,k,kkk)=c(l,k)
           enddo
         enddo
         DO J=I+1,NCON_work
@@ -164,8 +167,16 @@ c          write (iout,'(2i4,i10,f10.5)') i,j,ind,DISS(IND)
       t1=tcpu()
       PRINT '(a)','End of distance computation'
 
+      scount_buf=scount(me)
+
+      do ijk=1, ndis
+      diss_buf(ijk)=diss(ijk)
+      enddo
+
+
 #ifdef MPI
-      call MPI_Gatherv(diss(1),scount(me),MPI_REAL,diss(1),
+      WRITE (iout,*) "Wchodze do call MPI_Gatherv"
+      call MPI_Gatherv(diss_buf(1),scount_buf,MPI_REAL,diss(1),
      &     scount(0),idispl(0),MPI_REAL,Master,MPI_COMM_WORLD, IERROR)
       if (me.eq.master) then
 #endif
@@ -305,17 +316,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
@@ -358,7 +369,7 @@ c          write (iout,*) "tutaj",zzz
           ibezperm=(run-1)*chalen+i
           do j=1,3
             xx(j,ii)=allcart(j,iaperm,jcon)
-            yy(j,ii)=cref(j,ibezperm)
+            yy(j,ii)=cref(j,ibezperm,kkk)
           enddo
          enddo
         enddo
@@ -372,7 +383,7 @@ c          if (itype(i).ne.10) then
             ii=ii+1
             do j=1,3 
               xx(j,ii)=allcart(j,iaperm+nres,jcon)
-              yy(j,ii)=cref(j,ibezperm+nres)
+              yy(j,ii)=cref(j,ibezperm+nres,kkk)
             enddo
            enddo
 c          endif
@@ -392,7 +403,8 @@ c        do i=nnt,nct
           enddo
          enddo
         enddo
-        call fitsq(rms,c(1,nstart),cref(1,nstart),nend-nstart+1,przes,
+        call fitsq(rms,c(1,nstart),cref(1,nstart,kkk),nend-nstart+1,
+     &       przes,
      &       obrot,non_conv)
       endif
       if (rms.lt.0.0) then