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

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_delete" c_tattmarker_delete ::
               Ptr RawTAttMarker -> IO ()

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_newTAttMarker"
               c_tattmarker_newtattmarker ::
               CShort -> CShort -> CShort -> IO (Ptr RawTAttMarker)

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_GetMarkerColor"
               c_tattmarker_getmarkercolor :: Ptr RawTAttMarker -> IO CShort

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_GetMarkerStyle"
               c_tattmarker_getmarkerstyle :: Ptr RawTAttMarker -> IO CShort

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_GetMarkerSize"
               c_tattmarker_getmarkersize :: Ptr RawTAttMarker -> IO CFloat

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_ResetAttMarker"
               c_tattmarker_resetattmarker ::
               Ptr RawTAttMarker -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_SetMarkerAttributes"
               c_tattmarker_setmarkerattributes :: Ptr RawTAttMarker -> IO ()

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_SetMarkerColor"
               c_tattmarker_setmarkercolor :: Ptr RawTAttMarker -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_SetMarkerStyle"
               c_tattmarker_setmarkerstyle :: Ptr RawTAttMarker -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTCoreTAttMarker.h TAttMarker_SetMarkerSize"
               c_tattmarker_setmarkersize :: Ptr RawTAttMarker -> CShort -> IO ()