Fized same buffer issue in gather and gatherv in wham and cluster and a minor issue...
authorAdam Liwo <adam@piasek4.chem.univ.gda.pl>
Fri, 18 Dec 2015 19:29:56 +0000 (20:29 +0100)
committerAdam Liwo <adam@piasek4.chem.univ.gda.pl>
Fri, 18 Dec 2015 19:29:56 +0000 (20:29 +0100)
12 files changed:
source/cluster/wham/src-M/initialize_p.F
source/cluster/wham/src-M/main_clust.F
source/cluster/wham/src-M/parmread.F
source/cluster/wham/src-M/probabl.F
source/cluster/wham/src/initialize_p.F
source/cluster/wham/src/main_clust.F
source/cluster/wham/src/parmread.F
source/cluster/wham/src/probabl.F
source/wham/src-M/enecalc1.F
source/wham/src-M/make_ensemble1.F
source/wham/src/enecalc1.F
source/wham/src/make_ensemble1.F

index c17f282..515201d 100644 (file)
@@ -341,7 +341,7 @@ cd      write (iout,*) 'i=',i,' scheck=',scheck,' jj=',jj
           nint_gr(i)=1
           istart(i,1)=i+1
           iend(i,1)=nct
-          ind_scint=int_scint+nct-i
+          ind_scint=ind_scint+nct-i
 #endif
         endif
 #ifdef MPL
index f01f859..a2e4769 100644 (file)
@@ -36,6 +36,7 @@ C
       integer i,j,k,l,m,n,len,lev,idum,ii,ind,ioffset,jj,icut,ncon,
      & it,ncon_work,ind1
       double precision t1,t2,tcpu,difconf
+      real diss_(maxdist)
       
       double precision varia(maxvar)
       double precision hrtime,mintime,sectime
@@ -151,7 +152,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
@@ -165,7 +170,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
index 877d72b..5517e89 100644 (file)
@@ -548,6 +548,7 @@ cc maxinter is maximum interaction sites
       close (isccor)
       if (lprint) then
         write (iout,'(/a/)') 'Torsional constants of SCCORR:'
+        do l=1,maxinter
         do i=1,nsccortyp
           do j=1,nsccortyp
             write (iout,*) 'ityp',i,' jtyp',j
@@ -563,6 +564,7 @@ cc maxinter is maximum interaction sites
             enddo 
           enddo
         enddo
+        enddo
       endif
 C
 C 9/18/99 (AL) Read coefficients of the Fourier expansion of the local
index 293fb8f..d235ea5 100644 (file)
@@ -29,8 +29,9 @@
       character*5 ctemper
       integer ilen
       external ilen
-      real*4 Fdimless(maxconf)
+      real*4 Fdimless(maxconf),Fdimless_(maxconf)
       double precision energia(0:max_ene)
+      double precision totfree_(maxconf),entfac_(maxconf)
       do i=1,ncon
         list_conf(i)=i
       enddo
@@ -207,8 +208,13 @@ c#endif
         write (iout,*) "evdw1", wvdwpp,evdw1
         write (iout,*) "ebe" ebe,wang
 #endif        
+#ifdef MPI
+        Fdimless_(i)=beta_h(ib)*etot+entfac(ii)
+        totfree_(i)=etot
+#else
         Fdimless(i)=beta_h(ib)*etot+entfac(ii)
         totfree(i)=etot
+#endif
 #ifdef DEBUG
         write (iout,*) "fdim calc", i,ii,ib,
      &   1.0d0/(1.987d-3*beta_h(ib)),totfree(i),
@@ -216,19 +222,22 @@ c#endif
 #endif
       enddo   ! i
 #ifdef MPI
-      call MPI_Gatherv(Fdimless(1),scount(me),
+      call MPI_Gatherv(Fdimless_(1),scount(me),
      & MPI_REAL,Fdimless(1),
      & scount(0),idispl(0),MPI_REAL,Master,
      & MPI_COMM_WORLD, IERROR)
-      call MPI_Gatherv(totfree(1),scount(me),
+      call MPI_Gatherv(totfree_(1),scount(me),
      & MPI_DOUBLE_PRECISION,totfree(1),
      & scount(0),idispl(0),MPI_DOUBLE_PRECISION,Master,
      & MPI_COMM_WORLD, IERROR)
       call MPI_Gatherv(entfac(indstart(me)+1),scount(me),
-     & MPI_DOUBLE_PRECISION,entfac(1),
+     & MPI_DOUBLE_PRECISION,entfac_(1),
      & scount(0),idispl(0),MPI_DOUBLE_PRECISION,Master,
      & MPI_COMM_WORLD, IERROR)
       if (me.eq.Master) then
+        do i=1,ncon
+          entfac(i)=entfac_(i)
+        enddo 
 #endif
 #ifdef DEBUG
         write (iout,*) "The FDIMLESS array before sorting"
index f8b9426..224cb21 100644 (file)
@@ -345,7 +345,7 @@ cd      write (iout,*) 'i=',i,' scheck=',scheck,' jj=',jj
           nint_gr(i)=1
           istart(i,1)=i+1
           iend(i,1)=nct
-          ind_scint=int_scint+nct-i
+          ind_scint=ind_scint+nct-i
 #endif
         endif
 #ifdef MPL
index 4b6478a..b4bfe0a 100644 (file)
@@ -36,6 +36,7 @@ C
       integer i,j,k,l,m,n,len,lev,idum,ii,ind,ioffset,jj,icut,ncon,
      & it,ncon_work,ind1,ilen
       double precision t1,t2,tcpu,difconf
+      real diss_(maxdist)
       
       double precision varia(maxvar)
       double precision hrtime,mintime,sectime
@@ -146,7 +147,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 +165,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
index 656d219..b1a9a32 100644 (file)
@@ -502,6 +502,7 @@ cc maxinter is maximum interaction sites
 
       if (lprint) then
         write (iout,'(/a/)') 'Torsional constants:'
+        do l=1,maxinter
         do i=1,nsccortyp
           do j=1,nsccortyp
             write (iout,*) 'ityp',i,' jtyp',j
@@ -517,6 +518,7 @@ cc maxinter is maximum interaction sites
             enddo
           enddo
         enddo
+        enddo
       endif
 
 C
index 7fcd29b..53735e8 100644 (file)
@@ -28,8 +28,9 @@
       character*5 ctemper
       integer ilen
       external ilen
-      real*4 Fdimless(maxconf)
+      real*4 Fdimless(maxconf),Fdimless_(maxconf)
       double precision energia(0:max_ene)
+      double precision totfree_(maxconf),entfac_(maxconf)
       do i=1,ncon
         list_conf(i)=i
       enddo
@@ -111,13 +112,13 @@ c        write (iout,*) "i",i," ii",ii
           call int_from_cart1(.false.)
           call etotal(energia(0),fT)
           totfree(i)=energia(0)
-c#define DEBUG
+#define DEBUG
 #ifdef DEBUG
           write (iout,*) i," energia",(energia(j),j=0,20)
           call enerprint(energia(0),ft)
           call flush(iout)
 #endif
-c#undef DEBUG
+#undef DEBUG
           do k=1,max_ene
             enetb(k,i)=energia(k)
           enddo
@@ -172,8 +173,13 @@ cc        if (wcorr6.eq.0) ecorr6=0.0d0
      &  +ft(2)*wtor_d*etors_d+ft(1)*wsccor*esccor
      &  +wbond*estr
 #endif
+#ifdef MPI
+        Fdimless_(i)=beta_h(ib)*etot+entfac(ii)
+        totfree_(i)=etot
+#else
         Fdimless(i)=beta_h(ib)*etot+entfac(ii)
         totfree(i)=etot
+#endif
 #ifdef DEBUG
         
         write (iout,*) "etrop", i,ii,ib,
@@ -182,19 +188,22 @@ cc        if (wcorr6.eq.0) ecorr6=0.0d0
 #endif
       enddo   ! i
 #ifdef MPI
-      call MPI_Gatherv(Fdimless(1),scount(me),
+      call MPI_Gatherv(Fdimless_(1),scount(me),
      & MPI_REAL,Fdimless(1),
      & scount(0),idispl(0),MPI_REAL,Master,
      & MPI_COMM_WORLD, IERROR)
-      call MPI_Gatherv(totfree(1),scount(me),
+      call MPI_Gatherv(totfree_(1),scount(me),
      & MPI_DOUBLE_PRECISION,totfree(1),
      & scount(0),idispl(0),MPI_DOUBLE_PRECISION,Master,
      & MPI_COMM_WORLD, IERROR)
       call MPI_Gatherv(entfac(indstart(me)+1),scount(me),
-     & MPI_DOUBLE_PRECISION,entfac(1),
+     & MPI_DOUBLE_PRECISION,entfac_(1),
      & scount(0),idispl(0),MPI_DOUBLE_PRECISION,Master,
      & MPI_COMM_WORLD, IERROR)
       if (me.eq.Master) then
+        do i=1,ncon
+          entfac(i)=entfac_(i)
+        enddo
 #endif
 c#define DEBUG
 #ifdef DEBUG
index 880664c..0137fe6 100644 (file)
@@ -45,6 +45,7 @@
       double precision fT(6),quot,quotl,kfacl,kfac /2.4d0/,T0 /3.0d2/
       double precision tt
       integer snk_p(MaxR,MaxT_h,Max_parm)
+      integer scount_(MaxProcs)
       logical lerr
       character*64 bprotfile_temp
       call opentmp(islice,ientout,bprotfile_temp)
@@ -269,11 +270,11 @@ c     &   " snk",snk_p(iR,ib,ipar)
   121   continue
       enddo   
 #ifdef MPI
-      scount(me)=iii 
+      scount_(me)=iii 
       write (iout,*) "Me",me," scount",scount(me)
       call flush(iout)
 c  Master gathers updated numbers of conformations written by all procs.
-      call MPI_AllGather( scount(me), 1, MPI_INTEGER, scount(0), 1, 
+      call MPI_AllGather( scount_(me), 1, MPI_INTEGER, scount(0), 1, 
      &  MPI_INTEGER, WHAM_COMM, IERROR)
       indstart(0)=1
       indend(0)=scount(0)
index 5d7b750..b0fa827 100644 (file)
@@ -34,7 +34,7 @@
       character*5 ctemper
       integer ilen
       external ilen
-      real*4 Fdimless(MaxStr)
+      real*4 Fdimless(MaxStr),Fdimless_(MaxStr)
       double precision enepot(MaxStr)
       integer iperm(MaxStr)
       integer islice
@@ -184,7 +184,7 @@ c              write (iout,*) 1.0d0/(beta_h(ib,iparm)*1.987D-3),ft
      &      +wbond*estr
 #endif
 #ifdef MPI
-            Fdimless(i)=
+            Fdimless_(i)=
      &        beta_h(ib,iparm)*etot-entfac(i)
             potE(i,iparm)=etot
 #ifdef DEBUG
@@ -198,7 +198,7 @@ c              write (iout,*) 1.0d0/(beta_h(ib,iparm)*1.987D-3),ft
 #endif
           enddo   ! i
 #ifdef MPI
-          call MPI_Gatherv(Fdimless(1),scount(me),
+          call MPI_Gatherv(Fdimless_(1),scount(me),
      &     MPI_REAL,Fdimless(1),
      &     scount(0),idispl(0),MPI_REAL,Master,
      &     WHAM_COMM, IERROR)
index 01e5684..0ed44d5 100644 (file)
@@ -44,6 +44,7 @@
       double precision fT(6),quot,quotl,kfacl,kfac /2.4d0/,T0 /3.0d2/
       double precision tt
       integer snk_p(MaxR,MaxT_h,Max_parm)
+      integer scount_(0:MaxProcs)
       logical lerr
       character*64 bprotfile_temp
       call opentmp(islice,ientout,bprotfile_temp)
@@ -269,11 +270,12 @@ c     &   " snk",snk_p(iR,ib,ipar)
   121   continue
       enddo   
 #ifdef MPI
-      scount(me)=iii 
+c      scount(me)=iii 
+      scount_(me)=iii 
       write (iout,*) "Me",me," scount",scount(me)
       call flush(iout)
 c  Master gathers updated numbers of conformations written by all procs.
-      call MPI_AllGather( scount(me), 1, MPI_INTEGER, scount(0), 1, 
+      call MPI_AllGather( scount_(me), 1, MPI_INTEGER, scount(0), 1, 
      &  MPI_INTEGER, WHAM_COMM, IERROR)
       indstart(0)=1
       indend(0)=scount(0)
index e9c0754..5402f2c 100644 (file)
@@ -34,7 +34,7 @@
       character*5 ctemper
       integer ilen
       external ilen
-      real*4 Fdimless(MaxStr)
+      real*4 Fdimless(MaxStr),Fdimless_(MaxStr)
       double precision enepot(MaxStr)
       integer iperm(MaxStr)
       integer islice
@@ -184,7 +184,7 @@ c              write (iout,*) 1.0d0/(beta_h(ib,iparm)*1.987D-3),ft
      &      +wbond*estr
 #endif
 #ifdef MPI
-            Fdimless(i)=
+            Fdimless_(i)=
      &        beta_h(ib,iparm)*etot-entfac(i)
             potE(i,iparm)=etot
 #ifdef DEBUG
@@ -198,7 +198,7 @@ c              write (iout,*) 1.0d0/(beta_h(ib,iparm)*1.987D-3),ft
 #endif
           enddo   ! i
 #ifdef MPI
-          call MPI_Gatherv(Fdimless(1),scount(me),
+          call MPI_Gatherv(Fdimless_(1),scount(me),
      &     MPI_REAL,Fdimless(1),
      &     scount(0),idispl(0),MPI_REAL,Master,
      &     WHAM_COMM, IERROR)