{-# LANGUAGE EmptyDataDecls, ExistentialQuantification, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeSynonymInstances #-} module HROOT.Core.TVirtualPad.Interface where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import FFICXX.Runtime.Cast import HROOT.Core.TVirtualPad.RawType import HROOT.Core.TObject.Interface import HROOT.Core.TAttLine.Interface import HROOT.Core.TAttFill.Interface import HROOT.Core.TAttPad.Interface import HROOT.Core.TQObject.Interface class (ITObject a, ITAttLine a, ITAttFill a, ITAttPad a, ITQObject a) => ITVirtualPad a where cd :: () => a -> CInt -> IO a divide_tvirtualpad :: () => a -> CInt -> CInt -> CFloat -> CFloat -> CInt -> IO () modified :: () => a -> CBool -> IO () range :: () => a -> CDouble -> CDouble -> CDouble -> CDouble -> IO () setLogx :: () => a -> CInt -> IO () setLogy :: () => a -> CInt -> IO () setLogz :: () => a -> CInt -> IO () update :: () => a -> IO () upcastTVirtualPad :: forall a . (FPtr a, ITVirtualPad a) => a -> TVirtualPad upcastTVirtualPad h = let fh = get_fptr h fh2 :: Ptr RawTVirtualPad = castPtr fh in cast_fptr_to_obj fh2 downcastTVirtualPad :: forall a . (FPtr a, ITVirtualPad a) => TVirtualPad -> a downcastTVirtualPad h = let fh = get_fptr h fh2 = castPtr fh in cast_fptr_to_obj fh2