byline-0.4.0.0: Library for creating command-line interfaces (colors, menus, etc.)

Safe HaskellNone
LanguageHaskell2010

System.Console.Byline

Contents

Synopsis

Introduction

Byline provides a monad transformer that allows you to compose interactive terminal actions. When producing output, these actions accept stylized text that can include foreground and background colors, underlined text, and bold text.

Stylized text can be constructed with string literals (using the OverloadedStrings extension) or using the text function. Attributes such as color can be changed using modifier functions and the mappend operator, (<>).

Actions that read user input can work with completion functions which are activated when the user presses the tab key. Most input actions also support default values that will be returned when the user presses the enter key without providing any input.

Example:

    {-# LANGUAGE OverloadedStrings #-}

    ...

    language <- runByline $ do
        sayLn ("Look mom, " <> ("colors" <> fg blue) <> "!")

        let question = "What's your favorite " <>
                       ("language" <> bold)    <> "? "

        ask question Nothing

More complete examples can be found in the examples directory of the distribution tarball or in the repository.

Executing Interactive Sessions

data Byline m a Source #

A monad transformer that encapsulates interactive actions.

Instances
MonadTrans Byline Source # 
Instance details

Defined in System.Console.Byline.Internal.Byline

Methods

lift :: Monad m => m a -> Byline m a #

Monad m => Monad (Byline m) Source # 
Instance details

Defined in System.Console.Byline.Internal.Byline

Methods

(>>=) :: Byline m a -> (a -> Byline m b) -> Byline m b #

(>>) :: Byline m a -> Byline m b -> Byline m b #

return :: a -> Byline m a #

fail :: String -> Byline m a #

Functor m => Functor (Byline m) Source # 
Instance details

Defined in System.Console.Byline.Internal.Byline

Methods

fmap :: (a -> b) -> Byline m a -> Byline m b #

(<$) :: a -> Byline m b -> Byline m a #

Monad m => Applicative (Byline m) Source # 
Instance details

Defined in System.Console.Byline.Internal.Byline

Methods

pure :: a -> Byline m a #

(<*>) :: Byline m (a -> b) -> Byline m a -> Byline m b #

liftA2 :: (a -> b -> c) -> Byline m a -> Byline m b -> Byline m c #

(*>) :: Byline m a -> Byline m b -> Byline m b #

(<*) :: Byline m a -> Byline m b -> Byline m a #

MonadIO m => MonadIO (Byline m) Source # 
Instance details

Defined in System.Console.Byline.Internal.Byline

Methods

liftIO :: IO a -> Byline m a #

runByline :: (MonadIO m, MonadMask m) => Byline m a -> m (Maybe a) Source #

Execute Byline actions and produce a result within the base monad.

A note about EOF:

If an End of File (EOF) is encountered during an input action then this function will return Nothing. This can occur when the user manually enters an EOF character by pressing Control-d or if standard input is a file.

This decision was made to simplify the Byline interface for actions that read user input and is a typical strategy for terminal applications. If this isn't desirable, you may want to break your actions up into groups and call runByline multiple times.

Primitive Operations

say :: MonadIO m => Stylized -> Byline m () Source #

Output the stylized text to the output handle (default: stdout).

sayLn :: MonadIO m => Stylized -> Byline m () Source #

Like say, but append a newline character.

ask Source #

Arguments

:: MonadIO m 
=> Stylized

The prompt.

-> Maybe Text

Optional default answer that will be returned if the user presses return without providing any input (a zero-length string).

-> Byline m Text 

Read input after printing the given stylized text as a prompt.

askChar :: MonadIO m => Stylized -> Byline m Char Source #

Read a single character of input.

askPassword Source #

Arguments

:: MonadIO m 
=> Stylized

The prompt.

-> Maybe Char

Optional masking character that will be printed each time the user presses a key.

-> Byline m Text 

Read a password without echoing it to the terminal. If a masking character is given it will replace each typed character.

askUntil Source #

Arguments

:: MonadIO m 
=> Stylized

The prompt.

-> Maybe Text

Optional default answer.

-> (Text -> m (Either Stylized a))

Confirmation function.

-> Byline m a 

Continue to prompt for a response until a confirmation function returns a valid result.

The confirmation function receives the output from ask and should return a Left Stylized to produce an error message (printed with sayLn). When an acceptable answer from ask is received, the confirmation function should return it with Right.

report :: MonadIO m => ReportType -> Stylized -> Byline m () Source #

Output stylized text with a prefix determined by ReportType.

reportLn :: MonadIO m => ReportType -> Stylized -> Byline m () Source #

Like report, but append a newline character.

Constructing Stylized Text

data Stylized Source #

Stylized text. Construct text with modifiers using string literals and the OverloadedStrings extension and/or the text function.

text :: Text -> Stylized Source #

Helper function to create stylized text. If you enable the OverloadedStrings extension then you can create stylized text directly without using this function.

This function is also helpful for producing stylized text from an existing Text value.

Modifying Output Text

The Stylized type is an instance of the monoid class. This means you can change attributes of the text by using the following functions along with mappend or the (<>) operator.

fg :: Color -> Stylized Source #

Set the foreground color. For example:

    "Hello World!" <> fg magenta

bg :: Color -> Stylized Source #

Set the background color.

bold :: Stylized Source #

Produce bold text.

underline :: Stylized Source #

Produce underlined text.

swapFgBg :: Stylized Source #

Produce swapped foreground/background text.

Specifying Colors

data Color Source #

Opaque type for representing a color.

A color can be one of the eight standard terminal colors constructed with one of the named color functions (e.g., black, red, etc.) or using the rgb function.

black :: Color Source #

Standard ANSI color by name.

red :: Color Source #

Standard ANSI color by name.

green :: Color Source #

Standard ANSI color by name.

yellow :: Color Source #

Standard ANSI color by name.

blue :: Color Source #

Standard ANSI color by name.

magenta :: Color Source #

Standard ANSI color by name.

cyan :: Color Source #

Standard ANSI color by name.

white :: Color Source #

Standard ANSI color by name.

rgb :: Word8 -> Word8 -> Word8 -> Color Source #

Specify a color using a RGB triplet where each component is in the range [0 .. 255]. The actual rendered color will depend on the terminal.

If the terminal advertises that it supports 256 colors, the color given to this function will be converted to the nearest color in the 216-color pallet supported by the terminal. (216 colors because the first 16 are the standard colors and the last 24 are grayscale entries.)

However, if the terminal doesn't support extra colors, or doesn't have a TERMINFO entry (e.g., Windows) then the nearest standard color will be chosen.

Nearest colors are calculated using their CIE distance from one another.

See also:

Menus

Menus provide a way to display a small number of list items to the user. The desired list item is selected by typing its index or by typing a unique prefix string. A default completion function is provided to allow the user to select a list item using tab completion.

data Menu a Source #

Opaque type representing a menu containing items of type a.

data Choice a Source #

A type representing the choice made by a user while working with a menu.

Constructors

NoItems

Menu has no items to choose from.

Match a

User picked a menu item.

Other Text

User entered text that doesn't match an item.

Instances
Show a => Show (Choice a) Source # 
Instance details

Defined in System.Console.Byline.Menu

Methods

showsPrec :: Int -> Choice a -> ShowS #

show :: Choice a -> String #

showList :: [Choice a] -> ShowS #

menu :: [a] -> (a -> Stylized) -> Menu a Source #

Create a Menu by giving a list of menu items and a function that can convert those items into stylized text.

askWithMenu Source #

Arguments

:: MonadIO m 
=> Menu a

The Menu to display.

-> Stylized

The prompt.

-> Byline m (Choice a) 

Ask the user to choose an item from a menu. The menu will only be shown once and the user's choice will be returned in a Choice value.

If you want to force the user to only choose from the displayed menu items you should use askWithMenuRepeatedly instead.

askWithMenuRepeatedly Source #

Arguments

:: MonadIO m 
=> Menu a

The Menu to display.

-> Stylized

The prompt.

-> Stylized

Error message.

-> Byline m (Choice a) 

Like askWithMenu except that arbitrary input is not allowed. If the user doesn't correctly select a menu item then the menu will be repeated and an error message will be displayed.

banner :: Stylized -> Menu a -> Menu a Source #

Change the banner of a menu. The banner is printed just before the menu items are displayed.

prefix :: (Int -> Stylized) -> Menu a -> Menu a Source #

Change the prefix function. The prefix function should generate unique, stylized text that the user can use to select a menu item. The default prefix function numbers the menu items starting with 1.

suffix :: Stylized -> Menu a -> Menu a Source #

Change the menu item suffix. It is displayed directly after the menu item prefix and just before the menu item itself.

Default: ") "

type Matcher a = Menu a -> Map Text a -> Text -> Choice a Source #

A function that is given the input from a user while working in a menu and should translate that into a Choice.

The Map contains the menu item indexes/prefixes (numbers or letters) and the items themselves.

The default matcher function allows the user to select a menu item by typing its index or part of its textual representation. As long as input from the user is a unique prefix of one of the menu items then that item will be returned.

matcher :: Matcher a -> Menu a -> Menu a Source #

Change the Matcher function. The matcher function should compare the user's input to the menu items and their assigned prefix values and return a Choice.

Completion

type CompletionFunc = (Text, Text) -> IO (Text, [Completion]) Source #

A completion function modeled after the one used in Haskeline.

Warning: If you're familiar with the Haskeline version of the CompletionFunc type please be sure to read this description carefully since the two behave differently.

The completion function is called when the user presses the tab key. The current input line is split into two parts based on where the cursor is positioned. Text to the left of the cursor will be the first value in the tuple and text to the right of the cursor will be the second value.

The text returned from the completion function is the text from the left of the cursor which wasn't used in the completion. It should also produce a list of possible Completion values.

In Haskeline, some of these text values are reversed. This is not the case in Byline.

A note about IO:

Due to the way that Byline uses Haskeline, the completion function is forced to return an IO value. It would be better if it could return a value in the base monad instead. Patches welcome.

data Completion Source #

A type representing a completion match to the user's input.

Constructors

Completion 

Fields

  • replacement :: Text

    Text to insert to the right of the cursor.

  • display :: Text

    Text to display when listing all completions.

  • isFinished :: Bool

    Whether to follow the completed word with a terminating space or close existing quotes.

withCompletionFunc :: MonadIO m => CompletionFunc -> Byline m a -> Byline m a Source #

Run the given Byline action with a different completion function.

Utility Functions, Operators, and Types

data ReportType Source #

Report types for the report function.

Constructors

Error

Report errors with: "error: "

Warning

Report warnings with: "warning: "

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.