{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gtk.Objects.TextView
    ( 

-- * Exported types
    TextView(..)                            ,
    TextViewK                               ,
    toTextView                              ,
    noTextView                              ,


 -- * Methods
-- ** textViewAddChildAtAnchor
    textViewAddChildAtAnchor                ,


-- ** textViewAddChildInWindow
    textViewAddChildInWindow                ,


-- ** textViewBackwardDisplayLine
    textViewBackwardDisplayLine             ,


-- ** textViewBackwardDisplayLineStart
    textViewBackwardDisplayLineStart        ,


-- ** textViewBufferToWindowCoords
    textViewBufferToWindowCoords            ,


-- ** textViewForwardDisplayLine
    textViewForwardDisplayLine              ,


-- ** textViewForwardDisplayLineEnd
    textViewForwardDisplayLineEnd           ,


-- ** textViewGetAcceptsTab
    textViewGetAcceptsTab                   ,


-- ** textViewGetBorderWindowSize
    textViewGetBorderWindowSize             ,


-- ** textViewGetBuffer
    textViewGetBuffer                       ,


-- ** textViewGetCursorLocations
    textViewGetCursorLocations              ,


-- ** textViewGetCursorVisible
    textViewGetCursorVisible                ,


-- ** textViewGetDefaultAttributes
    textViewGetDefaultAttributes            ,


-- ** textViewGetEditable
    textViewGetEditable                     ,


-- ** textViewGetHadjustment
    textViewGetHadjustment                  ,


-- ** textViewGetIndent
    textViewGetIndent                       ,


-- ** textViewGetInputHints
    textViewGetInputHints                   ,


-- ** textViewGetInputPurpose
    textViewGetInputPurpose                 ,


-- ** textViewGetIterAtLocation
    textViewGetIterAtLocation               ,


-- ** textViewGetIterAtPosition
    textViewGetIterAtPosition               ,


-- ** textViewGetIterLocation
    textViewGetIterLocation                 ,


-- ** textViewGetJustification
    textViewGetJustification                ,


-- ** textViewGetLeftMargin
    textViewGetLeftMargin                   ,


-- ** textViewGetLineAtY
    textViewGetLineAtY                      ,


-- ** textViewGetLineYrange
    textViewGetLineYrange                   ,


-- ** textViewGetMonospace
    textViewGetMonospace                    ,


-- ** textViewGetOverwrite
    textViewGetOverwrite                    ,


-- ** textViewGetPixelsAboveLines
    textViewGetPixelsAboveLines             ,


-- ** textViewGetPixelsBelowLines
    textViewGetPixelsBelowLines             ,


-- ** textViewGetPixelsInsideWrap
    textViewGetPixelsInsideWrap             ,


-- ** textViewGetRightMargin
    textViewGetRightMargin                  ,


-- ** textViewGetTabs
    textViewGetTabs                         ,


-- ** textViewGetVadjustment
    textViewGetVadjustment                  ,


-- ** textViewGetVisibleRect
    textViewGetVisibleRect                  ,


-- ** textViewGetWindow
    textViewGetWindow                       ,


-- ** textViewGetWindowType
    textViewGetWindowType                   ,


-- ** textViewGetWrapMode
    textViewGetWrapMode                     ,


-- ** textViewImContextFilterKeypress
    textViewImContextFilterKeypress         ,


-- ** textViewMoveChild
    textViewMoveChild                       ,


-- ** textViewMoveMarkOnscreen
    textViewMoveMarkOnscreen                ,


-- ** textViewMoveVisually
    textViewMoveVisually                    ,


-- ** textViewNew
    textViewNew                             ,


-- ** textViewNewWithBuffer
    textViewNewWithBuffer                   ,


-- ** textViewPlaceCursorOnscreen
    textViewPlaceCursorOnscreen             ,


-- ** textViewResetImContext
    textViewResetImContext                  ,


-- ** textViewScrollMarkOnscreen
    textViewScrollMarkOnscreen              ,


-- ** textViewScrollToIter
    textViewScrollToIter                    ,


-- ** textViewScrollToMark
    textViewScrollToMark                    ,


-- ** textViewSetAcceptsTab
    textViewSetAcceptsTab                   ,


-- ** textViewSetBorderWindowSize
    textViewSetBorderWindowSize             ,


-- ** textViewSetBuffer
    textViewSetBuffer                       ,


-- ** textViewSetCursorVisible
    textViewSetCursorVisible                ,


-- ** textViewSetEditable
    textViewSetEditable                     ,


-- ** textViewSetIndent
    textViewSetIndent                       ,


-- ** textViewSetInputHints
    textViewSetInputHints                   ,


-- ** textViewSetInputPurpose
    textViewSetInputPurpose                 ,


-- ** textViewSetJustification
    textViewSetJustification                ,


-- ** textViewSetLeftMargin
    textViewSetLeftMargin                   ,


-- ** textViewSetMonospace
    textViewSetMonospace                    ,


-- ** textViewSetOverwrite
    textViewSetOverwrite                    ,


-- ** textViewSetPixelsAboveLines
    textViewSetPixelsAboveLines             ,


-- ** textViewSetPixelsBelowLines
    textViewSetPixelsBelowLines             ,


-- ** textViewSetPixelsInsideWrap
    textViewSetPixelsInsideWrap             ,


-- ** textViewSetRightMargin
    textViewSetRightMargin                  ,


-- ** textViewSetTabs
    textViewSetTabs                         ,


-- ** textViewSetWrapMode
    textViewSetWrapMode                     ,


-- ** textViewStartsDisplayLine
    textViewStartsDisplayLine               ,


-- ** textViewWindowToBufferCoords
    textViewWindowToBufferCoords            ,




 -- * Properties
-- ** AcceptsTab
    TextViewAcceptsTabPropertyInfo          ,
    constructTextViewAcceptsTab             ,
    getTextViewAcceptsTab                   ,
    setTextViewAcceptsTab                   ,


-- ** Buffer
    TextViewBufferPropertyInfo              ,
    constructTextViewBuffer                 ,
    getTextViewBuffer                       ,
    setTextViewBuffer                       ,


-- ** CursorVisible
    TextViewCursorVisiblePropertyInfo       ,
    constructTextViewCursorVisible          ,
    getTextViewCursorVisible                ,
    setTextViewCursorVisible                ,


-- ** Editable
    TextViewEditablePropertyInfo            ,
    constructTextViewEditable               ,
    getTextViewEditable                     ,
    setTextViewEditable                     ,


-- ** ImModule
    TextViewImModulePropertyInfo            ,
    constructTextViewImModule               ,
    getTextViewImModule                     ,
    setTextViewImModule                     ,


-- ** Indent
    TextViewIndentPropertyInfo              ,
    constructTextViewIndent                 ,
    getTextViewIndent                       ,
    setTextViewIndent                       ,


-- ** InputHints
    TextViewInputHintsPropertyInfo          ,
    constructTextViewInputHints             ,
    getTextViewInputHints                   ,
    setTextViewInputHints                   ,


-- ** InputPurpose
    TextViewInputPurposePropertyInfo        ,
    constructTextViewInputPurpose           ,
    getTextViewInputPurpose                 ,
    setTextViewInputPurpose                 ,


-- ** Justification
    TextViewJustificationPropertyInfo       ,
    constructTextViewJustification          ,
    getTextViewJustification                ,
    setTextViewJustification                ,


-- ** LeftMargin
    TextViewLeftMarginPropertyInfo          ,
    constructTextViewLeftMargin             ,
    getTextViewLeftMargin                   ,
    setTextViewLeftMargin                   ,


-- ** Monospace
    TextViewMonospacePropertyInfo           ,
    constructTextViewMonospace              ,
    getTextViewMonospace                    ,
    setTextViewMonospace                    ,


-- ** Overwrite
    TextViewOverwritePropertyInfo           ,
    constructTextViewOverwrite              ,
    getTextViewOverwrite                    ,
    setTextViewOverwrite                    ,


-- ** PixelsAboveLines
    TextViewPixelsAboveLinesPropertyInfo    ,
    constructTextViewPixelsAboveLines       ,
    getTextViewPixelsAboveLines             ,
    setTextViewPixelsAboveLines             ,


-- ** PixelsBelowLines
    TextViewPixelsBelowLinesPropertyInfo    ,
    constructTextViewPixelsBelowLines       ,
    getTextViewPixelsBelowLines             ,
    setTextViewPixelsBelowLines             ,


-- ** PixelsInsideWrap
    TextViewPixelsInsideWrapPropertyInfo    ,
    constructTextViewPixelsInsideWrap       ,
    getTextViewPixelsInsideWrap             ,
    setTextViewPixelsInsideWrap             ,


-- ** PopulateAll
    TextViewPopulateAllPropertyInfo         ,
    constructTextViewPopulateAll            ,
    getTextViewPopulateAll                  ,
    setTextViewPopulateAll                  ,


-- ** RightMargin
    TextViewRightMarginPropertyInfo         ,
    constructTextViewRightMargin            ,
    getTextViewRightMargin                  ,
    setTextViewRightMargin                  ,


-- ** Tabs
    TextViewTabsPropertyInfo                ,
    constructTextViewTabs                   ,
    getTextViewTabs                         ,
    setTextViewTabs                         ,


-- ** WrapMode
    TextViewWrapModePropertyInfo            ,
    constructTextViewWrapMode               ,
    getTextViewWrapMode                     ,
    setTextViewWrapMode                     ,




 -- * Signals
-- ** Backspace
    TextViewBackspaceCallback               ,
    TextViewBackspaceCallbackC              ,
    TextViewBackspaceSignalInfo             ,
    afterTextViewBackspace                  ,
    mkTextViewBackspaceCallback             ,
    noTextViewBackspaceCallback             ,
    onTextViewBackspace                     ,
    textViewBackspaceCallbackWrapper        ,
    textViewBackspaceClosure                ,


-- ** CopyClipboard
    TextViewCopyClipboardCallback           ,
    TextViewCopyClipboardCallbackC          ,
    TextViewCopyClipboardSignalInfo         ,
    afterTextViewCopyClipboard              ,
    mkTextViewCopyClipboardCallback         ,
    noTextViewCopyClipboardCallback         ,
    onTextViewCopyClipboard                 ,
    textViewCopyClipboardCallbackWrapper    ,
    textViewCopyClipboardClosure            ,


-- ** CutClipboard
    TextViewCutClipboardCallback            ,
    TextViewCutClipboardCallbackC           ,
    TextViewCutClipboardSignalInfo          ,
    afterTextViewCutClipboard               ,
    mkTextViewCutClipboardCallback          ,
    noTextViewCutClipboardCallback          ,
    onTextViewCutClipboard                  ,
    textViewCutClipboardCallbackWrapper     ,
    textViewCutClipboardClosure             ,


-- ** DeleteFromCursor
    TextViewDeleteFromCursorCallback        ,
    TextViewDeleteFromCursorCallbackC       ,
    TextViewDeleteFromCursorSignalInfo      ,
    afterTextViewDeleteFromCursor           ,
    mkTextViewDeleteFromCursorCallback      ,
    noTextViewDeleteFromCursorCallback      ,
    onTextViewDeleteFromCursor              ,
    textViewDeleteFromCursorCallbackWrapper ,
    textViewDeleteFromCursorClosure         ,


-- ** ExtendSelection
    TextViewExtendSelectionCallback         ,
    TextViewExtendSelectionCallbackC        ,
    TextViewExtendSelectionSignalInfo       ,
    afterTextViewExtendSelection            ,
    mkTextViewExtendSelectionCallback       ,
    noTextViewExtendSelectionCallback       ,
    onTextViewExtendSelection               ,
    textViewExtendSelectionCallbackWrapper  ,
    textViewExtendSelectionClosure          ,


-- ** InsertAtCursor
    TextViewInsertAtCursorCallback          ,
    TextViewInsertAtCursorCallbackC         ,
    TextViewInsertAtCursorSignalInfo        ,
    afterTextViewInsertAtCursor             ,
    mkTextViewInsertAtCursorCallback        ,
    noTextViewInsertAtCursorCallback        ,
    onTextViewInsertAtCursor                ,
    textViewInsertAtCursorCallbackWrapper   ,
    textViewInsertAtCursorClosure           ,


-- ** MoveCursor
    TextViewMoveCursorCallback              ,
    TextViewMoveCursorCallbackC             ,
    TextViewMoveCursorSignalInfo            ,
    afterTextViewMoveCursor                 ,
    mkTextViewMoveCursorCallback            ,
    noTextViewMoveCursorCallback            ,
    onTextViewMoveCursor                    ,
    textViewMoveCursorCallbackWrapper       ,
    textViewMoveCursorClosure               ,


-- ** MoveViewport
    TextViewMoveViewportCallback            ,
    TextViewMoveViewportCallbackC           ,
    TextViewMoveViewportSignalInfo          ,
    afterTextViewMoveViewport               ,
    mkTextViewMoveViewportCallback          ,
    noTextViewMoveViewportCallback          ,
    onTextViewMoveViewport                  ,
    textViewMoveViewportCallbackWrapper     ,
    textViewMoveViewportClosure             ,


-- ** PasteClipboard
    TextViewPasteClipboardCallback          ,
    TextViewPasteClipboardCallbackC         ,
    TextViewPasteClipboardSignalInfo        ,
    afterTextViewPasteClipboard             ,
    mkTextViewPasteClipboardCallback        ,
    noTextViewPasteClipboardCallback        ,
    onTextViewPasteClipboard                ,
    textViewPasteClipboardCallbackWrapper   ,
    textViewPasteClipboardClosure           ,


-- ** PopulatePopup
    TextViewPopulatePopupCallback           ,
    TextViewPopulatePopupCallbackC          ,
    TextViewPopulatePopupSignalInfo         ,
    afterTextViewPopulatePopup              ,
    mkTextViewPopulatePopupCallback         ,
    noTextViewPopulatePopupCallback         ,
    onTextViewPopulatePopup                 ,
    textViewPopulatePopupCallbackWrapper    ,
    textViewPopulatePopupClosure            ,


-- ** PreeditChanged
    TextViewPreeditChangedCallback          ,
    TextViewPreeditChangedCallbackC         ,
    TextViewPreeditChangedSignalInfo        ,
    afterTextViewPreeditChanged             ,
    mkTextViewPreeditChangedCallback        ,
    noTextViewPreeditChangedCallback        ,
    onTextViewPreeditChanged                ,
    textViewPreeditChangedCallbackWrapper   ,
    textViewPreeditChangedClosure           ,


-- ** SelectAll
    TextViewSelectAllCallback               ,
    TextViewSelectAllCallbackC              ,
    TextViewSelectAllSignalInfo             ,
    afterTextViewSelectAll                  ,
    mkTextViewSelectAllCallback             ,
    noTextViewSelectAllCallback             ,
    onTextViewSelectAll                     ,
    textViewSelectAllCallbackWrapper        ,
    textViewSelectAllClosure                ,


-- ** SetAnchor
    TextViewSetAnchorCallback               ,
    TextViewSetAnchorCallbackC              ,
    TextViewSetAnchorSignalInfo             ,
    afterTextViewSetAnchor                  ,
    mkTextViewSetAnchorCallback             ,
    noTextViewSetAnchorCallback             ,
    onTextViewSetAnchor                     ,
    textViewSetAnchorCallbackWrapper        ,
    textViewSetAnchorClosure                ,


-- ** ToggleCursorVisible
    TextViewToggleCursorVisibleCallback     ,
    TextViewToggleCursorVisibleCallbackC    ,
    TextViewToggleCursorVisibleSignalInfo   ,
    afterTextViewToggleCursorVisible        ,
    mkTextViewToggleCursorVisibleCallback   ,
    noTextViewToggleCursorVisibleCallback   ,
    onTextViewToggleCursorVisible           ,
    textViewToggleCursorVisibleCallbackWrapper,
    textViewToggleCursorVisibleClosure      ,


-- ** ToggleOverwrite
    TextViewToggleOverwriteCallback         ,
    TextViewToggleOverwriteCallbackC        ,
    TextViewToggleOverwriteSignalInfo       ,
    afterTextViewToggleOverwrite            ,
    mkTextViewToggleOverwriteCallback       ,
    noTextViewToggleOverwriteCallback       ,
    onTextViewToggleOverwrite               ,
    textViewToggleOverwriteCallbackWrapper  ,
    textViewToggleOverwriteClosure          ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.Atk as Atk
import qualified GI.GObject as GObject
import qualified GI.Gdk as Gdk
import qualified GI.Pango as Pango
import qualified GI.Cairo as Cairo

newtype TextView = TextView (ForeignPtr TextView)
foreign import ccall "gtk_text_view_get_type"
    c_gtk_text_view_get_type :: IO GType

type instance ParentTypes TextView = TextViewParentTypes
type TextViewParentTypes = '[Container, Widget, GObject.Object, Atk.ImplementorIface, Buildable, Scrollable]

instance GObject TextView where
    gobjectIsInitiallyUnowned _ = True
    gobjectType _ = c_gtk_text_view_get_type
    

class GObject o => TextViewK o
instance (GObject o, IsDescendantOf TextView o) => TextViewK o

toTextView :: TextViewK o => o -> IO TextView
toTextView = unsafeCastTo TextView

noTextView :: Maybe TextView
noTextView = Nothing

-- signal TextView::backspace
type TextViewBackspaceCallback =
    IO ()

noTextViewBackspaceCallback :: Maybe TextViewBackspaceCallback
noTextViewBackspaceCallback = Nothing

type TextViewBackspaceCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewBackspaceCallback :: TextViewBackspaceCallbackC -> IO (FunPtr TextViewBackspaceCallbackC)

textViewBackspaceClosure :: TextViewBackspaceCallback -> IO Closure
textViewBackspaceClosure cb = newCClosure =<< mkTextViewBackspaceCallback wrapped
    where wrapped = textViewBackspaceCallbackWrapper cb

textViewBackspaceCallbackWrapper ::
    TextViewBackspaceCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
textViewBackspaceCallbackWrapper _cb _ _ = do
    _cb 

onTextViewBackspace :: (GObject a, MonadIO m) => a -> TextViewBackspaceCallback -> m SignalHandlerId
onTextViewBackspace obj cb = liftIO $ connectTextViewBackspace obj cb SignalConnectBefore
afterTextViewBackspace :: (GObject a, MonadIO m) => a -> TextViewBackspaceCallback -> m SignalHandlerId
afterTextViewBackspace obj cb = connectTextViewBackspace obj cb SignalConnectAfter

connectTextViewBackspace :: (GObject a, MonadIO m) =>
                            a -> TextViewBackspaceCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewBackspace obj cb after = liftIO $ do
    cb' <- mkTextViewBackspaceCallback (textViewBackspaceCallbackWrapper cb)
    connectSignalFunPtr obj "backspace" cb' after

-- signal TextView::copy-clipboard
type TextViewCopyClipboardCallback =
    IO ()

noTextViewCopyClipboardCallback :: Maybe TextViewCopyClipboardCallback
noTextViewCopyClipboardCallback = Nothing

type TextViewCopyClipboardCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewCopyClipboardCallback :: TextViewCopyClipboardCallbackC -> IO (FunPtr TextViewCopyClipboardCallbackC)

textViewCopyClipboardClosure :: TextViewCopyClipboardCallback -> IO Closure
textViewCopyClipboardClosure cb = newCClosure =<< mkTextViewCopyClipboardCallback wrapped
    where wrapped = textViewCopyClipboardCallbackWrapper cb

textViewCopyClipboardCallbackWrapper ::
    TextViewCopyClipboardCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
textViewCopyClipboardCallbackWrapper _cb _ _ = do
    _cb 

onTextViewCopyClipboard :: (GObject a, MonadIO m) => a -> TextViewCopyClipboardCallback -> m SignalHandlerId
onTextViewCopyClipboard obj cb = liftIO $ connectTextViewCopyClipboard obj cb SignalConnectBefore
afterTextViewCopyClipboard :: (GObject a, MonadIO m) => a -> TextViewCopyClipboardCallback -> m SignalHandlerId
afterTextViewCopyClipboard obj cb = connectTextViewCopyClipboard obj cb SignalConnectAfter

connectTextViewCopyClipboard :: (GObject a, MonadIO m) =>
                                a -> TextViewCopyClipboardCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewCopyClipboard obj cb after = liftIO $ do
    cb' <- mkTextViewCopyClipboardCallback (textViewCopyClipboardCallbackWrapper cb)
    connectSignalFunPtr obj "copy-clipboard" cb' after

-- signal TextView::cut-clipboard
type TextViewCutClipboardCallback =
    IO ()

noTextViewCutClipboardCallback :: Maybe TextViewCutClipboardCallback
noTextViewCutClipboardCallback = Nothing

type TextViewCutClipboardCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewCutClipboardCallback :: TextViewCutClipboardCallbackC -> IO (FunPtr TextViewCutClipboardCallbackC)

textViewCutClipboardClosure :: TextViewCutClipboardCallback -> IO Closure
textViewCutClipboardClosure cb = newCClosure =<< mkTextViewCutClipboardCallback wrapped
    where wrapped = textViewCutClipboardCallbackWrapper cb

textViewCutClipboardCallbackWrapper ::
    TextViewCutClipboardCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
textViewCutClipboardCallbackWrapper _cb _ _ = do
    _cb 

onTextViewCutClipboard :: (GObject a, MonadIO m) => a -> TextViewCutClipboardCallback -> m SignalHandlerId
onTextViewCutClipboard obj cb = liftIO $ connectTextViewCutClipboard obj cb SignalConnectBefore
afterTextViewCutClipboard :: (GObject a, MonadIO m) => a -> TextViewCutClipboardCallback -> m SignalHandlerId
afterTextViewCutClipboard obj cb = connectTextViewCutClipboard obj cb SignalConnectAfter

connectTextViewCutClipboard :: (GObject a, MonadIO m) =>
                               a -> TextViewCutClipboardCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewCutClipboard obj cb after = liftIO $ do
    cb' <- mkTextViewCutClipboardCallback (textViewCutClipboardCallbackWrapper cb)
    connectSignalFunPtr obj "cut-clipboard" cb' after

-- signal TextView::delete-from-cursor
type TextViewDeleteFromCursorCallback =
    DeleteType ->
    Int32 ->
    IO ()

noTextViewDeleteFromCursorCallback :: Maybe TextViewDeleteFromCursorCallback
noTextViewDeleteFromCursorCallback = Nothing

type TextViewDeleteFromCursorCallbackC =
    Ptr () ->                               -- object
    CUInt ->
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewDeleteFromCursorCallback :: TextViewDeleteFromCursorCallbackC -> IO (FunPtr TextViewDeleteFromCursorCallbackC)

textViewDeleteFromCursorClosure :: TextViewDeleteFromCursorCallback -> IO Closure
textViewDeleteFromCursorClosure cb = newCClosure =<< mkTextViewDeleteFromCursorCallback wrapped
    where wrapped = textViewDeleteFromCursorCallbackWrapper cb

textViewDeleteFromCursorCallbackWrapper ::
    TextViewDeleteFromCursorCallback ->
    Ptr () ->
    CUInt ->
    Int32 ->
    Ptr () ->
    IO ()
textViewDeleteFromCursorCallbackWrapper _cb _ type_ count _ = do
    let type_' = (toEnum . fromIntegral) type_
    _cb  type_' count

onTextViewDeleteFromCursor :: (GObject a, MonadIO m) => a -> TextViewDeleteFromCursorCallback -> m SignalHandlerId
onTextViewDeleteFromCursor obj cb = liftIO $ connectTextViewDeleteFromCursor obj cb SignalConnectBefore
afterTextViewDeleteFromCursor :: (GObject a, MonadIO m) => a -> TextViewDeleteFromCursorCallback -> m SignalHandlerId
afterTextViewDeleteFromCursor obj cb = connectTextViewDeleteFromCursor obj cb SignalConnectAfter

connectTextViewDeleteFromCursor :: (GObject a, MonadIO m) =>
                                   a -> TextViewDeleteFromCursorCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewDeleteFromCursor obj cb after = liftIO $ do
    cb' <- mkTextViewDeleteFromCursorCallback (textViewDeleteFromCursorCallbackWrapper cb)
    connectSignalFunPtr obj "delete-from-cursor" cb' after

-- signal TextView::extend-selection
type TextViewExtendSelectionCallback =
    TextExtendSelection ->
    TextIter ->
    TextIter ->
    TextIter ->
    IO Bool

noTextViewExtendSelectionCallback :: Maybe TextViewExtendSelectionCallback
noTextViewExtendSelectionCallback = Nothing

type TextViewExtendSelectionCallbackC =
    Ptr () ->                               -- object
    CUInt ->
    Ptr TextIter ->
    Ptr TextIter ->
    Ptr TextIter ->
    Ptr () ->                               -- user_data
    IO CInt

foreign import ccall "wrapper"
    mkTextViewExtendSelectionCallback :: TextViewExtendSelectionCallbackC -> IO (FunPtr TextViewExtendSelectionCallbackC)

textViewExtendSelectionClosure :: TextViewExtendSelectionCallback -> IO Closure
textViewExtendSelectionClosure cb = newCClosure =<< mkTextViewExtendSelectionCallback wrapped
    where wrapped = textViewExtendSelectionCallbackWrapper cb

textViewExtendSelectionCallbackWrapper ::
    TextViewExtendSelectionCallback ->
    Ptr () ->
    CUInt ->
    Ptr TextIter ->
    Ptr TextIter ->
    Ptr TextIter ->
    Ptr () ->
    IO CInt
textViewExtendSelectionCallbackWrapper _cb _ granularity location start end _ = do
    let granularity' = (toEnum . fromIntegral) granularity
    location' <- (newBoxed TextIter) location
    start' <- (newBoxed TextIter) start
    end' <- (newBoxed TextIter) end
    result <- _cb  granularity' location' start' end'
    let result' = (fromIntegral . fromEnum) result
    return result'

onTextViewExtendSelection :: (GObject a, MonadIO m) => a -> TextViewExtendSelectionCallback -> m SignalHandlerId
onTextViewExtendSelection obj cb = liftIO $ connectTextViewExtendSelection obj cb SignalConnectBefore
afterTextViewExtendSelection :: (GObject a, MonadIO m) => a -> TextViewExtendSelectionCallback -> m SignalHandlerId
afterTextViewExtendSelection obj cb = connectTextViewExtendSelection obj cb SignalConnectAfter

connectTextViewExtendSelection :: (GObject a, MonadIO m) =>
                                  a -> TextViewExtendSelectionCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewExtendSelection obj cb after = liftIO $ do
    cb' <- mkTextViewExtendSelectionCallback (textViewExtendSelectionCallbackWrapper cb)
    connectSignalFunPtr obj "extend-selection" cb' after

-- signal TextView::insert-at-cursor
type TextViewInsertAtCursorCallback =
    T.Text ->
    IO ()

noTextViewInsertAtCursorCallback :: Maybe TextViewInsertAtCursorCallback
noTextViewInsertAtCursorCallback = Nothing

type TextViewInsertAtCursorCallbackC =
    Ptr () ->                               -- object
    CString ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewInsertAtCursorCallback :: TextViewInsertAtCursorCallbackC -> IO (FunPtr TextViewInsertAtCursorCallbackC)

textViewInsertAtCursorClosure :: TextViewInsertAtCursorCallback -> IO Closure
textViewInsertAtCursorClosure cb = newCClosure =<< mkTextViewInsertAtCursorCallback wrapped
    where wrapped = textViewInsertAtCursorCallbackWrapper cb

textViewInsertAtCursorCallbackWrapper ::
    TextViewInsertAtCursorCallback ->
    Ptr () ->
    CString ->
    Ptr () ->
    IO ()
textViewInsertAtCursorCallbackWrapper _cb _ string _ = do
    string' <- cstringToText string
    _cb  string'

onTextViewInsertAtCursor :: (GObject a, MonadIO m) => a -> TextViewInsertAtCursorCallback -> m SignalHandlerId
onTextViewInsertAtCursor obj cb = liftIO $ connectTextViewInsertAtCursor obj cb SignalConnectBefore
afterTextViewInsertAtCursor :: (GObject a, MonadIO m) => a -> TextViewInsertAtCursorCallback -> m SignalHandlerId
afterTextViewInsertAtCursor obj cb = connectTextViewInsertAtCursor obj cb SignalConnectAfter

connectTextViewInsertAtCursor :: (GObject a, MonadIO m) =>
                                 a -> TextViewInsertAtCursorCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewInsertAtCursor obj cb after = liftIO $ do
    cb' <- mkTextViewInsertAtCursorCallback (textViewInsertAtCursorCallbackWrapper cb)
    connectSignalFunPtr obj "insert-at-cursor" cb' after

-- signal TextView::move-cursor
type TextViewMoveCursorCallback =
    MovementStep ->
    Int32 ->
    Bool ->
    IO ()

noTextViewMoveCursorCallback :: Maybe TextViewMoveCursorCallback
noTextViewMoveCursorCallback = Nothing

type TextViewMoveCursorCallbackC =
    Ptr () ->                               -- object
    CUInt ->
    Int32 ->
    CInt ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewMoveCursorCallback :: TextViewMoveCursorCallbackC -> IO (FunPtr TextViewMoveCursorCallbackC)

textViewMoveCursorClosure :: TextViewMoveCursorCallback -> IO Closure
textViewMoveCursorClosure cb = newCClosure =<< mkTextViewMoveCursorCallback wrapped
    where wrapped = textViewMoveCursorCallbackWrapper cb

textViewMoveCursorCallbackWrapper ::
    TextViewMoveCursorCallback ->
    Ptr () ->
    CUInt ->
    Int32 ->
    CInt ->
    Ptr () ->
    IO ()
textViewMoveCursorCallbackWrapper _cb _ step count extend_selection _ = do
    let step' = (toEnum . fromIntegral) step
    let extend_selection' = (/= 0) extend_selection
    _cb  step' count extend_selection'

onTextViewMoveCursor :: (GObject a, MonadIO m) => a -> TextViewMoveCursorCallback -> m SignalHandlerId
onTextViewMoveCursor obj cb = liftIO $ connectTextViewMoveCursor obj cb SignalConnectBefore
afterTextViewMoveCursor :: (GObject a, MonadIO m) => a -> TextViewMoveCursorCallback -> m SignalHandlerId
afterTextViewMoveCursor obj cb = connectTextViewMoveCursor obj cb SignalConnectAfter

connectTextViewMoveCursor :: (GObject a, MonadIO m) =>
                             a -> TextViewMoveCursorCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewMoveCursor obj cb after = liftIO $ do
    cb' <- mkTextViewMoveCursorCallback (textViewMoveCursorCallbackWrapper cb)
    connectSignalFunPtr obj "move-cursor" cb' after

-- signal TextView::move-viewport
type TextViewMoveViewportCallback =
    ScrollStep ->
    Int32 ->
    IO ()

noTextViewMoveViewportCallback :: Maybe TextViewMoveViewportCallback
noTextViewMoveViewportCallback = Nothing

type TextViewMoveViewportCallbackC =
    Ptr () ->                               -- object
    CUInt ->
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewMoveViewportCallback :: TextViewMoveViewportCallbackC -> IO (FunPtr TextViewMoveViewportCallbackC)

textViewMoveViewportClosure :: TextViewMoveViewportCallback -> IO Closure
textViewMoveViewportClosure cb = newCClosure =<< mkTextViewMoveViewportCallback wrapped
    where wrapped = textViewMoveViewportCallbackWrapper cb

textViewMoveViewportCallbackWrapper ::
    TextViewMoveViewportCallback ->
    Ptr () ->
    CUInt ->
    Int32 ->
    Ptr () ->
    IO ()
textViewMoveViewportCallbackWrapper _cb _ step count _ = do
    let step' = (toEnum . fromIntegral) step
    _cb  step' count

onTextViewMoveViewport :: (GObject a, MonadIO m) => a -> TextViewMoveViewportCallback -> m SignalHandlerId
onTextViewMoveViewport obj cb = liftIO $ connectTextViewMoveViewport obj cb SignalConnectBefore
afterTextViewMoveViewport :: (GObject a, MonadIO m) => a -> TextViewMoveViewportCallback -> m SignalHandlerId
afterTextViewMoveViewport obj cb = connectTextViewMoveViewport obj cb SignalConnectAfter

connectTextViewMoveViewport :: (GObject a, MonadIO m) =>
                               a -> TextViewMoveViewportCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewMoveViewport obj cb after = liftIO $ do
    cb' <- mkTextViewMoveViewportCallback (textViewMoveViewportCallbackWrapper cb)
    connectSignalFunPtr obj "move-viewport" cb' after

-- signal TextView::paste-clipboard
type TextViewPasteClipboardCallback =
    IO ()

noTextViewPasteClipboardCallback :: Maybe TextViewPasteClipboardCallback
noTextViewPasteClipboardCallback = Nothing

type TextViewPasteClipboardCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewPasteClipboardCallback :: TextViewPasteClipboardCallbackC -> IO (FunPtr TextViewPasteClipboardCallbackC)

textViewPasteClipboardClosure :: TextViewPasteClipboardCallback -> IO Closure
textViewPasteClipboardClosure cb = newCClosure =<< mkTextViewPasteClipboardCallback wrapped
    where wrapped = textViewPasteClipboardCallbackWrapper cb

textViewPasteClipboardCallbackWrapper ::
    TextViewPasteClipboardCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
textViewPasteClipboardCallbackWrapper _cb _ _ = do
    _cb 

onTextViewPasteClipboard :: (GObject a, MonadIO m) => a -> TextViewPasteClipboardCallback -> m SignalHandlerId
onTextViewPasteClipboard obj cb = liftIO $ connectTextViewPasteClipboard obj cb SignalConnectBefore
afterTextViewPasteClipboard :: (GObject a, MonadIO m) => a -> TextViewPasteClipboardCallback -> m SignalHandlerId
afterTextViewPasteClipboard obj cb = connectTextViewPasteClipboard obj cb SignalConnectAfter

connectTextViewPasteClipboard :: (GObject a, MonadIO m) =>
                                 a -> TextViewPasteClipboardCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewPasteClipboard obj cb after = liftIO $ do
    cb' <- mkTextViewPasteClipboardCallback (textViewPasteClipboardCallbackWrapper cb)
    connectSignalFunPtr obj "paste-clipboard" cb' after

-- signal TextView::populate-popup
type TextViewPopulatePopupCallback =
    Widget ->
    IO ()

noTextViewPopulatePopupCallback :: Maybe TextViewPopulatePopupCallback
noTextViewPopulatePopupCallback = Nothing

type TextViewPopulatePopupCallbackC =
    Ptr () ->                               -- object
    Ptr Widget ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewPopulatePopupCallback :: TextViewPopulatePopupCallbackC -> IO (FunPtr TextViewPopulatePopupCallbackC)

textViewPopulatePopupClosure :: TextViewPopulatePopupCallback -> IO Closure
textViewPopulatePopupClosure cb = newCClosure =<< mkTextViewPopulatePopupCallback wrapped
    where wrapped = textViewPopulatePopupCallbackWrapper cb

textViewPopulatePopupCallbackWrapper ::
    TextViewPopulatePopupCallback ->
    Ptr () ->
    Ptr Widget ->
    Ptr () ->
    IO ()
textViewPopulatePopupCallbackWrapper _cb _ popup _ = do
    popup' <- (newObject Widget) popup
    _cb  popup'

onTextViewPopulatePopup :: (GObject a, MonadIO m) => a -> TextViewPopulatePopupCallback -> m SignalHandlerId
onTextViewPopulatePopup obj cb = liftIO $ connectTextViewPopulatePopup obj cb SignalConnectBefore
afterTextViewPopulatePopup :: (GObject a, MonadIO m) => a -> TextViewPopulatePopupCallback -> m SignalHandlerId
afterTextViewPopulatePopup obj cb = connectTextViewPopulatePopup obj cb SignalConnectAfter

connectTextViewPopulatePopup :: (GObject a, MonadIO m) =>
                                a -> TextViewPopulatePopupCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewPopulatePopup obj cb after = liftIO $ do
    cb' <- mkTextViewPopulatePopupCallback (textViewPopulatePopupCallbackWrapper cb)
    connectSignalFunPtr obj "populate-popup" cb' after

-- signal TextView::preedit-changed
type TextViewPreeditChangedCallback =
    T.Text ->
    IO ()

noTextViewPreeditChangedCallback :: Maybe TextViewPreeditChangedCallback
noTextViewPreeditChangedCallback = Nothing

type TextViewPreeditChangedCallbackC =
    Ptr () ->                               -- object
    CString ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewPreeditChangedCallback :: TextViewPreeditChangedCallbackC -> IO (FunPtr TextViewPreeditChangedCallbackC)

textViewPreeditChangedClosure :: TextViewPreeditChangedCallback -> IO Closure
textViewPreeditChangedClosure cb = newCClosure =<< mkTextViewPreeditChangedCallback wrapped
    where wrapped = textViewPreeditChangedCallbackWrapper cb

textViewPreeditChangedCallbackWrapper ::
    TextViewPreeditChangedCallback ->
    Ptr () ->
    CString ->
    Ptr () ->
    IO ()
textViewPreeditChangedCallbackWrapper _cb _ preedit _ = do
    preedit' <- cstringToText preedit
    _cb  preedit'

onTextViewPreeditChanged :: (GObject a, MonadIO m) => a -> TextViewPreeditChangedCallback -> m SignalHandlerId
onTextViewPreeditChanged obj cb = liftIO $ connectTextViewPreeditChanged obj cb SignalConnectBefore
afterTextViewPreeditChanged :: (GObject a, MonadIO m) => a -> TextViewPreeditChangedCallback -> m SignalHandlerId
afterTextViewPreeditChanged obj cb = connectTextViewPreeditChanged obj cb SignalConnectAfter

connectTextViewPreeditChanged :: (GObject a, MonadIO m) =>
                                 a -> TextViewPreeditChangedCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewPreeditChanged obj cb after = liftIO $ do
    cb' <- mkTextViewPreeditChangedCallback (textViewPreeditChangedCallbackWrapper cb)
    connectSignalFunPtr obj "preedit-changed" cb' after

-- signal TextView::select-all
type TextViewSelectAllCallback =
    Bool ->
    IO ()

noTextViewSelectAllCallback :: Maybe TextViewSelectAllCallback
noTextViewSelectAllCallback = Nothing

type TextViewSelectAllCallbackC =
    Ptr () ->                               -- object
    CInt ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewSelectAllCallback :: TextViewSelectAllCallbackC -> IO (FunPtr TextViewSelectAllCallbackC)

textViewSelectAllClosure :: TextViewSelectAllCallback -> IO Closure
textViewSelectAllClosure cb = newCClosure =<< mkTextViewSelectAllCallback wrapped
    where wrapped = textViewSelectAllCallbackWrapper cb

textViewSelectAllCallbackWrapper ::
    TextViewSelectAllCallback ->
    Ptr () ->
    CInt ->
    Ptr () ->
    IO ()
textViewSelectAllCallbackWrapper _cb _ select _ = do
    let select' = (/= 0) select
    _cb  select'

onTextViewSelectAll :: (GObject a, MonadIO m) => a -> TextViewSelectAllCallback -> m SignalHandlerId
onTextViewSelectAll obj cb = liftIO $ connectTextViewSelectAll obj cb SignalConnectBefore
afterTextViewSelectAll :: (GObject a, MonadIO m) => a -> TextViewSelectAllCallback -> m SignalHandlerId
afterTextViewSelectAll obj cb = connectTextViewSelectAll obj cb SignalConnectAfter

connectTextViewSelectAll :: (GObject a, MonadIO m) =>
                            a -> TextViewSelectAllCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewSelectAll obj cb after = liftIO $ do
    cb' <- mkTextViewSelectAllCallback (textViewSelectAllCallbackWrapper cb)
    connectSignalFunPtr obj "select-all" cb' after

-- signal TextView::set-anchor
type TextViewSetAnchorCallback =
    IO ()

noTextViewSetAnchorCallback :: Maybe TextViewSetAnchorCallback
noTextViewSetAnchorCallback = Nothing

type TextViewSetAnchorCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewSetAnchorCallback :: TextViewSetAnchorCallbackC -> IO (FunPtr TextViewSetAnchorCallbackC)

textViewSetAnchorClosure :: TextViewSetAnchorCallback -> IO Closure
textViewSetAnchorClosure cb = newCClosure =<< mkTextViewSetAnchorCallback wrapped
    where wrapped = textViewSetAnchorCallbackWrapper cb

textViewSetAnchorCallbackWrapper ::
    TextViewSetAnchorCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
textViewSetAnchorCallbackWrapper _cb _ _ = do
    _cb 

onTextViewSetAnchor :: (GObject a, MonadIO m) => a -> TextViewSetAnchorCallback -> m SignalHandlerId
onTextViewSetAnchor obj cb = liftIO $ connectTextViewSetAnchor obj cb SignalConnectBefore
afterTextViewSetAnchor :: (GObject a, MonadIO m) => a -> TextViewSetAnchorCallback -> m SignalHandlerId
afterTextViewSetAnchor obj cb = connectTextViewSetAnchor obj cb SignalConnectAfter

connectTextViewSetAnchor :: (GObject a, MonadIO m) =>
                            a -> TextViewSetAnchorCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewSetAnchor obj cb after = liftIO $ do
    cb' <- mkTextViewSetAnchorCallback (textViewSetAnchorCallbackWrapper cb)
    connectSignalFunPtr obj "set-anchor" cb' after

-- signal TextView::toggle-cursor-visible
type TextViewToggleCursorVisibleCallback =
    IO ()

noTextViewToggleCursorVisibleCallback :: Maybe TextViewToggleCursorVisibleCallback
noTextViewToggleCursorVisibleCallback = Nothing

type TextViewToggleCursorVisibleCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewToggleCursorVisibleCallback :: TextViewToggleCursorVisibleCallbackC -> IO (FunPtr TextViewToggleCursorVisibleCallbackC)

textViewToggleCursorVisibleClosure :: TextViewToggleCursorVisibleCallback -> IO Closure
textViewToggleCursorVisibleClosure cb = newCClosure =<< mkTextViewToggleCursorVisibleCallback wrapped
    where wrapped = textViewToggleCursorVisibleCallbackWrapper cb

textViewToggleCursorVisibleCallbackWrapper ::
    TextViewToggleCursorVisibleCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
textViewToggleCursorVisibleCallbackWrapper _cb _ _ = do
    _cb 

onTextViewToggleCursorVisible :: (GObject a, MonadIO m) => a -> TextViewToggleCursorVisibleCallback -> m SignalHandlerId
onTextViewToggleCursorVisible obj cb = liftIO $ connectTextViewToggleCursorVisible obj cb SignalConnectBefore
afterTextViewToggleCursorVisible :: (GObject a, MonadIO m) => a -> TextViewToggleCursorVisibleCallback -> m SignalHandlerId
afterTextViewToggleCursorVisible obj cb = connectTextViewToggleCursorVisible obj cb SignalConnectAfter

connectTextViewToggleCursorVisible :: (GObject a, MonadIO m) =>
                                      a -> TextViewToggleCursorVisibleCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewToggleCursorVisible obj cb after = liftIO $ do
    cb' <- mkTextViewToggleCursorVisibleCallback (textViewToggleCursorVisibleCallbackWrapper cb)
    connectSignalFunPtr obj "toggle-cursor-visible" cb' after

-- signal TextView::toggle-overwrite
type TextViewToggleOverwriteCallback =
    IO ()

noTextViewToggleOverwriteCallback :: Maybe TextViewToggleOverwriteCallback
noTextViewToggleOverwriteCallback = Nothing

type TextViewToggleOverwriteCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkTextViewToggleOverwriteCallback :: TextViewToggleOverwriteCallbackC -> IO (FunPtr TextViewToggleOverwriteCallbackC)

textViewToggleOverwriteClosure :: TextViewToggleOverwriteCallback -> IO Closure
textViewToggleOverwriteClosure cb = newCClosure =<< mkTextViewToggleOverwriteCallback wrapped
    where wrapped = textViewToggleOverwriteCallbackWrapper cb

textViewToggleOverwriteCallbackWrapper ::
    TextViewToggleOverwriteCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
textViewToggleOverwriteCallbackWrapper _cb _ _ = do
    _cb 

onTextViewToggleOverwrite :: (GObject a, MonadIO m) => a -> TextViewToggleOverwriteCallback -> m SignalHandlerId
onTextViewToggleOverwrite obj cb = liftIO $ connectTextViewToggleOverwrite obj cb SignalConnectBefore
afterTextViewToggleOverwrite :: (GObject a, MonadIO m) => a -> TextViewToggleOverwriteCallback -> m SignalHandlerId
afterTextViewToggleOverwrite obj cb = connectTextViewToggleOverwrite obj cb SignalConnectAfter

connectTextViewToggleOverwrite :: (GObject a, MonadIO m) =>
                                  a -> TextViewToggleOverwriteCallback -> SignalConnectMode -> m SignalHandlerId
connectTextViewToggleOverwrite obj cb after = liftIO $ do
    cb' <- mkTextViewToggleOverwriteCallback (textViewToggleOverwriteCallbackWrapper cb)
    connectSignalFunPtr obj "toggle-overwrite" cb' after

-- VVV Prop "accepts-tab"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewAcceptsTab :: (MonadIO m, TextViewK o) => o -> m Bool
getTextViewAcceptsTab obj = liftIO $ getObjectPropertyBool obj "accepts-tab"

setTextViewAcceptsTab :: (MonadIO m, TextViewK o) => o -> Bool -> m ()
setTextViewAcceptsTab obj val = liftIO $ setObjectPropertyBool obj "accepts-tab" val

constructTextViewAcceptsTab :: Bool -> IO ([Char], GValue)
constructTextViewAcceptsTab val = constructObjectPropertyBool "accepts-tab" val

data TextViewAcceptsTabPropertyInfo
instance AttrInfo TextViewAcceptsTabPropertyInfo where
    type AttrAllowedOps TextViewAcceptsTabPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewAcceptsTabPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint TextViewAcceptsTabPropertyInfo = TextViewK
    type AttrGetType TextViewAcceptsTabPropertyInfo = Bool
    type AttrLabel TextViewAcceptsTabPropertyInfo = "TextView::accepts-tab"
    attrGet _ = getTextViewAcceptsTab
    attrSet _ = setTextViewAcceptsTab
    attrConstruct _ = constructTextViewAcceptsTab

-- VVV Prop "buffer"
   -- Type: TInterface "Gtk" "TextBuffer"
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewBuffer :: (MonadIO m, TextViewK o) => o -> m TextBuffer
getTextViewBuffer obj = liftIO $ getObjectPropertyObject obj "buffer" TextBuffer

setTextViewBuffer :: (MonadIO m, TextViewK o, TextBufferK a) => o -> a -> m ()
setTextViewBuffer obj val = liftIO $ setObjectPropertyObject obj "buffer" val

constructTextViewBuffer :: (TextBufferK a) => a -> IO ([Char], GValue)
constructTextViewBuffer val = constructObjectPropertyObject "buffer" val

data TextViewBufferPropertyInfo
instance AttrInfo TextViewBufferPropertyInfo where
    type AttrAllowedOps TextViewBufferPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewBufferPropertyInfo = TextBufferK
    type AttrBaseTypeConstraint TextViewBufferPropertyInfo = TextViewK
    type AttrGetType TextViewBufferPropertyInfo = TextBuffer
    type AttrLabel TextViewBufferPropertyInfo = "TextView::buffer"
    attrGet _ = getTextViewBuffer
    attrSet _ = setTextViewBuffer
    attrConstruct _ = constructTextViewBuffer

-- VVV Prop "cursor-visible"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewCursorVisible :: (MonadIO m, TextViewK o) => o -> m Bool
getTextViewCursorVisible obj = liftIO $ getObjectPropertyBool obj "cursor-visible"

setTextViewCursorVisible :: (MonadIO m, TextViewK o) => o -> Bool -> m ()
setTextViewCursorVisible obj val = liftIO $ setObjectPropertyBool obj "cursor-visible" val

constructTextViewCursorVisible :: Bool -> IO ([Char], GValue)
constructTextViewCursorVisible val = constructObjectPropertyBool "cursor-visible" val

data TextViewCursorVisiblePropertyInfo
instance AttrInfo TextViewCursorVisiblePropertyInfo where
    type AttrAllowedOps TextViewCursorVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewCursorVisiblePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint TextViewCursorVisiblePropertyInfo = TextViewK
    type AttrGetType TextViewCursorVisiblePropertyInfo = Bool
    type AttrLabel TextViewCursorVisiblePropertyInfo = "TextView::cursor-visible"
    attrGet _ = getTextViewCursorVisible
    attrSet _ = setTextViewCursorVisible
    attrConstruct _ = constructTextViewCursorVisible

-- VVV Prop "editable"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewEditable :: (MonadIO m, TextViewK o) => o -> m Bool
getTextViewEditable obj = liftIO $ getObjectPropertyBool obj "editable"

setTextViewEditable :: (MonadIO m, TextViewK o) => o -> Bool -> m ()
setTextViewEditable obj val = liftIO $ setObjectPropertyBool obj "editable" val

constructTextViewEditable :: Bool -> IO ([Char], GValue)
constructTextViewEditable val = constructObjectPropertyBool "editable" val

data TextViewEditablePropertyInfo
instance AttrInfo TextViewEditablePropertyInfo where
    type AttrAllowedOps TextViewEditablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewEditablePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint TextViewEditablePropertyInfo = TextViewK
    type AttrGetType TextViewEditablePropertyInfo = Bool
    type AttrLabel TextViewEditablePropertyInfo = "TextView::editable"
    attrGet _ = getTextViewEditable
    attrSet _ = setTextViewEditable
    attrConstruct _ = constructTextViewEditable

-- VVV Prop "im-module"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewImModule :: (MonadIO m, TextViewK o) => o -> m T.Text
getTextViewImModule obj = liftIO $ getObjectPropertyString obj "im-module"

setTextViewImModule :: (MonadIO m, TextViewK o) => o -> T.Text -> m ()
setTextViewImModule obj val = liftIO $ setObjectPropertyString obj "im-module" val

constructTextViewImModule :: T.Text -> IO ([Char], GValue)
constructTextViewImModule val = constructObjectPropertyString "im-module" val

data TextViewImModulePropertyInfo
instance AttrInfo TextViewImModulePropertyInfo where
    type AttrAllowedOps TextViewImModulePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewImModulePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint TextViewImModulePropertyInfo = TextViewK
    type AttrGetType TextViewImModulePropertyInfo = T.Text
    type AttrLabel TextViewImModulePropertyInfo = "TextView::im-module"
    attrGet _ = getTextViewImModule
    attrSet _ = setTextViewImModule
    attrConstruct _ = constructTextViewImModule

-- VVV Prop "indent"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewIndent :: (MonadIO m, TextViewK o) => o -> m Int32
getTextViewIndent obj = liftIO $ getObjectPropertyCInt obj "indent"

setTextViewIndent :: (MonadIO m, TextViewK o) => o -> Int32 -> m ()
setTextViewIndent obj val = liftIO $ setObjectPropertyCInt obj "indent" val

constructTextViewIndent :: Int32 -> IO ([Char], GValue)
constructTextViewIndent val = constructObjectPropertyCInt "indent" val

data TextViewIndentPropertyInfo
instance AttrInfo TextViewIndentPropertyInfo where
    type AttrAllowedOps TextViewIndentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewIndentPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint TextViewIndentPropertyInfo = TextViewK
    type AttrGetType TextViewIndentPropertyInfo = Int32
    type AttrLabel TextViewIndentPropertyInfo = "TextView::indent"
    attrGet _ = getTextViewIndent
    attrSet _ = setTextViewIndent
    attrConstruct _ = constructTextViewIndent

-- VVV Prop "input-hints"
   -- Type: TInterface "Gtk" "InputHints"
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewInputHints :: (MonadIO m, TextViewK o) => o -> m [InputHints]
getTextViewInputHints obj = liftIO $ getObjectPropertyFlags obj "input-hints"

setTextViewInputHints :: (MonadIO m, TextViewK o) => o -> [InputHints] -> m ()
setTextViewInputHints obj val = liftIO $ setObjectPropertyFlags obj "input-hints" val

constructTextViewInputHints :: [InputHints] -> IO ([Char], GValue)
constructTextViewInputHints val = constructObjectPropertyFlags "input-hints" val

data TextViewInputHintsPropertyInfo
instance AttrInfo TextViewInputHintsPropertyInfo where
    type AttrAllowedOps TextViewInputHintsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewInputHintsPropertyInfo = (~) [InputHints]
    type AttrBaseTypeConstraint TextViewInputHintsPropertyInfo = TextViewK
    type AttrGetType TextViewInputHintsPropertyInfo = [InputHints]
    type AttrLabel TextViewInputHintsPropertyInfo = "TextView::input-hints"
    attrGet _ = getTextViewInputHints
    attrSet _ = setTextViewInputHints
    attrConstruct _ = constructTextViewInputHints

-- VVV Prop "input-purpose"
   -- Type: TInterface "Gtk" "InputPurpose"
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewInputPurpose :: (MonadIO m, TextViewK o) => o -> m InputPurpose
getTextViewInputPurpose obj = liftIO $ getObjectPropertyEnum obj "input-purpose"

setTextViewInputPurpose :: (MonadIO m, TextViewK o) => o -> InputPurpose -> m ()
setTextViewInputPurpose obj val = liftIO $ setObjectPropertyEnum obj "input-purpose" val

constructTextViewInputPurpose :: InputPurpose -> IO ([Char], GValue)
constructTextViewInputPurpose val = constructObjectPropertyEnum "input-purpose" val

data TextViewInputPurposePropertyInfo
instance AttrInfo TextViewInputPurposePropertyInfo where
    type AttrAllowedOps TextViewInputPurposePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewInputPurposePropertyInfo = (~) InputPurpose
    type AttrBaseTypeConstraint TextViewInputPurposePropertyInfo = TextViewK
    type AttrGetType TextViewInputPurposePropertyInfo = InputPurpose
    type AttrLabel TextViewInputPurposePropertyInfo = "TextView::input-purpose"
    attrGet _ = getTextViewInputPurpose
    attrSet _ = setTextViewInputPurpose
    attrConstruct _ = constructTextViewInputPurpose

-- VVV Prop "justification"
   -- Type: TInterface "Gtk" "Justification"
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewJustification :: (MonadIO m, TextViewK o) => o -> m Justification
getTextViewJustification obj = liftIO $ getObjectPropertyEnum obj "justification"

setTextViewJustification :: (MonadIO m, TextViewK o) => o -> Justification -> m ()
setTextViewJustification obj val = liftIO $ setObjectPropertyEnum obj "justification" val

constructTextViewJustification :: Justification -> IO ([Char], GValue)
constructTextViewJustification val = constructObjectPropertyEnum "justification" val

data TextViewJustificationPropertyInfo
instance AttrInfo TextViewJustificationPropertyInfo where
    type AttrAllowedOps TextViewJustificationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewJustificationPropertyInfo = (~) Justification
    type AttrBaseTypeConstraint TextViewJustificationPropertyInfo = TextViewK
    type AttrGetType TextViewJustificationPropertyInfo = Justification
    type AttrLabel TextViewJustificationPropertyInfo = "TextView::justification"
    attrGet _ = getTextViewJustification
    attrSet _ = setTextViewJustification
    attrConstruct _ = constructTextViewJustification

-- VVV Prop "left-margin"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewLeftMargin :: (MonadIO m, TextViewK o) => o -> m Int32
getTextViewLeftMargin obj = liftIO $ getObjectPropertyCInt obj "left-margin"

setTextViewLeftMargin :: (MonadIO m, TextViewK o) => o -> Int32 -> m ()
setTextViewLeftMargin obj val = liftIO $ setObjectPropertyCInt obj "left-margin" val

constructTextViewLeftMargin :: Int32 -> IO ([Char], GValue)
constructTextViewLeftMargin val = constructObjectPropertyCInt "left-margin" val

data TextViewLeftMarginPropertyInfo
instance AttrInfo TextViewLeftMarginPropertyInfo where
    type AttrAllowedOps TextViewLeftMarginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewLeftMarginPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint TextViewLeftMarginPropertyInfo = TextViewK
    type AttrGetType TextViewLeftMarginPropertyInfo = Int32
    type AttrLabel TextViewLeftMarginPropertyInfo = "TextView::left-margin"
    attrGet _ = getTextViewLeftMargin
    attrSet _ = setTextViewLeftMargin
    attrConstruct _ = constructTextViewLeftMargin

-- VVV Prop "monospace"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewMonospace :: (MonadIO m, TextViewK o) => o -> m Bool
getTextViewMonospace obj = liftIO $ getObjectPropertyBool obj "monospace"

setTextViewMonospace :: (MonadIO m, TextViewK o) => o -> Bool -> m ()
setTextViewMonospace obj val = liftIO $ setObjectPropertyBool obj "monospace" val

constructTextViewMonospace :: Bool -> IO ([Char], GValue)
constructTextViewMonospace val = constructObjectPropertyBool "monospace" val

data TextViewMonospacePropertyInfo
instance AttrInfo TextViewMonospacePropertyInfo where
    type AttrAllowedOps TextViewMonospacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewMonospacePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint TextViewMonospacePropertyInfo = TextViewK
    type AttrGetType TextViewMonospacePropertyInfo = Bool
    type AttrLabel TextViewMonospacePropertyInfo = "TextView::monospace"
    attrGet _ = getTextViewMonospace
    attrSet _ = setTextViewMonospace
    attrConstruct _ = constructTextViewMonospace

-- VVV Prop "overwrite"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewOverwrite :: (MonadIO m, TextViewK o) => o -> m Bool
getTextViewOverwrite obj = liftIO $ getObjectPropertyBool obj "overwrite"

setTextViewOverwrite :: (MonadIO m, TextViewK o) => o -> Bool -> m ()
setTextViewOverwrite obj val = liftIO $ setObjectPropertyBool obj "overwrite" val

constructTextViewOverwrite :: Bool -> IO ([Char], GValue)
constructTextViewOverwrite val = constructObjectPropertyBool "overwrite" val

data TextViewOverwritePropertyInfo
instance AttrInfo TextViewOverwritePropertyInfo where
    type AttrAllowedOps TextViewOverwritePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewOverwritePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint TextViewOverwritePropertyInfo = TextViewK
    type AttrGetType TextViewOverwritePropertyInfo = Bool
    type AttrLabel TextViewOverwritePropertyInfo = "TextView::overwrite"
    attrGet _ = getTextViewOverwrite
    attrSet _ = setTextViewOverwrite
    attrConstruct _ = constructTextViewOverwrite

-- VVV Prop "pixels-above-lines"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewPixelsAboveLines :: (MonadIO m, TextViewK o) => o -> m Int32
getTextViewPixelsAboveLines obj = liftIO $ getObjectPropertyCInt obj "pixels-above-lines"

setTextViewPixelsAboveLines :: (MonadIO m, TextViewK o) => o -> Int32 -> m ()
setTextViewPixelsAboveLines obj val = liftIO $ setObjectPropertyCInt obj "pixels-above-lines" val

constructTextViewPixelsAboveLines :: Int32 -> IO ([Char], GValue)
constructTextViewPixelsAboveLines val = constructObjectPropertyCInt "pixels-above-lines" val

data TextViewPixelsAboveLinesPropertyInfo
instance AttrInfo TextViewPixelsAboveLinesPropertyInfo where
    type AttrAllowedOps TextViewPixelsAboveLinesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewPixelsAboveLinesPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint TextViewPixelsAboveLinesPropertyInfo = TextViewK
    type AttrGetType TextViewPixelsAboveLinesPropertyInfo = Int32
    type AttrLabel TextViewPixelsAboveLinesPropertyInfo = "TextView::pixels-above-lines"
    attrGet _ = getTextViewPixelsAboveLines
    attrSet _ = setTextViewPixelsAboveLines
    attrConstruct _ = constructTextViewPixelsAboveLines

-- VVV Prop "pixels-below-lines"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewPixelsBelowLines :: (MonadIO m, TextViewK o) => o -> m Int32
getTextViewPixelsBelowLines obj = liftIO $ getObjectPropertyCInt obj "pixels-below-lines"

setTextViewPixelsBelowLines :: (MonadIO m, TextViewK o) => o -> Int32 -> m ()
setTextViewPixelsBelowLines obj val = liftIO $ setObjectPropertyCInt obj "pixels-below-lines" val

constructTextViewPixelsBelowLines :: Int32 -> IO ([Char], GValue)
constructTextViewPixelsBelowLines val = constructObjectPropertyCInt "pixels-below-lines" val

data TextViewPixelsBelowLinesPropertyInfo
instance AttrInfo TextViewPixelsBelowLinesPropertyInfo where
    type AttrAllowedOps TextViewPixelsBelowLinesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewPixelsBelowLinesPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint TextViewPixelsBelowLinesPropertyInfo = TextViewK
    type AttrGetType TextViewPixelsBelowLinesPropertyInfo = Int32
    type AttrLabel TextViewPixelsBelowLinesPropertyInfo = "TextView::pixels-below-lines"
    attrGet _ = getTextViewPixelsBelowLines
    attrSet _ = setTextViewPixelsBelowLines
    attrConstruct _ = constructTextViewPixelsBelowLines

-- VVV Prop "pixels-inside-wrap"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewPixelsInsideWrap :: (MonadIO m, TextViewK o) => o -> m Int32
getTextViewPixelsInsideWrap obj = liftIO $ getObjectPropertyCInt obj "pixels-inside-wrap"

setTextViewPixelsInsideWrap :: (MonadIO m, TextViewK o) => o -> Int32 -> m ()
setTextViewPixelsInsideWrap obj val = liftIO $ setObjectPropertyCInt obj "pixels-inside-wrap" val

constructTextViewPixelsInsideWrap :: Int32 -> IO ([Char], GValue)
constructTextViewPixelsInsideWrap val = constructObjectPropertyCInt "pixels-inside-wrap" val

data TextViewPixelsInsideWrapPropertyInfo
instance AttrInfo TextViewPixelsInsideWrapPropertyInfo where
    type AttrAllowedOps TextViewPixelsInsideWrapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewPixelsInsideWrapPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint TextViewPixelsInsideWrapPropertyInfo = TextViewK
    type AttrGetType TextViewPixelsInsideWrapPropertyInfo = Int32
    type AttrLabel TextViewPixelsInsideWrapPropertyInfo = "TextView::pixels-inside-wrap"
    attrGet _ = getTextViewPixelsInsideWrap
    attrSet _ = setTextViewPixelsInsideWrap
    attrConstruct _ = constructTextViewPixelsInsideWrap

-- VVV Prop "populate-all"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewPopulateAll :: (MonadIO m, TextViewK o) => o -> m Bool
getTextViewPopulateAll obj = liftIO $ getObjectPropertyBool obj "populate-all"

setTextViewPopulateAll :: (MonadIO m, TextViewK o) => o -> Bool -> m ()
setTextViewPopulateAll obj val = liftIO $ setObjectPropertyBool obj "populate-all" val

constructTextViewPopulateAll :: Bool -> IO ([Char], GValue)
constructTextViewPopulateAll val = constructObjectPropertyBool "populate-all" val

data TextViewPopulateAllPropertyInfo
instance AttrInfo TextViewPopulateAllPropertyInfo where
    type AttrAllowedOps TextViewPopulateAllPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewPopulateAllPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint TextViewPopulateAllPropertyInfo = TextViewK
    type AttrGetType TextViewPopulateAllPropertyInfo = Bool
    type AttrLabel TextViewPopulateAllPropertyInfo = "TextView::populate-all"
    attrGet _ = getTextViewPopulateAll
    attrSet _ = setTextViewPopulateAll
    attrConstruct _ = constructTextViewPopulateAll

-- VVV Prop "right-margin"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewRightMargin :: (MonadIO m, TextViewK o) => o -> m Int32
getTextViewRightMargin obj = liftIO $ getObjectPropertyCInt obj "right-margin"

setTextViewRightMargin :: (MonadIO m, TextViewK o) => o -> Int32 -> m ()
setTextViewRightMargin obj val = liftIO $ setObjectPropertyCInt obj "right-margin" val

constructTextViewRightMargin :: Int32 -> IO ([Char], GValue)
constructTextViewRightMargin val = constructObjectPropertyCInt "right-margin" val

data TextViewRightMarginPropertyInfo
instance AttrInfo TextViewRightMarginPropertyInfo where
    type AttrAllowedOps TextViewRightMarginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewRightMarginPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint TextViewRightMarginPropertyInfo = TextViewK
    type AttrGetType TextViewRightMarginPropertyInfo = Int32
    type AttrLabel TextViewRightMarginPropertyInfo = "TextView::right-margin"
    attrGet _ = getTextViewRightMargin
    attrSet _ = setTextViewRightMargin
    attrConstruct _ = constructTextViewRightMargin

-- VVV Prop "tabs"
   -- Type: TInterface "Pango" "TabArray"
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewTabs :: (MonadIO m, TextViewK o) => o -> m Pango.TabArray
getTextViewTabs obj = liftIO $ getObjectPropertyBoxed obj "tabs" Pango.TabArray

setTextViewTabs :: (MonadIO m, TextViewK o) => o -> Pango.TabArray -> m ()
setTextViewTabs obj val = liftIO $ setObjectPropertyBoxed obj "tabs" val

constructTextViewTabs :: Pango.TabArray -> IO ([Char], GValue)
constructTextViewTabs val = constructObjectPropertyBoxed "tabs" val

data TextViewTabsPropertyInfo
instance AttrInfo TextViewTabsPropertyInfo where
    type AttrAllowedOps TextViewTabsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewTabsPropertyInfo = (~) Pango.TabArray
    type AttrBaseTypeConstraint TextViewTabsPropertyInfo = TextViewK
    type AttrGetType TextViewTabsPropertyInfo = Pango.TabArray
    type AttrLabel TextViewTabsPropertyInfo = "TextView::tabs"
    attrGet _ = getTextViewTabs
    attrSet _ = setTextViewTabs
    attrConstruct _ = constructTextViewTabs

-- VVV Prop "wrap-mode"
   -- Type: TInterface "Gtk" "WrapMode"
   -- Flags: [PropertyReadable,PropertyWritable]

getTextViewWrapMode :: (MonadIO m, TextViewK o) => o -> m WrapMode
getTextViewWrapMode obj = liftIO $ getObjectPropertyEnum obj "wrap-mode"

setTextViewWrapMode :: (MonadIO m, TextViewK o) => o -> WrapMode -> m ()
setTextViewWrapMode obj val = liftIO $ setObjectPropertyEnum obj "wrap-mode" val

constructTextViewWrapMode :: WrapMode -> IO ([Char], GValue)
constructTextViewWrapMode val = constructObjectPropertyEnum "wrap-mode" val

data TextViewWrapModePropertyInfo
instance AttrInfo TextViewWrapModePropertyInfo where
    type AttrAllowedOps TextViewWrapModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint TextViewWrapModePropertyInfo = (~) WrapMode
    type AttrBaseTypeConstraint TextViewWrapModePropertyInfo = TextViewK
    type AttrGetType TextViewWrapModePropertyInfo = WrapMode
    type AttrLabel TextViewWrapModePropertyInfo = "TextView::wrap-mode"
    attrGet _ = getTextViewWrapMode
    attrSet _ = setTextViewWrapMode
    attrConstruct _ = constructTextViewWrapMode

type instance AttributeList TextView = TextViewAttributeList
type TextViewAttributeList = ('[ '("accepts-tab", TextViewAcceptsTabPropertyInfo), '("app-paintable", WidgetAppPaintablePropertyInfo), '("border-width", ContainerBorderWidthPropertyInfo), '("buffer", TextViewBufferPropertyInfo), '("can-default", WidgetCanDefaultPropertyInfo), '("can-focus", WidgetCanFocusPropertyInfo), '("child", ContainerChildPropertyInfo), '("composite-child", WidgetCompositeChildPropertyInfo), '("cursor-visible", TextViewCursorVisiblePropertyInfo), '("double-buffered", WidgetDoubleBufferedPropertyInfo), '("editable", TextViewEditablePropertyInfo), '("events", WidgetEventsPropertyInfo), '("expand", WidgetExpandPropertyInfo), '("hadjustment", ScrollableHadjustmentPropertyInfo), '("halign", WidgetHalignPropertyInfo), '("has-default", WidgetHasDefaultPropertyInfo), '("has-focus", WidgetHasFocusPropertyInfo), '("has-tooltip", WidgetHasTooltipPropertyInfo), '("height-request", WidgetHeightRequestPropertyInfo), '("hexpand", WidgetHexpandPropertyInfo), '("hexpand-set", WidgetHexpandSetPropertyInfo), '("hscroll-policy", ScrollableHscrollPolicyPropertyInfo), '("im-module", TextViewImModulePropertyInfo), '("indent", TextViewIndentPropertyInfo), '("input-hints", TextViewInputHintsPropertyInfo), '("input-purpose", TextViewInputPurposePropertyInfo), '("is-focus", WidgetIsFocusPropertyInfo), '("justification", TextViewJustificationPropertyInfo), '("left-margin", TextViewLeftMarginPropertyInfo), '("margin", WidgetMarginPropertyInfo), '("margin-bottom", WidgetMarginBottomPropertyInfo), '("margin-end", WidgetMarginEndPropertyInfo), '("margin-left", WidgetMarginLeftPropertyInfo), '("margin-right", WidgetMarginRightPropertyInfo), '("margin-start", WidgetMarginStartPropertyInfo), '("margin-top", WidgetMarginTopPropertyInfo), '("monospace", TextViewMonospacePropertyInfo), '("name", WidgetNamePropertyInfo), '("no-show-all", WidgetNoShowAllPropertyInfo), '("opacity", WidgetOpacityPropertyInfo), '("overwrite", TextViewOverwritePropertyInfo), '("parent", WidgetParentPropertyInfo), '("pixels-above-lines", TextViewPixelsAboveLinesPropertyInfo), '("pixels-below-lines", TextViewPixelsBelowLinesPropertyInfo), '("pixels-inside-wrap", TextViewPixelsInsideWrapPropertyInfo), '("populate-all", TextViewPopulateAllPropertyInfo), '("receives-default", WidgetReceivesDefaultPropertyInfo), '("resize-mode", ContainerResizeModePropertyInfo), '("right-margin", TextViewRightMarginPropertyInfo), '("scale-factor", WidgetScaleFactorPropertyInfo), '("sensitive", WidgetSensitivePropertyInfo), '("style", WidgetStylePropertyInfo), '("tabs", TextViewTabsPropertyInfo), '("tooltip-markup", WidgetTooltipMarkupPropertyInfo), '("tooltip-text", WidgetTooltipTextPropertyInfo), '("vadjustment", ScrollableVadjustmentPropertyInfo), '("valign", WidgetValignPropertyInfo), '("vexpand", WidgetVexpandPropertyInfo), '("vexpand-set", WidgetVexpandSetPropertyInfo), '("visible", WidgetVisiblePropertyInfo), '("vscroll-policy", ScrollableVscrollPolicyPropertyInfo), '("width-request", WidgetWidthRequestPropertyInfo), '("window", WidgetWindowPropertyInfo), '("wrap-mode", TextViewWrapModePropertyInfo)] :: [(Symbol, *)])

data TextViewBackspaceSignalInfo
instance SignalInfo TextViewBackspaceSignalInfo where
    type HaskellCallbackType TextViewBackspaceSignalInfo = TextViewBackspaceCallback
    connectSignal _ = connectTextViewBackspace

data TextViewCopyClipboardSignalInfo
instance SignalInfo TextViewCopyClipboardSignalInfo where
    type HaskellCallbackType TextViewCopyClipboardSignalInfo = TextViewCopyClipboardCallback
    connectSignal _ = connectTextViewCopyClipboard

data TextViewCutClipboardSignalInfo
instance SignalInfo TextViewCutClipboardSignalInfo where
    type HaskellCallbackType TextViewCutClipboardSignalInfo = TextViewCutClipboardCallback
    connectSignal _ = connectTextViewCutClipboard

data TextViewDeleteFromCursorSignalInfo
instance SignalInfo TextViewDeleteFromCursorSignalInfo where
    type HaskellCallbackType TextViewDeleteFromCursorSignalInfo = TextViewDeleteFromCursorCallback
    connectSignal _ = connectTextViewDeleteFromCursor

data TextViewExtendSelectionSignalInfo
instance SignalInfo TextViewExtendSelectionSignalInfo where
    type HaskellCallbackType TextViewExtendSelectionSignalInfo = TextViewExtendSelectionCallback
    connectSignal _ = connectTextViewExtendSelection

data TextViewInsertAtCursorSignalInfo
instance SignalInfo TextViewInsertAtCursorSignalInfo where
    type HaskellCallbackType TextViewInsertAtCursorSignalInfo = TextViewInsertAtCursorCallback
    connectSignal _ = connectTextViewInsertAtCursor

data TextViewMoveCursorSignalInfo
instance SignalInfo TextViewMoveCursorSignalInfo where
    type HaskellCallbackType TextViewMoveCursorSignalInfo = TextViewMoveCursorCallback
    connectSignal _ = connectTextViewMoveCursor

data TextViewMoveViewportSignalInfo
instance SignalInfo TextViewMoveViewportSignalInfo where
    type HaskellCallbackType TextViewMoveViewportSignalInfo = TextViewMoveViewportCallback
    connectSignal _ = connectTextViewMoveViewport

data TextViewPasteClipboardSignalInfo
instance SignalInfo TextViewPasteClipboardSignalInfo where
    type HaskellCallbackType TextViewPasteClipboardSignalInfo = TextViewPasteClipboardCallback
    connectSignal _ = connectTextViewPasteClipboard

data TextViewPopulatePopupSignalInfo
instance SignalInfo TextViewPopulatePopupSignalInfo where
    type HaskellCallbackType TextViewPopulatePopupSignalInfo = TextViewPopulatePopupCallback
    connectSignal _ = connectTextViewPopulatePopup

data TextViewPreeditChangedSignalInfo
instance SignalInfo TextViewPreeditChangedSignalInfo where
    type HaskellCallbackType TextViewPreeditChangedSignalInfo = TextViewPreeditChangedCallback
    connectSignal _ = connectTextViewPreeditChanged

data TextViewSelectAllSignalInfo
instance SignalInfo TextViewSelectAllSignalInfo where
    type HaskellCallbackType TextViewSelectAllSignalInfo = TextViewSelectAllCallback
    connectSignal _ = connectTextViewSelectAll

data TextViewSetAnchorSignalInfo
instance SignalInfo TextViewSetAnchorSignalInfo where
    type HaskellCallbackType TextViewSetAnchorSignalInfo = TextViewSetAnchorCallback
    connectSignal _ = connectTextViewSetAnchor

data TextViewToggleCursorVisibleSignalInfo
instance SignalInfo TextViewToggleCursorVisibleSignalInfo where
    type HaskellCallbackType TextViewToggleCursorVisibleSignalInfo = TextViewToggleCursorVisibleCallback
    connectSignal _ = connectTextViewToggleCursorVisible

data TextViewToggleOverwriteSignalInfo
instance SignalInfo TextViewToggleOverwriteSignalInfo where
    type HaskellCallbackType TextViewToggleOverwriteSignalInfo = TextViewToggleOverwriteCallback
    connectSignal _ = connectTextViewToggleOverwrite

type instance SignalList TextView = TextViewSignalList
type TextViewSignalList = ('[ '("accel-closures-changed", WidgetAccelClosuresChangedSignalInfo), '("add", ContainerAddSignalInfo), '("backspace", TextViewBackspaceSignalInfo), '("button-press-event", WidgetButtonPressEventSignalInfo), '("button-release-event", WidgetButtonReleaseEventSignalInfo), '("can-activate-accel", WidgetCanActivateAccelSignalInfo), '("check-resize", ContainerCheckResizeSignalInfo), '("child-notify", WidgetChildNotifySignalInfo), '("composited-changed", WidgetCompositedChangedSignalInfo), '("configure-event", WidgetConfigureEventSignalInfo), '("copy-clipboard", TextViewCopyClipboardSignalInfo), '("cut-clipboard", TextViewCutClipboardSignalInfo), '("damage-event", WidgetDamageEventSignalInfo), '("delete-event", WidgetDeleteEventSignalInfo), '("delete-from-cursor", TextViewDeleteFromCursorSignalInfo), '("destroy", WidgetDestroySignalInfo), '("destroy-event", WidgetDestroyEventSignalInfo), '("direction-changed", WidgetDirectionChangedSignalInfo), '("drag-begin", WidgetDragBeginSignalInfo), '("drag-data-delete", WidgetDragDataDeleteSignalInfo), '("drag-data-get", WidgetDragDataGetSignalInfo), '("drag-data-received", WidgetDragDataReceivedSignalInfo), '("drag-drop", WidgetDragDropSignalInfo), '("drag-end", WidgetDragEndSignalInfo), '("drag-failed", WidgetDragFailedSignalInfo), '("drag-leave", WidgetDragLeaveSignalInfo), '("drag-motion", WidgetDragMotionSignalInfo), '("draw", WidgetDrawSignalInfo), '("enter-notify-event", WidgetEnterNotifyEventSignalInfo), '("event", WidgetEventSignalInfo), '("event-after", WidgetEventAfterSignalInfo), '("extend-selection", TextViewExtendSelectionSignalInfo), '("focus", WidgetFocusSignalInfo), '("focus-in-event", WidgetFocusInEventSignalInfo), '("focus-out-event", WidgetFocusOutEventSignalInfo), '("grab-broken-event", WidgetGrabBrokenEventSignalInfo), '("grab-focus", WidgetGrabFocusSignalInfo), '("grab-notify", WidgetGrabNotifySignalInfo), '("hide", WidgetHideSignalInfo), '("hierarchy-changed", WidgetHierarchyChangedSignalInfo), '("insert-at-cursor", TextViewInsertAtCursorSignalInfo), '("key-press-event", WidgetKeyPressEventSignalInfo), '("key-release-event", WidgetKeyReleaseEventSignalInfo), '("keynav-failed", WidgetKeynavFailedSignalInfo), '("leave-notify-event", WidgetLeaveNotifyEventSignalInfo), '("map", WidgetMapSignalInfo), '("map-event", WidgetMapEventSignalInfo), '("mnemonic-activate", WidgetMnemonicActivateSignalInfo), '("motion-notify-event", WidgetMotionNotifyEventSignalInfo), '("move-cursor", TextViewMoveCursorSignalInfo), '("move-focus", WidgetMoveFocusSignalInfo), '("move-viewport", TextViewMoveViewportSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("parent-set", WidgetParentSetSignalInfo), '("paste-clipboard", TextViewPasteClipboardSignalInfo), '("populate-popup", TextViewPopulatePopupSignalInfo), '("popup-menu", WidgetPopupMenuSignalInfo), '("preedit-changed", TextViewPreeditChangedSignalInfo), '("property-notify-event", WidgetPropertyNotifyEventSignalInfo), '("proximity-in-event", WidgetProximityInEventSignalInfo), '("proximity-out-event", WidgetProximityOutEventSignalInfo), '("query-tooltip", WidgetQueryTooltipSignalInfo), '("realize", WidgetRealizeSignalInfo), '("remove", ContainerRemoveSignalInfo), '("screen-changed", WidgetScreenChangedSignalInfo), '("scroll-event", WidgetScrollEventSignalInfo), '("select-all", TextViewSelectAllSignalInfo), '("selection-clear-event", WidgetSelectionClearEventSignalInfo), '("selection-get", WidgetSelectionGetSignalInfo), '("selection-notify-event", WidgetSelectionNotifyEventSignalInfo), '("selection-received", WidgetSelectionReceivedSignalInfo), '("selection-request-event", WidgetSelectionRequestEventSignalInfo), '("set-anchor", TextViewSetAnchorSignalInfo), '("set-focus-child", ContainerSetFocusChildSignalInfo), '("show", WidgetShowSignalInfo), '("show-help", WidgetShowHelpSignalInfo), '("size-allocate", WidgetSizeAllocateSignalInfo), '("state-changed", WidgetStateChangedSignalInfo), '("state-flags-changed", WidgetStateFlagsChangedSignalInfo), '("style-set", WidgetStyleSetSignalInfo), '("style-updated", WidgetStyleUpdatedSignalInfo), '("toggle-cursor-visible", TextViewToggleCursorVisibleSignalInfo), '("toggle-overwrite", TextViewToggleOverwriteSignalInfo), '("touch-event", WidgetTouchEventSignalInfo), '("unmap", WidgetUnmapSignalInfo), '("unmap-event", WidgetUnmapEventSignalInfo), '("unrealize", WidgetUnrealizeSignalInfo), '("visibility-notify-event", WidgetVisibilityNotifyEventSignalInfo), '("window-state-event", WidgetWindowStateEventSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method TextView::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Gtk" "TextView"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_new" gtk_text_view_new :: 
    IO (Ptr TextView)


textViewNew ::
    (MonadIO m) =>
    m TextView
textViewNew  = liftIO $ do
    result <- gtk_text_view_new
    checkUnexpectedReturnNULL "gtk_text_view_new" result
    result' <- (newObject TextView) result
    return result'

-- method TextView::new_with_buffer
-- method type : Constructor
-- Args : [Arg {argName = "buffer", argType = TInterface "Gtk" "TextBuffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "buffer", argType = TInterface "Gtk" "TextBuffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "TextView"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_new_with_buffer" gtk_text_view_new_with_buffer :: 
    Ptr TextBuffer ->                       -- buffer : TInterface "Gtk" "TextBuffer"
    IO (Ptr TextView)


textViewNewWithBuffer ::
    (MonadIO m, TextBufferK a) =>
    a ->                                    -- buffer
    m TextView
textViewNewWithBuffer buffer = liftIO $ do
    let buffer' = unsafeManagedPtrCastPtr buffer
    result <- gtk_text_view_new_with_buffer buffer'
    checkUnexpectedReturnNULL "gtk_text_view_new_with_buffer" result
    result' <- (newObject TextView) result
    touchManagedPtr buffer
    return result'

-- method TextView::add_child_at_anchor
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "anchor", argType = TInterface "Gtk" "TextChildAnchor", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "anchor", argType = TInterface "Gtk" "TextChildAnchor", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_add_child_at_anchor" gtk_text_view_add_child_at_anchor :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    Ptr TextChildAnchor ->                  -- anchor : TInterface "Gtk" "TextChildAnchor"
    IO ()


textViewAddChildAtAnchor ::
    (MonadIO m, TextViewK a, WidgetK b, TextChildAnchorK c) =>
    a ->                                    -- _obj
    b ->                                    -- child
    c ->                                    -- anchor
    m ()
textViewAddChildAtAnchor _obj child anchor = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    let anchor' = unsafeManagedPtrCastPtr anchor
    gtk_text_view_add_child_at_anchor _obj' child' anchor'
    touchManagedPtr _obj
    touchManagedPtr child
    touchManagedPtr anchor
    return ()

-- method TextView::add_child_in_window
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "which_window", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xpos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ypos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "which_window", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xpos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ypos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_add_child_in_window" gtk_text_view_add_child_in_window :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    CUInt ->                                -- which_window : TInterface "Gtk" "TextWindowType"
    Int32 ->                                -- xpos : TBasicType TInt32
    Int32 ->                                -- ypos : TBasicType TInt32
    IO ()


textViewAddChildInWindow ::
    (MonadIO m, TextViewK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- child
    TextWindowType ->                       -- which_window
    Int32 ->                                -- xpos
    Int32 ->                                -- ypos
    m ()
textViewAddChildInWindow _obj child which_window xpos ypos = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    let which_window' = (fromIntegral . fromEnum) which_window
    gtk_text_view_add_child_in_window _obj' child' which_window' xpos ypos
    touchManagedPtr _obj
    touchManagedPtr child
    return ()

-- method TextView::backward_display_line
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_backward_display_line" gtk_text_view_backward_display_line :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    IO CInt


textViewBackwardDisplayLine ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    m Bool
textViewBackwardDisplayLine _obj iter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    result <- gtk_text_view_backward_display_line _obj' iter'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr iter
    return result'

-- method TextView::backward_display_line_start
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_backward_display_line_start" gtk_text_view_backward_display_line_start :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    IO CInt


textViewBackwardDisplayLineStart ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    m Bool
textViewBackwardDisplayLineStart _obj iter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    result <- gtk_text_view_backward_display_line_start _obj' iter'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr iter
    return result'

-- method TextView::buffer_to_window_coords
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "win", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer_x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer_y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "window_x", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "window_y", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "win", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer_x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer_y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_buffer_to_window_coords" gtk_text_view_buffer_to_window_coords :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- win : TInterface "Gtk" "TextWindowType"
    Int32 ->                                -- buffer_x : TBasicType TInt32
    Int32 ->                                -- buffer_y : TBasicType TInt32
    Ptr Int32 ->                            -- window_x : TBasicType TInt32
    Ptr Int32 ->                            -- window_y : TBasicType TInt32
    IO ()


textViewBufferToWindowCoords ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextWindowType ->                       -- win
    Int32 ->                                -- buffer_x
    Int32 ->                                -- buffer_y
    m (Int32,Int32)
textViewBufferToWindowCoords _obj win buffer_x buffer_y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let win' = (fromIntegral . fromEnum) win
    window_x <- allocMem :: IO (Ptr Int32)
    window_y <- allocMem :: IO (Ptr Int32)
    gtk_text_view_buffer_to_window_coords _obj' win' buffer_x buffer_y window_x window_y
    window_x' <- peek window_x
    window_y' <- peek window_y
    touchManagedPtr _obj
    freeMem window_x
    freeMem window_y
    return (window_x', window_y')

-- method TextView::forward_display_line
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_forward_display_line" gtk_text_view_forward_display_line :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    IO CInt


textViewForwardDisplayLine ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    m Bool
textViewForwardDisplayLine _obj iter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    result <- gtk_text_view_forward_display_line _obj' iter'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr iter
    return result'

-- method TextView::forward_display_line_end
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_forward_display_line_end" gtk_text_view_forward_display_line_end :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    IO CInt


textViewForwardDisplayLineEnd ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    m Bool
textViewForwardDisplayLineEnd _obj iter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    result <- gtk_text_view_forward_display_line_end _obj' iter'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr iter
    return result'

-- method TextView::get_accepts_tab
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_accepts_tab" gtk_text_view_get_accepts_tab :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CInt


textViewGetAcceptsTab ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Bool
textViewGetAcceptsTab _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_accepts_tab _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_border_window_size
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_border_window_size" gtk_text_view_get_border_window_size :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- type : TInterface "Gtk" "TextWindowType"
    IO Int32


textViewGetBorderWindowSize ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextWindowType ->                       -- type
    m Int32
textViewGetBorderWindowSize _obj type_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let type_' = (fromIntegral . fromEnum) type_
    result <- gtk_text_view_get_border_window_size _obj' type_'
    touchManagedPtr _obj
    return result

-- method TextView::get_buffer
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "TextBuffer"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_buffer" gtk_text_view_get_buffer :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO (Ptr TextBuffer)


textViewGetBuffer ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m TextBuffer
textViewGetBuffer _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_buffer _obj'
    checkUnexpectedReturnNULL "gtk_text_view_get_buffer" result
    result' <- (newObject TextBuffer) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_cursor_locations
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "strong", argType = TInterface "cairo" "RectangleInt", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "weak", argType = TInterface "cairo" "RectangleInt", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_cursor_locations" gtk_text_view_get_cursor_locations :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    Ptr Cairo.RectangleInt ->               -- strong : TInterface "cairo" "RectangleInt"
    Ptr Cairo.RectangleInt ->               -- weak : TInterface "cairo" "RectangleInt"
    IO ()


textViewGetCursorLocations ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Maybe (TextIter) ->                     -- iter
    m (Cairo.RectangleInt,Cairo.RectangleInt)
textViewGetCursorLocations _obj iter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeIter <- case iter of
        Nothing -> return nullPtr
        Just jIter -> do
            let jIter' = unsafeManagedPtrGetPtr jIter
            return jIter'
    strong <- callocBoxedBytes 16 :: IO (Ptr Cairo.RectangleInt)
    weak <- callocBoxedBytes 16 :: IO (Ptr Cairo.RectangleInt)
    gtk_text_view_get_cursor_locations _obj' maybeIter strong weak
    strong' <- (wrapBoxed Cairo.RectangleInt) strong
    weak' <- (wrapBoxed Cairo.RectangleInt) weak
    touchManagedPtr _obj
    whenJust iter touchManagedPtr
    return (strong', weak')

-- method TextView::get_cursor_visible
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_cursor_visible" gtk_text_view_get_cursor_visible :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CInt


textViewGetCursorVisible ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Bool
textViewGetCursorVisible _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_cursor_visible _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_default_attributes
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "TextAttributes"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_default_attributes" gtk_text_view_get_default_attributes :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO (Ptr TextAttributes)


textViewGetDefaultAttributes ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m TextAttributes
textViewGetDefaultAttributes _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_default_attributes _obj'
    checkUnexpectedReturnNULL "gtk_text_view_get_default_attributes" result
    result' <- (wrapBoxed TextAttributes) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_editable
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_editable" gtk_text_view_get_editable :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CInt


textViewGetEditable ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Bool
textViewGetEditable _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_editable _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_hadjustment
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Adjustment"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_hadjustment" gtk_text_view_get_hadjustment :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO (Ptr Adjustment)

{-# DEPRECATED textViewGetHadjustment ["(Since version 3.0)","Use gtk_scrollable_get_hadjustment()"]#-}
textViewGetHadjustment ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Adjustment
textViewGetHadjustment _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_hadjustment _obj'
    checkUnexpectedReturnNULL "gtk_text_view_get_hadjustment" result
    result' <- (newObject Adjustment) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_indent
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_indent" gtk_text_view_get_indent :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO Int32


textViewGetIndent ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Int32
textViewGetIndent _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_indent _obj'
    touchManagedPtr _obj
    return result

-- method TextView::get_input_hints
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "InputHints"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_input_hints" gtk_text_view_get_input_hints :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CUInt


textViewGetInputHints ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m [InputHints]
textViewGetInputHints _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_input_hints _obj'
    let result' = wordToGFlags result
    touchManagedPtr _obj
    return result'

-- method TextView::get_input_purpose
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "InputPurpose"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_input_purpose" gtk_text_view_get_input_purpose :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CUInt


textViewGetInputPurpose ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m InputPurpose
textViewGetInputPurpose _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_input_purpose _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_iter_at_location
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_iter_at_location" gtk_text_view_get_iter_at_location :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    Int32 ->                                -- x : TBasicType TInt32
    Int32 ->                                -- y : TBasicType TInt32
    IO ()


textViewGetIterAtLocation ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- x
    Int32 ->                                -- y
    m (TextIter)
textViewGetIterAtLocation _obj x y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    iter <- callocBoxedBytes 80 :: IO (Ptr TextIter)
    gtk_text_view_get_iter_at_location _obj' iter x y
    iter' <- (wrapBoxed TextIter) iter
    touchManagedPtr _obj
    return iter'

-- method TextView::get_iter_at_position
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "trailing", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_iter_at_position" gtk_text_view_get_iter_at_position :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    Ptr Int32 ->                            -- trailing : TBasicType TInt32
    Int32 ->                                -- x : TBasicType TInt32
    Int32 ->                                -- y : TBasicType TInt32
    IO ()


textViewGetIterAtPosition ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- x
    Int32 ->                                -- y
    m (TextIter,Int32)
textViewGetIterAtPosition _obj x y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    iter <- callocBoxedBytes 80 :: IO (Ptr TextIter)
    trailing <- allocMem :: IO (Ptr Int32)
    gtk_text_view_get_iter_at_position _obj' iter trailing x y
    iter' <- (wrapBoxed TextIter) iter
    trailing' <- peek trailing
    touchManagedPtr _obj
    freeMem trailing
    return (iter', trailing')

-- method TextView::get_iter_location
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "location", argType = TInterface "cairo" "RectangleInt", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_iter_location" gtk_text_view_get_iter_location :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    Ptr Cairo.RectangleInt ->               -- location : TInterface "cairo" "RectangleInt"
    IO ()


textViewGetIterLocation ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    m (Cairo.RectangleInt)
textViewGetIterLocation _obj iter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    location <- callocBoxedBytes 16 :: IO (Ptr Cairo.RectangleInt)
    gtk_text_view_get_iter_location _obj' iter' location
    location' <- (wrapBoxed Cairo.RectangleInt) location
    touchManagedPtr _obj
    touchManagedPtr iter
    return location'

-- method TextView::get_justification
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Justification"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_justification" gtk_text_view_get_justification :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CUInt


textViewGetJustification ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Justification
textViewGetJustification _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_justification _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_left_margin
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_left_margin" gtk_text_view_get_left_margin :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO Int32


textViewGetLeftMargin ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Int32
textViewGetLeftMargin _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_left_margin _obj'
    touchManagedPtr _obj
    return result

-- method TextView::get_line_at_y
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "target_iter", argType = TInterface "Gtk" "TextIter", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line_top", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_line_at_y" gtk_text_view_get_line_at_y :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- target_iter : TInterface "Gtk" "TextIter"
    Int32 ->                                -- y : TBasicType TInt32
    Ptr Int32 ->                            -- line_top : TBasicType TInt32
    IO ()


textViewGetLineAtY ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- y
    m (TextIter,Int32)
textViewGetLineAtY _obj y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    target_iter <- callocBoxedBytes 80 :: IO (Ptr TextIter)
    line_top <- allocMem :: IO (Ptr Int32)
    gtk_text_view_get_line_at_y _obj' target_iter y line_top
    target_iter' <- (wrapBoxed TextIter) target_iter
    line_top' <- peek line_top
    touchManagedPtr _obj
    freeMem line_top
    return (target_iter', line_top')

-- method TextView::get_line_yrange
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "height", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_line_yrange" gtk_text_view_get_line_yrange :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    Ptr Int32 ->                            -- y : TBasicType TInt32
    Ptr Int32 ->                            -- height : TBasicType TInt32
    IO ()


textViewGetLineYrange ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    m (Int32,Int32)
textViewGetLineYrange _obj iter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    y <- allocMem :: IO (Ptr Int32)
    height <- allocMem :: IO (Ptr Int32)
    gtk_text_view_get_line_yrange _obj' iter' y height
    y' <- peek y
    height' <- peek height
    touchManagedPtr _obj
    touchManagedPtr iter
    freeMem y
    freeMem height
    return (y', height')

-- method TextView::get_monospace
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_monospace" gtk_text_view_get_monospace :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CInt


textViewGetMonospace ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Bool
textViewGetMonospace _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_monospace _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_overwrite
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_overwrite" gtk_text_view_get_overwrite :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CInt


textViewGetOverwrite ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Bool
textViewGetOverwrite _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_overwrite _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_pixels_above_lines
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_pixels_above_lines" gtk_text_view_get_pixels_above_lines :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO Int32


textViewGetPixelsAboveLines ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Int32
textViewGetPixelsAboveLines _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_pixels_above_lines _obj'
    touchManagedPtr _obj
    return result

-- method TextView::get_pixels_below_lines
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_pixels_below_lines" gtk_text_view_get_pixels_below_lines :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO Int32


textViewGetPixelsBelowLines ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Int32
textViewGetPixelsBelowLines _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_pixels_below_lines _obj'
    touchManagedPtr _obj
    return result

-- method TextView::get_pixels_inside_wrap
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_pixels_inside_wrap" gtk_text_view_get_pixels_inside_wrap :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO Int32


textViewGetPixelsInsideWrap ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Int32
textViewGetPixelsInsideWrap _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_pixels_inside_wrap _obj'
    touchManagedPtr _obj
    return result

-- method TextView::get_right_margin
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_right_margin" gtk_text_view_get_right_margin :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO Int32


textViewGetRightMargin ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Int32
textViewGetRightMargin _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_right_margin _obj'
    touchManagedPtr _obj
    return result

-- method TextView::get_tabs
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Pango" "TabArray"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_tabs" gtk_text_view_get_tabs :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO (Ptr Pango.TabArray)


textViewGetTabs ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Pango.TabArray
textViewGetTabs _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_tabs _obj'
    checkUnexpectedReturnNULL "gtk_text_view_get_tabs" result
    result' <- (wrapBoxed Pango.TabArray) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_vadjustment
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Adjustment"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_vadjustment" gtk_text_view_get_vadjustment :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO (Ptr Adjustment)

{-# DEPRECATED textViewGetVadjustment ["(Since version 3.0)","Use gtk_scrollable_get_vadjustment()"]#-}
textViewGetVadjustment ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Adjustment
textViewGetVadjustment _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_vadjustment _obj'
    checkUnexpectedReturnNULL "gtk_text_view_get_vadjustment" result
    result' <- (newObject Adjustment) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_visible_rect
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "visible_rect", argType = TInterface "cairo" "RectangleInt", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_visible_rect" gtk_text_view_get_visible_rect :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr Cairo.RectangleInt ->               -- visible_rect : TInterface "cairo" "RectangleInt"
    IO ()


textViewGetVisibleRect ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m (Cairo.RectangleInt)
textViewGetVisibleRect _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    visible_rect <- callocBoxedBytes 16 :: IO (Ptr Cairo.RectangleInt)
    gtk_text_view_get_visible_rect _obj' visible_rect
    visible_rect' <- (wrapBoxed Cairo.RectangleInt) visible_rect
    touchManagedPtr _obj
    return visible_rect'

-- method TextView::get_window
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "win", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "win", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gdk" "Window"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_window" gtk_text_view_get_window :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- win : TInterface "Gtk" "TextWindowType"
    IO (Ptr Gdk.Window)


textViewGetWindow ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextWindowType ->                       -- win
    m Gdk.Window
textViewGetWindow _obj win = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let win' = (fromIntegral . fromEnum) win
    result <- gtk_text_view_get_window _obj' win'
    checkUnexpectedReturnNULL "gtk_text_view_get_window" result
    result' <- (newObject Gdk.Window) result
    touchManagedPtr _obj
    return result'

-- method TextView::get_window_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "window", argType = TInterface "Gdk" "Window", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "window", argType = TInterface "Gdk" "Window", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "TextWindowType"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_window_type" gtk_text_view_get_window_type :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr Gdk.Window ->                       -- window : TInterface "Gdk" "Window"
    IO CUInt


textViewGetWindowType ::
    (MonadIO m, TextViewK a, Gdk.WindowK b) =>
    a ->                                    -- _obj
    b ->                                    -- window
    m TextWindowType
textViewGetWindowType _obj window = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let window' = unsafeManagedPtrCastPtr window
    result <- gtk_text_view_get_window_type _obj' window'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    touchManagedPtr window
    return result'

-- method TextView::get_wrap_mode
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "WrapMode"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_get_wrap_mode" gtk_text_view_get_wrap_mode :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CUInt


textViewGetWrapMode ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m WrapMode
textViewGetWrapMode _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_get_wrap_mode _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method TextView::im_context_filter_keypress
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "event", argType = TInterface "Gdk" "EventKey", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "event", argType = TInterface "Gdk" "EventKey", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_im_context_filter_keypress" gtk_text_view_im_context_filter_keypress :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr Gdk.EventKey ->                     -- event : TInterface "Gdk" "EventKey"
    IO CInt


textViewImContextFilterKeypress ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Gdk.EventKey ->                         -- event
    m Bool
textViewImContextFilterKeypress _obj event = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let event' = unsafeManagedPtrGetPtr event
    result <- gtk_text_view_im_context_filter_keypress _obj' event'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr event
    return result'

-- method TextView::move_child
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xpos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ypos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xpos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ypos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_move_child" gtk_text_view_move_child :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    Int32 ->                                -- xpos : TBasicType TInt32
    Int32 ->                                -- ypos : TBasicType TInt32
    IO ()


textViewMoveChild ::
    (MonadIO m, TextViewK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- child
    Int32 ->                                -- xpos
    Int32 ->                                -- ypos
    m ()
textViewMoveChild _obj child xpos ypos = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    gtk_text_view_move_child _obj' child' xpos ypos
    touchManagedPtr _obj
    touchManagedPtr child
    return ()

-- method TextView::move_mark_onscreen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mark", argType = TInterface "Gtk" "TextMark", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mark", argType = TInterface "Gtk" "TextMark", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_move_mark_onscreen" gtk_text_view_move_mark_onscreen :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextMark ->                         -- mark : TInterface "Gtk" "TextMark"
    IO CInt


textViewMoveMarkOnscreen ::
    (MonadIO m, TextViewK a, TextMarkK b) =>
    a ->                                    -- _obj
    b ->                                    -- mark
    m Bool
textViewMoveMarkOnscreen _obj mark = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let mark' = unsafeManagedPtrCastPtr mark
    result <- gtk_text_view_move_mark_onscreen _obj' mark'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr mark
    return result'

-- method TextView::move_visually
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "count", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "count", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_move_visually" gtk_text_view_move_visually :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    Int32 ->                                -- count : TBasicType TInt32
    IO CInt


textViewMoveVisually ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    Int32 ->                                -- count
    m Bool
textViewMoveVisually _obj iter count = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    result <- gtk_text_view_move_visually _obj' iter' count
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr iter
    return result'

-- method TextView::place_cursor_onscreen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_place_cursor_onscreen" gtk_text_view_place_cursor_onscreen :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO CInt


textViewPlaceCursorOnscreen ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m Bool
textViewPlaceCursorOnscreen _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_text_view_place_cursor_onscreen _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method TextView::reset_im_context
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_reset_im_context" gtk_text_view_reset_im_context :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    IO ()


textViewResetImContext ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    m ()
textViewResetImContext _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_text_view_reset_im_context _obj'
    touchManagedPtr _obj
    return ()

-- method TextView::scroll_mark_onscreen
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mark", argType = TInterface "Gtk" "TextMark", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mark", argType = TInterface "Gtk" "TextMark", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_scroll_mark_onscreen" gtk_text_view_scroll_mark_onscreen :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextMark ->                         -- mark : TInterface "Gtk" "TextMark"
    IO ()


textViewScrollMarkOnscreen ::
    (MonadIO m, TextViewK a, TextMarkK b) =>
    a ->                                    -- _obj
    b ->                                    -- mark
    m ()
textViewScrollMarkOnscreen _obj mark = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let mark' = unsafeManagedPtrCastPtr mark
    gtk_text_view_scroll_mark_onscreen _obj' mark'
    touchManagedPtr _obj
    touchManagedPtr mark
    return ()

-- method TextView::scroll_to_iter
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "within_margin", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "use_align", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xalign", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "yalign", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "within_margin", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "use_align", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xalign", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "yalign", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_scroll_to_iter" gtk_text_view_scroll_to_iter :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    CDouble ->                              -- within_margin : TBasicType TDouble
    CInt ->                                 -- use_align : TBasicType TBoolean
    CDouble ->                              -- xalign : TBasicType TDouble
    CDouble ->                              -- yalign : TBasicType TDouble
    IO CInt


textViewScrollToIter ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    Double ->                               -- within_margin
    Bool ->                                 -- use_align
    Double ->                               -- xalign
    Double ->                               -- yalign
    m Bool
textViewScrollToIter _obj iter within_margin use_align xalign yalign = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    let within_margin' = realToFrac within_margin
    let use_align' = (fromIntegral . fromEnum) use_align
    let xalign' = realToFrac xalign
    let yalign' = realToFrac yalign
    result <- gtk_text_view_scroll_to_iter _obj' iter' within_margin' use_align' xalign' yalign'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr iter
    return result'

-- method TextView::scroll_to_mark
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mark", argType = TInterface "Gtk" "TextMark", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "within_margin", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "use_align", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xalign", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "yalign", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mark", argType = TInterface "Gtk" "TextMark", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "within_margin", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "use_align", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xalign", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "yalign", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_scroll_to_mark" gtk_text_view_scroll_to_mark :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextMark ->                         -- mark : TInterface "Gtk" "TextMark"
    CDouble ->                              -- within_margin : TBasicType TDouble
    CInt ->                                 -- use_align : TBasicType TBoolean
    CDouble ->                              -- xalign : TBasicType TDouble
    CDouble ->                              -- yalign : TBasicType TDouble
    IO ()


textViewScrollToMark ::
    (MonadIO m, TextViewK a, TextMarkK b) =>
    a ->                                    -- _obj
    b ->                                    -- mark
    Double ->                               -- within_margin
    Bool ->                                 -- use_align
    Double ->                               -- xalign
    Double ->                               -- yalign
    m ()
textViewScrollToMark _obj mark within_margin use_align xalign yalign = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let mark' = unsafeManagedPtrCastPtr mark
    let within_margin' = realToFrac within_margin
    let use_align' = (fromIntegral . fromEnum) use_align
    let xalign' = realToFrac xalign
    let yalign' = realToFrac yalign
    gtk_text_view_scroll_to_mark _obj' mark' within_margin' use_align' xalign' yalign'
    touchManagedPtr _obj
    touchManagedPtr mark
    return ()

-- method TextView::set_accepts_tab
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accepts_tab", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accepts_tab", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_accepts_tab" gtk_text_view_set_accepts_tab :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CInt ->                                 -- accepts_tab : TBasicType TBoolean
    IO ()


textViewSetAcceptsTab ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- accepts_tab
    m ()
textViewSetAcceptsTab _obj accepts_tab = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let accepts_tab' = (fromIntegral . fromEnum) accepts_tab
    gtk_text_view_set_accepts_tab _obj' accepts_tab'
    touchManagedPtr _obj
    return ()

-- method TextView::set_border_window_size
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "size", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "size", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_border_window_size" gtk_text_view_set_border_window_size :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- type : TInterface "Gtk" "TextWindowType"
    Int32 ->                                -- size : TBasicType TInt32
    IO ()


textViewSetBorderWindowSize ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextWindowType ->                       -- type
    Int32 ->                                -- size
    m ()
textViewSetBorderWindowSize _obj type_ size = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let type_' = (fromIntegral . fromEnum) type_
    gtk_text_view_set_border_window_size _obj' type_' size
    touchManagedPtr _obj
    return ()

-- method TextView::set_buffer
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TInterface "Gtk" "TextBuffer", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TInterface "Gtk" "TextBuffer", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_buffer" gtk_text_view_set_buffer :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextBuffer ->                       -- buffer : TInterface "Gtk" "TextBuffer"
    IO ()


textViewSetBuffer ::
    (MonadIO m, TextViewK a, TextBufferK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- buffer
    m ()
textViewSetBuffer _obj buffer = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeBuffer <- case buffer of
        Nothing -> return nullPtr
        Just jBuffer -> do
            let jBuffer' = unsafeManagedPtrCastPtr jBuffer
            return jBuffer'
    gtk_text_view_set_buffer _obj' maybeBuffer
    touchManagedPtr _obj
    whenJust buffer touchManagedPtr
    return ()

-- method TextView::set_cursor_visible
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "setting", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "setting", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_cursor_visible" gtk_text_view_set_cursor_visible :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CInt ->                                 -- setting : TBasicType TBoolean
    IO ()


textViewSetCursorVisible ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- setting
    m ()
textViewSetCursorVisible _obj setting = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let setting' = (fromIntegral . fromEnum) setting
    gtk_text_view_set_cursor_visible _obj' setting'
    touchManagedPtr _obj
    return ()

-- method TextView::set_editable
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "setting", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "setting", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_editable" gtk_text_view_set_editable :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CInt ->                                 -- setting : TBasicType TBoolean
    IO ()


textViewSetEditable ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- setting
    m ()
textViewSetEditable _obj setting = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let setting' = (fromIntegral . fromEnum) setting
    gtk_text_view_set_editable _obj' setting'
    touchManagedPtr _obj
    return ()

-- method TextView::set_indent
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "indent", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "indent", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_indent" gtk_text_view_set_indent :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Int32 ->                                -- indent : TBasicType TInt32
    IO ()


textViewSetIndent ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- indent
    m ()
textViewSetIndent _obj indent = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_text_view_set_indent _obj' indent
    touchManagedPtr _obj
    return ()

-- method TextView::set_input_hints
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hints", argType = TInterface "Gtk" "InputHints", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hints", argType = TInterface "Gtk" "InputHints", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_input_hints" gtk_text_view_set_input_hints :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- hints : TInterface "Gtk" "InputHints"
    IO ()


textViewSetInputHints ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    [InputHints] ->                         -- hints
    m ()
textViewSetInputHints _obj hints = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let hints' = gflagsToWord hints
    gtk_text_view_set_input_hints _obj' hints'
    touchManagedPtr _obj
    return ()

-- method TextView::set_input_purpose
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "purpose", argType = TInterface "Gtk" "InputPurpose", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "purpose", argType = TInterface "Gtk" "InputPurpose", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_input_purpose" gtk_text_view_set_input_purpose :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- purpose : TInterface "Gtk" "InputPurpose"
    IO ()


textViewSetInputPurpose ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    InputPurpose ->                         -- purpose
    m ()
textViewSetInputPurpose _obj purpose = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let purpose' = (fromIntegral . fromEnum) purpose
    gtk_text_view_set_input_purpose _obj' purpose'
    touchManagedPtr _obj
    return ()

-- method TextView::set_justification
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "justification", argType = TInterface "Gtk" "Justification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "justification", argType = TInterface "Gtk" "Justification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_justification" gtk_text_view_set_justification :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- justification : TInterface "Gtk" "Justification"
    IO ()


textViewSetJustification ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Justification ->                        -- justification
    m ()
textViewSetJustification _obj justification = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let justification' = (fromIntegral . fromEnum) justification
    gtk_text_view_set_justification _obj' justification'
    touchManagedPtr _obj
    return ()

-- method TextView::set_left_margin
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "left_margin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "left_margin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_left_margin" gtk_text_view_set_left_margin :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Int32 ->                                -- left_margin : TBasicType TInt32
    IO ()


textViewSetLeftMargin ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- left_margin
    m ()
textViewSetLeftMargin _obj left_margin = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_text_view_set_left_margin _obj' left_margin
    touchManagedPtr _obj
    return ()

-- method TextView::set_monospace
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "monospace", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "monospace", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_monospace" gtk_text_view_set_monospace :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CInt ->                                 -- monospace : TBasicType TBoolean
    IO ()


textViewSetMonospace ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- monospace
    m ()
textViewSetMonospace _obj monospace = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let monospace' = (fromIntegral . fromEnum) monospace
    gtk_text_view_set_monospace _obj' monospace'
    touchManagedPtr _obj
    return ()

-- method TextView::set_overwrite
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "overwrite", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "overwrite", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_overwrite" gtk_text_view_set_overwrite :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CInt ->                                 -- overwrite : TBasicType TBoolean
    IO ()


textViewSetOverwrite ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- overwrite
    m ()
textViewSetOverwrite _obj overwrite = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let overwrite' = (fromIntegral . fromEnum) overwrite
    gtk_text_view_set_overwrite _obj' overwrite'
    touchManagedPtr _obj
    return ()

-- method TextView::set_pixels_above_lines
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pixels_above_lines", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pixels_above_lines", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_pixels_above_lines" gtk_text_view_set_pixels_above_lines :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Int32 ->                                -- pixels_above_lines : TBasicType TInt32
    IO ()


textViewSetPixelsAboveLines ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- pixels_above_lines
    m ()
textViewSetPixelsAboveLines _obj pixels_above_lines = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_text_view_set_pixels_above_lines _obj' pixels_above_lines
    touchManagedPtr _obj
    return ()

-- method TextView::set_pixels_below_lines
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pixels_below_lines", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pixels_below_lines", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_pixels_below_lines" gtk_text_view_set_pixels_below_lines :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Int32 ->                                -- pixels_below_lines : TBasicType TInt32
    IO ()


textViewSetPixelsBelowLines ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- pixels_below_lines
    m ()
textViewSetPixelsBelowLines _obj pixels_below_lines = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_text_view_set_pixels_below_lines _obj' pixels_below_lines
    touchManagedPtr _obj
    return ()

-- method TextView::set_pixels_inside_wrap
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pixels_inside_wrap", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pixels_inside_wrap", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_pixels_inside_wrap" gtk_text_view_set_pixels_inside_wrap :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Int32 ->                                -- pixels_inside_wrap : TBasicType TInt32
    IO ()


textViewSetPixelsInsideWrap ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- pixels_inside_wrap
    m ()
textViewSetPixelsInsideWrap _obj pixels_inside_wrap = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_text_view_set_pixels_inside_wrap _obj' pixels_inside_wrap
    touchManagedPtr _obj
    return ()

-- method TextView::set_right_margin
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "right_margin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "right_margin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_right_margin" gtk_text_view_set_right_margin :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Int32 ->                                -- right_margin : TBasicType TInt32
    IO ()


textViewSetRightMargin ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- right_margin
    m ()
textViewSetRightMargin _obj right_margin = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_text_view_set_right_margin _obj' right_margin
    touchManagedPtr _obj
    return ()

-- method TextView::set_tabs
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tabs", argType = TInterface "Pango" "TabArray", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tabs", argType = TInterface "Pango" "TabArray", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_tabs" gtk_text_view_set_tabs :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr Pango.TabArray ->                   -- tabs : TInterface "Pango" "TabArray"
    IO ()


textViewSetTabs ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    Pango.TabArray ->                       -- tabs
    m ()
textViewSetTabs _obj tabs = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let tabs' = unsafeManagedPtrGetPtr tabs
    gtk_text_view_set_tabs _obj' tabs'
    touchManagedPtr _obj
    touchManagedPtr tabs
    return ()

-- method TextView::set_wrap_mode
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "wrap_mode", argType = TInterface "Gtk" "WrapMode", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "wrap_mode", argType = TInterface "Gtk" "WrapMode", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_set_wrap_mode" gtk_text_view_set_wrap_mode :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- wrap_mode : TInterface "Gtk" "WrapMode"
    IO ()


textViewSetWrapMode ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    WrapMode ->                             -- wrap_mode
    m ()
textViewSetWrapMode _obj wrap_mode = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let wrap_mode' = (fromIntegral . fromEnum) wrap_mode
    gtk_text_view_set_wrap_mode _obj' wrap_mode'
    touchManagedPtr _obj
    return ()

-- method TextView::starts_display_line
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TextIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_starts_display_line" gtk_text_view_starts_display_line :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    Ptr TextIter ->                         -- iter : TInterface "Gtk" "TextIter"
    IO CInt


textViewStartsDisplayLine ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextIter ->                             -- iter
    m Bool
textViewStartsDisplayLine _obj iter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let iter' = unsafeManagedPtrGetPtr iter
    result <- gtk_text_view_starts_display_line _obj' iter'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr iter
    return result'

-- method TextView::window_to_buffer_coords
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "win", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "window_x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "window_y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer_x", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "buffer_y", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TextView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "win", argType = TInterface "Gtk" "TextWindowType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "window_x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "window_y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_view_window_to_buffer_coords" gtk_text_view_window_to_buffer_coords :: 
    Ptr TextView ->                         -- _obj : TInterface "Gtk" "TextView"
    CUInt ->                                -- win : TInterface "Gtk" "TextWindowType"
    Int32 ->                                -- window_x : TBasicType TInt32
    Int32 ->                                -- window_y : TBasicType TInt32
    Ptr Int32 ->                            -- buffer_x : TBasicType TInt32
    Ptr Int32 ->                            -- buffer_y : TBasicType TInt32
    IO ()


textViewWindowToBufferCoords ::
    (MonadIO m, TextViewK a) =>
    a ->                                    -- _obj
    TextWindowType ->                       -- win
    Int32 ->                                -- window_x
    Int32 ->                                -- window_y
    m (Int32,Int32)
textViewWindowToBufferCoords _obj win window_x window_y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let win' = (fromIntegral . fromEnum) win
    buffer_x <- allocMem :: IO (Ptr Int32)
    buffer_y <- allocMem :: IO (Ptr Int32)
    gtk_text_view_window_to_buffer_coords _obj' win' window_x window_y buffer_x buffer_y
    buffer_x' <- peek buffer_x
    buffer_y' <- peek buffer_y
    touchManagedPtr _obj
    freeMem buffer_x
    freeMem buffer_y
    return (buffer_x', buffer_y')