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