readpdb & fort.2 from unres
[unres.git] / source / cluster / wham / src-HCD-5D / readpdb.F
1       subroutine readpdb
2 C Read the PDB file and convert the peptide geometry into virtual-chain 
3 C geometry.
4       implicit real*8 (a-h,o-z)
5       include 'DIMENSIONS'
6       include 'COMMON.FRAG'
7       include 'COMMON.LOCAL'
8       include 'COMMON.VAR'
9       include 'COMMON.CHAIN'
10       include 'COMMON.INTERACT'
11       include 'COMMON.IOUNITS'
12       include 'COMMON.GEO'
13       include 'COMMON.NAMES'
14       include 'COMMON.CONTROL'
15       integer i,j,ibeg,ishift1,ires,iii,ires_old,ishift,ity
16       logical lprn /.false./,fail
17       double precision e1(3),e2(3),e3(3)
18       double precision dcj,efree_temp
19       character*3 seq,res
20       character*5 atom
21       character*80 card
22       double precision sccor(3,20)
23       integer rescode
24       integer iterter(maxres)
25       efree_temp=0.0d0
26       ibeg=1
27       ishift1=0
28       ishift=0
29 c      write (2,*) "UNRES_PDB",unres_pdb
30       ires=0
31       ires_old=0
32       iii=0
33       lsecondary=.false.
34       nhfrag=0
35       nbfrag=0
36       do
37         read (ipdbin,'(a80)',end=10) card
38 !       write (iout,'(a)') card
39         if (card(:5).eq.'HELIX') then
40           nhfrag=nhfrag+1
41           lsecondary=.true.
42           read(card(22:25),*) hfrag(1,nhfrag)
43           read(card(34:37),*) hfrag(2,nhfrag)
44         endif
45         if (card(:5).eq.'SHEET') then
46           nbfrag=nbfrag+1
47           lsecondary=.true.
48           read(card(24:26),*) bfrag(1,nbfrag)
49           read(card(35:37),*) bfrag(2,nbfrag)
50 !rc----------------------------------------
51 !rc  to be corrected !!!
52           bfrag(3,nbfrag)=bfrag(1,nbfrag)
53           bfrag(4,nbfrag)=bfrag(2,nbfrag)
54 !rc----------------------------------------
55         endif
56         if (card(:3).eq.'END') then
57           goto 10
58         else if (card(:3).eq.'TER') then
59 ! End current chain
60           ires_old=ires+2
61           itype(ires_old-1)=ntyp1
62           iterter(ires_old-1)=1
63           itype(ires_old)=ntyp1
64           ishift1=ishift1+1
65           ibeg=2
66 !          write (iout,*) "Chain ended",ires,ishift,ires_old
67           if (unres_pdb) then
68             do j=1,3
69               dc(j,ires)=sccor(j,iii)
70             enddo
71           else
72             call sccenter(ires,iii,sccor)
73           endif
74 c          iii=0
75         endif
76 ! Read free energy
77         if (index(card,"FREE ENERGY").gt.0) read(card(35:),*) efree_temp
78 ! Fish out the ATOM cards.
79         if (index(card(1:4),'ATOM').gt.0) then  
80           read (card(12:16),*) atom
81 c          write (2,'(a)') card
82 !          write (iout,*) "! ",atom," !",ires
83 !          if (atom.eq.'CA' .or. atom.eq.'CH3') then
84           read (card(23:26),*) ires
85           read (card(18:20),'(a3)') res
86 !          write (iout,*) "ires",ires,ires-ishift+ishift1,
87 !     &      " ires_old",ires_old
88 !          write (iout,*) "ishift",ishift," ishift1",ishift1
89 !          write (iout,*) "IRES",ires-ishift+ishift1,ires_old
90           if (ires-ishift+ishift1.ne.ires_old) then
91 ! Calculate the CM of the preceding residue.
92 !            if (ibeg.eq.0) call sccenter(ires,iii,sccor)
93             if (ibeg.eq.0) then
94 !              write (iout,*) "Calculating sidechain center iii",iii
95               if (unres_pdb) then
96                 do j=1,3
97                   dc(j,ires+nres)=sccor(j,iii)
98                 enddo
99               else
100                 call sccenter(ires_old,iii,sccor)
101               endif
102               iii=0
103             endif
104 ! Start new residue.
105             if (res.eq.'Cl-' .or. res.eq.'Na+') then
106               ires=ires_old
107               cycle
108             else if (ibeg.eq.1) then
109 c              write (iout,*) "BEG ires",ires
110               ishift=ires-1
111               if (res.ne.'GLY' .and. res.ne. 'ACE') then
112                 ishift=ishift-1
113                 itype(1)=ntyp1
114               endif
115               ires=ires-ishift+ishift1
116               ires_old=ires
117 !              write (iout,*) "ishift",ishift," ires",ires,&
118 !               " ires_old",ires_old
119               ibeg=0 
120             else if (ibeg.eq.2) then
121 ! Start a new chain
122               ishift=-ires_old+ires-1 !!!!!
123               ishift1=ishift1-1    !!!!!
124 !              write (iout,*) "New chain started",ires,ishift,ishift1,"!"
125               ires=ires-ishift+ishift1
126               ires_old=ires
127               ibeg=0
128             else
129               ishift=ishift-(ires-ishift+ishift1-ires_old-1)
130               ires=ires-ishift+ishift1
131               ires_old=ires
132             endif
133             if (res.eq.'ACE' .or. res.eq.'NHE') then
134               itype(ires)=10
135             else
136               itype(ires)=rescode(ires,res,0)
137             endif
138           else
139             ires=ires-ishift+ishift1
140           endif
141 !          write (iout,*) "ires_old",ires_old," ires",ires
142           if (card(27:27).eq."A" .or. card(27:27).eq."B") then
143 !            ishift1=ishift1+1
144           endif
145 !          write (2,*) "ires",ires," res ",res!," ity"!,ity 
146           if (atom.eq.'CA' .or. atom.eq.'CH3' .or. 
147      &       res.eq.'NHE'.and.atom(:2).eq.'HN') then
148             read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
149 !            write (iout,*) "backbone ",atom
150 #ifdef DEBUG
151             write (iout,'(2i3,2x,a,3f8.3)') 
152      &      ires,itype(ires),res,(c(j,ires),j=1,3)
153 #endif
154             iii=iii+1
155             do j=1,3
156               sccor(j,iii)=c(j,ires)
157             enddo
158 c            write (2,*) card(23:27),ires,itype(ires),iii
159           else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and. 
160      &             atom.ne.'N' .and. atom.ne.'C' .and. 
161      &             atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and. 
162      &             atom.ne.'OXT' .and. atom(:2).ne.'3H') then
163 !            write (iout,*) "sidechain ",atom
164             iii=iii+1
165             read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
166 c            write (2,*) "iii",iii
167           endif
168         endif
169       enddo
170    10 continue
171 #ifdef DEBUG
172       write (iout,'(a,i5)') ' Number of residues found: ',ires
173 #endif
174       if (ires.eq.0) return
175 C Calculate the CM of the last side chain.
176       if (iii.gt.0)  then
177       if (unres_pdb) then
178         do j=1,3
179           dc(j,ires)=sccor(j,iii)
180         enddo
181       else
182         call sccenter(ires,iii,sccor)
183       endif
184       endif
185       nres=ires
186       nsup=nres
187       nstart_sup=1
188       if (itype(nres).ne.10) then
189         nres=nres+1
190         itype(nres)=ntyp1
191         if (unres_pdb) then
192 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
193           call refsys(nres-3,nres-2,nres-1,e1,e2,e3,fail)
194           if (fail) then
195             e2(1)=0.0d0
196             e2(2)=1.0d0
197             e2(3)=0.0d0
198           endif
199           do j=1,3
200             c(j,nres)=c(j,nres-1)-3.8d0*e2(j)
201           enddo
202         else
203         do j=1,3
204           dcj=c(j,nres-2)-c(j,nres-3)
205           c(j,nres)=c(j,nres-1)+dcj
206           c(j,2*nres)=c(j,nres)
207         enddo
208         endif
209       endif
210       do i=2,nres-1
211         do j=1,3
212           c(j,i+nres)=dc(j,i)
213         enddo
214       enddo
215       do j=1,3
216         c(j,nres+1)=c(j,1)
217         c(j,2*nres)=c(j,nres)
218       enddo
219       if (itype(1).eq.ntyp1) then
220         nsup=nsup-1
221         nstart_sup=2
222         if (unres_pdb) then
223 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
224           call refsys(2,3,4,e1,e2,e3,fail)
225           if (fail) then
226             e2(1)=0.0d0
227             e2(2)=1.0d0
228             e2(3)=0.0d0
229           endif
230           do j=1,3
231             c(j,1)=c(j,2)-3.8d0*e2(j)
232           enddo
233         else
234         do j=1,3
235           dcj=c(j,4)-c(j,3)
236           c(j,1)=c(j,2)-dcj
237           c(j,nres+1)=c(j,1)
238         enddo
239         endif
240       endif
241 C Copy the coordinates to reference coordinates
242 c      do i=1,2*nres
243 c        do j=1,3
244 c          cref(j,i)=c(j,i)
245 c        enddo
246 c      enddo
247 C Calculate internal coordinates.
248       if (lprn) then
249       write (iout,'(/a)') 
250      &  "Cartesian coordinates of the reference structure"
251       write (iout,'(a,3(3x,a5),5x,3(3x,a5))') 
252      & "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
253       do ires=1,nres
254         write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)') 
255      &    restyp(itype(ires)),ires,(c(j,ires),j=1,3),
256      &    (c(j,ires+nres),j=1,3)
257       enddo
258       endif
259 C Calculate internal coordinates.
260        write (iout,'(a)') 
261      &   "Backbone and SC coordinates as read from the PDB"
262        do ires=1,nres
263         write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)') 
264      &    ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
265      &    (c(j,nres+ires),j=1,3)
266        enddo
267       call int_from_cart(.true.,.false.)
268       call sc_loc_geom(.false.)
269       do i=1,nres
270         thetaref(i)=theta(i)
271         phiref(i)=phi(i)
272       enddo
273       do i=1,nres-1
274         do j=1,3
275           dc(j,i)=c(j,i+1)-c(j,i)
276           dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
277         enddo
278       enddo
279       do i=2,nres-1
280         do j=1,3
281           dc(j,i+nres)=c(j,i+nres)-c(j,i)
282           dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
283         enddo
284 c        write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
285 c     &   vbld_inv(i+nres)
286       enddo
287 c      call chainbuild
288 C Copy the coordinates to reference coordinates
289       do i=1,2*nres
290         do j=1,3
291           cref(j,i)=c(j,i)
292         enddo
293       enddo
294
295
296       do j=1,nbfrag     
297         do i=1,4                                                       
298          bfrag(i,j)=bfrag(i,j)-ishift
299         enddo
300       enddo
301
302       do j=1,nhfrag
303         do i=1,2
304          hfrag(i,j)=hfrag(i,j)-ishift
305         enddo
306       enddo
307       ishift_pdb=ishift
308       return
309       end
310 c---------------------------------------------------------------------------
311       subroutine int_from_cart(lside,lprn)
312       implicit real*8 (a-h,o-z)
313       include 'DIMENSIONS'
314       include 'COMMON.LOCAL'
315       include 'COMMON.VAR'
316       include 'COMMON.CHAIN'
317       include 'COMMON.INTERACT'
318       include 'COMMON.IOUNITS'
319       include 'COMMON.GEO'
320       include 'COMMON.NAMES'
321       character*3 seq,res
322 c      character*5 atom
323       character*80 card
324       dimension sccor(3,20)
325       integer rescode
326       logical lside,lprn
327        if (lprn) then 
328         write (iout,'(/a)') 
329      &  'Internal coordinates calculated from crystal structure.'
330         if (lside) then 
331           write (iout,'(8a)') '  Res  ','       dvb','     Theta',
332      & '     Gamma','    Dsc_id','       Dsc','     Alpha',
333      & '     Beta '
334         else 
335           write (iout,'(4a)') '  Res  ','       dvb','     Theta',
336      & '     Gamma'
337         endif
338        endif
339       do i=1,nres-1
340         iti=itype(i)
341         if (dist(i,i+1).lt.2.0D0 .or. dist(i,i+1).gt.5.0D0) then
342           write (iout,'(a,i4)') 'Bad Cartesians for residue',i
343 ctest          stop
344         endif
345         vbld(i+1)=dist(i,i+1)
346         vbld_inv(i+1)=1.0d0/vbld(i+1)
347         if (i.gt.1) theta(i+1)=alpha(i-1,i,i+1)
348         if (i.gt.2) phi(i+1)=beta(i-2,i-1,i,i+1)
349       enddo
350 c      if (unres_pdb) then
351 c        if (itype(1).eq.ntyp1) then
352 c          theta(3)=90.0d0*deg2rad
353 c          phi(4)=180.0d0*deg2rad
354 c          vbld(2)=3.8d0
355 c          vbld_inv(2)=1.0d0/vbld(2)
356 c        endif
357 c        if (itype(nres).eq.ntyp1) then
358 c          theta(nres)=90.0d0*deg2rad
359 c          phi(nres)=180.0d0*deg2rad
360 c          vbld(nres)=3.8d0
361 c          vbld_inv(nres)=1.0d0/vbld(2)
362 c        endif
363 c      endif
364       if (lside) then
365         do i=2,nres-1
366           do j=1,3
367             c(j,maxres2)=0.5D0*(2*c(j,i)+(c(j,i-1)-c(j,i))*vbld_inv(i)
368      &     +(c(j,i+1)-c(j,i))*vbld_inv(i+1))
369           enddo
370           iti=itype(i)
371           di=dist(i,nres+i)
372 C 10/03/12 Adam: Correction for zero SC-SC bond length
373           if (itype(i).ne.10 .and. itype(i).ne.ntyp1. and. di.eq.0.0d0)
374      &     di=dsc(itype(i))
375           vbld(i+nres)=di
376           if (itype(i).ne.10) then
377             vbld_inv(i+nres)=1.0d0/di
378           else
379             vbld_inv(i+nres)=0.0d0
380           endif
381           if (iti.ne.10) then
382             alph(i)=alpha(nres+i,i,maxres2)
383             omeg(i)=beta(nres+i,i,maxres2,i+1)
384           endif
385            if (lprn)
386      &     write (iout,'(a3,i4,7f10.3)') restyp(iti),i,vbld(i),
387      &     rad2deg*theta(i),rad2deg*phi(i),dsc(iti),vbld(nres+i),
388      &     rad2deg*alph(i),rad2deg*omeg(i)
389         enddo
390       else if (lprn) then
391         do i=2,nres
392           iti=itype(i)
393           write (iout,'(a3,i4,7f10.3)') restyp(iti),i,dist(i,i-1),
394      &     rad2deg*theta(i),rad2deg*phi(i)
395         enddo
396       endif
397       return
398       end
399 c-------------------------------------------------------------------------------
400       subroutine sc_loc_geom(lprn)
401       implicit real*8 (a-h,o-z)
402       include 'DIMENSIONS'
403       include 'COMMON.LOCAL'
404       include 'COMMON.VAR'
405       include 'COMMON.CHAIN'
406       include 'COMMON.INTERACT'
407       include 'COMMON.IOUNITS'
408       include 'COMMON.GEO'
409       include 'COMMON.NAMES'
410       include 'COMMON.CONTROL'
411       double precision x_prime(3),y_prime(3),z_prime(3)
412       logical lprn
413       do i=1,nres-1
414         do j=1,3
415           dc_norm(j,i)=vbld_inv(i+1)*(c(j,i+1)-c(j,i))
416         enddo
417       enddo
418       do i=2,nres-1
419         if (itype(i).ne.10) then
420           do j=1,3
421             dc_norm(j,i+nres)=vbld_inv(i+nres)*(c(j,i+nres)-c(j,i))
422           enddo
423         else
424           do j=1,3
425             dc_norm(j,i+nres)=0.0d0
426           enddo
427         endif
428       enddo
429       do i=2,nres-1
430         costtab(i+1) =dcos(theta(i+1))
431         sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
432         cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
433         sint2tab(i+1)=dsqrt(0.5d0*(1.0d0-costtab(i+1)))
434         cosfac2=0.5d0/(1.0d0+costtab(i+1))
435         cosfac=dsqrt(cosfac2)
436         sinfac2=0.5d0/(1.0d0-costtab(i+1))
437         sinfac=dsqrt(sinfac2)
438         it=itype(i)
439         if (it.ne.10) then
440 c
441 C  Compute the axes of tghe local cartesian coordinates system; store in
442 c   x_prime, y_prime and z_prime 
443 c
444         do j=1,3
445           x_prime(j) = 0.00
446           y_prime(j) = 0.00
447           z_prime(j) = 0.00
448         enddo
449         do j = 1,3
450           x_prime(j) = (dc_norm(j,i) - dc_norm(j,i-1))*cosfac
451           y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
452         enddo
453         call vecpr(x_prime,y_prime,z_prime)
454 c
455 C Transform the unit vector of the ith side-chain centroid, dC_norm(*,i),
456 C to local coordinate system. Store in xx, yy, zz.
457 c
458         xx=0.0d0
459         yy=0.0d0
460         zz=0.0d0
461         do j = 1,3
462           xx = xx + x_prime(j)*dc_norm(j,i+nres)
463           yy = yy + y_prime(j)*dc_norm(j,i+nres)
464           zz = zz + z_prime(j)*dc_norm(j,i+nres)
465         enddo
466
467         xxref(i)=xx
468         yyref(i)=yy
469         zzref(i)=zz
470         else
471         xxref(i)=0.0d0
472         yyref(i)=0.0d0
473         zzref(i)=0.0d0
474         endif
475       enddo
476       if (lprn) then
477         do i=2,nres
478           iti=itype(i)
479           write (iout,'(a3,i4,3f10.5)') restyp(iti),i,xxref(i),
480      &      yyref(i),zzref(i)
481         enddo
482       endif
483       return
484       end
485 c---------------------------------------------------------------------------
486       subroutine sccenter(ires,nscat,sccor)
487       implicit real*8 (a-h,o-z)
488       include 'DIMENSIONS'
489       include 'COMMON.CHAIN'
490       dimension sccor(3,20)
491       do j=1,3
492         sccmj=0.0D0
493         do i=1,nscat
494           sccmj=sccmj+sccor(j,i) 
495         enddo
496         dc(j,ires)=sccmj/nscat
497       enddo
498       return
499       end
500 c---------------------------------------------------------------------------
501       subroutine bond_regular
502       implicit none
503       include 'DIMENSIONS'
504       include 'COMMON.VAR'
505       include 'COMMON.LOCAL'
506       include 'COMMON.INTERACT'
507       include 'COMMON.CHAIN'
508       integer i,i1,i2
509       do i=1,nres-1
510        vbld(i+1)=vbl
511        vbld_inv(i+1)=vblinv
512        vbld(i+1+nres)=dsc(iabs(itype(i+1)))
513        vbld_inv(i+1+nres)=dsc_inv(iabs(itype(i+1)))
514 c       print *,vbld(i+1),vbld(i+1+nres)
515       enddo
516 c Adam 2/26/20 Alter virtual bonds for non-blocking end groups of each chain
517       do i=1,nchain
518         i1=chain_border(1,i)
519         i2=chain_border(2,i)
520         if (i1.gt.1) then
521           vbld(i1)=vbld(i1)/2
522           vbld_inv(i1)=vbld_inv(i1)*2
523         endif
524         if (i2.lt.nres) then
525           vbld(i2+1)=vbld(i2+1)/2
526           vbld_inv(i2+1)=vbld_inv(i2+1)*2
527         endif
528       enddo
529       return
530       end
531 c---------------------------------------------------------------------------
532       subroutine readpdb_template(k)
533 C Read the PDB file with gaps for read_constr_homology with read2sigma
534 C and convert the peptide geometry into virtual-chain geometry.
535       implicit real*8 (a-h,o-z)
536       include 'DIMENSIONS'
537       include 'COMMON.LOCAL'
538       include 'COMMON.VAR'
539       include 'COMMON.CHAIN'
540       include 'COMMON.INTERACT'
541       include 'COMMON.IOUNITS'
542       include 'COMMON.GEO'
543       include 'COMMON.NAMES'
544       include 'COMMON.CONTROL'
545       integer i,j,ibeg,ishift1,ires,iii,ires_old,ishift,ity
546       logical lprn /.false./,fail
547       double precision e1(3),e2(3),e3(3)
548       double precision dcj,efree_temp
549       character*3 seq,res
550       character*5 atom
551       character*80 card
552       double precision sccor(3,20)
553       integer rescode
554       efree_temp=0.0d0
555       ibeg=1
556       ishift1=0
557       ishift=0
558 c      write (2,*) "UNRES_PDB",unres_pdb
559       ires=0
560       ires_old=0
561       iii=0
562       lsecondary=.false.
563       nhfrag=0
564       nbfrag=0
565       do 
566         read (ipdbin,'(a80)',end=10) card
567 c        write (iout,'(a)') card
568         if (card(:3).eq.'END' .or. card(:3).eq.'TER') goto 10
569 C Fish out the ATOM cards.
570         if (index(card(1:4),'ATOM').gt.0) then  
571           read (card(12:16),*) atom
572 c          write (iout,*) "! ",atom," !",ires
573 c          if (atom.eq.'CA' .or. atom.eq.'CH3') then
574           read (card(23:26),*) ires
575           read (card(18:20),'(a3)') res
576 c          write (iout,*) "ires",ires,ires-ishift+ishift1,
577 c     &      " ires_old",ires_old
578 c          write (iout,*) "ishift",ishift," ishift1",ishift1
579 c          write (iout,*) "IRES",ires-ishift+ishift1,ires_old
580           if (ires-ishift+ishift1.ne.ires_old) then
581 C Calculate the CM of the preceding residue.
582 c            if (ibeg.eq.0) call sccenter(ires,iii,sccor)
583             if (ibeg.eq.0) then
584 c              write (iout,*) "Calculating sidechain center iii",iii
585               if (unres_pdb) then
586                 do j=1,3
587                   dc(j,ires)=sccor(j,iii)
588                 enddo
589               else
590                 call sccenter(ires_old,iii,sccor)
591               endif
592               iii=0
593             endif
594 C Start new residue.
595             if (res.eq.'Cl-' .or. res.eq.'Na+') then
596               ires=ires_old
597               cycle
598             else if (ibeg.eq.1) then
599 c              write (iout,*) "BEG ires",ires
600               ishift=ires-1
601               if (res.ne.'GLY' .and. res.ne. 'ACE') then
602                 ishift=ishift-1
603                 itype(1)=ntyp1
604               endif
605               ires=ires-ishift+ishift1
606               ires_old=ires
607 c              write (iout,*) "ishift",ishift," ires",ires,
608 c     &         " ires_old",ires_old
609               ibeg=0          
610             else
611               ishift=ishift-(ires-ishift+ishift1-ires_old-1)
612               ires=ires-ishift+ishift1
613               ires_old=ires
614             endif
615             if (res.eq.'ACE' .or. res.eq.'NHE') then
616               itype(ires)=10
617             else
618               itype(ires)=rescode(ires,res,0)
619             endif
620           else
621             ires=ires-ishift+ishift1
622           endif
623 c          write (iout,*) "ires_old",ires_old," ires",ires
624           if (card(27:27).eq."A" .or. card(27:27).eq."B") then
625 c            ishift1=ishift1+1
626           endif
627 c          write (2,*) "ires",ires," res ",res," ity",ity
628           if (atom.eq.'CA' .or. atom.eq.'CH3' .or. 
629      &       res.eq.'NHE'.and.atom(:2).eq.'HN') then
630             read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
631 c            write (iout,*) "backbone ",atom 
632 #ifdef DEBUG
633             write (iout,'(2i3,2x,a,3f8.3)') 
634      &      ires,itype(ires),res,(c(j,ires),j=1,3)
635 #endif
636             iii=iii+1
637             do j=1,3
638               sccor(j,iii)=c(j,ires)
639             enddo
640             if (ishift.ne.0) then
641               ires_ca=ires+ishift-ishift1
642             else
643               ires_ca=ires
644             endif
645 c            write (*,*) card(23:27),ires,itype(ires)
646           else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
647      &             atom.ne.'N' .and. atom.ne.'C' .and.
648      &             atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
649      &             atom.ne.'OXT' .and. atom(:2).ne.'3H') then
650 c            write (iout,*) "sidechain ",atom
651             iii=iii+1
652             read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
653           endif
654         endif
655       enddo
656    10 continue
657 #ifdef DEBUG
658       write (iout,'(a,i5)') ' Number of residues found: ',ires
659 #endif
660       if (ires.eq.0) return
661 C Calculate the CM of the last side chain.
662       if (iii.gt.0)  then
663       if (unres_pdb) then
664         do j=1,3
665           dc(j,ires)=sccor(j,iii)
666         enddo
667       else
668         call sccenter(ires,iii,sccor)
669       endif
670       endif
671       nres=ires
672       nsup=nres
673       nstart_sup=1
674       if (itype(nres).ne.10) then
675         nres=nres+1
676         itype(nres)=ntyp1
677         do j=1,3
678           dcj=c(j,nres-2)-c(j,nres-3)
679           c(j,nres)=c(j,nres-1)+dcj
680           c(j,2*nres)=c(j,nres)
681         enddo
682       endif
683       do i=2,nres-1
684         do j=1,3
685           c(j,i+nres)=dc(j,i)
686         enddo
687       enddo
688       do j=1,3
689         c(j,nres+1)=c(j,1)
690         c(j,2*nres)=c(j,nres)
691       enddo
692       if (itype(1).eq.ntyp1) then
693         nsup=nsup-1
694         nstart_sup=2
695         if (unres_pdb) then
696 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
697           call refsys(2,3,4,e1,e2,e3,fail)
698           if (fail) then
699             e2(1)=0.0d0
700             e2(2)=1.0d0
701             e2(3)=0.0d0
702           endif
703           do j=1,3
704             c(j,1)=c(j,2)-3.8d0*e2(j)
705           enddo
706         else
707         do j=1,3
708           dcj=c(j,4)-c(j,3)
709           c(j,1)=c(j,2)-dcj
710           c(j,nres+1)=c(j,1)
711         enddo
712         endif
713       endif
714 C Calculate internal coordinates.
715       if (lprn) then
716       write (iout,'(/a)') 
717      &  "Cartesian coordinates of the reference structure"
718       write (iout,'(a,3(3x,a5),5x,3(3x,a5))') 
719      & "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
720       do ires=1,nres
721         write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)') 
722      &    restyp(itype(ires)),ires,(c(j,ires),j=1,3),
723      &    (c(j,ires+nres),j=1,3)
724       enddo
725       endif
726 C Calculate internal coordinates.
727        write (iout,'(a)') 
728      &   "Backbone and SC coordinates as read from the PDB"
729        do ires=1,nres
730         write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)') 
731      &    ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
732      &    (c(j,nres+ires),j=1,3)
733        enddo
734       call int_from_cart(.true.,.false.)
735       call sc_loc_geom(.false.)
736       do i=1,nres
737         thetaref(i)=theta(i)
738         phiref(i)=phi(i)
739       enddo
740       do i=1,nres-1
741         do j=1,3
742           dc(j,i)=c(j,i+1)-c(j,i)
743           dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
744         enddo
745       enddo
746       do i=2,nres-1
747         do j=1,3
748           dc(j,i+nres)=c(j,i+nres)-c(j,i)
749           dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
750         enddo
751 c        write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
752 c     &   vbld_inv(i+nres)
753       enddo
754 c      call chainbuild
755 C Copy the coordinates to reference coordinates
756       do i=1,2*nres
757         do j=1,3
758           cref(j,i)=c(j,i)
759           chomo(j,i,k)=c(j,i)
760         enddo
761       enddo
762
763
764       ishift_pdb=ishift
765       return
766       end