{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @PangoAttrList@ represents a list of attributes that apply to a section
-- of text.
-- 
-- The attributes in a @PangoAttrList@ are, in general, allowed to overlap in
-- an arbitrary fashion. However, if the attributes are manipulated only through
-- 'GI.Pango.Structs.AttrList.attrListChange', the overlap between properties will meet
-- stricter criteria.
-- 
-- Since the @PangoAttrList@ structure is stored as a linear list, it is not
-- suitable for storing attributes for large amounts of text. In general, you
-- should not use a single @PangoAttrList@ for more than one paragraph of text.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Pango.Structs.AttrList
    ( 

-- * Exported types
    AttrList(..)                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [change]("GI.Pango.Structs.AttrList#g:method:change"), [copy]("GI.Pango.Structs.AttrList#g:method:copy"), [equal]("GI.Pango.Structs.AttrList#g:method:equal"), [filter]("GI.Pango.Structs.AttrList#g:method:filter"), [insert]("GI.Pango.Structs.AttrList#g:method:insert"), [insertBefore]("GI.Pango.Structs.AttrList#g:method:insertBefore"), [ref]("GI.Pango.Structs.AttrList#g:method:ref"), [splice]("GI.Pango.Structs.AttrList#g:method:splice"), [toString]("GI.Pango.Structs.AttrList#g:method:toString"), [unref]("GI.Pango.Structs.AttrList#g:method:unref"), [update]("GI.Pango.Structs.AttrList#g:method:update").
-- 
-- ==== Getters
-- [getAttributes]("GI.Pango.Structs.AttrList#g:method:getAttributes"), [getIterator]("GI.Pango.Structs.AttrList#g:method:getIterator").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveAttrListMethod                   ,
#endif

-- ** change #method:change#

#if defined(ENABLE_OVERLOADING)
    AttrListChangeMethodInfo                ,
#endif
    attrListChange                          ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    AttrListCopyMethodInfo                  ,
#endif
    attrListCopy                            ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    AttrListEqualMethodInfo                 ,
#endif
    attrListEqual                           ,


-- ** filter #method:filter#

#if defined(ENABLE_OVERLOADING)
    AttrListFilterMethodInfo                ,
#endif
    attrListFilter                          ,


-- ** fromString #method:fromString#

    attrListFromString                      ,


-- ** getAttributes #method:getAttributes#

#if defined(ENABLE_OVERLOADING)
    AttrListGetAttributesMethodInfo         ,
#endif
    attrListGetAttributes                   ,


-- ** getIterator #method:getIterator#

#if defined(ENABLE_OVERLOADING)
    AttrListGetIteratorMethodInfo           ,
#endif
    attrListGetIterator                     ,


-- ** insert #method:insert#

#if defined(ENABLE_OVERLOADING)
    AttrListInsertMethodInfo                ,
#endif
    attrListInsert                          ,


-- ** insertBefore #method:insertBefore#

#if defined(ENABLE_OVERLOADING)
    AttrListInsertBeforeMethodInfo          ,
#endif
    attrListInsertBefore                    ,


-- ** new #method:new#

    attrListNew                             ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    AttrListRefMethodInfo                   ,
#endif
    attrListRef                             ,


-- ** splice #method:splice#

#if defined(ENABLE_OVERLOADING)
    AttrListSpliceMethodInfo                ,
#endif
    attrListSplice                          ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    AttrListToStringMethodInfo              ,
#endif
    attrListToString                        ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    AttrListUnrefMethodInfo                 ,
#endif
    attrListUnref                           ,


-- ** update #method:update#

#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.GArray as B.GArray
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.Coerce as Coerce
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 GHC.Records as R

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

-- | Memory-managed wrapper type.
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

-- | Convert 'AttrList' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe AttrList) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_pango_attr_list_get_type
    gvalueSet_ :: Ptr GValue -> Maybe AttrList -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AttrList
P.Nothing = Ptr GValue -> Ptr AttrList -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr AttrList
forall a. Ptr a
FP.nullPtr :: FP.Ptr AttrList)
    gvalueSet_ Ptr GValue
gv (P.Just AttrList
obj) = AttrList -> (Ptr AttrList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AttrList
obj (Ptr GValue -> Ptr AttrList -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe AttrList)
gvalueGet_ Ptr GValue
gv = do
        Ptr AttrList
ptr <- Ptr GValue -> IO (Ptr AttrList)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr AttrList)
        if Ptr AttrList
ptr Ptr AttrList -> Ptr AttrList -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AttrList
forall a. Ptr a
FP.nullPtr
        then AttrList -> Maybe AttrList
forall a. a -> Maybe a
P.Just (AttrList -> Maybe AttrList) -> IO AttrList -> IO (Maybe AttrList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe AttrList -> IO (Maybe AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AttrList
forall a. Maybe a
P.Nothing
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AttrList
type instance O.AttributeList AttrList = AttrListAttributeList
type AttrListAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method AttrList::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "AttrList" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_new" pango_attr_list_new :: 
    IO (Ptr AttrList)

-- | Create a new empty attribute list with a reference
-- count of one.
attrListNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m AttrList
    -- ^ __Returns:__ the newly allocated
    --   @PangoAttrList@, which should be freed with
    --   'GI.Pango.Structs.AttrList.attrListUnref'
attrListNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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

-- method AttrList::change
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attr"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Attribute" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute to insert"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_change" pango_attr_list_change :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    Ptr Pango.Attribute.Attribute ->        -- attr : TInterface (Name {namespace = "Pango", name = "Attribute"})
    IO ()

-- | Insert the given attribute into the @PangoAttrList@.
-- 
-- It will replace any attributes of the same type
-- on that segment and be merged with any adjoining
-- attributes that are identical.
-- 
-- This function is slower than 'GI.Pango.Structs.AttrList.attrListInsert'
-- for creating an attribute list in order (potentially
-- much slower for large lists). However,
-- 'GI.Pango.Structs.AttrList.attrListInsert' is not suitable for
-- continually changing a set of attributes since it
-- never removes or combines existing attributes.
attrListChange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> Pango.Attribute.Attribute
    -- ^ /@attr@/: the attribute to insert
    -> m ()
attrListChange :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListChangeMethodInfo AttrList signature where
    overloadedMethod = attrListChange

instance O.OverloadedMethodInfo AttrListChangeMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListChange",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListChange"
        })


#endif

-- method AttrList::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "AttrList" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_copy" pango_attr_list_copy :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    IO (Ptr AttrList)

-- | Copy /@list@/ and return an identical new list.
attrListCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> m (Maybe AttrList)
    -- ^ __Returns:__ the newly allocated
    --   @PangoAttrList@, with a reference count of one,
    --   which should be freed with 'GI.Pango.Structs.AttrList.attrListUnref'.
    --   Returns 'P.Nothing' if /@list@/ was 'P.Nothing'.
attrListCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListCopyMethodInfo AttrList signature where
    overloadedMethod = attrListCopy

instance O.OverloadedMethodInfo AttrListCopyMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListCopy"
        })


#endif

-- method AttrList::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "other_list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the other `PangoAttrList`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_equal" pango_attr_list_equal :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    Ptr AttrList ->                         -- other_list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    IO CInt

-- | Checks whether /@list@/ and /@otherList@/ contain the same
-- attributes and whether those attributes apply to the
-- same ranges.
-- 
-- Beware that this will return wrong values if any list
-- contains duplicates.
-- 
-- /Since: 1.46/
attrListEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> AttrList
    -- ^ /@otherList@/: the other @PangoAttrList@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the lists are equal, 'P.False' if
    --   they aren\'t
attrListEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrList -> AttrList -> m Bool
attrListEqual AttrList
list AttrList
otherList = 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 AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
    Ptr AttrList
otherList' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
otherList
    CInt
result <- Ptr AttrList -> Ptr AttrList -> IO CInt
pango_attr_list_equal Ptr AttrList
list' Ptr AttrList
otherList'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
otherList
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AttrListEqualMethodInfo
instance (signature ~ (AttrList -> m Bool), MonadIO m) => O.OverloadedMethod AttrListEqualMethodInfo AttrList signature where
    overloadedMethod = attrListEqual

instance O.OverloadedMethodInfo AttrListEqualMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListEqual",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListEqual"
        })


#endif

-- method AttrList::filter
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "func"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrFilterFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "callback function;\n  returns %TRUE if an attribute should be filtered out"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Data to be passed to @func"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "AttrList" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_filter" pango_attr_list_filter :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    FunPtr Pango.Callbacks.C_AttrFilterFunc -> -- func : TInterface (Name {namespace = "Pango", name = "AttrFilterFunc"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO (Ptr AttrList)

-- | Given a @PangoAttrList@ and callback function, removes
-- any elements of /@list@/ for which /@func@/ returns 'P.True' and
-- inserts them into a new list.
-- 
-- /Since: 1.2/
attrListFilter ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> Pango.Callbacks.AttrFilterFunc
    -- ^ /@func@/: callback function;
    --   returns 'P.True' if an attribute should be filtered out
    -> m (Maybe AttrList)
    -- ^ __Returns:__ the new
    --   @PangoAttrList@ or 'P.Nothing' if no attributes of the
    --   given types were found
attrListFilter :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListFilterMethodInfo AttrList signature where
    overloadedMethod = attrListFilter

instance O.OverloadedMethodInfo AttrListFilterMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListFilter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListFilter"
        })


#endif

-- method AttrList::get_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGSList
--                  (TInterface Name { namespace = "Pango" , name = "Attribute" }))
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_get_attributes" pango_attr_list_get_attributes :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    IO (Ptr (GSList (Ptr Pango.Attribute.Attribute)))

-- | Gets a list of all attributes in /@list@/.
-- 
-- /Since: 1.44/
attrListGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> m [Pango.Attribute.Attribute]
    -- ^ __Returns:__ 
    --   a list of all attributes in /@list@/. To free this value,
    --   call 'GI.Pango.Structs.Attribute.attributeDestroy' on each value and
    --   @/g_slist_free()/@ on the list.
attrListGetAttributes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListGetAttributesMethodInfo AttrList signature where
    overloadedMethod = attrListGetAttributes

instance O.OverloadedMethodInfo AttrListGetAttributesMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListGetAttributes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListGetAttributes"
        })


#endif

-- method AttrList::get_iterator
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Pango" , name = "AttrIterator" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_get_iterator" pango_attr_list_get_iterator :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    IO (Ptr Pango.AttrIterator.AttrIterator)

-- | Create a iterator initialized to the beginning of the list.
-- 
-- /@list@/ must not be modified until this iterator is freed.
attrListGetIterator ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> m Pango.AttrIterator.AttrIterator
    -- ^ __Returns:__ the newly allocated
    --   @PangoAttrIterator@, which should be freed with
    --   'GI.Pango.Structs.AttrIterator.attrIteratorDestroy'
attrListGetIterator :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListGetIteratorMethodInfo AttrList signature where
    overloadedMethod = attrListGetIterator

instance O.OverloadedMethodInfo AttrListGetIteratorMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListGetIterator",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListGetIterator"
        })


#endif

-- method AttrList::insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attr"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Attribute" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute to insert"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_insert" pango_attr_list_insert :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    Ptr Pango.Attribute.Attribute ->        -- attr : TInterface (Name {namespace = "Pango", name = "Attribute"})
    IO ()

-- | Insert the given attribute into the @PangoAttrList@.
-- 
-- It will be inserted after all other attributes with a
-- matching /@startIndex@/.
attrListInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> Pango.Attribute.Attribute
    -- ^ /@attr@/: the attribute to insert
    -> m ()
attrListInsert :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListInsertMethodInfo AttrList signature where
    overloadedMethod = attrListInsert

instance O.OverloadedMethodInfo AttrListInsertMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListInsert",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListInsert"
        })


#endif

-- method AttrList::insert_before
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attr"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Attribute" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute to insert"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_insert_before" pango_attr_list_insert_before :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    Ptr Pango.Attribute.Attribute ->        -- attr : TInterface (Name {namespace = "Pango", name = "Attribute"})
    IO ()

-- | Insert the given attribute into the @PangoAttrList@.
-- 
-- It will be inserted before all other attributes with a
-- matching /@startIndex@/.
attrListInsertBefore ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> Pango.Attribute.Attribute
    -- ^ /@attr@/: the attribute to insert
    -> m ()
attrListInsertBefore :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListInsertBeforeMethodInfo AttrList signature where
    overloadedMethod = attrListInsertBefore

instance O.OverloadedMethodInfo AttrListInsertBeforeMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListInsertBefore",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListInsertBefore"
        })


#endif

-- method AttrList::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "AttrList" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_ref" pango_attr_list_ref :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    IO (Ptr AttrList)

-- | Increase the reference count of the given attribute
-- list by one.
-- 
-- /Since: 1.10/
attrListRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> m AttrList
    -- ^ __Returns:__ The attribute list passed in
attrListRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListRefMethodInfo AttrList signature where
    overloadedMethod = attrListRef

instance O.OverloadedMethodInfo AttrListRefMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListRef"
        })


#endif

-- method AttrList::splice
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "other"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another `PangoAttrList`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the position in @list at which to insert @other"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the length of the spliced segment. (Note that this\n  must be specified since the attributes in @other may only\n  be present at some subsection of this range)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_splice" pango_attr_list_splice :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    Ptr AttrList ->                         -- other : TInterface (Name {namespace = "Pango", name = "AttrList"})
    Int32 ->                                -- pos : TBasicType TInt
    Int32 ->                                -- len : TBasicType TInt
    IO ()

-- | This function opens up a hole in /@list@/, fills it
-- in with attributes from the left, and then merges
-- /@other@/ on top of the hole.
-- 
-- This operation is equivalent to stretching every attribute
-- that applies at position /@pos@/ in /@list@/ by an amount /@len@/,
-- and then calling 'GI.Pango.Structs.AttrList.attrListChange' with a copy
-- of each attribute in /@other@/ in sequence (offset in position
-- by /@pos@/).
-- 
-- This operation proves useful for, for instance, inserting
-- a pre-edit string in the middle of an edit buffer.
attrListSplice ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> AttrList
    -- ^ /@other@/: another @PangoAttrList@
    -> Int32
    -- ^ /@pos@/: the position in /@list@/ at which to insert /@other@/
    -> Int32
    -- ^ /@len@/: the length of the spliced segment. (Note that this
    --   must be specified since the attributes in /@other@/ may only
    --   be present at some subsection of this range)
    -> m ()
attrListSplice :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListSpliceMethodInfo AttrList signature where
    overloadedMethod = attrListSplice

instance O.OverloadedMethodInfo AttrListSpliceMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListSplice",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListSplice"
        })


#endif

-- method AttrList::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_to_string" pango_attr_list_to_string :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    IO CString

-- | Serializes a @PangoAttrList@ to a string.
-- 
-- No guarantees are made about the format of the string,
-- it may change between Pango versions.
-- 
-- The intended use of this function is testing and
-- debugging. The format is not meant as a permanent
-- storage format.
-- 
-- /Since: 1.50/
attrListToString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> m T.Text
    -- ^ __Returns:__ a newly allocated string
attrListToString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrList -> m Text
attrListToString AttrList
list = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
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
    CString
result <- Ptr AttrList -> IO CString
pango_attr_list_to_string Ptr AttrList
list'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"attrListToString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data AttrListToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod AttrListToStringMethodInfo AttrList signature where
    overloadedMethod = attrListToString

instance O.OverloadedMethodInfo AttrListToStringMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListToString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListToString"
        })


#endif

-- method AttrList::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_unref" pango_attr_list_unref :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    IO ()

-- | Decrease the reference count of the given attribute
-- list by one.
-- 
-- If the result is zero, free the attribute list
-- and the attributes it contains.
attrListUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> m ()
attrListUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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.OverloadedMethod AttrListUnrefMethodInfo AttrList signature where
    overloadedMethod = attrListUnref

instance O.OverloadedMethodInfo AttrListUnrefMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListUnref"
        })


#endif

-- method AttrList::update
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position of the change"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "remove"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of removed bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "add"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of added bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_update" pango_attr_list_update :: 
    Ptr AttrList ->                         -- list : TInterface (Name {namespace = "Pango", name = "AttrList"})
    Int32 ->                                -- pos : TBasicType TInt
    Int32 ->                                -- remove : TBasicType TInt
    Int32 ->                                -- add : TBasicType TInt
    IO ()

-- | Update indices of attributes in /@list@/ for a change in the
-- text they refer to.
-- 
-- The change that this function applies is removing /@remove@/
-- bytes at position /@pos@/ and inserting /@add@/ bytes instead.
-- 
-- Attributes that fall entirely in the (/@pos@/, /@pos@/ + /@remove@/)
-- range are removed.
-- 
-- Attributes that start or end inside the (/@pos@/, /@pos@/ + /@remove@/)
-- range are shortened to reflect the removal.
-- 
-- Attributes start and end positions are updated if they are
-- behind /@pos@/ + /@remove@/.
-- 
-- /Since: 1.44/
attrListUpdate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrList
    -- ^ /@list@/: a @PangoAttrList@
    -> Int32
    -- ^ /@pos@/: the position of the change
    -> Int32
    -- ^ /@remove@/: the number of removed bytes
    -> Int32
    -- ^ /@add@/: the number of added bytes
    -> m ()
attrListUpdate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod AttrListUpdateMethodInfo AttrList signature where
    overloadedMethod = attrListUpdate

instance O.OverloadedMethodInfo AttrListUpdateMethodInfo AttrList where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrList.attrListUpdate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrList.html#v:attrListUpdate"
        })


#endif

-- method AttrList::from_string
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "AttrList" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_list_from_string" pango_attr_list_from_string :: 
    CString ->                              -- text : TBasicType TUTF8
    IO (Ptr AttrList)

-- | Deserializes a @PangoAttrList@ from a string.
-- 
-- This is the counterpart to 'GI.Pango.Structs.AttrList.attrListToString'.
-- See that functions for details about the format.
-- 
-- /Since: 1.50/
attrListFromString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@text@/: a string
    -> m (Maybe AttrList)
    -- ^ __Returns:__ a new @PangoAttrList@
attrListFromString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe AttrList)
attrListFromString Text
text = 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
    CString
text' <- Text -> IO CString
textToCString Text
text
    Ptr AttrList
result <- CString -> IO (Ptr AttrList)
pango_attr_list_from_string CString
text'
    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''
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    Maybe AttrList -> IO (Maybe AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AttrList
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveAttrListMethod (t :: Symbol) (o :: *) :: * where
    ResolveAttrListMethod "change" o = AttrListChangeMethodInfo
    ResolveAttrListMethod "copy" o = AttrListCopyMethodInfo
    ResolveAttrListMethod "equal" o = AttrListEqualMethodInfo
    ResolveAttrListMethod "filter" o = AttrListFilterMethodInfo
    ResolveAttrListMethod "insert" o = AttrListInsertMethodInfo
    ResolveAttrListMethod "insertBefore" o = AttrListInsertBeforeMethodInfo
    ResolveAttrListMethod "ref" o = AttrListRefMethodInfo
    ResolveAttrListMethod "splice" o = AttrListSpliceMethodInfo
    ResolveAttrListMethod "toString" o = AttrListToStringMethodInfo
    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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveAttrListMethod t AttrList, O.OverloadedMethod info AttrList p, R.HasField t AttrList p) => R.HasField t AttrList p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveAttrListMethod t AttrList, O.OverloadedMethodInfo info AttrList) => OL.IsLabel t (O.MethodProxy info AttrList) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif