working PBC
authorAdam Sieradzan <adasko@piasek4.chem.univ.gda.pl>
Thu, 4 May 2017 08:49:28 +0000 (10:49 +0200)
committerAdam Sieradzan <adasko@piasek4.chem.univ.gda.pl>
Thu, 4 May 2017 08:49:28 +0000 (10:49 +0200)
source/unres/MD.f90
source/unres/compare.F90
source/unres/geometry.f90
source/unres/io_base.f90
source/unres/io_config.f90
source/unres/unres.f90

index 36124aa..929337f 100644 (file)
        write (iout,*) "vcm right after adjustment:"
        write (iout,*) (vcm(j),j=1,3) 
       endif
-      if (.not.rest) then              
+      if ((.not.rest).and.(indpdb.eq.0)) then          
          call chainbuild
          if(iranconf.ne.0) then
           if (overlapsc) then 
index b65e57c..c938098 100644 (file)
 
 !el      allocate(icont(2,12*nres),isec(nres,4),nsec(nres))
 
-      if(.not.dccart) call chainbuild
+      if(.not.dccart) call chainbuild_cart
       if(.not.allocated(hfrag)) allocate(hfrag(2,nres/3)) !(2,maxres/3)
 !d      call write_pdb(99,'sec structure',0d0)
       ncont=0
       real(kind=8),dimension(3) :: xpi,xpj
       integer :: i,k,j,i1,j1,nbeta,nstrand,ii1,jj1,ij,iii1,jjj1,&
             nhelix
-      call chainbuild
+      call chainbuild_cart
 !d      call write_pdb(99,'sec structure',0d0)
       ncont=0
       nbfrag=0
index f9751f6..951e8eb 100644 (file)
@@ -83,6 +83,7 @@
       nres2=2*nres
 ! Set lprn=.true. for debugging
       lprn = .false.
+      print *,"I ENTER CHAINBUILD"
 !
 ! Define the origin and orientation of the coordinate system and locate the
 ! first three CA's and SC(2).
index f86b4dd..0a9dc14 100644 (file)
       character*(*) :: tytul
       character(len=1),dimension(10) :: chainid= (/'A','B','C','D','E','F','G','H','I','J'/)
       integer,dimension(nres) :: ica   !(maxres)
-
+       integer iti1
 !el  local variables
       integer :: j,iti,itj,itk,itl,i,iatom,ichain,ires,iunit
       real(kind=8) :: etot
       ires=0
       do i=nnt,nct
         iti=itype(i)
+        iti1=itype(i+1)
+        if ((iti.eq.ntyp1).and.(iti1.eq.ntyp1)) cycle
         if (iti.eq.ntyp1) then
           ichain=ichain+1
-          ires=0
+!          ires=0
           write (iunit,'(a)') 'TER'
         else
         ires=ires+1
index da0414d..451731d 100644 (file)
             enddo
           else
             call sccenter(ires,iii,sccor)
+!          iii=0
           endif
           iii=0
         endif
 !              write (iout,*) "Calculating sidechain center iii",iii
               if (unres_pdb) then
                 do j=1,3
-                  dc(j,ires+nres)=sccor(j,iii)
+                  dc(j,ires+ishift1-ishift-1)=sccor(j,iii)
                 enddo
               else
                 call sccenter(ires_old,iii,sccor)
index deb5713..619aa73 100644 (file)
 #ifdef MPI
       include "mpif.h"
 #endif
+      print *,'Start MD'
       call alloc_MD_arrays
-      if (me.eq.king .or. .not. out1file) &
-         write (iout,*) "Calling chainbuild"
-      call chainbuild
+!      if (me.eq.king .or. .not. out1file) &
+!         write (iout,*) "Calling chainbuild"
+!      call chainbuild
       call MD
       return
       end subroutine exec_MD
       call alloc_MD_arrays
       call alloc_MREMD_arrays
 
-      if (me.eq.king .or. .not. out1file) &
-         write (iout,*) "Calling chainbuild"
-      call chainbuild
+!     if (me.eq.king .or. .not. out1file) &
+!         write (iout,*) "Calling chainbuild"
+!      call chainbuild
       if (me.eq.king .or. .not. out1file) &
          write (iout,*) "Calling REMD"
       if (remd_mlist) then