1 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
5 C Program to carry out conformational search of proteins in an united-residue C
8 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
9 implicit real*8 (a-h,o-z)
15 include 'COMMON.SETUP'
17 include 'COMMON.TIME1'
18 include 'COMMON.INTERACT'
19 include 'COMMON.NAMES'
21 include 'COMMON.HEADER'
22 include 'COMMON.CONTROL'
23 include 'COMMON.CONTACTS'
24 include 'COMMON.CHAIN'
26 include 'COMMON.IOUNITS'
27 include 'COMMON.FFIELD'
30 include 'COMMON.SBRIDGE'
31 double precision hrtime,mintime,sectime
32 character*64 text_mode_calc(-2:14) /'test',
33 & 'SC rotamer distribution',
34 & 'Energy evaluation or minimization',
35 & 'Regularization of PDB structure',
36 & 'Threading of a sequence on PDB structures',
37 & 'Monte Carlo (with minimization) ',
38 & 'Energy minimization of multiple conformations',
39 & 'Checking energy gradient',
40 & 'Entropic sampling Monte Carlo (with minimization)',
45 & 'Soft regularization of PDB structure',
46 & 'Mesoscopic molecular dynamics (MD) ',
48 & 'Replica exchange molecular dynamics (REMD)'/
51 c call memmon_print_usage()
55 & write(iout,*)'### LAST MODIFIED 4/25/08 7:29PM by adam'
56 if (me.eq.king) call cinfo
57 C Read force field parameters and job setup data
60 if (me.eq.king .or. .not. out1file) then
62 & text_mode_calc(modecalc)(:ilen(text_mode_calc(modecalc))),
64 if (minim) write (iout,'(a)')
65 & 'Conformations will be energy-minimized.'
66 write (iout,'(80(1h*)/)')
70 if (modecalc.eq.-2) then
73 else if (modecalc.eq.-1) then
74 write(iout,*) "call check_sc_map next"
79 if (fg_rank.gt.0) then
80 C Fine-grain slaves just do energy and gradient components.
81 call ergastulum ! slave workhouse in Latin
84 if (modecalc.eq.0) then
85 call exec_eeval_or_minim
86 else if (modecalc.eq.1) then
88 else if (modecalc.eq.2) then
90 else if (modecalc.eq.3 .or. modecalc .eq.6) then
92 else if (modecalc.eq.4) then
93 call exec_mult_eeval_or_minim
94 else if (modecalc.eq.5) then
96 else if (ModeCalc.eq.7) then
98 else if (ModeCalc.eq.8) then
100 else if (modecalc.eq.11) then
102 else if (modecalc.eq.12) then
104 else if (modecalc.eq.14) then
108 write (iout,*) "Need a parallel version to run MREMD."
112 write (iout,'(a)') 'This calculation type is not supported',
118 if (fg_rank.eq.0) call finish_task
119 c call memmon_print_usage()
121 call print_detailed_timing
123 call MPI_Finalize(ierr)
126 call dajczas(tcpu(),hrtime,mintime,sectime)
127 stop '********** Program terminated normally.'
130 c--------------------------------------------------------------------------
136 include 'COMMON.SETUP'
137 include 'COMMON.CONTROL'
138 include 'COMMON.IOUNITS'
139 c if (me.eq.king .or. .not. out1file) then
140 c write (iout,*) "Calling chainbuild"
144 c if (me.eq.king .or. .not. out1file) then
145 c write (iout,*) "Calling MD"
151 c---------------------------------------------------------------------------
153 subroutine exec_MREMD
158 include 'COMMON.SETUP'
159 include 'COMMON.CONTROL'
160 include 'COMMON.IOUNITS'
161 include 'COMMON.REMD'
162 if (me.eq.king .or. .not. out1file)
163 & write (iout,*) "Calling chainbuild"
165 if (me.eq.king .or. .not. out1file)
166 & write (iout,*) "Calling REMD"
178 c---------------------------------------------------------------------------
179 subroutine exec_eeval_or_minim
180 implicit real*8 (a-h,o-z)
185 include 'COMMON.SETUP'
186 include 'COMMON.TIME1'
187 include 'COMMON.INTERACT'
188 include 'COMMON.NAMES'
190 include 'COMMON.HEADER'
191 include 'COMMON.CONTROL'
192 include 'COMMON.CONTACTS'
193 include 'COMMON.CHAIN'
195 include 'COMMON.IOUNITS'
196 include 'COMMON.FFIELD'
197 include 'COMMON.REMD'
199 include 'COMMON.SBRIDGE'
201 double precision energy(0:n_ene)
202 double precision energy_long(0:n_ene),energy_short(0:n_ene)
203 double precision varia(maxvar)
204 if (indpdb.eq.0) call chainbuild
212 print *,"Processor",myrank," after chainbuild"
214 call etotal_long(energy_long(0))
215 write (iout,*) "Printing long range energy"
216 call enerprint(energy_long(0))
217 call etotal_short(energy_short(0))
218 write (iout,*) "Printing short range energy"
219 call enerprint(energy_short(0))
221 energy(i)=energy_long(i)+energy_short(i)
222 write (iout,*) i,energy_long(i),energy_short(i),energy(i)
224 write (iout,*) "Printing long+short range energy"
225 call enerprint(energy(0))
227 call etotal(energy(0))
229 time_ene=MPI_Wtime()-time00
231 time_ene=tcpu()-time00
233 write (iout,*) "Time for energy evaluation",time_ene
234 print *,"after etotal"
237 call enerprint(energy(0))
238 call hairpin(.true.,nharp,iharp)
239 call secondary2(.true.)
243 print *, 'Calling OVERLAP_SC'
244 call overlap_sc(fail)
248 call sc_move(2,nres-1,10,1d10,nft_sc,etot)
249 print *,'SC_move',nft_sc,etot
250 write(iout,*) 'SC_move',nft_sc,etot
254 print *, 'Calling MINIM_DC'
260 call minim_dc(etot,iretcode,nfun)
261 if(iretcode.eq.8) call check_ecartint
263 if (indpdb.ne.0) then
267 call geom_to_var(nvar,varia)
268 print *,'Calling MINIMIZE.'
274 call minimize(etot,varia,iretcode,nfun)
276 print *,'SUMSL return code is',iretcode,' eval ',nfun
278 evals=nfun/(MPI_WTIME()-time1)
280 evals=nfun/(tcpu()-time1)
282 print *,'# eval/s',evals
283 print *,'refstr=',refstr
284 call hairpin(.true.,nharp,iharp)
285 call secondary2(.true.)
286 call etotal(energy(0))
288 call enerprint(energy(0))
291 call briefout(0,etot)
292 if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
293 write (iout,'(a,i3)') 'SUMSL return code:',iretcode
294 write (iout,'(a,i20)') '# of energy evaluations:',nfun+1
295 write (iout,'(a,f16.3)')'# of energy evaluations/sec:',evals
297 print *,'refstr=',refstr
298 if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
299 call briefout(0,etot)
301 if (outpdb) call pdbout(etot,titel(:32),ipdb)
302 if (outmol2) call mol2out(etot,titel(:32))
305 c---------------------------------------------------------------------------
306 subroutine exec_regularize
307 implicit real*8 (a-h,o-z)
312 include 'COMMON.SETUP'
313 include 'COMMON.TIME1'
314 include 'COMMON.INTERACT'
315 include 'COMMON.NAMES'
317 include 'COMMON.HEADER'
318 include 'COMMON.CONTROL'
319 include 'COMMON.CONTACTS'
320 include 'COMMON.CHAIN'
322 include 'COMMON.IOUNITS'
323 include 'COMMON.FFIELD'
324 include 'COMMON.REMD'
326 include 'COMMON.SBRIDGE'
327 double precision energy(0:n_ene)
332 call regularize(nct-nnt+1,etot,rms,cref(1,nnt,1),iretcode)
333 call etotal(energy(0))
334 energy(0)=energy(0)-energy(14)
336 call enerprint(energy(0))
338 call briefout(0,etot)
339 if (outpdb) call pdbout(etot,titel(:32),ipdb)
340 if (outmol2) call mol2out(etot,titel(:32))
341 if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
342 write (iout,'(a,i3)') 'SUMSL return code:',iretcode
345 c---------------------------------------------------------------------------
346 subroutine exec_thread
351 include "COMMON.SETUP"
355 c---------------------------------------------------------------------------
357 implicit real*8 (a-h,o-z)
359 character*10 nodeinfo
360 double precision varia(maxvar)
364 include "COMMON.SETUP"
365 include 'COMMON.CONTROL'
369 if (modecalc.eq.3) then
375 if (modecalc.eq.3) then
386 c---------------------------------------------------------------------------
387 subroutine exec_mult_eeval_or_minim
388 implicit real*8 (a-h,o-z)
392 dimension muster(mpi_status_size)
394 include 'COMMON.SETUP'
395 include 'COMMON.TIME1'
396 include 'COMMON.INTERACT'
397 include 'COMMON.NAMES'
399 include 'COMMON.HEADER'
400 include 'COMMON.CONTROL'
401 include 'COMMON.CONTACTS'
402 include 'COMMON.CHAIN'
404 include 'COMMON.IOUNITS'
405 include 'COMMON.FFIELD'
406 include 'COMMON.REMD'
408 include 'COMMON.SBRIDGE'
409 double precision varia(maxvar)
411 double precision energy(0:max_ene)
421 open(intin,file=intinname,status='old')
422 write (istat,'(a5,20a12)')"# ",
423 & (wname(print_order(i)),i=1,nprint_ene)
425 write (istat,'(a5,20a12)')"# ",
426 & (ename(print_order(i)),i=1,nprint_ene),
427 & "ETOT total","RMSD","nat.contact","nnt.contact"
429 write (istat,'(a5,20a12)')"# ",
430 & (ename(print_order(i)),i=1,nprint_ene),"ETOT total"
436 read (intin,'(e15.10,e15.5)',end=1100,err=1100) time,ene
437 call read_x(intin,*11)
439 c Broadcast the order to compute internal coordinates to the slaves.
441 & call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
443 call int_from_cart1(.false.)
445 read (intin,'(i5)',end=1100,err=1100) iconf
446 call read_angles(intin,*11)
447 call geom_to_var(nvar,varia)
450 write (iout,'(a,i7)') 'Conformation #',iconf
451 call etotal(energy(0))
452 call briefout(iconf,energy(0))
453 call enerprint(energy(0))
456 call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
457 write (istat,'(i5,20(f12.3))') iconf,
458 & (energy(print_order(i)),i=1,nprint_ene),etot,
459 & rms,frac,frac_nn,co
462 write (istat,'(i5,16(f12.3))') iconf,
463 & (energy(print_order(i)),i=1,nprint_ene),etot
479 if (mm.lt.nodes) then
481 read (intin,'(e15.10,e15.5)',end=11,err=11) time,ene
482 call read_x(intin,*11)
484 c Broadcast the order to compute internal coordinates to the slaves.
486 & call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
488 call int_from_cart1(.false.)
490 read (intin,'(i5)',end=11,err=11) iconf
491 call read_angles(intin,*11)
492 call geom_to_var(nvar,varia)
495 write (iout,'(a,i7)') 'Conformation #',iconf
505 call mpi_send(ind,6,mpi_integer,mm,idint,CG_COMM,
507 call mpi_send(varia,nvar,mpi_double_precision,mm,
508 * idreal,CG_COMM,ierr)
509 call mpi_send(ene0,1,mpi_double_precision,mm,
510 * idreal,CG_COMM,ierr)
511 c print *,'task ',n,' sent to worker ',mm,nvar
513 call mpi_recv(ind,6,mpi_integer,mpi_any_source,idint,
514 * CG_COMM,muster,ierr)
515 man=muster(mpi_source)
516 c print *,'receiving result from worker ',man,' (',iii1,iii,')'
517 call mpi_recv(varia,nvar,mpi_double_precision,
518 * man,idreal,CG_COMM,muster,ierr)
520 * mpi_double_precision,man,idreal,
521 * CG_COMM,muster,ierr)
522 call mpi_recv(ene0,1,
523 * mpi_double_precision,man,idreal,
524 * CG_COMM,muster,ierr)
525 c print *,'result received from worker ',man,' sending now'
527 call var_to_geom(nvar,varia)
529 call etotal(energy(0))
533 write (iout,'(a,2i7)') 'Conformation #',iconf,ind(5)
536 call enerprint(energy(0))
537 call briefout(it,etot)
538 c if (minim) call briefout(it,etot)
540 call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
541 write (istat,'(i5,19(f12.3))') iconf,
542 & (energy(print_order(i)),i=1,nprint_ene),etot,
543 & rms,frac,frac_nn,co
545 write (istat,'(i5,15(f12.3))') iconf,
546 & (energy(print_order(i)),i=1,nprint_ene),etot
551 read (intin,'(e15.10,e15.5)',end=1101,err=1101) time,ene
552 call read_x(intin,*11)
554 c Broadcast the order to compute internal coordinates to the slaves.
556 & call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
558 call int_from_cart1(.false.)
560 read (intin,'(i5)',end=1101,err=1101) iconf
561 call read_angles(intin,*11)
562 call geom_to_var(nvar,varia)
573 call mpi_send(ind,6,mpi_integer,man,idint,CG_COMM,
575 call mpi_send(varia,nvar,mpi_double_precision,man,
576 * idreal,CG_COMM,ierr)
577 call mpi_send(ene0,1,mpi_double_precision,man,
578 * idreal,CG_COMM,ierr)
579 nf_mcmf=nf_mcmf+ind(4)
585 call mpi_recv(ind,6,mpi_integer,mpi_any_source,idint,
586 * CG_COMM,muster,ierr)
587 man=muster(mpi_source)
588 call mpi_recv(varia,nvar,mpi_double_precision,
589 * man,idreal,CG_COMM,muster,ierr)
591 * mpi_double_precision,man,idreal,
592 * CG_COMM,muster,ierr)
593 call mpi_recv(ene0,1,
594 * mpi_double_precision,man,idreal,
595 * CG_COMM,muster,ierr)
597 call var_to_geom(nvar,varia)
599 call etotal(energy(0))
603 write (iout,'(a,2i7)') 'Conformation #',iconf,ind(5)
606 call enerprint(energy(0))
607 call briefout(it,etot)
609 call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
610 write (istat,'(i5,19(f12.3))') iconf,
611 & (energy(print_order(i)),i=1,nprint_ene),etot,
612 & rms,frac,frac_nn,co
614 write (istat,'(i5,15(f12.3))') iconf,
615 & (energy(print_order(i)),i=1,nprint_ene),etot
627 call mpi_send(ind,6,mpi_integer,i,idint,CG_COMM,
632 open(intin,file=intinname,status='old')
633 write (istat,'(a5,20a12)')"# ",
634 & (wname(print_order(i)),i=1,nprint_ene)
635 write (istat,'("# ",20(1pe12.4))')
636 & (weights(print_order(i)),i=1,nprint_ene)
638 write (istat,'(a5,20a12)')"# ",
639 & (ename(print_order(i)),i=1,nprint_ene),
640 & "ETOT total","RMSD","nat.contact","nnt.contact"
642 write (istat,'(a5,14a12)')"# ",
643 & (ename(print_order(i)),i=1,nprint_ene),"ETOT total"
647 read (intin,'(e15.10,e15.5)',end=11,err=11) time,ene
648 call read_x(intin,*11)
650 c Broadcast the order to compute internal coordinates to the slaves.
652 & call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
654 call int_from_cart1(.false.)
656 read (intin,'(i5)',end=11,err=11) iconf
657 call read_angles(intin,*11)
658 call geom_to_var(nvar,varia)
661 write (iout,'(a,i7)') 'Conformation #',iconf
662 if (minim) call minimize(etot,varia,iretcode,nfun)
663 call etotal(energy(0))
666 call enerprint(energy(0))
667 if (minim) call briefout(it,etot)
669 call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
670 write (istat,'(i5,18(f12.3))') iconf,
671 & (energy(print_order(i)),i=1,nprint_ene),
672 & etot,rms,frac,frac_nn,co
675 write (istat,'(i5,14(f12.3))') iconf,
676 & (energy(print_order(i)),i=1,nprint_ene),etot
683 c---------------------------------------------------------------------------
684 subroutine exec_checkgrad
685 implicit real*8 (a-h,o-z)
690 include 'COMMON.SETUP'
691 include 'COMMON.TIME1'
692 include 'COMMON.INTERACT'
693 include 'COMMON.NAMES'
695 include 'COMMON.HEADER'
696 include 'COMMON.CONTROL'
697 include 'COMMON.CONTACTS'
698 include 'COMMON.CHAIN'
700 include 'COMMON.IOUNITS'
701 include 'COMMON.FFIELD'
702 include 'COMMON.REMD'
704 include 'COMMON.SBRIDGE'
706 double precision energy(0:max_ene)
708 c vbld(i)=vbld(i)+ran_number(-0.1d0,0.1d0)
709 c if (itype(i).ne.10)
710 c & vbld(i+nres)=vbld(i+nres)+ran_number(-0.001d0,0.001d0)
712 if (indpdb.eq.0) call chainbuild
715 c dc(j,i)=dc(j,i)+ran_number(-0.2d0,0.2d0)
719 c if (itype(i).ne.10) then
721 c dc(j,i+nres)=dc(j,i+nres)+ran_number(-0.2d0,0.2d0)
726 c dc(j,0)=ran_number(-0.2d0,0.2d0)
736 call etotal(energy(0))
738 call enerprint(energy(0))
739 write (iout,*) "Uconst",Uconst," Uconst_back",uconst_back
740 print *,'icheckgrad=',icheckgrad
741 goto (10,20,30) icheckgrad
742 10 call check_ecartint
743 write(iout,*) "kupadupa"
746 20 call check_cartgrad
751 c---------------------------------------------------------------------------
758 c---------------------------------------------------------------------------
764 include 'COMMON.IOUNITS'
765 C Conformational Space Annealling programmed by Jooyoung Lee.
766 C This method works only with parallel machines!
770 write (iout,*) "CSA works on parallel machines only"
774 c---------------------------------------------------------------------------
775 subroutine exec_softreg
777 include 'COMMON.IOUNITS'
778 include 'COMMON.CONTROL'
779 double precision energy(0:max_ene)
781 call etotal(energy(0))
782 call enerprint(energy(0))
783 if (.not.lsecondary) then
784 write(iout,*) 'Calling secondary structure recognition'
785 call secondary2(debug)
787 write(iout,*) 'Using secondary structure supplied in pdb'
792 call etotal(energy(0))
794 call enerprint(energy(0))
796 call briefout(0,etot)
797 call secondary2(.true.)
798 if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)