{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Hist.TGraphBentErrors.Implementation where import FFICXX.Runtime.Cast import HROOT.Hist.TGraphBentErrors.RawType import HROOT.Hist.TGraphBentErrors.FFI import HROOT.Hist.TGraphBentErrors.Interface import HROOT.Hist.TGraphBentErrors.Cast 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.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Hist.TGraph.RawType import HROOT.Hist.TGraph.Cast import HROOT.Hist.TGraph.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 HROOT.Core.Deletable.RawType import HROOT.Core.Deletable.Cast import HROOT.Core.Deletable.Interface import Data.Word import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import System.IO.Unsafe instance ITGraphBentErrors TGraphBentErrors where instance ITGraph TGraphBentErrors where apply = xform1 c_tgraphbenterrors_apply chisquare = xform1 c_tgraphbenterrors_chisquare drawGraph = xform4 c_tgraphbenterrors_drawgraph drawPanelTGraph = xform0 c_tgraphbenterrors_drawpaneltgraph expand = xform2 c_tgraphbenterrors_expand fitPanelTGraph = xform0 c_tgraphbenterrors_fitpaneltgraph getCorrelationFactorTGraph = xform0 c_tgraphbenterrors_getcorrelationfactortgraph getCovarianceTGraph = xform0 c_tgraphbenterrors_getcovariancetgraph getMeanTGraph = xform1 c_tgraphbenterrors_getmeantgraph getRMSTGraph = xform1 c_tgraphbenterrors_getrmstgraph getErrorX = xform1 c_tgraphbenterrors_geterrorx getErrorY = xform1 c_tgraphbenterrors_geterrory getErrorXhigh = xform1 c_tgraphbenterrors_geterrorxhigh getErrorXlow = xform1 c_tgraphbenterrors_geterrorxlow getErrorYhigh = xform1 c_tgraphbenterrors_geterroryhigh getErrorYlow = xform1 c_tgraphbenterrors_geterrorylow initExpo = xform2 c_tgraphbenterrors_initexpo initGaus = xform2 c_tgraphbenterrors_initgaus initPolynom = xform2 c_tgraphbenterrors_initpolynom insertPoint = xform0 c_tgraphbenterrors_insertpoint integralTGraph = xform2 c_tgraphbenterrors_integraltgraph isEditable = xform0 c_tgraphbenterrors_iseditable isInsideTGraph = xform2 c_tgraphbenterrors_isinsidetgraph leastSquareFit = xform4 c_tgraphbenterrors_leastsquarefit paintStats = xform1 c_tgraphbenterrors_paintstats removePoint = xform1 c_tgraphbenterrors_removepoint setEditable = xform1 c_tgraphbenterrors_seteditable setHistogram = xform1 c_tgraphbenterrors_sethistogram setMaximumTGraph = xform1 c_tgraphbenterrors_setmaximumtgraph setMinimumTGraph = xform1 c_tgraphbenterrors_setminimumtgraph set = xform1 c_tgraphbenterrors_set setPoint = xform3 c_tgraphbenterrors_setpoint instance ITNamed TGraphBentErrors where setName = xform1 c_tgraphbenterrors_setname setNameTitle = xform2 c_tgraphbenterrors_setnametitle setTitle = xform1 c_tgraphbenterrors_settitle instance ITAttLine TGraphBentErrors where getLineColor = xform0 c_tgraphbenterrors_getlinecolor getLineStyle = xform0 c_tgraphbenterrors_getlinestyle getLineWidth = xform0 c_tgraphbenterrors_getlinewidth resetAttLine = xform1 c_tgraphbenterrors_resetattline setLineAttributes = xform0 c_tgraphbenterrors_setlineattributes setLineColor = xform1 c_tgraphbenterrors_setlinecolor setLineStyle = xform1 c_tgraphbenterrors_setlinestyle setLineWidth = xform1 c_tgraphbenterrors_setlinewidth instance ITAttFill TGraphBentErrors where setFillColor = xform1 c_tgraphbenterrors_setfillcolor setFillStyle = xform1 c_tgraphbenterrors_setfillstyle instance ITAttMarker TGraphBentErrors where getMarkerColor = xform0 c_tgraphbenterrors_getmarkercolor getMarkerStyle = xform0 c_tgraphbenterrors_getmarkerstyle getMarkerSize = xform0 c_tgraphbenterrors_getmarkersize resetAttMarker = xform1 c_tgraphbenterrors_resetattmarker setMarkerAttributes = xform0 c_tgraphbenterrors_setmarkerattributes setMarkerColor = xform1 c_tgraphbenterrors_setmarkercolor setMarkerStyle = xform1 c_tgraphbenterrors_setmarkerstyle setMarkerSize = xform1 c_tgraphbenterrors_setmarkersize instance ITObject TGraphBentErrors where draw = xform1 c_tgraphbenterrors_draw findObject = xform1 c_tgraphbenterrors_findobject getName = xform0 c_tgraphbenterrors_getname isA = xform0 c_tgraphbenterrors_isa paint = xform1 c_tgraphbenterrors_paint printObj = xform1 c_tgraphbenterrors_printobj saveAs = xform2 c_tgraphbenterrors_saveas write = xform3 c_tgraphbenterrors_write instance IDeletable TGraphBentErrors where delete = xform0 c_tgraphbenterrors_delete instance ITGraphBentErrors (Exist TGraphBentErrors) where instance ITGraph (Exist TGraphBentErrors) where apply (ETGraphBentErrors x) = apply x chisquare (ETGraphBentErrors x) = chisquare x drawGraph (ETGraphBentErrors x) = drawGraph x drawPanelTGraph (ETGraphBentErrors x) = drawPanelTGraph x expand (ETGraphBentErrors x) = expand x fitPanelTGraph (ETGraphBentErrors x) = fitPanelTGraph x getCorrelationFactorTGraph (ETGraphBentErrors x) = getCorrelationFactorTGraph x getCovarianceTGraph (ETGraphBentErrors x) = getCovarianceTGraph x getMeanTGraph (ETGraphBentErrors x) = getMeanTGraph x getRMSTGraph (ETGraphBentErrors x) = getRMSTGraph x getErrorX (ETGraphBentErrors x) = getErrorX x getErrorY (ETGraphBentErrors x) = getErrorY x getErrorXhigh (ETGraphBentErrors x) = getErrorXhigh x getErrorXlow (ETGraphBentErrors x) = getErrorXlow x getErrorYhigh (ETGraphBentErrors x) = getErrorYhigh x getErrorYlow (ETGraphBentErrors x) = getErrorYlow x initExpo (ETGraphBentErrors x) = initExpo x initGaus (ETGraphBentErrors x) = initGaus x initPolynom (ETGraphBentErrors x) = initPolynom x insertPoint (ETGraphBentErrors x) = insertPoint x integralTGraph (ETGraphBentErrors x) = integralTGraph x isEditable (ETGraphBentErrors x) = isEditable x isInsideTGraph (ETGraphBentErrors x) = isInsideTGraph x leastSquareFit (ETGraphBentErrors x) = leastSquareFit x paintStats (ETGraphBentErrors x) = paintStats x removePoint (ETGraphBentErrors x) = removePoint x setEditable (ETGraphBentErrors x) = setEditable x setHistogram (ETGraphBentErrors x) = setHistogram x setMaximumTGraph (ETGraphBentErrors x) = setMaximumTGraph x setMinimumTGraph (ETGraphBentErrors x) = setMinimumTGraph x set (ETGraphBentErrors x) = set x setPoint (ETGraphBentErrors x) = setPoint x instance ITNamed (Exist TGraphBentErrors) where setName (ETGraphBentErrors x) = setName x setNameTitle (ETGraphBentErrors x) = setNameTitle x setTitle (ETGraphBentErrors x) = setTitle x instance ITAttLine (Exist TGraphBentErrors) where getLineColor (ETGraphBentErrors x) = getLineColor x getLineStyle (ETGraphBentErrors x) = getLineStyle x getLineWidth (ETGraphBentErrors x) = getLineWidth x resetAttLine (ETGraphBentErrors x) = resetAttLine x setLineAttributes (ETGraphBentErrors x) = setLineAttributes x setLineColor (ETGraphBentErrors x) = setLineColor x setLineStyle (ETGraphBentErrors x) = setLineStyle x setLineWidth (ETGraphBentErrors x) = setLineWidth x instance ITAttFill (Exist TGraphBentErrors) where setFillColor (ETGraphBentErrors x) = setFillColor x setFillStyle (ETGraphBentErrors x) = setFillStyle x instance ITAttMarker (Exist TGraphBentErrors) where getMarkerColor (ETGraphBentErrors x) = getMarkerColor x getMarkerStyle (ETGraphBentErrors x) = getMarkerStyle x getMarkerSize (ETGraphBentErrors x) = getMarkerSize x resetAttMarker (ETGraphBentErrors x) = resetAttMarker x setMarkerAttributes (ETGraphBentErrors x) = setMarkerAttributes x setMarkerColor (ETGraphBentErrors x) = setMarkerColor x setMarkerStyle (ETGraphBentErrors x) = setMarkerStyle x setMarkerSize (ETGraphBentErrors x) = setMarkerSize x instance ITObject (Exist TGraphBentErrors) where draw (ETGraphBentErrors x) = draw x findObject (ETGraphBentErrors x) = findObject x getName (ETGraphBentErrors x) = getName x isA (ETGraphBentErrors x) = isA x paint (ETGraphBentErrors x) = paint x printObj (ETGraphBentErrors x) = printObj x saveAs (ETGraphBentErrors x) = saveAs x write (ETGraphBentErrors x) = write x instance IDeletable (Exist TGraphBentErrors) where delete (ETGraphBentErrors x) = delete x newTGraphBentErrors :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO TGraphBentErrors newTGraphBentErrors = xform10 c_tgraphbenterrors_newtgraphbenterrors instance FPtr (Exist TGraphBentErrors) where type Raw (Exist TGraphBentErrors) = RawTGraphBentErrors get_fptr (ETGraphBentErrors obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETGraphBentErrors (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphBentErrors) :: TGraphBentErrors)