unres_package_Oct_2016 from emilial
[unres4.git] / source / unres / io_base.f90
index f5c7bbf..f86b4dd 100644 (file)
@@ -5,10 +5,18 @@
       implicit none
 !-----------------------------------------------------------------------------
 ! Max. number of AA residues
-      integer,parameter :: maxres=4000!1200
+      integer,parameter :: maxres=6000!1200
 ! Appr. max. number of interaction sites
       integer,parameter :: maxres2=2*maxres
+!      parameter (maxres6=6*maxres)
+!      parameter (mmaxres2=(maxres2*(maxres2+1)/2))
 !-----------------------------------------------------------------------------
+! Max. number of S-S bridges
+!      integer,parameter :: maxss=20
+!-----------------------------------------------------------------------------
+! Max. number of derivatives of virtual-bond and side-chain vectors in theta
+! or phi.
+!      integer,parameter :: maxdim=(maxres-1)*(maxres-2)/2
 !-----------------------------------------------------------------------------
 !
 !
@@ -77,7 +85,7 @@
       enddo
 ! Read preformed bridges.
       if (ns.gt.0) then
-      read (inp,*) nss
+        read (inp,*) nss
       if (nss.gt.0) then
         if(.not.allocated(ihpb)) allocate(ihpb(nss))
         if(.not.allocated(jhpb)) allocate(jhpb(nss))
         enddo
       endif
       endif
-!write(iout,*) "end read_bridge"
+!      write(iout,*) "end read_bridge"
       return
       end subroutine read_bridge
 !-----------------------------------------------------------------------------
 !      include 'COMMON.CONTROL'
 !      include 'COMMON.LOCAL'
 !      include 'COMMON.INTERACT'
+! Read coordinates from input
 !
 !el local variables
       integer :: l,k,j,i,kanal
 
-! Read coordinates from input
-!
       read(kanal,'(8f10.5)',end=10,err=10) &
         ((c(l,k),l=1,3),k=1,nres),&
         ((c(l,k+nres),l=1,3),k=nnt,nct)
       end subroutine read_threadbase
 !-----------------------------------------------------------------------------
 #ifdef WHAM_RUN
-      subroutine read_angles(kanal,iscor,energ,iprot,*)
+!el      subroutine read_angles(kanal,iscor,energ,iprot,*)
+      subroutine read_angles(kanal,*)
 
       use geometry_data
       use energy_data
       subroutine read_angles(kanal,*)
 
       use geometry_data
+   !  use energy
+   !  use control
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.GEO'
 !-----------------------------------------------------------------------------
       subroutine read_dist_constr
       use MPI_data
+   !  use control
       use geometry, only: dist
       use geometry_data
       use control_data
 
       use geometry_data, only: c,nres
       use energy_data
+   !  use control
       use compare_data
       use MD_data
 !      implicit real*8 (a-h,o-z)
 ! format.
       use geometry_data, only: c
       use energy_data
+   !  use control
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.CHAIN'
       return
       end subroutine intout
 !-----------------------------------------------------------------------------
+#ifdef CLUSTER
+      subroutine briefout(it,ener,free)!,plik)
+#else
       subroutine briefout(it,ener)
-
+#endif
       use geometry_data
       use energy_data
+   !  use control
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.IOUNITS'
 !     print '(a,i5)',intname,igeom
 !el  local variables
       integer :: i,it
-      real(kind=8) :: ener
-#ifdef WHAM_RUN
-      integer :: iii
-#endif
+      real(kind=8) :: ener,free
+!     character(len=80) :: plik
+!      integer :: iii
 
 #if defined(AIX) || defined(PGI)
       open (igeom,file=intname,position='append')
       open (igeom,file=intname,access='append')
 #endif
 #ifdef WHAM_RUN
-      iii=igeom
+!      iii=igeom
       igeom=iout
 #endif
       IF (NSS.LE.9) THEN
+#ifdef CLUSTER
+        WRITE (igeom,180) IT,ENER,free,NSS,(IHPB(I),JHPB(I),I=1,NSS)
+      ELSE
+        WRITE (igeom,180) IT,ENER,free,NSS,(IHPB(I),JHPB(I),I=1,8)
+#else
         WRITE (igeom,180) IT,ENER,NSS,(IHPB(I),JHPB(I),I=1,NSS)
       ELSE
         WRITE (igeom,180) IT,ENER,NSS,(IHPB(I),JHPB(I),I=1,9)
+#endif
         WRITE (igeom,190) (IHPB(I),JHPB(I),I=10,NSS)
       ENDIF
 !     IF (nvar.gt.nphi) WRITE (igeom,200) (RAD2DEG*THETA(I),I=3,NRES)
       end subroutine reads
 #endif
 !-----------------------------------------------------------------------------
+! permut.F
+!-----------------------------------------------------------------------------
+      subroutine permut(isym)
+
+      use geometry_data, only: tabperm
+!      implicit real*8 (a-h,o-z) 
+!      include 'DIMENSIONS'
+!      include 'COMMON.LOCAL'
+!      include 'COMMON.VAR'
+!      include 'COMMON.CHAIN'
+!      include 'COMMON.INTERACT'
+!      include 'COMMON.IOUNITS'
+!      include 'COMMON.GEO'
+!      include 'COMMON.NAMES'
+!      include 'COMMON.CONTROL'
+
+      integer :: n,isym
+!      logical nextp
+!el      external nextp
+      integer,dimension(isym) :: a
+!      parameter(n=symetr)
+!el local variables
+      integer :: kkk,i
+
+      n=isym
+      if (n.eq.1) then
+        tabperm(1,1)=1
+        return
+      endif
+      kkk=0
+      do i=1,n
+      a(i)=i
+      enddo
+   10 print *,(a(i),i=1,n)
+      kkk=kkk+1
+      do i=1,n
+      tabperm(kkk,i)=a(i)
+!      write (iout,*) "tututu", kkk
+      enddo
+      if(nextp(n,a)) go to 10
+      return
+      end subroutine permut
+!-----------------------------------------------------------------------------
+      logical function nextp(n,a)
+
+      integer :: n,i,j,k,t
+!      logical :: nextp
+      integer,dimension(n) :: a
+      i=n-1
+   10 if(a(i).lt.a(i+1)) go to 20
+      i=i-1
+      if(i.eq.0) go to 20
+      go to 10
+   20 j=i+1
+      k=n
+   30 t=a(j)
+      a(j)=a(k)
+      a(k)=t
+      j=j+1
+      k=k-1
+      if(j.lt.k) go to 30
+      j=i
+      if(j.ne.0) go to 40
+      nextp=.false.
+      return
+   40 j=j+1
+      if(a(j).lt.a(i)) go to 40
+      t=a(i)
+      a(i)=a(j)
+      a(j)=t
+      nextp=.true.
+      return
+      end function nextp
+!-----------------------------------------------------------------------------
 !-----------------------------------------------------------------------------
       end module io_base