*************************************************************************
*     
*     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

c$$$      
c$$$c$$$c------------------------------------------------------------------------
c$$$c$$$
c$$$c$$$c     NB: le coordinate in mech_pos.dat sono calcolate a partire da alcuni dati
c$$$c$$$c     contenuti in commontracker.f. forse si puo' evitare mech_pos.dat e mettere
c$$$c$$$c     tutto in commontracker.f
c$$$c$$$
c$$$c$$$
c$$$c$$$      subroutine mech_sensor    !it reads sensors coordinates (in PAMELA reference
c$$$c$$$                                ! frame) from a text file and it uses them to fill
c$$$c$$$                                ! x/y/z_mech_sensor variables, taking into account
c$$$c$$$                                ! last plane inversion
c$$$c$$$
c$$$c$$$      include './commontracker.f'
c$$$c$$$      include './common_tracks.f'
c$$$c$$$
c$$$c$$$      real xvec(nladders_view),yvec(2),zvec(nplanes)
c$$$c$$$
c$$$c$$$      integer id                !file identifier
c$$$c$$$      logical od                !.true. if the specified unit is connected to a file
c$$$c$$$
c$$$c$$$      do id=20,100,1            !opens the file using a free file id
c$$$c$$$        inquire (id, opened=od)
c$$$c$$$        if(.not.od) goto 666
c$$$c$$$      enddo      
c$$$c$$$ 666  continue
c$$$c$$$
c$$$c$$$      open(id,FILE='../common/mech_pos.dat') !sensors centres coordinates in mm in 
c$$$c$$$                                ! PAMELA reference frame:
c$$$c$$$                                ! the first plane is the one with lowest Z (the one
c$$$c$$$                                ! nearest the calorimeter)
c$$$c$$$                                ! the first ladder is the one with lowest X (the
c$$$c$$$                                ! one on which the first X strip is)
c$$$c$$$                                ! the first sensor is the one with lowest Y (the
c$$$c$$$                                ! one on which the first Y strip is) for planes
c$$$c$$$                                ! 2..6. for plane 1 the first sensor has higher Y
c$$$c$$$
c$$$c$$$      read(20,*) xvec
c$$$c$$$      read(20,*) yvec
c$$$c$$$      read(20,*) zvec
c$$$c$$$
c$$$c$$$      do i=1,nplanes
c$$$c$$$        do j=1,nladders_view
c$$$c$$$          do k=1,2
c$$$c$$$            x_mech_sensor(i,j,k)=xvec(j)
c$$$c$$$            y_mech_sensor(i,j,k)=yvec(k)
c$$$c$$$            z_mech_sensor(i,j,k)=zvec(i)
c$$$c$$$            if(i.eq.1) then     !y coordinates of first plane (11th view) are
c$$$c$$$              y_mech_sensor(i,j,k)=-yvec(k) ! exchanged due to last plane inversion
c$$$c$$$            endif              
c$$$c$$$          enddo
c$$$c$$$        enddo
c$$$c$$$      enddo
c$$$c$$$
c$$$c$$$      close(id)
c$$$c$$$
c$$$c$$$
c$$$c$$$c$$$  ! *** INIZIO DEBUG ***
c$$$c$$$c$$$  do i=1,6
c$$$c$$$c$$$  do j=1,3
c$$$c$$$c$$$  do k=1,2
c$$$c$$$c$$$  c            print*,x_mech_sensor(1,j,k)
c$$$c$$$c$$$  print*,y_mech_sensor(i,j,k)
c$$$c$$$c$$$  c            print*,z_mech_sensor(i,j,k)
c$$$c$$$c$$$  enddo
c$$$c$$$c$$$  enddo
c$$$c$$$c$$$  print*,' '
c$$$c$$$c$$$  enddo
c$$$c$$$c$$$  ! *** FINE DEBUG ***
c$$$c$$$
c$$$c$$$      
c$$$c$$$      return
c$$$c$$$      end


c$$$c------------------------------------------------------------------------
c$$$
c$$$c     NB: le coordinate in mech_pos.dat sono calcolate a partire da alcuni dati
c$$$c     contenuti in commontracker.f. forse si puo' evitare mech_pos.dat e mettere
c$$$c     tutto in commontracker.f
c$$$
c$$$
c$$$      subroutine mech_sensor    
c$$$c     !it reads sensors coordinates (in PAMELA reference
c$$$c     ! frame) from a text file and it uses them to fill
c$$$c     ! x/y/z_mech_sensor variables, taking into account
c$$$c     ! last plane inversion
c$$$
c$$$      include './commontracker.f'
c$$$      include './common_tracks.f'
c$$$
c$$$      real xvec(nladders_view),yvec(2),zvec(nplanes)
c$$$
c$$$      integer id                !file identifier
c$$$      logical od                !.true. if the specified unit is connected to a file
c$$$
c$$$      do id=20,100,1            !opens the file using a free file id
c$$$        inquire (id, opened=od)
c$$$        if(.not.od) goto 666
c$$$      enddo      
c$$$ 666  continue
c$$$
c$$$c      open(id,FILE='../common/mech_pos.dat') !sensors centres coordinates in mm in 
c$$$c      open(id,FILE='source/common/mech_pos.dat') 
c$$$c      call system('cp $TRK_GRND/source/common/mech_pos.dat .')
c$$$      print *,'Opening file: mech_pos.dat'
c$$$      open(id,FILE='./bin-aux/mech_pos.dat',IOSTAT=iostat) 
c$$$c     !sensors centres coordinates in mm in 
c$$$c     ! PAMELA reference frame:
c$$$c     ! the first plane is the one with lowest Z (the one
c$$$c     ! nearest the calorimeter)
c$$$c     ! the first ladder is the one with lowest X (the
c$$$c     ! one on which the first X strip is)
c$$$c     ! the first sensor is the one with lowest Y (the
c$$$c     ! one on which the first Y strip is) for planes
c$$$c     ! 2..6. for plane 1 the first sensor has higher Y
c$$$      
c$$$      if(iostat.ne.0)then
c$$$         print*,'MECH_SENSOR: *** Error in opening file ***'
c$$$         return
c$$$      endif
c$$$
c$$$      read(id,*) xvec
c$$$      read(id,*) yvec
c$$$      read(id,*) zvec
c$$$
c$$$      do i=1,nplanes
c$$$        do j=1,nladders_view
c$$$          do k=1,2
c$$$            x_mech_sensor(i,j,k)=xvec(j)
c$$$            y_mech_sensor(i,j,k)=yvec(k)
c$$$            z_mech_sensor(i,j,k)=zvec(i)
c$$$            if(i.eq.1) then     !y coordinates of first plane (11th view) are
c$$$              y_mech_sensor(i,j,k)=-yvec(k) ! exchanged due to last plane inversion
c$$$            endif              
c$$$          enddo
c$$$        enddo
c$$$      enddo
c$$$
c$$$      close(id)
c$$$c      call system('rm -f mech_pos.dat')
c$$$
c$$$c$$$                                ! *** INIZIO DEBUG ***
c$$$c$$$      do i=1,6
c$$$c$$$c        do j=1,3
c$$$c$$$          do k=1,2
c$$$c$$$            j=1
c$$$c$$$c            print*,x_mech_sensor(1,j,k)
c$$$c$$$            print*,y_mech_sensor(i,j,k)
c$$$c$$$c            print*,z_mech_sensor(i,j,k)
c$$$c$$$          enddo
c$$$c$$$c        enddo
c$$$c$$$        print*,' '
c$$$c$$$      enddo
c$$$c$$$                                ! *** FINE DEBUG ***
c$$$
c$$$      
c$$$      return
c$$$      end
c$$$
c$$$
c$$$c------------------------------------------------------------------------


      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

        if((is.le.3).or.(is.ge.1022)) then !X has 1018 strips...
          print*,'functions: WARNING: false X strip: strip ',is
        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

        if((is.le.3).or.(is.ge.1022)) then !X has 1018 strips...
          print*,'functions: WARNING: false X strip: strip ',is
        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.
      
      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------------------------------------------------------------------------