MODULE Threshold USE f90_kind PRIVATE PUBLIC :: POLY ! values for these parameters are read in from file TPCinput.txt !-- thresholds REAL,PUBLIC,SAVE :: minSignal =1.0 , & ! min level for a signal smallSignal =1.0 , & ! min level to determine T0 minSignalVeto=0.0 , & ! min level in Veto couter to reject event minSignalRow =1.0 , & ! min level of signal in a row minSignalCalib=10.0 , & ! min level of signal used for calibration minDistPad =0.0 ! min distance between pads to be called adjacent INTEGER,PUBLIC,SAVE :: minHitTrack =2 ! min number of rows with signal > minSignalRow requied for a track !-- pulse shape and fitting stuff REAL,PUBLIC,SAVE :: tBin0 =0.0 , & ! time bin of T=0 tBin2ns =0.0 , & ! nsec per timebin vDrift =0.0 ! drift velocity REAL,PUBLIC,SAVE,ALLOCATABLE,DIMENSION(:) :: riseTimePar,fallTimePar ! riseTimePar,fallTimePar as function of time bin REAL,PUBLIC,SAVE,ALLOCATABLE,DIMENSION(:) :: & gainCor, & ! gainCor(nGroups) Pedestal, & ! Pedestal(nGroups) riseTimeGr, & ! riseTimeGr(nGroups) fallTimeGr ! fallTimeGr(nGroups) INTEGER,PUBLIC,SAVE,ALLOCATABLE,DIMENSION(:) :: & iRowBias ! iRowBias(nRows) ; rows for which a bias is given REAL(KIND=double),PUBLIC,SAVE,ALLOCATABLE,DIMENSION(:) :: & biasX ! biasX(nPkt_bias) ! x valus at which the bias is given, same for all rows REAL(KIND=double),PUBLIC,SAVE,ALLOCATABLE,DIMENSION(:,:) :: & biasData ! biasData(nPKT_bias,nRows_bias) REAL,PUBLIC,SAVE,ALLOCATABLE,DIMENSION(:) :: & trackWidthPar, & ! trackWidthPar as function of drift distance PRFdel ! PadResponseFunction base width REAL,PUBLIC,SAVE :: PRFa =-0.6, & ! PRF shape parameter PRFb = 0.0 ! PRF shape parameter REAL,PUBLIC,SAVE,ALLOCATABLE,DIMENSION(:) :: & AERRpar ! Amplitude error for chisq fit !-- for pulse fit REAL,PUBLIC :: ADC2Electron=1.0, & ! ADC -> nElectron scale factor pNoise=0.005 ! noise Level for fit INTEGER,PUBLIC :: Tshift=10 ! difference between TMax and T0 !-- steering parameters INTEGER,PUBLIC :: FitType = 1 ! type of track fit ! 1=likelihood ; 2=likelihood truncated ; 3=chisq LOGICAL,PUBLIC :: Lcalib =.FALSE., & ! do calibration or read from file Lcalhist =.FALSE., & ! calibration histograms for each group? Lplot =.TRUE., & ! en/disable pulse plots LDData =.FALSE., & ! write Dense Data LoldDD =.FALSE., & ! read old DD format (no track) LPRF =.FALSE. ! use PRF parametrisation ! -- filled automatically depending on file TPCpedestal.txt LOGICAL,PUBLIC,SAVE :: LPedestalEvent=.TRUE. CONTAINS FUNCTION POLY(x,par) RESULT(y) ! evaluate the polynomial y = x + x*par(1) + x**2*par(2) + ... REAL,INTENT(IN) :: x REAL,DIMENSION(:),INTENT(IN) :: par REAL :: y INTEGER :: i y = 0.0 DO i = size(par),1,-1 y = par(i) + x*y ENDDO END FUNCTION POLY END MODULE Threshold