X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2FMREMD.f90;h=0630c7dec76949b325d688804125beb756b02aef;hb=d9408016c2011e3dade935da06f883a2665bb73b;hp=ef6ac045e09904c6336cb4895cab73ed7a73f58e;hpb=affbf55b871a9bcc8fdb91efeb8e6bf7a3d8d003;p=unres4.git diff --git a/source/unres/MREMD.f90 b/source/unres/MREMD.f90 index ef6ac04..0630c7d 100644 --- a/source/unres/MREMD.f90 +++ b/source/unres/MREMD.f90 @@ -193,8 +193,8 @@ !d print '(i4,a6,100i4)',me,' ndown',(ndown(i),i=0,ndown(0)) !el common /przechowalnia/ - if(.not.allocated(d_restart1)) allocate(d_restart1(3,nres2*nodes)) - if(.not.allocated(d_restart2)) allocate(d_restart2(3,nres2*nodes)) + if(.not.allocated(d_restart1)) allocate(d_restart1(3,(nres2+1)*nodes)) + if(.not.allocated(d_restart2)) allocate(d_restart2(3,(nres2+1)*nodes)) if(.not.allocated(p_c)) allocate(p_c(3,(nres2+2)*nodes)) !el------------- @@ -1331,7 +1331,7 @@ !el real(kind=4) :: d_restart1(3,2*nres*maxprocs),& !el d_restart2(3,2*nres*maxprocs) - real(kind=4) :: r_d(3,2*nres) + real(kind=4) :: r_d(3,0:2*nres) real(kind=4) :: t5_restart1(5) integer :: iret,itmp integer(kind=2) :: i_index(Nprocs/4,Nprocs/20,Nprocs/200,Nprocs/200) @@ -1349,23 +1349,26 @@ t_restart1,5,mpi_real,king,CG_COMM,ierr) - do i=1,2*nres + do i=0,2*nres do j=1,3 r_d(j,i)=d_t(j,i) enddo enddo - call mpi_gather(r_d,3*2*nres,mpi_real,& - d_restart1,3*2*nres,mpi_real,king,& + call mpi_gather(r_d,3*2*nres+3,mpi_real,& + d_restart1,3*2*nres+3,mpi_real,king,& CG_COMM,ierr) + do j=1,3 + dc(j,0)=c(j,1) + enddo - do i=1,2*nres + do i=0,2*nres do j=1,3 r_d(j,i)=dc(j,i) enddo enddo - call mpi_gather(r_d,3*2*nres,mpi_real,& - d_restart2,3*2*nres,mpi_real,king,& + call mpi_gather(r_d,3*2*nres+3,mpi_real,& + d_restart2,3*2*nres+3,mpi_real,king,& CG_COMM,ierr) if(me.eq.king) then @@ -1394,16 +1397,16 @@ enddo do il=0,nodes-1 - do i=1,2*nres + do i=0,2*nres do j=1,3 - call xdrffloat_(ixdrf, d_restart1(j,i+2*nres*il), iret) + call xdrffloat_(ixdrf, d_restart1(j,i+(2*nres+1)*il), iret) enddo enddo enddo do il=0,nodes-1 - do i=1,2*nres + do i=0,2*nres do j=1,3 - call xdrffloat_(ixdrf, d_restart2(j,i+2*nres*il), iret) + call xdrffloat_(ixdrf, d_restart2(j,i+(2*nres+1)*il), iret) enddo enddo enddo @@ -1454,16 +1457,16 @@ enddo do il=0,nodes-1 - do i=1,2*nres + do i=0,2*nres do j=1,3 - call xdrffloat(ixdrf, d_restart1(j,i+2*nres*il), iret) + call xdrffloat(ixdrf, d_restart1(j,i+(2*nres+1)*il), iret) enddo enddo enddo do il=0,nodes-1 - do i=1,2*nres + do i=0,2*nres do j=1,3 - call xdrffloat(ixdrf, d_restart2(j,i+2*nres*il), iret) + call xdrffloat(ixdrf, d_restart2(j,i+(2*nres+1)*il), iret) enddo enddo enddo @@ -1744,7 +1747,7 @@ ! include 'COMMON.SBRIDGE' ! include 'COMMON.INTERACT' !el real(kind=4) :: d_restart1(3,2*nres*maxprocs) - real(kind=4) :: r_d(3,2*nres),t5_restart1(5) + real(kind=4) :: r_d(3,0:2*nres),t5_restart1(5) integer(kind=2) :: i_index(Nprocs/4,Nprocs/20,Nprocs/200,Nprocs/200) !(maxprocs/4,maxprocs/20,maxprocs/200,maxprocs/200) !el common /przechowalnia/ d_restart1 @@ -1821,45 +1824,45 @@ if(me.eq.king)then do il=0,nodes-1 - do i=1,2*nres + do i=0,2*nres ! read(irest2,'(3e15.5)') ! & (d_restart1(j,i+2*nres*il),j=1,3) do j=1,3 #ifdef AIX - call xdrffloat_(ixdrf, d_restart1(j,i+2*nres*il), iret) + call xdrffloat_(ixdrf, d_restart1(j,i+(2*nres+1)*il), iret) #else - call xdrffloat(ixdrf, d_restart1(j,i+2*nres*il), iret) + call xdrffloat(ixdrf, d_restart1(j,i+(2*nres+1)*il), iret) #endif enddo enddo enddo endif - call mpi_scatter(d_restart1,3*2*nres,mpi_real,& - r_d,3*2*nres,mpi_real,king,CG_COMM,ierr) + call mpi_scatter(d_restart1,3*2*nres+3,mpi_real,& + r_d,3*2*nres+3,mpi_real,king,CG_COMM,ierr) - do i=1,2*nres + do i=0,2*nres do j=1,3 d_t(j,i)=r_d(j,i) enddo enddo if(me.eq.king)then do il=0,nodes-1 - do i=1,2*nres + do i=0,2*nres ! read(irest2,'(3e15.5)') ! & (d_restart1(j,i+2*nres*il),j=1,3) do j=1,3 #ifdef AIX - call xdrffloat_(ixdrf, d_restart1(j,i+2*nres*il), iret) + call xdrffloat_(ixdrf, d_restart1(j,i+(2*nres+1)*il), iret) #else - call xdrffloat(ixdrf, d_restart1(j,i+2*nres*il), iret) + call xdrffloat(ixdrf, d_restart1(j,i+(2*nres+1)*il), iret) #endif enddo enddo enddo endif - call mpi_scatter(d_restart1,3*2*nres,mpi_real,& - r_d,3*2*nres,mpi_real,king,CG_COMM,ierr) - do i=1,2*nres + call mpi_scatter(d_restart1,3*2*nres+3,mpi_real,& + r_d,3*2*nres+3,mpi_real,king,CG_COMM,ierr) + do i=0,2*nres do j=1,3 dc(j,i)=r_d(j,i) enddo @@ -1931,7 +1934,7 @@ ! include 'COMMON.SBRIDGE' ! include 'COMMON.INTERACT' !el real(kind=4) :: d_restart1(3,2*nres*maxprocs) - real(kind=4) :: r_d(3,2*nres),t5_restart1(5) + real(kind=4) :: r_d(3,0:2*nres),t5_restart1(5) !el common /przechowalnia/ d_restart1 integer :: i,j,il,ierr @@ -1958,16 +1961,16 @@ if(me.eq.king)then do il=0,nodes-1 - do i=1,2*nres + do i=0,2*nres read(irest2,'(3e15.5)') & - (d_restart1(j,i+2*nres*il),j=1,3) + (d_restart1(j,i+(2*nres+1)*il),j=1,3) enddo enddo endif - call mpi_scatter(d_restart1,3*2*nres,mpi_real,& - r_d,3*2*nres,mpi_real,king,CG_COMM,ierr) + call mpi_scatter(d_restart1,3*2*nres+3,mpi_real,& + r_d,3*2*nres+3,mpi_real,king,CG_COMM,ierr) - do i=1,2*nres + do i=0,2*nres do j=1,3 d_t(j,i)=r_d(j,i) enddo @@ -1976,13 +1979,13 @@ do il=0,nodes-1 do i=1,2*nres read(irest2,'(3e15.5)') & - (d_restart1(j,i+2*nres*il),j=1,3) + (d_restart1(j,i+(2*nres+1)*il),j=1,3) enddo enddo endif - call mpi_scatter(d_restart1,3*2*nres,mpi_real,& - r_d,3*2*nres,mpi_real,king,CG_COMM,ierr) - do i=1,2*nres + call mpi_scatter(d_restart1,3*2*nres+3,mpi_real,& + r_d,3*2*nres+3,mpi_real,king,CG_COMM,ierr) + do i=0,2*nres do j=1,3 dc(j,i)=r_d(j,i) enddo