intoduction of quartic restrains in multichain, bugfix in single chain
[unres.git] / source / unres / src_MD / ssMD.F
index dd210e5..6c7d523 100644 (file)
@@ -512,9 +512,13 @@ c      implicit none
 
 c     Includes
       include 'DIMENSIONS'
+#ifdef MPI
+      include "mpif.h"
+#endif
       include 'COMMON.SBRIDGE'
       include 'COMMON.CHAIN'
       include 'COMMON.IOUNITS'
+      include 'COMMON.SETUP'
 #ifndef CLUST
 #ifndef WHAM
       include 'COMMON.MD'
@@ -528,7 +532,8 @@ c     Local variables
      &     allihpb(maxdim),alljhpb(maxdim),
      &     newnss,newihpb(maxdim),newjhpb(maxdim)
       logical found
-
+      integer i_newnss(max_fg_procs),displ(max_fg_procs)
+      integer g_newihpb(maxdim),g_newjhpb(maxdim),g_newnss
 
       allnss=0
       do i=1,nres-1
@@ -576,6 +581,37 @@ cmc      write(iout,*)"ALLNSS ",allnss,(allihpb(i),alljhpb(i),i=1,allnss)
           newjhpb(newnss)=alljhpb(i)
         endif
       enddo
+
+#ifdef MPI
+      if (nfgtasks.gt.1)then
+
+        call MPI_Reduce(newnss,g_newnss,1,
+     &    MPI_INTEGER,MPI_SUM,king,FG_COMM,IERR)
+        call MPI_Gather(newnss,1,MPI_INTEGER,
+     &                  i_newnss,1,MPI_INTEGER,king,FG_COMM,IERR)
+C        displ(0)=0
+        do i=1,nfgtasks-1,1
+          displ(i)=i_newnss(i-1)+displ(i-1)
+        enddo
+        call MPI_Gatherv(newihpb,newnss,MPI_INTEGER,
+     &                   g_newihpb,i_newnss,displ,MPI_INTEGER,
+     &                   king,FG_COMM,IERR)     
+        call MPI_Gatherv(newjhpb,newnss,MPI_INTEGER,
+     &                   g_newjhpb,i_newnss,displ,MPI_INTEGER,
+     &                   king,FG_COMM,IERR)     
+        if(fg_rank.eq.0) then
+c         print *,'g_newnss',g_newnss
+c         print *,'g_newihpb',(g_newihpb(i),i=1,g_newnss)
+c         print *,'g_newjhpb',(g_newjhpb(i),i=1,g_newnss)
+         newnss=g_newnss  
+         do i=1,newnss
+          newihpb(i)=g_newihpb(i)
+          newjhpb(i)=g_newjhpb(i)
+         enddo
+        endif
+      endif
+#endif
+
       diff=newnss-nss
 
 cmc      write(iout,*)"NEWNSS ",newnss,(newihpb(i),newjhpb(i),i=1,newnss)
@@ -583,13 +619,14 @@ cmc      write(iout,*)"NEWNSS ",newnss,(newihpb(i),newjhpb(i),i=1,newnss)
       do i=1,nss
         found=.false.
         do j=1,newnss
-          if (ihpb(i).eq.newihpb(j) .and.
-     &         jhpb(i).eq.newjhpb(j)) found=.true.
+          if (idssb(i).eq.newihpb(j) .and.
+     &         jdssb(i).eq.newjhpb(j)) found=.true.
         enddo
 #ifndef CLUST
 #ifndef WHAM
-        if (.not.found) write(iout,'(a15,f12.2,f8.1,2i5)')
-     &       "SSBOND_BREAK",totT,t_bath,ihpb(i),jhpb(i)
+        if (.not.found.and.fg_rank.eq.0) 
+     &      write(iout,'(a15,f12.2,f8.1,2i5)')
+     &       "SSBOND_BREAK",totT,t_bath,idssb(i),jdssb(i)
 #endif
 #endif
       enddo
@@ -597,83 +634,27 @@ cmc      write(iout,*)"NEWNSS ",newnss,(newihpb(i),newjhpb(i),i=1,newnss)
       do i=1,newnss
         found=.false.
         do j=1,nss
-          if (newihpb(i).eq.ihpb(j) .and.
-     &         newjhpb(i).eq.jhpb(j)) found=.true.
+          if (newihpb(i).eq.idssb(j) .and.
+     &         newjhpb(i).eq.jdssb(j)) found=.true.
         enddo
 #ifndef CLUST
 #ifndef WHAM
-        if (.not.found) write(iout,'(a15,f12.2,f8.1,2i5)')
+        if (.not.found.and.fg_rank.eq.0) 
+     &      write(iout,'(a15,f12.2,f8.1,2i5)')
      &       "SSBOND_FORM",totT,t_bath,newihpb(i),newjhpb(i)
 #endif
 #endif
       enddo
 
-c CRC this part of code is not clean, 
-c dyn_ss will not work with contrains
-
-      if (diff.gt.0) then
-        do i=1,diff
-          ihpb(nhpb+i)=ihpb(nss+i)
-          jhpb(nhpb+i)=jhpb(nss+i)
-          forcon(nhpb+i)=forcon(nss+i)
-          dhpb(nhpb+i)=dhpb(nss+i)
-        enddo
-      else if (diff.lt.0) then
-        do i=diff,-1
-         if(nss+i.gt.0.and.nhpb+i.gt.0) then
-          ihpb(nss+i)=ihpb(nhpb+i)
-          jhpb(nss+i)=jhpb(nhpb+i)
-          forcon(nss+i)=forcon(nhpb+i)
-          dhpb(nss+i)=dhpb(nhpb+i)
-         endif
-        enddo
-      endif
-
-      nhpb=nhpb+diff
       nss=newnss
       do i=1,nss
-        ihpb(i)=newihpb(i)
-        jhpb(i)=newjhpb(i)
+        idssb(i)=newihpb(i)
+        jdssb(i)=newjhpb(i)
       enddo
 
       return
       end
 
-c----------------------------------------------------------------------------
-
-#ifdef WHAM
-      subroutine read_ssHist
-      implicit none
-
-c     Includes
-      include 'DIMENSIONS'
-      include "DIMENSIONS.FREE"
-      include 'COMMON.FREE'
-
-c     Local variables
-      integer i,j
-      character*80 controlcard
-
-      do i=1,dyn_nssHist
-        call card_concat(controlcard,.true.)
-        read(controlcard,*)
-     &       dyn_ssHist(i,0),(dyn_ssHist(i,j),j=1,2*dyn_ssHist(i,0))
-      enddo
-
-      return
-      end
-#endif
-
-c----------------------------------------------------------------------------
-
-
-C-----------------------------------------------------------------------------
-C-----------------------------------------------------------------------------
-C-----------------------------------------------------------------------------
-C-----------------------------------------------------------------------------
-C-----------------------------------------------------------------------------
-C-----------------------------------------------------------------------------
-C-----------------------------------------------------------------------------
 
 c$$$c-----------------------------------------------------------------------------
 c$$$