HROOT-hist-0.10.0.3: Haskell binding to ROOT Hist modules
Safe HaskellSafe-Inferred
LanguageHaskell2010

HROOT.Hist.TGraph.Interface

Documentation

class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITGraph a where Source #

Methods

apply :: (ITF1 c0, FPtr c0) => a -> c0 -> IO () Source #

chisquare :: (ITF1 c0, FPtr c0) => a -> c0 -> IO CDouble Source #

drawGraph :: Castable c0 CString => a -> CInt -> Ptr CDouble -> Ptr CDouble -> c0 -> IO () Source #

drawPanelTGraph :: a -> IO () Source #

expand :: a -> CInt -> CInt -> IO () Source #

fitPanelTGraph :: a -> IO () Source #

getCorrelationFactorTGraph :: a -> IO CDouble Source #

getCovarianceTGraph :: a -> IO CDouble Source #

getMeanTGraph :: a -> CInt -> IO CDouble Source #

getRMSTGraph :: a -> CInt -> IO CDouble Source #

getErrorX :: a -> CInt -> IO CDouble Source #

getErrorY :: a -> CInt -> IO CDouble Source #

getErrorXhigh :: a -> CInt -> IO CDouble Source #

getErrorXlow :: a -> CInt -> IO CDouble Source #

getErrorYhigh :: a -> CInt -> IO CDouble Source #

getErrorYlow :: a -> CInt -> IO CDouble Source #

initExpo :: a -> CDouble -> CDouble -> IO () Source #

initGaus :: a -> CDouble -> CDouble -> IO () Source #

initPolynom :: a -> CDouble -> CDouble -> IO () Source #

insertPoint :: a -> IO CInt Source #

integralTGraph :: a -> CInt -> CInt -> IO CDouble Source #

isEditable :: a -> IO CBool Source #

isInsideTGraph :: a -> CDouble -> CDouble -> IO CInt Source #

leastSquareFit :: a -> CInt -> Ptr CDouble -> CDouble -> CDouble -> IO () Source #

paintStats :: (ITF1 c0, FPtr c0) => a -> c0 -> IO () Source #

removePoint :: a -> CInt -> IO CInt Source #

setEditable :: a -> CBool -> IO () Source #

setHistogram :: (ITH1F c0, FPtr c0) => a -> c0 -> IO () Source #

setMaximumTGraph :: a -> CDouble -> IO () Source #

setMinimumTGraph :: a -> CDouble -> IO () Source #

set :: a -> CInt -> IO () Source #

setPoint :: a -> CInt -> CDouble -> CDouble -> IO () Source #

Instances

Instances details
ITGraph TGraph Source # 
Instance details

Defined in HROOT.Hist.TGraph.Implementation

Methods

apply :: (ITF1 c0, FPtr c0) => TGraph -> c0 -> IO () Source #

chisquare :: (ITF1 c0, FPtr c0) => TGraph -> c0 -> IO CDouble Source #

drawGraph :: Castable c0 CString => TGraph -> CInt -> Ptr CDouble -> Ptr CDouble -> c0 -> IO () Source #

drawPanelTGraph :: TGraph -> IO () Source #

expand :: TGraph -> CInt -> CInt -> IO () Source #

fitPanelTGraph :: TGraph -> IO () Source #

getCorrelationFactorTGraph :: TGraph -> IO CDouble Source #

getCovarianceTGraph :: TGraph -> IO CDouble Source #

getMeanTGraph :: TGraph -> CInt -> IO CDouble Source #

getRMSTGraph :: TGraph -> CInt -> IO CDouble Source #

getErrorX :: TGraph -> CInt -> IO CDouble Source #

getErrorY :: TGraph -> CInt -> IO CDouble Source #

getErrorXhigh :: TGraph -> CInt -> IO CDouble Source #

getErrorXlow :: TGraph -> CInt -> IO CDouble Source #

getErrorYhigh :: TGraph -> CInt -> IO CDouble Source #

getErrorYlow :: TGraph -> CInt -> IO CDouble Source #

initExpo :: TGraph -> CDouble -> CDouble -> IO () Source #

initGaus :: TGraph -> CDouble -> CDouble -> IO () Source #

initPolynom :: TGraph -> CDouble -> CDouble -> IO () Source #

insertPoint :: TGraph -> IO CInt Source #

integralTGraph :: TGraph -> CInt -> CInt -> IO CDouble Source #

isEditable :: TGraph -> IO CBool Source #

isInsideTGraph :: TGraph -> CDouble -> CDouble -> IO CInt Source #

leastSquareFit :: TGraph -> CInt -> Ptr CDouble -> CDouble -> CDouble -> IO () Source #

paintStats :: (ITF1 c0, FPtr c0) => TGraph -> c0 -> IO () Source #

removePoint :: TGraph -> CInt -> IO CInt Source #

setEditable :: TGraph -> CBool -> IO () Source #

setHistogram :: (ITH1F c0, FPtr c0) => TGraph -> c0 -> IO () Source #

setMaximumTGraph :: TGraph -> CDouble -> IO () Source #

setMinimumTGraph :: TGraph -> CDouble -> IO () Source #

set :: TGraph -> CInt -> IO () Source #

setPoint :: TGraph -> CInt -> CDouble -> CDouble -> IO () Source #

ITGraph TGraphAsymmErrors Source # 
Instance details

Defined in HROOT.Hist.TGraphAsymmErrors.Implementation

Methods

apply :: (ITF1 c0, FPtr c0) => TGraphAsymmErrors -> c0 -> IO () Source #

chisquare :: (ITF1 c0, FPtr c0) => TGraphAsymmErrors -> c0 -> IO CDouble Source #

drawGraph :: Castable c0 CString => TGraphAsymmErrors -> CInt -> Ptr CDouble -> Ptr CDouble -> c0 -> IO () Source #

drawPanelTGraph :: TGraphAsymmErrors -> IO () Source #

expand :: TGraphAsymmErrors -> CInt -> CInt -> IO () Source #

fitPanelTGraph :: TGraphAsymmErrors -> IO () Source #

getCorrelationFactorTGraph :: TGraphAsymmErrors -> IO CDouble Source #

getCovarianceTGraph :: TGraphAsymmErrors -> IO CDouble Source #

getMeanTGraph :: TGraphAsymmErrors -> CInt -> IO CDouble Source #

getRMSTGraph :: TGraphAsymmErrors -> CInt -> IO CDouble Source #

getErrorX :: TGraphAsymmErrors -> CInt -> IO CDouble Source #

getErrorY :: TGraphAsymmErrors -> CInt -> IO CDouble Source #

getErrorXhigh :: TGraphAsymmErrors -> CInt -> IO CDouble Source #

getErrorXlow :: TGraphAsymmErrors -> CInt -> IO CDouble Source #

getErrorYhigh :: TGraphAsymmErrors -> CInt -> IO CDouble Source #

getErrorYlow :: TGraphAsymmErrors -> CInt -> IO CDouble Source #

initExpo :: TGraphAsymmErrors -> CDouble -> CDouble -> IO () Source #

initGaus :: TGraphAsymmErrors -> CDouble -> CDouble -> IO () Source #

initPolynom :: TGraphAsymmErrors -> CDouble -> CDouble -> IO () Source #

insertPoint :: TGraphAsymmErrors -> IO CInt Source #

integralTGraph :: TGraphAsymmErrors -> CInt -> CInt -> IO CDouble Source #

isEditable :: TGraphAsymmErrors -> IO CBool Source #

isInsideTGraph :: TGraphAsymmErrors -> CDouble -> CDouble -> IO CInt Source #

leastSquareFit :: TGraphAsymmErrors -> CInt -> Ptr CDouble -> CDouble -> CDouble -> IO () Source #

paintStats :: (ITF1 c0, FPtr c0) => TGraphAsymmErrors -> c0 -> IO () Source #

removePoint :: TGraphAsymmErrors -> CInt -> IO CInt Source #

setEditable :: TGraphAsymmErrors -> CBool -> IO () Source #

setHistogram :: (ITH1F c0, FPtr c0) => TGraphAsymmErrors -> c0 -> IO () Source #

setMaximumTGraph :: TGraphAsymmErrors -> CDouble -> IO () Source #

setMinimumTGraph :: TGraphAsymmErrors -> CDouble -> IO () Source #

set :: TGraphAsymmErrors -> CInt -> IO () Source #

setPoint :: TGraphAsymmErrors -> CInt -> CDouble -> CDouble -> IO () Source #

ITGraph TGraphBentErrors Source # 
Instance details

Defined in HROOT.Hist.TGraphBentErrors.Implementation

Methods

apply :: (ITF1 c0, FPtr c0) => TGraphBentErrors -> c0 -> IO () Source #

chisquare :: (ITF1 c0, FPtr c0) => TGraphBentErrors -> c0 -> IO CDouble Source #

drawGraph :: Castable c0 CString => TGraphBentErrors -> CInt -> Ptr CDouble -> Ptr CDouble -> c0 -> IO () Source #

drawPanelTGraph :: TGraphBentErrors -> IO () Source #

expand :: TGraphBentErrors -> CInt -> CInt -> IO () Source #

fitPanelTGraph :: TGraphBentErrors -> IO () Source #

getCorrelationFactorTGraph :: TGraphBentErrors -> IO CDouble Source #

getCovarianceTGraph :: TGraphBentErrors -> IO CDouble Source #

getMeanTGraph :: TGraphBentErrors -> CInt -> IO CDouble Source #

getRMSTGraph :: TGraphBentErrors -> CInt -> IO CDouble Source #

getErrorX :: TGraphBentErrors -> CInt -> IO CDouble Source #

getErrorY :: TGraphBentErrors -> CInt -> IO CDouble Source #

getErrorXhigh :: TGraphBentErrors -> CInt -> IO CDouble Source #

getErrorXlow :: TGraphBentErrors -> CInt -> IO CDouble Source #

getErrorYhigh :: TGraphBentErrors -> CInt -> IO CDouble Source #

getErrorYlow :: TGraphBentErrors -> CInt -> IO CDouble Source #

initExpo :: TGraphBentErrors -> CDouble -> CDouble -> IO () Source #

initGaus :: TGraphBentErrors -> CDouble -> CDouble -> IO () Source #

initPolynom :: TGraphBentErrors -> CDouble -> CDouble -> IO () Source #

insertPoint :: TGraphBentErrors -> IO CInt Source #

integralTGraph :: TGraphBentErrors -> CInt -> CInt -> IO CDouble Source #

isEditable :: TGraphBentErrors -> IO CBool Source #

isInsideTGraph :: TGraphBentErrors -> CDouble -> CDouble -> IO CInt Source #

leastSquareFit :: TGraphBentErrors -> CInt -> Ptr CDouble -> CDouble -> CDouble -> IO () Source #

paintStats :: (ITF1 c0, FPtr c0) => TGraphBentErrors -> c0 -> IO () Source #

removePoint :: TGraphBentErrors -> CInt -> IO CInt Source #

setEditable :: TGraphBentErrors -> CBool -> IO () Source #

setHistogram :: (ITH1F c0, FPtr c0) => TGraphBentErrors -> c0 -> IO () Source #

setMaximumTGraph :: TGraphBentErrors -> CDouble -> IO () Source #

setMinimumTGraph :: TGraphBentErrors -> CDouble -> IO () Source #

set :: TGraphBentErrors -> CInt -> IO () Source #

setPoint :: TGraphBentErrors -> CInt -> CDouble -> CDouble -> IO () Source #

ITGraph TGraphErrors Source # 
Instance details

Defined in HROOT.Hist.TGraphErrors.Implementation

Methods

apply :: (ITF1 c0, FPtr c0) => TGraphErrors -> c0 -> IO () Source #

chisquare :: (ITF1 c0, FPtr c0) => TGraphErrors -> c0 -> IO CDouble Source #

drawGraph :: Castable c0 CString => TGraphErrors -> CInt -> Ptr CDouble -> Ptr CDouble -> c0 -> IO () Source #

drawPanelTGraph :: TGraphErrors -> IO () Source #

expand :: TGraphErrors -> CInt -> CInt -> IO () Source #

fitPanelTGraph :: TGraphErrors -> IO () Source #

getCorrelationFactorTGraph :: TGraphErrors -> IO CDouble Source #

getCovarianceTGraph :: TGraphErrors -> IO CDouble Source #

getMeanTGraph :: TGraphErrors -> CInt -> IO CDouble Source #

getRMSTGraph :: TGraphErrors -> CInt -> IO CDouble Source #

getErrorX :: TGraphErrors -> CInt -> IO CDouble Source #

getErrorY :: TGraphErrors -> CInt -> IO CDouble Source #

getErrorXhigh :: TGraphErrors -> CInt -> IO CDouble Source #

getErrorXlow :: TGraphErrors -> CInt -> IO CDouble Source #

getErrorYhigh :: TGraphErrors -> CInt -> IO CDouble Source #

getErrorYlow :: TGraphErrors -> CInt -> IO CDouble Source #

initExpo :: TGraphErrors -> CDouble -> CDouble -> IO () Source #

initGaus :: TGraphErrors -> CDouble -> CDouble -> IO () Source #

initPolynom :: TGraphErrors -> CDouble -> CDouble -> IO () Source #

insertPoint :: TGraphErrors -> IO CInt Source #

integralTGraph :: TGraphErrors -> CInt -> CInt -> IO CDouble Source #

isEditable :: TGraphErrors -> IO CBool Source #

isInsideTGraph :: TGraphErrors -> CDouble -> CDouble -> IO CInt Source #

leastSquareFit :: TGraphErrors -> CInt -> Ptr CDouble -> CDouble -> CDouble -> IO () Source #

paintStats :: (ITF1 c0, FPtr c0) => TGraphErrors -> c0 -> IO () Source #

removePoint :: TGraphErrors -> CInt -> IO CInt Source #

setEditable :: TGraphErrors -> CBool -> IO () Source #

setHistogram :: (ITH1F c0, FPtr c0) => TGraphErrors -> c0 -> IO () Source #

setMaximumTGraph :: TGraphErrors -> CDouble -> IO () Source #

setMinimumTGraph :: TGraphErrors -> CDouble -> IO () Source #

set :: TGraphErrors -> CInt -> IO () Source #

setPoint :: TGraphErrors -> CInt -> CDouble -> CDouble -> IO () Source #

upcastTGraph :: forall a. (FPtr a, ITGraph a) => a -> TGraph Source #

downcastTGraph :: forall a. (FPtr a, ITGraph a) => TGraph -> a Source #