changes in wham and unres
[unres4.git] / source / wham / io_database.f90
index 13d4f37..e5ab5bc 100644 (file)
@@ -4,7 +4,8 @@
       use wham_data
       use io_units
       use io_base, only:ilen
-      use energy_data, only:nnt,nct,nss,ihpb,jhpb,iset
+      use energy_data, only:nnt,nct,nss,ihpb,jhpb
+      use MD_data, only:iset
       use geometry_data, only:nres,c
 #ifdef MPI
       use MPI_data
@@ -393,7 +394,7 @@ write(iout,*) "end of read database"
 !--------------------------------------------------------------------------------
       subroutine cxread(nazwa,ii,jj,kk,ll,mm,iR,ib,iparm,*)
 
-#define DEBUG
+!#define DEBUG
 #ifdef DEBUG
       use geometry, only:int_from_cart1
       use geometry_data, only:vbld,rad2deg,theta,phi,alph,omeg
@@ -468,7 +469,7 @@ write(iout,*) "end of read database"
       call xdrffloat_(ixdrf, rtime, iret)
       print *,"rtime",rtime," iret",iret !d
       call xdrffloat_(ixdrf, rpotE, iret)
-      write (iout,*) "rpotE",rpotE," iret",iret !d
+!      write (iout,*) "rpotE",rpotE," iret",iret !d
       call flush(iout)
       call xdrffloat_(ixdrf, ruconst, iret)
       call xdrffloat_(ixdrf, rt_bath, iret)
@@ -486,7 +487,7 @@ write(iout,*) "end of read database"
 #else
       call xdrffloat(ixdrf, rtime, iret)
       call xdrffloat(ixdrf, rpotE, iret)
-      write (iout,*) "rpotE",rpotE," iret",iret !d
+!      write (iout,*) "rpotE",rpotE," iret",iret !d
       call flush(iout)
       call xdrffloat(ixdrf, ruconst, iret)
       call xdrffloat(ixdrf, rt_bath, iret)
@@ -496,7 +497,7 @@ write(iout,*) "end of read database"
         call xdrfint(ixdrf, jhpb(j), iret)
       enddo
       call xdrfint(ixdrf, nprop, iret)
-      write (iout,*) "nprop",nprop !d
+!      write (iout,*) "nprop",nprop !d
       if (it.gt.0 .and. nprop.ne.nprop_prev) then
         write (iout,*) "Warning previous nprop",nprop_prev,&
          " current",nprop
@@ -513,7 +514,7 @@ write(iout,*) "end of read database"
 #endif
       if (iret.eq.0) exit
       itraj=mod(it,totraj(iR,iparm))
-#define DEBUG
+!#define DEBUG
 #ifdef DEBUG
       write (iout,*) "ii",ii," itraj",itraj," it",it
 #endif
@@ -541,7 +542,7 @@ write(iout,*) "end of read database"
 #ifdef DEBUG
       write (iout,'(10f8.3)') ((xoord(j,i),j=1,3),i=1,2*nres+2)
 #endif
-#undef DEBUG
+!#undef DEBUG
       if (iret.eq.0) exit
       if (itmp .ne. nres + nct - nnt + 1) then
         write (iout,*) "Error: inconsistent sizes",itmp,nres+nct-nnt+1
@@ -550,10 +551,10 @@ write(iout,*) "end of read database"
       endif
 
       time=rtime
-      write (iout,*) "calling slice" !d
+!      write (iout,*) "calling slice" !d
       call flush(iout) !d
       islice=slice(nstep(itraj),time,is,ie,ts,te)
-      write (iout,*) "islice",islice !d
+!      write (iout,*) "islice",islice !d
       call flush(iout) !d
 
       do i=1,nres
@@ -703,7 +704,7 @@ write(iout,*) "end of read database"
         " conformations stored so far, slice",islice
       enddo
       call flush(iout)
-#undef DEBUG
+!#undef DEBUG
       return
       end subroutine cxread
 !--------------------------------------------------------------------------------
@@ -1370,7 +1371,7 @@ write(iout,*) "end of read database"
 
       use names, only:ntyp1
       use geometry_data
-      use energy_data, only:itype,dsc
+      use energy_data, only:itype,dsc,molnum
       use geometry, only:int_from_cart1
 !      use 
 !      include "DIMENSIONS"
@@ -1402,14 +1403,16 @@ write(iout,*) "end of read database"
       include "mpif.h"
       integer :: IERROR,ERRCODE,STATUS(MPI_STATUS_SIZE)
 #endif
-      integer :: j,k,l,ii,itj,iprint
+      integer :: j,k,l,ii,itj,iprint,mnum
       if (.not. check_conf) then
         conf_check=.true.
         return
       endif
       call int_from_cart1(.false.)
       do j=nnt+1,nct
-        if (itype(j-1).ne.ntyp1 .and. itype(j).ne.ntyp1 .and. &
+         mnum=molnum(j)
+         if (mnum.eq.5) cycle
+        if (itype(j-1,mnum).ne.ntyp1 .and. itype(j,mnum).ne.ntyp1_molec(mnum) .and. &
           (vbld(j).lt.2.0d0 .or. vbld(j).gt.5.0d0)) then
           if (iprint.gt.0) &
           write (iout,*) "Bad CA-CA bond length",j," ",vbld(j),&
@@ -1433,8 +1436,10 @@ write(iout,*) "end of read database"
         endif
       enddo
       do j=nnt,nct
-        itj=itype(j)
-        if (itype(j).ne.10 .and.itype(j).ne.ntyp1 .and. &
+        mnum=molnum(j)
+        if (mnum.eq.5) cycle
+        itj=itype(j,mnum)
+        if (itype(j,mnum).ne.10 .and.itype(j,mnum).ne.ntyp1_molec(mnum) .and. &
            (vbld(nres+j)-dsc(iabs(itj))).gt.2.0d0) then
           if (iprint.gt.0) &
           write (iout,*) "Bad CA-SC bond length",j," ",vbld(nres+j),&