extension tu fosforylated potentials
[unres4.git] / source / unres / REMD.f90
index e2db478..3d11d5c 100644 (file)
         ind=1
         do i=nnt,nct
         mnum=molnum(i)
-       if (iabs(itype(i,1)).ne.10 .and.iabs(itype(i,mnum)).ne.ntyp1 &
-          .and.mnum.eq.5) then
+!       if (iabs(itype(i,1)).ne.10 .and.iabs(itype(i,mnum)).ne.ntyp1 &
+!          .and.mnum.eq.5) then
+       if (iabs(itype(i,1)).ne.10 .and. &
+          iabs(itype(i,mnum)).ne.ntyp1_molec(mnum) .and. mnum.ne.5) then
           DU1(ind)=-isc(iabs(itype(i,1)),1)
           DU1(ind+1)=0.0d0
          ind=ind+2
 !  Diagonal elements of the dC part of A and the respective friction coefficients
       ind=1
       ind1=0
-      print *,"TUTUTUT?!",nnt,nct-1
+!      print *,"TUTUTUT?!",nnt,nct-1
       do i=nnt,nct-1
         mnum=molnum(i)
         ind=ind+1
         print *,i,coeff,mp(mnum)
         massvec(ind1)=mp(mnum)
         Gmat(ind,ind)=coeff
-        print *,"i",mp(mnum)
+!        print *,"i",mp(mnum)
         A(ind1,ind)=0.5d0
       enddo
       
       endif
       deallocate(Gcopy)
 #endif
+!write(iout,*) "end setup_MD_matr"
       return
       end subroutine setup_MD_matrices
 !-----------------------------------------------------------------------------