{-# LINE 1 "src/HROOT/Hist/TGraph2D/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-}
module HROOT.Hist.TGraph2D.FFI where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import HROOT.Hist.TGraph2D.RawType
import HROOT.Hist.TGraph2D.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType
import HROOT.Hist.TAxis.RawType

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetName" c_tgraph2d_setname ::
               Ptr RawTGraph2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetNameTitle" c_tgraph2d_setnametitle
               :: Ptr RawTGraph2D -> CString -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetTitle" c_tgraph2d_settitle ::
               Ptr RawTGraph2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_GetLineColor" c_tgraph2d_getlinecolor
               :: Ptr RawTGraph2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_GetLineStyle" c_tgraph2d_getlinestyle
               :: Ptr RawTGraph2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_GetLineWidth" c_tgraph2d_getlinewidth
               :: Ptr RawTGraph2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_ResetAttLine" c_tgraph2d_resetattline
               :: Ptr RawTGraph2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetLineAttributes"
               c_tgraph2d_setlineattributes :: Ptr RawTGraph2D -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetLineColor" c_tgraph2d_setlinecolor
               :: Ptr RawTGraph2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetLineStyle" c_tgraph2d_setlinestyle
               :: Ptr RawTGraph2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetLineWidth" c_tgraph2d_setlinewidth
               :: Ptr RawTGraph2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetFillColor" c_tgraph2d_setfillcolor
               :: Ptr RawTGraph2D -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetFillStyle" c_tgraph2d_setfillstyle
               :: Ptr RawTGraph2D -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_GetMarkerColor"
               c_tgraph2d_getmarkercolor :: Ptr RawTGraph2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_GetMarkerStyle"
               c_tgraph2d_getmarkerstyle :: Ptr RawTGraph2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_GetMarkerSize"
               c_tgraph2d_getmarkersize :: Ptr RawTGraph2D -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_ResetAttMarker"
               c_tgraph2d_resetattmarker :: Ptr RawTGraph2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetMarkerAttributes"
               c_tgraph2d_setmarkerattributes :: Ptr RawTGraph2D -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetMarkerColor"
               c_tgraph2d_setmarkercolor :: Ptr RawTGraph2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetMarkerStyle"
               c_tgraph2d_setmarkerstyle :: Ptr RawTGraph2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetMarkerSize"
               c_tgraph2d_setmarkersize :: Ptr RawTGraph2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_Clear" c_tgraph2d_clear ::
               Ptr RawTGraph2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_Draw" c_tgraph2d_draw ::
               Ptr RawTGraph2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_FindObject" c_tgraph2d_findobject ::
               Ptr RawTGraph2D -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_GetName" c_tgraph2d_getname ::
               Ptr RawTGraph2D -> IO CString

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_IsA" c_tgraph2d_isa ::
               Ptr RawTGraph2D -> IO (Ptr RawTClass)

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_Paint" c_tgraph2d_paint ::
               Ptr RawTGraph2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_printObj" c_tgraph2d_printobj ::
               Ptr RawTGraph2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SaveAs" c_tgraph2d_saveas ::
               Ptr RawTGraph2D -> CString -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_Write" c_tgraph2d_write ::
               Ptr RawTGraph2D -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_Write_" c_tgraph2d_write_ ::
               Ptr RawTGraph2D -> IO CInt

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_delete" c_tgraph2d_delete ::
               Ptr RawTGraph2D -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_newTGraph2D_" c_tgraph2d_newtgraph2d_
               :: IO (Ptr RawTGraph2D)

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_newTGraph2D" c_tgraph2d_newtgraph2d
               ::
               CInt ->
                 Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO (Ptr RawTGraph2D)

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_tGraph2D_GetXaxis"
               c_tgraph2d_tgraph2d_getxaxis ::
               Ptr RawTGraph2D -> IO (Ptr RawTAxis)

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_tGraph2D_GetYaxis"
               c_tgraph2d_tgraph2d_getyaxis ::
               Ptr RawTGraph2D -> IO (Ptr RawTAxis)

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_tGraph2D_GetZaxis"
               c_tgraph2d_tgraph2d_getzaxis ::
               Ptr RawTGraph2D -> IO (Ptr RawTAxis)

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetN" c_tgraph2d_setn ::
               Ptr RawTGraph2D -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_tGraph2D_SetMaximum"
               c_tgraph2d_tgraph2d_setmaximum ::
               Ptr RawTGraph2D -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_tGraph2D_SetMinimum"
               c_tgraph2d_tgraph2d_setminimum ::
               Ptr RawTGraph2D -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTGraph2D.h TGraph2D_SetPointXYZ" c_tgraph2d_setpointxyz
               ::
               Ptr RawTGraph2D -> CInt -> CDouble -> CDouble -> CDouble -> IO ()