{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TypeFamilies, TypeSynonymInstances #-} module HROOT.Core.TROOT.Implementation where import FFICXX.Runtime.Cast import Data.Word import Foreign.C import Foreign.Ptr import System.IO.Unsafe import HROOT.Core.TROOT.RawType import HROOT.Core.TROOT.FFI import HROOT.Core.TROOT.Interface import HROOT.Core.TROOT.Cast import HROOT.Core.TKey.RawType import HROOT.Core.TKey.Cast import HROOT.Core.TKey.Interface import HROOT.Core.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Core.TGlobal.RawType import HROOT.Core.TGlobal.Cast import HROOT.Core.TGlobal.Interface import HROOT.Core.TDirectory.RawType import HROOT.Core.TDirectory.Cast import HROOT.Core.TDirectory.Interface import HROOT.Core.TNamed.RawType import HROOT.Core.TNamed.Cast import HROOT.Core.TNamed.Interface import HROOT.Core.TObject.RawType import HROOT.Core.TObject.Cast import HROOT.Core.TObject.Interface import HROOT.Core.Deletable.RawType import HROOT.Core.Deletable.Cast import HROOT.Core.Deletable.Interface instance ITROOT TROOT instance ITDirectory TROOT where append = xform2 c_troot_append addD = xform2 c_troot_addd appendKey = xform1 c_troot_appendkey close = xform1 c_troot_close get = xform1 c_troot_get cd_TDirectory = xform1 c_troot_cd_tdirectory instance ITNamed TROOT where setName = xform1 c_troot_setname setNameTitle = xform2 c_troot_setnametitle setTitle = xform1 c_troot_settitle instance ITObject TROOT where draw = xform1 c_troot_draw findObject = xform1 c_troot_findobject getName = xform0 c_troot_getname isA = xform0 c_troot_isa paint = xform1 c_troot_paint printObj = xform1 c_troot_printobj saveAs = xform2 c_troot_saveas write = xform3 c_troot_write instance IDeletable TROOT where delete = xform0 c_troot_delete tROOTGetGlobal :: Castable c0 CString => TROOT -> c0 -> CInt -> IO TGlobal tROOTGetGlobal = xform2 c_troot_trootgetglobal tROOTInitialized :: IO CInt tROOTInitialized = xformnull c_troot_trootinitialized