4903ec0d7112ba2289cb908bb50588159a372441
[unres.git] / source / unres / src_MD-M / unres.F
1 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
2 C                                                                              C
3 C                                U N R E S                                     C
4 C                                                                              C
5 C Program to carry out conformational search of proteins in an united-residue  C
6 C approximation.                                                               C
7 C                                                                              C
8 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
9       implicit real*8 (a-h,o-z)
10       include 'DIMENSIONS'
11
12
13 #ifdef MPI
14       include 'mpif.h'
15       include 'COMMON.SETUP'
16 #endif
17       include 'COMMON.TIME1'
18       include 'COMMON.INTERACT'
19       include 'COMMON.NAMES'
20       include 'COMMON.GEO'
21       include 'COMMON.HEADER'
22       include 'COMMON.CONTROL'
23       include 'COMMON.CONTACTS'
24       include 'COMMON.CHAIN'
25       include 'COMMON.VAR'
26       include 'COMMON.IOUNITS'
27       include 'COMMON.FFIELD'
28       include 'COMMON.REMD'
29       include 'COMMON.MD'
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)',
41      & 'Energy map',
42      & 'CSA calculations',
43      & 'Not used 9',
44      & 'Not used 10',
45      & 'Soft regularization of PDB structure',
46      & 'Mesoscopic molecular dynamics (MD) ',
47      & 'Not used 13',
48      & 'Replica exchange molecular dynamics (REMD)'/
49       external ilen
50
51 c      call memmon_print_usage()
52
53       call init_task
54       if (me.eq.king)
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
58       call readrtns
59       call flush(iout)
60 C
61       if (me.eq.king .or. .not. out1file) then
62        write (iout,'(2a/)') 
63      & text_mode_calc(modecalc)(:ilen(text_mode_calc(modecalc))),
64      & ' calculation.' 
65        if (minim) write (iout,'(a)') 
66      &  'Conformations will be energy-minimized.'
67        write (iout,'(80(1h*)/)') 
68       endif
69       call flush(iout)
70 C
71       if (modecalc.eq.-2) then
72         call test
73         stop
74       else if (modecalc.eq.-1) then
75         write(iout,*) "call check_sc_map next"
76         call check_bond
77         stop
78       endif
79 #ifdef MPI
80       if (fg_rank.gt.0) then
81 C Fine-grain slaves just do energy and gradient components.
82         call ergastulum ! slave workhouse in Latin
83       else
84 #endif
85       if (modecalc.eq.0) then
86         call exec_eeval_or_minim
87       else if (modecalc.eq.1) then
88         call exec_regularize
89       else if (modecalc.eq.2) then
90         call exec_thread
91       else if (modecalc.eq.3 .or. modecalc .eq.6) then
92         call exec_MC
93       else if (modecalc.eq.4) then
94         call exec_mult_eeval_or_minim
95       else if (modecalc.eq.5) then
96         call exec_checkgrad
97       else if (ModeCalc.eq.7) then
98         call exec_map
99       else if (ModeCalc.eq.8) then
100         call exec_CSA
101       else if (modecalc.eq.11) then
102         call exec_softreg
103       else if (modecalc.eq.12) then
104         call exec_MD
105       else if (modecalc.eq.14) then
106 #ifdef MPI
107         call exec_MREMD
108 #else
109         write (iout,*) "Need a parallel version to run MREMD."
110         stop
111 #endif
112       else
113         write (iout,'(a)') 'This calculation type is not supported',
114      &   ModeCalc
115       endif
116 #ifdef MPI
117       endif
118 C Finish task.
119       if (fg_rank.eq.0) call finish_task
120 c      call memmon_print_usage()
121 #ifdef TIMING
122        call print_detailed_timing
123 #endif
124       call MPI_Finalize(ierr)
125       stop 'Bye Bye...'
126 #else
127       call dajczas(tcpu(),hrtime,mintime,sectime)
128       stop '********** Program terminated normally.'
129 #endif
130       end
131 c--------------------------------------------------------------------------
132       subroutine exec_MD
133       include 'DIMENSIONS'
134 #ifdef MPI
135       include "mpif.h"
136 #endif
137       include 'COMMON.SETUP'
138       include 'COMMON.CONTROL'
139       include 'COMMON.IOUNITS'
140       if (me.eq.king .or. .not. out1file)
141      &   write (iout,*) "Calling chainbuild"
142       call chainbuild
143       call MD
144       return
145       end
146 c---------------------------------------------------------------------------
147 #ifdef MPI
148       subroutine exec_MREMD
149       include 'DIMENSIONS'
150 #ifdef MPI
151       include "mpif.h"
152 #endif
153       include 'COMMON.SETUP'
154       include 'COMMON.CONTROL'
155       include 'COMMON.IOUNITS'
156       include 'COMMON.REMD'
157       if (me.eq.king .or. .not. out1file)
158      &   write (iout,*) "Calling chainbuild"
159       call chainbuild
160       if (me.eq.king .or. .not. out1file)
161      &   write (iout,*) "Calling REMD"
162       if (remd_mlist) then 
163         call MREMD
164       else
165         do i=1,nrep
166           remd_m(i)=1
167         enddo
168         call MREMD
169       endif
170       return
171       end
172 #endif
173 c---------------------------------------------------------------------------
174       subroutine exec_eeval_or_minim
175       implicit real*8 (a-h,o-z)
176       include 'DIMENSIONS'
177 #ifdef MPI
178       include 'mpif.h'
179 #endif
180       include 'COMMON.SETUP'
181       include 'COMMON.TIME1'
182       include 'COMMON.INTERACT'
183       include 'COMMON.NAMES'
184       include 'COMMON.GEO'
185       include 'COMMON.HEADER'
186       include 'COMMON.CONTROL'
187       include 'COMMON.CONTACTS'
188       include 'COMMON.CHAIN'
189       include 'COMMON.VAR'
190       include 'COMMON.IOUNITS'
191       include 'COMMON.FFIELD'
192       include 'COMMON.REMD'
193       include 'COMMON.MD'
194       include 'COMMON.SBRIDGE'
195       common /srutu/ icall
196       double precision energy(0:n_ene)
197       double precision energy_long(0:n_ene),energy_short(0:n_ene)
198       double precision varia(maxvar)
199 <<<<<<< HEAD
200       if (indpdb.eq.0)     call chainbuild
201       time00=MPI_Wtime()
202       print *,'dc',c(1,1)
203       if (indpdb.ne.0) then
204       dc(1,0)=c(1,1)
205       dc(2,0)=c(2,1)
206       dc(3,0)=c(3,1)
207       endif
208 =======
209       if (indpdb.eq.0) call chainbuild
210 #ifdef MPI
211       time00=MPI_Wtime()
212 #else
213       time00=tcpu()
214 #endif
215 >>>>>>> f5379d3246c4bd95e946c4d35d4a1c13e329c4cb
216       call chainbuild_cart
217       print *,'dc',dc(1,0),dc(2,0),dc(3,0)
218       if (split_ene) then
219        print *,"Processor",myrank," after chainbuild"
220        icall=1
221        call etotal_long(energy_long(0))
222        write (iout,*) "Printing long range energy"
223        call enerprint(energy_long(0))
224        call etotal_short(energy_short(0))
225        write (iout,*) "Printing short range energy"
226        call enerprint(energy_short(0))
227        do i=0,n_ene
228          energy(i)=energy_long(i)+energy_short(i)
229          write (iout,*) i,energy_long(i),energy_short(i),energy(i)
230        enddo
231        write (iout,*) "Printing long+short range energy"
232        call enerprint(energy(0))
233       endif
234       call etotal(energy(0))
235 #ifdef MPI
236       time_ene=MPI_Wtime()-time00
237 #else 
238       time_ene=tcpu()-time00
239 #endif
240       write (iout,*) "Time for energy evaluation",time_ene
241       print *,"after etotal"
242       etota = energy(0)
243       etot =etota
244       call enerprint(energy(0))
245       call hairpin(.true.,nharp,iharp)
246         print *,'after hairpin'
247       call secondary2(.true.)
248         print *,'after secondary'
249       if (minim) then
250 crc overlap test
251         if (overlapsc) then 
252           print *, 'Calling OVERLAP_SC'
253           call overlap_sc(fail)
254         endif 
255
256         if (searchsc) then 
257           call sc_move(2,nres-1,10,1d10,nft_sc,etot)
258           print *,'SC_move',nft_sc,etot
259           write(iout,*) 'SC_move',nft_sc,etot
260         endif 
261
262         if (dccart) then
263           print *, 'Calling MINIM_DC'
264 #ifdef MPI
265           time1=MPI_WTIME()
266 #else
267           time1=tcpu()
268 #endif
269           call minim_dc(etot,iretcode,nfun)
270         else
271           if (indpdb.ne.0) then 
272             call bond_regular
273             call chainbuild
274           endif
275           call geom_to_var(nvar,varia)
276           print *,'Calling MINIMIZE.'
277 #ifdef MPI
278           time1=MPI_WTIME()
279 #else
280           time1=tcpu()
281 #endif
282           call minimize(etot,varia,iretcode,nfun)
283         endif
284         print *,'SUMSL return code is',iretcode,' eval ',nfun
285 #ifdef MPI
286         evals=nfun/(MPI_WTIME()-time1)
287 #else
288         evals=nfun/(tcpu()-time1)
289 #endif
290         print *,'# eval/s',evals
291         print *,'refstr=',refstr
292         call hairpin(.false.,nharp,iharp)
293         print *,'after hairpin'
294         call secondary2(.true.)
295         print *,'after secondary'
296         call etotal(energy(0))
297         etot = energy(0)
298         call enerprint(energy(0))
299
300         call intout
301         call briefout(0,etot)
302         if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
303           write (iout,'(a,i3)') 'SUMSL return code:',iretcode
304           write (iout,'(a,i20)') '# of energy evaluations:',nfun+1
305           write (iout,'(a,f16.3)')'# of energy evaluations/sec:',evals
306       else
307         print *,'refstr=',refstr
308         if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
309         call briefout(0,etot)
310       endif
311       if (outpdb) call pdbout(etot,titel(:32),ipdb)
312       if (outmol2) call mol2out(etot,titel(:32))
313       return
314       end
315 c---------------------------------------------------------------------------
316       subroutine exec_regularize
317       implicit real*8 (a-h,o-z)
318       include 'DIMENSIONS'
319 #ifdef MPI
320       include 'mpif.h'
321 #endif
322       include 'COMMON.SETUP'
323       include 'COMMON.TIME1'
324       include 'COMMON.INTERACT'
325       include 'COMMON.NAMES'
326       include 'COMMON.GEO'
327       include 'COMMON.HEADER'
328       include 'COMMON.CONTROL'
329       include 'COMMON.CONTACTS'
330       include 'COMMON.CHAIN'
331       include 'COMMON.VAR'
332       include 'COMMON.IOUNITS'
333       include 'COMMON.FFIELD'
334       include 'COMMON.REMD'
335       include 'COMMON.MD'
336       include 'COMMON.SBRIDGE'
337       double precision energy(0:n_ene)
338
339       call gen_dist_constr
340       call sc_conf
341       call intout
342       call regularize(nct-nnt+1,etot,rms,cref(1,nnt,1),iretcode)
343       call etotal(energy(0))
344       energy(0)=energy(0)-energy(14)
345       etot=energy(0)
346       call enerprint(energy(0))
347       call intout
348       call briefout(0,etot)
349       if (outpdb) call pdbout(etot,titel(:32),ipdb)
350       if (outmol2) call mol2out(etot,titel(:32))
351       if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
352       write (iout,'(a,i3)') 'SUMSL return code:',iretcode
353       return
354       end
355 c---------------------------------------------------------------------------
356       subroutine exec_thread
357       include 'DIMENSIONS'
358 #ifdef MP
359       include "mpif.h"
360 #endif
361       include "COMMON.SETUP"
362       call thread_seq
363       return
364       end
365 c---------------------------------------------------------------------------
366       subroutine exec_MC
367       implicit real*8 (a-h,o-z)
368       include 'DIMENSIONS'
369       character*10 nodeinfo
370       double precision varia(maxvar)
371 #ifdef MPI
372       include "mpif.h"
373 #endif
374       include "COMMON.SETUP"
375       include 'COMMON.CONTROL'
376       call mcm_setup
377       if (minim) then
378 #ifdef MPI
379         if (modecalc.eq.3) then
380           call do_mcm(ipar)
381         else
382           call entmcm
383         endif
384 #else
385         if (modecalc.eq.3) then
386           call do_mcm(ipar)
387         else
388           call entmcm
389         endif
390 #endif
391       else
392         call monte_carlo
393       endif
394       return
395       end
396 c---------------------------------------------------------------------------
397       subroutine exec_mult_eeval_or_minim
398       implicit real*8 (a-h,o-z)
399       include 'DIMENSIONS'
400 #ifdef MPI
401       include 'mpif.h'
402       dimension muster(mpi_status_size)
403 #endif
404       include 'COMMON.SETUP'
405       include 'COMMON.TIME1'
406       include 'COMMON.INTERACT'
407       include 'COMMON.NAMES'
408       include 'COMMON.GEO'
409       include 'COMMON.HEADER'
410       include 'COMMON.CONTROL'
411       include 'COMMON.CONTACTS'
412       include 'COMMON.CHAIN'
413       include 'COMMON.VAR'
414       include 'COMMON.IOUNITS'
415       include 'COMMON.FFIELD'
416       include 'COMMON.REMD'
417       include 'COMMON.MD'
418       include 'COMMON.SBRIDGE'
419       double precision varia(maxvar)
420       dimension ind(6)
421       double precision energy(0:max_ene)
422       logical eof
423       eof=.false.
424 #ifdef MPI
425       if(me.ne.king) then
426         call minim_mcmf
427         return
428       endif
429
430       close (intin)
431       open(intin,file=intinname,status='old')
432       write (istat,'(a5,20a12)')"#    ",
433      &  (wname(print_order(i)),i=1,nprint_ene)
434       if (refstr) then
435         write (istat,'(a5,20a12)')"#    ",
436      &   (ename(print_order(i)),i=1,nprint_ene),
437      &   "ETOT total","RMSD","nat.contact","nnt.contact"        
438       else
439         write (istat,'(a5,20a12)')"#    ",
440      &    (ename(print_order(i)),i=1,nprint_ene),"ETOT total"
441       endif
442
443       if (.not.minim) then
444         do while (.not. eof)
445           if (read_cart) then
446             read (intin,'(e15.10,e15.5)',end=1100,err=1100) time,ene
447             call read_x(intin,*11)
448 #ifdef MPI
449 c Broadcast the order to compute internal coordinates to the slaves.
450             if (nfgtasks.gt.1)
451      &        call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
452 #endif
453             call int_from_cart1(.false.)
454           else
455             read (intin,'(i5)',end=1100,err=1100) iconf
456             call read_angles(intin,*11)
457             call geom_to_var(nvar,varia)
458             call chainbuild
459           endif
460           write (iout,'(a,i7)') 'Conformation #',iconf
461           call etotal(energy(0))
462           call briefout(iconf,energy(0))
463           call enerprint(energy(0))
464           etot=energy(0)
465           if (refstr) then 
466             call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
467             write (istat,'(i5,20(f12.3))') iconf,
468      &      (energy(print_order(i)),i=1,nprint_ene),etot,
469      &       rms,frac,frac_nn,co
470 cjlee end
471           else
472             write (istat,'(i5,16(f12.3))') iconf,
473      &     (energy(print_order(i)),i=1,nprint_ene),etot
474           endif
475         enddo
476 1100    continue
477         goto 1101
478       endif
479
480       mm=0
481       imm=0
482       nft=0
483       ene0=0.0d0
484       n=0
485       iconf=0
486 c      do n=1,nzsc
487       do while (.not. eof)
488         mm=mm+1
489         if (mm.lt.nodes) then
490           if (read_cart) then
491             read (intin,'(e15.10,e15.5)',end=11,err=11) time,ene
492             call read_x(intin,*11)
493 #ifdef MPI
494 c Broadcast the order to compute internal coordinates to the slaves.
495             if (nfgtasks.gt.1) 
496      &        call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
497 #endif
498             call int_from_cart1(.false.)
499           else
500             read (intin,'(i5)',end=11,err=11) iconf
501             call read_angles(intin,*11)
502             call geom_to_var(nvar,varia)
503             call chainbuild
504           endif
505           write (iout,'(a,i7)') 'Conformation #',iconf
506           n=n+1
507          imm=imm+1
508          ind(1)=1
509          ind(2)=n
510          ind(3)=0
511          ind(4)=0
512          ind(5)=0
513          ind(6)=0
514          ene0=0.0d0
515          call mpi_send(ind,6,mpi_integer,mm,idint,CG_COMM,
516      *                  ierr)
517          call mpi_send(varia,nvar,mpi_double_precision,mm,
518      *                  idreal,CG_COMM,ierr)
519          call mpi_send(ene0,1,mpi_double_precision,mm,
520      *                  idreal,CG_COMM,ierr)
521 c         print *,'task ',n,' sent to worker ',mm,nvar
522         else
523          call mpi_recv(ind,6,mpi_integer,mpi_any_source,idint,
524      *                 CG_COMM,muster,ierr)
525          man=muster(mpi_source)
526 c         print *,'receiving result from worker ',man,' (',iii1,iii,')'
527          call mpi_recv(varia,nvar,mpi_double_precision, 
528      *               man,idreal,CG_COMM,muster,ierr)
529          call mpi_recv(ene,1,
530      *               mpi_double_precision,man,idreal,
531      *               CG_COMM,muster,ierr)
532          call mpi_recv(ene0,1,
533      *               mpi_double_precision,man,idreal,
534      *               CG_COMM,muster,ierr)
535 c         print *,'result received from worker ',man,' sending now'
536
537           call var_to_geom(nvar,varia)
538           call chainbuild
539           call etotal(energy(0))
540           iconf=ind(2)
541           write (iout,*)
542           write (iout,*)
543           write (iout,'(a,2i7)') 'Conformation #',iconf,ind(5)
544
545           etot=energy(0)
546           call enerprint(energy(0))
547           call briefout(it,etot)
548 c          if (minim) call briefout(it,etot)
549           if (refstr) then 
550             call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
551             write (istat,'(i5,19(f12.3))') iconf,
552      &     (energy(print_order(i)),i=1,nprint_ene),etot,
553      &     rms,frac,frac_nn,co
554           else
555             write (istat,'(i5,15(f12.3))') iconf,
556      &     (energy(print_order(i)),i=1,nprint_ene),etot
557           endif
558
559           imm=imm-1
560           if (read_cart) then
561             read (intin,'(e15.10,e15.5)',end=1101,err=1101) time,ene
562             call read_x(intin,*11)
563 #ifdef MPI
564 c Broadcast the order to compute internal coordinates to the slaves.
565             if (nfgtasks.gt.1)
566      &        call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
567 #endif
568             call int_from_cart1(.false.)
569           else
570             read (intin,'(i5)',end=1101,err=1101) iconf
571             call read_angles(intin,*11)
572             call geom_to_var(nvar,varia)
573             call chainbuild
574           endif
575           n=n+1
576           imm=imm+1
577           ind(1)=1
578           ind(2)=n
579           ind(3)=0
580           ind(4)=0
581           ind(5)=0
582           ind(6)=0
583           call mpi_send(ind,6,mpi_integer,man,idint,CG_COMM,
584      *                  ierr)
585           call mpi_send(varia,nvar,mpi_double_precision,man, 
586      *                  idreal,CG_COMM,ierr)
587           call mpi_send(ene0,1,mpi_double_precision,man,
588      *                  idreal,CG_COMM,ierr)
589           nf_mcmf=nf_mcmf+ind(4)
590           nmin=nmin+1
591         endif
592       enddo
593 11    continue
594       do j=1,imm
595         call mpi_recv(ind,6,mpi_integer,mpi_any_source,idint,
596      *               CG_COMM,muster,ierr)
597         man=muster(mpi_source)
598         call mpi_recv(varia,nvar,mpi_double_precision, 
599      *               man,idreal,CG_COMM,muster,ierr)
600         call mpi_recv(ene,1,
601      *               mpi_double_precision,man,idreal,
602      *               CG_COMM,muster,ierr)
603         call mpi_recv(ene0,1,
604      *               mpi_double_precision,man,idreal,
605      *               CG_COMM,muster,ierr)
606
607         call var_to_geom(nvar,varia)
608         call chainbuild
609         call etotal(energy(0))
610         iconf=ind(2)
611         write (iout,*)
612         write (iout,*)
613         write (iout,'(a,2i7)') 'Conformation #',iconf,ind(5)
614
615         etot=energy(0)
616         call enerprint(energy(0))
617         call briefout(it,etot)
618         if (refstr) then 
619           call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
620           write (istat,'(i5,19(f12.3))') iconf,
621      &   (energy(print_order(i)),i=1,nprint_ene),etot,
622      &   rms,frac,frac_nn,co
623         else
624           write (istat,'(i5,15(f12.3))') iconf,
625      &    (energy(print_order(i)),i=1,nprint_ene),etot
626         endif
627         nmin=nmin+1
628       enddo
629 1101  continue
630       do i=1, nodes-1
631          ind(1)=0
632          ind(2)=0
633          ind(3)=0
634          ind(4)=0
635          ind(5)=0
636          ind(6)=0
637          call mpi_send(ind,6,mpi_integer,i,idint,CG_COMM,
638      *                  ierr)
639       enddo
640 #else
641       close (intin)
642       open(intin,file=intinname,status='old')
643       write (istat,'(a5,20a12)')"#    ",
644      &   (wname(print_order(i)),i=1,nprint_ene)
645       write (istat,'("#    ",20(1pe12.4))')
646      &   (weights(print_order(i)),i=1,nprint_ene)
647       if (refstr) then
648         write (istat,'(a5,20a12)')"#    ",
649      &   (ename(print_order(i)),i=1,nprint_ene),
650      &   "ETOT total","RMSD","nat.contact","nnt.contact"
651       else
652         write (istat,'(a5,14a12)')"#    ",
653      &   (ename(print_order(i)),i=1,nprint_ene),"ETOT total"
654       endif
655       do while (.not. eof)
656           if (read_cart) then
657             read (intin,'(e15.10,e15.5)',end=11,err=11) time,ene
658             call read_x(intin,*11)
659 #ifdef MPI
660 c Broadcast the order to compute internal coordinates to the slaves.
661             if (nfgtasks.gt.1)
662      &        call MPI_Bcast(6,1,MPI_INTEGER,king,FG_COMM,IERROR)
663 #endif
664             call int_from_cart1(.false.)
665           else
666             read (intin,'(i5)',end=11,err=11) iconf
667             call read_angles(intin,*11)
668             call geom_to_var(nvar,varia)
669             call chainbuild
670           endif
671         write (iout,'(a,i7)') 'Conformation #',iconf
672         if (minim) call minimize(etot,varia,iretcode,nfun)
673         call etotal(energy(0))
674
675         etot=energy(0)
676         call enerprint(energy(0))
677         if (minim) call briefout(it,etot) 
678         if (refstr) then 
679           call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
680           write (istat,'(i5,18(f12.3))') iconf,
681      &   (energy(print_order(i)),i=1,nprint_ene),
682      &   etot,rms,frac,frac_nn,co
683 cjlee end
684         else
685           write (istat,'(i5,14(f12.3))') iconf,
686      &   (energy(print_order(i)),i=1,nprint_ene),etot
687         endif
688       enddo
689    11 continue
690 #endif
691       return
692       end
693 c---------------------------------------------------------------------------
694       subroutine exec_checkgrad
695       implicit real*8 (a-h,o-z)
696       include 'DIMENSIONS'
697 #ifdef MPI
698       include 'mpif.h'
699 #endif
700       include 'COMMON.SETUP'
701       include 'COMMON.TIME1'
702       include 'COMMON.INTERACT'
703       include 'COMMON.NAMES'
704       include 'COMMON.GEO'
705       include 'COMMON.HEADER'
706       include 'COMMON.CONTROL'
707       include 'COMMON.CONTACTS'
708       include 'COMMON.CHAIN'
709       include 'COMMON.VAR'
710       include 'COMMON.IOUNITS'
711       include 'COMMON.FFIELD'
712       include 'COMMON.REMD'
713       include 'COMMON.MD'
714       include 'COMMON.SBRIDGE'
715       common /srutu/ icall
716       double precision energy(0:max_ene)
717 c      do i=2,nres
718 c        vbld(i)=vbld(i)+ran_number(-0.1d0,0.1d0)
719 c        if (itype(i).ne.10) 
720 c     &      vbld(i+nres)=vbld(i+nres)+ran_number(-0.001d0,0.001d0)
721 c      enddo
722       if (indpdb.eq.0) call chainbuild
723 c      do i=0,nres
724 c        do j=1,3
725 c          dc(j,i)=dc(j,i)+ran_number(-0.2d0,0.2d0)
726 c        enddo
727 c      enddo
728 c      do i=1,nres-1
729 c        if (itype(i).ne.10) then
730 c          do j=1,3
731 c            dc(j,i+nres)=dc(j,i+nres)+ran_number(-0.2d0,0.2d0)
732 c          enddo
733 c        endif
734 c      enddo
735 c      do j=1,3
736 c        dc(j,0)=ran_number(-0.2d0,0.2d0)
737 c      enddo
738       usampl=.true.
739       totT=1.d0
740       eq_time=0.0d0
741       call read_fragments
742       call chainbuild_cart
743       call cartprint
744       call intout
745       icall=1
746       call etotal(energy(0))
747       etot = energy(0)
748       call enerprint(energy(0))
749       write (iout,*) "Uconst",Uconst," Uconst_back",uconst_back
750       print *,'icheckgrad=',icheckgrad
751       goto (10,20,30) icheckgrad
752   10  call check_ecartint
753       return
754   20  call check_cartgrad
755       return
756   30  call check_eint
757       return
758       end
759 c---------------------------------------------------------------------------
760       subroutine exec_map
761 C Energy maps
762       call map_read
763       call map
764       return
765       end
766 c---------------------------------------------------------------------------
767       subroutine exec_CSA
768 #ifdef MPI
769       include "mpif.h"
770 #endif
771       include 'DIMENSIONS'
772       include 'COMMON.IOUNITS'
773 C Conformational Space Annealling programmed by Jooyoung Lee.
774 C This method works only with parallel machines!
775 #ifdef MPI
776       call together
777 #else
778       write (iout,*) "CSA works on parallel machines only"
779 #endif
780       return
781       end
782 c---------------------------------------------------------------------------
783       subroutine exec_softreg
784       include 'DIMENSIONS'
785       include 'COMMON.IOUNITS'
786       include 'COMMON.CONTROL'
787       double precision energy(0:max_ene)
788       call chainbuild
789       call etotal(energy(0))
790       call enerprint(energy(0))
791       if (.not.lsecondary) then
792         write(iout,*) 'Calling secondary structure recognition'
793         call secondary2(debug)
794       else
795         write(iout,*) 'Using secondary structure supplied in pdb'
796       endif
797
798       call softreg
799
800       call etotal(energy(0))
801       etot=energy(0)
802       call enerprint(energy(0))
803       call intout
804       call briefout(0,etot)
805       call secondary2(.true.)
806       if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
807       return
808       end