{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TGraph.Implementation where import HROOT.TypeCast import HROOT.Class.TGraph.RawType import HROOT.Class.TGraph.FFI import HROOT.Class.TGraph.Interface import HROOT.Class.TGraph.Cast import HROOT.Class.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TF1.RawType import HROOT.Class.TF1.Cast import HROOT.Class.TF1.Interface import HROOT.Class.TH1F.RawType import HROOT.Class.TH1F.Cast import HROOT.Class.TH1F.Interface import HROOT.Class.TList.RawType import HROOT.Class.TList.Cast import HROOT.Class.TList.Interface import HROOT.Class.TAxis.RawType import HROOT.Class.TAxis.Cast import HROOT.Class.TAxis.Interface import HROOT.Class.TNamed.RawType import HROOT.Class.TNamed.Cast import HROOT.Class.TNamed.Interface import HROOT.Class.TAttLine.RawType import HROOT.Class.TAttLine.Cast import HROOT.Class.TAttLine.Interface import HROOT.Class.TAttFill.RawType import HROOT.Class.TAttFill.Cast import HROOT.Class.TAttFill.Interface import HROOT.Class.TAttMarker.RawType import HROOT.Class.TAttMarker.Cast import HROOT.Class.TAttMarker.Interface import HROOT.Class.TObject.RawType import HROOT.Class.TObject.Cast import HROOT.Class.TObject.Interface import HROOT.Class.Deletable.RawType import HROOT.Class.Deletable.Cast import HROOT.Class.Deletable.Interface import Data.Word -- import Foreign.C -- import Foreign.Ptr import Foreign.ForeignPtr import System.IO.Unsafe 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 draw = xform1 c_tgraph_draw findObject = xform1 c_tgraph_findobject getName = xform0 c_tgraph_getname isA = xform0 c_tgraph_isa isFolder = xform0 c_tgraph_isfolder isEqual = xform1 c_tgraph_isequal isSortable = xform0 c_tgraph_issortable paint = xform1 c_tgraph_paint printObj = xform1 c_tgraph_printobj recursiveRemove = xform1 c_tgraph_recursiveremove saveAs = xform2 c_tgraph_saveas useCurrentStyle = xform0 c_tgraph_usecurrentstyle write = xform3 c_tgraph_write instance IDeletable TGraph where delete = xform0 c_tgraph_delete instance ITGraph (Exist TGraph) where apply (ETGraph x) = apply x chisquare (ETGraph x) = chisquare x drawGraph (ETGraph x) = drawGraph x drawPanelTGraph (ETGraph x) = drawPanelTGraph x expand (ETGraph x) = expand x fitPanelTGraph (ETGraph x) = fitPanelTGraph x getCorrelationFactorTGraph (ETGraph x) = getCorrelationFactorTGraph x getCovarianceTGraph (ETGraph x) = getCovarianceTGraph x getMeanTGraph (ETGraph x) = getMeanTGraph x getRMSTGraph (ETGraph x) = getRMSTGraph x getErrorX (ETGraph x) = getErrorX x getErrorY (ETGraph x) = getErrorY x getErrorXhigh (ETGraph x) = getErrorXhigh x getErrorXlow (ETGraph x) = getErrorXlow x getErrorYhigh (ETGraph x) = getErrorYhigh x getErrorYlow (ETGraph x) = getErrorYlow x initExpo (ETGraph x) = initExpo x initGaus (ETGraph x) = initGaus x initPolynom (ETGraph x) = initPolynom x insertPoint (ETGraph x) = insertPoint x integralTGraph (ETGraph x) = integralTGraph x isEditable (ETGraph x) = isEditable x isInsideTGraph (ETGraph x) = isInsideTGraph x leastSquareFit (ETGraph x) = leastSquareFit x paintStats (ETGraph x) = paintStats x removePoint (ETGraph x) = removePoint x setEditable (ETGraph x) = setEditable x setHistogram (ETGraph x) = setHistogram x setMaximumTGraph (ETGraph x) = setMaximumTGraph x setMinimumTGraph (ETGraph x) = setMinimumTGraph x set (ETGraph x) = set x setPoint (ETGraph x) = setPoint x instance ITNamed (Exist TGraph) where setName (ETGraph x) = setName x setNameTitle (ETGraph x) = setNameTitle x setTitle (ETGraph x) = setTitle x instance ITAttLine (Exist TGraph) where getLineColor (ETGraph x) = getLineColor x getLineStyle (ETGraph x) = getLineStyle x getLineWidth (ETGraph x) = getLineWidth x resetAttLine (ETGraph x) = resetAttLine x setLineAttributes (ETGraph x) = setLineAttributes x setLineColor (ETGraph x) = setLineColor x setLineStyle (ETGraph x) = setLineStyle x setLineWidth (ETGraph x) = setLineWidth x instance ITAttFill (Exist TGraph) where setFillColor (ETGraph x) = setFillColor x setFillStyle (ETGraph x) = setFillStyle x instance ITAttMarker (Exist TGraph) where getMarkerColor (ETGraph x) = getMarkerColor x getMarkerStyle (ETGraph x) = getMarkerStyle x getMarkerSize (ETGraph x) = getMarkerSize x resetAttMarker (ETGraph x) = resetAttMarker x setMarkerAttributes (ETGraph x) = setMarkerAttributes x setMarkerColor (ETGraph x) = setMarkerColor x setMarkerStyle (ETGraph x) = setMarkerStyle x setMarkerSize (ETGraph x) = setMarkerSize x instance ITObject (Exist TGraph) where draw (ETGraph x) = draw x findObject (ETGraph x) = findObject x getName (ETGraph x) = getName x isA (ETGraph x) = isA x isFolder (ETGraph x) = isFolder x isEqual (ETGraph x) = isEqual x isSortable (ETGraph x) = isSortable x paint (ETGraph x) = paint x printObj (ETGraph x) = printObj x recursiveRemove (ETGraph x) = recursiveRemove x saveAs (ETGraph x) = saveAs x useCurrentStyle (ETGraph x) = useCurrentStyle x write (ETGraph x) = write x instance IDeletable (Exist TGraph) where delete (ETGraph x) = delete x newTGraph :: Int -> [Double] -> [Double] -> IO TGraph newTGraph = xform2 c_tgraph_newtgraph tGraphGetEditable :: TGraph -> IO Int tGraphGetEditable = xform0 c_tgraph_tgraphgeteditable tGraphGetFunction :: TGraph -> String -> IO TF1 tGraphGetFunction = xform1 c_tgraph_tgraphgetfunction tGraphGetHistogram :: TGraph -> IO TH1F tGraphGetHistogram = xform0 c_tgraph_tgraphgethistogram tGraphGetListOfFunctions :: TGraph -> IO TList tGraphGetListOfFunctions = xform0 c_tgraph_tgraphgetlistoffunctions tGraphGetMaxSize :: TGraph -> IO Int tGraphGetMaxSize = xform0 c_tgraph_tgraphgetmaxsize tGraphGetN :: TGraph -> IO Int tGraphGetN = xform0 c_tgraph_tgraphgetn tGraphGetMaximum :: TGraph -> IO Double tGraphGetMaximum = xform0 c_tgraph_tgraphgetmaximum tGraphGetMinimum :: TGraph -> IO Double tGraphGetMinimum = xform0 c_tgraph_tgraphgetminimum tGraphGetXaxis :: TGraph -> IO TAxis tGraphGetXaxis = xform0 c_tgraph_tgraphgetxaxis tGraphGetYaxis :: TGraph -> IO TAxis tGraphGetYaxis = xform0 c_tgraph_tgraphgetyaxis tGraphPaintGraph :: TGraph -> Int -> [Double] -> [Double] -> String -> IO () tGraphPaintGraph = xform4 c_tgraph_tgraphpaintgraph tGraphPaintGrapHist :: TGraph -> Int -> [Double] -> [Double] -> String -> IO () tGraphPaintGrapHist = xform4 c_tgraph_tgraphpaintgraphist instance FPtr (Exist TGraph) where type Raw (Exist TGraph) = RawTGraph get_fptr (ETGraph obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETGraph (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraph) :: TGraph)