{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Atk.Interfaces.Text.Text' should be implemented by @/AtkObjects/@ on behalf of widgets
-- that have text content which is either attributed or otherwise
-- non-trivial.  @/AtkObjects/@ whose text content is simple,
-- unattributed, and very brief may expose that content via
-- @/atk_object_get_name/@ instead; however if the text is editable,
-- multi-line, typically longer than three or four words, attributed,
-- selectable, or if the object already uses the \'name\' ATK property
-- for other information, the t'GI.Atk.Interfaces.Text.Text' interface should be used to
-- expose the text content.  In the case of editable text content,
-- t'GI.Atk.Interfaces.EditableText.EditableText' (a subtype of the t'GI.Atk.Interfaces.Text.Text' interface) should be
-- implemented instead.
-- 
--  t'GI.Atk.Interfaces.Text.Text' provides not only traversal facilities and change
-- notification for text content, but also caret tracking and glyph
-- bounding box calculations.  Note that the text strings are exposed
-- as UTF-8, and are therefore potentially multi-byte, and
-- caret-to-byte offset mapping makes no assumptions about the
-- character length; also bounding box glyph-to-offset mapping may be
-- complex for languages which use ligatures.

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

module GI.Atk.Interfaces.Text
    ( 

-- * Exported types
    Text(..)                                ,
    noText                                  ,
    IsText                                  ,
    toText                                  ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveTextMethod                       ,
#endif


-- ** addSelection #method:addSelection#

#if defined(ENABLE_OVERLOADING)
    TextAddSelectionMethodInfo              ,
#endif
    textAddSelection                        ,


-- ** freeRanges #method:freeRanges#

    textFreeRanges                          ,


-- ** getBoundedRanges #method:getBoundedRanges#

#if defined(ENABLE_OVERLOADING)
    TextGetBoundedRangesMethodInfo          ,
#endif
    textGetBoundedRanges                    ,


-- ** getCaretOffset #method:getCaretOffset#

#if defined(ENABLE_OVERLOADING)
    TextGetCaretOffsetMethodInfo            ,
#endif
    textGetCaretOffset                      ,


-- ** getCharacterAtOffset #method:getCharacterAtOffset#

#if defined(ENABLE_OVERLOADING)
    TextGetCharacterAtOffsetMethodInfo      ,
#endif
    textGetCharacterAtOffset                ,


-- ** getCharacterCount #method:getCharacterCount#

#if defined(ENABLE_OVERLOADING)
    TextGetCharacterCountMethodInfo         ,
#endif
    textGetCharacterCount                   ,


-- ** getCharacterExtents #method:getCharacterExtents#

#if defined(ENABLE_OVERLOADING)
    TextGetCharacterExtentsMethodInfo       ,
#endif
    textGetCharacterExtents                 ,


-- ** getDefaultAttributes #method:getDefaultAttributes#

#if defined(ENABLE_OVERLOADING)
    TextGetDefaultAttributesMethodInfo      ,
#endif
    textGetDefaultAttributes                ,


-- ** getNSelections #method:getNSelections#

#if defined(ENABLE_OVERLOADING)
    TextGetNSelectionsMethodInfo            ,
#endif
    textGetNSelections                      ,


-- ** getOffsetAtPoint #method:getOffsetAtPoint#

#if defined(ENABLE_OVERLOADING)
    TextGetOffsetAtPointMethodInfo          ,
#endif
    textGetOffsetAtPoint                    ,


-- ** getRangeExtents #method:getRangeExtents#

#if defined(ENABLE_OVERLOADING)
    TextGetRangeExtentsMethodInfo           ,
#endif
    textGetRangeExtents                     ,


-- ** getRunAttributes #method:getRunAttributes#

#if defined(ENABLE_OVERLOADING)
    TextGetRunAttributesMethodInfo          ,
#endif
    textGetRunAttributes                    ,


-- ** getSelection #method:getSelection#

#if defined(ENABLE_OVERLOADING)
    TextGetSelectionMethodInfo              ,
#endif
    textGetSelection                        ,


-- ** getStringAtOffset #method:getStringAtOffset#

#if defined(ENABLE_OVERLOADING)
    TextGetStringAtOffsetMethodInfo         ,
#endif
    textGetStringAtOffset                   ,


-- ** getText #method:getText#

#if defined(ENABLE_OVERLOADING)
    TextGetTextMethodInfo                   ,
#endif
    textGetText                             ,


-- ** getTextAfterOffset #method:getTextAfterOffset#

#if defined(ENABLE_OVERLOADING)
    TextGetTextAfterOffsetMethodInfo        ,
#endif
    textGetTextAfterOffset                  ,


-- ** getTextAtOffset #method:getTextAtOffset#

#if defined(ENABLE_OVERLOADING)
    TextGetTextAtOffsetMethodInfo           ,
#endif
    textGetTextAtOffset                     ,


-- ** getTextBeforeOffset #method:getTextBeforeOffset#

#if defined(ENABLE_OVERLOADING)
    TextGetTextBeforeOffsetMethodInfo       ,
#endif
    textGetTextBeforeOffset                 ,


-- ** removeSelection #method:removeSelection#

#if defined(ENABLE_OVERLOADING)
    TextRemoveSelectionMethodInfo           ,
#endif
    textRemoveSelection                     ,


-- ** scrollSubstringTo #method:scrollSubstringTo#

#if defined(ENABLE_OVERLOADING)
    TextScrollSubstringToMethodInfo         ,
#endif
    textScrollSubstringTo                   ,


-- ** scrollSubstringToPoint #method:scrollSubstringToPoint#

#if defined(ENABLE_OVERLOADING)
    TextScrollSubstringToPointMethodInfo    ,
#endif
    textScrollSubstringToPoint              ,


-- ** setCaretOffset #method:setCaretOffset#

#if defined(ENABLE_OVERLOADING)
    TextSetCaretOffsetMethodInfo            ,
#endif
    textSetCaretOffset                      ,


-- ** setSelection #method:setSelection#

#if defined(ENABLE_OVERLOADING)
    TextSetSelectionMethodInfo              ,
#endif
    textSetSelection                        ,




 -- * Signals
-- ** textAttributesChanged #signal:textAttributesChanged#

    C_TextTextAttributesChangedCallback     ,
    TextTextAttributesChangedCallback       ,
#if defined(ENABLE_OVERLOADING)
    TextTextAttributesChangedSignalInfo     ,
#endif
    afterTextTextAttributesChanged          ,
    genClosure_TextTextAttributesChanged    ,
    mk_TextTextAttributesChangedCallback    ,
    noTextTextAttributesChangedCallback     ,
    onTextTextAttributesChanged             ,
    wrap_TextTextAttributesChangedCallback  ,


-- ** textCaretMoved #signal:textCaretMoved#

    C_TextTextCaretMovedCallback            ,
    TextTextCaretMovedCallback              ,
#if defined(ENABLE_OVERLOADING)
    TextTextCaretMovedSignalInfo            ,
#endif
    afterTextTextCaretMoved                 ,
    genClosure_TextTextCaretMoved           ,
    mk_TextTextCaretMovedCallback           ,
    noTextTextCaretMovedCallback            ,
    onTextTextCaretMoved                    ,
    wrap_TextTextCaretMovedCallback         ,


-- ** textChanged #signal:textChanged#

    C_TextTextChangedCallback               ,
    TextTextChangedCallback                 ,
#if defined(ENABLE_OVERLOADING)
    TextTextChangedSignalInfo               ,
#endif
    afterTextTextChanged                    ,
    genClosure_TextTextChanged              ,
    mk_TextTextChangedCallback              ,
    noTextTextChangedCallback               ,
    onTextTextChanged                       ,
    wrap_TextTextChangedCallback            ,


-- ** textInsert #signal:textInsert#

    C_TextTextInsertCallback                ,
    TextTextInsertCallback                  ,
#if defined(ENABLE_OVERLOADING)
    TextTextInsertSignalInfo                ,
#endif
    afterTextTextInsert                     ,
    genClosure_TextTextInsert               ,
    mk_TextTextInsertCallback               ,
    noTextTextInsertCallback                ,
    onTextTextInsert                        ,
    wrap_TextTextInsertCallback             ,


-- ** textRemove #signal:textRemove#

    C_TextTextRemoveCallback                ,
    TextTextRemoveCallback                  ,
#if defined(ENABLE_OVERLOADING)
    TextTextRemoveSignalInfo                ,
#endif
    afterTextTextRemove                     ,
    genClosure_TextTextRemove               ,
    mk_TextTextRemoveCallback               ,
    noTextTextRemoveCallback                ,
    onTextTextRemove                        ,
    wrap_TextTextRemoveCallback             ,


-- ** textSelectionChanged #signal:textSelectionChanged#

    C_TextTextSelectionChangedCallback      ,
    TextTextSelectionChangedCallback        ,
#if defined(ENABLE_OVERLOADING)
    TextTextSelectionChangedSignalInfo      ,
#endif
    afterTextTextSelectionChanged           ,
    genClosure_TextTextSelectionChanged     ,
    mk_TextTextSelectionChangedCallback     ,
    noTextTextSelectionChangedCallback      ,
    onTextTextSelectionChanged              ,
    wrap_TextTextSelectionChangedCallback   ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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 {-# SOURCE #-} qualified GI.Atk.Enums as Atk.Enums
import {-# SOURCE #-} qualified GI.Atk.Structs.TextRange as Atk.TextRange
import {-# SOURCE #-} qualified GI.Atk.Structs.TextRectangle as Atk.TextRectangle
import qualified GI.GObject.Objects.Object as GObject.Object

-- interface Text 
-- | Memory-managed wrapper type.
newtype Text = Text (ManagedPtr Text)
    deriving (Text -> Text -> Bool
(Text -> Text -> Bool) -> (Text -> Text -> Bool) -> Eq Text
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Text -> Text -> Bool
$c/= :: Text -> Text -> Bool
== :: Text -> Text -> Bool
$c== :: Text -> Text -> Bool
Eq)
-- | A convenience alias for `Nothing` :: `Maybe` `Text`.
noText :: Maybe Text
noText :: Maybe Text
noText = Maybe Text
forall a. Maybe a
Nothing

-- signal Text::text-attributes-changed
-- | The \"text-attributes-changed\" signal is emitted when the text
-- attributes of the text of an object which implements AtkText
-- changes.
type TextTextAttributesChangedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `TextTextAttributesChangedCallback`@.
noTextTextAttributesChangedCallback :: Maybe TextTextAttributesChangedCallback
noTextTextAttributesChangedCallback :: Maybe TextTextAttributesChangedCallback
noTextTextAttributesChangedCallback = Maybe TextTextAttributesChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_TextTextAttributesChangedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_TextTextAttributesChanged :: MonadIO m => TextTextAttributesChangedCallback -> m (GClosure C_TextTextAttributesChangedCallback)
genClosure_TextTextAttributesChanged :: TextTextAttributesChangedCallback
-> m (GClosure C_TextTextAttributesChangedCallback)
genClosure_TextTextAttributesChanged cb :: TextTextAttributesChangedCallback
cb = IO (GClosure C_TextTextAttributesChangedCallback)
-> m (GClosure C_TextTextAttributesChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextTextAttributesChangedCallback)
 -> m (GClosure C_TextTextAttributesChangedCallback))
-> IO (GClosure C_TextTextAttributesChangedCallback)
-> m (GClosure C_TextTextAttributesChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextTextAttributesChangedCallback
cb' = TextTextAttributesChangedCallback
-> C_TextTextAttributesChangedCallback
wrap_TextTextAttributesChangedCallback TextTextAttributesChangedCallback
cb
    C_TextTextAttributesChangedCallback
-> IO (FunPtr C_TextTextAttributesChangedCallback)
mk_TextTextAttributesChangedCallback C_TextTextAttributesChangedCallback
cb' IO (FunPtr C_TextTextAttributesChangedCallback)
-> (FunPtr C_TextTextAttributesChangedCallback
    -> IO (GClosure C_TextTextAttributesChangedCallback))
-> IO (GClosure C_TextTextAttributesChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextTextAttributesChangedCallback
-> IO (GClosure C_TextTextAttributesChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `TextTextAttributesChangedCallback` into a `C_TextTextAttributesChangedCallback`.
wrap_TextTextAttributesChangedCallback ::
    TextTextAttributesChangedCallback ->
    C_TextTextAttributesChangedCallback
wrap_TextTextAttributesChangedCallback :: TextTextAttributesChangedCallback
-> C_TextTextAttributesChangedCallback
wrap_TextTextAttributesChangedCallback _cb :: TextTextAttributesChangedCallback
_cb _ _ = do
    TextTextAttributesChangedCallback
_cb 


-- | Connect a signal handler for the [textAttributesChanged](#signal:textAttributesChanged) 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' text #textAttributesChanged callback
-- @
-- 
-- 
onTextTextAttributesChanged :: (IsText a, MonadIO m) => a -> TextTextAttributesChangedCallback -> m SignalHandlerId
onTextTextAttributesChanged :: a -> TextTextAttributesChangedCallback -> m SignalHandlerId
onTextTextAttributesChanged obj :: a
obj cb :: TextTextAttributesChangedCallback
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 cb' :: C_TextTextAttributesChangedCallback
cb' = TextTextAttributesChangedCallback
-> C_TextTextAttributesChangedCallback
wrap_TextTextAttributesChangedCallback TextTextAttributesChangedCallback
cb
    FunPtr C_TextTextAttributesChangedCallback
cb'' <- C_TextTextAttributesChangedCallback
-> IO (FunPtr C_TextTextAttributesChangedCallback)
mk_TextTextAttributesChangedCallback C_TextTextAttributesChangedCallback
cb'
    a
-> Text
-> FunPtr C_TextTextAttributesChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-attributes-changed" FunPtr C_TextTextAttributesChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [textAttributesChanged](#signal:textAttributesChanged) 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' text #textAttributesChanged callback
-- @
-- 
-- 
afterTextTextAttributesChanged :: (IsText a, MonadIO m) => a -> TextTextAttributesChangedCallback -> m SignalHandlerId
afterTextTextAttributesChanged :: a -> TextTextAttributesChangedCallback -> m SignalHandlerId
afterTextTextAttributesChanged obj :: a
obj cb :: TextTextAttributesChangedCallback
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 cb' :: C_TextTextAttributesChangedCallback
cb' = TextTextAttributesChangedCallback
-> C_TextTextAttributesChangedCallback
wrap_TextTextAttributesChangedCallback TextTextAttributesChangedCallback
cb
    FunPtr C_TextTextAttributesChangedCallback
cb'' <- C_TextTextAttributesChangedCallback
-> IO (FunPtr C_TextTextAttributesChangedCallback)
mk_TextTextAttributesChangedCallback C_TextTextAttributesChangedCallback
cb'
    a
-> Text
-> FunPtr C_TextTextAttributesChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-attributes-changed" FunPtr C_TextTextAttributesChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TextTextAttributesChangedSignalInfo
instance SignalInfo TextTextAttributesChangedSignalInfo where
    type HaskellCallbackType TextTextAttributesChangedSignalInfo = TextTextAttributesChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextTextAttributesChangedCallback cb
        cb'' <- mk_TextTextAttributesChangedCallback cb'
        connectSignalFunPtr obj "text-attributes-changed" cb'' connectMode detail

#endif

-- signal Text::text-caret-moved
-- | The \"text-caret-moved\" signal is emitted when the caret
-- position of the text of an object which implements AtkText
-- changes.
type TextTextCaretMovedCallback =
    Int32
    -- ^ /@arg1@/: The new position of the text caret.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `TextTextCaretMovedCallback`@.
noTextTextCaretMovedCallback :: Maybe TextTextCaretMovedCallback
noTextTextCaretMovedCallback :: Maybe TextTextCaretMovedCallback
noTextTextCaretMovedCallback = Maybe TextTextCaretMovedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_TextTextCaretMovedCallback =
    Ptr () ->                               -- object
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_TextTextCaretMoved :: MonadIO m => TextTextCaretMovedCallback -> m (GClosure C_TextTextCaretMovedCallback)
genClosure_TextTextCaretMoved :: TextTextCaretMovedCallback
-> m (GClosure C_TextTextCaretMovedCallback)
genClosure_TextTextCaretMoved cb :: TextTextCaretMovedCallback
cb = IO (GClosure C_TextTextCaretMovedCallback)
-> m (GClosure C_TextTextCaretMovedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextTextCaretMovedCallback)
 -> m (GClosure C_TextTextCaretMovedCallback))
-> IO (GClosure C_TextTextCaretMovedCallback)
-> m (GClosure C_TextTextCaretMovedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextTextCaretMovedCallback
cb' = TextTextCaretMovedCallback -> C_TextTextCaretMovedCallback
wrap_TextTextCaretMovedCallback TextTextCaretMovedCallback
cb
    C_TextTextCaretMovedCallback
-> IO (FunPtr C_TextTextCaretMovedCallback)
mk_TextTextCaretMovedCallback C_TextTextCaretMovedCallback
cb' IO (FunPtr C_TextTextCaretMovedCallback)
-> (FunPtr C_TextTextCaretMovedCallback
    -> IO (GClosure C_TextTextCaretMovedCallback))
-> IO (GClosure C_TextTextCaretMovedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextTextCaretMovedCallback
-> IO (GClosure C_TextTextCaretMovedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `TextTextCaretMovedCallback` into a `C_TextTextCaretMovedCallback`.
wrap_TextTextCaretMovedCallback ::
    TextTextCaretMovedCallback ->
    C_TextTextCaretMovedCallback
wrap_TextTextCaretMovedCallback :: TextTextCaretMovedCallback -> C_TextTextCaretMovedCallback
wrap_TextTextCaretMovedCallback _cb :: TextTextCaretMovedCallback
_cb _ arg1 :: Int32
arg1 _ = do
    TextTextCaretMovedCallback
_cb  Int32
arg1


-- | Connect a signal handler for the [textCaretMoved](#signal:textCaretMoved) 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' text #textCaretMoved callback
-- @
-- 
-- 
onTextTextCaretMoved :: (IsText a, MonadIO m) => a -> TextTextCaretMovedCallback -> m SignalHandlerId
onTextTextCaretMoved :: a -> TextTextCaretMovedCallback -> m SignalHandlerId
onTextTextCaretMoved obj :: a
obj cb :: TextTextCaretMovedCallback
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 cb' :: C_TextTextCaretMovedCallback
cb' = TextTextCaretMovedCallback -> C_TextTextCaretMovedCallback
wrap_TextTextCaretMovedCallback TextTextCaretMovedCallback
cb
    FunPtr C_TextTextCaretMovedCallback
cb'' <- C_TextTextCaretMovedCallback
-> IO (FunPtr C_TextTextCaretMovedCallback)
mk_TextTextCaretMovedCallback C_TextTextCaretMovedCallback
cb'
    a
-> Text
-> FunPtr C_TextTextCaretMovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-caret-moved" FunPtr C_TextTextCaretMovedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [textCaretMoved](#signal:textCaretMoved) 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' text #textCaretMoved callback
-- @
-- 
-- 
afterTextTextCaretMoved :: (IsText a, MonadIO m) => a -> TextTextCaretMovedCallback -> m SignalHandlerId
afterTextTextCaretMoved :: a -> TextTextCaretMovedCallback -> m SignalHandlerId
afterTextTextCaretMoved obj :: a
obj cb :: TextTextCaretMovedCallback
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 cb' :: C_TextTextCaretMovedCallback
cb' = TextTextCaretMovedCallback -> C_TextTextCaretMovedCallback
wrap_TextTextCaretMovedCallback TextTextCaretMovedCallback
cb
    FunPtr C_TextTextCaretMovedCallback
cb'' <- C_TextTextCaretMovedCallback
-> IO (FunPtr C_TextTextCaretMovedCallback)
mk_TextTextCaretMovedCallback C_TextTextCaretMovedCallback
cb'
    a
-> Text
-> FunPtr C_TextTextCaretMovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-caret-moved" FunPtr C_TextTextCaretMovedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TextTextCaretMovedSignalInfo
instance SignalInfo TextTextCaretMovedSignalInfo where
    type HaskellCallbackType TextTextCaretMovedSignalInfo = TextTextCaretMovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextTextCaretMovedCallback cb
        cb'' <- mk_TextTextCaretMovedCallback cb'
        connectSignalFunPtr obj "text-caret-moved" cb'' connectMode detail

#endif

-- signal Text::text-changed
{-# DEPRECATED TextTextChangedCallback ["(Since version 2.9.4)","Use t'GI.Atk.Objects.Object.Object'::@/text-insert/@ or","t'GI.Atk.Objects.Object.Object'::@/text-remove/@ instead."] #-}
-- | The \"text-changed\" signal is emitted when the text of the
-- object which implements the AtkText interface changes, This
-- signal will have a detail which is either \"insert\" or
-- \"delete\" which identifies whether the text change was an
-- insertion or a deletion.
type TextTextChangedCallback =
    Int32
    -- ^ /@arg1@/: The position (character offset) of the insertion or deletion.
    -> Int32
    -- ^ /@arg2@/: The length (in characters) of text inserted or deleted.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `TextTextChangedCallback`@.
noTextTextChangedCallback :: Maybe TextTextChangedCallback
noTextTextChangedCallback :: Maybe TextTextChangedCallback
noTextTextChangedCallback = Maybe TextTextChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_TextTextChangedCallback =
    Ptr () ->                               -- object
    Int32 ->
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_TextTextChanged :: MonadIO m => TextTextChangedCallback -> m (GClosure C_TextTextChangedCallback)
genClosure_TextTextChanged :: TextTextChangedCallback -> m (GClosure C_TextTextChangedCallback)
genClosure_TextTextChanged cb :: TextTextChangedCallback
cb = IO (GClosure C_TextTextChangedCallback)
-> m (GClosure C_TextTextChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextTextChangedCallback)
 -> m (GClosure C_TextTextChangedCallback))
-> IO (GClosure C_TextTextChangedCallback)
-> m (GClosure C_TextTextChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextTextChangedCallback
cb' = TextTextChangedCallback -> C_TextTextChangedCallback
wrap_TextTextChangedCallback TextTextChangedCallback
cb
    C_TextTextChangedCallback -> IO (FunPtr C_TextTextChangedCallback)
mk_TextTextChangedCallback C_TextTextChangedCallback
cb' IO (FunPtr C_TextTextChangedCallback)
-> (FunPtr C_TextTextChangedCallback
    -> IO (GClosure C_TextTextChangedCallback))
-> IO (GClosure C_TextTextChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextTextChangedCallback
-> IO (GClosure C_TextTextChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `TextTextChangedCallback` into a `C_TextTextChangedCallback`.
wrap_TextTextChangedCallback ::
    TextTextChangedCallback ->
    C_TextTextChangedCallback
wrap_TextTextChangedCallback :: TextTextChangedCallback -> C_TextTextChangedCallback
wrap_TextTextChangedCallback _cb :: TextTextChangedCallback
_cb _ arg1 :: Int32
arg1 arg2 :: Int32
arg2 _ = do
    TextTextChangedCallback
_cb  Int32
arg1 Int32
arg2


-- | Connect a signal handler for the [textChanged](#signal:textChanged) 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' text #textChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@text-changed::detail@” instead.
-- 
onTextTextChanged :: (IsText a, MonadIO m) => a -> P.Maybe T.Text -> TextTextChangedCallback -> m SignalHandlerId
onTextTextChanged :: a -> Maybe Text -> TextTextChangedCallback -> m SignalHandlerId
onTextTextChanged obj :: a
obj detail :: Maybe Text
detail cb :: TextTextChangedCallback
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 cb' :: C_TextTextChangedCallback
cb' = TextTextChangedCallback -> C_TextTextChangedCallback
wrap_TextTextChangedCallback TextTextChangedCallback
cb
    FunPtr C_TextTextChangedCallback
cb'' <- C_TextTextChangedCallback -> IO (FunPtr C_TextTextChangedCallback)
mk_TextTextChangedCallback C_TextTextChangedCallback
cb'
    a
-> Text
-> FunPtr C_TextTextChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-changed" FunPtr C_TextTextChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [textChanged](#signal:textChanged) 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' text #textChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@text-changed::detail@” instead.
-- 
afterTextTextChanged :: (IsText a, MonadIO m) => a -> P.Maybe T.Text -> TextTextChangedCallback -> m SignalHandlerId
afterTextTextChanged :: a -> Maybe Text -> TextTextChangedCallback -> m SignalHandlerId
afterTextTextChanged obj :: a
obj detail :: Maybe Text
detail cb :: TextTextChangedCallback
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 cb' :: C_TextTextChangedCallback
cb' = TextTextChangedCallback -> C_TextTextChangedCallback
wrap_TextTextChangedCallback TextTextChangedCallback
cb
    FunPtr C_TextTextChangedCallback
cb'' <- C_TextTextChangedCallback -> IO (FunPtr C_TextTextChangedCallback)
mk_TextTextChangedCallback C_TextTextChangedCallback
cb'
    a
-> Text
-> FunPtr C_TextTextChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-changed" FunPtr C_TextTextChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data TextTextChangedSignalInfo
instance SignalInfo TextTextChangedSignalInfo where
    type HaskellCallbackType TextTextChangedSignalInfo = TextTextChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextTextChangedCallback cb
        cb'' <- mk_TextTextChangedCallback cb'
        connectSignalFunPtr obj "text-changed" cb'' connectMode detail

#endif

-- signal Text::text-insert
-- | The \"text-insert\" signal is emitted when a new text is
-- inserted. If the signal was not triggered by the user
-- (e.g. typing or pasting text), the \"system\" detail should be
-- included.
type TextTextInsertCallback =
    Int32
    -- ^ /@arg1@/: The position (character offset) of the insertion.
    -> Int32
    -- ^ /@arg2@/: The length (in characters) of text inserted.
    -> T.Text
    -- ^ /@arg3@/: The new text inserted
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `TextTextInsertCallback`@.
noTextTextInsertCallback :: Maybe TextTextInsertCallback
noTextTextInsertCallback :: Maybe TextTextInsertCallback
noTextTextInsertCallback = Maybe TextTextInsertCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_TextTextInsertCallback =
    Ptr () ->                               -- object
    Int32 ->
    Int32 ->
    CString ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_TextTextInsert :: MonadIO m => TextTextInsertCallback -> m (GClosure C_TextTextInsertCallback)
genClosure_TextTextInsert :: TextTextInsertCallback -> m (GClosure C_TextTextInsertCallback)
genClosure_TextTextInsert cb :: TextTextInsertCallback
cb = IO (GClosure C_TextTextInsertCallback)
-> m (GClosure C_TextTextInsertCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextTextInsertCallback)
 -> m (GClosure C_TextTextInsertCallback))
-> IO (GClosure C_TextTextInsertCallback)
-> m (GClosure C_TextTextInsertCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextTextInsertCallback
cb' = TextTextInsertCallback -> C_TextTextInsertCallback
wrap_TextTextInsertCallback TextTextInsertCallback
cb
    C_TextTextInsertCallback -> IO (FunPtr C_TextTextInsertCallback)
mk_TextTextInsertCallback C_TextTextInsertCallback
cb' IO (FunPtr C_TextTextInsertCallback)
-> (FunPtr C_TextTextInsertCallback
    -> IO (GClosure C_TextTextInsertCallback))
-> IO (GClosure C_TextTextInsertCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextTextInsertCallback
-> IO (GClosure C_TextTextInsertCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `TextTextInsertCallback` into a `C_TextTextInsertCallback`.
wrap_TextTextInsertCallback ::
    TextTextInsertCallback ->
    C_TextTextInsertCallback
wrap_TextTextInsertCallback :: TextTextInsertCallback -> C_TextTextInsertCallback
wrap_TextTextInsertCallback _cb :: TextTextInsertCallback
_cb _ arg1 :: Int32
arg1 arg2 :: Int32
arg2 arg3 :: CString
arg3 _ = do
    Text
arg3' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
arg3
    TextTextInsertCallback
_cb  Int32
arg1 Int32
arg2 Text
arg3'


-- | Connect a signal handler for the [textInsert](#signal:textInsert) 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' text #textInsert callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@text-insert::detail@” instead.
-- 
onTextTextInsert :: (IsText a, MonadIO m) => a -> P.Maybe T.Text -> TextTextInsertCallback -> m SignalHandlerId
onTextTextInsert :: a -> Maybe Text -> TextTextInsertCallback -> m SignalHandlerId
onTextTextInsert obj :: a
obj detail :: Maybe Text
detail cb :: TextTextInsertCallback
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 cb' :: C_TextTextInsertCallback
cb' = TextTextInsertCallback -> C_TextTextInsertCallback
wrap_TextTextInsertCallback TextTextInsertCallback
cb
    FunPtr C_TextTextInsertCallback
cb'' <- C_TextTextInsertCallback -> IO (FunPtr C_TextTextInsertCallback)
mk_TextTextInsertCallback C_TextTextInsertCallback
cb'
    a
-> Text
-> FunPtr C_TextTextInsertCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-insert" FunPtr C_TextTextInsertCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [textInsert](#signal:textInsert) 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' text #textInsert callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@text-insert::detail@” instead.
-- 
afterTextTextInsert :: (IsText a, MonadIO m) => a -> P.Maybe T.Text -> TextTextInsertCallback -> m SignalHandlerId
afterTextTextInsert :: a -> Maybe Text -> TextTextInsertCallback -> m SignalHandlerId
afterTextTextInsert obj :: a
obj detail :: Maybe Text
detail cb :: TextTextInsertCallback
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 cb' :: C_TextTextInsertCallback
cb' = TextTextInsertCallback -> C_TextTextInsertCallback
wrap_TextTextInsertCallback TextTextInsertCallback
cb
    FunPtr C_TextTextInsertCallback
cb'' <- C_TextTextInsertCallback -> IO (FunPtr C_TextTextInsertCallback)
mk_TextTextInsertCallback C_TextTextInsertCallback
cb'
    a
-> Text
-> FunPtr C_TextTextInsertCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-insert" FunPtr C_TextTextInsertCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data TextTextInsertSignalInfo
instance SignalInfo TextTextInsertSignalInfo where
    type HaskellCallbackType TextTextInsertSignalInfo = TextTextInsertCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextTextInsertCallback cb
        cb'' <- mk_TextTextInsertCallback cb'
        connectSignalFunPtr obj "text-insert" cb'' connectMode detail

#endif

-- signal Text::text-remove
-- | The \"text-remove\" signal is emitted when a new text is
-- removed. If the signal was not triggered by the user
-- (e.g. typing or pasting text), the \"system\" detail should be
-- included.
type TextTextRemoveCallback =
    Int32
    -- ^ /@arg1@/: The position (character offset) of the removal.
    -> Int32
    -- ^ /@arg2@/: The length (in characters) of text removed.
    -> T.Text
    -- ^ /@arg3@/: The old text removed
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `TextTextRemoveCallback`@.
noTextTextRemoveCallback :: Maybe TextTextRemoveCallback
noTextTextRemoveCallback :: Maybe TextTextInsertCallback
noTextTextRemoveCallback = Maybe TextTextInsertCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_TextTextRemoveCallback =
    Ptr () ->                               -- object
    Int32 ->
    Int32 ->
    CString ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_TextTextRemove :: MonadIO m => TextTextRemoveCallback -> m (GClosure C_TextTextRemoveCallback)
genClosure_TextTextRemove :: TextTextInsertCallback -> m (GClosure C_TextTextInsertCallback)
genClosure_TextTextRemove cb :: TextTextInsertCallback
cb = IO (GClosure C_TextTextInsertCallback)
-> m (GClosure C_TextTextInsertCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextTextInsertCallback)
 -> m (GClosure C_TextTextInsertCallback))
-> IO (GClosure C_TextTextInsertCallback)
-> m (GClosure C_TextTextInsertCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextTextInsertCallback
cb' = TextTextInsertCallback -> C_TextTextInsertCallback
wrap_TextTextRemoveCallback TextTextInsertCallback
cb
    C_TextTextInsertCallback -> IO (FunPtr C_TextTextInsertCallback)
mk_TextTextRemoveCallback C_TextTextInsertCallback
cb' IO (FunPtr C_TextTextInsertCallback)
-> (FunPtr C_TextTextInsertCallback
    -> IO (GClosure C_TextTextInsertCallback))
-> IO (GClosure C_TextTextInsertCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextTextInsertCallback
-> IO (GClosure C_TextTextInsertCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `TextTextRemoveCallback` into a `C_TextTextRemoveCallback`.
wrap_TextTextRemoveCallback ::
    TextTextRemoveCallback ->
    C_TextTextRemoveCallback
wrap_TextTextRemoveCallback :: TextTextInsertCallback -> C_TextTextInsertCallback
wrap_TextTextRemoveCallback _cb :: TextTextInsertCallback
_cb _ arg1 :: Int32
arg1 arg2 :: Int32
arg2 arg3 :: CString
arg3 _ = do
    Text
arg3' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
arg3
    TextTextInsertCallback
_cb  Int32
arg1 Int32
arg2 Text
arg3'


-- | Connect a signal handler for the [textRemove](#signal:textRemove) 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' text #textRemove callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@text-remove::detail@” instead.
-- 
onTextTextRemove :: (IsText a, MonadIO m) => a -> P.Maybe T.Text -> TextTextRemoveCallback -> m SignalHandlerId
onTextTextRemove :: a -> Maybe Text -> TextTextInsertCallback -> m SignalHandlerId
onTextTextRemove obj :: a
obj detail :: Maybe Text
detail cb :: TextTextInsertCallback
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 cb' :: C_TextTextInsertCallback
cb' = TextTextInsertCallback -> C_TextTextInsertCallback
wrap_TextTextRemoveCallback TextTextInsertCallback
cb
    FunPtr C_TextTextInsertCallback
cb'' <- C_TextTextInsertCallback -> IO (FunPtr C_TextTextInsertCallback)
mk_TextTextRemoveCallback C_TextTextInsertCallback
cb'
    a
-> Text
-> FunPtr C_TextTextInsertCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-remove" FunPtr C_TextTextInsertCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [textRemove](#signal:textRemove) 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' text #textRemove callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@text-remove::detail@” instead.
-- 
afterTextTextRemove :: (IsText a, MonadIO m) => a -> P.Maybe T.Text -> TextTextRemoveCallback -> m SignalHandlerId
afterTextTextRemove :: a -> Maybe Text -> TextTextInsertCallback -> m SignalHandlerId
afterTextTextRemove obj :: a
obj detail :: Maybe Text
detail cb :: TextTextInsertCallback
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 cb' :: C_TextTextInsertCallback
cb' = TextTextInsertCallback -> C_TextTextInsertCallback
wrap_TextTextRemoveCallback TextTextInsertCallback
cb
    FunPtr C_TextTextInsertCallback
cb'' <- C_TextTextInsertCallback -> IO (FunPtr C_TextTextInsertCallback)
mk_TextTextRemoveCallback C_TextTextInsertCallback
cb'
    a
-> Text
-> FunPtr C_TextTextInsertCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-remove" FunPtr C_TextTextInsertCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data TextTextRemoveSignalInfo
instance SignalInfo TextTextRemoveSignalInfo where
    type HaskellCallbackType TextTextRemoveSignalInfo = TextTextRemoveCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextTextRemoveCallback cb
        cb'' <- mk_TextTextRemoveCallback cb'
        connectSignalFunPtr obj "text-remove" cb'' connectMode detail

#endif

-- signal Text::text-selection-changed
-- | The \"text-selection-changed\" signal is emitted when the
-- selected text of an object which implements AtkText changes.
type TextTextSelectionChangedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `TextTextSelectionChangedCallback`@.
noTextTextSelectionChangedCallback :: Maybe TextTextSelectionChangedCallback
noTextTextSelectionChangedCallback :: Maybe TextTextAttributesChangedCallback
noTextTextSelectionChangedCallback = Maybe TextTextAttributesChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_TextTextSelectionChangedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_TextTextSelectionChanged :: MonadIO m => TextTextSelectionChangedCallback -> m (GClosure C_TextTextSelectionChangedCallback)
genClosure_TextTextSelectionChanged :: TextTextAttributesChangedCallback
-> m (GClosure C_TextTextAttributesChangedCallback)
genClosure_TextTextSelectionChanged cb :: TextTextAttributesChangedCallback
cb = IO (GClosure C_TextTextAttributesChangedCallback)
-> m (GClosure C_TextTextAttributesChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextTextAttributesChangedCallback)
 -> m (GClosure C_TextTextAttributesChangedCallback))
-> IO (GClosure C_TextTextAttributesChangedCallback)
-> m (GClosure C_TextTextAttributesChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextTextAttributesChangedCallback
cb' = TextTextAttributesChangedCallback
-> C_TextTextAttributesChangedCallback
wrap_TextTextSelectionChangedCallback TextTextAttributesChangedCallback
cb
    C_TextTextAttributesChangedCallback
-> IO (FunPtr C_TextTextAttributesChangedCallback)
mk_TextTextSelectionChangedCallback C_TextTextAttributesChangedCallback
cb' IO (FunPtr C_TextTextAttributesChangedCallback)
-> (FunPtr C_TextTextAttributesChangedCallback
    -> IO (GClosure C_TextTextAttributesChangedCallback))
-> IO (GClosure C_TextTextAttributesChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextTextAttributesChangedCallback
-> IO (GClosure C_TextTextAttributesChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `TextTextSelectionChangedCallback` into a `C_TextTextSelectionChangedCallback`.
wrap_TextTextSelectionChangedCallback ::
    TextTextSelectionChangedCallback ->
    C_TextTextSelectionChangedCallback
wrap_TextTextSelectionChangedCallback :: TextTextAttributesChangedCallback
-> C_TextTextAttributesChangedCallback
wrap_TextTextSelectionChangedCallback _cb :: TextTextAttributesChangedCallback
_cb _ _ = do
    TextTextAttributesChangedCallback
_cb 


-- | Connect a signal handler for the [textSelectionChanged](#signal:textSelectionChanged) 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' text #textSelectionChanged callback
-- @
-- 
-- 
onTextTextSelectionChanged :: (IsText a, MonadIO m) => a -> TextTextSelectionChangedCallback -> m SignalHandlerId
onTextTextSelectionChanged :: a -> TextTextAttributesChangedCallback -> m SignalHandlerId
onTextTextSelectionChanged obj :: a
obj cb :: TextTextAttributesChangedCallback
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 cb' :: C_TextTextAttributesChangedCallback
cb' = TextTextAttributesChangedCallback
-> C_TextTextAttributesChangedCallback
wrap_TextTextSelectionChangedCallback TextTextAttributesChangedCallback
cb
    FunPtr C_TextTextAttributesChangedCallback
cb'' <- C_TextTextAttributesChangedCallback
-> IO (FunPtr C_TextTextAttributesChangedCallback)
mk_TextTextSelectionChangedCallback C_TextTextAttributesChangedCallback
cb'
    a
-> Text
-> FunPtr C_TextTextAttributesChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-selection-changed" FunPtr C_TextTextAttributesChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [textSelectionChanged](#signal:textSelectionChanged) 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' text #textSelectionChanged callback
-- @
-- 
-- 
afterTextTextSelectionChanged :: (IsText a, MonadIO m) => a -> TextTextSelectionChangedCallback -> m SignalHandlerId
afterTextTextSelectionChanged :: a -> TextTextAttributesChangedCallback -> m SignalHandlerId
afterTextTextSelectionChanged obj :: a
obj cb :: TextTextAttributesChangedCallback
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 cb' :: C_TextTextAttributesChangedCallback
cb' = TextTextAttributesChangedCallback
-> C_TextTextAttributesChangedCallback
wrap_TextTextSelectionChangedCallback TextTextAttributesChangedCallback
cb
    FunPtr C_TextTextAttributesChangedCallback
cb'' <- C_TextTextAttributesChangedCallback
-> IO (FunPtr C_TextTextAttributesChangedCallback)
mk_TextTextSelectionChangedCallback C_TextTextAttributesChangedCallback
cb'
    a
-> Text
-> FunPtr C_TextTextAttributesChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "text-selection-changed" FunPtr C_TextTextAttributesChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TextTextSelectionChangedSignalInfo
instance SignalInfo TextTextSelectionChangedSignalInfo where
    type HaskellCallbackType TextTextSelectionChangedSignalInfo = TextTextSelectionChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextTextSelectionChangedCallback cb
        cb'' <- mk_TextTextSelectionChangedCallback cb'
        connectSignalFunPtr obj "text-selection-changed" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Text = TextSignalList
type TextSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("textAttributesChanged", TextTextAttributesChangedSignalInfo), '("textCaretMoved", TextTextCaretMovedSignalInfo), '("textChanged", TextTextChangedSignalInfo), '("textInsert", TextTextInsertSignalInfo), '("textRemove", TextTextRemoveSignalInfo), '("textSelectionChanged", TextTextSelectionChangedSignalInfo)] :: [(Symbol, *)])

#endif

foreign import ccall "atk_text_get_type"
    c_atk_text_get_type :: IO GType

instance GObject Text where
    gobjectType :: IO GType
gobjectType = IO GType
c_atk_text_get_type
    

-- | Convert 'Text' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Text where
    toGValue :: Text -> IO GValue
toGValue o :: Text
o = do
        GType
gtype <- IO GType
c_atk_text_get_type
        Text -> (Ptr Text -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Text
o (GType
-> (GValue -> Ptr Text -> TextTextAttributesChangedCallback)
-> Ptr Text
-> IO GValue
forall a.
GType
-> (GValue -> a -> TextTextAttributesChangedCallback)
-> a
-> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Text -> TextTextAttributesChangedCallback
forall a.
GObject a =>
GValue -> Ptr a -> TextTextAttributesChangedCallback
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Text
fromGValue gv :: GValue
gv = do
        Ptr Text
ptr <- GValue -> IO (Ptr Text)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Text)
        (ManagedPtr Text -> Text) -> Ptr Text -> IO Text
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Text -> Text
Text Ptr Text
ptr
        
    

-- | Type class for types which can be safely cast to `Text`, for instance with `toText`.
class (GObject o, O.IsDescendantOf Text o) => IsText o
instance (GObject o, O.IsDescendantOf Text o) => IsText o

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

-- | Cast to `Text`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toText :: (MonadIO m, IsText o) => o -> m Text
toText :: o -> m Text
toText = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> (o -> IO Text) -> o -> m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Text -> Text) -> o -> IO Text
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Text -> Text
Text

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTextMethod (t :: Symbol) (o :: *) :: * where
    ResolveTextMethod "addSelection" o = TextAddSelectionMethodInfo
    ResolveTextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTextMethod "removeSelection" o = TextRemoveSelectionMethodInfo
    ResolveTextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTextMethod "scrollSubstringTo" o = TextScrollSubstringToMethodInfo
    ResolveTextMethod "scrollSubstringToPoint" o = TextScrollSubstringToPointMethodInfo
    ResolveTextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTextMethod "getBoundedRanges" o = TextGetBoundedRangesMethodInfo
    ResolveTextMethod "getCaretOffset" o = TextGetCaretOffsetMethodInfo
    ResolveTextMethod "getCharacterAtOffset" o = TextGetCharacterAtOffsetMethodInfo
    ResolveTextMethod "getCharacterCount" o = TextGetCharacterCountMethodInfo
    ResolveTextMethod "getCharacterExtents" o = TextGetCharacterExtentsMethodInfo
    ResolveTextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTextMethod "getDefaultAttributes" o = TextGetDefaultAttributesMethodInfo
    ResolveTextMethod "getNSelections" o = TextGetNSelectionsMethodInfo
    ResolveTextMethod "getOffsetAtPoint" o = TextGetOffsetAtPointMethodInfo
    ResolveTextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTextMethod "getRangeExtents" o = TextGetRangeExtentsMethodInfo
    ResolveTextMethod "getRunAttributes" o = TextGetRunAttributesMethodInfo
    ResolveTextMethod "getSelection" o = TextGetSelectionMethodInfo
    ResolveTextMethod "getStringAtOffset" o = TextGetStringAtOffsetMethodInfo
    ResolveTextMethod "getText" o = TextGetTextMethodInfo
    ResolveTextMethod "getTextAfterOffset" o = TextGetTextAfterOffsetMethodInfo
    ResolveTextMethod "getTextAtOffset" o = TextGetTextAtOffsetMethodInfo
    ResolveTextMethod "getTextBeforeOffset" o = TextGetTextBeforeOffsetMethodInfo
    ResolveTextMethod "setCaretOffset" o = TextSetCaretOffsetMethodInfo
    ResolveTextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTextMethod "setSelection" o = TextSetSelectionMethodInfo
    ResolveTextMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTextMethod t Text, O.MethodInfo info Text p) => OL.IsLabel t (Text -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- method Text::add_selection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the starting character offset of the selected region"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the offset of the first character after the selected region."
--                 , 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_text_add_selection" atk_text_add_selection :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- start_offset : TBasicType TInt
    Int32 ->                                -- end_offset : TBasicType TInt
    IO CInt

-- | Adds a selection bounded by the specified offsets.
textAddSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@startOffset@/: the starting character offset of the selected region
    -> Int32
    -- ^ /@endOffset@/: the offset of the first character after the selected region.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if successful, 'P.False' otherwise
textAddSelection :: a -> Int32 -> Int32 -> m Bool
textAddSelection text :: a
text startOffset :: Int32
startOffset endOffset :: Int32
endOffset = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    CInt
result <- Ptr Text -> Int32 -> Int32 -> IO CInt
atk_text_add_selection Ptr Text
text' Int32
startOffset Int32
endOffset
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextAddSelectionMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Bool), MonadIO m, IsText a) => O.MethodInfo TextAddSelectionMethodInfo a signature where
    overloadedMethod = textAddSelection

#endif

-- method Text::get_bounded_ranges
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rect"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TextRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An AtkTextRectangle giving the dimensions of the bounding box."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Specify whether coordinates are relative to the screen or widget window."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_clip_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TextClipType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Specify the horizontal clip type."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y_clip_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TextClipType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Specify the vertical clip type."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TCArray
--                  True
--                  (-1)
--                  (-1)
--                  (TInterface Name { namespace = "Atk" , name = "TextRange" }))
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_bounded_ranges" atk_text_get_bounded_ranges :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Ptr Atk.TextRectangle.TextRectangle ->  -- rect : TInterface (Name {namespace = "Atk", name = "TextRectangle"})
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    CUInt ->                                -- x_clip_type : TInterface (Name {namespace = "Atk", name = "TextClipType"})
    CUInt ->                                -- y_clip_type : TInterface (Name {namespace = "Atk", name = "TextClipType"})
    IO (Ptr (Ptr Atk.TextRange.TextRange))

-- | Get the ranges of text in the specified bounding box.
-- 
-- /Since: 1.3/
textGetBoundedRanges ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Atk.TextRectangle.TextRectangle
    -- ^ /@rect@/: An AtkTextRectangle giving the dimensions of the bounding box.
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: Specify whether coordinates are relative to the screen or widget window.
    -> Atk.Enums.TextClipType
    -- ^ /@xClipType@/: Specify the horizontal clip type.
    -> Atk.Enums.TextClipType
    -- ^ /@yClipType@/: Specify the vertical clip type.
    -> m [Atk.TextRange.TextRange]
    -- ^ __Returns:__ Array of AtkTextRange. The last
    --          element of the array returned by this function will be NULL.
textGetBoundedRanges :: a
-> TextRectangle
-> CoordType
-> TextClipType
-> TextClipType
-> m [TextRange]
textGetBoundedRanges text :: a
text rect :: TextRectangle
rect coordType :: CoordType
coordType xClipType :: TextClipType
xClipType yClipType :: TextClipType
yClipType = IO [TextRange] -> m [TextRange]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TextRange] -> m [TextRange])
-> IO [TextRange] -> m [TextRange]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    Ptr TextRectangle
rect' <- TextRectangle -> IO (Ptr TextRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextRectangle
rect
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    let xClipType' :: CUInt
xClipType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextClipType -> Int) -> TextClipType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextClipType -> Int
forall a. Enum a => a -> Int
fromEnum) TextClipType
xClipType
    let yClipType' :: CUInt
yClipType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextClipType -> Int) -> TextClipType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextClipType -> Int
forall a. Enum a => a -> Int
fromEnum) TextClipType
yClipType
    Ptr (Ptr TextRange)
result <- Ptr Text
-> Ptr TextRectangle
-> CUInt
-> CUInt
-> CUInt
-> IO (Ptr (Ptr TextRange))
atk_text_get_bounded_ranges Ptr Text
text' Ptr TextRectangle
rect' CUInt
coordType' CUInt
xClipType' CUInt
yClipType'
    Text -> Ptr (Ptr TextRange) -> TextTextAttributesChangedCallback
forall a.
HasCallStack =>
Text -> Ptr a -> TextTextAttributesChangedCallback
checkUnexpectedReturnNULL "textGetBoundedRanges" Ptr (Ptr TextRange)
result
    [Ptr TextRange]
result' <- Ptr (Ptr TextRange) -> IO [Ptr TextRange]
forall a. Ptr (Ptr a) -> IO [Ptr a]
unpackZeroTerminatedPtrArray Ptr (Ptr TextRange)
result
    [TextRange]
result'' <- (Ptr TextRange -> IO TextRange)
-> [Ptr TextRange] -> IO [TextRange]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr TextRange -> TextRange)
-> Ptr TextRange -> IO TextRange
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextRange -> TextRange
Atk.TextRange.TextRange) [Ptr TextRange]
result'
    Ptr (Ptr TextRange) -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr (Ptr TextRange)
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    TextRectangle -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr TextRectangle
rect
    [TextRange] -> IO [TextRange]
forall (m :: * -> *) a. Monad m => a -> m a
return [TextRange]
result''

#if defined(ENABLE_OVERLOADING)
data TextGetBoundedRangesMethodInfo
instance (signature ~ (Atk.TextRectangle.TextRectangle -> Atk.Enums.CoordType -> Atk.Enums.TextClipType -> Atk.Enums.TextClipType -> m [Atk.TextRange.TextRange]), MonadIO m, IsText a) => O.MethodInfo TextGetBoundedRangesMethodInfo a signature where
    overloadedMethod = textGetBoundedRanges

#endif

-- method Text::get_caret_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , 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_text_get_caret_offset" atk_text_get_caret_offset :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    IO Int32

-- | Gets the offset of the position of the caret (cursor).
textGetCaretOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> m Int32
    -- ^ __Returns:__ the character offset of the position of the caret or 0  if
    --          the caret is not located inside the element or in the case of
    --          any other failure.
textGetCaretOffset :: a -> m Int32
textGetCaretOffset text :: a
text = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    Int32
result <- Ptr Text -> IO Int32
atk_text_get_caret_offset Ptr Text
text'
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextGetCaretOffsetMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsText a) => O.MethodInfo TextGetCaretOffsetMethodInfo a signature where
    overloadedMethod = textGetCaretOffset

#endif

-- method Text::get_character_at_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a character offset within @text"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUniChar)
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_character_at_offset" atk_text_get_character_at_offset :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- offset : TBasicType TInt
    IO CInt

-- | Gets the specified text.
textGetCharacterAtOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@offset@/: a character offset within /@text@/
    -> m Char
    -- ^ __Returns:__ the character at /@offset@/ or 0 in the case of failure.
textGetCharacterAtOffset :: a -> Int32 -> m Char
textGetCharacterAtOffset text :: a
text offset :: Int32
offset = IO Char -> m Char
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Char -> m Char) -> IO Char -> m Char
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    CInt
result <- Ptr Text -> Int32 -> IO CInt
atk_text_get_character_at_offset Ptr Text
text' Int32
offset
    let result' :: Char
result' = (Int -> Char
chr (Int -> Char) -> (CInt -> Int) -> CInt -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Char -> IO Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
result'

#if defined(ENABLE_OVERLOADING)
data TextGetCharacterAtOffsetMethodInfo
instance (signature ~ (Int32 -> m Char), MonadIO m, IsText a) => O.MethodInfo TextGetCharacterAtOffsetMethodInfo a signature where
    overloadedMethod = textGetCharacterAtOffset

#endif

-- method Text::get_character_count
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , 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_text_get_character_count" atk_text_get_character_count :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    IO Int32

-- | Gets the character count.
textGetCharacterCount ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> m Int32
    -- ^ __Returns:__ the number of characters or -1 in case of failure.
textGetCharacterCount :: a -> m Int32
textGetCharacterCount text :: a
text = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    Int32
result <- Ptr Text -> IO Int32
atk_text_get_character_count Ptr Text
text'
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextGetCharacterCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsText a) => O.MethodInfo TextGetCharacterCountMethodInfo a signature where
    overloadedMethod = textGetCharacterCount

#endif

-- method Text::get_character_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The offset of the text character for which bounding information is required."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Pointer for the x coordinate of the bounding box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Pointer for the y coordinate of the bounding box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Pointer for the width of the bounding box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Pointer for the height of the bounding box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "coords"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specify whether coordinates are relative to the screen or widget window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_character_extents" atk_text_get_character_extents :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- offset : TBasicType TInt
    Ptr Int32 ->                            -- x : TBasicType TInt
    Ptr Int32 ->                            -- y : TBasicType TInt
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    CUInt ->                                -- coords : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO ()

-- | Get the bounding box containing the glyph representing the character at
--     a particular text offset.
textGetCharacterExtents ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@offset@/: The offset of the text character for which bounding information is required.
    -> Atk.Enums.CoordType
    -- ^ /@coords@/: specify whether coordinates are relative to the screen or widget window
    -> m ((Int32, Int32, Int32, Int32))
textGetCharacterExtents :: a -> Int32 -> CoordType -> m (Int32, Int32, Int32, Int32)
textGetCharacterExtents text :: a
text offset :: Int32
offset coords :: CoordType
coords = IO (Int32, Int32, Int32, Int32) -> m (Int32, Int32, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32, Int32, Int32) -> m (Int32, Int32, Int32, Int32))
-> IO (Int32, Int32, Int32, Int32)
-> m (Int32, Int32, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    Ptr Int32
x <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
y <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    let coords' :: CUInt
coords' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coords
    Ptr Text
-> Int32
-> Ptr Int32
-> Ptr Int32
-> Ptr Int32
-> Ptr Int32
-> CUInt
-> TextTextAttributesChangedCallback
atk_text_get_character_extents Ptr Text
text' Int32
offset Ptr Int32
x Ptr Int32
y Ptr Int32
width Ptr Int32
height CUInt
coords'
    Int32
x' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
x
    Int32
y' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y
    Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
x
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
y
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
width
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
height
    (Int32, Int32, Int32, Int32) -> IO (Int32, Int32, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
x', Int32
y', Int32
width', Int32
height')

#if defined(ENABLE_OVERLOADING)
data TextGetCharacterExtentsMethodInfo
instance (signature ~ (Int32 -> Atk.Enums.CoordType -> m ((Int32, Int32, Int32, Int32))), MonadIO m, IsText a) => O.MethodInfo TextGetCharacterExtentsMethodInfo a signature where
    overloadedMethod = textGetCharacterExtents

#endif

-- method Text::get_default_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , 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_text_get_default_attributes" atk_text_get_default_attributes :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    IO (Ptr (GSList (Ptr ())))

-- | Creates an @/AtkAttributeSet/@ which consists of the default values of
-- attributes for the text. See the enum AtkTextAttribute for types of text
-- attributes that can be returned. Note that other attributes may also be
-- returned.
textGetDefaultAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> m ([Ptr ()])
    -- ^ __Returns:__ an @/AtkAttributeSet/@ which contains the default values
    --          of attributes.  at /@offset@/. this @/atkattributeset/@ should be freed by
    --          a call to 'GI.Atk.Functions.attributeSetFree'.
textGetDefaultAttributes :: a -> m [Ptr ()]
textGetDefaultAttributes text :: a
text = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    Ptr (GSList (Ptr ()))
result <- Ptr Text -> IO (Ptr (GSList (Ptr ())))
atk_text_get_default_attributes Ptr Text
text'
    [Ptr ()]
result' <- Ptr (GSList (Ptr ())) -> IO [Ptr ()]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr ()))
result
    Ptr (GSList (Ptr ())) -> TextTextAttributesChangedCallback
forall a. Ptr (GSList a) -> TextTextAttributesChangedCallback
g_slist_free Ptr (GSList (Ptr ()))
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    [Ptr ()] -> IO [Ptr ()]
forall (m :: * -> *) a. Monad m => a -> m a
return [Ptr ()]
result'

#if defined(ENABLE_OVERLOADING)
data TextGetDefaultAttributesMethodInfo
instance (signature ~ (m ([Ptr ()])), MonadIO m, IsText a) => O.MethodInfo TextGetDefaultAttributesMethodInfo a signature where
    overloadedMethod = textGetDefaultAttributes

#endif

-- method Text::get_n_selections
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , 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_text_get_n_selections" atk_text_get_n_selections :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    IO Int32

-- | Gets the number of selected regions.
textGetNSelections ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> m Int32
    -- ^ __Returns:__ The number of selected regions, or -1 in the case of failure.
textGetNSelections :: a -> m Int32
textGetNSelections text :: a
text = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    Int32
result <- Ptr Text -> IO Int32
atk_text_get_n_selections Ptr Text
text'
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextGetNSelectionsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsText a) => O.MethodInfo TextGetNSelectionsMethodInfo a signature where
    overloadedMethod = textGetNSelections

#endif

-- method Text::get_offset_at_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "screen x-position of character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "screen y-position of character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coords"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specify whether coordinates are relative to the screen or\nwidget window"
--                 , 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_text_get_offset_at_point" atk_text_get_offset_at_point :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    CUInt ->                                -- coords : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO Int32

-- | Gets the offset of the character located at coordinates /@x@/ and /@y@/. /@x@/ and /@y@/
-- are interpreted as being relative to the screen or this widget\'s window
-- depending on /@coords@/.
textGetOffsetAtPoint ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@x@/: screen x-position of character
    -> Int32
    -- ^ /@y@/: screen y-position of character
    -> Atk.Enums.CoordType
    -- ^ /@coords@/: specify whether coordinates are relative to the screen or
    -- widget window
    -> m Int32
    -- ^ __Returns:__ the offset to the character which is located at  the specified
    --          /@x@/ and /@y@/ coordinates of -1 in case of failure.
textGetOffsetAtPoint :: a -> Int32 -> Int32 -> CoordType -> m Int32
textGetOffsetAtPoint text :: a
text x :: Int32
x y :: Int32
y coords :: CoordType
coords = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    let coords' :: CUInt
coords' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coords
    Int32
result <- Ptr Text -> Int32 -> Int32 -> CUInt -> IO Int32
atk_text_get_offset_at_point Ptr Text
text' Int32
x Int32
y CUInt
coords'
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextGetOffsetAtPointMethodInfo
instance (signature ~ (Int32 -> Int32 -> Atk.Enums.CoordType -> m Int32), MonadIO m, IsText a) => O.MethodInfo TextGetOffsetAtPointMethodInfo a signature where
    overloadedMethod = textGetOffsetAtPoint

#endif

-- method Text::get_range_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The offset of the first text character for which boundary\n       information is required."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The offset of the text character after the last character\n       for which boundary information is required."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Specify whether coordinates are relative to the screen or widget window."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rect"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TextRectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A pointer to a AtkTextRectangle which is filled in by this function."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_range_extents" atk_text_get_range_extents :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- start_offset : TBasicType TInt
    Int32 ->                                -- end_offset : TBasicType TInt
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    Ptr Atk.TextRectangle.TextRectangle ->  -- rect : TInterface (Name {namespace = "Atk", name = "TextRectangle"})
    IO ()

-- | Get the bounding box for text within the specified range.
-- 
-- /Since: 1.3/
textGetRangeExtents ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@startOffset@/: The offset of the first text character for which boundary
    --        information is required.
    -> Int32
    -- ^ /@endOffset@/: The offset of the text character after the last character
    --        for which boundary information is required.
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: Specify whether coordinates are relative to the screen or widget window.
    -> m (Atk.TextRectangle.TextRectangle)
textGetRangeExtents :: a -> Int32 -> Int32 -> CoordType -> m TextRectangle
textGetRangeExtents text :: a
text startOffset :: Int32
startOffset endOffset :: Int32
endOffset coordType :: CoordType
coordType = IO TextRectangle -> m TextRectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextRectangle -> m TextRectangle)
-> IO TextRectangle -> m TextRectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    Ptr TextRectangle
rect <- Int -> IO (Ptr TextRectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Atk.TextRectangle.TextRectangle)
    Ptr Text
-> Int32
-> Int32
-> CUInt
-> Ptr TextRectangle
-> TextTextAttributesChangedCallback
atk_text_get_range_extents Ptr Text
text' Int32
startOffset Int32
endOffset CUInt
coordType' Ptr TextRectangle
rect
    TextRectangle
rect' <- ((ManagedPtr TextRectangle -> TextRectangle)
-> Ptr TextRectangle -> IO TextRectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TextRectangle -> TextRectangle
Atk.TextRectangle.TextRectangle) Ptr TextRectangle
rect
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    TextRectangle -> IO TextRectangle
forall (m :: * -> *) a. Monad m => a -> m a
return TextRectangle
rect'

#if defined(ENABLE_OVERLOADING)
data TextGetRangeExtentsMethodInfo
instance (signature ~ (Int32 -> Int32 -> Atk.Enums.CoordType -> m (Atk.TextRectangle.TextRectangle)), MonadIO m, IsText a) => O.MethodInfo TextGetRangeExtentsMethodInfo a signature where
    overloadedMethod = textGetRangeExtents

#endif

-- method Text::get_run_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the character offset at which to get the attributes, -1 means the offset of\nthe character to be inserted at the caret location."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the address to put the start offset of the range"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the address to put the end offset of the range"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGSList (TBasicType TPtr))
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_run_attributes" atk_text_get_run_attributes :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- offset : TBasicType TInt
    Ptr Int32 ->                            -- start_offset : TBasicType TInt
    Ptr Int32 ->                            -- end_offset : TBasicType TInt
    IO (Ptr (GSList (Ptr ())))

-- | Creates an @/AtkAttributeSet/@ which consists of the attributes explicitly
-- set at the position /@offset@/ in the text. /@startOffset@/ and /@endOffset@/ are
-- set to the start and end of the range around /@offset@/ where the attributes are
-- invariant. Note that /@endOffset@/ is the offset of the first character
-- after the range.  See the enum AtkTextAttribute for types of text
-- attributes that can be returned. Note that other attributes may also be
-- returned.
textGetRunAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@offset@/: the character offset at which to get the attributes, -1 means the offset of
    -- the character to be inserted at the caret location.
    -> m (([Ptr ()], Int32, Int32))
    -- ^ __Returns:__ an @/AtkAttributeSet/@ which contains the attributes
    --         explicitly set at /@offset@/. This @/AtkAttributeSet/@ should be freed by
    --         a call to 'GI.Atk.Functions.attributeSetFree'.
textGetRunAttributes :: a -> Int32 -> m ([Ptr ()], Int32, Int32)
textGetRunAttributes text :: a
text offset :: Int32
offset = IO ([Ptr ()], Int32, Int32) -> m ([Ptr ()], Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Ptr ()], Int32, Int32) -> m ([Ptr ()], Int32, Int32))
-> IO ([Ptr ()], Int32, Int32) -> m ([Ptr ()], Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    Ptr Int32
startOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
endOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr (GSList (Ptr ()))
result <- Ptr Text
-> Int32 -> Ptr Int32 -> Ptr Int32 -> IO (Ptr (GSList (Ptr ())))
atk_text_get_run_attributes Ptr Text
text' Int32
offset Ptr Int32
startOffset Ptr Int32
endOffset
    [Ptr ()]
result' <- Ptr (GSList (Ptr ())) -> IO [Ptr ()]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr ()))
result
    Ptr (GSList (Ptr ())) -> TextTextAttributesChangedCallback
forall a. Ptr (GSList a) -> TextTextAttributesChangedCallback
g_slist_free Ptr (GSList (Ptr ()))
result
    Int32
startOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
startOffset
    Int32
endOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
endOffset
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
startOffset
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
endOffset
    ([Ptr ()], Int32, Int32) -> IO ([Ptr ()], Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return ([Ptr ()]
result', Int32
startOffset', Int32
endOffset')

#if defined(ENABLE_OVERLOADING)
data TextGetRunAttributesMethodInfo
instance (signature ~ (Int32 -> m (([Ptr ()], Int32, Int32))), MonadIO m, IsText a) => O.MethodInfo TextGetRunAttributesMethodInfo a signature where
    overloadedMethod = textGetRunAttributes

#endif

-- method Text::get_selection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "selection_num"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The selection number.  The selected regions are\nassigned numbers that correspond to how far the region is from the\nstart of the text.  The selected region closest to the beginning\nof the text region is assigned the number 0, etc.  Note that adding,\nmoving or deleting a selected region can change the numbering."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "passes back the starting character offset of the selected region"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "passes back the ending character offset (offset immediately past)\nof the selected region"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_selection" atk_text_get_selection :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- selection_num : TBasicType TInt
    Ptr Int32 ->                            -- start_offset : TBasicType TInt
    Ptr Int32 ->                            -- end_offset : TBasicType TInt
    IO CString

-- | Gets the text from the specified selection.
textGetSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@selectionNum@/: The selection number.  The selected regions are
    -- assigned numbers that correspond to how far the region is from the
    -- start of the text.  The selected region closest to the beginning
    -- of the text region is assigned the number 0, etc.  Note that adding,
    -- moving or deleting a selected region can change the numbering.
    -> m ((T.Text, Int32, Int32))
    -- ^ __Returns:__ a newly allocated string containing the selected text. Use 'GI.GLib.Functions.free'
    --          to free the returned string.
textGetSelection :: a -> Int32 -> m (Text, Int32, Int32)
textGetSelection text :: a
text selectionNum :: Int32
selectionNum = IO (Text, Int32, Int32) -> m (Text, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Int32, Int32) -> m (Text, Int32, Int32))
-> IO (Text, Int32, Int32) -> m (Text, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    Ptr Int32
startOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
endOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CString
result <- Ptr Text -> Int32 -> Ptr Int32 -> Ptr Int32 -> IO CString
atk_text_get_selection Ptr Text
text' Int32
selectionNum Ptr Int32
startOffset Ptr Int32
endOffset
    Text -> CString -> TextTextAttributesChangedCallback
forall a.
HasCallStack =>
Text -> Ptr a -> TextTextAttributesChangedCallback
checkUnexpectedReturnNULL "textGetSelection" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem CString
result
    Int32
startOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
startOffset
    Int32
endOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
endOffset
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
startOffset
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
endOffset
    (Text, Int32, Int32) -> IO (Text, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
result', Int32
startOffset', Int32
endOffset')

#if defined(ENABLE_OVERLOADING)
data TextGetSelectionMethodInfo
instance (signature ~ (Int32 -> m ((T.Text, Int32, Int32))), MonadIO m, IsText a) => O.MethodInfo TextGetSelectionMethodInfo a signature where
    overloadedMethod = textGetSelection

#endif

-- method Text::get_string_at_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "granularity"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TextGranularity" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #AtkTextGranularity"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the starting character offset of the returned string, or -1\n               in the case of error (e.g. invalid offset, not implemented)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset of the first character after the returned string,\n             or -1 in the case of error (e.g. invalid offset, not implemented)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_string_at_offset" atk_text_get_string_at_offset :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- offset : TBasicType TInt
    CUInt ->                                -- granularity : TInterface (Name {namespace = "Atk", name = "TextGranularity"})
    Ptr Int32 ->                            -- start_offset : TBasicType TInt
    Ptr Int32 ->                            -- end_offset : TBasicType TInt
    IO CString

-- | Gets a portion of the text exposed through an t'GI.Atk.Interfaces.Text.Text' according to a given /@offset@/
-- and a specific /@granularity@/, along with the start and end offsets defining the
-- boundaries of such a portion of text.
-- 
-- If /@granularity@/ is ATK_TEXT_GRANULARITY_CHAR the character at the
-- offset is returned.
-- 
-- If /@granularity@/ is ATK_TEXT_GRANULARITY_WORD the returned string
-- is from the word start at or before the offset to the word start after
-- the offset.
-- 
-- The returned string will contain the word at the offset if the offset
-- is inside a word and will contain the word before the offset if the
-- offset is not inside a word.
-- 
-- If /@granularity@/ is ATK_TEXT_GRANULARITY_SENTENCE the returned string
-- is from the sentence start at or before the offset to the sentence
-- start after the offset.
-- 
-- The returned string will contain the sentence at the offset if the offset
-- is inside a sentence and will contain the sentence before the offset
-- if the offset is not inside a sentence.
-- 
-- If /@granularity@/ is ATK_TEXT_GRANULARITY_LINE the returned string
-- is from the line start at or before the offset to the line
-- start after the offset.
-- 
-- If /@granularity@/ is ATK_TEXT_GRANULARITY_PARAGRAPH the returned string
-- is from the start of the paragraph at or before the offset to the start
-- of the following paragraph after the offset.
-- 
-- /Since: 2.10/
textGetStringAtOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@offset@/: position
    -> Atk.Enums.TextGranularity
    -- ^ /@granularity@/: An t'GI.Atk.Enums.TextGranularity'
    -> m ((Maybe T.Text, Int32, Int32))
    -- ^ __Returns:__ a newly allocated string containing the text at
    --          the /@offset@/ bounded by the specified /@granularity@/. Use 'GI.GLib.Functions.free'
    --          to free the returned string.  Returns 'P.Nothing' if the offset is invalid
    --          or no implementation is available.
textGetStringAtOffset :: a -> Int32 -> TextGranularity -> m (Maybe Text, Int32, Int32)
textGetStringAtOffset text :: a
text offset :: Int32
offset granularity :: TextGranularity
granularity = IO (Maybe Text, Int32, Int32) -> m (Maybe Text, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text, Int32, Int32) -> m (Maybe Text, Int32, Int32))
-> IO (Maybe Text, Int32, Int32) -> m (Maybe Text, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    let granularity' :: CUInt
granularity' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TextGranularity -> Int) -> TextGranularity -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextGranularity -> Int
forall a. Enum a => a -> Int
fromEnum) TextGranularity
granularity
    Ptr Int32
startOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
endOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CString
result <- Ptr Text -> Int32 -> CUInt -> Ptr Int32 -> Ptr Int32 -> IO CString
atk_text_get_string_at_offset Ptr Text
text' Int32
offset CUInt
granularity' Ptr Int32
startOffset Ptr Int32
endOffset
    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
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    Int32
startOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
startOffset
    Int32
endOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
endOffset
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
startOffset
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
endOffset
    (Maybe Text, Int32, Int32) -> IO (Maybe Text, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Text
maybeResult, Int32
startOffset', Int32
endOffset')

#if defined(ENABLE_OVERLOADING)
data TextGetStringAtOffsetMethodInfo
instance (signature ~ (Int32 -> Atk.Enums.TextGranularity -> m ((Maybe T.Text, Int32, Int32))), MonadIO m, IsText a) => O.MethodInfo TextGetStringAtOffsetMethodInfo a signature where
    overloadedMethod = textGetStringAtOffset

#endif

-- method Text::get_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a starting character offset within @text"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an ending character offset within @text, or -1 for the end of the string."
--                 , 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_text_get_text" atk_text_get_text :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- start_offset : TBasicType TInt
    Int32 ->                                -- end_offset : TBasicType TInt
    IO CString

-- | Gets the specified text.
textGetText ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@startOffset@/: a starting character offset within /@text@/
    -> Int32
    -- ^ /@endOffset@/: an ending character offset within /@text@/, or -1 for the end of the string.
    -> m T.Text
    -- ^ __Returns:__ a newly allocated string containing the text from /@startOffset@/ up
    --          to, but not including /@endOffset@/. Use 'GI.GLib.Functions.free' to free the returned
    --          string.
textGetText :: a -> Int32 -> Int32 -> m Text
textGetText text :: a
text startOffset :: Int32
startOffset endOffset :: Int32
endOffset = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    CString
result <- Ptr Text -> Int32 -> Int32 -> IO CString
atk_text_get_text Ptr Text
text' Int32
startOffset Int32
endOffset
    Text -> CString -> TextTextAttributesChangedCallback
forall a.
HasCallStack =>
Text -> Ptr a -> TextTextAttributesChangedCallback
checkUnexpectedReturnNULL "textGetText" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem CString
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data TextGetTextMethodInfo
instance (signature ~ (Int32 -> Int32 -> m T.Text), MonadIO m, IsText a) => O.MethodInfo TextGetTextMethodInfo a signature where
    overloadedMethod = textGetText

#endif

-- method Text::get_text_after_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "boundary_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TextBoundary" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #AtkTextBoundary"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the starting character offset of the returned string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset of the first character after the\n             returned substring"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_text_after_offset" atk_text_get_text_after_offset :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- offset : TBasicType TInt
    CUInt ->                                -- boundary_type : TInterface (Name {namespace = "Atk", name = "TextBoundary"})
    Ptr Int32 ->                            -- start_offset : TBasicType TInt
    Ptr Int32 ->                            -- end_offset : TBasicType TInt
    IO CString

{-# DEPRECATED textGetTextAfterOffset ["(Since version 2.9.3)","Please use 'GI.Atk.Interfaces.Text.textGetStringAtOffset' instead."] #-}
-- | Gets the specified text.
textGetTextAfterOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@offset@/: position
    -> Atk.Enums.TextBoundary
    -- ^ /@boundaryType@/: An t'GI.Atk.Enums.TextBoundary'
    -> m ((T.Text, Int32, Int32))
    -- ^ __Returns:__ a newly allocated string containing the text after /@offset@/ bounded
    --          by the specified /@boundaryType@/. Use 'GI.GLib.Functions.free' to free the returned
    --          string.
textGetTextAfterOffset :: a -> Int32 -> TextBoundary -> m (Text, Int32, Int32)
textGetTextAfterOffset text :: a
text offset :: Int32
offset boundaryType :: TextBoundary
boundaryType = IO (Text, Int32, Int32) -> m (Text, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Int32, Int32) -> m (Text, Int32, Int32))
-> IO (Text, Int32, Int32) -> m (Text, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    let boundaryType' :: CUInt
boundaryType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextBoundary -> Int) -> TextBoundary -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextBoundary -> Int
forall a. Enum a => a -> Int
fromEnum) TextBoundary
boundaryType
    Ptr Int32
startOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
endOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CString
result <- Ptr Text -> Int32 -> CUInt -> Ptr Int32 -> Ptr Int32 -> IO CString
atk_text_get_text_after_offset Ptr Text
text' Int32
offset CUInt
boundaryType' Ptr Int32
startOffset Ptr Int32
endOffset
    Text -> CString -> TextTextAttributesChangedCallback
forall a.
HasCallStack =>
Text -> Ptr a -> TextTextAttributesChangedCallback
checkUnexpectedReturnNULL "textGetTextAfterOffset" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem CString
result
    Int32
startOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
startOffset
    Int32
endOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
endOffset
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
startOffset
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
endOffset
    (Text, Int32, Int32) -> IO (Text, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
result', Int32
startOffset', Int32
endOffset')

#if defined(ENABLE_OVERLOADING)
data TextGetTextAfterOffsetMethodInfo
instance (signature ~ (Int32 -> Atk.Enums.TextBoundary -> m ((T.Text, Int32, Int32))), MonadIO m, IsText a) => O.MethodInfo TextGetTextAfterOffsetMethodInfo a signature where
    overloadedMethod = textGetTextAfterOffset

#endif

-- method Text::get_text_at_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "boundary_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TextBoundary" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #AtkTextBoundary"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the starting character offset of the returned string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset of the first character after the\n             returned substring"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_text_at_offset" atk_text_get_text_at_offset :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- offset : TBasicType TInt
    CUInt ->                                -- boundary_type : TInterface (Name {namespace = "Atk", name = "TextBoundary"})
    Ptr Int32 ->                            -- start_offset : TBasicType TInt
    Ptr Int32 ->                            -- end_offset : TBasicType TInt
    IO CString

{-# DEPRECATED textGetTextAtOffset ["This method is deprecated since ATK version","2.9.4. Please use 'GI.Atk.Interfaces.Text.textGetStringAtOffset' instead."] #-}
-- | Gets the specified text.
-- 
-- If the boundary_type if ATK_TEXT_BOUNDARY_CHAR the character at the
-- offset is returned.
-- 
-- If the boundary_type is ATK_TEXT_BOUNDARY_WORD_START the returned string
-- is from the word start at or before the offset to the word start after
-- the offset.
-- 
-- The returned string will contain the word at the offset if the offset
-- is inside a word and will contain the word before the offset if the
-- offset is not inside a word.
-- 
-- If the boundary type is ATK_TEXT_BOUNDARY_SENTENCE_START the returned
-- string is from the sentence start at or before the offset to the sentence
-- start after the offset.
-- 
-- The returned string will contain the sentence at the offset if the offset
-- is inside a sentence and will contain the sentence before the offset
-- if the offset is not inside a sentence.
-- 
-- If the boundary type is ATK_TEXT_BOUNDARY_LINE_START the returned
-- string is from the line start at or before the offset to the line
-- start after the offset.
textGetTextAtOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@offset@/: position
    -> Atk.Enums.TextBoundary
    -- ^ /@boundaryType@/: An t'GI.Atk.Enums.TextBoundary'
    -> m ((T.Text, Int32, Int32))
    -- ^ __Returns:__ a newly allocated string containing the text at /@offset@/ bounded
    --          by the specified /@boundaryType@/. Use 'GI.GLib.Functions.free' to free the returned
    --          string.
textGetTextAtOffset :: a -> Int32 -> TextBoundary -> m (Text, Int32, Int32)
textGetTextAtOffset text :: a
text offset :: Int32
offset boundaryType :: TextBoundary
boundaryType = IO (Text, Int32, Int32) -> m (Text, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Int32, Int32) -> m (Text, Int32, Int32))
-> IO (Text, Int32, Int32) -> m (Text, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    let boundaryType' :: CUInt
boundaryType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextBoundary -> Int) -> TextBoundary -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextBoundary -> Int
forall a. Enum a => a -> Int
fromEnum) TextBoundary
boundaryType
    Ptr Int32
startOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
endOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CString
result <- Ptr Text -> Int32 -> CUInt -> Ptr Int32 -> Ptr Int32 -> IO CString
atk_text_get_text_at_offset Ptr Text
text' Int32
offset CUInt
boundaryType' Ptr Int32
startOffset Ptr Int32
endOffset
    Text -> CString -> TextTextAttributesChangedCallback
forall a.
HasCallStack =>
Text -> Ptr a -> TextTextAttributesChangedCallback
checkUnexpectedReturnNULL "textGetTextAtOffset" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem CString
result
    Int32
startOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
startOffset
    Int32
endOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
endOffset
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
startOffset
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
endOffset
    (Text, Int32, Int32) -> IO (Text, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
result', Int32
startOffset', Int32
endOffset')

#if defined(ENABLE_OVERLOADING)
data TextGetTextAtOffsetMethodInfo
instance (signature ~ (Int32 -> Atk.Enums.TextBoundary -> m ((T.Text, Int32, Int32))), MonadIO m, IsText a) => O.MethodInfo TextGetTextAtOffsetMethodInfo a signature where
    overloadedMethod = textGetTextAtOffset

#endif

-- method Text::get_text_before_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "boundary_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TextBoundary" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #AtkTextBoundary"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the starting character offset of the returned string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset of the first character after the\n             returned substring"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_get_text_before_offset" atk_text_get_text_before_offset :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- offset : TBasicType TInt
    CUInt ->                                -- boundary_type : TInterface (Name {namespace = "Atk", name = "TextBoundary"})
    Ptr Int32 ->                            -- start_offset : TBasicType TInt
    Ptr Int32 ->                            -- end_offset : TBasicType TInt
    IO CString

{-# DEPRECATED textGetTextBeforeOffset ["(Since version 2.9.3)","Please use 'GI.Atk.Interfaces.Text.textGetStringAtOffset' instead."] #-}
-- | Gets the specified text.
textGetTextBeforeOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@offset@/: position
    -> Atk.Enums.TextBoundary
    -- ^ /@boundaryType@/: An t'GI.Atk.Enums.TextBoundary'
    -> m ((T.Text, Int32, Int32))
    -- ^ __Returns:__ a newly allocated string containing the text before /@offset@/ bounded
    --          by the specified /@boundaryType@/. Use 'GI.GLib.Functions.free' to free the returned
    --          string.
textGetTextBeforeOffset :: a -> Int32 -> TextBoundary -> m (Text, Int32, Int32)
textGetTextBeforeOffset text :: a
text offset :: Int32
offset boundaryType :: TextBoundary
boundaryType = IO (Text, Int32, Int32) -> m (Text, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Int32, Int32) -> m (Text, Int32, Int32))
-> IO (Text, Int32, Int32) -> m (Text, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    let boundaryType' :: CUInt
boundaryType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextBoundary -> Int) -> TextBoundary -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextBoundary -> Int
forall a. Enum a => a -> Int
fromEnum) TextBoundary
boundaryType
    Ptr Int32
startOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
endOffset <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CString
result <- Ptr Text -> Int32 -> CUInt -> Ptr Int32 -> Ptr Int32 -> IO CString
atk_text_get_text_before_offset Ptr Text
text' Int32
offset CUInt
boundaryType' Ptr Int32
startOffset Ptr Int32
endOffset
    Text -> CString -> TextTextAttributesChangedCallback
forall a.
HasCallStack =>
Text -> Ptr a -> TextTextAttributesChangedCallback
checkUnexpectedReturnNULL "textGetTextBeforeOffset" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem CString
result
    Int32
startOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
startOffset
    Int32
endOffset' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
endOffset
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
startOffset
    Ptr Int32 -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr Int32
endOffset
    (Text, Int32, Int32) -> IO (Text, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
result', Int32
startOffset', Int32
endOffset')

#if defined(ENABLE_OVERLOADING)
data TextGetTextBeforeOffsetMethodInfo
instance (signature ~ (Int32 -> Atk.Enums.TextBoundary -> m ((T.Text, Int32, Int32))), MonadIO m, IsText a) => O.MethodInfo TextGetTextBeforeOffsetMethodInfo a signature where
    overloadedMethod = textGetTextBeforeOffset

#endif

-- method Text::remove_selection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "selection_num"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The selection number.  The selected regions are\nassigned numbers that correspond to how far the region is from the\nstart of the text.  The selected region closest to the beginning\nof the text region is assigned the number 0, etc.  Note that adding,\nmoving or deleting a selected region can change the numbering."
--                 , 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_text_remove_selection" atk_text_remove_selection :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- selection_num : TBasicType TInt
    IO CInt

-- | Removes the specified selection.
textRemoveSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@selectionNum@/: The selection number.  The selected regions are
    -- assigned numbers that correspond to how far the region is from the
    -- start of the text.  The selected region closest to the beginning
    -- of the text region is assigned the number 0, etc.  Note that adding,
    -- moving or deleting a selected region can change the numbering.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if successful, 'P.False' otherwise
textRemoveSelection :: a -> Int32 -> m Bool
textRemoveSelection text :: a
text selectionNum :: Int32
selectionNum = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    CInt
result <- Ptr Text -> Int32 -> IO CInt
atk_text_remove_selection Ptr Text
text' Int32
selectionNum
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextRemoveSelectionMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m, IsText a) => O.MethodInfo TextRemoveSelectionMethodInfo a signature where
    overloadedMethod = textRemoveSelection

#endif

-- method Text::scroll_substring_to
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "start position" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "end position, or -1 for the end of the string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "ScrollType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "specify where the object should be made visible."
--                 , 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_text_scroll_substring_to" atk_text_scroll_substring_to :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- start_offset : TBasicType TInt
    Int32 ->                                -- end_offset : TBasicType TInt
    CUInt ->                                -- type : TInterface (Name {namespace = "Atk", name = "ScrollType"})
    IO CInt

-- | Makes /@text@/ visible on the screen by scrolling all necessary parents.
-- 
-- Contrary to atk_text_set_position, this does not actually move
-- /@text@/ in its parent, this only makes the parents scroll so that the
-- object shows up on the screen, given its current position within the parents.
-- 
-- /Since: 2.32/
textScrollSubstringTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@startOffset@/: start position
    -> Int32
    -- ^ /@endOffset@/: end position, or -1 for the end of the string.
    -> Atk.Enums.ScrollType
    -- ^ /@type@/: specify where the object should be made visible.
    -> m Bool
    -- ^ __Returns:__ whether scrolling was successful.
textScrollSubstringTo :: a -> Int32 -> Int32 -> ScrollType -> m Bool
textScrollSubstringTo text :: a
text startOffset :: Int32
startOffset endOffset :: Int32
endOffset type_ :: ScrollType
type_ = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (ScrollType -> Int) -> ScrollType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScrollType -> Int
forall a. Enum a => a -> Int
fromEnum) ScrollType
type_
    CInt
result <- Ptr Text -> Int32 -> Int32 -> CUInt -> IO CInt
atk_text_scroll_substring_to Ptr Text
text' Int32
startOffset Int32
endOffset CUInt
type_'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextScrollSubstringToMethodInfo
instance (signature ~ (Int32 -> Int32 -> Atk.Enums.ScrollType -> m Bool), MonadIO m, IsText a) => O.MethodInfo TextScrollSubstringToMethodInfo a signature where
    overloadedMethod = textScrollSubstringTo

#endif

-- method Text::scroll_substring_to_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "start position" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "end position, or -1 for the end of the string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "coords"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specify whether coordinates are relative to the screen or to the\nparent object."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x-position where to scroll to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y-position where to scroll to"
--                 , 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_text_scroll_substring_to_point" atk_text_scroll_substring_to_point :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- start_offset : TBasicType TInt
    Int32 ->                                -- end_offset : TBasicType TInt
    CUInt ->                                -- coords : TInterface (Name {namespace = "Atk", name = "CoordType"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO CInt

-- | Makes an object visible on the screen at a given position by scrolling all
-- necessary parents.
-- 
-- /Since: 2.32/
textScrollSubstringToPoint ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@startOffset@/: start position
    -> Int32
    -- ^ /@endOffset@/: end position, or -1 for the end of the string.
    -> Atk.Enums.CoordType
    -- ^ /@coords@/: specify whether coordinates are relative to the screen or to the
    -- parent object.
    -> Int32
    -- ^ /@x@/: x-position where to scroll to
    -> Int32
    -- ^ /@y@/: y-position where to scroll to
    -> m Bool
    -- ^ __Returns:__ whether scrolling was successful.
textScrollSubstringToPoint :: a -> Int32 -> Int32 -> CoordType -> Int32 -> Int32 -> m Bool
textScrollSubstringToPoint text :: a
text startOffset :: Int32
startOffset endOffset :: Int32
endOffset coords :: CoordType
coords x :: Int32
x y :: Int32
y = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    let coords' :: CUInt
coords' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coords
    CInt
result <- Ptr Text -> Int32 -> Int32 -> CUInt -> Int32 -> Int32 -> IO CInt
atk_text_scroll_substring_to_point Ptr Text
text' Int32
startOffset Int32
endOffset CUInt
coords' Int32
x Int32
y
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextScrollSubstringToPointMethodInfo
instance (signature ~ (Int32 -> Int32 -> Atk.Enums.CoordType -> Int32 -> Int32 -> m Bool), MonadIO m, IsText a) => O.MethodInfo TextScrollSubstringToPointMethodInfo a signature where
    overloadedMethod = textScrollSubstringToPoint

#endif

-- method Text::set_caret_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the character offset of the new caret position"
--                 , 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_text_set_caret_offset" atk_text_set_caret_offset :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- offset : TBasicType TInt
    IO CInt

-- | Sets the caret (cursor) position to the specified /@offset@/.
textSetCaretOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@offset@/: the character offset of the new caret position
    -> m Bool
    -- ^ __Returns:__ 'P.True' if successful, 'P.False' otherwise.
textSetCaretOffset :: a -> Int32 -> m Bool
textSetCaretOffset text :: a
text offset :: Int32
offset = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    CInt
result <- Ptr Text -> Int32 -> IO CInt
atk_text_set_caret_offset Ptr Text
text' Int32
offset
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextSetCaretOffsetMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m, IsText a) => O.MethodInfo TextSetCaretOffsetMethodInfo a signature where
    overloadedMethod = textSetCaretOffset

#endif

-- method Text::set_selection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "text"
--           , argType = TInterface Name { namespace = "Atk" , name = "Text" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkText" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "selection_num"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The selection number.  The selected regions are\nassigned numbers that correspond to how far the region is from the\nstart of the text.  The selected region closest to the beginning\nof the text region is assigned the number 0, etc.  Note that adding,\nmoving or deleting a selected region can change the numbering."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the new starting character offset of the selection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the new end position of (e.g. offset immediately past)\nthe selection"
--                 , 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_text_set_selection" atk_text_set_selection :: 
    Ptr Text ->                             -- text : TInterface (Name {namespace = "Atk", name = "Text"})
    Int32 ->                                -- selection_num : TBasicType TInt
    Int32 ->                                -- start_offset : TBasicType TInt
    Int32 ->                                -- end_offset : TBasicType TInt
    IO CInt

-- | Changes the start and end offset of the specified selection.
textSetSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsText a) =>
    a
    -- ^ /@text@/: an t'GI.Atk.Interfaces.Text.Text'
    -> Int32
    -- ^ /@selectionNum@/: The selection number.  The selected regions are
    -- assigned numbers that correspond to how far the region is from the
    -- start of the text.  The selected region closest to the beginning
    -- of the text region is assigned the number 0, etc.  Note that adding,
    -- moving or deleting a selected region can change the numbering.
    -> Int32
    -- ^ /@startOffset@/: the new starting character offset of the selection
    -> Int32
    -- ^ /@endOffset@/: the new end position of (e.g. offset immediately past)
    -- the selection
    -> m Bool
    -- ^ __Returns:__ 'P.True' if successful, 'P.False' otherwise
textSetSelection :: a -> Int32 -> Int32 -> Int32 -> m Bool
textSetSelection text :: a
text selectionNum :: Int32
selectionNum startOffset :: Int32
startOffset endOffset :: Int32
endOffset = 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 Text
text' <- a -> IO (Ptr Text)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
text
    CInt
result <- Ptr Text -> Int32 -> Int32 -> Int32 -> IO CInt
atk_text_set_selection Ptr Text
text' Int32
selectionNum Int32
startOffset Int32
endOffset
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr a
text
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextSetSelectionMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> m Bool), MonadIO m, IsText a) => O.MethodInfo TextSetSelectionMethodInfo a signature where
    overloadedMethod = textSetSelection

#endif

-- method Text::free_ranges
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "ranges"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 (-1)
--                 (TInterface Name { namespace = "Atk" , name = "TextRange" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A pointer to an array of #AtkTextRange which is\n  to be freed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_text_free_ranges" atk_text_free_ranges :: 
    Ptr Atk.TextRange.TextRange ->          -- ranges : TCArray False (-1) (-1) (TInterface (Name {namespace = "Atk", name = "TextRange"}))
    IO ()

-- | Frees the memory associated with an array of AtkTextRange. It is assumed
-- that the array was returned by the function atk_text_get_bounded_ranges
-- and is NULL terminated.
-- 
-- /Since: 1.3/
textFreeRanges ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Atk.TextRange.TextRange]
    -- ^ /@ranges@/: A pointer to an array of t'GI.Atk.Structs.TextRange.TextRange' which is
    --   to be freed.
    -> m ()
textFreeRanges :: [TextRange] -> m ()
textFreeRanges ranges :: [TextRange]
ranges = TextTextAttributesChangedCallback -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (TextTextAttributesChangedCallback -> m ())
-> TextTextAttributesChangedCallback -> m ()
forall a b. (a -> b) -> a -> b
$ do
    [Ptr TextRange]
ranges' <- (TextRange -> IO (Ptr TextRange))
-> [TextRange] -> IO [Ptr TextRange]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TextRange -> IO (Ptr TextRange)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [TextRange]
ranges
    Ptr TextRange
ranges'' <- Int -> [Ptr TextRange] -> IO (Ptr TextRange)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 32 [Ptr TextRange]
ranges'
    Ptr TextRange -> TextTextAttributesChangedCallback
atk_text_free_ranges Ptr TextRange
ranges''
    (TextRange -> TextTextAttributesChangedCallback)
-> [TextRange] -> TextTextAttributesChangedCallback
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ TextRange -> TextTextAttributesChangedCallback
forall a.
ManagedPtrNewtype a =>
a -> TextTextAttributesChangedCallback
touchManagedPtr [TextRange]
ranges
    Ptr TextRange -> TextTextAttributesChangedCallback
forall a. Ptr a -> TextTextAttributesChangedCallback
freeMem Ptr TextRange
ranges''
    () -> TextTextAttributesChangedCallback
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif