{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Hist.TF1.Implementation where import FFICXX.Runtime.Cast import HROOT.Hist.TF1.RawType import HROOT.Hist.TF1.FFI import HROOT.Hist.TF1.Interface import HROOT.Hist.TF1.Cast import HROOT.Core.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Hist.TH1.RawType import HROOT.Hist.TH1.Cast import HROOT.Hist.TH1.Interface import HROOT.Hist.TAxis.RawType import HROOT.Hist.TAxis.Cast import HROOT.Hist.TAxis.Interface import HROOT.Hist.TFormula.RawType import HROOT.Hist.TFormula.Cast import HROOT.Hist.TFormula.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.TNamed.RawType import HROOT.Core.TNamed.Cast import HROOT.Core.TNamed.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 ITF1 TF1 where derivative = xform3 c_tf1_derivative derivative2 = xform3 c_tf1_derivative2 derivative3 = xform3 c_tf1_derivative3 drawCopyTF1 = xform1 c_tf1_drawcopytf1 drawDerivative = xform1 c_tf1_drawderivative drawIntegral = xform1 c_tf1_drawintegral drawF1 = xform4 c_tf1_drawf1 fixParameter = xform2 c_tf1_fixparameter getMaximumTF1 = xform5 c_tf1_getmaximumtf1 getMinimumTF1 = xform5 c_tf1_getminimumtf1 getMaximumX = xform5 c_tf1_getmaximumx getMinimumX = xform5 c_tf1_getminimumx getNDF = xform0 c_tf1_getndf getNpx = xform0 c_tf1_getnpx getNumberFreeParameters = xform0 c_tf1_getnumberfreeparameters getNumberFitPoints = xform0 c_tf1_getnumberfitpoints getParError = xform1 c_tf1_getparerror getProb = xform0 c_tf1_getprob getQuantilesTF1 = xform3 c_tf1_getquantilestf1 getRandomTF1 = xform2 c_tf1_getrandomtf1 getSave = xform1 c_tf1_getsave getX = xform5 c_tf1_getx getXmin = xform0 c_tf1_getxmin getXmax = xform0 c_tf1_getxmax gradientPar = xform3 c_tf1_gradientpar initArgs = xform2 c_tf1_initargs integralTF1 = xform4 c_tf1_integraltf1 integralError = xform5 c_tf1_integralerror integralFast = xform7 c_tf1_integralfast isInside = xform1 c_tf1_isinside releaseParameter = xform1 c_tf1_releaseparameter setChisquare = xform1 c_tf1_setchisquare setMaximumTF1 = xform1 c_tf1_setmaximumtf1 setMinimumTF1 = xform1 c_tf1_setminimumtf1 setNDF = xform1 c_tf1_setndf setNumberFitPoints = xform1 c_tf1_setnumberfitpoints setNpx = xform1 c_tf1_setnpx setParError = xform2 c_tf1_setparerror setParErrors = xform1 c_tf1_setparerrors setParLimits = xform3 c_tf1_setparlimits setParent = xform1 c_tf1_setparent setRange1 = xform2 c_tf1_setrange1 setRange2 = xform4 c_tf1_setrange2 setRange3 = xform6 c_tf1_setrange3 setSavedPoint = xform2 c_tf1_setsavedpoint moment = xform5 c_tf1_moment centralMoment = xform5 c_tf1_centralmoment mean = xform4 c_tf1_mean variance = xform4 c_tf1_variance instance ITFormula TF1 where compile = xform1 c_tf1_compile clear = xform1 c_tf1_clear definedValue = xform1 c_tf1_definedvalue eval = xform4 c_tf1_eval evalParOld = xform2 c_tf1_evalparold evalPar = xform2 c_tf1_evalpar getNdim = xform0 c_tf1_getndim getNpar = xform0 c_tf1_getnpar getNumber = xform0 c_tf1_getnumber getParNumber = xform1 c_tf1_getparnumber isLinear = xform0 c_tf1_islinear isNormalized = xform0 c_tf1_isnormalized setNumber = xform1 c_tf1_setnumber setParameter = xform2 c_tf1_setparameter setParameters = xform1 c_tf1_setparameters setParName = xform2 c_tf1_setparname setParNames = xform11 c_tf1_setparnames update = xform0 c_tf1_update instance ITAttLine TF1 where getLineColor = xform0 c_tf1_getlinecolor getLineStyle = xform0 c_tf1_getlinestyle getLineWidth = xform0 c_tf1_getlinewidth resetAttLine = xform1 c_tf1_resetattline setLineAttributes = xform0 c_tf1_setlineattributes setLineColor = xform1 c_tf1_setlinecolor setLineStyle = xform1 c_tf1_setlinestyle setLineWidth = xform1 c_tf1_setlinewidth instance ITAttFill TF1 where setFillColor = xform1 c_tf1_setfillcolor setFillStyle = xform1 c_tf1_setfillstyle instance ITAttMarker TF1 where getMarkerColor = xform0 c_tf1_getmarkercolor getMarkerStyle = xform0 c_tf1_getmarkerstyle getMarkerSize = xform0 c_tf1_getmarkersize resetAttMarker = xform1 c_tf1_resetattmarker setMarkerAttributes = xform0 c_tf1_setmarkerattributes setMarkerColor = xform1 c_tf1_setmarkercolor setMarkerStyle = xform1 c_tf1_setmarkerstyle setMarkerSize = xform1 c_tf1_setmarkersize instance ITNamed TF1 where setName = xform1 c_tf1_setname setNameTitle = xform2 c_tf1_setnametitle setTitle = xform1 c_tf1_settitle instance ITObject TF1 where draw = xform1 c_tf1_draw findObject = xform1 c_tf1_findobject getName = xform0 c_tf1_getname isA = xform0 c_tf1_isa paint = xform1 c_tf1_paint printObj = xform1 c_tf1_printobj saveAs = xform2 c_tf1_saveas write = xform3 c_tf1_write instance IDeletable TF1 where delete = xform0 c_tf1_delete instance ITF1 (Exist TF1) where derivative (ETF1 x) = derivative x derivative2 (ETF1 x) = derivative2 x derivative3 (ETF1 x) = derivative3 x drawCopyTF1 (ETF1 x) a1 = return . ETF1 =<< drawCopyTF1 x a1 drawDerivative (ETF1 x) = drawDerivative x drawIntegral (ETF1 x) = drawIntegral x drawF1 (ETF1 x) = drawF1 x fixParameter (ETF1 x) = fixParameter x getMaximumTF1 (ETF1 x) = getMaximumTF1 x getMinimumTF1 (ETF1 x) = getMinimumTF1 x getMaximumX (ETF1 x) = getMaximumX x getMinimumX (ETF1 x) = getMinimumX x getNDF (ETF1 x) = getNDF x getNpx (ETF1 x) = getNpx x getNumberFreeParameters (ETF1 x) = getNumberFreeParameters x getNumberFitPoints (ETF1 x) = getNumberFitPoints x getParError (ETF1 x) = getParError x getProb (ETF1 x) = getProb x getQuantilesTF1 (ETF1 x) = getQuantilesTF1 x getRandomTF1 (ETF1 x) = getRandomTF1 x getSave (ETF1 x) = getSave x getX (ETF1 x) = getX x getXmin (ETF1 x) = getXmin x getXmax (ETF1 x) = getXmax x gradientPar (ETF1 x) = gradientPar x initArgs (ETF1 x) = initArgs x integralTF1 (ETF1 x) = integralTF1 x integralError (ETF1 x) = integralError x integralFast (ETF1 x) = integralFast x isInside (ETF1 x) = isInside x releaseParameter (ETF1 x) = releaseParameter x setChisquare (ETF1 x) = setChisquare x setMaximumTF1 (ETF1 x) = setMaximumTF1 x setMinimumTF1 (ETF1 x) = setMinimumTF1 x setNDF (ETF1 x) = setNDF x setNumberFitPoints (ETF1 x) = setNumberFitPoints x setNpx (ETF1 x) = setNpx x setParError (ETF1 x) = setParError x setParErrors (ETF1 x) = setParErrors x setParLimits (ETF1 x) = setParLimits x setParent (ETF1 x) = setParent x setRange1 (ETF1 x) = setRange1 x setRange2 (ETF1 x) = setRange2 x setRange3 (ETF1 x) = setRange3 x setSavedPoint (ETF1 x) = setSavedPoint x moment (ETF1 x) = moment x centralMoment (ETF1 x) = centralMoment x mean (ETF1 x) = mean x variance (ETF1 x) = variance x instance ITFormula (Exist TF1) where compile (ETF1 x) = compile x clear (ETF1 x) = clear x definedValue (ETF1 x) = definedValue x eval (ETF1 x) = eval x evalParOld (ETF1 x) = evalParOld x evalPar (ETF1 x) = evalPar x getNdim (ETF1 x) = getNdim x getNpar (ETF1 x) = getNpar x getNumber (ETF1 x) = getNumber x getParNumber (ETF1 x) = getParNumber x isLinear (ETF1 x) = isLinear x isNormalized (ETF1 x) = isNormalized x setNumber (ETF1 x) = setNumber x setParameter (ETF1 x) = setParameter x setParameters (ETF1 x) = setParameters x setParName (ETF1 x) = setParName x setParNames (ETF1 x) = setParNames x update (ETF1 x) = update x instance ITAttLine (Exist TF1) where getLineColor (ETF1 x) = getLineColor x getLineStyle (ETF1 x) = getLineStyle x getLineWidth (ETF1 x) = getLineWidth x resetAttLine (ETF1 x) = resetAttLine x setLineAttributes (ETF1 x) = setLineAttributes x setLineColor (ETF1 x) = setLineColor x setLineStyle (ETF1 x) = setLineStyle x setLineWidth (ETF1 x) = setLineWidth x instance ITAttFill (Exist TF1) where setFillColor (ETF1 x) = setFillColor x setFillStyle (ETF1 x) = setFillStyle x instance ITAttMarker (Exist TF1) where getMarkerColor (ETF1 x) = getMarkerColor x getMarkerStyle (ETF1 x) = getMarkerStyle x getMarkerSize (ETF1 x) = getMarkerSize x resetAttMarker (ETF1 x) = resetAttMarker x setMarkerAttributes (ETF1 x) = setMarkerAttributes x setMarkerColor (ETF1 x) = setMarkerColor x setMarkerStyle (ETF1 x) = setMarkerStyle x setMarkerSize (ETF1 x) = setMarkerSize x instance ITNamed (Exist TF1) where setName (ETF1 x) = setName x setNameTitle (ETF1 x) = setNameTitle x setTitle (ETF1 x) = setTitle x instance ITObject (Exist TF1) where draw (ETF1 x) = draw x findObject (ETF1 x) = findObject x getName (ETF1 x) = getName x isA (ETF1 x) = isA x paint (ETF1 x) = paint x printObj (ETF1 x) = printObj x saveAs (ETF1 x) = saveAs x write (ETF1 x) = write x instance IDeletable (Exist TF1) where delete (ETF1 x) = delete x newTF1 :: CString -> CString -> CDouble -> CDouble -> IO TF1 newTF1 = xform3 c_tf1_newtf1 tF1GetChisquare :: TF1 -> IO CDouble tF1GetChisquare = xform0 c_tf1_tf1getchisquare tF1GetHistogram :: TF1 -> IO TH1 tF1GetHistogram = xform0 c_tf1_tf1gethistogram tF1GetParent :: TF1 -> IO TObject tF1GetParent = xform0 c_tf1_tf1getparent tF1GetXaxis :: TF1 -> IO TAxis tF1GetXaxis = xform0 c_tf1_tf1getxaxis tF1GetYaxis :: TF1 -> IO TAxis tF1GetYaxis = xform0 c_tf1_tf1getyaxis tF1GetZaxis :: TF1 -> IO TAxis tF1GetZaxis = xform0 c_tf1_tf1getzaxis tF1DerivativeError :: IO CDouble tF1DerivativeError = xformnull c_tf1_tf1derivativeerror tF1InitStandardFunctions :: IO () tF1InitStandardFunctions = xformnull c_tf1_tf1initstandardfunctions tF1GetCurrent :: IO TF1 tF1GetCurrent = xformnull c_tf1_tf1getcurrent tF1AbsValue :: CInt -> IO () tF1AbsValue = xform0 c_tf1_tf1absvalue tF1RejectPoint :: CInt -> IO () tF1RejectPoint = xform0 c_tf1_tf1rejectpoint tF1RejectedPoint :: IO CInt tF1RejectedPoint = xformnull c_tf1_tf1rejectedpoint tF1SetCurrent :: TF1 -> IO () tF1SetCurrent = xform0 c_tf1_tf1setcurrent tF1CalcGaussLegendreSamplingPoints :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CDouble -> IO () tF1CalcGaussLegendreSamplingPoints = xform3 c_tf1_tf1calcgausslegendresamplingpoints instance FPtr (Exist TF1) where type Raw (Exist TF1) = RawTF1 get_fptr (ETF1 obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETF1 (cast_fptr_to_obj (fptr :: ForeignPtr RawTF1) :: TF1)