Merge branch 'master' of mmka:unres into multichain
authorAdam Sieradzan <adasko@piasek4.chem.univ.gda.pl>
Wed, 17 Dec 2014 09:40:58 +0000 (10:40 +0100)
committerAdam Sieradzan <adasko@piasek4.chem.univ.gda.pl>
Wed, 17 Dec 2014 09:40:58 +0000 (10:40 +0100)
Conflicts:
.gitignore
bin/cluster/unres_clustMD-mult_MPICH-GAB.exe
bin/unres/MD/unres_gfortran_single_GAB.exe
bin/unres/MD/unres_ifort_single_GAB.exe
bin/unres/MINIM/unres_ifort_MIN_single_E0LL2Y.exe
bin/unres/MINIM/unres_ifort_MIN_single_GAB.exe
bin/unres_clustMD_MPI-oldparm
bin/wham/wham_multparm-ham_rep-oldparm
source/cluster/wham/src/COMMON.SCCOR
source/cluster/wham/src/Makefile
source/unres/src_MD-M/MREMD.F
source/unres/src_MD-M/Makefile
source/unres/src_MD-M/energy_p_new_barrier.F
source/unres/src_MD-M/stochfric.F
source/unres/src_MD-M/unres.F
source/unres/src_MD/cinfo.f
source/wham/src-M/Makefile
source/wham/src/DIMENSIONS.FREE

19 files changed:
1  2 
CMakeLists.txt
bin/unres/MINIM/unres_ifort_MIN_single_GAB.exe
source/unres/src_MD-M/CMakeLists.txt
source/unres/src_MD-M/COMMON.DERIV
source/unres/src_MD-M/MD_A-MTS.F
source/unres/src_MD-M/MREMD.F
source/unres/src_MD-M/energy_p_new_barrier.F
source/unres/src_MD-M/geomout.F
source/unres/src_MD-M/initialize_p.F
source/unres/src_MD-M/readrtns_CSA.F
source/unres/src_MD-M/sc_move.F
source/unres/src_MD-M/unres.F
source/unres/src_MD/CMakeLists.txt
source/unres/src_MD/COMMON.SCCOR
source/unres/src_MD/energy_p_new_barrier.F
source/unres/src_MIN/CMakeLists.txt
source/wham/src-M/CMakeLists.txt
source/wham/src/CMakeLists.txt
source/wham/src/energy_p_new.F

diff --cc CMakeLists.txt
@@@ -207,10 -182,8 +180,9 @@@ if(UNRES_NA_MMCE
      # Brak MPI dla gfortrana, wiec tylko na ifort sie skompiluje
      if (Fortran_COMPILER_NAME STREQUAL "ifort")
        add_subdirectory(source/unres/src_MD)
 +      add_subdirectory(source/unres/src_MD_DFA)
        add_subdirectory(source/unres/src_MD-M)
        add_subdirectory(source/unres/src_CSA)
-       add_subdirectory(source/unres/src_CSA_DiL)
        add_subdirectory(source/cluster/wham/src)
        add_subdirectory(source/cluster/wham/src-M)
      endif (Fortran_COMPILER_NAME STREQUAL "ifort")
@@@ -229,9 -202,7 +201,8 @@@ else(
    add_subdirectory(source/unres/src_MD)
    if(UNRES_WITH_MPI)
      add_subdirectory(source/unres/src_MD-M)
 +    add_subdirectory(source/unres/src_MD_DFA)
      add_subdirectory(source/unres/src_CSA)
-     add_subdirectory(source/unres/src_CSA_DiL)
      add_subdirectory(source/wham/src)
      add_subdirectory(source/wham/src-M)
      add_subdirectory(source/cluster/wham/src)
diff --cc bin/unres/MINIM/unres_ifort_MIN_single_GAB.exe
index 6e1ebca,8fbedcf..0000000
deleted file mode 100755,100755
Binary files differ
Simple merge
Simple merge
Simple merge
Simple merge
        energia(17)=estr
        energia(20)=Uconst+Uconst_back
        energia(21)=esccor
 +c    Here are the energies showed per procesor if the are more processors 
 +c    per molecule then we sum it up in sum_energy subroutine 
  c      print *," Processor",myrank," calls SUM_ENERGY"
        call sum_energy(energia,.true.)
+       if (dyn_ss) call dyn_set_nss
  c      print *," Processor",myrank," left SUM_ENERGY"
  #ifdef TIMING
        time_sumene=time_sumene+MPI_Wtime()-time00
@@@ -436,9 -439,9 +442,9 @@@ cMS$ATTRIBUTES C ::  proc_pro
  #endif
  #ifdef MPI
        include 'mpif.h'
+ #endif
        double precision gradbufc(3,maxres),gradbufx(3,maxres),
 -     &  glocbuf(4*maxres),gradbufc_sum(3,maxres)
 +     &  glocbuf(4*maxres),gradbufc_sum(3,maxres),gloc_scbuf(3,maxres)
- #endif
        include 'COMMON.SETUP'
        include 'COMMON.IOUNITS'
        include 'COMMON.FFIELD'
        include 'COMMON.IOUNITS'
        include 'COMMON.CALC'
        include 'COMMON.CONTROL'
 +      include 'COMMON.SPLITELE'
+       include 'COMMON.SBRIDGE'
        logical lprn
 +      integer xshift,yshift,zshift
        evdw=0.0D0
  ccccc      energy_dec=.false.
  c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
@@@ -1482,9 -1416,15 +1489,15 @@@ C Calculate SC interaction energy
  C
          do iint=1,nint_gr(i)
            do j=istart(i,iint),iend(i,iint)
+             IF (dyn_ss_mask(i).and.dyn_ss_mask(j)) THEN
+               call dyn_ssbond_ene(i,j,evdwij)
+               evdw=evdw+evdwij
+               if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') 
+      &                        'evdw',i,j,evdwij,' ss'
+             ELSE
              ind=ind+1
 -            itypj=itype(j)
 -            if (itypj.eq.21) cycle
 +            itypj=iabs(itype(j))
 +            if (itypj.eq.ntyp1) cycle
  c            dscj_inv=dsc_inv(itypj)
              dscj_inv=vbld_inv(j+nres)
  c            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
@@@ -4632,13 -4035,19 +4645,22 @@@ C iii and jjj point to the residues fo
            iii=ii
            jjj=jj
          endif
- cd        write (iout,*) "i",i," ii",ii," iii",iii," jj",jj," jjj",jjj
+ c        write (iout,*) "i",i," ii",ii," iii",iii," jj",jj," jjj",jjj,
+ c     &    dhpb(i),dhpb1(i),forcon(i)
  C 24/11/03 AL: SS bridges handled separately because of introducing a specific
  C    distance and angle dependent SS bond potential.
 +        if (ii.gt.nres .and. iabs(itype(iii)).eq.1 .and.
 +     & iabs(itype(jjj)).eq.1) then
+ cmc        if (ii.gt.nres .and. itype(iii).eq.1 .and. itype(jjj).eq.1) then
+ C 18/07/06 MC: Use the convention that the first nss pairs are SS bonds
+         if (.not.dyn_ss .and. i.le.nss) then
+ C 15/02/13 CC dynamic SSbond - additional check
+          if (ii.gt.nres 
+      &       .and. itype(iii).eq.1 .and. itype(jjj).eq.1) then 
++>>>>>>> f5379d3246c4bd95e946c4d35d4a1c13e329c4cb
            call ssbond_ene(iii,jjj,eij)
            ehpb=ehpb+2*eij
+          endif
  cd          write (iout,*) "eij",eij
          else
  C Calculate the distance between the two points and its difference from the
Simple merge
Simple merge
Simple merge
Simple merge
@@@ -189,16 -196,13 +196,25 @@@ c--------------------------------------
        double precision energy(0:n_ene)
        double precision energy_long(0:n_ene),energy_short(0:n_ene)
        double precision varia(maxvar)
++<<<<<<< HEAD
 +      if (indpdb.eq.0)     call chainbuild
 +      time00=MPI_Wtime()
 +      print *,'dc',c(1,1)
 +      if (indpdb.ne.0) then
 +      dc(1,0)=c(1,1)
 +      dc(2,0)=c(2,1)
 +      dc(3,0)=c(3,1)
 +      endif
++=======
+       if (indpdb.eq.0) call chainbuild
+ #ifdef MPI
+       time00=MPI_Wtime()
+ #else
+       time00=tcpu()
+ #endif
++>>>>>>> f5379d3246c4bd95e946c4d35d4a1c13e329c4cb
        call chainbuild_cart
 +      print *,'dc',dc(1,0),dc(2,0),dc(3,0)
        if (split_ene) then
         print *,"Processor",myrank," after chainbuild"
         icall=1
@@@ -254,13 -268,15 +282,17 @@@ crc overlap tes
            call minimize(etot,varia,iretcode,nfun)
          endif
          print *,'SUMSL return code is',iretcode,' eval ',nfun
+ #ifdef MPI
          evals=nfun/(MPI_WTIME()-time1)
+ #else
+         evals=nfun/(tcpu()-time1)
+ #endif
          print *,'# eval/s',evals
          print *,'refstr=',refstr
 -        call hairpin(.true.,nharp,iharp)
 +        call hairpin(.false.,nharp,iharp)
 +        print *,'after hairpin'
          call secondary2(.true.)
 +        print *,'after secondary'
          call etotal(energy(0))
          etot = energy(0)
          call enerprint(energy(0))
Simple merge
@@@ -2,14 -2,10 +2,14 @@@ cc Parameters of the SCCOR ter
        double precision v1sccor,v2sccor,vlor1sccor,
       &                 vlor2sccor,vlor3sccor,gloc_sc,
       &                 dcostau,dsintau,dtauangle,dcosomicron,
-      &                 domicron
+      &                 domicron,v0sccor
        integer nterm_sccor,isccortyp,nsccortyp,nlor_sccor
 -      common/sccor/v1sccor(maxterm_sccor,3,20,20),
 -     &    v2sccor(maxterm_sccor,3,20,20),
 +      common/sccor/v1sccor(maxterm_sccor,3,-ntyp:ntyp,-ntyp:ntyp),
 +     &    v2sccor(maxterm_sccor,3,-ntyp:ntyp,-ntyp:ntyp),
 +     &    v0sccor(maxterm_sccor,-ntyp:ntyp,-ntyp:ntyp),
 +     &    nterm_sccor(-ntyp:ntyp,-ntyp:ntyp),isccortyp(-ntyp:ntyp),
 +     &    nsccortyp,
 +     &    nlor_sccor(-ntyp:ntyp,-ntyp:ntyp),
       &    vlor1sccor(maxterm_sccor,20,20),
       &    vlor2sccor(maxterm_sccor,20,20),
       &    vlor3sccor(maxterm_sccor,20,20),gloc_sc(3,0:maxres2,10),
Simple merge
Simple merge
@@@ -94,9 -94,11 +94,11 @@@ set(UNRES_WHAM_PP_SR
  # Set comipiler flags for different sourcefiles  
  #================================================
  if (Fortran_COMPILER_NAME STREQUAL "ifort")
 -  set(FFLAGS0 "-mcmodel=medium -g -CB -I. -I${CMAKE_CURRENT_SOURCE_DIR}/include_unres" ) 
 +  set(FFLAGS0 "-mcmodel=large -g -CB -I. -I${CMAKE_CURRENT_SOURCE_DIR}/include_unres" ) 
  elseif (Fortran_COMPILER_NAME STREQUAL "gfortran")
    set(FFLAGS0 "-std=legacy -g -I. -I${CMAKE_CURRENT_SOURCE_DIR}/include_unres" ) 
+ else ()
+   set(FFLAGS0 "-g -I. -I${CMAKE_CURRENT_SOURCE_DIR}/include_unres" )   
  endif (Fortran_COMPILER_NAME STREQUAL "ifort")
  
  
Simple merge