update new files
[unres.git] / source / maxlik / src_MD_T_maxlik-NEWCORR-PMF / initialize_p.F
1       subroutine initialize
2
3 C Define constants and zero out tables.
4 C
5       implicit real*8 (a-h,o-z)
6       include 'DIMENSIONS'
7       include 'DIMENSIONS.ZSCOPT'
8 #ifdef MPI
9       include 'mpif.h'
10 #endif
11       include 'COMMON.IOUNITS'
12       include 'COMMON.CHAIN'
13       include 'COMMON.INTERACT'
14       include 'COMMON.GEO'
15       include 'COMMON.LOCAL'
16       include 'COMMON.TORSION'
17       include 'COMMON.FFIELD'
18       include 'COMMON.SBRIDGE'
19       include 'COMMON.MINIM' 
20       include 'COMMON.DERIV'
21       include "COMMON.WEIGHTS"
22       include "COMMON.NAMES"
23       include "COMMON.TIME1"
24       include "COMMON.THERMAL"
25       include "COMMON.TORCNSTR"
26       include "COMMON.ENERGIES"
27 C
28 C The following is just to define auxiliary variables used in angle conversion
29 C
30       pi=4.0D0*datan(1.0D0)
31       dwapi=2.0D0*pi
32       dwapi3=dwapi/3.0D0
33       pipol=0.5D0*pi
34       deg2rad=pi/180.0D0
35       rad2deg=1.0D0/deg2rad
36       angmin=10.0D0*deg2rad
37       Rgas = 1.987D-3
38       eps_out = 80.0d0
39 C
40 C Define I/O units.
41 C
42       inp=    1
43       iout=   2
44       ipdbin= 3
45       ipdb=   7
46       imol2=  4
47       igeom=  8
48       intin=  9
49       ithep= 11
50       irotam=12
51       itorp= 13
52       itordp= 23
53       ielep= 14
54       isidep=15 
55       isidep1=22
56       iscpp=25
57       icbase=16
58       ifourier=20
59       istat= 17
60       ientin=18
61       ientout=19
62       ibond=28
63       isccor=29
64 C
65 C CSA I/O units (separated from others especially for Jooyoung)
66 C
67       icsa_rbank=30
68       icsa_seed=31
69       icsa_history=32
70       icsa_bank=33
71       icsa_bank1=34
72       icsa_alpha=35
73       icsa_alpha1=36
74       icsa_bankt=37
75       icsa_int=39
76       icsa_bank_reminimized=38
77       icsa_native_int=41
78       icsa_in=40
79 C
80 C Set default weights of the energy terms.
81 C
82       wlong=1.0D0
83       welec=1.0D0
84       wtor =1.0D0
85       wang =1.0D0
86       wscloc=1.0D0
87       wstrain=1.0D0
88 C
89 C Zero out tables.
90 C
91       ndih_constr=0
92       do i=1,maxres2
93         do j=1,3
94           c(j,i)=0.0D0
95           dc(j,i)=0.0D0
96         enddo
97       enddo
98       do i=1,maxres
99         do j=1,3
100           xloc(j,i)=0.0D0
101         enddo
102       enddo
103       do i=1,ntyp
104         do j=1,ntyp
105           aa(i,j)=0.0D0
106           bb(i,j)=0.0D0
107           augm(i,j)=0.0D0
108           sigma(i,j)=0.0D0
109           r0(i,j)=0.0D0
110           chi(i,j)=0.0D0
111         enddo
112         do j=1,2
113           bad(i,j)=0.0D0
114         enddo
115         chip(i)=0.0D0
116         alp(i)=0.0D0
117         sigma0(i)=0.0D0
118         sigii(i)=0.0D0
119         rr0(i)=0.0D0
120         a0thet(i)=0.0D0
121         do j=1,2
122          do ichir1=-1,1
123           do ichir2=-1,1
124           athet(j,i,ichir1,ichir2)=0.0D0
125           bthet(j,i,ichir1,ichir2)=0.0D0
126           enddo
127          enddo
128         enddo
129         do j=0,3
130           polthet(j,i)=0.0D0
131         enddo
132         do j=1,3
133           gthet(j,i)=0.0D0
134         enddo
135         theta0(i)=0.0D0
136         sig0(i)=0.0D0
137         sigc0(i)=0.0D0
138         do j=1,maxlob
139           bsc(j,i)=0.0D0
140           do k=1,3
141             censc(k,j,i)=0.0D0
142           enddo
143           do k=1,3
144             do l=1,3
145               gaussc(l,k,j,i)=0.0D0
146             enddo
147           enddo
148           nlob(i)=0
149         enddo
150       enddo
151       nlob(ntyp1)=0
152       dsc(ntyp1)=0.0D0
153       do iblock=1,2
154       do i=1,maxtor
155         itortyp(i)=0
156         do j=1,maxtor
157           do k=1,maxterm
158             v1(k,j,i,iblock)=0.0D0
159             v2(k,j,i,iblock)=0.0D0
160           enddo
161         enddo
162       enddo
163       enddo
164       do i=1,maxres
165         itype(i)=0
166         itel(i)=0
167       enddo
168 C Initialize the bridge arrays
169       ns=0
170       nss=0 
171       nhpb=0
172       do i=1,maxss
173         iss(i)=0
174       enddo
175       do i=1,maxdim
176         dhpb(i)=0.0D0
177       enddo
178       do i=1,maxres
179         ihpb(i)=0
180         jhpb(i)=0
181       enddo
182 C
183 C Initialize timing.
184 C
185       call set_timers
186 C
187 C Initialize variables used in minimization.
188 C   
189 c     maxfun=5000
190 c     maxit=2000
191       maxfun=500
192       maxit=200
193       tolf=1.0D-2
194       rtolf=5.0D-4
195
196 C Initialize the variables responsible for the mode of gradient storage.
197 C
198       nfl=0
199       icg=1
200       do i=1,14
201         do j=1,14
202           if (print_order(i).eq.j) then
203             iw(print_order(i))=j
204             goto 1121
205           endif
206         enddo
207 1121    continue
208       enddo
209       calc_grad=.false.
210 C Set timers and counters for the respective routines
211       t_func = 0.0d0
212       t_grad = 0.0d0
213       t_fhel = 0.0d0
214       t_fbet = 0.0d0
215       t_ghel = 0.0d0
216       t_gbet = 0.0d0
217       t_viol = 0.0d0
218       t_gviol = 0.0d0
219       n_func = 0
220       n_grad = 0
221       n_fhel = 0
222       n_fbet = 0
223       n_ghel = 0
224       n_gbet = 0
225       n_viol = 0
226       n_gviol = 0
227       n_map = 0
228 #ifndef SPLITELE
229       nprint_ene=nprint_ene-1
230 #endif
231       enetb=0.0d0
232       return
233       end
234 c-------------------------------------------------------------------------
235       block data nazwy
236       implicit real*8 (a-h,o-z)
237       include 'DIMENSIONS'
238       include 'DIMENSIONS.ZSCOPT'
239       include 'COMMON.NAMES'
240       include 'COMMON.WEIGHTS'
241       include 'COMMON.FFIELD'
242       data restyp /
243      &'DD','DAU','DAI','DDB','DSM','DPR','DLY','DAR','DHI','DAS','DGL',
244      & 'DSG','DGN','DSN','DTH',
245      &'DYY','DAL','DTY','DTR','DVA','DLE','DIL','DPN','MED','DCY','ZER',
246      &'CYS','MET','PHE','ILE','LEU','VAL','TRP','TYR','ALA','GLY','THR',
247      &'SER','GLN','ASN','GLU','ASP','HIS','ARG','LYS','PRO','SME','DBZ',
248      &'AIB','ABU','D'/
249       data onelet /
250      &'z','z','z','z','z','p','k','r','h','d','e','n','q','s','t','g',
251      &'a','y','w','v','l','i','f','m','c','x',
252      &'C','M','F','I','L','V','W','Y','A','G','T',
253      &'S','Q','N','E','D','H','R','K','P','z','z','z','z','X'/
254       data potname /'LJ','LJK','BP','GB','GBV','MM'/
255       data ename /
256      &   "EVDW SC-SC","EVDW2 SC-p","EES p-p","ECORR4 ","ECORR5 ",
257      &   "ECORR6 ","EELLO ","ETURN3 ","ETURN4 ","ETURN6 ",
258      &   "EBE bend","ESC SCloc","ETORS ","ETORSD ","EHPB","EVDWPP",
259      &   "ESTR","EVDW2_14","ESCCOR","EDIHC","EVDW_T","ELIPTRAN",
260      &   "EAFM","ETHETC","EMPTY"/
261       data wname /
262      &   "WSC","WSCP","WELEC","WCORR","WCORR5","WCORR6","WEL_LOC",
263      &   "WTURN3","WTURN4","WTURN6","WANG","WSCLOC","WTOR","WTORD",
264      &   "WHPB","WVDWPP","WBOND","WSCP14","WSCCOR","WDIHC","WSC_T",
265      &   "WLIPTRAN","WAFM","WTHETC","WSHIELD"/
266       data ww0 /1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,
267      &    1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,0.0d0,1.0d0,
268      &    0.0d0,0.0,0.0d0,0.0d0,0.0d0,0.0d0/
269       data nprint_ene /25/
270       data print_order /1,2,3,17,11,12,13,14,4,5,6,7,8,9,10,19,16,15,18,
271      &  20,21,22,23,24,25/
272       end 
273 c---------------------------------------------------------------------------
274       subroutine init_int_table
275       implicit real*8 (a-h,o-z)
276       include 'DIMENSIONS'
277       include 'DIMENSIONS.ZSCOPT'
278 #ifdef MPI
279       include 'mpif.h'
280 #endif
281 #ifdef MP
282       include 'COMMON.INFO'
283 #endif
284       include 'COMMON.CHAIN'
285       include 'COMMON.INTERACT'
286       include 'COMMON.LOCAL'
287       include 'COMMON.SBRIDGE'
288       include 'COMMON.IOUNITS'
289       logical scheck,lprint
290       lprint=.false.
291       do i=1,maxres
292         nint_gr(i)=0
293         nscp_gr(i)=0
294         do j=1,maxint_gr
295           istart(i,1)=0
296           iend(i,1)=0
297           ielstart(i)=0
298           ielend(i)=0
299           iscpstart(i,1)=0
300           iscpend(i,1)=0    
301         enddo
302       enddo
303       ind_scint=0
304       ind_scint_old=0
305 cd    write (iout,*) 'ns=',ns,' nss=',nss,' ihpb,jhpb',
306 cd   &   (ihpb(i),jhpb(i),i=1,nss)
307       do i=nnt,nct-1
308         scheck=.false.
309         do ii=1,nss
310           if (ihpb(ii).eq.i+nres) then
311             scheck=.true.
312             jj=jhpb(ii)-nres
313             goto 10
314           endif
315         enddo
316    10   continue
317 cd      write (iout,*) 'i=',i,' scheck=',scheck,' jj=',jj
318         if (scheck) then
319           if (jj.eq.i+1) then
320             nint_gr(i)=1
321             istart(i,1)=i+2
322             iend(i,1)=nct
323           else if (jj.eq.nct) then
324             nint_gr(i)=1
325             istart(i,1)=i+1
326             iend(i,1)=nct-1
327           else
328             nint_gr(i)=2
329             istart(i,1)=i+1
330             iend(i,1)=jj-1
331             istart(i,2)=jj+1
332             iend(i,2)=nct
333           endif
334         else
335           nint_gr(i)=1
336           istart(i,1)=i+1
337           iend(i,1)=nct
338           ind_scint=int_scint+nct-i
339         endif
340       enddo
341    12 continue
342       iatsc_s=nnt
343       iatsc_e=nct-1
344       if (lprint) then
345       write (iout,'(a)') 'Interaction array:'
346       do i=iatsc_s,iatsc_e
347         write (iout,'(i3,2(2x,2i3))') 
348      & i,(istart(i,iint),iend(i,iint),iint=1,nint_gr(i))
349       enddo
350       endif
351       ispp=2
352       iatel_s=nnt
353       iatel_e=nct-3
354       do i=iatel_s,iatel_e
355         ielstart(i)=i+4
356         ielend(i)=nct-1
357       enddo
358       if (lprint) then
359         write (iout,'(a)') 'Electrostatic interaction array:'
360         do i=iatel_s,iatel_e
361           write (iout,'(i3,2(2x,2i3))') i,ielstart(i),ielend(i)
362         enddo
363       endif ! lprint
364 c     iscp=3
365       iscp=2
366 C Partition the SC-p interaction array
367       iatscp_s=nnt
368       iatscp_e=nct-1
369       do i=nnt,nct-1
370         if (i.lt.nnt+iscp) then
371           nscp_gr(i)=1
372           iscpstart(i,1)=i+iscp
373           iscpend(i,1)=nct
374         elseif (i.gt.nct-iscp) then
375           nscp_gr(i)=1
376           iscpstart(i,1)=nnt
377           iscpend(i,1)=i-iscp
378         else
379           nscp_gr(i)=2
380           iscpstart(i,1)=nnt
381           iscpend(i,1)=i-iscp
382           iscpstart(i,2)=i+iscp
383           iscpend(i,2)=nct
384         endif 
385       enddo ! i
386       if (lprint) then
387         write (iout,'(a)') 'SC-p interaction array:'
388         do i=iatscp_s,iatscp_e
389           write (iout,'(i3,2(2x,2i3))') 
390      &         i,(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
391         enddo
392       endif ! lprint
393 C Partition local interactions
394       loc_start=2
395       loc_end=nres-1
396       ithet_start=3 
397       ithet_end=nres
398       iturn3_start=nnt
399       iturn3_end=nct-3
400       iturn4_start=nnt
401       iturn4_end=nct-4
402       iphi_start=nnt+3
403       iphi_end=nct
404       idihconstr_start=1
405       idihconstr_end=ndih_constr
406       ithetaconstr_start=1
407       ithetaconstr_end=ntheta_constr
408       itau_start=4
409       itau_end=nres
410       return
411       end 
412 c---------------------------------------------------------------------------
413       subroutine int_partition(int_index,lower_index,upper_index,atom,
414      & at_start,at_end,first_atom,last_atom,int_gr,jat_start,jat_end,*)
415       implicit real*8 (a-h,o-z)
416       include 'DIMENSIONS'
417       include 'DIMENSIONS.ZSCOPT'
418       include 'COMMON.IOUNITS'
419       integer int_index,lower_index,upper_index,atom,at_start,at_end,
420      & first_atom,last_atom,int_gr,jat_start,jat_end
421       logical lprn
422       lprn=.false.
423       if (lprn) write (iout,*) 'int_index=',int_index
424       int_index_old=int_index
425       int_index=int_index+last_atom-first_atom+1
426       if (lprn) 
427      &   write (iout,*) 'int_index=',int_index,
428      &               ' int_index_old',int_index_old,
429      &               ' lower_index=',lower_index,
430      &               ' upper_index=',upper_index,
431      &               ' atom=',atom,' first_atom=',first_atom,
432      &               ' last_atom=',last_atom
433       if (int_index.ge.lower_index) then
434         int_gr=int_gr+1
435         if (at_start.eq.0) then
436           at_start=atom
437           jat_start=first_atom-1+lower_index-int_index_old
438         else
439           jat_start=first_atom
440         endif
441         if (lprn) write (iout,*) 'jat_start',jat_start
442         if (int_index.ge.upper_index) then
443           at_end=atom
444           jat_end=first_atom-1+upper_index-int_index_old
445           return1
446         else
447           jat_end=last_atom
448         endif
449         if (lprn) write (iout,*) 'jat_end',jat_end
450       endif
451       return
452       end
453 c------------------------------------------------------------------------------
454       subroutine hpb_partition
455       implicit real*8 (a-h,o-z)
456       include 'DIMENSIONS'
457       include 'DIMENSIONS.ZSCOPT'
458       include 'COMMON.SBRIDGE'
459       include 'COMMON.IOUNITS'
460       link_start=1
461       link_end=nhpb
462 cd    write (iout,*) 'Processor',MyID,' MyRank',MyRank,
463 cd   &  ' nhpb',nhpb,' link_start=',link_start,
464 cd   &  ' link_end',link_end
465       return
466       end