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

A #GtkRequisition-struct represents the desired size of a widget. See
[GtkWidget’s geometry management section][geometry-management] for
more information.
-}

module GI.Gtk.Structs.Requisition
    ( 

-- * Exported types
    Requisition(..)                         ,
    noRequisition                           ,


 -- * Methods
-- ** requisitionCopy
    requisitionCopy                         ,


-- ** requisitionFree
    requisitionFree                         ,


-- ** requisitionNew
    requisitionNew                          ,




 -- * Properties
-- ** Height
    requisitionReadHeight                   ,


-- ** Width
    requisitionReadWidth                    ,




    ) 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.Gtk.Types
import GI.Gtk.Callbacks

newtype Requisition = Requisition (ForeignPtr Requisition)
foreign import ccall "gtk_requisition_get_type" c_gtk_requisition_get_type :: 
    IO GType

instance BoxedObject Requisition where
    boxedType _ = c_gtk_requisition_get_type

noRequisition :: Maybe Requisition
noRequisition = Nothing

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

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

-- method Requisition::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Gtk" "Requisition"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_requisition_new" gtk_requisition_new :: 
    IO (Ptr Requisition)


requisitionNew ::
    (MonadIO m) =>
    m Requisition
requisitionNew  = liftIO $ do
    result <- gtk_requisition_new
    checkUnexpectedReturnNULL "gtk_requisition_new" result
    result' <- (wrapBoxed Requisition) result
    return result'

-- method Requisition::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Requisition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Requisition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Requisition"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_requisition_copy" gtk_requisition_copy :: 
    Ptr Requisition ->                      -- _obj : TInterface "Gtk" "Requisition"
    IO (Ptr Requisition)


requisitionCopy ::
    (MonadIO m) =>
    Requisition ->                          -- _obj
    m Requisition
requisitionCopy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- gtk_requisition_copy _obj'
    checkUnexpectedReturnNULL "gtk_requisition_copy" result
    result' <- (wrapBoxed Requisition) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_requisition_free" gtk_requisition_free :: 
    Ptr Requisition ->                      -- _obj : TInterface "Gtk" "Requisition"
    IO ()


requisitionFree ::
    (MonadIO m) =>
    Requisition ->                          -- _obj
    m ()
requisitionFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    gtk_requisition_free _obj'
    touchManagedPtr _obj
    return ()