- class Castable a b where
- class FPtr a where
- type Raw a :: *
- get_fptr :: a -> ForeignPtr (Raw a)
- cast_fptr_to_obj :: ForeignPtr (Raw a) -> a
- class Existable a where
- data Exist a :: *
- xformnull :: Castable a ca => IO ca -> IO a
- xform0 :: (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y
- xform1 :: (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y
- xform2 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) => (ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y
- xform3 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO y
- xform4 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> IO y
- xform5 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO y
- xform6 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO y
- xform7 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO y
- xform8 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable x8 cx8, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO y
- xform9 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable x8 cx8, Castable x9 cx9, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> cx9 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO y
- xform10 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable x8 cx8, Castable x9 cx9, Castable x10 cx10, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> cx9 -> cx10 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> x10 -> IO y
- xform11 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable x8 cx8, Castable x9 cx9, Castable x10 cx10, Castable x11 cx11, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> cx9 -> cx10 -> cx11 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> x10 -> x11 -> IO y
- data RawTObject
- newtype TObject = TObject (ForeignPtr RawTObject)
- data RawTNamed
- newtype TNamed = TNamed (ForeignPtr RawTNamed)
- data RawTClass
- newtype TClass = TClass (ForeignPtr RawTClass)
- data RawTFormula
- newtype TFormula = TFormula (ForeignPtr RawTFormula)
- data RawTAtt3D
- newtype TAtt3D = TAtt3D (ForeignPtr RawTAtt3D)
- data RawTAttAxis
- newtype TAttAxis = TAttAxis (ForeignPtr RawTAttAxis)
- data RawTAttBBox
- newtype TAttBBox = TAttBBox (ForeignPtr RawTAttBBox)
- data RawTAttCanvas
- newtype TAttCanvas = TAttCanvas (ForeignPtr RawTAttCanvas)
- data RawTAttFill
- newtype TAttFill = TAttFill (ForeignPtr RawTAttFill)
- data RawTAttImage
- newtype TAttImage = TAttImage (ForeignPtr RawTAttImage)
- data RawTAttLine
- newtype TAttLine = TAttLine (ForeignPtr RawTAttLine)
- data RawTAttMarker
- newtype TAttMarker = TAttMarker (ForeignPtr RawTAttMarker)
- data RawTAttPad
- newtype TAttPad = TAttPad (ForeignPtr RawTAttPad)
- data RawTAttParticle
- newtype TAttParticle = TAttParticle (ForeignPtr RawTAttParticle)
- data RawTAttText
- newtype TAttText = TAttText (ForeignPtr RawTAttText)
- data RawTHStack
- newtype THStack = THStack (ForeignPtr RawTHStack)
- data RawTF1
- newtype TF1 = TF1 (ForeignPtr RawTF1)
- data RawTGraph
- newtype TGraph = TGraph (ForeignPtr RawTGraph)
- data RawTGraphAsymmErrors
- newtype TGraphAsymmErrors = TGraphAsymmErrors (ForeignPtr RawTGraphAsymmErrors)
- data RawTCutG
- newtype TCutG = TCutG (ForeignPtr RawTCutG)
- data RawTGraphBentErrors
- newtype TGraphBentErrors = TGraphBentErrors (ForeignPtr RawTGraphBentErrors)
- data RawTGraphErrors
- newtype TGraphErrors = TGraphErrors (ForeignPtr RawTGraphErrors)
- data RawTGraphPolar
- newtype TGraphPolar = TGraphPolar (ForeignPtr RawTGraphPolar)
- data RawTGraphQQ
- newtype TGraphQQ = TGraphQQ (ForeignPtr RawTGraphQQ)
- data RawTEllipse
- newtype TEllipse = TEllipse (ForeignPtr RawTEllipse)
- data RawTArc
- newtype TArc = TArc (ForeignPtr RawTArc)
- data RawTCrown
- newtype TCrown = TCrown (ForeignPtr RawTCrown)
- data RawTLine
- newtype TLine = TLine (ForeignPtr RawTLine)
- data RawTArrow
- newtype TArrow = TArrow (ForeignPtr RawTArrow)
- data RawTGaxis
- newtype TGaxis = TGaxis (ForeignPtr RawTGaxis)
- data RawTShape
- newtype TShape = TShape (ForeignPtr RawTShape)
- data RawTBRIK
- newtype TBRIK = TBRIK (ForeignPtr RawTBRIK)
- data RawTTUBE
- newtype TTUBE = TTUBE (ForeignPtr RawTTUBE)
- data RawTPCON
- newtype TPCON = TPCON (ForeignPtr RawTPCON)
- data RawTSPHE
- newtype TSPHE = TSPHE (ForeignPtr RawTSPHE)
- data RawTXTRU
- newtype TXTRU = TXTRU (ForeignPtr RawTXTRU)
- data RawTBox
- newtype TBox = TBox (ForeignPtr RawTBox)
- data RawTPave
- newtype TPave = TPave (ForeignPtr RawTPave)
- data RawTPaveText
- newtype TPaveText = TPaveText (ForeignPtr RawTPaveText)
- data RawTDiamond
- newtype TDiamond = TDiamond (ForeignPtr RawTDiamond)
- data RawTPaveStats
- newtype TPaveStats = TPaveStats (ForeignPtr RawTPaveStats)
- data RawTPavesText
- newtype TPavesText = TPavesText (ForeignPtr RawTPavesText)
- data RawTLegend
- newtype TLegend = TLegend (ForeignPtr RawTLegend)
- data RawTLegendEntry
- newtype TLegendEntry = TLegendEntry (ForeignPtr RawTLegendEntry)
- data RawTPaveLabel
- newtype TPaveLabel = TPaveLabel (ForeignPtr RawTPaveLabel)
- data RawTPaveClass
- newtype TPaveClass = TPaveClass (ForeignPtr RawTPaveClass)
- data RawTWbox
- newtype TWbox = TWbox (ForeignPtr RawTWbox)
- data RawTFrame
- newtype TFrame = TFrame (ForeignPtr RawTFrame)
- data RawTSliderBox
- newtype TSliderBox = TSliderBox (ForeignPtr RawTSliderBox)
- data RawTTree
- newtype TTree = TTree (ForeignPtr RawTTree)
- data RawTChain
- newtype TChain = TChain (ForeignPtr RawTChain)
- data RawTNtuple
- newtype TNtuple = TNtuple (ForeignPtr RawTNtuple)
- data RawTNtupleD
- newtype TNtupleD = TNtupleD (ForeignPtr RawTNtupleD)
- data RawTTreeSQL
- newtype TTreeSQL = TTreeSQL (ForeignPtr RawTTreeSQL)
- data RawTPolyLine
- newtype TPolyLine = TPolyLine (ForeignPtr RawTPolyLine)
- data RawTCurlyLine
- newtype TCurlyLine = TCurlyLine (ForeignPtr RawTCurlyLine)
- data RawTCurlyArc
- newtype TCurlyArc = TCurlyArc (ForeignPtr RawTCurlyArc)
- data RawTEfficiency
- newtype TEfficiency = TEfficiency (ForeignPtr RawTEfficiency)
- data RawTAxis
- newtype TAxis = TAxis (ForeignPtr RawTAxis)
- data RawTLatex
- newtype TLatex = TLatex (ForeignPtr RawTLatex)
- data RawTText
- newtype TText = TText (ForeignPtr RawTText)
- data RawTDirectory
- newtype TDirectory = TDirectory (ForeignPtr RawTDirectory)
- data RawTDirectoryFile
- newtype TDirectoryFile = TDirectoryFile (ForeignPtr RawTDirectoryFile)
- data RawTFile
- newtype TFile = TFile (ForeignPtr RawTFile)
- data RawTBranch
- newtype TBranch = TBranch (ForeignPtr RawTBranch)
- data RawTVirtualTreePlayer
- newtype TVirtualTreePlayer = TVirtualTreePlayer (ForeignPtr RawTVirtualTreePlayer)
- data RawTTreePlayer
- newtype TTreePlayer = TTreePlayer (ForeignPtr RawTTreePlayer)
- data RawTArray
- newtype TArray = TArray (ForeignPtr RawTArray)
- data RawTArrayC
- newtype TArrayC = TArrayC (ForeignPtr RawTArrayC)
- data RawTArrayD
- newtype TArrayD = TArrayD (ForeignPtr RawTArrayD)
- data RawTArrayF
- newtype TArrayF = TArrayF (ForeignPtr RawTArrayF)
- data RawTArrayI
- newtype TArrayI = TArrayI (ForeignPtr RawTArrayI)
- data RawTArrayL
- newtype TArrayL = TArrayL (ForeignPtr RawTArrayL)
- data RawTArrayL64
- newtype TArrayL64 = TArrayL64 (ForeignPtr RawTArrayL64)
- data RawTArrayS
- newtype TArrayS = TArrayS (ForeignPtr RawTArrayS)
- data RawTH1
- newtype TH1 = TH1 (ForeignPtr RawTH1)
- data RawTH2
- newtype TH2 = TH2 (ForeignPtr RawTH2)
- data RawTH3
- newtype TH3 = TH3 (ForeignPtr RawTH3)
- data RawTH1C
- newtype TH1C = TH1C (ForeignPtr RawTH1C)
- data RawTH1D
- newtype TH1D = TH1D (ForeignPtr RawTH1D)
- data RawTH1F
- newtype TH1F = TH1F (ForeignPtr RawTH1F)
- data RawTH1I
- newtype TH1I = TH1I (ForeignPtr RawTH1I)
- data RawTH1S
- newtype TH1S = TH1S (ForeignPtr RawTH1S)
- data RawTH2C
- newtype TH2C = TH2C (ForeignPtr RawTH2C)
- data RawTH2D
- newtype TH2D = TH2D (ForeignPtr RawTH2D)
- data RawTH2F
- newtype TH2F = TH2F (ForeignPtr RawTH2F)
- data RawTH2I
- newtype TH2I = TH2I (ForeignPtr RawTH2I)
- data RawTH2Poly
- newtype TH2Poly = TH2Poly (ForeignPtr RawTH2Poly)
- data RawTH2S
- newtype TH2S = TH2S (ForeignPtr RawTH2S)
- data RawTH3C
- newtype TH3C = TH3C (ForeignPtr RawTH3C)
- data RawTH3D
- newtype TH3D = TH3D (ForeignPtr RawTH3D)
- data RawTH3F
- newtype TH3F = TH3F (ForeignPtr RawTH3F)
- data RawTH3I
- newtype TH3I = TH3I (ForeignPtr RawTH3I)
- data RawTH3S
- newtype TH3S = TH3S (ForeignPtr RawTH3S)
- data RawTQObject
- newtype TQObject = TQObject (ForeignPtr RawTQObject)
- data RawTVirtualPad
- newtype TVirtualPad = TVirtualPad (ForeignPtr RawTVirtualPad)
- data RawTPad
- newtype TPad = TPad (ForeignPtr RawTPad)
- data RawTButton
- newtype TButton = TButton (ForeignPtr RawTButton)
- data RawTGroupButton
- newtype TGroupButton = TGroupButton (ForeignPtr RawTGroupButton)
- data RawTCanvas
- newtype TCanvas = TCanvas (ForeignPtr RawTCanvas)
- data RawTDialogCanvas
- newtype TDialogCanvas = TDialogCanvas (ForeignPtr RawTDialogCanvas)
- data RawTInspectCanvas
- newtype TInspectCanvas = TInspectCanvas (ForeignPtr RawTInspectCanvas)
- data RawTEvePad
- newtype TEvePad = TEvePad (ForeignPtr RawTEvePad)
- data RawTSlider
- newtype TSlider = TSlider (ForeignPtr RawTSlider)
- data RawTApplication
- newtype TApplication = TApplication (ForeignPtr RawTApplication)
- data RawTRint
- newtype TRint = TRint (ForeignPtr RawTRint)
- data RawTRandom
- newtype TRandom = TRandom (ForeignPtr RawTRandom)
- data RawTCollection
- newtype TCollection = TCollection (ForeignPtr RawTCollection)
- data RawTSeqCollection
- newtype TSeqCollection = TSeqCollection (ForeignPtr RawTSeqCollection)
- data RawTObjArray
- newtype TObjArray = TObjArray (ForeignPtr RawTObjArray)
- data RawTList
- newtype TList = TList (ForeignPtr RawTList)
- data RawTKey
- newtype TKey = TKey (ForeignPtr RawTKey)
- data RawTDatime
- newtype TDatime = TDatime (ForeignPtr RawTDatime)
- class IDeletable a where
- class IDeletable a => ITObject a where
- draw :: a -> String -> IO ()
- findObject :: a -> String -> IO (Exist TObject)
- getName :: a -> IO String
- isA :: a -> IO (Exist TClass)
- isFolder :: a -> IO Int
- isEqual :: (ITObject c0, FPtr c0) => a -> c0 -> IO Int
- isSortable :: a -> IO Int
- paint :: a -> String -> IO ()
- printObj :: a -> String -> IO ()
- recursiveRemove :: (ITObject c0, FPtr c0) => a -> c0 -> IO ()
- saveAs :: a -> String -> String -> IO ()
- useCurrentStyle :: a -> IO ()
- write :: a -> String -> Int -> Int -> IO Int
- class ITObject a => ITNamed a where
- class ITNamed a => ITDictionary a
- class ITDictionary a => ITClass a
- class ITNamed a => ITFormula a where
- compile :: a -> String -> IO Int
- clear :: a -> String -> IO ()
- definedValue :: a -> Int -> IO Double
- eval :: a -> Double -> Double -> Double -> Double -> IO Double
- evalParOld :: a -> [Double] -> [Double] -> IO Double
- evalPar :: a -> [Double] -> [Double] -> IO Double
- getNdim :: a -> IO Int
- getNpar :: a -> IO Int
- getNumber :: a -> IO Int
- getParNumber :: a -> String -> IO Int
- isLinear :: a -> IO Int
- isNormalized :: a -> IO Int
- setNumber :: a -> Int -> IO ()
- setParameter :: a -> String -> Double -> IO ()
- setParameters :: a -> [Double] -> IO ()
- setParName :: a -> Int -> String -> IO ()
- setParNames :: a -> String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> IO ()
- update :: a -> IO ()
- class IDeletable a => ITAtt3D a
- class IDeletable a => ITAttAxis a where
- getNdivisions :: a -> IO Int
- getAxisColor :: a -> IO Int
- getLabelColor :: a -> IO Int
- getLabelFont :: a -> IO Int
- getLabelOffset :: a -> IO Double
- getLabelSize :: a -> IO Double
- getTitleOffset :: a -> IO Double
- getTitleSize :: a -> IO Double
- getTickLength :: a -> IO Double
- getTitleFont :: a -> IO Int
- setNdivisions :: a -> Int -> Int -> IO ()
- setAxisColor :: a -> Int -> IO ()
- setLabelColor :: a -> Int -> IO ()
- setLabelFont :: a -> Int -> IO ()
- setLabelOffset :: a -> Double -> IO ()
- setLabelSize :: a -> Double -> IO ()
- setTickLength :: a -> Double -> IO ()
- setTitleOffset :: a -> Double -> IO ()
- setTitleSize :: a -> Double -> IO ()
- setTitleColor :: a -> Int -> IO ()
- setTitleFont :: a -> Int -> IO ()
- class IDeletable a => ITAttBBox a
- class IDeletable a => ITAttCanvas a
- class IDeletable a => ITAttFill a where
- setFillColor :: a -> Int -> IO ()
- setFillStyle :: a -> Int -> IO ()
- class IDeletable a => ITAttImage a
- class IDeletable a => ITAttLine a where
- setLineColor :: a -> Int -> IO ()
- class IDeletable a => ITAttMarker a
- class IDeletable a => ITAttPad a
- class ITNamed a => ITAttParticle a
- class IDeletable a => ITAttText a where
- setTextColor :: a -> Int -> IO ()
- setTextAlign :: a -> Int -> IO ()
- setTextSize :: a -> Double -> IO ()
- class ITNamed a => ITHStack a
- class (ITFormula a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITF1 a where
- derivative :: a -> Double -> [Double] -> Double -> IO Double
- derivative2 :: a -> Double -> [Double] -> Double -> IO Double
- derivative3 :: a -> Double -> [Double] -> Double -> IO Double
- drawCopyTF1 :: a -> String -> IO a
- drawDerivative :: a -> String -> IO (Exist TObject)
- drawIntegral :: a -> String -> IO (Exist TObject)
- drawF1 :: a -> String -> Double -> Double -> String -> IO ()
- fixParameter :: a -> Int -> Double -> IO ()
- getMaximumTF1 :: a -> Double -> Double -> Double -> Double -> Int -> IO Double
- getMinimumTF1 :: a -> Double -> Double -> Double -> Double -> Int -> IO Double
- getMaximumX :: a -> Double -> Double -> Double -> Double -> Int -> IO Double
- getMinimumX :: a -> Double -> Double -> Double -> Double -> Int -> IO Double
- getNDF :: a -> IO Int
- getNpx :: a -> IO Int
- getNumberFreeParameters :: a -> IO Int
- getNumberFitPoints :: a -> IO Int
- getParError :: a -> Int -> IO Double
- getProb :: a -> IO Double
- getQuantilesTF1 :: a -> Int -> [Double] -> [Double] -> IO Int
- getRandomTF1 :: a -> Double -> Double -> IO Double
- getSave :: a -> [Double] -> IO Double
- getX :: a -> Double -> Double -> Double -> Double -> Int -> IO Double
- getXmin :: a -> IO Double
- getXmax :: a -> IO Double
- gradientPar :: a -> Int -> [Double] -> Double -> IO Double
- initArgs :: a -> [Double] -> [Double] -> IO ()
- integralTF1 :: a -> Double -> Double -> [Double] -> Double -> IO Double
- integralError :: a -> Double -> Double -> [Double] -> [Double] -> Double -> IO Double
- integralFast :: a -> Int -> [Double] -> [Double] -> Double -> Double -> [Double] -> Double -> IO Double
- isInside :: a -> [Double] -> IO Int
- releaseParameter :: a -> Int -> IO ()
- setChisquare :: a -> Double -> IO ()
- setMaximumTF1 :: a -> Double -> IO ()
- setMinimumTF1 :: a -> Double -> IO ()
- setNDF :: a -> Int -> IO ()
- setNumberFitPoints :: a -> Int -> IO ()
- setNpx :: a -> Int -> IO ()
- setParError :: a -> Int -> Double -> IO ()
- setParErrors :: a -> [Double] -> IO ()
- setParLimits :: a -> Int -> Double -> Double -> IO ()
- setParent :: (ITObject c0, FPtr c0) => a -> c0 -> IO ()
- setRange1 :: a -> Double -> Double -> IO ()
- setRange2 :: a -> Double -> Double -> Double -> Double -> IO ()
- setRange3 :: a -> Double -> Double -> Double -> Double -> Double -> Double -> IO ()
- setSavedPoint :: a -> Int -> Double -> IO ()
- moment :: a -> Double -> Double -> Double -> [Double] -> Double -> IO Double
- centralMoment :: a -> Double -> Double -> Double -> [Double] -> Double -> IO Double
- mean :: a -> Double -> Double -> [Double] -> Double -> IO Double
- variance :: a -> Double -> Double -> [Double] -> Double -> IO Double
- class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITGraph a where
- apply :: (ITF1 c0, FPtr c0) => a -> c0 -> IO ()
- chisquare :: (ITF1 c0, FPtr c0) => a -> c0 -> IO Double
- drawGraph :: a -> Int -> [Double] -> [Double] -> String -> IO ()
- drawPanelTGraph :: a -> IO ()
- expand :: a -> Int -> Int -> IO ()
- fitPanelTGraph :: a -> IO ()
- getCorrelationFactorTGraph :: a -> IO Double
- getCovarianceTGraph :: a -> IO Double
- getMeanTGraph :: a -> Int -> IO Double
- getRMSTGraph :: a -> Int -> IO Double
- getErrorX :: a -> Int -> IO Double
- getErrorY :: a -> Int -> IO Double
- getErrorXhigh :: a -> Int -> IO Double
- getErrorXlow :: a -> Int -> IO Double
- getErrorYhigh :: a -> Int -> IO Double
- getErrorYlow :: a -> Int -> IO Double
- initExpo :: a -> Double -> Double -> IO ()
- initGaus :: a -> Double -> Double -> IO ()
- initPolynom :: a -> Double -> Double -> IO ()
- insertPoint :: a -> IO Int
- integralTGraph :: a -> Int -> Int -> IO Double
- isEditable :: a -> IO Int
- isInsideTGraph :: a -> Double -> Double -> IO Int
- leastSquareFit :: a -> Int -> [Double] -> Double -> Double -> IO ()
- paintStats :: (ITF1 c0, FPtr c0) => a -> c0 -> IO ()
- removePoint :: a -> Int -> IO Int
- setEditable :: a -> Int -> IO ()
- setHistogram :: (ITH1F c0, FPtr c0) => a -> c0 -> IO ()
- setMaximumTGraph :: a -> Double -> IO ()
- setMinimumTGraph :: a -> Double -> IO ()
- set :: a -> Int -> IO ()
- setPoint :: a -> Int -> Double -> Double -> IO ()
- class ITGraph a => ITGraphAsymmErrors a
- class ITGraph a => ITCutG a
- class ITGraph a => ITGraphBentErrors a
- class ITGraph a => ITGraphErrors a
- class ITGraphErrors a => ITGraphPolar a
- class ITGraph a => ITGraphQQ a
- class (ITObject a, ITAttLine a, ITAttFill a) => ITEllipse a
- class ITEllipse a => ITArc a
- class ITEllipse a => ITCrown a
- class (ITObject a, ITAttLine a) => ITLine a
- class (ITLine a, ITAttFill a) => ITArrow a
- class (ITLine a, ITAttText a) => ITGaxis a
- class (ITNamed a, ITAttLine a, ITAttFill a, ITAtt3D a) => ITShape a
- class ITShape a => ITBRIK a
- class ITShape a => ITTUBE a
- class ITShape a => ITPCON a
- class ITShape a => ITSPHE a
- class ITShape a => ITXTRU a
- class (ITObject a, ITAttLine a, ITAttFill a) => ITBox a
- class ITBox a => ITPave a
- class (ITPave a, ITAttText a) => ITPaveText a
- class ITPaveText a => ITDiamond a
- class ITPaveText a => ITPaveStats a
- class ITPaveText a => ITPavesText a
- class (ITPave a, ITAttText a) => ITLegend a where
- class (ITObject a, ITAttText a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITLegendEntry a
- class (ITPave a, ITAttText a) => ITPaveLabel a
- class ITPaveLabel a => ITPaveClass a
- class ITBox a => ITWbox a where
- setBorderMode :: a -> Int -> IO ()
- class ITWbox a => ITFrame a
- class ITWbox a => ITSliderBox a
- class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITTree a
- class ITTree a => ITChain a
- class ITTree a => ITNtuple a
- class ITTree a => ITNtupleD a
- class ITTree a => ITTreeSQL a
- class (ITObject a, ITAttLine a, ITAttFill a) => ITPolyLine a
- class ITPolyLine a => ITCurlyLine a
- class ITCurlyLine a => ITCurlyArc a
- class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITEfficiency a
- class (ITNamed a, ITAttAxis a) => ITAxis a where
- setTimeDisplay :: a -> Int -> IO ()
- setTimeFormat :: a -> String -> IO ()
- setTimeOffset :: a -> Double -> String -> IO ()
- class (ITText a, ITAttLine a) => ITLatex a
- class (ITNamed a, ITAttText a) => ITText a
- class ITNamed a => ITDirectory a where
- class ITDirectory a => ITDirectoryFile a where
- getListOfKeys :: a -> IO (Exist TList)
- class ITDirectoryFile a => ITFile a
- class (ITNamed a, ITAttFill a) => ITBranch a
- class ITObject a => ITVirtualTreePlayer a
- class ITVirtualTreePlayer a => ITTreePlayer a
- class IDeletable a => ITArray a
- class ITArray a => ITArrayC a
- class ITArray a => ITArrayD a
- class ITArray a => ITArrayF a
- class ITArray a => ITArrayI a
- class ITArray a => ITArrayL a
- class ITArray a => ITArrayL64 a
- class ITArray a => ITArrayS a
- class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITH1 a where
- add :: (ITH1 c0, FPtr c0) => a -> c0 -> Double -> IO ()
- addBinContent :: a -> Int -> Double -> IO ()
- chi2Test :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> [Double] -> IO Double
- computeIntegral :: a -> IO Double
- directoryAutoAdd :: (ITDirectory c0, FPtr c0) => a -> c0 -> IO ()
- divide :: (ITH2 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> Double -> Double -> String -> IO ()
- drawCopyTH1 :: a -> String -> IO a
- drawNormalized :: a -> String -> Double -> IO (Exist TH1)
- drawPanelTH1 :: a -> IO ()
- bufferEmpty :: a -> Int -> IO Int
- evalF :: (ITF1 c0, FPtr c0) => a -> c0 -> String -> IO ()
- fFT :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> IO (Exist TH1)
- fill1 :: a -> Double -> IO Int
- fill1w :: a -> Double -> Double -> IO Int
- fillN1 :: a -> Int -> [Double] -> [Double] -> Int -> IO ()
- fillRandom :: (ITH1 c0, FPtr c0) => a -> c0 -> Int -> IO ()
- findBin :: a -> Double -> Double -> Double -> IO Int
- findFixBin :: a -> Double -> Double -> Double -> IO Int
- findFirstBinAbove :: a -> Double -> Int -> IO Int
- findLastBinAbove :: a -> Double -> Int -> IO Int
- fitPanelTH1 :: a -> IO ()
- getNdivisionA :: a -> String -> IO Int
- getAxisColorA :: a -> String -> IO Int
- getLabelColorA :: a -> String -> IO Int
- getLabelFontA :: a -> String -> IO Int
- getLabelOffsetA :: a -> String -> IO Double
- getLabelSizeA :: a -> String -> IO Double
- getTitleFontA :: a -> String -> IO Int
- getTitleOffsetA :: a -> String -> IO Double
- getTitleSizeA :: a -> String -> IO Double
- getTickLengthA :: a -> String -> IO Double
- getBarOffset :: a -> IO Double
- getBarWidth :: a -> IO Double
- getContour :: a -> [Double] -> IO Int
- getContourLevel :: a -> Int -> IO Double
- getContourLevelPad :: a -> Int -> IO Double
- getBin :: a -> Int -> Int -> Int -> IO Int
- getBinCenter :: a -> Int -> IO Double
- getBinContent1 :: a -> Int -> IO Double
- getBinContent2 :: a -> Int -> Int -> IO Double
- getBinContent3 :: a -> Int -> Int -> Int -> IO Double
- getBinError1 :: a -> Int -> IO Double
- getBinError2 :: a -> Int -> Int -> IO Double
- getBinError3 :: a -> Int -> Int -> Int -> IO Double
- getBinLowEdge :: a -> Int -> IO Double
- getBinWidth :: a -> Int -> IO Double
- getCellContent :: a -> Int -> Int -> IO Double
- getCellError :: a -> Int -> Int -> IO Double
- getEntries :: a -> IO Double
- getEffectiveEntries :: a -> IO Double
- getFunction :: a -> String -> IO (Exist TF1)
- getDimension :: a -> IO Int
- getKurtosis :: a -> Int -> IO Double
- getLowEdge :: a -> [Double] -> IO ()
- getMaximumTH1 :: a -> Double -> IO Double
- getMaximumBin :: a -> IO Int
- getMaximumStored :: a -> IO Double
- getMinimumTH1 :: a -> Double -> IO Double
- getMinimumBin :: a -> IO Int
- getMinimumStored :: a -> IO Double
- getMean :: a -> Int -> IO Double
- getMeanError :: a -> Int -> IO Double
- getNbinsX :: a -> IO Double
- getNbinsY :: a -> IO Double
- getNbinsZ :: a -> IO Double
- getQuantilesTH1 :: a -> Int -> [Double] -> [Double] -> IO Int
- getRandom :: a -> IO Double
- getStats :: a -> [Double] -> IO ()
- getSumOfWeights :: a -> IO Double
- getSumw2 :: a -> IO (Exist TArrayD)
- getSumw2N :: a -> IO Int
- getRMS :: a -> Int -> IO Double
- getRMSError :: a -> Int -> IO Double
- getSkewness :: a -> Int -> IO Double
- integral1 :: a -> Int -> Int -> String -> IO Double
- interpolate1 :: a -> Double -> IO Double
- interpolate2 :: a -> Double -> Double -> IO Double
- interpolate3 :: a -> Double -> Double -> Double -> IO Double
- kolmogorovTest :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> IO Double
- labelsDeflate :: a -> String -> IO ()
- labelsInflate :: a -> String -> IO ()
- labelsOption :: a -> String -> String -> IO ()
- multiflyF :: (ITF1 c0, FPtr c0) => a -> c0 -> Double -> IO ()
- multiply :: (ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> Double -> Double -> String -> IO ()
- putStats :: a -> [Double] -> IO ()
- rebin :: a -> Int -> String -> [Double] -> IO (Exist TH1)
- rebinAxis :: (ITAxis c0, FPtr c0) => a -> Double -> c0 -> IO ()
- rebuild :: a -> String -> IO ()
- reset :: a -> String -> IO ()
- resetStats :: a -> IO ()
- scale :: a -> Double -> String -> IO ()
- setAxisColorA :: a -> Int -> String -> IO ()
- setAxisRange :: a -> Double -> Double -> String -> IO ()
- setBarOffset :: a -> Double -> IO ()
- setBarWidth :: a -> Double -> IO ()
- setBinContent1 :: a -> Int -> Double -> IO ()
- setBinContent2 :: a -> Int -> Int -> Double -> IO ()
- setBinContent3 :: a -> Int -> Int -> Int -> Double -> IO ()
- setBinError1 :: a -> Int -> Double -> IO ()
- setBinError2 :: a -> Int -> Int -> Double -> IO ()
- setBinError3 :: a -> Int -> Int -> Int -> Double -> IO ()
- setBins1 :: a -> Int -> [Double] -> IO ()
- setBins2 :: a -> Int -> [Double] -> Int -> [Double] -> IO ()
- setBins3 :: a -> Int -> [Double] -> Int -> [Double] -> Int -> [Double] -> IO ()
- setBinsLength :: a -> Int -> IO ()
- setBuffer :: a -> Int -> String -> IO ()
- setCellContent :: a -> Int -> Int -> Double -> IO ()
- setContent :: a -> [Double] -> IO ()
- setContour :: a -> Int -> [Double] -> IO ()
- setContourLevel :: a -> Int -> Double -> IO ()
- setDirectory :: (ITDirectory c0, FPtr c0) => a -> c0 -> IO ()
- setEntries :: a -> Double -> IO ()
- setError :: a -> [Double] -> IO ()
- setLabelColorA :: a -> Int -> String -> IO ()
- setLabelSizeA :: a -> Double -> String -> IO ()
- setLabelFontA :: a -> Int -> String -> IO ()
- setLabelOffsetA :: a -> Double -> String -> IO ()
- setMaximum :: a -> Double -> IO ()
- setMinimum :: a -> Double -> IO ()
- setNormFactor :: a -> Double -> IO ()
- setStats :: a -> Int -> IO ()
- setOption :: a -> String -> IO ()
- setXTitle :: a -> String -> IO ()
- setYTitle :: a -> String -> IO ()
- setZTitle :: a -> String -> IO ()
- showBackground :: a -> Int -> String -> IO (Exist TH1)
- showPeaks :: a -> Double -> String -> Double -> IO Int
- smooth :: a -> Int -> String -> IO ()
- sumw2 :: a -> IO ()
- class ITH1 a => ITH2 a where
- fill2 :: a -> Double -> Double -> IO Int
- fill2w :: a -> Double -> Double -> Double -> IO Int
- fillN2 :: a -> Int -> [Double] -> [Double] -> [Double] -> Int -> IO ()
- fillRandom2 :: (ITH1 c0, FPtr c0) => a -> c0 -> Int -> IO ()
- findFirstBinAbove2 :: a -> Double -> Int -> IO Int
- findLastBinAbove2 :: a -> Double -> Int -> IO Int
- fitSlicesX :: (ITObjArray c1, FPtr c1, ITF1 c0, FPtr c0) => a -> c0 -> Int -> Int -> Int -> String -> c1 -> IO ()
- fitSlicesY :: (ITObjArray c1, FPtr c1, ITF1 c0, FPtr c0) => a -> c0 -> Int -> Int -> Int -> String -> c1 -> IO ()
- getCorrelationFactor2 :: a -> Int -> Int -> IO Double
- getCovariance2 :: a -> Int -> Int -> IO Double
- integral2 :: a -> Int -> Int -> Int -> Int -> String -> IO Double
- rebinX2 :: a -> Int -> String -> IO (Exist TH2)
- rebinY2 :: a -> Int -> String -> IO (Exist TH2)
- rebin2D :: a -> Int -> Int -> String -> IO (Exist TH2)
- setShowProjectionX :: a -> Int -> IO ()
- setShowProjectionY :: a -> Int -> IO ()
- class (ITH1 a, ITAtt3D a) => ITH3 a where
- fill3 :: a -> Double -> Double -> Double -> IO Int
- fill3w :: a -> Double -> Double -> Double -> Double -> IO Int
- fitSlicesZ :: (ITF1 c0, FPtr c0) => a -> c0 -> Int -> Int -> Int -> Int -> Int -> String -> IO ()
- getCorrelationFactor3 :: a -> Int -> Int -> IO Double
- getCovariance3 :: a -> Int -> Int -> IO Double
- rebinX3 :: a -> Int -> String -> IO (Exist TH3)
- rebinY3 :: a -> Int -> String -> IO (Exist TH3)
- rebinZ3 :: a -> Int -> String -> IO (Exist TH3)
- rebin3D :: a -> Int -> Int -> Int -> String -> IO (Exist TH3)
- class (ITH1 a, ITArrayC a) => ITH1C a
- class (ITH1 a, ITArrayD a) => ITH1D a
- class (ITH1 a, ITArrayF a) => ITH1F a
- class (ITH1 a, ITArrayI a) => ITH1I a
- class (ITH1 a, ITArrayS a) => ITH1S a
- class (ITH2 a, ITArrayC a) => ITH2C a
- class (ITH2 a, ITArrayD a) => ITH2D a
- class (ITH2 a, ITArrayF a) => ITH2F a
- class (ITH2 a, ITArrayI a) => ITH2I a
- class ITH2 a => ITH2Poly a
- class (ITH2 a, ITArrayS a) => ITH2S a
- class (ITH3 a, ITArrayC a) => ITH3C a
- class (ITH3 a, ITArrayD a) => ITH3D a
- class (ITH3 a, ITArrayF a) => ITH3F a
- class (ITH3 a, ITArrayI a) => ITH3I a
- class (ITH3 a, ITArrayS a) => ITH3S a
- class IDeletable a => ITQObject a
- class (ITObject a, ITAttLine a, ITAttFill a, ITAttPad a, ITQObject a) => ITVirtualPad a where
- class ITVirtualPad a => ITPad a
- class (ITPad a, ITAttText a) => ITButton a
- class ITButton a => ITGroupButton a
- class ITPad a => ITCanvas a
- class (ITCanvas a, ITAttText a) => ITDialogCanvas a
- class (ITCanvas a, ITAttText a) => ITInspectCanvas a
- class ITPad a => ITEvePad a
- class ITPad a => ITSlider a
- class (ITObject a, ITQObject a) => ITApplication a where
- class ITApplication a => ITRint a
- class ITNamed a => ITRandom a where
- class ITObject a => ITCollection a
- class ITCollection a => ITSeqCollection a
- class ITSeqCollection a => ITObjArray a
- class ITSeqCollection a => ITList a
- class ITNamed a => ITKey a
- class IDeletable a => ITDatime a where
- class ITObject a => ITVirtualHistPainter a
- upcastTObject :: (FPtr a, ITObject a) => a -> TObject
- upcastTNamed :: (FPtr a, ITNamed a) => a -> TNamed
- upcastTClass :: (FPtr a, ITClass a) => a -> TClass
- upcastTFormula :: (FPtr a, ITFormula a) => a -> TFormula
- upcastTAtt3D :: (FPtr a, ITAtt3D a) => a -> TAtt3D
- upcastTAttAxis :: (FPtr a, ITAttAxis a) => a -> TAttAxis
- upcastTAttBBox :: (FPtr a, ITAttBBox a) => a -> TAttBBox
- upcastTAttCanvas :: (FPtr a, ITAttCanvas a) => a -> TAttCanvas
- upcastTAttFill :: (FPtr a, ITAttFill a) => a -> TAttFill
- upcastTAttImage :: (FPtr a, ITAttImage a) => a -> TAttImage
- upcastTAttLine :: (FPtr a, ITAttLine a) => a -> TAttLine
- upcastTAttMarker :: (FPtr a, ITAttMarker a) => a -> TAttMarker
- upcastTAttPad :: (FPtr a, ITAttPad a) => a -> TAttPad
- upcastTAttParticle :: (FPtr a, ITAttParticle a) => a -> TAttParticle
- upcastTAttText :: (FPtr a, ITAttText a) => a -> TAttText
- upcastTHStack :: (FPtr a, ITHStack a) => a -> THStack
- upcastTF1 :: (FPtr a, ITF1 a) => a -> TF1
- upcastTGraph :: (FPtr a, ITGraph a) => a -> TGraph
- upcastTGraphAsymmErrors :: (FPtr a, ITGraphAsymmErrors a) => a -> TGraphAsymmErrors
- upcastTCutG :: (FPtr a, ITCutG a) => a -> TCutG
- upcastTGraphBentErrors :: (FPtr a, ITGraphBentErrors a) => a -> TGraphBentErrors
- upcastTGraphErrors :: (FPtr a, ITGraphErrors a) => a -> TGraphErrors
- upcastTGraphPolar :: (FPtr a, ITGraphPolar a) => a -> TGraphPolar
- upcastTGraphQQ :: (FPtr a, ITGraphQQ a) => a -> TGraphQQ
- upcastTEllipse :: (FPtr a, ITEllipse a) => a -> TEllipse
- upcastTArc :: (FPtr a, ITArc a) => a -> TArc
- upcastTCrown :: (FPtr a, ITCrown a) => a -> TCrown
- upcastTLine :: (FPtr a, ITLine a) => a -> TLine
- upcastTArrow :: (FPtr a, ITArrow a) => a -> TArrow
- upcastTGaxis :: (FPtr a, ITGaxis a) => a -> TGaxis
- upcastTShape :: (FPtr a, ITShape a) => a -> TShape
- upcastTBRIK :: (FPtr a, ITBRIK a) => a -> TBRIK
- upcastTTUBE :: (FPtr a, ITTUBE a) => a -> TTUBE
- upcastTPCON :: (FPtr a, ITPCON a) => a -> TPCON
- upcastTSPHE :: (FPtr a, ITSPHE a) => a -> TSPHE
- upcastTXTRU :: (FPtr a, ITXTRU a) => a -> TXTRU
- upcastTBox :: (FPtr a, ITBox a) => a -> TBox
- upcastTPave :: (FPtr a, ITPave a) => a -> TPave
- upcastTPaveText :: (FPtr a, ITPaveText a) => a -> TPaveText
- upcastTDiamond :: (FPtr a, ITDiamond a) => a -> TDiamond
- upcastTPaveStats :: (FPtr a, ITPaveStats a) => a -> TPaveStats
- upcastTPavesText :: (FPtr a, ITPavesText a) => a -> TPavesText
- upcastTLegend :: (FPtr a, ITLegend a) => a -> TLegend
- upcastTLegendEntry :: (FPtr a, ITLegendEntry a) => a -> TLegendEntry
- upcastTPaveLabel :: (FPtr a, ITPaveLabel a) => a -> TPaveLabel
- upcastTPaveClass :: (FPtr a, ITPaveClass a) => a -> TPaveClass
- upcastTWbox :: (FPtr a, ITWbox a) => a -> TWbox
- upcastTFrame :: (FPtr a, ITFrame a) => a -> TFrame
- upcastTSliderBox :: (FPtr a, ITSliderBox a) => a -> TSliderBox
- upcastTTree :: (FPtr a, ITTree a) => a -> TTree
- upcastTChain :: (FPtr a, ITChain a) => a -> TChain
- upcastTNtuple :: (FPtr a, ITNtuple a) => a -> TNtuple
- upcastTNtupleD :: (FPtr a, ITNtupleD a) => a -> TNtupleD
- upcastTTreeSQL :: (FPtr a, ITTreeSQL a) => a -> TTreeSQL
- upcastTPolyLine :: (FPtr a, ITPolyLine a) => a -> TPolyLine
- upcastTCurlyLine :: (FPtr a, ITCurlyLine a) => a -> TCurlyLine
- upcastTCurlyArc :: (FPtr a, ITCurlyArc a) => a -> TCurlyArc
- upcastTEfficiency :: (FPtr a, ITEfficiency a) => a -> TEfficiency
- upcastTAxis :: (FPtr a, ITAxis a) => a -> TAxis
- upcastTLatex :: (FPtr a, ITLatex a) => a -> TLatex
- upcastTText :: (FPtr a, ITText a) => a -> TText
- upcastTDirectory :: (FPtr a, ITDirectory a) => a -> TDirectory
- upcastTDirectoryFile :: (FPtr a, ITDirectoryFile a) => a -> TDirectoryFile
- upcastTFile :: (FPtr a, ITFile a) => a -> TFile
- upcastTBranch :: (FPtr a, ITBranch a) => a -> TBranch
- upcastTVirtualTreePlayer :: (FPtr a, ITVirtualTreePlayer a) => a -> TVirtualTreePlayer
- upcastTTreePlayer :: (FPtr a, ITTreePlayer a) => a -> TTreePlayer
- upcastTArray :: (FPtr a, ITArray a) => a -> TArray
- upcastTArrayC :: (FPtr a, ITArrayC a) => a -> TArrayC
- upcastTArrayD :: (FPtr a, ITArrayD a) => a -> TArrayD
- upcastTArrayF :: (FPtr a, ITArrayF a) => a -> TArrayF
- upcastTArrayI :: (FPtr a, ITArrayI a) => a -> TArrayI
- upcastTArrayL :: (FPtr a, ITArrayL a) => a -> TArrayL
- upcastTArrayL64 :: (FPtr a, ITArrayL64 a) => a -> TArrayL64
- upcastTArrayS :: (FPtr a, ITArrayS a) => a -> TArrayS
- upcastTH1 :: (FPtr a, ITH1 a) => a -> TH1
- upcastTH2 :: (FPtr a, ITH2 a) => a -> TH2
- upcastTH3 :: (FPtr a, ITH3 a) => a -> TH3
- upcastTH1C :: (FPtr a, ITH1C a) => a -> TH1C
- upcastTH1D :: (FPtr a, ITH1D a) => a -> TH1D
- upcastTH1F :: (FPtr a, ITH1F a) => a -> TH1F
- upcastTH1I :: (FPtr a, ITH1I a) => a -> TH1I
- upcastTH1S :: (FPtr a, ITH1S a) => a -> TH1S
- upcastTH2C :: (FPtr a, ITH2C a) => a -> TH2C
- upcastTH2D :: (FPtr a, ITH2D a) => a -> TH2D
- upcastTH2F :: (FPtr a, ITH2F a) => a -> TH2F
- upcastTH2I :: (FPtr a, ITH2I a) => a -> TH2I
- upcastTH2Poly :: (FPtr a, ITH2Poly a) => a -> TH2Poly
- upcastTH2S :: (FPtr a, ITH2S a) => a -> TH2S
- upcastTH3C :: (FPtr a, ITH3C a) => a -> TH3C
- upcastTH3D :: (FPtr a, ITH3D a) => a -> TH3D
- upcastTH3F :: (FPtr a, ITH3F a) => a -> TH3F
- upcastTH3I :: (FPtr a, ITH3I a) => a -> TH3I
- upcastTH3S :: (FPtr a, ITH3S a) => a -> TH3S
- upcastTQObject :: (FPtr a, ITQObject a) => a -> TQObject
- upcastTVirtualPad :: (FPtr a, ITVirtualPad a) => a -> TVirtualPad
- upcastTPad :: (FPtr a, ITPad a) => a -> TPad
- upcastTButton :: (FPtr a, ITButton a) => a -> TButton
- upcastTGroupButton :: (FPtr a, ITGroupButton a) => a -> TGroupButton
- upcastTCanvas :: (FPtr a, ITCanvas a) => a -> TCanvas
- upcastTDialogCanvas :: (FPtr a, ITDialogCanvas a) => a -> TDialogCanvas
- upcastTInspectCanvas :: (FPtr a, ITInspectCanvas a) => a -> TInspectCanvas
- upcastTEvePad :: (FPtr a, ITEvePad a) => a -> TEvePad
- upcastTSlider :: (FPtr a, ITSlider a) => a -> TSlider
- upcastTApplication :: (FPtr a, ITApplication a) => a -> TApplication
- upcastTRint :: (FPtr a, ITRint a) => a -> TRint
- upcastTRandom :: (FPtr a, ITRandom a) => a -> TRandom
- upcastTCollection :: (FPtr a, ITCollection a) => a -> TCollection
- upcastTSeqCollection :: (FPtr a, ITSeqCollection a) => a -> TSeqCollection
- upcastTObjArray :: (FPtr a, ITObjArray a) => a -> TObjArray
- upcastTList :: (FPtr a, ITList a) => a -> TList
- upcastTKey :: (FPtr a, ITKey a) => a -> TKey
- upcastTDatime :: (FPtr a, ITDatime a) => a -> TDatime
Documentation
class Castable a b whereSource
get_fptr :: a -> ForeignPtr (Raw a)Source
cast_fptr_to_obj :: ForeignPtr (Raw a) -> aSource
xform1 :: (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO ySource
xform2 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) => (ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO ySource
xform3 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> IO cy) -> a -> x1 -> x2 -> x3 -> IO ySource
xform4 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> IO ySource
xform5 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> IO ySource
xform6 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> IO ySource
xform7 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> IO ySource
xform8 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable x8 cx8, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> IO ySource
xform9 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable x8 cx8, Castable x9 cx9, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> cx9 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> IO ySource
xform10 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable x8 cx8, Castable x9 cx9, Castable x10 cx10, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> cx9 -> cx10 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> x10 -> IO ySource
xform11 :: (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable x3 cx3, Castable x4 cx4, Castable x5 cx5, Castable x6 cx6, Castable x7 cx7, Castable x8 cx8, Castable x9 cx9, Castable x10 cx10, Castable x11 cx11, Castable y cy) => (ca -> cx1 -> cx2 -> cx3 -> cx4 -> cx5 -> cx6 -> cx7 -> cx8 -> cx9 -> cx10 -> cx11 -> IO cy) -> a -> x1 -> x2 -> x3 -> x4 -> x5 -> x6 -> x7 -> x8 -> x9 -> x10 -> x11 -> IO ySource
data RawTObject Source
(ITObject a, FPtr a) => Castable a (Ptr RawTObject) |
data RawTFormula Source
(ITFormula a, FPtr a) => Castable a (Ptr RawTFormula) |
data RawTAttAxis Source
(ITAttAxis a, FPtr a) => Castable a (Ptr RawTAttAxis) |
data RawTAttBBox Source
(ITAttBBox a, FPtr a) => Castable a (Ptr RawTAttBBox) |
data RawTAttCanvas Source
(ITAttCanvas a, FPtr a) => Castable a (Ptr RawTAttCanvas) |
newtype TAttCanvas Source
data RawTAttFill Source
(ITAttFill a, FPtr a) => Castable a (Ptr RawTAttFill) |
data RawTAttImage Source
(ITAttImage a, FPtr a) => Castable a (Ptr RawTAttImage) |
data RawTAttLine Source
(ITAttLine a, FPtr a) => Castable a (Ptr RawTAttLine) |
data RawTAttMarker Source
(ITAttMarker a, FPtr a) => Castable a (Ptr RawTAttMarker) |
newtype TAttMarker Source
data RawTAttPad Source
(ITAttPad a, FPtr a) => Castable a (Ptr RawTAttPad) |
data RawTAttParticle Source
(ITAttParticle a, FPtr a) => Castable a (Ptr RawTAttParticle) |
newtype TAttParticle Source
data RawTAttText Source
(ITAttText a, FPtr a) => Castable a (Ptr RawTAttText) |
data RawTHStack Source
(ITHStack a, FPtr a) => Castable a (Ptr RawTHStack) |
Eq TF1 | |
Ord TF1 | |
Show TF1 | |
ITF1 TF1 | |
ITAttMarker TF1 | |
ITAttLine TF1 | |
ITAttFill TF1 | |
ITFormula TF1 | |
ITNamed TF1 | |
ITObject TF1 | |
IDeletable TF1 | |
Existable TF1 | |
FPtr TF1 | |
GADTTypeable TF1 | |
ITF1 (Exist TF1) | |
ITAttMarker (Exist TF1) | |
ITAttLine (Exist TF1) | |
ITAttFill (Exist TF1) | |
ITFormula (Exist TF1) | |
ITNamed (Exist TF1) | |
ITObject (Exist TF1) | |
IDeletable (Exist TF1) | |
FPtr (Exist TF1) |
data RawTGraphAsymmErrors Source
(ITGraphAsymmErrors a, FPtr a) => Castable a (Ptr RawTGraphAsymmErrors) |
newtype TGraphAsymmErrors Source
data RawTGraphBentErrors Source
(ITGraphBentErrors a, FPtr a) => Castable a (Ptr RawTGraphBentErrors) |
newtype TGraphBentErrors Source
data RawTGraphErrors Source
(ITGraphErrors a, FPtr a) => Castable a (Ptr RawTGraphErrors) |
newtype TGraphErrors Source
data RawTGraphPolar Source
(ITGraphPolar a, FPtr a) => Castable a (Ptr RawTGraphPolar) |
newtype TGraphPolar Source
data RawTGraphQQ Source
(ITGraphQQ a, FPtr a) => Castable a (Ptr RawTGraphQQ) |
data RawTEllipse Source
(ITEllipse a, FPtr a) => Castable a (Ptr RawTEllipse) |
data RawTPaveText Source
(ITPaveText a, FPtr a) => Castable a (Ptr RawTPaveText) |
data RawTDiamond Source
(ITDiamond a, FPtr a) => Castable a (Ptr RawTDiamond) |
data RawTPaveStats Source
(ITPaveStats a, FPtr a) => Castable a (Ptr RawTPaveStats) |
newtype TPaveStats Source
data RawTPavesText Source
(ITPavesText a, FPtr a) => Castable a (Ptr RawTPavesText) |
newtype TPavesText Source
data RawTLegend Source
(ITLegend a, FPtr a) => Castable a (Ptr RawTLegend) |
data RawTLegendEntry Source
(ITLegendEntry a, FPtr a) => Castable a (Ptr RawTLegendEntry) |
newtype TLegendEntry Source
data RawTPaveLabel Source
(ITPaveLabel a, FPtr a) => Castable a (Ptr RawTPaveLabel) |
newtype TPaveLabel Source
data RawTPaveClass Source
(ITPaveClass a, FPtr a) => Castable a (Ptr RawTPaveClass) |
newtype TPaveClass Source
data RawTSliderBox Source
(ITSliderBox a, FPtr a) => Castable a (Ptr RawTSliderBox) |
newtype TSliderBox Source
data RawTNtuple Source
(ITNtuple a, FPtr a) => Castable a (Ptr RawTNtuple) |
data RawTNtupleD Source
(ITNtupleD a, FPtr a) => Castable a (Ptr RawTNtupleD) |
data RawTTreeSQL Source
(ITTreeSQL a, FPtr a) => Castable a (Ptr RawTTreeSQL) |
data RawTPolyLine Source
(ITPolyLine a, FPtr a) => Castable a (Ptr RawTPolyLine) |
data RawTCurlyLine Source
(ITCurlyLine a, FPtr a) => Castable a (Ptr RawTCurlyLine) |
newtype TCurlyLine Source
data RawTCurlyArc Source
(ITCurlyArc a, FPtr a) => Castable a (Ptr RawTCurlyArc) |
data RawTEfficiency Source
(ITEfficiency a, FPtr a) => Castable a (Ptr RawTEfficiency) |
newtype TEfficiency Source
data RawTDirectory Source
(ITDirectory a, FPtr a) => Castable a (Ptr RawTDirectory) |
newtype TDirectory Source
data RawTDirectoryFile Source
(ITDirectoryFile a, FPtr a) => Castable a (Ptr RawTDirectoryFile) |
newtype TDirectoryFile Source
data RawTBranch Source
(ITBranch a, FPtr a) => Castable a (Ptr RawTBranch) |
data RawTVirtualTreePlayer Source
(ITVirtualTreePlayer a, FPtr a) => Castable a (Ptr RawTVirtualTreePlayer) |
newtype TVirtualTreePlayer Source
data RawTTreePlayer Source
(ITTreePlayer a, FPtr a) => Castable a (Ptr RawTTreePlayer) |
newtype TTreePlayer Source
data RawTArrayC Source
(ITArrayC a, FPtr a) => Castable a (Ptr RawTArrayC) |
data RawTArrayD Source
(ITArrayD a, FPtr a) => Castable a (Ptr RawTArrayD) |
data RawTArrayF Source
(ITArrayF a, FPtr a) => Castable a (Ptr RawTArrayF) |
data RawTArrayI Source
(ITArrayI a, FPtr a) => Castable a (Ptr RawTArrayI) |
data RawTArrayL Source
(ITArrayL a, FPtr a) => Castable a (Ptr RawTArrayL) |
data RawTArrayL64 Source
(ITArrayL64 a, FPtr a) => Castable a (Ptr RawTArrayL64) |
data RawTArrayS Source
(ITArrayS a, FPtr a) => Castable a (Ptr RawTArrayS) |
Eq TH1 | |
Ord TH1 | |
Show TH1 | |
ITH1 TH1 | |
ITAttMarker TH1 | |
ITAttLine TH1 | |
ITAttFill TH1 | |
ITNamed TH1 | |
ITObject TH1 | |
IDeletable TH1 | |
Existable TH1 | |
FPtr TH1 | |
GADTTypeable TH1 | |
ITH1 (Exist TH1) | |
ITAttMarker (Exist TH1) | |
ITAttLine (Exist TH1) | |
ITAttFill (Exist TH1) | |
ITNamed (Exist TH1) | |
ITObject (Exist TH1) | |
IDeletable (Exist TH1) | |
FPtr (Exist TH1) |
Eq TH2 | |
Ord TH2 | |
Show TH2 | |
ITH2 TH2 | |
ITH1 TH2 | |
ITAttMarker TH2 | |
ITAttLine TH2 | |
ITAttFill TH2 | |
ITNamed TH2 | |
ITObject TH2 | |
IDeletable TH2 | |
Existable TH2 | |
FPtr TH2 | |
GADTTypeable TH2 | |
ITH2 (Exist TH2) | |
ITH1 (Exist TH2) | |
ITAttMarker (Exist TH2) | |
ITAttLine (Exist TH2) | |
ITAttFill (Exist TH2) | |
ITNamed (Exist TH2) | |
ITObject (Exist TH2) | |
IDeletable (Exist TH2) | |
FPtr (Exist TH2) |
Eq TH3 | |
Ord TH3 | |
Show TH3 | |
ITH3 TH3 | |
ITH1 TH3 | |
ITAttMarker TH3 | |
ITAttLine TH3 | |
ITAttFill TH3 | |
ITAtt3D TH3 | |
ITNamed TH3 | |
ITObject TH3 | |
IDeletable TH3 | |
Existable TH3 | |
FPtr TH3 | |
GADTTypeable TH3 | |
ITH3 (Exist TH3) | |
ITH1 (Exist TH3) | |
ITAttMarker (Exist TH3) | |
ITAttLine (Exist TH3) | |
ITAttFill (Exist TH3) | |
ITAtt3D (Exist TH3) | |
ITNamed (Exist TH3) | |
ITObject (Exist TH3) | |
IDeletable (Exist TH3) | |
FPtr (Exist TH3) |
data RawTH2Poly Source
(ITH2Poly a, FPtr a) => Castable a (Ptr RawTH2Poly) |
data RawTQObject Source
(ITQObject a, FPtr a) => Castable a (Ptr RawTQObject) |
data RawTVirtualPad Source
(ITVirtualPad a, FPtr a) => Castable a (Ptr RawTVirtualPad) |
newtype TVirtualPad Source
data RawTButton Source
(ITButton a, FPtr a) => Castable a (Ptr RawTButton) |
data RawTGroupButton Source
(ITGroupButton a, FPtr a) => Castable a (Ptr RawTGroupButton) |
newtype TGroupButton Source
data RawTCanvas Source
(ITCanvas a, FPtr a) => Castable a (Ptr RawTCanvas) |
data RawTDialogCanvas Source
(ITDialogCanvas a, FPtr a) => Castable a (Ptr RawTDialogCanvas) |
newtype TDialogCanvas Source
data RawTInspectCanvas Source
(ITInspectCanvas a, FPtr a) => Castable a (Ptr RawTInspectCanvas) |
newtype TInspectCanvas Source
data RawTEvePad Source
(ITEvePad a, FPtr a) => Castable a (Ptr RawTEvePad) |
data RawTSlider Source
(ITSlider a, FPtr a) => Castable a (Ptr RawTSlider) |
data RawTApplication Source
(ITApplication a, FPtr a) => Castable a (Ptr RawTApplication) |
newtype TApplication Source
data RawTRandom Source
(ITRandom a, FPtr a) => Castable a (Ptr RawTRandom) |
data RawTCollection Source
(ITCollection a, FPtr a) => Castable a (Ptr RawTCollection) |
newtype TCollection Source
data RawTSeqCollection Source
(ITSeqCollection a, FPtr a) => Castable a (Ptr RawTSeqCollection) |
newtype TSeqCollection Source
data RawTObjArray Source
(ITObjArray a, FPtr a) => Castable a (Ptr RawTObjArray) |
data RawTDatime Source
(ITDatime a, FPtr a) => Castable a (Ptr RawTDatime) |
class IDeletable a whereSource
class IDeletable a => ITObject a whereSource
draw :: a -> String -> IO ()Source
void TObject::Draw( char* option )
findObject :: a -> String -> IO (Exist TObject)Source
TObject* TObject::FindObject( char* name )
getName :: a -> IO StringSource
char* TObject::GetName()
isA :: a -> IO (Exist TClass)Source
isEqual :: (ITObject c0, FPtr c0) => a -> c0 -> IO IntSource
isSortable :: a -> IO IntSource
paint :: a -> String -> IO ()Source
void Paint(Option_t *option="")
printObj :: a -> String -> IO ()Source
recursiveRemove :: (ITObject c0, FPtr c0) => a -> c0 -> IO ()Source
void RecursiveRemove(TObject *obj)
saveAs :: a -> String -> String -> IO ()Source
useCurrentStyle :: a -> IO ()Source
class ITObject a => ITNamed a whereSource
Class TNamed reference : http:root.cern.ch
setName :: a -> String -> IO ()Source
setNameTitle :: a -> String -> String -> IO ()Source
setTitle :: a -> String -> IO ()Source
SetTitle method
SetTitle( char* name, char* title )
class ITNamed a => ITDictionary a Source
class ITNamed a => ITFormula a whereSource
compile :: a -> String -> IO IntSource
clear :: a -> String -> IO ()Source
definedValue :: a -> Int -> IO DoubleSource
eval :: a -> Double -> Double -> Double -> Double -> IO DoubleSource
evalParOld :: a -> [Double] -> [Double] -> IO DoubleSource
evalPar :: a -> [Double] -> [Double] -> IO DoubleSource
getNumber :: a -> IO IntSource
getParNumber :: a -> String -> IO IntSource
isNormalized :: a -> IO IntSource
setNumber :: a -> Int -> IO ()Source
setParameter :: a -> String -> Double -> IO ()Source
setParameters :: a -> [Double] -> IO ()Source
setParName :: a -> Int -> String -> IO ()Source
setParNames :: a -> String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> IO ()Source
class IDeletable a => ITAtt3D a Source
class IDeletable a => ITAttAxis a whereSource
getNdivisions :: a -> IO IntSource
getAxisColor :: a -> IO IntSource
getLabelColor :: a -> IO IntSource
getLabelFont :: a -> IO IntSource
getLabelOffset :: a -> IO DoubleSource
getLabelSize :: a -> IO DoubleSource
getTitleOffset :: a -> IO DoubleSource
getTitleSize :: a -> IO DoubleSource
getTickLength :: a -> IO DoubleSource
getTitleFont :: a -> IO IntSource
setNdivisions :: a -> Int -> Int -> IO ()Source
setAxisColor :: a -> Int -> IO ()Source
setLabelColor :: a -> Int -> IO ()Source
setLabelFont :: a -> Int -> IO ()Source
setLabelOffset :: a -> Double -> IO ()Source
setLabelSize :: a -> Double -> IO ()Source
setTickLength :: a -> Double -> IO ()Source
setTitleOffset :: a -> Double -> IO ()Source
setTitleSize :: a -> Double -> IO ()Source
setTitleColor :: a -> Int -> IO ()Source
setTitleFont :: a -> Int -> IO ()Source
class IDeletable a => ITAttCanvas a Source
class IDeletable a => ITAttFill a whereSource
setFillColor :: a -> Int -> IO ()Source
setFillStyle :: a -> Int -> IO ()Source
class IDeletable a => ITAttImage a Source
class IDeletable a => ITAttLine a whereSource
setLineColor :: a -> Int -> IO ()Source
class IDeletable a => ITAttMarker a Source
class IDeletable a => ITAttPad a Source
class ITNamed a => ITAttParticle a Source
class IDeletable a => ITAttText a whereSource
setTextColor :: a -> Int -> IO ()Source
setTextAlign :: a -> Int -> IO ()Source
setTextSize :: a -> Double -> IO ()Source
class (ITFormula a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITF1 a whereSource
derivative :: a -> Double -> [Double] -> Double -> IO DoubleSource
derivative2 :: a -> Double -> [Double] -> Double -> IO DoubleSource
derivative3 :: a -> Double -> [Double] -> Double -> IO DoubleSource
drawCopyTF1 :: a -> String -> IO aSource
drawDerivative :: a -> String -> IO (Exist TObject)Source
drawIntegral :: a -> String -> IO (Exist TObject)Source
drawF1 :: a -> String -> Double -> Double -> String -> IO ()Source
fixParameter :: a -> Int -> Double -> IO ()Source
getMaximumTF1 :: a -> Double -> Double -> Double -> Double -> Int -> IO DoubleSource
getMinimumTF1 :: a -> Double -> Double -> Double -> Double -> Int -> IO DoubleSource
getMaximumX :: a -> Double -> Double -> Double -> Double -> Int -> IO DoubleSource
getMinimumX :: a -> Double -> Double -> Double -> Double -> Int -> IO DoubleSource
getNumberFreeParameters :: a -> IO IntSource
getNumberFitPoints :: a -> IO IntSource
getParError :: a -> Int -> IO DoubleSource
getProb :: a -> IO DoubleSource
getQuantilesTF1 :: a -> Int -> [Double] -> [Double] -> IO IntSource
getRandomTF1 :: a -> Double -> Double -> IO DoubleSource
getSave :: a -> [Double] -> IO DoubleSource
getX :: a -> Double -> Double -> Double -> Double -> Int -> IO DoubleSource
getXmin :: a -> IO DoubleSource
getXmax :: a -> IO DoubleSource
gradientPar :: a -> Int -> [Double] -> Double -> IO DoubleSource
initArgs :: a -> [Double] -> [Double] -> IO ()Source
integralTF1 :: a -> Double -> Double -> [Double] -> Double -> IO DoubleSource
integralError :: a -> Double -> Double -> [Double] -> [Double] -> Double -> IO DoubleSource
integralFast :: a -> Int -> [Double] -> [Double] -> Double -> Double -> [Double] -> Double -> IO DoubleSource
isInside :: a -> [Double] -> IO IntSource
releaseParameter :: a -> Int -> IO ()Source
setChisquare :: a -> Double -> IO ()Source
setMaximumTF1 :: a -> Double -> IO ()Source
setMinimumTF1 :: a -> Double -> IO ()Source
setNDF :: a -> Int -> IO ()Source
setNumberFitPoints :: a -> Int -> IO ()Source
setNpx :: a -> Int -> IO ()Source
setParError :: a -> Int -> Double -> IO ()Source
setParErrors :: a -> [Double] -> IO ()Source
setParLimits :: a -> Int -> Double -> Double -> IO ()Source
setParent :: (ITObject c0, FPtr c0) => a -> c0 -> IO ()Source
setRange1 :: a -> Double -> Double -> IO ()Source
setRange2 :: a -> Double -> Double -> Double -> Double -> IO ()Source
setRange3 :: a -> Double -> Double -> Double -> Double -> Double -> Double -> IO ()Source
setSavedPoint :: a -> Int -> Double -> IO ()Source
moment :: a -> Double -> Double -> Double -> [Double] -> Double -> IO DoubleSource
centralMoment :: a -> Double -> Double -> Double -> [Double] -> Double -> IO DoubleSource
mean :: a -> Double -> Double -> [Double] -> Double -> IO DoubleSource
variance :: a -> Double -> Double -> [Double] -> Double -> IO DoubleSource
class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITGraph a whereSource
apply :: (ITF1 c0, FPtr c0) => a -> c0 -> IO ()Source
chisquare :: (ITF1 c0, FPtr c0) => a -> c0 -> IO DoubleSource
drawGraph :: a -> Int -> [Double] -> [Double] -> String -> IO ()Source
drawPanelTGraph :: a -> IO ()Source
expand :: a -> Int -> Int -> IO ()Source
fitPanelTGraph :: a -> IO ()Source
getCorrelationFactorTGraph :: a -> IO DoubleSource
getCovarianceTGraph :: a -> IO DoubleSource
getMeanTGraph :: a -> Int -> IO DoubleSource
getRMSTGraph :: a -> Int -> IO DoubleSource
getErrorX :: a -> Int -> IO DoubleSource
getErrorY :: a -> Int -> IO DoubleSource
getErrorXhigh :: a -> Int -> IO DoubleSource
getErrorXlow :: a -> Int -> IO DoubleSource
getErrorYhigh :: a -> Int -> IO DoubleSource
getErrorYlow :: a -> Int -> IO DoubleSource
initExpo :: a -> Double -> Double -> IO ()Source
initGaus :: a -> Double -> Double -> IO ()Source
initPolynom :: a -> Double -> Double -> IO ()Source
insertPoint :: a -> IO IntSource
integralTGraph :: a -> Int -> Int -> IO DoubleSource
isEditable :: a -> IO IntSource
isInsideTGraph :: a -> Double -> Double -> IO IntSource
leastSquareFit :: a -> Int -> [Double] -> Double -> Double -> IO ()Source
paintStats :: (ITF1 c0, FPtr c0) => a -> c0 -> IO ()Source
removePoint :: a -> Int -> IO IntSource
setEditable :: a -> Int -> IO ()Source
setHistogram :: (ITH1F c0, FPtr c0) => a -> c0 -> IO ()Source
setMaximumTGraph :: a -> Double -> IO ()Source
setMinimumTGraph :: a -> Double -> IO ()Source
class ITGraph a => ITGraphAsymmErrors a Source
class ITGraph a => ITGraphBentErrors a Source
class ITGraph a => ITGraphErrors a Source
class ITGraphErrors a => ITGraphPolar a Source
class (ITObject a, ITAttLine a, ITAttFill a) => ITBox a Source
class ITBox a => ITPave a Source
class (ITPave a, ITAttText a) => ITPaveText a Source
class ITPaveText a => ITPaveStats a Source
class ITPaveText a => ITPavesText a Source
class (ITObject a, ITAttText a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITLegendEntry a Source
class (ITPave a, ITAttText a) => ITPaveLabel a Source
class ITPaveLabel a => ITPaveClass a Source
class ITWbox a => ITSliderBox a Source
class (ITObject a, ITAttLine a, ITAttFill a) => ITPolyLine a Source
class ITPolyLine a => ITCurlyLine a Source
class ITCurlyLine a => ITCurlyArc a Source
class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITEfficiency a Source
class (ITNamed a, ITAttAxis a) => ITAxis a whereSource
setTimeDisplay :: a -> Int -> IO ()Source
setTimeFormat :: a -> String -> IO ()Source
class ITNamed a => ITDirectory a whereSource
class ITDirectory a => ITDirectoryFile a whereSource
getListOfKeys :: a -> IO (Exist TList)Source
class ITObject a => ITVirtualTreePlayer a Source
class ITVirtualTreePlayer a => ITTreePlayer a Source
class IDeletable a => ITArray a Source
class ITArray a => ITArrayL64 a Source
class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITH1 a whereSource
the TH1 class : the mother class of all histogram classes
class TH1 : TNamed, TAttLine, TAttFill, TAttMarker
add :: (ITH1 c0, FPtr c0) => a -> c0 -> Double -> IO ()Source
void TH1::Add( TH1* h1, Double_t c1 )
addBinContent :: a -> Int -> Double -> IO ()Source
void TH1::AddBinContent( Int_t bin, Double_t w )
chi2Test :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> [Double] -> IO DoubleSource
Double_t TH1::Chi2Test( const TH1* h2, Option_t* option="UU", Double_t* res=0 ) const
computeIntegral :: a -> IO DoubleSource
Double_t TH1::ComputeIntegral ()
directoryAutoAdd :: (ITDirectory c0, FPtr c0) => a -> c0 -> IO ()Source
void TH1::DirectoryAutoAdd(TDirectory* )
divide :: (ITH2 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> Double -> Double -> String -> IO ()Source
void TH1::Divide(const TH1* h1, const TH1* h2, Double_t c1=1, Double_t c2=1, Option_t* option="")
drawCopyTH1 :: a -> String -> IO aSource
drawNormalized :: a -> String -> Double -> IO (Exist TH1)Source
TH1* TH1::DrawNormalized (Option_t* option="", Double_t norm=1) const
drawPanelTH1 :: a -> IO ()Source
bufferEmpty :: a -> Int -> IO IntSource
evalF :: (ITF1 c0, FPtr c0) => a -> c0 -> String -> IO ()Source
fFT :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> IO (Exist TH1)Source
fill1 :: a -> Double -> IO IntSource
fill1w :: a -> Double -> Double -> IO IntSource
fillN1 :: a -> Int -> [Double] -> [Double] -> Int -> IO ()Source
fillRandom :: (ITH1 c0, FPtr c0) => a -> c0 -> Int -> IO ()Source
findBin :: a -> Double -> Double -> Double -> IO IntSource
findFixBin :: a -> Double -> Double -> Double -> IO IntSource
findFirstBinAbove :: a -> Double -> Int -> IO IntSource
findLastBinAbove :: a -> Double -> Int -> IO IntSource
fitPanelTH1 :: a -> IO ()Source
getNdivisionA :: a -> String -> IO IntSource
getAxisColorA :: a -> String -> IO IntSource
getLabelColorA :: a -> String -> IO IntSource
getLabelFontA :: a -> String -> IO IntSource
getLabelOffsetA :: a -> String -> IO DoubleSource
getLabelSizeA :: a -> String -> IO DoubleSource
getTitleFontA :: a -> String -> IO IntSource
getTitleOffsetA :: a -> String -> IO DoubleSource
getTitleSizeA :: a -> String -> IO DoubleSource
getTickLengthA :: a -> String -> IO DoubleSource
getBarOffset :: a -> IO DoubleSource
getBarWidth :: a -> IO DoubleSource
getContour :: a -> [Double] -> IO IntSource
getContourLevel :: a -> Int -> IO DoubleSource
getContourLevelPad :: a -> Int -> IO DoubleSource
getBin :: a -> Int -> Int -> Int -> IO IntSource
getBinCenter :: a -> Int -> IO DoubleSource
getBinContent1 :: a -> Int -> IO DoubleSource
getBinContent2 :: a -> Int -> Int -> IO DoubleSource
getBinContent3 :: a -> Int -> Int -> Int -> IO DoubleSource
getBinError1 :: a -> Int -> IO DoubleSource
getBinError2 :: a -> Int -> Int -> IO DoubleSource
getBinError3 :: a -> Int -> Int -> Int -> IO DoubleSource
getBinLowEdge :: a -> Int -> IO DoubleSource
getBinWidth :: a -> Int -> IO DoubleSource
getCellContent :: a -> Int -> Int -> IO DoubleSource
getCellError :: a -> Int -> Int -> IO DoubleSource
getEntries :: a -> IO DoubleSource
getEffectiveEntries :: a -> IO DoubleSource
getFunction :: a -> String -> IO (Exist TF1)Source
getDimension :: a -> IO IntSource
getKurtosis :: a -> Int -> IO DoubleSource
getLowEdge :: a -> [Double] -> IO ()Source
getMaximumTH1 :: a -> Double -> IO DoubleSource
getMaximumBin :: a -> IO IntSource
getMaximumStored :: a -> IO DoubleSource
getMinimumTH1 :: a -> Double -> IO DoubleSource
getMinimumBin :: a -> IO IntSource
getMinimumStored :: a -> IO DoubleSource
getMean :: a -> Int -> IO DoubleSource
getMeanError :: a -> Int -> IO DoubleSource
getNbinsX :: a -> IO DoubleSource
getNbinsY :: a -> IO DoubleSource
getNbinsZ :: a -> IO DoubleSource
getQuantilesTH1 :: a -> Int -> [Double] -> [Double] -> IO IntSource
getRandom :: a -> IO DoubleSource
getStats :: a -> [Double] -> IO ()Source
void GetStats(Double_t *stats) const;
getSumOfWeights :: a -> IO DoubleSource
getSumw2 :: a -> IO (Exist TArrayD)Source
getSumw2N :: a -> IO IntSource
getRMS :: a -> Int -> IO DoubleSource
getRMSError :: a -> Int -> IO DoubleSource
getSkewness :: a -> Int -> IO DoubleSource
integral1 :: a -> Int -> Int -> String -> IO DoubleSource
interpolate1 :: a -> Double -> IO DoubleSource
Double_t Interpolate(Double_t x)
interpolate2 :: a -> Double -> Double -> IO DoubleSource
Double_t Interpolate(Double_t x, Double_t y)
interpolate3 :: a -> Double -> Double -> Double -> IO DoubleSource
Double_t Interpolate(Double_t x, Double_t y, Double_t z)
kolmogorovTest :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> IO DoubleSource
Double_t KolmogorovTest(const TH1 *h2, Option_t *option="") const
labelsDeflate :: a -> String -> IO ()Source
void LabelsDeflate(Option_t *axis="X")
labelsInflate :: a -> String -> IO ()Source
void LabelsInflate(Option_t *axis="X")
labelsOption :: a -> String -> String -> IO ()Source
void LabelsOption(Option_t *option="h", Option_t *axis="X")
multiflyF :: (ITF1 c0, FPtr c0) => a -> c0 -> Double -> IO ()Source
multiply :: (ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> Double -> Double -> String -> IO ()Source
void Multiply(const TH1 *h1, const TH1 *h2, Double_t c1=1, Double_t c2=1, Option_t *option=""); // *MENU*
putStats :: a -> [Double] -> IO ()Source
void PutStats(Double_t *stats)
rebin :: a -> Int -> String -> [Double] -> IO (Exist TH1)Source
TH1 *Rebin(Int_t ngroup=2, const char*newname="", const Double_t *xbins=0); // *MENU*
rebinAxis :: (ITAxis c0, FPtr c0) => a -> Double -> c0 -> IO ()Source
void RebinAxis(Double_t x, TAxis *axis)
rebuild :: a -> String -> IO ()Source
void Rebuild(Option_t *option="")
reset :: a -> String -> IO ()Source
void Reset(Option_t *option="")
resetStats :: a -> IO ()Source
void ResetStats()
scale :: a -> Double -> String -> IO ()Source
void Scale(Double_t c1=1, Option_t *option="")
setAxisColorA :: a -> Int -> String -> IO ()Source
void SetAxisColor(Color_t color=1, Option_t *axis="X")
setAxisRange :: a -> Double -> Double -> String -> IO ()Source
void SetAxisRange(Double_t xmin, Double_t xmax, Option_t *axis="X")
setBarOffset :: a -> Double -> IO ()Source
void SetBarOffset(Float_t offset=0.25)
setBarWidth :: a -> Double -> IO ()Source
void SetBarWidth(Float_t width=0.5)
setBinContent1 :: a -> Int -> Double -> IO ()Source
void SetBinContent(Int_t bin, Double_t content)
setBinContent2 :: a -> Int -> Int -> Double -> IO ()Source
void SetBinContent(Int_t binx, Int_t biny, Double_t content)
setBinContent3 :: a -> Int -> Int -> Int -> Double -> IO ()Source
void SetBinContent(Int_t binx, Int_t biny, Int_t binz, Double_t content)
setBinError1 :: a -> Int -> Double -> IO ()Source
setBinError2 :: a -> Int -> Int -> Double -> IO ()Source
setBinError3 :: a -> Int -> Int -> Int -> Double -> IO ()Source
setBins1 :: a -> Int -> [Double] -> IO ()Source
setBins2 :: a -> Int -> [Double] -> Int -> [Double] -> IO ()Source
setBins3 :: a -> Int -> [Double] -> Int -> [Double] -> Int -> [Double] -> IO ()Source
setBinsLength :: a -> Int -> IO ()Source
setBuffer :: a -> Int -> String -> IO ()Source
setCellContent :: a -> Int -> Int -> Double -> IO ()Source
setContent :: a -> [Double] -> IO ()Source
setContour :: a -> Int -> [Double] -> IO ()Source
setContourLevel :: a -> Int -> Double -> IO ()Source
setDirectory :: (ITDirectory c0, FPtr c0) => a -> c0 -> IO ()Source
setEntries :: a -> Double -> IO ()Source
setError :: a -> [Double] -> IO ()Source
setLabelColorA :: a -> Int -> String -> IO ()Source
setLabelSizeA :: a -> Double -> String -> IO ()Source
setLabelFontA :: a -> Int -> String -> IO ()Source
setLabelOffsetA :: a -> Double -> String -> IO ()Source
setMaximum :: a -> Double -> IO ()Source
setMinimum :: a -> Double -> IO ()Source
setNormFactor :: a -> Double -> IO ()Source
setStats :: a -> Int -> IO ()Source
setOption :: a -> String -> IO ()Source
setXTitle :: a -> String -> IO ()Source
setYTitle :: a -> String -> IO ()Source
setZTitle :: a -> String -> IO ()Source
showBackground :: a -> Int -> String -> IO (Exist TH1)Source
TH1 *ShowBackground(Int_t niter=20, Option_t *option="same");
showPeaks :: a -> Double -> String -> Double -> IO IntSource
Int_t ShowPeaks(Double_t sigma=2, Option_t *option="", Double_t threshold=0.05); // *MENU*
smooth :: a -> Int -> String -> IO ()Source
void Smooth(Int_t ntimes=1, Option_t *option=""); // *MENU*
ITH1 TH3S | |
ITH1 TH3I | |
ITH1 TH3F | |
ITH1 TH3D | |
ITH1 TH3C | |
ITH1 TH2S | |
ITH1 TH2Poly | |
ITH1 TH2I | |
ITH1 TH2F | |
ITH1 TH2D | |
ITH1 TH2C | |
ITH1 TH1S | |
ITH1 TH1I | |
ITH1 TH1F | |
ITH1 TH1D | |
ITH1 TH1C | |
ITH1 TH3 | |
ITH1 TH2 | |
ITH1 TH1 | |
ITH1 (Exist TH3S) | |
ITH1 (Exist TH3I) | |
ITH1 (Exist TH3F) | |
ITH1 (Exist TH3D) | |
ITH1 (Exist TH3C) | |
ITH1 (Exist TH2S) | |
ITH1 (Exist TH2Poly) | |
ITH1 (Exist TH2I) | |
ITH1 (Exist TH2F) | |
ITH1 (Exist TH2D) | |
ITH1 (Exist TH2C) | |
ITH1 (Exist TH1S) | |
ITH1 (Exist TH1I) | |
ITH1 (Exist TH1F) | |
ITH1 (Exist TH1D) | |
ITH1 (Exist TH1C) | |
ITH1 (Exist TH3) | |
ITH1 (Exist TH2) | |
ITH1 (Exist TH1) |
class ITH1 a => ITH2 a whereSource
fill2 :: a -> Double -> Double -> IO IntSource
Int_t Fill(Double_t x, Double_t y);
fill2w :: a -> Double -> Double -> Double -> IO IntSource
fillN2 :: a -> Int -> [Double] -> [Double] -> [Double] -> Int -> IO ()Source
fillRandom2 :: (ITH1 c0, FPtr c0) => a -> c0 -> Int -> IO ()Source
void FillRandom(TH1 *h, Int_t ntimes=5000);
findFirstBinAbove2 :: a -> Double -> Int -> IO IntSource
Int_t FindFirstBinAbove(Double_t threshold=0, Int_t axis=1) const;
findLastBinAbove2 :: a -> Double -> Int -> IO IntSource
Int_t FindLastBinAbove (Double_t threshold=0, Int_t axis=1) const;
fitSlicesX :: (ITObjArray c1, FPtr c1, ITF1 c0, FPtr c0) => a -> c0 -> Int -> Int -> Int -> String -> c1 -> IO ()Source
void FitSlicesX(TF1 *f1=0,Int_t firstybin=0, Int_t lastybin=-1, Int_t cut=0, Option_t *option="QNR", TObjArray* arr = 0); // *MENU*
fitSlicesY :: (ITObjArray c1, FPtr c1, ITF1 c0, FPtr c0) => a -> c0 -> Int -> Int -> Int -> String -> c1 -> IO ()Source
void FitSlicesY(TF1 *f1=0,Int_t firstxbin=0, Int_t lastxbin=-1, Int_t cut=0, Option_t *option="QNR", TObjArray* arr = 0); // *MENU*
getCorrelationFactor2 :: a -> Int -> Int -> IO DoubleSource
getCovariance2 :: a -> Int -> Int -> IO DoubleSource
integral2 :: a -> Int -> Int -> Int -> Int -> String -> IO DoubleSource
rebinX2 :: a -> Int -> String -> IO (Exist TH2)Source
rebinY2 :: a -> Int -> String -> IO (Exist TH2)Source
rebin2D :: a -> Int -> Int -> String -> IO (Exist TH2)Source
TH2 *Rebin2D(Int_t nxgroup=2, Int_t nygroup=2, const char *newname="");
setShowProjectionX :: a -> Int -> IO ()Source
void SetShowProjectionX(Int_t nbins); // *MENU*
setShowProjectionY :: a -> Int -> IO ()Source
void SetShowProjectionY(Int_t nbins); // *MENU*
class (ITH1 a, ITAtt3D a) => ITH3 a whereSource
fill3 :: a -> Double -> Double -> Double -> IO IntSource
fill3w :: a -> Double -> Double -> Double -> Double -> IO IntSource
fitSlicesZ :: (ITF1 c0, FPtr c0) => a -> c0 -> Int -> Int -> Int -> Int -> Int -> String -> IO ()Source
getCorrelationFactor3 :: a -> Int -> Int -> IO DoubleSource
getCovariance3 :: a -> Int -> Int -> IO DoubleSource
rebinX3 :: a -> Int -> String -> IO (Exist TH3)Source
rebinY3 :: a -> Int -> String -> IO (Exist TH3)Source
rebinZ3 :: a -> Int -> String -> IO (Exist TH3)Source
rebin3D :: a -> Int -> Int -> Int -> String -> IO (Exist TH3)Source
class IDeletable a => ITQObject a Source
class (ITObject a, ITAttLine a, ITAttFill a, ITAttPad a, ITQObject a) => ITVirtualPad a whereSource
getFrame :: a -> IO (Exist TFrame)Source
range :: a -> Double -> Double -> Double -> Double -> IO ()Source
class ITVirtualPad a => ITPad a Source
class ITButton a => ITGroupButton a Source
class (ITCanvas a, ITAttText a) => ITDialogCanvas a Source
class (ITCanvas a, ITAttText a) => ITInspectCanvas a Source
class (ITObject a, ITQObject a) => ITApplication a whereSource
class ITObject a => ITCollection a Source
class ITCollection a => ITSeqCollection a Source
class ITSeqCollection a => ITObjArray a Source
class IDeletable a => ITDatime a whereSource
class ITObject a => ITVirtualHistPainter a Source
upcastTObject :: (FPtr a, ITObject a) => a -> TObjectSource
upcastTNamed :: (FPtr a, ITNamed a) => a -> TNamedSource
upcastTClass :: (FPtr a, ITClass a) => a -> TClassSource
upcastTFormula :: (FPtr a, ITFormula a) => a -> TFormulaSource
upcastTAtt3D :: (FPtr a, ITAtt3D a) => a -> TAtt3DSource
upcastTAttAxis :: (FPtr a, ITAttAxis a) => a -> TAttAxisSource
upcastTAttBBox :: (FPtr a, ITAttBBox a) => a -> TAttBBoxSource
upcastTAttCanvas :: (FPtr a, ITAttCanvas a) => a -> TAttCanvasSource
upcastTAttFill :: (FPtr a, ITAttFill a) => a -> TAttFillSource
upcastTAttImage :: (FPtr a, ITAttImage a) => a -> TAttImageSource
upcastTAttLine :: (FPtr a, ITAttLine a) => a -> TAttLineSource
upcastTAttMarker :: (FPtr a, ITAttMarker a) => a -> TAttMarkerSource
upcastTAttPad :: (FPtr a, ITAttPad a) => a -> TAttPadSource
upcastTAttParticle :: (FPtr a, ITAttParticle a) => a -> TAttParticleSource
upcastTAttText :: (FPtr a, ITAttText a) => a -> TAttTextSource
upcastTHStack :: (FPtr a, ITHStack a) => a -> THStackSource
upcastTGraph :: (FPtr a, ITGraph a) => a -> TGraphSource
upcastTGraphAsymmErrors :: (FPtr a, ITGraphAsymmErrors a) => a -> TGraphAsymmErrorsSource
upcastTCutG :: (FPtr a, ITCutG a) => a -> TCutGSource
upcastTGraphBentErrors :: (FPtr a, ITGraphBentErrors a) => a -> TGraphBentErrorsSource
upcastTGraphErrors :: (FPtr a, ITGraphErrors a) => a -> TGraphErrorsSource
upcastTGraphPolar :: (FPtr a, ITGraphPolar a) => a -> TGraphPolarSource
upcastTGraphQQ :: (FPtr a, ITGraphQQ a) => a -> TGraphQQSource
upcastTEllipse :: (FPtr a, ITEllipse a) => a -> TEllipseSource
upcastTArc :: (FPtr a, ITArc a) => a -> TArcSource
upcastTCrown :: (FPtr a, ITCrown a) => a -> TCrownSource
upcastTLine :: (FPtr a, ITLine a) => a -> TLineSource
upcastTArrow :: (FPtr a, ITArrow a) => a -> TArrowSource
upcastTGaxis :: (FPtr a, ITGaxis a) => a -> TGaxisSource
upcastTShape :: (FPtr a, ITShape a) => a -> TShapeSource
upcastTBRIK :: (FPtr a, ITBRIK a) => a -> TBRIKSource
upcastTTUBE :: (FPtr a, ITTUBE a) => a -> TTUBESource
upcastTPCON :: (FPtr a, ITPCON a) => a -> TPCONSource
upcastTSPHE :: (FPtr a, ITSPHE a) => a -> TSPHESource
upcastTXTRU :: (FPtr a, ITXTRU a) => a -> TXTRUSource
upcastTBox :: (FPtr a, ITBox a) => a -> TBoxSource
upcastTPave :: (FPtr a, ITPave a) => a -> TPaveSource
upcastTPaveText :: (FPtr a, ITPaveText a) => a -> TPaveTextSource
upcastTDiamond :: (FPtr a, ITDiamond a) => a -> TDiamondSource
upcastTPaveStats :: (FPtr a, ITPaveStats a) => a -> TPaveStatsSource
upcastTPavesText :: (FPtr a, ITPavesText a) => a -> TPavesTextSource
upcastTLegend :: (FPtr a, ITLegend a) => a -> TLegendSource
upcastTLegendEntry :: (FPtr a, ITLegendEntry a) => a -> TLegendEntrySource
upcastTPaveLabel :: (FPtr a, ITPaveLabel a) => a -> TPaveLabelSource
upcastTPaveClass :: (FPtr a, ITPaveClass a) => a -> TPaveClassSource
upcastTWbox :: (FPtr a, ITWbox a) => a -> TWboxSource
upcastTFrame :: (FPtr a, ITFrame a) => a -> TFrameSource
upcastTSliderBox :: (FPtr a, ITSliderBox a) => a -> TSliderBoxSource
upcastTTree :: (FPtr a, ITTree a) => a -> TTreeSource
upcastTChain :: (FPtr a, ITChain a) => a -> TChainSource
upcastTNtuple :: (FPtr a, ITNtuple a) => a -> TNtupleSource
upcastTNtupleD :: (FPtr a, ITNtupleD a) => a -> TNtupleDSource
upcastTTreeSQL :: (FPtr a, ITTreeSQL a) => a -> TTreeSQLSource
upcastTPolyLine :: (FPtr a, ITPolyLine a) => a -> TPolyLineSource
upcastTCurlyLine :: (FPtr a, ITCurlyLine a) => a -> TCurlyLineSource
upcastTCurlyArc :: (FPtr a, ITCurlyArc a) => a -> TCurlyArcSource
upcastTEfficiency :: (FPtr a, ITEfficiency a) => a -> TEfficiencySource
upcastTAxis :: (FPtr a, ITAxis a) => a -> TAxisSource
upcastTLatex :: (FPtr a, ITLatex a) => a -> TLatexSource
upcastTText :: (FPtr a, ITText a) => a -> TTextSource
upcastTDirectory :: (FPtr a, ITDirectory a) => a -> TDirectorySource
upcastTDirectoryFile :: (FPtr a, ITDirectoryFile a) => a -> TDirectoryFileSource
upcastTFile :: (FPtr a, ITFile a) => a -> TFileSource
upcastTBranch :: (FPtr a, ITBranch a) => a -> TBranchSource
upcastTVirtualTreePlayer :: (FPtr a, ITVirtualTreePlayer a) => a -> TVirtualTreePlayerSource
upcastTTreePlayer :: (FPtr a, ITTreePlayer a) => a -> TTreePlayerSource
upcastTArray :: (FPtr a, ITArray a) => a -> TArraySource
upcastTArrayC :: (FPtr a, ITArrayC a) => a -> TArrayCSource
upcastTArrayD :: (FPtr a, ITArrayD a) => a -> TArrayDSource
upcastTArrayF :: (FPtr a, ITArrayF a) => a -> TArrayFSource
upcastTArrayI :: (FPtr a, ITArrayI a) => a -> TArrayISource
upcastTArrayL :: (FPtr a, ITArrayL a) => a -> TArrayLSource
upcastTArrayL64 :: (FPtr a, ITArrayL64 a) => a -> TArrayL64Source
upcastTArrayS :: (FPtr a, ITArrayS a) => a -> TArraySSource
upcastTH1C :: (FPtr a, ITH1C a) => a -> TH1CSource
upcastTH1D :: (FPtr a, ITH1D a) => a -> TH1DSource
upcastTH1F :: (FPtr a, ITH1F a) => a -> TH1FSource
upcastTH1I :: (FPtr a, ITH1I a) => a -> TH1ISource
upcastTH1S :: (FPtr a, ITH1S a) => a -> TH1SSource
upcastTH2C :: (FPtr a, ITH2C a) => a -> TH2CSource
upcastTH2D :: (FPtr a, ITH2D a) => a -> TH2DSource
upcastTH2F :: (FPtr a, ITH2F a) => a -> TH2FSource
upcastTH2I :: (FPtr a, ITH2I a) => a -> TH2ISource
upcastTH2Poly :: (FPtr a, ITH2Poly a) => a -> TH2PolySource
upcastTH2S :: (FPtr a, ITH2S a) => a -> TH2SSource
upcastTH3C :: (FPtr a, ITH3C a) => a -> TH3CSource
upcastTH3D :: (FPtr a, ITH3D a) => a -> TH3DSource
upcastTH3F :: (FPtr a, ITH3F a) => a -> TH3FSource
upcastTH3I :: (FPtr a, ITH3I a) => a -> TH3ISource
upcastTH3S :: (FPtr a, ITH3S a) => a -> TH3SSource
upcastTQObject :: (FPtr a, ITQObject a) => a -> TQObjectSource
upcastTVirtualPad :: (FPtr a, ITVirtualPad a) => a -> TVirtualPadSource
upcastTPad :: (FPtr a, ITPad a) => a -> TPadSource
upcastTButton :: (FPtr a, ITButton a) => a -> TButtonSource
upcastTGroupButton :: (FPtr a, ITGroupButton a) => a -> TGroupButtonSource
upcastTCanvas :: (FPtr a, ITCanvas a) => a -> TCanvasSource
upcastTDialogCanvas :: (FPtr a, ITDialogCanvas a) => a -> TDialogCanvasSource
upcastTInspectCanvas :: (FPtr a, ITInspectCanvas a) => a -> TInspectCanvasSource
upcastTEvePad :: (FPtr a, ITEvePad a) => a -> TEvePadSource
upcastTSlider :: (FPtr a, ITSlider a) => a -> TSliderSource
upcastTApplication :: (FPtr a, ITApplication a) => a -> TApplicationSource
upcastTRint :: (FPtr a, ITRint a) => a -> TRintSource
upcastTRandom :: (FPtr a, ITRandom a) => a -> TRandomSource
upcastTCollection :: (FPtr a, ITCollection a) => a -> TCollectionSource
upcastTSeqCollection :: (FPtr a, ITSeqCollection a) => a -> TSeqCollectionSource
upcastTObjArray :: (FPtr a, ITObjArray a) => a -> TObjArraySource
upcastTList :: (FPtr a, ITList a) => a -> TListSource
upcastTKey :: (FPtr a, ITKey a) => a -> TKeySource
upcastTDatime :: (FPtr a, ITDatime a) => a -> TDatimeSource