{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.AttrList
    ( 
    AttrList(..)                            ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveAttrListMethod                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    AttrListChangeMethodInfo                ,
#endif
    attrListChange                          ,
#if defined(ENABLE_OVERLOADING)
    AttrListCopyMethodInfo                  ,
#endif
    attrListCopy                            ,
#if defined(ENABLE_OVERLOADING)
    AttrListFilterMethodInfo                ,
#endif
    attrListFilter                          ,
#if defined(ENABLE_OVERLOADING)
    AttrListGetAttributesMethodInfo         ,
#endif
    attrListGetAttributes                   ,
#if defined(ENABLE_OVERLOADING)
    AttrListGetIteratorMethodInfo           ,
#endif
    attrListGetIterator                     ,
#if defined(ENABLE_OVERLOADING)
    AttrListInsertMethodInfo                ,
#endif
    attrListInsert                          ,
#if defined(ENABLE_OVERLOADING)
    AttrListInsertBeforeMethodInfo          ,
#endif
    attrListInsertBefore                    ,
    attrListNew                             ,
#if defined(ENABLE_OVERLOADING)
    AttrListRefMethodInfo                   ,
#endif
    attrListRef                             ,
#if defined(ENABLE_OVERLOADING)
    AttrListSpliceMethodInfo                ,
#endif
    attrListSplice                          ,
#if defined(ENABLE_OVERLOADING)
    AttrListUnrefMethodInfo                 ,
#endif
    attrListUnref                           ,
#if defined(ENABLE_OVERLOADING)
    AttrListUpdateMethodInfo                ,
#endif
    attrListUpdate                          ,
    ) 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
import qualified GI.Pango.Callbacks as Pango.Callbacks
import {-# SOURCE #-} qualified GI.Pango.Structs.AttrIterator as Pango.AttrIterator
import {-# SOURCE #-} qualified GI.Pango.Structs.Attribute as Pango.Attribute
newtype AttrList = AttrList (SP.ManagedPtr AttrList)
    deriving (AttrList -> AttrList -> Bool
(AttrList -> AttrList -> Bool)
-> (AttrList -> AttrList -> Bool) -> Eq AttrList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttrList -> AttrList -> Bool
$c/= :: AttrList -> AttrList -> Bool
== :: AttrList -> AttrList -> Bool
$c== :: AttrList -> AttrList -> Bool
Eq)
instance SP.ManagedPtrNewtype AttrList where
    toManagedPtr :: AttrList -> ManagedPtr AttrList
toManagedPtr (AttrList ManagedPtr AttrList
p) = ManagedPtr AttrList
p
foreign import ccall "pango_attr_list_get_type" c_pango_attr_list_get_type :: 
    IO GType
type instance O.ParentTypes AttrList = '[]
instance O.HasParentTypes AttrList
instance B.Types.TypedObject AttrList where
    glibType :: IO GType
glibType = IO GType
c_pango_attr_list_get_type
instance B.Types.GBoxed AttrList
instance B.GValue.IsGValue AttrList where
    toGValue :: AttrList -> IO GValue
toGValue AttrList
o = do
        GType
gtype <- IO GType
c_pango_attr_list_get_type
        AttrList -> (Ptr AttrList -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AttrList
o (GType
-> (GValue -> Ptr AttrList -> IO ()) -> Ptr AttrList -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr AttrList -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO AttrList
fromGValue GValue
gv = do
        Ptr AttrList
ptr <- GValue -> IO (Ptr AttrList)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr AttrList)
        (ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr AttrList -> AttrList
AttrList Ptr AttrList
ptr
        
    
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AttrList
type instance O.AttributeList AttrList = AttrListAttributeList
type AttrListAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "pango_attr_list_new" pango_attr_list_new :: 
    IO (Ptr AttrList)
attrListNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m AttrList
    
    
attrListNew :: m AttrList
attrListNew  = IO AttrList -> m AttrList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AttrList -> m AttrList) -> IO AttrList -> m AttrList
forall a b. (a -> b) -> a -> b
$ do
    Ptr AttrList
result <- IO (Ptr AttrList)
pango_attr_list_new
    Text -> Ptr AttrList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"attrListNew" Ptr AttrList
result
    AttrList
result' <- ((ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AttrList -> AttrList
AttrList) Ptr AttrList
result
    AttrList -> IO AttrList
forall (m :: * -> *) a. Monad m => a -> m a
return AttrList
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "pango_attr_list_change" pango_attr_list_change :: 
    Ptr AttrList ->                         
    Ptr Pango.Attribute.Attribute ->        
    IO ()
attrListChange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> Pango.Attribute.Attribute
    
    
    -> m ()
attrListChange :: AttrList -> Attribute -> m ()
attrListChange AttrList
list Attribute
attr = 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 AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr Attribute
attr' <- Attribute -> IO (Ptr Attribute)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Attribute
attr
    Ptr AttrList -> Ptr Attribute -> IO ()
pango_attr_list_change Ptr AttrList
list' Ptr Attribute
attr'
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    Attribute -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Attribute
attr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AttrListChangeMethodInfo
instance (signature ~ (Pango.Attribute.Attribute -> m ()), MonadIO m) => O.MethodInfo AttrListChangeMethodInfo AttrList signature where
    overloadedMethod = attrListChange
#endif
foreign import ccall "pango_attr_list_copy" pango_attr_list_copy :: 
    Ptr AttrList ->                         
    IO (Ptr AttrList)
attrListCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> m (Maybe AttrList)
    
    
    
    
attrListCopy :: AttrList -> m (Maybe AttrList)
attrListCopy AttrList
list = IO (Maybe AttrList) -> m (Maybe AttrList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AttrList) -> m (Maybe AttrList))
-> IO (Maybe AttrList) -> m (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr AttrList
result <- Ptr AttrList -> IO (Ptr AttrList)
pango_attr_list_copy Ptr AttrList
list'
    Maybe AttrList
maybeResult <- Ptr AttrList
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AttrList
result ((Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList))
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ \Ptr AttrList
result' -> do
        AttrList
result'' <- ((ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AttrList -> AttrList
AttrList) Ptr AttrList
result'
        AttrList -> IO AttrList
forall (m :: * -> *) a. Monad m => a -> m a
return AttrList
result''
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    Maybe AttrList -> IO (Maybe AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AttrList
maybeResult
#if defined(ENABLE_OVERLOADING)
data AttrListCopyMethodInfo
instance (signature ~ (m (Maybe AttrList)), MonadIO m) => O.MethodInfo AttrListCopyMethodInfo AttrList signature where
    overloadedMethod = attrListCopy
#endif
foreign import ccall "pango_attr_list_filter" pango_attr_list_filter :: 
    Ptr AttrList ->                         
    FunPtr Pango.Callbacks.C_AttrFilterFunc -> 
    Ptr () ->                               
    IO (Ptr AttrList)
attrListFilter ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> Pango.Callbacks.AttrFilterFunc
    
    
    -> m (Maybe AttrList)
    
    
attrListFilter :: AttrList -> AttrFilterFunc -> m (Maybe AttrList)
attrListFilter AttrList
list AttrFilterFunc
func = IO (Maybe AttrList) -> m (Maybe AttrList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AttrList) -> m (Maybe AttrList))
-> IO (Maybe AttrList) -> m (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    FunPtr C_AttrFilterFunc
func' <- C_AttrFilterFunc -> IO (FunPtr C_AttrFilterFunc)
Pango.Callbacks.mk_AttrFilterFunc (Maybe (Ptr (FunPtr C_AttrFilterFunc))
-> AttrFilterFunc_WithClosures -> C_AttrFilterFunc
Pango.Callbacks.wrap_AttrFilterFunc Maybe (Ptr (FunPtr C_AttrFilterFunc))
forall a. Maybe a
Nothing (AttrFilterFunc -> AttrFilterFunc_WithClosures
Pango.Callbacks.drop_closures_AttrFilterFunc AttrFilterFunc
func))
    let data_ :: Ptr a
data_ = Ptr a
forall a. Ptr a
nullPtr
    Ptr AttrList
result <- Ptr AttrList
-> FunPtr C_AttrFilterFunc -> Ptr () -> IO (Ptr AttrList)
pango_attr_list_filter Ptr AttrList
list' FunPtr C_AttrFilterFunc
func' Ptr ()
forall a. Ptr a
data_
    Maybe AttrList
maybeResult <- Ptr AttrList
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AttrList
result ((Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList))
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ \Ptr AttrList
result' -> do
        AttrList
result'' <- ((ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AttrList -> AttrList
AttrList) Ptr AttrList
result'
        AttrList -> IO AttrList
forall (m :: * -> *) a. Monad m => a -> m a
return AttrList
result''
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_AttrFilterFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_AttrFilterFunc
func'
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    Maybe AttrList -> IO (Maybe AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AttrList
maybeResult
#if defined(ENABLE_OVERLOADING)
data AttrListFilterMethodInfo
instance (signature ~ (Pango.Callbacks.AttrFilterFunc -> m (Maybe AttrList)), MonadIO m) => O.MethodInfo AttrListFilterMethodInfo AttrList signature where
    overloadedMethod = attrListFilter
#endif
foreign import ccall "pango_attr_list_get_attributes" pango_attr_list_get_attributes :: 
    Ptr AttrList ->                         
    IO (Ptr (GSList (Ptr Pango.Attribute.Attribute)))
attrListGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> m [Pango.Attribute.Attribute]
    
    
    
    
attrListGetAttributes :: AttrList -> m [Attribute]
attrListGetAttributes AttrList
list = IO [Attribute] -> m [Attribute]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Attribute] -> m [Attribute])
-> IO [Attribute] -> m [Attribute]
forall a b. (a -> b) -> a -> b
$ do
    Ptr AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr (GSList (Ptr Attribute))
result <- Ptr AttrList -> IO (Ptr (GSList (Ptr Attribute)))
pango_attr_list_get_attributes Ptr AttrList
list'
    [Ptr Attribute]
result' <- Ptr (GSList (Ptr Attribute)) -> IO [Ptr Attribute]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr Attribute))
result
    [Attribute]
result'' <- (Ptr Attribute -> IO Attribute)
-> [Ptr Attribute] -> IO [Attribute]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Attribute -> Attribute)
-> Ptr Attribute -> IO Attribute
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) [Ptr Attribute]
result'
    Ptr (GSList (Ptr Attribute)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr Attribute))
result
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    [Attribute] -> IO [Attribute]
forall (m :: * -> *) a. Monad m => a -> m a
return [Attribute]
result''
#if defined(ENABLE_OVERLOADING)
data AttrListGetAttributesMethodInfo
instance (signature ~ (m [Pango.Attribute.Attribute]), MonadIO m) => O.MethodInfo AttrListGetAttributesMethodInfo AttrList signature where
    overloadedMethod = attrListGetAttributes
#endif
foreign import ccall "pango_attr_list_get_iterator" pango_attr_list_get_iterator :: 
    Ptr AttrList ->                         
    IO (Ptr Pango.AttrIterator.AttrIterator)
attrListGetIterator ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> m Pango.AttrIterator.AttrIterator
    
    
attrListGetIterator :: AttrList -> m AttrIterator
attrListGetIterator AttrList
list = IO AttrIterator -> m AttrIterator
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AttrIterator -> m AttrIterator)
-> IO AttrIterator -> m AttrIterator
forall a b. (a -> b) -> a -> b
$ do
    Ptr AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr AttrIterator
result <- Ptr AttrList -> IO (Ptr AttrIterator)
pango_attr_list_get_iterator Ptr AttrList
list'
    Text -> Ptr AttrIterator -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"attrListGetIterator" Ptr AttrIterator
result
    AttrIterator
result' <- ((ManagedPtr AttrIterator -> AttrIterator)
-> Ptr AttrIterator -> IO AttrIterator
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AttrIterator -> AttrIterator
Pango.AttrIterator.AttrIterator) Ptr AttrIterator
result
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    AttrIterator -> IO AttrIterator
forall (m :: * -> *) a. Monad m => a -> m a
return AttrIterator
result'
#if defined(ENABLE_OVERLOADING)
data AttrListGetIteratorMethodInfo
instance (signature ~ (m Pango.AttrIterator.AttrIterator), MonadIO m) => O.MethodInfo AttrListGetIteratorMethodInfo AttrList signature where
    overloadedMethod = attrListGetIterator
#endif
foreign import ccall "pango_attr_list_insert" pango_attr_list_insert :: 
    Ptr AttrList ->                         
    Ptr Pango.Attribute.Attribute ->        
    IO ()
attrListInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> Pango.Attribute.Attribute
    
    
    -> m ()
attrListInsert :: AttrList -> Attribute -> m ()
attrListInsert AttrList
list Attribute
attr = 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 AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr Attribute
attr' <- Attribute -> IO (Ptr Attribute)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Attribute
attr
    Ptr AttrList -> Ptr Attribute -> IO ()
pango_attr_list_insert Ptr AttrList
list' Ptr Attribute
attr'
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    Attribute -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Attribute
attr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AttrListInsertMethodInfo
instance (signature ~ (Pango.Attribute.Attribute -> m ()), MonadIO m) => O.MethodInfo AttrListInsertMethodInfo AttrList signature where
    overloadedMethod = attrListInsert
#endif
foreign import ccall "pango_attr_list_insert_before" pango_attr_list_insert_before :: 
    Ptr AttrList ->                         
    Ptr Pango.Attribute.Attribute ->        
    IO ()
attrListInsertBefore ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> Pango.Attribute.Attribute
    
    
    -> m ()
attrListInsertBefore :: AttrList -> Attribute -> m ()
attrListInsertBefore AttrList
list Attribute
attr = 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 AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr Attribute
attr' <- Attribute -> IO (Ptr Attribute)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Attribute
attr
    Ptr AttrList -> Ptr Attribute -> IO ()
pango_attr_list_insert_before Ptr AttrList
list' Ptr Attribute
attr'
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    Attribute -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Attribute
attr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AttrListInsertBeforeMethodInfo
instance (signature ~ (Pango.Attribute.Attribute -> m ()), MonadIO m) => O.MethodInfo AttrListInsertBeforeMethodInfo AttrList signature where
    overloadedMethod = attrListInsertBefore
#endif
foreign import ccall "pango_attr_list_ref" pango_attr_list_ref :: 
    Ptr AttrList ->                         
    IO (Ptr AttrList)
attrListRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> m AttrList
    
attrListRef :: AttrList -> m AttrList
attrListRef AttrList
list = IO AttrList -> m AttrList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AttrList -> m AttrList) -> IO AttrList -> m AttrList
forall a b. (a -> b) -> a -> b
$ do
    Ptr AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr AttrList
result <- Ptr AttrList -> IO (Ptr AttrList)
pango_attr_list_ref Ptr AttrList
list'
    Text -> Ptr AttrList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"attrListRef" Ptr AttrList
result
    AttrList
result' <- ((ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AttrList -> AttrList
AttrList) Ptr AttrList
result
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    AttrList -> IO AttrList
forall (m :: * -> *) a. Monad m => a -> m a
return AttrList
result'
#if defined(ENABLE_OVERLOADING)
data AttrListRefMethodInfo
instance (signature ~ (m AttrList), MonadIO m) => O.MethodInfo AttrListRefMethodInfo AttrList signature where
    overloadedMethod = attrListRef
#endif
foreign import ccall "pango_attr_list_splice" pango_attr_list_splice :: 
    Ptr AttrList ->                         
    Ptr AttrList ->                         
    Int32 ->                                
    Int32 ->                                
    IO ()
attrListSplice ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> AttrList
    
    -> Int32
    
    -> Int32
    
    
    
    -> m ()
attrListSplice :: AttrList -> AttrList -> Int32 -> Int32 -> m ()
attrListSplice AttrList
list AttrList
other Int32
pos Int32
len = 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 AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr AttrList
other' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
other
    Ptr AttrList -> Ptr AttrList -> Int32 -> Int32 -> IO ()
pango_attr_list_splice Ptr AttrList
list' Ptr AttrList
other' Int32
pos Int32
len
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
other
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AttrListSpliceMethodInfo
instance (signature ~ (AttrList -> Int32 -> Int32 -> m ()), MonadIO m) => O.MethodInfo AttrListSpliceMethodInfo AttrList signature where
    overloadedMethod = attrListSplice
#endif
foreign import ccall "pango_attr_list_unref" pango_attr_list_unref :: 
    Ptr AttrList ->                         
    IO ()
attrListUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> m ()
attrListUnref :: AttrList -> m ()
attrListUnref AttrList
list = 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 AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr AttrList -> IO ()
pango_attr_list_unref Ptr AttrList
list'
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AttrListUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AttrListUnrefMethodInfo AttrList signature where
    overloadedMethod = attrListUnref
#endif
foreign import ccall "pango_attr_list_update" pango_attr_list_update :: 
    Ptr AttrList ->                         
    Int32 ->                                
    Int32 ->                                
    Int32 ->                                
    IO ()
attrListUpdate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    
    -> Int32
    
    -> Int32
    
    -> Int32
    
    -> m ()
attrListUpdate :: AttrList -> Int32 -> Int32 -> Int32 -> m ()
attrListUpdate AttrList
list Int32
pos Int32
remove Int32
add = 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 AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr AttrList -> Int32 -> Int32 -> Int32 -> IO ()
pango_attr_list_update Ptr AttrList
list' Int32
pos Int32
remove Int32
add
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AttrListUpdateMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> m ()), MonadIO m) => O.MethodInfo AttrListUpdateMethodInfo AttrList signature where
    overloadedMethod = attrListUpdate
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAttrListMethod (t :: Symbol) (o :: *) :: * where
    ResolveAttrListMethod "change" o = AttrListChangeMethodInfo
    ResolveAttrListMethod "copy" o = AttrListCopyMethodInfo
    ResolveAttrListMethod "filter" o = AttrListFilterMethodInfo
    ResolveAttrListMethod "insert" o = AttrListInsertMethodInfo
    ResolveAttrListMethod "insertBefore" o = AttrListInsertBeforeMethodInfo
    ResolveAttrListMethod "ref" o = AttrListRefMethodInfo
    ResolveAttrListMethod "splice" o = AttrListSpliceMethodInfo
    ResolveAttrListMethod "unref" o = AttrListUnrefMethodInfo
    ResolveAttrListMethod "update" o = AttrListUpdateMethodInfo
    ResolveAttrListMethod "getAttributes" o = AttrListGetAttributesMethodInfo
    ResolveAttrListMethod "getIterator" o = AttrListGetIteratorMethodInfo
    ResolveAttrListMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAttrListMethod t AttrList, O.MethodInfo info AttrList p) => OL.IsLabel t (AttrList -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#endif