Merge branch 'prerelease-3.2.1' of mmka.chem.univ.gda.pl:unres into prerelease-3.2.1
[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 #ifdef MPI
71       if (fg_rank.gt.0) then
72 C Fine-grain slaves just do energy and gradient components.
73         call ergastulum ! slave workhouse in Latin
74       else
75 #endif
76       if (modecalc.eq.0) then
77         call exec_eeval_or_minim
78       else if (modecalc.eq.5) then
79          call exec_checkgrad
80       else
81         write (iout,'(a,i5)') 
82      &   'This calculation type is not supported',
83      &   ModeCalc
84       endif
85 #ifdef MPI
86       endif
87 C Finish task.
88       if (fg_rank.eq.0) call finish_task
89 c      call memmon_print_usage()
90 #ifdef TIMING
91        call print_detailed_timing
92 #endif
93       call MPI_Finalize(ierr)
94       stop 'Bye Bye...'
95 #else
96       call dajczas(tcpu(),hrtime,mintime,sectime)
97       stop '********** Program terminated normally.'
98 #endif
99       end
100 c---------------------------------------------------------------------------
101       subroutine exec_eeval_or_minim
102       implicit real*8 (a-h,o-z)
103       include 'DIMENSIONS'
104 #ifdef MPI
105       include 'mpif.h'
106 #endif
107       include 'COMMON.SETUP'
108       include 'COMMON.TIME1'
109       include 'COMMON.INTERACT'
110       include 'COMMON.NAMES'
111       include 'COMMON.GEO'
112       include 'COMMON.HEADER'
113       include 'COMMON.CONTROL'
114       include 'COMMON.CONTACTS'
115       include 'COMMON.CHAIN'
116       include 'COMMON.VAR'
117       include 'COMMON.IOUNITS'
118       include 'COMMON.FFIELD'
119       include 'COMMON.SBRIDGE'
120       common /srutu/ icall
121       double precision energy(0:n_ene),varia(maxvar)
122       double precision energy_long(0:n_ene),energy_short(0:n_ene)
123       if (indpdb.eq.0) call chainbuild
124 #ifdef MPI
125       time00=MPI_Wtime()
126 #else
127       time00=tcpu()
128 #endif
129       call chainbuild_cart
130       call etotal(energy(0))
131 #ifdef MPI
132       time_ene=MPI_Wtime()-time00
133 #else
134       time_ene=tcpu()
135 #endif
136       write (iout,*) "Time for energy evaluation",time_ene
137       print *,"after etotal"
138       etota = energy(0)
139       etot =etota
140       call enerprint(energy(0))
141 c      call hairpin(.true.,nharp,iharp)
142 c      call secondary2(.true.)
143       if (minim) then
144
145 crc overlap test
146         if (overlapsc) then
147           print *, 'Calling OVERLAP_SC'
148           call overlap_sc(fail)
149         endif
150
151         if (searchsc) then
152           call sc_move(2,nres-1,10,1d10,nft_sc,etot)
153           print *,'SC_move',nft_sc,etot
154           write(iout,*) 'SC_move',nft_sc,etot
155         endif
156
157         if (dccart) then
158           print *, 'Calling MINIM_DC'
159 #ifdef MPI
160           time1=MPI_WTIME()
161 #else
162           time1=tcpu()
163 #endif
164           call minim_dc(etot,iretcode,nfun)
165         else
166           if (indpdb.ne.0) then 
167             call bond_regular
168             call chainbuild
169           endif
170           call geom_to_var(nvar,varia)
171           print *,'Calling MINIMIZE.'
172 #ifdef MPI
173           time1=MPI_WTIME()
174 #else
175           time1=tcpu()
176 #endif
177           call minimize(etot,varia,iretcode,nfun)
178         endif
179         print *,'SUMSL return code is',iretcode,' eval ',nfun
180 #ifdef MPI
181         evals=nfun/(MPI_WTIME()-time1)
182 #else
183         evals=nfun/(tcpu()-time1)
184 #endif
185         print *,'# eval/s',evals
186         print *,'refstr=',refstr
187 c        call hairpin(.true.,nharp,iharp)
188 c        call secondary2(.true.)
189         call etotal(energy(0))
190         etot = energy(0)
191         call enerprint(energy(0))
192
193         call intout
194         call briefout(0,etot)
195 c        if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
196           write (iout,'(a,i3)') 'SUMSL return code:',iretcode
197           write (iout,'(a,i20)') '# of energy evaluations:',nfun+1
198           write (iout,'(a,f16.3)')'# of energy evaluations/sec:',evals
199 c      else
200 c        print *,'refstr=',refstr
201 c        if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
202 c        call briefout(0,etot)
203       endif
204       if (outpdb) call pdbout(etot,titel(:32),ipdb)
205       if (outmol2) call mol2out(etot,titel(:32))
206       return
207       end
208
209       subroutine exec_checkgrad
210       implicit real*8 (a-h,o-z)
211       include 'DIMENSIONS'
212 #ifdef MPI
213       include 'mpif.h'
214 #endif
215       include 'COMMON.SETUP'
216       include 'COMMON.TIME1'
217       include 'COMMON.INTERACT'
218       include 'COMMON.NAMES'
219       include 'COMMON.GEO'
220       include 'COMMON.HEADER'
221       include 'COMMON.CONTROL'
222       include 'COMMON.CONTACTS'
223       include 'COMMON.CHAIN'
224       include 'COMMON.VAR'
225       include 'COMMON.IOUNITS'
226       include 'COMMON.FFIELD'
227 c      include 'COMMON.REMD'
228       include 'COMMON.MD_'
229       include 'COMMON.SBRIDGE'
230       common /srutu/ icall
231       double precision energy(0:max_ene)
232 c      do i=2,nres
233 c        vbld(i)=vbld(i)+ran_number(-0.1d0,0.1d0)
234 c        if (itype(i).ne.10) 
235 c     &      vbld(i+nres)=vbld(i+nres)+ran_number(-0.001d0,0.001d0)
236 c      enddo
237       if (indpdb.eq.0) call chainbuild
238 c      do i=0,nres
239 c        do j=1,3
240 c          dc(j,i)=dc(j,i)+ran_number(-0.2d0,0.2d0)
241 c        enddo
242 c      enddo
243 c      do i=1,nres-1
244 c        if (itype(i).ne.10) then
245 c          do j=1,3
246 c            dc(j,i+nres)=dc(j,i+nres)+ran_number(-0.2d0,0.2d0)
247 c          enddo
248 c        endif
249 c      enddo
250 c      do j=1,3
251 c        dc(j,0)=ran_number(-0.2d0,0.2d0)
252 c      enddo
253       usampl=.true.
254       totT=1.d0
255       eq_time=0.0d0
256 c      call read_fragments
257       call chainbuild_cart
258       call cartprint
259       call intout
260       icall=1
261       call etotal(energy(0))
262       etot = energy(0)
263       call enerprint(energy(0))
264       write (iout,*) "Uconst",Uconst," Uconst_back",uconst_back
265       print *,'icheckgrad=',icheckgrad
266       goto (10,20,30) icheckgrad
267   10  call check_ecartint
268       return
269   20  call check_cartgrad
270       return
271   30  call check_eint
272       return
273       end