2 C Does modified entropic sampling in the space of minima.
3 implicit real*8 (a-h,o-z)
5 include 'COMMON.IOUNITS'
10 include 'COMMON.CHAIN'
13 include 'COMMON.CONTACTS'
14 include 'COMMON.CONTROL'
16 include 'COMMON.INTERACT'
17 include 'COMMON.THREAD'
18 include 'COMMON.NAMES'
19 logical accepted,not_done,over,ovrtim,error,lprint
20 integer MoveType,nbond
22 double precision RandOrPert
23 double precision varia(maxvar),elowest,ehighest,eold
24 double precision przes(3),obr(3,3)
25 double precision varold(maxvar)
27 double precision energia(0:n_ene),energia_ave(0:n_ene)
29 cd write (iout,*) 'print_mc=',print_mc
32 c---------------------------------------------------------------------------
33 C Initialize counters.
34 c---------------------------------------------------------------------------
35 C Total number of generated confs.
37 C Total number of moves. In general this won't be equal to the number of
38 C attempted moves, because we may want to reject some "bad" confs just by
41 C Total number of shift (nbond_move(1)), spike, crankshaft, three-bond,...
46 C Initialize total and accepted number of moves of various kind.
51 C Total number of energy evaluations.
57 facee=1.0D0/(maxacc*delte)
59 C Read entropy from previous simulations.
61 read (ientin,*) indminn,indmaxx,emin,emax
62 print *,'indminn=',indminn,' indmaxx=',indmaxx,' emin=',emin,
65 entropy(i)=(emin+i*delte)*betbol
67 read (ientin,*) (ijunk,ejunk,entropy(i),i=indminn,indmaxx)
70 write (iout,*) 'indminn=',indminn,' indmaxx=',indmaxx,
71 & ' emin=',emin,' emax=',emax
72 write (iout,'(/a)') 'Initial entropy'
74 write (iout,'(i5,2f10.5)') i,emin+i*delte,entropy(i)
77 C Read the pool of conformations
79 C----------------------------------------------------------------------------
80 C Entropy-sampling simulations with continually updated entropy
81 C Loop thru simulations
82 C----------------------------------------------------------------------------
84 C----------------------------------------------------------------------------
85 C Take a conformation from the pool
86 C----------------------------------------------------------------------------
92 write (iout,*) 'Took conformation',ii,' from the pool energy=',
94 call var_to_geom(nvar,varia)
95 C Print internal coordinates of the initial conformation
98 call gen_rand_conf(1,*20)
100 C----------------------------------------------------------------------------
101 C Compute and print initial energies.
102 C----------------------------------------------------------------------------
105 if (MyID.eq.MasterID) then
113 write (iout,'(/80(1h*)/a,i2/80(1h*)/)') 'MCE iteration #',isweep
114 write (iout,'(/80(1h*)/a)') 'Initial energies:'
116 call etotal(energia(0))
118 call enerprint(energia(0))
119 C Minimize the energy of the first conformation.
121 call geom_to_var(nvar,varia)
122 call minimize(etot,varia,iretcode,nfun)
123 call etotal(energia(0))
125 write (iout,'(/80(1h*)/a/80(1h*))')
126 & 'Results of the first energy minimization:'
127 call enerprint(energia(0))
130 call fitsq(rms,c(1,nstart_seq),cref(1,nstart_sup),nsup,przes,
133 call contact(.false.,ncont,icont,co)
134 frac=contact_fract(ncont,ncont_ref,icont,icont_ref)
135 write (iout,'(a,f8.3,a,f8.3,a,f8.3)')
136 & 'RMS deviation from the reference structure:',rms,
137 & ' % of native contacts:',frac*100,' contact order:',co
138 write (istat,'(i5,11(1pe14.5))') 0,
139 & (energia(print_order(i)),i=1,nprint_ene),etot,rms,frac,co
141 write (istat,'(i5,9(1pe14.5))') 0,
142 & (energia(print_order(i)),i=1,nprint_ene),etot
145 neneval=neneval+nfun+1
146 if (.not. ent_read) then
147 C Initialize the entropy array
148 do i=-max_ene,max_ene
150 C Uncomment the line below for actual entropic sampling (start with uniform
151 C energy distribution).
153 C Uncomment the line below for multicanonical sampling (start with Boltzmann
155 entropy(i)=(emin+i*delte)*betbol
159 write (iout,'(/a)') 'Initial entropy'
161 write (iout,'(i5,2f10.5)') i,emin+i*delte,entropy(i)
165 call recv_stop_sig(Kwita)
166 if (whatsup.eq.1) then
167 call send_stop_sig(-2)
169 else if (whatsup.le.-2) then
171 else if (whatsup.eq.2) then
177 not_done = (iretcode.ne.11)
179 write (iout,'(/80(1h*)/20x,a/80(1h*))')
180 & 'Enter Monte Carlo procedure.'
182 call briefout(0,etot)
187 indeold=(eold-emin)/delte
188 deix=eold-(emin+indeold*delte)
189 dent=entropy(indeold+1)-entropy(indeold)
190 cd write (iout,*) 'indeold=',indeold,' deix=',deix,' dent=',dent
191 cd write (*,*) 'Processor',MyID,' indeold=',indeold,' deix=',deix,
193 sold=entropy(indeold)+(dent/delte)*deix
195 write (iout,*) 'eold=',eold,' sold=',sold,' elowest=',etot
196 write (*,*) 'Processor',MyID,' eold=',eold,' sold=',sold,
198 if (minim) call zapis(varia,etot)
200 C NACC is the counter for the accepted conformations of a given processor
202 C NACC_TOT counts the total number of accepted conformations
205 if (MyID.eq.MasterID) then
206 call receive_MCM_info
208 call send_MCM_info(2)
211 do iene=indminn,indmaxx
218 c----------------------------------------------------------------------------
224 if (print_mc.gt.0) write (iout,'(80(1h*)/20x,a,i7)')
225 & 'Beginning iteration #',it
226 C Initialize local counter.
227 ntrial=0 ! # of generated non-overlapping confs.
228 noverlap=0 ! # of overlapping confs.
230 do while (.not. accepted .and. WhatsUp.eq.0 .and. Kwita.eq.0)
232 C Retrieve the angles of previously accepted conformation
236 cd write (iout,'(a)') 'Old variables:'
237 cd write (iout,'(10f8.1)') (rad2deg*varia(i),i=1,nvar)
238 call var_to_geom(nvar,varia)
244 C Decide whether to generate a random conformation or perturb the old one
245 RandOrPert=ran_number(0.0D0,1.0D0)
246 if (RandOrPert.gt.RanFract) then
248 & write (iout,'(a)') 'Perturbation-generated conformation.'
249 call perturb(error,lprint,MoveType,nbond,1.0D0)
251 if (MoveType.lt.1 .or. MoveType.gt.MaxMoveType) then
252 write (iout,'(/a,i7,a/)') 'Error - unknown MoveType=',
253 & MoveType,' returned from PERTURB.'
260 nstart_grow=iran_num(3,nres)
262 & write (iout,'(2a,i3)') 'Random-generated conformation',
263 & ' - chain regrown from residue',nstart_grow
264 call gen_rand_conf(nstart_grow,*30)
266 call geom_to_var(nvar,varia)
267 cd write (iout,'(a)') 'New variables:'
268 cd write (iout,'(10f8.1)') (rad2deg*varia(i),i=1,nvar)
270 if (print_mc.gt.0) write (iout,'(a,i5,a,i10,a,i10)')
271 & 'Processor',MyId,' trial move',ntrial,' total generated:',ngen
272 if (print_mc.gt.0) write (*,'(a,i5,a,i10,a,i10)')
273 & 'Processor',MyId,' trial move',ntrial,' total generated:',ngen
274 call etotal(energia(0))
276 c call enerprint(energia(0))
277 c write (iout,'(2(a,1pe14.5))') 'Etot=',Etot,' Elowest=',Elowest
278 if (etot-elowest.gt.overlap_cut) then
279 write (iout,'(a,i5,a,1pe14.5)') 'Iteration',it,
280 & ' Overlap detected in the current conf.; energy is',etot
284 if (noverlap.gt.maxoverlap) then
285 write (iout,'(a)') 'Too many overlapping confs.'
290 call minimize(etot,varia,iretcode,nfun)
291 cd write (iout,'(a)') 'Variables after minimization:'
292 cd write (iout,'(10f8.1)') (rad2deg*varia(i),i=1,nvar)
293 call etotal(energia(0))
295 neneval=neneval+nfun+1
297 if (print_mc.gt.2) then
298 write (iout,'(a)') 'Total energies of trial conf:'
299 call enerprint(energia(0))
300 else if (print_mc.eq.1) then
301 write (iout,'(a,i6,a,1pe16.6)')
302 & 'Trial conformation:',ngen,' energy:',etot
304 C--------------------------------------------------------------------------
306 C--------------------------------------------------------------------------
309 & call accepting(etot,eold,scur,sold,varia,varold,
314 if (elowest.gt.etot) elowest=etot
315 if (ehighest.lt.etot) ehighest=etot
316 moves_acc(MoveType)=moves_acc(MoveType)+1
317 if (MoveType.eq.1) then
318 nbond_acc(nbond)=nbond_acc(nbond)+1
320 C Check against conformation repetitions.
321 irep=conf_comp(varia,etot)
322 #if defined(AIX) || defined(PGI)
323 open (istat,file=statname,position='append')
325 open (istat,file=statname,access='append')
328 call fitsq(rms,c(1,nstart_seq),cref(1,nstart_sup),nsup,
329 & przes,obr,non_conv)
331 call contact(.false.,ncont,icont,co)
332 frac=contact_fract(ncont,ncont_ref,icont,icont_ref)
334 & write (iout,'(a,f8.3,a,f8.3,a,f8.3)')
335 & 'RMS deviation from the reference structure:',rms,
336 & ' % of native contacts:',frac*100,' contact order:',co
338 & write (istat,'(i5,11(1pe14.5))') it,
339 & (energia(print_order(i)),i=1,nprint_ene),etot,
341 elseif (print_stat) then
342 write (istat,'(i5,10(1pe14.5))') it,
343 & (energia(print_order(i)),i=1,nprint_ene),etot
347 & call statprint(nacc,nfun,iretcode,etot,elowest)
348 C Print internal coordinates.
349 if (print_int) call briefout(nacc,etot)
351 if (MyID.ne.MasterID) then
352 call recv_stop_sig(Kwita)
353 cd print *,'Processor:',MyID,' STOP=',Kwita
355 call send_MCM_info(2)
357 call send_MCM_info(1)
361 C Store the accepted conf. and its energy.
369 cd write (iout,*) 'Accepted conformation:'
370 cd write (iout,*) (rad2deg*varia(i),i=1,nphi)
371 if (minim) call zapis(varia,etot)
373 ener(i,nsave)=energia(i)
375 ener(n_ene+1,nsave)=etot
376 ener(n_ene+2,nsave)=frac
378 nminima(irep)=nminima(irep)+1.0D0
379 c print *,'irep=',irep,' nminima=',nminima(irep)
381 if (Kwita.eq.0) call recv_stop_sig(kwita)
386 if (MyID.eq.MasterID) then
387 call receive_MCM_info
388 if (nacc_tot.ge.maxacc) accepted=.true.
391 if (ntrial.gt.maxtrial_iter .and. npool.gt.0) then
392 C Take a conformation from the pool
397 write (iout,*) 'Iteration',it,' max. # of trials exceeded.'
399 & 'Take conformation',ii,' from the pool energy=',epool(ii)
401 & write (iout,'(10f8.3)') (rad2deg*varia(i),i=1,nvar)
403 endif ! (ntrial.gt.maxtrial_iter .and. npool.gt.0)
407 if (MyID.eq.MasterID) then
408 call receive_MCM_info
410 if (Kwita.eq.0) call recv_stop_sig(kwita)
412 if (ovrtim()) WhatsUp=-1
413 cd write (iout,*) 'WhatsUp=',WhatsUp,' Kwita=',Kwita
414 not_done = (nacc_tot.lt.maxacc) .and. (WhatsUp.eq.0)
416 cd write (iout,*) 'not_done=',not_done
419 print *,'Processor',MyID,
420 & ' has received STOP signal =',Kwita,' in EntSamp.'
421 cd print *,'not_done=',not_done
422 if (Kwita.lt.-1) WhatsUp=Kwita
423 else if (nacc_tot.ge.maxacc) then
424 print *,'Processor',MyID,' calls send_stop_sig,',
425 & ' because a sufficient # of confs. have been collected.'
426 cd print *,'not_done=',not_done
427 call send_stop_sig(-1)
428 else if (WhatsUp.eq.-1) then
429 print *,'Processor',MyID,
430 & ' calls send_stop_sig because of timeout.'
431 cd print *,'not_done=',not_done
432 call send_stop_sig(-2)
437 C-----------------------------------------------------------------
438 C... Construct energy histogram & update entropy
439 C-----------------------------------------------------------------
443 write (iout,*) 'Processor',MyID,
444 & ' is broadcasting ERROR-STOP signal.'
445 write (*,*) 'Processor',MyID,
446 & ' is broadcasting ERROR-STOP signal.'
447 call send_stop_sig(-3)
451 if (MyID.eq.MasterID) then
452 c call receive_MCM_results
453 call receive_energies
456 if (esave(i).lt.elowest) elowest=esave(i)
457 if (esave(i).gt.ehighest) ehighest=esave(i)
459 write (iout,'(a,i10)') '# of accepted confs:',nacc_tot
460 write (iout,'(a,f10.5,a,f10.5)') 'Lowest energy:',elowest,
461 & ' Highest energy',ehighest
462 if (isweep.eq.1 .and. .not.ent_read) then
465 write (iout,*) 'EMAX=',emax
467 indmaxx=(ehighest-emin)/delte
470 do i=-max_ene,max_ene
471 entropy(i)=(emin+i*delte)*betbol
475 indmin=(elowest-emin)/delte
476 indmax=(ehighest-emin)/delte
477 if (indmin.lt.indminn) indminn=indmin
478 if (indmax.gt.indmaxx) indmaxx=indmax
480 write(iout,*)'indminn=',indminn,' indmaxx=',indmaxx
481 C Construct energy histogram
483 inde=(esave(i)-emin)/delte
484 nhist(inde)=nhist(inde)+nminima(i)
486 C Update entropy (density of states)
488 if (nhist(i).gt.0) then
489 entropy(i)=entropy(i)+dlog(nhist(i)+0.0D0)
493 Cd entropy(i)=1.0D+10
495 write (iout,'(/80(1h*)/a,i2/80(1h*)/)')
496 & 'End of macroiteration',isweep
497 write (iout,'(a,f10.5,a,f10.5)') 'Elowest=',elowest,
498 & ' Ehighest=',ehighest
499 write (iout,'(a)') 'Frequecies of minima'
501 write (iout,'(i5,f5.0,f10.5)') i,nminima(i),esave(i)
503 write (iout,'(/a)') 'Energy histogram'
505 write (iout,'(i5,2f10.5)') i,emin+i*delte,nhist(i)
507 write (iout,'(/a)') 'Entropy'
509 write (iout,'(i5,2f10.5)') i,emin+i*delte,entropy(i)
511 C-----------------------------------------------------------------
512 C... End of energy histogram construction
513 C-----------------------------------------------------------------
515 entropy(-max_ene-4)=dfloat(indminn)
516 entropy(-max_ene-3)=dfloat(indmaxx)
517 entropy(-max_ene-2)=emin
518 entropy(-max_ene-1)=emax
520 cd print *,entname,ientout
521 open (ientout,file=entname,status='unknown')
522 write (ientout,'(2i5,2e25.17)') indminn,indmaxx,emin,emax
524 write (ientout,'(i5,f10.5,f20.15)') i,emin+i*delte,entropy(i)
528 write (iout,'(a)') 'Frequecies of minima'
530 write (iout,'(i5,f5.0,f10.5)') i,nminima(i),esave(i)
532 c call send_MCM_results
534 call receive_MCM_update
535 indminn=entropy(-max_ene-4)
536 indmaxx=entropy(-max_ene-3)
537 emin=entropy(-max_ene-2)
538 emax=entropy(-max_ene-1)
539 write (iout,*) 'Received from master:'
540 write (iout,*) 'indminn=',indminn,' indmaxx=',indmaxx,
541 & ' emin=',emin,' emax=',emax
542 write (iout,'(/a)') 'Entropy'
544 write (iout,'(i5,2f10.5)') i,emin+i*delte,entropy(i)
547 if (WhatsUp.lt.-1) return
549 if (ovrtim() .or. WhatsUp.lt.0) return
552 write (iout,'(/80(1h*)/20x,a)') 'Summary run statistics:'
553 call statprint(nacc,nfun,iretcode,etot,elowest)
555 & 'Statistics of multiple-bond motions. Total motions:'
556 write (iout,'(16i5)') (nbond_move(i),i=1,Nbm)
557 write (iout,'(a)') 'Accepted motions:'
558 write (iout,'(16i5)') (nbond_acc(i),i=1,Nbm)
559 write (iout,'(a,i10)') 'Number of chain regrowths:',nregrow
560 write (iout,'(a,i10)') 'Accepted chain regrowths:',nregrow_acc
562 C---------------------------------------------------------------------------
564 C---------------------------------------------------------------------------
568 if (isweep.eq.nsweep .and. it.ge.maxacc)
569 &write (iout,'(/80(1h*)/20x,a/80(1h*)/)') 'All iterations done.'
572 c------------------------------------------------------------------------------
573 subroutine accepting(ecur,eold,scur,sold,x,xold,accepted)
574 implicit real*8 (a-h,o-z)
578 include 'COMMON.IOUNITS'
581 include 'COMMON.INFO'
584 double precision ecur,eold,xx,ran_number,bol
585 double precision x(maxvar),xold(maxvar)
586 double precision tole /1.0D-1/, tola /5.0D0/
588 C Check if the conformation is similar.
589 cd write (iout,*) 'Enter ACCEPTING'
590 cd write (iout,*) 'Old PHI angles:'
591 cd write (iout,*) (rad2deg*xold(i),i=1,nphi)
592 cd write (iout,*) 'Current angles'
593 cd write (iout,*) (rad2deg*x(i),i=1,nphi)
594 cd ddif=dif_ang(nphi,x,xold)
595 cd write (iout,*) 'Angle norm:',ddif
596 cd write (iout,*) 'ecur=',ecur,' emax=',emax
597 if (ecur.gt.emax) then
600 & write (iout,'(a)') 'Conformation rejected as too high in energy'
602 else if (dabs(ecur-eold).lt.tole .and.
603 & dif_ang(nphi,x,xold).lt.tola) then
606 & write (iout,'(a)') 'Conformation rejected as too similar'
609 C Else evaluate the entropy of the conf and compare it with that of the previous
611 indecur=(ecur-emin)/delte
612 if (iabs(indecur).gt.max_ene) then
613 write (iout,'(a,2i5)')
614 & 'Accepting: Index out of range:',indecur
616 else if (indecur.eq.indmaxx) then
617 scur=entropy(indecur)
618 if (print_mc.gt.0) write (iout,*)'Energy boundary reached',
619 & indmaxx,indecur,entropy(indecur)
621 deix=ecur-(emin+indecur*delte)
622 dent=entropy(indecur+1)-entropy(indecur)
623 scur=entropy(indecur)+(dent/delte)*deix
625 cd print *,'Processor',MyID,' ecur=',ecur,' indecur=',indecur,
626 cd & ' scur=',scur,' eold=',eold,' sold=',sold
627 cd print *,'deix=',deix,' dent=',dent,' delte=',delte
628 if (print_mc.gt.1) then
629 write(iout,*)'ecur=',ecur,' indecur=',indecur,' scur=',scur
630 write(iout,*)'eold=',eold,' sold=',sold
632 if (scur.le.sold) then
635 C Else carry out acceptance test
636 xx=ran_number(0.0D0,1.0D0)
638 if (xxh.gt.50.0D0) then
645 if (print_mc.gt.0) write (iout,'(a)')
646 & 'Conformation accepted.'
649 if (print_mc.gt.0) write (iout,'(a)')
650 & 'Conformation rejected.'
655 c-----------------------------------------------------------------------------
657 implicit real*8 (a-h,o-z)
659 include 'COMMON.IOUNITS'
664 double precision varia(maxvar)
665 print '(a)','Call READ_POOL'
668 read (intin,'(i5,f10.5)',end=10,err=10) iconf,epool(npool)
669 if (epool(npool).eq.0.0D0) goto 10
670 call read_angles(intin,*10)
671 call geom_to_var(nvar,xpool(1,npool))
675 11 write (iout,'(a,i5)') 'Number of pool conformations:',npool
676 if (print_mc.gt.2) then
678 write (iout,'(a,i5,a,1pe14.5)') 'Pool conformation',i,' energy',
680 write (iout,'(10f8.3)') (rad2deg*xpool(j,i),j=1,nvar)
682 endif ! (print_mc.gt.2)