2 C Read the PDB file and convert the peptide geometry into virtual-chain
6 include 'DIMENSIONS.ZSCOPT'
7 include 'COMMON.CONTROL'
10 include 'COMMON.CHAIN'
11 include 'COMMON.INTERACT'
12 include 'COMMON.IOUNITS'
14 include 'COMMON.NAMES'
15 character*3 seq,atom,res
17 double precision sccor(3,20)
18 integer i,j,iii,ibeg,ishift,ishift1,ity,ires,ires_old
20 integer rescode,kkk,lll,icha,cou,kupa,iprzes
24 read (ipdbin,'(a80)',end=10) card
25 if (card(:3).eq.'END') then
27 else if (card(:3).eq.'TER') then
31 itype(ires_old-1)=ntyp1
34 c write (iout,*) "Chain ended",ires,ishift,ires_old
35 call sccenter(ires,iii,sccor)
37 C Fish out the ATOM cards.
38 if (index(card(1:4),'ATOM').gt.0) then
39 read (card(14:16),'(a3)') atom
40 if (atom.eq.'CA' .or. atom.eq.'CH3') then
41 C Calculate the CM of the preceding residue.
43 call sccenter(ires,iii,sccor)
46 c write (iout,'(a80)') card
47 read (card(24:26),*) ires
48 read (card(18:20),'(a3)') res
51 if (res.ne.'GLY' .and. res.ne. 'ACE') then
55 c write (iout,*) "ires",ires," ibeg",ibeg," ishift",ishift
57 else if (ibeg.eq.2) then
59 ishift=-ires_old+ires-1
60 c write (iout,*) "New chain started",ires,ishift
64 c write (2,*) "ires",ires," ishift",ishift
65 if (res.eq.'ACE') then
68 itype(ires)=rescode(ires,res,0)
70 read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
71 write (iout,'(2i3,2x,a,3f8.3)')
72 & ires,itype(ires),res,(c(j,ires),j=1,3)
75 sccor(j,iii)=c(j,ires)
77 else if (atom.ne.'O '.and.atom(1:1).ne.'H' .and.
78 & atom.ne.'N ' .and. atom.ne.'C ') then
80 read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
84 10 write (iout,'(a,i5)') ' Nres: ',ires
85 C Calculate dummy residue coordinates inside the "chain" of a multichain
89 c write (iout,*) i,itype(i)
91 if (itype(i).eq.ntyp1) then
92 if (itype(i+1).eq.ntyp1) then
93 C 16/01/2014 by Adasko: Adding to dummy atoms in the chain
94 C first is connected prevous chain (itype(i+1).eq.ntyp1)=true
95 C second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
97 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
98 C call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
105 C c(j,i)=c(j,i-1)-1.9d0*e2(j)
109 dcj=(c(j,i-2)-c(j,i-3))/2.0
114 else !itype(i+1).eq.ntyp1
115 C if (unres_pdb) then
116 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
117 C call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
124 C c(j,i)=c(j,i+1)-1.9d0*e2(j)
128 dcj=(c(j,i+3)-c(j,i+2))/2.0
133 endif !itype(i+1).eq.ntyp1
134 endif !itype.eq.ntyp1
136 C Calculate the CM of the last side chain.
137 call sccenter(ires,iii,sccor)
140 if (itype(nres).ne.10) then
144 dcj=(c(j,nres-2)-c(j,nres-3))/2.0
145 c(j,nres)=c(j,nres-1)+dcj
146 c(j,2*nres)=c(j,nres)
156 c(j,2*nres)=c(j,nres)
158 if (itype(1).eq.ntyp1) then
162 dcj=(c(j,4)-c(j,3))/2.0
167 C Calculate internal coordinates.
169 write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)')
170 & ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
171 & (c(j,nres+ires),j=1,3)
173 call int_from_cart(.true.,.false.)
174 write (iout,*) "After int_from_cart"
178 dc(j,i)=c(j,i+1)-c(j,i)
179 dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
184 dc(j,i+nres)=c(j,i+nres)-c(j,i)
185 dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
187 c write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
191 C Copy the coordinates to reference coordinates
197 C Splits to single chain if occurs
203 cc write (iout,*) "spraw lancuchy",(c(j,i),j=1,3)
205 if ((itype(i-1).eq.ntyp1).and.(i.gt.2).and.(i.ne.nres)) then
208 c write (iout,*) "spraw lancuchy",(c(j,i),j=1,3)
214 cref(j,i+nres,cou)=c(j,i+nres)
216 chain_rep(j,lll,kkk)=c(j,i)
217 chain_rep(j,lll+nres,kkk)=c(j,i+nres)
221 if (chain_length.eq.0) chain_length=nres
222 write (iout,*) chain_length
224 chain_rep(j,chain_length,symetr)=chain_rep(j,chain_length,1)
225 chain_rep(j,chain_length+nres,symetr)
226 &=chain_rep(j,chain_length+nres,1)
231 c write (iout,*) "spraw lancuchy",chain_length,symetr
233 c do kkk=1,chain_length
234 c write (iout,*) itype(kkk),(chain_rep(j,kkk,i), j=1,3)
238 C makes copy of chains
239 c write (iout,*) "symetr", symetr
241 if (symetr.gt.1) then
248 c write(iout,*) "tabperm", (tabperm(i,kkk),kkk=1,4)
254 c write (iout,*) i,icha
255 do lll=1,chain_length
257 if (cou.le.nres) then
259 kupa=mod(lll,chain_length)
260 iprzes=(kkk-1)*chain_length+lll
261 if (kupa.eq.0) kupa=chain_length
262 c write (iout,*) "kupa", kupa
263 cref(j,iprzes,i)=chain_rep(j,kupa,icha)
264 cref(j,iprzes+nres,i)=chain_rep(j,kupa+nres,icha)
271 C-koniec robienia kopidm
273 write (iout,*) "nowa struktura", nperm
275 write (iout,110) restyp(itype(i)),i,cref(1,i,kkk),
277 &cref(3,i,kkk),cref(1,nres+i,kkk),
278 &cref(2,nres+i,kkk),cref(3,nres+i,kkk)
280 100 format (//' alpha-carbon coordinates ',
281 & ' centroid coordinates'/
282 1 ' ', 6X,'X',11X,'Y',11X,'Z',
283 & 10X,'X',11X,'Y',11X,'Z')
284 110 format (a,'(',i3,')',6f12.5)
291 c---------------------------------------------------------------------------
292 subroutine int_from_cart(lside,lprn)
295 include 'DIMENSIONS.ZSCOPT'
296 include 'COMMON.LOCAL'
298 include 'COMMON.CHAIN'
299 include 'COMMON.INTERACT'
300 include 'COMMON.IOUNITS'
302 include 'COMMON.NAMES'
303 character*3 seq,atom,res
305 double precision sccor(3,20)
307 double precision dist,alpha,beta,di
312 & 'Internal coordinates calculated from crystal structure.'
314 write (iout,'(8a)') ' Res ',' dvb',' Theta',
315 & ' Phi',' Dsc_id',' Dsc',' Alpha',
318 write (iout,'(4a)') ' Res ',' dvb',' Theta',
324 write (iout,*) i,i-1,(c(j,i),j=1,3),(c(j,i-1),j=1,3),dist(i,i-1)
325 if (itype(i-1).ne.ntyp1 .and. itype(i).ne.ntyp1 .and.
326 & (dist(i,i-1).lt.2.0D0 .or. dist(i,i-1).gt.5.0D0)) then
327 write (iout,'(a,i4)') 'Bad Cartesians for residue',i
330 theta(i+1)=alpha(i-1,i,i+1)
331 if (i.gt.2) phi(i+1)=beta(i-2,i-1,i,i+1)
333 if (itype(1).eq.ntyp1) then
335 c(j,1)=c(j,2)+(c(j,3)-c(j,4))
338 if (itype(nres).eq.ntyp1) then
340 c(j,nres)=c(j,nres-1)+(c(j,nres-2)-c(j,nres-3))
346 c(j,maxres2)=0.5D0*(c(j,i-1)+c(j,i+1))
351 alph(i)=alpha(nres+i,i,maxres2)
352 omeg(i)=beta(nres+i,i,maxres2,i+1)
355 & write (iout,'(a3,i4,7f10.3)') restyp(iti),i,dist(i,i-1),
356 & rad2deg*theta(i),rad2deg*phi(i),dsc(iti),di,
357 & rad2deg*alph(i),rad2deg*omeg(i)
362 write (iout,'(a3,i4,7f10.3)') restyp(iti),i,dist(i,i-1),
363 & rad2deg*theta(i),rad2deg*phi(i)
368 c---------------------------------------------------------------------------
369 subroutine sccenter(ires,nscat,sccor)
372 include 'COMMON.CHAIN'
373 integer ires,nscat,i,j
374 double precision sccor(3,20),sccmj
378 sccmj=sccmj+sccor(j,i)
380 dc(j,ires)=sccmj/nscat