*************************************************************************
*     
*     functions.f
*     
*     - !???
*     
*     needs:
*     - !???
*     
*     output variables:
*     - !???
*     
*     to be called inside !???
*
*
*     MODIFIED in order to have in input a 
*     REAL-defined strip number instead of INTEGER
*     
*************************************************************************


      function pitch(view)      !it gives the strip pitch, knowing the view number

      real pitch
      integer view

      include 'commontracker.f'

      if(mod(view,2).eq.0) then !X
         pitch=pitchX
      else                      !Y
         pitch=pitchY
      endif

      end



c------------------------------------------------------------------------



      function npl(view)        !it gives the plane number, knowing the view number.
                                ! plane 1 = views 11+12, calorimeter side
                                ! ...
                                ! plane 6 = views 1+2, TRD side
      integer npl,view

      npl=7-(INT((view-1)/2)+1)

      end



c------------------------------------------------------------------------



      function nld(istrip,view) 
*     it gives the number of the ladder, knowing the
*     strip number (1..3072) and the view number.
*     the first strip belongs to ladder 1

      integer istrip,view,nld

      include 'commontracker.f'


      nld=INT((istrip-1)/nstrips_ladder)+1

      end


c------------------------------------------------------------------------


      function nviewx(iplane)   !it gives the view number of a X plane

      integer nviewx,iplane

      nviewx=2*(7-iplane)

      end


c------------------------------------------------------------------------

      function nviewy(iplane)   !it gives the view number of a Y plane

      integer nviewy,iplane

      nviewy=2*(7-iplane)-1

      end

c------------------------------------------------------------------------




      function nvk(istrip)      

*     it gives the number of the VA1, knowing the strip
*     number (1..3072).
*     the first strip belongs to VA1 1
      integer istrip,nvk

      include 'commontracker.f'

      nvk=INT((istrip-1)/nstrips_va1)+1
      
      end



c------------------------------------------------------------------------



      function nst(istrip)      

*     it gives the VA1 strip, knowing the strip number
*     (1..3072).
*     the first strip belongs to VA1 1

      integer istrip,nst

      include 'commontracker.f'

      nst=INT(mod((istrip-1),nstrips_va1))+1
      

      end



      function coordsi(istrip,view) 
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
*     it gives the strip coordinate in micrometers,
*     knowing the strip number (1..3072) and the view
*     number. the origin of the coordinate is on the
*     centre of the sensor the strip belongs to.
*     the axes directions are the same as in the PAMELA
*     reference frame (i.e.: the 11th view coordinate
*     direction has to be inverted here)
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *

c      integer is,view,istrip

      integer view,is,istrip
      real coordsi

      include 'commontracker.f'

c     NB mettere il 1024 nel commontracker...!???



      is=istrip                 !it stores istrip number
      is=mod(is-1,1024)+1       !it puts all clusters on a single ladder

      coordsi=0.
      
      if(mod(view,2).eq.0) then !X view

c        if((is.le.3).or.(is.ge.1022)) then !X has 1018 strips...
c          print*,'functions: WARNING: false X strip: strip ',is
c        endif

        is=is-3                 !4 =< is =< 1021 --> 1 =< is =< 1018

        edge=edgeX
        dim=SiDimX

      elseif(mod(view,2).eq.1) then !Y view

        edge=edgeY
        dim=SiDimY

c$$$        if(view.eq.11) then     !INVERSIONE!???
c$$$          is=1025-is
c$$$        endif

      endif

      p=pitch(view)

      coord1=(is-1)*p           !referred to 1st sensor strip
      coord1=coord1+edge        !referred to sensor edge
      
      coordsi=coord1-dim/2      !referred to the centre of the sensor

      if(view.eq.11) then       !INVERSION: it puts y axis in the same direction for all views
        coordsi=-coordsi
      endif
      
      end


c------------------------------------------------------------------------


      function acoordsi(strip,view) 
*
*     same as COORDSI, but accept a real value of strip!!!
*
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
*     it gives the strip coordinate in micrometers,
*     knowing the strip number (1..3072) and the view
*     number. the origin of the coordinate is on the
*     centre of the sensor the strip belongs to.
*     the axes directions are the same as in the PAMELA
*     reference frame (i.e.: the 11th view coordinate
*     direction has to be inverted here)
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *

c      integer is,view,istrip

      integer view,is,istrip
      real coordsi,acoordsi
      real strip,stripladder


      include 'commontracker.f'

c     NB mettere il 1024 nel commontracker...!???

      istrip = int(strip+0.5)   !istrip stores the closest integer to strip      

      is=istrip                 !it stores istrip number
      is=mod(is-1,1024)+1       !it puts all clusters on a single ladder
      
      coordsi=0.
      
      if(mod(view,2).eq.0) then !X view

c        if((is.le.3).or.(is.ge.1022)) then !X has 1018 strips...
c          print*,'functions: WARNING: false X strip: strip ',is
c        endif

        is=is-3                 !4 =< is =< 1021 --> 1 =< is =< 1018

        edge=edgeX
        dim=SiDimX

      elseif(mod(view,2).eq.1) then !Y view

        edge=edgeY
        dim=SiDimY

c$$$        if(view.eq.11) then     !INVERSIONE!???
c$$$          is=1025-is
c$$$        endif

      endif


      stripladder = float(is)+(strip-float(istrip))!cluster position relative to ladder
      p=pitch(view)

ccccc coord1=(is-1)*p           !referred to 1st sensor strip
      coord1=(stripladder-1)*p  !referred to 1st sensor strip
      coord1=coord1+edge        !referred to sensor edge
      acoordsi=coord1-dim/2      !referred to the centre of the sensor

      if(view.eq.11) then       !INVERSION: it puts y axis in the same direction for all views
        acoordsi=-acoordsi
      endif
      
      end



c------------------------------------------------------------------------


      function coord(coordsi,view,ladder,sen) 
*     it gives the coordinate in 
*     micrometers, knowing the coordinate in the sensor
*     frame, the view, the ladder and the sensor numbers.
*     the origin is in the centre of the magnet (PAMELA
*     reference frame)

      include 'commontracker.f'
      include 'common_tracks.f'

      integer view,ladder,sen
      integer sx,sy,sz

      real coord,coordsi,trasl

c$$$c     parameter (offset=4365.)  !???  ! in um !CONTROLLARE SE HA SENSO:
c$$$                                ! dalle misure sul piano dovrebbe essere 4970,
c$$$                                ! dallo shift dei residui viene 4365
c$$$                                ! va messo .ne.0. se in mech_sensor assegno ai 
c$$$                                ! sensori del sesto piano coordinate Y uguali
c$$$                                ! a quelle degli altri sensori
c$$$      parameter (offset=0.)     !???  altrimenti se il sesto piano ha coordinate
c$$$                                ! Y diverse offset dovrebbe essere .eq.0.
c$$$                                ! CONTROLLARE CON I GRAFICI DEI RESIDUI!!!


      coord=0.
      
      sx=ladder
      sy=sen
      sz=npl(view)

      if(mod(view,2).eq.0) then !X view

        trasl=x_mech_sensor(sz,sx,sy) !in mm

      elseif(mod(view,2).eq.1) then !Y view

        trasl=y_mech_sensor(sz,sx,sy) !in mm

c$$$        if(view.eq.11) then     !INVERSIONE!???INUTILE, ne e' gia' tenuto conto
c$$$          coordsi=coordsi+offset ! in y_mech_pos...
c$$$        endif

      endif

      coord=coordsi+trasl*1000.

      end


c------------------------------------------------------------------------
c------------------------------------------------------------------------

c     double precision version of the above subroutine

      double precision function dcoord(coordsi,view,ladder,sen) !it gives the coordinate in 
                                ! micrometers, knowing the coordinate in the sensor
                                ! frame, the view, the ladder and the sensor numbers.
                                ! the origin is in the centre of the magnet (PAMELA
                                ! reference frame)

      include 'commontracker.f'
      include 'common_tracks.f'

      integer view,ladder,sen
      integer sx,sy,sz

c      double precision dcoord
      double precision coordsi,trasl

c$$$c     parameter (offset=4365.)  !???  ! in um !CONTROLLARE SE HA SENSO:
c$$$                                ! dalle misure sul piano dovrebbe essere 4970,
c$$$                                ! dallo shift dei residui viene 4365
c$$$                                ! va messo .ne.0. se in mech_sensor assegno ai 
c$$$                                ! sensori del sesto piano coordinate Y uguali
c$$$                                ! a quelle degli altri sensori
c$$$      parameter (offset=0.)     !???  altrimenti se il sesto piano ha coordinate
c$$$                                ! Y diverse offset dovrebbe essere .eq.0.
c$$$                                ! CONTROLLARE CON I GRAFICI DEI RESIDUI!!!


      dcoord=0.
      
      if(
     $     ladder.lt.1.or.
     $     ladder.gt.nladders_view.or.
     $     sen.lt.1.or.
     $     sen.gt.2.or.
     $     view.lt.1.or.
     $     view.gt.nviews.or.
     $     .false.)then
         print*,'dcoord ---> wrong input: ladder ',ladder
     $        ,' sensor ',sen
     $        ,' view ',view
         return
      endif

      sx=ladder
      sy=sen
      sz=npl(view)


      if(mod(view,2).eq.0) then !X view

        trasl=x_mech_sensor(sz,sx,sy) !in mm

      elseif(mod(view,2).eq.1) then !Y view

        trasl=y_mech_sensor(sz,sx,sy) !in mm

c$$$        if(view.eq.11) then     !INVERSIONE!???INUTILE, ne e' gia' tenuto conto
c$$$          dcoordsi=dcoordsi+offset ! in y_mech_pos...
c$$$        endif

      endif

      dcoord=coordsi+trasl*1000.

      end


c------------------------------------------------------------------------
      integer function nsatstrips(ic)
*--------------------------------------------------------------
*     this function returns the number of saturated strips 
*     inside a cluster
*--------------------------------------------------------------
      include 'commontracker.f'
      include 'level1.f'
      include 'calib.f'

      

      integer nsat 
      nsat = 0 
      iv=VIEW(ic)               
      if(mod(iv,2).eq.1)incut=incuty
      if(mod(iv,2).eq.0)incut=incutx
      istart = INDSTART(IC)
      istop  = TOTCLLENGTH
      if(ic.lt.NCLSTR1)istop=INDSTART(IC+1)-1
      do i = INDMAX(IC),istart,-1
c         cut  = incut*CLSIGMA(i)
c         if(CLSIGNAL(i).ge.cut)then
         if(  (mod(iv,2).eq.1.and.CLADC(i).lt.ADCsatx)
     $        .or.
     $        (mod(iv,2).eq.0.and.CLADC(i).gt.ADCsaty) )then
            nsat = nsat +1 
         else
            goto 10
         endif
      enddo
 10   continue
      do i = INDMAX(IC)+1,istop
c         cut  = incut*CLSIGMA(i)
c         if(CLSIGNAL(i).ge.cut)then
         if(  (mod(iv,2).eq.1.and.CLADC(i).lt.ADCsatx)
     $        .or. 
     $        (mod(iv,2).eq.0.and.CLADC(i).gt.ADCsaty) )then
            nsat = nsat +1 
         else
            goto 20
         endif
      enddo
 20   continue
            
      nsatstrips = nsat
      return 
      end

c------------------------------------------------------------------------
      integer function nbadstrips(ncog,ic)
*--------------------------------------------------------------
*     this function returns the number of BAD strips 
*     inside a cluster:
*     - if NCOG=0, the number BAD strips inside the whole cluster
*     are given, according to the cluster multiplicity
*     
*     - if NCOG>0, the number BAD strips is evaluated using NCOG 
*     strips, even if they have a negative signal (according to Landi)
*--------------------------------------------------------------
      include 'commontracker.f'
      include 'level1.f'
      include 'calib.f'

      integer nbad 
      nbad = 0 

      if (ncog.gt.0) then

*     --> signal of the central strip
         sc = CLSIGNAL(INDMAX(ic)) !center
*     signal of adjacent strips
         sl1 = -100000                !left 1
         if(
     $        (INDMAX(ic)-1).ge.INDSTART(ic)
     $        )
     $        sl1 = CLSIGNAL(INDMAX(ic)-1)
         
         sl2 = -100000                !left 2
         if(
     $        (INDMAX(ic)-2).ge.INDSTART(ic)
     $        )
     $        sl2 = CLSIGNAL(INDMAX(ic)-2)
         
         sr1 = -100000                !right 1
         if(
     $        (ic.ne.NCLSTR1.and.(INDMAX(ic)+1).lt.INDSTART(ic+1))
     $        .or.
     $        (ic.eq.NCLSTR1.and.(INDMAX(ic)+1).le.TOTCLLENGTH)
     $        )
     $        sr1 = CLSIGNAL(INDMAX(ic)+1)
         
         sr2 = -100000                !right 2
         if(
     $        (ic.ne.NCLSTR1.and.(INDMAX(ic)+2).lt.INDSTART(ic+1))
     $        .or.
     $        (ic.eq.NCLSTR1.and.(INDMAX(ic)+2).le.TOTCLLENGTH)
     $        )
     $        sr2 = CLSIGNAL(INDMAX(ic)+2)
         
         if(ncog.ge.1)nbad = nbad+1-CLBAD(INDMAX(ic))
         
         if(ncog.ge.2)then
            if(sl1.gt.sr1.and.(INDMAX(ic)-1).ge.1)then
               nbad=nbad+1-CLBAD(INDMAX(ic)-1)      
            elseif(sl1.le.sr1.and.(INDMAX(ic)+1).le.NCLSTR1)then
               nbad=nbad+1-CLBAD(INDMAX(ic)+1)           
            endif
         endif
         
         if(ncog.ge.3)then
            if(sl1.gt.sr1.and.(INDMAX(ic)+1).le.NCLSTR1)then
               nbad=nbad+1-CLBAD(INDMAX(ic)+1)
            elseif(sl1.le.sr1.and.(INDMAX(ic)-1).ge.1)then
c               if(INDMAX(ic)-1.eq.0)
c     $              print*,' ======= ',sl2,sl1,sc,sr1,sr2
               nbad=nbad+1-CLBAD(INDMAX(ic)-1)
            endif
         endif 
         
         if(ncog.ge.4)then
            if(sl2.gt.sr2.and.(INDMAX(ic)-2).ge.1)then
               nbad=nbad+1-CLBAD(INDMAX(ic)-2)      
            elseif(sl2.le.sr2.and.(INDMAX(ic)+2).le.NCLSTR1)then
               nbad=nbad+1-CLBAD(INDMAX(ic)+2)           
            endif
         endif
         
c         if(ncog.ge.5)then
c            print*,'function CLBAD(NCOG,IC) ==> WARNING!! NCOG=',NCOG
c     $           ,' not implemented'
c         endif
            
      elseif(ncog.eq.0)then
*     =========================
*     COG computation
*     =========================


         
         iv=VIEW(ic)         
         if(mod(iv,2).eq.1)incut=incuty
         if(mod(iv,2).eq.0)incut=incutx
         
         istart = INDSTART(IC)
         istop  = TOTCLLENGTH
         if(ic.lt.NCLSTR1)istop=INDSTART(IC+1)-1
         nbad = 0
c$$$         do i=istart,istop
c$$$            cut  = incut*CLSIGMA(i)            
c$$$            if(CLSIGNAL(i).ge.cut)nbad = nbad +1 -CLBAD(i)
c$$$         enddo
         do i = INDMAX(IC),istart,-1
            cut  = incut*CLSIGMA(i)
            if(CLSIGNAL(i).ge.cut)then
               nbad = nbad +1 -CLBAD(i)
            else
               goto 10
            endif
         enddo
 10      continue
         do i = INDMAX(IC)+1,istop
            cut  = incut*CLSIGMA(i)
            if(CLSIGNAL(i).ge.cut)then
               nbad = nbad +1 -CLBAD(i)
            else
               goto 20
            endif
         enddo
 20      continue
         
      else
         
c         print*,'function CLBAD(NCOG,IC) ==> WARNING!! NCOG=',NCOG
c     $        ,' not implemented'
         

      endif

      nbadstrips = nbad 

      return
      end