{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, 
             FlexibleInstances, TypeSynonymInstances, 
             EmptyDataDecls, ExistentialQuantification, ScopedTypeVariables #-}

-- module HROOT.Class.Interface where

module HROOT.Class.TAttAxis.Interface where


import Data.Word
import Foreign.ForeignPtr
import HROOT.TypeCast

import HROOT.Class.TAttAxis.RawType

import HROOT.Class.Deletable.Interface


class (IDeletable a) => ITAttAxis a where

    getNdivisions :: a -> IO Int 

    getAxisColor :: a -> IO Int 

    getLabelColor :: a -> IO Int 

    getLabelFont :: a -> IO Int 

    getLabelOffset :: a -> IO Double 

    getLabelSize :: a -> IO Double 

    getTitleOffset :: a -> IO Double 

    getTitleSize :: a -> IO Double 

    getTickLength :: a -> IO Double 

    getTitleFont :: a -> IO Int 

    setNdivisions :: a -> Int -> Int -> IO () 

    setAxisColor :: a -> Int -> IO () 

    setLabelColor :: a -> Int -> IO () 

    setLabelFont :: a -> Int -> IO () 

    setLabelOffset :: a -> Double -> IO () 

    setLabelSize :: a -> Double -> IO () 

    setTickLength :: a -> Double -> IO () 

    setTitleOffset :: a -> Double -> IO () 

    setTitleSize :: a -> Double -> IO () 

    setTitleColor :: a -> Int -> IO () 

    setTitleFont :: a -> Int -> IO () 

instance Existable TAttAxis where
  data Exist TAttAxis = forall a. (FPtr a, ITAttAxis a) => ETAttAxis a

upcastTAttAxis :: (FPtr a, ITAttAxis a) => a -> TAttAxis
upcastTAttAxis h = let fh = get_fptr h
                       fh2 :: ForeignPtr RawTAttAxis = castForeignPtr fh
                   in cast_fptr_to_obj fh2