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