{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Atk.Interfaces.Component.Component' should be implemented by most if not all UI elements
-- with an actual on-screen presence, i.e. components which can be
-- said to have a screen-coordinate bounding box.  Virtually all
-- widgets will need to have t'GI.Atk.Interfaces.Component.Component' implementations provided
-- for their corresponding t'GI.Atk.Objects.Object.Object' class.  In short, only UI
-- elements which are *not* GUI elements will omit this ATK interface.
-- 
-- A possible exception might be textual information with a
-- transparent background, in which case text glyph bounding box
-- information is provided by t'GI.Atk.Interfaces.Text.Text'.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Atk.Interfaces.Component
    ( 

-- * Exported types
    Component(..)                           ,
    noComponent                             ,
    IsComponent                             ,
    toComponent                             ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveComponentMethod                  ,
#endif


-- ** contains #method:contains#

#if defined(ENABLE_OVERLOADING)
    ComponentContainsMethodInfo             ,
#endif
    componentContains                       ,


-- ** getAlpha #method:getAlpha#

#if defined(ENABLE_OVERLOADING)
    ComponentGetAlphaMethodInfo             ,
#endif
    componentGetAlpha                       ,


-- ** getExtents #method:getExtents#

#if defined(ENABLE_OVERLOADING)
    ComponentGetExtentsMethodInfo           ,
#endif
    componentGetExtents                     ,


-- ** getLayer #method:getLayer#

#if defined(ENABLE_OVERLOADING)
    ComponentGetLayerMethodInfo             ,
#endif
    componentGetLayer                       ,


-- ** getMdiZorder #method:getMdiZorder#

#if defined(ENABLE_OVERLOADING)
    ComponentGetMdiZorderMethodInfo         ,
#endif
    componentGetMdiZorder                   ,


-- ** getPosition #method:getPosition#

#if defined(ENABLE_OVERLOADING)
    ComponentGetPositionMethodInfo          ,
#endif
    componentGetPosition                    ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    ComponentGetSizeMethodInfo              ,
#endif
    componentGetSize                        ,


-- ** grabFocus #method:grabFocus#

#if defined(ENABLE_OVERLOADING)
    ComponentGrabFocusMethodInfo            ,
#endif
    componentGrabFocus                      ,


-- ** refAccessibleAtPoint #method:refAccessibleAtPoint#

#if defined(ENABLE_OVERLOADING)
    ComponentRefAccessibleAtPointMethodInfo ,
#endif
    componentRefAccessibleAtPoint           ,


-- ** removeFocusHandler #method:removeFocusHandler#

#if defined(ENABLE_OVERLOADING)
    ComponentRemoveFocusHandlerMethodInfo   ,
#endif
    componentRemoveFocusHandler             ,


-- ** scrollTo #method:scrollTo#

#if defined(ENABLE_OVERLOADING)
    ComponentScrollToMethodInfo             ,
#endif
    componentScrollTo                       ,


-- ** scrollToPoint #method:scrollToPoint#

#if defined(ENABLE_OVERLOADING)
    ComponentScrollToPointMethodInfo        ,
#endif
    componentScrollToPoint                  ,


-- ** setExtents #method:setExtents#

#if defined(ENABLE_OVERLOADING)
    ComponentSetExtentsMethodInfo           ,
#endif
    componentSetExtents                     ,


-- ** setPosition #method:setPosition#

#if defined(ENABLE_OVERLOADING)
    ComponentSetPositionMethodInfo          ,
#endif
    componentSetPosition                    ,


-- ** setSize #method:setSize#

#if defined(ENABLE_OVERLOADING)
    ComponentSetSizeMethodInfo              ,
#endif
    componentSetSize                        ,




 -- * Signals
-- ** boundsChanged #signal:boundsChanged#

    C_ComponentBoundsChangedCallback        ,
    ComponentBoundsChangedCallback          ,
#if defined(ENABLE_OVERLOADING)
    ComponentBoundsChangedSignalInfo        ,
#endif
    afterComponentBoundsChanged             ,
    genClosure_ComponentBoundsChanged       ,
    mk_ComponentBoundsChangedCallback       ,
    noComponentBoundsChangedCallback        ,
    onComponentBoundsChanged                ,
    wrap_ComponentBoundsChangedCallback     ,




    ) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
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 GHC.OverloadedLabels as OL

import {-# SOURCE #-} qualified GI.Atk.Enums as Atk.Enums
import {-# SOURCE #-} qualified GI.Atk.Objects.Object as Atk.Object
import {-# SOURCE #-} qualified GI.Atk.Structs.Rectangle as Atk.Rectangle
import qualified GI.GObject.Objects.Object as GObject.Object

-- interface Component 
-- | Memory-managed wrapper type.
newtype Component = Component (ManagedPtr Component)
    deriving (Component -> Component -> Bool
(Component -> Component -> Bool)
-> (Component -> Component -> Bool) -> Eq Component
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Component -> Component -> Bool
$c/= :: Component -> Component -> Bool
== :: Component -> Component -> Bool
$c== :: Component -> Component -> Bool
Eq)
-- | A convenience alias for `Nothing` :: `Maybe` `Component`.
noComponent :: Maybe Component
noComponent :: Maybe Component
noComponent = Maybe Component
forall a. Maybe a
Nothing

-- signal Component::bounds-changed
-- | The \'bounds-changed\" signal is emitted when the bposition or
-- size of the component changes.
type ComponentBoundsChangedCallback =
    Atk.Rectangle.Rectangle
    -- ^ /@arg1@/: The AtkRectangle giving the new position and size.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ComponentBoundsChangedCallback`@.
noComponentBoundsChangedCallback :: Maybe ComponentBoundsChangedCallback
noComponentBoundsChangedCallback :: Maybe ComponentBoundsChangedCallback
noComponentBoundsChangedCallback = Maybe ComponentBoundsChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ComponentBoundsChangedCallback =
    Ptr () ->                               -- object
    Ptr Atk.Rectangle.Rectangle ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ComponentBoundsChangedCallback`.
foreign import ccall "wrapper"
    mk_ComponentBoundsChangedCallback :: C_ComponentBoundsChangedCallback -> IO (FunPtr C_ComponentBoundsChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ComponentBoundsChanged :: MonadIO m => ComponentBoundsChangedCallback -> m (GClosure C_ComponentBoundsChangedCallback)
genClosure_ComponentBoundsChanged :: ComponentBoundsChangedCallback
-> m (GClosure C_ComponentBoundsChangedCallback)
genClosure_ComponentBoundsChanged cb :: ComponentBoundsChangedCallback
cb = IO (GClosure C_ComponentBoundsChangedCallback)
-> m (GClosure C_ComponentBoundsChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ComponentBoundsChangedCallback)
 -> m (GClosure C_ComponentBoundsChangedCallback))
-> IO (GClosure C_ComponentBoundsChangedCallback)
-> m (GClosure C_ComponentBoundsChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ComponentBoundsChangedCallback
cb' = ComponentBoundsChangedCallback -> C_ComponentBoundsChangedCallback
wrap_ComponentBoundsChangedCallback ComponentBoundsChangedCallback
cb
    C_ComponentBoundsChangedCallback
-> IO (FunPtr C_ComponentBoundsChangedCallback)
mk_ComponentBoundsChangedCallback C_ComponentBoundsChangedCallback
cb' IO (FunPtr C_ComponentBoundsChangedCallback)
-> (FunPtr C_ComponentBoundsChangedCallback
    -> IO (GClosure C_ComponentBoundsChangedCallback))
-> IO (GClosure C_ComponentBoundsChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ComponentBoundsChangedCallback
-> IO (GClosure C_ComponentBoundsChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ComponentBoundsChangedCallback` into a `C_ComponentBoundsChangedCallback`.
wrap_ComponentBoundsChangedCallback ::
    ComponentBoundsChangedCallback ->
    C_ComponentBoundsChangedCallback
wrap_ComponentBoundsChangedCallback :: ComponentBoundsChangedCallback -> C_ComponentBoundsChangedCallback
wrap_ComponentBoundsChangedCallback _cb :: ComponentBoundsChangedCallback
_cb _ arg1 :: Ptr Rectangle
arg1 _ = do
    (ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> ComponentBoundsChangedCallback -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr Rectangle -> Rectangle
Atk.Rectangle.Rectangle Ptr Rectangle
arg1 (ComponentBoundsChangedCallback -> IO ())
-> ComponentBoundsChangedCallback -> IO ()
forall a b. (a -> b) -> a -> b
$ \arg1' :: Rectangle
arg1' -> do
        ComponentBoundsChangedCallback
_cb  Rectangle
arg1'


-- | Connect a signal handler for the [boundsChanged](#signal:boundsChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' component #boundsChanged callback
-- @
-- 
-- 
onComponentBoundsChanged :: (IsComponent a, MonadIO m) => a -> ComponentBoundsChangedCallback -> m SignalHandlerId
onComponentBoundsChanged :: a -> ComponentBoundsChangedCallback -> m SignalHandlerId
onComponentBoundsChanged obj :: a
obj cb :: ComponentBoundsChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ComponentBoundsChangedCallback
cb' = ComponentBoundsChangedCallback -> C_ComponentBoundsChangedCallback
wrap_ComponentBoundsChangedCallback ComponentBoundsChangedCallback
cb
    FunPtr C_ComponentBoundsChangedCallback
cb'' <- C_ComponentBoundsChangedCallback
-> IO (FunPtr C_ComponentBoundsChangedCallback)
mk_ComponentBoundsChangedCallback C_ComponentBoundsChangedCallback
cb'
    a
-> Text
-> FunPtr C_ComponentBoundsChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "bounds-changed" FunPtr C_ComponentBoundsChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [boundsChanged](#signal:boundsChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' component #boundsChanged callback
-- @
-- 
-- 
afterComponentBoundsChanged :: (IsComponent a, MonadIO m) => a -> ComponentBoundsChangedCallback -> m SignalHandlerId
afterComponentBoundsChanged :: a -> ComponentBoundsChangedCallback -> m SignalHandlerId
afterComponentBoundsChanged obj :: a
obj cb :: ComponentBoundsChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ComponentBoundsChangedCallback
cb' = ComponentBoundsChangedCallback -> C_ComponentBoundsChangedCallback
wrap_ComponentBoundsChangedCallback ComponentBoundsChangedCallback
cb
    FunPtr C_ComponentBoundsChangedCallback
cb'' <- C_ComponentBoundsChangedCallback
-> IO (FunPtr C_ComponentBoundsChangedCallback)
mk_ComponentBoundsChangedCallback C_ComponentBoundsChangedCallback
cb'
    a
-> Text
-> FunPtr C_ComponentBoundsChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "bounds-changed" FunPtr C_ComponentBoundsChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data ComponentBoundsChangedSignalInfo
instance SignalInfo ComponentBoundsChangedSignalInfo where
    type HaskellCallbackType ComponentBoundsChangedSignalInfo = ComponentBoundsChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ComponentBoundsChangedCallback cb
        cb'' <- mk_ComponentBoundsChangedCallback cb'
        connectSignalFunPtr obj "bounds-changed" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Component = ComponentSignalList
type ComponentSignalList = ('[ '("boundsChanged", ComponentBoundsChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

foreign import ccall "atk_component_get_type"
    c_atk_component_get_type :: IO GType

instance GObject Component where
    gobjectType :: IO GType
gobjectType = IO GType
c_atk_component_get_type
    

-- | Convert 'Component' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Component where
    toGValue :: Component -> IO GValue
toGValue o :: Component
o = do
        GType
gtype <- IO GType
c_atk_component_get_type
        Component -> (Ptr Component -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Component
o (GType
-> (GValue -> Ptr Component -> IO ()) -> Ptr Component -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Component -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Component
fromGValue gv :: GValue
gv = do
        Ptr Component
ptr <- GValue -> IO (Ptr Component)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Component)
        (ManagedPtr Component -> Component)
-> Ptr Component -> IO Component
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Component -> Component
Component Ptr Component
ptr
        
    

-- | Type class for types which can be safely cast to `Component`, for instance with `toComponent`.
class (GObject o, O.IsDescendantOf Component o) => IsComponent o
instance (GObject o, O.IsDescendantOf Component o) => IsComponent o

instance O.HasParentTypes Component
type instance O.ParentTypes Component = '[GObject.Object.Object]

-- | Cast to `Component`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toComponent :: (MonadIO m, IsComponent o) => o -> m Component
toComponent :: o -> m Component
toComponent = IO Component -> m Component
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Component -> m Component)
-> (o -> IO Component) -> o -> m Component
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Component -> Component) -> o -> IO Component
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Component -> Component
Component

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Component
type instance O.AttributeList Component = ComponentAttributeList
type ComponentAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveComponentMethod (t :: Symbol) (o :: *) :: * where
    ResolveComponentMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveComponentMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveComponentMethod "contains" o = ComponentContainsMethodInfo
    ResolveComponentMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveComponentMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveComponentMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveComponentMethod "grabFocus" o = ComponentGrabFocusMethodInfo
    ResolveComponentMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveComponentMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveComponentMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveComponentMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveComponentMethod "refAccessibleAtPoint" o = ComponentRefAccessibleAtPointMethodInfo
    ResolveComponentMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveComponentMethod "removeFocusHandler" o = ComponentRemoveFocusHandlerMethodInfo
    ResolveComponentMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveComponentMethod "scrollTo" o = ComponentScrollToMethodInfo
    ResolveComponentMethod "scrollToPoint" o = ComponentScrollToPointMethodInfo
    ResolveComponentMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveComponentMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveComponentMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveComponentMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveComponentMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveComponentMethod "getAlpha" o = ComponentGetAlphaMethodInfo
    ResolveComponentMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveComponentMethod "getExtents" o = ComponentGetExtentsMethodInfo
    ResolveComponentMethod "getLayer" o = ComponentGetLayerMethodInfo
    ResolveComponentMethod "getMdiZorder" o = ComponentGetMdiZorderMethodInfo
    ResolveComponentMethod "getPosition" o = ComponentGetPositionMethodInfo
    ResolveComponentMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveComponentMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveComponentMethod "getSize" o = ComponentGetSizeMethodInfo
    ResolveComponentMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveComponentMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveComponentMethod "setExtents" o = ComponentSetExtentsMethodInfo
    ResolveComponentMethod "setPosition" o = ComponentSetPositionMethodInfo
    ResolveComponentMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveComponentMethod "setSize" o = ComponentSetSizeMethodInfo
    ResolveComponentMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveComponentMethod t Component, O.MethodInfo info Component p) => OL.IsLabel t (Component -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- method Component::contains
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies whether the coordinates are relative to the screen\nor to the components top level window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_contains" atk_component_contains :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO CInt

-- | Checks whether the specified point is within the extent of the /@component@/.
-- 
-- Toolkit implementor note: ATK provides a default implementation for
-- this virtual method. In general there are little reason to
-- re-implement it.
componentContains ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: the t'GI.Atk.Interfaces.Component.Component'
    -> Int32
    -- ^ /@x@/: x coordinate
    -> Int32
    -- ^ /@y@/: y coordinate
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: specifies whether the coordinates are relative to the screen
    -- or to the components top level window
    -> m Bool
    -- ^ __Returns:__ 'P.True' or 'P.False' indicating whether the specified point is within
    -- the extent of the /@component@/ or not
componentContains :: a -> Int32 -> Int32 -> CoordType -> m Bool
componentContains component :: a
component x :: Int32
x y :: Int32
y coordType :: CoordType
coordType = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    CInt
result <- Ptr Component -> Int32 -> Int32 -> CUInt -> IO CInt
atk_component_contains Ptr Component
component' Int32
x Int32
y CUInt
coordType'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComponentContainsMethodInfo
instance (signature ~ (Int32 -> Int32 -> Atk.Enums.CoordType -> m Bool), MonadIO m, IsComponent a) => O.MethodInfo ComponentContainsMethodInfo a signature where
    overloadedMethod = componentContains

#endif

-- method Component::get_alpha
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_get_alpha" atk_component_get_alpha :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    IO CDouble

-- | Returns the alpha value (i.e. the opacity) for this
-- /@component@/, on a scale from 0 (fully transparent) to 1.0
-- (fully opaque).
-- 
-- /Since: 1.12/
componentGetAlpha ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> m Double
    -- ^ __Returns:__ An alpha value from 0 to 1.0, inclusive.
componentGetAlpha :: a -> m Double
componentGetAlpha component :: a
component = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CDouble
result <- Ptr Component -> IO CDouble
atk_component_get_alpha Ptr Component
component'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetAlphaMethodInfo
instance (signature ~ (m Double), MonadIO m, IsComponent a) => O.MethodInfo ComponentGetAlphaMethodInfo a signature where
    overloadedMethod = componentGetAlpha

#endif

-- method Component::get_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address of #gint to put x coordinate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address of #gint to put y coordinate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address of #gint to put width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address of #gint to put height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies whether the coordinates are relative to the screen\nor to the components top level window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_get_extents" atk_component_get_extents :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Ptr Int32 ->                            -- x : TBasicType TInt
    Ptr Int32 ->                            -- y : TBasicType TInt
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO ()

-- | Gets the rectangle which gives the extent of the /@component@/.
componentGetExtents ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: specifies whether the coordinates are relative to the screen
    -- or to the components top level window
    -> m ((Int32, Int32, Int32, Int32))
componentGetExtents :: a -> CoordType -> m (Int32, Int32, Int32, Int32)
componentGetExtents component :: a
component coordType :: CoordType
coordType = IO (Int32, Int32, Int32, Int32) -> m (Int32, Int32, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32, Int32, Int32) -> m (Int32, Int32, Int32, Int32))
-> IO (Int32, Int32, Int32, Int32)
-> m (Int32, Int32, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr Int32
x <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
y <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    Ptr Component
-> Ptr Int32
-> Ptr Int32
-> Ptr Int32
-> Ptr Int32
-> CUInt
-> IO ()
atk_component_get_extents Ptr Component
component' Ptr Int32
x Ptr Int32
y Ptr Int32
width Ptr Int32
height CUInt
coordType'
    Int32
x' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
x
    Int32
y' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y
    Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
x
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    (Int32, Int32, Int32, Int32) -> IO (Int32, Int32, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
x', Int32
y', Int32
width', Int32
height')

#if defined(ENABLE_OVERLOADING)
data ComponentGetExtentsMethodInfo
instance (signature ~ (Atk.Enums.CoordType -> m ((Int32, Int32, Int32, Int32))), MonadIO m, IsComponent a) => O.MethodInfo ComponentGetExtentsMethodInfo a signature where
    overloadedMethod = componentGetExtents

#endif

-- method Component::get_layer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "Layer" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_get_layer" atk_component_get_layer :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    IO CUInt

-- | Gets the layer of the component.
componentGetLayer ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> m Atk.Enums.Layer
    -- ^ __Returns:__ an t'GI.Atk.Enums.Layer' which is the layer of the component
componentGetLayer :: a -> m Layer
componentGetLayer component :: a
component = IO Layer -> m Layer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Layer -> m Layer) -> IO Layer -> m Layer
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CUInt
result <- Ptr Component -> IO CUInt
atk_component_get_layer Ptr Component
component'
    let result' :: Layer
result' = (Int -> Layer
forall a. Enum a => Int -> a
toEnum (Int -> Layer) -> (CUInt -> Int) -> CUInt -> Layer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Layer -> IO Layer
forall (m :: * -> *) a. Monad m => a -> m a
return Layer
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetLayerMethodInfo
instance (signature ~ (m Atk.Enums.Layer), MonadIO m, IsComponent a) => O.MethodInfo ComponentGetLayerMethodInfo a signature where
    overloadedMethod = componentGetLayer

#endif

-- method Component::get_mdi_zorder
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_get_mdi_zorder" atk_component_get_mdi_zorder :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    IO Int32

-- | Gets the zorder of the component. The value G_MININT will be returned
-- if the layer of the component is not ATK_LAYER_MDI or ATK_LAYER_WINDOW.
componentGetMdiZorder ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> m Int32
    -- ^ __Returns:__ a gint which is the zorder of the component, i.e. the depth at
    -- which the component is shown in relation to other components in the same
    -- container.
componentGetMdiZorder :: a -> m Int32
componentGetMdiZorder component :: a
component = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Int32
result <- Ptr Component -> IO Int32
atk_component_get_mdi_zorder Ptr Component
component'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ComponentGetMdiZorderMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsComponent a) => O.MethodInfo ComponentGetMdiZorderMethodInfo a signature where
    overloadedMethod = componentGetMdiZorder

#endif

-- method Component::get_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address of #gint to put x coordinate position"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address of #gint to put y coordinate position"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies whether the coordinates are relative to the screen\nor to the components top level window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_get_position" atk_component_get_position :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Ptr Int32 ->                            -- x : TBasicType TInt
    Ptr Int32 ->                            -- y : TBasicType TInt
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO ()

{-# DEPRECATED componentGetPosition ["Since 2.12. Use 'GI.Atk.Interfaces.Component.componentGetExtents' instead."] #-}
-- | Gets the position of /@component@/ in the form of
-- a point specifying /@component@/\'s top-left corner.
componentGetPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: specifies whether the coordinates are relative to the screen
    -- or to the components top level window
    -> m ((Int32, Int32))
componentGetPosition :: a -> CoordType -> m (Int32, Int32)
componentGetPosition component :: a
component coordType :: CoordType
coordType = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr Int32
x <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
y <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    Ptr Component -> Ptr Int32 -> Ptr Int32 -> CUInt -> IO ()
atk_component_get_position Ptr Component
component' Ptr Int32
x Ptr Int32
y CUInt
coordType'
    Int32
x' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
x
    Int32
y' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
x
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
x', Int32
y')

#if defined(ENABLE_OVERLOADING)
data ComponentGetPositionMethodInfo
instance (signature ~ (Atk.Enums.CoordType -> m ((Int32, Int32))), MonadIO m, IsComponent a) => O.MethodInfo ComponentGetPositionMethodInfo a signature where
    overloadedMethod = componentGetPosition

#endif

-- method Component::get_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address of #gint to put width of @component"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address of #gint to put height of @component"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_get_size" atk_component_get_size :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    IO ()

{-# DEPRECATED componentGetSize ["Since 2.12. Use 'GI.Atk.Interfaces.Component.componentGetExtents' instead."] #-}
-- | Gets the size of the /@component@/ in terms of width and height.
componentGetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> m ((Int32, Int32))
componentGetSize :: a -> m (Int32, Int32)
componentGetSize component :: a
component = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Component -> Ptr Int32 -> Ptr Int32 -> IO ()
atk_component_get_size Ptr Component
component' Ptr Int32
width Ptr Int32
height
    Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
width', Int32
height')

#if defined(ENABLE_OVERLOADING)
data ComponentGetSizeMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsComponent a) => O.MethodInfo ComponentGetSizeMethodInfo a signature where
    overloadedMethod = componentGetSize

#endif

-- method Component::grab_focus
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_grab_focus" atk_component_grab_focus :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    IO CInt

-- | Grabs focus for this /@component@/.
componentGrabFocus ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if successful, 'P.False' otherwise.
componentGrabFocus :: a -> m Bool
componentGrabFocus component :: a
component = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CInt
result <- Ptr Component -> IO CInt
atk_component_grab_focus Ptr Component
component'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGrabFocusMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsComponent a) => O.MethodInfo ComponentGrabFocusMethodInfo a signature where
    overloadedMethod = componentGrabFocus

#endif

-- method Component::ref_accessible_at_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies whether the coordinates are relative to the screen\nor to the components top level window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_ref_accessible_at_point" atk_component_ref_accessible_at_point :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO (Ptr Atk.Object.Object)

-- | Gets a reference to the accessible child, if one exists, at the
-- coordinate point specified by /@x@/ and /@y@/.
componentRefAccessibleAtPoint ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: the t'GI.Atk.Interfaces.Component.Component'
    -> Int32
    -- ^ /@x@/: x coordinate
    -> Int32
    -- ^ /@y@/: y coordinate
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: specifies whether the coordinates are relative to the screen
    -- or to the components top level window
    -> m (Maybe Atk.Object.Object)
    -- ^ __Returns:__ a reference to the accessible
    -- child, if one exists
componentRefAccessibleAtPoint :: a -> Int32 -> Int32 -> CoordType -> m (Maybe Object)
componentRefAccessibleAtPoint component :: a
component x :: Int32
x y :: Int32
y coordType :: CoordType
coordType = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    Ptr Object
result <- Ptr Component -> Int32 -> Int32 -> CUInt -> IO (Ptr Object)
atk_component_ref_accessible_at_point Ptr Component
component' Int32
x Int32
y CUInt
coordType'
    Maybe Object
maybeResult <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Object
result ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Object
result' -> do
        Object
result'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
Atk.Object.Object) Ptr Object
result'
        Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
maybeResult

#if defined(ENABLE_OVERLOADING)
data ComponentRefAccessibleAtPointMethodInfo
instance (signature ~ (Int32 -> Int32 -> Atk.Enums.CoordType -> m (Maybe Atk.Object.Object)), MonadIO m, IsComponent a) => O.MethodInfo ComponentRefAccessibleAtPointMethodInfo a signature where
    overloadedMethod = componentRefAccessibleAtPoint

#endif

-- method Component::remove_focus_handler
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #AtkComponent to remove the focus handler from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "handler_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the handler id of the focus handler to be removed\nfrom @component"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_remove_focus_handler" atk_component_remove_focus_handler :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Word32 ->                               -- handler_id : TBasicType TUInt
    IO ()

{-# DEPRECATED componentRemoveFocusHandler ["(Since version 2.9.4)","If you need to track when an object gains or","lose the focus, use the [stateChange](\"GI.Atk.Objects.Object#signal:stateChange\") \\\"focused\\\" notification instead."] #-}
-- | Remove the handler specified by /@handlerId@/ from the list of
-- functions to be executed when this object receives focus events
-- (in or out).
componentRemoveFocusHandler ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: the t'GI.Atk.Interfaces.Component.Component' to remove the focus handler from
    -> Word32
    -- ^ /@handlerId@/: the handler id of the focus handler to be removed
    -- from /@component@/
    -> m ()
componentRemoveFocusHandler :: a -> Word32 -> m ()
componentRemoveFocusHandler component :: a
component handlerId :: Word32
handlerId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr Component -> Word32 -> IO ()
atk_component_remove_focus_handler Ptr Component
component' Word32
handlerId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComponentRemoveFocusHandlerMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsComponent a) => O.MethodInfo ComponentRemoveFocusHandlerMethodInfo a signature where
    overloadedMethod = componentRemoveFocusHandler

#endif

-- method Component::scroll_to
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "ScrollType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "specify where the object should be made visible."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_scroll_to" atk_component_scroll_to :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    CUInt ->                                -- type : TInterface (Name {namespace = "Atk", name = "ScrollType"})
    IO CInt

-- | Makes /@component@/ visible on the screen by scrolling all necessary parents.
-- 
-- Contrary to atk_component_set_position, this does not actually move
-- /@component@/ in its parent, this only makes the parents scroll so that the
-- object shows up on the screen, given its current position within the parents.
-- 
-- /Since: 2.30/
componentScrollTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> Atk.Enums.ScrollType
    -- ^ /@type@/: specify where the object should be made visible.
    -> m Bool
    -- ^ __Returns:__ whether scrolling was successful.
componentScrollTo :: a -> ScrollType -> m Bool
componentScrollTo component :: a
component type_ :: ScrollType
type_ = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (ScrollType -> Int) -> ScrollType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScrollType -> Int
forall a. Enum a => a -> Int
fromEnum) ScrollType
type_
    CInt
result <- Ptr Component -> CUInt -> IO CInt
atk_component_scroll_to Ptr Component
component' CUInt
type_'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComponentScrollToMethodInfo
instance (signature ~ (Atk.Enums.ScrollType -> m Bool), MonadIO m, IsComponent a) => O.MethodInfo ComponentScrollToMethodInfo a signature where
    overloadedMethod = componentScrollTo

#endif

-- method Component::scroll_to_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coords"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specify whether coordinates are relative to the screen or to the\nparent object."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x-position where to scroll to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y-position where to scroll to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_scroll_to_point" atk_component_scroll_to_point :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    CUInt ->                                -- coords : TInterface (Name {namespace = "Atk", name = "CoordType"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO CInt

-- | Makes an object visible on the screen at a given position by scrolling all
-- necessary parents.
-- 
-- /Since: 2.30/
componentScrollToPoint ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> Atk.Enums.CoordType
    -- ^ /@coords@/: specify whether coordinates are relative to the screen or to the
    -- parent object.
    -> Int32
    -- ^ /@x@/: x-position where to scroll to
    -> Int32
    -- ^ /@y@/: y-position where to scroll to
    -> m Bool
    -- ^ __Returns:__ whether scrolling was successful.
componentScrollToPoint :: a -> CoordType -> Int32 -> Int32 -> m Bool
componentScrollToPoint component :: a
component coords :: CoordType
coords x :: Int32
x y :: Int32
y = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    let coords' :: CUInt
coords' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coords
    CInt
result <- Ptr Component -> CUInt -> Int32 -> Int32 -> IO CInt
atk_component_scroll_to_point Ptr Component
component' CUInt
coords' Int32
x Int32
y
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComponentScrollToPointMethodInfo
instance (signature ~ (Atk.Enums.CoordType -> Int32 -> Int32 -> m Bool), MonadIO m, IsComponent a) => O.MethodInfo ComponentScrollToPointMethodInfo a signature where
    overloadedMethod = componentScrollToPoint

#endif

-- method Component::set_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width to set for @component"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height to set for @component"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies whether the coordinates are relative to the screen\nor to the components top level window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_set_extents" atk_component_set_extents :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO CInt

-- | Sets the extents of /@component@/.
componentSetExtents ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> Int32
    -- ^ /@x@/: x coordinate
    -> Int32
    -- ^ /@y@/: y coordinate
    -> Int32
    -- ^ /@width@/: width to set for /@component@/
    -> Int32
    -- ^ /@height@/: height to set for /@component@/
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: specifies whether the coordinates are relative to the screen
    -- or to the components top level window
    -> m Bool
    -- ^ __Returns:__ 'P.True' or 'P.False' whether the extents were set or not
componentSetExtents :: a -> Int32 -> Int32 -> Int32 -> Int32 -> CoordType -> m Bool
componentSetExtents component :: a
component x :: Int32
x y :: Int32
y width :: Int32
width height :: Int32
height coordType :: CoordType
coordType = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    CInt
result <- Ptr Component
-> Int32 -> Int32 -> Int32 -> Int32 -> CUInt -> IO CInt
atk_component_set_extents Ptr Component
component' Int32
x Int32
y Int32
width Int32
height CUInt
coordType'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComponentSetExtentsMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> Int32 -> Atk.Enums.CoordType -> m Bool), MonadIO m, IsComponent a) => O.MethodInfo ComponentSetExtentsMethodInfo a signature where
    overloadedMethod = componentSetExtents

#endif

-- method Component::set_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies whether the coordinates are relative to the screen\nor to the component's top level window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_set_position" atk_component_set_position :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO CInt

-- | Sets the position of /@component@/.
-- 
-- Contrary to atk_component_scroll_to, this does not trigger any scrolling,
-- this just moves /@component@/ in its parent.
componentSetPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> Int32
    -- ^ /@x@/: x coordinate
    -> Int32
    -- ^ /@y@/: y coordinate
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: specifies whether the coordinates are relative to the screen
    -- or to the component\'s top level window
    -> m Bool
    -- ^ __Returns:__ 'P.True' or 'P.False' whether or not the position was set or not
componentSetPosition :: a -> Int32 -> Int32 -> CoordType -> m Bool
componentSetPosition component :: a
component x :: Int32
x y :: Int32
y coordType :: CoordType
coordType = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    CInt
result <- Ptr Component -> Int32 -> Int32 -> CUInt -> IO CInt
atk_component_set_position Ptr Component
component' Int32
x Int32
y CUInt
coordType'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComponentSetPositionMethodInfo
instance (signature ~ (Int32 -> Int32 -> Atk.Enums.CoordType -> m Bool), MonadIO m, IsComponent a) => O.MethodInfo ComponentSetPositionMethodInfo a signature where
    overloadedMethod = componentSetPosition

#endif

-- method Component::set_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width to set for @component"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height to set for @component"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_component_set_size" atk_component_set_size :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "Atk", name = "Component"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO CInt

-- | Set the size of the /@component@/ in terms of width and height.
componentSetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: an t'GI.Atk.Interfaces.Component.Component'
    -> Int32
    -- ^ /@width@/: width to set for /@component@/
    -> Int32
    -- ^ /@height@/: height to set for /@component@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' or 'P.False' whether the size was set or not
componentSetSize :: a -> Int32 -> Int32 -> m Bool
componentSetSize component :: a
component width :: Int32
width height :: Int32
height = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CInt
result <- Ptr Component -> Int32 -> Int32 -> IO CInt
atk_component_set_size Ptr Component
component' Int32
width Int32
height
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComponentSetSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Bool), MonadIO m, IsComponent a) => O.MethodInfo ComponentSetSizeMethodInfo a signature where
    overloadedMethod = componentSetSize

#endif