adam's update
[unres.git] / source / unres / src-HCD-5D / energy_p_new_barrier.F
index e9ec117..b36b9a8 100644 (file)
@@ -324,6 +324,7 @@ C
       else
         esccor=0.0d0
       endif
+#ifdef FOURBODY
 C      print *,"PRZED MULIt"
 c      print *,"Processor",myrank," computed Usccorr"
 C 
@@ -352,6 +353,7 @@ c         write (iout,*) "MULTIBODY_HB ecorr",ecorr,ecorr5,ecorr6,n_corr,
 c     &     n_corr1
 c         call flush(iout)
       endif
+#endif
 c      print *,"Processor",myrank," computed Ucorr"
 c      write (iout,*) "nsaxs",nsaxs," saxs_mode",saxs_mode
       if (nsaxs.gt.0 .and. saxs_mode.eq.0) then
@@ -1314,9 +1316,16 @@ C     Bartek
       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,evdw1,wvdwpp,
      &  estr,wbond,ebe,wang,
      &  escloc,wscloc,etors,wtor,etors_d,wtor_d,ehpb,wstrain,
+#ifdef FOURBODY
      &  ecorr,wcorr,
-     &  ecorr5,wcorr5,ecorr6,wcorr6,eel_loc,wel_loc,eello_turn3,wturn3,
-     &  eello_turn4,wturn4,eello_turn6,wturn6,esccor,wsccor,edihcnstr,
+     &  ecorr5,wcorr5,ecorr6,wcorr6,
+#endif
+     &  eel_loc,wel_loc,eello_turn3,wturn3,
+     &  eello_turn4,wturn4,
+#ifdef FOURBODY
+     &  eello_turn6,wturn6,
+#endif
+     &  esccor,wsccor,edihcnstr,
      &  ethetacnstr,ebr*nss,Uconst,wumb,eliptran,wliptran,Eafmforce,
      &  etube,wtube,esaxs,wsaxs,ehomology_constr,
      &  edfadis,wdfa_dist,edfator,wdfa_tor,edfanei,wdfa_nei,
@@ -1334,13 +1343,17 @@ C     Bartek
      & 'ETORSD=',1pE16.6,' WEIGHT=',1pE16.6,' (double torsional)'/
      & 'EHBP=  ',1pE16.6,' WEIGHT=',1pE16.6,
      & ' (SS bridges & dist. cnstr.)'/
+#ifdef FOURBODY
      & 'ECORR4=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
      & 'ECORR5=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
      & 'ECORR6=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
+#endif
      & 'EELLO= ',1pE16.6,' WEIGHT=',1pE16.6,' (electrostatic-local)'/
      & 'ETURN3=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 3rd order)'/
      & 'ETURN4=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 4th order)'/
+#ifdef FOURBODY
      & 'ETURN6=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 6th order)'/
+#endif
      & 'ESCCOR=',1pE16.6,' WEIGHT=',1pE16.6,' (backbone-rotamer corr)'/
      & 'EDIHC= ',1pE16.6,' (virtual-bond dihedral angle restraints)'/
      & 'ETHETC=',1pE16.6,' (virtual-bond angle restraints)'/
@@ -1361,9 +1374,16 @@ C     Bartek
       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,
      &  estr,wbond,ebe,wang,
      &  escloc,wscloc,etors,wtor,etors_d,wtor_d,ehpb,wstrain,
+#ifdef FOURBODY
      &  ecorr,wcorr,
-     &  ecorr5,wcorr5,ecorr6,wcorr6,eel_loc,wel_loc,eello_turn3,wturn3,
-     &  eello_turn4,wturn4,eello_turn6,wturn6,esccor,wsccor,edihcnstr,
+     &  ecorr5,wcorr5,ecorr6,wcorr6,
+#endif
+     &  eel_loc,wel_loc,eello_turn3,wturn3,
+     &  eello_turn4,wturn4,
+#ifdef FOURBODY
+     &  eello_turn6,wturn6,
+#endif
+     &  esccor,wsccor,edihcnstr,
      &  ethetacnstr,ebr*nss,Uconst,wumb,eliptran,wliptran,Eafmforc,
      &  etube,wtube,esaxs,wsaxs,ehomology_constr,
      &  edfadis,wdfa_dist,edfator,wdfa_tor,edfanei,wdfa_nei,
@@ -1380,13 +1400,17 @@ C     Bartek
      & 'ETORSD=',1pE16.6,' WEIGHT=',1pE16.6,' (double torsional)'/
      & 'EHBP=  ',1pE16.6,' WEIGHT=',1pE16.6,
      & ' (SS bridges & dist. restr.)'/
+#ifdef FOURBODY
      & 'ECORR4=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
      & 'ECORR5=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
      & 'ECORR6=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
+#endif
      & 'EELLO= ',1pE16.6,' WEIGHT=',1pE16.6,' (electrostatic-local)'/
      & 'ETURN3=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 3rd order)'/
      & 'ETURN4=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 4th order)'/
+#ifdef FOURBODY
      & 'ETURN6=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 6th order)'/
+#endif
      & 'ESCCOR=',1pE16.6,' WEIGHT=',1pE16.6,' (backbone-rotamer corr)'/
      & 'EDIHC= ',1pE16.6,' (virtual-bond dihedral angle restraints)'/
      & 'ETHETC=',1pE16.6,' (virtual-bond angle restraints)'/
@@ -1425,7 +1449,10 @@ C
       include 'COMMON.SBRIDGE'
       include 'COMMON.NAMES'
       include 'COMMON.IOUNITS'
+#ifdef FOURBODY
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+#endif
       double precision gg(3)
       double precision evdw,evdwij
       integer i,j,k,itypi,itypj,itypi1,num_conti,iint
@@ -1491,6 +1518,7 @@ cgrad                gvdwc(l,k)=gvdwc(l,k)+gg(l)
 cgrad              enddo
 cgrad            enddo
 C
+#ifdef FOURBODY
 C 12/1/95, revised on 5/20/97
 C
 C Calculate the contact function. The ith column of the array JCONT will 
@@ -1546,10 +1574,13 @@ cd              write (iout,'(2i3,3f10.5)')
 cd   &           i,j,(gacont(kk,num_conti,i),kk=1,3)
               endif
             endif
+#endif
           enddo      ! j
         enddo        ! iint
 C Change 12/1/95
+#ifdef FOURBODY
         num_cont(i)=num_conti
+#endif
       enddo          ! i
       do i=1,nct
         do j=1,3
@@ -2548,7 +2579,7 @@ C
       include 'COMMON.SBRIDGE'
       include 'COMMON.NAMES'
       include 'COMMON.IOUNITS'
-      include 'COMMON.CONTACTS'
+c      include 'COMMON.CONTACTS'
       dimension gg(3)
 cd    print *,'Entering Esoft_sphere nnt=',nnt,' nct=',nct
       evdw=0.0D0
@@ -2622,7 +2653,7 @@ C
       include 'COMMON.CHAIN'
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
-      include 'COMMON.CONTACTS'
+c      include 'COMMON.CONTACTS'
       include 'COMMON.TORSION'
       include 'COMMON.VECTORS'
       include 'COMMON.FFIELD'
@@ -2946,7 +2977,7 @@ C--------------------------------------------------------------------------
       include 'COMMON.CHAIN'
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
-      include 'COMMON.CONTACTS'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VECTORS'
       include 'COMMON.FFIELD'
@@ -3197,6 +3228,7 @@ c     &    EE(1,2,iti),EE(2,2,i)
 c          write(iout,*) "Macierz EUG",
 c     &    eug(1,1,i-2),eug(1,2,i-2),eug(2,1,i-2),
 c     &    eug(2,2,i-2)
+#ifdef FOURBODY
           if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0) 
      &    then
           call matmat2(CC(1,1,i-2),Ug(1,1,i-2),CUg(1,1,i-2))
@@ -3205,6 +3237,7 @@ c     &    eug(2,2,i-2)
           call matvec2(Ctilde(1,1,i-1),obrot(1,i-2),Ctobr(1,i-2))
           call matvec2(Dtilde(1,1,i-2),obrot2(1,i-2),Dtobr2(1,i-2))
           endif
+#endif
         else
           do k=1,2
             Ub2(k,i-2)=0.0d0
@@ -3249,6 +3282,7 @@ c          mu(k,i-2)=Ub2(k,i-2)
 cd        write (iout,*) 'mu1',mu1(:,i-2)
 cd        write (iout,*) 'mu2',mu2(:,i-2)
 cd        write (iout,*) 'mu',i-2,mu(:,i-2)
+#ifdef FOURBODY
         if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or.wcorr6.gt.0.0d0)
      &  then  
         call matmat2(CC(1,1,i-1),Ugder(1,1,i-2),CUgder(1,1,i-2))
@@ -3267,7 +3301,9 @@ C Vectors and matrices dependent on a single virtual-bond dihedral.
         call matmat2(EUg(1,1,i-2),DD(1,1,i-1),EUgD(1,1,i-2))
         call matmat2(EUgder(1,1,i-2),DD(1,1,i-1),EUgDder(1,1,i-2))
         endif
+#endif
       enddo
+#ifdef FOURBODY
 C Matrices dependent on two consecutive virtual-bond dihedrals.
 C The order of matrices is from left to right.
       if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or.wcorr6.gt.0.0d0)
@@ -3284,6 +3320,7 @@ c      do i=max0(ivec_start,2),ivec_end
         call matmat2(auxmat(1,1),EUg(1,1,i),Ug2DtEUgder(1,1,1,i))
       enddo
       endif
+#endif
 #if defined(MPI) && defined(PARMAT)
 #ifdef DEBUG
 c      if (fg_rank.eq.0) then
@@ -3352,6 +3389,7 @@ c     &   " ivec_count",(ivec_count(i),i=0,nfgtasks-1)
         call MPI_Allgatherv(sintab2(ivec_start),ivec_count(fg_rank1),
      &   MPI_DOUBLE_PRECISION,sintab2(1),ivec_count(0),ivec_displ(0),
      &   MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
+#ifdef FOURBODY
         if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0)
      &  then
         call MPI_Allgatherv(Ctobr(1,ivec_start),ivec_count(fg_rank1),
@@ -3427,6 +3465,7 @@ c     &   " ivec_count",(ivec_count(i),i=0,nfgtasks-1)
      &   MPI_MAT2,Ug2DtEUgder(1,1,1,1),ivec_count(0),ivec_displ(0),
      &   MPI_MAT2,FG_COMM1,IERR)
         endif
+#endif
 #else
 c Passes matrix info through the ring
       isend=fg_rank1
@@ -3471,6 +3510,7 @@ c        call flush(iout)
      &   iprev,6600+irecv,FG_COMM,status,IERR)
 c        write (iout,*) "Gather PRECOMP12"
 c        call flush(iout)
+#ifdef FOURBODY
         if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0) 
      &  then
         call MPI_SENDRECV(ug2db1t(1,ivec_displ(isend)+1),1,
@@ -3490,6 +3530,7 @@ c        call flush(iout)
      &   Ug2DtEUgder(1,1,1,ivec_displ(irecv)+1),1,
      &   MPI_PRECOMP23(lenrecv),
      &   iprev,9900+irecv,FG_COMM,status,IERR)
+#endif
 c        write (iout,*) "Gather PRECOMP23"
 c        call flush(iout)
         endif
@@ -3565,7 +3606,11 @@ C
       include 'COMMON.CHAIN'
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
+#ifdef FOURBODY
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+#endif
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VECTORS'
       include 'COMMON.FFIELD'
@@ -3638,9 +3683,11 @@ cd      enddo
       eello_turn3=0.0d0
       eello_turn4=0.0d0
       ind=0
+#ifdef FOURBODY
       do i=1,nres
         num_cont_hb(i)=0
       enddo
+#endif
 cd      print '(a)','Enter EELEC'
 cd      write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
       do i=1,nres
@@ -3690,7 +3737,9 @@ c        end if
         num_conti=0
         call eelecij(i,i+2,ees,evdw1,eel_loc)
         if (wturn3.gt.0.0d0) call eturn3(i,eello_turn3)
+#ifdef FOURBODY
         num_cont_hb(i)=num_conti
+#endif
       enddo
       do i=iturn4_start,iturn4_end
         if (i.lt.1) cycle
@@ -3746,12 +3795,16 @@ c        endif
           zmedi=mod(zmedi,boxzsize)
           if (zmedi.lt.0) zmedi=zmedi+boxzsize
 
+#ifdef FOURBODY
         num_conti=num_cont_hb(i)
+#endif
 c        write(iout,*) "JESTEM W PETLI"
         call eelecij(i,i+3,ees,evdw1,eel_loc)
         if (wturn4.gt.0.0d0 .and. itype(i+2).ne.ntyp1) 
      &   call eturn4(i,eello_turn4)
+#ifdef FOURBODY
         num_cont_hb(i)=num_conti
+#endif
       enddo   ! i
 C Loop over all neighbouring boxes
 C      do xshift=-1,1
@@ -3818,7 +3871,9 @@ c        go to 166
 c        endif
 
 c        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
+#ifdef FOURBODY
         num_conti=num_cont_hb(i)
+#endif
 C I TU KURWA
         do j=ielstart(i),ielend(i)
 C          do j=16,17
@@ -3834,7 +3889,9 @@ c     & .or.itype(j-1).eq.ntyp1
      &) cycle
           call eelecij(i,j,ees,evdw1,eel_loc)
         enddo ! j
+#ifdef FOURBODY
         num_cont_hb(i)=num_conti
+#endif
       enddo   ! i
 C     enddo   ! zshift
 C      enddo   ! yshift
@@ -3865,7 +3922,11 @@ C-------------------------------------------------------------------------------
       include 'COMMON.CHAIN'
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
+#ifdef FOURBODY
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+#endif
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VECTORS'
       include 'COMMON.FFIELD'
@@ -4655,6 +4716,7 @@ C Remaining derivatives of eello
           ENDIF
 C Change 12/26/95 to calculate four-body contributions to H-bonding energy
 c          if (j.gt.i+1 .and. num_conti.le.maxconts) then
+#ifdef FOURBODY
           if (wcorr+wcorr4+wcorr5+wcorr6.gt.0.0d0
      &       .and. num_conti.le.maxconts) then
 c            write (iout,*) i,j," entered corr"
@@ -4845,6 +4907,7 @@ cdiag           enddo
               endif  ! num_conti.le.maxconts
             endif  ! fcont.gt.0
           endif    ! j.gt.i+1
+#endif
           if (wturn3.gt.0.0d0 .or. wturn4.gt.0.0d0) then
             do k=1,4
               do l=1,3
@@ -4877,7 +4940,7 @@ C Third- and fourth-order contributions from turns
       include 'COMMON.CHAIN'
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
-      include 'COMMON.CONTACTS'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VECTORS'
       include 'COMMON.FFIELD'
@@ -5060,7 +5123,7 @@ C Third- and fourth-order contributions from turns
       include 'COMMON.CHAIN'
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
-      include 'COMMON.CONTACTS'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VECTORS'
       include 'COMMON.FFIELD'
@@ -8726,6 +8789,7 @@ c      write (iout,*) "EBACK_SC_COR",i,v1ij*cosphi+v2ij*sinphi,intertyp
 
       return
       end
+#ifdef FOURBODY
 c----------------------------------------------------------------------------
       subroutine multibody(ecorr)
 C This subroutine calculates multi-body contributions to energy following
@@ -8738,6 +8802,8 @@ C contribution equal to sqrt(eps(i,j)*eps(i+1,j+1)) is added.
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       double precision gx(3),gx1(3)
       logical lprn
 
@@ -8792,6 +8858,8 @@ c------------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.SHIELD'
       double precision gx(3),gx1(3)
       logical lprn
@@ -8846,6 +8914,8 @@ C This subroutine calculates multi-body contributions to hydrogen-bonding
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.CONTROL'
       include 'COMMON.LOCAL'
       double precision gx(3),gx1(3),time00
@@ -9139,6 +9209,8 @@ c------------------------------------------------------------------------------
       parameter (max_cont=maxconts)
       parameter (max_dim=26)
       include "COMMON.CONTACTS"
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       double precision zapas(max_dim,maxconts,max_fg_procs),
      &  zapas_recv(max_dim,maxconts,max_fg_procs)
       common /przechowalnia/ zapas
@@ -9210,6 +9282,8 @@ C This subroutine calculates multi-body contributions to hydrogen-bonding
       include 'COMMON.LOCAL'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.CHAIN'
       include 'COMMON.CONTROL'
       include 'COMMON.SHIELD'
@@ -9580,6 +9654,8 @@ c------------------------------------------------------------------------------
       parameter (max_cont=maxconts)
       parameter (max_dim=70)
       include "COMMON.CONTACTS"
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       double precision zapas(max_dim,maxconts,max_fg_procs),
      &  zapas_recv(max_dim,maxconts,max_fg_procs)
       common /przechowalnia/ zapas
@@ -9633,6 +9709,8 @@ c------------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.SHIELD'
       include 'COMMON.CONTROL'
       double precision gx(3),gx1(3)
@@ -9808,6 +9886,8 @@ C---------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -9873,6 +9953,8 @@ C
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -10259,6 +10341,8 @@ C---------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -10380,6 +10464,8 @@ C---------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -10784,6 +10870,8 @@ c--------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -10924,6 +11012,8 @@ c--------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -11028,6 +11118,8 @@ c----------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -11213,6 +11305,8 @@ c----------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -11328,6 +11422,8 @@ c----------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -11572,6 +11668,8 @@ c----------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTMAT'
+      include 'COMMON.CORRMAT'
       include 'COMMON.TORSION'
       include 'COMMON.VAR'
       include 'COMMON.GEO'
@@ -11890,8 +11988,8 @@ cd      write (2,*) 'ekont',ekont
 cd      write (2,*) 'eel_turn6',ekont*eel_turn6
       return
       end
-
 C-----------------------------------------------------------------------------
+#endif
       double precision function scalar(u,v)
 !DIR$ INLINEALWAYS scalar
 #ifndef OSF