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