module Graphics.UI.Gtk.Multiline.TextView (
TextView,
TextViewClass,
TextChildAnchor,
TextChildAnchorClass,
castToTextView, gTypeTextView,
toTextView,
DeleteType(..),
DirectionType(..),
Justification(..),
MovementStep(..),
TextWindowType(..),
WrapMode(..),
textViewNew,
textViewNewWithBuffer,
textViewSetBuffer,
textViewGetBuffer,
textViewScrollToMark,
textViewScrollToIter,
textViewScrollMarkOnscreen,
textViewMoveMarkOnscreen,
textViewPlaceCursorOnscreen,
textViewGetLineAtY,
textViewGetLineYrange,
textViewGetIterAtLocation,
textViewBufferToWindowCoords,
textViewWindowToBufferCoords,
textViewGetWindow,
textViewGetWindowType,
textViewSetBorderWindowSize,
textViewGetBorderWindowSize,
textViewForwardDisplayLine,
textViewBackwardDisplayLine,
textViewForwardDisplayLineEnd,
textViewBackwardDisplayLineStart,
textViewStartsDisplayLine,
textViewMoveVisually,
textViewAddChildAtAnchor,
textChildAnchorNew,
textChildAnchorGetWidgets,
textChildAnchorGetDeleted,
textViewAddChildInWindow,
textViewMoveChild,
textViewSetWrapMode,
textViewGetWrapMode,
textViewSetEditable,
textViewGetEditable,
textViewSetCursorVisible,
textViewGetCursorVisible,
textViewSetPixelsAboveLines,
textViewGetPixelsAboveLines,
textViewSetPixelsBelowLines,
textViewGetPixelsBelowLines,
textViewSetPixelsInsideWrap,
textViewGetPixelsInsideWrap,
textViewSetJustification,
textViewGetJustification,
textViewSetLeftMargin,
textViewGetLeftMargin,
textViewSetRightMargin,
textViewGetRightMargin,
textViewSetIndent,
textViewGetIndent,
textViewGetDefaultAttributes,
textViewGetVisibleRect,
textViewGetIterLocation,
textViewGetIterAtPosition,
textViewSetOverwrite,
textViewGetOverwrite,
textViewSetAcceptsTab,
textViewGetAcceptsTab,
textViewGetHadjustment,
textViewGetVadjustment,
textViewImContextFilterKeypress,
textViewResetImContext,
textViewPixelsAboveLines,
textViewPixelsBelowLines,
textViewPixelsInsideWrap,
textViewEditable,
textViewImModule,
textViewWrapMode,
textViewJustification,
textViewLeftMargin,
textViewRightMargin,
textViewIndent,
textViewCursorVisible,
textViewBuffer,
textViewOverwrite,
textViewAcceptsTab,
backspace,
copyClipboard,
cutClipboard,
deleteFromCursor,
insertAtCursor,
moveCursor,
moveViewport,
moveFocus,
pageHorizontally,
pasteClipboard,
populatePopup,
selectAll,
setAnchor,
setTextViewScrollAdjustments,
toggleCursorVisible,
toggleOverwrite,
textViewPreeditChanged
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.Attributes
import System.Glib.Properties (newAttrFromStringProperty)
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import System.Glib.GObject (wrapNewGObject, makeNewGObject)
import Graphics.UI.Gtk.Gdk.EventM (EventM, EKey)
import Control.Monad.Reader ( ask )
import Control.Monad.Trans ( liftIO )
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
import Graphics.UI.Gtk.Multiline.Types
import Graphics.UI.Gtk.Multiline.TextIter
import Graphics.UI.Gtk.Multiline.TextTag
import Graphics.UI.Gtk.General.Enums (TextWindowType(..), DeleteType(..),
DirectionType(..), Justification(..),
MovementStep(..), WrapMode(..),
ScrollStep (..))
import System.Glib.GList (fromGList)
import Graphics.UI.Gtk.General.Structs (Rectangle(..))
textViewNew :: IO TextView
textViewNew =
makeNewObject mkTextView $
liftM (castPtr :: Ptr Widget -> Ptr TextView) $
gtk_text_view_new
textViewNewWithBuffer :: TextBufferClass buffer => buffer -> IO TextView
textViewNewWithBuffer buffer =
makeNewObject mkTextView $
liftM (castPtr :: Ptr Widget -> Ptr TextView) $
(\(TextBuffer arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_new_with_buffer argPtr1)
(toTextBuffer buffer)
textViewSetBuffer :: (TextViewClass self, TextBufferClass buffer) => self -> buffer -> IO ()
textViewSetBuffer self buffer =
(\(TextView arg1) (TextBuffer arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_set_buffer argPtr1 argPtr2)
(toTextView self)
(toTextBuffer buffer)
textViewGetBuffer :: TextViewClass self => self -> IO TextBuffer
textViewGetBuffer self =
makeNewGObject mkTextBuffer $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_buffer argPtr1)
(toTextView self)
textViewScrollToMark :: (TextViewClass self, TextMarkClass mark) => self
-> mark
-> Double
-> Maybe (Double, Double)
-> IO ()
textViewScrollToMark self mark withinMargin align =
let (useAlign, xalign, yalign) = case align of
Nothing -> (False, 0, 0)
Just (xalign, yalign) -> (True, xalign, yalign)
in
(\(TextView arg1) (TextMark arg2) arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_scroll_to_mark argPtr1 argPtr2 arg3 arg4 arg5 arg6)
(toTextView self)
(toTextMark mark)
(realToFrac withinMargin)
(fromBool useAlign)
(realToFrac xalign)
(realToFrac yalign)
textViewScrollToIter :: TextViewClass self => self
-> TextIter
-> Double
-> Maybe (Double, Double)
-> IO Bool
textViewScrollToIter self iter withinMargin align =
let (useAlign, xalign, yalign) = case align of
Nothing -> (False, 0, 0)
Just (xalign, yalign) -> (True, xalign, yalign)
in
liftM toBool $
(\(TextView arg1) (TextIter arg2) arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_scroll_to_iter argPtr1 argPtr2 arg3 arg4 arg5 arg6)
(toTextView self)
iter
(realToFrac withinMargin)
(fromBool useAlign)
(realToFrac xalign)
(realToFrac yalign)
textViewScrollMarkOnscreen :: (TextViewClass self, TextMarkClass mark) => self
-> mark
-> IO ()
textViewScrollMarkOnscreen self mark =
(\(TextView arg1) (TextMark arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_scroll_mark_onscreen argPtr1 argPtr2)
(toTextView self)
(toTextMark mark)
textViewMoveMarkOnscreen :: (TextViewClass self, TextMarkClass mark) => self
-> mark
-> IO Bool
textViewMoveMarkOnscreen self mark =
liftM toBool $
(\(TextView arg1) (TextMark arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_move_mark_onscreen argPtr1 argPtr2)
(toTextView self)
(toTextMark mark)
textViewPlaceCursorOnscreen :: TextViewClass self => self
-> IO Bool
textViewPlaceCursorOnscreen self =
liftM toBool $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_place_cursor_onscreen argPtr1)
(toTextView self)
textViewGetVisibleRect :: TextViewClass self => self -> IO Rectangle
textViewGetVisibleRect self =
alloca $ \rectPtr -> do
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_visible_rect argPtr1 arg2)
(toTextView self)
(castPtr rectPtr)
peek rectPtr
textViewGetIterLocation :: TextViewClass self => self -> TextIter -> IO Rectangle
textViewGetIterLocation self iter =
alloca $ \rectPtr -> do
(\(TextView arg1) (TextIter arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_get_iter_location argPtr1 argPtr2 arg3)
(toTextView self)
iter
(castPtr rectPtr)
peek rectPtr
textViewGetLineAtY :: TextViewClass self => self
-> Int
-> IO (TextIter, Int)
textViewGetLineAtY self y =
makeEmptyTextIter >>= \targetIter ->
alloca $ \lineTopPtr -> do
(\(TextView arg1) (TextIter arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_get_line_at_y argPtr1 argPtr2 arg3 arg4)
(toTextView self)
targetIter
(fromIntegral y)
lineTopPtr
lineTop <- peek lineTopPtr
return (targetIter, fromIntegral lineTop)
textViewGetLineYrange :: TextViewClass self => self
-> TextIter
-> IO (Int, Int)
textViewGetLineYrange self iter =
alloca $ \yPtr ->
alloca $ \heightPtr -> do
(\(TextView arg1) (TextIter arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_get_line_yrange argPtr1 argPtr2 arg3 arg4)
(toTextView self)
iter
yPtr
heightPtr
y <- peek yPtr
height <- peek heightPtr
return (fromIntegral y, fromIntegral height)
textViewGetIterAtLocation :: TextViewClass self => self
-> Int
-> Int
-> IO TextIter
textViewGetIterAtLocation self x y = do
iter <- makeEmptyTextIter
(\(TextView arg1) (TextIter arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_get_iter_at_location argPtr1 argPtr2 arg3 arg4)
(toTextView self)
iter
(fromIntegral x)
(fromIntegral y)
return iter
textViewBufferToWindowCoords :: TextViewClass self => self
-> TextWindowType
-> (Int, Int)
-> IO (Int, Int)
textViewBufferToWindowCoords self win (bufferX, bufferY) =
alloca $ \windowXPtr ->
alloca $ \windowYPtr -> do
(\(TextView arg1) arg2 arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_buffer_to_window_coords argPtr1 arg2 arg3 arg4 arg5 arg6)
(toTextView self)
((fromIntegral . fromEnum) win)
(fromIntegral bufferX)
(fromIntegral bufferY)
windowXPtr
windowYPtr
windowX <- peek windowXPtr
windowY <- peek windowYPtr
return (fromIntegral windowX, fromIntegral windowY)
textViewWindowToBufferCoords :: TextViewClass self => self
-> TextWindowType
-> (Int, Int)
-> IO (Int, Int)
textViewWindowToBufferCoords self win (windowX, windowY) =
alloca $ \bufferXPtr ->
alloca $ \bufferYPtr -> do
(\(TextView arg1) arg2 arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_window_to_buffer_coords argPtr1 arg2 arg3 arg4 arg5 arg6)
(toTextView self)
((fromIntegral . fromEnum) win)
(fromIntegral windowX)
(fromIntegral windowY)
bufferXPtr
bufferYPtr
bufferX <- peek bufferXPtr
bufferY <- peek bufferYPtr
return (fromIntegral bufferX, fromIntegral bufferY)
textViewGetWindow :: TextViewClass self => self
-> TextWindowType
-> IO (Maybe DrawWindow)
textViewGetWindow self win =
maybeNull (makeNewGObject mkDrawWindow) $
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_window argPtr1 arg2)
(toTextView self)
((fromIntegral . fromEnum) win)
textViewGetWindowType :: TextViewClass self => self
-> DrawWindow
-> IO TextWindowType
textViewGetWindowType self window =
liftM (toEnum . fromIntegral) $
(\(TextView arg1) (DrawWindow arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_get_window_type argPtr1 argPtr2)
(toTextView self)
window
textViewSetBorderWindowSize :: TextViewClass self => self
-> TextWindowType
-> Int
-> IO ()
textViewSetBorderWindowSize self type_ size =
(\(TextView arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_border_window_size argPtr1 arg2 arg3)
(toTextView self)
((fromIntegral . fromEnum) type_)
(fromIntegral size)
textViewGetBorderWindowSize :: TextViewClass self => self
-> TextWindowType
-> IO Int
textViewGetBorderWindowSize self type_ =
liftM fromIntegral $
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_border_window_size argPtr1 arg2)
(toTextView self)
((fromIntegral . fromEnum) type_)
textViewForwardDisplayLine :: TextViewClass self => self
-> TextIter
-> IO Bool
textViewForwardDisplayLine self iter =
liftM toBool $
(\(TextView arg1) (TextIter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_forward_display_line argPtr1 argPtr2)
(toTextView self)
iter
textViewBackwardDisplayLine :: TextViewClass self => self
-> TextIter
-> IO Bool
textViewBackwardDisplayLine self iter =
liftM toBool $
(\(TextView arg1) (TextIter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_backward_display_line argPtr1 argPtr2)
(toTextView self)
iter
textViewForwardDisplayLineEnd :: TextViewClass self => self
-> TextIter
-> IO Bool
textViewForwardDisplayLineEnd self iter =
liftM toBool $
(\(TextView arg1) (TextIter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_forward_display_line_end argPtr1 argPtr2)
(toTextView self)
iter
textViewBackwardDisplayLineStart :: TextViewClass self => self
-> TextIter
-> IO Bool
textViewBackwardDisplayLineStart self iter =
liftM toBool $
(\(TextView arg1) (TextIter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_backward_display_line_start argPtr1 argPtr2)
(toTextView self)
iter
textViewStartsDisplayLine :: TextViewClass self => self
-> TextIter
-> IO Bool
textViewStartsDisplayLine self iter =
liftM toBool $
(\(TextView arg1) (TextIter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_starts_display_line argPtr1 argPtr2)
(toTextView self)
iter
textViewMoveVisually :: TextViewClass self => self
-> TextIter
-> Int
-> IO Bool
textViewMoveVisually self iter count =
liftM toBool $
(\(TextView arg1) (TextIter arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_move_visually argPtr1 argPtr2 arg3)
(toTextView self)
iter
(fromIntegral count)
textViewAddChildAtAnchor :: (TextViewClass self, WidgetClass child) => self
-> child
-> TextChildAnchor
-> IO ()
textViewAddChildAtAnchor self child anchor =
(\(TextView arg1) (Widget arg2) (TextChildAnchor arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->gtk_text_view_add_child_at_anchor argPtr1 argPtr2 argPtr3)
(toTextView self)
(toWidget child)
anchor
textChildAnchorNew :: IO TextChildAnchor
textChildAnchorNew =
wrapNewGObject mkTextChildAnchor
gtk_text_child_anchor_new
textChildAnchorGetWidgets :: TextChildAnchor -> IO [Widget]
textChildAnchorGetWidgets tca = do
gList <- (\(TextChildAnchor arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_child_anchor_get_widgets argPtr1) tca
wList <- fromGList gList
mapM (makeNewObject mkWidget) (map return wList)
textChildAnchorGetDeleted :: TextChildAnchor -> IO Bool
textChildAnchorGetDeleted tca =
liftM toBool $
(\(TextChildAnchor arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_child_anchor_get_deleted argPtr1) tca
textViewAddChildInWindow :: (TextViewClass self, WidgetClass child) => self
-> child
-> TextWindowType
-> Int
-> Int
-> IO ()
textViewAddChildInWindow self child whichWindow xpos ypos =
(\(TextView arg1) (Widget arg2) arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_add_child_in_window argPtr1 argPtr2 arg3 arg4 arg5)
(toTextView self)
(toWidget child)
((fromIntegral . fromEnum) whichWindow)
(fromIntegral xpos)
(fromIntegral ypos)
textViewMoveChild :: (TextViewClass self, WidgetClass child) => self
-> child
-> Int
-> Int
-> IO ()
textViewMoveChild self child xpos ypos =
(\(TextView arg1) (Widget arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_move_child argPtr1 argPtr2 arg3 arg4)
(toTextView self)
(toWidget child)
(fromIntegral xpos)
(fromIntegral ypos)
textViewSetWrapMode :: TextViewClass self => self -> WrapMode -> IO ()
textViewSetWrapMode self wrapMode =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_wrap_mode argPtr1 arg2)
(toTextView self)
((fromIntegral . fromEnum) wrapMode)
textViewGetWrapMode :: TextViewClass self => self -> IO WrapMode
textViewGetWrapMode self =
liftM (toEnum . fromIntegral) $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_wrap_mode argPtr1)
(toTextView self)
textViewSetEditable :: TextViewClass self => self -> Bool -> IO ()
textViewSetEditable self setting =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_editable argPtr1 arg2)
(toTextView self)
(fromBool setting)
textViewGetEditable :: TextViewClass self => self -> IO Bool
textViewGetEditable self =
liftM toBool $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_editable argPtr1)
(toTextView self)
textViewSetCursorVisible :: TextViewClass self => self -> Bool -> IO ()
textViewSetCursorVisible self setting =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_cursor_visible argPtr1 arg2)
(toTextView self)
(fromBool setting)
textViewGetCursorVisible :: TextViewClass self => self -> IO Bool
textViewGetCursorVisible self =
liftM toBool $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_cursor_visible argPtr1)
(toTextView self)
textViewSetPixelsAboveLines :: TextViewClass self => self -> Int -> IO ()
textViewSetPixelsAboveLines self pixelsAboveLines =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_pixels_above_lines argPtr1 arg2)
(toTextView self)
(fromIntegral pixelsAboveLines)
textViewGetPixelsAboveLines :: TextViewClass self => self -> IO Int
textViewGetPixelsAboveLines self =
liftM fromIntegral $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_pixels_above_lines argPtr1)
(toTextView self)
textViewSetPixelsBelowLines :: TextViewClass self => self -> Int -> IO ()
textViewSetPixelsBelowLines self pixelsBelowLines =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_pixels_below_lines argPtr1 arg2)
(toTextView self)
(fromIntegral pixelsBelowLines)
textViewGetPixelsBelowLines :: TextViewClass self => self -> IO Int
textViewGetPixelsBelowLines self =
liftM fromIntegral $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_pixels_below_lines argPtr1)
(toTextView self)
textViewSetPixelsInsideWrap :: TextViewClass self => self -> Int -> IO ()
textViewSetPixelsInsideWrap self pixelsInsideWrap =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_pixels_inside_wrap argPtr1 arg2)
(toTextView self)
(fromIntegral pixelsInsideWrap)
textViewGetPixelsInsideWrap :: TextViewClass self => self -> IO Int
textViewGetPixelsInsideWrap self =
liftM fromIntegral $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_pixels_inside_wrap argPtr1)
(toTextView self)
textViewSetJustification :: TextViewClass self => self -> Justification -> IO ()
textViewSetJustification self justification =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_justification argPtr1 arg2)
(toTextView self)
((fromIntegral . fromEnum) justification)
textViewGetJustification :: TextViewClass self => self -> IO Justification
textViewGetJustification self =
liftM (toEnum . fromIntegral) $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_justification argPtr1)
(toTextView self)
textViewSetLeftMargin :: TextViewClass self => self
-> Int
-> IO ()
textViewSetLeftMargin self leftMargin =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_left_margin argPtr1 arg2)
(toTextView self)
(fromIntegral leftMargin)
textViewGetLeftMargin :: TextViewClass self => self
-> IO Int
textViewGetLeftMargin self =
liftM fromIntegral $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_left_margin argPtr1)
(toTextView self)
textViewSetRightMargin :: TextViewClass self => self
-> Int
-> IO ()
textViewSetRightMargin self rightMargin =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_right_margin argPtr1 arg2)
(toTextView self)
(fromIntegral rightMargin)
textViewGetRightMargin :: TextViewClass self => self
-> IO Int
textViewGetRightMargin self =
liftM fromIntegral $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_right_margin argPtr1)
(toTextView self)
textViewSetIndent :: TextViewClass self => self
-> Int
-> IO ()
textViewSetIndent self indent =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_indent argPtr1 arg2)
(toTextView self)
(fromIntegral indent)
textViewGetIndent :: TextViewClass self => self
-> IO Int
textViewGetIndent self =
liftM fromIntegral $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_indent argPtr1)
(toTextView self)
textViewGetDefaultAttributes :: TextViewClass self => self -> IO TextAttributes
textViewGetDefaultAttributes self =
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_default_attributes argPtr1)
(toTextView self)
>>= makeNewTextAttributes
textViewGetIterAtPosition :: TextViewClass self => self
-> Int
-> Int
-> IO (TextIter, Int)
textViewGetIterAtPosition self x y =
alloca $ \trailingPtr -> do
iter <- makeEmptyTextIter
(\(TextView arg1) (TextIter arg2) arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_view_get_iter_at_position argPtr1 argPtr2 arg3 arg4 arg5)
(toTextView self)
iter
trailingPtr
(fromIntegral x)
(fromIntegral y)
trailing <- peek trailingPtr
return (iter, fromIntegral trailing)
textViewSetOverwrite :: TextViewClass self => self
-> Bool
-> IO ()
textViewSetOverwrite self overwrite =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_overwrite argPtr1 arg2)
(toTextView self)
(fromBool overwrite)
textViewGetOverwrite :: TextViewClass self => self -> IO Bool
textViewGetOverwrite self =
liftM toBool $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_overwrite argPtr1)
(toTextView self)
textViewSetAcceptsTab :: TextViewClass self => self
-> Bool
-> IO ()
textViewSetAcceptsTab self acceptsTab =
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_set_accepts_tab argPtr1 arg2)
(toTextView self)
(fromBool acceptsTab)
textViewGetAcceptsTab :: TextViewClass self => self
-> IO Bool
textViewGetAcceptsTab self =
liftM toBool $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_accepts_tab argPtr1)
(toTextView self)
textViewGetHadjustment :: TextViewClass self => self -> IO Adjustment
textViewGetHadjustment self =
makeNewObject mkAdjustment $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_hadjustment argPtr1)
(toTextView self)
textViewGetVadjustment :: TextViewClass self => self -> IO Adjustment
textViewGetVadjustment self =
makeNewObject mkAdjustment $
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_get_vadjustment argPtr1)
(toTextView self)
textViewImContextFilterKeypress :: TextViewClass self => self -> EventM EKey Bool
textViewImContextFilterKeypress self = do
ptr <- ask
liftIO $ liftM toBool $
(\(TextView arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_im_context_filter_keypress argPtr1 arg2)
(toTextView self)
(castPtr ptr)
textViewResetImContext :: TextViewClass self => self -> IO ()
textViewResetImContext self =
(\(TextView arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_view_reset_im_context argPtr1) (toTextView self)
textViewPixelsAboveLines :: TextViewClass self => Attr self Int
textViewPixelsAboveLines = newAttr
textViewGetPixelsAboveLines
textViewSetPixelsAboveLines
textViewPixelsBelowLines :: TextViewClass self => Attr self Int
textViewPixelsBelowLines = newAttr
textViewGetPixelsBelowLines
textViewSetPixelsBelowLines
textViewPixelsInsideWrap :: TextViewClass self => Attr self Int
textViewPixelsInsideWrap = newAttr
textViewGetPixelsInsideWrap
textViewSetPixelsInsideWrap
textViewEditable :: TextViewClass self => Attr self Bool
textViewEditable = newAttr
textViewGetEditable
textViewSetEditable
textViewImModule :: TextViewClass self => Attr self String
textViewImModule =
newAttrFromStringProperty "im-module"
textViewWrapMode :: TextViewClass self => Attr self WrapMode
textViewWrapMode = newAttr
textViewGetWrapMode
textViewSetWrapMode
textViewJustification :: TextViewClass self => Attr self Justification
textViewJustification = newAttr
textViewGetJustification
textViewSetJustification
textViewLeftMargin :: TextViewClass self => Attr self Int
textViewLeftMargin = newAttr
textViewGetLeftMargin
textViewSetLeftMargin
textViewRightMargin :: TextViewClass self => Attr self Int
textViewRightMargin = newAttr
textViewGetRightMargin
textViewSetRightMargin
textViewIndent :: TextViewClass self => Attr self Int
textViewIndent = newAttr
textViewGetIndent
textViewSetIndent
textViewCursorVisible :: TextViewClass self => Attr self Bool
textViewCursorVisible = newAttr
textViewGetCursorVisible
textViewSetCursorVisible
textViewBuffer :: TextViewClass self => Attr self TextBuffer
textViewBuffer = newAttr
textViewGetBuffer
textViewSetBuffer
textViewOverwrite :: TextViewClass self => Attr self Bool
textViewOverwrite = newAttr
textViewGetOverwrite
textViewSetOverwrite
textViewAcceptsTab :: TextViewClass self => Attr self Bool
textViewAcceptsTab = newAttr
textViewGetAcceptsTab
textViewSetAcceptsTab
backspace :: TextViewClass self => Signal self (IO ())
backspace = Signal (connect_NONE__NONE "on-backspace")
copyClipboard :: TextViewClass self => Signal self (IO ())
copyClipboard = Signal (connect_NONE__NONE "copy-clipboard")
cutClipboard :: TextViewClass self => Signal self (IO ())
cutClipboard = Signal (connect_NONE__NONE "cut-clipboard")
deleteFromCursor :: TextViewClass self => Signal self (DeleteType -> Int -> IO ())
deleteFromCursor = Signal (connect_ENUM_INT__NONE "delete-from-cursor")
insertAtCursor :: TextViewClass self => Signal self (String -> IO ())
insertAtCursor = Signal (connect_STRING__NONE "insert-at-cursor")
moveCursor :: TextViewClass self => Signal self (MovementStep -> Int -> Bool -> IO ())
moveCursor = Signal (connect_ENUM_INT_BOOL__NONE "move-cursor")
moveViewport :: TextViewClass self => Signal self (ScrollStep -> Int -> IO ())
moveViewport = Signal (connect_ENUM_INT__NONE "move-viewport")
moveFocus :: TextViewClass self => Signal self (DirectionType -> IO ())
moveFocus = Signal (connect_ENUM__NONE "move-focus")
pageHorizontally :: TextViewClass self => Signal self (Int -> Bool -> IO ())
pageHorizontally = Signal (connect_INT_BOOL__NONE "page-horizontally")
pasteClipboard :: TextViewClass self => Signal self (IO ())
pasteClipboard = Signal (connect_NONE__NONE "paste-clipboard")
populatePopup :: TextViewClass self => Signal self (Menu -> IO ())
populatePopup = Signal (connect_OBJECT__NONE "populate-popup")
selectAll :: TextViewClass self => Signal self (Bool -> IO ())
selectAll = Signal (connect_BOOL__NONE "select-all")
setAnchor :: TextViewClass self => Signal self (IO ())
setAnchor = Signal (connect_NONE__NONE "set-anchor")
setTextViewScrollAdjustments :: TextViewClass self => Signal self (Adjustment -> Adjustment -> IO ())
setTextViewScrollAdjustments = Signal (connect_OBJECT_OBJECT__NONE "set-scroll-adjustments")
toggleCursorVisible :: TextViewClass self => Signal self (IO ())
toggleCursorVisible = Signal (connect_NONE__NONE "toggle-cursor-visible")
toggleOverwrite :: TextViewClass self => Signal self (IO ())
toggleOverwrite = Signal (connect_NONE__NONE "toggle-overwrite")
textViewPreeditChanged :: TextViewClass self => Signal self (String -> IO ())
textViewPreeditChanged = Signal (connect_STRING__NONE "preedit-changed")
foreign import ccall unsafe "gtk_text_view_new"
gtk_text_view_new :: (IO (Ptr Widget))
foreign import ccall safe "gtk_text_view_new_with_buffer"
gtk_text_view_new_with_buffer :: ((Ptr TextBuffer) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_text_view_set_buffer"
gtk_text_view_set_buffer :: ((Ptr TextView) -> ((Ptr TextBuffer) -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_buffer"
gtk_text_view_get_buffer :: ((Ptr TextView) -> (IO (Ptr TextBuffer)))
foreign import ccall safe "gtk_text_view_scroll_to_mark"
gtk_text_view_scroll_to_mark :: ((Ptr TextView) -> ((Ptr TextMark) -> (CDouble -> (CInt -> (CDouble -> (CDouble -> (IO ())))))))
foreign import ccall safe "gtk_text_view_scroll_to_iter"
gtk_text_view_scroll_to_iter :: ((Ptr TextView) -> ((Ptr TextIter) -> (CDouble -> (CInt -> (CDouble -> (CDouble -> (IO CInt)))))))
foreign import ccall safe "gtk_text_view_scroll_mark_onscreen"
gtk_text_view_scroll_mark_onscreen :: ((Ptr TextView) -> ((Ptr TextMark) -> (IO ())))
foreign import ccall safe "gtk_text_view_move_mark_onscreen"
gtk_text_view_move_mark_onscreen :: ((Ptr TextView) -> ((Ptr TextMark) -> (IO CInt)))
foreign import ccall safe "gtk_text_view_place_cursor_onscreen"
gtk_text_view_place_cursor_onscreen :: ((Ptr TextView) -> (IO CInt))
foreign import ccall unsafe "gtk_text_view_get_visible_rect"
gtk_text_view_get_visible_rect :: ((Ptr TextView) -> ((Ptr ()) -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_iter_location"
gtk_text_view_get_iter_location :: ((Ptr TextView) -> ((Ptr TextIter) -> ((Ptr ()) -> (IO ()))))
foreign import ccall unsafe "gtk_text_view_get_line_at_y"
gtk_text_view_get_line_at_y :: ((Ptr TextView) -> ((Ptr TextIter) -> (CInt -> ((Ptr CInt) -> (IO ())))))
foreign import ccall unsafe "gtk_text_view_get_line_yrange"
gtk_text_view_get_line_yrange :: ((Ptr TextView) -> ((Ptr TextIter) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ())))))
foreign import ccall unsafe "gtk_text_view_get_iter_at_location"
gtk_text_view_get_iter_at_location :: ((Ptr TextView) -> ((Ptr TextIter) -> (CInt -> (CInt -> (IO ())))))
foreign import ccall unsafe "gtk_text_view_buffer_to_window_coords"
gtk_text_view_buffer_to_window_coords :: ((Ptr TextView) -> (CInt -> (CInt -> (CInt -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ())))))))
foreign import ccall unsafe "gtk_text_view_window_to_buffer_coords"
gtk_text_view_window_to_buffer_coords :: ((Ptr TextView) -> (CInt -> (CInt -> (CInt -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ())))))))
foreign import ccall unsafe "gtk_text_view_get_window"
gtk_text_view_get_window :: ((Ptr TextView) -> (CInt -> (IO (Ptr DrawWindow))))
foreign import ccall unsafe "gtk_text_view_get_window_type"
gtk_text_view_get_window_type :: ((Ptr TextView) -> ((Ptr DrawWindow) -> (IO CInt)))
foreign import ccall safe "gtk_text_view_set_border_window_size"
gtk_text_view_set_border_window_size :: ((Ptr TextView) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall unsafe "gtk_text_view_get_border_window_size"
gtk_text_view_get_border_window_size :: ((Ptr TextView) -> (CInt -> (IO CInt)))
foreign import ccall unsafe "gtk_text_view_forward_display_line"
gtk_text_view_forward_display_line :: ((Ptr TextView) -> ((Ptr TextIter) -> (IO CInt)))
foreign import ccall unsafe "gtk_text_view_backward_display_line"
gtk_text_view_backward_display_line :: ((Ptr TextView) -> ((Ptr TextIter) -> (IO CInt)))
foreign import ccall unsafe "gtk_text_view_forward_display_line_end"
gtk_text_view_forward_display_line_end :: ((Ptr TextView) -> ((Ptr TextIter) -> (IO CInt)))
foreign import ccall unsafe "gtk_text_view_backward_display_line_start"
gtk_text_view_backward_display_line_start :: ((Ptr TextView) -> ((Ptr TextIter) -> (IO CInt)))
foreign import ccall unsafe "gtk_text_view_starts_display_line"
gtk_text_view_starts_display_line :: ((Ptr TextView) -> ((Ptr TextIter) -> (IO CInt)))
foreign import ccall unsafe "gtk_text_view_move_visually"
gtk_text_view_move_visually :: ((Ptr TextView) -> ((Ptr TextIter) -> (CInt -> (IO CInt))))
foreign import ccall safe "gtk_text_view_add_child_at_anchor"
gtk_text_view_add_child_at_anchor :: ((Ptr TextView) -> ((Ptr Widget) -> ((Ptr TextChildAnchor) -> (IO ()))))
foreign import ccall unsafe "gtk_text_child_anchor_new"
gtk_text_child_anchor_new :: (IO (Ptr TextChildAnchor))
foreign import ccall safe "gtk_text_child_anchor_get_widgets"
gtk_text_child_anchor_get_widgets :: ((Ptr TextChildAnchor) -> (IO (Ptr ())))
foreign import ccall unsafe "gtk_text_child_anchor_get_deleted"
gtk_text_child_anchor_get_deleted :: ((Ptr TextChildAnchor) -> (IO CInt))
foreign import ccall safe "gtk_text_view_add_child_in_window"
gtk_text_view_add_child_in_window :: ((Ptr TextView) -> ((Ptr Widget) -> (CInt -> (CInt -> (CInt -> (IO ()))))))
foreign import ccall safe "gtk_text_view_move_child"
gtk_text_view_move_child :: ((Ptr TextView) -> ((Ptr Widget) -> (CInt -> (CInt -> (IO ())))))
foreign import ccall safe "gtk_text_view_set_wrap_mode"
gtk_text_view_set_wrap_mode :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_wrap_mode"
gtk_text_view_get_wrap_mode :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_editable"
gtk_text_view_set_editable :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_editable"
gtk_text_view_get_editable :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_cursor_visible"
gtk_text_view_set_cursor_visible :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_cursor_visible"
gtk_text_view_get_cursor_visible :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_pixels_above_lines"
gtk_text_view_set_pixels_above_lines :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_pixels_above_lines"
gtk_text_view_get_pixels_above_lines :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_pixels_below_lines"
gtk_text_view_set_pixels_below_lines :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_pixels_below_lines"
gtk_text_view_get_pixels_below_lines :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_pixels_inside_wrap"
gtk_text_view_set_pixels_inside_wrap :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_pixels_inside_wrap"
gtk_text_view_get_pixels_inside_wrap :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_justification"
gtk_text_view_set_justification :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_justification"
gtk_text_view_get_justification :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_left_margin"
gtk_text_view_set_left_margin :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_left_margin"
gtk_text_view_get_left_margin :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_right_margin"
gtk_text_view_set_right_margin :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_right_margin"
gtk_text_view_get_right_margin :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_indent"
gtk_text_view_set_indent :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_view_get_indent"
gtk_text_view_get_indent :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_get_default_attributes"
gtk_text_view_get_default_attributes :: ((Ptr TextView) -> (IO (Ptr TextAttributes)))
foreign import ccall safe "gtk_text_view_get_iter_at_position"
gtk_text_view_get_iter_at_position :: ((Ptr TextView) -> ((Ptr TextIter) -> ((Ptr CInt) -> (CInt -> (CInt -> (IO ()))))))
foreign import ccall safe "gtk_text_view_set_overwrite"
gtk_text_view_set_overwrite :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_text_view_get_overwrite"
gtk_text_view_get_overwrite :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_set_accepts_tab"
gtk_text_view_set_accepts_tab :: ((Ptr TextView) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_text_view_get_accepts_tab"
gtk_text_view_get_accepts_tab :: ((Ptr TextView) -> (IO CInt))
foreign import ccall safe "gtk_text_view_get_hadjustment"
gtk_text_view_get_hadjustment :: ((Ptr TextView) -> (IO (Ptr Adjustment)))
foreign import ccall safe "gtk_text_view_get_vadjustment"
gtk_text_view_get_vadjustment :: ((Ptr TextView) -> (IO (Ptr Adjustment)))
foreign import ccall safe "gtk_text_view_im_context_filter_keypress"
gtk_text_view_im_context_filter_keypress :: ((Ptr TextView) -> ((Ptr ()) -> (IO CInt)))
foreign import ccall safe "gtk_text_view_reset_im_context"
gtk_text_view_reset_im_context :: ((Ptr TextView) -> (IO ()))