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

The #PangoAttribute structure represents the common portions of all
attributes. Particular types of attributes include this structure
as their initial portion. The common portion of the attribute holds
the range to which the value in the type-specific part of the attribute
applies and should be initialized using pango_attribute_init().
By default an attribute will have an all-inclusive range of [0,%G_MAXUINT].
-}

module GI.Pango.Structs.Attribute
    ( 

-- * Exported types
    Attribute(..)                           ,
    noAttribute                             ,


 -- * Methods
-- ** attributeDestroy
    attributeDestroy                        ,


-- ** attributeEqual
    attributeEqual                          ,


-- ** attributeInit
    attributeInit                           ,




 -- * Properties
-- ** EndIndex
    attributeReadEndIndex                   ,


-- ** Klass
    attributeReadKlass                      ,


-- ** StartIndex
    attributeReadStartIndex                 ,




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

newtype Attribute = Attribute (ForeignPtr Attribute)
noAttribute :: Maybe Attribute
noAttribute = Nothing

attributeReadKlass :: Attribute -> IO AttrClass
attributeReadKlass s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr AttrClass)
    val' <- (newPtr 32 AttrClass) val
    return val'

attributeReadStartIndex :: Attribute -> IO Word32
attributeReadStartIndex s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Word32
    return val

attributeReadEndIndex :: Attribute -> IO Word32
attributeReadEndIndex s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO Word32
    return val

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

foreign import ccall "pango_attribute_destroy" pango_attribute_destroy :: 
    Ptr Attribute ->                        -- _obj : TInterface "Pango" "Attribute"
    IO ()


attributeDestroy ::
    (MonadIO m) =>
    Attribute ->                            -- _obj
    m ()
attributeDestroy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    pango_attribute_destroy _obj'
    touchManagedPtr _obj
    return ()

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

foreign import ccall "pango_attribute_equal" pango_attribute_equal :: 
    Ptr Attribute ->                        -- _obj : TInterface "Pango" "Attribute"
    Ptr Attribute ->                        -- attr2 : TInterface "Pango" "Attribute"
    IO CInt


attributeEqual ::
    (MonadIO m) =>
    Attribute ->                            -- _obj
    Attribute ->                            -- attr2
    m Bool
attributeEqual _obj attr2 = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let attr2' = unsafeManagedPtrGetPtr attr2
    result <- pango_attribute_equal _obj' attr2'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr attr2
    return result'

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

foreign import ccall "pango_attribute_init" pango_attribute_init :: 
    Ptr Attribute ->                        -- _obj : TInterface "Pango" "Attribute"
    Ptr AttrClass ->                        -- klass : TInterface "Pango" "AttrClass"
    IO ()


attributeInit ::
    (MonadIO m) =>
    Attribute ->                            -- _obj
    AttrClass ->                            -- klass
    m ()
attributeInit _obj klass = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let klass' = unsafeManagedPtrGetPtr klass
    pango_attribute_init _obj' klass'
    touchManagedPtr _obj
    touchManagedPtr klass
    return ()