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