module HROOT.Class.TApplication.Implementation where
import HROOT.TypeCast
import HROOT.Class.TApplication.RawType
import HROOT.Class.TApplication.FFI
import HROOT.Class.TApplication.Interface
import HROOT.Class.TApplication.Cast
import HROOT.Class.TClass.RawType
import HROOT.Class.TClass.Cast
import HROOT.Class.TClass.Interface
import HROOT.Class.TObject.RawType
import HROOT.Class.TObject.Cast
import HROOT.Class.TObject.Interface
import HROOT.Class.TQObject.RawType
import HROOT.Class.TQObject.Cast
import HROOT.Class.TQObject.Interface
import HROOT.Class.Deletable.RawType
import HROOT.Class.Deletable.Cast
import HROOT.Class.Deletable.Interface
import Data.Word
import Foreign.ForeignPtr
import System.IO.Unsafe
instance ITApplication TApplication where
run = xform1 c_tapplication_run
instance ITObject TApplication where
draw = xform1 c_tapplication_draw
findObject = xform1 c_tapplication_findobject
getName = xform0 c_tapplication_getname
isA = xform0 c_tapplication_isa
isFolder = xform0 c_tapplication_isfolder
isEqual = xform1 c_tapplication_isequal
isSortable = xform0 c_tapplication_issortable
paint = xform1 c_tapplication_paint
printObj = xform1 c_tapplication_printobj
recursiveRemove = xform1 c_tapplication_recursiveremove
saveAs = xform2 c_tapplication_saveas
useCurrentStyle = xform0 c_tapplication_usecurrentstyle
write = xform3 c_tapplication_write
instance ITQObject TApplication where
instance IDeletable TApplication where
delete = xform0 c_tapplication_delete
instance ITApplication (Exist TApplication) where
run (ETApplication x) = run x
instance ITObject (Exist TApplication) where
draw (ETApplication x) = draw x
findObject (ETApplication x) = findObject x
getName (ETApplication x) = getName x
isA (ETApplication x) = isA x
isFolder (ETApplication x) = isFolder x
isEqual (ETApplication x) = isEqual x
isSortable (ETApplication x) = isSortable x
paint (ETApplication x) = paint x
printObj (ETApplication x) = printObj x
recursiveRemove (ETApplication x) = recursiveRemove x
saveAs (ETApplication x) = saveAs x
useCurrentStyle (ETApplication x) = useCurrentStyle x
write (ETApplication x) = write x
instance ITQObject (Exist TApplication) where
instance IDeletable (Exist TApplication) where
delete (ETApplication x) = delete x
newTApplication :: String -> [Int] -> [String] -> IO TApplication
newTApplication = xform2 c_tapplication_newtapplication
instance FPtr (Exist TApplication) where
type Raw (Exist TApplication) = RawTApplication
get_fptr (ETApplication obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETApplication (cast_fptr_to_obj (fptr :: ForeignPtr RawTApplication) :: TApplication)