{-# LANGUAGE EmptyDataDecls, ExistentialQuantification, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeSynonymInstances #-} module HROOT.Core.TAttAxis.Interface where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import FFICXX.Runtime.Cast import HROOT.Core.TAttAxis.RawType import STD.Deletable.Interface class (IDeletable a) => ITAttAxis a where getNdivisions :: () => a -> IO CInt getAxisColor :: () => a -> IO CShort getLabelColor :: () => a -> IO CShort getLabelFont :: () => a -> IO CShort getLabelOffset :: () => a -> IO CFloat getLabelSize :: () => a -> IO CFloat getTitleOffset :: () => a -> IO CFloat getTitleSize :: () => a -> IO CFloat getTickLength :: () => a -> IO CFloat getTitleFont :: () => a -> IO CShort setNdivisions :: () => a -> CInt -> CBool -> IO () setAxisColor :: () => a -> CShort -> IO () setLabelColor :: () => a -> CShort -> IO () setLabelFont :: () => a -> CShort -> IO () setLabelOffset :: () => a -> CFloat -> IO () setLabelSize :: () => a -> CFloat -> IO () setTickLength :: () => a -> CFloat -> IO () setTitleOffset :: () => a -> CFloat -> IO () setTitleSize :: () => a -> CFloat -> IO () setTitleColor :: () => a -> CShort -> IO () setTitleFont :: () => a -> CShort -> IO () upcastTAttAxis :: forall a . (FPtr a, ITAttAxis a) => a -> TAttAxis upcastTAttAxis h = let fh = get_fptr h fh2 :: Ptr RawTAttAxis = castPtr fh in cast_fptr_to_obj fh2 downcastTAttAxis :: forall a . (FPtr a, ITAttAxis a) => TAttAxis -> a downcastTAttAxis h = let fh = get_fptr h fh2 = castPtr fh in cast_fptr_to_obj fh2