{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, ExistentialQuantification, ScopedTypeVariables #-} -- module HROOT.Class.Interface where module HROOT.Hist.TAxis.Interface where import Data.Word import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import FFICXX.Runtime.Cast import HROOT.Hist.TAxis.RawType import HROOT.Core.TNamed.Interface import HROOT.Core.TAttAxis.Interface ---- ============ ---- class (ITNamed a,ITAttAxis a) => ITAxis a where findBinTAxis :: a -> CDouble -> IO CInt findFixBinTAxis :: a -> CDouble -> IO CInt getBinCenterTAxis :: a -> CInt -> IO CDouble getBinCenterLog :: a -> CInt -> IO CDouble getBinUpEdge :: a -> CInt -> IO CDouble setTimeDisplay :: a -> CInt -> IO () setTimeFormat :: a -> CString -> IO () setTimeOffset :: a -> CDouble -> CString -> IO () instance Existable TAxis where data Exist TAxis = forall a. (FPtr a, ITAxis a) => ETAxis a upcastTAxis :: (FPtr a, ITAxis a) => a -> TAxis upcastTAxis h = let fh = get_fptr h fh2 :: ForeignPtr RawTAxis = castForeignPtr fh in cast_fptr_to_obj fh2 downcastTAxis :: (FPtr a, ITAxis a) => TAxis -> a downcastTAxis h = let fh = get_fptr h fh2 = castForeignPtr fh in cast_fptr_to_obj fh2