vty-5.2.9: A simple terminal UI library

Safe HaskellNone
LanguageHaskell2010

Graphics.Vty.Output

Synopsis

Documentation

outputForConfig :: Config -> IO Output Source

Returns a Output for the terminal specified in Config

The specific Output implementation used is hidden from the API user. All terminal implementations are assumed to perform more, or less, the same. Currently, all implementations use terminfo for at least some terminal specific information.

Specifics about it being based on terminfo are hidden from the API user. If a terminal implementation is developed for a terminal without terminfo support then Vty should work as expected on that terminal.

Selection of a terminal is done as follows:

  • If TERM == xterm use XTermColor.
  • for any other TERM value TerminfoBased is used.

todo add an implementation for windows that does not depend on terminfo. Should be installable with only what is provided in the haskell platform. Use ansi-terminal

setCursorPos :: MonadIO m => Output -> Int -> Int -> m () Source

Sets the cursor position to the given output column and row.

This is not necessarially the same as the character position with the same coordinates. Characters can be a variable number of columns in width.

Currently, the only way to set the cursor position to a given character coordinate is to specify the coordinate in the Picture instance provided to outputPicture or refresh.

hideCursor :: MonadIO m => Output -> m () Source

Hides the cursor

showCursor :: MonadIO m => Output -> m () Source

Shows the cursor

data Output Source

Constructors

Output 

Fields

terminalID :: String

Text identifier for the output device. Used for debugging.

releaseTerminal :: MonadIO m => m ()
 
reserveDisplay :: MonadIO m => m ()

Clear the display and initialize the terminal to some initial display state.

The expectation of a program is that the display starts in some initial state. The initial state would consist of fixed values:

  • cursor at top left
  • UTF-8 character encoding
  • drawing characteristics are the default

The abstract operation I think all these behaviors are instances of is reserving exclusive access to a display such that:

  • The previous state cannot be determined
  • When exclusive access to a display is released the display returns to the previous state.
releaseDisplay :: MonadIO m => m ()

Return the display to the state before reserveDisplay If no previous state then set the display state to the initial state.

displayBounds :: MonadIO m => m DisplayRegion

Returns the current display bounds.

outputByteBuffer :: ByteString -> IO ()

Output the byte string to the terminal device.

contextColorCount :: Int

Maximum number of colors supported by the context.

supportsCursorVisibility :: Bool

if the cursor can be shown / hidden

assumedStateRef :: IORef AssumedState
 
mkDisplayContext :: MonadIO m => Output -> DisplayRegion -> m DisplayContext

Acquire display access to the given region of the display. Currently all regions have the upper left corner of (0,0) and the lower right corner at (max displayWidth providedWidth, max displayHeight providedHeight)

data DisplayContext Source

Constructors

DisplayContext 

Fields

contextDevice :: Output
 
contextRegion :: DisplayRegion

Provide the bounds of the display context.

writeMoveCursor :: Int -> Int -> Write
 
writeShowCursor :: Write
 
writeHideCursor :: Write
 
writeSetAttr :: FixedAttr -> Attr -> DisplayAttrDiff -> Write
 
writeDefaultAttr :: Write

Reset the display attributes to the default display attributes

writeRowEnd :: Write
 
inlineHack :: IO ()

See inlineHack

outputPicture :: MonadIO m => DisplayContext -> Picture -> m () Source

Displays the given Picture.

  1. The image is cropped to the display size.

    1. Converted into a sequence of attribute changes and text spans.
    2. The cursor is hidden.
    3. Serialized to the display.
    4. The cursor is then shown and positioned or kept hidden.

todo: specify possible IO exceptions. abstract from IO monad to a MonadIO instance.