{-# LANGUAGE EmptyDataDecls, ExistentialQuantification, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeSynonymInstances #-} module HROOT.Tree.TTree.Interface where import Data.Word import Foreign.C import Foreign.Ptr import FFICXX.Runtime.Cast import HROOT.Tree.TTree.RawType import HROOT.Tree.TBranch.RawType import HROOT.Core.TNamed.Interface import HROOT.Core.TAttLine.Interface import HROOT.Core.TAttFill.Interface import HROOT.Core.TAttMarker.Interface class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITTree a where branch :: Castable c0 CString => a -> c0 -> CInt -> CInt -> IO CInt branch1 :: (Castable c1 CString, Castable c0 CString) => a -> c0 -> (Ptr ()) -> c1 -> CInt -> IO TBranch fillTree :: a -> IO CInt upcastTTree :: forall a . (FPtr a, ITTree a) => a -> TTree upcastTTree h = let fh = get_fptr h fh2 :: Ptr RawTTree = castPtr fh in cast_fptr_to_obj fh2 downcastTTree :: forall a . (FPtr a, ITTree a) => TTree -> a downcastTTree h = let fh = get_fptr h fh2 = castPtr fh in cast_fptr_to_obj fh2