correction for homol_nset>1 and waga_homology(iset)=0 to prevent sigsegv
[unres.git] / source / unres / src_MD / energy_p_new_barrier.F
index 5d46bbb..dcdd311 100644 (file)
@@ -28,12 +28,6 @@ cMS$ATTRIBUTES C ::  proc_proc
 c      print*,"ETOTAL Processor",fg_rank," absolute rank",myrank,
 c     & " nfgtasks",nfgtasks
       call flush(iout)
-#ifndef DFA
-      edfadis=0.0d0
-      edfator=0.0d0
-      edfanei=0.0d0
-      edfabet=0.0d0
-#endif
       if (nfgtasks.gt.1) then
 #ifdef MPI
         time00=MPI_Wtime()
@@ -105,6 +99,12 @@ c      if (modecalc.eq.12.or.modecalc.eq.14) then
 c        call int_from_cart1(.false.)
 c      endif
 #endif     
+#ifndef DFA
+      edfadis=0.0d0
+      edfator=0.0d0
+      edfanei=0.0d0
+      edfabet=0.0d0
+#endif
 #ifdef TIMING
 #ifdef MPI
       time00=MPI_Wtime()
@@ -263,7 +263,7 @@ cd    print *,'nterm=',nterm
        edihcnstr=0
       endif
 
-      if (constr_homology.ge.1) then
+      if (constr_homology.ge.1.and.waga_homology(iset).ne.0d0) then
         call e_modeller(ehomology_constr)
 c        print *,'iset=',iset,'me=',me,ehomology_constr,
 c     &  'Processor',fg_rank,' CG group',kolor,
@@ -822,7 +822,7 @@ c      enddo
 #endif
         enddo
       enddo 
-      if (constr_homology.gt.0) then
+      if (constr_homology.gt.0.and.waga_homology(iset).ne.0d0) then
         do i=1,nct
           do j=1,3
             gradc(j,i,icg)=gradc(j,i,icg)+duscdiff(j,i)
@@ -4584,6 +4584,8 @@ c
       do i=ibondp_start,ibondp_end
         diff = vbld(i)-vbldp0
 c        write (iout,*) i,vbld(i),vbldp0,diff,AKP*diff*diff
+        if (energy_dec)    write (iout,'(a7,i5,4f7.3)') 
+     &     "estr bb",i,vbld(i),vbldp0,diff,AKP*diff*diff
         estr=estr+diff*diff
         do j=1,3
           gradb(j,i-1)=AKP*diff*dc(j,i-1)/vbld(i)
@@ -4602,6 +4604,9 @@ c
             diff=vbld(i+nres)-vbldsc0(1,iti)
 c            write (iout,*) i,iti,vbld(i+nres),vbldsc0(1,iti),diff,
 c     &      AKSC(1,iti),AKSC(1,iti)*diff*diff
+            if (energy_dec)  write (iout,*) 
+     &      "estr sc",i,iti,vbld(i+nres),vbldsc0(1,iti),diff,
+     &      AKSC(1,iti),AKSC(1,iti)*diff*diff
             estr=estr+0.5d0*AKSC(1,iti)*diff*diff
             do j=1,3
               gradbx(j,i)=AKSC(1,iti)*diff*dc(j,i+nres)/vbld(i+nres)
@@ -5041,6 +5046,8 @@ c        lprn1=.true.
      &   phii1*rad2deg,ethetai
 c        lprn1=.false.
         etheta=etheta+ethetai
+        if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
+     &      'ebend',i,ethetai
         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*dephii
         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*dephii1
         gloc(nphi+i-2,icg)=gloc(nphi+i-2,icg)+wang*dethetai
@@ -6038,6 +6045,8 @@ c     write(iout,*) "waga_theta",waga_theta,"waga_d",waga_d
          dij=dist(i,j)
 c        write (iout,*) "dij(",i,j,") =",dij
          do k=1,constr_homology
+c           write(iout,*) ii,k,i,j,l_homo(k,ii),dij,odl(k,ii)
+           if(.not.l_homo(k,ii)) cycle
            distance(k)=odl(k,ii)-dij
 c          write (iout,*) "distance(",k,") =",distance(k)
 c
@@ -6070,6 +6079,7 @@ c        write (iout,* )"min_odl",min_odl
 c Nie wiem po co to liczycie jeszcze raz!
 c            odleg3=-waga_dist(iset)*((distance(i,j,k)**2)/ 
 c     &              (2*(sigma_odl(i,j,k))**2))
+           if(.not.l_homo(k,ii)) cycle
            if (waga_dist.ge.0.0d0) then
 c
 c          For Gaussian-type Urestr
@@ -6119,6 +6129,7 @@ c            godl=dexp(((-(distance(i,j,k)**2)/(2*(sigma_odl(i,j,k))**2))
 c     &           *waga_dist)+min_odl
 c          sgodl=-godl(k)*distance(k)*sigma_odl(k,ii)*waga_dist
 c
+         if(.not.l_homo(k,ii)) cycle
          if (waga_dist.ge.0.0d0) then
 c          For Gaussian-type Urestr
 c
@@ -6343,9 +6354,6 @@ c
 c        sgtheta=-gtheta(k)*theta_diff(k)*sigma_theta(k,i)*waga_theta ! right functional form?
           sum_sgtheta=sum_sgtheta+sgtheta ! cum variable
         enddo
-c       grad_theta3=sum_sgtheta/sum_gtheta 1/*theta(i)? s. line below
-c       grad_theta3=sum_sgtheta/sum_gtheta
-c
 c       Final value of gradient using same var as in Econstr_back
         gloc(nphi+i-2,icg)=gloc(nphi+i-2,icg)
      &      +sum_sgtheta/sum_gtheta*waga_theta
@@ -6581,12 +6589,14 @@ C 6/23/01 Compute double torsional energy
       include 'COMMON.IOUNITS'
       include 'COMMON.FFIELD'
       include 'COMMON.TORCNSTR'
+      include 'COMMON.CONTROL'
       logical lprn
 C Set lprn=.true. for debugging
       lprn=.false.
 c     lprn=.true.
       etors_d=0.0D0
       do i=iphid_start,iphid_end
+        etors_d_ii=0.0D0
         itori=itortyp(itype(i-2))
         itori1=itortyp(itype(i-1))
         itori2=itortyp(itype(i))
@@ -6605,6 +6615,8 @@ c     lprn=.true.
           sinphi2=dsin(j*phii1)
           etors_d=etors_d+v1cij*cosphi1+v1sij*sinphi1+
      &     v2cij*cosphi2+v2sij*sinphi2
+          if (energy_dec) etors_d_ii=etors_d_ii+
+     &     v1cij*cosphi1+v1sij*sinphi1+v2cij*cosphi2+v2sij*sinphi2
           gloci1=gloci1+j*(v1sij*cosphi1-v1cij*sinphi1)
           gloci2=gloci2+j*(v2sij*cosphi2-v2cij*sinphi2)
         enddo
@@ -6620,12 +6632,17 @@ c     lprn=.true.
             sinphi1m2=dsin(l*phii-(k-l)*phii1)
             etors_d=etors_d+v1cdij*cosphi1p2+v2cdij*cosphi1m2+
      &        v1sdij*sinphi1p2+v2sdij*sinphi1m2
+            if (energy_dec) etors_d_ii=etors_d_ii+
+     &        v1cdij*cosphi1p2+v2cdij*cosphi1m2+
+     &        v1sdij*sinphi1p2+v2sdij*sinphi1m2
             gloci1=gloci1+l*(v1sdij*cosphi1p2+v2sdij*cosphi1m2
      &        -v1cdij*sinphi1p2-v2cdij*sinphi1m2)
             gloci2=gloci2+(k-l)*(v1sdij*cosphi1p2-v2sdij*cosphi1m2
      &        -v1cdij*sinphi1p2+v2cdij*sinphi1m2) 
           enddo
         enddo
+        if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
+     &        'etor_d',i,etors_d_ii
         gloc(i-3,icg)=gloc(i-3,icg)+wtor_d*gloci1
         gloc(i-2,icg)=gloc(i-2,icg)+wtor_d*gloci2
 c        write (iout,*) "gloci", gloc(i-3,icg)