{-# LINE 1 "src/HROOT/Graf/TGraphQQ/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "src/HROOT/Graf/TGraphQQ/FFI.hsc" #-}

-- module HROOT.Class.FFI where

module HROOT.Graf.TGraphQQ.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Graf.TGraphQQ.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


{-# LINE 23 "src/HROOT/Graf/TGraphQQ/FFI.hsc" #-}

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_Apply" c_tgraphqq_apply 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_Chisquare" c_tgraphqq_chisquare 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTF1) -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_DrawGraph" c_tgraphqq_drawgraph 
  :: (Ptr RawTGraphQQ) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_drawPanelTGraph" c_tgraphqq_drawpaneltgraph 
  :: (Ptr RawTGraphQQ) -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_Expand" c_tgraphqq_expand 
  :: (Ptr RawTGraphQQ) -> CInt -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_FitPanelTGraph" c_tgraphqq_fitpaneltgraph 
  :: (Ptr RawTGraphQQ) -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_getCorrelationFactorTGraph" c_tgraphqq_getcorrelationfactortgraph 
  :: (Ptr RawTGraphQQ) -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_getCovarianceTGraph" c_tgraphqq_getcovariancetgraph 
  :: (Ptr RawTGraphQQ) -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_getMeanTGraph" c_tgraphqq_getmeantgraph 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_getRMSTGraph" c_tgraphqq_getrmstgraph 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetErrorX" c_tgraphqq_geterrorx 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetErrorY" c_tgraphqq_geterrory 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetErrorXhigh" c_tgraphqq_geterrorxhigh 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetErrorXlow" c_tgraphqq_geterrorxlow 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetErrorYhigh" c_tgraphqq_geterroryhigh 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetErrorYlow" c_tgraphqq_geterrorylow 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_InitExpo" c_tgraphqq_initexpo 
  :: (Ptr RawTGraphQQ) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_InitGaus" c_tgraphqq_initgaus 
  :: (Ptr RawTGraphQQ) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_InitPolynom" c_tgraphqq_initpolynom 
  :: (Ptr RawTGraphQQ) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_InsertPoint" c_tgraphqq_insertpoint 
  :: (Ptr RawTGraphQQ) -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_integralTGraph" c_tgraphqq_integraltgraph 
  :: (Ptr RawTGraphQQ) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_IsEditable" c_tgraphqq_iseditable 
  :: (Ptr RawTGraphQQ) -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_isInsideTGraph" c_tgraphqq_isinsidetgraph 
  :: (Ptr RawTGraphQQ) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_LeastSquareFit" c_tgraphqq_leastsquarefit 
  :: (Ptr RawTGraphQQ) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_PaintStats" c_tgraphqq_paintstats 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_RemovePoint" c_tgraphqq_removepoint 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetEditable" c_tgraphqq_seteditable 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetHistogram" c_tgraphqq_sethistogram 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTH1F) -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_setMaximumTGraph" c_tgraphqq_setmaximumtgraph 
  :: (Ptr RawTGraphQQ) -> CDouble -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_setMinimumTGraph" c_tgraphqq_setminimumtgraph 
  :: (Ptr RawTGraphQQ) -> CDouble -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_Set" c_tgraphqq_set 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetPoint" c_tgraphqq_setpoint 
  :: (Ptr RawTGraphQQ) -> CInt -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetName" c_tgraphqq_setname 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetNameTitle" c_tgraphqq_setnametitle 
  :: (Ptr RawTGraphQQ) -> CString -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetTitle" c_tgraphqq_settitle 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetLineColor" c_tgraphqq_getlinecolor 
  :: (Ptr RawTGraphQQ) -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetLineStyle" c_tgraphqq_getlinestyle 
  :: (Ptr RawTGraphQQ) -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetLineWidth" c_tgraphqq_getlinewidth 
  :: (Ptr RawTGraphQQ) -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_ResetAttLine" c_tgraphqq_resetattline 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetLineAttributes" c_tgraphqq_setlineattributes 
  :: (Ptr RawTGraphQQ) -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetLineColor" c_tgraphqq_setlinecolor 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetLineStyle" c_tgraphqq_setlinestyle 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetLineWidth" c_tgraphqq_setlinewidth 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetFillColor" c_tgraphqq_setfillcolor 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetFillStyle" c_tgraphqq_setfillstyle 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetMarkerColor" c_tgraphqq_getmarkercolor 
  :: (Ptr RawTGraphQQ) -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetMarkerStyle" c_tgraphqq_getmarkerstyle 
  :: (Ptr RawTGraphQQ) -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetMarkerSize" c_tgraphqq_getmarkersize 
  :: (Ptr RawTGraphQQ) -> IO CDouble

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_ResetAttMarker" c_tgraphqq_resetattmarker 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetMarkerAttributes" c_tgraphqq_setmarkerattributes 
  :: (Ptr RawTGraphQQ) -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetMarkerColor" c_tgraphqq_setmarkercolor 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetMarkerStyle" c_tgraphqq_setmarkerstyle 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SetMarkerSize" c_tgraphqq_setmarkersize 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_Draw" c_tgraphqq_draw 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_FindObject" c_tgraphqq_findobject 
  :: (Ptr RawTGraphQQ) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_GetName" c_tgraphqq_getname 
  :: (Ptr RawTGraphQQ) -> IO CString

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_IsA" c_tgraphqq_isa 
  :: (Ptr RawTGraphQQ) -> IO (Ptr RawTClass)

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_Paint" c_tgraphqq_paint 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_printObj" c_tgraphqq_printobj 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_SaveAs" c_tgraphqq_saveas 
  :: (Ptr RawTGraphQQ) -> CString -> CString -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_Write" c_tgraphqq_write 
  :: (Ptr RawTGraphQQ) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_delete" c_tgraphqq_delete 
  :: (Ptr RawTGraphQQ) -> IO ()

foreign import ccall "HROOTGrafTGraphQQ.h TGraphQQ_newTGraphQQ" c_tgraphqq_newtgraphqq 
  :: CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO (Ptr RawTGraphQQ)