Usuniecie diagnostyki
authorAdam Sieradzan <adasko@piasek2.(none)>
Tue, 18 Dec 2012 11:51:32 +0000 (12:51 +0100)
committerAdam Sieradzan <adasko@piasek2.(none)>
Tue, 18 Dec 2012 11:51:32 +0000 (12:51 +0100)
source/unres/src_MD-M/energy_p_new_barrier.F
source/wham/src-M/energy_p_new.F

index 97986d2..fa388be 100644 (file)
@@ -2369,7 +2369,11 @@ c        if (i .gt. iatel_s+2) then
         enddo
 c        if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
         if (i.gt. nnt+1 .and. i.lt.nct+1) then
-          iti1 = itortyp(itype(i-1))
+          if (itype(i-1).le.ntyp) then
+            iti1 = itortyp(itype(i-1))
+          else
+            iti1=ntortyp+1
+          endif
         else
           iti1=ntortyp+1
         endif
@@ -3272,6 +3276,7 @@ cd          write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
 
           if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
      &            'eelloc',i,j,eel_loc_ij
+c              write (iout,*) a22,muij(1),a23,muij(2),a32,muij(3)
 
           eel_loc=eel_loc+eel_loc_ij
 C Partial derivatives in virtual-bond dihedral angles gamma
@@ -5051,7 +5056,7 @@ C
         cosfac=dsqrt(cosfac2)
         sinfac2=0.5d0/(1.0d0-costtab(i+1))
         sinfac=dsqrt(sinfac2)
-        it=itype(i)
+        it=iabs(itype(i))
         if (it.eq.10) goto 1
 c
 C  Compute the axes of tghe local cartesian coordinates system; store in
@@ -5151,7 +5156,8 @@ c     &   sumene4,
 c     &   dscp1,dscp2,sumene
 c        sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
         escloc = escloc + sumene
-c        write (2,*) "i",i," escloc",sumene,escloc
+c        write (2,*) "i",i," escloc",sumene,escloc,it,itype(i)
+c     & ,zz,xx,yy
 c#define DEBUG
 #ifdef DEBUG
 C
index 00ed59c..83f4d5e 100644 (file)
@@ -1920,11 +1920,11 @@ c             write (iout,'(a6,2i5,0pf7.3,2i5,2e11.3)')
 c     &'evdw1',i,j,evdwij
 c     &,iteli,itelj,aaa,evdw1
 
-              write (iout,'(a6,2i5,0pf7.3)') 'ees',i,j,eesij
-cd          write(iout,'(2(2i3,2x),7(1pd12.4)/2(3(1pd12.4),5x)/)')
-cd     &      iteli,i,itelj,j,aaa,bbb,ael6i,ael3i,
-cd     &      1.0D0/dsqrt(rrmij),evdwij,eesij,
-cd     &      xmedi,ymedi,zmedi,xj,yj,zj
+c              write (iout,'(a6,2i5,0pf7.3)') 'ees',i,j,eesij
+c          write(iout,'(2(2i3,2x),7(1pd12.4)/2(3(1pd12.4),5x)/)')
+c     &      iteli,i,itelj,j,aaa,bbb,ael6i,ael3i,
+c     &      1.0D0/dsqrt(rrmij),evdwij,eesij,
+c     &      xmedi,ymedi,zmedi,xj,yj,zj
 C
 C Calculate contributions to the Cartesian gradient.
 C
@@ -2270,8 +2270,10 @@ C Check the loc-el terms by numerical integration
 C Contribution to the local-electrostatic energy coming from the i-j pair
           eel_loc_ij=a22*muij(1)+a23*muij(2)+a32*muij(3)
      &     +a33*muij(4)
-cd          write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
-cd          write (iout,*) a22,muij(1),a23,muij(2),a32,muij(3)
+c          write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
+c          write (iout,'(a6,2i5,0pf7.3)')
+c     &            'eelloc',i,j,eel_loc_ij
+c          write (iout,*) a22,muij(1),a23,muij(2),a32,muij(3)
           eel_loc=eel_loc+eel_loc_ij
 C Partial derivatives in virtual-bond dihedral angles gamma
           if (calc_grad) then
@@ -3946,7 +3948,7 @@ C     &   dc_norm(3,i+nres)
           y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
         enddo
         do j = 1,3
-          z_prime(j) = -uz(j,i-1)*dsign(1.0,dfloat(itype(i)))
+          z_prime(j) = -uz(j,i-1)*dsign(1.0d0,dfloat(itype(i)))
         enddo     
 c       write (2,*) "i",i
 c       write (2,*) "x_prime",(x_prime(j),j=1,3)
@@ -3986,7 +3988,7 @@ c        write (2,*) "xx",xx," yy",yy," zz",zz
 Cc diagnostics - remove later
         xx1 = dcos(alph(2))
         yy1 = dsin(alph(2))*dcos(omeg(2))
-        zz1 = -dsign(1.0,itype(i))*dsin(alph(2))*dsin(omeg(2))
+        zz1 = -dsign(1.0d0,itype(i))*dsin(alph(2))*dsin(omeg(2))
         write(2,'(3f8.1,3f9.3,1x,3f9.3)') 
      &    alph(2)*rad2deg,omeg(2)*rad2deg,theta(3)*rad2deg,xx,yy,zz,
      &    xx1,yy1,zz1
@@ -4029,6 +4031,8 @@ c     &   dscp1,dscp2,sumene
 c        sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
         escloc = escloc + sumene
 c        write (2,*) "escloc",escloc
+c        write (2,*) "i",i," escloc",sumene,escloc,it,itype(i),
+c     &  zz,xx,yy
         if (.not. calc_grad) goto 1
 #ifdef DEBUG
 C
@@ -4158,9 +4162,9 @@ c     &   (dC_norm(j,i-1),j=1,3)," vbld_inv",vbld_inv(i+1),vbld_inv(i)
          dZZ_Ci(k)=0.0d0
          do j=1,3
            dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1)
-     & *dsign(1.0,dfloat(itype(i)))*dC_norm(j,i+nres)
+     & *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
            dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1)
-     &  *dsign(1.0,dfloat(itype(i)))*dC_norm(j,i+nres)
+     &  *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
          enddo
           
          dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
@@ -4731,9 +4735,9 @@ c------------------------------------------------------------------------------
       integer dimen1,dimen2,atom,indx
       double precision buffer(dimen1,dimen2)
       double precision zapas 
-      common /contacts_hb/ zapas(3,20,maxres,7),
-     &   facont_hb(20,maxres),ees0p(20,maxres),ees0m(20,maxres),
-     &         num_cont_hb(maxres),jcont_hb(20,maxres)
+      common /contacts_hb/ zapas(3,ntyp,maxres,7),
+     &   facont_hb(ntyp,maxres),ees0p(ntyp,maxres),ees0m(ntyp,maxres),
+     &         num_cont_hb(maxres),jcont_hb(ntyp,maxres)
       num_kont=num_cont_hb(atom)
       do i=1,num_kont
         do k=1,7
@@ -4756,9 +4760,10 @@ c------------------------------------------------------------------------------
       integer dimen1,dimen2,atom,indx
       double precision buffer(dimen1,dimen2)
       double precision zapas 
-      common /contacts_hb/ zapas(3,20,maxres,7),
-     &         facont_hb(20,maxres),ees0p(20,maxres),ees0m(20,maxres),
-     &         num_cont_hb(maxres),jcont_hb(20,maxres)
+      common /contacts_hb/ zapas(3,ntyp,maxres,7),
+     &         facont_hb(ntyp,maxres),ees0p(ntyp,maxres),
+     &         ees0m(ntyp,maxres),
+     &         num_cont_hb(maxres),jcont_hb(ntyp,maxres)
       num_kont=buffer(1,indx+26)
       num_kont_old=num_cont_hb(atom)
       num_cont_hb(atom)=num_kont+num_kont_old