added source code
[unres.git] / source / unres / src_MIN / unres_min.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 c      include 'COMMON.REMD'
29 c      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 c      if (modecalc.eq.-2) then
72 c        call test
73 c        stop
74 c      else if (modecalc.eq.-1) then
75 c        write(iout,*) "call check_sc_map next"
76 c        call check_bond
77 c        stop
78 c      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 c      else if (modecalc.eq.1) then
88 c        call exec_regularize
89 c      else if (modecalc.eq.2) then
90 c        call exec_thread
91 c      else if (modecalc.eq.3 .or. modecalc .eq.6) then
92 c        call exec_MC
93 c      else if (modecalc.eq.4) then
94 c        call exec_mult_eeval_or_minim
95       else if (modecalc.eq.5) then
96          call exec_checkgrad
97 c      else if (ModeCalc.eq.7) then
98 c        call exec_map
99 c      else if (ModeCalc.eq.8) then
100 c        call exec_CSA
101 c      else if (modecalc.eq.11) then
102 c        call exec_softreg
103 c      else if (modecalc.eq.12) then
104 c        call exec_MD
105 c      else if (modecalc.eq.14) then
106 c        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_eeval_or_minim
128       implicit real*8 (a-h,o-z)
129       include 'DIMENSIONS'
130 #ifdef MPI
131       include 'mpif.h'
132 #endif
133       include 'COMMON.SETUP'
134       include 'COMMON.TIME1'
135       include 'COMMON.INTERACT'
136       include 'COMMON.NAMES'
137       include 'COMMON.GEO'
138       include 'COMMON.HEADER'
139       include 'COMMON.CONTROL'
140       include 'COMMON.CONTACTS'
141       include 'COMMON.CHAIN'
142       include 'COMMON.VAR'
143       include 'COMMON.IOUNITS'
144       include 'COMMON.FFIELD'
145 c      include 'COMMON.REMD'
146 c      include 'COMMON.MD'
147       include 'COMMON.SBRIDGE'
148       common /srutu/ icall
149       double precision energy(0:n_ene)
150       double precision energy_long(0:n_ene),energy_short(0:n_ene)
151       if (indpdb.eq.0) call chainbuild
152 c      time00=MPI_Wtime()
153       call chainbuild_cart
154 c      if (split_ene) then
155 c       print *,"Processor",myrank," after chainbuild"
156 c       icall=1
157 c       call etotal_long(energy_long(0))
158 c       write (iout,*) "Printing long range energy"
159 c       call enerprint(energy_long(0))
160 c       call etotal_short(energy_short(0))
161 c       write (iout,*) "Printing short range energy"
162 c       call enerprint(energy_short(0))
163 c       do i=0,n_ene
164 c         energy(i)=energy_long(i)+energy_short(i)
165 c         write (iout,*) i,energy_long(i),energy_short(i),energy(i)
166 c       enddo
167 c       write (iout,*) "Printing long+short range energy"
168 c       call enerprint(energy(0))
169 c      endif
170       call etotal(energy(0))
171 c      time_ene=MPI_Wtime()-time00
172       write (iout,*) "Time for energy evaluation",time_ene
173       print *,"after etotal"
174       etota = energy(0)
175       etot =etota
176       call enerprint(energy(0))
177 c      call hairpin(.true.,nharp,iharp)
178 c      call secondary2(.true.)
179       if (minim) then
180
181         if (dccart) then
182           print *, 'Calling MINIM_DC'
183 c          time1=MPI_WTIME()
184           call minim_dc(etot,iretcode,nfun)
185         else
186           if (indpdb.ne.0) then 
187             call bond_regular
188             call chainbuild
189           endif
190           call geom_to_var(nvar,varia)
191           print *,'Calling MINIMIZE.'
192 c          time1=MPI_WTIME()
193           call minimize(etot,varia,iretcode,nfun)
194         endif
195         print *,'SUMSL return code is',iretcode,' eval ',nfun
196 c        evals=nfun/(MPI_WTIME()-time1)
197         print *,'# eval/s',evals
198         print *,'refstr=',refstr
199 c        call hairpin(.true.,nharp,iharp)
200 c        call secondary2(.true.)
201         call etotal(energy(0))
202         etot = energy(0)
203         call enerprint(energy(0))
204
205         call intout
206         call briefout(0,etot)
207 c        if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
208           write (iout,'(a,i3)') 'SUMSL return code:',iretcode
209           write (iout,'(a,i20)') '# of energy evaluations:',nfun+1
210           write (iout,'(a,f16.3)')'# of energy evaluations/sec:',evals
211 c      else
212 c        print *,'refstr=',refstr
213 c        if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
214 c        call briefout(0,etot)
215       endif
216       if (outpdb) call pdbout(etot,titel(:32),ipdb)
217       if (outmol2) call mol2out(etot,titel(:32))
218       return
219       end
220
221       subroutine exec_checkgrad
222       implicit real*8 (a-h,o-z)
223       include 'DIMENSIONS'
224 #ifdef MPI
225       include 'mpif.h'
226 #endif
227       include 'COMMON.SETUP'
228       include 'COMMON.TIME1'
229       include 'COMMON.INTERACT'
230       include 'COMMON.NAMES'
231       include 'COMMON.GEO'
232       include 'COMMON.HEADER'
233       include 'COMMON.CONTROL'
234       include 'COMMON.CONTACTS'
235       include 'COMMON.CHAIN'
236       include 'COMMON.VAR'
237       include 'COMMON.IOUNITS'
238       include 'COMMON.FFIELD'
239 c      include 'COMMON.REMD'
240       include 'COMMON.MD_'
241       include 'COMMON.SBRIDGE'
242       common /srutu/ icall
243       double precision energy(0:max_ene)
244 c      do i=2,nres
245 c        vbld(i)=vbld(i)+ran_number(-0.1d0,0.1d0)
246 c        if (itype(i).ne.10) 
247 c     &      vbld(i+nres)=vbld(i+nres)+ran_number(-0.001d0,0.001d0)
248 c      enddo
249       if (indpdb.eq.0) call chainbuild
250 c      do i=0,nres
251 c        do j=1,3
252 c          dc(j,i)=dc(j,i)+ran_number(-0.2d0,0.2d0)
253 c        enddo
254 c      enddo
255 c      do i=1,nres-1
256 c        if (itype(i).ne.10) then
257 c          do j=1,3
258 c            dc(j,i+nres)=dc(j,i+nres)+ran_number(-0.2d0,0.2d0)
259 c          enddo
260 c        endif
261 c      enddo
262 c      do j=1,3
263 c        dc(j,0)=ran_number(-0.2d0,0.2d0)
264 c      enddo
265       usampl=.true.
266       totT=1.d0
267       eq_time=0.0d0
268 c      call read_fragments
269       read(inp,*) t_bath
270       call rescale_weights(t_bath)
271       call chainbuild_cart
272       call cartprint
273       call intout
274       icall=1
275       call etotal(energy(0))
276       etot = energy(0)
277       call enerprint(energy(0))
278       write (iout,*) "Uconst",Uconst," Uconst_back",uconst_back
279       print *,'icheckgrad=',icheckgrad
280       goto (10,20,30) icheckgrad
281   10  call check_ecartint
282       return
283   20  call check_cartgrad
284       return
285   30  call check_eint
286       return
287       end