in debug mode on
[unres4.git] / source / wham / wham_calc.f90
index 08e166c..b2d16eb 100644 (file)
       integer,parameter :: MaxPoint=MaxStr,&
               MaxPointProc=MaxStr_Proc
       real(kind=8),parameter :: finorm_max=1.0d0
-      real(kind=8) :: potfac,entmin,entmax,expfac,vf
+      real(kind=8) :: potfac,expfac,vf
+!      real(kind=8) :: potfac,entmin,entmax,expfac,vf
       integer :: islice
       integer :: i,ii,j,jj,k,kk,l,m,ind,iter,t,tmax,ient,ientmax,iln
       integer :: start,end,iharm,ib,iib,nbin1,nbin,nbin_rms,nbin_rgy,&
               nbin_rmsrgy,liczbaW,iparm,nFi,indrgy,indrms
-      integer :: htot(0:MaxHdim),histent(0:2000)
+! 4/17/17 AKS & AL: histent is obsolete
+      integer :: htot(0:MaxHdim)!,histent(0:2000)
       real(kind=8) :: v(MaxPointProc,MaxR,MaxT_h,nParmSet)  !(MaxPointProc,MaxR,MaxT_h,Max_Parm)
       real(kind=8) :: energia(0:n_ene)
 !el      real(kind=8) :: energia(0:max_ene)
@@ -78,8 +80,8 @@
               hfin_ent_p(0:MaxHdim),histE_p(0:maxindE),sumH,&
               hrmsrgy_p(0:MaxBinRgy,0:MaxBinRms,maxT_h)
       real(kind=8) :: rgymin_t,rmsmin_t,rgymax_t,rmsmax_t
-      real(kind=8) :: potEmin_t,entmin_p,entmax_p
-      integer :: histent_p(0:2000)
+      real(kind=8) :: potEmin_t!,entmin_p,entmax_p
+!      integer :: histent_p(0:2000)
       logical :: lprint=.true.
 #endif
       real(kind=8) :: delta_T=1.0d0,iientmax
       upindE=0
 #endif
 ! 8/26/05 entropy distribution
-#ifdef MPI
-      entmin_p=1.0d10
-      entmax_p=-1.0d10
-      do t=1,scount(me1)
-!        ent=-dlog(entfac(t))
-        ent=entfac(t)
-        if (ent.lt.entmin_p) entmin_p=ent
-        if (ent.gt.entmax_p) entmax_p=ent
-      enddo
-      write (iout,*) "entmin",entmin_p," entmax",entmax_p
+!#ifdef MPI
+!      entmin_p=1.0d10
+!      entmax_p=-1.0d10
+!      do t=1,scount(me1)
+!!        ent=-dlog(entfac(t))
+!        ent=entfac(t)
+!        if (ent.lt.entmin_p) entmin_p=ent
+!        if (ent.gt.entmax_p) entmax_p=ent
+!      enddo
+!      write (iout,*) "entmin",entmin_p," entmax",entmax_p
+!!      write (iout,*) "entmin_p",entmin_p," entmax_p",entmax_p
+!      call flush(iout)
+!      call MPI_Allreduce(entmin_p,entmin,1,MPI_DOUBLE_PRECISION,MPI_MIN,&
+!        WHAM_COMM,IERROR)
+!      call MPI_Allreduce(entmax_p,entmax,1,MPI_DOUBLE_PRECISION,MPI_MAX,&
+!        WHAM_COMM,IERROR)
+!      write (iout,*) "entmin",entmin," entmax",entmax
 !      write (iout,*) "entmin_p",entmin_p," entmax_p",entmax_p
-      call flush(iout)
-      call MPI_Allreduce(entmin_p,entmin,1,MPI_DOUBLE_PRECISION,MPI_MIN,&
-        WHAM_COMM,IERROR)
-      call MPI_Allreduce(entmax_p,entmax,1,MPI_DOUBLE_PRECISION,MPI_MAX,&
-        WHAM_COMM,IERROR)
-      write (iout,*) "entmin",entmin_p," entmax",entmax_p
-!      write (iout,*) "entmin_p",entmin_p," entmax_p",entmax_p
-      ientmax=entmax-entmin 
+!      ientmax=entmax-entmin 
 !iientmax=entmax-entmin !el
 !write (iout,*) "ientmax",ientmax,entmax,entmin 
 !write (iout,*) "iientmax",iientmax
-      if (ientmax.gt.2000) ientmax=2000
-      write (iout,*) "entmin",entmin," entmax",entmax," ientmax",ientmax
-      call flush(iout)
-      do t=1,scount(me1)
-!        ient=-dlog(entfac(t))-entmin
-        ient=entfac(t)-entmin
-        if (ient.le.2000) histent_p(ient)=histent_p(ient)+1
-      enddo
-      call MPI_Allreduce(histent_p(0),histent(0),ientmax+1,MPI_INTEGER,&
-        MPI_SUM,WHAM_COMM,IERROR)
-      if (me1.eq.Master) then
-        write (iout,*) "Entropy histogram"
-        do i=0,ientmax
-          write(iout,'(f15.4,i10)') entmin+i,histent(i)
-        enddo
-      endif
-#else
-      entmin=1.0d10
-      entmax=-1.0d10
-      do t=1,ntot(islice)
-        ent=entfac(t)
-        if (ent.lt.entmin) entmin=ent
-        if (ent.gt.entmax) entmax=ent
-      enddo
-      ientmax=-dlog(entmax)-entmin
-      if (ientmax.gt.2000) ientmax=2000
-      do t=1,ntot(islice)
-        ient=entfac(t)-entmin
-        if (ient.le.2000) histent(ient)=histent(ient)+1
-      enddo
-      write (iout,*) "Entropy histogram"
-      do i=0,ientmax
-        write(iout,'(2f15.4)') entmin+i,histent(i)
-      enddo
-#endif
+!      if (ientmax.gt.2000) ientmax=2000
+!      write (iout,*) "entmin",entmin," entmax",entmax," ientmax",ientmax
+!      call flush(iout)
+!      do t=1,scount(me1)
+!!        ient=-dlog(entfac(t))-entmin
+!        ient=entfac(t)-entmin
+!        if (ient.le.2000) histent_p(ient)=histent_p(ient)+1
+!      enddo
+!      call MPI_Allreduce(histent_p(0),histent(0),ientmax+1,MPI_INTEGER,&
+!        MPI_SUM,WHAM_COMM,IERROR)
+!      if (me1.eq.Master) then
+!        write (iout,*) "Entropy histogram"
+!        do i=0,ientmax
+!          write(iout,'(f15.4,i10)') entmin+i,histent(i)
+!        enddo
+!      endif
+!#else
+!      entmin=1.0d10
+!      entmax=-1.0d10
+!      do t=1,ntot(islice)
+!        ent=entfac(t)
+!        if (ent.lt.entmin) entmin=ent
+!        if (ent.gt.entmax) entmax=ent
+!      enddo
+!      ientmax=-dlog(entmax)-entmin
+!      if (ientmax.gt.2000) ientmax=2000
+!      do t=1,ntot(islice)
+!        ient=entfac(t)-entmin
+!        if (ient.le.2000) histent(ient)=histent(ient)+1
+!      enddo
+!      write (iout,*) "Entropy histogram"
+!      do i=0,ientmax
+!        write(iout,'(2f15.4)') entmin+i,histent(i)
+!      enddo
+!#endif
       
 #ifdef MPI
       write (iout,*) "me1",me1," scount",scount(me1) !d