X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2Fio.f90;h=243c8b62acd3bb43e9411004a82352433f27afad;hb=cfa004813be91a2b6c43e3e5fd6821b31198b81f;hp=acbbc3d91551a22c9d93933c61c936cf6f38cdbb;hpb=35f220f409bd5d21be33a402d79da2c23d3e0c3a;p=unres4.git diff --git a/source/unres/io.f90 b/source/unres/io.f90 index acbbc3d..243c8b6 100644 --- a/source/unres/io.f90 +++ b/source/unres/io.f90 @@ -632,6 +632,7 @@ endif #endif ! print *,"Processor",myrank," leaves READRTNS" +! write(iout,*) "end readrtns" return end subroutine readrtns !----------------------------------------------------------------------------- @@ -639,6 +640,7 @@ ! ! Read molecular data. ! +! use control, only: ilen use control_data use geometry_data use energy_data @@ -701,16 +703,10 @@ allocate(itype(maxres)) !(maxres) ! ! Zero out tables. -! - do i=1,2*maxres - do j=1,3 - c(j,i)=0.0D0 - dc(j,i)=0.0D0 - enddo - enddo - do i=1,maxres - itype(i)=0 - enddo +! + c(:,:)=0.0D0 + dc(:,:)=0.0D0 + itype(:)=0 !----------------------------- ! ! Body @@ -885,7 +881,7 @@ ! print *,'Finished reading pdb data' if(me.eq.king.or..not.out1file) & write (iout,'(a,i3,a,i3)')'nsup=',nsup,& - ' nstart_sup=',nstart_sup,"ergwergewrgae" + ' nstart_sup=',nstart_sup !,"ergwergewrgae" !el if(.not.allocated(itype_pdb)) allocate(itype_pdb(nres)) do i=1,nres @@ -933,8 +929,11 @@ itype(i)=rescode(i,sequence(i),iscode) enddo ! Assign initial virtual bond lengths +!elwrite(iout,*) "test_alloc" if(.not.allocated(vbld)) allocate(vbld(2*nres)) +!elwrite(iout,*) "test_alloc" if(.not.allocated(vbld_inv)) allocate(vbld_inv(2*nres)) +!elwrite(iout,*) "test_alloc" do i=2,nres vbld(i)=vbl vbld_inv(i)=vblinv @@ -950,35 +949,36 @@ ! print '(20i4)',(itype(i),i=1,nres) !---------------------------- !el reallocate tables - do i=1,maxres2 - do j=1,3 - c_alloc(j,i)=c(j,i) - dc_alloc(j,i)=dc(j,i) - enddo - enddo - do i=1,maxres +! do i=1,maxres2 +! do j=1,3 +! c_alloc(j,i)=c(j,i) +! dc_alloc(j,i)=dc(j,i) +! enddo +! enddo +! do i=1,maxres !elwrite(iout,*) "itype",i,itype(i) - itype_alloc(i)=itype(i) - enddo +! itype_alloc(i)=itype(i) +! enddo - deallocate(c) - deallocate(dc) - deallocate(itype) - allocate(c(3,2*nres+2)) - allocate(dc(3,0:2*nres)) - allocate(itype(nres+2)) +! deallocate(c) +! deallocate(dc) +! deallocate(itype) +! allocate(c(3,2*nres+4)) +! allocate(dc(3,0:2*nres+2)) +! allocate(itype(nres+2)) allocate(itel(nres+2)) + itel(:)=0 - do i=1,2*nres - do j=1,3 - c(j,i)=c_alloc(j,i) - dc(j,i)=dc_alloc(j,i) - enddo - enddo - do i=1,nres+2 - itype(i)=itype_alloc(i) - itel(i)=0 - enddo +! do i=1,2*nres+2 +! do j=1,3 +! c(j,i)=c_alloc(j,i) +! dc(j,i)=dc_alloc(j,i) +! enddo +! enddo +! do i=1,nres+2 +! itype(i)=itype_alloc(i) +! itel(i)=0 +! enddo !-------------------------- do i=1,nres #ifdef PROCOR @@ -992,9 +992,9 @@ #else else if (iabs(itype(i)).ne.20) then #endif - itel(i)=1 + itel(i)=1 else - itel(i)=2 + itel(i)=2 endif enddo if(me.eq.king.or..not.out1file)then @@ -1088,7 +1088,7 @@ if (nstart_seq.eq.0) nstart_seq=nnt if(me.eq.king.or..not.out1file) & write (iout,*) 'nsup=',nsup,' nstart_sup=',nstart_sup,& - ' nstart_seq=',nstart_seq,"242343453254" + ' nstart_seq=',nstart_seq !,"242343453254" endif !--- Zscore rms ------- if (nz_start.eq.0) nz_start=nnt