X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2FMD.f90;h=3725902b446821db4a162c33a10183125febf9ca;hb=4fa6ed0fa1ee37552df6064fe60a73f218c101ca;hp=15fdf689fe73195a92084a6f5f6c78bf71bc6824;hpb=7035b39139b51c470f29086412b6ca2e98da40e5;p=unres4.git diff --git a/source/unres/MD.f90 b/source/unres/MD.f90 index 15fdf68..3725902 100644 --- a/source/unres/MD.f90 +++ b/source/unres/MD.f90 @@ -98,33 +98,33 @@ !el integer maxamino,maxnuc,maxbnd !el integer maxang,maxtors,maxpi !el integer maxpib,maxpit - integer :: maxatm !=2*nres !maxres2 maxres2=2*maxres - integer,parameter :: maxval=8 - integer,parameter :: maxgrp=1000 - integer,parameter :: maxtyp=3000 - integer,parameter :: maxclass=500 - integer,parameter :: maxkey=10000 - integer,parameter :: maxrot=1000 - integer,parameter :: maxopt=1000 - integer,parameter :: maxhess=1000000 - integer :: maxlight !=8*maxatm - integer,parameter :: maxvib=1000 - integer,parameter :: maxgeo=1000 - integer,parameter :: maxcell=10000 - integer,parameter :: maxring=10000 - integer,parameter :: maxfix=10000 - integer,parameter :: maxbio=10000 - integer,parameter :: maxamino=31 - integer,parameter :: maxnuc=12 - integer :: maxbnd !=2*maxatm - integer :: maxang !=3*maxatm - integer :: maxtors !=4*maxatm - integer,parameter :: maxpi=100 - integer,parameter :: maxpib=2*maxpi - integer,parameter :: maxpit=4*maxpi +! integer :: maxatm !=2*nres !maxres2 maxres2=2*maxres +! integer,parameter :: maxval=8 +! integer,parameter :: maxgrp=1000 +! integer,parameter :: maxtyp=3000 +! integer,parameter :: maxclass=500 +! integer,parameter :: maxkey=10000 +! integer,parameter :: maxrot=1000 +! integer,parameter :: maxopt=1000 +! integer,parameter :: maxhess=1000000 +! integer :: maxlight !=8*maxatm +! integer,parameter :: maxvib=1000 +! integer,parameter :: maxgeo=1000 +! integer,parameter :: maxcell=10000 +! integer,parameter :: maxring=10000 +! integer,parameter :: maxfix=10000 +! integer,parameter :: maxbio=10000 +! integer,parameter :: maxamino=31 +! integer,parameter :: maxnuc=12 +! integer :: maxbnd !=2*maxatm +! integer :: maxang !=3*maxatm +! integer :: maxtors !=4*maxatm +! integer,parameter :: maxpi=100 +! integer,parameter :: maxpib=2*maxpi +! integer,parameter :: maxpit=4*maxpi !----------------------------------------------------------------------------- ! Maximum number of seed - integer,parameter :: max_seed=1 +! integer,parameter :: max_seed=1 !----------------------------------------------------------------------------- real(kind=8),dimension(:),allocatable :: stochforcvec !(MAXRES6) maxres6=6*maxres ! common /stochcalc/ stochforcvec @@ -548,6 +548,7 @@ potE=potEcomp(0)-potEcomp(20) call cartgrad totT=totT+d_time + totTafm=totT ! Calculate the kinetic and total energy and the kinetic temperature call kinetic(EK) #ifdef MPI @@ -1001,6 +1002,7 @@ if (rstcount.eq.1000.or.itime.eq.n_timestep) then open(irest2,file=rest2name,status='unknown') write(irest2,*) totT,EK,potE,totE,t_bath + totTafm=totT ! AL 4/17/17: Now writing d_t(0,:) too do i=0,2*nres write (irest2,'(3e15.5)') (d_t(j,i),j=1,3) @@ -1163,6 +1165,12 @@ ! Calculate energy and forces call zerograd call etotal(potEcomp) +! AL 4/17/17: Reduce the steps if NaNs occurred. + if (potEcomp(0).gt.0.99e20 .or. isnan(potEcomp(0)).gt.0) then + d_time=d_time/2 + cycle + endif +! end change if (large.and. mod(itime,ntwe).eq.0) & call enerprint(potEcomp) #ifdef TIMING_ENE @@ -1281,6 +1289,7 @@ endif if (rattle) call rattle2 totT=totT+d_time + totTafm=totT if (d_time.ne.d_time0) then d_time=d_time0 #ifndef LANG0 @@ -1538,6 +1547,25 @@ ! Calculate energy and forces call zerograd call etotal_short(energia_short) +! AL 4/17/17: Exit itime_split loop when energy goes infinite + if (energia_short(0).gt.0.99e20 .or. isnan(energia_short(0)) ) then + if (PRINT_AMTS_MSG) & + write (iout,*) "Infinities/NaNs in energia_short",energia_short(0),"; increasing ntime_split to",ntime_split + ntime_split=ntime_split*2 + if (ntime_split.gt.maxtime_split) then +#ifdef MPI + write (iout,*) & + "Cannot rescue the run; aborting job. Retry with a smaller time step" + call flush(iout) + call MPI_Abort(MPI_COMM_WORLD,IERROR,ERRCODE) +#else + write (iout,*) & + "Cannot rescue the run; terminating. Retry with a smaller time step" +#endif + endif + exit + endif +! End change if (large.and. mod(itime,ntwe).eq.0) & call enerprint(energia_short) #ifdef TIMING_ENE @@ -1580,6 +1608,8 @@ if (ntime_split.lt.maxtime_split) then scale=.true. ntime_split=ntime_split*2 +! AL 4/17/17: We should exit the itime_split loop when acceleration change is too big + exit do i=0,2*nres do j=1,3 dc_old(j,i)=dc_old0(j,i) @@ -1642,6 +1672,17 @@ #endif call zerograd call etotal_long(energia_long) + if (energia_long(0).gt.0.99e20 .or. isnan(energia_long(0))) then +#ifdef MPI + write (iout,*) & + "Infinitied/NaNs in energia_long, Aborting MPI job." + call flush(iout) + call MPI_Abort(MPI_COMM_WORLD,IERROR,ERRCODE) +#else + write (iout,*) "Infinitied/NaNs in energia_long, terminating." + stop +#endif + endif if (large.and. mod(itime,ntwe).eq.0) & call enerprint(energia_long) #ifdef TIMING_ENE @@ -1688,6 +1729,7 @@ potE=potEcomp(0)-potEcomp(20) ! potE=energia_short(0)+energia_long(0) totT=totT+d_time + totTafm=totT ! Calculate the kinetic and the total energy and the kinetic temperature call kinetic(EK) totE=EK+potE @@ -2365,6 +2407,7 @@ endif call random_vel totT=0.0d0 + totTafm=totT endif else ! Generate initial velocities @@ -2372,6 +2415,7 @@ write(iout,*) "Initial velocities randomly generated" call random_vel totT=0.0d0 + totTafm=totT endif ! rest2name = prefix(:ilen(prefix))//'.rst' if(me.eq.king.or..not.out1file)then @@ -2397,7 +2441,7 @@ write (iout,*) "vcm right after adjustment:" write (iout,*) (vcm(j),j=1,3) endif - if (.not.rest) then + if ((.not.rest).and.(indpdb.eq.0)) then call chainbuild if(iranconf.ne.0) then if (overlapsc) then @@ -4443,7 +4487,7 @@ !el common /przechowalnia/ GGinv,gdc,Cmat,nbond !el common /przechowalnia/ nbond integer :: max_rattle = 5 - logical :: lprn = .true., lprn1 = .true., not_done + logical :: lprn = .false., lprn1 = .false., not_done real(kind=8) :: tol_rattle = 1.0d-5 integer :: nres2 nres2=2*nres @@ -5467,11 +5511,11 @@ logical :: omit(maxarc) ! ! include 'sizes.i' - maxatm = 2*nres !maxres2 maxres2=2*maxres - maxlight = 8*maxatm - maxbnd = 2*maxatm - maxang = 3*maxatm - maxtors = 4*maxatm +! maxatm = 2*nres !maxres2 maxres2=2*maxres +! maxlight = 8*maxatm +! maxbnd = 2*maxatm +! maxang = 3*maxatm +! maxtors = 4*maxatm ! ! zero out the surface area for the sphere of interest !