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