{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-} module HROOT.Hist.TGraphBentErrors.FFI where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import HROOT.Hist.TGraphBentErrors.RawType import HROOT.Hist.TGraphBentErrors.RawType import HROOT.Hist.TF1.RawType import HROOT.Hist.TH1F.RawType import HROOT.Hist.TAxis.RawType import HROOT.Core.TObject.RawType import HROOT.Core.TClass.RawType foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Apply" c_tgraphbenterrors_apply :: Ptr RawTGraphBentErrors -> Ptr RawTF1 -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Chisquare" c_tgraphbenterrors_chisquare :: Ptr RawTGraphBentErrors -> Ptr RawTF1 -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_DrawGraph" c_tgraphbenterrors_drawgraph :: Ptr RawTGraphBentErrors -> CInt -> Ptr CDouble -> Ptr CDouble -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_drawPanelTGraph" c_tgraphbenterrors_drawpaneltgraph :: Ptr RawTGraphBentErrors -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Expand" c_tgraphbenterrors_expand :: Ptr RawTGraphBentErrors -> CInt -> CInt -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_FitPanelTGraph" c_tgraphbenterrors_fitpaneltgraph :: Ptr RawTGraphBentErrors -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_getCorrelationFactorTGraph" c_tgraphbenterrors_getcorrelationfactortgraph :: Ptr RawTGraphBentErrors -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_getCovarianceTGraph" c_tgraphbenterrors_getcovariancetgraph :: Ptr RawTGraphBentErrors -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_getMeanTGraph" c_tgraphbenterrors_getmeantgraph :: Ptr RawTGraphBentErrors -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_getRMSTGraph" c_tgraphbenterrors_getrmstgraph :: Ptr RawTGraphBentErrors -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetErrorX" c_tgraphbenterrors_geterrorx :: Ptr RawTGraphBentErrors -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetErrorY" c_tgraphbenterrors_geterrory :: Ptr RawTGraphBentErrors -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetErrorXhigh" c_tgraphbenterrors_geterrorxhigh :: Ptr RawTGraphBentErrors -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetErrorXlow" c_tgraphbenterrors_geterrorxlow :: Ptr RawTGraphBentErrors -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetErrorYhigh" c_tgraphbenterrors_geterroryhigh :: Ptr RawTGraphBentErrors -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetErrorYlow" c_tgraphbenterrors_geterrorylow :: Ptr RawTGraphBentErrors -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_InitExpo" c_tgraphbenterrors_initexpo :: Ptr RawTGraphBentErrors -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_InitGaus" c_tgraphbenterrors_initgaus :: Ptr RawTGraphBentErrors -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_InitPolynom" c_tgraphbenterrors_initpolynom :: Ptr RawTGraphBentErrors -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_InsertPoint" c_tgraphbenterrors_insertpoint :: Ptr RawTGraphBentErrors -> IO CInt foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_integralTGraph" c_tgraphbenterrors_integraltgraph :: Ptr RawTGraphBentErrors -> CInt -> CInt -> IO CDouble foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_IsEditable" c_tgraphbenterrors_iseditable :: Ptr RawTGraphBentErrors -> IO CBool foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_isInsideTGraph" c_tgraphbenterrors_isinsidetgraph :: Ptr RawTGraphBentErrors -> CDouble -> CDouble -> IO CInt foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_LeastSquareFit" c_tgraphbenterrors_leastsquarefit :: Ptr RawTGraphBentErrors -> CInt -> Ptr CDouble -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_PaintStats" c_tgraphbenterrors_paintstats :: Ptr RawTGraphBentErrors -> Ptr RawTF1 -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_RemovePoint" c_tgraphbenterrors_removepoint :: Ptr RawTGraphBentErrors -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetEditable" c_tgraphbenterrors_seteditable :: Ptr RawTGraphBentErrors -> CBool -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetHistogram" c_tgraphbenterrors_sethistogram :: Ptr RawTGraphBentErrors -> Ptr RawTH1F -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_setMaximumTGraph" c_tgraphbenterrors_setmaximumtgraph :: Ptr RawTGraphBentErrors -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_setMinimumTGraph" c_tgraphbenterrors_setminimumtgraph :: Ptr RawTGraphBentErrors -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Set" c_tgraphbenterrors_set :: Ptr RawTGraphBentErrors -> CInt -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetPoint" c_tgraphbenterrors_setpoint :: Ptr RawTGraphBentErrors -> CInt -> CDouble -> CDouble -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetName" c_tgraphbenterrors_setname :: Ptr RawTGraphBentErrors -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetNameTitle" c_tgraphbenterrors_setnametitle :: Ptr RawTGraphBentErrors -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetTitle" c_tgraphbenterrors_settitle :: Ptr RawTGraphBentErrors -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetLineColor" c_tgraphbenterrors_getlinecolor :: Ptr RawTGraphBentErrors -> IO CShort foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetLineStyle" c_tgraphbenterrors_getlinestyle :: Ptr RawTGraphBentErrors -> IO CShort foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetLineWidth" c_tgraphbenterrors_getlinewidth :: Ptr RawTGraphBentErrors -> IO CShort foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_ResetAttLine" c_tgraphbenterrors_resetattline :: Ptr RawTGraphBentErrors -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetLineAttributes" c_tgraphbenterrors_setlineattributes :: Ptr RawTGraphBentErrors -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetLineColor" c_tgraphbenterrors_setlinecolor :: Ptr RawTGraphBentErrors -> CShort -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetLineStyle" c_tgraphbenterrors_setlinestyle :: Ptr RawTGraphBentErrors -> CShort -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetLineWidth" c_tgraphbenterrors_setlinewidth :: Ptr RawTGraphBentErrors -> CShort -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetFillColor" c_tgraphbenterrors_setfillcolor :: Ptr RawTGraphBentErrors -> CInt -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetFillStyle" c_tgraphbenterrors_setfillstyle :: Ptr RawTGraphBentErrors -> CInt -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetMarkerColor" c_tgraphbenterrors_getmarkercolor :: Ptr RawTGraphBentErrors -> IO CShort foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetMarkerStyle" c_tgraphbenterrors_getmarkerstyle :: Ptr RawTGraphBentErrors -> IO CShort foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetMarkerSize" c_tgraphbenterrors_getmarkersize :: Ptr RawTGraphBentErrors -> IO CFloat foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_ResetAttMarker" c_tgraphbenterrors_resetattmarker :: Ptr RawTGraphBentErrors -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetMarkerAttributes" c_tgraphbenterrors_setmarkerattributes :: Ptr RawTGraphBentErrors -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetMarkerColor" c_tgraphbenterrors_setmarkercolor :: Ptr RawTGraphBentErrors -> CShort -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetMarkerStyle" c_tgraphbenterrors_setmarkerstyle :: Ptr RawTGraphBentErrors -> CShort -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SetMarkerSize" c_tgraphbenterrors_setmarkersize :: Ptr RawTGraphBentErrors -> CShort -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Clear" c_tgraphbenterrors_clear :: Ptr RawTGraphBentErrors -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Draw" c_tgraphbenterrors_draw :: Ptr RawTGraphBentErrors -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_FindObject" c_tgraphbenterrors_findobject :: Ptr RawTGraphBentErrors -> CString -> IO (Ptr RawTObject) foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_GetName" c_tgraphbenterrors_getname :: Ptr RawTGraphBentErrors -> IO CString foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_IsA" c_tgraphbenterrors_isa :: Ptr RawTGraphBentErrors -> IO (Ptr RawTClass) foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Paint" c_tgraphbenterrors_paint :: Ptr RawTGraphBentErrors -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_printObj" c_tgraphbenterrors_printobj :: Ptr RawTGraphBentErrors -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_SaveAs" c_tgraphbenterrors_saveas :: Ptr RawTGraphBentErrors -> CString -> CString -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Write" c_tgraphbenterrors_write :: Ptr RawTGraphBentErrors -> CString -> CInt -> CInt -> IO CInt foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_Write_" c_tgraphbenterrors_write_ :: Ptr RawTGraphBentErrors -> IO CInt foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_delete" c_tgraphbenterrors_delete :: Ptr RawTGraphBentErrors -> IO () foreign import ccall interruptible "HROOTHistTGraphBentErrors.h TGraphBentErrors_newTGraphBentErrors" c_tgraphbenterrors_newtgraphbenterrors :: CInt -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO (Ptr RawTGraphBentErrors)