module HROOT.Class.Implementation where
import Foreign.Ptr
import Foreign.ForeignPtr
import System.IO.Unsafe
import HROOT.Class.Interface
import HROOT.Class.FFI
instance (ITObject a, FPtr a) => Castable a (Ptr RawTObject) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITNamed a, FPtr a) => Castable a (Ptr RawTNamed) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITClass a, FPtr a) => Castable a (Ptr RawTClass) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITFormula a, FPtr a) => Castable a (Ptr RawTFormula) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAtt3D a, FPtr a) => Castable a (Ptr RawTAtt3D) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttAxis a, FPtr a) => Castable a (Ptr RawTAttAxis) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttBBox a, FPtr a) => Castable a (Ptr RawTAttBBox) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttCanvas a, FPtr a) => Castable a (Ptr RawTAttCanvas) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttFill a, FPtr a) => Castable a (Ptr RawTAttFill) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttImage a, FPtr a) => Castable a (Ptr RawTAttImage) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttLine a, FPtr a) => Castable a (Ptr RawTAttLine) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttMarker a, FPtr a) => Castable a (Ptr RawTAttMarker) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttPad a, FPtr a) => Castable a (Ptr RawTAttPad) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttParticle a, FPtr a) => Castable a (Ptr RawTAttParticle) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAttText a, FPtr a) => Castable a (Ptr RawTAttText) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITHStack a, FPtr a) => Castable a (Ptr RawTHStack) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITF1 a, FPtr a) => Castable a (Ptr RawTF1) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITGraph a, FPtr a) => Castable a (Ptr RawTGraph) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITGraphAsymmErrors a, FPtr a) => Castable a (Ptr RawTGraphAsymmErrors) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITCutG a, FPtr a) => Castable a (Ptr RawTCutG) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITGraphBentErrors a, FPtr a) => Castable a (Ptr RawTGraphBentErrors) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITGraphErrors a, FPtr a) => Castable a (Ptr RawTGraphErrors) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITGraphPolar a, FPtr a) => Castable a (Ptr RawTGraphPolar) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITGraphQQ a, FPtr a) => Castable a (Ptr RawTGraphQQ) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITEllipse a, FPtr a) => Castable a (Ptr RawTEllipse) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArc a, FPtr a) => Castable a (Ptr RawTArc) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITCrown a, FPtr a) => Castable a (Ptr RawTCrown) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITLine a, FPtr a) => Castable a (Ptr RawTLine) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArrow a, FPtr a) => Castable a (Ptr RawTArrow) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITGaxis a, FPtr a) => Castable a (Ptr RawTGaxis) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITShape a, FPtr a) => Castable a (Ptr RawTShape) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITBRIK a, FPtr a) => Castable a (Ptr RawTBRIK) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITTUBE a, FPtr a) => Castable a (Ptr RawTTUBE) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPCON a, FPtr a) => Castable a (Ptr RawTPCON) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITSPHE a, FPtr a) => Castable a (Ptr RawTSPHE) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITXTRU a, FPtr a) => Castable a (Ptr RawTXTRU) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITBox a, FPtr a) => Castable a (Ptr RawTBox) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPave a, FPtr a) => Castable a (Ptr RawTPave) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPaveText a, FPtr a) => Castable a (Ptr RawTPaveText) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITDiamond a, FPtr a) => Castable a (Ptr RawTDiamond) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPaveStats a, FPtr a) => Castable a (Ptr RawTPaveStats) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPavesText a, FPtr a) => Castable a (Ptr RawTPavesText) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITLegend a, FPtr a) => Castable a (Ptr RawTLegend) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPaveLabel a, FPtr a) => Castable a (Ptr RawTPaveLabel) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPaveClass a, FPtr a) => Castable a (Ptr RawTPaveClass) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITWbox a, FPtr a) => Castable a (Ptr RawTWbox) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITFrame a, FPtr a) => Castable a (Ptr RawTFrame) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITSliderBox a, FPtr a) => Castable a (Ptr RawTSliderBox) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITTree a, FPtr a) => Castable a (Ptr RawTTree) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITChain a, FPtr a) => Castable a (Ptr RawTChain) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITNtuple a, FPtr a) => Castable a (Ptr RawTNtuple) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITNtupleD a, FPtr a) => Castable a (Ptr RawTNtupleD) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITTreeSQL a, FPtr a) => Castable a (Ptr RawTTreeSQL) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPolyLine a, FPtr a) => Castable a (Ptr RawTPolyLine) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITCurlyLine a, FPtr a) => Castable a (Ptr RawTCurlyLine) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITCurlyArc a, FPtr a) => Castable a (Ptr RawTCurlyArc) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITEfficiency a, FPtr a) => Castable a (Ptr RawTEfficiency) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITAxis a, FPtr a) => Castable a (Ptr RawTAxis) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITLatex a, FPtr a) => Castable a (Ptr RawTLatex) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITText a, FPtr a) => Castable a (Ptr RawTText) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITDirectory a, FPtr a) => Castable a (Ptr RawTDirectory) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITDirectoryFile a, FPtr a) => Castable a (Ptr RawTDirectoryFile) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITFile a, FPtr a) => Castable a (Ptr RawTFile) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITBranch a, FPtr a) => Castable a (Ptr RawTBranch) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITVirtualTreePlayer a, FPtr a) => Castable a (Ptr RawTVirtualTreePlayer) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITTreePlayer a, FPtr a) => Castable a (Ptr RawTTreePlayer) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArray a, FPtr a) => Castable a (Ptr RawTArray) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArrayC a, FPtr a) => Castable a (Ptr RawTArrayC) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArrayD a, FPtr a) => Castable a (Ptr RawTArrayD) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArrayF a, FPtr a) => Castable a (Ptr RawTArrayF) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArrayI a, FPtr a) => Castable a (Ptr RawTArrayI) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArrayL a, FPtr a) => Castable a (Ptr RawTArrayL) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArrayL64 a, FPtr a) => Castable a (Ptr RawTArrayL64) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITArrayS a, FPtr a) => Castable a (Ptr RawTArrayS) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH1 a, FPtr a) => Castable a (Ptr RawTH1) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH2 a, FPtr a) => Castable a (Ptr RawTH2) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH3 a, FPtr a) => Castable a (Ptr RawTH3) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH1C a, FPtr a) => Castable a (Ptr RawTH1C) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH1D a, FPtr a) => Castable a (Ptr RawTH1D) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH1F a, FPtr a) => Castable a (Ptr RawTH1F) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH1I a, FPtr a) => Castable a (Ptr RawTH1I) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH1S a, FPtr a) => Castable a (Ptr RawTH1S) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH2C a, FPtr a) => Castable a (Ptr RawTH2C) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH2D a, FPtr a) => Castable a (Ptr RawTH2D) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH2F a, FPtr a) => Castable a (Ptr RawTH2F) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH2I a, FPtr a) => Castable a (Ptr RawTH2I) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH2Poly a, FPtr a) => Castable a (Ptr RawTH2Poly) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH2S a, FPtr a) => Castable a (Ptr RawTH2S) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH3C a, FPtr a) => Castable a (Ptr RawTH3C) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH3D a, FPtr a) => Castable a (Ptr RawTH3D) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH3F a, FPtr a) => Castable a (Ptr RawTH3F) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH3I a, FPtr a) => Castable a (Ptr RawTH3I) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITH3S a, FPtr a) => Castable a (Ptr RawTH3S) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITQObject a, FPtr a) => Castable a (Ptr RawTQObject) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITVirtualPad a, FPtr a) => Castable a (Ptr RawTVirtualPad) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITPad a, FPtr a) => Castable a (Ptr RawTPad) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITButton a, FPtr a) => Castable a (Ptr RawTButton) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITGroupButton a, FPtr a) => Castable a (Ptr RawTGroupButton) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITCanvas a, FPtr a) => Castable a (Ptr RawTCanvas) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITDialogCanvas a, FPtr a) => Castable a (Ptr RawTDialogCanvas) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITInspectCanvas a, FPtr a) => Castable a (Ptr RawTInspectCanvas) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITEvePad a, FPtr a) => Castable a (Ptr RawTEvePad) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITSlider a, FPtr a) => Castable a (Ptr RawTSlider) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITApplication a, FPtr a) => Castable a (Ptr RawTApplication) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITRint a, FPtr a) => Castable a (Ptr RawTRint) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance (ITRandom a, FPtr a) => Castable a (Ptr RawTRandom) where
cast = unsafeForeignPtrToPtr . castForeignPtr . get_fptr
uncast = cast_fptr_to_obj . castForeignPtr . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TObject) where
type Raw (Exist TObject) = RawTObject
get_fptr (ETObject obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETObject (cast_fptr_to_obj (fptr :: ForeignPtr RawTObject) :: TObject)
instance Castable (Exist TObject) (Ptr RawTObject) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TNamed) where
type Raw (Exist TNamed) = RawTNamed
get_fptr (ETNamed obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETNamed (cast_fptr_to_obj (fptr :: ForeignPtr RawTNamed) :: TNamed)
instance Castable (Exist TNamed) (Ptr RawTNamed) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TClass) where
type Raw (Exist TClass) = RawTClass
get_fptr (ETClass obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETClass (cast_fptr_to_obj (fptr :: ForeignPtr RawTClass) :: TClass)
instance Castable (Exist TClass) (Ptr RawTClass) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TFormula) where
type Raw (Exist TFormula) = RawTFormula
get_fptr (ETFormula obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETFormula (cast_fptr_to_obj (fptr :: ForeignPtr RawTFormula) :: TFormula)
instance Castable (Exist TFormula) (Ptr RawTFormula) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAtt3D) where
type Raw (Exist TAtt3D) = RawTAtt3D
get_fptr (ETAtt3D obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAtt3D (cast_fptr_to_obj (fptr :: ForeignPtr RawTAtt3D) :: TAtt3D)
instance Castable (Exist TAtt3D) (Ptr RawTAtt3D) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttAxis) where
type Raw (Exist TAttAxis) = RawTAttAxis
get_fptr (ETAttAxis obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttAxis (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttAxis) :: TAttAxis)
instance Castable (Exist TAttAxis) (Ptr RawTAttAxis) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttBBox) where
type Raw (Exist TAttBBox) = RawTAttBBox
get_fptr (ETAttBBox obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttBBox (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttBBox) :: TAttBBox)
instance Castable (Exist TAttBBox) (Ptr RawTAttBBox) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttCanvas) where
type Raw (Exist TAttCanvas) = RawTAttCanvas
get_fptr (ETAttCanvas obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttCanvas (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttCanvas) :: TAttCanvas)
instance Castable (Exist TAttCanvas) (Ptr RawTAttCanvas) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttFill) where
type Raw (Exist TAttFill) = RawTAttFill
get_fptr (ETAttFill obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttFill (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttFill) :: TAttFill)
instance Castable (Exist TAttFill) (Ptr RawTAttFill) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttImage) where
type Raw (Exist TAttImage) = RawTAttImage
get_fptr (ETAttImage obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttImage (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttImage) :: TAttImage)
instance Castable (Exist TAttImage) (Ptr RawTAttImage) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttLine) where
type Raw (Exist TAttLine) = RawTAttLine
get_fptr (ETAttLine obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttLine (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttLine) :: TAttLine)
instance Castable (Exist TAttLine) (Ptr RawTAttLine) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttMarker) where
type Raw (Exist TAttMarker) = RawTAttMarker
get_fptr (ETAttMarker obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttMarker (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttMarker) :: TAttMarker)
instance Castable (Exist TAttMarker) (Ptr RawTAttMarker) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttPad) where
type Raw (Exist TAttPad) = RawTAttPad
get_fptr (ETAttPad obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttPad (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttPad) :: TAttPad)
instance Castable (Exist TAttPad) (Ptr RawTAttPad) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttParticle) where
type Raw (Exist TAttParticle) = RawTAttParticle
get_fptr (ETAttParticle obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttParticle (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttParticle) :: TAttParticle)
instance Castable (Exist TAttParticle) (Ptr RawTAttParticle) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAttText) where
type Raw (Exist TAttText) = RawTAttText
get_fptr (ETAttText obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAttText (cast_fptr_to_obj (fptr :: ForeignPtr RawTAttText) :: TAttText)
instance Castable (Exist TAttText) (Ptr RawTAttText) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist THStack) where
type Raw (Exist THStack) = RawTHStack
get_fptr (ETHStack obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETHStack (cast_fptr_to_obj (fptr :: ForeignPtr RawTHStack) :: THStack)
instance Castable (Exist THStack) (Ptr RawTHStack) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TF1) where
type Raw (Exist TF1) = RawTF1
get_fptr (ETF1 obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETF1 (cast_fptr_to_obj (fptr :: ForeignPtr RawTF1) :: TF1)
instance Castable (Exist TF1) (Ptr RawTF1) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TGraph) where
type Raw (Exist TGraph) = RawTGraph
get_fptr (ETGraph obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETGraph (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraph) :: TGraph)
instance Castable (Exist TGraph) (Ptr RawTGraph) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TGraphAsymmErrors) where
type Raw (Exist TGraphAsymmErrors) = RawTGraphAsymmErrors
get_fptr (ETGraphAsymmErrors obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETGraphAsymmErrors (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphAsymmErrors) :: TGraphAsymmErrors)
instance Castable (Exist TGraphAsymmErrors) (Ptr RawTGraphAsymmErrors) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TCutG) where
type Raw (Exist TCutG) = RawTCutG
get_fptr (ETCutG obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETCutG (cast_fptr_to_obj (fptr :: ForeignPtr RawTCutG) :: TCutG)
instance Castable (Exist TCutG) (Ptr RawTCutG) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TGraphBentErrors) where
type Raw (Exist TGraphBentErrors) = RawTGraphBentErrors
get_fptr (ETGraphBentErrors obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETGraphBentErrors (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphBentErrors) :: TGraphBentErrors)
instance Castable (Exist TGraphBentErrors) (Ptr RawTGraphBentErrors) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TGraphErrors) where
type Raw (Exist TGraphErrors) = RawTGraphErrors
get_fptr (ETGraphErrors obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETGraphErrors (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphErrors) :: TGraphErrors)
instance Castable (Exist TGraphErrors) (Ptr RawTGraphErrors) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TGraphPolar) where
type Raw (Exist TGraphPolar) = RawTGraphPolar
get_fptr (ETGraphPolar obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETGraphPolar (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphPolar) :: TGraphPolar)
instance Castable (Exist TGraphPolar) (Ptr RawTGraphPolar) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TGraphQQ) where
type Raw (Exist TGraphQQ) = RawTGraphQQ
get_fptr (ETGraphQQ obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETGraphQQ (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphQQ) :: TGraphQQ)
instance Castable (Exist TGraphQQ) (Ptr RawTGraphQQ) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TEllipse) where
type Raw (Exist TEllipse) = RawTEllipse
get_fptr (ETEllipse obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETEllipse (cast_fptr_to_obj (fptr :: ForeignPtr RawTEllipse) :: TEllipse)
instance Castable (Exist TEllipse) (Ptr RawTEllipse) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArc) where
type Raw (Exist TArc) = RawTArc
get_fptr (ETArc obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArc (cast_fptr_to_obj (fptr :: ForeignPtr RawTArc) :: TArc)
instance Castable (Exist TArc) (Ptr RawTArc) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TCrown) where
type Raw (Exist TCrown) = RawTCrown
get_fptr (ETCrown obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETCrown (cast_fptr_to_obj (fptr :: ForeignPtr RawTCrown) :: TCrown)
instance Castable (Exist TCrown) (Ptr RawTCrown) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TLine) where
type Raw (Exist TLine) = RawTLine
get_fptr (ETLine obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETLine (cast_fptr_to_obj (fptr :: ForeignPtr RawTLine) :: TLine)
instance Castable (Exist TLine) (Ptr RawTLine) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArrow) where
type Raw (Exist TArrow) = RawTArrow
get_fptr (ETArrow obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrow (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrow) :: TArrow)
instance Castable (Exist TArrow) (Ptr RawTArrow) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TGaxis) where
type Raw (Exist TGaxis) = RawTGaxis
get_fptr (ETGaxis obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETGaxis (cast_fptr_to_obj (fptr :: ForeignPtr RawTGaxis) :: TGaxis)
instance Castable (Exist TGaxis) (Ptr RawTGaxis) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TShape) where
type Raw (Exist TShape) = RawTShape
get_fptr (ETShape obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETShape (cast_fptr_to_obj (fptr :: ForeignPtr RawTShape) :: TShape)
instance Castable (Exist TShape) (Ptr RawTShape) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TBRIK) where
type Raw (Exist TBRIK) = RawTBRIK
get_fptr (ETBRIK obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETBRIK (cast_fptr_to_obj (fptr :: ForeignPtr RawTBRIK) :: TBRIK)
instance Castable (Exist TBRIK) (Ptr RawTBRIK) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TTUBE) where
type Raw (Exist TTUBE) = RawTTUBE
get_fptr (ETTUBE obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETTUBE (cast_fptr_to_obj (fptr :: ForeignPtr RawTTUBE) :: TTUBE)
instance Castable (Exist TTUBE) (Ptr RawTTUBE) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPCON) where
type Raw (Exist TPCON) = RawTPCON
get_fptr (ETPCON obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPCON (cast_fptr_to_obj (fptr :: ForeignPtr RawTPCON) :: TPCON)
instance Castable (Exist TPCON) (Ptr RawTPCON) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TSPHE) where
type Raw (Exist TSPHE) = RawTSPHE
get_fptr (ETSPHE obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETSPHE (cast_fptr_to_obj (fptr :: ForeignPtr RawTSPHE) :: TSPHE)
instance Castable (Exist TSPHE) (Ptr RawTSPHE) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TXTRU) where
type Raw (Exist TXTRU) = RawTXTRU
get_fptr (ETXTRU obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETXTRU (cast_fptr_to_obj (fptr :: ForeignPtr RawTXTRU) :: TXTRU)
instance Castable (Exist TXTRU) (Ptr RawTXTRU) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TBox) where
type Raw (Exist TBox) = RawTBox
get_fptr (ETBox obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETBox (cast_fptr_to_obj (fptr :: ForeignPtr RawTBox) :: TBox)
instance Castable (Exist TBox) (Ptr RawTBox) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPave) where
type Raw (Exist TPave) = RawTPave
get_fptr (ETPave obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPave (cast_fptr_to_obj (fptr :: ForeignPtr RawTPave) :: TPave)
instance Castable (Exist TPave) (Ptr RawTPave) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPaveText) where
type Raw (Exist TPaveText) = RawTPaveText
get_fptr (ETPaveText obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPaveText (cast_fptr_to_obj (fptr :: ForeignPtr RawTPaveText) :: TPaveText)
instance Castable (Exist TPaveText) (Ptr RawTPaveText) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TDiamond) where
type Raw (Exist TDiamond) = RawTDiamond
get_fptr (ETDiamond obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETDiamond (cast_fptr_to_obj (fptr :: ForeignPtr RawTDiamond) :: TDiamond)
instance Castable (Exist TDiamond) (Ptr RawTDiamond) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPaveStats) where
type Raw (Exist TPaveStats) = RawTPaveStats
get_fptr (ETPaveStats obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPaveStats (cast_fptr_to_obj (fptr :: ForeignPtr RawTPaveStats) :: TPaveStats)
instance Castable (Exist TPaveStats) (Ptr RawTPaveStats) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPavesText) where
type Raw (Exist TPavesText) = RawTPavesText
get_fptr (ETPavesText obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPavesText (cast_fptr_to_obj (fptr :: ForeignPtr RawTPavesText) :: TPavesText)
instance Castable (Exist TPavesText) (Ptr RawTPavesText) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TLegend) where
type Raw (Exist TLegend) = RawTLegend
get_fptr (ETLegend obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETLegend (cast_fptr_to_obj (fptr :: ForeignPtr RawTLegend) :: TLegend)
instance Castable (Exist TLegend) (Ptr RawTLegend) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPaveLabel) where
type Raw (Exist TPaveLabel) = RawTPaveLabel
get_fptr (ETPaveLabel obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPaveLabel (cast_fptr_to_obj (fptr :: ForeignPtr RawTPaveLabel) :: TPaveLabel)
instance Castable (Exist TPaveLabel) (Ptr RawTPaveLabel) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPaveClass) where
type Raw (Exist TPaveClass) = RawTPaveClass
get_fptr (ETPaveClass obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPaveClass (cast_fptr_to_obj (fptr :: ForeignPtr RawTPaveClass) :: TPaveClass)
instance Castable (Exist TPaveClass) (Ptr RawTPaveClass) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TWbox) where
type Raw (Exist TWbox) = RawTWbox
get_fptr (ETWbox obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETWbox (cast_fptr_to_obj (fptr :: ForeignPtr RawTWbox) :: TWbox)
instance Castable (Exist TWbox) (Ptr RawTWbox) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TFrame) where
type Raw (Exist TFrame) = RawTFrame
get_fptr (ETFrame obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETFrame (cast_fptr_to_obj (fptr :: ForeignPtr RawTFrame) :: TFrame)
instance Castable (Exist TFrame) (Ptr RawTFrame) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TSliderBox) where
type Raw (Exist TSliderBox) = RawTSliderBox
get_fptr (ETSliderBox obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETSliderBox (cast_fptr_to_obj (fptr :: ForeignPtr RawTSliderBox) :: TSliderBox)
instance Castable (Exist TSliderBox) (Ptr RawTSliderBox) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TTree) where
type Raw (Exist TTree) = RawTTree
get_fptr (ETTree obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETTree (cast_fptr_to_obj (fptr :: ForeignPtr RawTTree) :: TTree)
instance Castable (Exist TTree) (Ptr RawTTree) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TChain) where
type Raw (Exist TChain) = RawTChain
get_fptr (ETChain obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETChain (cast_fptr_to_obj (fptr :: ForeignPtr RawTChain) :: TChain)
instance Castable (Exist TChain) (Ptr RawTChain) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TNtuple) where
type Raw (Exist TNtuple) = RawTNtuple
get_fptr (ETNtuple obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETNtuple (cast_fptr_to_obj (fptr :: ForeignPtr RawTNtuple) :: TNtuple)
instance Castable (Exist TNtuple) (Ptr RawTNtuple) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TNtupleD) where
type Raw (Exist TNtupleD) = RawTNtupleD
get_fptr (ETNtupleD obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETNtupleD (cast_fptr_to_obj (fptr :: ForeignPtr RawTNtupleD) :: TNtupleD)
instance Castable (Exist TNtupleD) (Ptr RawTNtupleD) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TTreeSQL) where
type Raw (Exist TTreeSQL) = RawTTreeSQL
get_fptr (ETTreeSQL obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETTreeSQL (cast_fptr_to_obj (fptr :: ForeignPtr RawTTreeSQL) :: TTreeSQL)
instance Castable (Exist TTreeSQL) (Ptr RawTTreeSQL) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPolyLine) where
type Raw (Exist TPolyLine) = RawTPolyLine
get_fptr (ETPolyLine obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPolyLine (cast_fptr_to_obj (fptr :: ForeignPtr RawTPolyLine) :: TPolyLine)
instance Castable (Exist TPolyLine) (Ptr RawTPolyLine) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TCurlyLine) where
type Raw (Exist TCurlyLine) = RawTCurlyLine
get_fptr (ETCurlyLine obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETCurlyLine (cast_fptr_to_obj (fptr :: ForeignPtr RawTCurlyLine) :: TCurlyLine)
instance Castable (Exist TCurlyLine) (Ptr RawTCurlyLine) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TCurlyArc) where
type Raw (Exist TCurlyArc) = RawTCurlyArc
get_fptr (ETCurlyArc obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETCurlyArc (cast_fptr_to_obj (fptr :: ForeignPtr RawTCurlyArc) :: TCurlyArc)
instance Castable (Exist TCurlyArc) (Ptr RawTCurlyArc) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TEfficiency) where
type Raw (Exist TEfficiency) = RawTEfficiency
get_fptr (ETEfficiency obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETEfficiency (cast_fptr_to_obj (fptr :: ForeignPtr RawTEfficiency) :: TEfficiency)
instance Castable (Exist TEfficiency) (Ptr RawTEfficiency) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TAxis) where
type Raw (Exist TAxis) = RawTAxis
get_fptr (ETAxis obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETAxis (cast_fptr_to_obj (fptr :: ForeignPtr RawTAxis) :: TAxis)
instance Castable (Exist TAxis) (Ptr RawTAxis) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TLatex) where
type Raw (Exist TLatex) = RawTLatex
get_fptr (ETLatex obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETLatex (cast_fptr_to_obj (fptr :: ForeignPtr RawTLatex) :: TLatex)
instance Castable (Exist TLatex) (Ptr RawTLatex) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TText) where
type Raw (Exist TText) = RawTText
get_fptr (ETText obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETText (cast_fptr_to_obj (fptr :: ForeignPtr RawTText) :: TText)
instance Castable (Exist TText) (Ptr RawTText) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TDirectory) where
type Raw (Exist TDirectory) = RawTDirectory
get_fptr (ETDirectory obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETDirectory (cast_fptr_to_obj (fptr :: ForeignPtr RawTDirectory) :: TDirectory)
instance Castable (Exist TDirectory) (Ptr RawTDirectory) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TDirectoryFile) where
type Raw (Exist TDirectoryFile) = RawTDirectoryFile
get_fptr (ETDirectoryFile obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETDirectoryFile (cast_fptr_to_obj (fptr :: ForeignPtr RawTDirectoryFile) :: TDirectoryFile)
instance Castable (Exist TDirectoryFile) (Ptr RawTDirectoryFile) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TFile) where
type Raw (Exist TFile) = RawTFile
get_fptr (ETFile obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETFile (cast_fptr_to_obj (fptr :: ForeignPtr RawTFile) :: TFile)
instance Castable (Exist TFile) (Ptr RawTFile) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TBranch) where
type Raw (Exist TBranch) = RawTBranch
get_fptr (ETBranch obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETBranch (cast_fptr_to_obj (fptr :: ForeignPtr RawTBranch) :: TBranch)
instance Castable (Exist TBranch) (Ptr RawTBranch) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TVirtualTreePlayer) where
type Raw (Exist TVirtualTreePlayer) = RawTVirtualTreePlayer
get_fptr (ETVirtualTreePlayer obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETVirtualTreePlayer (cast_fptr_to_obj (fptr :: ForeignPtr RawTVirtualTreePlayer) :: TVirtualTreePlayer)
instance Castable (Exist TVirtualTreePlayer) (Ptr RawTVirtualTreePlayer) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TTreePlayer) where
type Raw (Exist TTreePlayer) = RawTTreePlayer
get_fptr (ETTreePlayer obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETTreePlayer (cast_fptr_to_obj (fptr :: ForeignPtr RawTTreePlayer) :: TTreePlayer)
instance Castable (Exist TTreePlayer) (Ptr RawTTreePlayer) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArray) where
type Raw (Exist TArray) = RawTArray
get_fptr (ETArray obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArray (cast_fptr_to_obj (fptr :: ForeignPtr RawTArray) :: TArray)
instance Castable (Exist TArray) (Ptr RawTArray) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArrayC) where
type Raw (Exist TArrayC) = RawTArrayC
get_fptr (ETArrayC obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrayC (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayC) :: TArrayC)
instance Castable (Exist TArrayC) (Ptr RawTArrayC) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArrayD) where
type Raw (Exist TArrayD) = RawTArrayD
get_fptr (ETArrayD obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrayD (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayD) :: TArrayD)
instance Castable (Exist TArrayD) (Ptr RawTArrayD) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArrayF) where
type Raw (Exist TArrayF) = RawTArrayF
get_fptr (ETArrayF obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrayF (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayF) :: TArrayF)
instance Castable (Exist TArrayF) (Ptr RawTArrayF) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArrayI) where
type Raw (Exist TArrayI) = RawTArrayI
get_fptr (ETArrayI obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrayI (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayI) :: TArrayI)
instance Castable (Exist TArrayI) (Ptr RawTArrayI) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArrayL) where
type Raw (Exist TArrayL) = RawTArrayL
get_fptr (ETArrayL obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrayL (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayL) :: TArrayL)
instance Castable (Exist TArrayL) (Ptr RawTArrayL) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArrayL64) where
type Raw (Exist TArrayL64) = RawTArrayL64
get_fptr (ETArrayL64 obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrayL64 (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayL64) :: TArrayL64)
instance Castable (Exist TArrayL64) (Ptr RawTArrayL64) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TArrayS) where
type Raw (Exist TArrayS) = RawTArrayS
get_fptr (ETArrayS obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETArrayS (cast_fptr_to_obj (fptr :: ForeignPtr RawTArrayS) :: TArrayS)
instance Castable (Exist TArrayS) (Ptr RawTArrayS) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH1) where
type Raw (Exist TH1) = RawTH1
get_fptr (ETH1 obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH1 (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1) :: TH1)
instance Castable (Exist TH1) (Ptr RawTH1) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH2) where
type Raw (Exist TH2) = RawTH2
get_fptr (ETH2 obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH2 (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2) :: TH2)
instance Castable (Exist TH2) (Ptr RawTH2) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH3) where
type Raw (Exist TH3) = RawTH3
get_fptr (ETH3 obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH3 (cast_fptr_to_obj (fptr :: ForeignPtr RawTH3) :: TH3)
instance Castable (Exist TH3) (Ptr RawTH3) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH1C) where
type Raw (Exist TH1C) = RawTH1C
get_fptr (ETH1C obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH1C (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1C) :: TH1C)
instance Castable (Exist TH1C) (Ptr RawTH1C) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH1D) where
type Raw (Exist TH1D) = RawTH1D
get_fptr (ETH1D obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH1D (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1D) :: TH1D)
instance Castable (Exist TH1D) (Ptr RawTH1D) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH1F) where
type Raw (Exist TH1F) = RawTH1F
get_fptr (ETH1F obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH1F (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1F) :: TH1F)
instance Castable (Exist TH1F) (Ptr RawTH1F) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH1I) where
type Raw (Exist TH1I) = RawTH1I
get_fptr (ETH1I obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH1I (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1I) :: TH1I)
instance Castable (Exist TH1I) (Ptr RawTH1I) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH1S) where
type Raw (Exist TH1S) = RawTH1S
get_fptr (ETH1S obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH1S (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1S) :: TH1S)
instance Castable (Exist TH1S) (Ptr RawTH1S) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH2C) where
type Raw (Exist TH2C) = RawTH2C
get_fptr (ETH2C obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH2C (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2C) :: TH2C)
instance Castable (Exist TH2C) (Ptr RawTH2C) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH2D) where
type Raw (Exist TH2D) = RawTH2D
get_fptr (ETH2D obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH2D (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2D) :: TH2D)
instance Castable (Exist TH2D) (Ptr RawTH2D) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH2F) where
type Raw (Exist TH2F) = RawTH2F
get_fptr (ETH2F obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH2F (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2F) :: TH2F)
instance Castable (Exist TH2F) (Ptr RawTH2F) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH2I) where
type Raw (Exist TH2I) = RawTH2I
get_fptr (ETH2I obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH2I (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2I) :: TH2I)
instance Castable (Exist TH2I) (Ptr RawTH2I) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH2Poly) where
type Raw (Exist TH2Poly) = RawTH2Poly
get_fptr (ETH2Poly obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH2Poly (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2Poly) :: TH2Poly)
instance Castable (Exist TH2Poly) (Ptr RawTH2Poly) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH2S) where
type Raw (Exist TH2S) = RawTH2S
get_fptr (ETH2S obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH2S (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2S) :: TH2S)
instance Castable (Exist TH2S) (Ptr RawTH2S) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH3C) where
type Raw (Exist TH3C) = RawTH3C
get_fptr (ETH3C obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH3C (cast_fptr_to_obj (fptr :: ForeignPtr RawTH3C) :: TH3C)
instance Castable (Exist TH3C) (Ptr RawTH3C) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH3D) where
type Raw (Exist TH3D) = RawTH3D
get_fptr (ETH3D obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH3D (cast_fptr_to_obj (fptr :: ForeignPtr RawTH3D) :: TH3D)
instance Castable (Exist TH3D) (Ptr RawTH3D) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH3F) where
type Raw (Exist TH3F) = RawTH3F
get_fptr (ETH3F obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH3F (cast_fptr_to_obj (fptr :: ForeignPtr RawTH3F) :: TH3F)
instance Castable (Exist TH3F) (Ptr RawTH3F) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH3I) where
type Raw (Exist TH3I) = RawTH3I
get_fptr (ETH3I obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH3I (cast_fptr_to_obj (fptr :: ForeignPtr RawTH3I) :: TH3I)
instance Castable (Exist TH3I) (Ptr RawTH3I) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TH3S) where
type Raw (Exist TH3S) = RawTH3S
get_fptr (ETH3S obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH3S (cast_fptr_to_obj (fptr :: ForeignPtr RawTH3S) :: TH3S)
instance Castable (Exist TH3S) (Ptr RawTH3S) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TQObject) where
type Raw (Exist TQObject) = RawTQObject
get_fptr (ETQObject obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETQObject (cast_fptr_to_obj (fptr :: ForeignPtr RawTQObject) :: TQObject)
instance Castable (Exist TQObject) (Ptr RawTQObject) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TVirtualPad) where
type Raw (Exist TVirtualPad) = RawTVirtualPad
get_fptr (ETVirtualPad obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETVirtualPad (cast_fptr_to_obj (fptr :: ForeignPtr RawTVirtualPad) :: TVirtualPad)
instance Castable (Exist TVirtualPad) (Ptr RawTVirtualPad) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TPad) where
type Raw (Exist TPad) = RawTPad
get_fptr (ETPad obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETPad (cast_fptr_to_obj (fptr :: ForeignPtr RawTPad) :: TPad)
instance Castable (Exist TPad) (Ptr RawTPad) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TButton) where
type Raw (Exist TButton) = RawTButton
get_fptr (ETButton obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETButton (cast_fptr_to_obj (fptr :: ForeignPtr RawTButton) :: TButton)
instance Castable (Exist TButton) (Ptr RawTButton) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TGroupButton) where
type Raw (Exist TGroupButton) = RawTGroupButton
get_fptr (ETGroupButton obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETGroupButton (cast_fptr_to_obj (fptr :: ForeignPtr RawTGroupButton) :: TGroupButton)
instance Castable (Exist TGroupButton) (Ptr RawTGroupButton) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TCanvas) where
type Raw (Exist TCanvas) = RawTCanvas
get_fptr (ETCanvas obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETCanvas (cast_fptr_to_obj (fptr :: ForeignPtr RawTCanvas) :: TCanvas)
instance Castable (Exist TCanvas) (Ptr RawTCanvas) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TDialogCanvas) where
type Raw (Exist TDialogCanvas) = RawTDialogCanvas
get_fptr (ETDialogCanvas obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETDialogCanvas (cast_fptr_to_obj (fptr :: ForeignPtr RawTDialogCanvas) :: TDialogCanvas)
instance Castable (Exist TDialogCanvas) (Ptr RawTDialogCanvas) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TInspectCanvas) where
type Raw (Exist TInspectCanvas) = RawTInspectCanvas
get_fptr (ETInspectCanvas obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETInspectCanvas (cast_fptr_to_obj (fptr :: ForeignPtr RawTInspectCanvas) :: TInspectCanvas)
instance Castable (Exist TInspectCanvas) (Ptr RawTInspectCanvas) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TEvePad) where
type Raw (Exist TEvePad) = RawTEvePad
get_fptr (ETEvePad obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETEvePad (cast_fptr_to_obj (fptr :: ForeignPtr RawTEvePad) :: TEvePad)
instance Castable (Exist TEvePad) (Ptr RawTEvePad) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TSlider) where
type Raw (Exist TSlider) = RawTSlider
get_fptr (ETSlider obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETSlider (cast_fptr_to_obj (fptr :: ForeignPtr RawTSlider) :: TSlider)
instance Castable (Exist TSlider) (Ptr RawTSlider) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
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)
instance Castable (Exist TApplication) (Ptr RawTApplication) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TRint) where
type Raw (Exist TRint) = RawTRint
get_fptr (ETRint obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETRint (cast_fptr_to_obj (fptr :: ForeignPtr RawTRint) :: TRint)
instance Castable (Exist TRint) (Ptr RawTRint) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance FPtr (Exist TRandom) where
type Raw (Exist TRandom) = RawTRandom
get_fptr (ETRandom obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETRandom (cast_fptr_to_obj (fptr :: ForeignPtr RawTRandom) :: TRandom)
instance Castable (Exist TRandom) (Ptr RawTRandom) where
cast = unsafeForeignPtrToPtr . get_fptr
uncast = cast_fptr_to_obj . unsafePerformIO . newForeignPtr_
instance ITObject TObject where
getName = xform0 c_tobject_getname
draw = xform1 c_tobject_draw
findObject = xform1 c_tobject_findobject
saveAs = xform2 c_tobject_saveas
write = xform3 c_tobject_write
isA = xform0 c_tobject_isa
instance ITNamed TNamed where
setTitle = xform1 c_tnamed_settitle
instance ITClass TClass where
instance ITFormula TFormula where
getParameter = xform1 c_tformula_getparameter
setParameter = xform2 c_tformula_setparameter
instance ITAtt3D TAtt3D where
instance ITAttAxis TAttAxis where
setLabelColor = xform1 c_tattaxis_setlabelcolor
setLabelSize = xform1 c_tattaxis_setlabelsize
setTickLength = xform1 c_tattaxis_setticklength
setTitleOffset = xform1 c_tattaxis_settitleoffset
setNdivisions = xform2 c_tattaxis_setndivisions
instance ITAttBBox TAttBBox where
instance ITAttCanvas TAttCanvas where
instance ITAttFill TAttFill where
setFillColor = xform1 c_tattfill_setfillcolor
setFillStyle = xform1 c_tattfill_setfillstyle
instance ITAttImage TAttImage where
instance ITAttLine TAttLine where
setLineColor = xform1 c_tattline_setlinecolor
instance ITAttMarker TAttMarker where
instance ITAttPad TAttPad where
instance ITAttParticle TAttParticle where
instance ITAttText TAttText where
setTextColor = xform1 c_tatttext_settextcolor
setTextAlign = xform1 c_tatttext_settextalign
setTextSize = xform1 c_tatttext_settextsize
instance ITHStack THStack where
instance ITF1 TF1 where
instance ITGraph TGraph where
instance ITGraphAsymmErrors TGraphAsymmErrors where
instance ITCutG TCutG where
instance ITGraphBentErrors TGraphBentErrors where
instance ITGraphErrors TGraphErrors where
instance ITGraphPolar TGraphPolar where
instance ITGraphQQ TGraphQQ where
instance ITEllipse TEllipse where
instance ITArc TArc where
instance ITCrown TCrown where
instance ITLine TLine where
instance ITArrow TArrow where
instance ITGaxis TGaxis where
instance ITShape TShape where
instance ITBRIK TBRIK where
instance ITTUBE TTUBE where
instance ITPCON TPCON where
instance ITSPHE TSPHE where
instance ITXTRU TXTRU where
instance ITBox TBox where
instance ITPave TPave where
instance ITPaveText TPaveText where
instance ITDiamond TDiamond where
instance ITPaveStats TPaveStats where
instance ITPavesText TPavesText where
instance ITLegend TLegend where
instance ITPaveLabel TPaveLabel where
instance ITPaveClass TPaveClass where
instance ITWbox TWbox where
setBorderMode = xform1 c_twbox_setbordermode
instance ITFrame TFrame where
instance ITSliderBox TSliderBox where
instance ITTree TTree where
instance ITChain TChain where
instance ITNtuple TNtuple where
instance ITNtupleD TNtupleD where
instance ITTreeSQL TTreeSQL where
instance ITPolyLine TPolyLine where
instance ITCurlyLine TCurlyLine where
instance ITCurlyArc TCurlyArc where
instance ITEfficiency TEfficiency where
instance ITAxis TAxis where
instance ITLatex TLatex where
instance ITText TText where
instance ITDirectory TDirectory where
close = xform1 c_tdirectory_close
get = xform1 c_tdirectory_get
instance ITDirectoryFile TDirectoryFile where
instance ITFile TFile where
instance ITBranch TBranch where
instance ITVirtualTreePlayer TVirtualTreePlayer where
instance ITTreePlayer TTreePlayer where
instance ITArray TArray where
instance ITArrayC TArrayC where
instance ITArrayD TArrayD where
instance ITArrayF TArrayF where
instance ITArrayI TArrayI where
instance ITArrayL TArrayL where
instance ITArrayL64 TArrayL64 where
instance ITArrayS TArrayS where
instance ITH1 TH1 where
add = xform2 c_th1_add
addBinContent = xform2 c_th1_addbincontent
chi2Test = xform3 c_th1_chi2test
computeIntegral = xform0 c_th1_computeintegral
directoryAutoAdd = xform1 c_th1_directoryautoadd
distancetoPrimitive = xform2 c_th1_distancetoprimitive
divide = xform5 c_th1_divide
drawCopy = xform1 c_th1_drawcopy
drawNormalized = xform2 c_th1_drawnormalized
drawPanel = xform0 c_th1_drawpanel
bufferEmpty = xform1 c_th1_bufferempty
eval = xform2 c_th1_eval
executeEvent = xform3 c_th1_executeevent
fFT = xform2 c_th1_fft
fill1 = xform1 c_th1_fill1
fillN = xform4 c_th1_filln
fillRandom = xform2 c_th1_fillrandom
findBin = xform3 c_th1_findbin
findFixBin = xform3 c_th1_findfixbin
findFirstBinAbove = xform2 c_th1_findfirstbinabove
findLastBinAbove = xform2 c_th1_findlastbinabove
fitPanel = xform0 c_th1_fitpanel
getNdivisions = xform1 c_th1_getndivisions
getAxisColor = xform1 c_th1_getaxiscolor
getLabelColor = xform1 c_th1_getlabelcolor
getLabelFont = xform1 c_th1_getlabelfont
getLabelOffset = xform1 c_th1_getlabeloffset
getLabelSize = xform1 c_th1_getlabelsize
getTitleFont = xform1 c_th1_gettitlefont
getTitleOffset = xform1 c_th1_gettitleoffset
getTitleSize = xform1 c_th1_gettitlesize
getTickLength = xform1 c_th1_getticklength
getBarOffset = xform0 c_th1_getbaroffset
getBarWidth = xform0 c_th1_getbarwidth
getContour = xform1 c_th1_getcontour
getContourLevel = xform1 c_th1_getcontourlevel
getContourLevelPad = xform1 c_th1_getcontourlevelpad
getBin = xform3 c_th1_getbin
getBinCenter = xform1 c_th1_getbincenter
getBinContent1 = xform1 c_th1_getbincontent1
getBinContent2 = xform2 c_th1_getbincontent2
getBinContent3 = xform3 c_th1_getbincontent3
getBinError1 = xform1 c_th1_getbinerror1
getBinError2 = xform2 c_th1_getbinerror2
getBinError3 = xform3 c_th1_getbinerror3
getBinLowEdge = xform1 c_th1_getbinlowedge
getBinWidth = xform1 c_th1_getbinwidth
getCellContent = xform2 c_th1_getcellcontent
getCellError = xform2 c_th1_getcellerror
instance ITH2 TH2 where
fill2 = xform2 c_th2_fill2
instance ITH3 TH3 where
instance ITH1C TH1C where
instance ITH1D TH1D where
instance ITH1F TH1F where
instance ITH1I TH1I where
instance ITH1S TH1S where
instance ITH2C TH2C where
instance ITH2D TH2D where
instance ITH2F TH2F where
instance ITH2I TH2I where
instance ITH2Poly TH2Poly where
instance ITH2S TH2S where
instance ITH3C TH3C where
instance ITH3D TH3D where
instance ITH3F TH3F where
instance ITH3I TH3I where
instance ITH3S TH3S where
instance ITQObject TQObject where
instance ITVirtualPad TVirtualPad where
getFrame = xform0 c_tvirtualpad_getframe
range = xform4 c_tvirtualpad_range
instance ITPad TPad where
instance ITButton TButton where
instance ITGroupButton TGroupButton where
instance ITCanvas TCanvas where
instance ITDialogCanvas TDialogCanvas where
instance ITInspectCanvas TInspectCanvas where
instance ITEvePad TEvePad where
instance ITSlider TSlider where
instance ITApplication TApplication where
run = xform1 c_tapplication_run
instance ITRint TRint where
instance ITRandom TRandom where
gaus = xform2 c_trandom_gaus
uniform = xform2 c_trandom_uniform
instance IDeletable TRandom where
delete = xform0 c_trandom_delete
instance IDeletable TRint where
delete = xform0 c_trint_delete
instance IDeletable TApplication where
delete = xform0 c_tapplication_delete
instance IDeletable TSlider where
delete = xform0 c_tslider_delete
instance IDeletable TEvePad where
delete = xform0 c_tevepad_delete
instance IDeletable TInspectCanvas where
delete = xform0 c_tinspectcanvas_delete
instance IDeletable TDialogCanvas where
delete = xform0 c_tdialogcanvas_delete
instance IDeletable TCanvas where
delete = xform0 c_tcanvas_delete
instance IDeletable TGroupButton where
delete = xform0 c_tgroupbutton_delete
instance IDeletable TButton where
delete = xform0 c_tbutton_delete
instance IDeletable TPad where
delete = xform0 c_tpad_delete
instance IDeletable TVirtualPad where
delete = xform0 c_tvirtualpad_delete
instance IDeletable TQObject where
delete = xform0 c_tqobject_delete
instance IDeletable TH3S where
delete = xform0 c_th3s_delete
instance IDeletable TH3I where
delete = xform0 c_th3i_delete
instance IDeletable TH3F where
delete = xform0 c_th3f_delete
instance IDeletable TH3D where
delete = xform0 c_th3d_delete
instance IDeletable TH3C where
delete = xform0 c_th3c_delete
instance IDeletable TH2S where
delete = xform0 c_th2s_delete
instance IDeletable TH2Poly where
delete = xform0 c_th2poly_delete
instance IDeletable TH2I where
delete = xform0 c_th2i_delete
instance IDeletable TH2F where
delete = xform0 c_th2f_delete
instance IDeletable TH2D where
delete = xform0 c_th2d_delete
instance IDeletable TH2C where
delete = xform0 c_th2c_delete
instance IDeletable TH1S where
delete = xform0 c_th1s_delete
instance IDeletable TH1I where
delete = xform0 c_th1i_delete
instance IDeletable TH1F where
delete = xform0 c_th1f_delete
instance IDeletable TH1D where
delete = xform0 c_th1d_delete
instance IDeletable TH1C where
delete = xform0 c_th1c_delete
instance IDeletable TH3 where
delete = xform0 c_th3_delete
instance IDeletable TH2 where
delete = xform0 c_th2_delete
instance IDeletable TH1 where
delete = xform0 c_th1_delete
instance IDeletable TArrayS where
delete = xform0 c_tarrays_delete
instance IDeletable TArrayL64 where
delete = xform0 c_tarrayl64_delete
instance IDeletable TArrayL where
delete = xform0 c_tarrayl_delete
instance IDeletable TArrayI where
delete = xform0 c_tarrayi_delete
instance IDeletable TArrayF where
delete = xform0 c_tarrayf_delete
instance IDeletable TArrayD where
delete = xform0 c_tarrayd_delete
instance IDeletable TArrayC where
delete = xform0 c_tarrayc_delete
instance IDeletable TArray where
delete = xform0 c_tarray_delete
instance IDeletable TTreePlayer where
delete = xform0 c_ttreeplayer_delete
instance IDeletable TVirtualTreePlayer where
delete = xform0 c_tvirtualtreeplayer_delete
instance IDeletable TBranch where
delete = xform0 c_tbranch_delete
instance IDeletable TFile where
delete = xform0 c_tfile_delete
instance IDeletable TDirectoryFile where
delete = xform0 c_tdirectoryfile_delete
instance IDeletable TDirectory where
delete = xform0 c_tdirectory_delete
instance IDeletable TText where
delete = xform0 c_ttext_delete
instance IDeletable TLatex where
delete = xform0 c_tlatex_delete
instance IDeletable TAxis where
delete = xform0 c_taxis_delete
instance IDeletable TEfficiency where
delete = xform0 c_tefficiency_delete
instance IDeletable TCurlyArc where
delete = xform0 c_tcurlyarc_delete
instance IDeletable TCurlyLine where
delete = xform0 c_tcurlyline_delete
instance IDeletable TPolyLine where
delete = xform0 c_tpolyline_delete
instance IDeletable TTreeSQL where
delete = xform0 c_ttreesql_delete
instance IDeletable TNtupleD where
delete = xform0 c_tntupled_delete
instance IDeletable TNtuple where
delete = xform0 c_tntuple_delete
instance IDeletable TChain where
delete = xform0 c_tchain_delete
instance IDeletable TTree where
delete = xform0 c_ttree_delete
instance IDeletable TSliderBox where
delete = xform0 c_tsliderbox_delete
instance IDeletable TFrame where
delete = xform0 c_tframe_delete
instance IDeletable TWbox where
delete = xform0 c_twbox_delete
instance IDeletable TPaveClass where
delete = xform0 c_tpaveclass_delete
instance IDeletable TPaveLabel where
delete = xform0 c_tpavelabel_delete
instance IDeletable TLegend where
delete = xform0 c_tlegend_delete
instance IDeletable TPavesText where
delete = xform0 c_tpavestext_delete
instance IDeletable TPaveStats where
delete = xform0 c_tpavestats_delete
instance IDeletable TDiamond where
delete = xform0 c_tdiamond_delete
instance IDeletable TPaveText where
delete = xform0 c_tpavetext_delete
instance IDeletable TPave where
delete = xform0 c_tpave_delete
instance IDeletable TBox where
delete = xform0 c_tbox_delete
instance IDeletable TXTRU where
delete = xform0 c_txtru_delete
instance IDeletable TSPHE where
delete = xform0 c_tsphe_delete
instance IDeletable TPCON where
delete = xform0 c_tpcon_delete
instance IDeletable TTUBE where
delete = xform0 c_ttube_delete
instance IDeletable TBRIK where
delete = xform0 c_tbrik_delete
instance IDeletable TShape where
delete = xform0 c_tshape_delete
instance IDeletable TGaxis where
delete = xform0 c_tgaxis_delete
instance IDeletable TArrow where
delete = xform0 c_tarrow_delete
instance IDeletable TLine where
delete = xform0 c_tline_delete
instance IDeletable TCrown where
delete = xform0 c_tcrown_delete
instance IDeletable TArc where
delete = xform0 c_tarc_delete
instance IDeletable TEllipse where
delete = xform0 c_tellipse_delete
instance IDeletable TGraphQQ where
delete = xform0 c_tgraphqq_delete
instance IDeletable TGraphPolar where
delete = xform0 c_tgraphpolar_delete
instance IDeletable TGraphErrors where
delete = xform0 c_tgrapherrors_delete
instance IDeletable TGraphBentErrors where
delete = xform0 c_tgraphbenterrors_delete
instance IDeletable TCutG where
delete = xform0 c_tcutg_delete
instance IDeletable TGraphAsymmErrors where
delete = xform0 c_tgraphasymmerrors_delete
instance IDeletable TGraph where
delete = xform0 c_tgraph_delete
instance IDeletable TF1 where
delete = xform0 c_tf1_delete
instance IDeletable THStack where
delete = xform0 c_thstack_delete
instance IDeletable TAttText where
delete = xform0 c_tatttext_delete
instance IDeletable TAttParticle where
delete = xform0 c_tattparticle_delete
instance IDeletable TAttPad where
delete = xform0 c_tattpad_delete
instance IDeletable TAttMarker where
delete = xform0 c_tattmarker_delete
instance IDeletable TAttLine where
delete = xform0 c_tattline_delete
instance IDeletable TAttImage where
delete = xform0 c_tattimage_delete
instance IDeletable TAttFill where
delete = xform0 c_tattfill_delete
instance IDeletable TAttCanvas where
delete = xform0 c_tattcanvas_delete
instance IDeletable TAttBBox where
delete = xform0 c_tattbbox_delete
instance IDeletable TAttAxis where
delete = xform0 c_tattaxis_delete
instance IDeletable TAtt3D where
delete = xform0 c_tatt3d_delete
instance IDeletable TFormula where
delete = xform0 c_tformula_delete
instance IDeletable TClass where
delete = xform0 c_tclass_delete
instance IDeletable TNamed where
delete = xform0 c_tnamed_delete
instance IDeletable TObject where
delete = xform0 c_tobject_delete
instance ITApplication TRint where
run = xform1 c_trint_run
instance ITArray TH3S where
instance ITArray TH3I where
instance ITArray TH3F where
instance ITArray TH3D where
instance ITArray TH3C where
instance ITArray TH2S where
instance ITArray TH2I where
instance ITArray TH2F where
instance ITArray TH2D where
instance ITArray TH2C where
instance ITArray TH1S where
instance ITArray TH1I where
instance ITArray TH1F where
instance ITArray TH1D where
instance ITArray TH1C where
instance ITArray TArrayS where
instance ITArray TArrayL64 where
instance ITArray TArrayL where
instance ITArray TArrayI where
instance ITArray TArrayF where
instance ITArray TArrayD where
instance ITArray TArrayC where
instance ITArrayC TH3C where
instance ITArrayC TH2C where
instance ITArrayC TH1C where
instance ITArrayD TH3D where
instance ITArrayD TH2D where
instance ITArrayD TH1D where
instance ITArrayF TH3F where
instance ITArrayF TH2F where
instance ITArrayF TH1F where
instance ITArrayI TH3I where
instance ITArrayI TH2I where
instance ITArrayI TH1I where
instance ITArrayS TH3S where
instance ITArrayS TH2S where
instance ITArrayS TH1S where
instance ITAtt3D TH3S where
instance ITAtt3D TH3I where
instance ITAtt3D TH3F where
instance ITAtt3D TH3D where
instance ITAtt3D TH3C where
instance ITAtt3D TH3 where
instance ITAtt3D TXTRU where
instance ITAtt3D TSPHE where
instance ITAtt3D TPCON where
instance ITAtt3D TTUBE where
instance ITAtt3D TBRIK where
instance ITAtt3D TShape where
instance ITAttAxis TAxis where
setLabelColor = xform1 c_taxis_setlabelcolor
setLabelSize = xform1 c_taxis_setlabelsize
setTickLength = xform1 c_taxis_setticklength
setTitleOffset = xform1 c_taxis_settitleoffset
setNdivisions = xform2 c_taxis_setndivisions
instance ITAttFill TSlider where
setFillColor = xform1 c_tslider_setfillcolor
setFillStyle = xform1 c_tslider_setfillstyle
instance ITAttFill TEvePad where
setFillColor = xform1 c_tevepad_setfillcolor
setFillStyle = xform1 c_tevepad_setfillstyle
instance ITAttFill TInspectCanvas where
setFillColor = xform1 c_tinspectcanvas_setfillcolor
setFillStyle = xform1 c_tinspectcanvas_setfillstyle
instance ITAttFill TDialogCanvas where
setFillColor = xform1 c_tdialogcanvas_setfillcolor
setFillStyle = xform1 c_tdialogcanvas_setfillstyle
instance ITAttFill TCanvas where
setFillColor = xform1 c_tcanvas_setfillcolor
setFillStyle = xform1 c_tcanvas_setfillstyle
instance ITAttFill TGroupButton where
setFillColor = xform1 c_tgroupbutton_setfillcolor
setFillStyle = xform1 c_tgroupbutton_setfillstyle
instance ITAttFill TButton where
setFillColor = xform1 c_tbutton_setfillcolor
setFillStyle = xform1 c_tbutton_setfillstyle
instance ITAttFill TPad where
setFillColor = xform1 c_tpad_setfillcolor
setFillStyle = xform1 c_tpad_setfillstyle
instance ITAttFill TVirtualPad where
setFillColor = xform1 c_tvirtualpad_setfillcolor
setFillStyle = xform1 c_tvirtualpad_setfillstyle
instance ITAttFill TH3S where
setFillColor = xform1 c_th3s_setfillcolor
setFillStyle = xform1 c_th3s_setfillstyle
instance ITAttFill TH3I where
setFillColor = xform1 c_th3i_setfillcolor
setFillStyle = xform1 c_th3i_setfillstyle
instance ITAttFill TH3F where
setFillColor = xform1 c_th3f_setfillcolor
setFillStyle = xform1 c_th3f_setfillstyle
instance ITAttFill TH3D where
setFillColor = xform1 c_th3d_setfillcolor
setFillStyle = xform1 c_th3d_setfillstyle
instance ITAttFill TH3C where
setFillColor = xform1 c_th3c_setfillcolor
setFillStyle = xform1 c_th3c_setfillstyle
instance ITAttFill TH2S where
setFillColor = xform1 c_th2s_setfillcolor
setFillStyle = xform1 c_th2s_setfillstyle
instance ITAttFill TH2Poly where
setFillColor = xform1 c_th2poly_setfillcolor
setFillStyle = xform1 c_th2poly_setfillstyle
instance ITAttFill TH2I where
setFillColor = xform1 c_th2i_setfillcolor
setFillStyle = xform1 c_th2i_setfillstyle
instance ITAttFill TH2F where
setFillColor = xform1 c_th2f_setfillcolor
setFillStyle = xform1 c_th2f_setfillstyle
instance ITAttFill TH2D where
setFillColor = xform1 c_th2d_setfillcolor
setFillStyle = xform1 c_th2d_setfillstyle
instance ITAttFill TH2C where
setFillColor = xform1 c_th2c_setfillcolor
setFillStyle = xform1 c_th2c_setfillstyle
instance ITAttFill TH1S where
setFillColor = xform1 c_th1s_setfillcolor
setFillStyle = xform1 c_th1s_setfillstyle
instance ITAttFill TH1I where
setFillColor = xform1 c_th1i_setfillcolor
setFillStyle = xform1 c_th1i_setfillstyle
instance ITAttFill TH1F where
setFillColor = xform1 c_th1f_setfillcolor
setFillStyle = xform1 c_th1f_setfillstyle
instance ITAttFill TH1D where
setFillColor = xform1 c_th1d_setfillcolor
setFillStyle = xform1 c_th1d_setfillstyle
instance ITAttFill TH1C where
setFillColor = xform1 c_th1c_setfillcolor
setFillStyle = xform1 c_th1c_setfillstyle
instance ITAttFill TH3 where
setFillColor = xform1 c_th3_setfillcolor
setFillStyle = xform1 c_th3_setfillstyle
instance ITAttFill TH2 where
setFillColor = xform1 c_th2_setfillcolor
setFillStyle = xform1 c_th2_setfillstyle
instance ITAttFill TH1 where
setFillColor = xform1 c_th1_setfillcolor
setFillStyle = xform1 c_th1_setfillstyle
instance ITAttFill TBranch where
setFillColor = xform1 c_tbranch_setfillcolor
setFillStyle = xform1 c_tbranch_setfillstyle
instance ITAttFill TEfficiency where
setFillColor = xform1 c_tefficiency_setfillcolor
setFillStyle = xform1 c_tefficiency_setfillstyle
instance ITAttFill TCurlyArc where
setFillColor = xform1 c_tcurlyarc_setfillcolor
setFillStyle = xform1 c_tcurlyarc_setfillstyle
instance ITAttFill TCurlyLine where
setFillColor = xform1 c_tcurlyline_setfillcolor
setFillStyle = xform1 c_tcurlyline_setfillstyle
instance ITAttFill TPolyLine where
setFillColor = xform1 c_tpolyline_setfillcolor
setFillStyle = xform1 c_tpolyline_setfillstyle
instance ITAttFill TTreeSQL where
setFillColor = xform1 c_ttreesql_setfillcolor
setFillStyle = xform1 c_ttreesql_setfillstyle
instance ITAttFill TNtupleD where
setFillColor = xform1 c_tntupled_setfillcolor
setFillStyle = xform1 c_tntupled_setfillstyle
instance ITAttFill TNtuple where
setFillColor = xform1 c_tntuple_setfillcolor
setFillStyle = xform1 c_tntuple_setfillstyle
instance ITAttFill TChain where
setFillColor = xform1 c_tchain_setfillcolor
setFillStyle = xform1 c_tchain_setfillstyle
instance ITAttFill TTree where
setFillColor = xform1 c_ttree_setfillcolor
setFillStyle = xform1 c_ttree_setfillstyle
instance ITAttFill TSliderBox where
setFillColor = xform1 c_tsliderbox_setfillcolor
setFillStyle = xform1 c_tsliderbox_setfillstyle
instance ITAttFill TFrame where
setFillColor = xform1 c_tframe_setfillcolor
setFillStyle = xform1 c_tframe_setfillstyle
instance ITAttFill TWbox where
setFillColor = xform1 c_twbox_setfillcolor
setFillStyle = xform1 c_twbox_setfillstyle
instance ITAttFill TPaveClass where
setFillColor = xform1 c_tpaveclass_setfillcolor
setFillStyle = xform1 c_tpaveclass_setfillstyle
instance ITAttFill TPaveLabel where
setFillColor = xform1 c_tpavelabel_setfillcolor
setFillStyle = xform1 c_tpavelabel_setfillstyle
instance ITAttFill TLegend where
setFillColor = xform1 c_tlegend_setfillcolor
setFillStyle = xform1 c_tlegend_setfillstyle
instance ITAttFill TPavesText where
setFillColor = xform1 c_tpavestext_setfillcolor
setFillStyle = xform1 c_tpavestext_setfillstyle
instance ITAttFill TPaveStats where
setFillColor = xform1 c_tpavestats_setfillcolor
setFillStyle = xform1 c_tpavestats_setfillstyle
instance ITAttFill TDiamond where
setFillColor = xform1 c_tdiamond_setfillcolor
setFillStyle = xform1 c_tdiamond_setfillstyle
instance ITAttFill TPaveText where
setFillColor = xform1 c_tpavetext_setfillcolor
setFillStyle = xform1 c_tpavetext_setfillstyle
instance ITAttFill TPave where
setFillColor = xform1 c_tpave_setfillcolor
setFillStyle = xform1 c_tpave_setfillstyle
instance ITAttFill TBox where
setFillColor = xform1 c_tbox_setfillcolor
setFillStyle = xform1 c_tbox_setfillstyle
instance ITAttFill TXTRU where
setFillColor = xform1 c_txtru_setfillcolor
setFillStyle = xform1 c_txtru_setfillstyle
instance ITAttFill TSPHE where
setFillColor = xform1 c_tsphe_setfillcolor
setFillStyle = xform1 c_tsphe_setfillstyle
instance ITAttFill TPCON where
setFillColor = xform1 c_tpcon_setfillcolor
setFillStyle = xform1 c_tpcon_setfillstyle
instance ITAttFill TTUBE where
setFillColor = xform1 c_ttube_setfillcolor
setFillStyle = xform1 c_ttube_setfillstyle
instance ITAttFill TBRIK where
setFillColor = xform1 c_tbrik_setfillcolor
setFillStyle = xform1 c_tbrik_setfillstyle
instance ITAttFill TShape where
setFillColor = xform1 c_tshape_setfillcolor
setFillStyle = xform1 c_tshape_setfillstyle
instance ITAttFill TArrow where
setFillColor = xform1 c_tarrow_setfillcolor
setFillStyle = xform1 c_tarrow_setfillstyle
instance ITAttFill TCrown where
setFillColor = xform1 c_tcrown_setfillcolor
setFillStyle = xform1 c_tcrown_setfillstyle
instance ITAttFill TArc where
setFillColor = xform1 c_tarc_setfillcolor
setFillStyle = xform1 c_tarc_setfillstyle
instance ITAttFill TEllipse where
setFillColor = xform1 c_tellipse_setfillcolor
setFillStyle = xform1 c_tellipse_setfillstyle
instance ITAttFill TGraphQQ where
setFillColor = xform1 c_tgraphqq_setfillcolor
setFillStyle = xform1 c_tgraphqq_setfillstyle
instance ITAttFill TGraphPolar where
setFillColor = xform1 c_tgraphpolar_setfillcolor
setFillStyle = xform1 c_tgraphpolar_setfillstyle
instance ITAttFill TGraphErrors where
setFillColor = xform1 c_tgrapherrors_setfillcolor
setFillStyle = xform1 c_tgrapherrors_setfillstyle
instance ITAttFill TGraphBentErrors where
setFillColor = xform1 c_tgraphbenterrors_setfillcolor
setFillStyle = xform1 c_tgraphbenterrors_setfillstyle
instance ITAttFill TCutG where
setFillColor = xform1 c_tcutg_setfillcolor
setFillStyle = xform1 c_tcutg_setfillstyle
instance ITAttFill TGraphAsymmErrors where
setFillColor = xform1 c_tgraphasymmerrors_setfillcolor
setFillStyle = xform1 c_tgraphasymmerrors_setfillstyle
instance ITAttFill TGraph where
setFillColor = xform1 c_tgraph_setfillcolor
setFillStyle = xform1 c_tgraph_setfillstyle
instance ITAttFill TF1 where
setFillColor = xform1 c_tf1_setfillcolor
setFillStyle = xform1 c_tf1_setfillstyle
instance ITAttLine TSlider where
setLineColor = xform1 c_tslider_setlinecolor
instance ITAttLine TEvePad where
setLineColor = xform1 c_tevepad_setlinecolor
instance ITAttLine TInspectCanvas where
setLineColor = xform1 c_tinspectcanvas_setlinecolor
instance ITAttLine TDialogCanvas where
setLineColor = xform1 c_tdialogcanvas_setlinecolor
instance ITAttLine TCanvas where
setLineColor = xform1 c_tcanvas_setlinecolor
instance ITAttLine TGroupButton where
setLineColor = xform1 c_tgroupbutton_setlinecolor
instance ITAttLine TButton where
setLineColor = xform1 c_tbutton_setlinecolor
instance ITAttLine TPad where
setLineColor = xform1 c_tpad_setlinecolor
instance ITAttLine TVirtualPad where
setLineColor = xform1 c_tvirtualpad_setlinecolor
instance ITAttLine TH3S where
setLineColor = xform1 c_th3s_setlinecolor
instance ITAttLine TH3I where
setLineColor = xform1 c_th3i_setlinecolor
instance ITAttLine TH3F where
setLineColor = xform1 c_th3f_setlinecolor
instance ITAttLine TH3D where
setLineColor = xform1 c_th3d_setlinecolor
instance ITAttLine TH3C where
setLineColor = xform1 c_th3c_setlinecolor
instance ITAttLine TH2S where
setLineColor = xform1 c_th2s_setlinecolor
instance ITAttLine TH2Poly where
setLineColor = xform1 c_th2poly_setlinecolor
instance ITAttLine TH2I where
setLineColor = xform1 c_th2i_setlinecolor
instance ITAttLine TH2F where
setLineColor = xform1 c_th2f_setlinecolor
instance ITAttLine TH2D where
setLineColor = xform1 c_th2d_setlinecolor
instance ITAttLine TH2C where
setLineColor = xform1 c_th2c_setlinecolor
instance ITAttLine TH1S where
setLineColor = xform1 c_th1s_setlinecolor
instance ITAttLine TH1I where
setLineColor = xform1 c_th1i_setlinecolor
instance ITAttLine TH1F where
setLineColor = xform1 c_th1f_setlinecolor
instance ITAttLine TH1D where
setLineColor = xform1 c_th1d_setlinecolor
instance ITAttLine TH1C where
setLineColor = xform1 c_th1c_setlinecolor
instance ITAttLine TH3 where
setLineColor = xform1 c_th3_setlinecolor
instance ITAttLine TH2 where
setLineColor = xform1 c_th2_setlinecolor
instance ITAttLine TH1 where
setLineColor = xform1 c_th1_setlinecolor
instance ITAttLine TLatex where
setLineColor = xform1 c_tlatex_setlinecolor
instance ITAttLine TEfficiency where
setLineColor = xform1 c_tefficiency_setlinecolor
instance ITAttLine TCurlyArc where
setLineColor = xform1 c_tcurlyarc_setlinecolor
instance ITAttLine TCurlyLine where
setLineColor = xform1 c_tcurlyline_setlinecolor
instance ITAttLine TPolyLine where
setLineColor = xform1 c_tpolyline_setlinecolor
instance ITAttLine TTreeSQL where
setLineColor = xform1 c_ttreesql_setlinecolor
instance ITAttLine TNtupleD where
setLineColor = xform1 c_tntupled_setlinecolor
instance ITAttLine TNtuple where
setLineColor = xform1 c_tntuple_setlinecolor
instance ITAttLine TChain where
setLineColor = xform1 c_tchain_setlinecolor
instance ITAttLine TTree where
setLineColor = xform1 c_ttree_setlinecolor
instance ITAttLine TSliderBox where
setLineColor = xform1 c_tsliderbox_setlinecolor
instance ITAttLine TFrame where
setLineColor = xform1 c_tframe_setlinecolor
instance ITAttLine TWbox where
setLineColor = xform1 c_twbox_setlinecolor
instance ITAttLine TPaveClass where
setLineColor = xform1 c_tpaveclass_setlinecolor
instance ITAttLine TPaveLabel where
setLineColor = xform1 c_tpavelabel_setlinecolor
instance ITAttLine TLegend where
setLineColor = xform1 c_tlegend_setlinecolor
instance ITAttLine TPavesText where
setLineColor = xform1 c_tpavestext_setlinecolor
instance ITAttLine TPaveStats where
setLineColor = xform1 c_tpavestats_setlinecolor
instance ITAttLine TDiamond where
setLineColor = xform1 c_tdiamond_setlinecolor
instance ITAttLine TPaveText where
setLineColor = xform1 c_tpavetext_setlinecolor
instance ITAttLine TPave where
setLineColor = xform1 c_tpave_setlinecolor
instance ITAttLine TBox where
setLineColor = xform1 c_tbox_setlinecolor
instance ITAttLine TXTRU where
setLineColor = xform1 c_txtru_setlinecolor
instance ITAttLine TSPHE where
setLineColor = xform1 c_tsphe_setlinecolor
instance ITAttLine TPCON where
setLineColor = xform1 c_tpcon_setlinecolor
instance ITAttLine TTUBE where
setLineColor = xform1 c_ttube_setlinecolor
instance ITAttLine TBRIK where
setLineColor = xform1 c_tbrik_setlinecolor
instance ITAttLine TShape where
setLineColor = xform1 c_tshape_setlinecolor
instance ITAttLine TGaxis where
setLineColor = xform1 c_tgaxis_setlinecolor
instance ITAttLine TArrow where
setLineColor = xform1 c_tarrow_setlinecolor
instance ITAttLine TLine where
setLineColor = xform1 c_tline_setlinecolor
instance ITAttLine TCrown where
setLineColor = xform1 c_tcrown_setlinecolor
instance ITAttLine TArc where
setLineColor = xform1 c_tarc_setlinecolor
instance ITAttLine TEllipse where
setLineColor = xform1 c_tellipse_setlinecolor
instance ITAttLine TGraphQQ where
setLineColor = xform1 c_tgraphqq_setlinecolor
instance ITAttLine TGraphPolar where
setLineColor = xform1 c_tgraphpolar_setlinecolor
instance ITAttLine TGraphErrors where
setLineColor = xform1 c_tgrapherrors_setlinecolor
instance ITAttLine TGraphBentErrors where
setLineColor = xform1 c_tgraphbenterrors_setlinecolor
instance ITAttLine TCutG where
setLineColor = xform1 c_tcutg_setlinecolor
instance ITAttLine TGraphAsymmErrors where
setLineColor = xform1 c_tgraphasymmerrors_setlinecolor
instance ITAttLine TGraph where
setLineColor = xform1 c_tgraph_setlinecolor
instance ITAttLine TF1 where
setLineColor = xform1 c_tf1_setlinecolor
instance ITAttMarker TH3S where
instance ITAttMarker TH3I where
instance ITAttMarker TH3F where
instance ITAttMarker TH3D where
instance ITAttMarker TH3C where
instance ITAttMarker TH2S where
instance ITAttMarker TH2Poly where
instance ITAttMarker TH2I where
instance ITAttMarker TH2F where
instance ITAttMarker TH2D where
instance ITAttMarker TH2C where
instance ITAttMarker TH1S where
instance ITAttMarker TH1I where
instance ITAttMarker TH1F where
instance ITAttMarker TH1D where
instance ITAttMarker TH1C where
instance ITAttMarker TH3 where
instance ITAttMarker TH2 where
instance ITAttMarker TH1 where
instance ITAttMarker TEfficiency where
instance ITAttMarker TTreeSQL where
instance ITAttMarker TNtupleD where
instance ITAttMarker TNtuple where
instance ITAttMarker TChain where
instance ITAttMarker TTree where
instance ITAttMarker TGraphQQ where
instance ITAttMarker TGraphPolar where
instance ITAttMarker TGraphErrors where
instance ITAttMarker TGraphBentErrors where
instance ITAttMarker TCutG where
instance ITAttMarker TGraphAsymmErrors where
instance ITAttMarker TGraph where
instance ITAttPad TSlider where
instance ITAttPad TEvePad where
instance ITAttPad TInspectCanvas where
instance ITAttPad TDialogCanvas where
instance ITAttPad TCanvas where
instance ITAttPad TGroupButton where
instance ITAttPad TButton where
instance ITAttPad TPad where
instance ITAttPad TVirtualPad where
instance ITAttText TInspectCanvas where
setTextColor = xform1 c_tinspectcanvas_settextcolor
setTextAlign = xform1 c_tinspectcanvas_settextalign
setTextSize = xform1 c_tinspectcanvas_settextsize
instance ITAttText TDialogCanvas where
setTextColor = xform1 c_tdialogcanvas_settextcolor
setTextAlign = xform1 c_tdialogcanvas_settextalign
setTextSize = xform1 c_tdialogcanvas_settextsize
instance ITAttText TGroupButton where
setTextColor = xform1 c_tgroupbutton_settextcolor
setTextAlign = xform1 c_tgroupbutton_settextalign
setTextSize = xform1 c_tgroupbutton_settextsize
instance ITAttText TButton where
setTextColor = xform1 c_tbutton_settextcolor
setTextAlign = xform1 c_tbutton_settextalign
setTextSize = xform1 c_tbutton_settextsize
instance ITAttText TText where
setTextColor = xform1 c_ttext_settextcolor
setTextAlign = xform1 c_ttext_settextalign
setTextSize = xform1 c_ttext_settextsize
instance ITAttText TLatex where
setTextColor = xform1 c_tlatex_settextcolor
setTextAlign = xform1 c_tlatex_settextalign
setTextSize = xform1 c_tlatex_settextsize
instance ITAttText TPaveClass where
setTextColor = xform1 c_tpaveclass_settextcolor
setTextAlign = xform1 c_tpaveclass_settextalign
setTextSize = xform1 c_tpaveclass_settextsize
instance ITAttText TPaveLabel where
setTextColor = xform1 c_tpavelabel_settextcolor
setTextAlign = xform1 c_tpavelabel_settextalign
setTextSize = xform1 c_tpavelabel_settextsize
instance ITAttText TLegend where
setTextColor = xform1 c_tlegend_settextcolor
setTextAlign = xform1 c_tlegend_settextalign
setTextSize = xform1 c_tlegend_settextsize
instance ITAttText TPavesText where
setTextColor = xform1 c_tpavestext_settextcolor
setTextAlign = xform1 c_tpavestext_settextalign
setTextSize = xform1 c_tpavestext_settextsize
instance ITAttText TPaveStats where
setTextColor = xform1 c_tpavestats_settextcolor
setTextAlign = xform1 c_tpavestats_settextalign
setTextSize = xform1 c_tpavestats_settextsize
instance ITAttText TDiamond where
setTextColor = xform1 c_tdiamond_settextcolor
setTextAlign = xform1 c_tdiamond_settextalign
setTextSize = xform1 c_tdiamond_settextsize
instance ITAttText TPaveText where
setTextColor = xform1 c_tpavetext_settextcolor
setTextAlign = xform1 c_tpavetext_settextalign
setTextSize = xform1 c_tpavetext_settextsize
instance ITAttText TGaxis where
setTextColor = xform1 c_tgaxis_settextcolor
setTextAlign = xform1 c_tgaxis_settextalign
setTextSize = xform1 c_tgaxis_settextsize
instance ITBox TSliderBox where
instance ITBox TFrame where
instance ITBox TWbox where
instance ITBox TPaveClass where
instance ITBox TPaveLabel where
instance ITBox TLegend where
instance ITBox TPavesText where
instance ITBox TPaveStats where
instance ITBox TDiamond where
instance ITBox TPaveText where
instance ITBox TPave where
instance ITButton TGroupButton where
instance ITCanvas TInspectCanvas where
instance ITCanvas TDialogCanvas where
instance ITCurlyLine TCurlyArc where
instance ITDictionary TClass where
instance ITDirectory TFile where
close = xform1 c_tfile_close
get = xform1 c_tfile_get
instance ITDirectory TDirectoryFile where
close = xform1 c_tdirectoryfile_close
get = xform1 c_tdirectoryfile_get
instance ITDirectoryFile TFile where
instance ITEllipse TCrown where
instance ITEllipse TArc where
instance ITFormula TF1 where
getParameter = xform1 c_tf1_getparameter
setParameter = xform2 c_tf1_setparameter
instance ITGraph TGraphQQ where
instance ITGraph TGraphPolar where
instance ITGraph TGraphErrors where
instance ITGraph TGraphBentErrors where
instance ITGraph TCutG where
instance ITGraph TGraphAsymmErrors where
instance ITGraphErrors TGraphPolar where
instance ITH1 TH3S where
add = xform2 c_th3s_add
addBinContent = xform2 c_th3s_addbincontent
chi2Test = xform3 c_th3s_chi2test
computeIntegral = xform0 c_th3s_computeintegral
directoryAutoAdd = xform1 c_th3s_directoryautoadd
distancetoPrimitive = xform2 c_th3s_distancetoprimitive
divide = xform5 c_th3s_divide
drawCopy = xform1 c_th3s_drawcopy
drawNormalized = xform2 c_th3s_drawnormalized
drawPanel = xform0 c_th3s_drawpanel
bufferEmpty = xform1 c_th3s_bufferempty
eval = xform2 c_th3s_eval
executeEvent = xform3 c_th3s_executeevent
fFT = xform2 c_th3s_fft
fill1 = xform1 c_th3s_fill1
fillN = xform4 c_th3s_filln
fillRandom = xform2 c_th3s_fillrandom
findBin = xform3 c_th3s_findbin
findFixBin = xform3 c_th3s_findfixbin
findFirstBinAbove = xform2 c_th3s_findfirstbinabove
findLastBinAbove = xform2 c_th3s_findlastbinabove
fitPanel = xform0 c_th3s_fitpanel
getNdivisions = xform1 c_th3s_getndivisions
getAxisColor = xform1 c_th3s_getaxiscolor
getLabelColor = xform1 c_th3s_getlabelcolor
getLabelFont = xform1 c_th3s_getlabelfont
getLabelOffset = xform1 c_th3s_getlabeloffset
getLabelSize = xform1 c_th3s_getlabelsize
getTitleFont = xform1 c_th3s_gettitlefont
getTitleOffset = xform1 c_th3s_gettitleoffset
getTitleSize = xform1 c_th3s_gettitlesize
getTickLength = xform1 c_th3s_getticklength
getBarOffset = xform0 c_th3s_getbaroffset
getBarWidth = xform0 c_th3s_getbarwidth
getContour = xform1 c_th3s_getcontour
getContourLevel = xform1 c_th3s_getcontourlevel
getContourLevelPad = xform1 c_th3s_getcontourlevelpad
getBin = xform3 c_th3s_getbin
getBinCenter = xform1 c_th3s_getbincenter
getBinContent1 = xform1 c_th3s_getbincontent1
getBinContent2 = xform2 c_th3s_getbincontent2
getBinContent3 = xform3 c_th3s_getbincontent3
getBinError1 = xform1 c_th3s_getbinerror1
getBinError2 = xform2 c_th3s_getbinerror2
getBinError3 = xform3 c_th3s_getbinerror3
getBinLowEdge = xform1 c_th3s_getbinlowedge
getBinWidth = xform1 c_th3s_getbinwidth
getCellContent = xform2 c_th3s_getcellcontent
getCellError = xform2 c_th3s_getcellerror
instance ITH1 TH3I where
add = xform2 c_th3i_add
addBinContent = xform2 c_th3i_addbincontent
chi2Test = xform3 c_th3i_chi2test
computeIntegral = xform0 c_th3i_computeintegral
directoryAutoAdd = xform1 c_th3i_directoryautoadd
distancetoPrimitive = xform2 c_th3i_distancetoprimitive
divide = xform5 c_th3i_divide
drawCopy = xform1 c_th3i_drawcopy
drawNormalized = xform2 c_th3i_drawnormalized
drawPanel = xform0 c_th3i_drawpanel
bufferEmpty = xform1 c_th3i_bufferempty
eval = xform2 c_th3i_eval
executeEvent = xform3 c_th3i_executeevent
fFT = xform2 c_th3i_fft
fill1 = xform1 c_th3i_fill1
fillN = xform4 c_th3i_filln
fillRandom = xform2 c_th3i_fillrandom
findBin = xform3 c_th3i_findbin
findFixBin = xform3 c_th3i_findfixbin
findFirstBinAbove = xform2 c_th3i_findfirstbinabove
findLastBinAbove = xform2 c_th3i_findlastbinabove
fitPanel = xform0 c_th3i_fitpanel
getNdivisions = xform1 c_th3i_getndivisions
getAxisColor = xform1 c_th3i_getaxiscolor
getLabelColor = xform1 c_th3i_getlabelcolor
getLabelFont = xform1 c_th3i_getlabelfont
getLabelOffset = xform1 c_th3i_getlabeloffset
getLabelSize = xform1 c_th3i_getlabelsize
getTitleFont = xform1 c_th3i_gettitlefont
getTitleOffset = xform1 c_th3i_gettitleoffset
getTitleSize = xform1 c_th3i_gettitlesize
getTickLength = xform1 c_th3i_getticklength
getBarOffset = xform0 c_th3i_getbaroffset
getBarWidth = xform0 c_th3i_getbarwidth
getContour = xform1 c_th3i_getcontour
getContourLevel = xform1 c_th3i_getcontourlevel
getContourLevelPad = xform1 c_th3i_getcontourlevelpad
getBin = xform3 c_th3i_getbin
getBinCenter = xform1 c_th3i_getbincenter
getBinContent1 = xform1 c_th3i_getbincontent1
getBinContent2 = xform2 c_th3i_getbincontent2
getBinContent3 = xform3 c_th3i_getbincontent3
getBinError1 = xform1 c_th3i_getbinerror1
getBinError2 = xform2 c_th3i_getbinerror2
getBinError3 = xform3 c_th3i_getbinerror3
getBinLowEdge = xform1 c_th3i_getbinlowedge
getBinWidth = xform1 c_th3i_getbinwidth
getCellContent = xform2 c_th3i_getcellcontent
getCellError = xform2 c_th3i_getcellerror
instance ITH1 TH3F where
add = xform2 c_th3f_add
addBinContent = xform2 c_th3f_addbincontent
chi2Test = xform3 c_th3f_chi2test
computeIntegral = xform0 c_th3f_computeintegral
directoryAutoAdd = xform1 c_th3f_directoryautoadd
distancetoPrimitive = xform2 c_th3f_distancetoprimitive
divide = xform5 c_th3f_divide
drawCopy = xform1 c_th3f_drawcopy
drawNormalized = xform2 c_th3f_drawnormalized
drawPanel = xform0 c_th3f_drawpanel
bufferEmpty = xform1 c_th3f_bufferempty
eval = xform2 c_th3f_eval
executeEvent = xform3 c_th3f_executeevent
fFT = xform2 c_th3f_fft
fill1 = xform1 c_th3f_fill1
fillN = xform4 c_th3f_filln
fillRandom = xform2 c_th3f_fillrandom
findBin = xform3 c_th3f_findbin
findFixBin = xform3 c_th3f_findfixbin
findFirstBinAbove = xform2 c_th3f_findfirstbinabove
findLastBinAbove = xform2 c_th3f_findlastbinabove
fitPanel = xform0 c_th3f_fitpanel
getNdivisions = xform1 c_th3f_getndivisions
getAxisColor = xform1 c_th3f_getaxiscolor
getLabelColor = xform1 c_th3f_getlabelcolor
getLabelFont = xform1 c_th3f_getlabelfont
getLabelOffset = xform1 c_th3f_getlabeloffset
getLabelSize = xform1 c_th3f_getlabelsize
getTitleFont = xform1 c_th3f_gettitlefont
getTitleOffset = xform1 c_th3f_gettitleoffset
getTitleSize = xform1 c_th3f_gettitlesize
getTickLength = xform1 c_th3f_getticklength
getBarOffset = xform0 c_th3f_getbaroffset
getBarWidth = xform0 c_th3f_getbarwidth
getContour = xform1 c_th3f_getcontour
getContourLevel = xform1 c_th3f_getcontourlevel
getContourLevelPad = xform1 c_th3f_getcontourlevelpad
getBin = xform3 c_th3f_getbin
getBinCenter = xform1 c_th3f_getbincenter
getBinContent1 = xform1 c_th3f_getbincontent1
getBinContent2 = xform2 c_th3f_getbincontent2
getBinContent3 = xform3 c_th3f_getbincontent3
getBinError1 = xform1 c_th3f_getbinerror1
getBinError2 = xform2 c_th3f_getbinerror2
getBinError3 = xform3 c_th3f_getbinerror3
getBinLowEdge = xform1 c_th3f_getbinlowedge
getBinWidth = xform1 c_th3f_getbinwidth
getCellContent = xform2 c_th3f_getcellcontent
getCellError = xform2 c_th3f_getcellerror
instance ITH1 TH3D where
add = xform2 c_th3d_add
addBinContent = xform2 c_th3d_addbincontent
chi2Test = xform3 c_th3d_chi2test
computeIntegral = xform0 c_th3d_computeintegral
directoryAutoAdd = xform1 c_th3d_directoryautoadd
distancetoPrimitive = xform2 c_th3d_distancetoprimitive
divide = xform5 c_th3d_divide
drawCopy = xform1 c_th3d_drawcopy
drawNormalized = xform2 c_th3d_drawnormalized
drawPanel = xform0 c_th3d_drawpanel
bufferEmpty = xform1 c_th3d_bufferempty
eval = xform2 c_th3d_eval
executeEvent = xform3 c_th3d_executeevent
fFT = xform2 c_th3d_fft
fill1 = xform1 c_th3d_fill1
fillN = xform4 c_th3d_filln
fillRandom = xform2 c_th3d_fillrandom
findBin = xform3 c_th3d_findbin
findFixBin = xform3 c_th3d_findfixbin
findFirstBinAbove = xform2 c_th3d_findfirstbinabove
findLastBinAbove = xform2 c_th3d_findlastbinabove
fitPanel = xform0 c_th3d_fitpanel
getNdivisions = xform1 c_th3d_getndivisions
getAxisColor = xform1 c_th3d_getaxiscolor
getLabelColor = xform1 c_th3d_getlabelcolor
getLabelFont = xform1 c_th3d_getlabelfont
getLabelOffset = xform1 c_th3d_getlabeloffset
getLabelSize = xform1 c_th3d_getlabelsize
getTitleFont = xform1 c_th3d_gettitlefont
getTitleOffset = xform1 c_th3d_gettitleoffset
getTitleSize = xform1 c_th3d_gettitlesize
getTickLength = xform1 c_th3d_getticklength
getBarOffset = xform0 c_th3d_getbaroffset
getBarWidth = xform0 c_th3d_getbarwidth
getContour = xform1 c_th3d_getcontour
getContourLevel = xform1 c_th3d_getcontourlevel
getContourLevelPad = xform1 c_th3d_getcontourlevelpad
getBin = xform3 c_th3d_getbin
getBinCenter = xform1 c_th3d_getbincenter
getBinContent1 = xform1 c_th3d_getbincontent1
getBinContent2 = xform2 c_th3d_getbincontent2
getBinContent3 = xform3 c_th3d_getbincontent3
getBinError1 = xform1 c_th3d_getbinerror1
getBinError2 = xform2 c_th3d_getbinerror2
getBinError3 = xform3 c_th3d_getbinerror3
getBinLowEdge = xform1 c_th3d_getbinlowedge
getBinWidth = xform1 c_th3d_getbinwidth
getCellContent = xform2 c_th3d_getcellcontent
getCellError = xform2 c_th3d_getcellerror
instance ITH1 TH3C where
add = xform2 c_th3c_add
addBinContent = xform2 c_th3c_addbincontent
chi2Test = xform3 c_th3c_chi2test
computeIntegral = xform0 c_th3c_computeintegral
directoryAutoAdd = xform1 c_th3c_directoryautoadd
distancetoPrimitive = xform2 c_th3c_distancetoprimitive
divide = xform5 c_th3c_divide
drawCopy = xform1 c_th3c_drawcopy
drawNormalized = xform2 c_th3c_drawnormalized
drawPanel = xform0 c_th3c_drawpanel
bufferEmpty = xform1 c_th3c_bufferempty
eval = xform2 c_th3c_eval
executeEvent = xform3 c_th3c_executeevent
fFT = xform2 c_th3c_fft
fill1 = xform1 c_th3c_fill1
fillN = xform4 c_th3c_filln
fillRandom = xform2 c_th3c_fillrandom
findBin = xform3 c_th3c_findbin
findFixBin = xform3 c_th3c_findfixbin
findFirstBinAbove = xform2 c_th3c_findfirstbinabove
findLastBinAbove = xform2 c_th3c_findlastbinabove
fitPanel = xform0 c_th3c_fitpanel
getNdivisions = xform1 c_th3c_getndivisions
getAxisColor = xform1 c_th3c_getaxiscolor
getLabelColor = xform1 c_th3c_getlabelcolor
getLabelFont = xform1 c_th3c_getlabelfont
getLabelOffset = xform1 c_th3c_getlabeloffset
getLabelSize = xform1 c_th3c_getlabelsize
getTitleFont = xform1 c_th3c_gettitlefont
getTitleOffset = xform1 c_th3c_gettitleoffset
getTitleSize = xform1 c_th3c_gettitlesize
getTickLength = xform1 c_th3c_getticklength
getBarOffset = xform0 c_th3c_getbaroffset
getBarWidth = xform0 c_th3c_getbarwidth
getContour = xform1 c_th3c_getcontour
getContourLevel = xform1 c_th3c_getcontourlevel
getContourLevelPad = xform1 c_th3c_getcontourlevelpad
getBin = xform3 c_th3c_getbin
getBinCenter = xform1 c_th3c_getbincenter
getBinContent1 = xform1 c_th3c_getbincontent1
getBinContent2 = xform2 c_th3c_getbincontent2
getBinContent3 = xform3 c_th3c_getbincontent3
getBinError1 = xform1 c_th3c_getbinerror1
getBinError2 = xform2 c_th3c_getbinerror2
getBinError3 = xform3 c_th3c_getbinerror3
getBinLowEdge = xform1 c_th3c_getbinlowedge
getBinWidth = xform1 c_th3c_getbinwidth
getCellContent = xform2 c_th3c_getcellcontent
getCellError = xform2 c_th3c_getcellerror
instance ITH1 TH2S where
add = xform2 c_th2s_add
addBinContent = xform2 c_th2s_addbincontent
chi2Test = xform3 c_th2s_chi2test
computeIntegral = xform0 c_th2s_computeintegral
directoryAutoAdd = xform1 c_th2s_directoryautoadd
distancetoPrimitive = xform2 c_th2s_distancetoprimitive
divide = xform5 c_th2s_divide
drawCopy = xform1 c_th2s_drawcopy
drawNormalized = xform2 c_th2s_drawnormalized
drawPanel = xform0 c_th2s_drawpanel
bufferEmpty = xform1 c_th2s_bufferempty
eval = xform2 c_th2s_eval
executeEvent = xform3 c_th2s_executeevent
fFT = xform2 c_th2s_fft
fill1 = xform1 c_th2s_fill1
fillN = xform4 c_th2s_filln
fillRandom = xform2 c_th2s_fillrandom
findBin = xform3 c_th2s_findbin
findFixBin = xform3 c_th2s_findfixbin
findFirstBinAbove = xform2 c_th2s_findfirstbinabove
findLastBinAbove = xform2 c_th2s_findlastbinabove
fitPanel = xform0 c_th2s_fitpanel
getNdivisions = xform1 c_th2s_getndivisions
getAxisColor = xform1 c_th2s_getaxiscolor
getLabelColor = xform1 c_th2s_getlabelcolor
getLabelFont = xform1 c_th2s_getlabelfont
getLabelOffset = xform1 c_th2s_getlabeloffset
getLabelSize = xform1 c_th2s_getlabelsize
getTitleFont = xform1 c_th2s_gettitlefont
getTitleOffset = xform1 c_th2s_gettitleoffset
getTitleSize = xform1 c_th2s_gettitlesize
getTickLength = xform1 c_th2s_getticklength
getBarOffset = xform0 c_th2s_getbaroffset
getBarWidth = xform0 c_th2s_getbarwidth
getContour = xform1 c_th2s_getcontour
getContourLevel = xform1 c_th2s_getcontourlevel
getContourLevelPad = xform1 c_th2s_getcontourlevelpad
getBin = xform3 c_th2s_getbin
getBinCenter = xform1 c_th2s_getbincenter
getBinContent1 = xform1 c_th2s_getbincontent1
getBinContent2 = xform2 c_th2s_getbincontent2
getBinContent3 = xform3 c_th2s_getbincontent3
getBinError1 = xform1 c_th2s_getbinerror1
getBinError2 = xform2 c_th2s_getbinerror2
getBinError3 = xform3 c_th2s_getbinerror3
getBinLowEdge = xform1 c_th2s_getbinlowedge
getBinWidth = xform1 c_th2s_getbinwidth
getCellContent = xform2 c_th2s_getcellcontent
getCellError = xform2 c_th2s_getcellerror
instance ITH1 TH2Poly where
add = xform2 c_th2poly_add
addBinContent = xform2 c_th2poly_addbincontent
chi2Test = xform3 c_th2poly_chi2test
computeIntegral = xform0 c_th2poly_computeintegral
directoryAutoAdd = xform1 c_th2poly_directoryautoadd
distancetoPrimitive = xform2 c_th2poly_distancetoprimitive
divide = xform5 c_th2poly_divide
drawCopy = xform1 c_th2poly_drawcopy
drawNormalized = xform2 c_th2poly_drawnormalized
drawPanel = xform0 c_th2poly_drawpanel
bufferEmpty = xform1 c_th2poly_bufferempty
eval = xform2 c_th2poly_eval
executeEvent = xform3 c_th2poly_executeevent
fFT = xform2 c_th2poly_fft
fill1 = xform1 c_th2poly_fill1
fillN = xform4 c_th2poly_filln
fillRandom = xform2 c_th2poly_fillrandom
findBin = xform3 c_th2poly_findbin
findFixBin = xform3 c_th2poly_findfixbin
findFirstBinAbove = xform2 c_th2poly_findfirstbinabove
findLastBinAbove = xform2 c_th2poly_findlastbinabove
fitPanel = xform0 c_th2poly_fitpanel
getNdivisions = xform1 c_th2poly_getndivisions
getAxisColor = xform1 c_th2poly_getaxiscolor
getLabelColor = xform1 c_th2poly_getlabelcolor
getLabelFont = xform1 c_th2poly_getlabelfont
getLabelOffset = xform1 c_th2poly_getlabeloffset
getLabelSize = xform1 c_th2poly_getlabelsize
getTitleFont = xform1 c_th2poly_gettitlefont
getTitleOffset = xform1 c_th2poly_gettitleoffset
getTitleSize = xform1 c_th2poly_gettitlesize
getTickLength = xform1 c_th2poly_getticklength
getBarOffset = xform0 c_th2poly_getbaroffset
getBarWidth = xform0 c_th2poly_getbarwidth
getContour = xform1 c_th2poly_getcontour
getContourLevel = xform1 c_th2poly_getcontourlevel
getContourLevelPad = xform1 c_th2poly_getcontourlevelpad
getBin = xform3 c_th2poly_getbin
getBinCenter = xform1 c_th2poly_getbincenter
getBinContent1 = xform1 c_th2poly_getbincontent1
getBinContent2 = xform2 c_th2poly_getbincontent2
getBinContent3 = xform3 c_th2poly_getbincontent3
getBinError1 = xform1 c_th2poly_getbinerror1
getBinError2 = xform2 c_th2poly_getbinerror2
getBinError3 = xform3 c_th2poly_getbinerror3
getBinLowEdge = xform1 c_th2poly_getbinlowedge
getBinWidth = xform1 c_th2poly_getbinwidth
getCellContent = xform2 c_th2poly_getcellcontent
getCellError = xform2 c_th2poly_getcellerror
instance ITH1 TH2I where
add = xform2 c_th2i_add
addBinContent = xform2 c_th2i_addbincontent
chi2Test = xform3 c_th2i_chi2test
computeIntegral = xform0 c_th2i_computeintegral
directoryAutoAdd = xform1 c_th2i_directoryautoadd
distancetoPrimitive = xform2 c_th2i_distancetoprimitive
divide = xform5 c_th2i_divide
drawCopy = xform1 c_th2i_drawcopy
drawNormalized = xform2 c_th2i_drawnormalized
drawPanel = xform0 c_th2i_drawpanel
bufferEmpty = xform1 c_th2i_bufferempty
eval = xform2 c_th2i_eval
executeEvent = xform3 c_th2i_executeevent
fFT = xform2 c_th2i_fft
fill1 = xform1 c_th2i_fill1
fillN = xform4 c_th2i_filln
fillRandom = xform2 c_th2i_fillrandom
findBin = xform3 c_th2i_findbin
findFixBin = xform3 c_th2i_findfixbin
findFirstBinAbove = xform2 c_th2i_findfirstbinabove
findLastBinAbove = xform2 c_th2i_findlastbinabove
fitPanel = xform0 c_th2i_fitpanel
getNdivisions = xform1 c_th2i_getndivisions
getAxisColor = xform1 c_th2i_getaxiscolor
getLabelColor = xform1 c_th2i_getlabelcolor
getLabelFont = xform1 c_th2i_getlabelfont
getLabelOffset = xform1 c_th2i_getlabeloffset
getLabelSize = xform1 c_th2i_getlabelsize
getTitleFont = xform1 c_th2i_gettitlefont
getTitleOffset = xform1 c_th2i_gettitleoffset
getTitleSize = xform1 c_th2i_gettitlesize
getTickLength = xform1 c_th2i_getticklength
getBarOffset = xform0 c_th2i_getbaroffset
getBarWidth = xform0 c_th2i_getbarwidth
getContour = xform1 c_th2i_getcontour
getContourLevel = xform1 c_th2i_getcontourlevel
getContourLevelPad = xform1 c_th2i_getcontourlevelpad
getBin = xform3 c_th2i_getbin
getBinCenter = xform1 c_th2i_getbincenter
getBinContent1 = xform1 c_th2i_getbincontent1
getBinContent2 = xform2 c_th2i_getbincontent2
getBinContent3 = xform3 c_th2i_getbincontent3
getBinError1 = xform1 c_th2i_getbinerror1
getBinError2 = xform2 c_th2i_getbinerror2
getBinError3 = xform3 c_th2i_getbinerror3
getBinLowEdge = xform1 c_th2i_getbinlowedge
getBinWidth = xform1 c_th2i_getbinwidth
getCellContent = xform2 c_th2i_getcellcontent
getCellError = xform2 c_th2i_getcellerror
instance ITH1 TH2F where
add = xform2 c_th2f_add
addBinContent = xform2 c_th2f_addbincontent
chi2Test = xform3 c_th2f_chi2test
computeIntegral = xform0 c_th2f_computeintegral
directoryAutoAdd = xform1 c_th2f_directoryautoadd
distancetoPrimitive = xform2 c_th2f_distancetoprimitive
divide = xform5 c_th2f_divide
drawCopy = xform1 c_th2f_drawcopy
drawNormalized = xform2 c_th2f_drawnormalized
drawPanel = xform0 c_th2f_drawpanel
bufferEmpty = xform1 c_th2f_bufferempty
eval = xform2 c_th2f_eval
executeEvent = xform3 c_th2f_executeevent
fFT = xform2 c_th2f_fft
fill1 = xform1 c_th2f_fill1
fillN = xform4 c_th2f_filln
fillRandom = xform2 c_th2f_fillrandom
findBin = xform3 c_th2f_findbin
findFixBin = xform3 c_th2f_findfixbin
findFirstBinAbove = xform2 c_th2f_findfirstbinabove
findLastBinAbove = xform2 c_th2f_findlastbinabove
fitPanel = xform0 c_th2f_fitpanel
getNdivisions = xform1 c_th2f_getndivisions
getAxisColor = xform1 c_th2f_getaxiscolor
getLabelColor = xform1 c_th2f_getlabelcolor
getLabelFont = xform1 c_th2f_getlabelfont
getLabelOffset = xform1 c_th2f_getlabeloffset
getLabelSize = xform1 c_th2f_getlabelsize
getTitleFont = xform1 c_th2f_gettitlefont
getTitleOffset = xform1 c_th2f_gettitleoffset
getTitleSize = xform1 c_th2f_gettitlesize
getTickLength = xform1 c_th2f_getticklength
getBarOffset = xform0 c_th2f_getbaroffset
getBarWidth = xform0 c_th2f_getbarwidth
getContour = xform1 c_th2f_getcontour
getContourLevel = xform1 c_th2f_getcontourlevel
getContourLevelPad = xform1 c_th2f_getcontourlevelpad
getBin = xform3 c_th2f_getbin
getBinCenter = xform1 c_th2f_getbincenter
getBinContent1 = xform1 c_th2f_getbincontent1
getBinContent2 = xform2 c_th2f_getbincontent2
getBinContent3 = xform3 c_th2f_getbincontent3
getBinError1 = xform1 c_th2f_getbinerror1
getBinError2 = xform2 c_th2f_getbinerror2
getBinError3 = xform3 c_th2f_getbinerror3
getBinLowEdge = xform1 c_th2f_getbinlowedge
getBinWidth = xform1 c_th2f_getbinwidth
getCellContent = xform2 c_th2f_getcellcontent
getCellError = xform2 c_th2f_getcellerror
instance ITH1 TH2D where
add = xform2 c_th2d_add
addBinContent = xform2 c_th2d_addbincontent
chi2Test = xform3 c_th2d_chi2test
computeIntegral = xform0 c_th2d_computeintegral
directoryAutoAdd = xform1 c_th2d_directoryautoadd
distancetoPrimitive = xform2 c_th2d_distancetoprimitive
divide = xform5 c_th2d_divide
drawCopy = xform1 c_th2d_drawcopy
drawNormalized = xform2 c_th2d_drawnormalized
drawPanel = xform0 c_th2d_drawpanel
bufferEmpty = xform1 c_th2d_bufferempty
eval = xform2 c_th2d_eval
executeEvent = xform3 c_th2d_executeevent
fFT = xform2 c_th2d_fft
fill1 = xform1 c_th2d_fill1
fillN = xform4 c_th2d_filln
fillRandom = xform2 c_th2d_fillrandom
findBin = xform3 c_th2d_findbin
findFixBin = xform3 c_th2d_findfixbin
findFirstBinAbove = xform2 c_th2d_findfirstbinabove
findLastBinAbove = xform2 c_th2d_findlastbinabove
fitPanel = xform0 c_th2d_fitpanel
getNdivisions = xform1 c_th2d_getndivisions
getAxisColor = xform1 c_th2d_getaxiscolor
getLabelColor = xform1 c_th2d_getlabelcolor
getLabelFont = xform1 c_th2d_getlabelfont
getLabelOffset = xform1 c_th2d_getlabeloffset
getLabelSize = xform1 c_th2d_getlabelsize
getTitleFont = xform1 c_th2d_gettitlefont
getTitleOffset = xform1 c_th2d_gettitleoffset
getTitleSize = xform1 c_th2d_gettitlesize
getTickLength = xform1 c_th2d_getticklength
getBarOffset = xform0 c_th2d_getbaroffset
getBarWidth = xform0 c_th2d_getbarwidth
getContour = xform1 c_th2d_getcontour
getContourLevel = xform1 c_th2d_getcontourlevel
getContourLevelPad = xform1 c_th2d_getcontourlevelpad
getBin = xform3 c_th2d_getbin
getBinCenter = xform1 c_th2d_getbincenter
getBinContent1 = xform1 c_th2d_getbincontent1
getBinContent2 = xform2 c_th2d_getbincontent2
getBinContent3 = xform3 c_th2d_getbincontent3
getBinError1 = xform1 c_th2d_getbinerror1
getBinError2 = xform2 c_th2d_getbinerror2
getBinError3 = xform3 c_th2d_getbinerror3
getBinLowEdge = xform1 c_th2d_getbinlowedge
getBinWidth = xform1 c_th2d_getbinwidth
getCellContent = xform2 c_th2d_getcellcontent
getCellError = xform2 c_th2d_getcellerror
instance ITH1 TH2C where
add = xform2 c_th2c_add
addBinContent = xform2 c_th2c_addbincontent
chi2Test = xform3 c_th2c_chi2test
computeIntegral = xform0 c_th2c_computeintegral
directoryAutoAdd = xform1 c_th2c_directoryautoadd
distancetoPrimitive = xform2 c_th2c_distancetoprimitive
divide = xform5 c_th2c_divide
drawCopy = xform1 c_th2c_drawcopy
drawNormalized = xform2 c_th2c_drawnormalized
drawPanel = xform0 c_th2c_drawpanel
bufferEmpty = xform1 c_th2c_bufferempty
eval = xform2 c_th2c_eval
executeEvent = xform3 c_th2c_executeevent
fFT = xform2 c_th2c_fft
fill1 = xform1 c_th2c_fill1
fillN = xform4 c_th2c_filln
fillRandom = xform2 c_th2c_fillrandom
findBin = xform3 c_th2c_findbin
findFixBin = xform3 c_th2c_findfixbin
findFirstBinAbove = xform2 c_th2c_findfirstbinabove
findLastBinAbove = xform2 c_th2c_findlastbinabove
fitPanel = xform0 c_th2c_fitpanel
getNdivisions = xform1 c_th2c_getndivisions
getAxisColor = xform1 c_th2c_getaxiscolor
getLabelColor = xform1 c_th2c_getlabelcolor
getLabelFont = xform1 c_th2c_getlabelfont
getLabelOffset = xform1 c_th2c_getlabeloffset
getLabelSize = xform1 c_th2c_getlabelsize
getTitleFont = xform1 c_th2c_gettitlefont
getTitleOffset = xform1 c_th2c_gettitleoffset
getTitleSize = xform1 c_th2c_gettitlesize
getTickLength = xform1 c_th2c_getticklength
getBarOffset = xform0 c_th2c_getbaroffset
getBarWidth = xform0 c_th2c_getbarwidth
getContour = xform1 c_th2c_getcontour
getContourLevel = xform1 c_th2c_getcontourlevel
getContourLevelPad = xform1 c_th2c_getcontourlevelpad
getBin = xform3 c_th2c_getbin
getBinCenter = xform1 c_th2c_getbincenter
getBinContent1 = xform1 c_th2c_getbincontent1
getBinContent2 = xform2 c_th2c_getbincontent2
getBinContent3 = xform3 c_th2c_getbincontent3
getBinError1 = xform1 c_th2c_getbinerror1
getBinError2 = xform2 c_th2c_getbinerror2
getBinError3 = xform3 c_th2c_getbinerror3
getBinLowEdge = xform1 c_th2c_getbinlowedge
getBinWidth = xform1 c_th2c_getbinwidth
getCellContent = xform2 c_th2c_getcellcontent
getCellError = xform2 c_th2c_getcellerror
instance ITH1 TH1S where
add = xform2 c_th1s_add
addBinContent = xform2 c_th1s_addbincontent
chi2Test = xform3 c_th1s_chi2test
computeIntegral = xform0 c_th1s_computeintegral
directoryAutoAdd = xform1 c_th1s_directoryautoadd
distancetoPrimitive = xform2 c_th1s_distancetoprimitive
divide = xform5 c_th1s_divide
drawCopy = xform1 c_th1s_drawcopy
drawNormalized = xform2 c_th1s_drawnormalized
drawPanel = xform0 c_th1s_drawpanel
bufferEmpty = xform1 c_th1s_bufferempty
eval = xform2 c_th1s_eval
executeEvent = xform3 c_th1s_executeevent
fFT = xform2 c_th1s_fft
fill1 = xform1 c_th1s_fill1
fillN = xform4 c_th1s_filln
fillRandom = xform2 c_th1s_fillrandom
findBin = xform3 c_th1s_findbin
findFixBin = xform3 c_th1s_findfixbin
findFirstBinAbove = xform2 c_th1s_findfirstbinabove
findLastBinAbove = xform2 c_th1s_findlastbinabove
fitPanel = xform0 c_th1s_fitpanel
getNdivisions = xform1 c_th1s_getndivisions
getAxisColor = xform1 c_th1s_getaxiscolor
getLabelColor = xform1 c_th1s_getlabelcolor
getLabelFont = xform1 c_th1s_getlabelfont
getLabelOffset = xform1 c_th1s_getlabeloffset
getLabelSize = xform1 c_th1s_getlabelsize
getTitleFont = xform1 c_th1s_gettitlefont
getTitleOffset = xform1 c_th1s_gettitleoffset
getTitleSize = xform1 c_th1s_gettitlesize
getTickLength = xform1 c_th1s_getticklength
getBarOffset = xform0 c_th1s_getbaroffset
getBarWidth = xform0 c_th1s_getbarwidth
getContour = xform1 c_th1s_getcontour
getContourLevel = xform1 c_th1s_getcontourlevel
getContourLevelPad = xform1 c_th1s_getcontourlevelpad
getBin = xform3 c_th1s_getbin
getBinCenter = xform1 c_th1s_getbincenter
getBinContent1 = xform1 c_th1s_getbincontent1
getBinContent2 = xform2 c_th1s_getbincontent2
getBinContent3 = xform3 c_th1s_getbincontent3
getBinError1 = xform1 c_th1s_getbinerror1
getBinError2 = xform2 c_th1s_getbinerror2
getBinError3 = xform3 c_th1s_getbinerror3
getBinLowEdge = xform1 c_th1s_getbinlowedge
getBinWidth = xform1 c_th1s_getbinwidth
getCellContent = xform2 c_th1s_getcellcontent
getCellError = xform2 c_th1s_getcellerror
instance ITH1 TH1I where
add = xform2 c_th1i_add
addBinContent = xform2 c_th1i_addbincontent
chi2Test = xform3 c_th1i_chi2test
computeIntegral = xform0 c_th1i_computeintegral
directoryAutoAdd = xform1 c_th1i_directoryautoadd
distancetoPrimitive = xform2 c_th1i_distancetoprimitive
divide = xform5 c_th1i_divide
drawCopy = xform1 c_th1i_drawcopy
drawNormalized = xform2 c_th1i_drawnormalized
drawPanel = xform0 c_th1i_drawpanel
bufferEmpty = xform1 c_th1i_bufferempty
eval = xform2 c_th1i_eval
executeEvent = xform3 c_th1i_executeevent
fFT = xform2 c_th1i_fft
fill1 = xform1 c_th1i_fill1
fillN = xform4 c_th1i_filln
fillRandom = xform2 c_th1i_fillrandom
findBin = xform3 c_th1i_findbin
findFixBin = xform3 c_th1i_findfixbin
findFirstBinAbove = xform2 c_th1i_findfirstbinabove
findLastBinAbove = xform2 c_th1i_findlastbinabove
fitPanel = xform0 c_th1i_fitpanel
getNdivisions = xform1 c_th1i_getndivisions
getAxisColor = xform1 c_th1i_getaxiscolor
getLabelColor = xform1 c_th1i_getlabelcolor
getLabelFont = xform1 c_th1i_getlabelfont
getLabelOffset = xform1 c_th1i_getlabeloffset
getLabelSize = xform1 c_th1i_getlabelsize
getTitleFont = xform1 c_th1i_gettitlefont
getTitleOffset = xform1 c_th1i_gettitleoffset
getTitleSize = xform1 c_th1i_gettitlesize
getTickLength = xform1 c_th1i_getticklength
getBarOffset = xform0 c_th1i_getbaroffset
getBarWidth = xform0 c_th1i_getbarwidth
getContour = xform1 c_th1i_getcontour
getContourLevel = xform1 c_th1i_getcontourlevel
getContourLevelPad = xform1 c_th1i_getcontourlevelpad
getBin = xform3 c_th1i_getbin
getBinCenter = xform1 c_th1i_getbincenter
getBinContent1 = xform1 c_th1i_getbincontent1
getBinContent2 = xform2 c_th1i_getbincontent2
getBinContent3 = xform3 c_th1i_getbincontent3
getBinError1 = xform1 c_th1i_getbinerror1
getBinError2 = xform2 c_th1i_getbinerror2
getBinError3 = xform3 c_th1i_getbinerror3
getBinLowEdge = xform1 c_th1i_getbinlowedge
getBinWidth = xform1 c_th1i_getbinwidth
getCellContent = xform2 c_th1i_getcellcontent
getCellError = xform2 c_th1i_getcellerror
instance ITH1 TH1F where
add = xform2 c_th1f_add
addBinContent = xform2 c_th1f_addbincontent
chi2Test = xform3 c_th1f_chi2test
computeIntegral = xform0 c_th1f_computeintegral
directoryAutoAdd = xform1 c_th1f_directoryautoadd
distancetoPrimitive = xform2 c_th1f_distancetoprimitive
divide = xform5 c_th1f_divide
drawCopy = xform1 c_th1f_drawcopy
drawNormalized = xform2 c_th1f_drawnormalized
drawPanel = xform0 c_th1f_drawpanel
bufferEmpty = xform1 c_th1f_bufferempty
eval = xform2 c_th1f_eval
executeEvent = xform3 c_th1f_executeevent
fFT = xform2 c_th1f_fft
fill1 = xform1 c_th1f_fill1
fillN = xform4 c_th1f_filln
fillRandom = xform2 c_th1f_fillrandom
findBin = xform3 c_th1f_findbin
findFixBin = xform3 c_th1f_findfixbin
findFirstBinAbove = xform2 c_th1f_findfirstbinabove
findLastBinAbove = xform2 c_th1f_findlastbinabove
fitPanel = xform0 c_th1f_fitpanel
getNdivisions = xform1 c_th1f_getndivisions
getAxisColor = xform1 c_th1f_getaxiscolor
getLabelColor = xform1 c_th1f_getlabelcolor
getLabelFont = xform1 c_th1f_getlabelfont
getLabelOffset = xform1 c_th1f_getlabeloffset
getLabelSize = xform1 c_th1f_getlabelsize
getTitleFont = xform1 c_th1f_gettitlefont
getTitleOffset = xform1 c_th1f_gettitleoffset
getTitleSize = xform1 c_th1f_gettitlesize
getTickLength = xform1 c_th1f_getticklength
getBarOffset = xform0 c_th1f_getbaroffset
getBarWidth = xform0 c_th1f_getbarwidth
getContour = xform1 c_th1f_getcontour
getContourLevel = xform1 c_th1f_getcontourlevel
getContourLevelPad = xform1 c_th1f_getcontourlevelpad
getBin = xform3 c_th1f_getbin
getBinCenter = xform1 c_th1f_getbincenter
getBinContent1 = xform1 c_th1f_getbincontent1
getBinContent2 = xform2 c_th1f_getbincontent2
getBinContent3 = xform3 c_th1f_getbincontent3
getBinError1 = xform1 c_th1f_getbinerror1
getBinError2 = xform2 c_th1f_getbinerror2
getBinError3 = xform3 c_th1f_getbinerror3
getBinLowEdge = xform1 c_th1f_getbinlowedge
getBinWidth = xform1 c_th1f_getbinwidth
getCellContent = xform2 c_th1f_getcellcontent
getCellError = xform2 c_th1f_getcellerror
instance ITH1 TH1D where
add = xform2 c_th1d_add
addBinContent = xform2 c_th1d_addbincontent
chi2Test = xform3 c_th1d_chi2test
computeIntegral = xform0 c_th1d_computeintegral
directoryAutoAdd = xform1 c_th1d_directoryautoadd
distancetoPrimitive = xform2 c_th1d_distancetoprimitive
divide = xform5 c_th1d_divide
drawCopy = xform1 c_th1d_drawcopy
drawNormalized = xform2 c_th1d_drawnormalized
drawPanel = xform0 c_th1d_drawpanel
bufferEmpty = xform1 c_th1d_bufferempty
eval = xform2 c_th1d_eval
executeEvent = xform3 c_th1d_executeevent
fFT = xform2 c_th1d_fft
fill1 = xform1 c_th1d_fill1
fillN = xform4 c_th1d_filln
fillRandom = xform2 c_th1d_fillrandom
findBin = xform3 c_th1d_findbin
findFixBin = xform3 c_th1d_findfixbin
findFirstBinAbove = xform2 c_th1d_findfirstbinabove
findLastBinAbove = xform2 c_th1d_findlastbinabove
fitPanel = xform0 c_th1d_fitpanel
getNdivisions = xform1 c_th1d_getndivisions
getAxisColor = xform1 c_th1d_getaxiscolor
getLabelColor = xform1 c_th1d_getlabelcolor
getLabelFont = xform1 c_th1d_getlabelfont
getLabelOffset = xform1 c_th1d_getlabeloffset
getLabelSize = xform1 c_th1d_getlabelsize
getTitleFont = xform1 c_th1d_gettitlefont
getTitleOffset = xform1 c_th1d_gettitleoffset
getTitleSize = xform1 c_th1d_gettitlesize
getTickLength = xform1 c_th1d_getticklength
getBarOffset = xform0 c_th1d_getbaroffset
getBarWidth = xform0 c_th1d_getbarwidth
getContour = xform1 c_th1d_getcontour
getContourLevel = xform1 c_th1d_getcontourlevel
getContourLevelPad = xform1 c_th1d_getcontourlevelpad
getBin = xform3 c_th1d_getbin
getBinCenter = xform1 c_th1d_getbincenter
getBinContent1 = xform1 c_th1d_getbincontent1
getBinContent2 = xform2 c_th1d_getbincontent2
getBinContent3 = xform3 c_th1d_getbincontent3
getBinError1 = xform1 c_th1d_getbinerror1
getBinError2 = xform2 c_th1d_getbinerror2
getBinError3 = xform3 c_th1d_getbinerror3
getBinLowEdge = xform1 c_th1d_getbinlowedge
getBinWidth = xform1 c_th1d_getbinwidth
getCellContent = xform2 c_th1d_getcellcontent
getCellError = xform2 c_th1d_getcellerror
instance ITH1 TH1C where
add = xform2 c_th1c_add
addBinContent = xform2 c_th1c_addbincontent
chi2Test = xform3 c_th1c_chi2test
computeIntegral = xform0 c_th1c_computeintegral
directoryAutoAdd = xform1 c_th1c_directoryautoadd
distancetoPrimitive = xform2 c_th1c_distancetoprimitive
divide = xform5 c_th1c_divide
drawCopy = xform1 c_th1c_drawcopy
drawNormalized = xform2 c_th1c_drawnormalized
drawPanel = xform0 c_th1c_drawpanel
bufferEmpty = xform1 c_th1c_bufferempty
eval = xform2 c_th1c_eval
executeEvent = xform3 c_th1c_executeevent
fFT = xform2 c_th1c_fft
fill1 = xform1 c_th1c_fill1
fillN = xform4 c_th1c_filln
fillRandom = xform2 c_th1c_fillrandom
findBin = xform3 c_th1c_findbin
findFixBin = xform3 c_th1c_findfixbin
findFirstBinAbove = xform2 c_th1c_findfirstbinabove
findLastBinAbove = xform2 c_th1c_findlastbinabove
fitPanel = xform0 c_th1c_fitpanel
getNdivisions = xform1 c_th1c_getndivisions
getAxisColor = xform1 c_th1c_getaxiscolor
getLabelColor = xform1 c_th1c_getlabelcolor
getLabelFont = xform1 c_th1c_getlabelfont
getLabelOffset = xform1 c_th1c_getlabeloffset
getLabelSize = xform1 c_th1c_getlabelsize
getTitleFont = xform1 c_th1c_gettitlefont
getTitleOffset = xform1 c_th1c_gettitleoffset
getTitleSize = xform1 c_th1c_gettitlesize
getTickLength = xform1 c_th1c_getticklength
getBarOffset = xform0 c_th1c_getbaroffset
getBarWidth = xform0 c_th1c_getbarwidth
getContour = xform1 c_th1c_getcontour
getContourLevel = xform1 c_th1c_getcontourlevel
getContourLevelPad = xform1 c_th1c_getcontourlevelpad
getBin = xform3 c_th1c_getbin
getBinCenter = xform1 c_th1c_getbincenter
getBinContent1 = xform1 c_th1c_getbincontent1
getBinContent2 = xform2 c_th1c_getbincontent2
getBinContent3 = xform3 c_th1c_getbincontent3
getBinError1 = xform1 c_th1c_getbinerror1
getBinError2 = xform2 c_th1c_getbinerror2
getBinError3 = xform3 c_th1c_getbinerror3
getBinLowEdge = xform1 c_th1c_getbinlowedge
getBinWidth = xform1 c_th1c_getbinwidth
getCellContent = xform2 c_th1c_getcellcontent
getCellError = xform2 c_th1c_getcellerror
instance ITH1 TH3 where
add = xform2 c_th3_add
addBinContent = xform2 c_th3_addbincontent
chi2Test = xform3 c_th3_chi2test
computeIntegral = xform0 c_th3_computeintegral
directoryAutoAdd = xform1 c_th3_directoryautoadd
distancetoPrimitive = xform2 c_th3_distancetoprimitive
divide = xform5 c_th3_divide
drawCopy = xform1 c_th3_drawcopy
drawNormalized = xform2 c_th3_drawnormalized
drawPanel = xform0 c_th3_drawpanel
bufferEmpty = xform1 c_th3_bufferempty
eval = xform2 c_th3_eval
executeEvent = xform3 c_th3_executeevent
fFT = xform2 c_th3_fft
fill1 = xform1 c_th3_fill1
fillN = xform4 c_th3_filln
fillRandom = xform2 c_th3_fillrandom
findBin = xform3 c_th3_findbin
findFixBin = xform3 c_th3_findfixbin
findFirstBinAbove = xform2 c_th3_findfirstbinabove
findLastBinAbove = xform2 c_th3_findlastbinabove
fitPanel = xform0 c_th3_fitpanel
getNdivisions = xform1 c_th3_getndivisions
getAxisColor = xform1 c_th3_getaxiscolor
getLabelColor = xform1 c_th3_getlabelcolor
getLabelFont = xform1 c_th3_getlabelfont
getLabelOffset = xform1 c_th3_getlabeloffset
getLabelSize = xform1 c_th3_getlabelsize
getTitleFont = xform1 c_th3_gettitlefont
getTitleOffset = xform1 c_th3_gettitleoffset
getTitleSize = xform1 c_th3_gettitlesize
getTickLength = xform1 c_th3_getticklength
getBarOffset = xform0 c_th3_getbaroffset
getBarWidth = xform0 c_th3_getbarwidth
getContour = xform1 c_th3_getcontour
getContourLevel = xform1 c_th3_getcontourlevel
getContourLevelPad = xform1 c_th3_getcontourlevelpad
getBin = xform3 c_th3_getbin
getBinCenter = xform1 c_th3_getbincenter
getBinContent1 = xform1 c_th3_getbincontent1
getBinContent2 = xform2 c_th3_getbincontent2
getBinContent3 = xform3 c_th3_getbincontent3
getBinError1 = xform1 c_th3_getbinerror1
getBinError2 = xform2 c_th3_getbinerror2
getBinError3 = xform3 c_th3_getbinerror3
getBinLowEdge = xform1 c_th3_getbinlowedge
getBinWidth = xform1 c_th3_getbinwidth
getCellContent = xform2 c_th3_getcellcontent
getCellError = xform2 c_th3_getcellerror
instance ITH1 TH2 where
add = xform2 c_th2_add
addBinContent = xform2 c_th2_addbincontent
chi2Test = xform3 c_th2_chi2test
computeIntegral = xform0 c_th2_computeintegral
directoryAutoAdd = xform1 c_th2_directoryautoadd
distancetoPrimitive = xform2 c_th2_distancetoprimitive
divide = xform5 c_th2_divide
drawCopy = xform1 c_th2_drawcopy
drawNormalized = xform2 c_th2_drawnormalized
drawPanel = xform0 c_th2_drawpanel
bufferEmpty = xform1 c_th2_bufferempty
eval = xform2 c_th2_eval
executeEvent = xform3 c_th2_executeevent
fFT = xform2 c_th2_fft
fill1 = xform1 c_th2_fill1
fillN = xform4 c_th2_filln
fillRandom = xform2 c_th2_fillrandom
findBin = xform3 c_th2_findbin
findFixBin = xform3 c_th2_findfixbin
findFirstBinAbove = xform2 c_th2_findfirstbinabove
findLastBinAbove = xform2 c_th2_findlastbinabove
fitPanel = xform0 c_th2_fitpanel
getNdivisions = xform1 c_th2_getndivisions
getAxisColor = xform1 c_th2_getaxiscolor
getLabelColor = xform1 c_th2_getlabelcolor
getLabelFont = xform1 c_th2_getlabelfont
getLabelOffset = xform1 c_th2_getlabeloffset
getLabelSize = xform1 c_th2_getlabelsize
getTitleFont = xform1 c_th2_gettitlefont
getTitleOffset = xform1 c_th2_gettitleoffset
getTitleSize = xform1 c_th2_gettitlesize
getTickLength = xform1 c_th2_getticklength
getBarOffset = xform0 c_th2_getbaroffset
getBarWidth = xform0 c_th2_getbarwidth
getContour = xform1 c_th2_getcontour
getContourLevel = xform1 c_th2_getcontourlevel
getContourLevelPad = xform1 c_th2_getcontourlevelpad
getBin = xform3 c_th2_getbin
getBinCenter = xform1 c_th2_getbincenter
getBinContent1 = xform1 c_th2_getbincontent1
getBinContent2 = xform2 c_th2_getbincontent2
getBinContent3 = xform3 c_th2_getbincontent3
getBinError1 = xform1 c_th2_getbinerror1
getBinError2 = xform2 c_th2_getbinerror2
getBinError3 = xform3 c_th2_getbinerror3
getBinLowEdge = xform1 c_th2_getbinlowedge
getBinWidth = xform1 c_th2_getbinwidth
getCellContent = xform2 c_th2_getcellcontent
getCellError = xform2 c_th2_getcellerror
instance ITH2 TH2S where
fill2 = xform2 c_th2s_fill2
instance ITH2 TH2Poly where
fill2 = xform2 c_th2poly_fill2
instance ITH2 TH2I where
fill2 = xform2 c_th2i_fill2
instance ITH2 TH2F where
fill2 = xform2 c_th2f_fill2
instance ITH2 TH2D where
fill2 = xform2 c_th2d_fill2
instance ITH2 TH2C where
fill2 = xform2 c_th2c_fill2
instance ITH3 TH3S where
instance ITH3 TH3I where
instance ITH3 TH3F where
instance ITH3 TH3D where
instance ITH3 TH3C where
instance ITLine TGaxis where
instance ITLine TArrow where
instance ITNamed TRandom where
setTitle = xform1 c_trandom_settitle
instance ITNamed TH3S where
setTitle = xform1 c_th3s_settitle
instance ITNamed TH3I where
setTitle = xform1 c_th3i_settitle
instance ITNamed TH3F where
setTitle = xform1 c_th3f_settitle
instance ITNamed TH3D where
setTitle = xform1 c_th3d_settitle
instance ITNamed TH3C where
setTitle = xform1 c_th3c_settitle
instance ITNamed TH2S where
setTitle = xform1 c_th2s_settitle
instance ITNamed TH2Poly where
setTitle = xform1 c_th2poly_settitle
instance ITNamed TH2I where
setTitle = xform1 c_th2i_settitle
instance ITNamed TH2F where
setTitle = xform1 c_th2f_settitle
instance ITNamed TH2D where
setTitle = xform1 c_th2d_settitle
instance ITNamed TH2C where
setTitle = xform1 c_th2c_settitle
instance ITNamed TH1S where
setTitle = xform1 c_th1s_settitle
instance ITNamed TH1I where
setTitle = xform1 c_th1i_settitle
instance ITNamed TH1F where
setTitle = xform1 c_th1f_settitle
instance ITNamed TH1D where
setTitle = xform1 c_th1d_settitle
instance ITNamed TH1C where
setTitle = xform1 c_th1c_settitle
instance ITNamed TH3 where
setTitle = xform1 c_th3_settitle
instance ITNamed TH2 where
setTitle = xform1 c_th2_settitle
instance ITNamed TH1 where
setTitle = xform1 c_th1_settitle
instance ITNamed TBranch where
setTitle = xform1 c_tbranch_settitle
instance ITNamed TFile where
setTitle = xform1 c_tfile_settitle
instance ITNamed TDirectoryFile where
setTitle = xform1 c_tdirectoryfile_settitle
instance ITNamed TDirectory where
setTitle = xform1 c_tdirectory_settitle
instance ITNamed TText where
setTitle = xform1 c_ttext_settitle
instance ITNamed TLatex where
setTitle = xform1 c_tlatex_settitle
instance ITNamed TAxis where
setTitle = xform1 c_taxis_settitle
instance ITNamed TEfficiency where
setTitle = xform1 c_tefficiency_settitle
instance ITNamed TTreeSQL where
setTitle = xform1 c_ttreesql_settitle
instance ITNamed TNtupleD where
setTitle = xform1 c_tntupled_settitle
instance ITNamed TNtuple where
setTitle = xform1 c_tntuple_settitle
instance ITNamed TChain where
setTitle = xform1 c_tchain_settitle
instance ITNamed TTree where
setTitle = xform1 c_ttree_settitle
instance ITNamed TXTRU where
setTitle = xform1 c_txtru_settitle
instance ITNamed TSPHE where
setTitle = xform1 c_tsphe_settitle
instance ITNamed TPCON where
setTitle = xform1 c_tpcon_settitle
instance ITNamed TTUBE where
setTitle = xform1 c_ttube_settitle
instance ITNamed TBRIK where
setTitle = xform1 c_tbrik_settitle
instance ITNamed TShape where
setTitle = xform1 c_tshape_settitle
instance ITNamed TGraphQQ where
setTitle = xform1 c_tgraphqq_settitle
instance ITNamed TGraphPolar where
setTitle = xform1 c_tgraphpolar_settitle
instance ITNamed TGraphErrors where
setTitle = xform1 c_tgrapherrors_settitle
instance ITNamed TGraphBentErrors where
setTitle = xform1 c_tgraphbenterrors_settitle
instance ITNamed TCutG where
setTitle = xform1 c_tcutg_settitle
instance ITNamed TGraphAsymmErrors where
setTitle = xform1 c_tgraphasymmerrors_settitle
instance ITNamed TGraph where
setTitle = xform1 c_tgraph_settitle
instance ITNamed TF1 where
setTitle = xform1 c_tf1_settitle
instance ITNamed THStack where
setTitle = xform1 c_thstack_settitle
instance ITNamed TAttParticle where
setTitle = xform1 c_tattparticle_settitle
instance ITNamed TFormula where
setTitle = xform1 c_tformula_settitle
instance ITNamed TClass where
setTitle = xform1 c_tclass_settitle
instance ITObject TRandom where
getName = xform0 c_trandom_getname
draw = xform1 c_trandom_draw
findObject = xform1 c_trandom_findobject
saveAs = xform2 c_trandom_saveas
write = xform3 c_trandom_write
isA = xform0 c_trandom_isa
instance ITObject TRint where
getName = xform0 c_trint_getname
draw = xform1 c_trint_draw
findObject = xform1 c_trint_findobject
saveAs = xform2 c_trint_saveas
write = xform3 c_trint_write
isA = xform0 c_trint_isa
instance ITObject TApplication where
getName = xform0 c_tapplication_getname
draw = xform1 c_tapplication_draw
findObject = xform1 c_tapplication_findobject
saveAs = xform2 c_tapplication_saveas
write = xform3 c_tapplication_write
isA = xform0 c_tapplication_isa
instance ITObject TSlider where
getName = xform0 c_tslider_getname
draw = xform1 c_tslider_draw
findObject = xform1 c_tslider_findobject
saveAs = xform2 c_tslider_saveas
write = xform3 c_tslider_write
isA = xform0 c_tslider_isa
instance ITObject TEvePad where
getName = xform0 c_tevepad_getname
draw = xform1 c_tevepad_draw
findObject = xform1 c_tevepad_findobject
saveAs = xform2 c_tevepad_saveas
write = xform3 c_tevepad_write
isA = xform0 c_tevepad_isa
instance ITObject TInspectCanvas where
getName = xform0 c_tinspectcanvas_getname
draw = xform1 c_tinspectcanvas_draw
findObject = xform1 c_tinspectcanvas_findobject
saveAs = xform2 c_tinspectcanvas_saveas
write = xform3 c_tinspectcanvas_write
isA = xform0 c_tinspectcanvas_isa
instance ITObject TDialogCanvas where
getName = xform0 c_tdialogcanvas_getname
draw = xform1 c_tdialogcanvas_draw
findObject = xform1 c_tdialogcanvas_findobject
saveAs = xform2 c_tdialogcanvas_saveas
write = xform3 c_tdialogcanvas_write
isA = xform0 c_tdialogcanvas_isa
instance ITObject TCanvas where
getName = xform0 c_tcanvas_getname
draw = xform1 c_tcanvas_draw
findObject = xform1 c_tcanvas_findobject
saveAs = xform2 c_tcanvas_saveas
write = xform3 c_tcanvas_write
isA = xform0 c_tcanvas_isa
instance ITObject TGroupButton where
getName = xform0 c_tgroupbutton_getname
draw = xform1 c_tgroupbutton_draw
findObject = xform1 c_tgroupbutton_findobject
saveAs = xform2 c_tgroupbutton_saveas
write = xform3 c_tgroupbutton_write
isA = xform0 c_tgroupbutton_isa
instance ITObject TButton where
getName = xform0 c_tbutton_getname
draw = xform1 c_tbutton_draw
findObject = xform1 c_tbutton_findobject
saveAs = xform2 c_tbutton_saveas
write = xform3 c_tbutton_write
isA = xform0 c_tbutton_isa
instance ITObject TPad where
getName = xform0 c_tpad_getname
draw = xform1 c_tpad_draw
findObject = xform1 c_tpad_findobject
saveAs = xform2 c_tpad_saveas
write = xform3 c_tpad_write
isA = xform0 c_tpad_isa
instance ITObject TVirtualPad where
getName = xform0 c_tvirtualpad_getname
draw = xform1 c_tvirtualpad_draw
findObject = xform1 c_tvirtualpad_findobject
saveAs = xform2 c_tvirtualpad_saveas
write = xform3 c_tvirtualpad_write
isA = xform0 c_tvirtualpad_isa
instance ITObject TH3S where
getName = xform0 c_th3s_getname
draw = xform1 c_th3s_draw
findObject = xform1 c_th3s_findobject
saveAs = xform2 c_th3s_saveas
write = xform3 c_th3s_write
isA = xform0 c_th3s_isa
instance ITObject TH3I where
getName = xform0 c_th3i_getname
draw = xform1 c_th3i_draw
findObject = xform1 c_th3i_findobject
saveAs = xform2 c_th3i_saveas
write = xform3 c_th3i_write
isA = xform0 c_th3i_isa
instance ITObject TH3F where
getName = xform0 c_th3f_getname
draw = xform1 c_th3f_draw
findObject = xform1 c_th3f_findobject
saveAs = xform2 c_th3f_saveas
write = xform3 c_th3f_write
isA = xform0 c_th3f_isa
instance ITObject TH3D where
getName = xform0 c_th3d_getname
draw = xform1 c_th3d_draw
findObject = xform1 c_th3d_findobject
saveAs = xform2 c_th3d_saveas
write = xform3 c_th3d_write
isA = xform0 c_th3d_isa
instance ITObject TH3C where
getName = xform0 c_th3c_getname
draw = xform1 c_th3c_draw
findObject = xform1 c_th3c_findobject
saveAs = xform2 c_th3c_saveas
write = xform3 c_th3c_write
isA = xform0 c_th3c_isa
instance ITObject TH2S where
getName = xform0 c_th2s_getname
draw = xform1 c_th2s_draw
findObject = xform1 c_th2s_findobject
saveAs = xform2 c_th2s_saveas
write = xform3 c_th2s_write
isA = xform0 c_th2s_isa
instance ITObject TH2Poly where
getName = xform0 c_th2poly_getname
draw = xform1 c_th2poly_draw
findObject = xform1 c_th2poly_findobject
saveAs = xform2 c_th2poly_saveas
write = xform3 c_th2poly_write
isA = xform0 c_th2poly_isa
instance ITObject TH2I where
getName = xform0 c_th2i_getname
draw = xform1 c_th2i_draw
findObject = xform1 c_th2i_findobject
saveAs = xform2 c_th2i_saveas
write = xform3 c_th2i_write
isA = xform0 c_th2i_isa
instance ITObject TH2F where
getName = xform0 c_th2f_getname
draw = xform1 c_th2f_draw
findObject = xform1 c_th2f_findobject
saveAs = xform2 c_th2f_saveas
write = xform3 c_th2f_write
isA = xform0 c_th2f_isa
instance ITObject TH2D where
getName = xform0 c_th2d_getname
draw = xform1 c_th2d_draw
findObject = xform1 c_th2d_findobject
saveAs = xform2 c_th2d_saveas
write = xform3 c_th2d_write
isA = xform0 c_th2d_isa
instance ITObject TH2C where
getName = xform0 c_th2c_getname
draw = xform1 c_th2c_draw
findObject = xform1 c_th2c_findobject
saveAs = xform2 c_th2c_saveas
write = xform3 c_th2c_write
isA = xform0 c_th2c_isa
instance ITObject TH1S where
getName = xform0 c_th1s_getname
draw = xform1 c_th1s_draw
findObject = xform1 c_th1s_findobject
saveAs = xform2 c_th1s_saveas
write = xform3 c_th1s_write
isA = xform0 c_th1s_isa
instance ITObject TH1I where
getName = xform0 c_th1i_getname
draw = xform1 c_th1i_draw
findObject = xform1 c_th1i_findobject
saveAs = xform2 c_th1i_saveas
write = xform3 c_th1i_write
isA = xform0 c_th1i_isa
instance ITObject TH1F where
getName = xform0 c_th1f_getname
draw = xform1 c_th1f_draw
findObject = xform1 c_th1f_findobject
saveAs = xform2 c_th1f_saveas
write = xform3 c_th1f_write
isA = xform0 c_th1f_isa
instance ITObject TH1D where
getName = xform0 c_th1d_getname
draw = xform1 c_th1d_draw
findObject = xform1 c_th1d_findobject
saveAs = xform2 c_th1d_saveas
write = xform3 c_th1d_write
isA = xform0 c_th1d_isa
instance ITObject TH1C where
getName = xform0 c_th1c_getname
draw = xform1 c_th1c_draw
findObject = xform1 c_th1c_findobject
saveAs = xform2 c_th1c_saveas
write = xform3 c_th1c_write
isA = xform0 c_th1c_isa
instance ITObject TH3 where
getName = xform0 c_th3_getname
draw = xform1 c_th3_draw
findObject = xform1 c_th3_findobject
saveAs = xform2 c_th3_saveas
write = xform3 c_th3_write
isA = xform0 c_th3_isa
instance ITObject TH2 where
getName = xform0 c_th2_getname
draw = xform1 c_th2_draw
findObject = xform1 c_th2_findobject
saveAs = xform2 c_th2_saveas
write = xform3 c_th2_write
isA = xform0 c_th2_isa
instance ITObject TH1 where
getName = xform0 c_th1_getname
draw = xform1 c_th1_draw
findObject = xform1 c_th1_findobject
saveAs = xform2 c_th1_saveas
write = xform3 c_th1_write
isA = xform0 c_th1_isa
instance ITObject TTreePlayer where
getName = xform0 c_ttreeplayer_getname
draw = xform1 c_ttreeplayer_draw
findObject = xform1 c_ttreeplayer_findobject
saveAs = xform2 c_ttreeplayer_saveas
write = xform3 c_ttreeplayer_write
isA = xform0 c_ttreeplayer_isa
instance ITObject TVirtualTreePlayer where
getName = xform0 c_tvirtualtreeplayer_getname
draw = xform1 c_tvirtualtreeplayer_draw
findObject = xform1 c_tvirtualtreeplayer_findobject
saveAs = xform2 c_tvirtualtreeplayer_saveas
write = xform3 c_tvirtualtreeplayer_write
isA = xform0 c_tvirtualtreeplayer_isa
instance ITObject TBranch where
getName = xform0 c_tbranch_getname
draw = xform1 c_tbranch_draw
findObject = xform1 c_tbranch_findobject
saveAs = xform2 c_tbranch_saveas
write = xform3 c_tbranch_write
isA = xform0 c_tbranch_isa
instance ITObject TFile where
getName = xform0 c_tfile_getname
draw = xform1 c_tfile_draw
findObject = xform1 c_tfile_findobject
saveAs = xform2 c_tfile_saveas
write = xform3 c_tfile_write
isA = xform0 c_tfile_isa
instance ITObject TDirectoryFile where
getName = xform0 c_tdirectoryfile_getname
draw = xform1 c_tdirectoryfile_draw
findObject = xform1 c_tdirectoryfile_findobject
saveAs = xform2 c_tdirectoryfile_saveas
write = xform3 c_tdirectoryfile_write
isA = xform0 c_tdirectoryfile_isa
instance ITObject TDirectory where
getName = xform0 c_tdirectory_getname
draw = xform1 c_tdirectory_draw
findObject = xform1 c_tdirectory_findobject
saveAs = xform2 c_tdirectory_saveas
write = xform3 c_tdirectory_write
isA = xform0 c_tdirectory_isa
instance ITObject TText where
getName = xform0 c_ttext_getname
draw = xform1 c_ttext_draw
findObject = xform1 c_ttext_findobject
saveAs = xform2 c_ttext_saveas
write = xform3 c_ttext_write
isA = xform0 c_ttext_isa
instance ITObject TLatex where
getName = xform0 c_tlatex_getname
draw = xform1 c_tlatex_draw
findObject = xform1 c_tlatex_findobject
saveAs = xform2 c_tlatex_saveas
write = xform3 c_tlatex_write
isA = xform0 c_tlatex_isa
instance ITObject TAxis where
getName = xform0 c_taxis_getname
draw = xform1 c_taxis_draw
findObject = xform1 c_taxis_findobject
saveAs = xform2 c_taxis_saveas
write = xform3 c_taxis_write
isA = xform0 c_taxis_isa
instance ITObject TEfficiency where
getName = xform0 c_tefficiency_getname
draw = xform1 c_tefficiency_draw
findObject = xform1 c_tefficiency_findobject
saveAs = xform2 c_tefficiency_saveas
write = xform3 c_tefficiency_write
isA = xform0 c_tefficiency_isa
instance ITObject TCurlyArc where
getName = xform0 c_tcurlyarc_getname
draw = xform1 c_tcurlyarc_draw
findObject = xform1 c_tcurlyarc_findobject
saveAs = xform2 c_tcurlyarc_saveas
write = xform3 c_tcurlyarc_write
isA = xform0 c_tcurlyarc_isa
instance ITObject TCurlyLine where
getName = xform0 c_tcurlyline_getname
draw = xform1 c_tcurlyline_draw
findObject = xform1 c_tcurlyline_findobject
saveAs = xform2 c_tcurlyline_saveas
write = xform3 c_tcurlyline_write
isA = xform0 c_tcurlyline_isa
instance ITObject TPolyLine where
getName = xform0 c_tpolyline_getname
draw = xform1 c_tpolyline_draw
findObject = xform1 c_tpolyline_findobject
saveAs = xform2 c_tpolyline_saveas
write = xform3 c_tpolyline_write
isA = xform0 c_tpolyline_isa
instance ITObject TTreeSQL where
getName = xform0 c_ttreesql_getname
draw = xform1 c_ttreesql_draw
findObject = xform1 c_ttreesql_findobject
saveAs = xform2 c_ttreesql_saveas
write = xform3 c_ttreesql_write
isA = xform0 c_ttreesql_isa
instance ITObject TNtupleD where
getName = xform0 c_tntupled_getname
draw = xform1 c_tntupled_draw
findObject = xform1 c_tntupled_findobject
saveAs = xform2 c_tntupled_saveas
write = xform3 c_tntupled_write
isA = xform0 c_tntupled_isa
instance ITObject TNtuple where
getName = xform0 c_tntuple_getname
draw = xform1 c_tntuple_draw
findObject = xform1 c_tntuple_findobject
saveAs = xform2 c_tntuple_saveas
write = xform3 c_tntuple_write
isA = xform0 c_tntuple_isa
instance ITObject TChain where
getName = xform0 c_tchain_getname
draw = xform1 c_tchain_draw
findObject = xform1 c_tchain_findobject
saveAs = xform2 c_tchain_saveas
write = xform3 c_tchain_write
isA = xform0 c_tchain_isa
instance ITObject TTree where
getName = xform0 c_ttree_getname
draw = xform1 c_ttree_draw
findObject = xform1 c_ttree_findobject
saveAs = xform2 c_ttree_saveas
write = xform3 c_ttree_write
isA = xform0 c_ttree_isa
instance ITObject TSliderBox where
getName = xform0 c_tsliderbox_getname
draw = xform1 c_tsliderbox_draw
findObject = xform1 c_tsliderbox_findobject
saveAs = xform2 c_tsliderbox_saveas
write = xform3 c_tsliderbox_write
isA = xform0 c_tsliderbox_isa
instance ITObject TFrame where
getName = xform0 c_tframe_getname
draw = xform1 c_tframe_draw
findObject = xform1 c_tframe_findobject
saveAs = xform2 c_tframe_saveas
write = xform3 c_tframe_write
isA = xform0 c_tframe_isa
instance ITObject TWbox where
getName = xform0 c_twbox_getname
draw = xform1 c_twbox_draw
findObject = xform1 c_twbox_findobject
saveAs = xform2 c_twbox_saveas
write = xform3 c_twbox_write
isA = xform0 c_twbox_isa
instance ITObject TPaveClass where
getName = xform0 c_tpaveclass_getname
draw = xform1 c_tpaveclass_draw
findObject = xform1 c_tpaveclass_findobject
saveAs = xform2 c_tpaveclass_saveas
write = xform3 c_tpaveclass_write
isA = xform0 c_tpaveclass_isa
instance ITObject TPaveLabel where
getName = xform0 c_tpavelabel_getname
draw = xform1 c_tpavelabel_draw
findObject = xform1 c_tpavelabel_findobject
saveAs = xform2 c_tpavelabel_saveas
write = xform3 c_tpavelabel_write
isA = xform0 c_tpavelabel_isa
instance ITObject TLegend where
getName = xform0 c_tlegend_getname
draw = xform1 c_tlegend_draw
findObject = xform1 c_tlegend_findobject
saveAs = xform2 c_tlegend_saveas
write = xform3 c_tlegend_write
isA = xform0 c_tlegend_isa
instance ITObject TPavesText where
getName = xform0 c_tpavestext_getname
draw = xform1 c_tpavestext_draw
findObject = xform1 c_tpavestext_findobject
saveAs = xform2 c_tpavestext_saveas
write = xform3 c_tpavestext_write
isA = xform0 c_tpavestext_isa
instance ITObject TPaveStats where
getName = xform0 c_tpavestats_getname
draw = xform1 c_tpavestats_draw
findObject = xform1 c_tpavestats_findobject
saveAs = xform2 c_tpavestats_saveas
write = xform3 c_tpavestats_write
isA = xform0 c_tpavestats_isa
instance ITObject TDiamond where
getName = xform0 c_tdiamond_getname
draw = xform1 c_tdiamond_draw
findObject = xform1 c_tdiamond_findobject
saveAs = xform2 c_tdiamond_saveas
write = xform3 c_tdiamond_write
isA = xform0 c_tdiamond_isa
instance ITObject TPaveText where
getName = xform0 c_tpavetext_getname
draw = xform1 c_tpavetext_draw
findObject = xform1 c_tpavetext_findobject
saveAs = xform2 c_tpavetext_saveas
write = xform3 c_tpavetext_write
isA = xform0 c_tpavetext_isa
instance ITObject TPave where
getName = xform0 c_tpave_getname
draw = xform1 c_tpave_draw
findObject = xform1 c_tpave_findobject
saveAs = xform2 c_tpave_saveas
write = xform3 c_tpave_write
isA = xform0 c_tpave_isa
instance ITObject TBox where
getName = xform0 c_tbox_getname
draw = xform1 c_tbox_draw
findObject = xform1 c_tbox_findobject
saveAs = xform2 c_tbox_saveas
write = xform3 c_tbox_write
isA = xform0 c_tbox_isa
instance ITObject TXTRU where
getName = xform0 c_txtru_getname
draw = xform1 c_txtru_draw
findObject = xform1 c_txtru_findobject
saveAs = xform2 c_txtru_saveas
write = xform3 c_txtru_write
isA = xform0 c_txtru_isa
instance ITObject TSPHE where
getName = xform0 c_tsphe_getname
draw = xform1 c_tsphe_draw
findObject = xform1 c_tsphe_findobject
saveAs = xform2 c_tsphe_saveas
write = xform3 c_tsphe_write
isA = xform0 c_tsphe_isa
instance ITObject TPCON where
getName = xform0 c_tpcon_getname
draw = xform1 c_tpcon_draw
findObject = xform1 c_tpcon_findobject
saveAs = xform2 c_tpcon_saveas
write = xform3 c_tpcon_write
isA = xform0 c_tpcon_isa
instance ITObject TTUBE where
getName = xform0 c_ttube_getname
draw = xform1 c_ttube_draw
findObject = xform1 c_ttube_findobject
saveAs = xform2 c_ttube_saveas
write = xform3 c_ttube_write
isA = xform0 c_ttube_isa
instance ITObject TBRIK where
getName = xform0 c_tbrik_getname
draw = xform1 c_tbrik_draw
findObject = xform1 c_tbrik_findobject
saveAs = xform2 c_tbrik_saveas
write = xform3 c_tbrik_write
isA = xform0 c_tbrik_isa
instance ITObject TShape where
getName = xform0 c_tshape_getname
draw = xform1 c_tshape_draw
findObject = xform1 c_tshape_findobject
saveAs = xform2 c_tshape_saveas
write = xform3 c_tshape_write
isA = xform0 c_tshape_isa
instance ITObject TGaxis where
getName = xform0 c_tgaxis_getname
draw = xform1 c_tgaxis_draw
findObject = xform1 c_tgaxis_findobject
saveAs = xform2 c_tgaxis_saveas
write = xform3 c_tgaxis_write
isA = xform0 c_tgaxis_isa
instance ITObject TArrow where
getName = xform0 c_tarrow_getname
draw = xform1 c_tarrow_draw
findObject = xform1 c_tarrow_findobject
saveAs = xform2 c_tarrow_saveas
write = xform3 c_tarrow_write
isA = xform0 c_tarrow_isa
instance ITObject TLine where
getName = xform0 c_tline_getname
draw = xform1 c_tline_draw
findObject = xform1 c_tline_findobject
saveAs = xform2 c_tline_saveas
write = xform3 c_tline_write
isA = xform0 c_tline_isa
instance ITObject TCrown where
getName = xform0 c_tcrown_getname
draw = xform1 c_tcrown_draw
findObject = xform1 c_tcrown_findobject
saveAs = xform2 c_tcrown_saveas
write = xform3 c_tcrown_write
isA = xform0 c_tcrown_isa
instance ITObject TArc where
getName = xform0 c_tarc_getname
draw = xform1 c_tarc_draw
findObject = xform1 c_tarc_findobject
saveAs = xform2 c_tarc_saveas
write = xform3 c_tarc_write
isA = xform0 c_tarc_isa
instance ITObject TEllipse where
getName = xform0 c_tellipse_getname
draw = xform1 c_tellipse_draw
findObject = xform1 c_tellipse_findobject
saveAs = xform2 c_tellipse_saveas
write = xform3 c_tellipse_write
isA = xform0 c_tellipse_isa
instance ITObject TGraphQQ where
getName = xform0 c_tgraphqq_getname
draw = xform1 c_tgraphqq_draw
findObject = xform1 c_tgraphqq_findobject
saveAs = xform2 c_tgraphqq_saveas
write = xform3 c_tgraphqq_write
isA = xform0 c_tgraphqq_isa
instance ITObject TGraphPolar where
getName = xform0 c_tgraphpolar_getname
draw = xform1 c_tgraphpolar_draw
findObject = xform1 c_tgraphpolar_findobject
saveAs = xform2 c_tgraphpolar_saveas
write = xform3 c_tgraphpolar_write
isA = xform0 c_tgraphpolar_isa
instance ITObject TGraphErrors where
getName = xform0 c_tgrapherrors_getname
draw = xform1 c_tgrapherrors_draw
findObject = xform1 c_tgrapherrors_findobject
saveAs = xform2 c_tgrapherrors_saveas
write = xform3 c_tgrapherrors_write
isA = xform0 c_tgrapherrors_isa
instance ITObject TGraphBentErrors where
getName = xform0 c_tgraphbenterrors_getname
draw = xform1 c_tgraphbenterrors_draw
findObject = xform1 c_tgraphbenterrors_findobject
saveAs = xform2 c_tgraphbenterrors_saveas
write = xform3 c_tgraphbenterrors_write
isA = xform0 c_tgraphbenterrors_isa
instance ITObject TCutG where
getName = xform0 c_tcutg_getname
draw = xform1 c_tcutg_draw
findObject = xform1 c_tcutg_findobject
saveAs = xform2 c_tcutg_saveas
write = xform3 c_tcutg_write
isA = xform0 c_tcutg_isa
instance ITObject TGraphAsymmErrors where
getName = xform0 c_tgraphasymmerrors_getname
draw = xform1 c_tgraphasymmerrors_draw
findObject = xform1 c_tgraphasymmerrors_findobject
saveAs = xform2 c_tgraphasymmerrors_saveas
write = xform3 c_tgraphasymmerrors_write
isA = xform0 c_tgraphasymmerrors_isa
instance ITObject TGraph where
getName = xform0 c_tgraph_getname
draw = xform1 c_tgraph_draw
findObject = xform1 c_tgraph_findobject
saveAs = xform2 c_tgraph_saveas
write = xform3 c_tgraph_write
isA = xform0 c_tgraph_isa
instance ITObject TF1 where
getName = xform0 c_tf1_getname
draw = xform1 c_tf1_draw
findObject = xform1 c_tf1_findobject
saveAs = xform2 c_tf1_saveas
write = xform3 c_tf1_write
isA = xform0 c_tf1_isa
instance ITObject THStack where
getName = xform0 c_thstack_getname
draw = xform1 c_thstack_draw
findObject = xform1 c_thstack_findobject
saveAs = xform2 c_thstack_saveas
write = xform3 c_thstack_write
isA = xform0 c_thstack_isa
instance ITObject TAttParticle where
getName = xform0 c_tattparticle_getname
draw = xform1 c_tattparticle_draw
findObject = xform1 c_tattparticle_findobject
saveAs = xform2 c_tattparticle_saveas
write = xform3 c_tattparticle_write
isA = xform0 c_tattparticle_isa
instance ITObject TFormula where
getName = xform0 c_tformula_getname
draw = xform1 c_tformula_draw
findObject = xform1 c_tformula_findobject
saveAs = xform2 c_tformula_saveas
write = xform3 c_tformula_write
isA = xform0 c_tformula_isa
instance ITObject TClass where
getName = xform0 c_tclass_getname
draw = xform1 c_tclass_draw
findObject = xform1 c_tclass_findobject
saveAs = xform2 c_tclass_saveas
write = xform3 c_tclass_write
isA = xform0 c_tclass_isa
instance ITObject TNamed where
getName = xform0 c_tnamed_getname
draw = xform1 c_tnamed_draw
findObject = xform1 c_tnamed_findobject
saveAs = xform2 c_tnamed_saveas
write = xform3 c_tnamed_write
isA = xform0 c_tnamed_isa
instance ITPad TSlider where
instance ITPad TEvePad where
instance ITPad TInspectCanvas where
instance ITPad TDialogCanvas where
instance ITPad TCanvas where
instance ITPad TGroupButton where
instance ITPad TButton where
instance ITPave TPaveClass where
instance ITPave TPaveLabel where
instance ITPave TLegend where
instance ITPave TPavesText where
instance ITPave TPaveStats where
instance ITPave TDiamond where
instance ITPave TPaveText where
instance ITPaveLabel TPaveClass where
instance ITPaveText TPavesText where
instance ITPaveText TPaveStats where
instance ITPaveText TDiamond where
instance ITPolyLine TCurlyArc where
instance ITPolyLine TCurlyLine where
instance ITQObject TRint where
instance ITQObject TApplication where
instance ITQObject TSlider where
instance ITQObject TEvePad where
instance ITQObject TInspectCanvas where
instance ITQObject TDialogCanvas where
instance ITQObject TCanvas where
instance ITQObject TGroupButton where
instance ITQObject TButton where
instance ITQObject TPad where
instance ITQObject TVirtualPad where
instance ITShape TXTRU where
instance ITShape TSPHE where
instance ITShape TPCON where
instance ITShape TTUBE where
instance ITShape TBRIK where
instance ITText TLatex where
instance ITTree TTreeSQL where
instance ITTree TNtupleD where
instance ITTree TNtuple where
instance ITTree TChain where
instance ITVirtualPad TSlider where
getFrame = xform0 c_tslider_getframe
range = xform4 c_tslider_range
instance ITVirtualPad TEvePad where
getFrame = xform0 c_tevepad_getframe
range = xform4 c_tevepad_range
instance ITVirtualPad TInspectCanvas where
getFrame = xform0 c_tinspectcanvas_getframe
range = xform4 c_tinspectcanvas_range
instance ITVirtualPad TDialogCanvas where
getFrame = xform0 c_tdialogcanvas_getframe
range = xform4 c_tdialogcanvas_range
instance ITVirtualPad TCanvas where
getFrame = xform0 c_tcanvas_getframe
range = xform4 c_tcanvas_range
instance ITVirtualPad TGroupButton where
getFrame = xform0 c_tgroupbutton_getframe
range = xform4 c_tgroupbutton_range
instance ITVirtualPad TButton where
getFrame = xform0 c_tbutton_getframe
range = xform4 c_tbutton_range
instance ITVirtualPad TPad where
getFrame = xform0 c_tpad_getframe
range = xform4 c_tpad_range
instance ITVirtualTreePlayer TTreePlayer where
instance ITWbox TSliderBox where
setBorderMode = xform1 c_tsliderbox_setbordermode
instance ITWbox TFrame where
setBorderMode = xform1 c_tframe_setbordermode
newTObject :: IO TObject
newTObject = xformnull c_tobject_newtobject
newTNamed :: String -> String -> IO TNamed
newTNamed = xform1 c_tnamed_newtnamed
newTFormula :: String -> String -> IO TFormula
newTFormula = xform1 c_tformula_newtformula
newTAttAxis :: IO TAttAxis
newTAttAxis = xformnull c_tattaxis_newtattaxis
newTAttCanvas :: IO TAttCanvas
newTAttCanvas = xformnull c_tattcanvas_newtattcanvas
newTAttFill :: Int -> Int -> IO TAttFill
newTAttFill = xform1 c_tattfill_newtattfill
newTAttLine :: Int -> Int -> Int -> IO TAttLine
newTAttLine = xform2 c_tattline_newtattline
newTAttMarker :: Int -> Int -> Int -> IO TAttMarker
newTAttMarker = xform2 c_tattmarker_newtattmarker
newTAttPad :: IO TAttPad
newTAttPad = xformnull c_tattpad_newtattpad
newTAttText :: Int -> Double -> Int -> Int -> Double -> IO TAttText
newTAttText = xform4 c_tatttext_newtatttext
newTHStack :: String -> String -> IO THStack
newTHStack = xform1 c_thstack_newthstack
newTF1 :: String -> String -> Double -> Double -> IO TF1
newTF1 = xform3 c_tf1_newtf1
newTGraph :: Int -> [Double] -> [Double] -> IO TGraph
newTGraph = xform2 c_tgraph_newtgraph
newTGraphAsymmErrors :: Int -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> IO TGraphAsymmErrors
newTGraphAsymmErrors = xform6 c_tgraphasymmerrors_newtgraphasymmerrors
newTCutG :: String -> Int -> [Double] -> [Double] -> IO TCutG
newTCutG = xform3 c_tcutg_newtcutg
newTGraphBentErrors :: Int -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> IO TGraphBentErrors
newTGraphBentErrors = xform10 c_tgraphbenterrors_newtgraphbenterrors
newTGraphErrors :: Int -> [Double] -> [Double] -> [Double] -> [Double] -> IO TGraphErrors
newTGraphErrors = xform4 c_tgrapherrors_newtgrapherrors
newTGraphPolar :: Int -> [Double] -> [Double] -> [Double] -> [Double] -> IO TGraphPolar
newTGraphPolar = xform4 c_tgraphpolar_newtgraphpolar
newTGraphQQ :: Int -> [Double] -> Int -> [Double] -> IO TGraphQQ
newTGraphQQ = xform3 c_tgraphqq_newtgraphqq
newTEllipse :: Double -> Double -> Double -> Double -> Double -> Double -> Double -> IO TEllipse
newTEllipse = xform6 c_tellipse_newtellipse
newTArc :: Double -> Double -> Double -> Double -> Double -> IO TArc
newTArc = xform4 c_tarc_newtarc
newTCrown :: Double -> Double -> Double -> Double -> Double -> Double -> IO TCrown
newTCrown = xform5 c_tcrown_newtcrown
newTLine :: Double -> Double -> Double -> Double -> IO TLine
newTLine = xform3 c_tline_newtline
newTArrow :: Double -> Double -> Double -> Double -> Double -> String -> IO TArrow
newTArrow = xform5 c_tarrow_newtarrow
newTGaxis :: Double -> Double -> Double -> Double -> Double -> Double -> Int -> String -> Double -> IO TGaxis
newTGaxis = xform8 c_tgaxis_newtgaxis
newTShape :: String -> String -> String -> IO TShape
newTShape = xform2 c_tshape_newtshape
newTBRIK :: String -> String -> String -> Double -> Double -> Double -> IO TBRIK
newTBRIK = xform5 c_tbrik_newtbrik
newTTUBE :: String -> String -> String -> Double -> Double -> Double -> Double -> IO TTUBE
newTTUBE = xform6 c_ttube_newttube
newTPCON :: String -> String -> String -> Double -> Double -> Int -> IO TPCON
newTPCON = xform5 c_tpcon_newtpcon
newTSPHE :: String -> String -> String -> Double -> Double -> Double -> Double -> Double -> Double -> IO TSPHE
newTSPHE = xform8 c_tsphe_newtsphe
newTXTRU :: String -> String -> String -> Int -> Int -> IO TXTRU
newTXTRU = xform4 c_txtru_newtxtru
newTBox :: Double -> Double -> Double -> Double -> IO TBox
newTBox = xform3 c_tbox_newtbox
newTPave :: Double -> Double -> Double -> Double -> Int -> String -> IO TPave
newTPave = xform5 c_tpave_newtpave
newTPaveText :: Double -> Double -> Double -> Double -> String -> IO TPaveText
newTPaveText = xform4 c_tpavetext_newtpavetext
newTDiamond :: Double -> Double -> Double -> Double -> IO TDiamond
newTDiamond = xform3 c_tdiamond_newtdiamond
newTPaveStats :: Double -> Double -> Double -> Double -> String -> IO TPaveStats
newTPaveStats = xform4 c_tpavestats_newtpavestats
newTPavesText :: Double -> Double -> Double -> Double -> Int -> String -> IO TPavesText
newTPavesText = xform5 c_tpavestext_newtpavestext
newTLegend :: Double -> Double -> Double -> Double -> String -> String -> IO TLegend
newTLegend = xform5 c_tlegend_newtlegend
newTPaveLabel :: Double -> Double -> Double -> Double -> String -> String -> IO TPaveLabel
newTPaveLabel = xform5 c_tpavelabel_newtpavelabel
newTWbox :: Double -> Double -> Double -> Double -> Int -> Int -> Int -> IO TWbox
newTWbox = xform6 c_twbox_newtwbox
newTFrame :: Double -> Double -> Double -> Double -> IO TFrame
newTFrame = xform3 c_tframe_newtframe
newTSliderBox :: Double -> Double -> Double -> Double -> Int -> Int -> Int -> IO TSliderBox
newTSliderBox = xform6 c_tsliderbox_newtsliderbox
newTTree :: String -> String -> Int -> IO TTree
newTTree = xform2 c_ttree_newttree
newTChain :: String -> String -> IO TChain
newTChain = xform1 c_tchain_newtchain
newTNtuple :: String -> String -> String -> Int -> IO TNtuple
newTNtuple = xform3 c_tntuple_newtntuple
newTNtupleD :: String -> String -> String -> Int -> IO TNtupleD
newTNtupleD = xform3 c_tntupled_newtntupled
newTPolyLine :: Int -> [Double] -> [Double] -> String -> IO TPolyLine
newTPolyLine = xform3 c_tpolyline_newtpolyline
newTCurlyLine :: Double -> Double -> Double -> Double -> Double -> Double -> IO TCurlyLine
newTCurlyLine = xform5 c_tcurlyline_newtcurlyline
newTCurlyArc :: Double -> Double -> Double -> Double -> Double -> Double -> Double -> IO TCurlyArc
newTCurlyArc = xform6 c_tcurlyarc_newtcurlyarc
newTAxis :: Int -> Double -> Double -> IO TAxis
newTAxis = xform2 c_taxis_newtaxis
newTLatex :: Double -> Double -> String -> IO TLatex
newTLatex = xform2 c_tlatex_newtlatex
newTFile :: String -> String -> String -> Int -> IO TFile
newTFile = xform3 c_tfile_newtfile
newTH1F :: String -> String -> Int -> Double -> Double -> IO TH1F
newTH1F = xform4 c_th1f_newth1f
newTH2F :: String -> String -> Int -> Double -> Double -> Int -> Double -> Double -> IO TH2F
newTH2F = xform7 c_th2f_newth2f
newTCanvas :: String -> String -> Int -> Int -> IO TCanvas
newTCanvas = xform3 c_tcanvas_newtcanvas
newTApplication :: String -> [Int] -> [String] -> IO TApplication
newTApplication = xform2 c_tapplication_newtapplication
newTRint :: String -> [Int] -> [String] -> IO TRint
newTRint = xform2 c_trint_newtrint
newTRandom :: Int -> IO TRandom
newTRandom = xform0 c_trandom_newtrandom
tLatexDrawLatex :: TLatex -> Double -> Double -> String -> IO TLatex
tLatexDrawLatex = xform3 c_tlatex_tlatexdrawlatex
tH1GetAsymmetry :: TH1 -> TH1 -> Double -> Double -> IO TH1
tH1GetAsymmetry = xform3 c_th1_th1getasymmetry
tH1GetBufferLength :: TH1 -> IO Int
tH1GetBufferLength = xform0 c_th1_th1getbufferlength
tH1GetBufferSize :: TH1 -> IO Int
tH1GetBufferSize = xform0 c_th1_th1getbuffersize
tH1GetDirectory :: TH1 -> IO TDirectory
tH1GetDirectory = xform0 c_th1_th1getdirectory
tH1GetXaxis :: TH1 -> IO TAxis
tH1GetXaxis = xform0 c_th1_th1getxaxis
tH1GetYaxis :: TH1 -> IO TAxis
tH1GetYaxis = xform0 c_th1_th1getyaxis
tH1GetZaxis :: TH1 -> IO TAxis
tH1GetZaxis = xform0 c_th1_th1getzaxis