changes in wham and unres
[unres4.git] / source / unres / io_base.f90
index 79a6ea2..4be9dfe 100644 (file)
 !      include 'COMMON.SETUP'
 !el local variables
       integer :: i,j,ierror
-
+      print *,"ENTER READ"
 ! Read bridging residues.
       read (inp,*) ns
+      write(iout,*) "ns",ns
+      call flush(iout)
       if (ns.gt.0) then
         allocate(iss(ns))
         read (inp,*) (iss(i),i=1,ns)
         enddo
       endif
       endif
-!      write(iout,*) "end read_bridge"
+      write(iout,*) "end read_bridge"
       return
       end subroutine read_bridge
 !-----------------------------------------------------------------------------
       ichain=1
       ires=0
       do i=nnt,nct
-        iti=itype(i,1)
-        iti1=itype(i+1,1)
-        if ((iti.eq.ntyp1).and.(iti1.eq.ntyp1)) cycle
-        if (iti.eq.ntyp1) then
+        iti=itype(i,molnum(i))
+        print *,i,molnum(i)
+        if (molnum(i+1).eq.0) then
+        iti1=ntyp1_molec(molnum(i))
+        else
+        iti1=itype(i+1,molnum(i+1))
+        endif
+        if ((iti.eq.ntyp1_molec(molnum(i))).and.(iti1.eq.ntyp1_molec(molnum(i)))) cycle
+        if (i.lt.nnt) then
+        if (iti.eq.ntyp1_molec(molnum(i)).and.(molnum(i+1).eq.5)) cycle
+        endif
+        if (iti.eq.ntyp1_molec(molnum(i))) then
           ichain=ichain+1
 !          ires=0
           write (iunit,'(a)') 'TER'
         ires=ires+1
         iatom=iatom+1
         ica(i)=iatom
-        write (iunit,10) iatom,restyp(iti,1),chainid(ichain),&
+        if (molnum(i).eq.1) then
+        write (iunit,10) iatom,restyp(iti,molnum(i)),chainid(ichain),&
+           ires,(c(j,i),j=1,3),vtot(i)
+        elseif(molnum(i).eq.2) then
+           if (istype(i).eq.0) istype(i)=1
+        write (iunit,40) iatom,sugartyp(istype(i)),restyp(iti,2), &
+          chainid(ichain),ires,(c(j,i),j=1,3),vtot(i)
+        else
+        write (iunit,60) iatom,restyp(iti,molnum(i)),chainid(ichain),&
            ires,(c(j,i),j=1,3),vtot(i)
-        if (iti.ne.10) then
+        endif
+        if ((iti.ne.10).and.(molnum(i).ne.5)) then
           iatom=iatom+1
-          write (iunit,20) iatom,restyp(iti,1),chainid(ichain),&
+          if (molnum(i).eq.1) then
+           write (iunit,20) iatom,restyp(iti,1),chainid(ichain),&
             ires,(c(j,nres+i),j=1,3),&
             vtot(i+nres)
+           else if (molnum(i).eq.2) then
+           if (istype(i).eq.0) istype(i)=1
+          write (iunit,50) iatom,sugartyp(istype(i)),restyp(iti,2), &
+           chainid(ichain),ires,(c(j,nres+i),j=1,3),vtot(i+nres)
+           endif
+
         endif
         endif
       enddo
       write (iunit,'(a)') 'TER'
       do i=nnt,nct-1
         if (itype(i,1).eq.ntyp1) cycle
-        if (itype(i,1).eq.10 .and. itype(i+1,1).ne.ntyp1) then
+        if ((itype(i,1).eq.10 .and. itype(i+1,1).ne.ntyp1).or.(molnum(i).eq.5)) then
           write (iunit,30) ica(i),ica(i+1)
         else if (itype(i,1).ne.10 .and. itype(i+1,1).ne.ntyp1) then
           write (iunit,30) ica(i),ica(i+1),ica(i)+1
           write (iunit,30) ica(i),ica(i)+1
         endif
       enddo
-      if (itype(nct,1).ne.10) then
+      if ((itype(nct,1).ne.10).and.(molnum(i).ne.5)) then
         write (iunit,30) ica(nct),ica(nct)+1
       endif
       do i=1,nss
       enddo
       write (iunit,'(a6)') 'ENDMDL'     
   10  FORMAT ('ATOM',I7,'  CA  ',A3,1X,A1,I4,4X,3F8.3,f15.3)
+
   20  FORMAT ('ATOM',I7,'  CB  ',A3,1X,A1,I4,4X,3F8.3,f15.3)
+  40  FORMAT ("ATOM",I7,"  C5' ",1X,2A1,1X,A1,I4,4X,3F8.3,f15.3)
+  50  FORMAT ("ATOM",I7,"  C1' ",1X,2A1,1X,A1,I4,4X,3F8.3,f15.3)
+
   30  FORMAT ('CONECT',8I5)
+  60  FORMAT ('HETATM',I5,'  CA  ',A3,1X,A1,I4,4X,3F8.3,f15.3)
+
       return
       end subroutine pdbout
 !-----------------------------------------------------------------------------