X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2FMCM_MD.f90;h=657f0826ff89e6072a0bb62a1b0056b57306eb64;hb=10689ab7d813dfbdbb0c6e631d90234d78ea306a;hp=afb31bb4a99a86a7c2d5108f3720ad5d810f8582;hpb=299e2c41124d3fa8adba7244716515a2cc160ed1;p=unres4.git diff --git a/source/unres/MCM_MD.f90 b/source/unres/MCM_MD.f90 index afb31bb..657f082 100644 --- a/source/unres/MCM_MD.f90 +++ b/source/unres/MCM_MD.f90 @@ -161,6 +161,7 @@ nlist=0 #ifdef UNRES call var_to_geom(nvar,x) + write(iout,*) 'Warning calling chainbuild' call chainbuild do k=1,2*nres do kk=1,3 @@ -185,6 +186,7 @@ #ifdef UNRES call var_to_geom(nvar,x1) + write(iout,*) 'Warning calling chainbuild' call chainbuild !d write(iout,*)'C and CREF' !d write(iout,'(i5,3f10.5,5x,3f10.5)')(k,(c(j,k),j=1,3), @@ -439,6 +441,7 @@ WhatsUp=0 write (iout,'(/80(1h*)/a,i2/80(1h*)/)') 'MCE iteration #',isweep write (iout,'(/80(1h*)/a)') 'Initial energies:' + write(iout,*) 'Warning calling chainbuild' call chainbuild call etotal(energia) etot = energia(0) @@ -566,6 +569,7 @@ !d write (iout,'(10f8.1)') (rad2deg*varia(i),i=1,nvar) call var_to_geom(nvar,varia) ! Rebuild the chain. + write(iout,*) 'Warning calling chainbuild' call chainbuild MoveType=0 nbond=0 @@ -582,6 +586,7 @@ MoveType,' returned from PERTURB.' goto 20 endif + write(iout,*) 'Warning calling chainbuild' call chainbuild else MoveType=0 @@ -1034,8 +1039,8 @@ use energy_data use geometry_data - use MPI_data, only:ifinish,nctasks,WhatsUp,MyID - use control_data, only:refstr,MaxProcs + use MPI_data, only:ifinish,nctasks,WhatsUp,MyID,NProcs + use control_data, only:refstr !,MaxProcs use io_base use control, only:tcpu,ovrtim use regularize_, only:fitsq @@ -1067,12 +1072,12 @@ real(kind=8) :: przes(3),obr(3,3) real(kind=8),dimension(6*nres) :: varold !(maxvar) (maxvar=6*maxres) logical :: non_conv - integer,dimension(-1:MaxMoveType+1,0:MaxProcs-1) :: moves1,moves_acc1 !(-1:MaxMoveType+1,0:MaxProcs-1) + integer,dimension(-1:MaxMoveType+1,0:NProcs-1) :: moves1,moves_acc1 !(-1:MaxMoveType+1,0:MaxProcs-1) #ifdef MPL - real(kind=8) :: etot_temp,etot_all(0:MaxProcs) + real(kind=8) :: etot_temp,etot_all(0:NProcs) !(0:MaxProcs) external d_vadd,d_vmin,d_vmax real(kind=8),dimension(-max_ene:max_ene) :: entropy1,nhist1 - integer,dimension(nres*(MaxProcs+1)) :: nbond_move1,nbond_acc1 + integer,dimension(nres*(NProcs+1)) :: nbond_move1,nbond_acc1 !(nres*(MaxProcs+1)) integer,dimension(2) :: itemp #endif real(kind=8),dimension(6*nres) :: var_lowest !(maxvar) (maxvar=6*maxres) @@ -1193,6 +1198,7 @@ WhatsUp=0 write (iout,'(/80(1h*)/a,i2/80(1h*)/)') 'MCE iteration #',isweep write (iout,'(/80(1h*)/a)') 'Initial energies:' + write(iout,*) 'Warning calling chainbuild' call chainbuild call geom_to_var(nvar,varia) call etotal(energia) @@ -1335,6 +1341,7 @@ enddo call var_to_geom(nvar,varia) ! Rebuild the chain. + write(iout,*) 'Warning calling chainbuild' call chainbuild MoveType=0 nbond=0 @@ -1349,6 +1356,7 @@ varia(i)=xpool(i,ii) enddo call var_to_geom(nvar,varia) + write(iout,*) 'Warning calling chainbuild' call chainbuild !d call intout !d write (iout,'(10f8.1)') (rad2deg*varia(i),i=1,nvar) @@ -1910,9 +1918,9 @@ do i=1,nwindow i1=winstart(i) i2=winend(i) - it1=itype(i1) - it2=itype(i2) - write (iout,'(a,i3,a,i3,a,i3)') restyp(it1),i1,restyp(it2),i2,& + it1=itype(i1,1) + it2=itype(i2,1) + write (iout,'(a,i3,a,i3,a,i3)') restyp(it1,1),i1,restyp(it2,1),i2,& ' length',winlen(i) enddo endif @@ -1956,7 +1964,7 @@ ! print *,'nnt=',nnt,' nct=',nct ngly=0 do i=nnt,nct - if (itype(i).eq.10) ngly=ngly+1 + if (itype(i,1).eq.10) ngly=ngly+1 enddo mmm=nct-nnt-ngly+1 if (mmm.gt.0) then @@ -3035,7 +3043,7 @@ error=.true. return endif - if (itype(inds).eq.10) goto 111 + if (itype(inds,1).eq.10) goto 111 do j=1,i-1 if (inds.eq.ind_side(j)) goto 111 enddo @@ -3054,7 +3062,7 @@ ! Carry out perturbation. do i=1,nside_move ii=ind_side(i) - iti=itype(ii) + iti=itype(ii,1) call gen_side(iti,theta(ii+1),alph(ii),omeg(ii),fail) if (fail) then isctry=isctry+1 @@ -3066,7 +3074,7 @@ goto 301 endif if (print_mc.gt.1) write (iout,'(2a,i4,a,2f8.3)') & - 'Side chain ',restyp(iti),ii,' moved to ',& + 'Side chain ',restyp(iti,1),ii,' moved to ',& alph(ii)*rad2deg,omeg(ii)*rad2deg enddo moves(3)=moves(3)+1 @@ -3075,7 +3083,7 @@ !------------------------------------------------------------------------------ ! THETA move 400 end_select=iran_num(3,nres) - theta_new=gen_theta(itype(end_select),phi(end_select),& + theta_new=gen_theta(itype(end_select,1),phi(end_select),& phi(end_select+1)) if (print_mc.gt.1) write (iout,'(a,i3,a,f8.3,a,f8.3)') & 'Theta ',end_select,' moved from',theta(end_select)*rad2deg,&