module GI.Gdk.Structs.EventScroll
(
EventScroll(..) ,
newZeroEventScroll ,
noEventScroll ,
eventScroll_deltaX ,
getEventScrollDeltaX ,
setEventScrollDeltaX ,
eventScroll_deltaY ,
getEventScrollDeltaY ,
setEventScrollDeltaY ,
clearEventScrollDevice ,
eventScroll_device ,
getEventScrollDevice ,
setEventScrollDevice ,
eventScroll_direction ,
getEventScrollDirection ,
setEventScrollDirection ,
eventScroll_isStop ,
getEventScrollIsStop ,
setEventScrollIsStop ,
eventScroll_sendEvent ,
getEventScrollSendEvent ,
setEventScrollSendEvent ,
eventScroll_state ,
getEventScrollState ,
setEventScrollState ,
eventScroll_time ,
getEventScrollTime ,
setEventScrollTime ,
eventScroll_type ,
getEventScrollType ,
setEventScrollType ,
clearEventScrollWindow ,
eventScroll_window ,
getEventScrollWindow ,
setEventScrollWindow ,
eventScroll_x ,
getEventScrollX ,
setEventScrollX ,
eventScroll_xRoot ,
getEventScrollXRoot ,
setEventScrollXRoot ,
eventScroll_y ,
getEventScrollY ,
setEventScrollY ,
eventScroll_yRoot ,
getEventScrollYRoot ,
setEventScrollYRoot ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GI.Gdk.Enums as Gdk.Enums
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Window as Gdk.Window
newtype EventScroll = EventScroll (ManagedPtr EventScroll)
instance WrappedPtr EventScroll where
wrappedPtrCalloc = callocBytes 96
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 96 >=> wrapPtr EventScroll)
wrappedPtrFree = Just ptr_to_g_free
newZeroEventScroll :: MonadIO m => m EventScroll
newZeroEventScroll = liftIO $ wrappedPtrCalloc >>= wrapPtr EventScroll
instance tag ~ 'AttrSet => Constructible EventScroll tag where
new _ attrs = do
o <- newZeroEventScroll
GI.Attributes.set o attrs
return o
noEventScroll :: Maybe EventScroll
noEventScroll = Nothing
getEventScrollType :: MonadIO m => EventScroll -> m Gdk.Enums.EventType
getEventScrollType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setEventScrollType :: MonadIO m => EventScroll -> Gdk.Enums.EventType -> m ()
setEventScrollType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 0) (val' :: CUInt)
data EventScrollTypeFieldInfo
instance AttrInfo EventScrollTypeFieldInfo where
type AttrAllowedOps EventScrollTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrBaseTypeConstraint EventScrollTypeFieldInfo = (~) EventScroll
type AttrGetType EventScrollTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventScrollTypeFieldInfo = "type"
type AttrOrigin EventScrollTypeFieldInfo = EventScroll
attrGet _ = getEventScrollType
attrSet _ = setEventScrollType
attrConstruct = undefined
attrClear _ = undefined
eventScroll_type :: AttrLabelProxy "type"
eventScroll_type = AttrLabelProxy
getEventScrollWindow :: MonadIO m => EventScroll -> m (Maybe Gdk.Window.Window)
getEventScrollWindow s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO (Ptr Gdk.Window.Window)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.Window.Window) val'
return val''
return result
setEventScrollWindow :: MonadIO m => EventScroll -> Ptr Gdk.Window.Window -> m ()
setEventScrollWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventScrollWindow :: MonadIO m => EventScroll -> m ()
clearEventScrollWindow s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
data EventScrollWindowFieldInfo
instance AttrInfo EventScrollWindowFieldInfo where
type AttrAllowedOps EventScrollWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventScrollWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrBaseTypeConstraint EventScrollWindowFieldInfo = (~) EventScroll
type AttrGetType EventScrollWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventScrollWindowFieldInfo = "window"
type AttrOrigin EventScrollWindowFieldInfo = EventScroll
attrGet _ = getEventScrollWindow
attrSet _ = setEventScrollWindow
attrConstruct = undefined
attrClear _ = clearEventScrollWindow
eventScroll_window :: AttrLabelProxy "window"
eventScroll_window = AttrLabelProxy
getEventScrollSendEvent :: MonadIO m => EventScroll -> m Int8
getEventScrollSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int8
return val
setEventScrollSendEvent :: MonadIO m => EventScroll -> Int8 -> m ()
setEventScrollSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int8)
data EventScrollSendEventFieldInfo
instance AttrInfo EventScrollSendEventFieldInfo where
type AttrAllowedOps EventScrollSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollSendEventFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventScrollSendEventFieldInfo = (~) EventScroll
type AttrGetType EventScrollSendEventFieldInfo = Int8
type AttrLabel EventScrollSendEventFieldInfo = "send_event"
type AttrOrigin EventScrollSendEventFieldInfo = EventScroll
attrGet _ = getEventScrollSendEvent
attrSet _ = setEventScrollSendEvent
attrConstruct = undefined
attrClear _ = undefined
eventScroll_sendEvent :: AttrLabelProxy "sendEvent"
eventScroll_sendEvent = AttrLabelProxy
getEventScrollTime :: MonadIO m => EventScroll -> m Word32
getEventScrollTime s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 20) :: IO Word32
return val
setEventScrollTime :: MonadIO m => EventScroll -> Word32 -> m ()
setEventScrollTime s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 20) (val :: Word32)
data EventScrollTimeFieldInfo
instance AttrInfo EventScrollTimeFieldInfo where
type AttrAllowedOps EventScrollTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollTimeFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventScrollTimeFieldInfo = (~) EventScroll
type AttrGetType EventScrollTimeFieldInfo = Word32
type AttrLabel EventScrollTimeFieldInfo = "time"
type AttrOrigin EventScrollTimeFieldInfo = EventScroll
attrGet _ = getEventScrollTime
attrSet _ = setEventScrollTime
attrConstruct = undefined
attrClear _ = undefined
eventScroll_time :: AttrLabelProxy "time"
eventScroll_time = AttrLabelProxy
getEventScrollX :: MonadIO m => EventScroll -> m Double
getEventScrollX s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO CDouble
let val' = realToFrac val
return val'
setEventScrollX :: MonadIO m => EventScroll -> Double -> m ()
setEventScrollX s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 24) (val' :: CDouble)
data EventScrollXFieldInfo
instance AttrInfo EventScrollXFieldInfo where
type AttrAllowedOps EventScrollXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollXFieldInfo = (~) Double
type AttrBaseTypeConstraint EventScrollXFieldInfo = (~) EventScroll
type AttrGetType EventScrollXFieldInfo = Double
type AttrLabel EventScrollXFieldInfo = "x"
type AttrOrigin EventScrollXFieldInfo = EventScroll
attrGet _ = getEventScrollX
attrSet _ = setEventScrollX
attrConstruct = undefined
attrClear _ = undefined
eventScroll_x :: AttrLabelProxy "x"
eventScroll_x = AttrLabelProxy
getEventScrollY :: MonadIO m => EventScroll -> m Double
getEventScrollY s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO CDouble
let val' = realToFrac val
return val'
setEventScrollY :: MonadIO m => EventScroll -> Double -> m ()
setEventScrollY s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 32) (val' :: CDouble)
data EventScrollYFieldInfo
instance AttrInfo EventScrollYFieldInfo where
type AttrAllowedOps EventScrollYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollYFieldInfo = (~) Double
type AttrBaseTypeConstraint EventScrollYFieldInfo = (~) EventScroll
type AttrGetType EventScrollYFieldInfo = Double
type AttrLabel EventScrollYFieldInfo = "y"
type AttrOrigin EventScrollYFieldInfo = EventScroll
attrGet _ = getEventScrollY
attrSet _ = setEventScrollY
attrConstruct = undefined
attrClear _ = undefined
eventScroll_y :: AttrLabelProxy "y"
eventScroll_y = AttrLabelProxy
getEventScrollState :: MonadIO m => EventScroll -> m [Gdk.Flags.ModifierType]
getEventScrollState s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO CUInt
let val' = wordToGFlags val
return val'
setEventScrollState :: MonadIO m => EventScroll -> [Gdk.Flags.ModifierType] -> m ()
setEventScrollState s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = gflagsToWord val
poke (ptr `plusPtr` 40) (val' :: CUInt)
data EventScrollStateFieldInfo
instance AttrInfo EventScrollStateFieldInfo where
type AttrAllowedOps EventScrollStateFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollStateFieldInfo = (~) [Gdk.Flags.ModifierType]
type AttrBaseTypeConstraint EventScrollStateFieldInfo = (~) EventScroll
type AttrGetType EventScrollStateFieldInfo = [Gdk.Flags.ModifierType]
type AttrLabel EventScrollStateFieldInfo = "state"
type AttrOrigin EventScrollStateFieldInfo = EventScroll
attrGet _ = getEventScrollState
attrSet _ = setEventScrollState
attrConstruct = undefined
attrClear _ = undefined
eventScroll_state :: AttrLabelProxy "state"
eventScroll_state = AttrLabelProxy
getEventScrollDirection :: MonadIO m => EventScroll -> m Gdk.Enums.ScrollDirection
getEventScrollDirection s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 44) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setEventScrollDirection :: MonadIO m => EventScroll -> Gdk.Enums.ScrollDirection -> m ()
setEventScrollDirection s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 44) (val' :: CUInt)
data EventScrollDirectionFieldInfo
instance AttrInfo EventScrollDirectionFieldInfo where
type AttrAllowedOps EventScrollDirectionFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollDirectionFieldInfo = (~) Gdk.Enums.ScrollDirection
type AttrBaseTypeConstraint EventScrollDirectionFieldInfo = (~) EventScroll
type AttrGetType EventScrollDirectionFieldInfo = Gdk.Enums.ScrollDirection
type AttrLabel EventScrollDirectionFieldInfo = "direction"
type AttrOrigin EventScrollDirectionFieldInfo = EventScroll
attrGet _ = getEventScrollDirection
attrSet _ = setEventScrollDirection
attrConstruct = undefined
attrClear _ = undefined
eventScroll_direction :: AttrLabelProxy "direction"
eventScroll_direction = AttrLabelProxy
getEventScrollDevice :: MonadIO m => EventScroll -> m (Maybe Gdk.Device.Device)
getEventScrollDevice s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO (Ptr Gdk.Device.Device)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.Device.Device) val'
return val''
return result
setEventScrollDevice :: MonadIO m => EventScroll -> Ptr Gdk.Device.Device -> m ()
setEventScrollDevice s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 48) (val :: Ptr Gdk.Device.Device)
clearEventScrollDevice :: MonadIO m => EventScroll -> m ()
clearEventScrollDevice s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 48) (FP.nullPtr :: Ptr Gdk.Device.Device)
data EventScrollDeviceFieldInfo
instance AttrInfo EventScrollDeviceFieldInfo where
type AttrAllowedOps EventScrollDeviceFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventScrollDeviceFieldInfo = (~) (Ptr Gdk.Device.Device)
type AttrBaseTypeConstraint EventScrollDeviceFieldInfo = (~) EventScroll
type AttrGetType EventScrollDeviceFieldInfo = Maybe Gdk.Device.Device
type AttrLabel EventScrollDeviceFieldInfo = "device"
type AttrOrigin EventScrollDeviceFieldInfo = EventScroll
attrGet _ = getEventScrollDevice
attrSet _ = setEventScrollDevice
attrConstruct = undefined
attrClear _ = clearEventScrollDevice
eventScroll_device :: AttrLabelProxy "device"
eventScroll_device = AttrLabelProxy
getEventScrollXRoot :: MonadIO m => EventScroll -> m Double
getEventScrollXRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 56) :: IO CDouble
let val' = realToFrac val
return val'
setEventScrollXRoot :: MonadIO m => EventScroll -> Double -> m ()
setEventScrollXRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 56) (val' :: CDouble)
data EventScrollXRootFieldInfo
instance AttrInfo EventScrollXRootFieldInfo where
type AttrAllowedOps EventScrollXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollXRootFieldInfo = (~) Double
type AttrBaseTypeConstraint EventScrollXRootFieldInfo = (~) EventScroll
type AttrGetType EventScrollXRootFieldInfo = Double
type AttrLabel EventScrollXRootFieldInfo = "x_root"
type AttrOrigin EventScrollXRootFieldInfo = EventScroll
attrGet _ = getEventScrollXRoot
attrSet _ = setEventScrollXRoot
attrConstruct = undefined
attrClear _ = undefined
eventScroll_xRoot :: AttrLabelProxy "xRoot"
eventScroll_xRoot = AttrLabelProxy
getEventScrollYRoot :: MonadIO m => EventScroll -> m Double
getEventScrollYRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 64) :: IO CDouble
let val' = realToFrac val
return val'
setEventScrollYRoot :: MonadIO m => EventScroll -> Double -> m ()
setEventScrollYRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 64) (val' :: CDouble)
data EventScrollYRootFieldInfo
instance AttrInfo EventScrollYRootFieldInfo where
type AttrAllowedOps EventScrollYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollYRootFieldInfo = (~) Double
type AttrBaseTypeConstraint EventScrollYRootFieldInfo = (~) EventScroll
type AttrGetType EventScrollYRootFieldInfo = Double
type AttrLabel EventScrollYRootFieldInfo = "y_root"
type AttrOrigin EventScrollYRootFieldInfo = EventScroll
attrGet _ = getEventScrollYRoot
attrSet _ = setEventScrollYRoot
attrConstruct = undefined
attrClear _ = undefined
eventScroll_yRoot :: AttrLabelProxy "yRoot"
eventScroll_yRoot = AttrLabelProxy
getEventScrollDeltaX :: MonadIO m => EventScroll -> m Double
getEventScrollDeltaX s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 72) :: IO CDouble
let val' = realToFrac val
return val'
setEventScrollDeltaX :: MonadIO m => EventScroll -> Double -> m ()
setEventScrollDeltaX s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 72) (val' :: CDouble)
data EventScrollDeltaXFieldInfo
instance AttrInfo EventScrollDeltaXFieldInfo where
type AttrAllowedOps EventScrollDeltaXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollDeltaXFieldInfo = (~) Double
type AttrBaseTypeConstraint EventScrollDeltaXFieldInfo = (~) EventScroll
type AttrGetType EventScrollDeltaXFieldInfo = Double
type AttrLabel EventScrollDeltaXFieldInfo = "delta_x"
type AttrOrigin EventScrollDeltaXFieldInfo = EventScroll
attrGet _ = getEventScrollDeltaX
attrSet _ = setEventScrollDeltaX
attrConstruct = undefined
attrClear _ = undefined
eventScroll_deltaX :: AttrLabelProxy "deltaX"
eventScroll_deltaX = AttrLabelProxy
getEventScrollDeltaY :: MonadIO m => EventScroll -> m Double
getEventScrollDeltaY s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 80) :: IO CDouble
let val' = realToFrac val
return val'
setEventScrollDeltaY :: MonadIO m => EventScroll -> Double -> m ()
setEventScrollDeltaY s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 80) (val' :: CDouble)
data EventScrollDeltaYFieldInfo
instance AttrInfo EventScrollDeltaYFieldInfo where
type AttrAllowedOps EventScrollDeltaYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollDeltaYFieldInfo = (~) Double
type AttrBaseTypeConstraint EventScrollDeltaYFieldInfo = (~) EventScroll
type AttrGetType EventScrollDeltaYFieldInfo = Double
type AttrLabel EventScrollDeltaYFieldInfo = "delta_y"
type AttrOrigin EventScrollDeltaYFieldInfo = EventScroll
attrGet _ = getEventScrollDeltaY
attrSet _ = setEventScrollDeltaY
attrConstruct = undefined
attrClear _ = undefined
eventScroll_deltaY :: AttrLabelProxy "deltaY"
eventScroll_deltaY = AttrLabelProxy
getEventScrollIsStop :: MonadIO m => EventScroll -> m Word32
getEventScrollIsStop s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 88) :: IO Word32
return val
setEventScrollIsStop :: MonadIO m => EventScroll -> Word32 -> m ()
setEventScrollIsStop s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 88) (val :: Word32)
data EventScrollIsStopFieldInfo
instance AttrInfo EventScrollIsStopFieldInfo where
type AttrAllowedOps EventScrollIsStopFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventScrollIsStopFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventScrollIsStopFieldInfo = (~) EventScroll
type AttrGetType EventScrollIsStopFieldInfo = Word32
type AttrLabel EventScrollIsStopFieldInfo = "is_stop"
type AttrOrigin EventScrollIsStopFieldInfo = EventScroll
attrGet _ = getEventScrollIsStop
attrSet _ = setEventScrollIsStop
attrConstruct = undefined
attrClear _ = undefined
eventScroll_isStop :: AttrLabelProxy "isStop"
eventScroll_isStop = AttrLabelProxy
instance O.HasAttributeList EventScroll
type instance O.AttributeList EventScroll = EventScrollAttributeList
type EventScrollAttributeList = ('[ '("type", EventScrollTypeFieldInfo), '("window", EventScrollWindowFieldInfo), '("sendEvent", EventScrollSendEventFieldInfo), '("time", EventScrollTimeFieldInfo), '("x", EventScrollXFieldInfo), '("y", EventScrollYFieldInfo), '("state", EventScrollStateFieldInfo), '("direction", EventScrollDirectionFieldInfo), '("device", EventScrollDeviceFieldInfo), '("xRoot", EventScrollXRootFieldInfo), '("yRoot", EventScrollYRootFieldInfo), '("deltaX", EventScrollDeltaXFieldInfo), '("deltaY", EventScrollDeltaYFieldInfo), '("isStop", EventScrollIsStopFieldInfo)] :: [(Symbol, *)])
type family ResolveEventScrollMethod (t :: Symbol) (o :: *) :: * where
ResolveEventScrollMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventScrollMethod t EventScroll, O.MethodInfo info EventScroll p) => O.IsLabelProxy t (EventScroll -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveEventScrollMethod t EventScroll, O.MethodInfo info EventScroll p) => O.IsLabel t (EventScroll -> p) where
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif