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

-- module HROOT.Class.FFI where

module HROOT.Core.TAttMarker.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Core.TAttMarker.RawType



{-# LINE 19 "src/HROOT/Core/TAttMarker/FFI.hsc" #-}

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

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

foreign import ccall "HROOTCoreTAttMarker.h TAttMarker_GetMarkerColor" c_tattmarker_getmarkercolor 
  :: (Ptr RawTAttMarker) -> IO CInt

foreign import ccall "HROOTCoreTAttMarker.h TAttMarker_GetMarkerStyle" c_tattmarker_getmarkerstyle 
  :: (Ptr RawTAttMarker) -> IO CInt

foreign import ccall "HROOTCoreTAttMarker.h TAttMarker_GetMarkerSize" c_tattmarker_getmarkersize 
  :: (Ptr RawTAttMarker) -> IO CDouble

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

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

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

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

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