unres_package_Oct_2016 from emilial
[unres4.git] / source / wham / work_partition.f90
diff --git a/source/wham/work_partition.f90 b/source/wham/work_partition.f90
new file mode 100644 (file)
index 0000000..a50da8e
--- /dev/null
@@ -0,0 +1,127 @@
+      module work_part
+!------------------------------------------------------------------------------
+      use io_units
+      use MPI_data
+      use wham_data
+      implicit none
+#ifdef MPI
+!------------------------------------------------------------------------------
+!
+!
+!-----------------------------------------------------------------------------
+      contains
+!-----------------------------------------------------------------------------
+#ifdef CLUSTER
+      subroutine work_partition(lprint,ncon_work)
+#else
+      subroutine work_partition(islice,lprint)
+#endif
+! Split the conformations between processors
+!      implicit none
+!      include "DIMENSIONS"
+!      include "DIMENSIONS.ZSCOPT"
+!      include "DIMENSIONS.FREE"
+      include "mpif.h"
+!      include "COMMON.IOUNITS"
+!      include "COMMON.MPI"
+!      include "COMMON.PROT"
+      integer :: islice,ncon_work
+      integer :: n,chunk,i,j,ii,remainder
+!el      integer :: kolor
+      integer :: key,ierror,errcode
+      logical :: lprint
+!
+! Divide conformations between processors; the first and
+! the last conformation to handle by ith processor is stored in 
+! indstart(i) and indend(i), respectively.
+!
+!el MPI_data
+      if (.not. allocated(indstart)) allocate(indstart(0:nprocs))
+      if (.not. allocated(indend)) allocate(indend(0:nprocs))
+      if (.not. allocated(idispl)) allocate(idispl(0:nprocs))
+      if (.not. allocated(scount)) allocate(scount(0:nprocs))
+! First try to assign equal number of conformations to each processor.
+!
+#ifdef CLUSTER
+        n=ncon_work
+        write (iout,*) "n=",n," nprocs=",nprocs
+        nprocs1=nprocs
+#else
+        n=ntot(islice)
+        write (iout,*) "n=",n
+#endif
+        indstart(0)=1
+        chunk = N/nprocs1
+        scount(0) = chunk
+write(iout,*)"chunk",chunk,scount(0)
+flush(iout)
+!        print *,"i",0," indstart",indstart(0)," scount",&
+!          scount(0)
+        do i=1,nprocs1-1
+          indstart(i)=chunk+indstart(i-1) 
+          scount(i)=scount(i-1)
+!          print *,"i",i," indstart",indstart(i)," scount",
+!     &     scount(i)
+        enddo 
+!
+! Determine how many conformations remained yet unassigned.
+!
+        remainder=N-(indstart(nprocs1-1) &
+          +scount(nprocs1-1)-1)
+!        print *,"remainder",remainder
+!
+! Assign the remainder conformations to consecutive processors, starting
+! from the lowest rank; this continues until the list is exhausted.
+!
+        if (remainder .gt. 0) then 
+          do i=1,remainder
+            scount(i-1) = scount(i-1) + 1
+            indstart(i) = indstart(i) + i
+          enddo
+          do i=remainder+1,nprocs1-1
+            indstart(i) = indstart(i) + remainder
+          enddo
+        endif
+
+        indstart(nprocs1)=N+1
+        scount(nprocs1)=0
+
+        do i=0,NProcs1
+          indend(i)=indstart(i)+scount(i)-1
+          idispl(i)=indstart(i)-1
+        enddo
+
+        N=0
+        do i=0,Nprocs1-1
+          N=N+indend(i)-indstart(i)+1
+        enddo
+
+!        print *,"N",n," NTOT",ntot(islice)
+#ifdef CLUSTER
+        if (N.ne.ncon_work) then
+          write (iout,*) "!!! Checksum error on processor",me,&
+            n,ncon_work
+#else
+        if (N.ne.ntot(islice)) then
+          write (iout,*) "!!! Checksum error on processor",me,&
+           " slice",islice
+#endif
+          call flush(iout)
+          call MPI_Abort( MPI_COMM_WORLD, Ierror, Errcode )
+        endif
+
+      if (lprint) then
+        write (iout,*) "Partition of work between processors"
+          do i=0,nprocs1-1
+            write (iout,'(a,i5,a,i7,a,i7,a,i7)') &
+              "Processor",i," indstart",indstart(i),&
+              " indend",indend(i)," count",scount(i)
+          enddo
+      endif
+      return
+      end subroutine work_partition
+#endif
+!----------------------------------------------------------------------------
+      end module work_part
+!-----------------------------------------------------------------------------
+!-----------------------------------------------------------------------------