constr_dist problem fixed
authorEmilia Lubecka <emilia.lubecka@ug.edu.pl>
Wed, 28 Mar 2018 10:52:30 +0000 (12:52 +0200)
committerEmilia Lubecka <emilia.lubecka@ug.edu.pl>
Wed, 28 Mar 2018 10:52:30 +0000 (12:52 +0200)
source/unres/MD.f90
source/unres/energy.f90
source/unres/io.f90
source/unres/io_base.f90

index 1d044a7..7aaac15 100644 (file)
 !      include 'COMMON.NAMES'
 !      include 'COMMON.TIME1'
       real(kind=8) :: xv,sigv,lowb,highb  ,Ek1
 !      include 'COMMON.NAMES'
 !      include 'COMMON.TIME1'
       real(kind=8) :: xv,sigv,lowb,highb  ,Ek1
-#define DEBUG
+!#define DEBUG
 #ifdef FIVEDIAG
        real(kind=8) ,allocatable, dimension(:)  :: DDU1,DDU2,DL2,DL1,xsolv,DML,rs
        real(kind=8) :: sumx
 #ifdef FIVEDIAG
        real(kind=8) ,allocatable, dimension(:)  :: DDU1,DDU2,DL2,DL1,xsolv,DML,rs
        real(kind=8) :: sumx
index cece655..55fdb4c 100644 (file)
 ! This subrouting calculates total Cartesian coordinate gradient. 
 ! The subroutine chainbuild_cart and energy MUST be called beforehand.
 !
 ! This subrouting calculates total Cartesian coordinate gradient. 
 ! The subroutine chainbuild_cart and energy MUST be called beforehand.
 !
-#define DEBUG
+!#define DEBUG
 #ifdef TIMING
       time00=MPI_Wtime()
 #endif
 #ifdef TIMING
       time00=MPI_Wtime()
 #endif
 #ifdef TIMING
             time_cartgrad=time_cartgrad+MPI_Wtime()-time00
 #endif
 #ifdef TIMING
             time_cartgrad=time_cartgrad+MPI_Wtime()-time00
 #endif
-#undef DEBUG
+!#undef DEBUG
             return
             end subroutine cartgrad
       !-----------------------------------------------------------------------------
             return
             end subroutine cartgrad
       !-----------------------------------------------------------------------------
index 331210b..cc8b681 100644 (file)
           call contact(.true.,ncont_ref,icont_ref,co)
         endif
 !        write (iout,*) "constr_dist",constr_dist,nstart_sup,nsup
           call contact(.true.,ncont_ref,icont_ref,co)
         endif
 !        write (iout,*) "constr_dist",constr_dist,nstart_sup,nsup
-        call flush(iout)
-        if (constr_dist.gt.0) call read_dist_constr
-        write (iout,*) "After read_dist_constr nhpb",nhpb
-        if ((AFMlog.gt.0).or.(selfguide.gt.0)) call read_afminp
-        call hpb_partition
+!        call flush(iout)
+!EL        if (constr_dist.gt.0) call read_dist_constr
+!EL        write (iout,*) "After read_dist_constr nhpb",nhpb
+!EL        if ((AFMlog.gt.0).or.(selfguide.gt.0)) call read_afminp
+!EL        call hpb_partition
         if(me.eq.king.or..not.out1file) &
          write (iout,*) 'Contact order:',co
         if (pdbref) then
         if(me.eq.king.or..not.out1file) &
          write (iout,*) 'Contact order:',co
         if (pdbref) then
         enddo
         endif
       endif
         enddo
         endif
       endif
+        if (constr_dist.gt.0) call read_dist_constr
+        write (iout,*) "After read_dist_constr nhpb",nhpb
+        if ((AFMlog.gt.0).or.(selfguide.gt.0)) call read_afminp
+        call hpb_partition
+
       if (indpdb.eq.0 .and. modecalc.ne.2 .and. modecalc.ne.4 &
           .and. modecalc.ne.8 .and. modecalc.ne.9 .and. &
           modecalc.ne.10) then
       if (indpdb.eq.0 .and. modecalc.ne.2 .and. modecalc.ne.4 &
           .and. modecalc.ne.8 .and. modecalc.ne.9 .and. &
           modecalc.ne.10) then
index 4be9dfe..bec648e 100644 (file)
 !-----------------------------------------------------------------------------
       subroutine read_dist_constr
       use MPI_data
 !-----------------------------------------------------------------------------
       subroutine read_dist_constr
       use MPI_data
-   !  use control
+!     use control
       use geometry, only: dist
       use geometry_data
       use control_data
       use geometry, only: dist
       use geometry_data
       use control_data
       if(.not.allocated(dhpb1)) allocate(dhpb1(maxdim))
       if(.not.allocated(forcon)) allocate(forcon(maxdim))
       if(.not.allocated(fordepth)) allocate(fordepth(maxdim))
       if(.not.allocated(dhpb1)) allocate(dhpb1(maxdim))
       if(.not.allocated(forcon)) allocate(forcon(maxdim))
       if(.not.allocated(fordepth)) allocate(fordepth(maxdim))
+      if(.not.allocated(ibecarb)) allocate(ibecarb(maxdim))
       if ((genconstr.gt.0).and.(constr_dist.eq.11)) then
       call gen_dist_constr2
       go to 1712
       if ((genconstr.gt.0).and.(constr_dist.eq.11)) then
       call gen_dist_constr2
       go to 1712
         if (constr_dist.eq.11) then
         read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),dhpb(i),dhpb1(i), &
           ibecarb(i),forcon(nhpb+1),fordepth(nhpb+1)
         if (constr_dist.eq.11) then
         read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),dhpb(i),dhpb1(i), &
           ibecarb(i),forcon(nhpb+1),fordepth(nhpb+1)
-        fordepth(nhpb+1)=fordepth(nhpb+1)/forcon(nhpb+1)
+!EL        fordepth(nhpb+1)=fordepth(nhpb+1)/forcon(nhpb+1)
+          fordepth(nhpb+1)=fordepth(nhpb+1)**(0.25d0)
+          forcon(nhpb+1)=forcon(nhpb+1)**(0.25d0)
         else
 !C        print *,"in else"
         read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),dhpb(i),dhpb1(i), &
         else
 !C        print *,"in else"
         read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),dhpb(i),dhpb1(i), &