{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module HROOT.Hist.TGraph.Implementation where import Data.Monoid import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import Language.Haskell.TH import Language.Haskell.TH.Syntax import System.IO.Unsafe import FFICXX.Runtime.Cast import FFICXX.Runtime.CodeGen.Cxx import FFICXX.Runtime.TH import HROOT.Hist.TGraph.RawType import HROOT.Hist.TGraph.FFI import HROOT.Hist.TGraph.Interface import HROOT.Hist.TGraph.Cast import HROOT.Hist.TGraph.RawType import HROOT.Hist.TGraph.Cast import HROOT.Hist.TGraph.Interface import HROOT.Core.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Hist.TF1.RawType import HROOT.Hist.TF1.Cast import HROOT.Hist.TF1.Interface import HROOT.Hist.TH1F.RawType import HROOT.Hist.TH1F.Cast import HROOT.Hist.TH1F.Interface import HROOT.Hist.TAxis.RawType import HROOT.Hist.TAxis.Cast import HROOT.Hist.TAxis.Interface import HROOT.Core.TNamed.RawType import HROOT.Core.TNamed.Cast import HROOT.Core.TNamed.Interface import HROOT.Core.TAttLine.RawType import HROOT.Core.TAttLine.Cast import HROOT.Core.TAttLine.Interface import HROOT.Core.TAttFill.RawType import HROOT.Core.TAttFill.Cast import HROOT.Core.TAttFill.Interface import HROOT.Core.TAttMarker.RawType import HROOT.Core.TAttMarker.Cast import HROOT.Core.TAttMarker.Interface import HROOT.Core.TObject.RawType import HROOT.Core.TObject.Cast import HROOT.Core.TObject.Interface import STD.Deletable.RawType import STD.Deletable.Cast import STD.Deletable.Interface instance () => ITGraph (TGraph) where apply = xform1 c_tgraph_apply chisquare = xform1 c_tgraph_chisquare drawGraph = xform4 c_tgraph_drawgraph drawPanelTGraph = xform0 c_tgraph_drawpaneltgraph expand = xform2 c_tgraph_expand fitPanelTGraph = xform0 c_tgraph_fitpaneltgraph getCorrelationFactorTGraph = xform0 c_tgraph_getcorrelationfactortgraph getCovarianceTGraph = xform0 c_tgraph_getcovariancetgraph getMeanTGraph = xform1 c_tgraph_getmeantgraph getRMSTGraph = xform1 c_tgraph_getrmstgraph getErrorX = xform1 c_tgraph_geterrorx getErrorY = xform1 c_tgraph_geterrory getErrorXhigh = xform1 c_tgraph_geterrorxhigh getErrorXlow = xform1 c_tgraph_geterrorxlow getErrorYhigh = xform1 c_tgraph_geterroryhigh getErrorYlow = xform1 c_tgraph_geterrorylow initExpo = xform2 c_tgraph_initexpo initGaus = xform2 c_tgraph_initgaus initPolynom = xform2 c_tgraph_initpolynom insertPoint = xform0 c_tgraph_insertpoint integralTGraph = xform2 c_tgraph_integraltgraph isEditable = xform0 c_tgraph_iseditable isInsideTGraph = xform2 c_tgraph_isinsidetgraph leastSquareFit = xform4 c_tgraph_leastsquarefit paintStats = xform1 c_tgraph_paintstats removePoint = xform1 c_tgraph_removepoint setEditable = xform1 c_tgraph_seteditable setHistogram = xform1 c_tgraph_sethistogram setMaximumTGraph = xform1 c_tgraph_setmaximumtgraph setMinimumTGraph = xform1 c_tgraph_setminimumtgraph set = xform1 c_tgraph_set setPoint = xform3 c_tgraph_setpoint instance () => ITNamed (TGraph) where setName = xform1 c_tgraph_setname setNameTitle = xform2 c_tgraph_setnametitle setTitle = xform1 c_tgraph_settitle instance () => ITAttLine (TGraph) where getLineColor = xform0 c_tgraph_getlinecolor getLineStyle = xform0 c_tgraph_getlinestyle getLineWidth = xform0 c_tgraph_getlinewidth resetAttLine = xform1 c_tgraph_resetattline setLineAttributes = xform0 c_tgraph_setlineattributes setLineColor = xform1 c_tgraph_setlinecolor setLineStyle = xform1 c_tgraph_setlinestyle setLineWidth = xform1 c_tgraph_setlinewidth instance () => ITAttFill (TGraph) where setFillColor = xform1 c_tgraph_setfillcolor setFillStyle = xform1 c_tgraph_setfillstyle instance () => ITAttMarker (TGraph) where getMarkerColor = xform0 c_tgraph_getmarkercolor getMarkerStyle = xform0 c_tgraph_getmarkerstyle getMarkerSize = xform0 c_tgraph_getmarkersize resetAttMarker = xform1 c_tgraph_resetattmarker setMarkerAttributes = xform0 c_tgraph_setmarkerattributes setMarkerColor = xform1 c_tgraph_setmarkercolor setMarkerStyle = xform1 c_tgraph_setmarkerstyle setMarkerSize = xform1 c_tgraph_setmarkersize instance () => ITObject (TGraph) where clear = xform1 c_tgraph_clear draw = xform1 c_tgraph_draw findObject = xform1 c_tgraph_findobject getName = xform0 c_tgraph_getname isA = xform0 c_tgraph_isa paint = xform1 c_tgraph_paint printObj = xform1 c_tgraph_printobj saveAs = xform2 c_tgraph_saveas write = xform3 c_tgraph_write write_ = xform0 c_tgraph_write_ instance () => IDeletable (TGraph) where delete = xform0 c_tgraph_delete newTGraph :: () => CInt -> Ptr CDouble -> Ptr CDouble -> IO TGraph newTGraph = xform2 c_tgraph_newtgraph tGraph_GetEditable :: () => TGraph -> IO CBool tGraph_GetEditable = xform0 c_tgraph_tgraph_geteditable tGraph_GetFunction :: (Castable c0 CString) => TGraph -> c0 -> IO TF1 tGraph_GetFunction = xform1 c_tgraph_tgraph_getfunction tGraph_GetHistogram :: () => TGraph -> IO TH1F tGraph_GetHistogram = xform0 c_tgraph_tgraph_gethistogram tGraph_GetMaxSize :: () => TGraph -> IO CInt tGraph_GetMaxSize = xform0 c_tgraph_tgraph_getmaxsize tGraph_GetN :: () => TGraph -> IO CInt tGraph_GetN = xform0 c_tgraph_tgraph_getn tGraph_GetMaximum :: () => TGraph -> IO CDouble tGraph_GetMaximum = xform0 c_tgraph_tgraph_getmaximum tGraph_GetMinimum :: () => TGraph -> IO CDouble tGraph_GetMinimum = xform0 c_tgraph_tgraph_getminimum tGraph_GetXaxis :: () => TGraph -> IO TAxis tGraph_GetXaxis = xform0 c_tgraph_tgraph_getxaxis tGraph_GetYaxis :: () => TGraph -> IO TAxis tGraph_GetYaxis = xform0 c_tgraph_tgraph_getyaxis tGraph_PaintGraph :: (Castable c0 CString) => TGraph -> CInt -> Ptr CDouble -> Ptr CDouble -> c0 -> IO () tGraph_PaintGraph = xform4 c_tgraph_tgraph_paintgraph tGraph_PaintGrapHist :: (Castable c0 CString) => TGraph -> CInt -> Ptr CDouble -> Ptr CDouble -> c0 -> IO () tGraph_PaintGrapHist = xform4 c_tgraph_tgraph_paintgraphist