{-# LANGUAGE EmptyDataDecls, ExistentialQuantification, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeSynonymInstances #-} module HROOT.Core.TAttMarker.Interface where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import FFICXX.Runtime.Cast import HROOT.Core.TAttMarker.RawType import STD.Deletable.Interface class (IDeletable a) => ITAttMarker a where getMarkerColor :: () => a -> IO CShort getMarkerStyle :: () => a -> IO CShort getMarkerSize :: () => a -> IO CFloat resetAttMarker :: (Castable c0 CString) => a -> c0 -> IO () setMarkerAttributes :: () => a -> IO () setMarkerColor :: () => a -> CShort -> IO () setMarkerStyle :: () => a -> CShort -> IO () setMarkerSize :: () => a -> CShort -> 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