1 subroutine read_control
8 include 'COMMON.IOUNITS'
10 include 'COMMON.SBRIDGE'
11 include 'COMMON.CONTROL'
12 include 'COMMON.CLUSTER'
13 include 'COMMON.CHAIN'
14 include 'COMMON.HEADER'
15 include 'COMMON.FFIELD'
17 include 'COMMON.INTERACT'
18 include "COMMON.SPLITELE"
19 include 'COMMON.SHIELD'
20 character*320 controlcard,ucase
24 integer i,i1,i2,it1,it2
26 read (INP,'(a80)') titel
27 call card_concat(controlcard)
29 call readi(controlcard,'NRES',nres,0)
30 call readi(controlcard,'RESCALE',rescale_mode,2)
31 call reada(controlcard,'DISTCHAINMAX',distchainmax,50.0d0)
32 write (iout,*) "DISTCHAINMAX",distchainmax
33 C Reading the dimensions of box in x,y,z coordinates
34 call reada(controlcard,'BOXX',boxxsize,100.0d0)
35 call reada(controlcard,'BOXY',boxysize,100.0d0)
36 call reada(controlcard,'BOXZ',boxzsize,100.0d0)
37 c Cutoff range for interactions
38 call reada(controlcard,"R_CUT",r_cut,15.0d0)
39 call reada(controlcard,"LAMBDA",rlamb,0.3d0)
40 call reada(controlcard,"LIPTHICK",lipthick,0.0d0)
41 call reada(controlcard,"LIPAQBUF",lipbufthick,0.0d0)
42 if (lipthick.gt.0.0d0) then
43 bordliptop=(boxzsize+lipthick)/2.0
44 bordlipbot=bordliptop-lipthick
46 if ((bordliptop.gt.boxzsize).or.(bordlipbot.lt.0.0))
47 & write(iout,*) "WARNING WRONG SIZE OF LIPIDIC PHASE"
48 buflipbot=bordlipbot+lipbufthick
49 bufliptop=bordliptop-lipbufthick
50 if ((lipbufthick*2.0d0).gt.lipthick)
51 &write(iout,*) "WARNING WRONG SIZE OF LIP AQ BUF"
53 write(iout,*) "bordliptop=",bordliptop
54 write(iout,*) "bordlipbot=",bordlipbot
55 write(iout,*) "bufliptop=",bufliptop
56 write(iout,*) "buflipbot=",buflipbot
58 call readi(controlcard,'SHIELD',shield_mode,0)
59 write (iout,*) "SHIELD MODE",shield_mode
60 if (shield_mode.gt.0) then
62 C VSolvSphere the volume of solving sphere
64 C rpp(1,1) is the energy r0 for peptide group contact and will be used for it
65 C there will be no distinction between proline peptide group and normal peptide
66 C group in case of shielding parameters
67 VSolvSphere=4.0/3.0*pi*rpp(1,1)**3
68 VSolvSphere_div=VSolvSphere-4.0/3.0*pi*(rpp(1,1)/2.0)**3
69 write (iout,*) VSolvSphere,VSolvSphere_div
70 C long axis of side chain
72 long_r_sidechain(i)=vbldsc0(1,i)
73 short_r_sidechain(i)=sigma0(i)
77 call readi(controlcard,'PDBOUT',outpdb,0)
78 call readi(controlcard,'MOL2OUT',outmol2,0)
79 refstr=(index(controlcard,'REFSTR').gt.0)
80 write (iout,*) "REFSTR",refstr
81 pdbref=(index(controlcard,'PDBREF').gt.0)
82 iscode=index(controlcard,'ONE_LETTER')
83 tree=(index(controlcard,'MAKE_TREE').gt.0)
84 with_dihed_constr = index(controlcard,"WITH_DIHED_CONSTR").gt.0
85 call readi(controlcard,'CONSTR_DIST',constr_dist,0)
86 write (iout,*) "with_dihed_constr ",with_dihed_constr,
87 & " CONSTR_DIST",constr_dist
88 with_theta_constr = index(controlcard,"WITH_THETA_CONSTR").gt.0
89 write (iout,*) "with_theta_constr ",with_theta_constr
91 min_var=(index(controlcard,'MINVAR').gt.0)
92 plot_tree=(index(controlcard,'PLOT_TREE').gt.0)
93 punch_dist=(index(controlcard,'PUNCH_DIST').gt.0)
94 call readi(controlcard,'NCUT',ncut,1)
95 call readi(controlcard,'SYM',symetr,1)
96 write (iout,*) 'sym', symetr
97 call readi(controlcard,'NSTART',nstart,0)
98 call readi(controlcard,'NEND',nend,0)
99 call reada(controlcard,'ECUT',ecut,10.0d0)
100 call reada(controlcard,'PROB',prob_limit,0.99d0)
101 write (iout,*) "Probability limit",prob_limit
102 lgrp=(index(controlcard,'LGRP').gt.0)
103 caonly=(index(controlcard,'CA_ONLY').gt.0)
104 print_dist=(index(controlcard,'PRINT_DIST').gt.0)
105 call multreada(controlcard,'CUTOFF',rcutoff,ncut,-1.0d0)
106 call readi(controlcard,'IOPT',iopt,2)
107 lside = index(controlcard,"SIDE").gt.0
108 efree = index(controlcard,"EFREE").gt.0
109 call readi(controlcard,'NTEMP',nT,1)
110 write (iout,*) "nT",nT
111 call multreada(controlcard,'TEMPER',beta_h,nT,300.0d0)
112 write (iout,*) "nT",nT
113 write (iout,*) 'beta_h',(beta_h(i),i=1,nT)
115 beta_h(i)=1.0d0/(1.987D-3*beta_h(i))
117 write (iout,*) 'beta_h',(beta_h(i),i=1,nT)
118 lprint_cart=index(controlcard,"PRINT_CART") .gt.0
119 lprint_int=index(controlcard,"PRINT_INT") .gt.0
120 call readi(controlcard,'CONSTR_HOMOL',constr_homology,0)
121 write (iout,*) "with_homology_constr ",with_dihed_constr,
122 & " CONSTR_HOMOLOGY",constr_homology
123 print_homology_restraints=
124 & index(controlcard,"PRINT_HOMOLOGY_RESTRAINTS").gt.0
125 print_contact_map=index(controlcard,"PRINT_CONTACT_MAP").gt.0
126 print_homology_models=
127 & index(controlcard,"PRINT_HOMOLOGY_MODELS").gt.0
131 c--------------------------------------------------------------------------
134 C Read molecular data.
138 include 'COMMON.IOUNITS'
141 include 'COMMON.INTERACT'
142 include 'COMMON.LOCAL'
143 include 'COMMON.NAMES'
144 include 'COMMON.CHAIN'
145 include 'COMMON.FFIELD'
146 include 'COMMON.SBRIDGE'
147 include 'COMMON.HEADER'
148 include 'COMMON.CONTROL'
149 include 'COMMON.CONTACTS'
150 include 'COMMON.TIME1'
151 include 'COMMON.TORCNSTR'
152 include 'COMMON.SHIELD'
154 include 'COMMON.INFO'
156 character*4 sequence(maxres)
157 character*800 weightcard
159 double precision x(maxvar)
160 integer itype_pdb(maxres)
162 integer i,j,kkk,i1,i2,it1,it2
166 C Read weights of the subsequent energy terms.
167 call card_concat(weightcard)
168 write(iout,*) weightcard
169 C call reada(weightcard,'WSC',wsc,1.0d0)
171 call reada(weightcard,'WLONG',wsc,wsc)
172 call reada(weightcard,'WSCP',wscp,1.0d0)
173 call reada(weightcard,'WELEC',welec,1.0D0)
174 call reada(weightcard,'WVDWPP',wvdwpp,welec)
175 call reada(weightcard,'WEL_LOC',wel_loc,1.0D0)
176 call reada(weightcard,'WCORR4',wcorr4,0.0D0)
177 call reada(weightcard,'WCORR5',wcorr5,0.0D0)
178 call reada(weightcard,'WCORR6',wcorr6,0.0D0)
179 call reada(weightcard,'WTURN3',wturn3,1.0D0)
180 call reada(weightcard,'WTURN4',wturn4,1.0D0)
181 call reada(weightcard,'WTURN6',wturn6,1.0D0)
182 call reada(weightcard,'WSTRAIN',wstrain,1.0D0)
183 call reada(weightcard,'WSCCOR',wsccor,1.0D0)
184 call reada(weightcard,'WBOND',wbond,1.0D0)
185 call reada(weightcard,'WTOR',wtor,1.0D0)
186 call reada(weightcard,'WTORD',wtor_d,1.0D0)
187 call reada(weightcard,'WANG',wang,1.0D0)
188 call reada(weightcard,'WSCLOC',wscloc,1.0D0)
189 call reada(weightcard,'SCAL14',scal14,0.4D0)
190 call reada(weightcard,'SCALSCP',scalscp,1.0d0)
191 call reada(weightcard,'CUTOFF',cutoff_corr,7.0d0)
192 call reada(weightcard,'DELT_CORR',delt_corr,0.5d0)
193 if (index(weightcard,'SOFT').gt.0) ipot=6
194 call reada(weightcard,"D0CM",d0cm,3.78d0)
195 call reada(weightcard,"AKCM",akcm,15.1d0)
196 call reada(weightcard,"AKTH",akth,11.0d0)
197 call reada(weightcard,"AKCT",akct,12.0d0)
198 call reada(weightcard,"V1SS",v1ss,-1.08d0)
199 call reada(weightcard,"V2SS",v2ss,7.61d0)
200 call reada(weightcard,"V3SS",v3ss,13.7d0)
201 call reada(weightcard,"EBR",ebr,-5.50D0)
202 call reada(weightcard,'WSHIELD',wshield,1.0d0)
203 write(iout,*) 'WSHIELD',wshield
204 call reada(weightcard,'WLT',wliptran,0.0D0)
205 call reada(weightcard,"ATRISS",atriss,0.301D0)
206 call reada(weightcard,"BTRISS",btriss,0.021D0)
207 call reada(weightcard,"CTRISS",ctriss,1.001D0)
208 call reada(weightcard,"DTRISS",dtriss,1.001D0)
209 write (iout,*) "ATRISS=", atriss
210 write (iout,*) "BTRISS=", btriss
211 write (iout,*) "CTRISS=", ctriss
212 write (iout,*) "DTRISS=", dtriss
213 dyn_ss=(index(weightcard,'DYN_SS').gt.0)
215 dyn_ss_mask(i)=.false.
219 dyn_ssbond_ij(i,j)=1.0d300
222 call reada(weightcard,"HT",Ht,0.0D0)
224 ss_depth=ebr/wsc-0.25*eps(1,1)
225 Ht=Ht/wsc-0.25*eps(1,1)
226 akcm=akcm*wstrain/wsc
227 akth=akth*wstrain/wsc
228 akct=akct*wstrain/wsc
229 v1ss=v1ss*wstrain/wsc
230 v2ss=v2ss*wstrain/wsc
231 v3ss=v3ss*wstrain/wsc
233 ss_depth=ebr/wstrain-0.25*eps(1,1)*wsc/wstrain
235 write (iout,'(/a)') "Disulfide bridge parameters:"
236 write (iout,'(a,f10.2)') 'S-S bridge energy: ',ebr
237 write (iout,'(2(a,f10.2))') 'd0cm:',d0cm,' akcm:',akcm
238 write (iout,'(2(a,f10.2))') 'akth:',akth,' akct:',akct
239 write (iout,'(3(a,f10.2))') 'v1ss:',v1ss,' v2ss:',v2ss,
242 C 12/1/95 Added weight for the multi-body term WCORR
243 call reada(weightcard,'WCORRH',wcorr,1.0D0)
244 if (wcorr4.gt.0.0d0) wcorr=wcorr4
264 write (iout,10) wsc,wscp,welec,wvdwpp,wbond,wang,wscloc,wtor,
265 & wtor_d,wstrain,wel_loc,wcorr,wcorr5,wcorr6,wturn3,
266 & wturn4,wturn6,wsccor
267 10 format (/'Energy-term weights (unscaled):'//
268 & 'WSCC= ',f10.6,' (SC-SC)'/
269 & 'WSCP= ',f10.6,' (SC-p)'/
270 & 'WELEC= ',f10.6,' (p-p electr)'/
271 & 'WVDWPP= ',f10.6,' (p-p VDW)'/
272 & 'WBOND= ',f10.6,' (stretching)'/
273 & 'WANG= ',f10.6,' (bending)'/
274 & 'WSCLOC= ',f10.6,' (SC local)'/
275 & 'WTOR= ',f10.6,' (torsional)'/
276 & 'WTORD= ',f10.6,' (double torsional)'/
277 & 'WSTRAIN=',f10.6,' (SS bridges & dist. cnstr.)'/
278 & 'WEL_LOC=',f10.6,' (multi-body 3-rd order)'/
279 & 'WCORR4= ',f10.6,' (multi-body 4th order)'/
280 & 'WCORR5= ',f10.6,' (multi-body 5th order)'/
281 & 'WCORR6= ',f10.6,' (multi-body 6th order)'/
282 & 'WTURN3= ',f10.6,' (turns, 3rd order)'/
283 & 'WTURN4= ',f10.6,' (turns, 4th order)'/
284 & 'WTURN6= ',f10.6,' (turns, 6th order)'/
285 & 'WSCCOR= ',f10.6,' (SC-backbone torsinal correalations)')
287 if (wcorr4.gt.0.0d0) then
288 write (iout,'(/2a/)') 'Local-electrostatic type correlation ',
289 & 'between contact pairs of peptide groups'
290 write (iout,'(2(a,f5.3/))')
291 & 'Cutoff on 4-6th order correlation terms: ',cutoff_corr,
292 & 'Range of quenching the correlation terms:',2*delt_corr
293 else if (wcorr.gt.0.0d0) then
294 write (iout,'(/2a/)') 'Hydrogen-bonding correlation ',
295 & 'between contact pairs of peptide groups'
297 write (iout,'(a,f8.3)')
298 & 'Scaling factor of 1,4 SC-p interactions:',scal14
299 write (iout,'(a,f8.3)')
300 & 'General scaling factor of SC-p interactions:',scalscp
301 r0_corr=cutoff_corr-delt_corr
303 aad(i,1)=scalscp*aad(i,1)
304 aad(i,2)=scalscp*aad(i,2)
305 bad(i,1)=scalscp*bad(i,1)
306 bad(i,2)=scalscp*bad(i,2)
310 print *,'indpdb=',indpdb,' pdbref=',pdbref
312 C Read sequence if not taken from the pdb file.
313 if (iscode.gt.0) then
314 read (inp,'(80a1)') (sequence(i)(1:1),i=1,nres)
316 read (inp,'(20(1x,a3))') (sequence(i),i=1,nres)
318 C Convert sequence to numeric code
320 itype(i)=rescode(i,sequence(i),iscode)
323 print '(20i4)',(itype(i),i=1,nres)
327 if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) then
329 if (itype(i).eq.ntyp1) then
333 else if (iabs(itype(i+1)).ne.20) then
335 else if (iabs(itype(i)).ne.20) then
342 write (iout,*) "ITEL"
344 write (iout,*) i,itype(i),itel(i)
347 print *,'Call Read_Bridge.'
349 C this fragment reads diheadral constrains
350 if (with_dihed_constr) then
352 read (inp,*) ndih_constr
353 if (ndih_constr.gt.0) then
355 C write (iout,*) 'FTORS',ftors
356 C ftors is the force constant for torsional quartic constrains
357 read (inp,*) (idih_constr(i),phi0(i),drange(i),ftors(i),
360 & 'There are',ndih_constr,' constraints on phi angles.'
362 write (iout,'(i5,3f8.3)') idih_constr(i),phi0(i),drange(i),
366 phi0(i)=deg2rad*phi0(i)
367 drange(i)=deg2rad*drange(i)
369 endif ! endif ndif_constr.gt.0
370 endif ! with_dihed_constr
371 if (with_theta_constr) then
372 C with_theta_constr is keyword allowing for occurance of theta constrains
373 read (inp,*) ntheta_constr
374 C ntheta_constr is the number of theta constrains
375 if (ntheta_constr.gt.0) then
377 read (inp,*) (itheta_constr(i),theta_constr0(i),
378 & theta_drange(i),for_thet_constr(i),
380 C the above code reads from 1 to ntheta_constr
381 C itheta_constr(i) residue i for which is theta_constr
382 C theta_constr0 the global minimum value
383 C theta_drange is range for which there is no energy penalty
384 C for_thet_constr is the force constant for quartic energy penalty
386 C if(me.eq.king.or..not.out1file)then
388 & 'There are',ntheta_constr,' constraints on phi angles.'
390 write (iout,'(i5,3f8.3)') itheta_constr(i),theta_constr0(i),
396 theta_constr0(i)=deg2rad*theta_constr0(i)
397 theta_drange(i)=deg2rad*theta_drange(i)
399 C if(me.eq.king.or..not.out1file)
400 C & write (iout,*) 'FTORS',ftors
401 C do i=1,ntheta_constr
402 C ii = itheta_constr(i)
403 C thetabound(1,ii) = phi0(i)-drange(i)
404 C thetabound(2,ii) = phi0(i)+drange(i)
406 endif ! ntheta_constr.gt.0
407 endif! with_theta_constr
411 print *,'NNT=',NNT,' NCT=',NCT
412 if (itype(1).eq.ntyp1) nnt=2
413 if (itype(nres).eq.ntyp1) nct=nct-1
414 if (nstart.lt.nnt) nstart=nnt
415 if (nend.gt.nct .or. nend.eq.0) nend=nct
416 write (iout,*) "nstart",nstart," nend",nend
418 if (constr_homology.gt.0) then
419 call read_constr_homology(print_homology_restraints)
423 c read(inp,'(a)') pdbfile
424 c write (iout,'(2a)') 'PDB data will be read from file ',pdbfile
425 c open(ipdbin,file=pdbfile,status='old',err=33)
427 c 33 write (iout,'(a)') 'Error opening PDB file.'
430 c print *,'Begin reading pdb data'
432 c print *,'Finished reading pdb data'
433 c write (iout,'(a,i3,a,i3)')'nsup=',nsup,' nstart_sup=',nstart_sup
435 c itype_pdb(i)=itype(i)
438 c write (iout,'(a,i3)') 'nsup=',nsup
440 c if (nsup.le.(nct-nnt+1)) then
441 c do i=0,nct-nnt+1-nsup
442 c if (seq_comp(itype(nnt+i),itype_pdb(nstart_sup),nsup)) then
448 c & 'Error - sequences to be superposed do not match.'
451 c do i=0,nsup-(nct-nnt+1)
452 c if (seq_comp(itype(nnt),itype_pdb(nstart_sup+i),nct-nnt+1))
454 c nstart_sup=nstart_sup+i
460 c & 'Error - sequences to be superposed do not match.'
463 c write (iout,*) 'nsup=',nsup,' nstart_sup=',nstart_sup,
464 c & ' nstart_seq=',nstart_seq
468 write (iout,*) "molread: REFSTR",refstr
470 if (.not.pdbref) then
471 call read_angles(inp,*38)
473 38 write (iout,'(a)') 'Error reading reference structure.'
475 call mp_stopall(Error_Msg)
477 stop 'Error reading reference structure'
490 call contact(.true.,ncont_ref,icont_ref)
493 C write (iout,'(/a,i3,a)')
494 C & 'The chain contains',ns,' disulfide-bridging cysteines.'
495 write (iout,'(20i4)') (iss(i),i=1,ns)
497 write(iout,*)"Running with dynamic disulfide-bond formation"
499 write (iout,'(/a/)') 'Pre-formed links are:'
505 write (iout,'(2a,i3,3a,i3,a,3f10.3)')
506 & restyp(it1),'(',i1,') -- ',restyp(it2),'(',i2,')',dhpb(i),
512 if (ns.gt.0.and.dyn_ss) then
516 forcon(i-nss)=forcon(i)
523 dyn_ss_mask(iss(i))=.true.
526 c Read distance restraints
527 if (constr_dist.gt.0) then
528 call read_dist_constr
533 c-----------------------------------------------------------------------------
534 logical function seq_comp(itypea,itypeb,length)
536 integer length,itypea(length),itypeb(length)
539 if (itypea(i).ne.itypeb(i)) then
547 c-----------------------------------------------------------------------------
548 subroutine read_bridge
549 C Read information about disulfide bridges.
552 include 'COMMON.IOUNITS'
555 include 'COMMON.INTERACT'
556 include 'COMMON.LOCAL'
557 include 'COMMON.NAMES'
558 include 'COMMON.CHAIN'
559 include 'COMMON.FFIELD'
560 include 'COMMON.SBRIDGE'
561 include 'COMMON.HEADER'
562 include 'COMMON.CONTROL'
563 include 'COMMON.TIME1'
565 include 'COMMON.INFO'
568 C Read bridging residues.
569 read (inp,*) ns,(iss(i),i=1,ns)
571 C Check whether the specified bridging residues are cystines.
573 if (itype(iss(i)).ne.1) then
574 write (iout,'(2a,i3,a)')
575 & 'Do you REALLY think that the residue ',
576 & restyp(itype(iss(i))),i,
577 & ' can form a disulfide bridge?!!!'
578 write (*,'(2a,i3,a)')
579 & 'Do you REALLY think that the residue ',
580 & restyp(itype(iss(i))),i,
581 & ' can form a disulfide bridge?!!!'
583 call mp_stopall(error_msg)
589 C Read preformed bridges.
591 read (inp,*) nss,(ihpb(i),jhpb(i),i=1,nss)
594 C Check if the residues involved in bridges are in the specified list of
598 if (ihpb(i).eq.ihpb(j).or.ihpb(i).eq.jhpb(j)
599 & .or.jhpb(i).eq.ihpb(j).or.jhpb(i).eq.jhpb(j)) then
600 write (iout,'(a,i3,a)') 'Disulfide pair',i,
601 & ' contains residues present in other pairs.'
602 write (*,'(a,i3,a)') 'Disulfide pair',i,
603 & ' contains residues present in other pairs.'
605 call mp_stopall(error_msg)
612 if (ihpb(i).eq.iss(j)) goto 10
614 write (iout,'(a,i3,a)') 'Pair',i,' contains unknown cystine.'
617 if (jhpb(i).eq.iss(j)) goto 20
619 write (iout,'(a,i3,a)') 'Pair',i,' contains unknown cystine.'
632 c----------------------------------------------------------------------------
633 subroutine read_angles(kanal,*)
638 include 'COMMON.CHAIN'
639 include 'COMMON.IOUNITS'
641 read (kanal,*,err=10,end=10) (theta(i),i=3,nres)
642 read (kanal,*,err=10,end=10) (phi(i),i=4,nres)
643 read (kanal,*,err=10,end=10) (alph(i),i=2,nres-1)
644 read (kanal,*,err=10,end=10) (omeg(i),i=2,nres-1)
646 theta(i)=deg2rad*theta(i)
647 phi(i)=deg2rad*phi(i)
648 alph(i)=deg2rad*alph(i)
649 omeg(i)=deg2rad*omeg(i)
654 c----------------------------------------------------------------------------
655 subroutine reada(rekord,lancuch,wartosc,default)
657 character*(*) rekord,lancuch
658 double precision wartosc,default
661 iread=index(rekord,lancuch)
666 iread=iread+ilen(lancuch)+1
667 read (rekord(iread:),*) wartosc
670 c----------------------------------------------------------------------------
671 subroutine multreada(rekord,lancuch,tablica,dim,default)
674 double precision tablica(dim),default
675 character*(*) rekord,lancuch
681 iread=index(rekord,lancuch)
682 if (iread.eq.0) return
683 iread=iread+ilen(lancuch)+1
684 read (rekord(iread:),*,end=10,err=10) (tablica(i),i=1,dim)
687 c----------------------------------------------------------------------------
688 subroutine readi(rekord,lancuch,wartosc,default)
690 character*(*) rekord,lancuch
691 integer wartosc,default
694 iread=index(rekord,lancuch)
699 iread=iread+ilen(lancuch)+1
700 read (rekord(iread:),*) wartosc
703 C----------------------------------------------------------------------
704 subroutine multreadi(rekord,lancuch,tablica,dim,default)
707 integer tablica(dim),default
708 character*(*) rekord,lancuch
715 iread=index(rekord,lancuch(:ilen(lancuch))//"=")
716 if (iread.eq.0) return
717 iread=iread+ilen(lancuch)+1
718 read (rekord(iread:),*,end=10,err=10) (tablica(i),i=1,dim)
722 c----------------------------------------------------------------------------
723 subroutine card_concat(card)
725 include 'COMMON.IOUNITS'
727 character*80 karta,ucase
729 read (inp,'(a)') karta
732 do while (karta(80:80).eq.'&')
733 card=card(:ilen(card)+1)//karta(:79)
734 read (inp,'(a)') karta
737 card=card(:ilen(card)+1)//karta
740 c----------------------------------------------------------------------------
749 include 'COMMON.IOUNITS'
750 include 'COMMON.CONTROL'
751 integer lenpre,lenpot,ilen
753 character*16 cformat,cprint
755 integer lenint,lenout
756 call getenv('INPUT',prefix)
757 call getenv('OUTPUT',prefout)
758 call getenv('INTIN',prefintin)
759 call getenv('COORD',cformat)
760 call getenv('PRINTCOOR',cprint)
761 call getenv('SCRATCHDIR',scratchdir)
764 if (index(ucase(cformat),'CX').gt.0) then
771 lenint=ilen(prefintin)
772 C Get the names and open the input files
773 open (inp,file=prefix(:ilen(prefix))//'.inp',status='old')
775 write (liczba,'(bz,i3.3)') me
776 outname=prefout(:lenout)//'_clust.out_'//liczba
778 outname=prefout(:lenout)//'_clust.out'
781 intinname=prefintin(:lenint)//'.bx'
782 else if (from_cx) then
783 intinname=prefintin(:lenint)//'.cx'
785 intinname=prefintin(:lenint)//'.int'
787 rmsname=prefintin(:lenint)//'.rms'
788 open (jplot,file=prefout(:ilen(prefout))//'.tex',
790 open (jrms,file=rmsname,status='unknown')
791 open(iout,file=outname,status='unknown')
792 C Get parameter filenames and open the parameter files.
793 call getenv('BONDPAR',bondname)
794 open (ibond,file=bondname,status='old')
795 call getenv('THETPAR',thetname)
796 open (ithep,file=thetname,status='old')
797 call getenv('ROTPAR',rotname)
798 open (irotam,file=rotname,status='old')
799 call getenv('TORPAR',torname)
800 open (itorp,file=torname,status='old')
801 call getenv('TORDPAR',tordname)
802 open (itordp,file=tordname,status='old')
803 call getenv('FOURIER',fouriername)
804 open (ifourier,file=fouriername,status='old')
805 call getenv('ELEPAR',elename)
806 open (ielep,file=elename,status='old')
807 call getenv('SIDEPAR',sidename)
808 open (isidep,file=sidename,status='old')
809 call getenv('SIDEP',sidepname)
810 open (isidep1,file=sidepname,status="old")
811 call getenv('SCCORPAR',sccorname)
812 open (isccor,file=sccorname,status="old")
813 call getenv('LIPTRANPAR',liptranname)
814 open (iliptranpar,file=liptranname,status='old')
817 C 8/9/01 In the newest version SCp interaction constants are read from a file
818 C Use -DOLDSCP to use hard-coded constants instead.
820 call getenv('SCPPAR',scpname)
821 open (iscpp,file=scpname,status='old')
825 subroutine read_dist_constr
826 implicit real*8 (a-h,o-z)
831 include 'COMMON.CONTROL'
832 include 'COMMON.CHAIN'
833 include 'COMMON.IOUNITS'
834 include 'COMMON.SBRIDGE'
835 integer ifrag_(2,100),ipair_(2,100)
836 double precision wfrag_(100),wpair_(100)
837 character*500 controlcard
838 logical lprn /.true./
839 write (iout,*) "Calling read_dist_constr"
840 C write (iout,*) "nres",nres," nstart_sup",nstart_sup," nsup",nsup
842 write(iout,*) "TU sie wywalam?"
843 call card_concat(controlcard)
844 write (iout,*) controlcard
846 call readi(controlcard,"NFRAG",nfrag_,0)
847 call readi(controlcard,"NPAIR",npair_,0)
848 call readi(controlcard,"NDIST",ndist_,0)
849 call reada(controlcard,'DIST_CUT',dist_cut,5.0d0)
850 call multreadi(controlcard,"IFRAG",ifrag_(1,1),2*nfrag_,0)
851 call multreadi(controlcard,"IPAIR",ipair_(1,1),2*npair_,0)
852 call multreada(controlcard,"WFRAG",wfrag_(1),nfrag_,0.0d0)
853 call multreada(controlcard,"WPAIR",wpair_(1),npair_,0.0d0)
854 write (iout,*) "NFRAG",nfrag_," NPAIR",npair_," NDIST",ndist_
855 write (iout,*) "IFRAG"
857 write (iout,*) i,ifrag_(1,i),ifrag_(2,i),wfrag_(i)
859 write (iout,*) "IPAIR"
861 write (iout,*) i,ipair_(1,i),ipair_(2,i),wpair_(i)
865 if (ifrag_(1,i).lt.nstart_sup) ifrag_(1,i)=nstart_sup
866 if (ifrag_(2,i).gt.nstart_sup+nsup-1)
867 & ifrag_(2,i)=nstart_sup+nsup-1
868 c write (iout,*) i,ifrag_(1,i),ifrag_(2,i),wfrag_(i)
870 if (wfrag_(i).gt.0.0d0) then
871 do j=ifrag_(1,i),ifrag_(2,i)-1
873 write (iout,*) "j",j," k",k
875 if (constr_dist.eq.1) then
880 forcon(nhpb)=wfrag_(i)
881 else if (constr_dist.eq.2) then
882 if (ddjk.le.dist_cut) then
887 forcon(nhpb)=wfrag_(i)
894 forcon(nhpb)=wfrag_(i)*dexp(-0.5d0*(ddjk/dist_cut)**2)
897 & write (iout,'(a,3i5,f8.2,1pe12.2)') "+dist.constr ",
898 & nhpb,ihpb(nhpb),jhpb(nhpb),dhpb(nhpb),forcon(nhpb)
904 if (wpair_(i).gt.0.0d0) then
912 do j=ifrag_(1,ii),ifrag_(2,ii)
913 do k=ifrag_(1,jj),ifrag_(2,jj)
917 forcon(nhpb)=wpair_(i)
919 write (iout,'(a,3i5,f8.2,f10.1)') "+dist.constr ",
920 & nhpb,ihpb(nhpb),jhpb(nhpb),dhpb(nhpb),forcon(nhpb)
926 if (constr_dist.eq.11) then
927 read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),dhpb(i),dhpb1(i),
928 & ibecarb(i),forcon(nhpb+1),fordepth(nhpb+1)
929 fordepth(nhpb+1)=fordepth(nhpb+1)/forcon(nhpb+1)
930 C write (iout,'(a,3i5,f8.2,f10.1)') "+dist.constr ",
931 C & nhpb,ihpb(nhpb),jhpb(nhpb),dhpb(nhpb),forcon(nhpb)
933 read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),forcon(nhpb+1)
935 if (forcon(nhpb+1).gt.0.0d0) then
937 if (ibecarb(i).gt.0) then
941 if (dhpb(nhpb).eq.0.0d0)
942 & dhpb(nhpb)=dist(ihpb(nhpb),jhpb(nhpb))
943 C dhpb(nhpb)=dist(ihpb(nhpb),jhpb(nhpb))
944 write (iout,'(a,3i5,f8.2,f10.1)') "+dist.constr ",
945 & nhpb,ihpb(nhpb),jhpb(nhpb),dhpb(nhpb),forcon(nhpb)
958 c====-------------------------------------------------------------------
959 subroutine read_constr_homology(lprn)
965 include 'COMMON.SETUP'
966 include 'COMMON.CONTROL'
967 include 'COMMON.CHAIN'
968 include 'COMMON.IOUNITS'
970 include 'COMMON.INTERACT'
971 include 'COMMON.NAMES'
972 include 'COMMON.HOMRESTR'
977 c include 'include_unres/COMMON.VAR'
980 c double precision odl_temp,sigma_odl_temp,waga_theta,waga_d,
982 c common /przechowalnia/ odl_temp(maxres,maxres,max_template),
983 c & sigma_odl_temp(maxres,maxres,max_template)
985 character*24 model_ki_dist, model_ki_angle
986 character*500 controlcard
987 integer ki, i, j, k, l, ii_in_use(maxdim),i_tmp,idomain_tmp
988 integer idomain(max_template,maxres)
992 logical unres_pdb,liiflag
994 c FP - Nov. 2014 Temporary specifications for new vars
996 double precision rescore_tmp,x12,y12,z12,rescore2_tmp,
998 double precision, dimension (max_template,maxres) :: rescore
999 double precision, dimension (max_template,maxres) :: rescore2
1000 double precision, dimension (max_template,maxres) :: rescore3
1001 character*24 tpl_k_rescore
1002 c -----------------------------------------------------------------
1003 c Reading multiple PDB ref structures and calculation of retraints
1004 c not using pre-computed ones stored in files model_ki_{dist,angle}
1006 c -----------------------------------------------------------------
1009 c Alternative: reading from input
1011 write (iout,*) "BEGIN READ HOMOLOGY INFO"
1018 call card_concat(controlcard)
1019 call reada(controlcard,"HOMOL_DIST",waga_dist,1.0d0)
1020 call reada(controlcard,"HOMOL_ANGLE",waga_angle,1.0d0)
1021 call reada(controlcard,"HOMOL_THETA",waga_theta,1.0d0) ! new
1022 call reada(controlcard,"HOMOL_SCD",waga_d,1.0d0) ! new
1023 call reada(controlcard,'DIST_CUT',dist_cut,5.0d0) ! for diff ways of calc sigma
1024 call reada(controlcard,'DIST2_CUT',dist2_cut,9999.0d0)
1025 call readi(controlcard,"HOMOL_NSET",homol_nset,1)
1026 read2sigma=(index(controlcard,'READ2SIGMA').gt.0)
1027 if (homol_nset.gt.1)then
1028 call readi(controlcard,"ISET",iset,1)
1029 call card_concat(controlcard)
1030 read(controlcard,*) (waga_homology(i),i=1,homol_nset)
1033 waga_homology(1)=1.0
1037 write(iout,*) "read_constr_homology iset",iset
1038 write(iout,*) "waga_homology(",iset,")",waga_homology(iset)
1045 cd write (iout,*) "nnt",nnt," nct",nct
1055 c Reading HM global scores (prob not required)
1058 do k=1,constr_homology
1062 c open (4,file="HMscore")
1063 c do k=1,constr_homology
1064 c read (4,*,end=521) hmscore_tmp
1065 c hmscore(k)=hmscore_tmp ! Another transformation can be used
1066 c write(*,*) "Model", k, ":", hmscore(k)
1077 c write(iout,*) "waga_theta",waga_theta,"waga_d",waga_d
1079 write (iout,*) "CONSTR_HOMOLOGY",constr_homology
1080 do k=1,constr_homology
1082 read(inp,'(a)') pdbfile
1083 c write (iout,*) "k ",k," pdbfile ",pdbfile
1084 c Next stament causes error upon compilation (?)
1085 c if(me.eq.king.or. .not. out1file)
1086 c write (iout,'(2a)') 'PDB data will be read from file ',
1087 c & pdbfile(:ilen(pdbfile))
1088 write (iout,'(a,5x,a)') 'HOMOL: Opening PDB file',
1089 & pdbfile(:ilen(pdbfile))
1090 open(ipdbin,file=pdbfile,status='old',err=33)
1092 33 write (iout,'(a,5x,a)') 'Error opening PDB file',
1093 & pdbfile(:ilen(pdbfile))
1096 c print *,'Begin reading pdb data'
1098 c Files containing res sim or local scores (former containing sigmas)
1101 write(kic2,'(bz,i2.2)') k
1103 tpl_k_rescore="template"//kic2//".sco"
1106 call readpdb_template(k)
1109 crefjlee(j,i)=c(j,i)
1114 write (iout,'(i5,3f8.3,5x,3f8.3)') i,(crefjlee(j,i),j=1,3),
1115 & (crefjlee(j,i+nres),j=1,3)
1117 write (iout,*) "READ HOMOLOGY INFO"
1118 write (iout,*) "read_constr_homology x: after reading pdb file"
1119 write (iout,*) "waga_homology(",iset,")",waga_homology(iset)
1120 write (iout,*) "waga_dist",waga_dist
1121 write (iout,*) "waga_angle",waga_angle
1122 write (iout,*) "waga_theta",waga_theta
1123 write (iout,*) "waga_d",waga_d
1124 write (iout,*) "dist_cut",dist_cut
1133 c Distance restraints
1136 C Copy the coordinates from reference coordinates (?)
1140 c write (iout,*) "c(",j,i,") =",c(j,i)
1144 c From read_dist_constr (commented out 25/11/2014 <-> res sim)
1146 c write(iout,*) "tpl_k_rescore - ",tpl_k_rescore
1147 open (ientin,file=tpl_k_rescore,status='old')
1148 if (nnt.gt.1) rescore(k,1)=0.0d0
1149 do irec=nnt,nct ! loop for reading res sim
1150 if (read2sigma) then
1151 read (ientin,*,end=1401) i_tmp,rescore2_tmp,rescore_tmp,
1152 & rescore3_tmp,idomain_tmp
1154 idomain(k,i_tmp)=idomain_tmp
1155 rescore(k,i_tmp)=rescore_tmp
1156 rescore2(k,i_tmp)=rescore2_tmp
1157 rescore3(k,i_tmp)=rescore3_tmp
1158 write(iout,'(a7,i5,3f10.5,i5)') "rescore",
1159 & i_tmp,rescore2_tmp,rescore_tmp,
1160 & rescore3_tmp,idomain_tmp
1163 read (ientin,*,end=1401) rescore_tmp
1165 c rescore(k,irec)=rescore_tmp+1.0d0 ! to avoid 0 values
1166 rescore(k,irec)=0.5d0*(rescore_tmp+0.5d0) ! alt transf to reduce scores
1167 c write(iout,*) "rescore(",k,irec,") =",rescore(k,irec)
1172 if (waga_dist.ne.0.0d0) then
1180 distal=dsqrt(x12*x12+y12*y12+z12*z12)
1181 c write (iout,*) k,i,j,distal,dist2_cut
1183 if (idomain(k,i).eq.idomain(k,j).and.idomain(k,i).ne.0
1184 & .and. distal.le.dist2_cut ) then
1190 c write (iout,*) "k",k
1191 c write (iout,*) "i",i," j",j," constr_homology",
1196 if (read2sigma) then
1199 sigma_odl(k,ii)=sigma_odl(k,ii)+rescore2(k,ik)
1201 sigma_odl(k,ii)=sigma_odl(k,ii)/(j-i+1)
1202 if (odl(k,ii).gt.dist_cut) sigma_odl(k,ii) =
1203 & sigma_odl(k,ii)*dexp(0.5d0*(odl(k,ii)/dist_cut)**2-0.5d0)
1205 if (odl(k,ii).le.dist_cut) then
1206 sigma_odl(k,ii)=rescore(k,i)+rescore(k,j)
1209 sigma_odl(k,ii)=(rescore(k,i)+rescore(k,j))*
1210 & dexp(0.5d0*(odl(k,ii)/dist_cut)**2)
1212 sigma_odl(k,ii)=(rescore(k,i)+rescore(k,j))*
1213 & dexp(0.5d0*(odl(k,ii)/dist_cut)**2-0.5d0)
1217 sigma_odl(k,ii)=1.0d0/(sigma_odl(k,ii)*sigma_odl(k,ii))
1220 l_homo(k,ii)=.false.
1227 c Theta, dihedral and SC retraints
1229 if (waga_angle.gt.0.0d0) then
1230 c open (ientin,file=tpl_k_sigma_dih,status='old')
1231 c do irec=1,maxres-3 ! loop for reading sigma_dih
1232 c read (ientin,*,end=1402) i,j,ki,l,sigma_dih(k,i+nnt-1) ! j,ki,l what for?
1233 c if (i+nnt-1.gt.lim_dih) lim_dih=i+nnt-1 ! right?
1234 c sigma_dih(k,i+nnt-1)=sigma_dih(k,i+nnt-1)* ! not inverse because of use of res. similarity
1235 c & sigma_dih(k,i+nnt-1)
1240 if (idomain(k,i).eq.0) then
1244 dih(k,i)=phiref(i) ! right?
1245 c read (ientin,*) sigma_dih(k,i) ! original variant
1246 c write (iout,*) "dih(",k,i,") =",dih(k,i)
1247 c write(iout,*) "rescore(",k,i,") =",rescore(k,i),
1248 c & "rescore(",k,i-1,") =",rescore(k,i-1),
1249 c & "rescore(",k,i-2,") =",rescore(k,i-2),
1250 c & "rescore(",k,i-3,") =",rescore(k,i-3)
1252 sigma_dih(k,i)=(rescore(k,i)+rescore(k,i-1)+
1253 & rescore(k,i-2)+rescore(k,i-3))/4.0
1254 c if (read2sigma) sigma_dih(k,i)=sigma_dih(k,i)/4.0
1255 c write (iout,*) "Raw sigmas for dihedral angle restraints"
1256 c write (iout,'(i5,10(2f8.2,4x))') i,sigma_dih(k,i)
1257 c sigma_dih(k,i)=hmscore(k)*rescore(k,i)*rescore(k,i-1)*
1258 c rescore(k,i-2)*rescore(k,i-3) ! right expression ?
1259 c Instead of res sim other local measure of b/b str reliability possible
1260 if (sigma_dih(k,i).ne.0)
1261 & sigma_dih(k,i)=1.0d0/(sigma_dih(k,i)*sigma_dih(k,i))
1262 c sigma_dih(k,i)=sigma_dih(k,i)*sigma_dih(k,i)
1267 if (waga_theta.gt.0.0d0) then
1268 c open (ientin,file=tpl_k_sigma_theta,status='old')
1269 c do irec=1,maxres-2 ! loop for reading sigma_theta, right bounds?
1270 c read (ientin,*,end=1403) i,j,ki,sigma_theta(k,i+nnt-1) ! j,ki what for?
1271 c sigma_theta(k,i+nnt-1)=sigma_theta(k,i+nnt-1)* ! not inverse because of use of res. similarity
1272 c & sigma_theta(k,i+nnt-1)
1277 do i = nnt+2,nct ! right? without parallel.
1278 c do i = i=1,nres ! alternative for bounds acc to readpdb?
1279 c do i=ithet_start,ithet_end ! with FG parallel.
1280 if (idomain(k,i).eq.0) then
1281 sigma_theta(k,i)=0.0
1284 thetatpl(k,i)=thetaref(i)
1285 c write (iout,*) "thetatpl(",k,i,") =",thetatpl(k,i)
1286 c write(iout,*) "rescore(",k,i,") =",rescore(k,i),
1287 c & "rescore(",k,i-1,") =",rescore(k,i-1),
1288 c & "rescore(",k,i-2,") =",rescore(k,i-2)
1289 c read (ientin,*) sigma_theta(k,i) ! 1st variant
1290 sigma_theta(k,i)=(rescore(k,i)+rescore(k,i-1)+
1291 & rescore(k,i-2))/3.0
1292 c if (read2sigma) sigma_theta(k,i)=sigma_theta(k,i)/3.0
1293 if (sigma_theta(k,i).ne.0)
1294 & sigma_theta(k,i)=1.0d0/(sigma_theta(k,i)*sigma_theta(k,i))
1296 c sigma_theta(k,i)=hmscore(k)*rescore(k,i)*rescore(k,i-1)*
1297 c rescore(k,i-2) ! right expression ?
1298 c sigma_theta(k,i)=sigma_theta(k,i)*sigma_theta(k,i)
1302 if (waga_d.gt.0.0d0) then
1303 c open (ientin,file=tpl_k_sigma_d,status='old')
1304 c do irec=1,maxres-1 ! loop for reading sigma_theta, right bounds?
1305 c read (ientin,*,end=1404) i,j,sigma_d(k,i+nnt-1) ! j,ki what for?
1306 c sigma_d(k,i+nnt-1)=sigma_d(k,i+nnt-1)* ! not inverse because of use of res. similarity
1307 c & sigma_d(k,i+nnt-1)
1311 do i = nnt,nct ! right? without parallel.
1312 c do i=2,nres-1 ! alternative for bounds acc to readpdb?
1313 c do i=loc_start,loc_end ! with FG parallel.
1314 if (itype(i).eq.10) cycle
1315 if (idomain(k,i).eq.0 ) then
1322 c write (iout,*) "xxtpl(",k,i,") =",xxtpl(k,i)
1323 c write (iout,*) "yytpl(",k,i,") =",yytpl(k,i)
1324 c write (iout,*) "zztpl(",k,i,") =",zztpl(k,i)
1325 c write(iout,*) "rescore(",k,i,") =",rescore(k,i)
1326 sigma_d(k,i)=rescore3(k,i) ! right expression ?
1327 if (sigma_d(k,i).ne.0)
1328 & sigma_d(k,i)=1.0d0/(sigma_d(k,i)*sigma_d(k,i))
1330 c sigma_d(k,i)=hmscore(k)*rescore(k,i) ! right expression ?
1331 c sigma_d(k,i)=sigma_d(k,i)*sigma_d(k,i)
1332 c read (ientin,*) sigma_d(k,i) ! 1st variant
1337 c remove distance restraints not used in any model from the list
1338 c shift data in all arrays
1340 if (waga_dist.ne.0.0d0) then
1346 if (ii_in_use(ii).eq.0.and.liiflag) then
1350 if (ii_in_use(ii).ne.0.and..not.liiflag.or.
1351 & .not.liiflag.and.ii.eq.lim_odl) then
1352 if (ii.eq.lim_odl) then
1353 iishift=ii-iistart+1
1358 do ki=iistart,lim_odl-iishift
1359 ires_homo(ki)=ires_homo(ki+iishift)
1360 jres_homo(ki)=jres_homo(ki+iishift)
1361 ii_in_use(ki)=ii_in_use(ki+iishift)
1362 do k=1,constr_homology
1363 odl(k,ki)=odl(k,ki+iishift)
1364 sigma_odl(k,ki)=sigma_odl(k,ki+iishift)
1365 l_homo(k,ki)=l_homo(k,ki+iishift)
1369 lim_odl=lim_odl-iishift
1374 if (constr_homology.gt.0) call homology_partition
1375 if (constr_homology.gt.0) call init_int_table
1376 cd write (iout,*) "homology_partition: lim_theta= ",lim_theta,
1377 cd & "lim_xx=",lim_xx
1378 c write (iout,*) "ithet_start =",ithet_start,"ithet_end =",ithet_end
1379 c write (iout,*) "loc_start =",loc_start,"loc_end =",loc_end
1383 if (.not.lprn) return
1384 cd write(iout,*) "waga_theta",waga_theta,"waga_d",waga_d
1385 if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0) then
1386 write (iout,*) "Distance restraints from templates"
1388 write(iout,'(3i5,100(2f8.2,1x,l1,4x))')
1389 & ii,ires_homo(ii),jres_homo(ii),
1390 & (odl(ki,ii),1.0d0/dsqrt(sigma_odl(ki,ii)),l_homo(ki,ii),
1391 & ki=1,constr_homology)
1393 write (iout,*) "Dihedral angle restraints from templates"
1395 write (iout,'(i5,a4,100(2f8.2,4x))') i,restyp(itype(i)),
1396 & (rad2deg*dih(ki,i),
1397 & rad2deg/dsqrt(sigma_dih(ki,i)),ki=1,constr_homology)
1399 write (iout,*) "Virtual-bond angle restraints from templates"
1401 write (iout,'(i5,a4,100(2f8.2,4x))') i,restyp(itype(i)),
1402 & (rad2deg*thetatpl(ki,i),
1403 & rad2deg/dsqrt(sigma_theta(ki,i)),ki=1,constr_homology)
1405 write (iout,*) "SC restraints from templates"
1407 write(iout,'(i5,100(4f8.2,4x))') i,
1408 & (xxtpl(ki,i),yytpl(ki,i),zztpl(ki,i),
1409 & 1.0d0/dsqrt(sigma_d(ki,i)),ki=1,constr_homology)
1412 c -----------------------------------------------------------------