corrections
[unres.git] / source / unres / src-HCD-5D / make_xx_list.F
index a69ee13..480aeb2 100644 (file)
@@ -5,6 +5,7 @@
       include 'mpif.h'
       include "COMMON.SETUP"
 #endif
+      include "COMMON.CONTROL"
       include "COMMON.CHAIN"
       include "COMMON.INTERACT"
       include "COMMON.SPLITELE"
       double precision xi,yi,zi,xj,yj,zj,xj_safe,yj_safe,zj_safe,
      &  xj_temp,yj_temp,zj_temp
       double precision dist_init, dist_temp,r_buff_list
-      integer contlisti(2000*maxres),contlistj(2000*maxres)
+      integer contlisti(maxint_res*maxres),contlistj(maxint_res*maxres)
 !      integer :: newcontlisti(200*nres),newcontlistj(200*nres) 
       integer i,j,itypi,itypj,subchap,xshift,yshift,zshift,iint,
      &  ilist_sc,g_ilist_sc
       integer displ(0:max_fg_procs),i_ilist_sc(0:max_fg_procs),ierr
+      logical lprn /.false./
 !            print *,"START make_SC"
 #ifdef DEBUG
-      write (iout,*) "make_SCSC_inter_list"
+      write (iout,*) "make_SCSC_inter_list maxint_res",maxint_res
 #endif
           r_buff_list=5.0d0
             ilist_sc=0
@@ -80,7 +82,7 @@
                zj=zj_safe-zi
                endif
 ! r_buff_list is a read value for a buffer 
-               if (sqrt(dist_init).le.(r_cut_int+r_buff_list)) then
+               if (dsqrt(dist_init).le.(r_cut_int+r_buff_list)) then
 ! Here the list is created
                  ilist_sc=ilist_sc+1
 ! this can be substituted by cantor and anti-cantor
 
         call MPI_Reduce(ilist_sc,g_ilist_sc,1,
      &                  MPI_INTEGER,MPI_SUM,king,FG_COMM,IERR)
+c        write (iout,*) "SCSC after reduce ierr",ierr
+        if (fg_rank.eq.0.and.g_ilist_sc.gt.maxres*maxint_res) then
+          if ((me.eq.king.or.out1file).and.energy_dec) then
+            write (iout,*) "Too many SCSC interactions",
+     &      g_ilist_sc," only",maxres*maxint_res," allowed."
+            write (iout,*) "Reduce r_cut_int and resubmit"
+            write (iout,*) "Specify a smaller r_cut_int and resubmit"
+            call flush(iout)
+          endif
+          write (*,*) "Processor:",me,": Too many SCSC interactions",
+     &      g_ilist_sc," only",maxres*maxint_res," allowed."
+            write (iout,*) "Reduce r_cut_int and resubmit"
+            write (iout,*) "Specify a smaller r_cut_int and resubmit"
+          call MPI_Abort(MPI_COMM_WORLD,ierr)
+        endif
 c        write(iout,*) "before bcast",g_ilist_sc
         call MPI_Gather(ilist_sc,1,MPI_INTEGER,
      &                  i_ilist_sc,1,MPI_INTEGER,king,FG_COMM,IERR)
+c        write (iout,*) "SCSC after gather ierr",ierr
         displ(0)=0
         do i=1,nfgtasks-1,1
           displ(i)=i_ilist_sc(i-1)+displ(i-1)
@@ -117,16 +135,20 @@ c        write(iout,*) "before bcast",g_ilist_sc
         call MPI_Gatherv(contlisti,ilist_sc,MPI_INTEGER,
      &                   newcontlisti,i_ilist_sc,displ,MPI_INTEGER,
      &                   king,FG_COMM,IERR)
+c        write (iout,*) "SCSC after gatherv ierr",ierr
         call MPI_Gatherv(contlistj,ilist_sc,MPI_INTEGER,
      &                   newcontlistj,i_ilist_sc,displ,MPI_INTEGER,
      &                   king,FG_COMM,IERR)
         call MPI_Bcast(g_ilist_sc,1,MPI_INT,king,FG_COMM,IERR)
+c        write (iout,*) "SCSC bcast reduce ierr",ierr
 !        write(iout,*) "before bcast",g_ilist_sc
 !        call MPI_Bcast(g_ilist_sc,1,MPI_INT,king,FG_COMM)
         call MPI_Bcast(newcontlisti,g_ilist_sc,MPI_INT,king,FG_COMM,
      &                 IERR)
+c        write (iout,*) "SCSC bcast reduce ierr",ierr
         call MPI_Bcast(newcontlistj,g_ilist_sc,MPI_INT,king,FG_COMM,
      &                 IERR)
+c        write (iout,*) "SCSC after bcast ierr",ierr
 !        call MPI_Bcast(g_ilist_sc,1,MPI_INT,king,FG_COMM)
 
         else
@@ -140,8 +162,11 @@ c        write(iout,*) "before bcast",g_ilist_sc
 #ifdef MPI
         endif
 #endif      
+      if (fg_rank.eq.0 .and. (me.eq.king.or.out1file) .and. energy_dec) 
+     & write (iout,'(a30,i10,a,i4)') "Number of SC-SC interactions",
+     & g_ilist_sc," per residue on average",g_ilist_sc/nres
 #ifdef DEBUG
-      write (iout,*) "after GATHERV",g_ilist_sc
+      write (iout,*) "make_SCSC_inter_list: after GATHERV",g_ilist_sc
       do i=1,g_ilist_sc
       write (iout,*) i,newcontlisti(i),newcontlistj(i)
       enddo
@@ -157,6 +182,7 @@ c        write(iout,*) "before bcast",g_ilist_sc
       include 'mpif.h'
       include "COMMON.SETUP"
 #endif
+      include "COMMON.CONTROL"
       include "COMMON.CHAIN"
       include "COMMON.INTERACT"
       include "COMMON.SPLITELE"
@@ -164,16 +190,18 @@ c        write(iout,*) "before bcast",g_ilist_sc
       double precision xi,yi,zi,xj,yj,zj,xj_safe,yj_safe,zj_safe,
      &  xj_temp,yj_temp,zj_temp
       double precision dist_init, dist_temp,r_buff_list
-      integer contlistscpi(2000*maxres),contlistscpj(2000*maxres)
+      integer contlistscpi(2*maxint_res*maxres),
+     & contlistscpj(2*maxint_res*maxres)
 !      integer :: newcontlistscpi(200*nres),newcontlistscpj(200*nres)
       integer i,j,itypi,itypj,subchap,xshift,yshift,zshift,iint,
      &  ilist_scp,g_ilist_scp
       integer displ(0:max_fg_procs),i_ilist_scp(0:max_fg_procs),ierr
-      integer contlistscpi_f(2000*maxres),contlistscpj_f(2000*maxres)
+c      integer contlistscpi_f(2*maxint_res*maxres),
+c     &  contlistscpj_f(2*maxint_res*maxres)
       integer ilist_scp_first,ifirstrun,g_ilist_sc
 !            print *,"START make_SC"
 #ifdef DEBUG
-      write (iout,*) "make_SCp_inter_list"
+      write (iout,*) "make_SCp_inter_list maxint_res",maxint_res
 #endif
       r_buff_list=5.0
             ilist_scp=0
@@ -245,7 +273,7 @@ c        write(iout,*) "before bcast",g_ilist_sc
        endif
 #ifdef DEBUG
                 ! r_buff_list is a read value for a buffer 
-              if ((sqrt(dist_init).le.(r_cut_int)).and.(ifirstrun.eq.0))
+              if((dsqrt(dist_init).le.(r_cut_int)).and.(ifirstrun.eq.0))
      &        then
 ! Here the list is created
                  ilist_scp_first=ilist_scp_first+1
@@ -255,7 +283,7 @@ c        write(iout,*) "before bcast",g_ilist_sc
               endif
 #endif
 ! r_buff_list is a read value for a buffer 
-               if (sqrt(dist_init).le.(r_cut_int+r_buff_list)) then
+               if (dsqrt(dist_init).le.(r_cut_int+r_buff_list)) then
 ! Here the list is created
                  ilist_scp=ilist_scp+1
 ! this can be substituted by cantor and anti-cantor
@@ -276,9 +304,23 @@ c        write(iout,*) "before bcast",g_ilist_sc
 
         call MPI_Reduce(ilist_scp,g_ilist_scp,1,
      &    MPI_INTEGER,MPI_SUM,king,FG_COMM,IERR)
+c        write (iout,*) "SCp after reduce ierr",ierr
+        if (fg_rank.eq.0.and.g_ilist_scp.gt.2*maxres*maxint_res) then
+          if ((me.eq.king.or.out1file).and.energy_dec) then
+            write (iout,*) "Too many SCp interactions",
+     &      g_ilist_scp," only",2*maxres*maxint_res," allowed."
+            write (iout,*) "Specify a smaller r_cut_int and resubmit"
+            call flush(iout)
+          endif
+          write (*,*) "Processor:",me,": Too many SCp interactions",
+     &      g_ilist_scp," only",2*maxres*maxint_res," allowed."
+          write (*,*) "Specify a smaller r_cut_int and resubmit"
+          call MPI_Abort(MPI_COMM_WORLD,ierr)
+        endif
 c        write(iout,*) "before bcast",g_ilist_sc
         call MPI_Gather(ilist_scp,1,MPI_INTEGER,
      &                  i_ilist_scp,1,MPI_INTEGER,king,FG_COMM,IERR)
+c        write (iout,*) "SCp after gather ierr",ierr
         displ(0)=0
         do i=1,nfgtasks-1,1
           displ(i)=i_ilist_scp(i-1)+displ(i-1)
@@ -287,16 +329,21 @@ c        write(iout,*) "before bcast",g_ilist_sc
         call MPI_Gatherv(contlistscpi,ilist_scp,MPI_INTEGER,
      &                   newcontlistscpi,i_ilist_scp,displ,MPI_INTEGER,
      &                   king,FG_COMM,IERR)
+c        write (iout,*) "SCp after gatherv ierr",ierr
         call MPI_Gatherv(contlistscpj,ilist_scp,MPI_INTEGER,
      &                   newcontlistscpj,i_ilist_scp,displ,MPI_INTEGER,
      &                   king,FG_COMM,IERR)
+c        write (iout,*) "SCp after gatherv ierr",ierr
         call MPI_Bcast(g_ilist_scp,1,MPI_INT,king,FG_COMM,IERR)
+c        write (iout,*) "SCp after bcast ierr",ierr
 !        write(iout,*) "before bcast",g_ilist_sc
 !        call MPI_Bcast(g_ilist_sc,1,MPI_INT,king,FG_COMM)
         call MPI_Bcast(newcontlistscpi,g_ilist_scp,MPI_INT,king,FG_COMM,
      &                   IERR)
+c        write (iout,*) "SCp after bcast ierr",ierr
         call MPI_Bcast(newcontlistscpj,g_ilist_scp,MPI_INT,king,FG_COMM,
      &                   IERR)
+c        write (iout,*) "SCp bcast reduce ierr",ierr
 !        call MPI_Bcast(g_ilist_sc,1,MPI_INT,king,FG_COMM)
         else
 #endif
@@ -309,8 +356,11 @@ c        write(iout,*) "before bcast",g_ilist_sc
 #ifdef MPI
         endif
 #endif
+      if (fg_rank.eq.0 .and. (me.eq.king.or.out1file) .and. energy_dec) 
+     & write (iout,'(a30,i10,a,i4)') "Number of SC-p interactions",
+     & g_ilist_scp," per residue on average",g_ilist_scp/nres
 #ifdef DEBUG
-      write (iout,*) "after MPIREDUCE",g_ilist_scp
+      write (iout,*) "make_SCp_inter_list: after GATHERV",g_ilist_scp
       do i=1,g_ilist_scp
       write (iout,*) i,newcontlistscpi(i),newcontlistscpj(i)
       enddo
@@ -338,6 +388,7 @@ c        write(iout,*) "before bcast",g_ilist_sc
       include 'mpif.h'
       include "COMMON.SETUP"
 #endif
+      include "COMMON.CONTROL"
       include "COMMON.CHAIN"
       include "COMMON.INTERACT"
       include "COMMON.SPLITELE"
@@ -349,7 +400,8 @@ c        write(iout,*) "before bcast",g_ilist_sc
      &  xmedi,ymedi,zmedi
       double precision dx_normi,dy_normi,dz_normi,dxj,dyj,dzj,
      &  dx_normj,dy_normj,dz_normj
-      integer contlistpp_vdwi(2000*maxres),contlistpp_vdwj(2000*maxres)
+      integer contlistpp_vdwi(maxint_res*maxres),
+     & contlistpp_vdwj(maxint_res*maxres)
 !      integer :: newcontlistppi(200*nres),newcontlistppj(200*nres)
       integer i,j,itypi,itypj,subchap,xshift,yshift,zshift,iint,
      &  ilist_pp_vdw,g_ilist_pp_vdw
@@ -422,7 +474,7 @@ c        write(iout,*) "before bcast",g_ilist_sc
           enddo
           enddo
 
-          if (sqrt(dist_init).le.(r_cut_int+r_buff_list)) then
+          if (dsqrt(dist_init).le.(r_cut_int+r_buff_list)) then
 ! Here the list is created
             ilist_pp_vdw=ilist_pp_vdw+1
 ! this can be substituted by cantor and anti-cantor
@@ -443,6 +495,18 @@ c        write(iout,*) "before bcast",g_ilist_sc
 
         call MPI_Reduce(ilist_pp_vdw,g_ilist_pp_vdw,1,
      &    MPI_INTEGER,MPI_SUM,king,FG_COMM,IERR)
+        if (fg_rank.eq.0.and.g_ilist_pp_vdw.gt.maxres*maxint_res) then
+          if ((me.eq.king.or.out1file).and.energy_dec) then
+            write (iout,*) "Too many pp VDW interactions",
+     &      g_ilist_pp_vdw," only",maxres*maxint_res," allowed."
+            write (iout,*) "Specify a smaller r_cut_int and resubmit"
+            call flush(iout)
+          endif
+          write (*,*) "Processor:",me,": Too many pp VDW interactions",
+     &      g_ilist_pp_vdw," only",maxres*maxint_res," allowed."
+          write (8,*) "Specify a smaller r_cut_int and resubmit"
+          call MPI_Abort(MPI_COMM_WORLD,ierr)
+        endif
 !        write(iout,*) "before bcast",g_ilist_sc
         call MPI_Gather(ilist_pp_vdw,1,MPI_INTEGER,
      &                  i_ilist_pp_vdw,1,MPI_INTEGER,king,FG_COMM,IERR)
@@ -480,10 +544,14 @@ c        write(iout,*) "before bcast",g_ilist_sc
 #endif
         call int_bounds(g_ilist_pp_vdw,g_listpp_vdw_start,
      &       g_listpp_vdw_end)
+      if (fg_rank.eq.0 .and. (me.eq.king.or.out1file) .and. energy_dec) 
+     &write (iout,'(a30,i10,a,i4)') "Number of p-p VDW interactions",
+     & g_ilist_pp_vdw," per residue on average",g_ilist_pp_vdw/nres
 #ifdef DEBUG
       write (iout,*) "g_listpp_vdw_start",g_listpp_vdw_start,
      &  "g_listpp_vdw_end",g_listpp_vdw_end
-      write (iout,*) "after MPIREDUCE",g_ilist_pp_vdw
+      write (iout,*) "make_pp_vdw_inter_list: after GATHERV",
+     &  g_ilist_pp_vdw
       do i=1,g_ilist_pp_vdw
         write (iout,*) i,newcontlistpp_vdwi(i),newcontlistpp_vdwj(i)
       enddo
@@ -498,6 +566,7 @@ c        write(iout,*) "before bcast",g_ilist_sc
       include 'mpif.h'
       include "COMMON.SETUP"
 #endif
+      include "COMMON.CONTROL"
       include "COMMON.CHAIN"
       include "COMMON.INTERACT"
       include "COMMON.SPLITELE"
@@ -509,7 +578,8 @@ c        write(iout,*) "before bcast",g_ilist_sc
      &  xmedi,ymedi,zmedi
       double precision dx_normi,dy_normi,dz_normi,dxj,dyj,dzj,
      &  dx_normj,dy_normj,dz_normj
-      integer contlistppi(2000*maxres),contlistppj(2000*maxres)
+      integer contlistppi(maxint_res*maxres),
+     &  contlistppj(maxint_res*maxres)
 !      integer :: newcontlistppi(200*nres),newcontlistppj(200*nres)
       integer i,j,itypi,itypj,subchap,xshift,yshift,zshift,iint,
      &  ilist_pp,g_ilist_pp
@@ -582,7 +652,7 @@ c        write(iout,*) "before bcast",g_ilist_sc
        enddo
        enddo
 
-      if (sqrt(dist_init).le.(r_cut_int+r_buff_list)) then
+      if (dsqrt(dist_init).le.(r_cut_int+r_buff_list)) then
 ! Here the list is created
                  ilist_pp=ilist_pp+1
 ! this can be substituted by cantor and anti-cantor
@@ -603,9 +673,23 @@ c        write(iout,*) "before bcast",g_ilist_sc
 
         call MPI_Reduce(ilist_pp,g_ilist_pp,1,
      &    MPI_INTEGER,MPI_SUM,king,FG_COMM,IERR)
+c       write (iout,*) "After reduce ierr",ierr
+        if (fg_rank.eq.0.and.g_ilist_pp.gt.maxres*maxint_res) then
+          if ((me.eq.king.or.out1file).and.energy_dec) then
+            write (iout,*) "Too many pp interactions",
+     &      g_ilist_pp," only",maxres*maxint_res," allowed."
+            write (iout,*) "Specify a smaller r_cut_int and resubmit"
+            call flush(iout)
+          endif
+          write (*,*) "Processor:",me,": Too many pp interactions",
+     &      g_ilist_pp," only",maxres*maxint_res," allowed."
+          write (*,*) "Specify a smaller r_cut_int and resubmit"
+          call MPI_Abort(MPI_COMM_WORLD,ierr)
+        endif
 !        write(iout,*) "before bcast",g_ilist_sc
         call MPI_Gather(ilist_pp,1,MPI_INTEGER,
      &                  i_ilist_pp,1,MPI_INTEGER,king,FG_COMM,IERR)
+c       write (iout,*) "After gather ierr",ierr
         displ(0)=0
         do i=1,nfgtasks-1,1
           displ(i)=i_ilist_pp(i-1)+displ(i-1)
@@ -614,16 +698,21 @@ c        write(iout,*) "before bcast",g_ilist_sc
         call MPI_Gatherv(contlistppi,ilist_pp,MPI_INTEGER,
      &                   newcontlistppi,i_ilist_pp,displ,MPI_INTEGER,
      &                   king,FG_COMM,IERR)
+c       write (iout,*) "After gatherb ierr",ierr
         call MPI_Gatherv(contlistppj,ilist_pp,MPI_INTEGER,
      &                   newcontlistppj,i_ilist_pp,displ,MPI_INTEGER,
      &                   king,FG_COMM,IERR)
+c       write (iout,*) "After gatherb ierr",ierr
         call MPI_Bcast(g_ilist_pp,1,MPI_INT,king,FG_COMM,IERR)
 !        write(iout,*) "before bcast",g_ilist_sc
 !        call MPI_Bcast(g_ilist_sc,1,MPI_INT,king,FG_COMM)
+c       write (iout,*) "After bcast ierr",ierr
         call MPI_Bcast(newcontlistppi,g_ilist_pp,MPI_INT,king,FG_COMM,
      &                   IERR)
+c       write (iout,*) "After bcast ierr",ierr
         call MPI_Bcast(newcontlistppj,g_ilist_pp,MPI_INT,king,FG_COMM,
      &                   IERR)
+c       write (iout,*) "After bcast ierr",ierr
 
 !        call MPI_Bcast(g_ilist_sc,1,MPI_INT,king,FG_COMM)
 
@@ -639,8 +728,11 @@ c        write(iout,*) "before bcast",g_ilist_sc
         endif
 #endif
         call int_bounds(g_ilist_pp,g_listpp_start,g_listpp_end)
+      if (fg_rank.eq.0 .and. (me.eq.king.or.out1file) .and. energy_dec) 
+     & write (iout,'(a30,i10,a,i4)') "Number of p-p interactions",
+     & g_ilist_pp," per residue on average",g_ilist_pp/nres
 #ifdef DEBUG
-      write (iout,*) "after MPIREDUCE",g_ilist_pp
+      write (iout,*) "make_pp_inter_list: after GATHERV",g_ilist_pp
       do i=1,g_ilist_pp
       write (iout,*) i,newcontlistppi(i),newcontlistppj(i)
       enddo