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