update new files
[unres.git] / source / maxlik / src_FPy / 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       wliptran=0.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       return
232       end
233 c-------------------------------------------------------------------------
234       block data nazwy
235       implicit real*8 (a-h,o-z)
236       include 'DIMENSIONS'
237       include 'DIMENSIONS.ZSCOPT'
238       include 'COMMON.NAMES'
239       include 'COMMON.WEIGHTS'
240       include 'COMMON.FFIELD'
241       data restyp /
242      &'DD','DAU','DAI','DDB','DSM','DPR','DLY','DAR','DHI','DAS','DGL',
243      & 'DSG','DGN','DSN','DTH',
244      &'DYY','DAL','DTY','DTR','DVA','DLE','DIL','DPN','MED','DCY','ZER',
245      &'CYS','MET','PHE','ILE','LEU','VAL','TRP','TYR','ALA','GLY','THR',
246      &'SER','GLN','ASN','GLU','ASP','HIS','ARG','LYS','PRO','SME','DBZ',
247      &'AIB','ABU','D'/
248       data onelet /
249      &'z','z','z','z','z','p','k','r','h','d','e','n','q','s','t','g',
250      &'a','y','w','v','l','i','f','m','c','x',
251      &'C','M','F','I','L','V','W','Y','A','G','T',
252      &'S','Q','N','E','D','H','R','K','P','z','z','z','z','X'/
253       data potname /'LJ','LJK','BP','GB','GBV','MM'/
254       data ename /
255      &   "EVDW SC-SC","EVDW2 SC-p","EES p-p","ECORR4 ","ECORR5 ",
256      &   "ECORR6 ","EELLO ","ETURN3 ","ETURN4 ","ETURN6 ",
257      &   "EBE bend","ESC SCloc","ETORS ","ETORSD ","EHPB","EVDWPP",
258      &   "ESTR","EVDW2_14","ESCCOR","EDIHC","EVDW_T","ELIPTRAN",
259      &   "EAFM","ETHETC","EMPTY"/
260       data wname /
261      &   "WSC","WSCP","WELEC","WCORR","WCORR5","WCORR6","WEL_LOC",
262      &   "WTURN3","WTURN4","WTURN6","WANG","WSCLOC","WTOR","WTORD",
263      &   "WHPB","WVDWPP","WBOND","WSCP14","WSCCOR","WDIHC","WSC",
264      &   "WLIPTRAN","WAFM","WTHETC","WSHIELD"/
265       data ww0 /1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,
266      &    1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,0.0d0,1.0d0,
267      &    0.0d0,0.0,0.0d0,0.0d0,0.0d0,0.0d0/
268       data nprint_ene /25/
269       data print_order /1,2,3,17,11,12,13,14,4,5,6,7,8,9,10,19,16,15,18,
270      &  20,21,22,23,24,25/
271       end 
272 c---------------------------------------------------------------------------
273       subroutine init_int_table
274       implicit real*8 (a-h,o-z)
275       include 'DIMENSIONS'
276       include 'DIMENSIONS.ZSCOPT'
277 #ifdef MPI
278       include 'mpif.h'
279 #endif
280 #ifdef MP
281       include 'COMMON.INFO'
282 #endif
283       include 'COMMON.CHAIN'
284       include 'COMMON.INTERACT'
285       include 'COMMON.LOCAL'
286       include 'COMMON.SBRIDGE'
287       include 'COMMON.IOUNITS'
288       logical scheck,lprint
289       lprint=.false.
290       do i=1,maxres
291         nint_gr(i)=0
292         nscp_gr(i)=0
293         do j=1,maxint_gr
294           istart(i,1)=0
295           iend(i,1)=0
296           ielstart(i)=0
297           ielend(i)=0
298           iscpstart(i,1)=0
299           iscpend(i,1)=0    
300         enddo
301       enddo
302       ind_scint=0
303       ind_scint_old=0
304 cd    write (iout,*) 'ns=',ns,' nss=',nss,' ihpb,jhpb',
305 cd   &   (ihpb(i),jhpb(i),i=1,nss)
306       do i=nnt,nct-1
307         scheck=.false.
308         do ii=1,nss
309           if (ihpb(ii).eq.i+nres) then
310             scheck=.true.
311             jj=jhpb(ii)-nres
312             goto 10
313           endif
314         enddo
315    10   continue
316 cd      write (iout,*) 'i=',i,' scheck=',scheck,' jj=',jj
317         if (scheck) then
318           if (jj.eq.i+1) then
319             nint_gr(i)=1
320             istart(i,1)=i+2
321             iend(i,1)=nct
322           else if (jj.eq.nct) then
323             nint_gr(i)=1
324             istart(i,1)=i+1
325             iend(i,1)=nct-1
326           else
327             nint_gr(i)=2
328             istart(i,1)=i+1
329             iend(i,1)=jj-1
330             istart(i,2)=jj+1
331             iend(i,2)=nct
332           endif
333         else
334           nint_gr(i)=1
335           istart(i,1)=i+1
336           iend(i,1)=nct
337           ind_scint=int_scint+nct-i
338         endif
339       enddo
340    12 continue
341       iatsc_s=nnt
342       iatsc_e=nct-1
343       if (lprint) then
344       write (iout,'(a)') 'Interaction array:'
345       do i=iatsc_s,iatsc_e
346         write (iout,'(i3,2(2x,2i3))') 
347      & i,(istart(i,iint),iend(i,iint),iint=1,nint_gr(i))
348       enddo
349       endif
350       ispp=2
351       iatel_s=nnt
352       iatel_e=nct-3
353       do i=iatel_s,iatel_e
354         ielstart(i)=i+4
355         ielend(i)=nct-1
356       enddo
357       if (lprint) then
358         write (iout,'(a)') 'Electrostatic interaction array:'
359         do i=iatel_s,iatel_e
360           write (iout,'(i3,2(2x,2i3))') i,ielstart(i),ielend(i)
361         enddo
362       endif ! lprint
363 c     iscp=3
364       iscp=2
365 C Partition the SC-p interaction array
366       iatscp_s=nnt
367       iatscp_e=nct-1
368       do i=nnt,nct-1
369         if (i.lt.nnt+iscp) then
370           nscp_gr(i)=1
371           iscpstart(i,1)=i+iscp
372           iscpend(i,1)=nct
373         elseif (i.gt.nct-iscp) then
374           nscp_gr(i)=1
375           iscpstart(i,1)=nnt
376           iscpend(i,1)=i-iscp
377         else
378           nscp_gr(i)=2
379           iscpstart(i,1)=nnt
380           iscpend(i,1)=i-iscp
381           iscpstart(i,2)=i+iscp
382           iscpend(i,2)=nct
383         endif 
384       enddo ! i
385       if (lprint) then
386         write (iout,'(a)') 'SC-p interaction array:'
387         do i=iatscp_s,iatscp_e
388           write (iout,'(i3,2(2x,2i3))') 
389      &         i,(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
390         enddo
391       endif ! lprint
392 C Partition local interactions
393       loc_start=2
394       loc_end=nres-1
395       ithet_start=3 
396       ithet_end=nres
397       iturn3_start=nnt
398       iturn3_end=nct-3
399       iturn4_start=nnt
400       iturn4_end=nct-4
401       iphi_start=nnt+3
402       iphi_end=nct
403       idihconstr_start=1
404       idihconstr_end=ndih_constr
405       ithetaconstr_start=1
406       ithetaconstr_end=ntheta_constr
407       itau_start=4
408       itau_end=nres
409       return
410       end 
411 c---------------------------------------------------------------------------
412       subroutine int_partition(int_index,lower_index,upper_index,atom,
413      & at_start,at_end,first_atom,last_atom,int_gr,jat_start,jat_end,*)
414       implicit real*8 (a-h,o-z)
415       include 'DIMENSIONS'
416       include 'DIMENSIONS.ZSCOPT'
417       include 'COMMON.IOUNITS'
418       integer int_index,lower_index,upper_index,atom,at_start,at_end,
419      & first_atom,last_atom,int_gr,jat_start,jat_end
420       logical lprn
421       lprn=.false.
422       if (lprn) write (iout,*) 'int_index=',int_index
423       int_index_old=int_index
424       int_index=int_index+last_atom-first_atom+1
425       if (lprn) 
426      &   write (iout,*) 'int_index=',int_index,
427      &               ' int_index_old',int_index_old,
428      &               ' lower_index=',lower_index,
429      &               ' upper_index=',upper_index,
430      &               ' atom=',atom,' first_atom=',first_atom,
431      &               ' last_atom=',last_atom
432       if (int_index.ge.lower_index) then
433         int_gr=int_gr+1
434         if (at_start.eq.0) then
435           at_start=atom
436           jat_start=first_atom-1+lower_index-int_index_old
437         else
438           jat_start=first_atom
439         endif
440         if (lprn) write (iout,*) 'jat_start',jat_start
441         if (int_index.ge.upper_index) then
442           at_end=atom
443           jat_end=first_atom-1+upper_index-int_index_old
444           return1
445         else
446           jat_end=last_atom
447         endif
448         if (lprn) write (iout,*) 'jat_end',jat_end
449       endif
450       return
451       end
452 c------------------------------------------------------------------------------
453       subroutine hpb_partition
454       implicit real*8 (a-h,o-z)
455       include 'DIMENSIONS'
456       include 'DIMENSIONS.ZSCOPT'
457       include 'COMMON.SBRIDGE'
458       include 'COMMON.IOUNITS'
459       link_start=1
460       link_end=nhpb
461 cd    write (iout,*) 'Processor',MyID,' MyRank',MyRank,
462 cd   &  ' nhpb',nhpb,' link_start=',link_start,
463 cd   &  ' link_end',link_end
464       return
465       end