{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The AtkDocument interface should be supported by any object whose
-- content is a representation or view of a document.  The AtkDocument
-- interface should appear on the toplevel container for the document
-- content; however AtkDocument instances may be nested (i.e. an
-- AtkDocument may be a descendant of another AtkDocument) in those
-- cases where one document contains \"embedded content\" which can
-- reasonably be considered a document in its own right.

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

module GI.Atk.Interfaces.Document
    ( 

-- * Exported types
    Document(..)                            ,
    IsDocument                              ,
    toDocument                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAttributeValue]("GI.Atk.Interfaces.Document#g:method:getAttributeValue"), [getAttributes]("GI.Atk.Interfaces.Document#g:method:getAttributes"), [getCurrentPageNumber]("GI.Atk.Interfaces.Document#g:method:getCurrentPageNumber"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDocument]("GI.Atk.Interfaces.Document#g:method:getDocument"), [getDocumentType]("GI.Atk.Interfaces.Document#g:method:getDocumentType"), [getLocale]("GI.Atk.Interfaces.Document#g:method:getLocale"), [getPageCount]("GI.Atk.Interfaces.Document#g:method:getPageCount"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setAttributeValue]("GI.Atk.Interfaces.Document#g:method:setAttributeValue"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDocumentMethod                   ,
#endif

-- ** getAttributeValue #method:getAttributeValue#

#if defined(ENABLE_OVERLOADING)
    DocumentGetAttributeValueMethodInfo     ,
#endif
    documentGetAttributeValue               ,


-- ** getAttributes #method:getAttributes#

#if defined(ENABLE_OVERLOADING)
    DocumentGetAttributesMethodInfo         ,
#endif
    documentGetAttributes                   ,


-- ** getCurrentPageNumber #method:getCurrentPageNumber#

#if defined(ENABLE_OVERLOADING)
    DocumentGetCurrentPageNumberMethodInfo  ,
#endif
    documentGetCurrentPageNumber            ,


-- ** getDocument #method:getDocument#

#if defined(ENABLE_OVERLOADING)
    DocumentGetDocumentMethodInfo           ,
#endif
    documentGetDocument                     ,


-- ** getDocumentType #method:getDocumentType#

#if defined(ENABLE_OVERLOADING)
    DocumentGetDocumentTypeMethodInfo       ,
#endif
    documentGetDocumentType                 ,


-- ** getLocale #method:getLocale#

#if defined(ENABLE_OVERLOADING)
    DocumentGetLocaleMethodInfo             ,
#endif
    documentGetLocale                       ,


-- ** getPageCount #method:getPageCount#

#if defined(ENABLE_OVERLOADING)
    DocumentGetPageCountMethodInfo          ,
#endif
    documentGetPageCount                    ,


-- ** setAttributeValue #method:setAttributeValue#

#if defined(ENABLE_OVERLOADING)
    DocumentSetAttributeValueMethodInfo     ,
#endif
    documentSetAttributeValue               ,




 -- * Signals


-- ** loadComplete #signal:loadComplete#

    DocumentLoadCompleteCallback            ,
#if defined(ENABLE_OVERLOADING)
    DocumentLoadCompleteSignalInfo          ,
#endif
    afterDocumentLoadComplete               ,
    onDocumentLoadComplete                  ,


-- ** loadStopped #signal:loadStopped#

    DocumentLoadStoppedCallback             ,
#if defined(ENABLE_OVERLOADING)
    DocumentLoadStoppedSignalInfo           ,
#endif
    afterDocumentLoadStopped                ,
    onDocumentLoadStopped                   ,


-- ** pageChanged #signal:pageChanged#

    DocumentPageChangedCallback             ,
#if defined(ENABLE_OVERLOADING)
    DocumentPageChangedSignalInfo           ,
#endif
    afterDocumentPageChanged                ,
    onDocumentPageChanged                   ,


-- ** reload #signal:reload#

    DocumentReloadCallback                  ,
#if defined(ENABLE_OVERLOADING)
    DocumentReloadSignalInfo                ,
#endif
    afterDocumentReload                     ,
    onDocumentReload                        ,




    ) 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.GObject.Objects.Object as GObject.Object

-- interface Document 
-- | Memory-managed wrapper type.
newtype Document = Document (SP.ManagedPtr Document)
    deriving (Document -> Document -> Bool
(Document -> Document -> Bool)
-> (Document -> Document -> Bool) -> Eq Document
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Document -> Document -> Bool
$c/= :: Document -> Document -> Bool
== :: Document -> Document -> Bool
$c== :: Document -> Document -> Bool
Eq)

instance SP.ManagedPtrNewtype Document where
    toManagedPtr :: Document -> ManagedPtr Document
toManagedPtr (Document ManagedPtr Document
p) = ManagedPtr Document
p

foreign import ccall "atk_document_get_type"
    c_atk_document_get_type :: IO B.Types.GType

instance B.Types.TypedObject Document where
    glibType :: IO GType
glibType = IO GType
c_atk_document_get_type

instance B.Types.GObject Document

-- | Type class for types which can be safely cast to `Document`, for instance with `toDocument`.
class (SP.GObject o, O.IsDescendantOf Document o) => IsDocument o
instance (SP.GObject o, O.IsDescendantOf Document o) => IsDocument o

instance O.HasParentTypes Document
type instance O.ParentTypes Document = '[GObject.Object.Object]

-- | Cast to `Document`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDocument :: (MIO.MonadIO m, IsDocument o) => o -> m Document
toDocument :: forall (m :: * -> *) o.
(MonadIO m, IsDocument o) =>
o -> m Document
toDocument = IO Document -> m Document
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Document -> m Document)
-> (o -> IO Document) -> o -> m Document
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Document -> Document) -> o -> IO Document
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Document -> Document
Document

-- | Convert 'Document' 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 Document) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_atk_document_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Document -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Document
P.Nothing = Ptr GValue -> Ptr Document -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Document
forall a. Ptr a
FP.nullPtr :: FP.Ptr Document)
    gvalueSet_ Ptr GValue
gv (P.Just Document
obj) = Document -> (Ptr Document -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Document
obj (Ptr GValue -> Ptr Document -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Document)
gvalueGet_ Ptr GValue
gv = do
        Ptr Document
ptr <- Ptr GValue -> IO (Ptr Document)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Document)
        if Ptr Document
ptr Ptr Document -> Ptr Document -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Document
forall a. Ptr a
FP.nullPtr
        then Document -> Maybe Document
forall a. a -> Maybe a
P.Just (Document -> Maybe Document) -> IO Document -> IO (Maybe Document)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Document -> Document) -> Ptr Document -> IO Document
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Document -> Document
Document Ptr Document
ptr
        else Maybe Document -> IO (Maybe Document)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Document
forall a. Maybe a
P.Nothing
        
    

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDocumentMethod (t :: Symbol) (o :: *) :: * where
    ResolveDocumentMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDocumentMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDocumentMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDocumentMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDocumentMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDocumentMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDocumentMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDocumentMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDocumentMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDocumentMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDocumentMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDocumentMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDocumentMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDocumentMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDocumentMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDocumentMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDocumentMethod "getAttributeValue" o = DocumentGetAttributeValueMethodInfo
    ResolveDocumentMethod "getAttributes" o = DocumentGetAttributesMethodInfo
    ResolveDocumentMethod "getCurrentPageNumber" o = DocumentGetCurrentPageNumberMethodInfo
    ResolveDocumentMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDocumentMethod "getDocument" o = DocumentGetDocumentMethodInfo
    ResolveDocumentMethod "getDocumentType" o = DocumentGetDocumentTypeMethodInfo
    ResolveDocumentMethod "getLocale" o = DocumentGetLocaleMethodInfo
    ResolveDocumentMethod "getPageCount" o = DocumentGetPageCountMethodInfo
    ResolveDocumentMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDocumentMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDocumentMethod "setAttributeValue" o = DocumentSetAttributeValueMethodInfo
    ResolveDocumentMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDocumentMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDocumentMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDocumentMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDocumentMethod t Document, O.OverloadedMethod info Document p) => OL.IsLabel t (Document -> 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 ~ ResolveDocumentMethod t Document, O.OverloadedMethod info Document p, R.HasField t Document p) => R.HasField t Document p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- method Document::get_attribute_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "document"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkDocumentIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attribute_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a character string representing the name of the attribute\n  whose value is being queried."
--                 , 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 "atk_document_get_attribute_value" atk_document_get_attribute_value :: 
    Ptr Document ->                         -- document : TInterface (Name {namespace = "Atk", name = "Document"})
    CString ->                              -- attribute_name : TBasicType TUTF8
    IO CString

-- | Retrieves the value of the given /@attributeName@/ inside /@document@/.
-- 
-- /Since: 1.12/
documentGetAttributeValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDocument a) =>
    a
    -- ^ /@document@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkDocumentIface
    -> T.Text
    -- ^ /@attributeName@/: a character string representing the name of the attribute
    --   whose value is being queried.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a string value associated with the named
    --    attribute for this document, or 'P.Nothing' if a value for
    --    /@attributeName@/ has not been specified for this document.
documentGetAttributeValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> Text -> m (Maybe Text)
documentGetAttributeValue a
document Text
attributeName = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    CString
attributeName' <- Text -> IO CString
textToCString Text
attributeName
    CString
result <- Ptr Document -> CString -> IO CString
atk_document_get_attribute_value Ptr Document
document' CString
attributeName'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attributeName'
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data DocumentGetAttributeValueMethodInfo
instance (signature ~ (T.Text -> m (Maybe T.Text)), MonadIO m, IsDocument a) => O.OverloadedMethod DocumentGetAttributeValueMethodInfo a signature where
    overloadedMethod = documentGetAttributeValue

instance O.OverloadedMethodInfo DocumentGetAttributeValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document.documentGetAttributeValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#v:documentGetAttributeValue"
        })


#endif

-- method Document::get_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "document"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkDocumentIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGSList (TBasicType TPtr))
-- throws : False
-- Skip return : False

foreign import ccall "atk_document_get_attributes" atk_document_get_attributes :: 
    Ptr Document ->                         -- document : TInterface (Name {namespace = "Atk", name = "Document"})
    IO (Ptr (GSList (Ptr ())))

-- | Gets an AtkAttributeSet which describes document-wide
--          attributes as name-value pairs.
-- 
-- /Since: 1.12/
documentGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDocument a) =>
    a
    -- ^ /@document@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkDocumentIface
    -> m ([Ptr ()])
    -- ^ __Returns:__ An AtkAttributeSet containing the explicitly
    --          set name-value-pair attributes associated with this document
    --          as a whole.
documentGetAttributes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> m [Ptr ()]
documentGetAttributes a
document = IO [Ptr ()] -> m [Ptr ()]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Ptr ()] -> m [Ptr ()]) -> IO [Ptr ()] -> m [Ptr ()]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    Ptr (GSList (Ptr ()))
result <- Ptr Document -> IO (Ptr (GSList (Ptr ())))
atk_document_get_attributes Ptr Document
document'
    [Ptr ()]
result' <- Ptr (GSList (Ptr ())) -> IO [Ptr ()]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr ()))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    [Ptr ()] -> IO [Ptr ()]
forall (m :: * -> *) a. Monad m => a -> m a
return [Ptr ()]
result'

#if defined(ENABLE_OVERLOADING)
data DocumentGetAttributesMethodInfo
instance (signature ~ (m ([Ptr ()])), MonadIO m, IsDocument a) => O.OverloadedMethod DocumentGetAttributesMethodInfo a signature where
    overloadedMethod = documentGetAttributes

instance O.OverloadedMethodInfo DocumentGetAttributesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document.documentGetAttributes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#v:documentGetAttributes"
        })


#endif

-- method Document::get_current_page_number
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "document"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #AtkDocument" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "atk_document_get_current_page_number" atk_document_get_current_page_number :: 
    Ptr Document ->                         -- document : TInterface (Name {namespace = "Atk", name = "Document"})
    IO Int32

-- | Retrieves the current page number inside /@document@/.
-- 
-- /Since: 2.12/
documentGetCurrentPageNumber ::
    (B.CallStack.HasCallStack, MonadIO m, IsDocument a) =>
    a
    -- ^ /@document@/: the t'GI.Atk.Interfaces.Document.Document'
    -> m Int32
    -- ^ __Returns:__ the current page number inside /@document@/, or -1 if
    --   not implemented, not know by the implementor, or irrelevant.
documentGetCurrentPageNumber :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> m Int32
documentGetCurrentPageNumber a
document = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    Int32
result <- Ptr Document -> IO Int32
atk_document_get_current_page_number Ptr Document
document'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data DocumentGetCurrentPageNumberMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDocument a) => O.OverloadedMethod DocumentGetCurrentPageNumberMethodInfo a signature where
    overloadedMethod = documentGetCurrentPageNumber

instance O.OverloadedMethodInfo DocumentGetCurrentPageNumberMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document.documentGetCurrentPageNumber",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#v:documentGetCurrentPageNumber"
        })


#endif

-- method Document::get_document
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "document"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkDocumentIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "atk_document_get_document" atk_document_get_document :: 
    Ptr Document ->                         -- document : TInterface (Name {namespace = "Atk", name = "Document"})
    IO (Ptr ())

{-# DEPRECATED documentGetDocument ["Since 2.12. /@document@/ is already a representation of","the document. Use it directly, or one of its children, as an","instance of the DOM."] #-}
-- | Gets a @/gpointer/@ that points to an instance of the DOM.  It is
-- up to the caller to check atk_document_get_type to determine
-- how to cast this pointer.
documentGetDocument ::
    (B.CallStack.HasCallStack, MonadIO m, IsDocument a) =>
    a
    -- ^ /@document@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkDocumentIface
    -> m (Ptr ())
    -- ^ __Returns:__ a @/gpointer/@ that points to an instance of the DOM.
documentGetDocument :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> m (Ptr ())
documentGetDocument a
document = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    Ptr ()
result <- Ptr Document -> IO (Ptr ())
atk_document_get_document Ptr Document
document'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data DocumentGetDocumentMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m, IsDocument a) => O.OverloadedMethod DocumentGetDocumentMethodInfo a signature where
    overloadedMethod = documentGetDocument

instance O.OverloadedMethodInfo DocumentGetDocumentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document.documentGetDocument",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#v:documentGetDocument"
        })


#endif

-- method Document::get_document_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "document"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkDocumentIface"
--                 , 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 "atk_document_get_document_type" atk_document_get_document_type :: 
    Ptr Document ->                         -- document : TInterface (Name {namespace = "Atk", name = "Document"})
    IO CString

{-# DEPRECATED documentGetDocumentType ["Since 2.12. Please use 'GI.Atk.Interfaces.Document.documentGetAttributes' to","ask for the document type if it applies."] #-}
-- | Gets a string indicating the document type.
documentGetDocumentType ::
    (B.CallStack.HasCallStack, MonadIO m, IsDocument a) =>
    a
    -- ^ /@document@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkDocumentIface
    -> m T.Text
    -- ^ __Returns:__ a string indicating the document type
documentGetDocumentType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> m Text
documentGetDocumentType a
document = 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 Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    CString
result <- Ptr Document -> IO CString
atk_document_get_document_type Ptr Document
document'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"documentGetDocumentType" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DocumentGetDocumentTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDocument a) => O.OverloadedMethod DocumentGetDocumentTypeMethodInfo a signature where
    overloadedMethod = documentGetDocumentType

instance O.OverloadedMethodInfo DocumentGetDocumentTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document.documentGetDocumentType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#v:documentGetDocumentType"
        })


#endif

-- method Document::get_locale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "document"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkDocumentIface"
--                 , 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 "atk_document_get_locale" atk_document_get_locale :: 
    Ptr Document ->                         -- document : TInterface (Name {namespace = "Atk", name = "Document"})
    IO CString

{-# DEPRECATED documentGetLocale ["(Since version 2.7.90)","Please use 'GI.Atk.Objects.Object.objectGetObjectLocale' instead."] #-}
-- | Gets a UTF-8 string indicating the POSIX-style LC_MESSAGES locale
--          of the content of this document instance.  Individual
--          text substrings or images within this document may have
--          a different locale, see atk_text_get_attributes and
--          atk_image_get_image_locale.
documentGetLocale ::
    (B.CallStack.HasCallStack, MonadIO m, IsDocument a) =>
    a
    -- ^ /@document@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkDocumentIface
    -> m T.Text
    -- ^ __Returns:__ a UTF-8 string indicating the POSIX-style LC_MESSAGES
    --          locale of the document content as a whole, or NULL if
    --          the document content does not specify a locale.
documentGetLocale :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> m Text
documentGetLocale a
document = 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 Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    CString
result <- Ptr Document -> IO CString
atk_document_get_locale Ptr Document
document'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"documentGetLocale" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DocumentGetLocaleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDocument a) => O.OverloadedMethod DocumentGetLocaleMethodInfo a signature where
    overloadedMethod = documentGetLocale

instance O.OverloadedMethodInfo DocumentGetLocaleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document.documentGetLocale",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#v:documentGetLocale"
        })


#endif

-- method Document::get_page_count
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "document"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #AtkDocument" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "atk_document_get_page_count" atk_document_get_page_count :: 
    Ptr Document ->                         -- document : TInterface (Name {namespace = "Atk", name = "Document"})
    IO Int32

-- | Retrieves the total number of pages inside /@document@/.
-- 
-- /Since: 2.12/
documentGetPageCount ::
    (B.CallStack.HasCallStack, MonadIO m, IsDocument a) =>
    a
    -- ^ /@document@/: the t'GI.Atk.Interfaces.Document.Document'
    -> m Int32
    -- ^ __Returns:__ total page count of /@document@/, or -1 if not implemented,
    --   not know by the implementor or irrelevant.
documentGetPageCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> m Int32
documentGetPageCount a
document = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    Int32
result <- Ptr Document -> IO Int32
atk_document_get_page_count Ptr Document
document'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data DocumentGetPageCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDocument a) => O.OverloadedMethod DocumentGetPageCountMethodInfo a signature where
    overloadedMethod = documentGetPageCount

instance O.OverloadedMethodInfo DocumentGetPageCountMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document.documentGetPageCount",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#v:documentGetPageCount"
        })


#endif

-- method Document::set_attribute_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "document"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements #AtkDocumentIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attribute_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a character string representing the name of the attribute\n  whose value is being set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attribute_value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a string value to be associated with @attribute_name."
--                 , 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 "atk_document_set_attribute_value" atk_document_set_attribute_value :: 
    Ptr Document ->                         -- document : TInterface (Name {namespace = "Atk", name = "Document"})
    CString ->                              -- attribute_name : TBasicType TUTF8
    CString ->                              -- attribute_value : TBasicType TUTF8
    IO CInt

-- | Sets the value for the given /@attributeName@/ inside /@document@/.
-- 
-- /Since: 1.12/
documentSetAttributeValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsDocument a) =>
    a
    -- ^ /@document@/: a t'GI.GObject.Objects.Object.Object' instance that implements t'GI.Atk.Structs.DocumentIface.DocumentIface'
    -> T.Text
    -- ^ /@attributeName@/: a character string representing the name of the attribute
    --   whose value is being set.
    -> T.Text
    -- ^ /@attributeValue@/: a string value to be associated with /@attributeName@/.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@attributeValue@/ is successfully associated
    --   with /@attributeName@/ for this /@document@/, and 'P.False' if if the
    --   document does not allow the attribute to be modified
documentSetAttributeValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> Text -> Text -> m Bool
documentSetAttributeValue a
document Text
attributeName Text
attributeValue = 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 Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    CString
attributeName' <- Text -> IO CString
textToCString Text
attributeName
    CString
attributeValue' <- Text -> IO CString
textToCString Text
attributeValue
    CInt
result <- Ptr Document -> CString -> CString -> IO CInt
atk_document_set_attribute_value Ptr Document
document' CString
attributeName' CString
attributeValue'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attributeName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attributeValue'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DocumentSetAttributeValueMethodInfo
instance (signature ~ (T.Text -> T.Text -> m Bool), MonadIO m, IsDocument a) => O.OverloadedMethod DocumentSetAttributeValueMethodInfo a signature where
    overloadedMethod = documentSetAttributeValue

instance O.OverloadedMethodInfo DocumentSetAttributeValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document.documentSetAttributeValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#v:documentSetAttributeValue"
        })


#endif

-- signal Document::load-complete
-- | The \'load-complete\' signal is emitted when a pending load of
-- a static document has completed.  This signal is to be
-- expected by ATK clients if and when AtkDocument implementors
-- expose ATK_STATE_BUSY.  If the state of an AtkObject which
-- implements AtkDocument does not include ATK_STATE_BUSY, it
-- should be safe for clients to assume that the AtkDocument\'s
-- static contents are fully loaded into the container.
-- (Dynamic document contents should be exposed via other
-- signals.)
type DocumentLoadCompleteCallback =
    IO ()

type C_DocumentLoadCompleteCallback =
    Ptr Document ->                         -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DocumentLoadCompleteCallback`.
foreign import ccall "wrapper"
    mk_DocumentLoadCompleteCallback :: C_DocumentLoadCompleteCallback -> IO (FunPtr C_DocumentLoadCompleteCallback)

wrap_DocumentLoadCompleteCallback :: 
    GObject a => (a -> DocumentLoadCompleteCallback) ->
    C_DocumentLoadCompleteCallback
wrap_DocumentLoadCompleteCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentLoadCompleteCallback a -> IO ()
gi'cb Ptr Document
gi'selfPtr Ptr ()
_ = do
    Ptr Document -> (Document -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Document
gi'selfPtr ((Document -> IO ()) -> IO ()) -> (Document -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Document
gi'self -> a -> IO ()
gi'cb (Document -> a
Coerce.coerce Document
gi'self) 


-- | Connect a signal handler for the [loadComplete](#signal:loadComplete) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' document #loadComplete callback
-- @
-- 
-- 
onDocumentLoadComplete :: (IsDocument a, MonadIO m) => a -> ((?self :: a) => DocumentLoadCompleteCallback) -> m SignalHandlerId
onDocumentLoadComplete :: forall a (m :: * -> *).
(IsDocument a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDocumentLoadComplete a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_DocumentLoadCompleteCallback
wrapped' = (a -> IO ()) -> C_DocumentLoadCompleteCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentLoadCompleteCallback a -> IO ()
wrapped
    FunPtr C_DocumentLoadCompleteCallback
wrapped'' <- C_DocumentLoadCompleteCallback
-> IO (FunPtr C_DocumentLoadCompleteCallback)
mk_DocumentLoadCompleteCallback C_DocumentLoadCompleteCallback
wrapped'
    a
-> Text
-> FunPtr C_DocumentLoadCompleteCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"load-complete" FunPtr C_DocumentLoadCompleteCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [loadComplete](#signal:loadComplete) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' document #loadComplete callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDocumentLoadComplete :: (IsDocument a, MonadIO m) => a -> ((?self :: a) => DocumentLoadCompleteCallback) -> m SignalHandlerId
afterDocumentLoadComplete :: forall a (m :: * -> *).
(IsDocument a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDocumentLoadComplete a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_DocumentLoadCompleteCallback
wrapped' = (a -> IO ()) -> C_DocumentLoadCompleteCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentLoadCompleteCallback a -> IO ()
wrapped
    FunPtr C_DocumentLoadCompleteCallback
wrapped'' <- C_DocumentLoadCompleteCallback
-> IO (FunPtr C_DocumentLoadCompleteCallback)
mk_DocumentLoadCompleteCallback C_DocumentLoadCompleteCallback
wrapped'
    a
-> Text
-> FunPtr C_DocumentLoadCompleteCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"load-complete" FunPtr C_DocumentLoadCompleteCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DocumentLoadCompleteSignalInfo
instance SignalInfo DocumentLoadCompleteSignalInfo where
    type HaskellCallbackType DocumentLoadCompleteSignalInfo = DocumentLoadCompleteCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DocumentLoadCompleteCallback cb
        cb'' <- mk_DocumentLoadCompleteCallback cb'
        connectSignalFunPtr obj "load-complete" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document::load-complete"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#g:signal:loadComplete"})

#endif

-- signal Document::load-stopped
-- | The \'load-stopped\' signal is emitted when a pending load of
-- document contents is cancelled, paused, or otherwise
-- interrupted by the user or application logic.  It should not
-- however be emitted while waiting for a resource (for instance
-- while blocking on a file or network read) unless a
-- user-significant timeout has occurred.
type DocumentLoadStoppedCallback =
    IO ()

type C_DocumentLoadStoppedCallback =
    Ptr Document ->                         -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DocumentLoadStoppedCallback`.
foreign import ccall "wrapper"
    mk_DocumentLoadStoppedCallback :: C_DocumentLoadStoppedCallback -> IO (FunPtr C_DocumentLoadStoppedCallback)

wrap_DocumentLoadStoppedCallback :: 
    GObject a => (a -> DocumentLoadStoppedCallback) ->
    C_DocumentLoadStoppedCallback
wrap_DocumentLoadStoppedCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentLoadStoppedCallback a -> IO ()
gi'cb Ptr Document
gi'selfPtr Ptr ()
_ = do
    Ptr Document -> (Document -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Document
gi'selfPtr ((Document -> IO ()) -> IO ()) -> (Document -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Document
gi'self -> a -> IO ()
gi'cb (Document -> a
Coerce.coerce Document
gi'self) 


-- | Connect a signal handler for the [loadStopped](#signal:loadStopped) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' document #loadStopped callback
-- @
-- 
-- 
onDocumentLoadStopped :: (IsDocument a, MonadIO m) => a -> ((?self :: a) => DocumentLoadStoppedCallback) -> m SignalHandlerId
onDocumentLoadStopped :: forall a (m :: * -> *).
(IsDocument a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDocumentLoadStopped a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_DocumentLoadCompleteCallback
wrapped' = (a -> IO ()) -> C_DocumentLoadCompleteCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentLoadStoppedCallback a -> IO ()
wrapped
    FunPtr C_DocumentLoadCompleteCallback
wrapped'' <- C_DocumentLoadCompleteCallback
-> IO (FunPtr C_DocumentLoadCompleteCallback)
mk_DocumentLoadStoppedCallback C_DocumentLoadCompleteCallback
wrapped'
    a
-> Text
-> FunPtr C_DocumentLoadCompleteCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"load-stopped" FunPtr C_DocumentLoadCompleteCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [loadStopped](#signal:loadStopped) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' document #loadStopped callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDocumentLoadStopped :: (IsDocument a, MonadIO m) => a -> ((?self :: a) => DocumentLoadStoppedCallback) -> m SignalHandlerId
afterDocumentLoadStopped :: forall a (m :: * -> *).
(IsDocument a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDocumentLoadStopped a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_DocumentLoadCompleteCallback
wrapped' = (a -> IO ()) -> C_DocumentLoadCompleteCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentLoadStoppedCallback a -> IO ()
wrapped
    FunPtr C_DocumentLoadCompleteCallback
wrapped'' <- C_DocumentLoadCompleteCallback
-> IO (FunPtr C_DocumentLoadCompleteCallback)
mk_DocumentLoadStoppedCallback C_DocumentLoadCompleteCallback
wrapped'
    a
-> Text
-> FunPtr C_DocumentLoadCompleteCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"load-stopped" FunPtr C_DocumentLoadCompleteCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DocumentLoadStoppedSignalInfo
instance SignalInfo DocumentLoadStoppedSignalInfo where
    type HaskellCallbackType DocumentLoadStoppedSignalInfo = DocumentLoadStoppedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DocumentLoadStoppedCallback cb
        cb'' <- mk_DocumentLoadStoppedCallback cb'
        connectSignalFunPtr obj "load-stopped" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document::load-stopped"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#g:signal:loadStopped"})

#endif

-- signal Document::page-changed
-- | The \'page-changed\' signal is emitted when the current page of
-- a document changes, e.g. pressing page up\/down in a document
-- viewer.
-- 
-- /Since: 2.12/
type DocumentPageChangedCallback =
    Int32
    -- ^ /@pageNumber@/: the new page number. If this value is unknown
    -- or not applicable, -1 should be provided.
    -> IO ()

type C_DocumentPageChangedCallback =
    Ptr Document ->                         -- object
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DocumentPageChangedCallback`.
foreign import ccall "wrapper"
    mk_DocumentPageChangedCallback :: C_DocumentPageChangedCallback -> IO (FunPtr C_DocumentPageChangedCallback)

wrap_DocumentPageChangedCallback :: 
    GObject a => (a -> DocumentPageChangedCallback) ->
    C_DocumentPageChangedCallback
wrap_DocumentPageChangedCallback :: forall a.
GObject a =>
(a -> DocumentPageChangedCallback) -> C_DocumentPageChangedCallback
wrap_DocumentPageChangedCallback a -> DocumentPageChangedCallback
gi'cb Ptr Document
gi'selfPtr Int32
pageNumber Ptr ()
_ = do
    Ptr Document -> (Document -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Document
gi'selfPtr ((Document -> IO ()) -> IO ()) -> (Document -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Document
gi'self -> a -> DocumentPageChangedCallback
gi'cb (Document -> a
Coerce.coerce Document
gi'self)  Int32
pageNumber


-- | Connect a signal handler for the [pageChanged](#signal:pageChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' document #pageChanged callback
-- @
-- 
-- 
onDocumentPageChanged :: (IsDocument a, MonadIO m) => a -> ((?self :: a) => DocumentPageChangedCallback) -> m SignalHandlerId
onDocumentPageChanged :: forall a (m :: * -> *).
(IsDocument a, MonadIO m) =>
a
-> ((?self::a) => DocumentPageChangedCallback) -> m SignalHandlerId
onDocumentPageChanged a
obj (?self::a) => DocumentPageChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DocumentPageChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DocumentPageChangedCallback
DocumentPageChangedCallback
cb
    let wrapped' :: C_DocumentPageChangedCallback
wrapped' = (a -> DocumentPageChangedCallback) -> C_DocumentPageChangedCallback
forall a.
GObject a =>
(a -> DocumentPageChangedCallback) -> C_DocumentPageChangedCallback
wrap_DocumentPageChangedCallback a -> DocumentPageChangedCallback
wrapped
    FunPtr C_DocumentPageChangedCallback
wrapped'' <- C_DocumentPageChangedCallback
-> IO (FunPtr C_DocumentPageChangedCallback)
mk_DocumentPageChangedCallback C_DocumentPageChangedCallback
wrapped'
    a
-> Text
-> FunPtr C_DocumentPageChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"page-changed" FunPtr C_DocumentPageChangedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [pageChanged](#signal:pageChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' document #pageChanged callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDocumentPageChanged :: (IsDocument a, MonadIO m) => a -> ((?self :: a) => DocumentPageChangedCallback) -> m SignalHandlerId
afterDocumentPageChanged :: forall a (m :: * -> *).
(IsDocument a, MonadIO m) =>
a
-> ((?self::a) => DocumentPageChangedCallback) -> m SignalHandlerId
afterDocumentPageChanged a
obj (?self::a) => DocumentPageChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DocumentPageChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DocumentPageChangedCallback
DocumentPageChangedCallback
cb
    let wrapped' :: C_DocumentPageChangedCallback
wrapped' = (a -> DocumentPageChangedCallback) -> C_DocumentPageChangedCallback
forall a.
GObject a =>
(a -> DocumentPageChangedCallback) -> C_DocumentPageChangedCallback
wrap_DocumentPageChangedCallback a -> DocumentPageChangedCallback
wrapped
    FunPtr C_DocumentPageChangedCallback
wrapped'' <- C_DocumentPageChangedCallback
-> IO (FunPtr C_DocumentPageChangedCallback)
mk_DocumentPageChangedCallback C_DocumentPageChangedCallback
wrapped'
    a
-> Text
-> FunPtr C_DocumentPageChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"page-changed" FunPtr C_DocumentPageChangedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DocumentPageChangedSignalInfo
instance SignalInfo DocumentPageChangedSignalInfo where
    type HaskellCallbackType DocumentPageChangedSignalInfo = DocumentPageChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DocumentPageChangedCallback cb
        cb'' <- mk_DocumentPageChangedCallback cb'
        connectSignalFunPtr obj "page-changed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document::page-changed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#g:signal:pageChanged"})

#endif

-- signal Document::reload
-- | The \'reload\' signal is emitted when the contents of a
-- document is refreshed from its source.  Once \'reload\' has
-- been emitted, a matching \'load-complete\' or \'load-stopped\'
-- signal should follow, which clients may await before
-- interrogating ATK for the latest document content.
type DocumentReloadCallback =
    IO ()

type C_DocumentReloadCallback =
    Ptr Document ->                         -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DocumentReloadCallback`.
foreign import ccall "wrapper"
    mk_DocumentReloadCallback :: C_DocumentReloadCallback -> IO (FunPtr C_DocumentReloadCallback)

wrap_DocumentReloadCallback :: 
    GObject a => (a -> DocumentReloadCallback) ->
    C_DocumentReloadCallback
wrap_DocumentReloadCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentReloadCallback a -> IO ()
gi'cb Ptr Document
gi'selfPtr Ptr ()
_ = do
    Ptr Document -> (Document -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Document
gi'selfPtr ((Document -> IO ()) -> IO ()) -> (Document -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Document
gi'self -> a -> IO ()
gi'cb (Document -> a
Coerce.coerce Document
gi'self) 


-- | Connect a signal handler for the [reload](#signal:reload) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' document #reload callback
-- @
-- 
-- 
onDocumentReload :: (IsDocument a, MonadIO m) => a -> ((?self :: a) => DocumentReloadCallback) -> m SignalHandlerId
onDocumentReload :: forall a (m :: * -> *).
(IsDocument a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDocumentReload a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_DocumentLoadCompleteCallback
wrapped' = (a -> IO ()) -> C_DocumentLoadCompleteCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentReloadCallback a -> IO ()
wrapped
    FunPtr C_DocumentLoadCompleteCallback
wrapped'' <- C_DocumentLoadCompleteCallback
-> IO (FunPtr C_DocumentLoadCompleteCallback)
mk_DocumentReloadCallback C_DocumentLoadCompleteCallback
wrapped'
    a
-> Text
-> FunPtr C_DocumentLoadCompleteCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"reload" FunPtr C_DocumentLoadCompleteCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [reload](#signal:reload) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' document #reload callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDocumentReload :: (IsDocument a, MonadIO m) => a -> ((?self :: a) => DocumentReloadCallback) -> m SignalHandlerId
afterDocumentReload :: forall a (m :: * -> *).
(IsDocument a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDocumentReload a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_DocumentLoadCompleteCallback
wrapped' = (a -> IO ()) -> C_DocumentLoadCompleteCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DocumentLoadCompleteCallback
wrap_DocumentReloadCallback a -> IO ()
wrapped
    FunPtr C_DocumentLoadCompleteCallback
wrapped'' <- C_DocumentLoadCompleteCallback
-> IO (FunPtr C_DocumentLoadCompleteCallback)
mk_DocumentReloadCallback C_DocumentLoadCompleteCallback
wrapped'
    a
-> Text
-> FunPtr C_DocumentLoadCompleteCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"reload" FunPtr C_DocumentLoadCompleteCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DocumentReloadSignalInfo
instance SignalInfo DocumentReloadSignalInfo where
    type HaskellCallbackType DocumentReloadSignalInfo = DocumentReloadCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DocumentReloadCallback cb
        cb'' <- mk_DocumentReloadCallback cb'
        connectSignalFunPtr obj "reload" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Interfaces.Document::reload"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Interfaces-Document.html#g:signal:reload"})

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Document = DocumentSignalList
type DocumentSignalList = ('[ '("loadComplete", DocumentLoadCompleteSignalInfo), '("loadStopped", DocumentLoadStoppedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("pageChanged", DocumentPageChangedSignalInfo), '("reload", DocumentReloadSignalInfo)] :: [(Symbol, *)])

#endif