{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

Defines the position and size of a rectangle. It is identical to
#cairo_rectangle_int_t.
-}

module GI.Gdk.Structs.Rectangle
    ( 

-- * Exported types
    Rectangle(..)                           ,
    noRectangle                             ,


 -- * Methods
-- ** rectangleIntersect
    rectangleIntersect                      ,


-- ** rectangleUnion
    rectangleUnion                          ,




 -- * Properties
-- ** Height
    rectangleReadHeight                     ,


-- ** Width
    rectangleReadWidth                      ,


-- ** X
    rectangleReadX                          ,


-- ** Y
    rectangleReadY                          ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gdk.Types
import GI.Gdk.Callbacks

newtype Rectangle = Rectangle (ForeignPtr Rectangle)
foreign import ccall "gdk_rectangle_get_type" c_gdk_rectangle_get_type :: 
    IO GType

instance BoxedObject Rectangle where
    boxedType _ = c_gdk_rectangle_get_type

noRectangle :: Maybe Rectangle
noRectangle = Nothing

rectangleReadX :: Rectangle -> IO Int32
rectangleReadX s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int32
    return val

rectangleReadY :: Rectangle -> IO Int32
rectangleReadY s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO Int32
    return val

rectangleReadWidth :: Rectangle -> IO Int32
rectangleReadWidth s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Int32
    return val

rectangleReadHeight :: Rectangle -> IO Int32
rectangleReadHeight s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO Int32
    return val

-- method Rectangle::intersect
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gdk" "Rectangle", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src2", argType = TInterface "Gdk" "Rectangle", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest", argType = TInterface "Gdk" "Rectangle", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gdk" "Rectangle", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src2", argType = TInterface "Gdk" "Rectangle", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gdk_rectangle_intersect" gdk_rectangle_intersect :: 
    Ptr Rectangle ->                        -- _obj : TInterface "Gdk" "Rectangle"
    Ptr Rectangle ->                        -- src2 : TInterface "Gdk" "Rectangle"
    Ptr Rectangle ->                        -- dest : TInterface "Gdk" "Rectangle"
    IO CInt


rectangleIntersect ::
    (MonadIO m) =>
    Rectangle ->                            -- _obj
    Rectangle ->                            -- src2
    m (Bool,Rectangle)
rectangleIntersect _obj src2 = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let src2' = unsafeManagedPtrGetPtr src2
    dest <- callocBoxedBytes 16 :: IO (Ptr Rectangle)
    result <- gdk_rectangle_intersect _obj' src2' dest
    let result' = (/= 0) result
    dest' <- (wrapBoxed Rectangle) dest
    touchManagedPtr _obj
    touchManagedPtr src2
    return (result', dest')

-- method Rectangle::union
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gdk" "Rectangle", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src2", argType = TInterface "Gdk" "Rectangle", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest", argType = TInterface "Gdk" "Rectangle", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gdk" "Rectangle", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src2", argType = TInterface "Gdk" "Rectangle", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gdk_rectangle_union" gdk_rectangle_union :: 
    Ptr Rectangle ->                        -- _obj : TInterface "Gdk" "Rectangle"
    Ptr Rectangle ->                        -- src2 : TInterface "Gdk" "Rectangle"
    Ptr Rectangle ->                        -- dest : TInterface "Gdk" "Rectangle"
    IO ()


rectangleUnion ::
    (MonadIO m) =>
    Rectangle ->                            -- _obj
    Rectangle ->                            -- src2
    m (Rectangle)
rectangleUnion _obj src2 = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let src2' = unsafeManagedPtrGetPtr src2
    dest <- callocBoxedBytes 16 :: IO (Ptr Rectangle)
    gdk_rectangle_union _obj' src2' dest
    dest' <- (wrapBoxed Rectangle) dest
    touchManagedPtr _obj
    touchManagedPtr src2
    return dest'