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)
262 if (indpdb.ne.0) then
266 call geom_to_var(nvar,varia)
267 print *,'Calling MINIMIZE.'
273 call minimize(etot,varia,iretcode,nfun)
275 print *,'SUMSL return code is',iretcode,' eval ',nfun
277 evals=nfun/(MPI_WTIME()-time1)
279 evals=nfun/(tcpu()-time1)
281 print *,'# eval/s',evals
282 print *,'refstr=',refstr
283 call hairpin(.true.,nharp,iharp)
284 call secondary2(.true.)
285 call etotal(energy(0))
287 call enerprint(energy(0))
290 call briefout(0,etot)
291 if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
292 write (iout,'(a,i3)') 'SUMSL return code:',iretcode
293 write (iout,'(a,i20)') '# of energy evaluations:',nfun+1
294 write (iout,'(a,f16.3)')'# of energy evaluations/sec:',evals
296 print *,'refstr=',refstr
297 if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
298 call briefout(0,etot)
300 if (outpdb) call pdbout(etot,titel(:32),ipdb)
301 if (outmol2) call mol2out(etot,titel(:32))
304 c---------------------------------------------------------------------------
305 subroutine exec_regularize
306 implicit real*8 (a-h,o-z)
311 include 'COMMON.SETUP'
312 include 'COMMON.TIME1'
313 include 'COMMON.INTERACT'
314 include 'COMMON.NAMES'
316 include 'COMMON.HEADER'
317 include 'COMMON.CONTROL'
318 include 'COMMON.CONTACTS'
319 include 'COMMON.CHAIN'
321 include 'COMMON.IOUNITS'
322 include 'COMMON.FFIELD'
323 include 'COMMON.REMD'
325 include 'COMMON.SBRIDGE'
326 double precision energy(0:n_ene)
331 call regularize(nct-nnt+1,etot,rms,cref(1,nnt,1),iretcode)
332 call etotal(energy(0))
333 energy(0)=energy(0)-energy(14)
335 call enerprint(energy(0))
337 call briefout(0,etot)
338 if (outpdb) call pdbout(etot,titel(:32),ipdb)
339 if (outmol2) call mol2out(etot,titel(:32))
340 if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
341 write (iout,'(a,i3)') 'SUMSL return code:',iretcode
344 c---------------------------------------------------------------------------
345 subroutine exec_thread
350 include "COMMON.SETUP"
354 c---------------------------------------------------------------------------
356 implicit real*8 (a-h,o-z)
358 character*10 nodeinfo
359 double precision varia(maxvar)
363 include "COMMON.SETUP"
364 include 'COMMON.CONTROL'
368 if (modecalc.eq.3) then
374 if (modecalc.eq.3) then
385 c---------------------------------------------------------------------------
386 subroutine exec_mult_eeval_or_minim
387 implicit real*8 (a-h,o-z)
391 dimension muster(mpi_status_size)
393 include 'COMMON.SETUP'
394 include 'COMMON.TIME1'
395 include 'COMMON.INTERACT'
396 include 'COMMON.NAMES'
398 include 'COMMON.HEADER'
399 include 'COMMON.CONTROL'
400 include 'COMMON.CONTACTS'
401 include 'COMMON.CHAIN'
403 include 'COMMON.IOUNITS'
404 include 'COMMON.FFIELD'
405 include 'COMMON.REMD'
407 include 'COMMON.SBRIDGE'
408 double precision varia(maxvar)
410 double precision energy(0:max_ene)
420 open(intin,file=intinname,status='old')
421 write (istat,'(a5,20a12)')"# ",
422 & (wname(print_order(i)),i=1,nprint_ene)
424 write (istat,'(a5,20a12)')"# ",
425 & (ename(print_order(i)),i=1,nprint_ene),
426 & "ETOT total","RMSD","nat.contact","nnt.contact"
428 write (istat,'(a5,20a12)')"# ",
429 & (ename(print_order(i)),i=1,nprint_ene),"ETOT total"
435 read (intin,'(e15.10,e15.5)',end=1100,err=1100) time,ene
436 call read_x(intin,*11)
438 c Broadcast the order to compute internal coordinates to the slaves.
440 & call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
442 call int_from_cart1(.false.)
444 read (intin,'(i5)',end=1100,err=1100) iconf
445 call read_angles(intin,*11)
446 call geom_to_var(nvar,varia)
449 write (iout,'(a,i7)') 'Conformation #',iconf
450 call etotal(energy(0))
451 call briefout(iconf,energy(0))
452 call enerprint(energy(0))
455 call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
456 write (istat,'(i5,20(f12.3))') iconf,
457 & (energy(print_order(i)),i=1,nprint_ene),etot,
458 & rms,frac,frac_nn,co
461 write (istat,'(i5,16(f12.3))') iconf,
462 & (energy(print_order(i)),i=1,nprint_ene),etot
478 if (mm.lt.nodes) then
480 read (intin,'(e15.10,e15.5)',end=11,err=11) time,ene
481 call read_x(intin,*11)
483 c Broadcast the order to compute internal coordinates to the slaves.
485 & call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
487 call int_from_cart1(.false.)
489 read (intin,'(i5)',end=11,err=11) iconf
490 call read_angles(intin,*11)
491 call geom_to_var(nvar,varia)
494 write (iout,'(a,i7)') 'Conformation #',iconf
504 call mpi_send(ind,6,mpi_integer,mm,idint,CG_COMM,
506 call mpi_send(varia,nvar,mpi_double_precision,mm,
507 * idreal,CG_COMM,ierr)
508 call mpi_send(ene0,1,mpi_double_precision,mm,
509 * idreal,CG_COMM,ierr)
510 c print *,'task ',n,' sent to worker ',mm,nvar
512 call mpi_recv(ind,6,mpi_integer,mpi_any_source,idint,
513 * CG_COMM,muster,ierr)
514 man=muster(mpi_source)
515 c print *,'receiving result from worker ',man,' (',iii1,iii,')'
516 call mpi_recv(varia,nvar,mpi_double_precision,
517 * man,idreal,CG_COMM,muster,ierr)
519 * mpi_double_precision,man,idreal,
520 * CG_COMM,muster,ierr)
521 call mpi_recv(ene0,1,
522 * mpi_double_precision,man,idreal,
523 * CG_COMM,muster,ierr)
524 c print *,'result received from worker ',man,' sending now'
526 call var_to_geom(nvar,varia)
528 call etotal(energy(0))
532 write (iout,'(a,2i7)') 'Conformation #',iconf,ind(5)
535 call enerprint(energy(0))
536 call briefout(it,etot)
537 c if (minim) call briefout(it,etot)
539 call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
540 write (istat,'(i5,19(f12.3))') iconf,
541 & (energy(print_order(i)),i=1,nprint_ene),etot,
542 & rms,frac,frac_nn,co
544 write (istat,'(i5,15(f12.3))') iconf,
545 & (energy(print_order(i)),i=1,nprint_ene),etot
550 read (intin,'(e15.10,e15.5)',end=1101,err=1101) time,ene
551 call read_x(intin,*11)
553 c Broadcast the order to compute internal coordinates to the slaves.
555 & call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
557 call int_from_cart1(.false.)
559 read (intin,'(i5)',end=1101,err=1101) iconf
560 call read_angles(intin,*11)
561 call geom_to_var(nvar,varia)
572 call mpi_send(ind,6,mpi_integer,man,idint,CG_COMM,
574 call mpi_send(varia,nvar,mpi_double_precision,man,
575 * idreal,CG_COMM,ierr)
576 call mpi_send(ene0,1,mpi_double_precision,man,
577 * idreal,CG_COMM,ierr)
578 nf_mcmf=nf_mcmf+ind(4)
584 call mpi_recv(ind,6,mpi_integer,mpi_any_source,idint,
585 * CG_COMM,muster,ierr)
586 man=muster(mpi_source)
587 call mpi_recv(varia,nvar,mpi_double_precision,
588 * man,idreal,CG_COMM,muster,ierr)
590 * mpi_double_precision,man,idreal,
591 * CG_COMM,muster,ierr)
592 call mpi_recv(ene0,1,
593 * mpi_double_precision,man,idreal,
594 * CG_COMM,muster,ierr)
596 call var_to_geom(nvar,varia)
598 call etotal(energy(0))
602 write (iout,'(a,2i7)') 'Conformation #',iconf,ind(5)
605 call enerprint(energy(0))
606 call briefout(it,etot)
608 call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
609 write (istat,'(i5,19(f12.3))') iconf,
610 & (energy(print_order(i)),i=1,nprint_ene),etot,
611 & rms,frac,frac_nn,co
613 write (istat,'(i5,15(f12.3))') iconf,
614 & (energy(print_order(i)),i=1,nprint_ene),etot
626 call mpi_send(ind,6,mpi_integer,i,idint,CG_COMM,
631 open(intin,file=intinname,status='old')
632 write (istat,'(a5,20a12)')"# ",
633 & (wname(print_order(i)),i=1,nprint_ene)
634 write (istat,'("# ",20(1pe12.4))')
635 & (weights(print_order(i)),i=1,nprint_ene)
637 write (istat,'(a5,20a12)')"# ",
638 & (ename(print_order(i)),i=1,nprint_ene),
639 & "ETOT total","RMSD","nat.contact","nnt.contact"
641 write (istat,'(a5,14a12)')"# ",
642 & (ename(print_order(i)),i=1,nprint_ene),"ETOT total"
646 read (intin,'(e15.10,e15.5)',end=11,err=11) time,ene
647 call read_x(intin,*11)
649 c Broadcast the order to compute internal coordinates to the slaves.
651 & call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
653 call int_from_cart1(.false.)
655 read (intin,'(i5)',end=11,err=11) iconf
656 call read_angles(intin,*11)
657 call geom_to_var(nvar,varia)
660 write (iout,'(a,i7)') 'Conformation #',iconf
661 if (minim) call minimize(etot,varia,iretcode,nfun)
662 call etotal(energy(0))
665 call enerprint(energy(0))
666 if (minim) call briefout(it,etot)
668 call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
669 write (istat,'(i5,18(f12.3))') iconf,
670 & (energy(print_order(i)),i=1,nprint_ene),
671 & etot,rms,frac,frac_nn,co
674 write (istat,'(i5,14(f12.3))') iconf,
675 & (energy(print_order(i)),i=1,nprint_ene),etot
682 c---------------------------------------------------------------------------
683 subroutine exec_checkgrad
684 implicit real*8 (a-h,o-z)
689 include 'COMMON.SETUP'
690 include 'COMMON.TIME1'
691 include 'COMMON.INTERACT'
692 include 'COMMON.NAMES'
694 include 'COMMON.HEADER'
695 include 'COMMON.CONTROL'
696 include 'COMMON.CONTACTS'
697 include 'COMMON.CHAIN'
699 include 'COMMON.IOUNITS'
700 include 'COMMON.FFIELD'
701 include 'COMMON.REMD'
703 include 'COMMON.SBRIDGE'
705 double precision energy(0:max_ene)
707 c vbld(i)=vbld(i)+ran_number(-0.1d0,0.1d0)
708 c if (itype(i).ne.10)
709 c & vbld(i+nres)=vbld(i+nres)+ran_number(-0.001d0,0.001d0)
711 if (indpdb.eq.0) call chainbuild
714 c dc(j,i)=dc(j,i)+ran_number(-0.2d0,0.2d0)
718 c if (itype(i).ne.10) then
720 c dc(j,i+nres)=dc(j,i+nres)+ran_number(-0.2d0,0.2d0)
725 c dc(j,0)=ran_number(-0.2d0,0.2d0)
735 call etotal(energy(0))
737 call enerprint(energy(0))
738 write (iout,*) "Uconst",Uconst," Uconst_back",uconst_back
739 print *,'icheckgrad=',icheckgrad
740 goto (10,20,30) icheckgrad
741 10 call check_ecartint
742 write(iout,*) "kupadupa"
745 20 call check_cartgrad
750 c---------------------------------------------------------------------------
757 c---------------------------------------------------------------------------
763 include 'COMMON.IOUNITS'
764 C Conformational Space Annealling programmed by Jooyoung Lee.
765 C This method works only with parallel machines!
769 write (iout,*) "CSA works on parallel machines only"
773 c---------------------------------------------------------------------------
774 subroutine exec_softreg
776 include 'COMMON.IOUNITS'
777 include 'COMMON.CONTROL'
778 double precision energy(0:max_ene)
780 call etotal(energy(0))
781 call enerprint(energy(0))
782 if (.not.lsecondary) then
783 write(iout,*) 'Calling secondary structure recognition'
784 call secondary2(debug)
786 write(iout,*) 'Using secondary structure supplied in pdb'
791 call etotal(energy(0))
793 call enerprint(energy(0))
795 call briefout(0,etot)
796 call secondary2(.true.)
797 if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)