{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- You may wish to begin by reading the
-- [text widget conceptual overview][TextWidget]
-- which gives an overview of all the objects and data
-- types related to the text widget and how they work together.

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

module GI.Gtk.Structs.TextIter
    ( 

-- * Exported types
    TextIter(..)                            ,
    newZeroTextIter                         ,
    noTextIter                              ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveTextIterMethod                   ,
#endif


-- ** assign #method:assign#

#if defined(ENABLE_OVERLOADING)
    TextIterAssignMethodInfo                ,
#endif
    textIterAssign                          ,


-- ** backwardChar #method:backwardChar#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardCharMethodInfo          ,
#endif
    textIterBackwardChar                    ,


-- ** backwardChars #method:backwardChars#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardCharsMethodInfo         ,
#endif
    textIterBackwardChars                   ,


-- ** backwardCursorPosition #method:backwardCursorPosition#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardCursorPositionMethodInfo,
#endif
    textIterBackwardCursorPosition          ,


-- ** backwardCursorPositions #method:backwardCursorPositions#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardCursorPositionsMethodInfo,
#endif
    textIterBackwardCursorPositions         ,


-- ** backwardFindChar #method:backwardFindChar#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardFindCharMethodInfo      ,
#endif
    textIterBackwardFindChar                ,


-- ** backwardLine #method:backwardLine#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardLineMethodInfo          ,
#endif
    textIterBackwardLine                    ,


-- ** backwardLines #method:backwardLines#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardLinesMethodInfo         ,
#endif
    textIterBackwardLines                   ,


-- ** backwardSearch #method:backwardSearch#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardSearchMethodInfo        ,
#endif
    textIterBackwardSearch                  ,


-- ** backwardSentenceStart #method:backwardSentenceStart#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardSentenceStartMethodInfo ,
#endif
    textIterBackwardSentenceStart           ,


-- ** backwardSentenceStarts #method:backwardSentenceStarts#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardSentenceStartsMethodInfo,
#endif
    textIterBackwardSentenceStarts          ,


-- ** backwardToTagToggle #method:backwardToTagToggle#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardToTagToggleMethodInfo   ,
#endif
    textIterBackwardToTagToggle             ,


-- ** backwardVisibleCursorPosition #method:backwardVisibleCursorPosition#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardVisibleCursorPositionMethodInfo,
#endif
    textIterBackwardVisibleCursorPosition   ,


-- ** backwardVisibleCursorPositions #method:backwardVisibleCursorPositions#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardVisibleCursorPositionsMethodInfo,
#endif
    textIterBackwardVisibleCursorPositions  ,


-- ** backwardVisibleLine #method:backwardVisibleLine#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardVisibleLineMethodInfo   ,
#endif
    textIterBackwardVisibleLine             ,


-- ** backwardVisibleLines #method:backwardVisibleLines#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardVisibleLinesMethodInfo  ,
#endif
    textIterBackwardVisibleLines            ,


-- ** backwardVisibleWordStart #method:backwardVisibleWordStart#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardVisibleWordStartMethodInfo,
#endif
    textIterBackwardVisibleWordStart        ,


-- ** backwardVisibleWordStarts #method:backwardVisibleWordStarts#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardVisibleWordStartsMethodInfo,
#endif
    textIterBackwardVisibleWordStarts       ,


-- ** backwardWordStart #method:backwardWordStart#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardWordStartMethodInfo     ,
#endif
    textIterBackwardWordStart               ,


-- ** backwardWordStarts #method:backwardWordStarts#

#if defined(ENABLE_OVERLOADING)
    TextIterBackwardWordStartsMethodInfo    ,
#endif
    textIterBackwardWordStarts              ,


-- ** beginsTag #method:beginsTag#

#if defined(ENABLE_OVERLOADING)
    TextIterBeginsTagMethodInfo             ,
#endif
    textIterBeginsTag                       ,


-- ** canInsert #method:canInsert#

#if defined(ENABLE_OVERLOADING)
    TextIterCanInsertMethodInfo             ,
#endif
    textIterCanInsert                       ,


-- ** compare #method:compare#

#if defined(ENABLE_OVERLOADING)
    TextIterCompareMethodInfo               ,
#endif
    textIterCompare                         ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    TextIterCopyMethodInfo                  ,
#endif
    textIterCopy                            ,


-- ** editable #method:editable#

#if defined(ENABLE_OVERLOADING)
    TextIterEditableMethodInfo              ,
#endif
    textIterEditable                        ,


-- ** endsLine #method:endsLine#

#if defined(ENABLE_OVERLOADING)
    TextIterEndsLineMethodInfo              ,
#endif
    textIterEndsLine                        ,


-- ** endsSentence #method:endsSentence#

#if defined(ENABLE_OVERLOADING)
    TextIterEndsSentenceMethodInfo          ,
#endif
    textIterEndsSentence                    ,


-- ** endsTag #method:endsTag#

#if defined(ENABLE_OVERLOADING)
    TextIterEndsTagMethodInfo               ,
#endif
    textIterEndsTag                         ,


-- ** endsWord #method:endsWord#

#if defined(ENABLE_OVERLOADING)
    TextIterEndsWordMethodInfo              ,
#endif
    textIterEndsWord                        ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    TextIterEqualMethodInfo                 ,
#endif
    textIterEqual                           ,


-- ** forwardChar #method:forwardChar#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardCharMethodInfo           ,
#endif
    textIterForwardChar                     ,


-- ** forwardChars #method:forwardChars#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardCharsMethodInfo          ,
#endif
    textIterForwardChars                    ,


-- ** forwardCursorPosition #method:forwardCursorPosition#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardCursorPositionMethodInfo ,
#endif
    textIterForwardCursorPosition           ,


-- ** forwardCursorPositions #method:forwardCursorPositions#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardCursorPositionsMethodInfo,
#endif
    textIterForwardCursorPositions          ,


-- ** forwardFindChar #method:forwardFindChar#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardFindCharMethodInfo       ,
#endif
    textIterForwardFindChar                 ,


-- ** forwardLine #method:forwardLine#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardLineMethodInfo           ,
#endif
    textIterForwardLine                     ,


-- ** forwardLines #method:forwardLines#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardLinesMethodInfo          ,
#endif
    textIterForwardLines                    ,


-- ** forwardSearch #method:forwardSearch#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardSearchMethodInfo         ,
#endif
    textIterForwardSearch                   ,


-- ** forwardSentenceEnd #method:forwardSentenceEnd#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardSentenceEndMethodInfo    ,
#endif
    textIterForwardSentenceEnd              ,


-- ** forwardSentenceEnds #method:forwardSentenceEnds#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardSentenceEndsMethodInfo   ,
#endif
    textIterForwardSentenceEnds             ,


-- ** forwardToEnd #method:forwardToEnd#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardToEndMethodInfo          ,
#endif
    textIterForwardToEnd                    ,


-- ** forwardToLineEnd #method:forwardToLineEnd#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardToLineEndMethodInfo      ,
#endif
    textIterForwardToLineEnd                ,


-- ** forwardToTagToggle #method:forwardToTagToggle#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardToTagToggleMethodInfo    ,
#endif
    textIterForwardToTagToggle              ,


-- ** forwardVisibleCursorPosition #method:forwardVisibleCursorPosition#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardVisibleCursorPositionMethodInfo,
#endif
    textIterForwardVisibleCursorPosition    ,


-- ** forwardVisibleCursorPositions #method:forwardVisibleCursorPositions#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardVisibleCursorPositionsMethodInfo,
#endif
    textIterForwardVisibleCursorPositions   ,


-- ** forwardVisibleLine #method:forwardVisibleLine#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardVisibleLineMethodInfo    ,
#endif
    textIterForwardVisibleLine              ,


-- ** forwardVisibleLines #method:forwardVisibleLines#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardVisibleLinesMethodInfo   ,
#endif
    textIterForwardVisibleLines             ,


-- ** forwardVisibleWordEnd #method:forwardVisibleWordEnd#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardVisibleWordEndMethodInfo ,
#endif
    textIterForwardVisibleWordEnd           ,


-- ** forwardVisibleWordEnds #method:forwardVisibleWordEnds#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardVisibleWordEndsMethodInfo,
#endif
    textIterForwardVisibleWordEnds          ,


-- ** forwardWordEnd #method:forwardWordEnd#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardWordEndMethodInfo        ,
#endif
    textIterForwardWordEnd                  ,


-- ** forwardWordEnds #method:forwardWordEnds#

#if defined(ENABLE_OVERLOADING)
    TextIterForwardWordEndsMethodInfo       ,
#endif
    textIterForwardWordEnds                 ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    TextIterFreeMethodInfo                  ,
#endif
    textIterFree                            ,


-- ** getAttributes #method:getAttributes#

#if defined(ENABLE_OVERLOADING)
    TextIterGetAttributesMethodInfo         ,
#endif
    textIterGetAttributes                   ,


-- ** getBuffer #method:getBuffer#

#if defined(ENABLE_OVERLOADING)
    TextIterGetBufferMethodInfo             ,
#endif
    textIterGetBuffer                       ,


-- ** getBytesInLine #method:getBytesInLine#

#if defined(ENABLE_OVERLOADING)
    TextIterGetBytesInLineMethodInfo        ,
#endif
    textIterGetBytesInLine                  ,


-- ** getChar #method:getChar#

#if defined(ENABLE_OVERLOADING)
    TextIterGetCharMethodInfo               ,
#endif
    textIterGetChar                         ,


-- ** getCharsInLine #method:getCharsInLine#

#if defined(ENABLE_OVERLOADING)
    TextIterGetCharsInLineMethodInfo        ,
#endif
    textIterGetCharsInLine                  ,


-- ** getChildAnchor #method:getChildAnchor#

#if defined(ENABLE_OVERLOADING)
    TextIterGetChildAnchorMethodInfo        ,
#endif
    textIterGetChildAnchor                  ,


-- ** getLanguage #method:getLanguage#

#if defined(ENABLE_OVERLOADING)
    TextIterGetLanguageMethodInfo           ,
#endif
    textIterGetLanguage                     ,


-- ** getLine #method:getLine#

#if defined(ENABLE_OVERLOADING)
    TextIterGetLineMethodInfo               ,
#endif
    textIterGetLine                         ,


-- ** getLineIndex #method:getLineIndex#

#if defined(ENABLE_OVERLOADING)
    TextIterGetLineIndexMethodInfo          ,
#endif
    textIterGetLineIndex                    ,


-- ** getLineOffset #method:getLineOffset#

#if defined(ENABLE_OVERLOADING)
    TextIterGetLineOffsetMethodInfo         ,
#endif
    textIterGetLineOffset                   ,


-- ** getMarks #method:getMarks#

#if defined(ENABLE_OVERLOADING)
    TextIterGetMarksMethodInfo              ,
#endif
    textIterGetMarks                        ,


-- ** getOffset #method:getOffset#

#if defined(ENABLE_OVERLOADING)
    TextIterGetOffsetMethodInfo             ,
#endif
    textIterGetOffset                       ,


-- ** getPixbuf #method:getPixbuf#

#if defined(ENABLE_OVERLOADING)
    TextIterGetPixbufMethodInfo             ,
#endif
    textIterGetPixbuf                       ,


-- ** getSlice #method:getSlice#

#if defined(ENABLE_OVERLOADING)
    TextIterGetSliceMethodInfo              ,
#endif
    textIterGetSlice                        ,


-- ** getTags #method:getTags#

#if defined(ENABLE_OVERLOADING)
    TextIterGetTagsMethodInfo               ,
#endif
    textIterGetTags                         ,


-- ** getText #method:getText#

#if defined(ENABLE_OVERLOADING)
    TextIterGetTextMethodInfo               ,
#endif
    textIterGetText                         ,


-- ** getToggledTags #method:getToggledTags#

#if defined(ENABLE_OVERLOADING)
    TextIterGetToggledTagsMethodInfo        ,
#endif
    textIterGetToggledTags                  ,


-- ** getVisibleLineIndex #method:getVisibleLineIndex#

#if defined(ENABLE_OVERLOADING)
    TextIterGetVisibleLineIndexMethodInfo   ,
#endif
    textIterGetVisibleLineIndex             ,


-- ** getVisibleLineOffset #method:getVisibleLineOffset#

#if defined(ENABLE_OVERLOADING)
    TextIterGetVisibleLineOffsetMethodInfo  ,
#endif
    textIterGetVisibleLineOffset            ,


-- ** getVisibleSlice #method:getVisibleSlice#

#if defined(ENABLE_OVERLOADING)
    TextIterGetVisibleSliceMethodInfo       ,
#endif
    textIterGetVisibleSlice                 ,


-- ** getVisibleText #method:getVisibleText#

#if defined(ENABLE_OVERLOADING)
    TextIterGetVisibleTextMethodInfo        ,
#endif
    textIterGetVisibleText                  ,


-- ** hasTag #method:hasTag#

#if defined(ENABLE_OVERLOADING)
    TextIterHasTagMethodInfo                ,
#endif
    textIterHasTag                          ,


-- ** inRange #method:inRange#

#if defined(ENABLE_OVERLOADING)
    TextIterInRangeMethodInfo               ,
#endif
    textIterInRange                         ,


-- ** insideSentence #method:insideSentence#

#if defined(ENABLE_OVERLOADING)
    TextIterInsideSentenceMethodInfo        ,
#endif
    textIterInsideSentence                  ,


-- ** insideWord #method:insideWord#

#if defined(ENABLE_OVERLOADING)
    TextIterInsideWordMethodInfo            ,
#endif
    textIterInsideWord                      ,


-- ** isCursorPosition #method:isCursorPosition#

#if defined(ENABLE_OVERLOADING)
    TextIterIsCursorPositionMethodInfo      ,
#endif
    textIterIsCursorPosition                ,


-- ** isEnd #method:isEnd#

#if defined(ENABLE_OVERLOADING)
    TextIterIsEndMethodInfo                 ,
#endif
    textIterIsEnd                           ,


-- ** isStart #method:isStart#

#if defined(ENABLE_OVERLOADING)
    TextIterIsStartMethodInfo               ,
#endif
    textIterIsStart                         ,


-- ** order #method:order#

#if defined(ENABLE_OVERLOADING)
    TextIterOrderMethodInfo                 ,
#endif
    textIterOrder                           ,


-- ** setLine #method:setLine#

#if defined(ENABLE_OVERLOADING)
    TextIterSetLineMethodInfo               ,
#endif
    textIterSetLine                         ,


-- ** setLineIndex #method:setLineIndex#

#if defined(ENABLE_OVERLOADING)
    TextIterSetLineIndexMethodInfo          ,
#endif
    textIterSetLineIndex                    ,


-- ** setLineOffset #method:setLineOffset#

#if defined(ENABLE_OVERLOADING)
    TextIterSetLineOffsetMethodInfo         ,
#endif
    textIterSetLineOffset                   ,


-- ** setOffset #method:setOffset#

#if defined(ENABLE_OVERLOADING)
    TextIterSetOffsetMethodInfo             ,
#endif
    textIterSetOffset                       ,


-- ** setVisibleLineIndex #method:setVisibleLineIndex#

#if defined(ENABLE_OVERLOADING)
    TextIterSetVisibleLineIndexMethodInfo   ,
#endif
    textIterSetVisibleLineIndex             ,


-- ** setVisibleLineOffset #method:setVisibleLineOffset#

#if defined(ENABLE_OVERLOADING)
    TextIterSetVisibleLineOffsetMethodInfo  ,
#endif
    textIterSetVisibleLineOffset            ,


-- ** startsLine #method:startsLine#

#if defined(ENABLE_OVERLOADING)
    TextIterStartsLineMethodInfo            ,
#endif
    textIterStartsLine                      ,


-- ** startsSentence #method:startsSentence#

#if defined(ENABLE_OVERLOADING)
    TextIterStartsSentenceMethodInfo        ,
#endif
    textIterStartsSentence                  ,


-- ** startsTag #method:startsTag#

#if defined(ENABLE_OVERLOADING)
    TextIterStartsTagMethodInfo             ,
#endif
    textIterStartsTag                       ,


-- ** startsWord #method:startsWord#

#if defined(ENABLE_OVERLOADING)
    TextIterStartsWordMethodInfo            ,
#endif
    textIterStartsWord                      ,


-- ** togglesTag #method:togglesTag#

#if defined(ENABLE_OVERLOADING)
    TextIterTogglesTagMethodInfo            ,
#endif
    textIterTogglesTag                      ,




    ) 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 qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextBuffer as Gtk.TextBuffer
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextChildAnchor as Gtk.TextChildAnchor
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextMark as Gtk.TextMark
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextTag as Gtk.TextTag
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextAttributes as Gtk.TextAttributes
import qualified GI.Pango.Structs.Language as Pango.Language

-- | Memory-managed wrapper type.
newtype TextIter = TextIter (ManagedPtr TextIter)
    deriving (TextIter -> TextIter -> Bool
(TextIter -> TextIter -> Bool)
-> (TextIter -> TextIter -> Bool) -> Eq TextIter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextIter -> TextIter -> Bool
$c/= :: TextIter -> TextIter -> Bool
== :: TextIter -> TextIter -> Bool
$c== :: TextIter -> TextIter -> Bool
Eq)
foreign import ccall "gtk_text_iter_get_type" c_gtk_text_iter_get_type :: 
    IO GType

instance BoxedObject TextIter where
    boxedType :: TextIter -> IO GType
boxedType _ = IO GType
c_gtk_text_iter_get_type

-- | Convert 'TextIter' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue TextIter where
    toGValue :: TextIter -> IO GValue
toGValue o :: TextIter
o = do
        GType
gtype <- IO GType
c_gtk_text_iter_get_type
        TextIter -> (Ptr TextIter -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TextIter
o (GType
-> (GValue -> Ptr TextIter -> IO ()) -> Ptr TextIter -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TextIter -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO TextIter
fromGValue gv :: GValue
gv = do
        Ptr TextIter
ptr <- GValue -> IO (Ptr TextIter)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr TextIter)
        (ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr TextIter -> TextIter
TextIter Ptr TextIter
ptr
        
    

-- | Construct a `TextIter` struct initialized to zero.
newZeroTextIter :: MonadIO m => m TextIter
newZeroTextIter :: m TextIter
newZeroTextIter = IO TextIter -> m TextIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextIter -> m TextIter) -> IO TextIter -> m TextIter
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr TextIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 80 IO (Ptr TextIter) -> (Ptr TextIter -> IO TextIter) -> IO TextIter
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
TextIter

instance tag ~ 'AttrSet => Constructible TextIter tag where
    new :: (ManagedPtr TextIter -> TextIter)
-> [AttrOp TextIter tag] -> m TextIter
new _ attrs :: [AttrOp TextIter tag]
attrs = do
        TextIter
o <- m TextIter
forall (m :: * -> *). MonadIO m => m TextIter
newZeroTextIter
        TextIter -> [AttrOp TextIter 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TextIter
o [AttrOp TextIter tag]
[AttrOp TextIter 'AttrSet]
attrs
        TextIter -> m TextIter
forall (m :: * -> *) a. Monad m => a -> m a
return TextIter
o


-- | A convenience alias for `Nothing` :: `Maybe` `TextIter`.
noTextIter :: Maybe TextIter
noTextIter :: Maybe TextIter
noTextIter = Maybe TextIter
forall a. Maybe a
Nothing


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

-- method TextIter::assign
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "other"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GtkTextIter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_assign" gtk_text_iter_assign :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr TextIter ->                         -- other : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO ()

-- | Assigns the value of /@other@/ to /@iter@/.  This function
-- is not useful in applications, because iterators can be assigned
-- with @GtkTextIter i = j;@. The
-- function is used by language bindings.
-- 
-- /Since: 3.2/
textIterAssign ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> TextIter
    -- ^ /@other@/: another t'GI.Gtk.Structs.TextIter.TextIter'
    -> m ()
textIterAssign :: TextIter -> TextIter -> m ()
textIterAssign iter :: TextIter
iter other :: TextIter
other = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextIter
other' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
other
    Ptr TextIter -> Ptr TextIter -> IO ()
gtk_text_iter_assign Ptr TextIter
iter' Ptr TextIter
other'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
other
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TextIterAssignMethodInfo
instance (signature ~ (TextIter -> m ()), MonadIO m) => O.MethodInfo TextIterAssignMethodInfo TextIter signature where
    overloadedMethod = textIterAssign

#endif

-- method TextIter::backward_char
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_backward_char" gtk_text_iter_backward_char :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves backward by one character offset. Returns 'P.True' if movement
-- was possible; if /@iter@/ was the first in the buffer (character
-- offset 0), 'GI.Gtk.Structs.TextIter.textIterBackwardChar' returns 'P.False' for convenience when
-- writing loops.
textIterBackwardChar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Bool
    -- ^ __Returns:__ whether movement was possible
textIterBackwardChar :: TextIter -> m Bool
textIterBackwardChar iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_backward_char Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardCharMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterBackwardCharMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardChar

#endif

-- method TextIter::backward_chars
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of characters to move"
--                 , 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 "gtk_text_iter_backward_chars" gtk_text_iter_backward_chars :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves /@count@/ characters backward, if possible (if /@count@/ would move
-- past the start or end of the buffer, moves to the start or end of
-- the buffer).  The return value indicates whether the iterator moved
-- onto a dereferenceable position; if the iterator didn’t move, or
-- moved onto the end iterator, then 'P.False' is returned. If /@count@/ is 0,
-- the function does nothing and returns 'P.False'.
textIterBackwardChars ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> Int32
    -- ^ /@count@/: number of characters to move
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved and is dereferenceable
textIterBackwardChars :: TextIter -> Int32 -> m Bool
textIterBackwardChars iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_backward_chars Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardCharsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardCharsMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardChars

#endif

-- method TextIter::backward_cursor_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_backward_cursor_position" gtk_text_iter_backward_cursor_position :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Like 'GI.Gtk.Structs.TextIter.textIterForwardCursorPosition', but moves backward.
textIterBackwardCursorPosition ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved
textIterBackwardCursorPosition :: TextIter -> m Bool
textIterBackwardCursorPosition iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_backward_cursor_position Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardCursorPositionMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterBackwardCursorPositionMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardCursorPosition

#endif

-- method TextIter::backward_cursor_positions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of positions to move"
--                 , 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 "gtk_text_iter_backward_cursor_positions" gtk_text_iter_backward_cursor_positions :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves up to /@count@/ cursor positions. See
-- 'GI.Gtk.Structs.TextIter.textIterForwardCursorPosition' for details.
textIterBackwardCursorPositions ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of positions to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved and the new position is dereferenceable
textIterBackwardCursorPositions :: TextIter -> Int32 -> m Bool
textIterBackwardCursorPositions iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_backward_cursor_positions Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardCursorPositionsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardCursorPositionsMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardCursorPositions

#endif

-- method TextIter::backward_find_char
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pred"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextCharPredicate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "function to be called on each character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data for @pred"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "limit"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "search limit, or %NULL for none"
--                 , 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 "gtk_text_iter_backward_find_char" gtk_text_iter_backward_find_char :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    FunPtr Gtk.Callbacks.C_TextCharPredicate -> -- pred : TInterface (Name {namespace = "Gtk", name = "TextCharPredicate"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    Ptr TextIter ->                         -- limit : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Same as 'GI.Gtk.Structs.TextIter.textIterForwardFindChar', but goes backward from /@iter@/.
textIterBackwardFindChar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Gtk.Callbacks.TextCharPredicate
    -- ^ /@pred@/: function to be called on each character
    -> Maybe (TextIter)
    -- ^ /@limit@/: search limit, or 'P.Nothing' for none
    -> m Bool
    -- ^ __Returns:__ whether a match was found
textIterBackwardFindChar :: TextIter -> TextCharPredicate -> Maybe TextIter -> m Bool
textIterBackwardFindChar iter :: TextIter
iter pred :: TextCharPredicate
pred limit :: Maybe TextIter
limit = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    FunPtr C_TextCharPredicate
pred' <- C_TextCharPredicate -> IO (FunPtr C_TextCharPredicate)
Gtk.Callbacks.mk_TextCharPredicate (Maybe (Ptr (FunPtr C_TextCharPredicate))
-> TextCharPredicate_WithClosures -> C_TextCharPredicate
Gtk.Callbacks.wrap_TextCharPredicate Maybe (Ptr (FunPtr C_TextCharPredicate))
forall a. Maybe a
Nothing (TextCharPredicate -> TextCharPredicate_WithClosures
Gtk.Callbacks.drop_closures_TextCharPredicate TextCharPredicate
pred))
    Ptr TextIter
maybeLimit <- case Maybe TextIter
limit of
        Nothing -> Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
forall a. Ptr a
nullPtr
        Just jLimit :: TextIter
jLimit -> do
            Ptr TextIter
jLimit' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
jLimit
            Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
jLimit'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    CInt
result <- Ptr TextIter
-> FunPtr C_TextCharPredicate -> Ptr () -> Ptr TextIter -> IO CInt
gtk_text_iter_backward_find_char Ptr TextIter
iter' FunPtr C_TextCharPredicate
pred' Ptr ()
forall a. Ptr a
userData Ptr TextIter
maybeLimit
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_TextCharPredicate -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_TextCharPredicate
pred'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Maybe TextIter -> (TextIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TextIter
limit TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardFindCharMethodInfo
instance (signature ~ (Gtk.Callbacks.TextCharPredicate -> Maybe (TextIter) -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardFindCharMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardFindChar

#endif

-- method TextIter::backward_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_backward_line" gtk_text_iter_backward_line :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves /@iter@/ to the start of the previous line. Returns 'P.True' if
-- /@iter@/ could be moved; i.e. if /@iter@/ was at character offset 0, this
-- function returns 'P.False'. Therefore if /@iter@/ was already on line 0,
-- but not at the start of the line, /@iter@/ is snapped to the start of
-- the line and the function returns 'P.True'. (Note that this implies that
-- in a loop calling this function, the line number may not change on
-- every iteration, if your first iteration is on line 0.)
textIterBackwardLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved
textIterBackwardLine :: TextIter -> m Bool
textIterBackwardLine iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_backward_line Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardLineMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterBackwardLineMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardLine

#endif

-- method TextIter::backward_lines
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of lines to move backward"
--                 , 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 "gtk_text_iter_backward_lines" gtk_text_iter_backward_lines :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves /@count@/ lines backward, if possible (if /@count@/ would move
-- past the start or end of the buffer, moves to the start or end of
-- the buffer).  The return value indicates whether the iterator moved
-- onto a dereferenceable position; if the iterator didn’t move, or
-- moved onto the end iterator, then 'P.False' is returned. If /@count@/ is 0,
-- the function does nothing and returns 'P.False'. If /@count@/ is negative,
-- moves forward by 0 - /@count@/ lines.
textIterBackwardLines ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of lines to move backward
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved and is dereferenceable
textIterBackwardLines :: TextIter -> Int32 -> m Bool
textIterBackwardLines iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_backward_lines Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardLinesMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardLinesMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardLines

#endif

-- method TextIter::backward_search
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter where the search begins"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "str"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "search string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextSearchFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "bitmask of flags affecting the search"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "match_start"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for start of match, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "match_end"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for end of match, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "limit"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location of last possible @match_start, or %NULL for start of buffer"
--                 , 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 "gtk_text_iter_backward_search" gtk_text_iter_backward_search :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    CString ->                              -- str : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "TextSearchFlags"})
    Ptr TextIter ->                         -- match_start : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr TextIter ->                         -- match_end : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr TextIter ->                         -- limit : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Same as 'GI.Gtk.Structs.TextIter.textIterForwardSearch', but moves backward.
-- 
-- /@matchEnd@/ will never be set to a t'GI.Gtk.Structs.TextIter.TextIter' located after /@iter@/, even if
-- there is a possible /@matchStart@/ before or at /@iter@/.
textIterBackwardSearch ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter' where the search begins
    -> T.Text
    -- ^ /@str@/: search string
    -> [Gtk.Flags.TextSearchFlags]
    -- ^ /@flags@/: bitmask of flags affecting the search
    -> Maybe (TextIter)
    -- ^ /@limit@/: location of last possible /@matchStart@/, or 'P.Nothing' for start of buffer
    -> m ((Bool, TextIter, TextIter))
    -- ^ __Returns:__ whether a match was found
textIterBackwardSearch :: TextIter
-> Text
-> [TextSearchFlags]
-> Maybe TextIter
-> m (Bool, TextIter, TextIter)
textIterBackwardSearch iter :: TextIter
iter str :: Text
str flags :: [TextSearchFlags]
flags limit :: Maybe TextIter
limit = IO (Bool, TextIter, TextIter) -> m (Bool, TextIter, TextIter)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, TextIter, TextIter) -> m (Bool, TextIter, TextIter))
-> IO (Bool, TextIter, TextIter) -> m (Bool, TextIter, TextIter)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CString
str' <- Text -> IO CString
textToCString Text
str
    let flags' :: CUInt
flags' = [TextSearchFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TextSearchFlags]
flags
    Ptr TextIter
matchStart <- Int -> IO (Ptr TextIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 80 :: IO (Ptr TextIter)
    Ptr TextIter
matchEnd <- Int -> IO (Ptr TextIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 80 :: IO (Ptr TextIter)
    Ptr TextIter
maybeLimit <- case Maybe TextIter
limit of
        Nothing -> Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
forall a. Ptr a
nullPtr
        Just jLimit :: TextIter
jLimit -> do
            Ptr TextIter
jLimit' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
jLimit
            Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
jLimit'
    CInt
result <- Ptr TextIter
-> CString
-> CUInt
-> Ptr TextIter
-> Ptr TextIter
-> Ptr TextIter
-> IO CInt
gtk_text_iter_backward_search Ptr TextIter
iter' CString
str' CUInt
flags' Ptr TextIter
matchStart Ptr TextIter
matchEnd Ptr TextIter
maybeLimit
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter
matchStart' <- ((ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
TextIter) Ptr TextIter
matchStart
    TextIter
matchEnd' <- ((ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
TextIter) Ptr TextIter
matchEnd
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Maybe TextIter -> (TextIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TextIter
limit TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    (Bool, TextIter, TextIter) -> IO (Bool, TextIter, TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', TextIter
matchStart', TextIter
matchEnd')

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardSearchMethodInfo
instance (signature ~ (T.Text -> [Gtk.Flags.TextSearchFlags] -> Maybe (TextIter) -> m ((Bool, TextIter, TextIter))), MonadIO m) => O.MethodInfo TextIterBackwardSearchMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardSearch

#endif

-- method TextIter::backward_sentence_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_backward_sentence_start" gtk_text_iter_backward_sentence_start :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves backward to the previous sentence start; if /@iter@/ is already at
-- the start of a sentence, moves backward to the next one.  Sentence
-- boundaries are determined by Pango and should be correct for nearly
-- any language (if not, the correct fix would be to the Pango text
-- boundary algorithms).
textIterBackwardSentenceStart ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterBackwardSentenceStart :: TextIter -> m Bool
textIterBackwardSentenceStart iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_backward_sentence_start Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardSentenceStartMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterBackwardSentenceStartMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardSentenceStart

#endif

-- method TextIter::backward_sentence_starts
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of sentences to move"
--                 , 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 "gtk_text_iter_backward_sentence_starts" gtk_text_iter_backward_sentence_starts :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Calls 'GI.Gtk.Structs.TextIter.textIterBackwardSentenceStart' up to /@count@/ times,
-- or until it returns 'P.False'. If /@count@/ is negative, moves forward
-- instead of backward.
textIterBackwardSentenceStarts ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of sentences to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterBackwardSentenceStarts :: TextIter -> Int32 -> m Bool
textIterBackwardSentenceStarts iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_backward_sentence_starts Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardSentenceStartsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardSentenceStartsMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardSentenceStarts

#endif

-- method TextIter::backward_to_tag_toggle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tag"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextTag" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextTag, or %NULL"
--                 , 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 "gtk_text_iter_backward_to_tag_toggle" gtk_text_iter_backward_to_tag_toggle :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr Gtk.TextTag.TextTag ->              -- tag : TInterface (Name {namespace = "Gtk", name = "TextTag"})
    IO CInt

-- | Moves backward to the next toggle (on or off) of the
-- t'GI.Gtk.Objects.TextTag.TextTag' /@tag@/, or to the next toggle of any tag if
-- /@tag@/ is 'P.Nothing'. If no matching tag toggles are found,
-- returns 'P.False', otherwise 'P.True'. Does not return toggles
-- located at /@iter@/, only toggles before /@iter@/. Sets /@iter@/
-- to the location of the toggle, or the start of the buffer
-- if no toggle is found.
textIterBackwardToTagToggle ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.TextTag.IsTextTag a) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Maybe (a)
    -- ^ /@tag@/: a t'GI.Gtk.Objects.TextTag.TextTag', or 'P.Nothing'
    -> m Bool
    -- ^ __Returns:__ whether we found a tag toggle before /@iter@/
textIterBackwardToTagToggle :: TextIter -> Maybe a -> m Bool
textIterBackwardToTagToggle iter :: TextIter
iter tag :: Maybe a
tag = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextTag
maybeTag <- case Maybe a
tag of
        Nothing -> Ptr TextTag -> IO (Ptr TextTag)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextTag
forall a. Ptr a
nullPtr
        Just jTag :: a
jTag -> do
            Ptr TextTag
jTag' <- a -> IO (Ptr TextTag)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jTag
            Ptr TextTag -> IO (Ptr TextTag)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextTag
jTag'
    CInt
result <- Ptr TextIter -> Ptr TextTag -> IO CInt
gtk_text_iter_backward_to_tag_toggle Ptr TextIter
iter' Ptr TextTag
maybeTag
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
tag a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardToTagToggleMethodInfo
instance (signature ~ (Maybe (a) -> m Bool), MonadIO m, Gtk.TextTag.IsTextTag a) => O.MethodInfo TextIterBackwardToTagToggleMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardToTagToggle

#endif

-- method TextIter::backward_visible_cursor_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_backward_visible_cursor_position" gtk_text_iter_backward_visible_cursor_position :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves /@iter@/ forward to the previous visible cursor position. See
-- 'GI.Gtk.Structs.TextIter.textIterBackwardCursorPosition' for details.
-- 
-- /Since: 2.4/
textIterBackwardVisibleCursorPosition ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved and the new position is dereferenceable
textIterBackwardVisibleCursorPosition :: TextIter -> m Bool
textIterBackwardVisibleCursorPosition iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_backward_visible_cursor_position Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardVisibleCursorPositionMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterBackwardVisibleCursorPositionMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardVisibleCursorPosition

#endif

-- method TextIter::backward_visible_cursor_positions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of positions to move"
--                 , 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 "gtk_text_iter_backward_visible_cursor_positions" gtk_text_iter_backward_visible_cursor_positions :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves up to /@count@/ visible cursor positions. See
-- 'GI.Gtk.Structs.TextIter.textIterBackwardCursorPosition' for details.
-- 
-- /Since: 2.4/
textIterBackwardVisibleCursorPositions ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of positions to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved and the new position is dereferenceable
textIterBackwardVisibleCursorPositions :: TextIter -> Int32 -> m Bool
textIterBackwardVisibleCursorPositions iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_backward_visible_cursor_positions Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardVisibleCursorPositionsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardVisibleCursorPositionsMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardVisibleCursorPositions

#endif

-- method TextIter::backward_visible_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_backward_visible_line" gtk_text_iter_backward_visible_line :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves /@iter@/ to the start of the previous visible line. Returns 'P.True' if
-- /@iter@/ could be moved; i.e. if /@iter@/ was at character offset 0, this
-- function returns 'P.False'. Therefore if /@iter@/ was already on line 0,
-- but not at the start of the line, /@iter@/ is snapped to the start of
-- the line and the function returns 'P.True'. (Note that this implies that
-- in a loop calling this function, the line number may not change on
-- every iteration, if your first iteration is on line 0.)
-- 
-- /Since: 2.8/
textIterBackwardVisibleLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved
textIterBackwardVisibleLine :: TextIter -> m Bool
textIterBackwardVisibleLine iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_backward_visible_line Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardVisibleLineMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterBackwardVisibleLineMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardVisibleLine

#endif

-- method TextIter::backward_visible_lines
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of lines to move backward"
--                 , 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 "gtk_text_iter_backward_visible_lines" gtk_text_iter_backward_visible_lines :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves /@count@/ visible lines backward, if possible (if /@count@/ would move
-- past the start or end of the buffer, moves to the start or end of
-- the buffer).  The return value indicates whether the iterator moved
-- onto a dereferenceable position; if the iterator didn’t move, or
-- moved onto the end iterator, then 'P.False' is returned. If /@count@/ is 0,
-- the function does nothing and returns 'P.False'. If /@count@/ is negative,
-- moves forward by 0 - /@count@/ lines.
-- 
-- /Since: 2.8/
textIterBackwardVisibleLines ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of lines to move backward
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved and is dereferenceable
textIterBackwardVisibleLines :: TextIter -> Int32 -> m Bool
textIterBackwardVisibleLines iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_backward_visible_lines Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardVisibleLinesMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardVisibleLinesMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardVisibleLines

#endif

-- method TextIter::backward_visible_word_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_backward_visible_word_start" gtk_text_iter_backward_visible_word_start :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves backward to the previous visible word start. (If /@iter@/ is currently
-- on a word start, moves backward to the next one after that.) Word breaks
-- are determined by Pango and should be correct for nearly any
-- language (if not, the correct fix would be to the Pango word break
-- algorithms).
-- 
-- /Since: 2.4/
textIterBackwardVisibleWordStart ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterBackwardVisibleWordStart :: TextIter -> m Bool
textIterBackwardVisibleWordStart iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_backward_visible_word_start Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardVisibleWordStartMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterBackwardVisibleWordStartMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardVisibleWordStart

#endif

-- method TextIter::backward_visible_word_starts
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of times to move"
--                 , 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 "gtk_text_iter_backward_visible_word_starts" gtk_text_iter_backward_visible_word_starts :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Calls 'GI.Gtk.Structs.TextIter.textIterBackwardVisibleWordStart' up to /@count@/ times.
-- 
-- /Since: 2.4/
textIterBackwardVisibleWordStarts ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of times to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterBackwardVisibleWordStarts :: TextIter -> Int32 -> m Bool
textIterBackwardVisibleWordStarts iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_backward_visible_word_starts Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardVisibleWordStartsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardVisibleWordStartsMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardVisibleWordStarts

#endif

-- method TextIter::backward_word_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_backward_word_start" gtk_text_iter_backward_word_start :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves backward to the previous word start. (If /@iter@/ is currently on a
-- word start, moves backward to the next one after that.) Word breaks
-- are determined by Pango and should be correct for nearly any
-- language (if not, the correct fix would be to the Pango word break
-- algorithms).
textIterBackwardWordStart ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterBackwardWordStart :: TextIter -> m Bool
textIterBackwardWordStart iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_backward_word_start Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardWordStartMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterBackwardWordStartMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardWordStart

#endif

-- method TextIter::backward_word_starts
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of times to move"
--                 , 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 "gtk_text_iter_backward_word_starts" gtk_text_iter_backward_word_starts :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Calls 'GI.Gtk.Structs.TextIter.textIterBackwardWordStart' up to /@count@/ times.
textIterBackwardWordStarts ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of times to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterBackwardWordStarts :: TextIter -> Int32 -> m Bool
textIterBackwardWordStarts iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_backward_word_starts Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBackwardWordStartsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterBackwardWordStartsMethodInfo TextIter signature where
    overloadedMethod = textIterBackwardWordStarts

#endif

-- method TextIter::begins_tag
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tag"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextTag" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextTag, or %NULL"
--                 , 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 "gtk_text_iter_begins_tag" gtk_text_iter_begins_tag :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr Gtk.TextTag.TextTag ->              -- tag : TInterface (Name {namespace = "Gtk", name = "TextTag"})
    IO CInt

{-# DEPRECATED textIterBeginsTag ["(Since version 3.20)","Use 'GI.Gtk.Structs.TextIter.textIterStartsTag' instead."] #-}
-- | Returns 'P.True' if /@tag@/ is toggled on at exactly this point. If /@tag@/
-- is 'P.Nothing', returns 'P.True' if any tag is toggled on at this point.
-- 
-- Note that if 'GI.Gtk.Structs.TextIter.textIterBeginsTag' returns 'P.True', it means that /@iter@/ is
-- at the beginning of the tagged range, and that the
-- character at /@iter@/ is inside the tagged range. In other
-- words, unlike 'GI.Gtk.Structs.TextIter.textIterEndsTag', if 'GI.Gtk.Structs.TextIter.textIterBeginsTag' returns
-- 'P.True', 'GI.Gtk.Structs.TextIter.textIterHasTag' will also return 'P.True' for the same
-- parameters.
textIterBeginsTag ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.TextTag.IsTextTag a) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> Maybe (a)
    -- ^ /@tag@/: a t'GI.Gtk.Objects.TextTag.TextTag', or 'P.Nothing'
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ is the start of a range tagged with /@tag@/
textIterBeginsTag :: TextIter -> Maybe a -> m Bool
textIterBeginsTag iter :: TextIter
iter tag :: Maybe a
tag = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextTag
maybeTag <- case Maybe a
tag of
        Nothing -> Ptr TextTag -> IO (Ptr TextTag)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextTag
forall a. Ptr a
nullPtr
        Just jTag :: a
jTag -> do
            Ptr TextTag
jTag' <- a -> IO (Ptr TextTag)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jTag
            Ptr TextTag -> IO (Ptr TextTag)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextTag
jTag'
    CInt
result <- Ptr TextIter -> Ptr TextTag -> IO CInt
gtk_text_iter_begins_tag Ptr TextIter
iter' Ptr TextTag
maybeTag
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
tag a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterBeginsTagMethodInfo
instance (signature ~ (Maybe (a) -> m Bool), MonadIO m, Gtk.TextTag.IsTextTag a) => O.MethodInfo TextIterBeginsTagMethodInfo TextIter signature where
    overloadedMethod = textIterBeginsTag

#endif

-- method TextIter::can_insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "default_editability"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE if text is editable by default"
--                 , 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 "gtk_text_iter_can_insert" gtk_text_iter_can_insert :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    CInt ->                                 -- default_editability : TBasicType TBoolean
    IO CInt

-- | Considering the default editability of the buffer, and tags that
-- affect editability, determines whether text inserted at /@iter@/ would
-- be editable. If text inserted at /@iter@/ would be editable then the
-- user should be allowed to insert text at /@iter@/.
-- 'GI.Gtk.Objects.TextBuffer.textBufferInsertInteractive' uses this function to decide
-- whether insertions are allowed at a given position.
textIterCanInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> Bool
    -- ^ /@defaultEditability@/: 'P.True' if text is editable by default
    -> m Bool
    -- ^ __Returns:__ whether text inserted at /@iter@/ would be editable
textIterCanInsert :: TextIter -> Bool -> m Bool
textIterCanInsert iter :: TextIter
iter defaultEditability :: Bool
defaultEditability = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    let defaultEditability' :: CInt
defaultEditability' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
defaultEditability
    CInt
result <- Ptr TextIter -> CInt -> IO CInt
gtk_text_iter_can_insert Ptr TextIter
iter' CInt
defaultEditability'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterCanInsertMethodInfo
instance (signature ~ (Bool -> m Bool), MonadIO m) => O.MethodInfo TextIterCanInsertMethodInfo TextIter signature where
    overloadedMethod = textIterCanInsert

#endif

-- method TextIter::compare
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "lhs"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rhs"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GtkTextIter"
--                 , 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 "gtk_text_iter_compare" gtk_text_iter_compare :: 
    Ptr TextIter ->                         -- lhs : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr TextIter ->                         -- rhs : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO Int32

-- | A @/qsort()/@-style function that returns negative if /@lhs@/ is less than
-- /@rhs@/, positive if /@lhs@/ is greater than /@rhs@/, and 0 if they’re equal.
-- Ordering is in character offset order, i.e. the first character in the buffer
-- is less than the second character in the buffer.
textIterCompare ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@lhs@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> TextIter
    -- ^ /@rhs@/: another t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Int32
    -- ^ __Returns:__ -1 if /@lhs@/ is less than /@rhs@/, 1 if /@lhs@/ is greater, 0 if they are equal
textIterCompare :: TextIter -> TextIter -> m Int32
textIterCompare lhs :: TextIter
lhs rhs :: TextIter
rhs = 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 TextIter
lhs' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
lhs
    Ptr TextIter
rhs' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
rhs
    Int32
result <- Ptr TextIter -> Ptr TextIter -> IO Int32
gtk_text_iter_compare Ptr TextIter
lhs' Ptr TextIter
rhs'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
lhs
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
rhs
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextIterCompareMethodInfo
instance (signature ~ (TextIter -> m Int32), MonadIO m) => O.MethodInfo TextIterCompareMethodInfo TextIter signature where
    overloadedMethod = textIterCompare

#endif

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

foreign import ccall "gtk_text_iter_copy" gtk_text_iter_copy :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO (Ptr TextIter)

-- | Creates a dynamically-allocated copy of an iterator. This function
-- is not useful in applications, because iterators can be copied with a
-- simple assignment (@GtkTextIter i = j;@). The
-- function is used by language bindings.
textIterCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m TextIter
    -- ^ __Returns:__ a copy of the /@iter@/, free with 'GI.Gtk.Structs.TextIter.textIterFree'
textIterCopy :: TextIter -> m TextIter
textIterCopy iter :: TextIter
iter = IO TextIter -> m TextIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextIter -> m TextIter) -> IO TextIter -> m TextIter
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextIter
result <- Ptr TextIter -> IO (Ptr TextIter)
gtk_text_iter_copy Ptr TextIter
iter'
    Text -> Ptr TextIter -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textIterCopy" Ptr TextIter
result
    TextIter
result' <- ((ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
TextIter) Ptr TextIter
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    TextIter -> IO TextIter
forall (m :: * -> *) a. Monad m => a -> m a
return TextIter
result'

#if defined(ENABLE_OVERLOADING)
data TextIterCopyMethodInfo
instance (signature ~ (m TextIter), MonadIO m) => O.MethodInfo TextIterCopyMethodInfo TextIter signature where
    overloadedMethod = textIterCopy

#endif

-- method TextIter::editable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "default_setting"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE if text is editable by default"
--                 , 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 "gtk_text_iter_editable" gtk_text_iter_editable :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    CInt ->                                 -- default_setting : TBasicType TBoolean
    IO CInt

-- | Returns whether the character at /@iter@/ is within an editable region
-- of text.  Non-editable text is “locked” and can’t be changed by the
-- user via t'GI.Gtk.Objects.TextView.TextView'. This function is simply a convenience
-- wrapper around 'GI.Gtk.Structs.TextIter.textIterGetAttributes'. If no tags applied
-- to this text affect editability, /@defaultSetting@/ will be returned.
-- 
-- You don’t want to use this function to decide whether text can be
-- inserted at /@iter@/, because for insertion you don’t want to know
-- whether the char at /@iter@/ is inside an editable range, you want to
-- know whether a new character inserted at /@iter@/ would be inside an
-- editable range. Use 'GI.Gtk.Structs.TextIter.textIterCanInsert' to handle this
-- case.
textIterEditable ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> Bool
    -- ^ /@defaultSetting@/: 'P.True' if text is editable by default
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ is inside an editable range
textIterEditable :: TextIter -> Bool -> m Bool
textIterEditable iter :: TextIter
iter defaultSetting :: Bool
defaultSetting = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    let defaultSetting' :: CInt
defaultSetting' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
defaultSetting
    CInt
result <- Ptr TextIter -> CInt -> IO CInt
gtk_text_iter_editable Ptr TextIter
iter' CInt
defaultSetting'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterEditableMethodInfo
instance (signature ~ (Bool -> m Bool), MonadIO m) => O.MethodInfo TextIterEditableMethodInfo TextIter signature where
    overloadedMethod = textIterEditable

#endif

-- method TextIter::ends_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_ends_line" gtk_text_iter_ends_line :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Returns 'P.True' if /@iter@/ points to the start of the paragraph
-- delimiter characters for a line (delimiters will be either a
-- newline, a carriage return, a carriage return followed by a
-- newline, or a Unicode paragraph separator character). Note that an
-- iterator pointing to the \\n of a \\r\\n pair will not be counted as
-- the end of a line, the line ends before the \\r. The end iterator is
-- considered to be at the end of a line, even though there are no
-- paragraph delimiter chars there.
textIterEndsLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ is at the end of a line
textIterEndsLine :: TextIter -> m Bool
textIterEndsLine iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_ends_line Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterEndsLineMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterEndsLineMethodInfo TextIter signature where
    overloadedMethod = textIterEndsLine

#endif

-- method TextIter::ends_sentence
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_ends_sentence" gtk_text_iter_ends_sentence :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Determines whether /@iter@/ ends a sentence.  Sentence boundaries are
-- determined by Pango and should be correct for nearly any language
-- (if not, the correct fix would be to the Pango text boundary
-- algorithms).
textIterEndsSentence ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ is at the end of a sentence.
textIterEndsSentence :: TextIter -> m Bool
textIterEndsSentence iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_ends_sentence Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterEndsSentenceMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterEndsSentenceMethodInfo TextIter signature where
    overloadedMethod = textIterEndsSentence

#endif

-- method TextIter::ends_tag
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tag"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextTag" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextTag, or %NULL"
--                 , 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 "gtk_text_iter_ends_tag" gtk_text_iter_ends_tag :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr Gtk.TextTag.TextTag ->              -- tag : TInterface (Name {namespace = "Gtk", name = "TextTag"})
    IO CInt

-- | Returns 'P.True' if /@tag@/ is toggled off at exactly this point. If /@tag@/
-- is 'P.Nothing', returns 'P.True' if any tag is toggled off at this point.
-- 
-- Note that if 'GI.Gtk.Structs.TextIter.textIterEndsTag' returns 'P.True', it means that /@iter@/ is
-- at the end of the tagged range, but that the character
-- at /@iter@/ is outside the tagged range. In other words,
-- unlike 'GI.Gtk.Structs.TextIter.textIterStartsTag', if 'GI.Gtk.Structs.TextIter.textIterEndsTag' returns 'P.True',
-- 'GI.Gtk.Structs.TextIter.textIterHasTag' will return 'P.False' for the same parameters.
textIterEndsTag ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.TextTag.IsTextTag a) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> Maybe (a)
    -- ^ /@tag@/: a t'GI.Gtk.Objects.TextTag.TextTag', or 'P.Nothing'
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ is the end of a range tagged with /@tag@/
textIterEndsTag :: TextIter -> Maybe a -> m Bool
textIterEndsTag iter :: TextIter
iter tag :: Maybe a
tag = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextTag
maybeTag <- case Maybe a
tag of
        Nothing -> Ptr TextTag -> IO (Ptr TextTag)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextTag
forall a. Ptr a
nullPtr
        Just jTag :: a
jTag -> do
            Ptr TextTag
jTag' <- a -> IO (Ptr TextTag)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jTag
            Ptr TextTag -> IO (Ptr TextTag)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextTag
jTag'
    CInt
result <- Ptr TextIter -> Ptr TextTag -> IO CInt
gtk_text_iter_ends_tag Ptr TextIter
iter' Ptr TextTag
maybeTag
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
tag a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterEndsTagMethodInfo
instance (signature ~ (Maybe (a) -> m Bool), MonadIO m, Gtk.TextTag.IsTextTag a) => O.MethodInfo TextIterEndsTagMethodInfo TextIter signature where
    overloadedMethod = textIterEndsTag

#endif

-- method TextIter::ends_word
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_ends_word" gtk_text_iter_ends_word :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Determines whether /@iter@/ ends a natural-language word.  Word breaks
-- are determined by Pango and should be correct for nearly any
-- language (if not, the correct fix would be to the Pango word break
-- algorithms).
textIterEndsWord ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ is at the end of a word
textIterEndsWord :: TextIter -> m Bool
textIterEndsWord iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_ends_word Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterEndsWordMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterEndsWordMethodInfo TextIter signature where
    overloadedMethod = textIterEndsWord

#endif

-- method TextIter::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "lhs"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rhs"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GtkTextIter"
--                 , 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 "gtk_text_iter_equal" gtk_text_iter_equal :: 
    Ptr TextIter ->                         -- lhs : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr TextIter ->                         -- rhs : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Tests whether two iterators are equal, using the fastest possible
-- mechanism. This function is very fast; you can expect it to perform
-- better than e.g. getting the character offset for each iterator and
-- comparing the offsets yourself. Also, it’s a bit faster than
-- 'GI.Gtk.Structs.TextIter.textIterCompare'.
textIterEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@lhs@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> TextIter
    -- ^ /@rhs@/: another t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the iterators point to the same place in the buffer
textIterEqual :: TextIter -> TextIter -> m Bool
textIterEqual lhs :: TextIter
lhs rhs :: TextIter
rhs = 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 TextIter
lhs' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
lhs
    Ptr TextIter
rhs' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
rhs
    CInt
result <- Ptr TextIter -> Ptr TextIter -> IO CInt
gtk_text_iter_equal Ptr TextIter
lhs' Ptr TextIter
rhs'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
lhs
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
rhs
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterEqualMethodInfo
instance (signature ~ (TextIter -> m Bool), MonadIO m) => O.MethodInfo TextIterEqualMethodInfo TextIter signature where
    overloadedMethod = textIterEqual

#endif

-- method TextIter::forward_char
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_forward_char" gtk_text_iter_forward_char :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves /@iter@/ forward by one character offset. Note that images
-- embedded in the buffer occupy 1 character slot, so
-- 'GI.Gtk.Structs.TextIter.textIterForwardChar' may actually move onto an image instead
-- of a character, if you have images in your buffer.  If /@iter@/ is the
-- end iterator or one character before it, /@iter@/ will now point at
-- the end iterator, and 'GI.Gtk.Structs.TextIter.textIterForwardChar' returns 'P.False' for
-- convenience when writing loops.
textIterForwardChar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved and is dereferenceable
textIterForwardChar :: TextIter -> m Bool
textIterForwardChar iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_char Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardCharMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardCharMethodInfo TextIter signature where
    overloadedMethod = textIterForwardChar

#endif

-- method TextIter::forward_chars
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of characters to move, may be negative"
--                 , 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 "gtk_text_iter_forward_chars" gtk_text_iter_forward_chars :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves /@count@/ characters if possible (if /@count@/ would move past the
-- start or end of the buffer, moves to the start or end of the
-- buffer). The return value indicates whether the new position of
-- /@iter@/ is different from its original position, and dereferenceable
-- (the last iterator in the buffer is not dereferenceable). If /@count@/
-- is 0, the function does nothing and returns 'P.False'.
textIterForwardChars ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> Int32
    -- ^ /@count@/: number of characters to move, may be negative
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved and is dereferenceable
textIterForwardChars :: TextIter -> Int32 -> m Bool
textIterForwardChars iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_forward_chars Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardCharsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardCharsMethodInfo TextIter signature where
    overloadedMethod = textIterForwardChars

#endif

-- method TextIter::forward_cursor_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_forward_cursor_position" gtk_text_iter_forward_cursor_position :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves /@iter@/ forward by a single cursor position. Cursor positions
-- are (unsurprisingly) positions where the cursor can appear. Perhaps
-- surprisingly, there may not be a cursor position between all
-- characters. The most common example for European languages would be
-- a carriage return\/newline sequence. For some Unicode characters,
-- the equivalent of say the letter “a” with an accent mark will be
-- represented as two characters, first the letter then a \"combining
-- mark\" that causes the accent to be rendered; so the cursor can’t go
-- between those two characters. See also the t'GI.Pango.Structs.LogAttr.LogAttr'-struct and
-- 'GI.Pango.Functions.break' function.
textIterForwardCursorPosition ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved and the new position is dereferenceable
textIterForwardCursorPosition :: TextIter -> m Bool
textIterForwardCursorPosition iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_cursor_position Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardCursorPositionMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardCursorPositionMethodInfo TextIter signature where
    overloadedMethod = textIterForwardCursorPosition

#endif

-- method TextIter::forward_cursor_positions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of positions to move"
--                 , 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 "gtk_text_iter_forward_cursor_positions" gtk_text_iter_forward_cursor_positions :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves up to /@count@/ cursor positions. See
-- 'GI.Gtk.Structs.TextIter.textIterForwardCursorPosition' for details.
textIterForwardCursorPositions ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of positions to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved and the new position is dereferenceable
textIterForwardCursorPositions :: TextIter -> Int32 -> m Bool
textIterForwardCursorPositions iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_forward_cursor_positions Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardCursorPositionsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardCursorPositionsMethodInfo TextIter signature where
    overloadedMethod = textIterForwardCursorPositions

#endif

-- method TextIter::forward_find_char
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pred"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextCharPredicate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a function to be called on each character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data for @pred"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "limit"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "search limit, or %NULL for none"
--                 , 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 "gtk_text_iter_forward_find_char" gtk_text_iter_forward_find_char :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    FunPtr Gtk.Callbacks.C_TextCharPredicate -> -- pred : TInterface (Name {namespace = "Gtk", name = "TextCharPredicate"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    Ptr TextIter ->                         -- limit : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Advances /@iter@/, calling /@pred@/ on each character. If
-- /@pred@/ returns 'P.True', returns 'P.True' and stops scanning.
-- If /@pred@/ never returns 'P.True', /@iter@/ is set to /@limit@/ if
-- /@limit@/ is non-'P.Nothing', otherwise to the end iterator.
textIterForwardFindChar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Gtk.Callbacks.TextCharPredicate
    -- ^ /@pred@/: a function to be called on each character
    -> Maybe (TextIter)
    -- ^ /@limit@/: search limit, or 'P.Nothing' for none
    -> m Bool
    -- ^ __Returns:__ whether a match was found
textIterForwardFindChar :: TextIter -> TextCharPredicate -> Maybe TextIter -> m Bool
textIterForwardFindChar iter :: TextIter
iter pred :: TextCharPredicate
pred limit :: Maybe TextIter
limit = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    FunPtr C_TextCharPredicate
pred' <- C_TextCharPredicate -> IO (FunPtr C_TextCharPredicate)
Gtk.Callbacks.mk_TextCharPredicate (Maybe (Ptr (FunPtr C_TextCharPredicate))
-> TextCharPredicate_WithClosures -> C_TextCharPredicate
Gtk.Callbacks.wrap_TextCharPredicate Maybe (Ptr (FunPtr C_TextCharPredicate))
forall a. Maybe a
Nothing (TextCharPredicate -> TextCharPredicate_WithClosures
Gtk.Callbacks.drop_closures_TextCharPredicate TextCharPredicate
pred))
    Ptr TextIter
maybeLimit <- case Maybe TextIter
limit of
        Nothing -> Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
forall a. Ptr a
nullPtr
        Just jLimit :: TextIter
jLimit -> do
            Ptr TextIter
jLimit' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
jLimit
            Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
jLimit'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    CInt
result <- Ptr TextIter
-> FunPtr C_TextCharPredicate -> Ptr () -> Ptr TextIter -> IO CInt
gtk_text_iter_forward_find_char Ptr TextIter
iter' FunPtr C_TextCharPredicate
pred' Ptr ()
forall a. Ptr a
userData Ptr TextIter
maybeLimit
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_TextCharPredicate -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_TextCharPredicate
pred'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Maybe TextIter -> (TextIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TextIter
limit TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardFindCharMethodInfo
instance (signature ~ (Gtk.Callbacks.TextCharPredicate -> Maybe (TextIter) -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardFindCharMethodInfo TextIter signature where
    overloadedMethod = textIterForwardFindChar

#endif

-- method TextIter::forward_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_forward_line" gtk_text_iter_forward_line :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves /@iter@/ to the start of the next line. If the iter is already on the
-- last line of the buffer, moves the iter to the end of the current line.
-- If after the operation, the iter is at the end of the buffer and not
-- dereferencable, returns 'P.False'. Otherwise, returns 'P.True'.
textIterForwardLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ can be dereferenced
textIterForwardLine :: TextIter -> m Bool
textIterForwardLine iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_line Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardLineMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardLineMethodInfo TextIter signature where
    overloadedMethod = textIterForwardLine

#endif

-- method TextIter::forward_lines
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of lines to move forward"
--                 , 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 "gtk_text_iter_forward_lines" gtk_text_iter_forward_lines :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves /@count@/ lines forward, if possible (if /@count@/ would move
-- past the start or end of the buffer, moves to the start or end of
-- the buffer).  The return value indicates whether the iterator moved
-- onto a dereferenceable position; if the iterator didn’t move, or
-- moved onto the end iterator, then 'P.False' is returned. If /@count@/ is 0,
-- the function does nothing and returns 'P.False'. If /@count@/ is negative,
-- moves backward by 0 - /@count@/ lines.
textIterForwardLines ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of lines to move forward
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved and is dereferenceable
textIterForwardLines :: TextIter -> Int32 -> m Bool
textIterForwardLines iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_forward_lines Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardLinesMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardLinesMethodInfo TextIter signature where
    overloadedMethod = textIterForwardLines

#endif

-- method TextIter::forward_search
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "start of search" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "str"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a search string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextSearchFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags affecting how the search is done"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "match_start"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for start of match, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "match_end"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for end of match, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "limit"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location of last possible @match_end, or %NULL for the end of the buffer"
--                 , 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 "gtk_text_iter_forward_search" gtk_text_iter_forward_search :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    CString ->                              -- str : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "TextSearchFlags"})
    Ptr TextIter ->                         -- match_start : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr TextIter ->                         -- match_end : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr TextIter ->                         -- limit : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Searches forward for /@str@/. Any match is returned by setting
-- /@matchStart@/ to the first character of the match and /@matchEnd@/ to the
-- first character after the match. The search will not continue past
-- /@limit@/. Note that a search is a linear or O(n) operation, so you
-- may wish to use /@limit@/ to avoid locking up your UI on large
-- buffers.
-- 
-- /@matchStart@/ will never be set to a t'GI.Gtk.Structs.TextIter.TextIter' located before /@iter@/, even if
-- there is a possible /@matchEnd@/ after or at /@iter@/.
textIterForwardSearch ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: start of search
    -> T.Text
    -- ^ /@str@/: a search string
    -> [Gtk.Flags.TextSearchFlags]
    -- ^ /@flags@/: flags affecting how the search is done
    -> Maybe (TextIter)
    -- ^ /@limit@/: location of last possible /@matchEnd@/, or 'P.Nothing' for the end of the buffer
    -> m ((Bool, TextIter, TextIter))
    -- ^ __Returns:__ whether a match was found
textIterForwardSearch :: TextIter
-> Text
-> [TextSearchFlags]
-> Maybe TextIter
-> m (Bool, TextIter, TextIter)
textIterForwardSearch iter :: TextIter
iter str :: Text
str flags :: [TextSearchFlags]
flags limit :: Maybe TextIter
limit = IO (Bool, TextIter, TextIter) -> m (Bool, TextIter, TextIter)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, TextIter, TextIter) -> m (Bool, TextIter, TextIter))
-> IO (Bool, TextIter, TextIter) -> m (Bool, TextIter, TextIter)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CString
str' <- Text -> IO CString
textToCString Text
str
    let flags' :: CUInt
flags' = [TextSearchFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TextSearchFlags]
flags
    Ptr TextIter
matchStart <- Int -> IO (Ptr TextIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 80 :: IO (Ptr TextIter)
    Ptr TextIter
matchEnd <- Int -> IO (Ptr TextIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 80 :: IO (Ptr TextIter)
    Ptr TextIter
maybeLimit <- case Maybe TextIter
limit of
        Nothing -> Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
forall a. Ptr a
nullPtr
        Just jLimit :: TextIter
jLimit -> do
            Ptr TextIter
jLimit' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
jLimit
            Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
jLimit'
    CInt
result <- Ptr TextIter
-> CString
-> CUInt
-> Ptr TextIter
-> Ptr TextIter
-> Ptr TextIter
-> IO CInt
gtk_text_iter_forward_search Ptr TextIter
iter' CString
str' CUInt
flags' Ptr TextIter
matchStart Ptr TextIter
matchEnd Ptr TextIter
maybeLimit
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter
matchStart' <- ((ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
TextIter) Ptr TextIter
matchStart
    TextIter
matchEnd' <- ((ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
TextIter) Ptr TextIter
matchEnd
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Maybe TextIter -> (TextIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TextIter
limit TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    (Bool, TextIter, TextIter) -> IO (Bool, TextIter, TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', TextIter
matchStart', TextIter
matchEnd')

#if defined(ENABLE_OVERLOADING)
data TextIterForwardSearchMethodInfo
instance (signature ~ (T.Text -> [Gtk.Flags.TextSearchFlags] -> Maybe (TextIter) -> m ((Bool, TextIter, TextIter))), MonadIO m) => O.MethodInfo TextIterForwardSearchMethodInfo TextIter signature where
    overloadedMethod = textIterForwardSearch

#endif

-- method TextIter::forward_sentence_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_forward_sentence_end" gtk_text_iter_forward_sentence_end :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves forward to the next sentence end. (If /@iter@/ is at the end of
-- a sentence, moves to the next end of sentence.)  Sentence
-- boundaries are determined by Pango and should be correct for nearly
-- any language (if not, the correct fix would be to the Pango text
-- boundary algorithms).
textIterForwardSentenceEnd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterForwardSentenceEnd :: TextIter -> m Bool
textIterForwardSentenceEnd iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_sentence_end Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardSentenceEndMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardSentenceEndMethodInfo TextIter signature where
    overloadedMethod = textIterForwardSentenceEnd

#endif

-- method TextIter::forward_sentence_ends
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of sentences to move"
--                 , 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 "gtk_text_iter_forward_sentence_ends" gtk_text_iter_forward_sentence_ends :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Calls 'GI.Gtk.Structs.TextIter.textIterForwardSentenceEnd' /@count@/ times (or until
-- 'GI.Gtk.Structs.TextIter.textIterForwardSentenceEnd' returns 'P.False'). If /@count@/ is
-- negative, moves backward instead of forward.
textIterForwardSentenceEnds ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of sentences to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterForwardSentenceEnds :: TextIter -> Int32 -> m Bool
textIterForwardSentenceEnds iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_forward_sentence_ends Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardSentenceEndsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardSentenceEndsMethodInfo TextIter signature where
    overloadedMethod = textIterForwardSentenceEnds

#endif

-- method TextIter::forward_to_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_forward_to_end" gtk_text_iter_forward_to_end :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO ()

-- | Moves /@iter@/ forward to the “end iterator,” which points one past the last
-- valid character in the buffer. 'GI.Gtk.Structs.TextIter.textIterGetChar' called on the
-- end iterator returns 0, which is convenient for writing loops.
textIterForwardToEnd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m ()
textIterForwardToEnd :: TextIter -> m ()
textIterForwardToEnd iter :: TextIter
iter = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextIter -> IO ()
gtk_text_iter_forward_to_end Ptr TextIter
iter'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TextIterForwardToEndMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TextIterForwardToEndMethodInfo TextIter signature where
    overloadedMethod = textIterForwardToEnd

#endif

-- method TextIter::forward_to_line_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_forward_to_line_end" gtk_text_iter_forward_to_line_end :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves the iterator to point to the paragraph delimiter characters,
-- which will be either a newline, a carriage return, a carriage
-- return\/newline in sequence, or the Unicode paragraph separator
-- character. If the iterator is already at the paragraph delimiter
-- characters, moves to the paragraph delimiter characters for the
-- next line. If /@iter@/ is on the last line in the buffer, which does
-- not end in paragraph delimiters, moves to the end iterator (end of
-- the last line), and returns 'P.False'.
textIterForwardToLineEnd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved and the new location is not the end iterator
textIterForwardToLineEnd :: TextIter -> m Bool
textIterForwardToLineEnd iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_to_line_end Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardToLineEndMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardToLineEndMethodInfo TextIter signature where
    overloadedMethod = textIterForwardToLineEnd

#endif

-- method TextIter::forward_to_tag_toggle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tag"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextTag" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextTag, or %NULL"
--                 , 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 "gtk_text_iter_forward_to_tag_toggle" gtk_text_iter_forward_to_tag_toggle :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr Gtk.TextTag.TextTag ->              -- tag : TInterface (Name {namespace = "Gtk", name = "TextTag"})
    IO CInt

-- | Moves forward to the next toggle (on or off) of the
-- t'GI.Gtk.Objects.TextTag.TextTag' /@tag@/, or to the next toggle of any tag if
-- /@tag@/ is 'P.Nothing'. If no matching tag toggles are found,
-- returns 'P.False', otherwise 'P.True'. Does not return toggles
-- located at /@iter@/, only toggles after /@iter@/. Sets /@iter@/ to
-- the location of the toggle, or to the end of the buffer
-- if no toggle is found.
textIterForwardToTagToggle ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.TextTag.IsTextTag a) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Maybe (a)
    -- ^ /@tag@/: a t'GI.Gtk.Objects.TextTag.TextTag', or 'P.Nothing'
    -> m Bool
    -- ^ __Returns:__ whether we found a tag toggle after /@iter@/
textIterForwardToTagToggle :: TextIter -> Maybe a -> m Bool
textIterForwardToTagToggle iter :: TextIter
iter tag :: Maybe a
tag = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextTag
maybeTag <- case Maybe a
tag of
        Nothing -> Ptr TextTag -> IO (Ptr TextTag)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextTag
forall a. Ptr a
nullPtr
        Just jTag :: a
jTag -> do
            Ptr TextTag
jTag' <- a -> IO (Ptr TextTag)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jTag
            Ptr TextTag -> IO (Ptr TextTag)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextTag
jTag'
    CInt
result <- Ptr TextIter -> Ptr TextTag -> IO CInt
gtk_text_iter_forward_to_tag_toggle Ptr TextIter
iter' Ptr TextTag
maybeTag
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
tag a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardToTagToggleMethodInfo
instance (signature ~ (Maybe (a) -> m Bool), MonadIO m, Gtk.TextTag.IsTextTag a) => O.MethodInfo TextIterForwardToTagToggleMethodInfo TextIter signature where
    overloadedMethod = textIterForwardToTagToggle

#endif

-- method TextIter::forward_visible_cursor_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_forward_visible_cursor_position" gtk_text_iter_forward_visible_cursor_position :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves /@iter@/ forward to the next visible cursor position. See
-- 'GI.Gtk.Structs.TextIter.textIterForwardCursorPosition' for details.
-- 
-- /Since: 2.4/
textIterForwardVisibleCursorPosition ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved and the new position is dereferenceable
textIterForwardVisibleCursorPosition :: TextIter -> m Bool
textIterForwardVisibleCursorPosition iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_visible_cursor_position Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardVisibleCursorPositionMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardVisibleCursorPositionMethodInfo TextIter signature where
    overloadedMethod = textIterForwardVisibleCursorPosition

#endif

-- method TextIter::forward_visible_cursor_positions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of positions to move"
--                 , 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 "gtk_text_iter_forward_visible_cursor_positions" gtk_text_iter_forward_visible_cursor_positions :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves up to /@count@/ visible cursor positions. See
-- 'GI.Gtk.Structs.TextIter.textIterForwardCursorPosition' for details.
-- 
-- /Since: 2.4/
textIterForwardVisibleCursorPositions ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of positions to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if we moved and the new position is dereferenceable
textIterForwardVisibleCursorPositions :: TextIter -> Int32 -> m Bool
textIterForwardVisibleCursorPositions iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_forward_visible_cursor_positions Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardVisibleCursorPositionsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardVisibleCursorPositionsMethodInfo TextIter signature where
    overloadedMethod = textIterForwardVisibleCursorPositions

#endif

-- method TextIter::forward_visible_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_forward_visible_line" gtk_text_iter_forward_visible_line :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves /@iter@/ to the start of the next visible line. Returns 'P.True' if there
-- was a next line to move to, and 'P.False' if /@iter@/ was simply moved to
-- the end of the buffer and is now not dereferenceable, or if /@iter@/ was
-- already at the end of the buffer.
-- 
-- /Since: 2.8/
textIterForwardVisibleLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ can be dereferenced
textIterForwardVisibleLine :: TextIter -> m Bool
textIterForwardVisibleLine iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_visible_line Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardVisibleLineMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardVisibleLineMethodInfo TextIter signature where
    overloadedMethod = textIterForwardVisibleLine

#endif

-- method TextIter::forward_visible_lines
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of lines to move forward"
--                 , 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 "gtk_text_iter_forward_visible_lines" gtk_text_iter_forward_visible_lines :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Moves /@count@/ visible lines forward, if possible (if /@count@/ would move
-- past the start or end of the buffer, moves to the start or end of
-- the buffer).  The return value indicates whether the iterator moved
-- onto a dereferenceable position; if the iterator didn’t move, or
-- moved onto the end iterator, then 'P.False' is returned. If /@count@/ is 0,
-- the function does nothing and returns 'P.False'. If /@count@/ is negative,
-- moves backward by 0 - /@count@/ lines.
-- 
-- /Since: 2.8/
textIterForwardVisibleLines ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of lines to move forward
    -> m Bool
    -- ^ __Returns:__ whether /@iter@/ moved and is dereferenceable
textIterForwardVisibleLines :: TextIter -> Int32 -> m Bool
textIterForwardVisibleLines iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_forward_visible_lines Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardVisibleLinesMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardVisibleLinesMethodInfo TextIter signature where
    overloadedMethod = textIterForwardVisibleLines

#endif

-- method TextIter::forward_visible_word_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_forward_visible_word_end" gtk_text_iter_forward_visible_word_end :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves forward to the next visible word end. (If /@iter@/ is currently on a
-- word end, moves forward to the next one after that.) Word breaks
-- are determined by Pango and should be correct for nearly any
-- language (if not, the correct fix would be to the Pango word break
-- algorithms).
-- 
-- /Since: 2.4/
textIterForwardVisibleWordEnd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterForwardVisibleWordEnd :: TextIter -> m Bool
textIterForwardVisibleWordEnd iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_visible_word_end Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardVisibleWordEndMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardVisibleWordEndMethodInfo TextIter signature where
    overloadedMethod = textIterForwardVisibleWordEnd

#endif

-- method TextIter::forward_visible_word_ends
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of times to move"
--                 , 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 "gtk_text_iter_forward_visible_word_ends" gtk_text_iter_forward_visible_word_ends :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Calls 'GI.Gtk.Structs.TextIter.textIterForwardVisibleWordEnd' up to /@count@/ times.
-- 
-- /Since: 2.4/
textIterForwardVisibleWordEnds ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of times to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterForwardVisibleWordEnds :: TextIter -> Int32 -> m Bool
textIterForwardVisibleWordEnds iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_forward_visible_word_ends Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardVisibleWordEndsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardVisibleWordEndsMethodInfo TextIter signature where
    overloadedMethod = textIterForwardVisibleWordEnds

#endif

-- method TextIter::forward_word_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , 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 "gtk_text_iter_forward_word_end" gtk_text_iter_forward_word_end :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | Moves forward to the next word end. (If /@iter@/ is currently on a
-- word end, moves forward to the next one after that.) Word breaks
-- are determined by Pango and should be correct for nearly any
-- language (if not, the correct fix would be to the Pango word break
-- algorithms).
textIterForwardWordEnd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterForwardWordEnd :: TextIter -> m Bool
textIterForwardWordEnd iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_forward_word_end Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardWordEndMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextIterForwardWordEndMethodInfo TextIter signature where
    overloadedMethod = textIterForwardWordEnd

#endif

-- method TextIter::forward_word_ends
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextIter" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of times to move"
--                 , 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 "gtk_text_iter_forward_word_ends" gtk_text_iter_forward_word_ends :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Int32 ->                                -- count : TBasicType TInt
    IO CInt

-- | Calls 'GI.Gtk.Structs.TextIter.textIterForwardWordEnd' up to /@count@/ times.
textIterForwardWordEnds ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a t'GI.Gtk.Structs.TextIter.TextIter'
    -> Int32
    -- ^ /@count@/: number of times to move
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ moved and is not the end iterator
textIterForwardWordEnds :: TextIter -> Int32 -> m Bool
textIterForwardWordEnds iter :: TextIter
iter count :: Int32
count = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> Int32 -> IO CInt
gtk_text_iter_forward_word_ends Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TextIterForwardWordEndsMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo TextIterForwardWordEndsMethodInfo TextIter signature where
    overloadedMethod = textIterForwardWordEnds

#endif

-- method TextIter::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a dynamically-allocated iterator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_free" gtk_text_iter_free :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO ()

-- | Free an iterator allocated on the heap. This function
-- is intended for use in language bindings, and is not
-- especially useful for applications, because iterators can
-- simply be allocated on the stack.
textIterFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: a dynamically-allocated iterator
    -> m ()
textIterFree :: TextIter -> m ()
textIterFree iter :: TextIter
iter = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextIter -> IO ()
gtk_text_iter_free Ptr TextIter
iter'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TextIterFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TextIterFreeMethodInfo TextIter signature where
    overloadedMethod = textIterFree

#endif

-- method TextIter::get_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "values"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextAttributes" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextAttributes to be filled in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_get_attributes" gtk_text_iter_get_attributes :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr Gtk.TextAttributes.TextAttributes -> -- values : TInterface (Name {namespace = "Gtk", name = "TextAttributes"})
    IO CInt

-- | Computes the effect of any tags applied to this spot in the
-- text. The /@values@/ parameter should be initialized to the default
-- settings you wish to use if no tags are in effect. You’d typically
-- obtain the defaults from 'GI.Gtk.Objects.TextView.textViewGetDefaultAttributes'.
-- 
-- 'GI.Gtk.Structs.TextIter.textIterGetAttributes' will modify /@values@/, applying the
-- effects of any tags present at /@iter@/. If any tags affected /@values@/,
-- the function returns 'P.True'.
textIterGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m ((Bool, Gtk.TextAttributes.TextAttributes))
    -- ^ __Returns:__ 'P.True' if /@values@/ was modified
textIterGetAttributes :: TextIter -> m (Bool, TextAttributes)
textIterGetAttributes iter :: TextIter
iter = IO (Bool, TextAttributes) -> m (Bool, TextAttributes)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, TextAttributes) -> m (Bool, TextAttributes))
-> IO (Bool, TextAttributes) -> m (Bool, TextAttributes)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextAttributes
values <- Int -> IO (Ptr TextAttributes)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 168 :: IO (Ptr Gtk.TextAttributes.TextAttributes)
    CInt
result <- Ptr TextIter -> Ptr TextAttributes -> IO CInt
gtk_text_iter_get_attributes Ptr TextIter
iter' Ptr TextAttributes
values
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TextAttributes
values' <- ((ManagedPtr TextAttributes -> TextAttributes)
-> Ptr TextAttributes -> IO TextAttributes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextAttributes -> TextAttributes
Gtk.TextAttributes.TextAttributes) Ptr TextAttributes
values
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    (Bool, TextAttributes) -> IO (Bool, TextAttributes)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', TextAttributes
values')

#if defined(ENABLE_OVERLOADING)
data TextIterGetAttributesMethodInfo
instance (signature ~ (m ((Bool, Gtk.TextAttributes.TextAttributes))), MonadIO m) => O.MethodInfo TextIterGetAttributesMethodInfo TextIter signature where
    overloadedMethod = textIterGetAttributes

#endif

-- method TextIter::get_buffer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "TextBuffer" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_get_buffer" gtk_text_iter_get_buffer :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO (Ptr Gtk.TextBuffer.TextBuffer)

-- | Returns the t'GI.Gtk.Objects.TextBuffer.TextBuffer' this iterator is associated with.
textIterGetBuffer ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Gtk.TextBuffer.TextBuffer
    -- ^ __Returns:__ the buffer
textIterGetBuffer :: TextIter -> m TextBuffer
textIterGetBuffer iter :: TextIter
iter = IO TextBuffer -> m TextBuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextBuffer -> m TextBuffer) -> IO TextBuffer -> m TextBuffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextBuffer
result <- Ptr TextIter -> IO (Ptr TextBuffer)
gtk_text_iter_get_buffer Ptr TextIter
iter'
    Text -> Ptr TextBuffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textIterGetBuffer" Ptr TextBuffer
result
    TextBuffer
result' <- ((ManagedPtr TextBuffer -> TextBuffer)
-> Ptr TextBuffer -> IO TextBuffer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TextBuffer -> TextBuffer
Gtk.TextBuffer.TextBuffer) Ptr TextBuffer
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    TextBuffer -> IO TextBuffer
forall (m :: * -> *) a. Monad m => a -> m a
return TextBuffer
result'

#if defined(ENABLE_OVERLOADING)
data TextIterGetBufferMethodInfo
instance (signature ~ (m Gtk.TextBuffer.TextBuffer), MonadIO m) => O.MethodInfo TextIterGetBufferMethodInfo TextIter signature where
    overloadedMethod = textIterGetBuffer

#endif

-- method TextIter::get_bytes_in_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_get_bytes_in_line" gtk_text_iter_get_bytes_in_line :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO Int32

-- | Returns the number of bytes in the line containing /@iter@/,
-- including the paragraph delimiters.
textIterGetBytesInLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Int32
    -- ^ __Returns:__ number of bytes in the line
textIterGetBytesInLine :: TextIter -> m Int32
textIterGetBytesInLine iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Int32
result <- Ptr TextIter -> IO Int32
gtk_text_iter_get_bytes_in_line Ptr TextIter
iter'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextIterGetBytesInLineMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo TextIterGetBytesInLineMethodInfo TextIter signature where
    overloadedMethod = textIterGetBytesInLine

#endif

-- method TextIter::get_char
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_get_char" gtk_text_iter_get_char :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CInt

-- | The Unicode character at this iterator is returned.  (Equivalent to
-- operator* on a C++ iterator.)  If the element at this iterator is a
-- non-character element, such as an image embedded in the buffer, the
-- Unicode “unknown” character 0xFFFC is returned. If invoked on
-- the end iterator, zero is returned; zero is not a valid Unicode character.
-- So you can write a loop which ends when 'GI.Gtk.Structs.TextIter.textIterGetChar'
-- returns 0.
textIterGetChar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Char
    -- ^ __Returns:__ a Unicode character, or 0 if /@iter@/ is not dereferenceable
textIterGetChar :: TextIter -> m Char
textIterGetChar iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextIter -> IO CInt
gtk_text_iter_get_char Ptr TextIter
iter'
    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
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Char -> IO Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
result'

#if defined(ENABLE_OVERLOADING)
data TextIterGetCharMethodInfo
instance (signature ~ (m Char), MonadIO m) => O.MethodInfo TextIterGetCharMethodInfo TextIter signature where
    overloadedMethod = textIterGetChar

#endif

-- method TextIter::get_chars_in_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_get_chars_in_line" gtk_text_iter_get_chars_in_line :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO Int32

-- | Returns the number of characters in the line containing /@iter@/,
-- including the paragraph delimiters.
textIterGetCharsInLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Int32
    -- ^ __Returns:__ number of characters in the line
textIterGetCharsInLine :: TextIter -> m Int32
textIterGetCharsInLine iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Int32
result <- Ptr TextIter -> IO Int32
gtk_text_iter_get_chars_in_line Ptr TextIter
iter'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextIterGetCharsInLineMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo TextIterGetCharsInLineMethodInfo TextIter signature where
    overloadedMethod = textIterGetCharsInLine

#endif

-- method TextIter::get_child_anchor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "TextChildAnchor" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_get_child_anchor" gtk_text_iter_get_child_anchor :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO (Ptr Gtk.TextChildAnchor.TextChildAnchor)

-- | If the location at /@iter@/ contains a child anchor, the
-- anchor is returned (with no new reference count added). Otherwise,
-- 'P.Nothing' is returned.
textIterGetChildAnchor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Gtk.TextChildAnchor.TextChildAnchor
    -- ^ __Returns:__ the anchor at /@iter@/
textIterGetChildAnchor :: TextIter -> m TextChildAnchor
textIterGetChildAnchor iter :: TextIter
iter = IO TextChildAnchor -> m TextChildAnchor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextChildAnchor -> m TextChildAnchor)
-> IO TextChildAnchor -> m TextChildAnchor
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr TextChildAnchor
result <- Ptr TextIter -> IO (Ptr TextChildAnchor)
gtk_text_iter_get_child_anchor Ptr TextIter
iter'
    Text -> Ptr TextChildAnchor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textIterGetChildAnchor" Ptr TextChildAnchor
result
    TextChildAnchor
result' <- ((ManagedPtr TextChildAnchor -> TextChildAnchor)
-> Ptr TextChildAnchor -> IO TextChildAnchor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TextChildAnchor -> TextChildAnchor
Gtk.TextChildAnchor.TextChildAnchor) Ptr TextChildAnchor
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    TextChildAnchor -> IO TextChildAnchor
forall (m :: * -> *) a. Monad m => a -> m a
return TextChildAnchor
result'

#if defined(ENABLE_OVERLOADING)
data TextIterGetChildAnchorMethodInfo
instance (signature ~ (m Gtk.TextChildAnchor.TextChildAnchor), MonadIO m) => O.MethodInfo TextIterGetChildAnchorMethodInfo TextIter signature where
    overloadedMethod = textIterGetChildAnchor

#endif

-- method TextIter::get_language
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Language" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_get_language" gtk_text_iter_get_language :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO (Ptr Pango.Language.Language)

-- | A convenience wrapper around 'GI.Gtk.Structs.TextIter.textIterGetAttributes',
-- which returns the language in effect at /@iter@/. If no tags affecting
-- language apply to /@iter@/, the return value is identical to that of
-- 'GI.Gtk.Functions.getDefaultLanguage'.
textIterGetLanguage ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Pango.Language.Language
    -- ^ __Returns:__ language in effect at /@iter@/
textIterGetLanguage :: TextIter -> m Language
textIterGetLanguage iter :: TextIter
iter = IO Language -> m Language
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Language -> m Language) -> IO Language -> m Language
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr Language
result <- Ptr TextIter -> IO (Ptr Language)
gtk_text_iter_get_language Ptr TextIter
iter'
    Text -> Ptr Language -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textIterGetLanguage" Ptr Language
result
    Language
result' <- ((ManagedPtr Language -> Language) -> Ptr Language -> IO Language
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Language -> Language
Pango.Language.Language) Ptr Language
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Language -> IO Language
forall (m :: * -> *) a. Monad m => a -> m a
return Language
result'

#if defined(ENABLE_OVERLOADING)
data TextIterGetLanguageMethodInfo
instance (signature ~ (m Pango.Language.Language), MonadIO m) => O.MethodInfo TextIterGetLanguageMethodInfo TextIter signature where
    overloadedMethod = textIterGetLanguage

#endif

-- method TextIter::get_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_get_line" gtk_text_iter_get_line :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO Int32

-- | Returns the line number containing the iterator. Lines in
-- a t'GI.Gtk.Objects.TextBuffer.TextBuffer' are numbered beginning with 0 for the first
-- line in the buffer.
textIterGetLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Int32
    -- ^ __Returns:__ a line number
textIterGetLine :: TextIter -> m Int32
textIterGetLine iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Int32
result <- Ptr TextIter -> IO Int32
gtk_text_iter_get_line Ptr TextIter
iter'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextIterGetLineMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo TextIterGetLineMethodInfo TextIter signature where
    overloadedMethod = textIterGetLine

#endif

-- method TextIter::get_line_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_get_line_index" gtk_text_iter_get_line_index :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO Int32

-- | Returns the byte index of the iterator, counting
-- from the start of a newline-terminated line.
-- Remember that t'GI.Gtk.Objects.TextBuffer.TextBuffer' encodes text in
-- UTF-8, and that characters can require a variable
-- number of bytes to represent.
textIterGetLineIndex ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Int32
    -- ^ __Returns:__ distance from start of line, in bytes
textIterGetLineIndex :: TextIter -> m Int32
textIterGetLineIndex iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Int32
result <- Ptr TextIter -> IO Int32
gtk_text_iter_get_line_index Ptr TextIter
iter'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextIterGetLineIndexMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo TextIterGetLineIndexMethodInfo TextIter signature where
    overloadedMethod = textIterGetLineIndex

#endif

-- method TextIter::get_line_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_get_line_offset" gtk_text_iter_get_line_offset :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO Int32

-- | Returns the character offset of the iterator,
-- counting from the start of a newline-terminated line.
-- The first character on the line has offset 0.
textIterGetLineOffset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Int32
    -- ^ __Returns:__ offset from start of line
textIterGetLineOffset :: TextIter -> m Int32
textIterGetLineOffset iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Int32
result <- Ptr TextIter -> IO Int32
gtk_text_iter_get_line_offset Ptr TextIter
iter'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextIterGetLineOffsetMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo TextIterGetLineOffsetMethodInfo TextIter signature where
    overloadedMethod = textIterGetLineOffset

#endif

-- method TextIter::get_marks
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGSList
--                  (TInterface Name { namespace = "Gtk" , name = "TextMark" }))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_get_marks" gtk_text_iter_get_marks :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO (Ptr (GSList (Ptr Gtk.TextMark.TextMark)))

-- | Returns a list of all t'GI.Gtk.Objects.TextMark.TextMark' at this location. Because marks
-- are not iterable (they don’t take up any \"space\" in the buffer,
-- they are just marks in between iterable locations), multiple marks
-- can exist in the same place. The returned list is not in any
-- meaningful order.
textIterGetMarks ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m [Gtk.TextMark.TextMark]
    -- ^ __Returns:__ list of t'GI.Gtk.Objects.TextMark.TextMark'
textIterGetMarks :: TextIter -> m [TextMark]
textIterGetMarks iter :: TextIter
iter = IO [TextMark] -> m [TextMark]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [TextMark] -> m [TextMark]) -> IO [TextMark] -> m [TextMark]
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr (GSList (Ptr TextMark))
result <- Ptr TextIter -> IO (Ptr (GSList (Ptr TextMark)))
gtk_text_iter_get_marks Ptr TextIter
iter'
    [Ptr TextMark]
result' <- Ptr (GSList (Ptr TextMark)) -> IO [Ptr TextMark]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr TextMark))
result
    [TextMark]
result'' <- (Ptr TextMark -> IO TextMark) -> [Ptr TextMark] -> IO [TextMark]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr TextMark -> TextMark) -> Ptr TextMark -> IO TextMark
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TextMark -> TextMark
Gtk.TextMark.TextMark) [Ptr TextMark]
result'
    Ptr (GSList (Ptr TextMark)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr TextMark))
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    [TextMark] -> IO [TextMark]
forall (m :: * -> *) a. Monad m => a -> m a
return [TextMark]
result''

#if defined(ENABLE_OVERLOADING)
data TextIterGetMarksMethodInfo
instance (signature ~ (m [Gtk.TextMark.TextMark]), MonadIO m) => O.MethodInfo TextIterGetMarksMethodInfo TextIter signature where
    overloadedMethod = textIterGetMarks

#endif

-- method TextIter::get_offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , 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 "gtk_text_iter_get_offset" gtk_text_iter_get_offset :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO Int32

-- | Returns the character offset of an iterator.
-- Each character in a t'GI.Gtk.Objects.TextBuffer.TextBuffer' has an offset,
-- starting with 0 for the first character in the buffer.
-- Use 'GI.Gtk.Objects.TextBuffer.textBufferGetIterAtOffset' to convert an
-- offset back into an iterator.
textIterGetOffset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m Int32
    -- ^ __Returns:__ a character offset
textIterGetOffset :: TextIter -> m Int32
textIterGetOffset iter :: TextIter
iter = 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 TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Int32
result <- Ptr TextIter -> IO Int32
gtk_text_iter_get_offset Ptr TextIter
iter'
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TextIterGetOffsetMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo TextIterGetOffsetMethodInfo TextIter signature where
    overloadedMethod = textIterGetOffset

#endif

-- method TextIter::get_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an iterator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_iter_get_pixbuf" gtk_text_iter_get_pixbuf :: 
    Ptr TextIter ->                         -- iter : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | If the element at /@iter@/ is a pixbuf, the pixbuf is returned
-- (with no new reference count added). Otherwise,
-- 'P.Nothing' is returned.
textIterGetPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@iter@/: an iterator
    -> m GdkPixbuf.Pixbuf.Pixbuf
    -- ^ __Returns:__ the pixbuf at /@iter@/
textIterGetPixbuf :: TextIter -> m Pixbuf
textIterGetPixbuf iter :: TextIter
iter = IO Pixbuf -> m Pixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr Pixbuf
result <- Ptr TextIter -> IO (Ptr Pixbuf)
gtk_text_iter_get_pixbuf Ptr TextIter
iter'
    Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textIterGetPixbuf" Ptr Pixbuf
result
    Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'

#if defined(ENABLE_OVERLOADING)
data TextIterGetPixbufMethodInfo
instance (signature ~ (m GdkPixbuf.Pixbuf.Pixbuf), MonadIO m) => O.MethodInfo TextIterGetPixbufMethodInfo TextIter signature where
    overloadedMethod = textIterGetPixbuf

#endif

-- method TextIter::get_slice
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "start"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "iterator at start of a range"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "iterator at end of a range"
--                 , 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 "gtk_text_iter_get_slice" gtk_text_iter_get_slice :: 
    Ptr TextIter ->                         -- start : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    Ptr TextIter ->                         -- end : TInterface (Name {namespace = "Gtk", name = "TextIter"})
    IO CString

-- | Returns the text in the given range. A “slice” is an array of
-- characters encoded in UTF-8 format, including the Unicode “unknown”
-- character 0xFFFC for iterable non-character elements in the buffer,
-- such as images.  Because images are encoded in the slice, byte and
-- character offsets in the returned array will correspond to byte
-- offsets in the text buffer. Note that 0xFFFC can occur in normal
-- text as well, so it is not a reliable indicator that a pixbuf or
-- widget is in the buffer.
textIterGetSlice ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextIter
    -- ^ /@start@/: iterator at start of a range
    -> TextIter
    -- ^ /@end@/: iterator at end of a range
    -> m T.Text
    -- ^ __Returns:__ slice of text from the buffer
textIterGetSlice :: TextIter -> TextIter -> m Text
textIterGetSlice start :: TextIter
start end :: TextIter
end = 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 TextIter
start' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
start
    Ptr TextIter
end' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
end
    CString
result <- Ptr TextIter -> Ptr TextIter -> IO CString
gtk_text_iter_get_slice Ptr TextIter
start' Ptr TextIter
end'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textIterGetSlice" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result