vty-3.0.0: A simple terminal access libraryContentsIndex
Graphics.Vty
Synopsis
data Vty = Vty {
update :: (Picture -> IO ())
getEvent :: (IO Event)
getSize :: (IO (Int, Int))
shutdown :: (IO ())
}
beep :: IO ()
mkVty :: IO Vty
data Cursor
= NoCursor
| Cursor Int Int
newtype Attr = Attr Int
setFG :: Color -> Attr -> Attr
setBG :: Color -> Attr -> Attr
setBold :: Attr -> Attr
setBlink :: Attr -> Attr
setRV :: Attr -> Attr
setHalfBright :: Attr -> Attr
setUnderline :: Attr -> Attr
attr :: Attr
newtype Color = Color Int
black :: Color
red :: Color
green :: Color
yellow :: Color
blue :: Color
magenta :: Color
cyan :: Color
white :: Color
def :: Color
data Image = Image (Int -> Ptr Int -> IO ()) !Int !Int
empty :: Image
(<|>) :: Image -> Image -> Image
(<->) :: Image -> Image -> Image
fillSeg :: Attr -> Char -> Ptr Int -> Ptr Int -> IO ()
horzcat :: [Image] -> Image
vertcat :: [Image] -> Image
renderBS :: Attr -> ByteString -> Image
renderChar :: Attr -> Char -> Image
renderHFill :: Attr -> Char -> Int -> Image
renderFill :: Attr -> Char -> Int -> Int -> Image
data Picture = Pic {
pCursor :: Cursor
pImage :: Image
}
pic :: Picture
data Key
= KEsc
| KFun Int
| KPrtScr
| KPause
| KASCII Char
| KBS
| KIns
| KHome
| KPageUp
| KDel
| KEnd
| KPageDown
| KNP5
| KUp
| KMenu
| KLeft
| KDown
| KRight
| KEnter
data Modifier
= MShift
| MCtrl
| MMeta
| MAlt
data Button
= BLeft
| BMiddle
| BRight
data Event
= EvKey Key [Modifier]
| EvMouse Int Int Button [Modifier]
| EvResize Int Int
Documentation
data Vty
The main object. At most one should be created.
Constructors
Vty
update :: (Picture -> IO ())Update the screen to reflect the contents of a Picture. This is not currently threadsafe.
getEvent :: (IO Event)Get one Event object, blocking if necessary.
getSize :: (IO (Int, Int))Get the size of the display.
shutdown :: (IO ())Clean up after vty.
beep :: IO ()
Make the terminal beep.
mkVty :: IO Vty
Set up the state object for using vty. At most one state object should be created at a time.
data Cursor
This type represents the visible cursor state.
Constructors
NoCursorHide the cursor.
Cursor Int IntDisplay the cursor at the given XY position.
newtype Attr
Opaque data type representing character attributes.
Constructors
Attr Int
show/hide Instances
setFG :: Color -> Attr -> Attr
Set the foreground color of an Attr.
setBG :: Color -> Attr -> Attr
Set the background color of an Attr.
setBold :: Attr -> Attr
Set bold attribute of an Attr.
setBlink :: Attr -> Attr
Set blink attribute of an Attr.
setRV :: Attr -> Attr
Set reverse-video attribute of an Attr.
setHalfBright :: Attr -> Attr
Set half-bright attribute of an Attr.
setUnderline :: Attr -> Attr
Set underline attribute of an Attr.
attr :: Attr
Attr with all default values.
newtype Color
Abstract data type representing a color.
Constructors
Color Int
show/hide Instances
black :: Color
Basic color definitions.
red :: Color
green :: Color
yellow :: Color
blue :: Color
magenta :: Color
cyan :: Color
white :: Color
def :: Color
data Image
A two-dimensional array of (Char,Attr) pairs.
Constructors
Image (Int -> Ptr Int -> IO ()) !Int !Int
empty :: Image
The empty image.
(<|>) :: Image -> Image -> Image
Compose two images side by side. The images must of the same height, or one must be empty.
(<->) :: Image -> Image -> Image
Compose two images vertically. The images must of the same width, or one must be empty.
fillSeg :: Attr -> Char -> Ptr Int -> Ptr Int -> IO ()
Helper - fill a buffer segment with a char/attr.
horzcat :: [Image] -> Image
Compose any number of images horizontally.
vertcat :: [Image] -> Image
Compose any number of images vertically.
renderBS :: Attr -> ByteString -> Image
Create an Image from a ByteString with a single uniform Attr.
renderChar :: Attr -> Char -> Image
Create a 1x1 image. Warning, this is likely to be inefficient.
renderHFill :: Attr -> Char -> Int -> Image
Create an image by repeating a single character and attribute horizontally.
renderFill :: Attr -> Char -> Int -> Int -> Image
Create an image by repeating a single character and attribute.
data Picture
The type of images to be displayed using update. You probably shouldn't create this directly if you care about compatibility with future versions of vty; instead use pic and record update syntax.
Constructors
Pic
pCursor :: CursorThe position and visibility status of the virtual cursor.
pImage :: ImageA 2d array of (character,attribute) pairs, representing the screen image.
pic :: Picture
Create a Picture object with all default values. By using this and record update, rather than directly using the Pic constructor, your code will be compatible with additions to the Picture object. You must specify at least pImage.
data Key
Representations of non-modifier keys.
Constructors
KEsc
KFun Int
KPrtScr
KPause
KASCII Char
KBS
KIns
KHome
KPageUp
KDel
KEnd
KPageDown
KNP5
KUp
KMenu
KLeft
KDown
KRight
KEnter
show/hide Instances
data Modifier
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.
Constructors
MShift
MCtrl
MMeta
MAlt
show/hide Instances
data Button
Mouse buttons. Not yet used.
Constructors
BLeft
BMiddle
BRight
show/hide Instances
data Event
Generic events.
Constructors
EvKey Key [Modifier]
EvMouse Int Int Button [Modifier]
EvResize Int Int
show/hide Instances
Produced by Haddock version 0.8