Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria (garetxe@gmail.com) |
Safe Haskell | None |
Language | Haskell2010 |
- Exported types
- Methods
- copyClipboard
- copyClipboardFormat
- copyPrimary
- feed
- feedChild
- feedChildBinary
- getAllowBold
- getAllowHyperlink
- getAudibleBell
- getBoldIsBright
- getCellHeightScale
- getCellWidthScale
- getCharHeight
- getCharWidth
- getCjkAmbiguousWidth
- getColumnCount
- getCurrentDirectoryUri
- getCurrentFileUri
- getCursorBlinkMode
- getCursorPosition
- getCursorShape
- getEncoding
- getFont
- getFontScale
- getGeometryHints
- getHasSelection
- getIconTitle
- getInputEnabled
- getMouseAutohide
- getPty
- getRewrapOnResize
- getRowCount
- getScrollOnKeystroke
- getScrollOnOutput
- getScrollbackLines
- getTextBlinkMode
- getWindowTitle
- getWordCharExceptions
- hyperlinkCheckEvent
- matchAddGregex
- matchAddRegex
- matchCheck
- matchCheckEvent
- matchRemove
- matchRemoveAll
- matchSetCursor
- matchSetCursorName
- matchSetCursorType
- new
- pasteClipboard
- pastePrimary
- ptyNewSync
- reset
- searchFindNext
- searchFindPrevious
- searchGetGregex
- searchGetRegex
- searchGetWrapAround
- searchSetGregex
- searchSetRegex
- searchSetWrapAround
- selectAll
- setAllowBold
- setAllowHyperlink
- setAudibleBell
- setBackspaceBinding
- setBoldIsBright
- setCellHeightScale
- setCellWidthScale
- setCjkAmbiguousWidth
- setClearBackground
- setColorBackground
- setColorBold
- setColorCursor
- setColorCursorForeground
- setColorForeground
- setColorHighlight
- setColorHighlightForeground
- setColors
- setCursorBlinkMode
- setCursorShape
- setDefaultColors
- setDeleteBinding
- setEncoding
- setFont
- setFontScale
- setGeometryHintsForWindow
- setInputEnabled
- setMouseAutohide
- setPty
- setRewrapOnResize
- setScrollOnKeystroke
- setScrollOnOutput
- setScrollSpeed
- setScrollbackLines
- setSize
- setTextBlinkMode
- setWordCharExceptions
- spawnSync
- unselectAll
- watchChild
- writeContentsSync
- Properties
- allowBold
- allowHyperlink
- audibleBell
- backspaceBinding
- boldIsBright
- cellHeightScale
- cellWidthScale
- cjkAmbiguousWidth
- currentDirectoryUri
- currentFileUri
- cursorBlinkMode
- cursorShape
- deleteBinding
- encoding
- fontDesc
- fontScale
- hyperlinkHoverUri
- iconTitle
- inputEnabled
- pointerAutohide
- pty
- rewrapOnResize
- scrollOnKeystroke
- scrollOnOutput
- scrollSpeed
- scrollbackLines
- textBlinkMode
- windowTitle
- wordCharExceptions
- Signals
- bell
- charSizeChanged
- childExited
- commit
- contentsChanged
- copyClipboard
- currentDirectoryUriChanged
- currentFileUriChanged
- cursorMoved
- decreaseFontSize
- deiconifyWindow
- encodingChanged
- eof
- hyperlinkHoverUriChanged
- iconTitleChanged
- iconifyWindow
- increaseFontSize
- lowerWindow
- maximizeWindow
- moveWindow
- notificationReceived
- pasteClipboard
- raiseWindow
- refreshWindow
- resizeWindow
- restoreWindow
- selectionChanged
- textDeleted
- textInserted
- textModified
- textScrolled
- windowTitleChanged
No description available in the introspection data.
Synopsis
- newtype Terminal = Terminal (ManagedPtr Terminal)
- class GObject o => IsTerminal o
- toTerminal :: (MonadIO m, IsTerminal o) => o -> m Terminal
- noTerminal :: Maybe Terminal
- terminalCopyClipboard :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m ()
- terminalCopyClipboardFormat :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Format -> m ()
- terminalCopyPrimary :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m ()
- terminalFeed :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe ByteString -> m ()
- terminalFeedChild :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe [Int8] -> m ()
- terminalFeedChildBinary :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe ByteString -> m ()
- terminalGetAllowBold :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetAllowHyperlink :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetAudibleBell :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetBoldIsBright :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetCellHeightScale :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Double
- terminalGetCellWidthScale :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Double
- terminalGetCharHeight :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m CLong
- terminalGetCharWidth :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m CLong
- terminalGetCjkAmbiguousWidth :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Int32
- terminalGetColumnCount :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m CLong
- terminalGetCurrentDirectoryUri :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m (Maybe Text)
- terminalGetCurrentFileUri :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Text
- terminalGetCursorBlinkMode :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m CursorBlinkMode
- terminalGetCursorPosition :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m (CLong, CLong)
- terminalGetCursorShape :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m CursorShape
- terminalGetEncoding :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Text
- terminalGetFont :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m FontDescription
- terminalGetFontScale :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Double
- terminalGetGeometryHints :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Int32 -> Int32 -> m Geometry
- terminalGetHasSelection :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetIconTitle :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Text
- terminalGetInputEnabled :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetMouseAutohide :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetPty :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Pty
- terminalGetRewrapOnResize :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetRowCount :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m CLong
- terminalGetScrollOnKeystroke :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetScrollOnOutput :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalGetScrollbackLines :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m CLong
- terminalGetTextBlinkMode :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m TextBlinkMode
- terminalGetWindowTitle :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m (Maybe Text)
- terminalGetWordCharExceptions :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Text
- terminalHyperlinkCheckEvent :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Event -> m Text
- terminalMatchAddGregex :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Regex -> [RegexMatchFlags] -> m Int32
- terminalMatchAddRegex :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Regex -> Word32 -> m Int32
- terminalMatchCheck :: (HasCallStack, MonadIO m, IsTerminal a) => a -> CLong -> CLong -> m (Text, Int32)
- terminalMatchCheckEvent :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Event -> m (Text, Int32)
- terminalMatchRemove :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Int32 -> m ()
- terminalMatchRemoveAll :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m ()
- terminalMatchSetCursor :: (HasCallStack, MonadIO m, IsTerminal a, IsCursor b) => a -> Int32 -> Maybe b -> m ()
- terminalMatchSetCursorName :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Int32 -> Text -> m ()
- terminalMatchSetCursorType :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Int32 -> CursorType -> m ()
- terminalNew :: (HasCallStack, MonadIO m) => m Terminal
- terminalPasteClipboard :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m ()
- terminalPastePrimary :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m ()
- terminalPtyNewSync :: (HasCallStack, MonadIO m, IsTerminal a, IsCancellable b) => a -> [PtyFlags] -> Maybe b -> m Pty
- terminalReset :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> Bool -> m ()
- terminalSearchFindNext :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalSearchFindPrevious :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalSearchGetGregex :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Regex
- terminalSearchGetRegex :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Regex
- terminalSearchGetWrapAround :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m Bool
- terminalSearchSetGregex :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe Regex -> [RegexMatchFlags] -> m ()
- terminalSearchSetRegex :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe Regex -> Word32 -> m ()
- terminalSearchSetWrapAround :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSelectAll :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m ()
- terminalSetAllowBold :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetAllowHyperlink :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetAudibleBell :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetBackspaceBinding :: (HasCallStack, MonadIO m, IsTerminal a) => a -> EraseBinding -> m ()
- terminalSetBoldIsBright :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetCellHeightScale :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Double -> m ()
- terminalSetCellWidthScale :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Double -> m ()
- terminalSetCjkAmbiguousWidth :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Int32 -> m ()
- terminalSetClearBackground :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetColorBackground :: (HasCallStack, MonadIO m, IsTerminal a) => a -> RGBA -> m ()
- terminalSetColorBold :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe RGBA -> m ()
- terminalSetColorCursor :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe RGBA -> m ()
- terminalSetColorCursorForeground :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe RGBA -> m ()
- terminalSetColorForeground :: (HasCallStack, MonadIO m, IsTerminal a) => a -> RGBA -> m ()
- terminalSetColorHighlight :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe RGBA -> m ()
- terminalSetColorHighlightForeground :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe RGBA -> m ()
- terminalSetColors :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe RGBA -> Maybe RGBA -> Maybe [RGBA] -> m ()
- terminalSetCursorBlinkMode :: (HasCallStack, MonadIO m, IsTerminal a) => a -> CursorBlinkMode -> m ()
- terminalSetCursorShape :: (HasCallStack, MonadIO m, IsTerminal a) => a -> CursorShape -> m ()
- terminalSetDefaultColors :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m ()
- terminalSetDeleteBinding :: (HasCallStack, MonadIO m, IsTerminal a) => a -> EraseBinding -> m ()
- terminalSetEncoding :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe Text -> m ()
- terminalSetFont :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Maybe FontDescription -> m ()
- terminalSetFontScale :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Double -> m ()
- terminalSetGeometryHintsForWindow :: (HasCallStack, MonadIO m, IsTerminal a, IsWindow b) => a -> b -> m ()
- terminalSetInputEnabled :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetMouseAutohide :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetPty :: (HasCallStack, MonadIO m, IsTerminal a, IsPty b) => a -> Maybe b -> m ()
- terminalSetRewrapOnResize :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetScrollOnKeystroke :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetScrollOnOutput :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Bool -> m ()
- terminalSetScrollSpeed :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Word32 -> m ()
- terminalSetScrollbackLines :: (HasCallStack, MonadIO m, IsTerminal a) => a -> CLong -> m ()
- terminalSetSize :: (HasCallStack, MonadIO m, IsTerminal a) => a -> CLong -> CLong -> m ()
- terminalSetTextBlinkMode :: (HasCallStack, MonadIO m, IsTerminal a) => a -> TextBlinkMode -> m ()
- terminalSetWordCharExceptions :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Text -> m ()
- terminalSpawnSync :: (HasCallStack, MonadIO m, IsTerminal a, IsCancellable b) => a -> [PtyFlags] -> Maybe Text -> [[Char]] -> Maybe [[Char]] -> [SpawnFlags] -> Maybe SpawnChildSetupFunc -> Maybe b -> m Int32
- terminalUnselectAll :: (HasCallStack, MonadIO m, IsTerminal a) => a -> m ()
- terminalWatchChild :: (HasCallStack, MonadIO m, IsTerminal a) => a -> Int32 -> m ()
- terminalWriteContentsSync :: (HasCallStack, MonadIO m, IsTerminal a, IsOutputStream b, IsCancellable c) => a -> b -> WriteFlags -> Maybe c -> m ()
- constructTerminalAllowBold :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalAllowBold :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalAllowBold :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- constructTerminalAllowHyperlink :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalAllowHyperlink :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalAllowHyperlink :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- constructTerminalAudibleBell :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalAudibleBell :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalAudibleBell :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- constructTerminalBackspaceBinding :: IsTerminal o => EraseBinding -> IO (GValueConstruct o)
- getTerminalBackspaceBinding :: (MonadIO m, IsTerminal o) => o -> m EraseBinding
- setTerminalBackspaceBinding :: (MonadIO m, IsTerminal o) => o -> EraseBinding -> m ()
- constructTerminalBoldIsBright :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalBoldIsBright :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalBoldIsBright :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- constructTerminalCellHeightScale :: IsTerminal o => Double -> IO (GValueConstruct o)
- getTerminalCellHeightScale :: (MonadIO m, IsTerminal o) => o -> m Double
- setTerminalCellHeightScale :: (MonadIO m, IsTerminal o) => o -> Double -> m ()
- constructTerminalCellWidthScale :: IsTerminal o => Double -> IO (GValueConstruct o)
- getTerminalCellWidthScale :: (MonadIO m, IsTerminal o) => o -> m Double
- setTerminalCellWidthScale :: (MonadIO m, IsTerminal o) => o -> Double -> m ()
- constructTerminalCjkAmbiguousWidth :: IsTerminal o => Int32 -> IO (GValueConstruct o)
- getTerminalCjkAmbiguousWidth :: (MonadIO m, IsTerminal o) => o -> m Int32
- setTerminalCjkAmbiguousWidth :: (MonadIO m, IsTerminal o) => o -> Int32 -> m ()
- getTerminalCurrentDirectoryUri :: (MonadIO m, IsTerminal o) => o -> m (Maybe Text)
- getTerminalCurrentFileUri :: (MonadIO m, IsTerminal o) => o -> m Text
- constructTerminalCursorBlinkMode :: IsTerminal o => CursorBlinkMode -> IO (GValueConstruct o)
- getTerminalCursorBlinkMode :: (MonadIO m, IsTerminal o) => o -> m CursorBlinkMode
- setTerminalCursorBlinkMode :: (MonadIO m, IsTerminal o) => o -> CursorBlinkMode -> m ()
- constructTerminalCursorShape :: IsTerminal o => CursorShape -> IO (GValueConstruct o)
- getTerminalCursorShape :: (MonadIO m, IsTerminal o) => o -> m CursorShape
- setTerminalCursorShape :: (MonadIO m, IsTerminal o) => o -> CursorShape -> m ()
- constructTerminalDeleteBinding :: IsTerminal o => EraseBinding -> IO (GValueConstruct o)
- getTerminalDeleteBinding :: (MonadIO m, IsTerminal o) => o -> m EraseBinding
- setTerminalDeleteBinding :: (MonadIO m, IsTerminal o) => o -> EraseBinding -> m ()
- clearTerminalEncoding :: (MonadIO m, IsTerminal o) => o -> m ()
- constructTerminalEncoding :: IsTerminal o => Text -> IO (GValueConstruct o)
- getTerminalEncoding :: (MonadIO m, IsTerminal o) => o -> m Text
- setTerminalEncoding :: (MonadIO m, IsTerminal o) => o -> Text -> m ()
- clearTerminalFontDesc :: (MonadIO m, IsTerminal o) => o -> m ()
- constructTerminalFontDesc :: IsTerminal o => FontDescription -> IO (GValueConstruct o)
- getTerminalFontDesc :: (MonadIO m, IsTerminal o) => o -> m (Maybe FontDescription)
- setTerminalFontDesc :: (MonadIO m, IsTerminal o) => o -> FontDescription -> m ()
- constructTerminalFontScale :: IsTerminal o => Double -> IO (GValueConstruct o)
- getTerminalFontScale :: (MonadIO m, IsTerminal o) => o -> m Double
- setTerminalFontScale :: (MonadIO m, IsTerminal o) => o -> Double -> m ()
- getTerminalHyperlinkHoverUri :: (MonadIO m, IsTerminal o) => o -> m (Maybe Text)
- getTerminalIconTitle :: (MonadIO m, IsTerminal o) => o -> m Text
- constructTerminalInputEnabled :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalInputEnabled :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalInputEnabled :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- constructTerminalPointerAutohide :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalPointerAutohide :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalPointerAutohide :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- clearTerminalPty :: (MonadIO m, IsTerminal o) => o -> m ()
- constructTerminalPty :: (IsTerminal o, IsPty a) => a -> IO (GValueConstruct o)
- getTerminalPty :: (MonadIO m, IsTerminal o) => o -> m Pty
- setTerminalPty :: (MonadIO m, IsTerminal o, IsPty a) => o -> a -> m ()
- constructTerminalRewrapOnResize :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalRewrapOnResize :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalRewrapOnResize :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- constructTerminalScrollOnKeystroke :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalScrollOnKeystroke :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalScrollOnKeystroke :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- constructTerminalScrollOnOutput :: IsTerminal o => Bool -> IO (GValueConstruct o)
- getTerminalScrollOnOutput :: (MonadIO m, IsTerminal o) => o -> m Bool
- setTerminalScrollOnOutput :: (MonadIO m, IsTerminal o) => o -> Bool -> m ()
- constructTerminalScrollSpeed :: IsTerminal o => Word32 -> IO (GValueConstruct o)
- getTerminalScrollSpeed :: (MonadIO m, IsTerminal o) => o -> m Word32
- setTerminalScrollSpeed :: (MonadIO m, IsTerminal o) => o -> Word32 -> m ()
- constructTerminalScrollbackLines :: IsTerminal o => Word32 -> IO (GValueConstruct o)
- getTerminalScrollbackLines :: (MonadIO m, IsTerminal o) => o -> m Word32
- setTerminalScrollbackLines :: (MonadIO m, IsTerminal o) => o -> Word32 -> m ()
- constructTerminalTextBlinkMode :: IsTerminal o => TextBlinkMode -> IO (GValueConstruct o)
- getTerminalTextBlinkMode :: (MonadIO m, IsTerminal o) => o -> m TextBlinkMode
- setTerminalTextBlinkMode :: (MonadIO m, IsTerminal o) => o -> TextBlinkMode -> m ()
- getTerminalWindowTitle :: (MonadIO m, IsTerminal o) => o -> m (Maybe Text)
- getTerminalWordCharExceptions :: (MonadIO m, IsTerminal o) => o -> m Text
- type C_TerminalBellCallback = Ptr () -> Ptr () -> IO ()
- type TerminalBellCallback = IO ()
- afterTerminalBell :: (IsTerminal a, MonadIO m) => a -> TerminalBellCallback -> m SignalHandlerId
- genClosure_TerminalBell :: TerminalBellCallback -> IO Closure
- mk_TerminalBellCallback :: C_TerminalBellCallback -> IO (FunPtr C_TerminalBellCallback)
- noTerminalBellCallback :: Maybe TerminalBellCallback
- onTerminalBell :: (IsTerminal a, MonadIO m) => a -> TerminalBellCallback -> m SignalHandlerId
- wrap_TerminalBellCallback :: TerminalBellCallback -> C_TerminalBellCallback
- type C_TerminalCharSizeChangedCallback = Ptr () -> Word32 -> Word32 -> Ptr () -> IO ()
- type TerminalCharSizeChangedCallback = Word32 -> Word32 -> IO ()
- afterTerminalCharSizeChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCharSizeChangedCallback -> m SignalHandlerId
- genClosure_TerminalCharSizeChanged :: TerminalCharSizeChangedCallback -> IO Closure
- mk_TerminalCharSizeChangedCallback :: C_TerminalCharSizeChangedCallback -> IO (FunPtr C_TerminalCharSizeChangedCallback)
- noTerminalCharSizeChangedCallback :: Maybe TerminalCharSizeChangedCallback
- onTerminalCharSizeChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCharSizeChangedCallback -> m SignalHandlerId
- wrap_TerminalCharSizeChangedCallback :: TerminalCharSizeChangedCallback -> C_TerminalCharSizeChangedCallback
- type C_TerminalChildExitedCallback = Ptr () -> Int32 -> Ptr () -> IO ()
- type TerminalChildExitedCallback = Int32 -> IO ()
- afterTerminalChildExited :: (IsTerminal a, MonadIO m) => a -> TerminalChildExitedCallback -> m SignalHandlerId
- genClosure_TerminalChildExited :: TerminalChildExitedCallback -> IO Closure
- mk_TerminalChildExitedCallback :: C_TerminalChildExitedCallback -> IO (FunPtr C_TerminalChildExitedCallback)
- noTerminalChildExitedCallback :: Maybe TerminalChildExitedCallback
- onTerminalChildExited :: (IsTerminal a, MonadIO m) => a -> TerminalChildExitedCallback -> m SignalHandlerId
- wrap_TerminalChildExitedCallback :: TerminalChildExitedCallback -> C_TerminalChildExitedCallback
- type C_TerminalCommitCallback = Ptr () -> CString -> Word32 -> Ptr () -> IO ()
- type TerminalCommitCallback = Text -> Word32 -> IO ()
- afterTerminalCommit :: (IsTerminal a, MonadIO m) => a -> TerminalCommitCallback -> m SignalHandlerId
- genClosure_TerminalCommit :: TerminalCommitCallback -> IO Closure
- mk_TerminalCommitCallback :: C_TerminalCommitCallback -> IO (FunPtr C_TerminalCommitCallback)
- noTerminalCommitCallback :: Maybe TerminalCommitCallback
- onTerminalCommit :: (IsTerminal a, MonadIO m) => a -> TerminalCommitCallback -> m SignalHandlerId
- wrap_TerminalCommitCallback :: TerminalCommitCallback -> C_TerminalCommitCallback
- type C_TerminalContentsChangedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalContentsChangedCallback = IO ()
- afterTerminalContentsChanged :: (IsTerminal a, MonadIO m) => a -> TerminalContentsChangedCallback -> m SignalHandlerId
- genClosure_TerminalContentsChanged :: TerminalContentsChangedCallback -> IO Closure
- mk_TerminalContentsChangedCallback :: C_TerminalContentsChangedCallback -> IO (FunPtr C_TerminalContentsChangedCallback)
- noTerminalContentsChangedCallback :: Maybe TerminalContentsChangedCallback
- onTerminalContentsChanged :: (IsTerminal a, MonadIO m) => a -> TerminalContentsChangedCallback -> m SignalHandlerId
- wrap_TerminalContentsChangedCallback :: TerminalContentsChangedCallback -> C_TerminalContentsChangedCallback
- type C_TerminalCopyClipboardCallback = Ptr () -> Ptr () -> IO ()
- type TerminalCopyClipboardCallback = IO ()
- afterTerminalCopyClipboard :: (IsTerminal a, MonadIO m) => a -> TerminalCopyClipboardCallback -> m SignalHandlerId
- genClosure_TerminalCopyClipboard :: TerminalCopyClipboardCallback -> IO Closure
- mk_TerminalCopyClipboardCallback :: C_TerminalCopyClipboardCallback -> IO (FunPtr C_TerminalCopyClipboardCallback)
- noTerminalCopyClipboardCallback :: Maybe TerminalCopyClipboardCallback
- onTerminalCopyClipboard :: (IsTerminal a, MonadIO m) => a -> TerminalCopyClipboardCallback -> m SignalHandlerId
- wrap_TerminalCopyClipboardCallback :: TerminalCopyClipboardCallback -> C_TerminalCopyClipboardCallback
- type C_TerminalCurrentDirectoryUriChangedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalCurrentDirectoryUriChangedCallback = IO ()
- afterTerminalCurrentDirectoryUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCurrentDirectoryUriChangedCallback -> m SignalHandlerId
- genClosure_TerminalCurrentDirectoryUriChanged :: TerminalCurrentDirectoryUriChangedCallback -> IO Closure
- mk_TerminalCurrentDirectoryUriChangedCallback :: C_TerminalCurrentDirectoryUriChangedCallback -> IO (FunPtr C_TerminalCurrentDirectoryUriChangedCallback)
- noTerminalCurrentDirectoryUriChangedCallback :: Maybe TerminalCurrentDirectoryUriChangedCallback
- onTerminalCurrentDirectoryUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCurrentDirectoryUriChangedCallback -> m SignalHandlerId
- wrap_TerminalCurrentDirectoryUriChangedCallback :: TerminalCurrentDirectoryUriChangedCallback -> C_TerminalCurrentDirectoryUriChangedCallback
- type C_TerminalCurrentFileUriChangedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalCurrentFileUriChangedCallback = IO ()
- afterTerminalCurrentFileUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCurrentFileUriChangedCallback -> m SignalHandlerId
- genClosure_TerminalCurrentFileUriChanged :: TerminalCurrentFileUriChangedCallback -> IO Closure
- mk_TerminalCurrentFileUriChangedCallback :: C_TerminalCurrentFileUriChangedCallback -> IO (FunPtr C_TerminalCurrentFileUriChangedCallback)
- noTerminalCurrentFileUriChangedCallback :: Maybe TerminalCurrentFileUriChangedCallback
- onTerminalCurrentFileUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCurrentFileUriChangedCallback -> m SignalHandlerId
- wrap_TerminalCurrentFileUriChangedCallback :: TerminalCurrentFileUriChangedCallback -> C_TerminalCurrentFileUriChangedCallback
- type C_TerminalCursorMovedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalCursorMovedCallback = IO ()
- afterTerminalCursorMoved :: (IsTerminal a, MonadIO m) => a -> TerminalCursorMovedCallback -> m SignalHandlerId
- genClosure_TerminalCursorMoved :: TerminalCursorMovedCallback -> IO Closure
- mk_TerminalCursorMovedCallback :: C_TerminalCursorMovedCallback -> IO (FunPtr C_TerminalCursorMovedCallback)
- noTerminalCursorMovedCallback :: Maybe TerminalCursorMovedCallback
- onTerminalCursorMoved :: (IsTerminal a, MonadIO m) => a -> TerminalCursorMovedCallback -> m SignalHandlerId
- wrap_TerminalCursorMovedCallback :: TerminalCursorMovedCallback -> C_TerminalCursorMovedCallback
- type C_TerminalDecreaseFontSizeCallback = Ptr () -> Ptr () -> IO ()
- type TerminalDecreaseFontSizeCallback = IO ()
- afterTerminalDecreaseFontSize :: (IsTerminal a, MonadIO m) => a -> TerminalDecreaseFontSizeCallback -> m SignalHandlerId
- genClosure_TerminalDecreaseFontSize :: TerminalDecreaseFontSizeCallback -> IO Closure
- mk_TerminalDecreaseFontSizeCallback :: C_TerminalDecreaseFontSizeCallback -> IO (FunPtr C_TerminalDecreaseFontSizeCallback)
- noTerminalDecreaseFontSizeCallback :: Maybe TerminalDecreaseFontSizeCallback
- onTerminalDecreaseFontSize :: (IsTerminal a, MonadIO m) => a -> TerminalDecreaseFontSizeCallback -> m SignalHandlerId
- wrap_TerminalDecreaseFontSizeCallback :: TerminalDecreaseFontSizeCallback -> C_TerminalDecreaseFontSizeCallback
- type C_TerminalDeiconifyWindowCallback = Ptr () -> Ptr () -> IO ()
- type TerminalDeiconifyWindowCallback = IO ()
- afterTerminalDeiconifyWindow :: (IsTerminal a, MonadIO m) => a -> TerminalDeiconifyWindowCallback -> m SignalHandlerId
- genClosure_TerminalDeiconifyWindow :: TerminalDeiconifyWindowCallback -> IO Closure
- mk_TerminalDeiconifyWindowCallback :: C_TerminalDeiconifyWindowCallback -> IO (FunPtr C_TerminalDeiconifyWindowCallback)
- noTerminalDeiconifyWindowCallback :: Maybe TerminalDeiconifyWindowCallback
- onTerminalDeiconifyWindow :: (IsTerminal a, MonadIO m) => a -> TerminalDeiconifyWindowCallback -> m SignalHandlerId
- wrap_TerminalDeiconifyWindowCallback :: TerminalDeiconifyWindowCallback -> C_TerminalDeiconifyWindowCallback
- type C_TerminalEncodingChangedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalEncodingChangedCallback = IO ()
- afterTerminalEncodingChanged :: (IsTerminal a, MonadIO m) => a -> TerminalEncodingChangedCallback -> m SignalHandlerId
- genClosure_TerminalEncodingChanged :: TerminalEncodingChangedCallback -> IO Closure
- mk_TerminalEncodingChangedCallback :: C_TerminalEncodingChangedCallback -> IO (FunPtr C_TerminalEncodingChangedCallback)
- noTerminalEncodingChangedCallback :: Maybe TerminalEncodingChangedCallback
- onTerminalEncodingChanged :: (IsTerminal a, MonadIO m) => a -> TerminalEncodingChangedCallback -> m SignalHandlerId
- wrap_TerminalEncodingChangedCallback :: TerminalEncodingChangedCallback -> C_TerminalEncodingChangedCallback
- type C_TerminalEofCallback = Ptr () -> Ptr () -> IO ()
- type TerminalEofCallback = IO ()
- afterTerminalEof :: (IsTerminal a, MonadIO m) => a -> TerminalEofCallback -> m SignalHandlerId
- genClosure_TerminalEof :: TerminalEofCallback -> IO Closure
- mk_TerminalEofCallback :: C_TerminalEofCallback -> IO (FunPtr C_TerminalEofCallback)
- noTerminalEofCallback :: Maybe TerminalEofCallback
- onTerminalEof :: (IsTerminal a, MonadIO m) => a -> TerminalEofCallback -> m SignalHandlerId
- wrap_TerminalEofCallback :: TerminalEofCallback -> C_TerminalEofCallback
- type C_TerminalHyperlinkHoverUriChangedCallback = Ptr () -> CString -> Ptr Rectangle -> Ptr () -> IO ()
- type TerminalHyperlinkHoverUriChangedCallback = Text -> Rectangle -> IO ()
- afterTerminalHyperlinkHoverUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalHyperlinkHoverUriChangedCallback -> m SignalHandlerId
- genClosure_TerminalHyperlinkHoverUriChanged :: TerminalHyperlinkHoverUriChangedCallback -> IO Closure
- mk_TerminalHyperlinkHoverUriChangedCallback :: C_TerminalHyperlinkHoverUriChangedCallback -> IO (FunPtr C_TerminalHyperlinkHoverUriChangedCallback)
- noTerminalHyperlinkHoverUriChangedCallback :: Maybe TerminalHyperlinkHoverUriChangedCallback
- onTerminalHyperlinkHoverUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalHyperlinkHoverUriChangedCallback -> m SignalHandlerId
- wrap_TerminalHyperlinkHoverUriChangedCallback :: TerminalHyperlinkHoverUriChangedCallback -> C_TerminalHyperlinkHoverUriChangedCallback
- type C_TerminalIconTitleChangedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalIconTitleChangedCallback = IO ()
- afterTerminalIconTitleChanged :: (IsTerminal a, MonadIO m) => a -> TerminalIconTitleChangedCallback -> m SignalHandlerId
- genClosure_TerminalIconTitleChanged :: TerminalIconTitleChangedCallback -> IO Closure
- mk_TerminalIconTitleChangedCallback :: C_TerminalIconTitleChangedCallback -> IO (FunPtr C_TerminalIconTitleChangedCallback)
- noTerminalIconTitleChangedCallback :: Maybe TerminalIconTitleChangedCallback
- onTerminalIconTitleChanged :: (IsTerminal a, MonadIO m) => a -> TerminalIconTitleChangedCallback -> m SignalHandlerId
- wrap_TerminalIconTitleChangedCallback :: TerminalIconTitleChangedCallback -> C_TerminalIconTitleChangedCallback
- type C_TerminalIconifyWindowCallback = Ptr () -> Ptr () -> IO ()
- type TerminalIconifyWindowCallback = IO ()
- afterTerminalIconifyWindow :: (IsTerminal a, MonadIO m) => a -> TerminalIconifyWindowCallback -> m SignalHandlerId
- genClosure_TerminalIconifyWindow :: TerminalIconifyWindowCallback -> IO Closure
- mk_TerminalIconifyWindowCallback :: C_TerminalIconifyWindowCallback -> IO (FunPtr C_TerminalIconifyWindowCallback)
- noTerminalIconifyWindowCallback :: Maybe TerminalIconifyWindowCallback
- onTerminalIconifyWindow :: (IsTerminal a, MonadIO m) => a -> TerminalIconifyWindowCallback -> m SignalHandlerId
- wrap_TerminalIconifyWindowCallback :: TerminalIconifyWindowCallback -> C_TerminalIconifyWindowCallback
- type C_TerminalIncreaseFontSizeCallback = Ptr () -> Ptr () -> IO ()
- type TerminalIncreaseFontSizeCallback = IO ()
- afterTerminalIncreaseFontSize :: (IsTerminal a, MonadIO m) => a -> TerminalIncreaseFontSizeCallback -> m SignalHandlerId
- genClosure_TerminalIncreaseFontSize :: TerminalIncreaseFontSizeCallback -> IO Closure
- mk_TerminalIncreaseFontSizeCallback :: C_TerminalIncreaseFontSizeCallback -> IO (FunPtr C_TerminalIncreaseFontSizeCallback)
- noTerminalIncreaseFontSizeCallback :: Maybe TerminalIncreaseFontSizeCallback
- onTerminalIncreaseFontSize :: (IsTerminal a, MonadIO m) => a -> TerminalIncreaseFontSizeCallback -> m SignalHandlerId
- wrap_TerminalIncreaseFontSizeCallback :: TerminalIncreaseFontSizeCallback -> C_TerminalIncreaseFontSizeCallback
- type C_TerminalLowerWindowCallback = Ptr () -> Ptr () -> IO ()
- type TerminalLowerWindowCallback = IO ()
- afterTerminalLowerWindow :: (IsTerminal a, MonadIO m) => a -> TerminalLowerWindowCallback -> m SignalHandlerId
- genClosure_TerminalLowerWindow :: TerminalLowerWindowCallback -> IO Closure
- mk_TerminalLowerWindowCallback :: C_TerminalLowerWindowCallback -> IO (FunPtr C_TerminalLowerWindowCallback)
- noTerminalLowerWindowCallback :: Maybe TerminalLowerWindowCallback
- onTerminalLowerWindow :: (IsTerminal a, MonadIO m) => a -> TerminalLowerWindowCallback -> m SignalHandlerId
- wrap_TerminalLowerWindowCallback :: TerminalLowerWindowCallback -> C_TerminalLowerWindowCallback
- type C_TerminalMaximizeWindowCallback = Ptr () -> Ptr () -> IO ()
- type TerminalMaximizeWindowCallback = IO ()
- afterTerminalMaximizeWindow :: (IsTerminal a, MonadIO m) => a -> TerminalMaximizeWindowCallback -> m SignalHandlerId
- genClosure_TerminalMaximizeWindow :: TerminalMaximizeWindowCallback -> IO Closure
- mk_TerminalMaximizeWindowCallback :: C_TerminalMaximizeWindowCallback -> IO (FunPtr C_TerminalMaximizeWindowCallback)
- noTerminalMaximizeWindowCallback :: Maybe TerminalMaximizeWindowCallback
- onTerminalMaximizeWindow :: (IsTerminal a, MonadIO m) => a -> TerminalMaximizeWindowCallback -> m SignalHandlerId
- wrap_TerminalMaximizeWindowCallback :: TerminalMaximizeWindowCallback -> C_TerminalMaximizeWindowCallback
- type C_TerminalMoveWindowCallback = Ptr () -> Word32 -> Word32 -> Ptr () -> IO ()
- type TerminalMoveWindowCallback = Word32 -> Word32 -> IO ()
- afterTerminalMoveWindow :: (IsTerminal a, MonadIO m) => a -> TerminalMoveWindowCallback -> m SignalHandlerId
- genClosure_TerminalMoveWindow :: TerminalMoveWindowCallback -> IO Closure
- mk_TerminalMoveWindowCallback :: C_TerminalMoveWindowCallback -> IO (FunPtr C_TerminalMoveWindowCallback)
- noTerminalMoveWindowCallback :: Maybe TerminalMoveWindowCallback
- onTerminalMoveWindow :: (IsTerminal a, MonadIO m) => a -> TerminalMoveWindowCallback -> m SignalHandlerId
- wrap_TerminalMoveWindowCallback :: TerminalMoveWindowCallback -> C_TerminalMoveWindowCallback
- type C_TerminalNotificationReceivedCallback = Ptr () -> CString -> CString -> Ptr () -> IO ()
- type TerminalNotificationReceivedCallback = Text -> Maybe Text -> IO ()
- afterTerminalNotificationReceived :: (IsTerminal a, MonadIO m) => a -> TerminalNotificationReceivedCallback -> m SignalHandlerId
- genClosure_TerminalNotificationReceived :: TerminalNotificationReceivedCallback -> IO Closure
- mk_TerminalNotificationReceivedCallback :: C_TerminalNotificationReceivedCallback -> IO (FunPtr C_TerminalNotificationReceivedCallback)
- noTerminalNotificationReceivedCallback :: Maybe TerminalNotificationReceivedCallback
- onTerminalNotificationReceived :: (IsTerminal a, MonadIO m) => a -> TerminalNotificationReceivedCallback -> m SignalHandlerId
- wrap_TerminalNotificationReceivedCallback :: TerminalNotificationReceivedCallback -> C_TerminalNotificationReceivedCallback
- type C_TerminalPasteClipboardCallback = Ptr () -> Ptr () -> IO ()
- type TerminalPasteClipboardCallback = IO ()
- afterTerminalPasteClipboard :: (IsTerminal a, MonadIO m) => a -> TerminalPasteClipboardCallback -> m SignalHandlerId
- genClosure_TerminalPasteClipboard :: TerminalPasteClipboardCallback -> IO Closure
- mk_TerminalPasteClipboardCallback :: C_TerminalPasteClipboardCallback -> IO (FunPtr C_TerminalPasteClipboardCallback)
- noTerminalPasteClipboardCallback :: Maybe TerminalPasteClipboardCallback
- onTerminalPasteClipboard :: (IsTerminal a, MonadIO m) => a -> TerminalPasteClipboardCallback -> m SignalHandlerId
- wrap_TerminalPasteClipboardCallback :: TerminalPasteClipboardCallback -> C_TerminalPasteClipboardCallback
- type C_TerminalRaiseWindowCallback = Ptr () -> Ptr () -> IO ()
- type TerminalRaiseWindowCallback = IO ()
- afterTerminalRaiseWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRaiseWindowCallback -> m SignalHandlerId
- genClosure_TerminalRaiseWindow :: TerminalRaiseWindowCallback -> IO Closure
- mk_TerminalRaiseWindowCallback :: C_TerminalRaiseWindowCallback -> IO (FunPtr C_TerminalRaiseWindowCallback)
- noTerminalRaiseWindowCallback :: Maybe TerminalRaiseWindowCallback
- onTerminalRaiseWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRaiseWindowCallback -> m SignalHandlerId
- wrap_TerminalRaiseWindowCallback :: TerminalRaiseWindowCallback -> C_TerminalRaiseWindowCallback
- type C_TerminalRefreshWindowCallback = Ptr () -> Ptr () -> IO ()
- type TerminalRefreshWindowCallback = IO ()
- afterTerminalRefreshWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRefreshWindowCallback -> m SignalHandlerId
- genClosure_TerminalRefreshWindow :: TerminalRefreshWindowCallback -> IO Closure
- mk_TerminalRefreshWindowCallback :: C_TerminalRefreshWindowCallback -> IO (FunPtr C_TerminalRefreshWindowCallback)
- noTerminalRefreshWindowCallback :: Maybe TerminalRefreshWindowCallback
- onTerminalRefreshWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRefreshWindowCallback -> m SignalHandlerId
- wrap_TerminalRefreshWindowCallback :: TerminalRefreshWindowCallback -> C_TerminalRefreshWindowCallback
- type C_TerminalResizeWindowCallback = Ptr () -> Word32 -> Word32 -> Ptr () -> IO ()
- type TerminalResizeWindowCallback = Word32 -> Word32 -> IO ()
- afterTerminalResizeWindow :: (IsTerminal a, MonadIO m) => a -> TerminalResizeWindowCallback -> m SignalHandlerId
- genClosure_TerminalResizeWindow :: TerminalResizeWindowCallback -> IO Closure
- mk_TerminalResizeWindowCallback :: C_TerminalResizeWindowCallback -> IO (FunPtr C_TerminalResizeWindowCallback)
- noTerminalResizeWindowCallback :: Maybe TerminalResizeWindowCallback
- onTerminalResizeWindow :: (IsTerminal a, MonadIO m) => a -> TerminalResizeWindowCallback -> m SignalHandlerId
- wrap_TerminalResizeWindowCallback :: TerminalResizeWindowCallback -> C_TerminalResizeWindowCallback
- type C_TerminalRestoreWindowCallback = Ptr () -> Ptr () -> IO ()
- type TerminalRestoreWindowCallback = IO ()
- afterTerminalRestoreWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRestoreWindowCallback -> m SignalHandlerId
- genClosure_TerminalRestoreWindow :: TerminalRestoreWindowCallback -> IO Closure
- mk_TerminalRestoreWindowCallback :: C_TerminalRestoreWindowCallback -> IO (FunPtr C_TerminalRestoreWindowCallback)
- noTerminalRestoreWindowCallback :: Maybe TerminalRestoreWindowCallback
- onTerminalRestoreWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRestoreWindowCallback -> m SignalHandlerId
- wrap_TerminalRestoreWindowCallback :: TerminalRestoreWindowCallback -> C_TerminalRestoreWindowCallback
- type C_TerminalSelectionChangedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalSelectionChangedCallback = IO ()
- afterTerminalSelectionChanged :: (IsTerminal a, MonadIO m) => a -> TerminalSelectionChangedCallback -> m SignalHandlerId
- genClosure_TerminalSelectionChanged :: TerminalSelectionChangedCallback -> IO Closure
- mk_TerminalSelectionChangedCallback :: C_TerminalSelectionChangedCallback -> IO (FunPtr C_TerminalSelectionChangedCallback)
- noTerminalSelectionChangedCallback :: Maybe TerminalSelectionChangedCallback
- onTerminalSelectionChanged :: (IsTerminal a, MonadIO m) => a -> TerminalSelectionChangedCallback -> m SignalHandlerId
- wrap_TerminalSelectionChangedCallback :: TerminalSelectionChangedCallback -> C_TerminalSelectionChangedCallback
- type C_TerminalTextDeletedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalTextDeletedCallback = IO ()
- afterTerminalTextDeleted :: (IsTerminal a, MonadIO m) => a -> TerminalTextDeletedCallback -> m SignalHandlerId
- genClosure_TerminalTextDeleted :: TerminalTextDeletedCallback -> IO Closure
- mk_TerminalTextDeletedCallback :: C_TerminalTextDeletedCallback -> IO (FunPtr C_TerminalTextDeletedCallback)
- noTerminalTextDeletedCallback :: Maybe TerminalTextDeletedCallback
- onTerminalTextDeleted :: (IsTerminal a, MonadIO m) => a -> TerminalTextDeletedCallback -> m SignalHandlerId
- wrap_TerminalTextDeletedCallback :: TerminalTextDeletedCallback -> C_TerminalTextDeletedCallback
- type C_TerminalTextInsertedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalTextInsertedCallback = IO ()
- afterTerminalTextInserted :: (IsTerminal a, MonadIO m) => a -> TerminalTextInsertedCallback -> m SignalHandlerId
- genClosure_TerminalTextInserted :: TerminalTextInsertedCallback -> IO Closure
- mk_TerminalTextInsertedCallback :: C_TerminalTextInsertedCallback -> IO (FunPtr C_TerminalTextInsertedCallback)
- noTerminalTextInsertedCallback :: Maybe TerminalTextInsertedCallback
- onTerminalTextInserted :: (IsTerminal a, MonadIO m) => a -> TerminalTextInsertedCallback -> m SignalHandlerId
- wrap_TerminalTextInsertedCallback :: TerminalTextInsertedCallback -> C_TerminalTextInsertedCallback
- type C_TerminalTextModifiedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalTextModifiedCallback = IO ()
- afterTerminalTextModified :: (IsTerminal a, MonadIO m) => a -> TerminalTextModifiedCallback -> m SignalHandlerId
- genClosure_TerminalTextModified :: TerminalTextModifiedCallback -> IO Closure
- mk_TerminalTextModifiedCallback :: C_TerminalTextModifiedCallback -> IO (FunPtr C_TerminalTextModifiedCallback)
- noTerminalTextModifiedCallback :: Maybe TerminalTextModifiedCallback
- onTerminalTextModified :: (IsTerminal a, MonadIO m) => a -> TerminalTextModifiedCallback -> m SignalHandlerId
- wrap_TerminalTextModifiedCallback :: TerminalTextModifiedCallback -> C_TerminalTextModifiedCallback
- type C_TerminalTextScrolledCallback = Ptr () -> Int32 -> Ptr () -> IO ()
- type TerminalTextScrolledCallback = Int32 -> IO ()
- afterTerminalTextScrolled :: (IsTerminal a, MonadIO m) => a -> TerminalTextScrolledCallback -> m SignalHandlerId
- genClosure_TerminalTextScrolled :: TerminalTextScrolledCallback -> IO Closure
- mk_TerminalTextScrolledCallback :: C_TerminalTextScrolledCallback -> IO (FunPtr C_TerminalTextScrolledCallback)
- noTerminalTextScrolledCallback :: Maybe TerminalTextScrolledCallback
- onTerminalTextScrolled :: (IsTerminal a, MonadIO m) => a -> TerminalTextScrolledCallback -> m SignalHandlerId
- wrap_TerminalTextScrolledCallback :: TerminalTextScrolledCallback -> C_TerminalTextScrolledCallback
- type C_TerminalWindowTitleChangedCallback = Ptr () -> Ptr () -> IO ()
- type TerminalWindowTitleChangedCallback = IO ()
- afterTerminalWindowTitleChanged :: (IsTerminal a, MonadIO m) => a -> TerminalWindowTitleChangedCallback -> m SignalHandlerId
- genClosure_TerminalWindowTitleChanged :: TerminalWindowTitleChangedCallback -> IO Closure
- mk_TerminalWindowTitleChangedCallback :: C_TerminalWindowTitleChangedCallback -> IO (FunPtr C_TerminalWindowTitleChangedCallback)
- noTerminalWindowTitleChangedCallback :: Maybe TerminalWindowTitleChangedCallback
- onTerminalWindowTitleChanged :: (IsTerminal a, MonadIO m) => a -> TerminalWindowTitleChangedCallback -> m SignalHandlerId
- wrap_TerminalWindowTitleChangedCallback :: TerminalWindowTitleChangedCallback -> C_TerminalWindowTitleChangedCallback
Exported types
Memory-managed wrapper type.
Instances
GObject Terminal Source # | |
Defined in GI.Vte.Objects.Terminal gobjectType :: Terminal -> IO GType # | |
IsImplementorIface Terminal Source # | |
Defined in GI.Vte.Objects.Terminal | |
IsObject Terminal Source # | |
Defined in GI.Vte.Objects.Terminal | |
IsWidget Terminal Source # | |
Defined in GI.Vte.Objects.Terminal | |
IsScrollable Terminal Source # | |
Defined in GI.Vte.Objects.Terminal | |
IsBuildable Terminal Source # | |
Defined in GI.Vte.Objects.Terminal | |
IsTerminal Terminal Source # | |
Defined in GI.Vte.Objects.Terminal |
class GObject o => IsTerminal o Source #
Type class for types which can be safely cast to Terminal
, for instance with toTerminal
.
Instances
(GObject a, (UnknownAncestorError Terminal a :: Constraint)) => IsTerminal a Source # | |
Defined in GI.Vte.Objects.Terminal | |
IsTerminal Terminal Source # | |
Defined in GI.Vte.Objects.Terminal |
toTerminal :: (MonadIO m, IsTerminal o) => o -> m Terminal Source #
Methods
copyClipboard
terminalCopyClipboard Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m () |
Deprecated: (Since version 0.50)Use terminalCopyClipboardFormat
with FormatText
instead.
Places the selected text in the terminal in the GDK_SELECTION_CLIPBOARD
selection.
copyClipboardFormat
terminalCopyClipboardFormat Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Format |
|
-> m () |
Places the selected text in the terminal in the GDK_SELECTION_CLIPBOARD
selection in the form specified by format
.
For all formats, the selection data (see SelectionData
) will include the
text targets (see targetListAddTextTargets
and
gtk_selection_data_targets_includes_text()
). For FormatHtml
,
the selection will also include the "text/html" target, which when requested,
returns the HTML data in UTF-16 with a U+FEFF BYTE ORDER MARK character at
the start.
Since: 0.50
copyPrimary
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m () |
Places the selected text in the terminal in the GDK_SELECTION_PRIMARY
selection.
feed
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe ByteString |
|
-> m () |
Interprets data
as if it were data received from a child process. This
can either be used to drive the terminal without a child process, or just
to mess with your users.
feedChild
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe [Int8] |
|
-> m () |
Sends a block of UTF-8 text to the child as if it were entered by the user at the keyboard.
feedChildBinary
terminalFeedChildBinary Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe ByteString |
|
-> m () |
Sends a block of binary data to the child.
getAllowBold
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool |
Checks whether or not the terminal will attempt to draw bold text, either by using a bold font variant or by repainting text with a different offset.
getAllowHyperlink
terminalGetAllowHyperlink Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool |
Checks whether or not hyperlinks (OSC 8 escape sequence) are allowed.
Since: 0.50
getAudibleBell
terminalGetAudibleBell Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool |
Checks whether or not the terminal will beep when the child outputs the "bl" sequence.
getBoldIsBright
terminalGetBoldIsBright Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool |
Checks whether the SGR 1 attribute also switches to the bright counterpart of the first 8 palette colors, in addition to making them bold (legacy behavior) or if SGR 1 only enables bold and leaves the color intact.
Since: 0.52
getCellHeightScale
terminalGetCellHeightScale Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Double | Returns: the terminal's cell height scale |
No description available in the introspection data.
Since: 0.52
getCellWidthScale
terminalGetCellWidthScale Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Double | Returns: the terminal's cell width scale |
No description available in the introspection data.
Since: 0.52
getCharHeight
terminalGetCharHeight Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m CLong | Returns: the height of a character cell Note that this method should rather be called vte_terminal_get_cell_height, because the return value takes cell-height-scale into account. |
No description available in the introspection data.
getCharWidth
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m CLong | Returns: the width of a character cell Note that this method should rather be called vte_terminal_get_cell_width, because the return value takes cell-width-scale into account. |
No description available in the introspection data.
getCjkAmbiguousWidth
terminalGetCjkAmbiguousWidth Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Int32 | Returns: 1 if ambiguous-width characters are narrow, or 2 if they are wide |
Returns whether ambiguous-width characters are narrow or wide when using
the UTF-8 encoding (terminalSetEncoding
).
getColumnCount
terminalGetColumnCount Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m CLong | Returns: the number of columns |
No description available in the introspection data.
getCurrentDirectoryUri
terminalGetCurrentDirectoryUri Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m (Maybe Text) | Returns: the URI of the current directory of the
process running in the terminal, or |
No description available in the introspection data.
getCurrentFileUri
terminalGetCurrentFileUri Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Text | Returns: the URI of the current file the
process running in the terminal is operating on, or |
No description available in the introspection data.
getCursorBlinkMode
terminalGetCursorBlinkMode Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m CursorBlinkMode | Returns: cursor blink mode. |
Returns the currently set cursor blink mode.
getCursorPosition
terminalGetCursorPosition Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m (CLong, CLong) |
Reads the location of the insertion cursor and returns it. The row coordinate is absolute.
getCursorShape
terminalGetCursorShape Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m CursorShape | Returns: cursor shape. |
Returns the currently set cursor shape.
getEncoding
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Text | Returns: the current encoding for the terminal |
Determines the name of the encoding in which the terminal expects data to be encoded.
getFont
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m FontDescription | Returns: a |
Queries the terminal for information about the fonts which will be used to draw text in the terminal. The actual font takes the font scale into account, this is not reflected in the return value, the unscaled font is returned.
getFontScale
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Double | Returns: the terminal's font scale |
No description available in the introspection data.
getGeometryHints
terminalGetGeometryHints Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Int32 |
|
-> Int32 |
|
-> m Geometry |
Deprecated: (Since version 0.52)
Fills in some hints
from terminal
's geometry. The hints
filled are those covered by the WindowHintsResizeInc
,
WindowHintsMinSize
and WindowHintsBaseSize
flags.
See windowSetGeometryHints
for more information.
terminal
must be realized (see widgetGetRealized
).
getHasSelection
terminalGetHasSelection Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool | Returns: |
Checks if the terminal currently contains selected text. Note that this
is different from determining if the terminal is the owner of any
Clipboard
items.
getIconTitle
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Text | Returns: the icon title |
No description available in the introspection data.
getInputEnabled
terminalGetInputEnabled Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool |
Returns whether the terminal allow user input.
getMouseAutohide
terminalGetMouseAutohide Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool |
Determines the value of the terminal's mouse autohide setting. When
autohiding is enabled, the mouse cursor will be hidden when the user presses
a key and shown when the user moves the mouse. This setting can be changed
using terminalSetMouseAutohide
.
getPty
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Pty |
Returns the Pty
of terminal
.
getRewrapOnResize
terminalGetRewrapOnResize Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool |
Checks whether or not the terminal will rewrap its contents upon resize.
getRowCount
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m CLong | Returns: the number of rows |
No description available in the introspection data.
getScrollOnKeystroke
terminalGetScrollOnKeystroke Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool | Returns: whether or not the terminal will forcibly scroll to the bottom of the viewable history when the user presses a key. Modifier keys do not trigger this behavior. |
No description available in the introspection data.
Since: 0.52
getScrollOnOutput
terminalGetScrollOnOutput Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool | Returns: whether or not the terminal will forcibly scroll to the bottom of the viewable history when the new data is received from the child. |
No description available in the introspection data.
Since: 0.52
getScrollbackLines
terminalGetScrollbackLines Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m CLong | Returns: length of the scrollback buffer used by the terminal. A negative value means "infinite scrollback". |
No description available in the introspection data.
Since: 0.52
getTextBlinkMode
terminalGetTextBlinkMode Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m TextBlinkMode | Returns: the blinking setting |
Checks whether or not the terminal will allow blinking text.
Since: 0.52
getWindowTitle
terminalGetWindowTitle Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m (Maybe Text) | Returns: the window title |
No description available in the introspection data.
getWordCharExceptions
terminalGetWordCharExceptions Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Text | Returns: a string, or |
Returns the set of characters which will be considered parts of a word when doing word-wise selection, in addition to the default which only considers alphanumeric characters part of a word.
If Nothing
, a built-in set is used.
Since: 0.40
hyperlinkCheckEvent
terminalHyperlinkCheckEvent Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Event |
|
-> m Text | Returns: a newly allocated string containing the target of the hyperlink |
Returns a nonempty string: the target of the explicit hyperlink (printed using the OSC 8
escape sequence) at the position of the event, or Nothing
.
Proper use of the escape sequence should result in URI-encoded URIs with a proper scheme like "http://", "https://", "file://", "mailto:" etc. This is, however, not enforced by VTE. The caller must tolerate the returned string potentially not being a valid URI.
Since: 0.50
matchAddGregex
terminalMatchAddGregex Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Regex |
|
-> [RegexMatchFlags] |
|
-> m Int32 | Returns: an integer associated with this expression, or -1 if |
Deprecated: (Since version 0.46)Use terminalMatchAddRegex
or vte_terminal_match_add_regex_full()
instead.
Adds the regular expression regex
to the list of matching expressions. When the
user moves the mouse cursor over a section of displayed text which matches
this expression, the text will be highlighted.
matchAddRegex
terminalMatchAddRegex Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Regex |
|
-> Word32 |
|
-> m Int32 | Returns: an integer associated with this expression |
Adds the regular expression regex
to the list of matching expressions. When the
user moves the mouse cursor over a section of displayed text which matches
this expression, the text will be highlighted.
Since: 0.46
matchCheck
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> CLong |
|
-> CLong |
|
-> m (Text, Int32) | Returns: a newly allocated string which matches one of the previously set regular expressions |
Deprecated: (Since version 0.46)Use terminalMatchCheckEvent
instead.
Checks if the text in and around the specified position matches any of the
regular expressions previously set using vte_terminal_match_add()
. If a
match exists, the text string is returned and if tag
is not Nothing
, the number
associated with the matched regular expression will be stored in tag
.
If more than one regular expression has been set with
vte_terminal_match_add()
, then expressions are checked in the order in
which they were added.
matchCheckEvent
terminalMatchCheckEvent Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Event |
|
-> m (Text, Int32) | Returns: a newly allocated string which matches one of the previously set regular expressions |
Checks if the text in and around the position of the event matches any of the
regular expressions previously set using vte_terminal_match_add()
. If a
match exists, the text string is returned and if tag
is not Nothing
, the number
associated with the matched regular expression will be stored in tag
.
If more than one regular expression has been set with
vte_terminal_match_add()
, then expressions are checked in the order in
which they were added.
matchRemove
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Int32 |
|
-> m () |
Removes the regular expression which is associated with the given tag
from
the list of expressions which the terminal will highlight when the user
moves the mouse cursor over matching text.
matchRemoveAll
terminalMatchRemoveAll Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m () |
Clears the list of regular expressions the terminal uses to highlight text when the user moves the mouse cursor.
matchSetCursor
terminalMatchSetCursor Source #
:: (HasCallStack, MonadIO m, IsTerminal a, IsCursor b) | |
=> a |
|
-> Int32 |
|
-> Maybe b |
|
-> m () |
Deprecated: (Since version 0.40)Use terminalMatchSetCursorType
or vte_terminal_match_set_cursor_named()
instead.
Sets which cursor the terminal will use if the pointer is over the pattern
specified by tag
. The terminal keeps a reference to cursor
.
matchSetCursorName
terminalMatchSetCursorName Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Int32 |
|
-> Text |
|
-> m () |
Sets which cursor the terminal will use if the pointer is over the pattern
specified by tag
.
matchSetCursorType
terminalMatchSetCursorType Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Int32 |
|
-> CursorType |
|
-> m () |
Sets which cursor the terminal will use if the pointer is over the pattern
specified by tag
.
new
:: (HasCallStack, MonadIO m) | |
=> m Terminal | Returns: a new |
Creates a new terminal widget.
pasteClipboard
terminalPasteClipboard Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m () |
Sends the contents of the GDK_SELECTION_CLIPBOARD
selection to the
terminal's child. If necessary, the data is converted from UTF-8 to the
terminal's current encoding. It's called on paste menu item, or when
user presses Shift+Insert.
pastePrimary
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m () |
Sends the contents of the GDK_SELECTION_PRIMARY
selection to the terminal's
child. If necessary, the data is converted from UTF-8 to the terminal's
current encoding. The terminal will call also paste the
GDK_SELECTION_PRIMARY
selection when the user clicks with the the second
mouse button.
ptyNewSync
:: (HasCallStack, MonadIO m, IsTerminal a, IsCancellable b) | |
=> a |
|
-> [PtyFlags] |
|
-> Maybe b |
|
-> m Pty |
reset
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> Bool |
|
-> m () |
Resets as much of the terminal's internal state as possible, discarding any unprocessed input data, resetting character attributes, cursor state, national character set state, status line, terminal modes (insert/delete), selection state, and encoding.
searchFindNext
terminalSearchFindNext Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool | Returns: |
Searches the next string matching the search regex set with
terminalSearchSetRegex
.
searchFindPrevious
terminalSearchFindPrevious Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool | Returns: |
Searches the previous string matching the search regex set with
terminalSearchSetRegex
.
searchGetGregex
terminalSearchGetGregex Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Regex | Returns: |
Deprecated: (Since version 0.46)use terminalSearchGetRegex
instead.
No description available in the introspection data.
searchGetRegex
terminalSearchGetRegex Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Regex |
No description available in the introspection data.
Since: 0.46
searchGetWrapAround
terminalSearchGetWrapAround Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m Bool | Returns: whether searching will wrap around |
No description available in the introspection data.
searchSetGregex
terminalSearchSetGregex Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe Regex | |
-> [RegexMatchFlags] |
|
-> m () |
Deprecated: (Since version 0.46)use terminalSearchSetRegex
instead.
Sets the Regex
regex to search for. Unsets the search regex when passed Nothing
.
searchSetRegex
terminalSearchSetRegex Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe Regex | |
-> Word32 |
|
-> m () |
Sets the regex to search for. Unsets the search regex when passed Nothing
.
Since: 0.46
searchSetWrapAround
terminalSearchSetWrapAround Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Sets whether search should wrap around to the beginning of the terminal content when reaching its end.
selectAll
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m () |
Selects all text within the terminal (including the scrollback buffer).
setAllowBold
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Controls whether or not the terminal will attempt to draw bold text, either by using a bold font variant or by repainting text with a different offset.
setAllowHyperlink
terminalSetAllowHyperlink Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Controls whether or not hyperlinks (OSC 8 escape sequence) are allowed.
Since: 0.50
setAudibleBell
terminalSetAudibleBell Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Controls whether or not the terminal will beep when the child outputs the "bl" sequence.
setBackspaceBinding
terminalSetBackspaceBinding Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> EraseBinding |
|
-> m () |
Modifies the terminal's backspace key binding, which controls what string or control sequence the terminal sends to its child when the user presses the backspace key.
setBoldIsBright
terminalSetBoldIsBright Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Sets whether the SGR 1 attribute also switches to the bright counterpart of the first 8 palette colors, in addition to making them bold (legacy behavior) or if SGR 1 only enables bold and leaves the color intact.
Since: 0.52
setCellHeightScale
terminalSetCellHeightScale Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Double |
|
-> m () |
Sets the terminal's cell height scale to scale
.
This can be used to increase the line spacing. (The font's height is not affected.) Valid values go from 1.0 (default) to 2.0 ("double spacing").
Since: 0.52
setCellWidthScale
terminalSetCellWidthScale Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Double |
|
-> m () |
Sets the terminal's cell width scale to scale
.
This can be used to increase the letter spacing. (The font's width is not affected.) Valid values go from 1.0 (default) to 2.0.
Since: 0.52
setCjkAmbiguousWidth
terminalSetCjkAmbiguousWidth Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Int32 |
|
-> m () |
This setting controls whether ambiguous-width characters are narrow or wide
when using the UTF-8 encoding (terminalSetEncoding
). In all other encodings,
the width of ambiguous-width characters is fixed.
setClearBackground
terminalSetClearBackground Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool | |
-> m () |
Sets whether to paint the background with the background colour.
The default is True
.
This function is rarely useful. One use for it is to add a background image to the terminal.
Since: 0.52
setColorBackground
terminalSetColorBackground Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> RGBA |
|
-> m () |
Sets the background color for text which does not have a specific background color assigned. Only has effect when no background image is set and when the terminal is not transparent.
setColorBold
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe RGBA |
|
-> m () |
Sets the color used to draw bold text in the default foreground color.
If bold
is Nothing
then the default color is used.
setColorCursor
terminalSetColorCursor Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe RGBA |
|
-> m () |
Sets the background color for text which is under the cursor. If Nothing
, text
under the cursor will be drawn with foreground and background colors
reversed.
setColorCursorForeground
terminalSetColorCursorForeground Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe RGBA |
|
-> m () |
Sets the foreground color for text which is under the cursor. If Nothing
, text
under the cursor will be drawn with foreground and background colors
reversed.
Since: 0.44
setColorForeground
terminalSetColorForeground Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> RGBA |
|
-> m () |
Sets the foreground color used to draw normal text.
setColorHighlight
terminalSetColorHighlight Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe RGBA |
|
-> m () |
Sets the background color for text which is highlighted. If Nothing
,
it is unset. If neither highlight background nor highlight foreground are set,
highlighted text (which is usually highlighted because it is selected) will
be drawn with foreground and background colors reversed.
setColorHighlightForeground
terminalSetColorHighlightForeground Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe RGBA |
|
-> m () |
Sets the foreground color for text which is highlighted. If Nothing
,
it is unset. If neither highlight background nor highlight foreground are set,
highlighted text (which is usually highlighted because it is selected) will
be drawn with foreground and background colors reversed.
setColors
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe RGBA |
|
-> Maybe RGBA |
|
-> Maybe [RGBA] |
|
-> m () |
palette
specifies the new values for the 256 palette colors: 8 standard colors,
their 8 bright counterparts, 6x6x6 color cube, and 24 grayscale colors.
Omitted entries will default to a hardcoded value.
paletteSize
must be 0, 8, 16, 232 or 256.
If foreground
is Nothing
and paletteSize
is greater than 0, the new foreground
color is taken from palette
[7]. If background
is Nothing
and paletteSize
is
greater than 0, the new background color is taken from palette
[0].
setCursorBlinkMode
terminalSetCursorBlinkMode Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> CursorBlinkMode |
|
-> m () |
Sets whether or not the cursor will blink. Using CursorBlinkModeSystem
will use the Settings
::gtk-cursor-blink
setting.
setCursorShape
terminalSetCursorShape Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> CursorShape |
|
-> m () |
Sets the shape of the cursor drawn.
setDefaultColors
terminalSetDefaultColors Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m () |
Reset the terminal palette to reasonable compiled-in default color.
setDeleteBinding
terminalSetDeleteBinding Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> EraseBinding |
|
-> m () |
Modifies the terminal's delete key binding, which controls what string or control sequence the terminal sends to its child when the user presses the delete key.
setEncoding
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe Text |
|
-> m () | (Can throw |
Changes the encoding the terminal will expect data from the child to
be encoded with. For certain terminal types, applications executing in the
terminal can change the encoding. If codeset
is Nothing
, it uses "UTF-8".
setFont
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Maybe FontDescription |
|
-> m () |
Sets the font used for rendering all text displayed by the terminal,
overriding any fonts set using widgetModifyFont
. The terminal
will immediately attempt to load the desired font, retrieve its
metrics, and attempt to resize itself to keep the same number of rows
and columns. The font scale is applied to the specified font.
setFontScale
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Double |
|
-> m () |
Sets the terminal's font scale to scale
.
setGeometryHintsForWindow
terminalSetGeometryHintsForWindow Source #
:: (HasCallStack, MonadIO m, IsTerminal a, IsWindow b) | |
=> a |
|
-> b |
|
-> m () |
Deprecated: (Since version 0.52)
Sets terminal
as window
's geometry widget. See
windowSetGeometryHints
for more information.
terminal
must be realized (see widgetGetRealized
).
setInputEnabled
terminalSetInputEnabled Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Enables or disables user input. When user input is disabled, the terminal's child will not receive any key press, or mouse button press or motion events sent to it.
setMouseAutohide
terminalSetMouseAutohide Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Changes the value of the terminal's mouse autohide setting. When autohiding
is enabled, the mouse cursor will be hidden when the user presses a key and
shown when the user moves the mouse. This setting can be read using
terminalGetMouseAutohide
.
setPty
:: (HasCallStack, MonadIO m, IsTerminal a, IsPty b) | |
=> a |
|
-> Maybe b | |
-> m () |
Sets pty
as the PTY to use in terminal
.
Use Nothing
to unset the PTY.
setRewrapOnResize
terminalSetRewrapOnResize Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Controls whether or not the terminal will rewrap its contents, including the scrollback history, whenever the terminal's width changes.
setScrollOnKeystroke
terminalSetScrollOnKeystroke Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Controls whether or not the terminal will forcibly scroll to the bottom of the viewable history when the user presses a key. Modifier keys do not trigger this behavior.
setScrollOnOutput
terminalSetScrollOnOutput Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Bool |
|
-> m () |
Controls whether or not the terminal will forcibly scroll to the bottom of the viewable history when the new data is received from the child.
setScrollSpeed
terminalSetScrollSpeed Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Word32 |
|
-> m () |
Sets the number of lines by which the buffer is moved when scrolling with a mouse wheel. Setting it to zero will cause the buffer to be moved by an amount depending on the number of visible rows the widget can display.
setScrollbackLines
terminalSetScrollbackLines Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> CLong |
|
-> m () |
Sets the length of the scrollback buffer used by the terminal. The size of the scrollback buffer will be set to the larger of this value and the number of visible rows the widget can display, so 0 can safely be used to disable scrollback.
A negative value means "infinite scrollback".
Note that this setting only affects the normal screen buffer. No scrollback is allowed on the alternate screen buffer.
setSize
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> CLong |
|
-> CLong |
|
-> m () |
Attempts to change the terminal's size in terms of rows and columns. If the attempt succeeds, the widget will resize itself to the proper size.
setTextBlinkMode
terminalSetTextBlinkMode Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> TextBlinkMode |
|
-> m () |
Controls whether or not the terminal will allow blinking text.
Since: 0.52
setWordCharExceptions
terminalSetWordCharExceptions Source #
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Text |
|
-> m () |
With this function you can provide a set of characters which will be considered parts of a word when doing word-wise selection, in addition to the default which only considers alphanumeric characters part of a word.
The characters in exceptions
must be non-alphanumeric, each character
must occur only once, and if exceptions
contains the character
U+002D HYPHEN-MINUS, it must be at the start of the string.
Use Nothing
to reset the set of exception characters to the default.
Since: 0.40
spawnSync
:: (HasCallStack, MonadIO m, IsTerminal a, IsCancellable b) | |
=> a |
|
-> [PtyFlags] |
|
-> Maybe Text |
|
-> [[Char]] |
|
-> Maybe [[Char]] |
|
-> [SpawnFlags] |
|
-> Maybe SpawnChildSetupFunc |
|
-> Maybe b |
|
-> m Int32 | (Can throw |
Deprecated: (Since version 0.48)Use vte_terminal_spawn_async()
instead.
Starts the specified command under a newly-allocated controlling
pseudo-terminal. The argv
and envv
lists should be Nothing
-terminated.
The "TERM" environment variable is automatically set to a default value,
but can be overridden from envv
.
ptyFlags
controls logging the session to the specified system log files.
Note that SpawnFlagsDoNotReapChild
will always be added to spawnFlags
.
Note that all open file descriptors will be closed in the child. If you want to keep some file descriptor open for use in the child process, you need to use a child setup function that unsets the FD_CLOEXEC flag on that file descriptor.
See vte_pty_new()
, spawnAsync
and terminalWatchChild
for more information.
Beginning with 0.52, sets PWD to workingDirectory
in order to preserve symlink components.
The caller should also make sure that symlinks were preserved while constructing the value of workingDirectory
,
e.g. by using terminalGetCurrentDirectoryUri
, getCurrentDir
or get_current_dir_name()
.
unselectAll
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> m () |
Clears the current selection.
watchChild
:: (HasCallStack, MonadIO m, IsTerminal a) | |
=> a |
|
-> Int32 |
|
-> m () |
Watches childPid
. When the process exists, the Terminal
::child-exited
signal will be called with the child's exit status.
Prior to calling this function, a Pty
must have been set in terminal
using terminalSetPty
.
When the child exits, the terminal's Pty
will be set to Nothing
.
Note: g_child_watch_add()
or childWatchAdd
must not have
been called for childPid
, nor a Source
for it been created with
childWatchSourceNew
.
Note: when using the spawnAsync
family of functions,
the SpawnFlagsDoNotReapChild
flag MUST have been passed.
writeContentsSync
terminalWriteContentsSync Source #
:: (HasCallStack, MonadIO m, IsTerminal a, IsOutputStream b, IsCancellable c) | |
=> a |
|
-> b |
|
-> WriteFlags |
|
-> Maybe c |
|
-> m () | (Can throw |
Write contents of the current contents of terminal
(including any
scrollback history) to stream
according to flags
.
If cancellable
is not Nothing
, then the operation can be cancelled by triggering
the cancellable object from another thread. If the operation was cancelled,
the error IOErrorEnumCancelled
will be returned in error
.
This is a synchronous operation and will make the widget (and input
processing) during the write operation, which may take a long time
depending on scrollback history and stream
availability for writing.
Properties
allowBold
Controls whether or not the terminal will attempt to draw bold text. This may happen either by using a bold font variant, or by repainting text with a different offset.
constructTerminalAllowBold :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “allow-bold
” property. This is rarely needed directly, but it is used by new
.
getTerminalAllowBold :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “allow-bold
” property.
When overloading is enabled, this is equivalent to
get
terminal #allowBold
setTerminalAllowBold :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “allow-bold
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #allowBold:=
value ]
allowHyperlink
Controls whether or not hyperlinks (OSC 8 escape sequence) are recognized and displayed.
Since: 0.50
constructTerminalAllowHyperlink :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “allow-hyperlink
” property. This is rarely needed directly, but it is used by new
.
getTerminalAllowHyperlink :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “allow-hyperlink
” property.
When overloading is enabled, this is equivalent to
get
terminal #allowHyperlink
setTerminalAllowHyperlink :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “allow-hyperlink
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #allowHyperlink:=
value ]
audibleBell
Controls whether or not the terminal will beep when the child outputs the "bl" sequence.
constructTerminalAudibleBell :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “audible-bell
” property. This is rarely needed directly, but it is used by new
.
getTerminalAudibleBell :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “audible-bell
” property.
When overloading is enabled, this is equivalent to
get
terminal #audibleBell
setTerminalAudibleBell :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “audible-bell
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #audibleBell:=
value ]
backspaceBinding
Controls what string or control sequence the terminal sends to its child when the user presses the backspace key.
constructTerminalBackspaceBinding :: IsTerminal o => EraseBinding -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “backspace-binding
” property. This is rarely needed directly, but it is used by new
.
getTerminalBackspaceBinding :: (MonadIO m, IsTerminal o) => o -> m EraseBinding Source #
Get the value of the “backspace-binding
” property.
When overloading is enabled, this is equivalent to
get
terminal #backspaceBinding
setTerminalBackspaceBinding :: (MonadIO m, IsTerminal o) => o -> EraseBinding -> m () Source #
Set the value of the “backspace-binding
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #backspaceBinding:=
value ]
boldIsBright
Whether the SGR 1 attribute also switches to the bright counterpart of the first 8 palette colors, in addition to making them bold (legacy behavior) or if SGR 1 only enables bold and leaves the color intact.
Since: 0.52
constructTerminalBoldIsBright :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “bold-is-bright
” property. This is rarely needed directly, but it is used by new
.
getTerminalBoldIsBright :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “bold-is-bright
” property.
When overloading is enabled, this is equivalent to
get
terminal #boldIsBright
setTerminalBoldIsBright :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “bold-is-bright
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #boldIsBright:=
value ]
cellHeightScale
Scale factor for the cell height, to increase line spacing. (The font's height is not affected.)
Since: 0.52
constructTerminalCellHeightScale :: IsTerminal o => Double -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “cell-height-scale
” property. This is rarely needed directly, but it is used by new
.
getTerminalCellHeightScale :: (MonadIO m, IsTerminal o) => o -> m Double Source #
Get the value of the “cell-height-scale
” property.
When overloading is enabled, this is equivalent to
get
terminal #cellHeightScale
setTerminalCellHeightScale :: (MonadIO m, IsTerminal o) => o -> Double -> m () Source #
Set the value of the “cell-height-scale
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #cellHeightScale:=
value ]
cellWidthScale
Scale factor for the cell width, to increase letter spacing. (The font's width is not affected.)
Since: 0.52
constructTerminalCellWidthScale :: IsTerminal o => Double -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “cell-width-scale
” property. This is rarely needed directly, but it is used by new
.
getTerminalCellWidthScale :: (MonadIO m, IsTerminal o) => o -> m Double Source #
Get the value of the “cell-width-scale
” property.
When overloading is enabled, this is equivalent to
get
terminal #cellWidthScale
setTerminalCellWidthScale :: (MonadIO m, IsTerminal o) => o -> Double -> m () Source #
Set the value of the “cell-width-scale
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #cellWidthScale:=
value ]
cjkAmbiguousWidth
This setting controls whether ambiguous-width characters are narrow or wide
when using the UTF-8 encoding (terminalSetEncoding
). In all other encodings,
the width of ambiguous-width characters is fixed.
This setting only takes effect the next time the terminal is reset, either
via escape sequence or with terminalReset
.
constructTerminalCjkAmbiguousWidth :: IsTerminal o => Int32 -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “cjk-ambiguous-width
” property. This is rarely needed directly, but it is used by new
.
getTerminalCjkAmbiguousWidth :: (MonadIO m, IsTerminal o) => o -> m Int32 Source #
Get the value of the “cjk-ambiguous-width
” property.
When overloading is enabled, this is equivalent to
get
terminal #cjkAmbiguousWidth
setTerminalCjkAmbiguousWidth :: (MonadIO m, IsTerminal o) => o -> Int32 -> m () Source #
Set the value of the “cjk-ambiguous-width
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #cjkAmbiguousWidth:=
value ]
currentDirectoryUri
The current directory URI, or Nothing
if unset.
getTerminalCurrentDirectoryUri :: (MonadIO m, IsTerminal o) => o -> m (Maybe Text) Source #
Get the value of the “current-directory-uri
” property.
When overloading is enabled, this is equivalent to
get
terminal #currentDirectoryUri
currentFileUri
The current file URI, or Nothing
if unset.
getTerminalCurrentFileUri :: (MonadIO m, IsTerminal o) => o -> m Text Source #
Get the value of the “current-file-uri
” property.
When overloading is enabled, this is equivalent to
get
terminal #currentFileUri
cursorBlinkMode
Sets whether or not the cursor will blink. Using CursorBlinkModeSystem
will use the Settings
::gtk-cursor-blink
setting.
constructTerminalCursorBlinkMode :: IsTerminal o => CursorBlinkMode -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “cursor-blink-mode
” property. This is rarely needed directly, but it is used by new
.
getTerminalCursorBlinkMode :: (MonadIO m, IsTerminal o) => o -> m CursorBlinkMode Source #
Get the value of the “cursor-blink-mode
” property.
When overloading is enabled, this is equivalent to
get
terminal #cursorBlinkMode
setTerminalCursorBlinkMode :: (MonadIO m, IsTerminal o) => o -> CursorBlinkMode -> m () Source #
Set the value of the “cursor-blink-mode
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #cursorBlinkMode:=
value ]
cursorShape
Controls the shape of the cursor.
constructTerminalCursorShape :: IsTerminal o => CursorShape -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “cursor-shape
” property. This is rarely needed directly, but it is used by new
.
getTerminalCursorShape :: (MonadIO m, IsTerminal o) => o -> m CursorShape Source #
Get the value of the “cursor-shape
” property.
When overloading is enabled, this is equivalent to
get
terminal #cursorShape
setTerminalCursorShape :: (MonadIO m, IsTerminal o) => o -> CursorShape -> m () Source #
Set the value of the “cursor-shape
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #cursorShape:=
value ]
deleteBinding
Controls what string or control sequence the terminal sends to its child when the user presses the delete key.
constructTerminalDeleteBinding :: IsTerminal o => EraseBinding -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “delete-binding
” property. This is rarely needed directly, but it is used by new
.
getTerminalDeleteBinding :: (MonadIO m, IsTerminal o) => o -> m EraseBinding Source #
Get the value of the “delete-binding
” property.
When overloading is enabled, this is equivalent to
get
terminal #deleteBinding
setTerminalDeleteBinding :: (MonadIO m, IsTerminal o) => o -> EraseBinding -> m () Source #
Set the value of the “delete-binding
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #deleteBinding:=
value ]
encoding
Controls the encoding the terminal will expect data from the child to be encoded with. For certain terminal types, applications executing in the terminal can change the encoding. The default is defined by the application's locale settings.
clearTerminalEncoding :: (MonadIO m, IsTerminal o) => o -> m () Source #
Set the value of the “encoding
” property to Nothing
.
When overloading is enabled, this is equivalent to
clear
#encoding
constructTerminalEncoding :: IsTerminal o => Text -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “encoding
” property. This is rarely needed directly, but it is used by new
.
getTerminalEncoding :: (MonadIO m, IsTerminal o) => o -> m Text Source #
Get the value of the “encoding
” property.
When overloading is enabled, this is equivalent to
get
terminal #encoding
setTerminalEncoding :: (MonadIO m, IsTerminal o) => o -> Text -> m () Source #
Set the value of the “encoding
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #encoding:=
value ]
fontDesc
Specifies the font used for rendering all text displayed by the terminal,
overriding any fonts set using widgetModifyFont
. The terminal
will immediately attempt to load the desired font, retrieve its
metrics, and attempt to resize itself to keep the same number of rows
and columns.
clearTerminalFontDesc :: (MonadIO m, IsTerminal o) => o -> m () Source #
Set the value of the “font-desc
” property to Nothing
.
When overloading is enabled, this is equivalent to
clear
#fontDesc
constructTerminalFontDesc :: IsTerminal o => FontDescription -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “font-desc
” property. This is rarely needed directly, but it is used by new
.
getTerminalFontDesc :: (MonadIO m, IsTerminal o) => o -> m (Maybe FontDescription) Source #
Get the value of the “font-desc
” property.
When overloading is enabled, this is equivalent to
get
terminal #fontDesc
setTerminalFontDesc :: (MonadIO m, IsTerminal o) => o -> FontDescription -> m () Source #
Set the value of the “font-desc
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #fontDesc:=
value ]
fontScale
The terminal's font scale.
constructTerminalFontScale :: IsTerminal o => Double -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “font-scale
” property. This is rarely needed directly, but it is used by new
.
getTerminalFontScale :: (MonadIO m, IsTerminal o) => o -> m Double Source #
Get the value of the “font-scale
” property.
When overloading is enabled, this is equivalent to
get
terminal #fontScale
setTerminalFontScale :: (MonadIO m, IsTerminal o) => o -> Double -> m () Source #
Set the value of the “font-scale
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #fontScale:=
value ]
hyperlinkHoverUri
The currently hovered hyperlink URI, or Nothing
if unset.
Since: 0.50
getTerminalHyperlinkHoverUri :: (MonadIO m, IsTerminal o) => o -> m (Maybe Text) Source #
Get the value of the “hyperlink-hover-uri
” property.
When overloading is enabled, this is equivalent to
get
terminal #hyperlinkHoverUri
iconTitle
The terminal's so-called icon title, or Nothing
if no icon title has been set.
getTerminalIconTitle :: (MonadIO m, IsTerminal o) => o -> m Text Source #
Get the value of the “icon-title
” property.
When overloading is enabled, this is equivalent to
get
terminal #iconTitle
inputEnabled
Controls whether the terminal allows user input. When user input is disabled, key press and mouse button press and motion events are not sent to the terminal's child.
constructTerminalInputEnabled :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “input-enabled
” property. This is rarely needed directly, but it is used by new
.
getTerminalInputEnabled :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “input-enabled
” property.
When overloading is enabled, this is equivalent to
get
terminal #inputEnabled
setTerminalInputEnabled :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “input-enabled
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #inputEnabled:=
value ]
pointerAutohide
Controls the value of the terminal's mouse autohide setting. When autohiding is enabled, the mouse cursor will be hidden when the user presses a key and shown when the user moves the mouse.
constructTerminalPointerAutohide :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “pointer-autohide
” property. This is rarely needed directly, but it is used by new
.
getTerminalPointerAutohide :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “pointer-autohide
” property.
When overloading is enabled, this is equivalent to
get
terminal #pointerAutohide
setTerminalPointerAutohide :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “pointer-autohide
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #pointerAutohide:=
value ]
pty
The PTY object for the terminal.
clearTerminalPty :: (MonadIO m, IsTerminal o) => o -> m () Source #
Set the value of the “pty
” property to Nothing
.
When overloading is enabled, this is equivalent to
clear
#pty
constructTerminalPty :: (IsTerminal o, IsPty a) => a -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “pty
” property. This is rarely needed directly, but it is used by new
.
getTerminalPty :: (MonadIO m, IsTerminal o) => o -> m Pty Source #
Get the value of the “pty
” property.
When overloading is enabled, this is equivalent to
get
terminal #pty
setTerminalPty :: (MonadIO m, IsTerminal o, IsPty a) => o -> a -> m () Source #
Set the value of the “pty
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #pty:=
value ]
rewrapOnResize
Controls whether or not the terminal will rewrap its contents, including the scrollback buffer, whenever the terminal's width changes.
constructTerminalRewrapOnResize :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “rewrap-on-resize
” property. This is rarely needed directly, but it is used by new
.
getTerminalRewrapOnResize :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “rewrap-on-resize
” property.
When overloading is enabled, this is equivalent to
get
terminal #rewrapOnResize
setTerminalRewrapOnResize :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “rewrap-on-resize
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #rewrapOnResize:=
value ]
scrollOnKeystroke
Controls whether or not the terminal will forcibly scroll to the bottom of the viewable history when the user presses a key. Modifier keys do not trigger this behavior.
constructTerminalScrollOnKeystroke :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “scroll-on-keystroke
” property. This is rarely needed directly, but it is used by new
.
getTerminalScrollOnKeystroke :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “scroll-on-keystroke
” property.
When overloading is enabled, this is equivalent to
get
terminal #scrollOnKeystroke
setTerminalScrollOnKeystroke :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “scroll-on-keystroke
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #scrollOnKeystroke:=
value ]
scrollOnOutput
Controls whether or not the terminal will forcibly scroll to the bottom of the viewable history when the new data is received from the child.
constructTerminalScrollOnOutput :: IsTerminal o => Bool -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “scroll-on-output
” property. This is rarely needed directly, but it is used by new
.
getTerminalScrollOnOutput :: (MonadIO m, IsTerminal o) => o -> m Bool Source #
Get the value of the “scroll-on-output
” property.
When overloading is enabled, this is equivalent to
get
terminal #scrollOnOutput
setTerminalScrollOnOutput :: (MonadIO m, IsTerminal o) => o -> Bool -> m () Source #
Set the value of the “scroll-on-output
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #scrollOnOutput:=
value ]
scrollSpeed
The number of lines by which the buffer is moved when scrolling with a mouse wheel on top of the terminal Setting it to zero will cause the buffer to be moved by an amount depending on the number of visible rows the widget can display.
constructTerminalScrollSpeed :: IsTerminal o => Word32 -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “scroll-speed
” property. This is rarely needed directly, but it is used by new
.
getTerminalScrollSpeed :: (MonadIO m, IsTerminal o) => o -> m Word32 Source #
Get the value of the “scroll-speed
” property.
When overloading is enabled, this is equivalent to
get
terminal #scrollSpeed
setTerminalScrollSpeed :: (MonadIO m, IsTerminal o) => o -> Word32 -> m () Source #
Set the value of the “scroll-speed
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #scrollSpeed:=
value ]
scrollbackLines
The length of the scrollback buffer used by the terminal. The size of the scrollback buffer will be set to the larger of this value and the number of visible rows the widget can display, so 0 can safely be used to disable scrollback. Note that this setting only affects the normal screen buffer. For terminal types which have an alternate screen buffer, no scrollback is allowed on the alternate screen buffer.
constructTerminalScrollbackLines :: IsTerminal o => Word32 -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “scrollback-lines
” property. This is rarely needed directly, but it is used by new
.
getTerminalScrollbackLines :: (MonadIO m, IsTerminal o) => o -> m Word32 Source #
Get the value of the “scrollback-lines
” property.
When overloading is enabled, this is equivalent to
get
terminal #scrollbackLines
setTerminalScrollbackLines :: (MonadIO m, IsTerminal o) => o -> Word32 -> m () Source #
Set the value of the “scrollback-lines
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #scrollbackLines:=
value ]
textBlinkMode
Controls whether or not the terminal will allow blinking text.
Since: 0.52
constructTerminalTextBlinkMode :: IsTerminal o => TextBlinkMode -> IO (GValueConstruct o) Source #
Construct a GValueConstruct
with valid value for the “text-blink-mode
” property. This is rarely needed directly, but it is used by new
.
getTerminalTextBlinkMode :: (MonadIO m, IsTerminal o) => o -> m TextBlinkMode Source #
Get the value of the “text-blink-mode
” property.
When overloading is enabled, this is equivalent to
get
terminal #textBlinkMode
setTerminalTextBlinkMode :: (MonadIO m, IsTerminal o) => o -> TextBlinkMode -> m () Source #
Set the value of the “text-blink-mode
” property.
When overloading is enabled, this is equivalent to
set
terminal [ #textBlinkMode:=
value ]
windowTitle
The terminal's title.
getTerminalWindowTitle :: (MonadIO m, IsTerminal o) => o -> m (Maybe Text) Source #
Get the value of the “window-title
” property.
When overloading is enabled, this is equivalent to
get
terminal #windowTitle
wordCharExceptions
The set of characters which will be considered parts of a word when doing word-wise selection, in addition to the default which only considers alphanumeric characters part of a word.
If Nothing
, a built-in set is used.
Since: 0.40
getTerminalWordCharExceptions :: (MonadIO m, IsTerminal o) => o -> m Text Source #
Get the value of the “word-char-exceptions
” property.
When overloading is enabled, this is equivalent to
get
terminal #wordCharExceptions
Signals
bell
type C_TerminalBellCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalBellCallback = IO () Source #
This signal is emitted when the a child sends a bell request to the terminal.
afterTerminalBell :: (IsTerminal a, MonadIO m) => a -> TerminalBellCallback -> m SignalHandlerId Source #
Connect a signal handler for the “bell
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #bell callback
genClosure_TerminalBell :: TerminalBellCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalBellCallback :: C_TerminalBellCallback -> IO (FunPtr C_TerminalBellCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalBellCallback
.
noTerminalBellCallback :: Maybe TerminalBellCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalBellCallback
onTerminalBell :: (IsTerminal a, MonadIO m) => a -> TerminalBellCallback -> m SignalHandlerId Source #
Connect a signal handler for the “bell
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #bell callback
wrap_TerminalBellCallback :: TerminalBellCallback -> C_TerminalBellCallback Source #
Wrap a TerminalBellCallback
into a C_TerminalBellCallback
.
charSizeChanged
type C_TerminalCharSizeChangedCallback = Ptr () -> Word32 -> Word32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalCharSizeChangedCallback Source #
Emitted whenever the cell size changes, e.g. due to a change in font, font-scale or cell-width/height-scale.
Note that this signal should rather be called "cell-size-changed".
afterTerminalCharSizeChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCharSizeChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “char-size-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #charSizeChanged callback
genClosure_TerminalCharSizeChanged :: TerminalCharSizeChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalCharSizeChangedCallback :: C_TerminalCharSizeChangedCallback -> IO (FunPtr C_TerminalCharSizeChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalCharSizeChangedCallback
.
noTerminalCharSizeChangedCallback :: Maybe TerminalCharSizeChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalCharSizeChangedCallback
onTerminalCharSizeChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCharSizeChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “char-size-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #charSizeChanged callback
wrap_TerminalCharSizeChangedCallback :: TerminalCharSizeChangedCallback -> C_TerminalCharSizeChangedCallback Source #
Wrap a TerminalCharSizeChangedCallback
into a C_TerminalCharSizeChangedCallback
.
childExited
type C_TerminalChildExitedCallback = Ptr () -> Int32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalChildExitedCallback Source #
This signal is emitted when the terminal detects that a child
watched using terminalWatchChild
has exited.
afterTerminalChildExited :: (IsTerminal a, MonadIO m) => a -> TerminalChildExitedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “child-exited
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #childExited callback
genClosure_TerminalChildExited :: TerminalChildExitedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalChildExitedCallback :: C_TerminalChildExitedCallback -> IO (FunPtr C_TerminalChildExitedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalChildExitedCallback
.
noTerminalChildExitedCallback :: Maybe TerminalChildExitedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalChildExitedCallback
onTerminalChildExited :: (IsTerminal a, MonadIO m) => a -> TerminalChildExitedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “child-exited
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #childExited callback
wrap_TerminalChildExitedCallback :: TerminalChildExitedCallback -> C_TerminalChildExitedCallback Source #
Wrap a TerminalChildExitedCallback
into a C_TerminalChildExitedCallback
.
commit
type C_TerminalCommitCallback = Ptr () -> CString -> Word32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalCommitCallback Source #
Emitted whenever the terminal receives input from the user and prepares to send it to the child process. The signal is emitted even when there is no child process.
afterTerminalCommit :: (IsTerminal a, MonadIO m) => a -> TerminalCommitCallback -> m SignalHandlerId Source #
Connect a signal handler for the “commit
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #commit callback
genClosure_TerminalCommit :: TerminalCommitCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalCommitCallback :: C_TerminalCommitCallback -> IO (FunPtr C_TerminalCommitCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalCommitCallback
.
noTerminalCommitCallback :: Maybe TerminalCommitCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalCommitCallback
onTerminalCommit :: (IsTerminal a, MonadIO m) => a -> TerminalCommitCallback -> m SignalHandlerId Source #
Connect a signal handler for the “commit
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #commit callback
wrap_TerminalCommitCallback :: TerminalCommitCallback -> C_TerminalCommitCallback Source #
Wrap a TerminalCommitCallback
into a C_TerminalCommitCallback
.
contentsChanged
type C_TerminalContentsChangedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalContentsChangedCallback = IO () Source #
Emitted whenever the visible appearance of the terminal has changed.
Used primarily by VteTerminalAccessible
.
afterTerminalContentsChanged :: (IsTerminal a, MonadIO m) => a -> TerminalContentsChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “contents-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #contentsChanged callback
genClosure_TerminalContentsChanged :: TerminalContentsChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalContentsChangedCallback :: C_TerminalContentsChangedCallback -> IO (FunPtr C_TerminalContentsChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalContentsChangedCallback
.
noTerminalContentsChangedCallback :: Maybe TerminalContentsChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalContentsChangedCallback
onTerminalContentsChanged :: (IsTerminal a, MonadIO m) => a -> TerminalContentsChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “contents-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #contentsChanged callback
wrap_TerminalContentsChangedCallback :: TerminalContentsChangedCallback -> C_TerminalContentsChangedCallback Source #
Wrap a TerminalContentsChangedCallback
into a C_TerminalContentsChangedCallback
.
copyClipboard
type C_TerminalCopyClipboardCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalCopyClipboardCallback = IO () Source #
Emitted whenever terminalCopyClipboard
is called.
afterTerminalCopyClipboard :: (IsTerminal a, MonadIO m) => a -> TerminalCopyClipboardCallback -> m SignalHandlerId Source #
Connect a signal handler for the “copy-clipboard
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #copyClipboard callback
genClosure_TerminalCopyClipboard :: TerminalCopyClipboardCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalCopyClipboardCallback :: C_TerminalCopyClipboardCallback -> IO (FunPtr C_TerminalCopyClipboardCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalCopyClipboardCallback
.
noTerminalCopyClipboardCallback :: Maybe TerminalCopyClipboardCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalCopyClipboardCallback
onTerminalCopyClipboard :: (IsTerminal a, MonadIO m) => a -> TerminalCopyClipboardCallback -> m SignalHandlerId Source #
Connect a signal handler for the “copy-clipboard
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #copyClipboard callback
wrap_TerminalCopyClipboardCallback :: TerminalCopyClipboardCallback -> C_TerminalCopyClipboardCallback Source #
Wrap a TerminalCopyClipboardCallback
into a C_TerminalCopyClipboardCallback
.
currentDirectoryUriChanged
type C_TerminalCurrentDirectoryUriChangedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalCurrentDirectoryUriChangedCallback = IO () Source #
Emitted when the current directory URI is modified.
afterTerminalCurrentDirectoryUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCurrentDirectoryUriChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “current-directory-uri-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #currentDirectoryUriChanged callback
genClosure_TerminalCurrentDirectoryUriChanged :: TerminalCurrentDirectoryUriChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalCurrentDirectoryUriChangedCallback :: C_TerminalCurrentDirectoryUriChangedCallback -> IO (FunPtr C_TerminalCurrentDirectoryUriChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalCurrentDirectoryUriChangedCallback
.
noTerminalCurrentDirectoryUriChangedCallback :: Maybe TerminalCurrentDirectoryUriChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalCurrentDirectoryUriChangedCallback
onTerminalCurrentDirectoryUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCurrentDirectoryUriChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “current-directory-uri-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #currentDirectoryUriChanged callback
wrap_TerminalCurrentDirectoryUriChangedCallback :: TerminalCurrentDirectoryUriChangedCallback -> C_TerminalCurrentDirectoryUriChangedCallback Source #
currentFileUriChanged
type C_TerminalCurrentFileUriChangedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalCurrentFileUriChangedCallback = IO () Source #
Emitted when the current file URI is modified.
afterTerminalCurrentFileUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCurrentFileUriChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “current-file-uri-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #currentFileUriChanged callback
genClosure_TerminalCurrentFileUriChanged :: TerminalCurrentFileUriChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalCurrentFileUriChangedCallback :: C_TerminalCurrentFileUriChangedCallback -> IO (FunPtr C_TerminalCurrentFileUriChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalCurrentFileUriChangedCallback
.
noTerminalCurrentFileUriChangedCallback :: Maybe TerminalCurrentFileUriChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalCurrentFileUriChangedCallback
onTerminalCurrentFileUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalCurrentFileUriChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “current-file-uri-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #currentFileUriChanged callback
wrap_TerminalCurrentFileUriChangedCallback :: TerminalCurrentFileUriChangedCallback -> C_TerminalCurrentFileUriChangedCallback Source #
cursorMoved
type C_TerminalCursorMovedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalCursorMovedCallback = IO () Source #
Emitted whenever the cursor moves to a new character cell. Used
primarily by VteTerminalAccessible
.
afterTerminalCursorMoved :: (IsTerminal a, MonadIO m) => a -> TerminalCursorMovedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “cursor-moved
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #cursorMoved callback
genClosure_TerminalCursorMoved :: TerminalCursorMovedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalCursorMovedCallback :: C_TerminalCursorMovedCallback -> IO (FunPtr C_TerminalCursorMovedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalCursorMovedCallback
.
noTerminalCursorMovedCallback :: Maybe TerminalCursorMovedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalCursorMovedCallback
onTerminalCursorMoved :: (IsTerminal a, MonadIO m) => a -> TerminalCursorMovedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “cursor-moved
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #cursorMoved callback
wrap_TerminalCursorMovedCallback :: TerminalCursorMovedCallback -> C_TerminalCursorMovedCallback Source #
Wrap a TerminalCursorMovedCallback
into a C_TerminalCursorMovedCallback
.
decreaseFontSize
type C_TerminalDecreaseFontSizeCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalDecreaseFontSizeCallback = IO () Source #
Emitted when the user hits the '-' key while holding the Control key.
afterTerminalDecreaseFontSize :: (IsTerminal a, MonadIO m) => a -> TerminalDecreaseFontSizeCallback -> m SignalHandlerId Source #
Connect a signal handler for the “decrease-font-size
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #decreaseFontSize callback
genClosure_TerminalDecreaseFontSize :: TerminalDecreaseFontSizeCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalDecreaseFontSizeCallback :: C_TerminalDecreaseFontSizeCallback -> IO (FunPtr C_TerminalDecreaseFontSizeCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalDecreaseFontSizeCallback
.
noTerminalDecreaseFontSizeCallback :: Maybe TerminalDecreaseFontSizeCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalDecreaseFontSizeCallback
onTerminalDecreaseFontSize :: (IsTerminal a, MonadIO m) => a -> TerminalDecreaseFontSizeCallback -> m SignalHandlerId Source #
Connect a signal handler for the “decrease-font-size
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #decreaseFontSize callback
wrap_TerminalDecreaseFontSizeCallback :: TerminalDecreaseFontSizeCallback -> C_TerminalDecreaseFontSizeCallback Source #
deiconifyWindow
type C_TerminalDeiconifyWindowCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalDeiconifyWindowCallback = IO () Source #
Emitted at the child application's request.
afterTerminalDeiconifyWindow :: (IsTerminal a, MonadIO m) => a -> TerminalDeiconifyWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “deiconify-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #deiconifyWindow callback
genClosure_TerminalDeiconifyWindow :: TerminalDeiconifyWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalDeiconifyWindowCallback :: C_TerminalDeiconifyWindowCallback -> IO (FunPtr C_TerminalDeiconifyWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalDeiconifyWindowCallback
.
noTerminalDeiconifyWindowCallback :: Maybe TerminalDeiconifyWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalDeiconifyWindowCallback
onTerminalDeiconifyWindow :: (IsTerminal a, MonadIO m) => a -> TerminalDeiconifyWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “deiconify-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #deiconifyWindow callback
wrap_TerminalDeiconifyWindowCallback :: TerminalDeiconifyWindowCallback -> C_TerminalDeiconifyWindowCallback Source #
Wrap a TerminalDeiconifyWindowCallback
into a C_TerminalDeiconifyWindowCallback
.
encodingChanged
type C_TerminalEncodingChangedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalEncodingChangedCallback = IO () Source #
Emitted whenever the terminal's current encoding has changed, either as a result of receiving a control sequence which toggled between the local and UTF-8 encodings, or at the parent application's request.
afterTerminalEncodingChanged :: (IsTerminal a, MonadIO m) => a -> TerminalEncodingChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “encoding-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #encodingChanged callback
genClosure_TerminalEncodingChanged :: TerminalEncodingChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalEncodingChangedCallback :: C_TerminalEncodingChangedCallback -> IO (FunPtr C_TerminalEncodingChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalEncodingChangedCallback
.
noTerminalEncodingChangedCallback :: Maybe TerminalEncodingChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalEncodingChangedCallback
onTerminalEncodingChanged :: (IsTerminal a, MonadIO m) => a -> TerminalEncodingChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “encoding-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #encodingChanged callback
wrap_TerminalEncodingChangedCallback :: TerminalEncodingChangedCallback -> C_TerminalEncodingChangedCallback Source #
Wrap a TerminalEncodingChangedCallback
into a C_TerminalEncodingChangedCallback
.
eof
type C_TerminalEofCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalEofCallback = IO () Source #
Emitted when the terminal receives an end-of-file from a child which
is running in the terminal. This signal is frequently (but not
always) emitted with a Terminal
::child-exited
signal.
afterTerminalEof :: (IsTerminal a, MonadIO m) => a -> TerminalEofCallback -> m SignalHandlerId Source #
Connect a signal handler for the “eof
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #eof callback
genClosure_TerminalEof :: TerminalEofCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalEofCallback :: C_TerminalEofCallback -> IO (FunPtr C_TerminalEofCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalEofCallback
.
noTerminalEofCallback :: Maybe TerminalEofCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalEofCallback
onTerminalEof :: (IsTerminal a, MonadIO m) => a -> TerminalEofCallback -> m SignalHandlerId Source #
Connect a signal handler for the “eof
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #eof callback
wrap_TerminalEofCallback :: TerminalEofCallback -> C_TerminalEofCallback Source #
Wrap a TerminalEofCallback
into a C_TerminalEofCallback
.
hyperlinkHoverUriChanged
type C_TerminalHyperlinkHoverUriChangedCallback = Ptr () -> CString -> Ptr Rectangle -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalHyperlinkHoverUriChangedCallback Source #
= Text |
|
-> Rectangle |
|
-> IO () |
Emitted when the hovered hyperlink changes.
uri
and bbox
are owned by VTE, must not be modified, and might
change after the signal handlers returns.
The signal is not re-emitted when the bounding box changes for the same hyperlink. This might change in a future VTE version without notice.
Since: 0.50
afterTerminalHyperlinkHoverUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalHyperlinkHoverUriChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “hyperlink-hover-uri-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #hyperlinkHoverUriChanged callback
genClosure_TerminalHyperlinkHoverUriChanged :: TerminalHyperlinkHoverUriChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalHyperlinkHoverUriChangedCallback :: C_TerminalHyperlinkHoverUriChangedCallback -> IO (FunPtr C_TerminalHyperlinkHoverUriChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalHyperlinkHoverUriChangedCallback
.
noTerminalHyperlinkHoverUriChangedCallback :: Maybe TerminalHyperlinkHoverUriChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalHyperlinkHoverUriChangedCallback
onTerminalHyperlinkHoverUriChanged :: (IsTerminal a, MonadIO m) => a -> TerminalHyperlinkHoverUriChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “hyperlink-hover-uri-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #hyperlinkHoverUriChanged callback
wrap_TerminalHyperlinkHoverUriChangedCallback :: TerminalHyperlinkHoverUriChangedCallback -> C_TerminalHyperlinkHoverUriChangedCallback Source #
iconTitleChanged
type C_TerminalIconTitleChangedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalIconTitleChangedCallback = IO () Source #
Emitted when the terminal's icon_title
field is modified.
afterTerminalIconTitleChanged :: (IsTerminal a, MonadIO m) => a -> TerminalIconTitleChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “icon-title-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #iconTitleChanged callback
genClosure_TerminalIconTitleChanged :: TerminalIconTitleChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalIconTitleChangedCallback :: C_TerminalIconTitleChangedCallback -> IO (FunPtr C_TerminalIconTitleChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalIconTitleChangedCallback
.
noTerminalIconTitleChangedCallback :: Maybe TerminalIconTitleChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalIconTitleChangedCallback
onTerminalIconTitleChanged :: (IsTerminal a, MonadIO m) => a -> TerminalIconTitleChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “icon-title-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #iconTitleChanged callback
wrap_TerminalIconTitleChangedCallback :: TerminalIconTitleChangedCallback -> C_TerminalIconTitleChangedCallback Source #
iconifyWindow
type C_TerminalIconifyWindowCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalIconifyWindowCallback = IO () Source #
Emitted at the child application's request.
afterTerminalIconifyWindow :: (IsTerminal a, MonadIO m) => a -> TerminalIconifyWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “iconify-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #iconifyWindow callback
genClosure_TerminalIconifyWindow :: TerminalIconifyWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalIconifyWindowCallback :: C_TerminalIconifyWindowCallback -> IO (FunPtr C_TerminalIconifyWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalIconifyWindowCallback
.
noTerminalIconifyWindowCallback :: Maybe TerminalIconifyWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalIconifyWindowCallback
onTerminalIconifyWindow :: (IsTerminal a, MonadIO m) => a -> TerminalIconifyWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “iconify-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #iconifyWindow callback
wrap_TerminalIconifyWindowCallback :: TerminalIconifyWindowCallback -> C_TerminalIconifyWindowCallback Source #
Wrap a TerminalIconifyWindowCallback
into a C_TerminalIconifyWindowCallback
.
increaseFontSize
type C_TerminalIncreaseFontSizeCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalIncreaseFontSizeCallback = IO () Source #
Emitted when the user hits the '+' key while holding the Control key.
afterTerminalIncreaseFontSize :: (IsTerminal a, MonadIO m) => a -> TerminalIncreaseFontSizeCallback -> m SignalHandlerId Source #
Connect a signal handler for the “increase-font-size
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #increaseFontSize callback
genClosure_TerminalIncreaseFontSize :: TerminalIncreaseFontSizeCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalIncreaseFontSizeCallback :: C_TerminalIncreaseFontSizeCallback -> IO (FunPtr C_TerminalIncreaseFontSizeCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalIncreaseFontSizeCallback
.
noTerminalIncreaseFontSizeCallback :: Maybe TerminalIncreaseFontSizeCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalIncreaseFontSizeCallback
onTerminalIncreaseFontSize :: (IsTerminal a, MonadIO m) => a -> TerminalIncreaseFontSizeCallback -> m SignalHandlerId Source #
Connect a signal handler for the “increase-font-size
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #increaseFontSize callback
wrap_TerminalIncreaseFontSizeCallback :: TerminalIncreaseFontSizeCallback -> C_TerminalIncreaseFontSizeCallback Source #
lowerWindow
type C_TerminalLowerWindowCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalLowerWindowCallback = IO () Source #
Emitted at the child application's request.
afterTerminalLowerWindow :: (IsTerminal a, MonadIO m) => a -> TerminalLowerWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “lower-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #lowerWindow callback
genClosure_TerminalLowerWindow :: TerminalLowerWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalLowerWindowCallback :: C_TerminalLowerWindowCallback -> IO (FunPtr C_TerminalLowerWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalLowerWindowCallback
.
noTerminalLowerWindowCallback :: Maybe TerminalLowerWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalLowerWindowCallback
onTerminalLowerWindow :: (IsTerminal a, MonadIO m) => a -> TerminalLowerWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “lower-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #lowerWindow callback
wrap_TerminalLowerWindowCallback :: TerminalLowerWindowCallback -> C_TerminalLowerWindowCallback Source #
Wrap a TerminalLowerWindowCallback
into a C_TerminalLowerWindowCallback
.
maximizeWindow
type C_TerminalMaximizeWindowCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalMaximizeWindowCallback = IO () Source #
Emitted at the child application's request.
afterTerminalMaximizeWindow :: (IsTerminal a, MonadIO m) => a -> TerminalMaximizeWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “maximize-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #maximizeWindow callback
genClosure_TerminalMaximizeWindow :: TerminalMaximizeWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalMaximizeWindowCallback :: C_TerminalMaximizeWindowCallback -> IO (FunPtr C_TerminalMaximizeWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalMaximizeWindowCallback
.
noTerminalMaximizeWindowCallback :: Maybe TerminalMaximizeWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalMaximizeWindowCallback
onTerminalMaximizeWindow :: (IsTerminal a, MonadIO m) => a -> TerminalMaximizeWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “maximize-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #maximizeWindow callback
wrap_TerminalMaximizeWindowCallback :: TerminalMaximizeWindowCallback -> C_TerminalMaximizeWindowCallback Source #
Wrap a TerminalMaximizeWindowCallback
into a C_TerminalMaximizeWindowCallback
.
moveWindow
type C_TerminalMoveWindowCallback = Ptr () -> Word32 -> Word32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalMoveWindowCallback Source #
= Word32 |
|
-> Word32 |
|
-> IO () |
Emitted at the child application's request.
afterTerminalMoveWindow :: (IsTerminal a, MonadIO m) => a -> TerminalMoveWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “move-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #moveWindow callback
genClosure_TerminalMoveWindow :: TerminalMoveWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalMoveWindowCallback :: C_TerminalMoveWindowCallback -> IO (FunPtr C_TerminalMoveWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalMoveWindowCallback
.
noTerminalMoveWindowCallback :: Maybe TerminalMoveWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalMoveWindowCallback
onTerminalMoveWindow :: (IsTerminal a, MonadIO m) => a -> TerminalMoveWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “move-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #moveWindow callback
wrap_TerminalMoveWindowCallback :: TerminalMoveWindowCallback -> C_TerminalMoveWindowCallback Source #
Wrap a TerminalMoveWindowCallback
into a C_TerminalMoveWindowCallback
.
notificationReceived
type C_TerminalNotificationReceivedCallback = Ptr () -> CString -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalNotificationReceivedCallback Source #
Emitted when a process running in the terminal wants to send a notification to the desktop environment.
afterTerminalNotificationReceived :: (IsTerminal a, MonadIO m) => a -> TerminalNotificationReceivedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “notification-received
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #notificationReceived callback
genClosure_TerminalNotificationReceived :: TerminalNotificationReceivedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalNotificationReceivedCallback :: C_TerminalNotificationReceivedCallback -> IO (FunPtr C_TerminalNotificationReceivedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalNotificationReceivedCallback
.
noTerminalNotificationReceivedCallback :: Maybe TerminalNotificationReceivedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalNotificationReceivedCallback
onTerminalNotificationReceived :: (IsTerminal a, MonadIO m) => a -> TerminalNotificationReceivedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “notification-received
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #notificationReceived callback
wrap_TerminalNotificationReceivedCallback :: TerminalNotificationReceivedCallback -> C_TerminalNotificationReceivedCallback Source #
pasteClipboard
type C_TerminalPasteClipboardCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalPasteClipboardCallback = IO () Source #
Emitted whenever terminalPasteClipboard
is called.
afterTerminalPasteClipboard :: (IsTerminal a, MonadIO m) => a -> TerminalPasteClipboardCallback -> m SignalHandlerId Source #
Connect a signal handler for the “paste-clipboard
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #pasteClipboard callback
genClosure_TerminalPasteClipboard :: TerminalPasteClipboardCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalPasteClipboardCallback :: C_TerminalPasteClipboardCallback -> IO (FunPtr C_TerminalPasteClipboardCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalPasteClipboardCallback
.
noTerminalPasteClipboardCallback :: Maybe TerminalPasteClipboardCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalPasteClipboardCallback
onTerminalPasteClipboard :: (IsTerminal a, MonadIO m) => a -> TerminalPasteClipboardCallback -> m SignalHandlerId Source #
Connect a signal handler for the “paste-clipboard
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #pasteClipboard callback
wrap_TerminalPasteClipboardCallback :: TerminalPasteClipboardCallback -> C_TerminalPasteClipboardCallback Source #
Wrap a TerminalPasteClipboardCallback
into a C_TerminalPasteClipboardCallback
.
raiseWindow
type C_TerminalRaiseWindowCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalRaiseWindowCallback = IO () Source #
Emitted at the child application's request.
afterTerminalRaiseWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRaiseWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “raise-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #raiseWindow callback
genClosure_TerminalRaiseWindow :: TerminalRaiseWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalRaiseWindowCallback :: C_TerminalRaiseWindowCallback -> IO (FunPtr C_TerminalRaiseWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalRaiseWindowCallback
.
noTerminalRaiseWindowCallback :: Maybe TerminalRaiseWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalRaiseWindowCallback
onTerminalRaiseWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRaiseWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “raise-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #raiseWindow callback
wrap_TerminalRaiseWindowCallback :: TerminalRaiseWindowCallback -> C_TerminalRaiseWindowCallback Source #
Wrap a TerminalRaiseWindowCallback
into a C_TerminalRaiseWindowCallback
.
refreshWindow
type C_TerminalRefreshWindowCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalRefreshWindowCallback = IO () Source #
Emitted at the child application's request.
afterTerminalRefreshWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRefreshWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “refresh-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #refreshWindow callback
genClosure_TerminalRefreshWindow :: TerminalRefreshWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalRefreshWindowCallback :: C_TerminalRefreshWindowCallback -> IO (FunPtr C_TerminalRefreshWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalRefreshWindowCallback
.
noTerminalRefreshWindowCallback :: Maybe TerminalRefreshWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalRefreshWindowCallback
onTerminalRefreshWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRefreshWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “refresh-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #refreshWindow callback
wrap_TerminalRefreshWindowCallback :: TerminalRefreshWindowCallback -> C_TerminalRefreshWindowCallback Source #
Wrap a TerminalRefreshWindowCallback
into a C_TerminalRefreshWindowCallback
.
resizeWindow
type C_TerminalResizeWindowCallback = Ptr () -> Word32 -> Word32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalResizeWindowCallback Source #
Emitted at the child application's request.
afterTerminalResizeWindow :: (IsTerminal a, MonadIO m) => a -> TerminalResizeWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “resize-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #resizeWindow callback
genClosure_TerminalResizeWindow :: TerminalResizeWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalResizeWindowCallback :: C_TerminalResizeWindowCallback -> IO (FunPtr C_TerminalResizeWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalResizeWindowCallback
.
noTerminalResizeWindowCallback :: Maybe TerminalResizeWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalResizeWindowCallback
onTerminalResizeWindow :: (IsTerminal a, MonadIO m) => a -> TerminalResizeWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “resize-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #resizeWindow callback
wrap_TerminalResizeWindowCallback :: TerminalResizeWindowCallback -> C_TerminalResizeWindowCallback Source #
Wrap a TerminalResizeWindowCallback
into a C_TerminalResizeWindowCallback
.
restoreWindow
type C_TerminalRestoreWindowCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalRestoreWindowCallback = IO () Source #
Emitted at the child application's request.
afterTerminalRestoreWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRestoreWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “restore-window
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #restoreWindow callback
genClosure_TerminalRestoreWindow :: TerminalRestoreWindowCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalRestoreWindowCallback :: C_TerminalRestoreWindowCallback -> IO (FunPtr C_TerminalRestoreWindowCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalRestoreWindowCallback
.
noTerminalRestoreWindowCallback :: Maybe TerminalRestoreWindowCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalRestoreWindowCallback
onTerminalRestoreWindow :: (IsTerminal a, MonadIO m) => a -> TerminalRestoreWindowCallback -> m SignalHandlerId Source #
Connect a signal handler for the “restore-window
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #restoreWindow callback
wrap_TerminalRestoreWindowCallback :: TerminalRestoreWindowCallback -> C_TerminalRestoreWindowCallback Source #
Wrap a TerminalRestoreWindowCallback
into a C_TerminalRestoreWindowCallback
.
selectionChanged
type C_TerminalSelectionChangedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalSelectionChangedCallback = IO () Source #
Emitted whenever the contents of terminal's selection changes.
afterTerminalSelectionChanged :: (IsTerminal a, MonadIO m) => a -> TerminalSelectionChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “selection-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #selectionChanged callback
genClosure_TerminalSelectionChanged :: TerminalSelectionChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalSelectionChangedCallback :: C_TerminalSelectionChangedCallback -> IO (FunPtr C_TerminalSelectionChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalSelectionChangedCallback
.
noTerminalSelectionChangedCallback :: Maybe TerminalSelectionChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalSelectionChangedCallback
onTerminalSelectionChanged :: (IsTerminal a, MonadIO m) => a -> TerminalSelectionChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “selection-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #selectionChanged callback
wrap_TerminalSelectionChangedCallback :: TerminalSelectionChangedCallback -> C_TerminalSelectionChangedCallback Source #
textDeleted
type C_TerminalTextDeletedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalTextDeletedCallback = IO () Source #
An internal signal used for communication between the terminal and its accessibility peer. May not be emitted under certain circumstances.
afterTerminalTextDeleted :: (IsTerminal a, MonadIO m) => a -> TerminalTextDeletedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “text-deleted
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #textDeleted callback
genClosure_TerminalTextDeleted :: TerminalTextDeletedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalTextDeletedCallback :: C_TerminalTextDeletedCallback -> IO (FunPtr C_TerminalTextDeletedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalTextDeletedCallback
.
noTerminalTextDeletedCallback :: Maybe TerminalTextDeletedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalTextDeletedCallback
onTerminalTextDeleted :: (IsTerminal a, MonadIO m) => a -> TerminalTextDeletedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “text-deleted
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #textDeleted callback
wrap_TerminalTextDeletedCallback :: TerminalTextDeletedCallback -> C_TerminalTextDeletedCallback Source #
Wrap a TerminalTextDeletedCallback
into a C_TerminalTextDeletedCallback
.
textInserted
type C_TerminalTextInsertedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalTextInsertedCallback = IO () Source #
An internal signal used for communication between the terminal and its accessibility peer. May not be emitted under certain circumstances.
afterTerminalTextInserted :: (IsTerminal a, MonadIO m) => a -> TerminalTextInsertedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “text-inserted
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #textInserted callback
genClosure_TerminalTextInserted :: TerminalTextInsertedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalTextInsertedCallback :: C_TerminalTextInsertedCallback -> IO (FunPtr C_TerminalTextInsertedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalTextInsertedCallback
.
noTerminalTextInsertedCallback :: Maybe TerminalTextInsertedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalTextInsertedCallback
onTerminalTextInserted :: (IsTerminal a, MonadIO m) => a -> TerminalTextInsertedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “text-inserted
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #textInserted callback
wrap_TerminalTextInsertedCallback :: TerminalTextInsertedCallback -> C_TerminalTextInsertedCallback Source #
Wrap a TerminalTextInsertedCallback
into a C_TerminalTextInsertedCallback
.
textModified
type C_TerminalTextModifiedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalTextModifiedCallback = IO () Source #
An internal signal used for communication between the terminal and its accessibility peer. May not be emitted under certain circumstances.
afterTerminalTextModified :: (IsTerminal a, MonadIO m) => a -> TerminalTextModifiedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “text-modified
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #textModified callback
genClosure_TerminalTextModified :: TerminalTextModifiedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalTextModifiedCallback :: C_TerminalTextModifiedCallback -> IO (FunPtr C_TerminalTextModifiedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalTextModifiedCallback
.
noTerminalTextModifiedCallback :: Maybe TerminalTextModifiedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalTextModifiedCallback
onTerminalTextModified :: (IsTerminal a, MonadIO m) => a -> TerminalTextModifiedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “text-modified
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #textModified callback
wrap_TerminalTextModifiedCallback :: TerminalTextModifiedCallback -> C_TerminalTextModifiedCallback Source #
Wrap a TerminalTextModifiedCallback
into a C_TerminalTextModifiedCallback
.
textScrolled
type C_TerminalTextScrolledCallback = Ptr () -> Int32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalTextScrolledCallback Source #
An internal signal used for communication between the terminal and its accessibility peer. May not be emitted under certain circumstances.
afterTerminalTextScrolled :: (IsTerminal a, MonadIO m) => a -> TerminalTextScrolledCallback -> m SignalHandlerId Source #
Connect a signal handler for the “text-scrolled
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #textScrolled callback
genClosure_TerminalTextScrolled :: TerminalTextScrolledCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalTextScrolledCallback :: C_TerminalTextScrolledCallback -> IO (FunPtr C_TerminalTextScrolledCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalTextScrolledCallback
.
noTerminalTextScrolledCallback :: Maybe TerminalTextScrolledCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalTextScrolledCallback
onTerminalTextScrolled :: (IsTerminal a, MonadIO m) => a -> TerminalTextScrolledCallback -> m SignalHandlerId Source #
Connect a signal handler for the “text-scrolled
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #textScrolled callback
wrap_TerminalTextScrolledCallback :: TerminalTextScrolledCallback -> C_TerminalTextScrolledCallback Source #
Wrap a TerminalTextScrolledCallback
into a C_TerminalTextScrolledCallback
.
windowTitleChanged
type C_TerminalWindowTitleChangedCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TerminalWindowTitleChangedCallback = IO () Source #
Emitted when the terminal's window_title
field is modified.
afterTerminalWindowTitleChanged :: (IsTerminal a, MonadIO m) => a -> TerminalWindowTitleChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “window-title-changed
” signal, to be run after the default handler.
When overloading is enabled, this is equivalent to
after
terminal #windowTitleChanged callback
genClosure_TerminalWindowTitleChanged :: TerminalWindowTitleChangedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_TerminalWindowTitleChangedCallback :: C_TerminalWindowTitleChangedCallback -> IO (FunPtr C_TerminalWindowTitleChangedCallback) Source #
Generate a function pointer callable from C code, from a C_TerminalWindowTitleChangedCallback
.
noTerminalWindowTitleChangedCallback :: Maybe TerminalWindowTitleChangedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TerminalWindowTitleChangedCallback
onTerminalWindowTitleChanged :: (IsTerminal a, MonadIO m) => a -> TerminalWindowTitleChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the “window-title-changed
” signal, to be run before the default handler.
When overloading is enabled, this is equivalent to
on
terminal #windowTitleChanged callback