-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A simple terminal UI library -- -- vty is terminal GUI library in the niche of ncurses. It is intended to -- be easy to use, have no confusing corner cases, and good support for -- common terminal types. -- -- See the vty-examples package as well as the program -- test/interactive_terminal_test.hs included in the -- vty package for examples on how to use the library. -- -- Import the Graphics.Vty convenience module to get access to the -- core parts of the library. -- -- © 2006-2007 Stefan O'Rear; BSD3 license. -- -- © Corey O'Connor; BSD3 license. -- -- © Jonathan Daugherty; BSD3 license. @package vty @version 5.15 module Graphics.Vty.Input.Events -- | Representations of non-modifier keys. -- -- data Key KEsc :: Key KChar :: Char -> Key KBS :: Key KEnter :: Key KLeft :: Key KRight :: Key KUp :: Key KDown :: Key KUpLeft :: Key KUpRight :: Key KDownLeft :: Key KDownRight :: Key KCenter :: Key KFun :: Int -> Key KBackTab :: Key KPrtScr :: Key KPause :: Key KIns :: Key KHome :: Key KPageUp :: Key KDel :: Key KEnd :: Key KPageDown :: Key KBegin :: Key KMenu :: Key -- | Modifier keys. Key codes are interpreted such that users are more -- likely to have Meta than Alt; for instance on the PC Linux console, -- MMeta will generally correspond to the physical Alt key. data Modifier MShift :: Modifier MCtrl :: Modifier MMeta :: Modifier MAlt :: Modifier -- | Mouse buttons. data Button BLeft :: Button BMiddle :: Button BRight :: Button -- | Events. data Event -- | A keyboard key was pressed with the specified modifiers. EvKey :: Key -> [Modifier] -> Event -- | A mouse button was pressed at the specified column and row. Any -- modifiers available in the event are also provided. EvMouseDown :: Int -> Int -> Button -> [Modifier] -> Event -- | A mouse button was released at the specified column and row. Some -- terminals report only that a button was released without specifying -- which one; in that case, Nothing is provided. Otherwise Just the -- button released is included in the event. EvMouseUp :: Int -> Int -> (Maybe Button) -> Event -- | If read from eventChannel this is the size at the time of the -- signal. If read from nextEvent this is the size at the time -- the event was processed by Vty. Typically these are the same, but if -- somebody is resizing the terminal quickly they can be different. EvResize :: Int -> Int -> Event -- | A paste event occurs when a bracketed paste input sequence is -- received. For terminals that support bracketed paste mode, these -- events will be triggered on a paste event. Terminals that do not -- support bracketed pastes will send the paste contents as ordinary -- input (which is probably bad, so beware!) Note that the data is -- provided in raw form and you'll have to decode (e.g. as UTF-8) if -- that's what your application expects. EvPaste :: ByteString -> Event type ClassifyMap = [(String, Event)] instance GHC.Generics.Generic Graphics.Vty.Input.Events.Event instance GHC.Classes.Ord Graphics.Vty.Input.Events.Event instance GHC.Read.Read Graphics.Vty.Input.Events.Event instance GHC.Show.Show Graphics.Vty.Input.Events.Event instance GHC.Classes.Eq Graphics.Vty.Input.Events.Event instance GHC.Generics.Generic Graphics.Vty.Input.Events.Button instance GHC.Classes.Ord Graphics.Vty.Input.Events.Button instance GHC.Read.Read Graphics.Vty.Input.Events.Button instance GHC.Show.Show Graphics.Vty.Input.Events.Button instance GHC.Classes.Eq Graphics.Vty.Input.Events.Button instance GHC.Generics.Generic Graphics.Vty.Input.Events.Modifier instance GHC.Classes.Ord Graphics.Vty.Input.Events.Modifier instance GHC.Read.Read Graphics.Vty.Input.Events.Modifier instance GHC.Show.Show Graphics.Vty.Input.Events.Modifier instance GHC.Classes.Eq Graphics.Vty.Input.Events.Modifier instance GHC.Generics.Generic Graphics.Vty.Input.Events.Key instance GHC.Classes.Ord Graphics.Vty.Input.Events.Key instance GHC.Read.Read Graphics.Vty.Input.Events.Key instance GHC.Show.Show Graphics.Vty.Input.Events.Key instance GHC.Classes.Eq Graphics.Vty.Input.Events.Key module Graphics.Vty.Input.Terminfo -- | Queries the terminal for all capability-based input sequences and then -- adds on a terminal-dependent input sequence mapping. -- -- For reference see: -- -- -- -- Terminfo is incomplete. The vim source implies that terminfo is also -- incorrect. Vty assumes that the internal terminfo table added to the -- system-provided terminfo table is correct. -- -- The procedure used here is: -- --
    --
  1. Build terminfo table for all caps. Missing caps are not -- added.
  2. --
  3. Add tables for visible chars, esc, del, ctrl, and meta.
  4. --
  5. Add internally-defined table for given terminal type.
  6. --
-- -- Precedence is currently implicit in the compile algorithm. classifyMapForTerm :: String -> Terminal -> ClassifyMap -- | The key table applicable to all terminals. -- -- Note that some of these entries are probably only applicable to -- ANSI/VT100 terminals. universalTable :: ClassifyMap capsClassifyMap :: Terminal -> [(String, Event)] -> ClassifyMap -- | Tables specific to a given terminal that are not derivable from -- terminfo. -- -- Note that this adds the ANSIVT100VT50 tables regardless of term -- identifier. termSpecificTables :: String -> [ClassifyMap] -- | Visible characters in the ISO-8859-1 and UTF-8 common set. -- -- We limit to < 0xC1. The UTF8 sequence detector will catch all -- values 0xC2 and above before this classify table is reached. visibleChars :: ClassifyMap -- | Non-printable characters in the ISO-8859-1 and UTF-8 common set -- translated to ctrl + char. -- -- This treats CTRL-i the same as tab. ctrlChars :: ClassifyMap -- | Ctrl+Meta+Char ctrlMetaChars :: ClassifyMap -- | Esc, meta-esc, delete, meta-delete, enter, meta-enter. specialSupportKeys :: ClassifyMap -- | A classification table directly generated from terminfo cap strings. -- These are: -- -- keysFromCapsTable :: ClassifyMap -- | Cap names for function keys. functionKeyCapsTable :: ClassifyMap -- | This module exports the input classification type to avoid import -- cycles between other modules that need this. module Graphics.Vty.Input.Classify.Types data KClass -- | A valid event was parsed. Any unused characters from the input stream -- are also provided. Valid :: Event -> [Char] -> KClass -- | The input characters did not represent a valid event. Invalid :: KClass -- | The input characters form the prefix of a valid event character -- sequence. Prefix :: KClass instance GHC.Classes.Eq Graphics.Vty.Input.Classify.Types.KClass instance GHC.Show.Show Graphics.Vty.Input.Classify.Types.KClass -- | This module provides bracketed paste support as described at -- -- http://cirw.in/blog/bracketed-paste module Graphics.Vty.Input.Paste -- | Parse a bracketed paste. This should only be called on a string if -- both bracketedPasteStarted and bracketedPasteFinished -- return True. parseBracketedPaste :: String -> KClass -- | Does the input start a bracketed paste? bracketedPasteStarted :: String -> Bool -- | Does the input contain a complete bracketed paste? bracketedPasteFinished :: String -> Bool -- | This module provides a simple parser for parsing input event control -- sequences. module Graphics.Vty.Input.Classify.Parse type Parser a = MaybeT (State String) a -- | Run a parser on a given input string. If the parser fails, return -- Invalid. Otherwise return the valid event (Valid) and -- the remaining unparsed characters. runParser :: String -> Parser Event -> KClass -- | Fail a parsing operation. failParse :: Parser a -- | Read an integer from the input stream. If an integer cannot be read, -- fail parsing. E.g. calling readInt on an input of "123abc" will return -- '123' and consume those characters. readInt :: Parser Int -- | Read a character from the input stream. If one cannot be read (e.g. we -- are out of characters), fail parsing. readChar :: Parser Char -- | Read a character from the input stream and fail parsing if it is not -- the specified character. expectChar :: Char -> Parser () -- | This module provides parsers for mouse events for both "normal" and -- "extended" modes. This implementation was informed by -- -- -- http://invisible-island.net/xterm/ctlseqs/ctlseqs.html#h2-Mouse-Tracking module Graphics.Vty.Input.Mouse -- | These sequences set xterm-based terminals to send mouse event -- sequences. requestMouseEvents :: String -- | These sequences disable mouse events. disableMouseEvents :: String -- | Does the specified string begin with a mouse event? isMouseEvent :: String -> Bool -- | Attempt to lassify an input string as a mouse event. classifyMouseEvent :: String -> KClass module Graphics.Vty.Error -- | The type of exceptions specific to vty. -- -- These have fully qualified names by default since, IMO, exception -- handling requires this. data VtyException -- | Uncategorized failure specific to vty. VtyFailure :: String -> VtyException -- | Vty supports a configuration file format and associated Config -- data type. The Config can be provided to mkVty to -- customize the application's use of Vty. -- -- Lines in config files that fail to parse are ignored. Later entries -- take precedence over earlier ones. -- --

Debug

-- --

debugLog

-- -- Format: -- --
--   "debugLog" string
--   
-- -- The value of the environment variable VTY_DEBUG_LOG is -- equivalent to a debugLog entry at the end of the last config file. -- --

Input Processing

-- --

map

-- -- Format: -- --
--   "map" term string key modifier_list
--   where
--       key := KEsc | KChar Char | KBS ... (same as Key)
--       modifier_list := "[" modifier+ "]"
--       modifier := MShift | MCtrl | MMeta | MAlt
--       term := "_" | string
--   
-- -- E.g., if the contents are -- --
--   map _       "\ESC[B"    KUp   []
--   map _       "\ESC[1;3B" KDown [MAlt]
--   map "xterm" "\ESC[D"    KLeft []
--   
-- -- Then the bytes "\ESC[B" will result in the KUp event on all -- terminals. The bytes "\ESC[1;3B" will result in the event -- KDown with the MAlt modifier on all terminals. The bytes -- "\ESC[D" will result in the KLeft event when TERM is -- xterm. -- -- If a debug log is requested then vty will output the current input -- table to the log in the above format. A workflow for using this is to -- set VTY_DEBUG_LOG. Run the application. Check the debug log -- for incorrect mappings. Add corrected mappings to -- $HOME.vtyconfig. module Graphics.Vty.Config -- | Mappings from input bytes to event in the order specified. Later -- entries take precedence over earlier in the case multiple entries have -- the same byte string. type InputMap = [(Maybe String, String, Event)] -- | A Vty configuration. data Config Config :: Maybe Int -> Maybe Int -> Maybe Bool -> Maybe Bool -> Maybe FilePath -> InputMap -> Maybe Fd -> Maybe Fd -> Maybe String -> Config -- | The default is 1 character. [vmin] :: Config -> Maybe Int -- | The default is 100 milliseconds, 0.1 seconds. [vtime] :: Config -> Maybe Int -- | The default is False. [mouseMode] :: Config -> Maybe Bool -- | The default is False. [bracketedPasteMode] :: Config -> Maybe Bool -- | Debug information is appended to this file if not Nothing. [debugLog] :: Config -> Maybe FilePath -- | The (input byte, output event) pairs extend the internal input table -- of VTY and the table from terminfo. -- -- See Graphics.Vty.Config module documentation for documentation -- of the map directive. [inputMap] :: Config -> InputMap -- | The input file descriptor to use. The default is stdInput [inputFd] :: Config -> Maybe Fd -- | The output file descriptor to use. The default is stdOutput [outputFd] :: Config -> Maybe Fd -- | The terminal name used to look up terminfo capabilities. The default -- is the value of the TERM environment variable. [termName] :: Config -> Maybe String -- | Type of errors that can be thrown when configuring VTY data VtyConfigurationError -- | TERM environment variable not set VtyMissingTermEnvVar :: VtyConfigurationError -- | Load a configuration from -- getAppUserDataDirectory/config and -- $VTY_CONFIG_FILE. userConfig :: IO Config overrideEnvConfig :: IO Config -- | Configures VTY using defaults suitable for terminals. This function -- can raise VtyConfigurationError. standardIOConfig :: IO Config runParseConfig :: String -> ByteString -> Config parseConfigFile :: FilePath -> IO Config defaultConfig :: Config instance GHC.Classes.Eq Graphics.Vty.Config.Config instance GHC.Show.Show Graphics.Vty.Config.Config instance GHC.Classes.Eq Graphics.Vty.Config.VtyConfigurationError instance GHC.Show.Show Graphics.Vty.Config.VtyConfigurationError instance GHC.Exception.Exception Graphics.Vty.Config.VtyConfigurationError instance GHC.Base.Monoid Graphics.Vty.Config.Config instance Graphics.Vty.Config.Parse GHC.Types.Char instance Graphics.Vty.Config.Parse GHC.Types.Int instance Graphics.Vty.Config.Parse Graphics.Vty.Input.Events.Key instance Graphics.Vty.Config.Parse Graphics.Vty.Input.Events.Modifier instance Graphics.Vty.Config.Parse a => Graphics.Vty.Config.Parse [a] instance Graphics.Vty.Config.GParse f => Graphics.Vty.Config.GParse (GHC.Generics.M1 GHC.Generics.S i f) instance Graphics.Vty.Config.GParse GHC.Generics.U1 instance Graphics.Vty.Config.Parse a => Graphics.Vty.Config.GParse (GHC.Generics.K1 i a) instance (Graphics.Vty.Config.GParse f, Graphics.Vty.Config.GParse g) => Graphics.Vty.Config.GParse (f GHC.Generics.:*: g) instance Graphics.Vty.Config.GParseAlts f => Graphics.Vty.Config.GParse (GHC.Generics.M1 GHC.Generics.D i f) instance (GHC.Generics.Constructor i, Graphics.Vty.Config.GParse f) => Graphics.Vty.Config.GParseAlts (GHC.Generics.M1 GHC.Generics.C i f) instance (Graphics.Vty.Config.GParseAlts f, Graphics.Vty.Config.GParseAlts g) => Graphics.Vty.Config.GParseAlts (f GHC.Generics.:+: g) instance Graphics.Vty.Config.GParseAlts GHC.Generics.V1 -- | This module provides the input layer for Vty, including methods for -- initializing an Input structure and reading Events from -- the terminal. -- -- Note that due to the evolution of terminal emulators, some keys and -- combinations will not reliably map to the expected events by any -- terminal program. There is no 1:1 mapping from key events to bytes -- read from the terminal input device. In very limited cases the -- terminal and vty's input process can be customized to resolve these -- issues; see Graphics.Vty.Config for how to configure vty's -- input processing. -- --

VTY's Implementation

-- -- There are two input modes: -- --
    --
  1. 7-bit
  2. --
  3. 8-bit
  4. --
-- -- The 7-bit input mode is the default and the expected mode in most use -- cases. This is what Vty uses. -- --

7-bit input encoding

-- -- Control key combinations are represented by masking the two high bits -- of the 7-bit input. Historically the control key actually grounded the -- two high bit wires: 6 and 7. This is why control key combos map to -- single character events: the input bytes are identical. The input byte -- is the bit encoding of the character with bits 6 and 7 masked. Bit 6 -- is set by shift. Bit 6 and 7 are masked by control. For example, -- -- -- --

8-bit encoding

-- -- The 8th bit was originally used for parity checking which is useless -- for terminal emulators. Some terminal emulators support an 8-bit input -- encoding. While this provides some advantages, the actual usage is -- low. Most systems use 7-bit mode but recognize 8-bit control -- characters when escaped. This is what Vty does. -- --

Escaped Control Keys

-- -- Using 7-bit input encoding, the ESC byte can signal the start -- of an encoded control key. To differentiate a single ESC -- event from a control key, the timing of the input is used. -- --
    --
  1. ESC individually: ESC byte; no bytes following -- for a period of VMIN milliseconds.
  2. --
  3. Control keys that contain ESC in their encoding: The @ESC -- byte is followed by more bytes read within VMIN milliseconds. -- All bytes up until the next valid input block are passed to the -- classifier.
  4. --
-- -- If the current runtime is the threaded runtime then the terminal's -- VMIN and VTIME behavior reliably implement the above -- rules. If the current runtime does not support forkOS then -- there is currently no implementation. -- --

Unicode Input and Escaped Control Key Sequences

-- -- The input encoding determines how UTF-8 encoded characters are -- recognized. -- -- -- --

Terminfo

-- -- The terminfo system is used to determine how some keys are encoded. -- Terminfo is incomplete and in some cases terminfo is incorrect. Vty -- assumes terminfo is correct but provides a mechanism to override -- terminfo; see Graphics.Vty.Config, specifically -- inputOverrides. -- --

Terminal Input is Broken

-- -- Clearly terminal input has fundemental issues. There is no easy way to -- reliably resolve these issues. -- -- One resolution would be to ditch standard terminal interfaces entirely -- and just go directly to scancodes. This would be a reasonable option -- for Vty if everybody used the linux kernel console but for obvious -- reasons this is not possible. -- -- The Graphics.Vty.Config module supports customizing the -- input-byte-to-event mapping and xterm supports customizing the -- scancode-to-input-byte mapping. With a lot of work a user's system can -- be set up to encode all the key combos in an almost-sane manner. -- --

See also

-- -- module Graphics.Vty.Input -- | Representations of non-modifier keys. -- -- data Key KEsc :: Key KChar :: Char -> Key KBS :: Key KEnter :: Key KLeft :: Key KRight :: Key KUp :: Key KDown :: Key KUpLeft :: Key KUpRight :: Key KDownLeft :: Key KDownRight :: Key KCenter :: Key KFun :: Int -> Key KBackTab :: Key KPrtScr :: Key KPause :: Key KIns :: Key KHome :: Key KPageUp :: Key KDel :: Key KEnd :: Key KPageDown :: Key KBegin :: Key KMenu :: Key -- | Modifier keys. Key codes are interpreted such that users are more -- likely to have Meta than Alt; for instance on the PC Linux console, -- MMeta will generally correspond to the physical Alt key. data Modifier MShift :: Modifier MCtrl :: Modifier MMeta :: Modifier MAlt :: Modifier -- | Mouse buttons. data Button BLeft :: Button BMiddle :: Button BRight :: Button -- | Events. data Event -- | A keyboard key was pressed with the specified modifiers. EvKey :: Key -> [Modifier] -> Event -- | A mouse button was pressed at the specified column and row. Any -- modifiers available in the event are also provided. EvMouseDown :: Int -> Int -> Button -> [Modifier] -> Event -- | A mouse button was released at the specified column and row. Some -- terminals report only that a button was released without specifying -- which one; in that case, Nothing is provided. Otherwise Just the -- button released is included in the event. EvMouseUp :: Int -> Int -> (Maybe Button) -> Event -- | If read from eventChannel this is the size at the time of the -- signal. If read from nextEvent this is the size at the time -- the event was processed by Vty. Typically these are the same, but if -- somebody is resizing the terminal quickly they can be different. EvResize :: Int -> Int -> Event -- | A paste event occurs when a bracketed paste input sequence is -- received. For terminals that support bracketed paste mode, these -- events will be triggered on a paste event. Terminals that do not -- support bracketed pastes will send the paste contents as ordinary -- input (which is probably bad, so beware!) Note that the data is -- provided in raw form and you'll have to decode (e.g. as UTF-8) if -- that's what your application expects. EvPaste :: ByteString -> Event data Input Input :: TChan Event -> IO () -> IORef Config -> Maybe Handle -> Input -- | Channel of events direct from input processing. Unlike -- nextEvent this will not refresh the display if the next event -- is an EvResize. [_eventChannel] :: Input -> TChan Event -- | Shuts down the input processing. This should return the terminal input -- state to before he input initialized. [shutdownInput] :: Input -> IO () -- | Changes to this value are reflected after the next event. [_configRef] :: Input -> IORef Config -- | input debug log [_inputDebug] :: Input -> Maybe Handle -- | Set up the terminal with file descriptor inputFd for input. -- Returns an Input. -- -- The table used to determine the Events to produce for the -- input bytes comes from classifyMapForTerm which is then -- overridden by the the applicable entries from the configuration's -- inputMap. -- -- The terminal device is configured with the attributes: -- -- inputForConfig :: Config -> IO Input -- | Display attributes -- -- Attributes have three components: a foreground color, a background -- color, and a style mask. The simplest attribute is the default -- attribute, or defAttr. Attributes can be modified with -- withForeColor, withBackColor, and withStyle, -- e.g., -- --
--   defAttr withForeColor red
--   
-- -- Image constructors often require an Attr to indicate -- the attributes used in the image, e.g., -- --
--   string (defAttr withForeColor red) "this text will be red"
--   
-- -- The appearance of Images using defAttr is determined -- by the The terminal, so this is not something VTY can control. The -- user is free to The define the color scheme of the terminal as they -- see fit. -- -- The value currentAttr will keep the attributes of whatever was -- output previously. module Graphics.Vty.Attributes -- | A display attribute defines the Color and Style of all the characters -- rendered after the attribute is applied. -- -- At most 256 colors, picked from a 240 and 16 color palette, are -- possible for the background and foreground. The 240 colors and 16 -- colors are points in different palettes. See Color for more -- information. data Attr Attr :: !(MaybeDefault Style) -> !(MaybeDefault Color) -> !(MaybeDefault Color) -> Attr [attrStyle] :: Attr -> !(MaybeDefault Style) [attrForeColor] :: Attr -> !(MaybeDefault Color) [attrBackColor] :: Attr -> !(MaybeDefault Color) -- | Specifies the display attributes such that the final style and color -- values do not depend on the previously applied display attribute. The -- display attributes can still depend on the terminal's default colors -- (unfortunately). data FixedAttr FixedAttr :: !Style -> !(Maybe Color) -> !(Maybe Color) -> FixedAttr [fixedStyle] :: FixedAttr -> !Style [fixedForeColor] :: FixedAttr -> !(Maybe Color) [fixedBackColor] :: FixedAttr -> !(Maybe Color) -- | The style and color attributes can either be the terminal defaults. Or -- be equivalent to the previously applied style. Or be a specific value. data MaybeDefault v [Default] :: MaybeDefault v [KeepCurrent] :: MaybeDefault v [SetTo] :: forall v. (Eq v, Show v, Read v) => !v -> MaybeDefault v -- | Sets the style, background color and foreground color to the default -- values for the terminal. There is no easy way to determine what the -- default background and foreground colors are. defAttr :: Attr -- | Keeps the style, background color and foreground color that was -- previously set. Used to override some part of the previous style. -- -- EG: current_style withForeColor brightMagenta -- -- Would be the currently applied style (be it underline, bold, etc) but -- with the foreground color set to brightMagenta. currentAttr :: Attr -- | Styles are represented as an 8 bit word. Each bit in the word is 1 if -- the style attribute assigned to that bit should be applied and 0 if -- the style attribute should not be applied. type Style = Word8 -- | Add the given style attribute withStyle :: Attr -> Style -> Attr -- | The 6 possible style attributes: -- -- -- -- (The invisible, protect, and altcharset display attributes some -- terminals support are not supported via VTY.) standout :: Style -- | The 6 possible style attributes: -- -- -- -- (The invisible, protect, and altcharset display attributes some -- terminals support are not supported via VTY.) underline :: Style -- | The 6 possible style attributes: -- -- -- -- (The invisible, protect, and altcharset display attributes some -- terminals support are not supported via VTY.) reverseVideo :: Style -- | The 6 possible style attributes: -- -- -- -- (The invisible, protect, and altcharset display attributes some -- terminals support are not supported via VTY.) blink :: Style -- | The 6 possible style attributes: -- -- -- -- (The invisible, protect, and altcharset display attributes some -- terminals support are not supported via VTY.) dim :: Style -- | The 6 possible style attributes: -- -- -- -- (The invisible, protect, and altcharset display attributes some -- terminals support are not supported via VTY.) bold :: Style defaultStyleMask :: Style styleMask :: Attr -> Word8 -- | true if the given Style value has the specified Style set. hasStyle :: Style -> Style -> Bool -- | Set the foreground color of an Attr. withForeColor :: Attr -> Color -> Attr -- | Set the background color of an Attr. withBackColor :: Attr -> Color -> Attr -- | Abstract data type representing a color. -- -- Currently the foreground and background color are specified as points -- in either a: -- -- -- -- The 8 ISO 6429 (ANSI) colors are as follows: -- --
    --
  1. black
  2. --
  3. red
  4. --
  5. green
  6. --
  7. yellow
  8. --
  9. blue
  10. --
  11. magenta
  12. --
  13. cyan
  14. --
  15. white
  16. --
-- -- The mapping from points in the 240 color palette to colors actually -- displayable by the terminal depends on the number of colors the -- terminal claims to support. Which is usually determined by the -- terminfo "colors" property. If this property is not being accurately -- reported then the color reproduction will be incorrect. -- -- If the terminal reports <= 16 colors then the 240 color palette -- points are only mapped to the 8 color pallete. I'm not sure of the RGB -- points for the "bright" colors which is why they are not addressable -- via the 240 color palette. -- -- If the terminal reports > 16 colors then the 240 color palette -- points are mapped to the nearest points in a ("color count" - 16) -- subsampling of the 240 color palette. -- -- All of this assumes the terminals are behaving similarly to xterm and -- rxvt when handling colors. And that the individual colors have not -- been remapped by the user. There may be a way to verify this through -- terminfo but I don't know it. -- -- Seriously, terminal color support is INSANE. data Color ISOColor :: !Word8 -> Color Color240 :: !Word8 -> Color -- | Standard 8-color ANSI terminal color codes. black :: Color -- | Standard 8-color ANSI terminal color codes. red :: Color -- | Standard 8-color ANSI terminal color codes. green :: Color -- | Standard 8-color ANSI terminal color codes. yellow :: Color -- | Standard 8-color ANSI terminal color codes. blue :: Color -- | Standard 8-color ANSI terminal color codes. magenta :: Color -- | Standard 8-color ANSI terminal color codes. cyan :: Color -- | Standard 8-color ANSI terminal color codes. white :: Color -- | Bright/Vivid variants of the standard 8-color ANSI brightBlack :: Color -- | Bright/Vivid variants of the standard 8-color ANSI brightRed :: Color -- | Bright/Vivid variants of the standard 8-color ANSI brightGreen :: Color -- | Bright/Vivid variants of the standard 8-color ANSI brightYellow :: Color brightBlue :: Color brightMagenta :: Color brightCyan :: Color brightWhite :: Color -- | Create a Vty Color (in the 240 color set) from an RGB triple. rgbColor :: Integral i => i -> i -> i -> Color instance GHC.Read.Read Graphics.Vty.Attributes.Attr instance GHC.Show.Show Graphics.Vty.Attributes.Attr instance GHC.Classes.Eq Graphics.Vty.Attributes.Attr instance GHC.Show.Show Graphics.Vty.Attributes.FixedAttr instance GHC.Classes.Eq Graphics.Vty.Attributes.FixedAttr instance GHC.Classes.Eq v => GHC.Classes.Eq (Graphics.Vty.Attributes.MaybeDefault v) instance GHC.Classes.Eq v => GHC.Show.Show (Graphics.Vty.Attributes.MaybeDefault v) instance (GHC.Classes.Eq v, GHC.Show.Show v, GHC.Read.Read v) => GHC.Read.Read (Graphics.Vty.Attributes.MaybeDefault v) instance GHC.Base.Monoid Graphics.Vty.Attributes.Attr instance GHC.Classes.Eq v => GHC.Base.Monoid (Graphics.Vty.Attributes.MaybeDefault v) module Graphics.Vty.DisplayAttributes -- | Given the previously applied display attributes as a FixedAttr and the -- current display attributes as an Attr produces a FixedAttr that -- represents the current display attributes. This is done by using the -- previously applied display attributes to remove the KeepCurrent -- abstraction. fixDisplayAttr :: FixedAttr -> Attr -> FixedAttr -- | difference between two display attributes. Used in the calculation of -- the operations required to go from one display attribute to the next. -- -- Previously, vty would reset display attributes to default then apply -- the new display attributes. This turned out to be very expensive: A -- *lot* more data would be sent to the terminal than required. data DisplayAttrDiff DisplayAttrDiff :: [StyleStateChange] -> DisplayColorDiff -> DisplayColorDiff -> DisplayAttrDiff [styleDiffs] :: DisplayAttrDiff -> [StyleStateChange] [foreColorDiff] :: DisplayAttrDiff -> DisplayColorDiff [backColorDiff] :: DisplayAttrDiff -> DisplayColorDiff -- | Used in the computation of a final style attribute change. simplifyStyleDiffs :: [StyleStateChange] -> [StyleStateChange] -> [StyleStateChange] -- | Consider two display color attributes diffs. What display color -- attribute diff are these equivalent to? simplifyColorDiffs :: DisplayColorDiff -> DisplayColorDiff -> DisplayColorDiff -- | Difference between two display color attribute changes. data DisplayColorDiff ColorToDefault :: DisplayColorDiff NoColorChange :: DisplayColorDiff SetColor :: !Color -> DisplayColorDiff -- | Style attribute changes are transformed into a sequence of -- apply/removes of the individual attributes. data StyleStateChange ApplyStandout :: StyleStateChange RemoveStandout :: StyleStateChange ApplyUnderline :: StyleStateChange RemoveUnderline :: StyleStateChange ApplyReverseVideo :: StyleStateChange RemoveReverseVideo :: StyleStateChange ApplyBlink :: StyleStateChange RemoveBlink :: StyleStateChange ApplyDim :: StyleStateChange RemoveDim :: StyleStateChange ApplyBold :: StyleStateChange RemoveBold :: StyleStateChange -- | Determines the diff between two display&color attributes. This -- diff determines the operations that actually get output to the -- terminal. displayAttrDiffs :: FixedAttr -> FixedAttr -> DisplayAttrDiff diffColor :: Maybe Color -> Maybe Color -> DisplayColorDiff diffStyles :: Style -> Style -> [StyleStateChange] instance GHC.Show.Show Graphics.Vty.DisplayAttributes.DisplayAttrDiff instance GHC.Classes.Eq Graphics.Vty.DisplayAttributes.StyleStateChange instance GHC.Show.Show Graphics.Vty.DisplayAttributes.StyleStateChange instance GHC.Classes.Eq Graphics.Vty.DisplayAttributes.DisplayColorDiff instance GHC.Show.Show Graphics.Vty.DisplayAttributes.DisplayColorDiff instance GHC.Base.Monoid Graphics.Vty.DisplayAttributes.DisplayAttrDiff module Graphics.Text.Width wcwidth :: Char -> Int wcswidth :: String -> Int -- | Returns the display width of a character. Assumes all characters with -- unknown widths are 0 width. safeWcwidth :: Char -> Int -- | Returns the display width of a string. Assumes all characters with -- unknown widths are 0 width. safeWcswidth :: String -> Int -- | A Vty program makes Pictures from Images. This module -- provides the core constructors for creating, combining, and modifying -- Images. module Graphics.Vty.Image -- | This is the internal representation of Images. Use the constructors in -- Graphics.Vty.Image to create instances. -- -- Images are: -- -- data Image -- | The width of an Image. This is the number display columns the image -- will occupy. imageWidth :: Image -> Int -- | The height of an Image. This is the number of display rows the image -- will occupy. imageHeight :: Image -> Int -- | The empty image. Useful for fold combinators. These occupy no space -- and do not affect display attributes. emptyImage :: Image -- | Make an image from a single character. This is a standard Haskell -- 31-bit character assumed to be in the ISO-10646 encoding. char :: Attr -> Char -> Image -- | Make an Image from a String. -- -- This is an alias for iso10646String since the usual case is that a -- literal string like "foo" is represented internally as a list of ISO -- 10646 31 bit characters. -- -- Note: Keep in mind that GHC will compile source encoded as UTF-8 but -- the literal strings, while UTF-8 encoded in the source, will be -- transcoded to a ISO 10646 31 bit characters runtime representation. string :: Attr -> String -> Image -- | Make an image from a string of characters layed out on a single row -- with the same display attribute. The string is assumed to be a -- sequence of ISO-10646 characters. -- -- Note: depending on how the Haskell compiler represents string -- literals, a string literal in a UTF-8 encoded source file, for -- example, may be represented as a ISO-10646 string. That is, I think, -- the case with GHC 6.10. This means, for the most part, you don't need -- to worry about the encoding format when outputting string literals. -- Just provide the string literal directly to iso10646String or string. iso10646String :: Attr -> String -> Image -- | Make an Image from a string of characters layed out on a single -- row. The input is assumed to be the bytes for UTF-8 encoded text. utf8String :: Attr -> [Word8] -> Image -- | Make an Image from a lazy text value. text :: Attr -> Text -> Image -- | Make an Image from a text value. text' :: Attr -> Text -> Image -- | An area of the picture's background (See Background). backgroundFill :: Int -> Int -> Image -- | Make an Image from a UTF-8 encoded lazy bytestring. utf8Bytestring :: Attr -> ByteString -> Image -- | Make an Image from a UTF-8 encoded lazy bytestring. utf8Bytestring' :: Attr -> ByteString -> Image -- | Make an image filling a region with the specified character. charFill :: Integral d => Attr -> Char -> d -> d -> Image -- | combines two images side by side -- -- Combines text chunks where possible. Assures outputWidth and -- outputHeight properties are not violated. -- -- The result image will have a width equal to the sum of the two images -- width. And the height will equal the largest height of the two images. -- The area not defined in one image due to a height missmatch will be -- filled with the background pattern. horizJoin :: Image -> Image -> Image -- | Combines two images horizontally. This is an alias for -- horizJoin. -- -- infixr 5 (<|>) :: Image -> Image -> Image infixr 5 <|> -- | combines two images vertically -- -- The result image will have a height equal to the sum of the heights of -- both images. The width will equal the largest width of the two images. -- The area not defined in one image due to a width missmatch will be -- filled with the background pattern. vertJoin :: Image -> Image -> Image -- | Combines two images vertically. This is an alias for vertJoin. -- -- infixr 4 (<->) :: Image -> Image -> Image infixr 4 <-> -- | Compose any number of images together horizontally, with the first in -- the list being leftmost. horizCat :: [Image] -> Image -- | Compose any number of images vertically, with the first in the list -- being topmost. vertCat :: [Image] -> Image -- | Ensure an image is no larger than the provided size. If the image is -- larger then crop the right or bottom. -- -- This is equivalent to a vertical crop from the bottom followed by -- horizontal crop from the right. crop :: Int -> Int -> Image -> Image -- | Crop an image's width. If the image's width is less than or equal to -- the specified width then this operation has no effect. Otherwise the -- image is cropped from the right. cropRight :: Int -> Image -> Image -- | Crop an image's width. If the image's width is less than or equal to -- the specified width then this operation has no effect. Otherwise the -- image is cropped from the left. cropLeft :: Int -> Image -> Image -- | Crop an image's height. If the image's height is less than or equal to -- the specified height then this operation has no effect. Otherwise the -- image is cropped from the bottom. cropBottom :: Int -> Image -> Image -- | Crop an image's height. If the image's height is less than or equal to -- the specified height then this operation has no effect. Otherwise the -- image is cropped from the top. cropTop :: Int -> Image -> Image -- | Pad the given image. This adds background character fills to the left, -- top, right, bottom. pad :: Int -> Int -> Int -> Int -> Image -> Image -- | Generic resize. Pads and crops are added to ensure that the resulting -- image matches the specified dimensions. This is biased to pad/crop the -- right and bottom. resize :: Int -> Int -> Image -> Image -- | Resize the width. Pads and crops as required to assure the given -- display width. This is biased to pad/crop on the right. resizeWidth :: Int -> Image -> Image -- | Resize the height. Pads and crops as required to assure the given -- display height. This is biased to pad/crop on the bottom. resizeHeight :: Int -> Image -> Image -- | Translates an image by padding or cropping the left and top. -- -- If translation offsets are negative then the image is cropped. translate :: Int -> Int -> Image -> Image -- | Translates an image by padding or cropping its left side. translateX :: Int -> Image -> Image -- | Translates an image by padding or cropping its top. translateY :: Int -> Image -> Image -- | Returns the display width of a character. Assumes all characters with -- unknown widths are 0 width. safeWcwidth :: Char -> Int -- | Returns the display width of a string. Assumes all characters with -- unknown widths are 0 width. safeWcswidth :: String -> Int wcwidth :: Char -> Int wcswidth :: String -> Int -- | A display text is a Data.Text.Lazy type DisplayText = Text -- | A region of the display (first width, then height) type DisplayRegion = (Int, Int) regionWidth :: DisplayRegion -> Int regionHeight :: DisplayRegion -> Int module Graphics.Vty.Picture -- | A Vty picture. -- -- These can be constructed directly or using picForImage. data Picture Picture :: Cursor -> [Image] -> Background -> Picture -- | The picture's cursor. [picCursor] :: Picture -> Cursor -- | The picture's image layers (top-most first). [picLayers] :: Picture -> [Image] -- | The picture's background to be displayed in locations with no Image -- data. [picBackground] :: Picture -> Background -- | A picture can be configured to hide the cursor or to show the cursor -- at the specified character position. -- -- There is not a 1:1 map from character positions to a row and column on -- the screen due to characters that take more than 1 column. data Cursor -- | Hide the cursor NoCursor :: Cursor -- | Show the cursor at the given logical column accounting for character -- width in the presence of multi-column characters. Cursor :: !Int -> !Int -> Cursor -- | Show the cursor at the given absolute terminal column and row AbsoluteCursor :: !Int -> !Int -> Cursor -- | A Picture has a background pattern. The background is either: -- -- -- -- If the display attribute used previously should be used for a -- background fill then use currentAttr for the background -- attribute. data Background Background :: Char -> Attr -> Background [backgroundChar] :: Background -> Char [backgroundAttr] :: Background -> Attr -- | A ClearBackground is: -- -- ClearBackground :: Background -- | A picture with no cursor, background or image layers. emptyPicture :: Picture -- | Add an Image as the top-most layer of a Picture. addToTop :: Picture -> Image -> Picture -- | Add an Image as the bottom-most layer of a Picture. addToBottom :: Picture -> Image -> Picture -- | Create a picture from the given image. The picture will not have a -- displayed cursor and no background pattern (ClearBackground) will be -- used. picForImage :: Image -> Picture -- | Create a picture with the given layers, top-most first. -- -- The picture will not have a displayed cursor and no background pattern -- (ClearBackgroun) will be used. picForLayers :: [Image] -> Picture -- | Return the top-most Image layer for a picture. This is unsafe -- for Pictures without at least one layer. -- -- This is provided for compatibility with applications that do not use -- more than a single layer. picImage :: Picture -> Image instance GHC.Show.Show Graphics.Vty.Picture.Picture instance Control.DeepSeq.NFData Graphics.Vty.Picture.Picture instance Control.DeepSeq.NFData Graphics.Vty.Picture.Cursor instance Control.DeepSeq.NFData Graphics.Vty.Picture.Background -- | A picture is translated into a sequences of state changes and -- character spans. The attribute is applied to all following spans, -- including spans of the next row. The nth element of the sequence -- represents the nth row (from top to bottom) of the picture to render. -- -- A span op sequence will be defined for all rows and columns (and no -- more) of the region provided with the picture to spansForPic. module Graphics.Vty.Span -- | This represents an operation on the terminal: either an attribute -- change or the output of a text string. data SpanOp -- | A span of UTF-8 text occupies a specific number of screen space -- columns. A single UTF character does not necessarily represent 1 -- colunm. See Codec.Binary.UTF8.Width TextSpan [Attr] [output width in -- columns] [number of characters] [data] TextSpan :: !Attr -> !Int -> !Int -> DisplayText -> SpanOp [textSpanAttr] :: SpanOp -> !Attr [textSpanOutputWidth] :: SpanOp -> !Int [textSpanCharWidth] :: SpanOp -> !Int [textSpanText] :: SpanOp -> DisplayText -- | Skips the given number of columns. Skip :: !Int -> SpanOp -- | Marks the end of a row. Specifies how many columns are remaining. -- These columns will not be explicitly overwritten with the span ops. -- The terminal is require to assure the remaining columns are clear. RowEnd :: !Int -> SpanOp -- | A vector of span operations executed in succession. This represents -- the operations required to render a row of the terminal. The -- operations in one row may affect subsequent rows. For example, setting -- the foreground color in one row will affect all subsequent rows until -- the foreground color is changed. type SpanOps = Vector SpanOp dropOps :: Int -> SpanOps -> SpanOps splitOpsAt :: Int -> SpanOps -> (SpanOps, SpanOps) -- | A vector of span operation vectors for display, one per row of the -- output region. type DisplayOps = Vector SpanOps -- | The number of columns the DisplayOps are defined for. -- -- All spans are verified to define same number of columns. displayOpsColumns :: DisplayOps -> Int -- | The number of rows the DisplayOps are defined for. displayOpsRows :: DisplayOps -> Int affectedRegion :: DisplayOps -> DisplayRegion -- | The number of columns a SpanOps affects. spanOpsEffectedColumns :: SpanOps -> Int -- | The width of a single SpanOp in columns. spanOpHasWidth :: SpanOp -> Maybe (Int, Int) -- | The number of columns to the character at the given position in the -- span op. columnsToCharOffset :: Int -> SpanOp -> Int instance GHC.Classes.Eq Graphics.Vty.Span.SpanOp instance GHC.Show.Show Graphics.Vty.Span.SpanOp module Graphics.Vty.Debug rowOpsEffectedColumns :: DisplayOps -> [Int] allSpansHaveWidth :: DisplayOps -> Int -> Bool spanOpsEffectedRows :: DisplayOps -> Int type SpanConstructLog = [SpanConstructEvent] data SpanConstructEvent SpanSetAttr :: Attr -> SpanConstructEvent isSetAttr :: Attr -> SpanConstructEvent -> Bool data MockWindow MockWindow :: Int -> Int -> MockWindow regionForWindow :: MockWindow -> DisplayRegion type ImageConstructLog = [ImageConstructEvent] data ImageConstructEvent ImageConstructEvent :: ImageConstructEvent forwardImageOps :: [Image -> Image] forwardTransform :: ImageOp -> (Image -> Image) reverseTransform :: ImageOp -> (Image -> Image) data ImageOp ImageOp :: ImageEndo -> ImageEndo -> ImageOp type ImageEndo = Image -> Image debugImageOps :: [ImageOp] idImageOp :: ImageOp instance GHC.Classes.Eq Graphics.Vty.Debug.MockWindow instance GHC.Show.Show Graphics.Vty.Debug.MockWindow -- | Transforms an image into rows of operations. module Graphics.Vty.PictureToSpans type MRowOps s = MVector s SpanOps type MSpanOps s = MVector s SpanOp data BlitState BlitState :: Int -> Int -> Int -> Int -> Int -> Int -> BlitState [_columnOffset] :: BlitState -> Int [_rowOffset] :: BlitState -> Int [_skipColumns] :: BlitState -> Int [_skipRows] :: BlitState -> Int [_remainingColumns] :: BlitState -> Int [_remainingRows] :: BlitState -> Int skipRows :: Lens' BlitState Int skipColumns :: Lens' BlitState Int rowOffset :: Lens' BlitState Int remainingRows :: Lens' BlitState Int remainingColumns :: Lens' BlitState Int columnOffset :: Lens' BlitState Int data BlitEnv s BlitEnv :: DisplayRegion -> MRowOps s -> BlitEnv s [_region] :: BlitEnv s -> DisplayRegion [_mrowOps] :: BlitEnv s -> MRowOps s region :: forall s_a1D2z. Lens' (BlitEnv s_a1D2z) DisplayRegion mrowOps :: forall s_a1D2z s_a1D4F. Lens (BlitEnv s_a1D2z) (BlitEnv s_a1D4F) (MRowOps s_a1D2z) (MRowOps s_a1D4F) type BlitM s a = ReaderT (BlitEnv s) (StateT BlitState (ST s)) a -- | Produces the span ops that will render the given picture, possibly -- cropped or padded, into the specified region. displayOpsForPic :: Picture -> DisplayRegion -> DisplayOps -- | Returns the DisplayOps for an image rendered to a window the size of -- the image. -- -- largerly used only for debugging. displayOpsForImage :: Image -> DisplayOps -- | Produces the span ops for each layer then combines them. combinedOpsForLayers :: Picture -> DisplayRegion -> ST s (MRowOps s) substituteSkips :: Background -> MRowOps s -> ST s (MRowOps s) mergeUnder :: MRowOps s -> MRowOps s -> ST s (MRowOps s) mergeRowUnder :: SpanOps -> SpanOps -> SpanOps swapSkipsForSingleColumnCharSpan :: Char -> Attr -> SpanOps -> SpanOps swapSkipsForCharSpan :: Int -> Char -> Attr -> SpanOps -> SpanOps -- | Builds a vector of row operations that will output the given picture -- to the terminal. -- -- Crops to the given display region. buildSpans :: Image -> DisplayRegion -> ST s (MRowOps s) -- | Add the operations required to build a given image to the current set -- of row operations. startImageBuild :: Image -> BlitM s () isOutOfBounds :: Image -> BlitState -> Bool -- | This adds an image that might be partially clipped to the output ops. -- -- This is a very touchy algorithm. Too touchy. For instance, the -- CropRight and CropBottom implementations are odd. They pass the -- current tests but something seems terribly wrong about all this. addMaybeClipped :: forall s. Image -> BlitM s () addMaybeClippedJoin :: forall s. String -> Lens BlitState BlitState Int Int -> Lens BlitState BlitState Int Int -> Lens BlitState BlitState Int Int -> Int -> Image -> Image -> Int -> BlitM s () addUnclippedText :: Attr -> DisplayText -> BlitM s () addRowCompletion :: DisplayRegion -> Int -> BlitM s () -- | snocs the operation to the operations for the given row. snocOp :: SpanOp -> Int -> BlitM s () (-~) :: Num a => ASetter s t a a -> a -> s -> t (+~) :: Num a => ASetter s t a a -> a -> s -> t -- | This module provides an abstract interface for performing terminal -- output. The only user-facing part of this API is Output. module Graphics.Vty.Output.Interface -- | The Vty terminal output interface. data Output Output :: String -> (forall m. MonadIO m => m ()) -> (forall m. MonadIO m => m ()) -> (forall m. MonadIO m => m ()) -> (forall m. MonadIO m => m DisplayRegion) -> (ByteString -> IO ()) -> Int -> Bool -> (Mode -> Bool) -> (forall m. MonadIO m => Mode -> Bool -> m ()) -> (forall m. MonadIO m => Mode -> m Bool) -> IORef AssumedState -> (forall m. MonadIO m => Output -> DisplayRegion -> m DisplayContext) -> (forall m. MonadIO m => m ()) -> (forall m. MonadIO m => m Bool) -> Output -- | Text identifier for the output device. Used for debugging. [terminalID] :: Output -> String -- | Release the terminal just prior to application exit and reset it to -- its state prior to application startup. [releaseTerminal] :: Output -> forall m. 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 The -- initial state. initial state would consist of fixed values: -- -- [reserveDisplay] :: Output -> forall m. MonadIO m => m () -- | Return the display to the state before reserveDisplay If no -- previous state then set the display state to the initial state. [releaseDisplay] :: Output -> forall m. MonadIO m => m () -- | Returns the current display bounds. [displayBounds] :: Output -> forall m. MonadIO m => m DisplayRegion -- | Output the bytestring to the terminal device. [outputByteBuffer] :: Output -> ByteString -> IO () -- | Specifies the maximum number of colors supported by the context. [contextColorCount] :: Output -> Int -- | Specifies whether the cursor can be shown / hidden. [supportsCursorVisibility] :: Output -> Bool -- | Indicates support for terminal modes for this output device. [supportsMode] :: Output -> Mode -> Bool -- | Enables or disables a mode (does nothing if the mode is unsupported). [setMode] :: Output -> forall m. MonadIO m => Mode -> Bool -> m () -- | Returns whether a mode is enabled. [getModeStatus] :: Output -> forall m. MonadIO m => Mode -> m Bool [assumedStateRef] :: Output -> IORef AssumedState -- | 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) [mkDisplayContext] :: Output -> forall m. MonadIO m => Output -> DisplayRegion -> m DisplayContext -- | Ring the terminal bell if supported. [ringTerminalBell] :: Output -> forall m. MonadIO m => m () -- | Returns whether the terminal has an audio bell feature. [supportsBell] :: Output -> forall m. MonadIO m => m Bool data AssumedState AssumedState :: Maybe FixedAttr -> Maybe DisplayOps -> AssumedState [prevFattr] :: AssumedState -> Maybe FixedAttr [prevOutputOps] :: AssumedState -> Maybe DisplayOps data DisplayContext DisplayContext :: Output -> DisplayRegion -> (Int -> Int -> Write) -> Write -> Write -> (FixedAttr -> Attr -> DisplayAttrDiff -> Write) -> Write -> Write -> IO () -> DisplayContext [contextDevice] :: DisplayContext -> Output -- | Provide the bounds of the display context. [contextRegion] :: DisplayContext -> DisplayRegion -- | Sets the output position to the specified row and column where the -- number of bytes required for the control codes can be specified -- seperate from the actual byte sequence. [writeMoveCursor] :: DisplayContext -> Int -> Int -> Write [writeShowCursor] :: DisplayContext -> Write [writeHideCursor] :: DisplayContext -> Write [writeSetAttr] :: DisplayContext -> FixedAttr -> Attr -> DisplayAttrDiff -> Write -- | Reset the display attributes to the default display attributes. [writeDefaultAttr] :: DisplayContext -> Write [writeRowEnd] :: DisplayContext -> Write -- | See inlineHack [inlineHack] :: DisplayContext -> IO () -- | Modal terminal features that can be enabled and disabled. data Mode -- | Mouse mode (whether the terminal is configured to provide mouse input -- events) Mouse :: Mode -- | Paste mode (whether the terminal is configured to provide events on OS -- pastes) BracketedPaste :: Mode displayContext :: MonadIO m => Output -> DisplayRegion -> m DisplayContext -- | Displays the given Picture. -- --
    --
  1. The image is cropped to the display size.
  2. --
  3. Converted into a sequence of attribute changes and text -- spans.
  4. --
  5. The cursor is hidden.
  6. --
  7. Serialized to the display.
  8. --
  9. The cursor is then shown and positioned or kept hidden.
  10. --
outputPicture :: MonadIO m => DisplayContext -> Picture -> m () initialAssumedState :: AssumedState -- | Not all terminals support all display attributes. This filters a -- display attribute to what the given terminal can display. limitAttrForDisplay :: Output -> Attr -> Attr instance GHC.Show.Show Graphics.Vty.Output.Interface.Mode instance GHC.Read.Read Graphics.Vty.Output.Interface.Mode instance GHC.Classes.Eq Graphics.Vty.Output.Interface.Mode -- | This provides a mock terminal implementation that is nice for testing. -- This transforms the output operations to visible characters which is -- useful for testing. module Graphics.Vty.Output.Mock type MockData = IORef (UTF8 ByteString) -- | The mock display terminal produces a string representation of the -- requested picture. There is *not* an isomorphism between the string -- representation and the picture. The string representation is a -- simplification of the picture that is only useful in debugging VTY -- without considering terminal specific issues. -- -- The mock implementation is useful in manually determining if the -- sequence of terminal operations matche the expected sequence. The -- requirement of the produced representation is simplicity in parsing -- the text representation and determining how the picture was mapped to -- terminal operations. -- -- The string representation is a sequence of identifiers where each -- identifier is the name of an operation in the algebra. mockTerminal :: (Applicative m, MonadIO m) => DisplayRegion -> m (MockData, Output) -- | Terminfo-based terminal output driver. -- -- Copyright Corey O'Connor (coreyoconnor@gmail.com) module Graphics.Vty.Output.TerminfoBased -- | Constructs an output driver that uses terminfo for all control codes. -- While this should provide the most compatible terminal, terminfo does -- not support some features that would increase efficiency and improve -- compatibility: -- -- reserveTerminal :: (Applicative m, MonadIO m) => String -> Fd -> m Output -- | Xterm output driver. This uses the Terminfo driver with some -- extensions for Xterm. module Graphics.Vty.Output.XTermColor -- | Construct an Xterm output driver. Initialize the display to UTF-8. reserveTerminal :: (Applicative m, MonadIO m) => String -> Fd -> m Output -- | This module provides functions for accessing the current terminal or a -- specific terminal device. -- -- See also: -- --
    --
  1. Graphics.Vty.Output: This instantiates an abtract interface -- to the terminal based on the TERM and COLORTERM -- environment variables.
  2. --
  3. Graphics.Vty.Output.Interface: Defines the generic -- interface all terminal modules need to implement.
  4. --
  5. Graphics.Vty.Output.TerminfoBased: Defines a terminal -- instance that uses terminfo for all control strings. No attempt is -- made to change the character set to UTF-8 for these terminals.
  6. --
  7. Graphics.Vty.Output.XTermColor: This module contains an -- interface suitable for xterm-like terminals. These are the terminals -- where TERM begins with xterm. This does use terminfo -- for as many control codes as possible.
  8. --
module Graphics.Vty.Output -- | Returns an 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. -- -- 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: -- -- outputForConfig :: Config -> IO Output -- | 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. setCursorPos :: MonadIO m => Output -> Int -> Int -> m () -- | Hides the cursor. hideCursor :: MonadIO m => Output -> m () -- | Shows the cursor. showCursor :: MonadIO m => Output -> m () -- | Vty provides interfaces for both terminal input and terminal output. -- -- -- --
--   import Graphics.Vty
--   
--   main = do
--       cfg <- standardIOConfig
--       vty <- mkVty cfg
--       let line0 = string (defAttr ` withForeColor ` green) "first line"
--           line1 = string (defAttr ` withBackColor ` blue) "second line"
--           img = line0 <-> line1
--           pic = picForImage img
--       update vty pic
--       e <- nextEvent vty
--       shutdown vty
--       print ("Last event was: " ++ show e)
--   
module Graphics.Vty -- | A Vty value represents a handle to the Vty library that the -- application must create in order to use Vty. -- -- The use of Vty typically follows this process: -- --
    --
  1. Initialize vty
  2. --
  3. Use update to display a picture.
  4. --
  5. Use nextEvent to get the next input event.
  6. --
  7. Depending on the event, go to 2 or 5.
  8. --
  9. Shutdown vty.
  10. --
-- -- Operations on Vty handles are not thread-safe. data Vty Vty :: (Picture -> IO ()) -> IO Event -> Input -> Output -> IO () -> IO () -> Vty -- | Outputs the given Picture. [update] :: Vty -> Picture -> IO () -- | Get one Event object, blocking if none are available. This will -- refresh the terminal if the event is a EvResize. [nextEvent] :: Vty -> IO Event -- | The input interface. See Input. [inputIface] :: Vty -> Input -- | The output interface. See Output. [outputIface] :: Vty -> Output -- | Refresh the display. nextEvent will refresh the display if a -- resize occurs, but this can be used to refresh the display explicitly. -- If other programs output to the terminal and mess up the display then -- the application might want to force a refresh using this function. [refresh] :: Vty -> IO () -- | Clean up after vty. A call to this function is necessary to cleanly -- restore the terminal state before application exit. The above methods -- will throw an exception if executed after this is executed. [shutdown] :: Vty -> IO () -- | Create a Vty handle. At most one handle should be created at a time -- for a given terminal device. -- -- The specified configuration is added to the the configuration loaded -- by userConfig with the userConfig configuration taking -- precedence. See Graphics.Vty.Config. -- -- For most applications mkVty defaultConfig is sufficient. mkVty :: Config -> IO Vty -- | Modal terminal features that can be enabled and disabled. data Mode -- | Mouse mode (whether the terminal is configured to provide mouse input -- events) Mouse :: Mode -- | Paste mode (whether the terminal is configured to provide events on OS -- pastes) BracketedPaste :: Mode -- | The inline module provides a limited interface to changing the style -- of terminal output. The intention is for this interface to be used -- inline with other output systems. -- -- The changes specified by the InlineM monad are applied to the -- terminal's display attributes. These display attributes affect the -- display of all following text output to the terminal file descriptor. -- -- For example, in an IO monad the following code will print the text -- "Not styled. " Followed by the text " Styled! " drawn over a red -- background and underlined. -- --
--   putStr "Not styled. "
--   putAttrChange_ $ do
--       backColor red
--       applyStyle underline
--   putStr " Styled! "
--   putAttrChange_ $ defaultAll
--   putStrLn "Not styled."
--   
-- -- putAttrChange emits the control codes to the terminal device -- attached to Handle. This is a duplicate of the stdout -- handle when the terminalHandle was (first) acquired. If -- stdout has since been changed then putStr, -- putStrLn, print etc. will output to a different -- Handle than putAttrChange. -- -- Copyright 2009-2010 Corey O'Connor module Graphics.Vty.Inline type InlineM v = State Attr v -- | Set the background color to the provided Color. backColor :: Color -> InlineM () -- | Set the foreground color to the provided Color. foreColor :: Color -> InlineM () -- | Attempt to change the Style of the following text.. -- -- If the terminal does not support the style change then no error is -- produced. The style can still be removed. applyStyle :: Style -> InlineM () -- | Attempt to remove the specified Style from the display of the -- following text. -- -- This will fail if applyStyle for the given style has not been -- previously called. removeStyle :: Style -> InlineM () -- | Reset the display attributes. defaultAll :: InlineM () -- | Apply the provided display attribute changes to the given terminal -- output device. -- -- This does not flush the terminal. putAttrChange :: (Applicative m, MonadIO m) => Output -> InlineM () -> m () -- | Apply the provided display attributes changes to the terminal output -- device. -- -- This will flush the terminal output. putAttrChange_ :: (Applicative m, MonadIO m) => InlineM () -> m () -- | This will create a Vty instance using mkVty and execute an IO -- action provided that instance. The created Vty instance will be stored -- to the unsafe IORef globalVty. -- -- This instance will use duplicates of the stdin and stdout Handles. withVty :: (Vty -> IO b) -> IO b