Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides an abstract interface for performing terminal
output. The only user-facing part of this API is Output
.
- data Output = Output {
- terminalID :: String
- releaseTerminal :: forall m. MonadIO m => m ()
- reserveDisplay :: forall m. MonadIO m => m ()
- releaseDisplay :: forall m. MonadIO m => m ()
- displayBounds :: forall m. MonadIO m => m DisplayRegion
- outputByteBuffer :: ByteString -> IO ()
- contextColorCount :: Int
- supportsCursorVisibility :: Bool
- supportsMode :: Mode -> Bool
- setMode :: forall m. MonadIO m => Mode -> Bool -> m ()
- getModeStatus :: forall m. MonadIO m => Mode -> m Bool
- assumedStateRef :: IORef AssumedState
- mkDisplayContext :: forall m. MonadIO m => Output -> DisplayRegion -> m DisplayContext
- ringTerminalBell :: forall m. MonadIO m => m ()
- supportsBell :: forall m. MonadIO m => m Bool
- data AssumedState = AssumedState {}
- data DisplayContext = DisplayContext {
- contextDevice :: Output
- contextRegion :: DisplayRegion
- writeMoveCursor :: Int -> Int -> Write
- writeShowCursor :: Write
- writeHideCursor :: Write
- writeSetAttr :: FixedAttr -> Attr -> DisplayAttrDiff -> Write
- writeDefaultAttr :: Write
- writeRowEnd :: Write
- inlineHack :: IO ()
- data Mode
- = Mouse
- | BracketedPaste
- | Focus
- displayContext :: MonadIO m => Output -> DisplayRegion -> m DisplayContext
- outputPicture :: MonadIO m => DisplayContext -> Picture -> m ()
- initialAssumedState :: AssumedState
- limitAttrForDisplay :: Output -> Attr -> Attr
Documentation
The Vty terminal output interface.
Output | |
|
data AssumedState Source #
data DisplayContext Source #
DisplayContext | |
|
Modal terminal features that can be enabled and disabled.
Mouse | Mouse mode (whether the terminal is configured to provide mouse input events) |
BracketedPaste | Paste mode (whether the terminal is configured to provide events on OS pastes) |
Focus | Focus-in/focus-out events (whether the terminal is configured to provide events on focus change) |
displayContext :: MonadIO m => Output -> DisplayRegion -> m DisplayContext Source #
outputPicture :: MonadIO m => DisplayContext -> Picture -> m () Source #
Displays the given Picture
.
- The image is cropped to the display size.
- Converted into a sequence of attribute changes and text spans.
- The cursor is hidden.
- Serialized to the display.
- The cursor is then shown and positioned or kept hidden.