0167c00b2428db8b3bb5ebdd0f41714ac18da27f
[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 write (iout,'(a,i5)') ' Nres: ',ires
171 C Calculate dummy residue coordinates inside the "chain" of a multichain
172 C system
173       nres=ires
174       do i=2,nres-1
175 c        write (iout,*) i,itype(i)
176
177         if (itype(i).eq.ntyp1) then
178          if (itype(i+1).eq.ntyp1) then
179 C 16/01/2014 by Adasko: Adding to dummy atoms in the chain
180 C first is connected prevous chain (itype(i+1).eq.ntyp1)=true
181 C second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
182 C           if (unres_pdb) then
183 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
184 C            call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
185 C            if (fail) then
186 C              e2(1)=0.0d0
187 C              e2(2)=1.0d0
188 C              e2(3)=0.0d0
189 C            endif !fail
190 C            do j=1,3
191 C             c(j,i)=c(j,i-1)-1.9d0*e2(j)
192 C            enddo
193 C           else   !unres_pdb
194            do j=1,3
195              dcj=(c(j,i-2)-c(j,i-3))/2.0
196              c(j,i)=c(j,i-1)+dcj
197              c(j,nres+i)=c(j,i)
198            enddo     
199 C          endif   !unres_pdb
200          else     !itype(i+1).eq.ntyp1
201 C          if (unres_pdb) then
202 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
203 C            call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
204 C            if (fail) then
205 C              e2(1)=0.0d0
206 C              e2(2)=1.0d0
207 C              e2(3)=0.0d0
208 C            endif
209 C            do j=1,3
210 C              c(j,i)=c(j,i+1)-1.9d0*e2(j)
211 C            enddo
212 C          else !unres_pdb
213            do j=1,3
214             dcj=(c(j,i+3)-c(j,i+2))/2.0
215             c(j,i)=c(j,i+1)-dcj
216             c(j,nres+i)=c(j,i)
217            enddo
218 C          endif !unres_pdb
219          endif !itype(i+1).eq.ntyp1
220         endif  !itype.eq.ntyp1
221       enddo
222 C Calculate the CM of the last side chain.
223       call sccenter(ires,iii,sccor)
224       nsup=nres
225       nstart_sup=1
226       if (itype(nres).ne.10) then
227         nres=nres+1
228         itype(nres)=ntyp1
229         do j=1,3
230           dcj=(c(j,nres-2)-c(j,nres-3))/2.0
231           c(j,nres)=c(j,nres-1)+dcj
232           c(j,2*nres)=c(j,nres)
233         enddo
234       endif
235       do i=2,nres-1
236         do j=1,3
237           c(j,i+nres)=dc(j,i)
238         enddo
239       enddo
240       do j=1,3
241         c(j,nres+1)=c(j,1)
242         c(j,2*nres)=c(j,nres)
243       enddo
244       if (itype(1).eq.ntyp1) then
245         nsup=nsup-1
246         nstart_sup=2
247         do j=1,3
248           dcj=(c(j,4)-c(j,3))/2.0
249           c(j,1)=c(j,2)-dcj
250           c(j,nres+1)=c(j,1)
251         enddo
252       endif
253 C Calculate internal coordinates.
254       if (lprn) then
255       write (iout,'(/a)') 
256      &  "Cartesian coordinates of the reference structure"
257       write (iout,'(a,3(3x,a5),5x,3(3x,a5))') 
258      & "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
259       do ires=1,nres
260         write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)') 
261      &    restyp(itype(ires)),ires,(c(j,ires),j=1,3),
262      &    (c(j,ires+nres),j=1,3)
263       enddo
264       endif
265 C Calculate internal coordinates.
266        write (iout,'(a)') 
267      &   "Backbone and SC coordinates as read from the PDB"
268        do ires=1,nres
269         write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)') 
270      &    ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
271      &    (c(j,nres+ires),j=1,3)
272        enddo
273       call int_from_cart(.true.,.false.)
274       call sc_loc_geom(.false.)
275       do i=1,nres
276         thetaref(i)=theta(i)
277         phiref(i)=phi(i)
278       enddo
279       do i=1,nres-1
280         do j=1,3
281           dc(j,i)=c(j,i+1)-c(j,i)
282           dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
283         enddo
284       enddo
285       do i=2,nres-1
286         do j=1,3
287           dc(j,i+nres)=c(j,i+nres)-c(j,i)
288           dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
289         enddo
290 c        write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
291 c     &   vbld_inv(i+nres)
292       enddo
293 c      call chainbuild
294 C Copy the coordinates to reference coordinates
295       do i=1,2*nres
296         do j=1,3
297           cref(j,i)=c(j,i)
298         enddo
299       enddo
300
301
302       do j=1,nbfrag     
303         do i=1,4                                                       
304          bfrag(i,j)=bfrag(i,j)-ishift
305         enddo
306       enddo
307
308       do j=1,nhfrag
309         do i=1,2
310          hfrag(i,j)=hfrag(i,j)-ishift
311         enddo
312       enddo
313       ishift_pdb=ishift
314       return
315       end
316 c---------------------------------------------------------------------------
317       subroutine int_from_cart(lside,lprn)
318       implicit real*8 (a-h,o-z)
319       include 'DIMENSIONS'
320       include 'COMMON.LOCAL'
321       include 'COMMON.VAR'
322       include 'COMMON.CHAIN'
323       include 'COMMON.INTERACT'
324       include 'COMMON.IOUNITS'
325       include 'COMMON.GEO'
326       include 'COMMON.NAMES'
327       character*3 seq,res
328 c      character*5 atom
329       character*80 card
330       dimension sccor(3,20)
331       integer rescode
332       logical lside,lprn
333        if (lprn) then 
334         write (iout,'(/a)') 
335      &  'Internal coordinates calculated from crystal structure.'
336         if (lside) then 
337           write (iout,'(8a)') '  Res  ','       dvb','     Theta',
338      & '     Gamma','    Dsc_id','       Dsc','     Alpha',
339      & '     Beta '
340         else 
341           write (iout,'(4a)') '  Res  ','       dvb','     Theta',
342      & '     Gamma'
343         endif
344        endif
345       do i=1,nres-1
346         iti=itype(i)
347         if (dist(i,i+1).lt.2.0D0 .or. dist(i,i+1).gt.5.0D0) then
348           write (iout,'(a,i4)') 'Bad Cartesians for residue',i
349 ctest          stop
350         endif
351         vbld(i+1)=dist(i,i+1)
352         vbld_inv(i+1)=1.0d0/vbld(i+1)
353         if (i.gt.1) theta(i+1)=alpha(i-1,i,i+1)
354         if (i.gt.2) phi(i+1)=beta(i-2,i-1,i,i+1)
355       enddo
356 c      if (unres_pdb) then
357 c        if (itype(1).eq.ntyp1) then
358 c          theta(3)=90.0d0*deg2rad
359 c          phi(4)=180.0d0*deg2rad
360 c          vbld(2)=3.8d0
361 c          vbld_inv(2)=1.0d0/vbld(2)
362 c        endif
363 c        if (itype(nres).eq.ntyp1) then
364 c          theta(nres)=90.0d0*deg2rad
365 c          phi(nres)=180.0d0*deg2rad
366 c          vbld(nres)=3.8d0
367 c          vbld_inv(nres)=1.0d0/vbld(2)
368 c        endif
369 c      endif
370       if (lside) then
371         do i=2,nres-1
372           do j=1,3
373             c(j,maxres2)=0.5D0*(2*c(j,i)+(c(j,i-1)-c(j,i))*vbld_inv(i)
374      &     +(c(j,i+1)-c(j,i))*vbld_inv(i+1))
375           enddo
376           iti=itype(i)
377           di=dist(i,nres+i)
378 C 10/03/12 Adam: Correction for zero SC-SC bond length
379           if (itype(i).ne.10 .and. itype(i).ne.ntyp1. and. di.eq.0.0d0)
380      &     di=dsc(itype(i))
381           vbld(i+nres)=di
382           if (itype(i).ne.10) then
383             vbld_inv(i+nres)=1.0d0/di
384           else
385             vbld_inv(i+nres)=0.0d0
386           endif
387           if (iti.ne.10) then
388             alph(i)=alpha(nres+i,i,maxres2)
389             omeg(i)=beta(nres+i,i,maxres2,i+1)
390           endif
391            if (lprn)
392      &     write (iout,'(a3,i4,7f10.3)') restyp(iti),i,vbld(i),
393      &     rad2deg*theta(i),rad2deg*phi(i),dsc(iti),vbld(nres+i),
394      &     rad2deg*alph(i),rad2deg*omeg(i)
395         enddo
396       else if (lprn) then
397         do i=2,nres
398           iti=itype(i)
399           write (iout,'(a3,i4,7f10.3)') restyp(iti),i,dist(i,i-1),
400      &     rad2deg*theta(i),rad2deg*phi(i)
401         enddo
402       endif
403       return
404       end
405 c-------------------------------------------------------------------------------
406       subroutine sc_loc_geom(lprn)
407       implicit real*8 (a-h,o-z)
408       include 'DIMENSIONS'
409       include 'COMMON.LOCAL'
410       include 'COMMON.VAR'
411       include 'COMMON.CHAIN'
412       include 'COMMON.INTERACT'
413       include 'COMMON.IOUNITS'
414       include 'COMMON.GEO'
415       include 'COMMON.NAMES'
416       include 'COMMON.CONTROL'
417       double precision x_prime(3),y_prime(3),z_prime(3)
418       logical lprn
419       do i=1,nres-1
420         do j=1,3
421           dc_norm(j,i)=vbld_inv(i+1)*(c(j,i+1)-c(j,i))
422         enddo
423       enddo
424       do i=2,nres-1
425         if (itype(i).ne.10) then
426           do j=1,3
427             dc_norm(j,i+nres)=vbld_inv(i+nres)*(c(j,i+nres)-c(j,i))
428           enddo
429         else
430           do j=1,3
431             dc_norm(j,i+nres)=0.0d0
432           enddo
433         endif
434       enddo
435       do i=2,nres-1
436         costtab(i+1) =dcos(theta(i+1))
437         sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
438         cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
439         sint2tab(i+1)=dsqrt(0.5d0*(1.0d0-costtab(i+1)))
440         cosfac2=0.5d0/(1.0d0+costtab(i+1))
441         cosfac=dsqrt(cosfac2)
442         sinfac2=0.5d0/(1.0d0-costtab(i+1))
443         sinfac=dsqrt(sinfac2)
444         it=itype(i)
445         if (it.ne.10) then
446 c
447 C  Compute the axes of tghe local cartesian coordinates system; store in
448 c   x_prime, y_prime and z_prime 
449 c
450         do j=1,3
451           x_prime(j) = 0.00
452           y_prime(j) = 0.00
453           z_prime(j) = 0.00
454         enddo
455         do j = 1,3
456           x_prime(j) = (dc_norm(j,i) - dc_norm(j,i-1))*cosfac
457           y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
458         enddo
459         call vecpr(x_prime,y_prime,z_prime)
460 c
461 C Transform the unit vector of the ith side-chain centroid, dC_norm(*,i),
462 C to local coordinate system. Store in xx, yy, zz.
463 c
464         xx=0.0d0
465         yy=0.0d0
466         zz=0.0d0
467         do j = 1,3
468           xx = xx + x_prime(j)*dc_norm(j,i+nres)
469           yy = yy + y_prime(j)*dc_norm(j,i+nres)
470           zz = zz + z_prime(j)*dc_norm(j,i+nres)
471         enddo
472
473         xxref(i)=xx
474         yyref(i)=yy
475         zzref(i)=zz
476         else
477         xxref(i)=0.0d0
478         yyref(i)=0.0d0
479         zzref(i)=0.0d0
480         endif
481       enddo
482       if (lprn) then
483         do i=2,nres
484           iti=itype(i)
485           write (iout,'(a3,i4,3f10.5)') restyp(iti),i,xxref(i),
486      &      yyref(i),zzref(i)
487         enddo
488       endif
489       return
490       end
491 c---------------------------------------------------------------------------
492       subroutine sccenter(ires,nscat,sccor)
493       implicit real*8 (a-h,o-z)
494       include 'DIMENSIONS'
495       include 'COMMON.CHAIN'
496       dimension sccor(3,20)
497       do j=1,3
498         sccmj=0.0D0
499         do i=1,nscat
500           sccmj=sccmj+sccor(j,i) 
501         enddo
502         dc(j,ires)=sccmj/nscat
503       enddo
504       return
505       end
506 c---------------------------------------------------------------------------
507       subroutine bond_regular
508       implicit none
509       include 'DIMENSIONS'
510       include 'COMMON.VAR'
511       include 'COMMON.LOCAL'
512       include 'COMMON.INTERACT'
513       include 'COMMON.CHAIN'
514       integer i,i1,i2
515       do i=1,nres-1
516        vbld(i+1)=vbl
517        vbld_inv(i+1)=vblinv
518        vbld(i+1+nres)=dsc(iabs(itype(i+1)))
519        vbld_inv(i+1+nres)=dsc_inv(iabs(itype(i+1)))
520 c       print *,vbld(i+1),vbld(i+1+nres)
521       enddo
522 c Adam 2/26/20 Alter virtual bonds for non-blocking end groups of each chain
523       do i=1,nchain
524         i1=chain_border(1,i)
525         i2=chain_border(2,i)
526         if (i1.gt.1) then
527           vbld(i1)=vbld(i1)/2
528           vbld_inv(i1)=vbld_inv(i1)*2
529         endif
530         if (i2.lt.nres) then
531           vbld(i2+1)=vbld(i2+1)/2
532           vbld_inv(i2+1)=vbld_inv(i2+1)*2
533         endif
534       enddo
535       return
536       end
537 c---------------------------------------------------------------------------
538       subroutine readpdb_template(k)
539 C Read the PDB file with gaps for read_constr_homology with read2sigma
540 C and convert the peptide geometry into virtual-chain geometry.
541       implicit real*8 (a-h,o-z)
542       include 'DIMENSIONS'
543       include 'COMMON.LOCAL'
544       include 'COMMON.VAR'
545       include 'COMMON.CHAIN'
546       include 'COMMON.INTERACT'
547       include 'COMMON.IOUNITS'
548       include 'COMMON.GEO'
549       include 'COMMON.NAMES'
550       include 'COMMON.CONTROL'
551       integer i,j,ibeg,ishift1,ires,iii,ires_old,ishift,ity
552       logical lprn /.false./,fail
553       double precision e1(3),e2(3),e3(3)
554       double precision dcj,efree_temp
555       character*3 seq,res
556       character*5 atom
557       character*80 card
558       double precision sccor(3,20)
559       integer rescode,iterter(maxres)
560       do i=1,maxres
561          iterter(i)=0
562       enddo
563       ibeg=1
564       ishift1=0
565       ishift=0
566 c      write (2,*) "UNRES_PDB",unres_pdb
567       ires=0
568       ires_old=0
569       iii=0
570       lsecondary=.false.
571       nhfrag=0
572       nbfrag=0
573       do
574         read (ipdbin,'(a80)',end=10) card
575         if (card(:3).eq.'END') then
576           goto 10
577         else if (card(:3).eq.'TER') then
578 C End current chain
579           ires_old=ires+2
580           itype(ires_old-1)=ntyp1 
581           iterter(ires_old-1)=1
582           itype(ires_old)=ntyp1
583           iterter(ires_old)=1
584           ibeg=2
585 c          write (iout,*) "Chain ended",ires,ishift,ires_old
586           if (unres_pdb) then
587             do j=1,3
588               dc(j,ires)=sccor(j,iii)
589             enddo
590           else 
591             call sccenter(ires,iii,sccor)
592           endif
593         endif
594 C Fish out the ATOM cards.
595         if (index(card(1:4),'ATOM').gt.0) then  
596           read (card(12:16),*) atom
597 c          write (iout,*) "! ",atom," !",ires
598 c          if (atom.eq.'CA' .or. atom.eq.'CH3') then
599           read (card(23:26),*) ires
600           read (card(18:20),'(a3)') res
601 c          write (iout,*) "ires",ires,ires-ishift+ishift1,
602 c     &      " ires_old",ires_old
603 c          write (iout,*) "ishift",ishift," ishift1",ishift1
604 c          write (iout,*) "IRES",ires-ishift+ishift1,ires_old
605           if (ires-ishift+ishift1.ne.ires_old) then
606 C Calculate the CM of the preceding residue.
607             if (ibeg.eq.0) then
608               if (unres_pdb) then
609                 do j=1,3
610                   dc(j,ires)=sccor(j,iii)
611                 enddo
612               else
613                 call sccenter(ires_old,iii,sccor)
614               endif
615               iii=0
616             endif
617 C Start new residue.
618             if (res.eq.'Cl-' .or. res.eq.'Na+') then
619               ires=ires_old
620               cycle
621             else if (ibeg.eq.1) then
622 c              write (iout,*) "BEG ires",ires
623               ishift=ires-1
624               if (res.ne.'GLY' .and. res.ne. 'ACE') then
625                 ishift=ishift-1
626                 itype(1)=ntyp1
627               endif
628               ires=ires-ishift+ishift1
629               ires_old=ires
630 c              write (iout,*) "ishift",ishift," ires",ires,
631 c     &         " ires_old",ires_old
632 c              write (iout,*) "ires",ires," ibeg",ibeg," ishift",ishift
633               ibeg=0          
634             else if (ibeg.eq.2) then
635 c Start a new chain
636               ishift=-ires_old+ires-1
637               ires=ires_old+1
638 c              write (iout,*) "New chain started",ires,ishift
639               ibeg=0          
640             else
641               ishift=ishift-(ires-ishift+ishift1-ires_old-1)
642               ires=ires-ishift+ishift1
643               ires_old=ires
644             endif
645             if (res.eq.'ACE' .or. res.eq.'NHE') then
646               itype(ires)=10
647             else
648               itype(ires)=rescode(ires,res,0)
649             endif
650           else
651             ires=ires-ishift+ishift1
652           endif
653 c          write (iout,*) "ires_old",ires_old," ires",ires
654 c          if (card(27:27).eq."A" .or. card(27:27).eq."B") then
655 c            ishift1=ishift1+1
656 c          endif
657 c          write (2,*) "ires",ires," res ",res," ity",ity
658           if (atom.eq.'CA' .or. atom.eq.'CH3' .or. 
659      &       res.eq.'NHE'.and.atom(:2).eq.'HN') then
660             read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
661 c            write (iout,*) "backbone ",atom ,ires,res, (c(j,ires),j=1,3)
662 #ifdef DEBUG
663             write (iout,'(2i3,2x,a,3f8.3)') 
664      &      ires,itype(ires),res,(c(j,ires),j=1,3)
665 #endif
666             iii=iii+1
667             do j=1,3
668               sccor(j,iii)=c(j,ires)
669             enddo
670             if (ishift.ne.0) then
671               ires_ca=ires+ishift-ishift1
672             else
673               ires_ca=ires
674             endif
675 c            write (*,*) card(23:27),ires,itype(ires)
676           else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
677      &             atom.ne.'N' .and. atom.ne.'C' .and.
678      &             atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
679      &             atom.ne.'OXT' .and. atom(:2).ne.'3H') then
680 c            write (iout,*) "sidechain ",atom
681             iii=iii+1
682             read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
683           endif
684         endif
685       enddo
686    10 write (iout,'(a,i5)') ' Nres: ',ires
687 C Calculate dummy residue coordinates inside the "chain" of a multichain
688 C system
689       nres=ires
690       do i=2,nres-1
691 c        write (iout,*) i,itype(i),itype(i+1)
692         if (itype(i).eq.ntyp1.and.iterter(i).eq.1) then
693          if (itype(i+1).eq.ntyp1.and.iterter(i+1).eq.1 ) then
694 C 16/01/2014 by Adasko: Adding to dummy atoms in the chain
695 C first is connected prevous chain (itype(i+1).eq.ntyp1)=true
696 C second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
697            if (unres_pdb) then
698 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
699             call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
700             if (fail) then
701               e2(1)=0.0d0
702               e2(2)=1.0d0
703               e2(3)=0.0d0
704             endif !fail
705             do j=1,3
706              c(j,i)=c(j,i-1)-1.9d0*e2(j)
707             enddo
708            else   !unres_pdb
709            do j=1,3
710              dcj=(c(j,i-2)-c(j,i-3))/2.0
711             if (dcj.eq.0) dcj=1.23591524223
712              c(j,i)=c(j,i-1)+dcj
713              c(j,nres+i)=c(j,i)
714            enddo     
715           endif   !unres_pdb
716          else     !itype(i+1).eq.ntyp1
717           if (unres_pdb) then
718 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
719             call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
720             if (fail) then
721               e2(1)=0.0d0
722               e2(2)=1.0d0
723               e2(3)=0.0d0
724             endif
725             do j=1,3
726               c(j,i)=c(j,i+1)-1.9d0*e2(j)
727             enddo
728           else !unres_pdb
729            do j=1,3
730             dcj=(c(j,i+3)-c(j,i+2))/2.0
731             if (dcj.eq.0) dcj=1.23591524223
732             c(j,i)=c(j,i+1)-dcj
733             c(j,nres+i)=c(j,i)
734            enddo
735           endif !unres_pdb
736          endif !itype(i+1).eq.ntyp1
737         endif  !itype.eq.ntyp1
738       enddo
739 C Calculate the CM of the last side chain.
740       if (unres_pdb) then
741         do j=1,3
742           dc(j,ires)=sccor(j,iii)
743         enddo
744       else
745         call sccenter(ires,iii,sccor)
746       endif
747       nsup=nres
748       nstart_sup=1
749       if (itype(nres).ne.10) then
750         nres=nres+1
751         itype(nres)=ntyp1
752         if (unres_pdb) then
753 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
754           call refsys(nres-3,nres-2,nres-1,e1,e2,e3,fail)
755           if (fail) then
756             e2(1)=0.0d0
757             e2(2)=1.0d0
758             e2(3)=0.0d0
759           endif
760           do j=1,3
761             c(j,nres)=c(j,nres-1)-1.9d0*e2(j)
762           enddo
763         else
764         do j=1,3
765           dcj=(c(j,nres-2)-c(j,nres-3))/2.0
766             if (dcj.eq.0) dcj=1.23591524223
767           c(j,nres)=c(j,nres-1)+dcj
768           c(j,2*nres)=c(j,nres)
769         enddo
770       endif
771       endif
772       do i=2,nres-1
773         do j=1,3
774           c(j,i+nres)=dc(j,i)
775         enddo
776       enddo
777       do j=1,3
778         c(j,nres+1)=c(j,1)
779         c(j,2*nres)=c(j,nres)
780       enddo
781       if (itype(1).eq.ntyp1) then
782         nsup=nsup-1
783         nstart_sup=2
784         if (unres_pdb) then
785 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
786           call refsys(2,3,4,e1,e2,e3,fail)
787           if (fail) then
788             e2(1)=0.0d0
789             e2(2)=1.0d0
790             e2(3)=0.0d0
791           endif
792           do j=1,3
793             c(j,1)=c(j,2)-1.9d0*e2(j)
794           enddo
795         else
796         do j=1,3
797           dcj=(c(j,4)-c(j,3))/2.0
798           c(j,1)=c(j,2)-dcj
799           c(j,nres+1)=c(j,1)
800         enddo
801         endif
802       endif
803 C Calculate internal coordinates.
804       if (lprn) then
805       write (iout,'(/a)') 
806      &  "Cartesian coordinates of the reference structure"
807       write (iout,'(a,3(3x,a5),5x,3(3x,a5))') 
808      & "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
809       do ires=1,nres
810         write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)') 
811      &    restyp(itype(ires)),ires,(c(j,ires),j=1,3),
812      &    (c(j,ires+nres),j=1,3)
813       enddo
814       endif
815 C Calculate internal coordinates.
816        write (iout,'(a)') 
817      &   "Backbone and SC coordinates as read from the PDB"
818        do ires=1,nres
819         write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)') 
820      &    ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
821      &    (c(j,nres+ires),j=1,3)
822        enddo
823       call int_from_cart(.true.,.false.)
824       call sc_loc_geom(.false.)
825       do i=1,nres
826         thetaref(i)=theta(i)
827         phiref(i)=phi(i)
828       enddo
829       do i=1,nres-1
830         do j=1,3
831           dc(j,i)=c(j,i+1)-c(j,i)
832           dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
833         enddo
834       enddo
835       do i=2,nres-1
836         do j=1,3
837           dc(j,i+nres)=c(j,i+nres)-c(j,i)
838           dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
839         enddo
840 c        write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
841 c     &   vbld_inv(i+nres)
842       enddo
843       do i=1,nres
844         do j=1,3
845           cref(j,i)=c(j,i)
846           cref(j,i+nres)=c(j,i+nres)
847         enddo
848       enddo
849       do i=1,2*nres
850         do j=1,3
851           chomo(j,i,k)=c(j,i)
852         enddo
853       enddo
854
855       return
856       end
857       
858