HROOT.Class.Interface
- 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
- 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 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)
- class IDeletable a where
- class IDeletable a => ITObject a where
- class ITObject a => ITNamed a where
- class ITNamed a => ITDictionary a
- class ITDictionary a => ITClass a
- class ITNamed a => ITFormula a where
- getParameter :: a -> Int -> IO Double
- setParameter :: a -> Int -> Double -> IO ()
- class IDeletable a => ITAtt3D a
- class IDeletable a => ITAttAxis a where
- setLabelColor :: a -> Int -> IO ()
- setLabelSize :: a -> Double -> IO ()
- setTickLength :: a -> Double -> IO ()
- setTitleOffset :: a -> Double -> IO ()
- setNdivisions :: a -> Int -> 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) => ITF1 a
- class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITGraph a
- 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
- 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
- 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
- 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 ()
- distancetoPrimitive :: a -> Int -> Int -> IO Int
- divide :: (ITH2 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> Double -> Double -> String -> IO ()
- drawCopy :: a -> String -> IO a
- drawNormalized :: a -> String -> Double -> IO (Exist TH1)
- drawPanel :: a -> IO ()
- bufferEmpty :: a -> Int -> IO Int
- eval :: (ITF1 c0, FPtr c0) => a -> c0 -> String -> IO ()
- executeEvent :: a -> Int -> Int -> Int -> IO ()
- fFT :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> IO (Exist TH1)
- fill1 :: a -> Double -> IO Int
- fillN :: 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
- fitPanel :: a -> IO ()
- getNdivisions :: a -> String -> IO Int
- getAxisColor :: a -> String -> IO Int
- getLabelColor :: a -> String -> IO Int
- getLabelFont :: a -> String -> IO Int
- getLabelOffset :: a -> String -> IO Double
- getLabelSize :: a -> String -> IO Double
- getTitleFont :: a -> String -> IO Int
- getTitleOffset :: a -> String -> IO Double
- getTitleSize :: a -> String -> IO Double
- getTickLength :: 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
- class ITH1 a => ITH2 a where
- fill2 :: a -> Double -> Double -> IO Int
- 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 ()
- getCorrelationFactor :: a -> Int -> Int -> IO Double
- getCovariance :: a -> Int -> Int -> IO Double
- getStats :: a -> [Double] -> IO ()
- integral :: a -> Int -> Int -> Int -> Int -> String -> IO Double
- interpolate :: a -> Double -> Double -> Double -> IO Double
- kolmogorovTest :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> IO Double
- rebinX :: a -> Int -> String -> IO (Exist TH2)
- rebinY :: a -> Int -> String -> IO (Exist TH2)
- rebin2D :: a -> Int -> Int -> String -> IO (Exist TH2)
- putStats :: a -> [Double] -> IO ()
- reset :: a -> String -> IO ()
- setShowProjectionX :: a -> Int -> IO ()
- setShowProjectionY :: a -> Int -> IO ()
- showBackground :: a -> Int -> String -> IO (Exist TH1)
- showPeaks :: a -> Double -> String -> Double -> IO Int
- smooth :: a -> Int -> String -> IO ()
- class (ITH1 a, ITAtt3D a) => ITH3 a
- 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
- 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
- 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
Documentation
class Castable a b whereSource
Instances
Instances
Instances
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
data RawTObject Source
Instances
| (ITObject a, FPtr a) => Castable a (Ptr RawTObject) | |
| Castable (Exist TObject) (Ptr RawTObject) |
Constructors
| TObject (ForeignPtr RawTObject) |
Constructors
| TNamed (ForeignPtr RawTNamed) |
Constructors
| TClass (ForeignPtr RawTClass) |
data RawTFormula Source
Instances
| (ITFormula a, FPtr a) => Castable a (Ptr RawTFormula) | |
| Castable (Exist TFormula) (Ptr RawTFormula) |
Constructors
| TFormula (ForeignPtr RawTFormula) |
Constructors
| TAtt3D (ForeignPtr RawTAtt3D) |
data RawTAttAxis Source
Instances
| (ITAttAxis a, FPtr a) => Castable a (Ptr RawTAttAxis) | |
| Castable (Exist TAttAxis) (Ptr RawTAttAxis) |
Constructors
| TAttAxis (ForeignPtr RawTAttAxis) |
data RawTAttBBox Source
Instances
| (ITAttBBox a, FPtr a) => Castable a (Ptr RawTAttBBox) | |
| Castable (Exist TAttBBox) (Ptr RawTAttBBox) |
Constructors
| TAttBBox (ForeignPtr RawTAttBBox) |
data RawTAttCanvas Source
Instances
| (ITAttCanvas a, FPtr a) => Castable a (Ptr RawTAttCanvas) | |
| Castable (Exist TAttCanvas) (Ptr RawTAttCanvas) |
newtype TAttCanvas Source
Constructors
| TAttCanvas (ForeignPtr RawTAttCanvas) |
data RawTAttFill Source
Instances
| (ITAttFill a, FPtr a) => Castable a (Ptr RawTAttFill) | |
| Castable (Exist TAttFill) (Ptr RawTAttFill) |
Constructors
| TAttFill (ForeignPtr RawTAttFill) |
data RawTAttImage Source
Instances
| (ITAttImage a, FPtr a) => Castable a (Ptr RawTAttImage) | |
| Castable (Exist TAttImage) (Ptr RawTAttImage) |
Constructors
| TAttImage (ForeignPtr RawTAttImage) |
data RawTAttLine Source
Instances
| (ITAttLine a, FPtr a) => Castable a (Ptr RawTAttLine) | |
| Castable (Exist TAttLine) (Ptr RawTAttLine) |
Constructors
| TAttLine (ForeignPtr RawTAttLine) |
data RawTAttMarker Source
Instances
| (ITAttMarker a, FPtr a) => Castable a (Ptr RawTAttMarker) | |
| Castable (Exist TAttMarker) (Ptr RawTAttMarker) |
newtype TAttMarker Source
Constructors
| TAttMarker (ForeignPtr RawTAttMarker) |
data RawTAttPad Source
Instances
| (ITAttPad a, FPtr a) => Castable a (Ptr RawTAttPad) | |
| Castable (Exist TAttPad) (Ptr RawTAttPad) |
Constructors
| TAttPad (ForeignPtr RawTAttPad) |
data RawTAttParticle Source
Instances
| (ITAttParticle a, FPtr a) => Castable a (Ptr RawTAttParticle) | |
| Castable (Exist TAttParticle) (Ptr RawTAttParticle) |
newtype TAttParticle Source
Constructors
| TAttParticle (ForeignPtr RawTAttParticle) |
data RawTAttText Source
Instances
| (ITAttText a, FPtr a) => Castable a (Ptr RawTAttText) | |
| Castable (Exist TAttText) (Ptr RawTAttText) |
Constructors
| TAttText (ForeignPtr RawTAttText) |
data RawTHStack Source
Instances
| (ITHStack a, FPtr a) => Castable a (Ptr RawTHStack) | |
| Castable (Exist THStack) (Ptr RawTHStack) |
Constructors
| THStack (ForeignPtr RawTHStack) |
Constructors
| TF1 (ForeignPtr RawTF1) |
Constructors
| TGraph (ForeignPtr RawTGraph) |
data RawTGraphAsymmErrors Source
Instances
| (ITGraphAsymmErrors a, FPtr a) => Castable a (Ptr RawTGraphAsymmErrors) | |
| Castable (Exist TGraphAsymmErrors) (Ptr RawTGraphAsymmErrors) |
newtype TGraphAsymmErrors Source
Constructors
| TGraphAsymmErrors (ForeignPtr RawTGraphAsymmErrors) |
Instances
Constructors
| TCutG (ForeignPtr RawTCutG) |
data RawTGraphBentErrors Source
Instances
| (ITGraphBentErrors a, FPtr a) => Castable a (Ptr RawTGraphBentErrors) | |
| Castable (Exist TGraphBentErrors) (Ptr RawTGraphBentErrors) |
newtype TGraphBentErrors Source
Constructors
| TGraphBentErrors (ForeignPtr RawTGraphBentErrors) |
Instances
data RawTGraphErrors Source
Instances
| (ITGraphErrors a, FPtr a) => Castable a (Ptr RawTGraphErrors) | |
| Castable (Exist TGraphErrors) (Ptr RawTGraphErrors) |
newtype TGraphErrors Source
Constructors
| TGraphErrors (ForeignPtr RawTGraphErrors) |
Instances
data RawTGraphPolar Source
Instances
| (ITGraphPolar a, FPtr a) => Castable a (Ptr RawTGraphPolar) | |
| Castable (Exist TGraphPolar) (Ptr RawTGraphPolar) |
newtype TGraphPolar Source
Constructors
| TGraphPolar (ForeignPtr RawTGraphPolar) |
Instances
data RawTGraphQQ Source
Instances
| (ITGraphQQ a, FPtr a) => Castable a (Ptr RawTGraphQQ) | |
| Castable (Exist TGraphQQ) (Ptr RawTGraphQQ) |
Constructors
| TGraphQQ (ForeignPtr RawTGraphQQ) |
Instances
data RawTEllipse Source
Instances
| (ITEllipse a, FPtr a) => Castable a (Ptr RawTEllipse) | |
| Castable (Exist TEllipse) (Ptr RawTEllipse) |
Constructors
| TEllipse (ForeignPtr RawTEllipse) |
Constructors
| TArc (ForeignPtr RawTArc) |
Constructors
| TCrown (ForeignPtr RawTCrown) |
Constructors
| TLine (ForeignPtr RawTLine) |
Constructors
| TArrow (ForeignPtr RawTArrow) |
Constructors
| TGaxis (ForeignPtr RawTGaxis) |
Constructors
| TShape (ForeignPtr RawTShape) |
Constructors
| TBRIK (ForeignPtr RawTBRIK) |
Constructors
| TTUBE (ForeignPtr RawTTUBE) |
Constructors
| TPCON (ForeignPtr RawTPCON) |
Constructors
| TSPHE (ForeignPtr RawTSPHE) |
Constructors
| TXTRU (ForeignPtr RawTXTRU) |
Constructors
| TBox (ForeignPtr RawTBox) |
Constructors
| TPave (ForeignPtr RawTPave) |
data RawTPaveText Source
Instances
| (ITPaveText a, FPtr a) => Castable a (Ptr RawTPaveText) | |
| Castable (Exist TPaveText) (Ptr RawTPaveText) |
Constructors
| TPaveText (ForeignPtr RawTPaveText) |
Instances
data RawTDiamond Source
Instances
| (ITDiamond a, FPtr a) => Castable a (Ptr RawTDiamond) | |
| Castable (Exist TDiamond) (Ptr RawTDiamond) |
Constructors
| TDiamond (ForeignPtr RawTDiamond) |
Instances
data RawTPaveStats Source
Instances
| (ITPaveStats a, FPtr a) => Castable a (Ptr RawTPaveStats) | |
| Castable (Exist TPaveStats) (Ptr RawTPaveStats) |
newtype TPaveStats Source
Constructors
| TPaveStats (ForeignPtr RawTPaveStats) |
Instances
data RawTPavesText Source
Instances
| (ITPavesText a, FPtr a) => Castable a (Ptr RawTPavesText) | |
| Castable (Exist TPavesText) (Ptr RawTPavesText) |
newtype TPavesText Source
Constructors
| TPavesText (ForeignPtr RawTPavesText) |
Instances
data RawTLegend Source
Instances
| (ITLegend a, FPtr a) => Castable a (Ptr RawTLegend) | |
| Castable (Exist TLegend) (Ptr RawTLegend) |
Constructors
| TLegend (ForeignPtr RawTLegend) |
data RawTPaveLabel Source
Instances
| (ITPaveLabel a, FPtr a) => Castable a (Ptr RawTPaveLabel) | |
| Castable (Exist TPaveLabel) (Ptr RawTPaveLabel) |
newtype TPaveLabel Source
Constructors
| TPaveLabel (ForeignPtr RawTPaveLabel) |
Instances
data RawTPaveClass Source
Instances
| (ITPaveClass a, FPtr a) => Castable a (Ptr RawTPaveClass) | |
| Castable (Exist TPaveClass) (Ptr RawTPaveClass) |
newtype TPaveClass Source
Constructors
| TPaveClass (ForeignPtr RawTPaveClass) |
Instances
Constructors
| TWbox (ForeignPtr RawTWbox) |
Constructors
| TFrame (ForeignPtr RawTFrame) |
data RawTSliderBox Source
Instances
| (ITSliderBox a, FPtr a) => Castable a (Ptr RawTSliderBox) | |
| Castable (Exist TSliderBox) (Ptr RawTSliderBox) |
newtype TSliderBox Source
Constructors
| TSliderBox (ForeignPtr RawTSliderBox) |
Instances
Constructors
| TTree (ForeignPtr RawTTree) |
Constructors
| TChain (ForeignPtr RawTChain) |
data RawTNtuple Source
Instances
| (ITNtuple a, FPtr a) => Castable a (Ptr RawTNtuple) | |
| Castable (Exist TNtuple) (Ptr RawTNtuple) |
Constructors
| TNtuple (ForeignPtr RawTNtuple) |
data RawTNtupleD Source
Instances
| (ITNtupleD a, FPtr a) => Castable a (Ptr RawTNtupleD) | |
| Castable (Exist TNtupleD) (Ptr RawTNtupleD) |
Constructors
| TNtupleD (ForeignPtr RawTNtupleD) |
Instances
data RawTTreeSQL Source
Instances
| (ITTreeSQL a, FPtr a) => Castable a (Ptr RawTTreeSQL) | |
| Castable (Exist TTreeSQL) (Ptr RawTTreeSQL) |
Constructors
| TTreeSQL (ForeignPtr RawTTreeSQL) |
Instances
data RawTPolyLine Source
Instances
| (ITPolyLine a, FPtr a) => Castable a (Ptr RawTPolyLine) | |
| Castable (Exist TPolyLine) (Ptr RawTPolyLine) |
Constructors
| TPolyLine (ForeignPtr RawTPolyLine) |
data RawTCurlyLine Source
Instances
| (ITCurlyLine a, FPtr a) => Castable a (Ptr RawTCurlyLine) | |
| Castable (Exist TCurlyLine) (Ptr RawTCurlyLine) |
newtype TCurlyLine Source
Constructors
| TCurlyLine (ForeignPtr RawTCurlyLine) |
Instances
data RawTCurlyArc Source
Instances
| (ITCurlyArc a, FPtr a) => Castable a (Ptr RawTCurlyArc) | |
| Castable (Exist TCurlyArc) (Ptr RawTCurlyArc) |
Constructors
| TCurlyArc (ForeignPtr RawTCurlyArc) |
Instances
data RawTEfficiency Source
Instances
| (ITEfficiency a, FPtr a) => Castable a (Ptr RawTEfficiency) | |
| Castable (Exist TEfficiency) (Ptr RawTEfficiency) |
newtype TEfficiency Source
Constructors
| TEfficiency (ForeignPtr RawTEfficiency) |
Instances
Constructors
| TAxis (ForeignPtr RawTAxis) |
Constructors
| TLatex (ForeignPtr RawTLatex) |
Constructors
| TText (ForeignPtr RawTText) |
data RawTDirectory Source
Instances
| (ITDirectory a, FPtr a) => Castable a (Ptr RawTDirectory) | |
| Castable (Exist TDirectory) (Ptr RawTDirectory) |
newtype TDirectory Source
Constructors
| TDirectory (ForeignPtr RawTDirectory) |
data RawTDirectoryFile Source
Instances
| (ITDirectoryFile a, FPtr a) => Castable a (Ptr RawTDirectoryFile) | |
| Castable (Exist TDirectoryFile) (Ptr RawTDirectoryFile) |
newtype TDirectoryFile Source
Constructors
| TDirectoryFile (ForeignPtr RawTDirectoryFile) |
Instances
Constructors
| TFile (ForeignPtr RawTFile) |
data RawTBranch Source
Instances
| (ITBranch a, FPtr a) => Castable a (Ptr RawTBranch) | |
| Castable (Exist TBranch) (Ptr RawTBranch) |
Constructors
| TBranch (ForeignPtr RawTBranch) |
data RawTVirtualTreePlayer Source
Instances
newtype TVirtualTreePlayer Source
Constructors
| TVirtualTreePlayer (ForeignPtr RawTVirtualTreePlayer) |
Instances
data RawTTreePlayer Source
Instances
| (ITTreePlayer a, FPtr a) => Castable a (Ptr RawTTreePlayer) | |
| Castable (Exist TTreePlayer) (Ptr RawTTreePlayer) |
newtype TTreePlayer Source
Constructors
| TTreePlayer (ForeignPtr RawTTreePlayer) |
Constructors
| TArray (ForeignPtr RawTArray) |
data RawTArrayC Source
Instances
| (ITArrayC a, FPtr a) => Castable a (Ptr RawTArrayC) | |
| Castable (Exist TArrayC) (Ptr RawTArrayC) |
Constructors
| TArrayC (ForeignPtr RawTArrayC) |
data RawTArrayD Source
Instances
| (ITArrayD a, FPtr a) => Castable a (Ptr RawTArrayD) | |
| Castable (Exist TArrayD) (Ptr RawTArrayD) |
Constructors
| TArrayD (ForeignPtr RawTArrayD) |
data RawTArrayF Source
Instances
| (ITArrayF a, FPtr a) => Castable a (Ptr RawTArrayF) | |
| Castable (Exist TArrayF) (Ptr RawTArrayF) |
Constructors
| TArrayF (ForeignPtr RawTArrayF) |
data RawTArrayI Source
Instances
| (ITArrayI a, FPtr a) => Castable a (Ptr RawTArrayI) | |
| Castable (Exist TArrayI) (Ptr RawTArrayI) |
Constructors
| TArrayI (ForeignPtr RawTArrayI) |
data RawTArrayL Source
Instances
| (ITArrayL a, FPtr a) => Castable a (Ptr RawTArrayL) | |
| Castable (Exist TArrayL) (Ptr RawTArrayL) |
Constructors
| TArrayL (ForeignPtr RawTArrayL) |
data RawTArrayL64 Source
Instances
| (ITArrayL64 a, FPtr a) => Castable a (Ptr RawTArrayL64) | |
| Castable (Exist TArrayL64) (Ptr RawTArrayL64) |
Constructors
| TArrayL64 (ForeignPtr RawTArrayL64) |
data RawTArrayS Source
Instances
| (ITArrayS a, FPtr a) => Castable a (Ptr RawTArrayS) | |
| Castable (Exist TArrayS) (Ptr RawTArrayS) |
Constructors
| TArrayS (ForeignPtr RawTArrayS) |
Constructors
| TH1 (ForeignPtr RawTH1) |
Constructors
| TH2 (ForeignPtr RawTH2) |
Constructors
| TH3 (ForeignPtr RawTH3) |
Constructors
| TH1C (ForeignPtr RawTH1C) |
Constructors
| TH1D (ForeignPtr RawTH1D) |
Constructors
| TH1F (ForeignPtr RawTH1F) |
Constructors
| TH1I (ForeignPtr RawTH1I) |
Constructors
| TH1S (ForeignPtr RawTH1S) |
Constructors
| TH2C (ForeignPtr RawTH2C) |
Constructors
| TH2D (ForeignPtr RawTH2D) |
Constructors
| TH2F (ForeignPtr RawTH2F) |
Constructors
| TH2I (ForeignPtr RawTH2I) |
data RawTH2Poly Source
Instances
| (ITH2Poly a, FPtr a) => Castable a (Ptr RawTH2Poly) | |
| Castable (Exist TH2Poly) (Ptr RawTH2Poly) |
Constructors
| TH2Poly (ForeignPtr RawTH2Poly) |
Instances
Constructors
| TH2S (ForeignPtr RawTH2S) |
Constructors
| TH3C (ForeignPtr RawTH3C) |
Constructors
| TH3D (ForeignPtr RawTH3D) |
Constructors
| TH3F (ForeignPtr RawTH3F) |
Constructors
| TH3I (ForeignPtr RawTH3I) |
Constructors
| TH3S (ForeignPtr RawTH3S) |
data RawTQObject Source
Instances
| (ITQObject a, FPtr a) => Castable a (Ptr RawTQObject) | |
| Castable (Exist TQObject) (Ptr RawTQObject) |
Constructors
| TQObject (ForeignPtr RawTQObject) |
data RawTVirtualPad Source
Instances
| (ITVirtualPad a, FPtr a) => Castable a (Ptr RawTVirtualPad) | |
| Castable (Exist TVirtualPad) (Ptr RawTVirtualPad) |
newtype TVirtualPad Source
Constructors
| TVirtualPad (ForeignPtr RawTVirtualPad) |
Instances
Constructors
| TPad (ForeignPtr RawTPad) |
data RawTButton Source
Instances
| (ITButton a, FPtr a) => Castable a (Ptr RawTButton) | |
| Castable (Exist TButton) (Ptr RawTButton) |
Constructors
| TButton (ForeignPtr RawTButton) |
Instances
data RawTGroupButton Source
Instances
| (ITGroupButton a, FPtr a) => Castable a (Ptr RawTGroupButton) | |
| Castable (Exist TGroupButton) (Ptr RawTGroupButton) |
newtype TGroupButton Source
Constructors
| TGroupButton (ForeignPtr RawTGroupButton) |
Instances
data RawTCanvas Source
Instances
| (ITCanvas a, FPtr a) => Castable a (Ptr RawTCanvas) | |
| Castable (Exist TCanvas) (Ptr RawTCanvas) |
Constructors
| TCanvas (ForeignPtr RawTCanvas) |
Instances
data RawTDialogCanvas Source
Instances
| (ITDialogCanvas a, FPtr a) => Castable a (Ptr RawTDialogCanvas) | |
| Castable (Exist TDialogCanvas) (Ptr RawTDialogCanvas) |
newtype TDialogCanvas Source
Constructors
| TDialogCanvas (ForeignPtr RawTDialogCanvas) |
Instances
data RawTInspectCanvas Source
Instances
| (ITInspectCanvas a, FPtr a) => Castable a (Ptr RawTInspectCanvas) | |
| Castable (Exist TInspectCanvas) (Ptr RawTInspectCanvas) |
newtype TInspectCanvas Source
Constructors
| TInspectCanvas (ForeignPtr RawTInspectCanvas) |
Instances
data RawTEvePad Source
Instances
| (ITEvePad a, FPtr a) => Castable a (Ptr RawTEvePad) | |
| Castable (Exist TEvePad) (Ptr RawTEvePad) |
Constructors
| TEvePad (ForeignPtr RawTEvePad) |
Instances
data RawTSlider Source
Instances
| (ITSlider a, FPtr a) => Castable a (Ptr RawTSlider) | |
| Castable (Exist TSlider) (Ptr RawTSlider) |
Constructors
| TSlider (ForeignPtr RawTSlider) |
Instances
data RawTApplication Source
Instances
| (ITApplication a, FPtr a) => Castable a (Ptr RawTApplication) | |
| Castable (Exist TApplication) (Ptr RawTApplication) |
Constructors
| TRint (ForeignPtr RawTRint) |
data RawTRandom Source
Instances
| (ITRandom a, FPtr a) => Castable a (Ptr RawTRandom) | |
| Castable (Exist TRandom) (Ptr RawTRandom) |
Constructors
| TRandom (ForeignPtr RawTRandom) |
data RawTCollection Source
Instances
| (ITCollection a, FPtr a) => Castable a (Ptr RawTCollection) | |
| Castable (Exist TCollection) (Ptr RawTCollection) |
newtype TCollection Source
Constructors
| TCollection (ForeignPtr RawTCollection) |
data RawTSeqCollection Source
Instances
| (ITSeqCollection a, FPtr a) => Castable a (Ptr RawTSeqCollection) | |
| Castable (Exist TSeqCollection) (Ptr RawTSeqCollection) |
newtype TSeqCollection Source
Constructors
| TSeqCollection (ForeignPtr RawTSeqCollection) |
Instances
data RawTObjArray Source
Instances
| (ITObjArray a, FPtr a) => Castable a (Ptr RawTObjArray) | |
| Castable (Exist TObjArray) (Ptr RawTObjArray) |
Constructors
| TObjArray (ForeignPtr RawTObjArray) |
class IDeletable a whereSource
Instances
class IDeletable a => ITObject a whereSource
Methods
getName :: a -> IO StringSource
char* TObject::GetName()
draw :: a -> String -> IO ()Source
void TObject::Draw( char* option )
findObject :: a -> String -> IO (Exist TObject)Source
TObject* TObject::FindObject( char* name )
saveAs :: a -> String -> String -> IO ()Source
Instances
class ITObject a => ITNamed a whereSource
Class TNamed reference : http:root.cern.ch
Instances
class ITNamed a => ITDictionary a Source
Instances
class ITDictionary a => ITClass a Source
class IDeletable a => ITAtt3D a Source
class IDeletable a => ITAttAxis a whereSource
Methods
setLabelColor :: a -> Int -> IO ()Source
setLabelSize :: a -> Double -> IO ()Source
setTickLength :: a -> Double -> IO ()Source
setTitleOffset :: a -> Double -> IO ()Source
class IDeletable a => ITAttBBox a Source
class IDeletable a => ITAttCanvas a Source
Instances
class IDeletable a => ITAttFill a whereSource
Instances
class IDeletable a => ITAttImage a Source
Instances
class IDeletable a => ITAttLine a whereSource
Methods
setLineColor :: a -> Int -> IO ()Source
Instances
class IDeletable a => ITAttMarker a Source
Instances
class IDeletable a => ITAttPad a Source
class ITNamed a => ITAttParticle a Source
Instances
class IDeletable a => ITAttText a whereSource
Methods
setTextColor :: a -> Int -> IO ()Source
setTextAlign :: a -> Int -> IO ()Source
setTextSize :: a -> Double -> IO ()Source
Instances
class ITGraph a => ITGraphAsymmErrors a Source
Instances
class ITGraph a => ITGraphBentErrors a Source
Instances
class ITGraph a => ITGraphErrors a Source
class ITGraphErrors a => ITGraphPolar a Source
Instances
class (ITPave a, ITAttText a) => ITPaveText a Source
class ITPaveText a => ITDiamond a Source
class ITPaveText a => ITPaveStats a Source
Instances
class ITPaveText a => ITPavesText a Source
Instances
class (ITPave a, ITAttText a) => ITPaveLabel a Source
Instances
class ITPaveLabel a => ITPaveClass a Source
Instances
class ITWbox a => ITSliderBox a Source
Instances
class (ITObject a, ITAttLine a, ITAttFill a) => ITPolyLine a Source
class ITPolyLine a => ITCurlyLine a Source
Instances
class ITCurlyLine a => ITCurlyArc a Source
Instances
class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITEfficiency a Source
Instances
class ITNamed a => ITDirectory a whereSource
class ITDirectory a => ITDirectoryFile a Source
class ITDirectoryFile a => ITFile a Source
class ITObject a => ITVirtualTreePlayer a Source
class ITVirtualTreePlayer a => ITTreePlayer a Source
Instances
class IDeletable a => ITArray a Source
Instances
class ITArray a => ITArrayL64 a Source
Instances
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
Methods
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* )
distancetoPrimitive :: a -> Int -> Int -> IO IntSource
Int_t TH1::DistancetoPrimitive(Int_t px, Int_t py)
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="")
drawCopy :: a -> String -> IO aSource
TH1* TH1::DrawCopy (Option_t* option="") const
drawNormalized :: a -> String -> Double -> IO (Exist TH1)Source
TH1* TH1::DrawNormalized (Option_t* option="", Double_t norm=1) const
void TH1::DrawPanel()
bufferEmpty :: a -> Int -> IO IntSource
eval :: (ITF1 c0, FPtr c0) => a -> c0 -> String -> IO ()Source
executeEvent :: a -> Int -> Int -> Int -> IO ()Source
fFT :: (ITH1 c0, FPtr c0) => a -> c0 -> String -> IO (Exist TH1)Source
fill1 :: a -> Double -> IO IntSource
fillN :: 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
getNdivisions :: a -> String -> IO IntSource
getAxisColor :: a -> String -> IO IntSource
getLabelColor :: a -> String -> IO IntSource
getLabelFont :: a -> String -> IO IntSource
getLabelOffset :: a -> String -> IO DoubleSource
getLabelSize :: a -> String -> IO DoubleSource
getTitleFont :: a -> String -> IO IntSource
getTitleOffset :: a -> String -> IO DoubleSource
getTitleSize :: a -> String -> IO DoubleSource
getTickLength :: 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
class ITH1 a => ITH2 a whereSource
Methods
fill2 :: a -> Double -> Double -> IO IntSource
Int_t Fill(Double_t x, Double_t y);
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*
getCorrelationFactor :: a -> Int -> Int -> IO DoubleSource
Double_t GetCorrelationFactor(Int_t axis1=1,Int_t axis2=2) const;
getCovariance :: a -> Int -> Int -> IO DoubleSource
Double_t GetCovariance(Int_t axis1=1,Int_t axis2=2) const;
getStats :: a -> [Double] -> IO ()Source
void GetStats(Double_t *stats) const;
integral :: a -> Int -> Int -> Int -> Int -> String -> IO DoubleSource
Double_t Integral(Int_t binx1, Int_t binx2, Int_t biny1, Int_t biny2, Option_t *option="") const;
interpolate :: 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;
rebinX :: a -> Int -> String -> IO (Exist TH2)Source
TH2 *RebinX(Int_t ngroup=2, const char *newname="");
rebinY :: a -> Int -> String -> IO (Exist TH2)Source
TH2 *RebinY(Int_t ngroup=2, const char *newname="");
rebin2D :: a -> Int -> Int -> String -> IO (Exist TH2)Source
TH2 *Rebin2D(Int_t nxgroup=2, Int_t nygroup=2, const char *newname="");
putStats :: a -> [Double] -> IO ()Source
void PutStats(Double_t *stats);
reset :: a -> String -> IO ()Source
void Reset(Option_t *option="");
setShowProjectionX :: a -> Int -> IO ()Source
void SetShowProjectionX(Int_t nbins); // *MENU*
setShowProjectionY :: a -> Int -> IO ()Source
void SetShowProjectionY(Int_t nbins); // *MENU*
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*
class IDeletable a => ITQObject a Source
class (ITObject a, ITAttLine a, ITAttFill a, ITAttPad a, ITQObject a) => ITVirtualPad a whereSource
class ITVirtualPad a => ITPad a Source
class ITButton a => ITGroupButton a Source
Instances
class (ITCanvas a, ITAttText a) => ITDialogCanvas a Source
Instances
class (ITCanvas a, ITAttText a) => ITInspectCanvas a Source
Instances
class (ITObject a, ITQObject a) => ITApplication a whereSource
Instances
class ITApplication a => ITRint a Source
class ITObject a => ITCollection a Source
class ITCollection a => ITSeqCollection a Source
class ITSeqCollection a => ITObjArray a Source
Instances
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
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