readpdb-mult
[unres.git] / source / unres / src-HCD-5D / readpdb_template.F
1       subroutine readpdb_template(k)
2 C Read the PDB file for read_constr_homology with read2sigma
3 C and convert the peptide geometry into virtual-chain geometry.
4       implicit none
5       include 'DIMENSIONS'
6       include 'COMMON.LOCAL'
7       include 'COMMON.VAR'
8       include 'COMMON.CHAIN'
9       include 'COMMON.INTERACT'
10       include 'COMMON.IOUNITS'
11       include 'COMMON.GEO'
12       include 'COMMON.NAMES'
13       include 'COMMON.CONTROL'
14       include 'COMMON.FRAG'
15       include 'COMMON.SETUP'
16       integer i,j,k,ibeg,ishift1,ires,iii,ires_old,ishift,ity,
17      &  ishift_pdb,ires_ca
18       logical lprn /.false./,fail
19       double precision e1(3),e2(3),e3(3)
20       double precision dcj,efree_temp
21       character*3 seq,res
22       character*5 atom
23       character*80 card
24       double precision sccor(3,20)
25       integer rescode,iterter(maxres)
26       do i=1,maxres
27          iterter(i)=0
28       enddo
29       ibeg=1
30       ishift1=0
31       ishift=0
32 c      write (2,*) "UNRES_PDB",unres_pdb
33       ires=0
34       ires_old=0
35       iii=0
36       lsecondary=.false.
37       nhfrag=0
38       nbfrag=0
39       do
40         read (ipdbin,'(a80)',end=10) card
41         if (card(:3).eq.'END') then
42           goto 10
43         else if (card(:3).eq.'TER') then
44 C End current chain
45           ires_old=ires+2
46           itype(ires_old-1)=ntyp1 
47           iterter(ires_old-1)=1
48           itype(ires_old)=ntyp1
49           iterter(ires_old)=1
50           ibeg=2
51 c          write (iout,*) "Chain ended",ires,ishift,ires_old
52           if (unres_pdb) then
53             do j=1,3
54               dc(j,ires)=sccor(j,iii)
55             enddo
56           else 
57             call sccenter(ires,iii,sccor)
58           endif
59         endif
60 C Fish out the ATOM cards.
61         if (index(card(1:4),'ATOM').gt.0) then  
62           read (card(12:16),*) atom
63 c          write (iout,*) "! ",atom," !",ires
64 c          if (atom.eq.'CA' .or. atom.eq.'CH3') then
65           read (card(23:26),*) ires
66           read (card(18:20),'(a3)') res
67 c          write (iout,*) "ires",ires,ires-ishift+ishift1,
68 c     &      " ires_old",ires_old
69 c          write (iout,*) "ishift",ishift," ishift1",ishift1
70 c          write (iout,*) "IRES",ires-ishift+ishift1,ires_old
71           if (ires-ishift+ishift1.ne.ires_old) then
72 C Calculate the CM of the preceding residue.
73             if (ibeg.eq.0) then
74               if (unres_pdb) then
75                 do j=1,3
76                   dc(j,ires_old)=sccor(j,iii)
77                 enddo
78               else
79                 call sccenter(ires_old,iii,sccor)
80               endif
81               iii=0
82             endif
83 C Start new residue.
84             if (res.eq.'Cl-' .or. res.eq.'Na+') then
85               ires=ires_old
86               cycle
87             else if (ibeg.eq.1) then
88 c              write (iout,*) "BEG ires",ires
89               ishift=ires-1
90               if (res.ne.'GLY' .and. res.ne. 'ACE') then
91                 ishift=ishift-1
92                 itype(1)=ntyp1
93               endif
94               ires=ires-ishift+ishift1
95               ires_old=ires
96 c              write (iout,*) "ishift",ishift," ires",ires,
97 c     &         " ires_old",ires_old
98 c              write (iout,*) "ires",ires," ibeg",ibeg," ishift",ishift
99               ibeg=0          
100             else if (ibeg.eq.2) then
101 c Start a new chain
102               ishift=-ires_old+ires-1
103               ires=ires_old+1
104 c              write (iout,*) "New chain started",ires,ishift
105               ibeg=0          
106             else
107               ishift=ishift-(ires-ishift+ishift1-ires_old-1)
108               ires=ires-ishift+ishift1
109               ires_old=ires
110             endif
111             if (res.eq.'ACE' .or. res.eq.'NHE') then
112               itype(ires)=10
113             else
114               itype(ires)=rescode(ires,res,0)
115             endif
116           else
117             ires=ires-ishift+ishift1
118           endif
119 c          write (iout,*) "ires_old",ires_old," ires",ires
120 c          if (card(27:27).eq."A" .or. card(27:27).eq."B") then
121 c            ishift1=ishift1+1
122 c          endif
123 c          write (2,*) "ires",ires," res ",res," ity",ity
124           if (atom.eq.'CA' .or. atom.eq.'CH3' .or. 
125      &       res.eq.'NHE'.and.atom(:2).eq.'HN') then
126             read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
127 c            write (iout,*) "backbone ",atom ,ires,res, (c(j,ires),j=1,3)
128 #ifdef DEBUG
129             write (iout,'(2i3,2x,a,3f8.3)') 
130      &      ires,itype(ires),res,(c(j,ires),j=1,3)
131 #endif
132             iii=iii+1
133             do j=1,3
134               sccor(j,iii)=c(j,ires)
135             enddo
136             if (ishift.ne.0) then
137               ires_ca=ires+ishift-ishift1
138             else
139               ires_ca=ires
140             endif
141 c            write (*,*) card(23:27),ires,itype(ires)
142           else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
143      &             atom.ne.'N' .and. atom.ne.'C' .and.
144      &             atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
145      &             atom.ne.'OXT' .and. atom(:2).ne.'3H') then
146 c            write (iout,*) "sidechain ",atom
147             iii=iii+1
148             read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
149           endif
150         endif
151       enddo
152    10 if(me.eq.king.or..not.out1file) 
153      & write (iout,'(a,i5)') ' Nres: ',ires
154 C Calculate dummy residue coordinates inside the "chain" of a multichain
155 C system
156       nres=ires
157       do i=2,nres-1
158 c        write (iout,*) i,itype(i),itype(i+1)
159         if (itype(i).eq.ntyp1.and.iterter(i).eq.1) then
160          if (itype(i+1).eq.ntyp1.and.iterter(i+1).eq.1 ) then
161 C 16/01/2014 by Adasko: Adding to dummy atoms in the chain
162 C first is connected prevous chain (itype(i+1).eq.ntyp1)=true
163 C second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
164            if (unres_pdb) then
165 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
166             call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
167             if (fail) then
168               e2(1)=0.0d0
169               e2(2)=1.0d0
170               e2(3)=0.0d0
171             endif !fail
172             do j=1,3
173              c(j,i)=c(j,i-1)-1.9d0*e2(j)
174             enddo
175            else   !unres_pdb
176            do j=1,3
177              dcj=(c(j,i-2)-c(j,i-3))/2.0
178             if (dcj.eq.0) dcj=1.23591524223
179              c(j,i)=c(j,i-1)+dcj
180              c(j,nres+i)=c(j,i)
181            enddo     
182           endif   !unres_pdb
183          else     !itype(i+1).eq.ntyp1
184           if (unres_pdb) then
185 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
186             call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
187             if (fail) then
188               e2(1)=0.0d0
189               e2(2)=1.0d0
190               e2(3)=0.0d0
191             endif
192             do j=1,3
193               c(j,i)=c(j,i+1)-1.9d0*e2(j)
194             enddo
195           else !unres_pdb
196            do j=1,3
197             dcj=(c(j,i+3)-c(j,i+2))/2.0
198             if (dcj.eq.0) dcj=1.23591524223
199             c(j,i)=c(j,i+1)-dcj
200             c(j,nres+i)=c(j,i)
201            enddo
202           endif !unres_pdb
203          endif !itype(i+1).eq.ntyp1
204         endif  !itype.eq.ntyp1
205       enddo
206 C Calculate the CM of the last side chain.
207       if (unres_pdb) then
208         do j=1,3
209           dc(j,ires)=sccor(j,iii)
210         enddo
211       else
212         call sccenter(ires,iii,sccor)
213       endif
214       nsup=nres
215       nstart_sup=1
216       if (itype(nres).ne.10) then
217         nres=nres+1
218         itype(nres)=ntyp1
219         if (unres_pdb) then
220 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
221           call refsys(nres-3,nres-2,nres-1,e1,e2,e3,fail)
222           if (fail) then
223             e2(1)=0.0d0
224             e2(2)=1.0d0
225             e2(3)=0.0d0
226           endif
227           do j=1,3
228             c(j,nres)=c(j,nres-1)-1.9d0*e2(j)
229           enddo
230         else
231         do j=1,3
232           dcj=(c(j,nres-2)-c(j,nres-3))/2.0
233             if (dcj.eq.0) dcj=1.23591524223
234           c(j,nres)=c(j,nres-1)+dcj
235           c(j,2*nres)=c(j,nres)
236         enddo
237       endif
238       endif
239       do i=2,nres-1
240         do j=1,3
241           c(j,i+nres)=dc(j,i)
242         enddo
243       enddo
244       do j=1,3
245         c(j,nres+1)=c(j,1)
246         c(j,2*nres)=c(j,nres)
247       enddo
248       if (itype(1).eq.ntyp1) then
249         nsup=nsup-1
250         nstart_sup=2
251         if (unres_pdb) then
252 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
253           call refsys(2,3,4,e1,e2,e3,fail)
254           if (fail) then
255             e2(1)=0.0d0
256             e2(2)=1.0d0
257             e2(3)=0.0d0
258           endif
259           do j=1,3
260             c(j,1)=c(j,2)-1.9d0*e2(j)
261           enddo
262         else
263         do j=1,3
264           dcj=(c(j,4)-c(j,3))/2.0
265           c(j,1)=c(j,2)-dcj
266           c(j,nres+1)=c(j,1)
267         enddo
268         endif
269       endif
270 C Copy the coordinates to reference coordinates
271 c      do i=1,2*nres
272 c        do j=1,3
273 c          cref(j,i)=c(j,i)
274 c        enddo
275 c      enddo
276 C Calculate internal coordinates.
277       if (out_template_coord) then
278       write (iout,'(/a)') 
279      &  "Cartesian coordinates of the reference structure"
280       write (iout,'(a,3(3x,a5),5x,3(3x,a5))') 
281      & "Residue ","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
282       do ires=1,nres
283         write (iout,'(a3,1x,i4,3f8.3,5x,3f8.3)') 
284      &    restyp(itype(ires)),ires,(c(j,ires),j=1,3),
285      &    (c(j,ires+nres),j=1,3)
286       enddo
287       endif
288 C Calculate internal coordinates.
289       call int_from_cart(.true.,out_template_coord)
290       call sc_loc_geom(.false.)
291       do i=1,nres
292         thetaref(i)=theta(i)
293         phiref(i)=phi(i)
294       enddo
295       do i=1,nres-1
296         do j=1,3
297           dc(j,i)=c(j,i+1)-c(j,i)
298           dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
299         enddo
300       enddo
301       do i=2,nres-1
302         do j=1,3
303           dc(j,i+nres)=c(j,i+nres)-c(j,i)
304           dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
305         enddo
306 c        write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
307 c     &   vbld_inv(i+nres)
308       enddo
309       do i=1,nres
310         do j=1,3
311           cref(j,i)=c(j,i)
312           cref(j,i+nres)=c(j,i+nres)
313         enddo
314       enddo
315       do i=1,2*nres
316         do j=1,3
317           chomo(j,i,k)=c(j,i)
318         enddo
319       enddo
320
321       return
322       end
323       
324