{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TCutG.Implementation where import HROOT.TypeCast import HROOT.Class.TCutG.RawType import HROOT.Class.TCutG.FFI import HROOT.Class.TCutG.Interface import HROOT.Class.TCutG.Cast 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.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TGraph.RawType import HROOT.Class.TGraph.Cast import HROOT.Class.TGraph.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 ITCutG TCutG where instance ITGraph TCutG where apply = xform1 c_tcutg_apply chisquare = xform1 c_tcutg_chisquare drawGraph = xform4 c_tcutg_drawgraph drawPanelTGraph = xform0 c_tcutg_drawpaneltgraph expand = xform2 c_tcutg_expand fitPanelTGraph = xform0 c_tcutg_fitpaneltgraph getCorrelationFactorTGraph = xform0 c_tcutg_getcorrelationfactortgraph getCovarianceTGraph = xform0 c_tcutg_getcovariancetgraph getMeanTGraph = xform1 c_tcutg_getmeantgraph getRMSTGraph = xform1 c_tcutg_getrmstgraph getErrorX = xform1 c_tcutg_geterrorx getErrorY = xform1 c_tcutg_geterrory getErrorXhigh = xform1 c_tcutg_geterrorxhigh getErrorXlow = xform1 c_tcutg_geterrorxlow getErrorYhigh = xform1 c_tcutg_geterroryhigh getErrorYlow = xform1 c_tcutg_geterrorylow initExpo = xform2 c_tcutg_initexpo initGaus = xform2 c_tcutg_initgaus initPolynom = xform2 c_tcutg_initpolynom insertPoint = xform0 c_tcutg_insertpoint integralTGraph = xform2 c_tcutg_integraltgraph isEditable = xform0 c_tcutg_iseditable isInsideTGraph = xform2 c_tcutg_isinsidetgraph leastSquareFit = xform4 c_tcutg_leastsquarefit paintStats = xform1 c_tcutg_paintstats removePoint = xform1 c_tcutg_removepoint setEditable = xform1 c_tcutg_seteditable setHistogram = xform1 c_tcutg_sethistogram setMaximumTGraph = xform1 c_tcutg_setmaximumtgraph setMinimumTGraph = xform1 c_tcutg_setminimumtgraph set = xform1 c_tcutg_set setPoint = xform3 c_tcutg_setpoint instance ITNamed TCutG where setName = xform1 c_tcutg_setname setNameTitle = xform2 c_tcutg_setnametitle setTitle = xform1 c_tcutg_settitle instance ITAttLine TCutG where getLineColor = xform0 c_tcutg_getlinecolor getLineStyle = xform0 c_tcutg_getlinestyle getLineWidth = xform0 c_tcutg_getlinewidth resetAttLine = xform1 c_tcutg_resetattline setLineAttributes = xform0 c_tcutg_setlineattributes setLineColor = xform1 c_tcutg_setlinecolor setLineStyle = xform1 c_tcutg_setlinestyle setLineWidth = xform1 c_tcutg_setlinewidth instance ITAttFill TCutG where setFillColor = xform1 c_tcutg_setfillcolor setFillStyle = xform1 c_tcutg_setfillstyle instance ITAttMarker TCutG where getMarkerColor = xform0 c_tcutg_getmarkercolor getMarkerStyle = xform0 c_tcutg_getmarkerstyle getMarkerSize = xform0 c_tcutg_getmarkersize resetAttMarker = xform1 c_tcutg_resetattmarker setMarkerAttributes = xform0 c_tcutg_setmarkerattributes setMarkerColor = xform1 c_tcutg_setmarkercolor setMarkerStyle = xform1 c_tcutg_setmarkerstyle setMarkerSize = xform1 c_tcutg_setmarkersize instance ITObject TCutG where draw = xform1 c_tcutg_draw findObject = xform1 c_tcutg_findobject getName = xform0 c_tcutg_getname isA = xform0 c_tcutg_isa isFolder = xform0 c_tcutg_isfolder isEqual = xform1 c_tcutg_isequal isSortable = xform0 c_tcutg_issortable paint = xform1 c_tcutg_paint printObj = xform1 c_tcutg_printobj recursiveRemove = xform1 c_tcutg_recursiveremove saveAs = xform2 c_tcutg_saveas useCurrentStyle = xform0 c_tcutg_usecurrentstyle write = xform3 c_tcutg_write instance IDeletable TCutG where delete = xform0 c_tcutg_delete instance ITCutG (Exist TCutG) where instance ITGraph (Exist TCutG) where apply (ETCutG x) = apply x chisquare (ETCutG x) = chisquare x drawGraph (ETCutG x) = drawGraph x drawPanelTGraph (ETCutG x) = drawPanelTGraph x expand (ETCutG x) = expand x fitPanelTGraph (ETCutG x) = fitPanelTGraph x getCorrelationFactorTGraph (ETCutG x) = getCorrelationFactorTGraph x getCovarianceTGraph (ETCutG x) = getCovarianceTGraph x getMeanTGraph (ETCutG x) = getMeanTGraph x getRMSTGraph (ETCutG x) = getRMSTGraph x getErrorX (ETCutG x) = getErrorX x getErrorY (ETCutG x) = getErrorY x getErrorXhigh (ETCutG x) = getErrorXhigh x getErrorXlow (ETCutG x) = getErrorXlow x getErrorYhigh (ETCutG x) = getErrorYhigh x getErrorYlow (ETCutG x) = getErrorYlow x initExpo (ETCutG x) = initExpo x initGaus (ETCutG x) = initGaus x initPolynom (ETCutG x) = initPolynom x insertPoint (ETCutG x) = insertPoint x integralTGraph (ETCutG x) = integralTGraph x isEditable (ETCutG x) = isEditable x isInsideTGraph (ETCutG x) = isInsideTGraph x leastSquareFit (ETCutG x) = leastSquareFit x paintStats (ETCutG x) = paintStats x removePoint (ETCutG x) = removePoint x setEditable (ETCutG x) = setEditable x setHistogram (ETCutG x) = setHistogram x setMaximumTGraph (ETCutG x) = setMaximumTGraph x setMinimumTGraph (ETCutG x) = setMinimumTGraph x set (ETCutG x) = set x setPoint (ETCutG x) = setPoint x instance ITNamed (Exist TCutG) where setName (ETCutG x) = setName x setNameTitle (ETCutG x) = setNameTitle x setTitle (ETCutG x) = setTitle x instance ITAttLine (Exist TCutG) where getLineColor (ETCutG x) = getLineColor x getLineStyle (ETCutG x) = getLineStyle x getLineWidth (ETCutG x) = getLineWidth x resetAttLine (ETCutG x) = resetAttLine x setLineAttributes (ETCutG x) = setLineAttributes x setLineColor (ETCutG x) = setLineColor x setLineStyle (ETCutG x) = setLineStyle x setLineWidth (ETCutG x) = setLineWidth x instance ITAttFill (Exist TCutG) where setFillColor (ETCutG x) = setFillColor x setFillStyle (ETCutG x) = setFillStyle x instance ITAttMarker (Exist TCutG) where getMarkerColor (ETCutG x) = getMarkerColor x getMarkerStyle (ETCutG x) = getMarkerStyle x getMarkerSize (ETCutG x) = getMarkerSize x resetAttMarker (ETCutG x) = resetAttMarker x setMarkerAttributes (ETCutG x) = setMarkerAttributes x setMarkerColor (ETCutG x) = setMarkerColor x setMarkerStyle (ETCutG x) = setMarkerStyle x setMarkerSize (ETCutG x) = setMarkerSize x instance ITObject (Exist TCutG) where draw (ETCutG x) = draw x findObject (ETCutG x) = findObject x getName (ETCutG x) = getName x isA (ETCutG x) = isA x isFolder (ETCutG x) = isFolder x isEqual (ETCutG x) = isEqual x isSortable (ETCutG x) = isSortable x paint (ETCutG x) = paint x printObj (ETCutG x) = printObj x recursiveRemove (ETCutG x) = recursiveRemove x saveAs (ETCutG x) = saveAs x useCurrentStyle (ETCutG x) = useCurrentStyle x write (ETCutG x) = write x instance IDeletable (Exist TCutG) where delete (ETCutG x) = delete x newTCutG :: String -> Int -> [Double] -> [Double] -> IO TCutG newTCutG = xform3 c_tcutg_newtcutg instance FPtr (Exist TCutG) where type Raw (Exist TCutG) = RawTCutG get_fptr (ETCutG obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETCutG (cast_fptr_to_obj (fptr :: ForeignPtr RawTCutG) :: TCutG)