module HROOT.Class.TAttMarker.Interface where
import Data.Word
import Foreign.ForeignPtr
import HROOT.TypeCast
import HROOT.Class.TAttMarker.RawType
import HROOT.Class.Deletable.Interface
class (IDeletable a) => ITAttMarker a where
getMarkerColor :: a -> IO Int
getMarkerStyle :: a -> IO Int
getMarkerSize :: a -> IO Double
resetAttMarker :: a -> String -> IO ()
setMarkerAttributes :: a -> IO ()
setMarkerColor :: a -> Int -> IO ()
setMarkerStyle :: a -> Int -> IO ()
setMarkerSize :: a -> Int -> IO ()
instance Existable TAttMarker where
data Exist TAttMarker = forall a. (FPtr a, ITAttMarker a) => ETAttMarker a
upcastTAttMarker :: (FPtr a, ITAttMarker a) => a -> TAttMarker
upcastTAttMarker h = let fh = get_fptr h
fh2 :: ForeignPtr RawTAttMarker = castForeignPtr fh
in cast_fptr_to_obj fh2