{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, ExistentialQuantification, ScopedTypeVariables #-} -- module HROOT.Class.Interface where module HROOT.Hist.TGraph.Interface where import Data.Word import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import FFICXX.Runtime.Cast import HROOT.Hist.TGraph.RawType import HROOT.Hist.TF1.RawType import HROOT.Hist.TH1F.RawType import HROOT.Hist.TAxis.RawType import HROOT.Core.TNamed.Interface import HROOT.Core.TAttLine.Interface import HROOT.Core.TAttFill.Interface import HROOT.Core.TAttMarker.Interface ---- ============ ---- import {-# SOURCE #-} HROOT.Hist.TF1.Interface import {-# SOURCE #-} HROOT.Hist.TH1F.Interface 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 CDouble drawGraph :: a -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO () drawPanelTGraph :: a -> IO () expand :: a -> CInt -> CInt -> IO () fitPanelTGraph :: a -> IO () getCorrelationFactorTGraph :: a -> IO CDouble getCovarianceTGraph :: a -> IO CDouble getMeanTGraph :: a -> CInt -> IO CDouble getRMSTGraph :: a -> CInt -> IO CDouble getErrorX :: a -> CInt -> IO CDouble getErrorY :: a -> CInt -> IO CDouble getErrorXhigh :: a -> CInt -> IO CDouble getErrorXlow :: a -> CInt -> IO CDouble getErrorYhigh :: a -> CInt -> IO CDouble getErrorYlow :: a -> CInt -> IO CDouble initExpo :: a -> CDouble -> CDouble -> IO () initGaus :: a -> CDouble -> CDouble -> IO () initPolynom :: a -> CDouble -> CDouble -> IO () insertPoint :: a -> IO CInt integralTGraph :: a -> CInt -> CInt -> IO CDouble isEditable :: a -> IO CInt isInsideTGraph :: a -> CDouble -> CDouble -> IO CInt leastSquareFit :: a -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO () paintStats :: (ITF1 c0, FPtr c0) => a -> c0 -> IO () removePoint :: a -> CInt -> IO CInt setEditable :: a -> CInt -> IO () setHistogram :: (ITH1F c0, FPtr c0) => a -> c0 -> IO () setMaximumTGraph :: a -> CDouble -> IO () setMinimumTGraph :: a -> CDouble -> IO () set :: a -> CInt -> IO () setPoint :: a -> CInt -> CDouble -> CDouble -> IO () instance Existable TGraph where data Exist TGraph = forall a. (FPtr a, ITGraph a) => ETGraph a upcastTGraph :: (FPtr a, ITGraph a) => a -> TGraph upcastTGraph h = let fh = get_fptr h fh2 :: ForeignPtr RawTGraph = castForeignPtr fh in cast_fptr_to_obj fh2 downcastTGraph :: (FPtr a, ITGraph a) => TGraph -> a downcastTGraph h = let fh = get_fptr h fh2 = castForeignPtr fh in cast_fptr_to_obj fh2