Adam's unres update
[unres.git] / source / unres / src-HCD-5D / energy_p_new_barrier.F
index 6d6a817..2d94dc0 100644 (file)
@@ -37,6 +37,7 @@ c      include 'COMMON.MD'
      & eliptran,Eafmforce,Etube,
      & esaxs_constr,ehomology_constr,edfator,edfanei,edfabet
       integer n_corr,n_corr1
+      double precision time01
 #ifdef MPI      
 c      print*,"ETOTAL Processor",fg_rank," absolute rank",myrank,
 c     & " nfgtasks",nfgtasks
@@ -117,6 +118,9 @@ c        call chainbuild_cart
       endif
 c      write (iout,*) "itime_mat",itime_mat," imatupdate",imatupdate
       if (mod(itime_mat,imatupdate).eq.0) then
+#ifdef TIMING_ENE
+        time01=MPI_Wtime()
+#endif
         call make_SCp_inter_list
 c        write (iout,*) "Finished make_SCp_inter_list"
 c        call flush(iout)
@@ -126,9 +130,12 @@ c        call flush(iout)
         call make_pp_inter_list
 c        write (iout,*) "Finished make_pp_inter_list"
 c        call flush(iout)
-        call make_pp_vdw_inter_list
+c        call make_pp_vdw_inter_list
 c        write (iout,*) "Finished make_pp_vdw_inter_list"
 c        call flush(iout)
+#ifdef TIMING_ENE
+        time_list=time_list+MPI_Wtime()-time01
+#endif
       endif
 c      print *,'Processor',myrank,' calling etotal ipot=',ipot
 c      print *,'Processor',myrank,' nnt=',nnt,' nct=',nct
@@ -151,6 +158,9 @@ C
 C Compute the side-chain and electrostatic interaction energy
 C
 C      print *,ipot
+#ifdef TIMING_ENE
+      time01=MPI_Wtime()
+#endif
       goto (101,102,103,104,105,106) ipot
 C Lennard-Jones potential.
   101 call elj(evdw)
@@ -175,6 +185,9 @@ C
 C Calculate electrostatic (H-bonding) energy of the main chain.
 C
   107 continue
+#ifdef TIMING_ENE
+      time_evdw=time_evdw+MPI_Wtime()-time01
+#endif
 #ifdef DFA
 C     BARTEK for dfa test!
 c      print *,"Processors",MyRank," wdfa",wdfa_dist
@@ -216,6 +229,9 @@ c      print *,"Processor",myrank," computed USCSC"
 #ifdef TIMING
       time_vec=time_vec+MPI_Wtime()-time01
 #endif
+#ifdef TIMING_ENE
+      time01=MPI_Wtime()
+#endif
 C Introduction of shielding effect first for each peptide group
 C the shielding factor is set this factor is describing how each
 C peptide group is shielded by side-chains
@@ -252,6 +268,9 @@ c      print *,"Processor",myrank," left VEC_AND_DERIV"
 c        call eelec_soft_sphere(ees,evdw1,eel_loc,eello_turn3,
 c     &   eello_turn4)
       endif
+#ifdef TIMING_ENE
+      time_eelec=time_eelec+MPI_Wtime()-time01
+#endif
 c#ifdef TIMING
 c      time_enecalc=time_enecalc+MPI_Wtime()-time00
 c#endif
@@ -260,6 +279,9 @@ C
 C Calculate excluded-volume interaction energy between peptide groups
 C and side chains.
 C
+#ifdef TIMING_ENE
+      time01=MPI_Wtime()
+#endif
       if (ipot.lt.6) then
        if(wscp.gt.0d0) then
         call escp(evdw2,evdw2_14)
@@ -271,6 +293,9 @@ C
 c        write (iout,*) "Soft-sphere SCP potential"
         call escp_soft_sphere(evdw2,evdw2_14)
       endif
+#ifdef TIMING_ENE
+      time_escp=time_escp+MPI_Wtime()-time01
+#endif
 c
 c Calculate the bond-stretching energy
 c
@@ -839,12 +864,12 @@ c      do i=nnt,nres
           gradbufc(k,i)=0.0d0
         enddo
       enddo
-#ifdef DEBUG
-      write (iout,*) "igrad_start",igrad_start," igrad_end",igrad_end
-      write (iout,*) (i," jgrad_start",jgrad_start(i),
-     &                  " jgrad_end  ",jgrad_end(i),
-     &                  i=igrad_start,igrad_end)
-#endif
+c#ifdef DEBUG
+c      write (iout,*) "igrad_start",igrad_start," igrad_end",igrad_end
+c      write (iout,*) (i," jgrad_start",jgrad_start(i),
+c     &                  " jgrad_end  ",jgrad_end(i),
+c     &                  i=igrad_start,igrad_end)
+c#endif
 c
 c Obsolete and inefficient code; we can make the effort O(n) and, therefore,
 c do not parallelize this part.
@@ -1510,6 +1535,7 @@ C
       double precision sscale,sscagrad,sscagradlip,sscalelip
       double precision gg_lipi(3),gg_lipj(3)
       double precision boxshift
+      external boxshift
 c      write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       gg_lipi=0.0d0
@@ -2039,6 +2065,7 @@ c          do j=istart(i,iint),iend(i,iint)
 c              write(iout,*) "PRZED ZWYKLE", evdwij
               call dyn_ssbond_ene(i,j,evdwij)
 c              write(iout,*) "PO ZWYKLE", evdwij
+c              call flush(iout)
 
               evdw=evdw+evdwij
               if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') 
@@ -2151,7 +2178,7 @@ C I hate to put IF's in the loops, but here don't have another choice!!!!
 cd              write (iout,'(2(a3,i3,2x),17(0pf7.3))')
 cd     &        restyp(itypi),i,restyp(itypj),j,
 cd     &        rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq) 
-c                return
+                return
               endif
               sigder=-sig*sigsq
 c---------------------------------------------------------------
@@ -3049,7 +3076,7 @@ c
         write(iout,*)  'b2=',(b2(k,i-2),k=1,2)
 #endif
       enddo
-      mu=0.0d0
+      mu(:,:nres)=0.0d0
 #ifdef PARMAT
       do i=ivec_start+2,ivec_end+2
 #else
@@ -5504,6 +5531,9 @@ C peptide-group centers and side chains and its gradient in virtual-bond and
 C side-chain vectors.
 C
       implicit none
+#ifdef MPI
+      include 'mpif.h'
+#endif
       include 'DIMENSIONS'
       include 'COMMON.GEO'
       include 'COMMON.VAR'
@@ -5515,6 +5545,7 @@ C
       include 'COMMON.IOUNITS'
       include 'COMMON.CONTROL'
       include 'COMMON.SPLITELE'
+      include 'COMMON.TIME1'
       double precision ggg(3)
       integer i,iint,j,k,iteli,itypj,subchap,ikont
       double precision xi,yi,zi,xj,yj,zj,rrij,sss1,sssgrad1,
@@ -5522,6 +5553,10 @@ C
       double precision evdw2,evdw2_14,evdwij
       double precision sscale,sscagrad
       double precision boxshift
+      external boxshift,to_box
+c#ifdef TIMING_ENE
+c      double precision time01
+c#endif
       evdw2=0.0D0
       evdw2_14=0.0d0
 c        print *,boxxsize,boxysize,boxzsize,'wymiary pudla'
@@ -5533,6 +5568,9 @@ C      do zshift=-1,1
       if (energy_dec) write (iout,*) "escp:",r_cut_int,rlamb
 c      do i=iatscp_s,iatscp_e
       do ikont=g_listscp_start,g_listscp_end
+c#ifdef TIMING_ENE
+c        time01=MPI_Wtime()
+c#endif
         i=newcontlistscpi(ikont)
         j=newcontlistscpj(ikont)
         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
@@ -5540,6 +5578,7 @@ c      do i=iatscp_s,iatscp_e
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         zi=0.5D0*(c(3,i)+c(3,i+1))
+!DIR$ INLINE
         call to_box(xi,yi,zi)
 c        do iint=1,nscp_gr(i)
 
@@ -5554,11 +5593,21 @@ C Uncomment following three lines for Ca-p interactions
           xj=c(1,j)
           yj=c(2,j)
           zj=c(3,j)
+!DIR$ INLINE
           call to_box(xj,yj,zj)
+c#ifdef TIMING_ENE
+c       time_escpsetup=time_escpsetup+MPI_Wtime()-time01
+c       time01=MPI_Wtime()
+c#endif
+!DIR$ INLINE
           xj=boxshift(xj-xi,boxxsize)
           yj=boxshift(yj-yi,boxysize)
           zj=boxshift(zj-zi,boxzsize)
 c          print *,xj,yj,zj,'polozenie j'
+c#ifdef TIMING_ENE
+c       time_escpsetup=time_escpsetup+MPI_Wtime()-time01
+c       time01=MPI_Wtime()
+c#endif
           rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
 c          print *,rrij
           sss=sscale(1.0d0/(dsqrt(rrij)),r_cut_int)
@@ -5619,6 +5668,9 @@ cgrad          enddo
             gvdwc_scpp(k,i)=gvdwc_scpp(k,i)-ggg(k)
             gvdwc_scp(k,j)=gvdwc_scp(k,j)+ggg(k)
           enddo
+c#ifdef TIMING_ENE
+c          time_escpcalc=time_escpcalc+MPI_Wtime()-time01
+c#endif
 c        endif !endif for sscale cutoff
 c        enddo ! j
 
@@ -5804,7 +5856,8 @@ C 15/02/13 CC dynamic SSbond - additional check
           if (ii.gt.nres .and. iabs(itype(iii)).eq.1 .and.
      &        iabs(itype(jjj)).eq.1) then
            call ssbond_ene(iii,jjj,eij)
-           ehpb=ehpb+2*eij
+c           ehpb=ehpb+2*eij
+           ehpb=ehpb+eij
          endif
 cd          write (iout,*) "eij",eij
 cd   &   ' waga=',waga,' fac=',fac