{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.TextView
    ( 
    TextView(..)                            ,
    IsTextView                              ,
    toTextView                              ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveTextViewMethod                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewAddChildAtAnchorMethodInfo      ,
#endif
    textViewAddChildAtAnchor                ,
#if defined(ENABLE_OVERLOADING)
    TextViewAddOverlayMethodInfo            ,
#endif
    textViewAddOverlay                      ,
#if defined(ENABLE_OVERLOADING)
    TextViewBackwardDisplayLineMethodInfo   ,
#endif
    textViewBackwardDisplayLine             ,
#if defined(ENABLE_OVERLOADING)
    TextViewBackwardDisplayLineStartMethodInfo,
#endif
    textViewBackwardDisplayLineStart        ,
#if defined(ENABLE_OVERLOADING)
    TextViewBufferToWindowCoordsMethodInfo  ,
#endif
    textViewBufferToWindowCoords            ,
#if defined(ENABLE_OVERLOADING)
    TextViewForwardDisplayLineMethodInfo    ,
#endif
    textViewForwardDisplayLine              ,
#if defined(ENABLE_OVERLOADING)
    TextViewForwardDisplayLineEndMethodInfo ,
#endif
    textViewForwardDisplayLineEnd           ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetAcceptsTabMethodInfo         ,
#endif
    textViewGetAcceptsTab                   ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetBottomMarginMethodInfo       ,
#endif
    textViewGetBottomMargin                 ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetBufferMethodInfo             ,
#endif
    textViewGetBuffer                       ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetCursorLocationsMethodInfo    ,
#endif
    textViewGetCursorLocations              ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetCursorVisibleMethodInfo      ,
#endif
    textViewGetCursorVisible                ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetEditableMethodInfo           ,
#endif
    textViewGetEditable                     ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetExtraMenuMethodInfo          ,
#endif
    textViewGetExtraMenu                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetGutterMethodInfo             ,
#endif
    textViewGetGutter                       ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetIndentMethodInfo             ,
#endif
    textViewGetIndent                       ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetInputHintsMethodInfo         ,
#endif
    textViewGetInputHints                   ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetInputPurposeMethodInfo       ,
#endif
    textViewGetInputPurpose                 ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetIterAtLocationMethodInfo     ,
#endif
    textViewGetIterAtLocation               ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetIterAtPositionMethodInfo     ,
#endif
    textViewGetIterAtPosition               ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetIterLocationMethodInfo       ,
#endif
    textViewGetIterLocation                 ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetJustificationMethodInfo      ,
#endif
    textViewGetJustification                ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetLeftMarginMethodInfo         ,
#endif
    textViewGetLeftMargin                   ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetLineAtYMethodInfo            ,
#endif
    textViewGetLineAtY                      ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetLineYrangeMethodInfo         ,
#endif
    textViewGetLineYrange                   ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetMonospaceMethodInfo          ,
#endif
    textViewGetMonospace                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetOverwriteMethodInfo          ,
#endif
    textViewGetOverwrite                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetPixelsAboveLinesMethodInfo   ,
#endif
    textViewGetPixelsAboveLines             ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetPixelsBelowLinesMethodInfo   ,
#endif
    textViewGetPixelsBelowLines             ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetPixelsInsideWrapMethodInfo   ,
#endif
    textViewGetPixelsInsideWrap             ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetRightMarginMethodInfo        ,
#endif
    textViewGetRightMargin                  ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetTabsMethodInfo               ,
#endif
    textViewGetTabs                         ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetTopMarginMethodInfo          ,
#endif
    textViewGetTopMargin                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetVisibleRectMethodInfo        ,
#endif
    textViewGetVisibleRect                  ,
#if defined(ENABLE_OVERLOADING)
    TextViewGetWrapModeMethodInfo           ,
#endif
    textViewGetWrapMode                     ,
#if defined(ENABLE_OVERLOADING)
    TextViewImContextFilterKeypressMethodInfo,
#endif
    textViewImContextFilterKeypress         ,
#if defined(ENABLE_OVERLOADING)
    TextViewMoveMarkOnscreenMethodInfo      ,
#endif
    textViewMoveMarkOnscreen                ,
#if defined(ENABLE_OVERLOADING)
    TextViewMoveOverlayMethodInfo           ,
#endif
    textViewMoveOverlay                     ,
#if defined(ENABLE_OVERLOADING)
    TextViewMoveVisuallyMethodInfo          ,
#endif
    textViewMoveVisually                    ,
    textViewNew                             ,
    textViewNewWithBuffer                   ,
#if defined(ENABLE_OVERLOADING)
    TextViewPlaceCursorOnscreenMethodInfo   ,
#endif
    textViewPlaceCursorOnscreen             ,
#if defined(ENABLE_OVERLOADING)
    TextViewRemoveMethodInfo                ,
#endif
    textViewRemove                          ,
#if defined(ENABLE_OVERLOADING)
    TextViewResetCursorBlinkMethodInfo      ,
#endif
    textViewResetCursorBlink                ,
#if defined(ENABLE_OVERLOADING)
    TextViewResetImContextMethodInfo        ,
#endif
    textViewResetImContext                  ,
#if defined(ENABLE_OVERLOADING)
    TextViewScrollMarkOnscreenMethodInfo    ,
#endif
    textViewScrollMarkOnscreen              ,
#if defined(ENABLE_OVERLOADING)
    TextViewScrollToIterMethodInfo          ,
#endif
    textViewScrollToIter                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewScrollToMarkMethodInfo          ,
#endif
    textViewScrollToMark                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetAcceptsTabMethodInfo         ,
#endif
    textViewSetAcceptsTab                   ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetBottomMarginMethodInfo       ,
#endif
    textViewSetBottomMargin                 ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetBufferMethodInfo             ,
#endif
    textViewSetBuffer                       ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetCursorVisibleMethodInfo      ,
#endif
    textViewSetCursorVisible                ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetEditableMethodInfo           ,
#endif
    textViewSetEditable                     ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetExtraMenuMethodInfo          ,
#endif
    textViewSetExtraMenu                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetGutterMethodInfo             ,
#endif
    textViewSetGutter                       ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetIndentMethodInfo             ,
#endif
    textViewSetIndent                       ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetInputHintsMethodInfo         ,
#endif
    textViewSetInputHints                   ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetInputPurposeMethodInfo       ,
#endif
    textViewSetInputPurpose                 ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetJustificationMethodInfo      ,
#endif
    textViewSetJustification                ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetLeftMarginMethodInfo         ,
#endif
    textViewSetLeftMargin                   ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetMonospaceMethodInfo          ,
#endif
    textViewSetMonospace                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetOverwriteMethodInfo          ,
#endif
    textViewSetOverwrite                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetPixelsAboveLinesMethodInfo   ,
#endif
    textViewSetPixelsAboveLines             ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetPixelsBelowLinesMethodInfo   ,
#endif
    textViewSetPixelsBelowLines             ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetPixelsInsideWrapMethodInfo   ,
#endif
    textViewSetPixelsInsideWrap             ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetRightMarginMethodInfo        ,
#endif
    textViewSetRightMargin                  ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetTabsMethodInfo               ,
#endif
    textViewSetTabs                         ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetTopMarginMethodInfo          ,
#endif
    textViewSetTopMargin                    ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetWrapModeMethodInfo           ,
#endif
    textViewSetWrapMode                     ,
#if defined(ENABLE_OVERLOADING)
    TextViewStartsDisplayLineMethodInfo     ,
#endif
    textViewStartsDisplayLine               ,
#if defined(ENABLE_OVERLOADING)
    TextViewWindowToBufferCoordsMethodInfo  ,
#endif
    textViewWindowToBufferCoords            ,
 
#if defined(ENABLE_OVERLOADING)
    TextViewAcceptsTabPropertyInfo          ,
#endif
    constructTextViewAcceptsTab             ,
    getTextViewAcceptsTab                   ,
    setTextViewAcceptsTab                   ,
#if defined(ENABLE_OVERLOADING)
    textViewAcceptsTab                      ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewBottomMarginPropertyInfo        ,
#endif
    constructTextViewBottomMargin           ,
    getTextViewBottomMargin                 ,
    setTextViewBottomMargin                 ,
#if defined(ENABLE_OVERLOADING)
    textViewBottomMargin                    ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewBufferPropertyInfo              ,
#endif
    clearTextViewBuffer                     ,
    constructTextViewBuffer                 ,
    getTextViewBuffer                       ,
    setTextViewBuffer                       ,
#if defined(ENABLE_OVERLOADING)
    textViewBuffer                          ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewCursorVisiblePropertyInfo       ,
#endif
    constructTextViewCursorVisible          ,
    getTextViewCursorVisible                ,
    setTextViewCursorVisible                ,
#if defined(ENABLE_OVERLOADING)
    textViewCursorVisible                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewEditablePropertyInfo            ,
#endif
    constructTextViewEditable               ,
    getTextViewEditable                     ,
    setTextViewEditable                     ,
#if defined(ENABLE_OVERLOADING)
    textViewEditable                        ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewExtraMenuPropertyInfo           ,
#endif
    clearTextViewExtraMenu                  ,
    constructTextViewExtraMenu              ,
    getTextViewExtraMenu                    ,
    setTextViewExtraMenu                    ,
#if defined(ENABLE_OVERLOADING)
    textViewExtraMenu                       ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewImModulePropertyInfo            ,
#endif
    clearTextViewImModule                   ,
    constructTextViewImModule               ,
    getTextViewImModule                     ,
    setTextViewImModule                     ,
#if defined(ENABLE_OVERLOADING)
    textViewImModule                        ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewIndentPropertyInfo              ,
#endif
    constructTextViewIndent                 ,
    getTextViewIndent                       ,
    setTextViewIndent                       ,
#if defined(ENABLE_OVERLOADING)
    textViewIndent                          ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewInputHintsPropertyInfo          ,
#endif
    constructTextViewInputHints             ,
    getTextViewInputHints                   ,
    setTextViewInputHints                   ,
#if defined(ENABLE_OVERLOADING)
    textViewInputHints                      ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewInputPurposePropertyInfo        ,
#endif
    constructTextViewInputPurpose           ,
    getTextViewInputPurpose                 ,
    setTextViewInputPurpose                 ,
#if defined(ENABLE_OVERLOADING)
    textViewInputPurpose                    ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewJustificationPropertyInfo       ,
#endif
    constructTextViewJustification          ,
    getTextViewJustification                ,
    setTextViewJustification                ,
#if defined(ENABLE_OVERLOADING)
    textViewJustification                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewLeftMarginPropertyInfo          ,
#endif
    constructTextViewLeftMargin             ,
    getTextViewLeftMargin                   ,
    setTextViewLeftMargin                   ,
#if defined(ENABLE_OVERLOADING)
    textViewLeftMargin                      ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewMonospacePropertyInfo           ,
#endif
    constructTextViewMonospace              ,
    getTextViewMonospace                    ,
    setTextViewMonospace                    ,
#if defined(ENABLE_OVERLOADING)
    textViewMonospace                       ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewOverwritePropertyInfo           ,
#endif
    constructTextViewOverwrite              ,
    getTextViewOverwrite                    ,
    setTextViewOverwrite                    ,
#if defined(ENABLE_OVERLOADING)
    textViewOverwrite                       ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewPixelsAboveLinesPropertyInfo    ,
#endif
    constructTextViewPixelsAboveLines       ,
    getTextViewPixelsAboveLines             ,
    setTextViewPixelsAboveLines             ,
#if defined(ENABLE_OVERLOADING)
    textViewPixelsAboveLines                ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewPixelsBelowLinesPropertyInfo    ,
#endif
    constructTextViewPixelsBelowLines       ,
    getTextViewPixelsBelowLines             ,
    setTextViewPixelsBelowLines             ,
#if defined(ENABLE_OVERLOADING)
    textViewPixelsBelowLines                ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewPixelsInsideWrapPropertyInfo    ,
#endif
    constructTextViewPixelsInsideWrap       ,
    getTextViewPixelsInsideWrap             ,
    setTextViewPixelsInsideWrap             ,
#if defined(ENABLE_OVERLOADING)
    textViewPixelsInsideWrap                ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewRightMarginPropertyInfo         ,
#endif
    constructTextViewRightMargin            ,
    getTextViewRightMargin                  ,
    setTextViewRightMargin                  ,
#if defined(ENABLE_OVERLOADING)
    textViewRightMargin                     ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewTabsPropertyInfo                ,
#endif
    constructTextViewTabs                   ,
    getTextViewTabs                         ,
    setTextViewTabs                         ,
#if defined(ENABLE_OVERLOADING)
    textViewTabs                            ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewTopMarginPropertyInfo           ,
#endif
    constructTextViewTopMargin              ,
    getTextViewTopMargin                    ,
    setTextViewTopMargin                    ,
#if defined(ENABLE_OVERLOADING)
    textViewTopMargin                       ,
#endif
#if defined(ENABLE_OVERLOADING)
    TextViewWrapModePropertyInfo            ,
#endif
    constructTextViewWrapMode               ,
    getTextViewWrapMode                     ,
    setTextViewWrapMode                     ,
#if defined(ENABLE_OVERLOADING)
    textViewWrapMode                        ,
#endif
 
    C_TextViewBackspaceCallback             ,
    TextViewBackspaceCallback               ,
#if defined(ENABLE_OVERLOADING)
    TextViewBackspaceSignalInfo             ,
#endif
    afterTextViewBackspace                  ,
    genClosure_TextViewBackspace            ,
    mk_TextViewBackspaceCallback            ,
    noTextViewBackspaceCallback             ,
    onTextViewBackspace                     ,
    wrap_TextViewBackspaceCallback          ,
    C_TextViewCopyClipboardCallback         ,
    TextViewCopyClipboardCallback           ,
#if defined(ENABLE_OVERLOADING)
    TextViewCopyClipboardSignalInfo         ,
#endif
    afterTextViewCopyClipboard              ,
    genClosure_TextViewCopyClipboard        ,
    mk_TextViewCopyClipboardCallback        ,
    noTextViewCopyClipboardCallback         ,
    onTextViewCopyClipboard                 ,
    wrap_TextViewCopyClipboardCallback      ,
    C_TextViewCutClipboardCallback          ,
    TextViewCutClipboardCallback            ,
#if defined(ENABLE_OVERLOADING)
    TextViewCutClipboardSignalInfo          ,
#endif
    afterTextViewCutClipboard               ,
    genClosure_TextViewCutClipboard         ,
    mk_TextViewCutClipboardCallback         ,
    noTextViewCutClipboardCallback          ,
    onTextViewCutClipboard                  ,
    wrap_TextViewCutClipboardCallback       ,
    C_TextViewDeleteFromCursorCallback      ,
    TextViewDeleteFromCursorCallback        ,
#if defined(ENABLE_OVERLOADING)
    TextViewDeleteFromCursorSignalInfo      ,
#endif
    afterTextViewDeleteFromCursor           ,
    genClosure_TextViewDeleteFromCursor     ,
    mk_TextViewDeleteFromCursorCallback     ,
    noTextViewDeleteFromCursorCallback      ,
    onTextViewDeleteFromCursor              ,
    wrap_TextViewDeleteFromCursorCallback   ,
    C_TextViewExtendSelectionCallback       ,
    TextViewExtendSelectionCallback         ,
#if defined(ENABLE_OVERLOADING)
    TextViewExtendSelectionSignalInfo       ,
#endif
    afterTextViewExtendSelection            ,
    genClosure_TextViewExtendSelection      ,
    mk_TextViewExtendSelectionCallback      ,
    noTextViewExtendSelectionCallback       ,
    onTextViewExtendSelection               ,
    wrap_TextViewExtendSelectionCallback    ,
    C_TextViewInsertAtCursorCallback        ,
    TextViewInsertAtCursorCallback          ,
#if defined(ENABLE_OVERLOADING)
    TextViewInsertAtCursorSignalInfo        ,
#endif
    afterTextViewInsertAtCursor             ,
    genClosure_TextViewInsertAtCursor       ,
    mk_TextViewInsertAtCursorCallback       ,
    noTextViewInsertAtCursorCallback        ,
    onTextViewInsertAtCursor                ,
    wrap_TextViewInsertAtCursorCallback     ,
    C_TextViewInsertEmojiCallback           ,
    TextViewInsertEmojiCallback             ,
#if defined(ENABLE_OVERLOADING)
    TextViewInsertEmojiSignalInfo           ,
#endif
    afterTextViewInsertEmoji                ,
    genClosure_TextViewInsertEmoji          ,
    mk_TextViewInsertEmojiCallback          ,
    noTextViewInsertEmojiCallback           ,
    onTextViewInsertEmoji                   ,
    wrap_TextViewInsertEmojiCallback        ,
    C_TextViewMoveCursorCallback            ,
    TextViewMoveCursorCallback              ,
#if defined(ENABLE_OVERLOADING)
    TextViewMoveCursorSignalInfo            ,
#endif
    afterTextViewMoveCursor                 ,
    genClosure_TextViewMoveCursor           ,
    mk_TextViewMoveCursorCallback           ,
    noTextViewMoveCursorCallback            ,
    onTextViewMoveCursor                    ,
    wrap_TextViewMoveCursorCallback         ,
    C_TextViewMoveViewportCallback          ,
    TextViewMoveViewportCallback            ,
#if defined(ENABLE_OVERLOADING)
    TextViewMoveViewportSignalInfo          ,
#endif
    afterTextViewMoveViewport               ,
    genClosure_TextViewMoveViewport         ,
    mk_TextViewMoveViewportCallback         ,
    noTextViewMoveViewportCallback          ,
    onTextViewMoveViewport                  ,
    wrap_TextViewMoveViewportCallback       ,
    C_TextViewPasteClipboardCallback        ,
    TextViewPasteClipboardCallback          ,
#if defined(ENABLE_OVERLOADING)
    TextViewPasteClipboardSignalInfo        ,
#endif
    afterTextViewPasteClipboard             ,
    genClosure_TextViewPasteClipboard       ,
    mk_TextViewPasteClipboardCallback       ,
    noTextViewPasteClipboardCallback        ,
    onTextViewPasteClipboard                ,
    wrap_TextViewPasteClipboardCallback     ,
    C_TextViewPreeditChangedCallback        ,
    TextViewPreeditChangedCallback          ,
#if defined(ENABLE_OVERLOADING)
    TextViewPreeditChangedSignalInfo        ,
#endif
    afterTextViewPreeditChanged             ,
    genClosure_TextViewPreeditChanged       ,
    mk_TextViewPreeditChangedCallback       ,
    noTextViewPreeditChangedCallback        ,
    onTextViewPreeditChanged                ,
    wrap_TextViewPreeditChangedCallback     ,
    C_TextViewSelectAllCallback             ,
    TextViewSelectAllCallback               ,
#if defined(ENABLE_OVERLOADING)
    TextViewSelectAllSignalInfo             ,
#endif
    afterTextViewSelectAll                  ,
    genClosure_TextViewSelectAll            ,
    mk_TextViewSelectAllCallback            ,
    noTextViewSelectAllCallback             ,
    onTextViewSelectAll                     ,
    wrap_TextViewSelectAllCallback          ,
    C_TextViewSetAnchorCallback             ,
    TextViewSetAnchorCallback               ,
#if defined(ENABLE_OVERLOADING)
    TextViewSetAnchorSignalInfo             ,
#endif
    afterTextViewSetAnchor                  ,
    genClosure_TextViewSetAnchor            ,
    mk_TextViewSetAnchorCallback            ,
    noTextViewSetAnchorCallback             ,
    onTextViewSetAnchor                     ,
    wrap_TextViewSetAnchorCallback          ,
    C_TextViewToggleCursorVisibleCallback   ,
    TextViewToggleCursorVisibleCallback     ,
#if defined(ENABLE_OVERLOADING)
    TextViewToggleCursorVisibleSignalInfo   ,
#endif
    afterTextViewToggleCursorVisible        ,
    genClosure_TextViewToggleCursorVisible  ,
    mk_TextViewToggleCursorVisibleCallback  ,
    noTextViewToggleCursorVisibleCallback   ,
    onTextViewToggleCursorVisible           ,
    wrap_TextViewToggleCursorVisibleCallback,
    C_TextViewToggleOverwriteCallback       ,
    TextViewToggleOverwriteCallback         ,
#if defined(ENABLE_OVERLOADING)
    TextViewToggleOverwriteSignalInfo       ,
#endif
    afterTextViewToggleOverwrite            ,
    genClosure_TextViewToggleOverwrite      ,
    mk_TextViewToggleOverwriteCallback      ,
    noTextViewToggleOverwriteCallback       ,
    onTextViewToggleOverwrite               ,
    wrap_TextViewToggleOverwriteCallback    ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Scrollable as Gtk.Scrollable
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.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextIter as Gtk.TextIter
import qualified GI.Pango.Structs.TabArray as Pango.TabArray
newtype TextView = TextView (SP.ManagedPtr TextView)
    deriving (TextView -> TextView -> Bool
(TextView -> TextView -> Bool)
-> (TextView -> TextView -> Bool) -> Eq TextView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextView -> TextView -> Bool
$c/= :: TextView -> TextView -> Bool
== :: TextView -> TextView -> Bool
$c== :: TextView -> TextView -> Bool
Eq)
instance SP.ManagedPtrNewtype TextView where
    toManagedPtr :: TextView -> ManagedPtr TextView
toManagedPtr (TextView ManagedPtr TextView
p) = ManagedPtr TextView
p
foreign import ccall "gtk_text_view_get_type"
    c_gtk_text_view_get_type :: IO B.Types.GType
instance B.Types.TypedObject TextView where
    glibType :: IO GType
glibType = IO GType
c_gtk_text_view_get_type
instance B.Types.GObject TextView
class (SP.GObject o, O.IsDescendantOf TextView o) => IsTextView o
instance (SP.GObject o, O.IsDescendantOf TextView o) => IsTextView o
instance O.HasParentTypes TextView
type instance O.ParentTypes TextView = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget, Gtk.Scrollable.Scrollable]
toTextView :: (MIO.MonadIO m, IsTextView o) => o -> m TextView
toTextView :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> m TextView
toTextView = IO TextView -> m TextView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO TextView -> m TextView)
-> (o -> IO TextView) -> o -> m TextView
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TextView -> TextView) -> o -> IO TextView
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr TextView -> TextView
TextView
instance B.GValue.IsGValue (Maybe TextView) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_text_view_get_type
    gvalueSet_ :: Ptr GValue -> Maybe TextView -> IO ()
gvalueSet_ Ptr GValue
gv Maybe TextView
P.Nothing = Ptr GValue -> Ptr TextView -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr TextView
forall a. Ptr a
FP.nullPtr :: FP.Ptr TextView)
    gvalueSet_ Ptr GValue
gv (P.Just TextView
obj) = TextView -> (Ptr TextView -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TextView
obj (Ptr GValue -> Ptr TextView -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe TextView)
gvalueGet_ Ptr GValue
gv = do
        Ptr TextView
ptr <- Ptr GValue -> IO (Ptr TextView)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr TextView)
        if Ptr TextView
ptr Ptr TextView -> Ptr TextView -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TextView
forall a. Ptr a
FP.nullPtr
        then TextView -> Maybe TextView
forall a. a -> Maybe a
P.Just (TextView -> Maybe TextView) -> IO TextView -> IO (Maybe TextView)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr TextView -> TextView) -> Ptr TextView -> IO TextView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TextView -> TextView
TextView Ptr TextView
ptr
        else Maybe TextView -> IO (Maybe TextView)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TextView
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveTextViewMethod (t :: Symbol) (o :: *) :: * where
    ResolveTextViewMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveTextViewMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveTextViewMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveTextViewMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveTextViewMethod "addChildAtAnchor" o = TextViewAddChildAtAnchorMethodInfo
    ResolveTextViewMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveTextViewMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveTextViewMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveTextViewMethod "addOverlay" o = TextViewAddOverlayMethodInfo
    ResolveTextViewMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveTextViewMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveTextViewMethod "backwardDisplayLine" o = TextViewBackwardDisplayLineMethodInfo
    ResolveTextViewMethod "backwardDisplayLineStart" o = TextViewBackwardDisplayLineStartMethodInfo
    ResolveTextViewMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTextViewMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTextViewMethod "bufferToWindowCoords" o = TextViewBufferToWindowCoordsMethodInfo
    ResolveTextViewMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveTextViewMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveTextViewMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveTextViewMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveTextViewMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveTextViewMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveTextViewMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveTextViewMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveTextViewMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveTextViewMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveTextViewMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTextViewMethod "forwardDisplayLine" o = TextViewForwardDisplayLineMethodInfo
    ResolveTextViewMethod "forwardDisplayLineEnd" o = TextViewForwardDisplayLineEndMethodInfo
    ResolveTextViewMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTextViewMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTextViewMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveTextViewMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveTextViewMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveTextViewMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveTextViewMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveTextViewMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveTextViewMethod "imContextFilterKeypress" o = TextViewImContextFilterKeypressMethodInfo
    ResolveTextViewMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveTextViewMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveTextViewMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveTextViewMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveTextViewMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveTextViewMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveTextViewMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveTextViewMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTextViewMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveTextViewMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveTextViewMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveTextViewMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveTextViewMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveTextViewMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveTextViewMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveTextViewMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveTextViewMethod "moveMarkOnscreen" o = TextViewMoveMarkOnscreenMethodInfo
    ResolveTextViewMethod "moveOverlay" o = TextViewMoveOverlayMethodInfo
    ResolveTextViewMethod "moveVisually" o = TextViewMoveVisuallyMethodInfo
    ResolveTextViewMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTextViewMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTextViewMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveTextViewMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveTextViewMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveTextViewMethod "placeCursorOnscreen" o = TextViewPlaceCursorOnscreenMethodInfo
    ResolveTextViewMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveTextViewMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveTextViewMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveTextViewMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveTextViewMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTextViewMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTextViewMethod "remove" o = TextViewRemoveMethodInfo
    ResolveTextViewMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveTextViewMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveTextViewMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveTextViewMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveTextViewMethod "resetCursorBlink" o = TextViewResetCursorBlinkMethodInfo
    ResolveTextViewMethod "resetImContext" o = TextViewResetImContextMethodInfo
    ResolveTextViewMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveTextViewMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveTextViewMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveTextViewMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTextViewMethod "scrollMarkOnscreen" o = TextViewScrollMarkOnscreenMethodInfo
    ResolveTextViewMethod "scrollToIter" o = TextViewScrollToIterMethodInfo
    ResolveTextViewMethod "scrollToMark" o = TextViewScrollToMarkMethodInfo
    ResolveTextViewMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveTextViewMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveTextViewMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveTextViewMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveTextViewMethod "startsDisplayLine" o = TextViewStartsDisplayLineMethodInfo
    ResolveTextViewMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTextViewMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTextViewMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTextViewMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveTextViewMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveTextViewMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveTextViewMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveTextViewMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveTextViewMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTextViewMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveTextViewMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveTextViewMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveTextViewMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveTextViewMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTextViewMethod "windowToBufferCoords" o = TextViewWindowToBufferCoordsMethodInfo
    ResolveTextViewMethod "getAcceptsTab" o = TextViewGetAcceptsTabMethodInfo
    ResolveTextViewMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveTextViewMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveTextViewMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveTextViewMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveTextViewMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveTextViewMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveTextViewMethod "getBorder" o = Gtk.Scrollable.ScrollableGetBorderMethodInfo
    ResolveTextViewMethod "getBottomMargin" o = TextViewGetBottomMarginMethodInfo
    ResolveTextViewMethod "getBuffer" o = TextViewGetBufferMethodInfo
    ResolveTextViewMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveTextViewMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveTextViewMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveTextViewMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveTextViewMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveTextViewMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveTextViewMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveTextViewMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveTextViewMethod "getCursorLocations" o = TextViewGetCursorLocationsMethodInfo
    ResolveTextViewMethod "getCursorVisible" o = TextViewGetCursorVisibleMethodInfo
    ResolveTextViewMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTextViewMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveTextViewMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveTextViewMethod "getEditable" o = TextViewGetEditableMethodInfo
    ResolveTextViewMethod "getExtraMenu" o = TextViewGetExtraMenuMethodInfo
    ResolveTextViewMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveTextViewMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveTextViewMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveTextViewMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveTextViewMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveTextViewMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveTextViewMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveTextViewMethod "getGutter" o = TextViewGetGutterMethodInfo
    ResolveTextViewMethod "getHadjustment" o = Gtk.Scrollable.ScrollableGetHadjustmentMethodInfo
    ResolveTextViewMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveTextViewMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveTextViewMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveTextViewMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveTextViewMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveTextViewMethod "getHscrollPolicy" o = Gtk.Scrollable.ScrollableGetHscrollPolicyMethodInfo
    ResolveTextViewMethod "getIndent" o = TextViewGetIndentMethodInfo
    ResolveTextViewMethod "getInputHints" o = TextViewGetInputHintsMethodInfo
    ResolveTextViewMethod "getInputPurpose" o = TextViewGetInputPurposeMethodInfo
    ResolveTextViewMethod "getIterAtLocation" o = TextViewGetIterAtLocationMethodInfo
    ResolveTextViewMethod "getIterAtPosition" o = TextViewGetIterAtPositionMethodInfo
    ResolveTextViewMethod "getIterLocation" o = TextViewGetIterLocationMethodInfo
    ResolveTextViewMethod "getJustification" o = TextViewGetJustificationMethodInfo
    ResolveTextViewMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveTextViewMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveTextViewMethod "getLeftMargin" o = TextViewGetLeftMarginMethodInfo
    ResolveTextViewMethod "getLineAtY" o = TextViewGetLineAtYMethodInfo
    ResolveTextViewMethod "getLineYrange" o = TextViewGetLineYrangeMethodInfo
    ResolveTextViewMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveTextViewMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveTextViewMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveTextViewMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveTextViewMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveTextViewMethod "getMonospace" o = TextViewGetMonospaceMethodInfo
    ResolveTextViewMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveTextViewMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveTextViewMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveTextViewMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveTextViewMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveTextViewMethod "getOverwrite" o = TextViewGetOverwriteMethodInfo
    ResolveTextViewMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveTextViewMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveTextViewMethod "getPixelsAboveLines" o = TextViewGetPixelsAboveLinesMethodInfo
    ResolveTextViewMethod "getPixelsBelowLines" o = TextViewGetPixelsBelowLinesMethodInfo
    ResolveTextViewMethod "getPixelsInsideWrap" o = TextViewGetPixelsInsideWrapMethodInfo
    ResolveTextViewMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveTextViewMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveTextViewMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveTextViewMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTextViewMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTextViewMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveTextViewMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveTextViewMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveTextViewMethod "getRightMargin" o = TextViewGetRightMarginMethodInfo
    ResolveTextViewMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveTextViewMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveTextViewMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveTextViewMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveTextViewMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveTextViewMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveTextViewMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveTextViewMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveTextViewMethod "getTabs" o = TextViewGetTabsMethodInfo
    ResolveTextViewMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveTextViewMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveTextViewMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveTextViewMethod "getTopMargin" o = TextViewGetTopMarginMethodInfo
    ResolveTextViewMethod "getVadjustment" o = Gtk.Scrollable.ScrollableGetVadjustmentMethodInfo
    ResolveTextViewMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveTextViewMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveTextViewMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveTextViewMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveTextViewMethod "getVisibleRect" o = TextViewGetVisibleRectMethodInfo
    ResolveTextViewMethod "getVscrollPolicy" o = Gtk.Scrollable.ScrollableGetVscrollPolicyMethodInfo
    ResolveTextViewMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveTextViewMethod "getWrapMode" o = TextViewGetWrapModeMethodInfo
    ResolveTextViewMethod "setAcceptsTab" o = TextViewSetAcceptsTabMethodInfo
    ResolveTextViewMethod "setBottomMargin" o = TextViewSetBottomMarginMethodInfo
    ResolveTextViewMethod "setBuffer" o = TextViewSetBufferMethodInfo
    ResolveTextViewMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveTextViewMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveTextViewMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveTextViewMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveTextViewMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveTextViewMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveTextViewMethod "setCursorVisible" o = TextViewSetCursorVisibleMethodInfo
    ResolveTextViewMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTextViewMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTextViewMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveTextViewMethod "setEditable" o = TextViewSetEditableMethodInfo
    ResolveTextViewMethod "setExtraMenu" o = TextViewSetExtraMenuMethodInfo
    ResolveTextViewMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveTextViewMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveTextViewMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveTextViewMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveTextViewMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveTextViewMethod "setGutter" o = TextViewSetGutterMethodInfo
    ResolveTextViewMethod "setHadjustment" o = Gtk.Scrollable.ScrollableSetHadjustmentMethodInfo
    ResolveTextViewMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveTextViewMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveTextViewMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveTextViewMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveTextViewMethod "setHscrollPolicy" o = Gtk.Scrollable.ScrollableSetHscrollPolicyMethodInfo
    ResolveTextViewMethod "setIndent" o = TextViewSetIndentMethodInfo
    ResolveTextViewMethod "setInputHints" o = TextViewSetInputHintsMethodInfo
    ResolveTextViewMethod "setInputPurpose" o = TextViewSetInputPurposeMethodInfo
    ResolveTextViewMethod "setJustification" o = TextViewSetJustificationMethodInfo
    ResolveTextViewMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveTextViewMethod "setLeftMargin" o = TextViewSetLeftMarginMethodInfo
    ResolveTextViewMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveTextViewMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveTextViewMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveTextViewMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveTextViewMethod "setMonospace" o = TextViewSetMonospaceMethodInfo
    ResolveTextViewMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveTextViewMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveTextViewMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveTextViewMethod "setOverwrite" o = TextViewSetOverwriteMethodInfo
    ResolveTextViewMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveTextViewMethod "setPixelsAboveLines" o = TextViewSetPixelsAboveLinesMethodInfo
    ResolveTextViewMethod "setPixelsBelowLines" o = TextViewSetPixelsBelowLinesMethodInfo
    ResolveTextViewMethod "setPixelsInsideWrap" o = TextViewSetPixelsInsideWrapMethodInfo
    ResolveTextViewMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTextViewMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveTextViewMethod "setRightMargin" o = TextViewSetRightMarginMethodInfo
    ResolveTextViewMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveTextViewMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveTextViewMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveTextViewMethod "setTabs" o = TextViewSetTabsMethodInfo
    ResolveTextViewMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveTextViewMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveTextViewMethod "setTopMargin" o = TextViewSetTopMarginMethodInfo
    ResolveTextViewMethod "setVadjustment" o = Gtk.Scrollable.ScrollableSetVadjustmentMethodInfo
    ResolveTextViewMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveTextViewMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveTextViewMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveTextViewMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveTextViewMethod "setVscrollPolicy" o = Gtk.Scrollable.ScrollableSetVscrollPolicyMethodInfo
    ResolveTextViewMethod "setWrapMode" o = TextViewSetWrapModeMethodInfo
    ResolveTextViewMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTextViewMethod t TextView, O.OverloadedMethod info TextView p) => OL.IsLabel t (TextView -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTextViewMethod t TextView, O.OverloadedMethod info TextView p, R.HasField t TextView p) => R.HasField t TextView p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveTextViewMethod t TextView, O.OverloadedMethodInfo info TextView) => OL.IsLabel t (O.MethodProxy info TextView) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
type TextViewBackspaceCallback =
    IO ()
noTextViewBackspaceCallback :: Maybe TextViewBackspaceCallback
noTextViewBackspaceCallback :: Maybe (IO ())
noTextViewBackspaceCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_TextViewBackspaceCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewBackspaceCallback :: C_TextViewBackspaceCallback -> IO (FunPtr C_TextViewBackspaceCallback)
genClosure_TextViewBackspace :: MonadIO m => TextViewBackspaceCallback -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewBackspace :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewBackspace IO ()
cb = IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewBackspaceCallback)
 -> m (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewBackspaceCallback IO ()
cb
    C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewBackspaceCallback C_TextViewBackspaceCallback
cb' IO (FunPtr C_TextViewBackspaceCallback)
-> (FunPtr C_TextViewBackspaceCallback
    -> IO (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewBackspaceCallback
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewBackspaceCallback ::
    TextViewBackspaceCallback ->
    C_TextViewBackspaceCallback
wrap_TextViewBackspaceCallback :: IO () -> C_TextViewBackspaceCallback
wrap_TextViewBackspaceCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onTextViewBackspace :: (IsTextView a, MonadIO m) => a -> TextViewBackspaceCallback -> m SignalHandlerId
onTextViewBackspace :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onTextViewBackspace a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewBackspaceCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewBackspaceCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"backspace" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewBackspace :: (IsTextView a, MonadIO m) => a -> TextViewBackspaceCallback -> m SignalHandlerId
afterTextViewBackspace :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterTextViewBackspace a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewBackspaceCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewBackspaceCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"backspace" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewBackspaceSignalInfo
instance SignalInfo TextViewBackspaceSignalInfo where
    type HaskellCallbackType TextViewBackspaceSignalInfo = TextViewBackspaceCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewBackspaceCallback cb
        cb'' <- mk_TextViewBackspaceCallback cb'
        connectSignalFunPtr obj "backspace" cb'' connectMode detail
#endif
type TextViewCopyClipboardCallback =
    IO ()
noTextViewCopyClipboardCallback :: Maybe TextViewCopyClipboardCallback
noTextViewCopyClipboardCallback :: Maybe (IO ())
noTextViewCopyClipboardCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_TextViewCopyClipboardCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewCopyClipboardCallback :: C_TextViewCopyClipboardCallback -> IO (FunPtr C_TextViewCopyClipboardCallback)
genClosure_TextViewCopyClipboard :: MonadIO m => TextViewCopyClipboardCallback -> m (GClosure C_TextViewCopyClipboardCallback)
genClosure_TextViewCopyClipboard :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewCopyClipboard IO ()
cb = IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewBackspaceCallback)
 -> m (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewCopyClipboardCallback IO ()
cb
    C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewCopyClipboardCallback C_TextViewBackspaceCallback
cb' IO (FunPtr C_TextViewBackspaceCallback)
-> (FunPtr C_TextViewBackspaceCallback
    -> IO (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewBackspaceCallback
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewCopyClipboardCallback ::
    TextViewCopyClipboardCallback ->
    C_TextViewCopyClipboardCallback
wrap_TextViewCopyClipboardCallback :: IO () -> C_TextViewBackspaceCallback
wrap_TextViewCopyClipboardCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onTextViewCopyClipboard :: (IsTextView a, MonadIO m) => a -> TextViewCopyClipboardCallback -> m SignalHandlerId
onTextViewCopyClipboard :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onTextViewCopyClipboard a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewCopyClipboardCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewCopyClipboardCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"copy-clipboard" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewCopyClipboard :: (IsTextView a, MonadIO m) => a -> TextViewCopyClipboardCallback -> m SignalHandlerId
afterTextViewCopyClipboard :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterTextViewCopyClipboard a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewCopyClipboardCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewCopyClipboardCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"copy-clipboard" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewCopyClipboardSignalInfo
instance SignalInfo TextViewCopyClipboardSignalInfo where
    type HaskellCallbackType TextViewCopyClipboardSignalInfo = TextViewCopyClipboardCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewCopyClipboardCallback cb
        cb'' <- mk_TextViewCopyClipboardCallback cb'
        connectSignalFunPtr obj "copy-clipboard" cb'' connectMode detail
#endif
type TextViewCutClipboardCallback =
    IO ()
noTextViewCutClipboardCallback :: Maybe TextViewCutClipboardCallback
noTextViewCutClipboardCallback :: Maybe (IO ())
noTextViewCutClipboardCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_TextViewCutClipboardCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewCutClipboardCallback :: C_TextViewCutClipboardCallback -> IO (FunPtr C_TextViewCutClipboardCallback)
genClosure_TextViewCutClipboard :: MonadIO m => TextViewCutClipboardCallback -> m (GClosure C_TextViewCutClipboardCallback)
genClosure_TextViewCutClipboard :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewCutClipboard IO ()
cb = IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewBackspaceCallback)
 -> m (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewCutClipboardCallback IO ()
cb
    C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewCutClipboardCallback C_TextViewBackspaceCallback
cb' IO (FunPtr C_TextViewBackspaceCallback)
-> (FunPtr C_TextViewBackspaceCallback
    -> IO (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewBackspaceCallback
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewCutClipboardCallback ::
    TextViewCutClipboardCallback ->
    C_TextViewCutClipboardCallback
wrap_TextViewCutClipboardCallback :: IO () -> C_TextViewBackspaceCallback
wrap_TextViewCutClipboardCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onTextViewCutClipboard :: (IsTextView a, MonadIO m) => a -> TextViewCutClipboardCallback -> m SignalHandlerId
onTextViewCutClipboard :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onTextViewCutClipboard a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewCutClipboardCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewCutClipboardCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"cut-clipboard" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewCutClipboard :: (IsTextView a, MonadIO m) => a -> TextViewCutClipboardCallback -> m SignalHandlerId
afterTextViewCutClipboard :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterTextViewCutClipboard a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewCutClipboardCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewCutClipboardCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"cut-clipboard" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewCutClipboardSignalInfo
instance SignalInfo TextViewCutClipboardSignalInfo where
    type HaskellCallbackType TextViewCutClipboardSignalInfo = TextViewCutClipboardCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewCutClipboardCallback cb
        cb'' <- mk_TextViewCutClipboardCallback cb'
        connectSignalFunPtr obj "cut-clipboard" cb'' connectMode detail
#endif
type TextViewDeleteFromCursorCallback =
    Gtk.Enums.DeleteType
    
    -> Int32
    
    -> IO ()
noTextViewDeleteFromCursorCallback :: Maybe TextViewDeleteFromCursorCallback
noTextViewDeleteFromCursorCallback :: Maybe TextViewDeleteFromCursorCallback
noTextViewDeleteFromCursorCallback = Maybe TextViewDeleteFromCursorCallback
forall a. Maybe a
Nothing
type C_TextViewDeleteFromCursorCallback =
    Ptr () ->                               
    CUInt ->
    Int32 ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewDeleteFromCursorCallback :: C_TextViewDeleteFromCursorCallback -> IO (FunPtr C_TextViewDeleteFromCursorCallback)
genClosure_TextViewDeleteFromCursor :: MonadIO m => TextViewDeleteFromCursorCallback -> m (GClosure C_TextViewDeleteFromCursorCallback)
genClosure_TextViewDeleteFromCursor :: forall (m :: * -> *).
MonadIO m =>
TextViewDeleteFromCursorCallback
-> m (GClosure C_TextViewDeleteFromCursorCallback)
genClosure_TextViewDeleteFromCursor TextViewDeleteFromCursorCallback
cb = IO (GClosure C_TextViewDeleteFromCursorCallback)
-> m (GClosure C_TextViewDeleteFromCursorCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewDeleteFromCursorCallback)
 -> m (GClosure C_TextViewDeleteFromCursorCallback))
-> IO (GClosure C_TextViewDeleteFromCursorCallback)
-> m (GClosure C_TextViewDeleteFromCursorCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewDeleteFromCursorCallback
cb' = TextViewDeleteFromCursorCallback
-> C_TextViewDeleteFromCursorCallback
wrap_TextViewDeleteFromCursorCallback TextViewDeleteFromCursorCallback
cb
    C_TextViewDeleteFromCursorCallback
-> IO (FunPtr C_TextViewDeleteFromCursorCallback)
mk_TextViewDeleteFromCursorCallback C_TextViewDeleteFromCursorCallback
cb' IO (FunPtr C_TextViewDeleteFromCursorCallback)
-> (FunPtr C_TextViewDeleteFromCursorCallback
    -> IO (GClosure C_TextViewDeleteFromCursorCallback))
-> IO (GClosure C_TextViewDeleteFromCursorCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewDeleteFromCursorCallback
-> IO (GClosure C_TextViewDeleteFromCursorCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewDeleteFromCursorCallback ::
    TextViewDeleteFromCursorCallback ->
    C_TextViewDeleteFromCursorCallback
wrap_TextViewDeleteFromCursorCallback :: TextViewDeleteFromCursorCallback
-> C_TextViewDeleteFromCursorCallback
wrap_TextViewDeleteFromCursorCallback TextViewDeleteFromCursorCallback
_cb Ptr ()
_ CUInt
type_ Int32
count Ptr ()
_ = do
    let type_' :: DeleteType
type_' = (Int -> DeleteType
forall a. Enum a => Int -> a
toEnum (Int -> DeleteType) -> (CUInt -> Int) -> CUInt -> DeleteType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
type_
    TextViewDeleteFromCursorCallback
_cb  DeleteType
type_' Int32
count
onTextViewDeleteFromCursor :: (IsTextView a, MonadIO m) => a -> TextViewDeleteFromCursorCallback -> m SignalHandlerId
onTextViewDeleteFromCursor :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewDeleteFromCursorCallback -> m SignalHandlerId
onTextViewDeleteFromCursor a
obj TextViewDeleteFromCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewDeleteFromCursorCallback
cb' = TextViewDeleteFromCursorCallback
-> C_TextViewDeleteFromCursorCallback
wrap_TextViewDeleteFromCursorCallback TextViewDeleteFromCursorCallback
cb
    FunPtr C_TextViewDeleteFromCursorCallback
cb'' <- C_TextViewDeleteFromCursorCallback
-> IO (FunPtr C_TextViewDeleteFromCursorCallback)
mk_TextViewDeleteFromCursorCallback C_TextViewDeleteFromCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewDeleteFromCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"delete-from-cursor" FunPtr C_TextViewDeleteFromCursorCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewDeleteFromCursor :: (IsTextView a, MonadIO m) => a -> TextViewDeleteFromCursorCallback -> m SignalHandlerId
afterTextViewDeleteFromCursor :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewDeleteFromCursorCallback -> m SignalHandlerId
afterTextViewDeleteFromCursor a
obj TextViewDeleteFromCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewDeleteFromCursorCallback
cb' = TextViewDeleteFromCursorCallback
-> C_TextViewDeleteFromCursorCallback
wrap_TextViewDeleteFromCursorCallback TextViewDeleteFromCursorCallback
cb
    FunPtr C_TextViewDeleteFromCursorCallback
cb'' <- C_TextViewDeleteFromCursorCallback
-> IO (FunPtr C_TextViewDeleteFromCursorCallback)
mk_TextViewDeleteFromCursorCallback C_TextViewDeleteFromCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewDeleteFromCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"delete-from-cursor" FunPtr C_TextViewDeleteFromCursorCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewDeleteFromCursorSignalInfo
instance SignalInfo TextViewDeleteFromCursorSignalInfo where
    type HaskellCallbackType TextViewDeleteFromCursorSignalInfo = TextViewDeleteFromCursorCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewDeleteFromCursorCallback cb
        cb'' <- mk_TextViewDeleteFromCursorCallback cb'
        connectSignalFunPtr obj "delete-from-cursor" cb'' connectMode detail
#endif
type TextViewExtendSelectionCallback =
    Gtk.Enums.TextExtendSelection
    
    -> Gtk.TextIter.TextIter
    
    -> Gtk.TextIter.TextIter
    
    -> Gtk.TextIter.TextIter
    
    -> IO Bool
    
    
noTextViewExtendSelectionCallback :: Maybe TextViewExtendSelectionCallback
noTextViewExtendSelectionCallback :: Maybe TextViewExtendSelectionCallback
noTextViewExtendSelectionCallback = Maybe TextViewExtendSelectionCallback
forall a. Maybe a
Nothing
type C_TextViewExtendSelectionCallback =
    Ptr () ->                               
    CUInt ->
    Ptr Gtk.TextIter.TextIter ->
    Ptr Gtk.TextIter.TextIter ->
    Ptr Gtk.TextIter.TextIter ->
    Ptr () ->                               
    IO CInt
foreign import ccall "wrapper"
    mk_TextViewExtendSelectionCallback :: C_TextViewExtendSelectionCallback -> IO (FunPtr C_TextViewExtendSelectionCallback)
genClosure_TextViewExtendSelection :: MonadIO m => TextViewExtendSelectionCallback -> m (GClosure C_TextViewExtendSelectionCallback)
genClosure_TextViewExtendSelection :: forall (m :: * -> *).
MonadIO m =>
TextViewExtendSelectionCallback
-> m (GClosure C_TextViewExtendSelectionCallback)
genClosure_TextViewExtendSelection TextViewExtendSelectionCallback
cb = IO (GClosure C_TextViewExtendSelectionCallback)
-> m (GClosure C_TextViewExtendSelectionCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewExtendSelectionCallback)
 -> m (GClosure C_TextViewExtendSelectionCallback))
-> IO (GClosure C_TextViewExtendSelectionCallback)
-> m (GClosure C_TextViewExtendSelectionCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewExtendSelectionCallback
cb' = TextViewExtendSelectionCallback
-> C_TextViewExtendSelectionCallback
wrap_TextViewExtendSelectionCallback TextViewExtendSelectionCallback
cb
    C_TextViewExtendSelectionCallback
-> IO (FunPtr C_TextViewExtendSelectionCallback)
mk_TextViewExtendSelectionCallback C_TextViewExtendSelectionCallback
cb' IO (FunPtr C_TextViewExtendSelectionCallback)
-> (FunPtr C_TextViewExtendSelectionCallback
    -> IO (GClosure C_TextViewExtendSelectionCallback))
-> IO (GClosure C_TextViewExtendSelectionCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewExtendSelectionCallback
-> IO (GClosure C_TextViewExtendSelectionCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewExtendSelectionCallback ::
    TextViewExtendSelectionCallback ->
    C_TextViewExtendSelectionCallback
wrap_TextViewExtendSelectionCallback :: TextViewExtendSelectionCallback
-> C_TextViewExtendSelectionCallback
wrap_TextViewExtendSelectionCallback TextViewExtendSelectionCallback
_cb Ptr ()
_ CUInt
granularity Ptr TextIter
location Ptr TextIter
start Ptr TextIter
end Ptr ()
_ = do
    let granularity' :: TextExtendSelection
granularity' = (Int -> TextExtendSelection
forall a. Enum a => Int -> a
toEnum (Int -> TextExtendSelection)
-> (CUInt -> Int) -> CUInt -> TextExtendSelection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
granularity
    (ManagedPtr TextIter -> TextIter)
-> Ptr TextIter -> (TextIter -> IO CInt) -> IO CInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr TextIter -> TextIter
Gtk.TextIter.TextIter Ptr TextIter
location ((TextIter -> IO CInt) -> IO CInt)
-> (TextIter -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \TextIter
location' -> do
        (ManagedPtr TextIter -> TextIter)
-> Ptr TextIter -> (TextIter -> IO CInt) -> IO CInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr TextIter -> TextIter
Gtk.TextIter.TextIter Ptr TextIter
start ((TextIter -> IO CInt) -> IO CInt)
-> (TextIter -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \TextIter
start' -> do
            (ManagedPtr TextIter -> TextIter)
-> Ptr TextIter -> (TextIter -> IO CInt) -> IO CInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr TextIter -> TextIter
Gtk.TextIter.TextIter Ptr TextIter
end ((TextIter -> IO CInt) -> IO CInt)
-> (TextIter -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \TextIter
end' -> do
                Bool
result <- TextViewExtendSelectionCallback
_cb  TextExtendSelection
granularity' TextIter
location' TextIter
start' TextIter
end'
                let result' :: CInt
result' = (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
result
                CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onTextViewExtendSelection :: (IsTextView a, MonadIO m) => a -> TextViewExtendSelectionCallback -> m SignalHandlerId
onTextViewExtendSelection :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewExtendSelectionCallback -> m SignalHandlerId
onTextViewExtendSelection a
obj TextViewExtendSelectionCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewExtendSelectionCallback
cb' = TextViewExtendSelectionCallback
-> C_TextViewExtendSelectionCallback
wrap_TextViewExtendSelectionCallback TextViewExtendSelectionCallback
cb
    FunPtr C_TextViewExtendSelectionCallback
cb'' <- C_TextViewExtendSelectionCallback
-> IO (FunPtr C_TextViewExtendSelectionCallback)
mk_TextViewExtendSelectionCallback C_TextViewExtendSelectionCallback
cb'
    a
-> Text
-> FunPtr C_TextViewExtendSelectionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"extend-selection" FunPtr C_TextViewExtendSelectionCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewExtendSelection :: (IsTextView a, MonadIO m) => a -> TextViewExtendSelectionCallback -> m SignalHandlerId
afterTextViewExtendSelection :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewExtendSelectionCallback -> m SignalHandlerId
afterTextViewExtendSelection a
obj TextViewExtendSelectionCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewExtendSelectionCallback
cb' = TextViewExtendSelectionCallback
-> C_TextViewExtendSelectionCallback
wrap_TextViewExtendSelectionCallback TextViewExtendSelectionCallback
cb
    FunPtr C_TextViewExtendSelectionCallback
cb'' <- C_TextViewExtendSelectionCallback
-> IO (FunPtr C_TextViewExtendSelectionCallback)
mk_TextViewExtendSelectionCallback C_TextViewExtendSelectionCallback
cb'
    a
-> Text
-> FunPtr C_TextViewExtendSelectionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"extend-selection" FunPtr C_TextViewExtendSelectionCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewExtendSelectionSignalInfo
instance SignalInfo TextViewExtendSelectionSignalInfo where
    type HaskellCallbackType TextViewExtendSelectionSignalInfo = TextViewExtendSelectionCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewExtendSelectionCallback cb
        cb'' <- mk_TextViewExtendSelectionCallback cb'
        connectSignalFunPtr obj "extend-selection" cb'' connectMode detail
#endif
type TextViewInsertAtCursorCallback =
    T.Text
    
    -> IO ()
noTextViewInsertAtCursorCallback :: Maybe TextViewInsertAtCursorCallback
noTextViewInsertAtCursorCallback :: Maybe TextViewInsertAtCursorCallback
noTextViewInsertAtCursorCallback = Maybe TextViewInsertAtCursorCallback
forall a. Maybe a
Nothing
type C_TextViewInsertAtCursorCallback =
    Ptr () ->                               
    CString ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewInsertAtCursorCallback :: C_TextViewInsertAtCursorCallback -> IO (FunPtr C_TextViewInsertAtCursorCallback)
genClosure_TextViewInsertAtCursor :: MonadIO m => TextViewInsertAtCursorCallback -> m (GClosure C_TextViewInsertAtCursorCallback)
genClosure_TextViewInsertAtCursor :: forall (m :: * -> *).
MonadIO m =>
TextViewInsertAtCursorCallback
-> m (GClosure C_TextViewInsertAtCursorCallback)
genClosure_TextViewInsertAtCursor TextViewInsertAtCursorCallback
cb = IO (GClosure C_TextViewInsertAtCursorCallback)
-> m (GClosure C_TextViewInsertAtCursorCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewInsertAtCursorCallback)
 -> m (GClosure C_TextViewInsertAtCursorCallback))
-> IO (GClosure C_TextViewInsertAtCursorCallback)
-> m (GClosure C_TextViewInsertAtCursorCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewInsertAtCursorCallback
cb' = TextViewInsertAtCursorCallback -> C_TextViewInsertAtCursorCallback
wrap_TextViewInsertAtCursorCallback TextViewInsertAtCursorCallback
cb
    C_TextViewInsertAtCursorCallback
-> IO (FunPtr C_TextViewInsertAtCursorCallback)
mk_TextViewInsertAtCursorCallback C_TextViewInsertAtCursorCallback
cb' IO (FunPtr C_TextViewInsertAtCursorCallback)
-> (FunPtr C_TextViewInsertAtCursorCallback
    -> IO (GClosure C_TextViewInsertAtCursorCallback))
-> IO (GClosure C_TextViewInsertAtCursorCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewInsertAtCursorCallback
-> IO (GClosure C_TextViewInsertAtCursorCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewInsertAtCursorCallback ::
    TextViewInsertAtCursorCallback ->
    C_TextViewInsertAtCursorCallback
wrap_TextViewInsertAtCursorCallback :: TextViewInsertAtCursorCallback -> C_TextViewInsertAtCursorCallback
wrap_TextViewInsertAtCursorCallback TextViewInsertAtCursorCallback
_cb Ptr ()
_ CString
string Ptr ()
_ = do
    Text
string' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
string
    TextViewInsertAtCursorCallback
_cb  Text
string'
onTextViewInsertAtCursor :: (IsTextView a, MonadIO m) => a -> TextViewInsertAtCursorCallback -> m SignalHandlerId
onTextViewInsertAtCursor :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewInsertAtCursorCallback -> m SignalHandlerId
onTextViewInsertAtCursor a
obj TextViewInsertAtCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewInsertAtCursorCallback
cb' = TextViewInsertAtCursorCallback -> C_TextViewInsertAtCursorCallback
wrap_TextViewInsertAtCursorCallback TextViewInsertAtCursorCallback
cb
    FunPtr C_TextViewInsertAtCursorCallback
cb'' <- C_TextViewInsertAtCursorCallback
-> IO (FunPtr C_TextViewInsertAtCursorCallback)
mk_TextViewInsertAtCursorCallback C_TextViewInsertAtCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewInsertAtCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"insert-at-cursor" FunPtr C_TextViewInsertAtCursorCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewInsertAtCursor :: (IsTextView a, MonadIO m) => a -> TextViewInsertAtCursorCallback -> m SignalHandlerId
afterTextViewInsertAtCursor :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewInsertAtCursorCallback -> m SignalHandlerId
afterTextViewInsertAtCursor a
obj TextViewInsertAtCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewInsertAtCursorCallback
cb' = TextViewInsertAtCursorCallback -> C_TextViewInsertAtCursorCallback
wrap_TextViewInsertAtCursorCallback TextViewInsertAtCursorCallback
cb
    FunPtr C_TextViewInsertAtCursorCallback
cb'' <- C_TextViewInsertAtCursorCallback
-> IO (FunPtr C_TextViewInsertAtCursorCallback)
mk_TextViewInsertAtCursorCallback C_TextViewInsertAtCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewInsertAtCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"insert-at-cursor" FunPtr C_TextViewInsertAtCursorCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewInsertAtCursorSignalInfo
instance SignalInfo TextViewInsertAtCursorSignalInfo where
    type HaskellCallbackType TextViewInsertAtCursorSignalInfo = TextViewInsertAtCursorCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewInsertAtCursorCallback cb
        cb'' <- mk_TextViewInsertAtCursorCallback cb'
        connectSignalFunPtr obj "insert-at-cursor" cb'' connectMode detail
#endif
type TextViewInsertEmojiCallback =
    IO ()
noTextViewInsertEmojiCallback :: Maybe TextViewInsertEmojiCallback
noTextViewInsertEmojiCallback :: Maybe (IO ())
noTextViewInsertEmojiCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_TextViewInsertEmojiCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewInsertEmojiCallback :: C_TextViewInsertEmojiCallback -> IO (FunPtr C_TextViewInsertEmojiCallback)
genClosure_TextViewInsertEmoji :: MonadIO m => TextViewInsertEmojiCallback -> m (GClosure C_TextViewInsertEmojiCallback)
genClosure_TextViewInsertEmoji :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewInsertEmoji IO ()
cb = IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewBackspaceCallback)
 -> m (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewInsertEmojiCallback IO ()
cb
    C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewInsertEmojiCallback C_TextViewBackspaceCallback
cb' IO (FunPtr C_TextViewBackspaceCallback)
-> (FunPtr C_TextViewBackspaceCallback
    -> IO (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewBackspaceCallback
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewInsertEmojiCallback ::
    TextViewInsertEmojiCallback ->
    C_TextViewInsertEmojiCallback
wrap_TextViewInsertEmojiCallback :: IO () -> C_TextViewBackspaceCallback
wrap_TextViewInsertEmojiCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onTextViewInsertEmoji :: (IsTextView a, MonadIO m) => a -> TextViewInsertEmojiCallback -> m SignalHandlerId
onTextViewInsertEmoji :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onTextViewInsertEmoji a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewInsertEmojiCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewInsertEmojiCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"insert-emoji" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewInsertEmoji :: (IsTextView a, MonadIO m) => a -> TextViewInsertEmojiCallback -> m SignalHandlerId
afterTextViewInsertEmoji :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterTextViewInsertEmoji a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewInsertEmojiCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewInsertEmojiCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"insert-emoji" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewInsertEmojiSignalInfo
instance SignalInfo TextViewInsertEmojiSignalInfo where
    type HaskellCallbackType TextViewInsertEmojiSignalInfo = TextViewInsertEmojiCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewInsertEmojiCallback cb
        cb'' <- mk_TextViewInsertEmojiCallback cb'
        connectSignalFunPtr obj "insert-emoji" cb'' connectMode detail
#endif
type TextViewMoveCursorCallback =
    Gtk.Enums.MovementStep
    
    -> Int32
    
    -> Bool
    
    -> IO ()
noTextViewMoveCursorCallback :: Maybe TextViewMoveCursorCallback
noTextViewMoveCursorCallback :: Maybe TextViewMoveCursorCallback
noTextViewMoveCursorCallback = Maybe TextViewMoveCursorCallback
forall a. Maybe a
Nothing
type C_TextViewMoveCursorCallback =
    Ptr () ->                               
    CUInt ->
    Int32 ->
    CInt ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewMoveCursorCallback :: C_TextViewMoveCursorCallback -> IO (FunPtr C_TextViewMoveCursorCallback)
genClosure_TextViewMoveCursor :: MonadIO m => TextViewMoveCursorCallback -> m (GClosure C_TextViewMoveCursorCallback)
genClosure_TextViewMoveCursor :: forall (m :: * -> *).
MonadIO m =>
TextViewMoveCursorCallback
-> m (GClosure C_TextViewMoveCursorCallback)
genClosure_TextViewMoveCursor TextViewMoveCursorCallback
cb = IO (GClosure C_TextViewMoveCursorCallback)
-> m (GClosure C_TextViewMoveCursorCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewMoveCursorCallback)
 -> m (GClosure C_TextViewMoveCursorCallback))
-> IO (GClosure C_TextViewMoveCursorCallback)
-> m (GClosure C_TextViewMoveCursorCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewMoveCursorCallback
cb' = TextViewMoveCursorCallback -> C_TextViewMoveCursorCallback
wrap_TextViewMoveCursorCallback TextViewMoveCursorCallback
cb
    C_TextViewMoveCursorCallback
-> IO (FunPtr C_TextViewMoveCursorCallback)
mk_TextViewMoveCursorCallback C_TextViewMoveCursorCallback
cb' IO (FunPtr C_TextViewMoveCursorCallback)
-> (FunPtr C_TextViewMoveCursorCallback
    -> IO (GClosure C_TextViewMoveCursorCallback))
-> IO (GClosure C_TextViewMoveCursorCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewMoveCursorCallback
-> IO (GClosure C_TextViewMoveCursorCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewMoveCursorCallback ::
    TextViewMoveCursorCallback ->
    C_TextViewMoveCursorCallback
wrap_TextViewMoveCursorCallback :: TextViewMoveCursorCallback -> C_TextViewMoveCursorCallback
wrap_TextViewMoveCursorCallback TextViewMoveCursorCallback
_cb Ptr ()
_ CUInt
step Int32
count CInt
extendSelection Ptr ()
_ = do
    let step' :: MovementStep
step' = (Int -> MovementStep
forall a. Enum a => Int -> a
toEnum (Int -> MovementStep) -> (CUInt -> Int) -> CUInt -> MovementStep
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
step
    let extendSelection' :: Bool
extendSelection' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
extendSelection
    TextViewMoveCursorCallback
_cb  MovementStep
step' Int32
count Bool
extendSelection'
onTextViewMoveCursor :: (IsTextView a, MonadIO m) => a -> TextViewMoveCursorCallback -> m SignalHandlerId
onTextViewMoveCursor :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewMoveCursorCallback -> m SignalHandlerId
onTextViewMoveCursor a
obj TextViewMoveCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewMoveCursorCallback
cb' = TextViewMoveCursorCallback -> C_TextViewMoveCursorCallback
wrap_TextViewMoveCursorCallback TextViewMoveCursorCallback
cb
    FunPtr C_TextViewMoveCursorCallback
cb'' <- C_TextViewMoveCursorCallback
-> IO (FunPtr C_TextViewMoveCursorCallback)
mk_TextViewMoveCursorCallback C_TextViewMoveCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewMoveCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"move-cursor" FunPtr C_TextViewMoveCursorCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewMoveCursor :: (IsTextView a, MonadIO m) => a -> TextViewMoveCursorCallback -> m SignalHandlerId
afterTextViewMoveCursor :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewMoveCursorCallback -> m SignalHandlerId
afterTextViewMoveCursor a
obj TextViewMoveCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewMoveCursorCallback
cb' = TextViewMoveCursorCallback -> C_TextViewMoveCursorCallback
wrap_TextViewMoveCursorCallback TextViewMoveCursorCallback
cb
    FunPtr C_TextViewMoveCursorCallback
cb'' <- C_TextViewMoveCursorCallback
-> IO (FunPtr C_TextViewMoveCursorCallback)
mk_TextViewMoveCursorCallback C_TextViewMoveCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewMoveCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"move-cursor" FunPtr C_TextViewMoveCursorCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewMoveCursorSignalInfo
instance SignalInfo TextViewMoveCursorSignalInfo where
    type HaskellCallbackType TextViewMoveCursorSignalInfo = TextViewMoveCursorCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewMoveCursorCallback cb
        cb'' <- mk_TextViewMoveCursorCallback cb'
        connectSignalFunPtr obj "move-cursor" cb'' connectMode detail
#endif
type TextViewMoveViewportCallback =
    Gtk.Enums.ScrollStep
    
    -> Int32
    
    -> IO ()
noTextViewMoveViewportCallback :: Maybe TextViewMoveViewportCallback
noTextViewMoveViewportCallback :: Maybe TextViewMoveViewportCallback
noTextViewMoveViewportCallback = Maybe TextViewMoveViewportCallback
forall a. Maybe a
Nothing
type C_TextViewMoveViewportCallback =
    Ptr () ->                               
    CUInt ->
    Int32 ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewMoveViewportCallback :: C_TextViewMoveViewportCallback -> IO (FunPtr C_TextViewMoveViewportCallback)
genClosure_TextViewMoveViewport :: MonadIO m => TextViewMoveViewportCallback -> m (GClosure C_TextViewMoveViewportCallback)
genClosure_TextViewMoveViewport :: forall (m :: * -> *).
MonadIO m =>
TextViewMoveViewportCallback
-> m (GClosure C_TextViewDeleteFromCursorCallback)
genClosure_TextViewMoveViewport TextViewMoveViewportCallback
cb = IO (GClosure C_TextViewDeleteFromCursorCallback)
-> m (GClosure C_TextViewDeleteFromCursorCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewDeleteFromCursorCallback)
 -> m (GClosure C_TextViewDeleteFromCursorCallback))
-> IO (GClosure C_TextViewDeleteFromCursorCallback)
-> m (GClosure C_TextViewDeleteFromCursorCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewDeleteFromCursorCallback
cb' = TextViewMoveViewportCallback -> C_TextViewDeleteFromCursorCallback
wrap_TextViewMoveViewportCallback TextViewMoveViewportCallback
cb
    C_TextViewDeleteFromCursorCallback
-> IO (FunPtr C_TextViewDeleteFromCursorCallback)
mk_TextViewMoveViewportCallback C_TextViewDeleteFromCursorCallback
cb' IO (FunPtr C_TextViewDeleteFromCursorCallback)
-> (FunPtr C_TextViewDeleteFromCursorCallback
    -> IO (GClosure C_TextViewDeleteFromCursorCallback))
-> IO (GClosure C_TextViewDeleteFromCursorCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewDeleteFromCursorCallback
-> IO (GClosure C_TextViewDeleteFromCursorCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewMoveViewportCallback ::
    TextViewMoveViewportCallback ->
    C_TextViewMoveViewportCallback
wrap_TextViewMoveViewportCallback :: TextViewMoveViewportCallback -> C_TextViewDeleteFromCursorCallback
wrap_TextViewMoveViewportCallback TextViewMoveViewportCallback
_cb Ptr ()
_ CUInt
step Int32
count Ptr ()
_ = do
    let step' :: ScrollStep
step' = (Int -> ScrollStep
forall a. Enum a => Int -> a
toEnum (Int -> ScrollStep) -> (CUInt -> Int) -> CUInt -> ScrollStep
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
step
    TextViewMoveViewportCallback
_cb  ScrollStep
step' Int32
count
onTextViewMoveViewport :: (IsTextView a, MonadIO m) => a -> TextViewMoveViewportCallback -> m SignalHandlerId
onTextViewMoveViewport :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewMoveViewportCallback -> m SignalHandlerId
onTextViewMoveViewport a
obj TextViewMoveViewportCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewDeleteFromCursorCallback
cb' = TextViewMoveViewportCallback -> C_TextViewDeleteFromCursorCallback
wrap_TextViewMoveViewportCallback TextViewMoveViewportCallback
cb
    FunPtr C_TextViewDeleteFromCursorCallback
cb'' <- C_TextViewDeleteFromCursorCallback
-> IO (FunPtr C_TextViewDeleteFromCursorCallback)
mk_TextViewMoveViewportCallback C_TextViewDeleteFromCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewDeleteFromCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"move-viewport" FunPtr C_TextViewDeleteFromCursorCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewMoveViewport :: (IsTextView a, MonadIO m) => a -> TextViewMoveViewportCallback -> m SignalHandlerId
afterTextViewMoveViewport :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewMoveViewportCallback -> m SignalHandlerId
afterTextViewMoveViewport a
obj TextViewMoveViewportCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewDeleteFromCursorCallback
cb' = TextViewMoveViewportCallback -> C_TextViewDeleteFromCursorCallback
wrap_TextViewMoveViewportCallback TextViewMoveViewportCallback
cb
    FunPtr C_TextViewDeleteFromCursorCallback
cb'' <- C_TextViewDeleteFromCursorCallback
-> IO (FunPtr C_TextViewDeleteFromCursorCallback)
mk_TextViewMoveViewportCallback C_TextViewDeleteFromCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewDeleteFromCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"move-viewport" FunPtr C_TextViewDeleteFromCursorCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewMoveViewportSignalInfo
instance SignalInfo TextViewMoveViewportSignalInfo where
    type HaskellCallbackType TextViewMoveViewportSignalInfo = TextViewMoveViewportCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewMoveViewportCallback cb
        cb'' <- mk_TextViewMoveViewportCallback cb'
        connectSignalFunPtr obj "move-viewport" cb'' connectMode detail
#endif
type TextViewPasteClipboardCallback =
    IO ()
noTextViewPasteClipboardCallback :: Maybe TextViewPasteClipboardCallback
noTextViewPasteClipboardCallback :: Maybe (IO ())
noTextViewPasteClipboardCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_TextViewPasteClipboardCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewPasteClipboardCallback :: C_TextViewPasteClipboardCallback -> IO (FunPtr C_TextViewPasteClipboardCallback)
genClosure_TextViewPasteClipboard :: MonadIO m => TextViewPasteClipboardCallback -> m (GClosure C_TextViewPasteClipboardCallback)
genClosure_TextViewPasteClipboard :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewPasteClipboard IO ()
cb = IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewBackspaceCallback)
 -> m (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewPasteClipboardCallback IO ()
cb
    C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewPasteClipboardCallback C_TextViewBackspaceCallback
cb' IO (FunPtr C_TextViewBackspaceCallback)
-> (FunPtr C_TextViewBackspaceCallback
    -> IO (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewBackspaceCallback
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewPasteClipboardCallback ::
    TextViewPasteClipboardCallback ->
    C_TextViewPasteClipboardCallback
wrap_TextViewPasteClipboardCallback :: IO () -> C_TextViewBackspaceCallback
wrap_TextViewPasteClipboardCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onTextViewPasteClipboard :: (IsTextView a, MonadIO m) => a -> TextViewPasteClipboardCallback -> m SignalHandlerId
onTextViewPasteClipboard :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onTextViewPasteClipboard a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewPasteClipboardCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewPasteClipboardCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"paste-clipboard" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewPasteClipboard :: (IsTextView a, MonadIO m) => a -> TextViewPasteClipboardCallback -> m SignalHandlerId
afterTextViewPasteClipboard :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterTextViewPasteClipboard a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewPasteClipboardCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewPasteClipboardCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"paste-clipboard" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewPasteClipboardSignalInfo
instance SignalInfo TextViewPasteClipboardSignalInfo where
    type HaskellCallbackType TextViewPasteClipboardSignalInfo = TextViewPasteClipboardCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewPasteClipboardCallback cb
        cb'' <- mk_TextViewPasteClipboardCallback cb'
        connectSignalFunPtr obj "paste-clipboard" cb'' connectMode detail
#endif
type TextViewPreeditChangedCallback =
    T.Text
    
    -> IO ()
noTextViewPreeditChangedCallback :: Maybe TextViewPreeditChangedCallback
noTextViewPreeditChangedCallback :: Maybe TextViewInsertAtCursorCallback
noTextViewPreeditChangedCallback = Maybe TextViewInsertAtCursorCallback
forall a. Maybe a
Nothing
type C_TextViewPreeditChangedCallback =
    Ptr () ->                               
    CString ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewPreeditChangedCallback :: C_TextViewPreeditChangedCallback -> IO (FunPtr C_TextViewPreeditChangedCallback)
genClosure_TextViewPreeditChanged :: MonadIO m => TextViewPreeditChangedCallback -> m (GClosure C_TextViewPreeditChangedCallback)
genClosure_TextViewPreeditChanged :: forall (m :: * -> *).
MonadIO m =>
TextViewInsertAtCursorCallback
-> m (GClosure C_TextViewInsertAtCursorCallback)
genClosure_TextViewPreeditChanged TextViewInsertAtCursorCallback
cb = IO (GClosure C_TextViewInsertAtCursorCallback)
-> m (GClosure C_TextViewInsertAtCursorCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewInsertAtCursorCallback)
 -> m (GClosure C_TextViewInsertAtCursorCallback))
-> IO (GClosure C_TextViewInsertAtCursorCallback)
-> m (GClosure C_TextViewInsertAtCursorCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewInsertAtCursorCallback
cb' = TextViewInsertAtCursorCallback -> C_TextViewInsertAtCursorCallback
wrap_TextViewPreeditChangedCallback TextViewInsertAtCursorCallback
cb
    C_TextViewInsertAtCursorCallback
-> IO (FunPtr C_TextViewInsertAtCursorCallback)
mk_TextViewPreeditChangedCallback C_TextViewInsertAtCursorCallback
cb' IO (FunPtr C_TextViewInsertAtCursorCallback)
-> (FunPtr C_TextViewInsertAtCursorCallback
    -> IO (GClosure C_TextViewInsertAtCursorCallback))
-> IO (GClosure C_TextViewInsertAtCursorCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewInsertAtCursorCallback
-> IO (GClosure C_TextViewInsertAtCursorCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewPreeditChangedCallback ::
    TextViewPreeditChangedCallback ->
    C_TextViewPreeditChangedCallback
wrap_TextViewPreeditChangedCallback :: TextViewInsertAtCursorCallback -> C_TextViewInsertAtCursorCallback
wrap_TextViewPreeditChangedCallback TextViewInsertAtCursorCallback
_cb Ptr ()
_ CString
preedit Ptr ()
_ = do
    Text
preedit' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
preedit
    TextViewInsertAtCursorCallback
_cb  Text
preedit'
onTextViewPreeditChanged :: (IsTextView a, MonadIO m) => a -> TextViewPreeditChangedCallback -> m SignalHandlerId
onTextViewPreeditChanged :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewInsertAtCursorCallback -> m SignalHandlerId
onTextViewPreeditChanged a
obj TextViewInsertAtCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewInsertAtCursorCallback
cb' = TextViewInsertAtCursorCallback -> C_TextViewInsertAtCursorCallback
wrap_TextViewPreeditChangedCallback TextViewInsertAtCursorCallback
cb
    FunPtr C_TextViewInsertAtCursorCallback
cb'' <- C_TextViewInsertAtCursorCallback
-> IO (FunPtr C_TextViewInsertAtCursorCallback)
mk_TextViewPreeditChangedCallback C_TextViewInsertAtCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewInsertAtCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"preedit-changed" FunPtr C_TextViewInsertAtCursorCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewPreeditChanged :: (IsTextView a, MonadIO m) => a -> TextViewPreeditChangedCallback -> m SignalHandlerId
afterTextViewPreeditChanged :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewInsertAtCursorCallback -> m SignalHandlerId
afterTextViewPreeditChanged a
obj TextViewInsertAtCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewInsertAtCursorCallback
cb' = TextViewInsertAtCursorCallback -> C_TextViewInsertAtCursorCallback
wrap_TextViewPreeditChangedCallback TextViewInsertAtCursorCallback
cb
    FunPtr C_TextViewInsertAtCursorCallback
cb'' <- C_TextViewInsertAtCursorCallback
-> IO (FunPtr C_TextViewInsertAtCursorCallback)
mk_TextViewPreeditChangedCallback C_TextViewInsertAtCursorCallback
cb'
    a
-> Text
-> FunPtr C_TextViewInsertAtCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"preedit-changed" FunPtr C_TextViewInsertAtCursorCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewPreeditChangedSignalInfo
instance SignalInfo TextViewPreeditChangedSignalInfo where
    type HaskellCallbackType TextViewPreeditChangedSignalInfo = TextViewPreeditChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewPreeditChangedCallback cb
        cb'' <- mk_TextViewPreeditChangedCallback cb'
        connectSignalFunPtr obj "preedit-changed" cb'' connectMode detail
#endif
type TextViewSelectAllCallback =
    Bool
    
    -> IO ()
noTextViewSelectAllCallback :: Maybe TextViewSelectAllCallback
noTextViewSelectAllCallback :: Maybe TextViewSelectAllCallback
noTextViewSelectAllCallback = Maybe TextViewSelectAllCallback
forall a. Maybe a
Nothing
type C_TextViewSelectAllCallback =
    Ptr () ->                               
    CInt ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewSelectAllCallback :: C_TextViewSelectAllCallback -> IO (FunPtr C_TextViewSelectAllCallback)
genClosure_TextViewSelectAll :: MonadIO m => TextViewSelectAllCallback -> m (GClosure C_TextViewSelectAllCallback)
genClosure_TextViewSelectAll :: forall (m :: * -> *).
MonadIO m =>
TextViewSelectAllCallback
-> m (GClosure C_TextViewSelectAllCallback)
genClosure_TextViewSelectAll TextViewSelectAllCallback
cb = IO (GClosure C_TextViewSelectAllCallback)
-> m (GClosure C_TextViewSelectAllCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewSelectAllCallback)
 -> m (GClosure C_TextViewSelectAllCallback))
-> IO (GClosure C_TextViewSelectAllCallback)
-> m (GClosure C_TextViewSelectAllCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewSelectAllCallback
cb' = TextViewSelectAllCallback -> C_TextViewSelectAllCallback
wrap_TextViewSelectAllCallback TextViewSelectAllCallback
cb
    C_TextViewSelectAllCallback
-> IO (FunPtr C_TextViewSelectAllCallback)
mk_TextViewSelectAllCallback C_TextViewSelectAllCallback
cb' IO (FunPtr C_TextViewSelectAllCallback)
-> (FunPtr C_TextViewSelectAllCallback
    -> IO (GClosure C_TextViewSelectAllCallback))
-> IO (GClosure C_TextViewSelectAllCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewSelectAllCallback
-> IO (GClosure C_TextViewSelectAllCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewSelectAllCallback ::
    TextViewSelectAllCallback ->
    C_TextViewSelectAllCallback
wrap_TextViewSelectAllCallback :: TextViewSelectAllCallback -> C_TextViewSelectAllCallback
wrap_TextViewSelectAllCallback TextViewSelectAllCallback
_cb Ptr ()
_ CInt
select Ptr ()
_ = do
    let select' :: Bool
select' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
select
    TextViewSelectAllCallback
_cb  Bool
select'
onTextViewSelectAll :: (IsTextView a, MonadIO m) => a -> TextViewSelectAllCallback -> m SignalHandlerId
onTextViewSelectAll :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewSelectAllCallback -> m SignalHandlerId
onTextViewSelectAll a
obj TextViewSelectAllCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewSelectAllCallback
cb' = TextViewSelectAllCallback -> C_TextViewSelectAllCallback
wrap_TextViewSelectAllCallback TextViewSelectAllCallback
cb
    FunPtr C_TextViewSelectAllCallback
cb'' <- C_TextViewSelectAllCallback
-> IO (FunPtr C_TextViewSelectAllCallback)
mk_TextViewSelectAllCallback C_TextViewSelectAllCallback
cb'
    a
-> Text
-> FunPtr C_TextViewSelectAllCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"select-all" FunPtr C_TextViewSelectAllCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewSelectAll :: (IsTextView a, MonadIO m) => a -> TextViewSelectAllCallback -> m SignalHandlerId
afterTextViewSelectAll :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> TextViewSelectAllCallback -> m SignalHandlerId
afterTextViewSelectAll a
obj TextViewSelectAllCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewSelectAllCallback
cb' = TextViewSelectAllCallback -> C_TextViewSelectAllCallback
wrap_TextViewSelectAllCallback TextViewSelectAllCallback
cb
    FunPtr C_TextViewSelectAllCallback
cb'' <- C_TextViewSelectAllCallback
-> IO (FunPtr C_TextViewSelectAllCallback)
mk_TextViewSelectAllCallback C_TextViewSelectAllCallback
cb'
    a
-> Text
-> FunPtr C_TextViewSelectAllCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"select-all" FunPtr C_TextViewSelectAllCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewSelectAllSignalInfo
instance SignalInfo TextViewSelectAllSignalInfo where
    type HaskellCallbackType TextViewSelectAllSignalInfo = TextViewSelectAllCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewSelectAllCallback cb
        cb'' <- mk_TextViewSelectAllCallback cb'
        connectSignalFunPtr obj "select-all" cb'' connectMode detail
#endif
type TextViewSetAnchorCallback =
    IO ()
noTextViewSetAnchorCallback :: Maybe TextViewSetAnchorCallback
noTextViewSetAnchorCallback :: Maybe (IO ())
noTextViewSetAnchorCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_TextViewSetAnchorCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewSetAnchorCallback :: C_TextViewSetAnchorCallback -> IO (FunPtr C_TextViewSetAnchorCallback)
genClosure_TextViewSetAnchor :: MonadIO m => TextViewSetAnchorCallback -> m (GClosure C_TextViewSetAnchorCallback)
genClosure_TextViewSetAnchor :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewSetAnchor IO ()
cb = IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewBackspaceCallback)
 -> m (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewSetAnchorCallback IO ()
cb
    C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewSetAnchorCallback C_TextViewBackspaceCallback
cb' IO (FunPtr C_TextViewBackspaceCallback)
-> (FunPtr C_TextViewBackspaceCallback
    -> IO (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewBackspaceCallback
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewSetAnchorCallback ::
    TextViewSetAnchorCallback ->
    C_TextViewSetAnchorCallback
wrap_TextViewSetAnchorCallback :: IO () -> C_TextViewBackspaceCallback
wrap_TextViewSetAnchorCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onTextViewSetAnchor :: (IsTextView a, MonadIO m) => a -> TextViewSetAnchorCallback -> m SignalHandlerId
onTextViewSetAnchor :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onTextViewSetAnchor a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewSetAnchorCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewSetAnchorCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"set-anchor" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewSetAnchor :: (IsTextView a, MonadIO m) => a -> TextViewSetAnchorCallback -> m SignalHandlerId
afterTextViewSetAnchor :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterTextViewSetAnchor a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewSetAnchorCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewSetAnchorCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"set-anchor" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewSetAnchorSignalInfo
instance SignalInfo TextViewSetAnchorSignalInfo where
    type HaskellCallbackType TextViewSetAnchorSignalInfo = TextViewSetAnchorCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewSetAnchorCallback cb
        cb'' <- mk_TextViewSetAnchorCallback cb'
        connectSignalFunPtr obj "set-anchor" cb'' connectMode detail
#endif
type TextViewToggleCursorVisibleCallback =
    IO ()
noTextViewToggleCursorVisibleCallback :: Maybe TextViewToggleCursorVisibleCallback
noTextViewToggleCursorVisibleCallback :: Maybe (IO ())
noTextViewToggleCursorVisibleCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_TextViewToggleCursorVisibleCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewToggleCursorVisibleCallback :: C_TextViewToggleCursorVisibleCallback -> IO (FunPtr C_TextViewToggleCursorVisibleCallback)
genClosure_TextViewToggleCursorVisible :: MonadIO m => TextViewToggleCursorVisibleCallback -> m (GClosure C_TextViewToggleCursorVisibleCallback)
genClosure_TextViewToggleCursorVisible :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewToggleCursorVisible IO ()
cb = IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewBackspaceCallback)
 -> m (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewToggleCursorVisibleCallback IO ()
cb
    C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewToggleCursorVisibleCallback C_TextViewBackspaceCallback
cb' IO (FunPtr C_TextViewBackspaceCallback)
-> (FunPtr C_TextViewBackspaceCallback
    -> IO (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewBackspaceCallback
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewToggleCursorVisibleCallback ::
    TextViewToggleCursorVisibleCallback ->
    C_TextViewToggleCursorVisibleCallback
wrap_TextViewToggleCursorVisibleCallback :: IO () -> C_TextViewBackspaceCallback
wrap_TextViewToggleCursorVisibleCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onTextViewToggleCursorVisible :: (IsTextView a, MonadIO m) => a -> TextViewToggleCursorVisibleCallback -> m SignalHandlerId
onTextViewToggleCursorVisible :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onTextViewToggleCursorVisible a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewToggleCursorVisibleCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewToggleCursorVisibleCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"toggle-cursor-visible" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewToggleCursorVisible :: (IsTextView a, MonadIO m) => a -> TextViewToggleCursorVisibleCallback -> m SignalHandlerId
afterTextViewToggleCursorVisible :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterTextViewToggleCursorVisible a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewToggleCursorVisibleCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewToggleCursorVisibleCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"toggle-cursor-visible" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewToggleCursorVisibleSignalInfo
instance SignalInfo TextViewToggleCursorVisibleSignalInfo where
    type HaskellCallbackType TextViewToggleCursorVisibleSignalInfo = TextViewToggleCursorVisibleCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewToggleCursorVisibleCallback cb
        cb'' <- mk_TextViewToggleCursorVisibleCallback cb'
        connectSignalFunPtr obj "toggle-cursor-visible" cb'' connectMode detail
#endif
type TextViewToggleOverwriteCallback =
    IO ()
noTextViewToggleOverwriteCallback :: Maybe TextViewToggleOverwriteCallback
noTextViewToggleOverwriteCallback :: Maybe (IO ())
noTextViewToggleOverwriteCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_TextViewToggleOverwriteCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_TextViewToggleOverwriteCallback :: C_TextViewToggleOverwriteCallback -> IO (FunPtr C_TextViewToggleOverwriteCallback)
genClosure_TextViewToggleOverwrite :: MonadIO m => TextViewToggleOverwriteCallback -> m (GClosure C_TextViewToggleOverwriteCallback)
genClosure_TextViewToggleOverwrite :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_TextViewBackspaceCallback)
genClosure_TextViewToggleOverwrite IO ()
cb = IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_TextViewBackspaceCallback)
 -> m (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
-> m (GClosure C_TextViewBackspaceCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewToggleOverwriteCallback IO ()
cb
    C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewToggleOverwriteCallback C_TextViewBackspaceCallback
cb' IO (FunPtr C_TextViewBackspaceCallback)
-> (FunPtr C_TextViewBackspaceCallback
    -> IO (GClosure C_TextViewBackspaceCallback))
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_TextViewBackspaceCallback
-> IO (GClosure C_TextViewBackspaceCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_TextViewToggleOverwriteCallback ::
    TextViewToggleOverwriteCallback ->
    C_TextViewToggleOverwriteCallback
wrap_TextViewToggleOverwriteCallback :: IO () -> C_TextViewBackspaceCallback
wrap_TextViewToggleOverwriteCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onTextViewToggleOverwrite :: (IsTextView a, MonadIO m) => a -> TextViewToggleOverwriteCallback -> m SignalHandlerId
onTextViewToggleOverwrite :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onTextViewToggleOverwrite a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewToggleOverwriteCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewToggleOverwriteCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"toggle-overwrite" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTextViewToggleOverwrite :: (IsTextView a, MonadIO m) => a -> TextViewToggleOverwriteCallback -> m SignalHandlerId
afterTextViewToggleOverwrite :: forall a (m :: * -> *).
(IsTextView a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterTextViewToggleOverwrite a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_TextViewBackspaceCallback
cb' = IO () -> C_TextViewBackspaceCallback
wrap_TextViewToggleOverwriteCallback IO ()
cb
    FunPtr C_TextViewBackspaceCallback
cb'' <- C_TextViewBackspaceCallback
-> IO (FunPtr C_TextViewBackspaceCallback)
mk_TextViewToggleOverwriteCallback C_TextViewBackspaceCallback
cb'
    a
-> Text
-> FunPtr C_TextViewBackspaceCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"toggle-overwrite" FunPtr C_TextViewBackspaceCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TextViewToggleOverwriteSignalInfo
instance SignalInfo TextViewToggleOverwriteSignalInfo where
    type HaskellCallbackType TextViewToggleOverwriteSignalInfo = TextViewToggleOverwriteCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TextViewToggleOverwriteCallback cb
        cb'' <- mk_TextViewToggleOverwriteCallback cb'
        connectSignalFunPtr obj "toggle-overwrite" cb'' connectMode detail
#endif
   
   
   
getTextViewAcceptsTab :: (MonadIO m, IsTextView o) => o -> m Bool
getTextViewAcceptsTab :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Bool
getTextViewAcceptsTab o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"accepts-tab"
setTextViewAcceptsTab :: (MonadIO m, IsTextView o) => o -> Bool -> m ()
setTextViewAcceptsTab :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Bool -> m ()
setTextViewAcceptsTab o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> TextViewSelectAllCallback
forall a. GObject a => a -> String -> TextViewSelectAllCallback
B.Properties.setObjectPropertyBool o
obj String
"accepts-tab" Bool
val
constructTextViewAcceptsTab :: (IsTextView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTextViewAcceptsTab :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTextViewAcceptsTab Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"accepts-tab" Bool
val
#if defined(ENABLE_OVERLOADING)
data TextViewAcceptsTabPropertyInfo
instance AttrInfo TextViewAcceptsTabPropertyInfo where
    type AttrAllowedOps TextViewAcceptsTabPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewAcceptsTabPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewAcceptsTabPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TextViewAcceptsTabPropertyInfo = (~) Bool
    type AttrTransferType TextViewAcceptsTabPropertyInfo = Bool
    type AttrGetType TextViewAcceptsTabPropertyInfo = Bool
    type AttrLabel TextViewAcceptsTabPropertyInfo = "accepts-tab"
    type AttrOrigin TextViewAcceptsTabPropertyInfo = TextView
    attrGet = getTextViewAcceptsTab
    attrSet = setTextViewAcceptsTab
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewAcceptsTab
    attrClear = undefined
#endif
   
   
   
getTextViewBottomMargin :: (MonadIO m, IsTextView o) => o -> m Int32
getTextViewBottomMargin :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Int32
getTextViewBottomMargin o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"bottom-margin"
setTextViewBottomMargin :: (MonadIO m, IsTextView o) => o -> Int32 -> m ()
setTextViewBottomMargin :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Int32 -> m ()
setTextViewBottomMargin o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"bottom-margin" Int32
val
constructTextViewBottomMargin :: (IsTextView o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructTextViewBottomMargin :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructTextViewBottomMargin Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"bottom-margin" Int32
val
#if defined(ENABLE_OVERLOADING)
data TextViewBottomMarginPropertyInfo
instance AttrInfo TextViewBottomMarginPropertyInfo where
    type AttrAllowedOps TextViewBottomMarginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewBottomMarginPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewBottomMarginPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint TextViewBottomMarginPropertyInfo = (~) Int32
    type AttrTransferType TextViewBottomMarginPropertyInfo = Int32
    type AttrGetType TextViewBottomMarginPropertyInfo = Int32
    type AttrLabel TextViewBottomMarginPropertyInfo = "bottom-margin"
    type AttrOrigin TextViewBottomMarginPropertyInfo = TextView
    attrGet = getTextViewBottomMargin
    attrSet = setTextViewBottomMargin
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewBottomMargin
    attrClear = undefined
#endif
   
   
   
getTextViewBuffer :: (MonadIO m, IsTextView o) => o -> m Gtk.TextBuffer.TextBuffer
getTextViewBuffer :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> m TextBuffer
getTextViewBuffer o
obj = IO TextBuffer -> m TextBuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO TextBuffer -> m TextBuffer) -> IO TextBuffer -> m TextBuffer
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe TextBuffer) -> IO TextBuffer
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTextViewBuffer" (IO (Maybe TextBuffer) -> IO TextBuffer)
-> IO (Maybe TextBuffer) -> IO TextBuffer
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TextBuffer -> TextBuffer)
-> IO (Maybe TextBuffer)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"buffer" ManagedPtr TextBuffer -> TextBuffer
Gtk.TextBuffer.TextBuffer
setTextViewBuffer :: (MonadIO m, IsTextView o, Gtk.TextBuffer.IsTextBuffer a) => o -> a -> m ()
setTextViewBuffer :: forall (m :: * -> *) o a.
(MonadIO m, IsTextView o, IsTextBuffer a) =>
o -> a -> m ()
setTextViewBuffer o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"buffer" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTextViewBuffer :: (IsTextView o, MIO.MonadIO m, Gtk.TextBuffer.IsTextBuffer a) => a -> m (GValueConstruct o)
constructTextViewBuffer :: forall o (m :: * -> *) a.
(IsTextView o, MonadIO m, IsTextBuffer a) =>
a -> m (GValueConstruct o)
constructTextViewBuffer a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"buffer" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearTextViewBuffer :: (MonadIO m, IsTextView o) => o -> m ()
clearTextViewBuffer :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m ()
clearTextViewBuffer o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe TextBuffer -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"buffer" (Maybe TextBuffer
forall a. Maybe a
Nothing :: Maybe Gtk.TextBuffer.TextBuffer)
#if defined(ENABLE_OVERLOADING)
data TextViewBufferPropertyInfo
instance AttrInfo TextViewBufferPropertyInfo where
    type AttrAllowedOps TextViewBufferPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TextViewBufferPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewBufferPropertyInfo = Gtk.TextBuffer.IsTextBuffer
    type AttrTransferTypeConstraint TextViewBufferPropertyInfo = Gtk.TextBuffer.IsTextBuffer
    type AttrTransferType TextViewBufferPropertyInfo = Gtk.TextBuffer.TextBuffer
    type AttrGetType TextViewBufferPropertyInfo = Gtk.TextBuffer.TextBuffer
    type AttrLabel TextViewBufferPropertyInfo = "buffer"
    type AttrOrigin TextViewBufferPropertyInfo = TextView
    attrGet = getTextViewBuffer
    attrSet = setTextViewBuffer
    attrTransfer _ v = do
        unsafeCastTo Gtk.TextBuffer.TextBuffer v
    attrConstruct = constructTextViewBuffer
    attrClear = clearTextViewBuffer
#endif
   
   
   
getTextViewCursorVisible :: (MonadIO m, IsTextView o) => o -> m Bool
getTextViewCursorVisible :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Bool
getTextViewCursorVisible o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"cursor-visible"
setTextViewCursorVisible :: (MonadIO m, IsTextView o) => o -> Bool -> m ()
setTextViewCursorVisible :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Bool -> m ()
setTextViewCursorVisible o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> TextViewSelectAllCallback
forall a. GObject a => a -> String -> TextViewSelectAllCallback
B.Properties.setObjectPropertyBool o
obj String
"cursor-visible" Bool
val
constructTextViewCursorVisible :: (IsTextView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTextViewCursorVisible :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTextViewCursorVisible Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"cursor-visible" Bool
val
#if defined(ENABLE_OVERLOADING)
data TextViewCursorVisiblePropertyInfo
instance AttrInfo TextViewCursorVisiblePropertyInfo where
    type AttrAllowedOps TextViewCursorVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewCursorVisiblePropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewCursorVisiblePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TextViewCursorVisiblePropertyInfo = (~) Bool
    type AttrTransferType TextViewCursorVisiblePropertyInfo = Bool
    type AttrGetType TextViewCursorVisiblePropertyInfo = Bool
    type AttrLabel TextViewCursorVisiblePropertyInfo = "cursor-visible"
    type AttrOrigin TextViewCursorVisiblePropertyInfo = TextView
    attrGet = getTextViewCursorVisible
    attrSet = setTextViewCursorVisible
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewCursorVisible
    attrClear = undefined
#endif
   
   
   
getTextViewEditable :: (MonadIO m, IsTextView o) => o -> m Bool
getTextViewEditable :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Bool
getTextViewEditable o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"editable"
setTextViewEditable :: (MonadIO m, IsTextView o) => o -> Bool -> m ()
setTextViewEditable :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Bool -> m ()
setTextViewEditable o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> TextViewSelectAllCallback
forall a. GObject a => a -> String -> TextViewSelectAllCallback
B.Properties.setObjectPropertyBool o
obj String
"editable" Bool
val
constructTextViewEditable :: (IsTextView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTextViewEditable :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTextViewEditable Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"editable" Bool
val
#if defined(ENABLE_OVERLOADING)
data TextViewEditablePropertyInfo
instance AttrInfo TextViewEditablePropertyInfo where
    type AttrAllowedOps TextViewEditablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewEditablePropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewEditablePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TextViewEditablePropertyInfo = (~) Bool
    type AttrTransferType TextViewEditablePropertyInfo = Bool
    type AttrGetType TextViewEditablePropertyInfo = Bool
    type AttrLabel TextViewEditablePropertyInfo = "editable"
    type AttrOrigin TextViewEditablePropertyInfo = TextView
    attrGet = getTextViewEditable
    attrSet = setTextViewEditable
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewEditable
    attrClear = undefined
#endif
   
   
   
getTextViewExtraMenu :: (MonadIO m, IsTextView o) => o -> m Gio.MenuModel.MenuModel
 o
obj = IO MenuModel -> m MenuModel
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO MenuModel -> m MenuModel) -> IO MenuModel -> m MenuModel
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe MenuModel) -> IO MenuModel
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getTextViewExtraMenu" (IO (Maybe MenuModel) -> IO MenuModel)
-> IO (Maybe MenuModel) -> IO MenuModel
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr MenuModel -> MenuModel)
-> IO (Maybe MenuModel)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"extra-menu" ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel
setTextViewExtraMenu :: (MonadIO m, IsTextView o, Gio.MenuModel.IsMenuModel a) => o -> a -> m ()
 o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"extra-menu" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTextViewExtraMenu :: (IsTextView o, MIO.MonadIO m, Gio.MenuModel.IsMenuModel a) => a -> m (GValueConstruct o)
 a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"extra-menu" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearTextViewExtraMenu :: (MonadIO m, IsTextView o) => o -> m ()
 o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe MenuModel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"extra-menu" (Maybe MenuModel
forall a. Maybe a
Nothing :: Maybe Gio.MenuModel.MenuModel)
#if defined(ENABLE_OVERLOADING)
data TextViewExtraMenuPropertyInfo
instance AttrInfo TextViewExtraMenuPropertyInfo where
    type AttrAllowedOps TextViewExtraMenuPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TextViewExtraMenuPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewExtraMenuPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferTypeConstraint TextViewExtraMenuPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferType TextViewExtraMenuPropertyInfo = Gio.MenuModel.MenuModel
    type AttrGetType TextViewExtraMenuPropertyInfo = Gio.MenuModel.MenuModel
    type AttrLabel TextViewExtraMenuPropertyInfo = "extra-menu"
    type AttrOrigin TextViewExtraMenuPropertyInfo = TextView
    attrGet = getTextViewExtraMenu
    attrSet = setTextViewExtraMenu
    attrTransfer _ v = do
        unsafeCastTo Gio.MenuModel.MenuModel v
    attrConstruct = constructTextViewExtraMenu
    attrClear = clearTextViewExtraMenu
#endif
   
   
   
getTextViewImModule :: (MonadIO m, IsTextView o) => o -> m (Maybe T.Text)
getTextViewImModule :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> m (Maybe Text)
getTextViewImModule o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"im-module"
setTextViewImModule :: (MonadIO m, IsTextView o) => o -> T.Text -> m ()
setTextViewImModule :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Text -> m ()
setTextViewImModule o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"im-module" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructTextViewImModule :: (IsTextView o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTextViewImModule :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructTextViewImModule Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"im-module" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearTextViewImModule :: (MonadIO m, IsTextView o) => o -> m ()
clearTextViewImModule :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m ()
clearTextViewImModule o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"im-module" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data TextViewImModulePropertyInfo
instance AttrInfo TextViewImModulePropertyInfo where
    type AttrAllowedOps TextViewImModulePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint TextViewImModulePropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewImModulePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint TextViewImModulePropertyInfo = (~) T.Text
    type AttrTransferType TextViewImModulePropertyInfo = T.Text
    type AttrGetType TextViewImModulePropertyInfo = (Maybe T.Text)
    type AttrLabel TextViewImModulePropertyInfo = "im-module"
    type AttrOrigin TextViewImModulePropertyInfo = TextView
    attrGet = getTextViewImModule
    attrSet = setTextViewImModule
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewImModule
    attrClear = clearTextViewImModule
#endif
   
   
   
getTextViewIndent :: (MonadIO m, IsTextView o) => o -> m Int32
getTextViewIndent :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Int32
getTextViewIndent o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"indent"
setTextViewIndent :: (MonadIO m, IsTextView o) => o -> Int32 -> m ()
setTextViewIndent :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Int32 -> m ()
setTextViewIndent o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"indent" Int32
val
constructTextViewIndent :: (IsTextView o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructTextViewIndent :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructTextViewIndent Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"indent" Int32
val
#if defined(ENABLE_OVERLOADING)
data TextViewIndentPropertyInfo
instance AttrInfo TextViewIndentPropertyInfo where
    type AttrAllowedOps TextViewIndentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewIndentPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewIndentPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint TextViewIndentPropertyInfo = (~) Int32
    type AttrTransferType TextViewIndentPropertyInfo = Int32
    type AttrGetType TextViewIndentPropertyInfo = Int32
    type AttrLabel TextViewIndentPropertyInfo = "indent"
    type AttrOrigin TextViewIndentPropertyInfo = TextView
    attrGet = getTextViewIndent
    attrSet = setTextViewIndent
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewIndent
    attrClear = undefined
#endif
   
   
   
getTextViewInputHints :: (MonadIO m, IsTextView o) => o -> m [Gtk.Flags.InputHints]
getTextViewInputHints :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> m [InputHints]
getTextViewInputHints o
obj = IO [InputHints] -> m [InputHints]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [InputHints] -> m [InputHints])
-> IO [InputHints] -> m [InputHints]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [InputHints]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"input-hints"
setTextViewInputHints :: (MonadIO m, IsTextView o) => o -> [Gtk.Flags.InputHints] -> m ()
setTextViewInputHints :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> [InputHints] -> m ()
setTextViewInputHints o
obj [InputHints]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> [InputHints] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"input-hints" [InputHints]
val
constructTextViewInputHints :: (IsTextView o, MIO.MonadIO m) => [Gtk.Flags.InputHints] -> m (GValueConstruct o)
constructTextViewInputHints :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
[InputHints] -> m (GValueConstruct o)
constructTextViewInputHints [InputHints]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [InputHints] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"input-hints" [InputHints]
val
#if defined(ENABLE_OVERLOADING)
data TextViewInputHintsPropertyInfo
instance AttrInfo TextViewInputHintsPropertyInfo where
    type AttrAllowedOps TextViewInputHintsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewInputHintsPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewInputHintsPropertyInfo = (~) [Gtk.Flags.InputHints]
    type AttrTransferTypeConstraint TextViewInputHintsPropertyInfo = (~) [Gtk.Flags.InputHints]
    type AttrTransferType TextViewInputHintsPropertyInfo = [Gtk.Flags.InputHints]
    type AttrGetType TextViewInputHintsPropertyInfo = [Gtk.Flags.InputHints]
    type AttrLabel TextViewInputHintsPropertyInfo = "input-hints"
    type AttrOrigin TextViewInputHintsPropertyInfo = TextView
    attrGet = getTextViewInputHints
    attrSet = setTextViewInputHints
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewInputHints
    attrClear = undefined
#endif
   
   
   
getTextViewInputPurpose :: (MonadIO m, IsTextView o) => o -> m Gtk.Enums.InputPurpose
getTextViewInputPurpose :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> m InputPurpose
getTextViewInputPurpose o
obj = IO InputPurpose -> m InputPurpose
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO InputPurpose -> m InputPurpose)
-> IO InputPurpose -> m InputPurpose
forall a b. (a -> b) -> a -> b
$ o -> String -> IO InputPurpose
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"input-purpose"
setTextViewInputPurpose :: (MonadIO m, IsTextView o) => o -> Gtk.Enums.InputPurpose -> m ()
setTextViewInputPurpose :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> InputPurpose -> m ()
setTextViewInputPurpose o
obj InputPurpose
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> InputPurpose -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"input-purpose" InputPurpose
val
constructTextViewInputPurpose :: (IsTextView o, MIO.MonadIO m) => Gtk.Enums.InputPurpose -> m (GValueConstruct o)
constructTextViewInputPurpose :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
InputPurpose -> m (GValueConstruct o)
constructTextViewInputPurpose InputPurpose
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> InputPurpose -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"input-purpose" InputPurpose
val
#if defined(ENABLE_OVERLOADING)
data TextViewInputPurposePropertyInfo
instance AttrInfo TextViewInputPurposePropertyInfo where
    type AttrAllowedOps TextViewInputPurposePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewInputPurposePropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewInputPurposePropertyInfo = (~) Gtk.Enums.InputPurpose
    type AttrTransferTypeConstraint TextViewInputPurposePropertyInfo = (~) Gtk.Enums.InputPurpose
    type AttrTransferType TextViewInputPurposePropertyInfo = Gtk.Enums.InputPurpose
    type AttrGetType TextViewInputPurposePropertyInfo = Gtk.Enums.InputPurpose
    type AttrLabel TextViewInputPurposePropertyInfo = "input-purpose"
    type AttrOrigin TextViewInputPurposePropertyInfo = TextView
    attrGet = getTextViewInputPurpose
    attrSet = setTextViewInputPurpose
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewInputPurpose
    attrClear = undefined
#endif
   
   
   
getTextViewJustification :: (MonadIO m, IsTextView o) => o -> m Gtk.Enums.Justification
getTextViewJustification :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> m Justification
getTextViewJustification o
obj = IO Justification -> m Justification
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Justification -> m Justification)
-> IO Justification -> m Justification
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Justification
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"justification"
setTextViewJustification :: (MonadIO m, IsTextView o) => o -> Gtk.Enums.Justification -> m ()
setTextViewJustification :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Justification -> m ()
setTextViewJustification o
obj Justification
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Justification -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"justification" Justification
val
constructTextViewJustification :: (IsTextView o, MIO.MonadIO m) => Gtk.Enums.Justification -> m (GValueConstruct o)
constructTextViewJustification :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Justification -> m (GValueConstruct o)
constructTextViewJustification Justification
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Justification -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"justification" Justification
val
#if defined(ENABLE_OVERLOADING)
data TextViewJustificationPropertyInfo
instance AttrInfo TextViewJustificationPropertyInfo where
    type AttrAllowedOps TextViewJustificationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewJustificationPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewJustificationPropertyInfo = (~) Gtk.Enums.Justification
    type AttrTransferTypeConstraint TextViewJustificationPropertyInfo = (~) Gtk.Enums.Justification
    type AttrTransferType TextViewJustificationPropertyInfo = Gtk.Enums.Justification
    type AttrGetType TextViewJustificationPropertyInfo = Gtk.Enums.Justification
    type AttrLabel TextViewJustificationPropertyInfo = "justification"
    type AttrOrigin TextViewJustificationPropertyInfo = TextView
    attrGet = getTextViewJustification
    attrSet = setTextViewJustification
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewJustification
    attrClear = undefined
#endif
   
   
   
getTextViewLeftMargin :: (MonadIO m, IsTextView o) => o -> m Int32
getTextViewLeftMargin :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Int32
getTextViewLeftMargin o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"left-margin"
setTextViewLeftMargin :: (MonadIO m, IsTextView o) => o -> Int32 -> m ()
setTextViewLeftMargin :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Int32 -> m ()
setTextViewLeftMargin o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"left-margin" Int32
val
constructTextViewLeftMargin :: (IsTextView o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructTextViewLeftMargin :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructTextViewLeftMargin Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"left-margin" Int32
val
#if defined(ENABLE_OVERLOADING)
data TextViewLeftMarginPropertyInfo
instance AttrInfo TextViewLeftMarginPropertyInfo where
    type AttrAllowedOps TextViewLeftMarginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewLeftMarginPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewLeftMarginPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint TextViewLeftMarginPropertyInfo = (~) Int32
    type AttrTransferType TextViewLeftMarginPropertyInfo = Int32
    type AttrGetType TextViewLeftMarginPropertyInfo = Int32
    type AttrLabel TextViewLeftMarginPropertyInfo = "left-margin"
    type AttrOrigin TextViewLeftMarginPropertyInfo = TextView
    attrGet = getTextViewLeftMargin
    attrSet = setTextViewLeftMargin
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewLeftMargin
    attrClear = undefined
#endif
   
   
   
getTextViewMonospace :: (MonadIO m, IsTextView o) => o -> m Bool
getTextViewMonospace :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Bool
getTextViewMonospace o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"monospace"
setTextViewMonospace :: (MonadIO m, IsTextView o) => o -> Bool -> m ()
setTextViewMonospace :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Bool -> m ()
setTextViewMonospace o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> TextViewSelectAllCallback
forall a. GObject a => a -> String -> TextViewSelectAllCallback
B.Properties.setObjectPropertyBool o
obj String
"monospace" Bool
val
constructTextViewMonospace :: (IsTextView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTextViewMonospace :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTextViewMonospace Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"monospace" Bool
val
#if defined(ENABLE_OVERLOADING)
data TextViewMonospacePropertyInfo
instance AttrInfo TextViewMonospacePropertyInfo where
    type AttrAllowedOps TextViewMonospacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewMonospacePropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewMonospacePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TextViewMonospacePropertyInfo = (~) Bool
    type AttrTransferType TextViewMonospacePropertyInfo = Bool
    type AttrGetType TextViewMonospacePropertyInfo = Bool
    type AttrLabel TextViewMonospacePropertyInfo = "monospace"
    type AttrOrigin TextViewMonospacePropertyInfo = TextView
    attrGet = getTextViewMonospace
    attrSet = setTextViewMonospace
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewMonospace
    attrClear = undefined
#endif
   
   
   
getTextViewOverwrite :: (MonadIO m, IsTextView o) => o -> m Bool
getTextViewOverwrite :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Bool
getTextViewOverwrite o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"overwrite"
setTextViewOverwrite :: (MonadIO m, IsTextView o) => o -> Bool -> m ()
setTextViewOverwrite :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Bool -> m ()
setTextViewOverwrite o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> TextViewSelectAllCallback
forall a. GObject a => a -> String -> TextViewSelectAllCallback
B.Properties.setObjectPropertyBool o
obj String
"overwrite" Bool
val
constructTextViewOverwrite :: (IsTextView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTextViewOverwrite :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTextViewOverwrite Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"overwrite" Bool
val
#if defined(ENABLE_OVERLOADING)
data TextViewOverwritePropertyInfo
instance AttrInfo TextViewOverwritePropertyInfo where
    type AttrAllowedOps TextViewOverwritePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewOverwritePropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewOverwritePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TextViewOverwritePropertyInfo = (~) Bool
    type AttrTransferType TextViewOverwritePropertyInfo = Bool
    type AttrGetType TextViewOverwritePropertyInfo = Bool
    type AttrLabel TextViewOverwritePropertyInfo = "overwrite"
    type AttrOrigin TextViewOverwritePropertyInfo = TextView
    attrGet = getTextViewOverwrite
    attrSet = setTextViewOverwrite
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewOverwrite
    attrClear = undefined
#endif
   
   
   
getTextViewPixelsAboveLines :: (MonadIO m, IsTextView o) => o -> m Int32
getTextViewPixelsAboveLines :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Int32
getTextViewPixelsAboveLines o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"pixels-above-lines"
setTextViewPixelsAboveLines :: (MonadIO m, IsTextView o) => o -> Int32 -> m ()
setTextViewPixelsAboveLines :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Int32 -> m ()
setTextViewPixelsAboveLines o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"pixels-above-lines" Int32
val
constructTextViewPixelsAboveLines :: (IsTextView o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructTextViewPixelsAboveLines :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructTextViewPixelsAboveLines Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"pixels-above-lines" Int32
val
#if defined(ENABLE_OVERLOADING)
data TextViewPixelsAboveLinesPropertyInfo
instance AttrInfo TextViewPixelsAboveLinesPropertyInfo where
    type AttrAllowedOps TextViewPixelsAboveLinesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewPixelsAboveLinesPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewPixelsAboveLinesPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint TextViewPixelsAboveLinesPropertyInfo = (~) Int32
    type AttrTransferType TextViewPixelsAboveLinesPropertyInfo = Int32
    type AttrGetType TextViewPixelsAboveLinesPropertyInfo = Int32
    type AttrLabel TextViewPixelsAboveLinesPropertyInfo = "pixels-above-lines"
    type AttrOrigin TextViewPixelsAboveLinesPropertyInfo = TextView
    attrGet = getTextViewPixelsAboveLines
    attrSet = setTextViewPixelsAboveLines
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewPixelsAboveLines
    attrClear = undefined
#endif
   
   
   
getTextViewPixelsBelowLines :: (MonadIO m, IsTextView o) => o -> m Int32
getTextViewPixelsBelowLines :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Int32
getTextViewPixelsBelowLines o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"pixels-below-lines"
setTextViewPixelsBelowLines :: (MonadIO m, IsTextView o) => o -> Int32 -> m ()
setTextViewPixelsBelowLines :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Int32 -> m ()
setTextViewPixelsBelowLines o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"pixels-below-lines" Int32
val
constructTextViewPixelsBelowLines :: (IsTextView o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructTextViewPixelsBelowLines :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructTextViewPixelsBelowLines Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"pixels-below-lines" Int32
val
#if defined(ENABLE_OVERLOADING)
data TextViewPixelsBelowLinesPropertyInfo
instance AttrInfo TextViewPixelsBelowLinesPropertyInfo where
    type AttrAllowedOps TextViewPixelsBelowLinesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewPixelsBelowLinesPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewPixelsBelowLinesPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint TextViewPixelsBelowLinesPropertyInfo = (~) Int32
    type AttrTransferType TextViewPixelsBelowLinesPropertyInfo = Int32
    type AttrGetType TextViewPixelsBelowLinesPropertyInfo = Int32
    type AttrLabel TextViewPixelsBelowLinesPropertyInfo = "pixels-below-lines"
    type AttrOrigin TextViewPixelsBelowLinesPropertyInfo = TextView
    attrGet = getTextViewPixelsBelowLines
    attrSet = setTextViewPixelsBelowLines
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewPixelsBelowLines
    attrClear = undefined
#endif
   
   
   
getTextViewPixelsInsideWrap :: (MonadIO m, IsTextView o) => o -> m Int32
getTextViewPixelsInsideWrap :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Int32
getTextViewPixelsInsideWrap o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"pixels-inside-wrap"
setTextViewPixelsInsideWrap :: (MonadIO m, IsTextView o) => o -> Int32 -> m ()
setTextViewPixelsInsideWrap :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Int32 -> m ()
setTextViewPixelsInsideWrap o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"pixels-inside-wrap" Int32
val
constructTextViewPixelsInsideWrap :: (IsTextView o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructTextViewPixelsInsideWrap :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructTextViewPixelsInsideWrap Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"pixels-inside-wrap" Int32
val
#if defined(ENABLE_OVERLOADING)
data TextViewPixelsInsideWrapPropertyInfo
instance AttrInfo TextViewPixelsInsideWrapPropertyInfo where
    type AttrAllowedOps TextViewPixelsInsideWrapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewPixelsInsideWrapPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewPixelsInsideWrapPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint TextViewPixelsInsideWrapPropertyInfo = (~) Int32
    type AttrTransferType TextViewPixelsInsideWrapPropertyInfo = Int32
    type AttrGetType TextViewPixelsInsideWrapPropertyInfo = Int32
    type AttrLabel TextViewPixelsInsideWrapPropertyInfo = "pixels-inside-wrap"
    type AttrOrigin TextViewPixelsInsideWrapPropertyInfo = TextView
    attrGet = getTextViewPixelsInsideWrap
    attrSet = setTextViewPixelsInsideWrap
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewPixelsInsideWrap
    attrClear = undefined
#endif
   
   
   
getTextViewRightMargin :: (MonadIO m, IsTextView o) => o -> m Int32
getTextViewRightMargin :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Int32
getTextViewRightMargin o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"right-margin"
setTextViewRightMargin :: (MonadIO m, IsTextView o) => o -> Int32 -> m ()
setTextViewRightMargin :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Int32 -> m ()
setTextViewRightMargin o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"right-margin" Int32
val
constructTextViewRightMargin :: (IsTextView o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructTextViewRightMargin :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructTextViewRightMargin Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"right-margin" Int32
val
#if defined(ENABLE_OVERLOADING)
data TextViewRightMarginPropertyInfo
instance AttrInfo TextViewRightMarginPropertyInfo where
    type AttrAllowedOps TextViewRightMarginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewRightMarginPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewRightMarginPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint TextViewRightMarginPropertyInfo = (~) Int32
    type AttrTransferType TextViewRightMarginPropertyInfo = Int32
    type AttrGetType TextViewRightMarginPropertyInfo = Int32
    type AttrLabel TextViewRightMarginPropertyInfo = "right-margin"
    type AttrOrigin TextViewRightMarginPropertyInfo = TextView
    attrGet = getTextViewRightMargin
    attrSet = setTextViewRightMargin
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewRightMargin
    attrClear = undefined
#endif
   
   
   
getTextViewTabs :: (MonadIO m, IsTextView o) => o -> m (Maybe Pango.TabArray.TabArray)
getTextViewTabs :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> m (Maybe TabArray)
getTextViewTabs o
obj = IO (Maybe TabArray) -> m (Maybe TabArray)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TabArray) -> m (Maybe TabArray))
-> IO (Maybe TabArray) -> m (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TabArray -> TabArray)
-> IO (Maybe TabArray)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"tabs" ManagedPtr TabArray -> TabArray
Pango.TabArray.TabArray
setTextViewTabs :: (MonadIO m, IsTextView o) => o -> Pango.TabArray.TabArray -> m ()
setTextViewTabs :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> TabArray -> m ()
setTextViewTabs o
obj TabArray
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe TabArray -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"tabs" (TabArray -> Maybe TabArray
forall a. a -> Maybe a
Just TabArray
val)
constructTextViewTabs :: (IsTextView o, MIO.MonadIO m) => Pango.TabArray.TabArray -> m (GValueConstruct o)
constructTextViewTabs :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
TabArray -> m (GValueConstruct o)
constructTextViewTabs TabArray
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe TabArray -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"tabs" (TabArray -> Maybe TabArray
forall a. a -> Maybe a
P.Just TabArray
val)
#if defined(ENABLE_OVERLOADING)
data TextViewTabsPropertyInfo
instance AttrInfo TextViewTabsPropertyInfo where
    type AttrAllowedOps TextViewTabsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewTabsPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewTabsPropertyInfo = (~) Pango.TabArray.TabArray
    type AttrTransferTypeConstraint TextViewTabsPropertyInfo = (~) Pango.TabArray.TabArray
    type AttrTransferType TextViewTabsPropertyInfo = Pango.TabArray.TabArray
    type AttrGetType TextViewTabsPropertyInfo = (Maybe Pango.TabArray.TabArray)
    type AttrLabel TextViewTabsPropertyInfo = "tabs"
    type AttrOrigin TextViewTabsPropertyInfo = TextView
    attrGet = getTextViewTabs
    attrSet = setTextViewTabs
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewTabs
    attrClear = undefined
#endif
   
   
   
getTextViewTopMargin :: (MonadIO m, IsTextView o) => o -> m Int32
getTextViewTopMargin :: forall (m :: * -> *) o. (MonadIO m, IsTextView o) => o -> m Int32
getTextViewTopMargin o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"top-margin"
setTextViewTopMargin :: (MonadIO m, IsTextView o) => o -> Int32 -> m ()
setTextViewTopMargin :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> Int32 -> m ()
setTextViewTopMargin o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"top-margin" Int32
val
constructTextViewTopMargin :: (IsTextView o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructTextViewTopMargin :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructTextViewTopMargin Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"top-margin" Int32
val
#if defined(ENABLE_OVERLOADING)
data TextViewTopMarginPropertyInfo
instance AttrInfo TextViewTopMarginPropertyInfo where
    type AttrAllowedOps TextViewTopMarginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewTopMarginPropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewTopMarginPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint TextViewTopMarginPropertyInfo = (~) Int32
    type AttrTransferType TextViewTopMarginPropertyInfo = Int32
    type AttrGetType TextViewTopMarginPropertyInfo = Int32
    type AttrLabel TextViewTopMarginPropertyInfo = "top-margin"
    type AttrOrigin TextViewTopMarginPropertyInfo = TextView
    attrGet = getTextViewTopMargin
    attrSet = setTextViewTopMargin
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewTopMargin
    attrClear = undefined
#endif
   
   
   
getTextViewWrapMode :: (MonadIO m, IsTextView o) => o -> m Gtk.Enums.WrapMode
getTextViewWrapMode :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> m WrapMode
getTextViewWrapMode o
obj = IO WrapMode -> m WrapMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO WrapMode -> m WrapMode) -> IO WrapMode -> m WrapMode
forall a b. (a -> b) -> a -> b
$ o -> String -> IO WrapMode
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"wrap-mode"
setTextViewWrapMode :: (MonadIO m, IsTextView o) => o -> Gtk.Enums.WrapMode -> m ()
setTextViewWrapMode :: forall (m :: * -> *) o.
(MonadIO m, IsTextView o) =>
o -> WrapMode -> m ()
setTextViewWrapMode o
obj WrapMode
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> WrapMode -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"wrap-mode" WrapMode
val
constructTextViewWrapMode :: (IsTextView o, MIO.MonadIO m) => Gtk.Enums.WrapMode -> m (GValueConstruct o)
constructTextViewWrapMode :: forall o (m :: * -> *).
(IsTextView o, MonadIO m) =>
WrapMode -> m (GValueConstruct o)
constructTextViewWrapMode WrapMode
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> WrapMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"wrap-mode" WrapMode
val
#if defined(ENABLE_OVERLOADING)
data TextViewWrapModePropertyInfo
instance AttrInfo TextViewWrapModePropertyInfo where
    type AttrAllowedOps TextViewWrapModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TextViewWrapModePropertyInfo = IsTextView
    type AttrSetTypeConstraint TextViewWrapModePropertyInfo = (~) Gtk.Enums.WrapMode
    type AttrTransferTypeConstraint TextViewWrapModePropertyInfo = (~) Gtk.Enums.WrapMode
    type AttrTransferType TextViewWrapModePropertyInfo = Gtk.Enums.WrapMode
    type AttrGetType TextViewWrapModePropertyInfo = Gtk.Enums.WrapMode
    type AttrLabel TextViewWrapModePropertyInfo = "wrap-mode"
    type AttrOrigin TextViewWrapModePropertyInfo = TextView
    attrGet = getTextViewWrapMode
    attrSet = setTextViewWrapMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructTextViewWrapMode
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TextView
type instance O.AttributeList TextView = TextViewAttributeList
type TextViewAttributeList = ('[ '("acceptsTab", TextViewAcceptsTabPropertyInfo), '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("bottomMargin", TextViewBottomMarginPropertyInfo), '("buffer", TextViewBufferPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("cursorVisible", TextViewCursorVisiblePropertyInfo), '("editable", TextViewEditablePropertyInfo), '("extraMenu", TextViewExtraMenuPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("hadjustment", Gtk.Scrollable.ScrollableHadjustmentPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("hscrollPolicy", Gtk.Scrollable.ScrollableHscrollPolicyPropertyInfo), '("imModule", TextViewImModulePropertyInfo), '("indent", TextViewIndentPropertyInfo), '("inputHints", TextViewInputHintsPropertyInfo), '("inputPurpose", TextViewInputPurposePropertyInfo), '("justification", TextViewJustificationPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("leftMargin", TextViewLeftMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("monospace", TextViewMonospacePropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("overwrite", TextViewOverwritePropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("pixelsAboveLines", TextViewPixelsAboveLinesPropertyInfo), '("pixelsBelowLines", TextViewPixelsBelowLinesPropertyInfo), '("pixelsInsideWrap", TextViewPixelsInsideWrapPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("rightMargin", TextViewRightMarginPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tabs", TextViewTabsPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("topMargin", TextViewTopMarginPropertyInfo), '("vadjustment", Gtk.Scrollable.ScrollableVadjustmentPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("vscrollPolicy", Gtk.Scrollable.ScrollableVscrollPolicyPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("wrapMode", TextViewWrapModePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
textViewAcceptsTab :: AttrLabelProxy "acceptsTab"
textViewAcceptsTab = AttrLabelProxy
textViewBottomMargin :: AttrLabelProxy "bottomMargin"
textViewBottomMargin = AttrLabelProxy
textViewBuffer :: AttrLabelProxy "buffer"
textViewBuffer = AttrLabelProxy
textViewCursorVisible :: AttrLabelProxy "cursorVisible"
textViewCursorVisible = AttrLabelProxy
textViewEditable :: AttrLabelProxy "editable"
textViewEditable = AttrLabelProxy
textViewExtraMenu :: AttrLabelProxy "extraMenu"
textViewExtraMenu = AttrLabelProxy
textViewImModule :: AttrLabelProxy "imModule"
textViewImModule = AttrLabelProxy
textViewIndent :: AttrLabelProxy "indent"
textViewIndent = AttrLabelProxy
textViewInputHints :: AttrLabelProxy "inputHints"
textViewInputHints = AttrLabelProxy
textViewInputPurpose :: AttrLabelProxy "inputPurpose"
textViewInputPurpose = AttrLabelProxy
textViewJustification :: AttrLabelProxy "justification"
textViewJustification = AttrLabelProxy
textViewLeftMargin :: AttrLabelProxy "leftMargin"
textViewLeftMargin = AttrLabelProxy
textViewMonospace :: AttrLabelProxy "monospace"
textViewMonospace = AttrLabelProxy
textViewOverwrite :: AttrLabelProxy "overwrite"
textViewOverwrite = AttrLabelProxy
textViewPixelsAboveLines :: AttrLabelProxy "pixelsAboveLines"
textViewPixelsAboveLines = AttrLabelProxy
textViewPixelsBelowLines :: AttrLabelProxy "pixelsBelowLines"
textViewPixelsBelowLines = AttrLabelProxy
textViewPixelsInsideWrap :: AttrLabelProxy "pixelsInsideWrap"
textViewPixelsInsideWrap = AttrLabelProxy
textViewRightMargin :: AttrLabelProxy "rightMargin"
textViewRightMargin = AttrLabelProxy
textViewTabs :: AttrLabelProxy "tabs"
textViewTabs = AttrLabelProxy
textViewTopMargin :: AttrLabelProxy "topMargin"
textViewTopMargin = AttrLabelProxy
textViewWrapMode :: AttrLabelProxy "wrapMode"
textViewWrapMode = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TextView = TextViewSignalList
type TextViewSignalList = ('[ '("backspace", TextViewBackspaceSignalInfo), '("copyClipboard", TextViewCopyClipboardSignalInfo), '("cutClipboard", TextViewCutClipboardSignalInfo), '("deleteFromCursor", TextViewDeleteFromCursorSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("extendSelection", TextViewExtendSelectionSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("insertAtCursor", TextViewInsertAtCursorSignalInfo), '("insertEmoji", TextViewInsertEmojiSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveCursor", TextViewMoveCursorSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("moveViewport", TextViewMoveViewportSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("pasteClipboard", TextViewPasteClipboardSignalInfo), '("preeditChanged", TextViewPreeditChangedSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("selectAll", TextViewSelectAllSignalInfo), '("setAnchor", TextViewSetAnchorSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("toggleCursorVisible", TextViewToggleCursorVisibleSignalInfo), '("toggleOverwrite", TextViewToggleOverwriteSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_text_view_new" gtk_text_view_new :: 
    IO (Ptr TextView)
textViewNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m TextView
    
textViewNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m TextView
textViewNew  = IO TextView -> m TextView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextView -> m TextView) -> IO TextView -> m TextView
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
result <- IO (Ptr TextView)
gtk_text_view_new
    Text -> Ptr TextView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"textViewNew" Ptr TextView
result
    TextView
result' <- ((ManagedPtr TextView -> TextView) -> Ptr TextView -> IO TextView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TextView -> TextView
TextView) Ptr TextView
result
    TextView -> IO TextView
forall (m :: * -> *) a. Monad m => a -> m a
return TextView
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_text_view_new_with_buffer" gtk_text_view_new_with_buffer :: 
    Ptr Gtk.TextBuffer.TextBuffer ->        
    IO (Ptr TextView)
textViewNewWithBuffer ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.TextBuffer.IsTextBuffer a) =>
    a
    
    -> m TextView
    
textViewNewWithBuffer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextBuffer a) =>
a -> m TextView
textViewNewWithBuffer a
buffer = IO TextView -> m TextView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextView -> m TextView) -> IO TextView -> m TextView
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextBuffer
buffer' <- a -> IO (Ptr TextBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buffer
    Ptr TextView
result <- Ptr TextBuffer -> IO (Ptr TextView)
gtk_text_view_new_with_buffer Ptr TextBuffer
buffer'
    Text -> Ptr TextView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"textViewNewWithBuffer" Ptr TextView
result
    TextView
result' <- ((ManagedPtr TextView -> TextView) -> Ptr TextView -> IO TextView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TextView -> TextView
TextView) Ptr TextView
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buffer
    TextView -> IO TextView
forall (m :: * -> *) a. Monad m => a -> m a
return TextView
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_text_view_add_child_at_anchor" gtk_text_view_add_child_at_anchor :: 
    Ptr TextView ->                         
    Ptr Gtk.Widget.Widget ->                
    Ptr Gtk.TextChildAnchor.TextChildAnchor -> 
    IO ()
textViewAddChildAtAnchor ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.Widget.IsWidget b, Gtk.TextChildAnchor.IsTextChildAnchor c) =>
    a
    
    -> b
    
    -> c
    
    -> m ()
textViewAddChildAtAnchor :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsTextView a, IsWidget b,
 IsTextChildAnchor c) =>
a -> b -> c -> m ()
textViewAddChildAtAnchor a
textView b
child c
anchor = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr TextChildAnchor
anchor' <- c -> IO (Ptr TextChildAnchor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
anchor
    Ptr TextView -> Ptr Widget -> Ptr TextChildAnchor -> IO ()
gtk_text_view_add_child_at_anchor Ptr TextView
textView' Ptr Widget
child' Ptr TextChildAnchor
anchor'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
anchor
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewAddChildAtAnchorMethodInfo
instance (signature ~ (b -> c -> m ()), MonadIO m, IsTextView a, Gtk.Widget.IsWidget b, Gtk.TextChildAnchor.IsTextChildAnchor c) => O.OverloadedMethod TextViewAddChildAtAnchorMethodInfo a signature where
    overloadedMethod = textViewAddChildAtAnchor
instance O.OverloadedMethodInfo TextViewAddChildAtAnchorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewAddChildAtAnchor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewAddChildAtAnchor"
        }
#endif
foreign import ccall "gtk_text_view_add_overlay" gtk_text_view_add_overlay :: 
    Ptr TextView ->                         
    Ptr Gtk.Widget.Widget ->                
    Int32 ->                                
    Int32 ->                                
    IO ()
textViewAddOverlay ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.Widget.IsWidget b) =>
    a
    
    -> b
    
    -> Int32
    
    -> Int32
    
    -> m ()
textViewAddOverlay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsWidget b) =>
a -> b -> Int32 -> Int32 -> m ()
textViewAddOverlay a
textView b
child Int32
xpos Int32
ypos = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr TextView -> Ptr Widget -> Int32 -> Int32 -> IO ()
gtk_text_view_add_overlay Ptr TextView
textView' Ptr Widget
child' Int32
xpos Int32
ypos
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewAddOverlayMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> m ()), MonadIO m, IsTextView a, Gtk.Widget.IsWidget b) => O.OverloadedMethod TextViewAddOverlayMethodInfo a signature where
    overloadedMethod = textViewAddOverlay
instance O.OverloadedMethodInfo TextViewAddOverlayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewAddOverlay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewAddOverlay"
        }
#endif
foreign import ccall "gtk_text_view_backward_display_line" gtk_text_view_backward_display_line :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    IO CInt
textViewBackwardDisplayLine ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> m Bool
    
textViewBackwardDisplayLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> m Bool
textViewBackwardDisplayLine a
textView 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextView -> Ptr TextIter -> IO CInt
gtk_text_view_backward_display_line Ptr TextView
textView' Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    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 TextViewBackwardDisplayLineMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewBackwardDisplayLineMethodInfo a signature where
    overloadedMethod = textViewBackwardDisplayLine
instance O.OverloadedMethodInfo TextViewBackwardDisplayLineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewBackwardDisplayLine",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewBackwardDisplayLine"
        }
#endif
foreign import ccall "gtk_text_view_backward_display_line_start" gtk_text_view_backward_display_line_start :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    IO CInt
textViewBackwardDisplayLineStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> m Bool
    
textViewBackwardDisplayLineStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> m Bool
textViewBackwardDisplayLineStart a
textView 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextView -> Ptr TextIter -> IO CInt
gtk_text_view_backward_display_line_start Ptr TextView
textView' Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    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 TextViewBackwardDisplayLineStartMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewBackwardDisplayLineStartMethodInfo a signature where
    overloadedMethod = textViewBackwardDisplayLineStart
instance O.OverloadedMethodInfo TextViewBackwardDisplayLineStartMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewBackwardDisplayLineStart",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewBackwardDisplayLineStart"
        }
#endif
foreign import ccall "gtk_text_view_buffer_to_window_coords" gtk_text_view_buffer_to_window_coords :: 
    Ptr TextView ->                         
    CUInt ->                                
    Int32 ->                                
    Int32 ->                                
    Ptr Int32 ->                            
    Ptr Int32 ->                            
    IO ()
textViewBufferToWindowCoords ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.Enums.TextWindowType
    
    -> Int32
    
    -> Int32
    
    -> m ((Int32, Int32))
textViewBufferToWindowCoords :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextWindowType -> Int32 -> Int32 -> m (Int32, Int32)
textViewBufferToWindowCoords a
textView TextWindowType
win Int32
bufferX Int32
bufferY = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let win' :: CUInt
win' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TextWindowType -> Int) -> TextWindowType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextWindowType -> Int
forall a. Enum a => a -> Int
fromEnum) TextWindowType
win
    Ptr Int32
windowX <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
windowY <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr TextView
-> CUInt -> Int32 -> Int32 -> Ptr Int32 -> Ptr Int32 -> IO ()
gtk_text_view_buffer_to_window_coords Ptr TextView
textView' CUInt
win' Int32
bufferX Int32
bufferY Ptr Int32
windowX Ptr Int32
windowY
    Int32
windowX' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
windowX
    Int32
windowY' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
windowY
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
windowX
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
windowY
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
windowX', Int32
windowY')
#if defined(ENABLE_OVERLOADING)
data TextViewBufferToWindowCoordsMethodInfo
instance (signature ~ (Gtk.Enums.TextWindowType -> Int32 -> Int32 -> m ((Int32, Int32))), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewBufferToWindowCoordsMethodInfo a signature where
    overloadedMethod = textViewBufferToWindowCoords
instance O.OverloadedMethodInfo TextViewBufferToWindowCoordsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewBufferToWindowCoords",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewBufferToWindowCoords"
        }
#endif
foreign import ccall "gtk_text_view_forward_display_line" gtk_text_view_forward_display_line :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    IO CInt
textViewForwardDisplayLine ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> m Bool
    
textViewForwardDisplayLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> m Bool
textViewForwardDisplayLine a
textView 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextView -> Ptr TextIter -> IO CInt
gtk_text_view_forward_display_line Ptr TextView
textView' Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    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 TextViewForwardDisplayLineMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewForwardDisplayLineMethodInfo a signature where
    overloadedMethod = textViewForwardDisplayLine
instance O.OverloadedMethodInfo TextViewForwardDisplayLineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewForwardDisplayLine",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewForwardDisplayLine"
        }
#endif
foreign import ccall "gtk_text_view_forward_display_line_end" gtk_text_view_forward_display_line_end :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    IO CInt
textViewForwardDisplayLineEnd ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> m Bool
    
textViewForwardDisplayLineEnd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> m Bool
textViewForwardDisplayLineEnd a
textView 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextView -> Ptr TextIter -> IO CInt
gtk_text_view_forward_display_line_end Ptr TextView
textView' Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    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 TextViewForwardDisplayLineEndMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewForwardDisplayLineEndMethodInfo a signature where
    overloadedMethod = textViewForwardDisplayLineEnd
instance O.OverloadedMethodInfo TextViewForwardDisplayLineEndMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewForwardDisplayLineEnd",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewForwardDisplayLineEnd"
        }
#endif
foreign import ccall "gtk_text_view_get_accepts_tab" gtk_text_view_get_accepts_tab :: 
    Ptr TextView ->                         
    IO CInt
textViewGetAcceptsTab ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Bool
    
    
textViewGetAcceptsTab :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Bool
textViewGetAcceptsTab a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CInt
result <- Ptr TextView -> IO CInt
gtk_text_view_get_accepts_tab Ptr TextView
textView'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetAcceptsTabMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetAcceptsTabMethodInfo a signature where
    overloadedMethod = textViewGetAcceptsTab
instance O.OverloadedMethodInfo TextViewGetAcceptsTabMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetAcceptsTab",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetAcceptsTab"
        }
#endif
foreign import ccall "gtk_text_view_get_bottom_margin" gtk_text_view_get_bottom_margin :: 
    Ptr TextView ->                         
    IO Int32
textViewGetBottomMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Int32
    
textViewGetBottomMargin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Int32
textViewGetBottomMargin a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Int32
result <- Ptr TextView -> IO Int32
gtk_text_view_get_bottom_margin Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data TextViewGetBottomMarginMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetBottomMarginMethodInfo a signature where
    overloadedMethod = textViewGetBottomMargin
instance O.OverloadedMethodInfo TextViewGetBottomMarginMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetBottomMargin",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetBottomMargin"
        }
#endif
foreign import ccall "gtk_text_view_get_buffer" gtk_text_view_get_buffer :: 
    Ptr TextView ->                         
    IO (Ptr Gtk.TextBuffer.TextBuffer)
textViewGetBuffer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Gtk.TextBuffer.TextBuffer
    
textViewGetBuffer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m TextBuffer
textViewGetBuffer a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextBuffer
result <- Ptr TextView -> IO (Ptr TextBuffer)
gtk_text_view_get_buffer Ptr TextView
textView'
    Text -> Ptr TextBuffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"textViewGetBuffer" 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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    TextBuffer -> IO TextBuffer
forall (m :: * -> *) a. Monad m => a -> m a
return TextBuffer
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetBufferMethodInfo
instance (signature ~ (m Gtk.TextBuffer.TextBuffer), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetBufferMethodInfo a signature where
    overloadedMethod = textViewGetBuffer
instance O.OverloadedMethodInfo TextViewGetBufferMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetBuffer",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetBuffer"
        }
#endif
foreign import ccall "gtk_text_view_get_cursor_locations" gtk_text_view_get_cursor_locations :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    Ptr Gdk.Rectangle.Rectangle ->          
    Ptr Gdk.Rectangle.Rectangle ->          
    IO ()
textViewGetCursorLocations ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Maybe (Gtk.TextIter.TextIter)
    
    -> m ((Gdk.Rectangle.Rectangle, Gdk.Rectangle.Rectangle))
textViewGetCursorLocations :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Maybe TextIter -> m (Rectangle, Rectangle)
textViewGetCursorLocations a
textView Maybe TextIter
iter = IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
maybeIter <- case Maybe TextIter
iter of
        Maybe TextIter
Nothing -> Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
forall a. Ptr a
nullPtr
        Just TextIter
jIter -> do
            Ptr TextIter
jIter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
jIter
            Ptr TextIter -> IO (Ptr TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextIter
jIter'
    Ptr Rectangle
strong <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Gdk.Rectangle.Rectangle)
    Ptr Rectangle
weak <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Gdk.Rectangle.Rectangle)
    Ptr TextView
-> Ptr TextIter -> Ptr Rectangle -> Ptr Rectangle -> IO ()
gtk_text_view_get_cursor_locations Ptr TextView
textView' Ptr TextIter
maybeIter Ptr Rectangle
strong Ptr Rectangle
weak
    Rectangle
strong' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Gdk.Rectangle.Rectangle) Ptr Rectangle
strong
    Rectangle
weak' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Gdk.Rectangle.Rectangle) Ptr Rectangle
weak
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Maybe TextIter -> (TextIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TextIter
iter TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    (Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
strong', Rectangle
weak')
#if defined(ENABLE_OVERLOADING)
data TextViewGetCursorLocationsMethodInfo
instance (signature ~ (Maybe (Gtk.TextIter.TextIter) -> m ((Gdk.Rectangle.Rectangle, Gdk.Rectangle.Rectangle))), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetCursorLocationsMethodInfo a signature where
    overloadedMethod = textViewGetCursorLocations
instance O.OverloadedMethodInfo TextViewGetCursorLocationsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetCursorLocations",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetCursorLocations"
        }
#endif
foreign import ccall "gtk_text_view_get_cursor_visible" gtk_text_view_get_cursor_visible :: 
    Ptr TextView ->                         
    IO CInt
textViewGetCursorVisible ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Bool
    
textViewGetCursorVisible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Bool
textViewGetCursorVisible a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CInt
result <- Ptr TextView -> IO CInt
gtk_text_view_get_cursor_visible Ptr TextView
textView'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetCursorVisibleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetCursorVisibleMethodInfo a signature where
    overloadedMethod = textViewGetCursorVisible
instance O.OverloadedMethodInfo TextViewGetCursorVisibleMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetCursorVisible",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetCursorVisible"
        }
#endif
foreign import ccall "gtk_text_view_get_editable" gtk_text_view_get_editable :: 
    Ptr TextView ->                         
    IO CInt
textViewGetEditable ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Bool
    
textViewGetEditable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Bool
textViewGetEditable a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CInt
result <- Ptr TextView -> IO CInt
gtk_text_view_get_editable Ptr TextView
textView'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetEditableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetEditableMethodInfo a signature where
    overloadedMethod = textViewGetEditable
instance O.OverloadedMethodInfo TextViewGetEditableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetEditable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetEditable"
        }
#endif
foreign import ccall "gtk_text_view_get_extra_menu"  :: 
    Ptr TextView ->                         
    IO (Ptr Gio.MenuModel.MenuModel)
textViewGetExtraMenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Gio.MenuModel.MenuModel
    
 a
textView = IO MenuModel -> m MenuModel
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MenuModel -> m MenuModel) -> IO MenuModel -> m MenuModel
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr MenuModel
result <- Ptr TextView -> IO (Ptr MenuModel)
gtk_text_view_get_extra_menu Ptr TextView
textView'
    Text -> Ptr MenuModel -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"textViewGetExtraMenu" Ptr MenuModel
result
    MenuModel
result' <- ((ManagedPtr MenuModel -> MenuModel)
-> Ptr MenuModel -> IO MenuModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel) Ptr MenuModel
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    MenuModel -> IO MenuModel
forall (m :: * -> *) a. Monad m => a -> m a
return MenuModel
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetExtraMenuMethodInfo
instance (signature ~ (m Gio.MenuModel.MenuModel), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetExtraMenuMethodInfo a signature where
    overloadedMethod = textViewGetExtraMenu
instance O.OverloadedMethodInfo TextViewGetExtraMenuMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetExtraMenu",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetExtraMenu"
        }
#endif
foreign import ccall "gtk_text_view_get_gutter" gtk_text_view_get_gutter :: 
    Ptr TextView ->                         
    CUInt ->                                
    IO (Ptr Gtk.Widget.Widget)
textViewGetGutter ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.Enums.TextWindowType
    
    -> m (Maybe Gtk.Widget.Widget)
    
textViewGetGutter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextWindowType -> m (Maybe Widget)
textViewGetGutter a
textView TextWindowType
win = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let win' :: CUInt
win' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TextWindowType -> Int) -> TextWindowType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextWindowType -> Int
forall a. Enum a => a -> Int
fromEnum) TextWindowType
win
    Ptr Widget
result <- Ptr TextView -> CUInt -> IO (Ptr Widget)
gtk_text_view_get_gutter Ptr TextView
textView' CUInt
win'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Maybe Widget -> IO (Maybe Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult
#if defined(ENABLE_OVERLOADING)
data TextViewGetGutterMethodInfo
instance (signature ~ (Gtk.Enums.TextWindowType -> m (Maybe Gtk.Widget.Widget)), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetGutterMethodInfo a signature where
    overloadedMethod = textViewGetGutter
instance O.OverloadedMethodInfo TextViewGetGutterMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetGutter",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetGutter"
        }
#endif
foreign import ccall "gtk_text_view_get_indent" gtk_text_view_get_indent :: 
    Ptr TextView ->                         
    IO Int32
textViewGetIndent ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Int32
    
textViewGetIndent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Int32
textViewGetIndent a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Int32
result <- Ptr TextView -> IO Int32
gtk_text_view_get_indent Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data TextViewGetIndentMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetIndentMethodInfo a signature where
    overloadedMethod = textViewGetIndent
instance O.OverloadedMethodInfo TextViewGetIndentMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetIndent",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetIndent"
        }
#endif
foreign import ccall "gtk_text_view_get_input_hints" gtk_text_view_get_input_hints :: 
    Ptr TextView ->                         
    IO CUInt
textViewGetInputHints ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m [Gtk.Flags.InputHints]
textViewGetInputHints :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m [InputHints]
textViewGetInputHints a
textView = IO [InputHints] -> m [InputHints]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [InputHints] -> m [InputHints])
-> IO [InputHints] -> m [InputHints]
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CUInt
result <- Ptr TextView -> IO CUInt
gtk_text_view_get_input_hints Ptr TextView
textView'
    let result' :: [InputHints]
result' = CUInt -> [InputHints]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    [InputHints] -> IO [InputHints]
forall (m :: * -> *) a. Monad m => a -> m a
return [InputHints]
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetInputHintsMethodInfo
instance (signature ~ (m [Gtk.Flags.InputHints]), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetInputHintsMethodInfo a signature where
    overloadedMethod = textViewGetInputHints
instance O.OverloadedMethodInfo TextViewGetInputHintsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetInputHints",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetInputHints"
        }
#endif
foreign import ccall "gtk_text_view_get_input_purpose" gtk_text_view_get_input_purpose :: 
    Ptr TextView ->                         
    IO CUInt
textViewGetInputPurpose ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Gtk.Enums.InputPurpose
textViewGetInputPurpose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m InputPurpose
textViewGetInputPurpose a
textView = IO InputPurpose -> m InputPurpose
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputPurpose -> m InputPurpose)
-> IO InputPurpose -> m InputPurpose
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CUInt
result <- Ptr TextView -> IO CUInt
gtk_text_view_get_input_purpose Ptr TextView
textView'
    let result' :: InputPurpose
result' = (Int -> InputPurpose
forall a. Enum a => Int -> a
toEnum (Int -> InputPurpose) -> (CUInt -> Int) -> CUInt -> InputPurpose
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    InputPurpose -> IO InputPurpose
forall (m :: * -> *) a. Monad m => a -> m a
return InputPurpose
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetInputPurposeMethodInfo
instance (signature ~ (m Gtk.Enums.InputPurpose), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetInputPurposeMethodInfo a signature where
    overloadedMethod = textViewGetInputPurpose
instance O.OverloadedMethodInfo TextViewGetInputPurposeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetInputPurpose",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetInputPurpose"
        }
#endif
foreign import ccall "gtk_text_view_get_iter_at_location" gtk_text_view_get_iter_at_location :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    Int32 ->                                
    Int32 ->                                
    IO CInt
textViewGetIterAtLocation ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> Int32
    
    -> m ((Bool, Gtk.TextIter.TextIter))
    
textViewGetIterAtLocation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> Int32 -> m (Bool, TextIter)
textViewGetIterAtLocation a
textView Int32
x Int32
y = IO (Bool, TextIter) -> m (Bool, TextIter)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, TextIter) -> m (Bool, TextIter))
-> IO (Bool, TextIter) -> m (Bool, TextIter)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter <- Int -> IO (Ptr TextIter)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
80 :: IO (Ptr Gtk.TextIter.TextIter)
    CInt
result <- Ptr TextView -> Ptr TextIter -> Int32 -> Int32 -> IO CInt
gtk_text_view_get_iter_at_location Ptr TextView
textView' Ptr TextIter
iter Int32
x Int32
y
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    TextIter
iter' <- ((ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
Gtk.TextIter.TextIter) Ptr TextIter
iter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    (Bool, TextIter) -> IO (Bool, TextIter)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', TextIter
iter')
#if defined(ENABLE_OVERLOADING)
data TextViewGetIterAtLocationMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ((Bool, Gtk.TextIter.TextIter))), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetIterAtLocationMethodInfo a signature where
    overloadedMethod = textViewGetIterAtLocation
instance O.OverloadedMethodInfo TextViewGetIterAtLocationMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetIterAtLocation",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetIterAtLocation"
        }
#endif
foreign import ccall "gtk_text_view_get_iter_at_position" gtk_text_view_get_iter_at_position :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    Ptr Int32 ->                            
    Int32 ->                                
    Int32 ->                                
    IO CInt
textViewGetIterAtPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> Int32
    
    -> m ((Bool, Gtk.TextIter.TextIter, Int32))
    
textViewGetIterAtPosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> Int32 -> m (Bool, TextIter, Int32)
textViewGetIterAtPosition a
textView Int32
x Int32
y = IO (Bool, TextIter, Int32) -> m (Bool, TextIter, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, TextIter, Int32) -> m (Bool, TextIter, Int32))
-> IO (Bool, TextIter, Int32) -> m (Bool, TextIter, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter <- Int -> IO (Ptr TextIter)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
80 :: IO (Ptr Gtk.TextIter.TextIter)
    Ptr Int32
trailing <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr TextView
-> Ptr TextIter -> Ptr Int32 -> Int32 -> Int32 -> IO CInt
gtk_text_view_get_iter_at_position Ptr TextView
textView' Ptr TextIter
iter Ptr Int32
trailing Int32
x Int32
y
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    TextIter
iter' <- ((ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
Gtk.TextIter.TextIter) Ptr TextIter
iter
    Int32
trailing' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
trailing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
trailing
    (Bool, TextIter, Int32) -> IO (Bool, TextIter, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', TextIter
iter', Int32
trailing')
#if defined(ENABLE_OVERLOADING)
data TextViewGetIterAtPositionMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ((Bool, Gtk.TextIter.TextIter, Int32))), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetIterAtPositionMethodInfo a signature where
    overloadedMethod = textViewGetIterAtPosition
instance O.OverloadedMethodInfo TextViewGetIterAtPositionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetIterAtPosition",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetIterAtPosition"
        }
#endif
foreign import ccall "gtk_text_view_get_iter_location" gtk_text_view_get_iter_location :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    Ptr Gdk.Rectangle.Rectangle ->          
    IO ()
textViewGetIterLocation ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> m (Gdk.Rectangle.Rectangle)
textViewGetIterLocation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> m Rectangle
textViewGetIterLocation a
textView TextIter
iter = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr Rectangle
location <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Gdk.Rectangle.Rectangle)
    Ptr TextView -> Ptr TextIter -> Ptr Rectangle -> IO ()
gtk_text_view_get_iter_location Ptr TextView
textView' Ptr TextIter
iter' Ptr Rectangle
location
    Rectangle
location' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Gdk.Rectangle.Rectangle) Ptr Rectangle
location
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
location'
#if defined(ENABLE_OVERLOADING)
data TextViewGetIterLocationMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> m (Gdk.Rectangle.Rectangle)), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetIterLocationMethodInfo a signature where
    overloadedMethod = textViewGetIterLocation
instance O.OverloadedMethodInfo TextViewGetIterLocationMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetIterLocation",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetIterLocation"
        }
#endif
foreign import ccall "gtk_text_view_get_justification" gtk_text_view_get_justification :: 
    Ptr TextView ->                         
    IO CUInt
textViewGetJustification ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Gtk.Enums.Justification
    
textViewGetJustification :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Justification
textViewGetJustification a
textView = IO Justification -> m Justification
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Justification -> m Justification)
-> IO Justification -> m Justification
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CUInt
result <- Ptr TextView -> IO CUInt
gtk_text_view_get_justification Ptr TextView
textView'
    let result' :: Justification
result' = (Int -> Justification
forall a. Enum a => Int -> a
toEnum (Int -> Justification) -> (CUInt -> Int) -> CUInt -> Justification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Justification -> IO Justification
forall (m :: * -> *) a. Monad m => a -> m a
return Justification
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetJustificationMethodInfo
instance (signature ~ (m Gtk.Enums.Justification), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetJustificationMethodInfo a signature where
    overloadedMethod = textViewGetJustification
instance O.OverloadedMethodInfo TextViewGetJustificationMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetJustification",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetJustification"
        }
#endif
foreign import ccall "gtk_text_view_get_left_margin" gtk_text_view_get_left_margin :: 
    Ptr TextView ->                         
    IO Int32
textViewGetLeftMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Int32
    
textViewGetLeftMargin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Int32
textViewGetLeftMargin a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Int32
result <- Ptr TextView -> IO Int32
gtk_text_view_get_left_margin Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data TextViewGetLeftMarginMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetLeftMarginMethodInfo a signature where
    overloadedMethod = textViewGetLeftMargin
instance O.OverloadedMethodInfo TextViewGetLeftMarginMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetLeftMargin",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetLeftMargin"
        }
#endif
foreign import ccall "gtk_text_view_get_line_at_y" gtk_text_view_get_line_at_y :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    Int32 ->                                
    Ptr Int32 ->                            
    IO ()
textViewGetLineAtY ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ((Gtk.TextIter.TextIter, Int32))
textViewGetLineAtY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m (TextIter, Int32)
textViewGetLineAtY a
textView Int32
y = IO (TextIter, Int32) -> m (TextIter, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (TextIter, Int32) -> m (TextIter, Int32))
-> IO (TextIter, Int32) -> m (TextIter, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
targetIter <- Int -> IO (Ptr TextIter)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
80 :: IO (Ptr Gtk.TextIter.TextIter)
    Ptr Int32
lineTop <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr TextView -> Ptr TextIter -> Int32 -> Ptr Int32 -> IO ()
gtk_text_view_get_line_at_y Ptr TextView
textView' Ptr TextIter
targetIter Int32
y Ptr Int32
lineTop
    TextIter
targetIter' <- ((ManagedPtr TextIter -> TextIter) -> Ptr TextIter -> IO TextIter
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextIter -> TextIter
Gtk.TextIter.TextIter) Ptr TextIter
targetIter
    Int32
lineTop' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
lineTop
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
lineTop
    (TextIter, Int32) -> IO (TextIter, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextIter
targetIter', Int32
lineTop')
#if defined(ENABLE_OVERLOADING)
data TextViewGetLineAtYMethodInfo
instance (signature ~ (Int32 -> m ((Gtk.TextIter.TextIter, Int32))), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetLineAtYMethodInfo a signature where
    overloadedMethod = textViewGetLineAtY
instance O.OverloadedMethodInfo TextViewGetLineAtYMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetLineAtY",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetLineAtY"
        }
#endif
foreign import ccall "gtk_text_view_get_line_yrange" gtk_text_view_get_line_yrange :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    Ptr Int32 ->                            
    Ptr Int32 ->                            
    IO ()
textViewGetLineYrange ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> m ((Int32, Int32))
textViewGetLineYrange :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> m (Int32, Int32)
textViewGetLineYrange a
textView TextIter
iter = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    Ptr Int32
y <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr TextView -> Ptr TextIter -> Ptr Int32 -> Ptr Int32 -> IO ()
gtk_text_view_get_line_yrange Ptr TextView
textView' Ptr TextIter
iter' Ptr Int32
y Ptr Int32
height
    Int32
y' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    TextIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextIter
iter
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
y', Int32
height')
#if defined(ENABLE_OVERLOADING)
data TextViewGetLineYrangeMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> m ((Int32, Int32))), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetLineYrangeMethodInfo a signature where
    overloadedMethod = textViewGetLineYrange
instance O.OverloadedMethodInfo TextViewGetLineYrangeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetLineYrange",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetLineYrange"
        }
#endif
foreign import ccall "gtk_text_view_get_monospace" gtk_text_view_get_monospace :: 
    Ptr TextView ->                         
    IO CInt
textViewGetMonospace ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Bool
    
textViewGetMonospace :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Bool
textViewGetMonospace a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CInt
result <- Ptr TextView -> IO CInt
gtk_text_view_get_monospace Ptr TextView
textView'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetMonospaceMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetMonospaceMethodInfo a signature where
    overloadedMethod = textViewGetMonospace
instance O.OverloadedMethodInfo TextViewGetMonospaceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetMonospace",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetMonospace"
        }
#endif
foreign import ccall "gtk_text_view_get_overwrite" gtk_text_view_get_overwrite :: 
    Ptr TextView ->                         
    IO CInt
textViewGetOverwrite ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Bool
    
textViewGetOverwrite :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Bool
textViewGetOverwrite a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CInt
result <- Ptr TextView -> IO CInt
gtk_text_view_get_overwrite Ptr TextView
textView'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetOverwriteMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetOverwriteMethodInfo a signature where
    overloadedMethod = textViewGetOverwrite
instance O.OverloadedMethodInfo TextViewGetOverwriteMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetOverwrite",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetOverwrite"
        }
#endif
foreign import ccall "gtk_text_view_get_pixels_above_lines" gtk_text_view_get_pixels_above_lines :: 
    Ptr TextView ->                         
    IO Int32
textViewGetPixelsAboveLines ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Int32
    
textViewGetPixelsAboveLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Int32
textViewGetPixelsAboveLines a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Int32
result <- Ptr TextView -> IO Int32
gtk_text_view_get_pixels_above_lines Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data TextViewGetPixelsAboveLinesMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetPixelsAboveLinesMethodInfo a signature where
    overloadedMethod = textViewGetPixelsAboveLines
instance O.OverloadedMethodInfo TextViewGetPixelsAboveLinesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetPixelsAboveLines",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetPixelsAboveLines"
        }
#endif
foreign import ccall "gtk_text_view_get_pixels_below_lines" gtk_text_view_get_pixels_below_lines :: 
    Ptr TextView ->                         
    IO Int32
textViewGetPixelsBelowLines ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Int32
    
textViewGetPixelsBelowLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Int32
textViewGetPixelsBelowLines a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Int32
result <- Ptr TextView -> IO Int32
gtk_text_view_get_pixels_below_lines Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data TextViewGetPixelsBelowLinesMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetPixelsBelowLinesMethodInfo a signature where
    overloadedMethod = textViewGetPixelsBelowLines
instance O.OverloadedMethodInfo TextViewGetPixelsBelowLinesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetPixelsBelowLines",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetPixelsBelowLines"
        }
#endif
foreign import ccall "gtk_text_view_get_pixels_inside_wrap" gtk_text_view_get_pixels_inside_wrap :: 
    Ptr TextView ->                         
    IO Int32
textViewGetPixelsInsideWrap ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Int32
    
textViewGetPixelsInsideWrap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Int32
textViewGetPixelsInsideWrap a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Int32
result <- Ptr TextView -> IO Int32
gtk_text_view_get_pixels_inside_wrap Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data TextViewGetPixelsInsideWrapMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetPixelsInsideWrapMethodInfo a signature where
    overloadedMethod = textViewGetPixelsInsideWrap
instance O.OverloadedMethodInfo TextViewGetPixelsInsideWrapMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetPixelsInsideWrap",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetPixelsInsideWrap"
        }
#endif
foreign import ccall "gtk_text_view_get_right_margin" gtk_text_view_get_right_margin :: 
    Ptr TextView ->                         
    IO Int32
textViewGetRightMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Int32
    
textViewGetRightMargin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Int32
textViewGetRightMargin a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Int32
result <- Ptr TextView -> IO Int32
gtk_text_view_get_right_margin Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data TextViewGetRightMarginMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetRightMarginMethodInfo a signature where
    overloadedMethod = textViewGetRightMargin
instance O.OverloadedMethodInfo TextViewGetRightMarginMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetRightMargin",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetRightMargin"
        }
#endif
foreign import ccall "gtk_text_view_get_tabs" gtk_text_view_get_tabs :: 
    Ptr TextView ->                         
    IO (Ptr Pango.TabArray.TabArray)
textViewGetTabs ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m (Maybe Pango.TabArray.TabArray)
    
    
textViewGetTabs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m (Maybe TabArray)
textViewGetTabs a
textView = IO (Maybe TabArray) -> m (Maybe TabArray)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TabArray) -> m (Maybe TabArray))
-> IO (Maybe TabArray) -> m (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TabArray
result <- Ptr TextView -> IO (Ptr TabArray)
gtk_text_view_get_tabs Ptr TextView
textView'
    Maybe TabArray
maybeResult <- Ptr TabArray
-> (Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TabArray
result ((Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray))
-> (Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ \Ptr TabArray
result' -> do
        TabArray
result'' <- ((ManagedPtr TabArray -> TabArray) -> Ptr TabArray -> IO TabArray
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TabArray -> TabArray
Pango.TabArray.TabArray) Ptr TabArray
result'
        TabArray -> IO TabArray
forall (m :: * -> *) a. Monad m => a -> m a
return TabArray
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Maybe TabArray -> IO (Maybe TabArray)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TabArray
maybeResult
#if defined(ENABLE_OVERLOADING)
data TextViewGetTabsMethodInfo
instance (signature ~ (m (Maybe Pango.TabArray.TabArray)), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetTabsMethodInfo a signature where
    overloadedMethod = textViewGetTabs
instance O.OverloadedMethodInfo TextViewGetTabsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetTabs",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetTabs"
        }
#endif
foreign import ccall "gtk_text_view_get_top_margin" gtk_text_view_get_top_margin :: 
    Ptr TextView ->                         
    IO Int32
textViewGetTopMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Int32
    
textViewGetTopMargin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Int32
textViewGetTopMargin a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Int32
result <- Ptr TextView -> IO Int32
gtk_text_view_get_top_margin Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data TextViewGetTopMarginMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetTopMarginMethodInfo a signature where
    overloadedMethod = textViewGetTopMargin
instance O.OverloadedMethodInfo TextViewGetTopMarginMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetTopMargin",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetTopMargin"
        }
#endif
foreign import ccall "gtk_text_view_get_visible_rect" gtk_text_view_get_visible_rect :: 
    Ptr TextView ->                         
    Ptr Gdk.Rectangle.Rectangle ->          
    IO ()
textViewGetVisibleRect ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m (Gdk.Rectangle.Rectangle)
textViewGetVisibleRect :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Rectangle
textViewGetVisibleRect a
textView = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr Rectangle
visibleRect <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Gdk.Rectangle.Rectangle)
    Ptr TextView -> Ptr Rectangle -> IO ()
gtk_text_view_get_visible_rect Ptr TextView
textView' Ptr Rectangle
visibleRect
    Rectangle
visibleRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Gdk.Rectangle.Rectangle) Ptr Rectangle
visibleRect
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
visibleRect'
#if defined(ENABLE_OVERLOADING)
data TextViewGetVisibleRectMethodInfo
instance (signature ~ (m (Gdk.Rectangle.Rectangle)), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetVisibleRectMethodInfo a signature where
    overloadedMethod = textViewGetVisibleRect
instance O.OverloadedMethodInfo TextViewGetVisibleRectMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetVisibleRect",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetVisibleRect"
        }
#endif
foreign import ccall "gtk_text_view_get_wrap_mode" gtk_text_view_get_wrap_mode :: 
    Ptr TextView ->                         
    IO CUInt
textViewGetWrapMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Gtk.Enums.WrapMode
    
textViewGetWrapMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m WrapMode
textViewGetWrapMode a
textView = IO WrapMode -> m WrapMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WrapMode -> m WrapMode) -> IO WrapMode -> m WrapMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CUInt
result <- Ptr TextView -> IO CUInt
gtk_text_view_get_wrap_mode Ptr TextView
textView'
    let result' :: WrapMode
result' = (Int -> WrapMode
forall a. Enum a => Int -> a
toEnum (Int -> WrapMode) -> (CUInt -> Int) -> CUInt -> WrapMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    WrapMode -> IO WrapMode
forall (m :: * -> *) a. Monad m => a -> m a
return WrapMode
result'
#if defined(ENABLE_OVERLOADING)
data TextViewGetWrapModeMethodInfo
instance (signature ~ (m Gtk.Enums.WrapMode), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewGetWrapModeMethodInfo a signature where
    overloadedMethod = textViewGetWrapMode
instance O.OverloadedMethodInfo TextViewGetWrapModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewGetWrapMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewGetWrapMode"
        }
#endif
foreign import ccall "gtk_text_view_im_context_filter_keypress" gtk_text_view_im_context_filter_keypress :: 
    Ptr TextView ->                         
    Ptr Gdk.Event.Event ->                  
    IO CInt
textViewImContextFilterKeypress ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gdk.Event.IsEvent b) =>
    a
    
    -> b
    
    -> m Bool
    
textViewImContextFilterKeypress :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsEvent b) =>
a -> b -> m Bool
textViewImContextFilterKeypress a
textView b
event = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr Event
event' <- b -> IO (Ptr Event)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
event
    CInt
result <- Ptr TextView -> Ptr Event -> IO CInt
gtk_text_view_im_context_filter_keypress Ptr TextView
textView' Ptr Event
event'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
event
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextViewImContextFilterKeypressMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsTextView a, Gdk.Event.IsEvent b) => O.OverloadedMethod TextViewImContextFilterKeypressMethodInfo a signature where
    overloadedMethod = textViewImContextFilterKeypress
instance O.OverloadedMethodInfo TextViewImContextFilterKeypressMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewImContextFilterKeypress",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewImContextFilterKeypress"
        }
#endif
foreign import ccall "gtk_text_view_move_mark_onscreen" gtk_text_view_move_mark_onscreen :: 
    Ptr TextView ->                         
    Ptr Gtk.TextMark.TextMark ->            
    IO CInt
textViewMoveMarkOnscreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.TextMark.IsTextMark b) =>
    a
    
    -> b
    
    -> m Bool
    
textViewMoveMarkOnscreen :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsTextMark b) =>
a -> b -> m Bool
textViewMoveMarkOnscreen a
textView b
mark = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextMark
mark' <- b -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
mark
    CInt
result <- Ptr TextView -> Ptr TextMark -> IO CInt
gtk_text_view_move_mark_onscreen Ptr TextView
textView' Ptr TextMark
mark'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
mark
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextViewMoveMarkOnscreenMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsTextView a, Gtk.TextMark.IsTextMark b) => O.OverloadedMethod TextViewMoveMarkOnscreenMethodInfo a signature where
    overloadedMethod = textViewMoveMarkOnscreen
instance O.OverloadedMethodInfo TextViewMoveMarkOnscreenMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewMoveMarkOnscreen",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewMoveMarkOnscreen"
        }
#endif
foreign import ccall "gtk_text_view_move_overlay" gtk_text_view_move_overlay :: 
    Ptr TextView ->                         
    Ptr Gtk.Widget.Widget ->                
    Int32 ->                                
    Int32 ->                                
    IO ()
textViewMoveOverlay ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.Widget.IsWidget b) =>
    a
    
    -> b
    
    -> Int32
    
    -> Int32
    
    -> m ()
textViewMoveOverlay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsWidget b) =>
a -> b -> Int32 -> Int32 -> m ()
textViewMoveOverlay a
textView b
child Int32
xpos Int32
ypos = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr TextView -> Ptr Widget -> Int32 -> Int32 -> IO ()
gtk_text_view_move_overlay Ptr TextView
textView' Ptr Widget
child' Int32
xpos Int32
ypos
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewMoveOverlayMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> m ()), MonadIO m, IsTextView a, Gtk.Widget.IsWidget b) => O.OverloadedMethod TextViewMoveOverlayMethodInfo a signature where
    overloadedMethod = textViewMoveOverlay
instance O.OverloadedMethodInfo TextViewMoveOverlayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewMoveOverlay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewMoveOverlay"
        }
#endif
foreign import ccall "gtk_text_view_move_visually" gtk_text_view_move_visually :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    Int32 ->                                
    IO CInt
textViewMoveVisually ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> Int32
    
    
    -> m Bool
    
textViewMoveVisually :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> Int32 -> m Bool
textViewMoveVisually a
textView TextIter
iter 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextView -> Ptr TextIter -> Int32 -> IO CInt
gtk_text_view_move_visually Ptr TextView
textView' Ptr TextIter
iter' Int32
count
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    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 TextViewMoveVisuallyMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> Int32 -> m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewMoveVisuallyMethodInfo a signature where
    overloadedMethod = textViewMoveVisually
instance O.OverloadedMethodInfo TextViewMoveVisuallyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewMoveVisually",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewMoveVisually"
        }
#endif
foreign import ccall "gtk_text_view_place_cursor_onscreen" gtk_text_view_place_cursor_onscreen :: 
    Ptr TextView ->                         
    IO CInt
textViewPlaceCursorOnscreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m Bool
    
textViewPlaceCursorOnscreen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m Bool
textViewPlaceCursorOnscreen a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    CInt
result <- Ptr TextView -> IO CInt
gtk_text_view_place_cursor_onscreen Ptr TextView
textView'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextViewPlaceCursorOnscreenMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewPlaceCursorOnscreenMethodInfo a signature where
    overloadedMethod = textViewPlaceCursorOnscreen
instance O.OverloadedMethodInfo TextViewPlaceCursorOnscreenMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewPlaceCursorOnscreen",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewPlaceCursorOnscreen"
        }
#endif
foreign import ccall "gtk_text_view_remove" gtk_text_view_remove :: 
    Ptr TextView ->                         
    Ptr Gtk.Widget.Widget ->                
    IO ()
textViewRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.Widget.IsWidget b) =>
    a
    
    -> b
    
    -> m ()
textViewRemove :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsWidget b) =>
a -> b -> m ()
textViewRemove a
textView b
child = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr TextView -> Ptr Widget -> IO ()
gtk_text_view_remove Ptr TextView
textView' Ptr Widget
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewRemoveMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTextView a, Gtk.Widget.IsWidget b) => O.OverloadedMethod TextViewRemoveMethodInfo a signature where
    overloadedMethod = textViewRemove
instance O.OverloadedMethodInfo TextViewRemoveMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewRemove",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewRemove"
        }
#endif
foreign import ccall "gtk_text_view_reset_cursor_blink" gtk_text_view_reset_cursor_blink :: 
    Ptr TextView ->                         
    IO ()
textViewResetCursorBlink ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m ()
textViewResetCursorBlink :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m ()
textViewResetCursorBlink a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> IO ()
gtk_text_view_reset_cursor_blink Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewResetCursorBlinkMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewResetCursorBlinkMethodInfo a signature where
    overloadedMethod = textViewResetCursorBlink
instance O.OverloadedMethodInfo TextViewResetCursorBlinkMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewResetCursorBlink",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewResetCursorBlink"
        }
#endif
foreign import ccall "gtk_text_view_reset_im_context" gtk_text_view_reset_im_context :: 
    Ptr TextView ->                         
    IO ()
textViewResetImContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> m ()
textViewResetImContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> m ()
textViewResetImContext a
textView = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> IO ()
gtk_text_view_reset_im_context Ptr TextView
textView'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewResetImContextMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewResetImContextMethodInfo a signature where
    overloadedMethod = textViewResetImContext
instance O.OverloadedMethodInfo TextViewResetImContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewResetImContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewResetImContext"
        }
#endif
foreign import ccall "gtk_text_view_scroll_mark_onscreen" gtk_text_view_scroll_mark_onscreen :: 
    Ptr TextView ->                         
    Ptr Gtk.TextMark.TextMark ->            
    IO ()
textViewScrollMarkOnscreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.TextMark.IsTextMark b) =>
    a
    
    -> b
    
    -> m ()
textViewScrollMarkOnscreen :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsTextMark b) =>
a -> b -> m ()
textViewScrollMarkOnscreen a
textView b
mark = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextMark
mark' <- b -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
mark
    Ptr TextView -> Ptr TextMark -> IO ()
gtk_text_view_scroll_mark_onscreen Ptr TextView
textView' Ptr TextMark
mark'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
mark
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewScrollMarkOnscreenMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTextView a, Gtk.TextMark.IsTextMark b) => O.OverloadedMethod TextViewScrollMarkOnscreenMethodInfo a signature where
    overloadedMethod = textViewScrollMarkOnscreen
instance O.OverloadedMethodInfo TextViewScrollMarkOnscreenMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewScrollMarkOnscreen",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewScrollMarkOnscreen"
        }
#endif
foreign import ccall "gtk_text_view_scroll_to_iter" gtk_text_view_scroll_to_iter :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    CDouble ->                              
    CInt ->                                 
    CDouble ->                              
    CDouble ->                              
    IO CInt
textViewScrollToIter ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> Double
    
    -> Bool
    
    
    -> Double
    
    -> Double
    
    -> m Bool
    
textViewScrollToIter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> Double -> Bool -> Double -> Double -> m Bool
textViewScrollToIter a
textView TextIter
iter Double
withinMargin Bool
useAlign Double
xalign Double
yalign = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    let withinMargin' :: CDouble
withinMargin' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
withinMargin
    let useAlign' :: CInt
useAlign' = (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
useAlign
    let xalign' :: CDouble
xalign' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
xalign
    let yalign' :: CDouble
yalign' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
yalign
    CInt
result <- Ptr TextView
-> Ptr TextIter -> CDouble -> CInt -> CDouble -> CDouble -> IO CInt
gtk_text_view_scroll_to_iter Ptr TextView
textView' Ptr TextIter
iter' CDouble
withinMargin' CInt
useAlign' CDouble
xalign' CDouble
yalign'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    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 TextViewScrollToIterMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> Double -> Bool -> Double -> Double -> m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewScrollToIterMethodInfo a signature where
    overloadedMethod = textViewScrollToIter
instance O.OverloadedMethodInfo TextViewScrollToIterMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewScrollToIter",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewScrollToIter"
        }
#endif
foreign import ccall "gtk_text_view_scroll_to_mark" gtk_text_view_scroll_to_mark :: 
    Ptr TextView ->                         
    Ptr Gtk.TextMark.TextMark ->            
    CDouble ->                              
    CInt ->                                 
    CDouble ->                              
    CDouble ->                              
    IO ()
textViewScrollToMark ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.TextMark.IsTextMark b) =>
    a
    
    -> b
    
    -> Double
    
    -> Bool
    
    
    -> Double
    
    -> Double
    
    -> m ()
textViewScrollToMark :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsTextMark b) =>
a -> b -> Double -> Bool -> Double -> Double -> m ()
textViewScrollToMark a
textView b
mark Double
withinMargin Bool
useAlign Double
xalign Double
yalign = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextMark
mark' <- b -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
mark
    let withinMargin' :: CDouble
withinMargin' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
withinMargin
    let useAlign' :: CInt
useAlign' = (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
useAlign
    let xalign' :: CDouble
xalign' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
xalign
    let yalign' :: CDouble
yalign' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
yalign
    Ptr TextView
-> Ptr TextMark -> CDouble -> CInt -> CDouble -> CDouble -> IO ()
gtk_text_view_scroll_to_mark Ptr TextView
textView' Ptr TextMark
mark' CDouble
withinMargin' CInt
useAlign' CDouble
xalign' CDouble
yalign'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
mark
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewScrollToMarkMethodInfo
instance (signature ~ (b -> Double -> Bool -> Double -> Double -> m ()), MonadIO m, IsTextView a, Gtk.TextMark.IsTextMark b) => O.OverloadedMethod TextViewScrollToMarkMethodInfo a signature where
    overloadedMethod = textViewScrollToMark
instance O.OverloadedMethodInfo TextViewScrollToMarkMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewScrollToMark",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewScrollToMark"
        }
#endif
foreign import ccall "gtk_text_view_set_accepts_tab" gtk_text_view_set_accepts_tab :: 
    Ptr TextView ->                         
    CInt ->                                 
    IO ()
textViewSetAcceptsTab ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Bool
    
    
    
    -> m ()
textViewSetAcceptsTab :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Bool -> m ()
textViewSetAcceptsTab a
textView Bool
acceptsTab = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let acceptsTab' :: CInt
acceptsTab' = (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
acceptsTab
    Ptr TextView -> CInt -> IO ()
gtk_text_view_set_accepts_tab Ptr TextView
textView' CInt
acceptsTab'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetAcceptsTabMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetAcceptsTabMethodInfo a signature where
    overloadedMethod = textViewSetAcceptsTab
instance O.OverloadedMethodInfo TextViewSetAcceptsTabMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetAcceptsTab",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetAcceptsTab"
        }
#endif
foreign import ccall "gtk_text_view_set_bottom_margin" gtk_text_view_set_bottom_margin :: 
    Ptr TextView ->                         
    Int32 ->                                
    IO ()
textViewSetBottomMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ()
textViewSetBottomMargin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m ()
textViewSetBottomMargin a
textView Int32
bottomMargin = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> Int32 -> IO ()
gtk_text_view_set_bottom_margin Ptr TextView
textView' Int32
bottomMargin
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetBottomMarginMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetBottomMarginMethodInfo a signature where
    overloadedMethod = textViewSetBottomMargin
instance O.OverloadedMethodInfo TextViewSetBottomMarginMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetBottomMargin",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetBottomMargin"
        }
#endif
foreign import ccall "gtk_text_view_set_buffer" gtk_text_view_set_buffer :: 
    Ptr TextView ->                         
    Ptr Gtk.TextBuffer.TextBuffer ->        
    IO ()
textViewSetBuffer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.TextBuffer.IsTextBuffer b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
textViewSetBuffer :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsTextBuffer b) =>
a -> Maybe b -> m ()
textViewSetBuffer a
textView Maybe b
buffer = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextBuffer
maybeBuffer <- case Maybe b
buffer of
        Maybe b
Nothing -> Ptr TextBuffer -> IO (Ptr TextBuffer)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextBuffer
forall a. Ptr a
nullPtr
        Just b
jBuffer -> do
            Ptr TextBuffer
jBuffer' <- b -> IO (Ptr TextBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jBuffer
            Ptr TextBuffer -> IO (Ptr TextBuffer)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TextBuffer
jBuffer'
    Ptr TextView -> Ptr TextBuffer -> IO ()
gtk_text_view_set_buffer Ptr TextView
textView' Ptr TextBuffer
maybeBuffer
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
buffer b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetBufferMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsTextView a, Gtk.TextBuffer.IsTextBuffer b) => O.OverloadedMethod TextViewSetBufferMethodInfo a signature where
    overloadedMethod = textViewSetBuffer
instance O.OverloadedMethodInfo TextViewSetBufferMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetBuffer",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetBuffer"
        }
#endif
foreign import ccall "gtk_text_view_set_cursor_visible" gtk_text_view_set_cursor_visible :: 
    Ptr TextView ->                         
    CInt ->                                 
    IO ()
textViewSetCursorVisible ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Bool
    
    -> m ()
textViewSetCursorVisible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Bool -> m ()
textViewSetCursorVisible a
textView Bool
setting = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let setting' :: CInt
setting' = (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
setting
    Ptr TextView -> CInt -> IO ()
gtk_text_view_set_cursor_visible Ptr TextView
textView' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetCursorVisibleMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetCursorVisibleMethodInfo a signature where
    overloadedMethod = textViewSetCursorVisible
instance O.OverloadedMethodInfo TextViewSetCursorVisibleMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetCursorVisible",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetCursorVisible"
        }
#endif
foreign import ccall "gtk_text_view_set_editable" gtk_text_view_set_editable :: 
    Ptr TextView ->                         
    CInt ->                                 
    IO ()
textViewSetEditable ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Bool
    
    -> m ()
textViewSetEditable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Bool -> m ()
textViewSetEditable a
textView Bool
setting = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let setting' :: CInt
setting' = (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
setting
    Ptr TextView -> CInt -> IO ()
gtk_text_view_set_editable Ptr TextView
textView' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetEditableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetEditableMethodInfo a signature where
    overloadedMethod = textViewSetEditable
instance O.OverloadedMethodInfo TextViewSetEditableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetEditable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetEditable"
        }
#endif
foreign import ccall "gtk_text_view_set_extra_menu"  :: 
    Ptr TextView ->                         
    Ptr Gio.MenuModel.MenuModel ->          
    IO ()
textViewSetExtraMenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gio.MenuModel.IsMenuModel b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
 a
textView Maybe b
model = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr MenuModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr MenuModel
jModel' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jModel'
    Ptr TextView -> Ptr MenuModel -> IO ()
gtk_text_view_set_extra_menu Ptr TextView
textView' Ptr MenuModel
maybeModel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetExtraMenuMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsTextView a, Gio.MenuModel.IsMenuModel b) => O.OverloadedMethod TextViewSetExtraMenuMethodInfo a signature where
    overloadedMethod = textViewSetExtraMenu
instance O.OverloadedMethodInfo TextViewSetExtraMenuMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetExtraMenu",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetExtraMenu"
        }
#endif
foreign import ccall "gtk_text_view_set_gutter" gtk_text_view_set_gutter :: 
    Ptr TextView ->                         
    CUInt ->                                
    Ptr Gtk.Widget.Widget ->                
    IO ()
textViewSetGutter ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a, Gtk.Widget.IsWidget b) =>
    a
    
    -> Gtk.Enums.TextWindowType
    
    -> Maybe (b)
    
    -> m ()
textViewSetGutter :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTextView a, IsWidget b) =>
a -> TextWindowType -> Maybe b -> m ()
textViewSetGutter a
textView TextWindowType
win Maybe b
widget = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let win' :: CUInt
win' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TextWindowType -> Int) -> TextWindowType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextWindowType -> Int
forall a. Enum a => a -> Int
fromEnum) TextWindowType
win
    Ptr Widget
maybeWidget <- case Maybe b
widget of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jWidget -> do
            Ptr Widget
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jWidget'
    Ptr TextView -> CUInt -> Ptr Widget -> IO ()
gtk_text_view_set_gutter Ptr TextView
textView' CUInt
win' Ptr Widget
maybeWidget
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
widget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetGutterMethodInfo
instance (signature ~ (Gtk.Enums.TextWindowType -> Maybe (b) -> m ()), MonadIO m, IsTextView a, Gtk.Widget.IsWidget b) => O.OverloadedMethod TextViewSetGutterMethodInfo a signature where
    overloadedMethod = textViewSetGutter
instance O.OverloadedMethodInfo TextViewSetGutterMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetGutter",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetGutter"
        }
#endif
foreign import ccall "gtk_text_view_set_indent" gtk_text_view_set_indent :: 
    Ptr TextView ->                         
    Int32 ->                                
    IO ()
textViewSetIndent ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ()
textViewSetIndent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m ()
textViewSetIndent a
textView Int32
indent = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> Int32 -> IO ()
gtk_text_view_set_indent Ptr TextView
textView' Int32
indent
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetIndentMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetIndentMethodInfo a signature where
    overloadedMethod = textViewSetIndent
instance O.OverloadedMethodInfo TextViewSetIndentMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetIndent",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetIndent"
        }
#endif
foreign import ccall "gtk_text_view_set_input_hints" gtk_text_view_set_input_hints :: 
    Ptr TextView ->                         
    CUInt ->                                
    IO ()
textViewSetInputHints ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> [Gtk.Flags.InputHints]
    
    -> m ()
textViewSetInputHints :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> [InputHints] -> m ()
textViewSetInputHints a
textView [InputHints]
hints = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let hints' :: CUInt
hints' = [InputHints] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [InputHints]
hints
    Ptr TextView -> CUInt -> IO ()
gtk_text_view_set_input_hints Ptr TextView
textView' CUInt
hints'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetInputHintsMethodInfo
instance (signature ~ ([Gtk.Flags.InputHints] -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetInputHintsMethodInfo a signature where
    overloadedMethod = textViewSetInputHints
instance O.OverloadedMethodInfo TextViewSetInputHintsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetInputHints",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetInputHints"
        }
#endif
foreign import ccall "gtk_text_view_set_input_purpose" gtk_text_view_set_input_purpose :: 
    Ptr TextView ->                         
    CUInt ->                                
    IO ()
textViewSetInputPurpose ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.Enums.InputPurpose
    
    -> m ()
textViewSetInputPurpose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> InputPurpose -> m ()
textViewSetInputPurpose a
textView InputPurpose
purpose = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let purpose' :: CUInt
purpose' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (InputPurpose -> Int) -> InputPurpose -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputPurpose -> Int
forall a. Enum a => a -> Int
fromEnum) InputPurpose
purpose
    Ptr TextView -> CUInt -> IO ()
gtk_text_view_set_input_purpose Ptr TextView
textView' CUInt
purpose'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetInputPurposeMethodInfo
instance (signature ~ (Gtk.Enums.InputPurpose -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetInputPurposeMethodInfo a signature where
    overloadedMethod = textViewSetInputPurpose
instance O.OverloadedMethodInfo TextViewSetInputPurposeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetInputPurpose",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetInputPurpose"
        }
#endif
foreign import ccall "gtk_text_view_set_justification" gtk_text_view_set_justification :: 
    Ptr TextView ->                         
    CUInt ->                                
    IO ()
textViewSetJustification ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.Enums.Justification
    
    -> m ()
textViewSetJustification :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Justification -> m ()
textViewSetJustification a
textView Justification
justification = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let justification' :: CUInt
justification' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Justification -> Int) -> Justification -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Justification -> Int
forall a. Enum a => a -> Int
fromEnum) Justification
justification
    Ptr TextView -> CUInt -> IO ()
gtk_text_view_set_justification Ptr TextView
textView' CUInt
justification'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetJustificationMethodInfo
instance (signature ~ (Gtk.Enums.Justification -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetJustificationMethodInfo a signature where
    overloadedMethod = textViewSetJustification
instance O.OverloadedMethodInfo TextViewSetJustificationMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetJustification",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetJustification"
        }
#endif
foreign import ccall "gtk_text_view_set_left_margin" gtk_text_view_set_left_margin :: 
    Ptr TextView ->                         
    Int32 ->                                
    IO ()
textViewSetLeftMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ()
textViewSetLeftMargin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m ()
textViewSetLeftMargin a
textView Int32
leftMargin = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> Int32 -> IO ()
gtk_text_view_set_left_margin Ptr TextView
textView' Int32
leftMargin
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetLeftMarginMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetLeftMarginMethodInfo a signature where
    overloadedMethod = textViewSetLeftMargin
instance O.OverloadedMethodInfo TextViewSetLeftMarginMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetLeftMargin",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetLeftMargin"
        }
#endif
foreign import ccall "gtk_text_view_set_monospace" gtk_text_view_set_monospace :: 
    Ptr TextView ->                         
    CInt ->                                 
    IO ()
textViewSetMonospace ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Bool
    
    -> m ()
textViewSetMonospace :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Bool -> m ()
textViewSetMonospace a
textView Bool
monospace = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let monospace' :: CInt
monospace' = (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
monospace
    Ptr TextView -> CInt -> IO ()
gtk_text_view_set_monospace Ptr TextView
textView' CInt
monospace'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetMonospaceMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetMonospaceMethodInfo a signature where
    overloadedMethod = textViewSetMonospace
instance O.OverloadedMethodInfo TextViewSetMonospaceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetMonospace",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetMonospace"
        }
#endif
foreign import ccall "gtk_text_view_set_overwrite" gtk_text_view_set_overwrite :: 
    Ptr TextView ->                         
    CInt ->                                 
    IO ()
textViewSetOverwrite ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Bool
    
    -> m ()
textViewSetOverwrite :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Bool -> m ()
textViewSetOverwrite a
textView Bool
overwrite = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let overwrite' :: CInt
overwrite' = (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
overwrite
    Ptr TextView -> CInt -> IO ()
gtk_text_view_set_overwrite Ptr TextView
textView' CInt
overwrite'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetOverwriteMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetOverwriteMethodInfo a signature where
    overloadedMethod = textViewSetOverwrite
instance O.OverloadedMethodInfo TextViewSetOverwriteMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetOverwrite",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetOverwrite"
        }
#endif
foreign import ccall "gtk_text_view_set_pixels_above_lines" gtk_text_view_set_pixels_above_lines :: 
    Ptr TextView ->                         
    Int32 ->                                
    IO ()
textViewSetPixelsAboveLines ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ()
textViewSetPixelsAboveLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m ()
textViewSetPixelsAboveLines a
textView Int32
pixelsAboveLines = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> Int32 -> IO ()
gtk_text_view_set_pixels_above_lines Ptr TextView
textView' Int32
pixelsAboveLines
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetPixelsAboveLinesMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetPixelsAboveLinesMethodInfo a signature where
    overloadedMethod = textViewSetPixelsAboveLines
instance O.OverloadedMethodInfo TextViewSetPixelsAboveLinesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetPixelsAboveLines",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetPixelsAboveLines"
        }
#endif
foreign import ccall "gtk_text_view_set_pixels_below_lines" gtk_text_view_set_pixels_below_lines :: 
    Ptr TextView ->                         
    Int32 ->                                
    IO ()
textViewSetPixelsBelowLines ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ()
textViewSetPixelsBelowLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m ()
textViewSetPixelsBelowLines a
textView Int32
pixelsBelowLines = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> Int32 -> IO ()
gtk_text_view_set_pixels_below_lines Ptr TextView
textView' Int32
pixelsBelowLines
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetPixelsBelowLinesMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetPixelsBelowLinesMethodInfo a signature where
    overloadedMethod = textViewSetPixelsBelowLines
instance O.OverloadedMethodInfo TextViewSetPixelsBelowLinesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetPixelsBelowLines",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetPixelsBelowLines"
        }
#endif
foreign import ccall "gtk_text_view_set_pixels_inside_wrap" gtk_text_view_set_pixels_inside_wrap :: 
    Ptr TextView ->                         
    Int32 ->                                
    IO ()
textViewSetPixelsInsideWrap ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ()
textViewSetPixelsInsideWrap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m ()
textViewSetPixelsInsideWrap a
textView Int32
pixelsInsideWrap = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> Int32 -> IO ()
gtk_text_view_set_pixels_inside_wrap Ptr TextView
textView' Int32
pixelsInsideWrap
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetPixelsInsideWrapMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetPixelsInsideWrapMethodInfo a signature where
    overloadedMethod = textViewSetPixelsInsideWrap
instance O.OverloadedMethodInfo TextViewSetPixelsInsideWrapMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetPixelsInsideWrap",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetPixelsInsideWrap"
        }
#endif
foreign import ccall "gtk_text_view_set_right_margin" gtk_text_view_set_right_margin :: 
    Ptr TextView ->                         
    Int32 ->                                
    IO ()
textViewSetRightMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ()
textViewSetRightMargin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m ()
textViewSetRightMargin a
textView Int32
rightMargin = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> Int32 -> IO ()
gtk_text_view_set_right_margin Ptr TextView
textView' Int32
rightMargin
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetRightMarginMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetRightMarginMethodInfo a signature where
    overloadedMethod = textViewSetRightMargin
instance O.OverloadedMethodInfo TextViewSetRightMarginMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetRightMargin",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetRightMargin"
        }
#endif
foreign import ccall "gtk_text_view_set_tabs" gtk_text_view_set_tabs :: 
    Ptr TextView ->                         
    Ptr Pango.TabArray.TabArray ->          
    IO ()
textViewSetTabs ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Pango.TabArray.TabArray
    
    -> m ()
textViewSetTabs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TabArray -> m ()
textViewSetTabs a
textView TabArray
tabs = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TabArray
tabs' <- TabArray -> IO (Ptr TabArray)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TabArray
tabs
    Ptr TextView -> Ptr TabArray -> IO ()
gtk_text_view_set_tabs Ptr TextView
textView' Ptr TabArray
tabs'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    TabArray -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TabArray
tabs
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetTabsMethodInfo
instance (signature ~ (Pango.TabArray.TabArray -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetTabsMethodInfo a signature where
    overloadedMethod = textViewSetTabs
instance O.OverloadedMethodInfo TextViewSetTabsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetTabs",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetTabs"
        }
#endif
foreign import ccall "gtk_text_view_set_top_margin" gtk_text_view_set_top_margin :: 
    Ptr TextView ->                         
    Int32 ->                                
    IO ()
textViewSetTopMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Int32
    
    -> m ()
textViewSetTopMargin :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> Int32 -> m ()
textViewSetTopMargin a
textView Int32
topMargin = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextView -> Int32 -> IO ()
gtk_text_view_set_top_margin Ptr TextView
textView' Int32
topMargin
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetTopMarginMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetTopMarginMethodInfo a signature where
    overloadedMethod = textViewSetTopMargin
instance O.OverloadedMethodInfo TextViewSetTopMarginMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetTopMargin",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetTopMargin"
        }
#endif
foreign import ccall "gtk_text_view_set_wrap_mode" gtk_text_view_set_wrap_mode :: 
    Ptr TextView ->                         
    CUInt ->                                
    IO ()
textViewSetWrapMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.Enums.WrapMode
    
    -> m ()
textViewSetWrapMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> WrapMode -> m ()
textViewSetWrapMode a
textView WrapMode
wrapMode = 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let wrapMode' :: CUInt
wrapMode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (WrapMode -> Int) -> WrapMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapMode -> Int
forall a. Enum a => a -> Int
fromEnum) WrapMode
wrapMode
    Ptr TextView -> CUInt -> IO ()
gtk_text_view_set_wrap_mode Ptr TextView
textView' CUInt
wrapMode'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextViewSetWrapModeMethodInfo
instance (signature ~ (Gtk.Enums.WrapMode -> m ()), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewSetWrapModeMethodInfo a signature where
    overloadedMethod = textViewSetWrapMode
instance O.OverloadedMethodInfo TextViewSetWrapModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewSetWrapMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewSetWrapMode"
        }
#endif
foreign import ccall "gtk_text_view_starts_display_line" gtk_text_view_starts_display_line :: 
    Ptr TextView ->                         
    Ptr Gtk.TextIter.TextIter ->            
    IO CInt
textViewStartsDisplayLine ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.TextIter.TextIter
    
    -> m Bool
    
textViewStartsDisplayLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextIter -> m Bool
textViewStartsDisplayLine a
textView 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 TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    Ptr TextIter
iter' <- TextIter -> IO (Ptr TextIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextIter
iter
    CInt
result <- Ptr TextView -> Ptr TextIter -> IO CInt
gtk_text_view_starts_display_line Ptr TextView
textView' Ptr TextIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    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 TextViewStartsDisplayLineMethodInfo
instance (signature ~ (Gtk.TextIter.TextIter -> m Bool), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewStartsDisplayLineMethodInfo a signature where
    overloadedMethod = textViewStartsDisplayLine
instance O.OverloadedMethodInfo TextViewStartsDisplayLineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewStartsDisplayLine",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewStartsDisplayLine"
        }
#endif
foreign import ccall "gtk_text_view_window_to_buffer_coords" gtk_text_view_window_to_buffer_coords :: 
    Ptr TextView ->                         
    CUInt ->                                
    Int32 ->                                
    Int32 ->                                
    Ptr Int32 ->                            
    Ptr Int32 ->                            
    IO ()
textViewWindowToBufferCoords ::
    (B.CallStack.HasCallStack, MonadIO m, IsTextView a) =>
    a
    
    -> Gtk.Enums.TextWindowType
    
    -> Int32
    
    -> Int32
    
    -> m ((Int32, Int32))
textViewWindowToBufferCoords :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextView a) =>
a -> TextWindowType -> Int32 -> Int32 -> m (Int32, Int32)
textViewWindowToBufferCoords a
textView TextWindowType
win Int32
windowX Int32
windowY = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextView
textView' <- a -> IO (Ptr TextView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
textView
    let win' :: CUInt
win' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TextWindowType -> Int) -> TextWindowType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextWindowType -> Int
forall a. Enum a => a -> Int
fromEnum) TextWindowType
win
    Ptr Int32
bufferX <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
bufferY <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr TextView
-> CUInt -> Int32 -> Int32 -> Ptr Int32 -> Ptr Int32 -> IO ()
gtk_text_view_window_to_buffer_coords Ptr TextView
textView' CUInt
win' Int32
windowX Int32
windowY Ptr Int32
bufferX Ptr Int32
bufferY
    Int32
bufferX' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
bufferX
    Int32
bufferY' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
bufferY
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
textView
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
bufferX
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
bufferY
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
bufferX', Int32
bufferY')
#if defined(ENABLE_OVERLOADING)
data TextViewWindowToBufferCoordsMethodInfo
instance (signature ~ (Gtk.Enums.TextWindowType -> Int32 -> Int32 -> m ((Int32, Int32))), MonadIO m, IsTextView a) => O.OverloadedMethod TextViewWindowToBufferCoordsMethodInfo a signature where
    overloadedMethod = textViewWindowToBufferCoords
instance O.OverloadedMethodInfo TextViewWindowToBufferCoordsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.TextView.textViewWindowToBufferCoords",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-TextView.html#v:textViewWindowToBufferCoords"
        }
#endif