wham in lipid still diff
[unres.git] / source / wham / src-M / 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 C
25 C The following is just to define auxiliary variables used in angle conversion
26 C
27       pi=4.0D0*datan(1.0D0)
28       dwapi=2.0D0*pi
29       dwapi3=dwapi/3.0D0
30       pipol=0.5D0*pi
31       deg2rad=pi/180.0D0
32       rad2deg=1.0D0/deg2rad
33       angmin=10.0D0*deg2rad
34 C
35 C Define I/O units.
36 C
37       inp=    1
38       iout=   2
39       ipdbin= 3
40       ipdb=   7
41       imol2=  4
42       igeom=  8
43       intin=  9
44       ithep= 11
45       irotam=12
46       itorp= 13
47       itordp= 23
48       ielep= 14
49       isidep=15 
50       isidep1=22
51       iscpp=25
52       icbase=16
53       ifourier=20
54       istat= 17
55       ientin=18
56       ientout=19
57       ibond=28
58       isccor=29
59 C
60 C WHAM files
61 C
62       ihist=30
63       iweight=31
64       izsc=32
65 C Lipidic input file for parameters range 60-79
66       iliptranpar=60
67 C
68 C Set default weights of the energy terms.
69 C
70       wlong=1.0D0
71       welec=1.0D0
72       wtor =1.0D0
73       wang =1.0D0
74       wscloc=1.0D0
75       wstrain=1.0D0
76 C
77 C Zero out tables.
78 C
79       ndih_constr=0
80       do i=1,maxres2
81         do j=1,3
82           c(j,i)=0.0D0
83           dc(j,i)=0.0D0
84         enddo
85       enddo
86       do i=1,maxres
87         do j=1,3
88           xloc(j,i)=0.0D0
89         enddo
90       enddo
91       do i=1,ntyp
92         do j=1,ntyp
93           aa_lip(i,j)=0.0D0
94           bb_lip(i,j)=0.0D0
95           aa_aq(i,j)=0.0D0
96           bb_aq(i,j)=0.0D0
97           augm(i,j)=0.0D0
98           sigma(i,j)=0.0D0
99           r0(i,j)=0.0D0
100           chi(i,j)=0.0D0
101         enddo
102         do j=1,2
103           bad(i,j)=0.0D0
104         enddo
105         chip(i)=0.0D0
106         alp(i)=0.0D0
107         sigma0(i)=0.0D0
108         sigii(i)=0.0D0
109         rr0(i)=0.0D0
110         a0thet(i)=0.0D0
111         do j=1,2
112          do ichir1=-1,1
113           do ichir2=-1,1
114           athet(j,i,ichir1,ichir2)=0.0D0
115           bthet(j,i,ichir1,ichir2)=0.0D0
116           enddo
117          enddo
118         enddo
119         do j=0,3
120           polthet(j,i)=0.0D0
121         enddo
122         do j=1,3
123           gthet(j,i)=0.0D0
124         enddo
125         theta0(i)=0.0D0
126         sig0(i)=0.0D0
127         sigc0(i)=0.0D0
128         do j=1,maxlob
129           bsc(j,i)=0.0D0
130           do k=1,3
131             censc(k,j,i)=0.0D0
132           enddo
133           do k=1,3
134             do l=1,3
135               gaussc(l,k,j,i)=0.0D0
136             enddo
137           enddo
138           nlob(i)=0
139         enddo
140       enddo
141       nlob(ntyp1)=0
142       dsc(ntyp1)=0.0D0
143       do i=-maxtor,maxtor
144         itortyp(i)=0
145        do iblock=1,2
146         do j=-maxtor,maxtor
147           do k=1,maxterm
148             v1(k,j,i,iblock)=0.0D0
149             v2(k,j,i,iblock)=0.0D0
150           enddo
151         enddo
152         enddo
153       enddo
154       do iblock=1,2
155        do i=-maxtor,maxtor
156         do j=-maxtor,maxtor
157          do k=-maxtor,maxtor
158           do l=1,maxtermd_1
159             v1c(1,l,i,j,k,iblock)=0.0D0
160             v1s(1,l,i,j,k,iblock)=0.0D0
161             v1c(2,l,i,j,k,iblock)=0.0D0
162             v1s(2,l,i,j,k,iblock)=0.0D0
163           enddo !l
164           do l=1,maxtermd_2
165            do m=1,maxtermd_2
166             v2c(m,l,i,j,k,iblock)=0.0D0
167             v2s(m,l,i,j,k,iblock)=0.0D0
168            enddo !m
169           enddo !l
170         enddo !k
171        enddo !j
172       enddo !i
173       enddo !iblock
174       do i=1,maxres
175         itype(i)=0
176         itel(i)=0
177       enddo
178 C Initialize the bridge arrays
179       ns=0
180       nss=0 
181       nhpb=0
182       do i=1,maxss
183         iss(i)=0
184       enddo
185       do i=1,maxdim
186         dhpb(i)=0.0D0
187       enddo
188       do i=1,maxres
189         ihpb(i)=0
190         jhpb(i)=0
191       enddo
192 C
193 C Initialize timing.
194 C
195       call set_timers
196 C
197 C Initialize variables used in minimization.
198 C   
199 c     maxfun=5000
200 c     maxit=2000
201       maxfun=500
202       maxit=200
203       tolf=1.0D-2
204       rtolf=5.0D-4
205
206 C Initialize the variables responsible for the mode of gradient storage.
207 C
208       nfl=0
209       icg=1
210       do i=1,14
211         do j=1,14
212           if (print_order(i).eq.j) then
213             iw(print_order(i))=j
214             goto 1121
215           endif
216         enddo
217 1121    continue
218       enddo
219       calc_grad=.false.
220 C Set timers and counters for the respective routines
221       t_func = 0.0d0
222       t_grad = 0.0d0
223       t_fhel = 0.0d0
224       t_fbet = 0.0d0
225       t_ghel = 0.0d0
226       t_gbet = 0.0d0
227       t_viol = 0.0d0
228       t_gviol = 0.0d0
229       n_func = 0
230       n_grad = 0
231       n_fhel = 0
232       n_fbet = 0
233       n_ghel = 0
234       n_gbet = 0
235       n_viol = 0
236       n_gviol = 0
237       n_map = 0
238 #ifndef SPLITELE
239       nprint_ene=nprint_ene-1
240 #endif
241       return
242       end
243 c-------------------------------------------------------------------------
244       block data nazwy
245       implicit real*8 (a-h,o-z)
246       include 'DIMENSIONS'
247       include 'DIMENSIONS.ZSCOPT'
248       include 'COMMON.NAMES'
249       include 'COMMON.WEIGHTS'
250       include 'COMMON.FFIELD'
251       data restyp /
252      &'DD','DAU','DAI','DDB','DSM','DPR','DLY','DAR','DHI','DAS','DGL',
253      & 'DSG','DGN','DSN','DTH',
254      &'DYY','DAL','DTY','DTR','DVA','DLE','DIL','DPN','MED','DCY','ZER',
255      &'CYS','MET','PHE','ILE','LEU','VAL','TRP','TYR','ALA','GLY','THR',
256      &'SER','GLN','ASN','GLU','ASP','HIS','ARG','LYS','PRO','SME','DBZ',
257      &'AIB','ABU','D'/
258       data onelet /
259      &'z','z','z','z','z','p','k','r','h','d','e','n','q','s','t','g',
260      &'a','y','w','v','l','i','f','m','c','x',
261      &'C','M','F','I','L','V','W','Y','A','G','T',
262      &'S','Q','N','E','D','H','R','K','P','z','z','z','z','X'/
263       data potname /'LJ','LJK','BP','GB','GBV'/
264       data ename / 
265      &   "EVDW SC-SC","EVDW2 SC-p","EES p-p","ECORR4 ","ECORR5 ",
266      &   "ECORR6 ","EELLO ","ETURN3 ","ETURN4 ","ETURN6 ",
267      &   "EBE bend","ESC SCloc","ETORS ","ETORSD ","EHPB","EVDWPP",
268      &   "EVDW2_14","ESTR","ESCCOR","EDIHC","EVDW_T","ELT"/
269       data wname /
270      &   "WSC","WSCP","WELEC","WCORR","WCORR5","WCORR6","WEL_LOC",
271      &   "WTURN3","WTURN4","WTURN6","WANG","WSCLOC","WTOR","WTORD",
272      &   "WHPB","WVDWPP","WSCP14","WBOND","WSCCOR","WDIHC","WSC","WLT"/
273       data ww0 /1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,
274      &    1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,0.4d0,1.0d0,1.0d0,
275      &    0.0d0,0.0,0.0/
276       data nprint_ene /22/
277       data print_order /1,2,3,18,11,12,13,14,4,5,6,7,8,9,10,19,
278      &  16,15,17,20,21,22/
279       end 
280 c---------------------------------------------------------------------------
281       subroutine init_int_table
282       implicit real*8 (a-h,o-z)
283       include 'DIMENSIONS'
284       include 'DIMENSIONS.ZSCOPT'
285 #ifdef MPI
286       include 'mpif.h'
287 #endif
288 #ifdef MP
289       include 'COMMON.INFO'
290 #endif
291       include 'COMMON.CHAIN'
292       include 'COMMON.INTERACT'
293       include 'COMMON.LOCAL'
294       include 'COMMON.SBRIDGE'
295       include 'COMMON.IOUNITS'
296       logical scheck,lprint
297 #ifdef MPL
298       integer my_sc_int(0:max_fg_Procs-1),my_sc_intt(0:max_fg_Procs),
299      & my_ele_int(0:max_fg_Procs-1),my_ele_intt(0:max_fg_Procs)
300 C... Determine the numbers of start and end SC-SC interaction 
301 C... to deal with by current processor.
302       lprint=.false.
303       if (lprint)
304      &write (iout,*) 'INIT_INT_TABLE nres=',nres,' nnt=',nnt,' nct=',nct
305       n_sc_int_tot=(nct-nnt+1)*(nct-nnt)/2-nss
306       MyRank=MyID-(MyGroup-1)*fgProcs
307       call int_bounds(n_sc_int_tot,my_sc_inds,my_sc_inde)
308       if (lprint)
309      &  write (iout,*) 'Processor',MyID,' MyRank',MyRank,
310      &  ' n_sc_int_tot',n_sc_int_tot,' my_sc_inds=',my_sc_inds,
311      &  ' my_sc_inde',my_sc_inde
312       ind_sctint=0
313       iatsc_s=0
314       iatsc_e=0
315 #endif
316       lprint=.false.
317       do i=1,maxres
318         nint_gr(i)=0
319         nscp_gr(i)=0
320         do j=1,maxint_gr
321           istart(i,1)=0
322           iend(i,1)=0
323           ielstart(i)=0
324           ielend(i)=0
325           iscpstart(i,1)=0
326           iscpend(i,1)=0    
327         enddo
328       enddo
329       ind_scint=0
330       ind_scint_old=0
331 cd    write (iout,*) 'ns=',ns,' nss=',nss,' ihpb,jhpb',
332 cd   &   (ihpb(i),jhpb(i),i=1,nss)
333       do i=nnt,nct-1
334         scheck=.false.
335         do ii=1,nss
336           if (ihpb(ii).eq.i+nres) then
337             scheck=.true.
338             jj=jhpb(ii)-nres
339             goto 10
340           endif
341         enddo
342    10   continue
343 cd      write (iout,*) 'i=',i,' scheck=',scheck,' jj=',jj
344         if (scheck) then
345           if (jj.eq.i+1) then
346 #ifdef MPL
347             write (iout,*) 'jj=i+1'
348             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
349      & iatsc_s,iatsc_e,i+2,nct,nint_gr(i),istart(i,1),iend(i,1),*12)
350 #else
351             nint_gr(i)=1
352             istart(i,1)=i+2
353             iend(i,1)=nct
354 #endif
355           else if (jj.eq.nct) then
356 #ifdef MPL
357             write (iout,*) 'jj=nct'
358             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
359      &  iatsc_s,iatsc_e,i+1,nct-1,nint_gr(i),istart(i,1),iend(i,1),*12)
360 #else
361             nint_gr(i)=1
362             istart(i,1)=i+1
363             iend(i,1)=nct-1
364 #endif
365           else
366 #ifdef MPL
367             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
368      & iatsc_s,iatsc_e,i+1,jj-1,nint_gr(i),istart(i,1),iend(i,1),*12)
369             ii=nint_gr(i)+1
370             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
371      & iatsc_s,iatsc_e,jj+1,nct,nint_gr(i),istart(i,ii),iend(i,ii),*12)
372 #else
373             nint_gr(i)=2
374             istart(i,1)=i+1
375             iend(i,1)=jj-1
376             istart(i,2)=jj+1
377             iend(i,2)=nct
378 #endif
379           endif
380         else
381 #ifdef MPL
382           call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
383      &    iatsc_s,iatsc_e,i+1,nct,nint_gr(i),istart(i,1),iend(i,1),*12)
384 #else
385           nint_gr(i)=1
386           istart(i,1)=i+1
387           iend(i,1)=nct
388           ind_scint=int_scint+nct-i
389 #endif
390         endif
391 #ifdef MPL
392         ind_scint_old=ind_scint
393 #endif
394       enddo
395    12 continue
396 #ifndef MPL
397       iatsc_s=nnt
398       iatsc_e=nct-1
399 #endif
400 #ifdef MPL
401       if (lprint) then
402         write (iout,*) 'Processor',MyID,' Group',MyGroup
403         write (iout,*) 'iatsc_s=',iatsc_s,' iatsc_e=',iatsc_e
404       endif
405 #endif
406       if (lprint) then
407       write (iout,'(a)') 'Interaction array:'
408       do i=iatsc_s,iatsc_e
409         write (iout,'(i3,2(2x,2i3))') 
410      & i,(istart(i,iint),iend(i,iint),iint=1,nint_gr(i))
411       enddo
412       endif
413       ispp=2
414 #ifdef MPL
415 C Now partition the electrostatic-interaction array
416       npept=nct-nnt
417       nele_int_tot=(npept-ispp)*(npept-ispp+1)/2
418       call int_bounds(nele_int_tot,my_ele_inds,my_ele_inde)
419       if (lprint)
420      & write (iout,*) 'Processor',MyID,' MyRank',MyRank,
421      &  ' nele_int_tot',nele_int_tot,' my_ele_inds=',my_ele_inds,
422      &               ' my_ele_inde',my_ele_inde
423       iatel_s=0
424       iatel_e=0
425       ind_eleint=0
426       ind_eleint_old=0
427       do i=nnt,nct-3
428         ijunk=0
429         call int_partition(ind_eleint,my_ele_inds,my_ele_inde,i,
430      &    iatel_s,iatel_e,i+ispp,nct-1,ijunk,ielstart(i),ielend(i),*13)
431       enddo ! i 
432    13 continue
433 #else
434       iatel_s=nnt
435       iatel_e=nct-3
436       do i=iatel_s,iatel_e
437         ielstart(i)=i+2
438         ielend(i)=nct-1
439       enddo
440 #endif
441       if (lprint) then
442         write (iout,'(a)') 'Electrostatic interaction array:'
443         do i=iatel_s,iatel_e
444           write (iout,'(i3,2(2x,2i3))') i,ielstart(i),ielend(i)
445         enddo
446       endif ! lprint
447 c     iscp=3
448       iscp=2
449 C Partition the SC-p interaction array
450 #ifdef MPL
451       nscp_int_tot=(npept-iscp+1)*(npept-iscp+1)
452       call int_bounds(nscp_int_tot,my_scp_inds,my_scp_inde)
453       if (lprint)
454      & write (iout,*) 'Processor',MyID,' MyRank',MyRank,
455      &  ' nscp_int_tot',nscp_int_tot,' my_scp_inds=',my_scp_inds,
456      &               ' my_scp_inde',my_scp_inde
457       iatscp_s=0
458       iatscp_e=0
459       ind_scpint=0
460       ind_scpint_old=0
461       do i=nnt,nct-1
462         if (i.lt.nnt+iscp) then
463 cd        write (iout,*) 'i.le.nnt+iscp'
464           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,
465      &      iatscp_s,iatscp_e,i+iscp,nct,nscp_gr(i),iscpstart(i,1),
466      &      iscpend(i,1),*14)
467         else if (i.gt.nct-iscp) then
468 cd        write (iout,*) 'i.gt.nct-iscp'
469           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,
470      &      iatscp_s,iatscp_e,nnt,i-iscp,nscp_gr(i),iscpstart(i,1),
471      &      iscpend(i,1),*14)
472         else
473           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,
474      &      iatscp_s,iatscp_e,nnt,i-iscp,nscp_gr(i),iscpstart(i,1),
475      &      iscpend(i,1),*14)
476           ii=nscp_gr(i)+1
477           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,
478      &      iatscp_s,iatscp_e,i+iscp,nct,nscp_gr(i),iscpstart(i,ii),
479      &      iscpend(i,ii),*14)
480         endif
481       enddo ! i
482    14 continue
483 #else
484       iatscp_s=nnt
485       iatscp_e=nct-1
486       do i=nnt,nct-1
487         if (i.lt.nnt+iscp) then
488           nscp_gr(i)=1
489           iscpstart(i,1)=i+iscp
490           iscpend(i,1)=nct
491         elseif (i.gt.nct-iscp) then
492           nscp_gr(i)=1
493           iscpstart(i,1)=nnt
494           iscpend(i,1)=i-iscp
495         else
496           nscp_gr(i)=2
497           iscpstart(i,1)=nnt
498           iscpend(i,1)=i-iscp
499           iscpstart(i,2)=i+iscp
500           iscpend(i,2)=nct
501         endif 
502       enddo ! i
503 #endif
504       if (lprint) then
505         write (iout,'(a)') 'SC-p interaction array:'
506         do i=iatscp_s,iatscp_e
507           write (iout,'(i3,2(2x,2i3))') 
508      &         i,(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
509         enddo
510       endif ! lprint
511 C Partition local interactions
512 #ifdef MPL
513       call int_bounds(nres-2,loc_start,loc_end)
514       loc_start=loc_start+1
515       loc_end=loc_end+1
516       call int_bounds(nres-2,ithet_start,ithet_end)
517       ithet_start=ithet_start+2
518       ithet_end=ithet_end+2
519       call int_bounds(nct-nnt-2,iphi_start,iphi_end) 
520       iphi_start=iphi_start+nnt+2
521       iphi_end=iphi_end+nnt+2
522       call int_bounds(nres-3,itau_start,itau_end)
523       itau_start=itau_start+3
524       itau_end=itau_end+3
525       if (lprint) then 
526         write (iout,*) 'Processor:',MyID,
527      & ' loc_start',loc_start,' loc_end',loc_end,
528      & ' ithet_start',ithet_start,' ithet_end',ithet_end,
529      & ' iphi_start',iphi_start,' iphi_end',iphi_end
530         write (*,*) 'Processor:',MyID,
531      & ' loc_start',loc_start,' loc_end',loc_end,
532      & ' ithet_start',ithet_start,' ithet_end',ithet_end,
533      & ' iphi_start',iphi_start,' iphi_end',iphi_end
534       endif
535       if (fgprocs.gt.1 .and. MyID.eq.BossID) then
536         write(iout,'(i10,a,i10,a,i10,a/a,i3,a)') n_sc_int_tot,' SC-SC ',
537      & nele_int_tot,' electrostatic and ',nscp_int_tot,
538      & ' SC-p interactions','were distributed among',fgprocs,
539      & ' fine-grain processors.'
540       endif
541 #else
542       loc_start=2
543       loc_end=nres-1
544       ithet_start=3
545       ithet_end=nres
546       iphi_start=nnt+3
547       iphi_end=nct
548       itau_start=4
549       itau_end=nres
550 #endif
551       return
552       end 
553 c---------------------------------------------------------------------------
554       subroutine int_partition(int_index,lower_index,upper_index,atom,
555      & at_start,at_end,first_atom,last_atom,int_gr,jat_start,jat_end,*)
556       implicit real*8 (a-h,o-z)
557       include 'DIMENSIONS'
558       include 'COMMON.IOUNITS'
559       integer int_index,lower_index,upper_index,atom,at_start,at_end,
560      & first_atom,last_atom,int_gr,jat_start,jat_end
561       logical lprn
562       lprn=.false.
563       if (lprn) write (iout,*) 'int_index=',int_index
564       int_index_old=int_index
565       int_index=int_index+last_atom-first_atom+1
566       if (lprn) 
567      &   write (iout,*) 'int_index=',int_index,
568      &               ' int_index_old',int_index_old,
569      &               ' lower_index=',lower_index,
570      &               ' upper_index=',upper_index,
571      &               ' atom=',atom,' first_atom=',first_atom,
572      &               ' last_atom=',last_atom
573       if (int_index.ge.lower_index) then
574         int_gr=int_gr+1
575         if (at_start.eq.0) then
576           at_start=atom
577           jat_start=first_atom-1+lower_index-int_index_old
578         else
579           jat_start=first_atom
580         endif
581         if (lprn) write (iout,*) 'jat_start',jat_start
582         if (int_index.ge.upper_index) then
583           at_end=atom
584           jat_end=first_atom-1+upper_index-int_index_old
585           return1
586         else
587           jat_end=last_atom
588         endif
589         if (lprn) write (iout,*) 'jat_end',jat_end
590       endif
591       return
592       end
593 c------------------------------------------------------------------------------
594       subroutine hpb_partition
595       implicit real*8 (a-h,o-z)
596       include 'DIMENSIONS'
597       include 'COMMON.SBRIDGE'
598       include 'COMMON.IOUNITS'
599 #ifdef MPL
600       include 'COMMON.INFO'
601       call int_bounds(nhpb,link_start,link_end)
602 #else
603       link_start=1
604       link_end=nhpb
605 #endif
606 cd    write (iout,*) 'Processor',MyID,' MyRank',MyRank,
607 cd   &  ' nhpb',nhpb,' link_start=',link_start,
608 cd   &  ' link_end',link_end
609       return
610       end