NEWCORR5D working with 15k, work and iwork in random_vel might need testing
[unres4.git] / source / unres / unres.F90
index 4a8e7a6..e6c19b4 100644 (file)
         call exec_softreg
       else if (modecalc.eq.12) then
         call exec_MD
+        call exec_checkgrad
       else if (modecalc.eq.14) then
         call exec_MREMD
       else
       subroutine exec_MD
       use MPI_data     !include 'COMMON.SETUP'
       use control_data !include 'COMMON.CONTROL'
-      use geometry, only:chainbuild
+      use geometry, only:chainbuild,chainbuild_cart
       use MDyn
       use io_units     !include 'COMMON.IOUNITS'
+      use compare, only:alloc_compare_arrays
 !      use io_common
       implicit none
 !      include 'DIMENSIONS'
       print *,'Start MD'
       call alloc_MD_arrays
       print *,'After MD alloc'
+      call alloc_compare_arrays
+      print *,'After compare alloc'
       if (me.eq.king .or. .not. out1file) &
          write (iout,*) "Calling chainbuild"
+      if (extconf) then
       call chainbuild
+      else
+      call chainbuild_cart
+      endif
       call MD
       return
       end subroutine exec_MD
       use REMD_data     !include 'COMMON.REMD'
       use geometry, only:chainbuild
       use MREMDyn
+      use compare, only:alloc_compare_arrays
 
       implicit none
 !      include 'DIMENSIONS'
       integer :: i
       call alloc_MD_arrays
       call alloc_MREMD_arrays
-
+      call alloc_compare_arrays
 !     if (me.eq.king .or. .not. out1file) &
 !         write (iout,*) "Calling chainbuild"
 !      call chainbuild
 !      use MD          !include 'COMMON.MD'
 
       use energy_data
-
+      use MD_data, only: iset
       use io_base
       use geometry, only:chainbuild
       use energy
       real(kind=8) :: varia(6*nres)    !(maxvar) (maxvar=6*maxres)
       real(kind=8) :: time00, evals, etota, etot, time_ene, time1
       integer :: nharp,nft_sc,iretcode,nfun
-      integer,dimension(4,nres/3) :: iharp     !(4,nres/3)(4,maxres/3)
+      integer,dimension(4,nres) :: iharp       !(4,nres/3)(4,maxres/3)
       logical :: fail
       real(kind=8) :: rms,frac,frac_nn,co
 
       integer :: j,k
+       if (iset.eq.0) iset=1
       call alloc_compare_arrays
       if ((indpdb.eq.0).and.(.not.read_cart)) then 
       call chainbuild
       etota = energy_(0)
       etot = etota
       call enerprint(energy_)
+      if (.false.) then
       call hairpin(.true.,nharp,iharp)
       call secondary2(.true.)
+      endif
       if (minim) then
 !rc overlap test
+        print *,"overlap",searchsc,overlapsc
         if (overlapsc) then 
           print *, 'Calling OVERLAP_SC'
           call overlap_sc(fail)
 !      do j=1,3
 !        dc(j,0)=ran_number(-0.2d0,0.2d0)
 !      enddo
+#ifdef UMB
       usampl=.true.
+#endif
       totT=1.d0
       eq_time=0.0d0
       call read_fragments
       use MD_data
       use energy
       use MDyn, only:setup_fricmat
+#ifndef FIVEDIAG
       use REMD, only:fricmat_mult,ginv_mult
+#endif
 #ifdef MPI
       include "mpif.h"
 #endif
 !          write (2,*) "After sum_gradient"
 !          write (2,*) "dimen",dimen," dimen3",dimen3
 !          call flush(2)
+#ifndef FIVEDIAG
         else if (iorder.eq.4) then
           call ginv_mult(z,d_a_tmp)
         else if (iorder.eq.5) then
 !          call flush(2)
 !           write (iout,*) "My chunk of ginv_block"
 !           call MATOUT2(my_ng_count,dimen3,maxres2,maxers2,ginv_block)
+#endif
         else if (iorder.eq.6) then
           call int_from_cart1(.false.)
         else if (iorder.eq.7) then
           call chainbuild_cart
         else if (iorder.eq.8) then
           call intcartderiv
+#ifndef FIVEDIAG
         else if (iorder.eq.9) then
           call fricmat_mult(z,d_a_tmp)
+#endif
         else if (iorder.eq.10) then
           call setup_fricmat
         endif