{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Interfaces.Component
(
Component(..) ,
noComponent ,
IsComponent ,
toComponent ,
#if defined(ENABLE_OVERLOADING)
ResolveComponentMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ComponentContainsMethodInfo ,
#endif
componentContains ,
#if defined(ENABLE_OVERLOADING)
ComponentGetAlphaMethodInfo ,
#endif
componentGetAlpha ,
#if defined(ENABLE_OVERLOADING)
ComponentGetExtentsMethodInfo ,
#endif
componentGetExtents ,
#if defined(ENABLE_OVERLOADING)
ComponentGetLayerMethodInfo ,
#endif
componentGetLayer ,
#if defined(ENABLE_OVERLOADING)
ComponentGetMdiZorderMethodInfo ,
#endif
componentGetMdiZorder ,
#if defined(ENABLE_OVERLOADING)
ComponentGetPositionMethodInfo ,
#endif
componentGetPosition ,
#if defined(ENABLE_OVERLOADING)
ComponentGetSizeMethodInfo ,
#endif
componentGetSize ,
#if defined(ENABLE_OVERLOADING)
ComponentGrabFocusMethodInfo ,
#endif
componentGrabFocus ,
#if defined(ENABLE_OVERLOADING)
ComponentRefAccessibleAtPointMethodInfo ,
#endif
componentRefAccessibleAtPoint ,
#if defined(ENABLE_OVERLOADING)
ComponentRemoveFocusHandlerMethodInfo ,
#endif
componentRemoveFocusHandler ,
#if defined(ENABLE_OVERLOADING)
ComponentScrollToMethodInfo ,
#endif
componentScrollTo ,
#if defined(ENABLE_OVERLOADING)
ComponentScrollToPointMethodInfo ,
#endif
componentScrollToPoint ,
#if defined(ENABLE_OVERLOADING)
ComponentSetExtentsMethodInfo ,
#endif
componentSetExtents ,
#if defined(ENABLE_OVERLOADING)
ComponentSetPositionMethodInfo ,
#endif
componentSetPosition ,
#if defined(ENABLE_OVERLOADING)
ComponentSetSizeMethodInfo ,
#endif
componentSetSize ,
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
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)
noComponent :: Maybe Component
noComponent :: Maybe Component
noComponent = Maybe Component
forall a. Maybe a
Nothing
type ComponentBoundsChangedCallback =
Atk.Rectangle.Rectangle
-> IO ()
noComponentBoundsChangedCallback :: Maybe ComponentBoundsChangedCallback
noComponentBoundsChangedCallback :: Maybe ComponentBoundsChangedCallback
noComponentBoundsChangedCallback = Maybe ComponentBoundsChangedCallback
forall a. Maybe a
Nothing
type C_ComponentBoundsChangedCallback =
Ptr () ->
Ptr Atk.Rectangle.Rectangle ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ComponentBoundsChangedCallback :: C_ComponentBoundsChangedCallback -> IO (FunPtr C_ComponentBoundsChangedCallback)
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_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'
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
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
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
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]
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
foreign import ccall "atk_component_contains" atk_component_contains ::
Ptr Component ->
Int32 ->
Int32 ->
CUInt ->
IO CInt
componentContains ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Int32
-> Int32
-> Atk.Enums.CoordType
-> m Bool
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
foreign import ccall "atk_component_get_alpha" atk_component_get_alpha ::
Ptr Component ->
IO CDouble
componentGetAlpha ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> m Double
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
foreign import ccall "atk_component_get_extents" atk_component_get_extents ::
Ptr Component ->
Ptr Int32 ->
Ptr Int32 ->
Ptr Int32 ->
Ptr Int32 ->
CUInt ->
IO ()
componentGetExtents ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Atk.Enums.CoordType
-> 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
foreign import ccall "atk_component_get_layer" atk_component_get_layer ::
Ptr Component ->
IO CUInt
componentGetLayer ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> m Atk.Enums.Layer
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
foreign import ccall "atk_component_get_mdi_zorder" atk_component_get_mdi_zorder ::
Ptr Component ->
IO Int32
componentGetMdiZorder ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> m Int32
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
foreign import ccall "atk_component_get_position" atk_component_get_position ::
Ptr Component ->
Ptr Int32 ->
Ptr Int32 ->
CUInt ->
IO ()
{-# DEPRECATED componentGetPosition ["Since 2.12. Use 'GI.Atk.Interfaces.Component.componentGetExtents' instead."] #-}
componentGetPosition ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Atk.Enums.CoordType
-> 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
foreign import ccall "atk_component_get_size" atk_component_get_size ::
Ptr Component ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
{-# DEPRECATED componentGetSize ["Since 2.12. Use 'GI.Atk.Interfaces.Component.componentGetExtents' instead."] #-}
componentGetSize ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> 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
foreign import ccall "atk_component_grab_focus" atk_component_grab_focus ::
Ptr Component ->
IO CInt
componentGrabFocus ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> m Bool
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
foreign import ccall "atk_component_ref_accessible_at_point" atk_component_ref_accessible_at_point ::
Ptr Component ->
Int32 ->
Int32 ->
CUInt ->
IO (Ptr Atk.Object.Object)
componentRefAccessibleAtPoint ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Int32
-> Int32
-> Atk.Enums.CoordType
-> m (Maybe Atk.Object.Object)
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
foreign import ccall "atk_component_remove_focus_handler" atk_component_remove_focus_handler ::
Ptr Component ->
Word32 ->
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."] #-}
componentRemoveFocusHandler ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Word32
-> 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
foreign import ccall "atk_component_scroll_to" atk_component_scroll_to ::
Ptr Component ->
CUInt ->
IO CInt
componentScrollTo ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Atk.Enums.ScrollType
-> m Bool
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
foreign import ccall "atk_component_scroll_to_point" atk_component_scroll_to_point ::
Ptr Component ->
CUInt ->
Int32 ->
Int32 ->
IO CInt
componentScrollToPoint ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Atk.Enums.CoordType
-> Int32
-> Int32
-> m Bool
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
foreign import ccall "atk_component_set_extents" atk_component_set_extents ::
Ptr Component ->
Int32 ->
Int32 ->
Int32 ->
Int32 ->
CUInt ->
IO CInt
componentSetExtents ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Int32
-> Int32
-> Int32
-> Int32
-> Atk.Enums.CoordType
-> m Bool
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
foreign import ccall "atk_component_set_position" atk_component_set_position ::
Ptr Component ->
Int32 ->
Int32 ->
CUInt ->
IO CInt
componentSetPosition ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Int32
-> Int32
-> Atk.Enums.CoordType
-> m Bool
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
foreign import ccall "atk_component_set_size" atk_component_set_size ::
Ptr Component ->
Int32 ->
Int32 ->
IO CInt
componentSetSize ::
(B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
a
-> Int32
-> Int32
-> m Bool
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