{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module HROOT.IO.TFile.Implementation where import Data.Monoid import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import Language.Haskell.TH import Language.Haskell.TH.Syntax import System.IO.Unsafe import FFICXX.Runtime.Cast import FFICXX.Runtime.CodeGen.Cxx import FFICXX.Runtime.TH import HROOT.IO.TFile.RawType import HROOT.IO.TFile.FFI import HROOT.IO.TFile.Interface import HROOT.IO.TFile.Cast import HROOT.IO.TFile.RawType import HROOT.IO.TFile.Cast import HROOT.IO.TFile.Interface 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.IO.TDirectoryFile.RawType import HROOT.IO.TDirectoryFile.Cast import HROOT.IO.TDirectoryFile.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 STD.Deletable.RawType import STD.Deletable.Cast import STD.Deletable.Interface instance () => ITFile (TFile) where instance () => ITDirectoryFile (TFile) where instance () => ITDirectory (TFile) where append = xform2 c_tfile_append addD = xform2 c_tfile_addd appendKey = xform1 c_tfile_appendkey close = xform1 c_tfile_close get = xform1 c_tfile_get cd_TDirectory = xform1 c_tfile_cd_tdirectory instance () => ITNamed (TFile) where setName = xform1 c_tfile_setname setNameTitle = xform2 c_tfile_setnametitle setTitle = xform1 c_tfile_settitle instance () => ITObject (TFile) where clear = xform1 c_tfile_clear draw = xform1 c_tfile_draw findObject = xform1 c_tfile_findobject getName = xform0 c_tfile_getname isA = xform0 c_tfile_isa paint = xform1 c_tfile_paint printObj = xform1 c_tfile_printobj saveAs = xform2 c_tfile_saveas write = xform3 c_tfile_write write_ = xform0 c_tfile_write_ instance () => IDeletable (TFile) where delete = xform0 c_tfile_delete newTFile :: (Castable c2 CString, Castable c1 CString, Castable c0 CString) => c0 -> c1 -> c2 -> CInt -> IO TFile newTFile = xform3 c_tfile_newtfile