changes for added xdrfpdb
authorEmilia Lubecka <emilia.lubecka@ug.edu.pl>
Fri, 6 Apr 2018 13:54:15 +0000 (15:54 +0200)
committerEmilia Lubecka <emilia.lubecka@ug.edu.pl>
Fri, 6 Apr 2018 13:54:15 +0000 (15:54 +0200)
source/cluster/io_clust.f90
source/unres/control.F90
source/unres/io_base.f90
source/unres/io_config.f90
source/wham/io_wham.f90

index 7570389..1e24794 100644 (file)
                  indpdb
       use geometry, only: chainbuild,alloc_geo_arrays
       use energy, only: alloc_ener_arrays
-      use control, only: rescode,setup_var,init_int_table
+      use io_base, only: rescode
+      use control, only: setup_var,init_int_table
       use conform_compar, only: contact
 !      implicit none
 !      include 'DIMENSIONS'
index 413fe23..f7cba30 100644 (file)
       return
       end subroutine setup_var
 !-----------------------------------------------------------------------------
-! rescode.f
-!-----------------------------------------------------------------------------
-      integer function rescode(iseq,nam,itype,molecule)
-
-      use io_base, only: ucase
-!      implicit real*8 (a-h,o-z)
-!      include 'DIMENSIONS'
-!      include 'COMMON.NAMES'
-!      include 'COMMON.IOUNITS'
-      character(len=3) :: nam  !,ucase
-      integer :: iseq,itype,i
-      integer :: molecule
-      print *,molecule,nam
-      if (molecule.eq.1) then 
-      if (itype.eq.0) then
-
-      do i=-ntyp1_molec(molecule),ntyp1_molec(molecule)
-        if (ucase(nam).eq.restyp(i,molecule)) then
-          rescode=i
-          return
-        endif
-      enddo
-
-      else
-
-      do i=-ntyp1_molec(molecule),ntyp1_molec(molecule)
-        if (nam(1:1).eq.onelet(i)) then
-          rescode=i
-          return  
-        endif  
-      enddo
-
-      endif
-      else if (molecule.eq.2) then
-      do i=1,ntyp1_molec(molecule)
-         print *,nam(1:1),restyp(i,molecule)(1:1) 
-        if (nam(2:2).eq.restyp(i,molecule)(1:1)) then
-          rescode=i
-          return
-        endif
-      enddo
-      else if (molecule.eq.3) then
-       write(iout,*) "SUGAR not yet implemented"
-       stop
-      else if (molecule.eq.4) then
-       write(iout,*) "Explicit LIPID not yet implemented"
-       stop
-      else if (molecule.eq.5) then
-      do i=1,ntyp1_molec(molecule)
-        print *,i,restyp(i,molecule)(1:2)
-        if (ucase(nam(1:2)).eq.restyp(i,molecule)(1:2)) then
-          rescode=i
-          return
-        endif
-      enddo
-      else   
-       write(iout,*) "molecule not defined"
-      endif
-      write (iout,10) iseq,nam
-      stop
-   10 format ('**** Error - residue',i4,' has an unresolved name ',a3)
-      end function rescode
-      integer function sugarcode(sugar,ires)
-      character sugar
-      integer ires
-      if (sugar.eq.'D') then
-        sugarcode=1
-      else if (sugar.eq.' ') then
-        sugarcode=2
-      else
-        write (iout,*) 'UNKNOWN sugar type for residue',ires,' ',sugar
-        stop
-      endif
-      return
-      end function sugarcode
-
-!-----------------------------------------------------------------------------
 ! timing.F
 !-----------------------------------------------------------------------------
 ! $Date: 1994/10/05 16:41:52 $
index bec648e..d07c1f0 100644 (file)
@@ -5,7 +5,7 @@
       implicit none
 !-----------------------------------------------------------------------------
 ! Max. number of AA residues
-      integer,parameter :: maxres=6000!1200
+      integer,parameter :: maxres=6500!1200
 ! Appr. max. number of interaction sites
       integer,parameter :: maxres2=2*maxres
 !      parameter (maxres6=6*maxres)
@@ -25,6 +25,7 @@
 !-----------------------------------------------------------------------------
 ! readrtns_CSA.F
 !-----------------------------------------------------------------------------
+#ifndef XDRFPDB
       subroutine read_bridge
 ! Read information about disulfide bridges.
       use geometry_data, only: nres
       subroutine read_angles(kanal,*)
 
       use geometry_data
-   !  use energy
-   !  use control
+
+!      use energy
+!      use control
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.GEO'
 !-----------------------------------------------------------------------------
       subroutine gen_dist_constr2
       use MPI_data
-   !  use control
+!     use control
       use geometry, only: dist
       use geometry_data
       use control_data
    10 find_group=.false.
       return
       end function find_group
+#endif
 !-----------------------------------------------------------------------------
       logical function iblnk(charc)
       character(len=1) :: charc
       return
       end function iblnk
 !-----------------------------------------------------------------------------
+#ifndef XDRFPDB
       integer function ilen(string)
       character*(*) ::  string
 !EL      logical :: iblnk
       numm(1:1)=huj(inum2+1:inum2+1)
       return
       end subroutine numstr
+#endif
 !-----------------------------------------------------------------------------
       function ucase(string)
       integer :: i, k, idiff
 
       use geometry_data, only: c,nres
       use energy_data
-   !  use control
+!     use control
       use compare_data
       use MD_data
 !      implicit real*8 (a-h,o-z)
 !      include 'COMMON.MD'
 !el      character(len=50) :: tytul
       character*(*) :: tytul
-      character(len=1),dimension(10) :: chainid= (/'A','B','C','D','E','F','G','H','I','J'/)
+      character(len=1),dimension(10) :: chainid=  (/'A','B','C','D','E','F','G','H','I','J'/)
+#ifdef XDRFPDB
+      integer,dimension(maxres) :: ica !(maxres)
+#else
       integer,dimension(nres) :: ica   !(maxres)
-       integer iti1
+#endif
+      integer :: iti1
 !el  local variables
       integer :: j,iti,itj,itk,itl,i,iatom,ichain,ires,iunit
       real(kind=8) :: etot
       integer :: nres2
       nres2=2*nres
-
+#ifdef XDRFPDB
+      if(.not.allocated(molnum)) allocate(molnum(maxres))
+      molnum(:)=1
+      if(.not.allocated(vtot)) allocate(vtot(maxres*2)) !(maxres2)
+#else
       if(.not.allocated(vtot)) allocate(vtot(nres2)) !(maxres2)
+#endif
 
       write (iunit,'(3a,1pe15.5)') 'REMARK ',tytul,' ENERGY ',etot
 !model      write (iunit,'(a5,i6)') 'MODEL',1
+#ifndef XDRFPDB
       if (nhfrag.gt.0) then
        do j=1,nhfrag
         iti=itype(hfrag(1,j),1)
          
        enddo
       endif 
-
+#endif
       if (nss.gt.0) then
         do i=1,nss
          if (dyn_ss) then
 
       return
       end subroutine pdbout
+#ifndef XDRFPDB
 !-----------------------------------------------------------------------------
       subroutine MOL2out(etot,tytul)
 ! Prints the Cartesian coordinates of the alpha-carbons in the Tripos mol2 
 ! format.
       use geometry_data, only: c
       use energy_data
-   !  use control
+!      use control
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.CHAIN'
 
       use geometry_data
       use energy_data, only: itype
-   !  use control
+!      use control
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.IOUNITS'
 #endif
       use geometry_data
       use energy_data
-   !  use control
+!      use control
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.IOUNITS'
 #endif
 
       use geometry_data, only: c
-   !  use geometry
+!      use geometry
       use energy_data
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
       nextp=.true.
       return
       end function nextp
+#endif
+!-----------------------------------------------------------------------------
+! rescode.f
+!-----------------------------------------------------------------------------
+      integer function rescode(iseq,nam,itype,molecule)
+
+!      use io_base, only: ucase
+!      implicit real*8 (a-h,o-z)
+!      include 'DIMENSIONS'
+!      include 'COMMON.NAMES'
+!      include 'COMMON.IOUNITS'
+      character(len=3) :: nam   !,ucase
+      integer :: iseq,itype,i
+      integer :: molecule
+      print *,molecule,nam
+      if (molecule.eq.1) then
+      if (itype.eq.0) then
+
+      do i=-ntyp1_molec(molecule),ntyp1_molec(molecule)
+        if (ucase(nam).eq.restyp(i,molecule)) then
+          rescode=i
+          return
+        endif
+      enddo
+
+      else
+
+      do i=-ntyp1_molec(molecule),ntyp1_molec(molecule)
+        if (nam(1:1).eq.onelet(i)) then
+          rescode=i
+          return
+        endif
+      enddo
+
+      endif
+      else if (molecule.eq.2) then
+      do i=1,ntyp1_molec(molecule)
+         print *,nam(1:1),restyp(i,molecule)(1:1)
+        if (nam(2:2).eq.restyp(i,molecule)(1:1)) then
+          rescode=i
+          return
+        endif
+      enddo
+      else if (molecule.eq.3) then
+       write(iout,*) "SUGAR not yet implemented"
+       stop
+      else if (molecule.eq.4) then
+       write(iout,*) "Explicit LIPID not yet implemented"
+       stop
+      else if (molecule.eq.5) then
+      do i=1,ntyp1_molec(molecule)
+        print *,i,restyp(i,molecule)(1:2)
+        if (ucase(nam(1:2)).eq.restyp(i,molecule)(1:2)) then
+          rescode=i
+          return
+        endif
+      enddo
+      else
+       write(iout,*) "molecule not defined"
+      endif
+      write (iout,10) iseq,nam
+      stop
+   10 format ('**** Error - residue',i4,' has an unresolved name ',a3)
+      end function rescode
+      integer function sugarcode(sugar,ires)
+      character sugar
+      integer ires
+      if (sugar.eq.'D') then
+        sugarcode=1
+      else if (sugar.eq.' ') then
+        sugarcode=2
+      else
+        write (iout,*) 'UNKNOWN sugar type for residue',ires,' ',sugar
+        stop
+      endif
+      return
+      end function sugarcode
 !-----------------------------------------------------------------------------
 !-----------------------------------------------------------------------------
       end module io_base
index 7534c41..ee1402f 100644 (file)
       use control_data
       use compare_data
       use MPI_data
-      use control, only: rescode,sugarcode
+!      use control, only: rescode,sugarcode
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.LOCAL'
index eab5a49..7ebde6f 100644 (file)
       use energy_data
       use geometry_data, only:nres,deg2rad,c,dc,nres_molec
       use control_data, only:iscode
-      use control, only:rescode,setup_var,init_int_table
+      use io_base, only:rescode
+      use control, only:setup_var,init_int_table
       use geometry, only:alloc_geo_arrays
       use energy, only:alloc_ener_arrays      
 !      implicit real*8 (a-h,o-z)