{-# LANGUAGE EmptyDataDecls, ExistentialQuantification, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeSynonymInstances #-} module HROOT.Core.TAttMarker.Interface where import Data.Word import Foreign.C import Foreign.Ptr import FFICXX.Runtime.Cast import HROOT.Core.TAttMarker.RawType import HROOT.Core.Deletable.Interface class IDeletable a => ITAttMarker a where getMarkerColor :: a -> IO CInt getMarkerStyle :: a -> IO CInt getMarkerSize :: a -> IO CDouble resetAttMarker :: Castable c0 CString => a -> c0 -> IO () setMarkerAttributes :: a -> IO () setMarkerColor :: a -> CInt -> IO () setMarkerStyle :: a -> CInt -> IO () setMarkerSize :: a -> CInt -> IO () upcastTAttMarker :: forall a . (FPtr a, ITAttMarker a) => a -> TAttMarker upcastTAttMarker h = let fh = get_fptr h fh2 :: Ptr RawTAttMarker = castPtr fh in cast_fptr_to_obj fh2 downcastTAttMarker :: forall a . (FPtr a, ITAttMarker a) => TAttMarker -> a downcastTAttMarker h = let fh = get_fptr h fh2 = castPtr fh in cast_fptr_to_obj fh2