{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.Rectangle
(
Rectangle(..) ,
newZeroRectangle ,
#if defined(ENABLE_OVERLOADING)
ResolveRectangleMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
RectangleEqualMethodInfo ,
#endif
rectangleEqual ,
#if defined(ENABLE_OVERLOADING)
RectangleIntersectMethodInfo ,
#endif
rectangleIntersect ,
#if defined(ENABLE_OVERLOADING)
RectangleUnionMethodInfo ,
#endif
rectangleUnion ,
getRectangleHeight ,
#if defined(ENABLE_OVERLOADING)
rectangle_height ,
#endif
setRectangleHeight ,
getRectangleWidth ,
#if defined(ENABLE_OVERLOADING)
rectangle_width ,
#endif
setRectangleWidth ,
getRectangleX ,
#if defined(ENABLE_OVERLOADING)
rectangle_x ,
#endif
setRectangleX ,
getRectangleY ,
#if defined(ENABLE_OVERLOADING)
rectangle_y ,
#endif
setRectangleY ,
) 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.BasicTypes as B.Types
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 Control.Monad.IO.Class as MIO
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
newtype Rectangle = Rectangle (SP.ManagedPtr Rectangle)
deriving (Rectangle -> Rectangle -> Bool
(Rectangle -> Rectangle -> Bool)
-> (Rectangle -> Rectangle -> Bool) -> Eq Rectangle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rectangle -> Rectangle -> Bool
$c/= :: Rectangle -> Rectangle -> Bool
== :: Rectangle -> Rectangle -> Bool
$c== :: Rectangle -> Rectangle -> Bool
Eq)
instance SP.ManagedPtrNewtype Rectangle where
toManagedPtr :: Rectangle -> ManagedPtr Rectangle
toManagedPtr (Rectangle ManagedPtr Rectangle
p) = ManagedPtr Rectangle
p
foreign import ccall "gdk_rectangle_get_type" c_gdk_rectangle_get_type ::
IO GType
type instance O.ParentTypes Rectangle = '[]
instance O.HasParentTypes Rectangle
instance B.Types.TypedObject Rectangle where
glibType :: IO GType
glibType = IO GType
c_gdk_rectangle_get_type
instance B.Types.GBoxed Rectangle
instance B.GValue.IsGValue Rectangle where
toGValue :: Rectangle -> IO GValue
toGValue Rectangle
o = do
GType
gtype <- IO GType
c_gdk_rectangle_get_type
Rectangle -> (Ptr Rectangle -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Rectangle
o (GType
-> (GValue -> Ptr Rectangle -> IO ()) -> Ptr Rectangle -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Rectangle -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO Rectangle
fromGValue GValue
gv = do
Ptr Rectangle
ptr <- GValue -> IO (Ptr Rectangle)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Rectangle)
(ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Rectangle -> Rectangle
Rectangle Ptr Rectangle
ptr
newZeroRectangle :: MonadIO m => m Rectangle
newZeroRectangle :: m Rectangle
newZeroRectangle = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
16 IO (Ptr Rectangle)
-> (Ptr Rectangle -> IO Rectangle) -> IO Rectangle
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Rectangle
instance tag ~ 'AttrSet => Constructible Rectangle tag where
new :: (ManagedPtr Rectangle -> Rectangle)
-> [AttrOp Rectangle tag] -> m Rectangle
new ManagedPtr Rectangle -> Rectangle
_ [AttrOp Rectangle tag]
attrs = do
Rectangle
o <- m Rectangle
forall (m :: * -> *). MonadIO m => m Rectangle
newZeroRectangle
Rectangle -> [AttrOp Rectangle 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Rectangle
o [AttrOp Rectangle tag]
[AttrOp Rectangle 'AttrSet]
attrs
Rectangle -> m Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
o
getRectangleX :: MonadIO m => Rectangle -> m Int32
getRectangleX :: Rectangle -> m Int32
getRectangleX Rectangle
s = 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
$ Rectangle -> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Int32) -> IO Int32)
-> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setRectangleX :: MonadIO m => Rectangle -> Int32 -> m ()
setRectangleX :: Rectangle -> Int32 -> m ()
setRectangleX Rectangle
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data RectangleXFieldInfo
instance AttrInfo RectangleXFieldInfo where
type AttrBaseTypeConstraint RectangleXFieldInfo = (~) Rectangle
type AttrAllowedOps RectangleXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RectangleXFieldInfo = (~) Int32
type AttrTransferTypeConstraint RectangleXFieldInfo = (~)Int32
type AttrTransferType RectangleXFieldInfo = Int32
type AttrGetType RectangleXFieldInfo = Int32
type AttrLabel RectangleXFieldInfo = "x"
type AttrOrigin RectangleXFieldInfo = Rectangle
attrGet = getRectangleX
attrSet = setRectangleX
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
rectangle_x :: AttrLabelProxy "x"
rectangle_x = AttrLabelProxy
#endif
getRectangleY :: MonadIO m => Rectangle -> m Int32
getRectangleY :: Rectangle -> m Int32
getRectangleY Rectangle
s = 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
$ Rectangle -> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Int32) -> IO Int32)
-> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setRectangleY :: MonadIO m => Rectangle -> Int32 -> m ()
setRectangleY :: Rectangle -> Int32 -> m ()
setRectangleY Rectangle
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data RectangleYFieldInfo
instance AttrInfo RectangleYFieldInfo where
type AttrBaseTypeConstraint RectangleYFieldInfo = (~) Rectangle
type AttrAllowedOps RectangleYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RectangleYFieldInfo = (~) Int32
type AttrTransferTypeConstraint RectangleYFieldInfo = (~)Int32
type AttrTransferType RectangleYFieldInfo = Int32
type AttrGetType RectangleYFieldInfo = Int32
type AttrLabel RectangleYFieldInfo = "y"
type AttrOrigin RectangleYFieldInfo = Rectangle
attrGet = getRectangleY
attrSet = setRectangleY
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
rectangle_y :: AttrLabelProxy "y"
rectangle_y = AttrLabelProxy
#endif
getRectangleWidth :: MonadIO m => Rectangle -> m Int32
getRectangleWidth :: Rectangle -> m Int32
getRectangleWidth Rectangle
s = 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
$ Rectangle -> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Int32) -> IO Int32)
-> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setRectangleWidth :: MonadIO m => Rectangle -> Int32 -> m ()
setRectangleWidth :: Rectangle -> Int32 -> m ()
setRectangleWidth Rectangle
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data RectangleWidthFieldInfo
instance AttrInfo RectangleWidthFieldInfo where
type AttrBaseTypeConstraint RectangleWidthFieldInfo = (~) Rectangle
type AttrAllowedOps RectangleWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RectangleWidthFieldInfo = (~) Int32
type AttrTransferTypeConstraint RectangleWidthFieldInfo = (~)Int32
type AttrTransferType RectangleWidthFieldInfo = Int32
type AttrGetType RectangleWidthFieldInfo = Int32
type AttrLabel RectangleWidthFieldInfo = "width"
type AttrOrigin RectangleWidthFieldInfo = Rectangle
attrGet = getRectangleWidth
attrSet = setRectangleWidth
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
rectangle_width :: AttrLabelProxy "width"
rectangle_width = AttrLabelProxy
#endif
getRectangleHeight :: MonadIO m => Rectangle -> m Int32
getRectangleHeight :: Rectangle -> m Int32
getRectangleHeight Rectangle
s = 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
$ Rectangle -> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Int32) -> IO Int32)
-> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setRectangleHeight :: MonadIO m => Rectangle -> Int32 -> m ()
setRectangleHeight :: Rectangle -> Int32 -> m ()
setRectangleHeight Rectangle
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data RectangleHeightFieldInfo
instance AttrInfo RectangleHeightFieldInfo where
type AttrBaseTypeConstraint RectangleHeightFieldInfo = (~) Rectangle
type AttrAllowedOps RectangleHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RectangleHeightFieldInfo = (~) Int32
type AttrTransferTypeConstraint RectangleHeightFieldInfo = (~)Int32
type AttrTransferType RectangleHeightFieldInfo = Int32
type AttrGetType RectangleHeightFieldInfo = Int32
type AttrLabel RectangleHeightFieldInfo = "height"
type AttrOrigin RectangleHeightFieldInfo = Rectangle
attrGet = getRectangleHeight
attrSet = setRectangleHeight
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
rectangle_height :: AttrLabelProxy "height"
rectangle_height = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Rectangle
type instance O.AttributeList Rectangle = RectangleAttributeList
type RectangleAttributeList = ('[ '("x", RectangleXFieldInfo), '("y", RectangleYFieldInfo), '("width", RectangleWidthFieldInfo), '("height", RectangleHeightFieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gdk_rectangle_equal" gdk_rectangle_equal ::
Ptr Rectangle ->
Ptr Rectangle ->
IO CInt
rectangleEqual ::
(B.CallStack.HasCallStack, MonadIO m) =>
Rectangle
-> Rectangle
-> m Bool
rectangleEqual :: Rectangle -> Rectangle -> m Bool
rectangleEqual Rectangle
rect1 Rectangle
rect2 = 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 Rectangle
rect1' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
rect1
Ptr Rectangle
rect2' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
rect2
CInt
result <- Ptr Rectangle -> Ptr Rectangle -> IO CInt
gdk_rectangle_equal Ptr Rectangle
rect1' Ptr Rectangle
rect2'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
rect1
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
rect2
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data RectangleEqualMethodInfo
instance (signature ~ (Rectangle -> m Bool), MonadIO m) => O.MethodInfo RectangleEqualMethodInfo Rectangle signature where
overloadedMethod = rectangleEqual
#endif
foreign import ccall "gdk_rectangle_intersect" gdk_rectangle_intersect ::
Ptr Rectangle ->
Ptr Rectangle ->
Ptr Rectangle ->
IO CInt
rectangleIntersect ::
(B.CallStack.HasCallStack, MonadIO m) =>
Rectangle
-> Rectangle
-> m ((Bool, Rectangle))
rectangleIntersect :: Rectangle -> Rectangle -> m (Bool, Rectangle)
rectangleIntersect Rectangle
src1 Rectangle
src2 = IO (Bool, Rectangle) -> m (Bool, Rectangle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Rectangle) -> m (Bool, Rectangle))
-> IO (Bool, Rectangle) -> m (Bool, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
Ptr Rectangle
src1' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
src1
Ptr Rectangle
src2' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
src2
Ptr Rectangle
dest <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Rectangle)
CInt
result <- Ptr Rectangle -> Ptr Rectangle -> Ptr Rectangle -> IO CInt
gdk_rectangle_intersect Ptr Rectangle
src1' Ptr Rectangle
src2' Ptr Rectangle
dest
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Rectangle
dest' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Rectangle) Ptr Rectangle
dest
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
src1
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
src2
(Bool, Rectangle) -> IO (Bool, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Rectangle
dest')
#if defined(ENABLE_OVERLOADING)
data RectangleIntersectMethodInfo
instance (signature ~ (Rectangle -> m ((Bool, Rectangle))), MonadIO m) => O.MethodInfo RectangleIntersectMethodInfo Rectangle signature where
overloadedMethod = rectangleIntersect
#endif
foreign import ccall "gdk_rectangle_union" gdk_rectangle_union ::
Ptr Rectangle ->
Ptr Rectangle ->
Ptr Rectangle ->
IO ()
rectangleUnion ::
(B.CallStack.HasCallStack, MonadIO m) =>
Rectangle
-> Rectangle
-> m (Rectangle)
rectangleUnion :: Rectangle -> Rectangle -> m Rectangle
rectangleUnion Rectangle
src1 Rectangle
src2 = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
Ptr Rectangle
src1' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
src1
Ptr Rectangle
src2' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
src2
Ptr Rectangle
dest <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Rectangle)
Ptr Rectangle -> Ptr Rectangle -> Ptr Rectangle -> IO ()
gdk_rectangle_union Ptr Rectangle
src1' Ptr Rectangle
src2' Ptr Rectangle
dest
Rectangle
dest' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Rectangle) Ptr Rectangle
dest
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
src1
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
src2
Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
dest'
#if defined(ENABLE_OVERLOADING)
data RectangleUnionMethodInfo
instance (signature ~ (Rectangle -> m (Rectangle)), MonadIO m) => O.MethodInfo RectangleUnionMethodInfo Rectangle signature where
overloadedMethod = rectangleUnion
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveRectangleMethod (t :: Symbol) (o :: *) :: * where
ResolveRectangleMethod "equal" o = RectangleEqualMethodInfo
ResolveRectangleMethod "intersect" o = RectangleIntersectMethodInfo
ResolveRectangleMethod "union" o = RectangleUnionMethodInfo
ResolveRectangleMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRectangleMethod t Rectangle, O.MethodInfo info Rectangle p) => OL.IsLabel t (Rectangle -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif