The itype(;) extension to itype(:,:)
[unres4.git] / source / unres / io_base.f90
index 0e1a986..303927a 100644 (file)
 ! Check whether the specified bridging residues are cystines.
       do i=1,ns
          write(iout,*) i,iss(i)
-       if (itype(iss(i)).ne.1) then
+       if (itype(iss(i),1).ne.1) then
          if (me.eq.king.or..not.out1file) write (iout,'(2a,i3,a)') &
          'Do you REALLY think that the residue ',&
-          restyp(itype(iss(i))),i,&
+          restyp(itype(iss(i),1)),i,&
          ' can form a disulfide bridge?!!!'
          write (*,'(2a,i3,a)') &
          'Do you REALLY think that the residue ',&
-          restyp(itype(iss(i))),i,&
+          restyp(itype(iss(i),1)),i,&
          ' can form a disulfide bridge?!!!'
 #ifdef MPI
         call MPI_Finalize(MPI_COMM_WORLD,ierror)
         enddo
       enddo
       do i=nnt,nct
-        if (itype(i).ne.10 .and. itype(i).ne.ntyp1) then
+        if (itype(i,1).ne.10 .and. itype(i,1).ne.ntyp1) then
           do j=1,3
             dc(j,i+nres)=c(j,i+nres)-c(j,i)
             dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
 !model      write (iunit,'(a5,i6)') 'MODEL',1
       if (nhfrag.gt.0) then
        do j=1,nhfrag
-        iti=itype(hfrag(1,j))
-        itj=itype(hfrag(2,j))
+        iti=itype(hfrag(1,j),1)
+        itj=itype(hfrag(2,j),1)
         if (j.lt.10) then
            write (iunit,'(a5,i5,1x,a1,i1,2x,a3,i7,2x,a3,i7,i3,t76,i5)') &
                  'HELIX',j,'H',j,&
 
        do j=1,nbfrag
 
-        iti=itype(bfrag(1,j))
-        itj=itype(bfrag(2,j)-1)
+        iti=itype(bfrag(1,j),1)
+        itj=itype(bfrag(2,j)-1,1)
 
         write (iunit,'(a5,i5,1x,a1,i1,i3,1x,a3,i6,2x,a3,i6,i3)') &
                  'SHEET',1,'B',j,2,&
 
         if (bfrag(3,j).gt.bfrag(4,j)) then
 
-         itk=itype(bfrag(3,j))
-         itl=itype(bfrag(4,j)+1)
+         itk=itype(bfrag(3,j),1)
+         itl=itype(bfrag(4,j)+1,1)
 
          write (iunit,'(a5,i5,1x,a1,i1,i3,1x,a3,i6,2x,a3,i6,i3,2x,a1,2x,a3,i6,3x,a1,2x,a3,i6)') &
                  'SHEET',2,'B',j,2,&
 
         else
 
-         itk=itype(bfrag(3,j))
-         itl=itype(bfrag(4,j)-1)
+         itk=itype(bfrag(3,j),1)
+         itl=itype(bfrag(4,j)-1,1)
 
 
         write (iunit,'(a5,i5,1x,a1,i1,i3,1x,a3,i6,2x,a3,i6,i3,2x,a1,2x,a3,i6,3x,a1,2x,a3,i6)') &
       ichain=1
       ires=0
       do i=nnt,nct
-        iti=itype(i)
-        iti1=itype(i+1)
+        iti=itype(i,1)
+        iti1=itype(i+1,1)
         if ((iti.eq.ntyp1).and.(iti1.eq.ntyp1)) cycle
         if (iti.eq.ntyp1) then
           ichain=ichain+1
       enddo
       write (iunit,'(a)') 'TER'
       do i=nnt,nct-1
-        if (itype(i).eq.ntyp1) cycle
-        if (itype(i).eq.10 .and. itype(i+1).ne.ntyp1) then
+        if (itype(i,1).eq.ntyp1) cycle
+        if (itype(i,1).eq.10 .and. itype(i+1,1).ne.ntyp1) then
           write (iunit,30) ica(i),ica(i+1)
-        else if (itype(i).ne.10 .and. itype(i+1).ne.ntyp1) then
+        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
-        else if (itype(i).ne.10 .and. itype(i+1).eq.ntyp1) then
+        else if (itype(i,1).ne.10 .and. itype(i+1,1).eq.ntyp1) then
           write (iunit,30) ica(i),ica(i)+1
         endif
       enddo
-      if (itype(nct).ne.10) then
+      if (itype(nct,1).ne.10) then
         write (iunit,30) ica(nct),ica(nct)+1
       endif
       do i=1,nss
       write (imol2,'(a)') '\@<TRIPOS>ATOM' 
       do i=nnt,nct
         write (zahl,'(i3)') i
-        pom=ucase(restyp(itype(i)))
+        pom=ucase(restyp(itype(i,1)))
         res_num = pom(:3)//zahl(2:)
         write (imol2,10) i,(c(j,i),j=1,3),i,res_num,0.0
       enddo
       write (imol2,'(a)') '\@<TRIPOS>SUBSTRUCTURE'
       do i=nnt,nct
         write (zahl,'(i3)') i
-        pom = ucase(restyp(itype(i)))
+        pom = ucase(restyp(itype(i,1)))
         res_num = pom(:3)//zahl(2:)
         write (imol2,30) i-nnt+1,res_num,i-nnt+1,0
       enddo
       write (iout,'(7a)') '  Res  ','         d','     Theta',&
        '       Phi','       Dsc','     Alpha','      Omega'
       do i=1,nres
-       iti=itype(i)
+       iti=itype(i,1)
         write (iout,'(a3,i4,6f10.3)') restyp(iti),i,vbld(i),&
            rad2deg*theta(i),rad2deg*phi(i),vbld(nres+i),rad2deg*alph(i),&
            rad2deg*omeg(i)