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

CopyrightThis file is part of the package byline. It is subject to the
license terms in the LICENSE file found in the top-level
directory of this distribution and at:

https://github.com/pjones/byline

No part of this package including this file may be copied
modified propagated or distributed except according to the
terms contained in the LICENSE file.
LicenseBSD-2-Clause
Safe HaskellNone
LanguageHaskell2010

Byline.Simulation

Contents

Description

 
Synopsis

Simulating User Interaction

This module provides a monad transformer that can simulate an interactive user session for testing MonadByline code.

Simulated Values

data Simulated Source #

Simulated user input.

Since: 1.0.0.0

Constructors

SimulatedInput Text

Simulate user input by providing the Text value they typed as a response to a prompt.

If the asking function wants a single character of input then only the first character of the provided Text is used. In this case, if an empty Text value is given, it will be treated as an end-of-file (EOF) character.

SimulatedEOF

Simulate an end-of-file (EOF) character. Usually this occurs when the user enters Control-D or when standard input is exhausted.

type SimulationFunction m = StateT (SimulationState m) m Simulated Source #

A function that simulates user input by returning a Simulated value.

The function has full access to the SimulationState including the ability to change the simulation function itself. For example, below is a function that will return the text "Current" the first time it is called and "Next" every time after that.

 textThenDefault :: Monad m => SimulationFunction m
 textThenDefault = do
   -- The next input request will come from this function:
   modify (s -> s {simulationFunction = pure (SimulatedInput "Next")})

   -- But this time we'll return different text:
   pure (SimulatedInput "Current")

Since: 1.0.0.0

Access to Simulation State

data SimulationState m Source #

Stateful information available to the simulation function.

Since: 1.0.0.0

Constructors

SimulationState 

Fields

Simulation as a Monad Transformer

data BylineT m a Source #

A monad transformer that implements the MonadByline class without actually doing anything.

Since: 1.0.0.0

Instances
MonadTrans BylineT Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

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

MonadState s m => MonadState s (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

get :: BylineT m s #

put :: s -> BylineT m () #

state :: (s -> (a, s)) -> BylineT m a #

MonadReader r m => MonadReader r (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

ask :: BylineT m r #

local :: (r -> r) -> BylineT m a -> BylineT m a #

reader :: (r -> a) -> BylineT m a #

MonadError e m => MonadError e (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

throwError :: e -> BylineT m a #

catchError :: BylineT m a -> (e -> BylineT m a) -> BylineT m a #

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

Defined in Byline.Internal.Simulation

Methods

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

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

return :: a -> BylineT m a #

fail :: String -> BylineT m a #

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

Defined in Byline.Internal.Simulation

Methods

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

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

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

Defined in Byline.Internal.Simulation

Methods

pure :: a -> BylineT m a #

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

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

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

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

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

Defined in Byline.Internal.Simulation

Methods

liftIO :: IO a -> BylineT m a #

MonadThrow m => MonadThrow (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

throwM :: Exception e => e -> BylineT m a #

MonadCatch m => MonadCatch (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

catch :: Exception e => BylineT m a -> (e -> BylineT m a) -> BylineT m a #

MonadCont m => MonadCont (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

callCC :: ((a -> BylineT m b) -> BylineT m a) -> BylineT m a #

Monad m => MonadByline (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

liftByline :: F PrimF a -> BylineT m a

runBylineT :: Monad m => SimulationFunction m -> BylineT m a -> m (Maybe a) Source #

Discharge the MonadByline effect using the given SimulationFunction.

Since: 1.0.0.0

Re-exports

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.

Since: 1.0.0.0

Instances
Eq Color Source # 
Instance details

Defined in Byline.Internal.Types

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Show Color Source # 
Instance details

Defined in Byline.Internal.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

black :: Color Source #

Standard ANSI color by name.

Since: 1.0.0.0

red :: Color Source #

Standard ANSI color by name.

Since: 1.0.0.0

green :: Color Source #

Standard ANSI color by name.

Since: 1.0.0.0

yellow :: Color Source #

Standard ANSI color by name.

Since: 1.0.0.0

blue :: Color Source #

Standard ANSI color by name.

Since: 1.0.0.0

magenta :: Color Source #

Standard ANSI color by name.

Since: 1.0.0.0

cyan :: Color Source #

Standard ANSI color by name.

Since: 1.0.0.0

white :: Color Source #

Standard ANSI color by name.

Since: 1.0.0.0

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:

Since: 1.0.0.0

class ToStylizedText a where Source #

A class for types that can be converted to Stylized text.

Instances
ToStylizedText (Stylized Text) Source #

Since: 1.0.0.0

Instance details

Defined in Byline.Internal.Stylized

data Stylized a Source #

A stylized value. Construct text with modifiers using string literals and the OverloadedStrings extension and/or the text function.

Since: 1.0.0.0

Instances
Functor Stylized Source # 
Instance details

Defined in Byline.Internal.Stylized

Methods

fmap :: (a -> b) -> Stylized a -> Stylized b #

(<$) :: a -> Stylized b -> Stylized a #

Foldable Stylized Source # 
Instance details

Defined in Byline.Internal.Stylized

Methods

fold :: Monoid m => Stylized m -> m #

foldMap :: Monoid m => (a -> m) -> Stylized a -> m #

foldr :: (a -> b -> b) -> b -> Stylized a -> b #

foldr' :: (a -> b -> b) -> b -> Stylized a -> b #

foldl :: (b -> a -> b) -> b -> Stylized a -> b #

foldl' :: (b -> a -> b) -> b -> Stylized a -> b #

foldr1 :: (a -> a -> a) -> Stylized a -> a #

foldl1 :: (a -> a -> a) -> Stylized a -> a #

toList :: Stylized a -> [a] #

null :: Stylized a -> Bool #

length :: Stylized a -> Int #

elem :: Eq a => a -> Stylized a -> Bool #

maximum :: Ord a => Stylized a -> a #

minimum :: Ord a => Stylized a -> a #

sum :: Num a => Stylized a -> a #

product :: Num a => Stylized a -> a #

Traversable Stylized Source # 
Instance details

Defined in Byline.Internal.Stylized

Methods

traverse :: Applicative f => (a -> f b) -> Stylized a -> f (Stylized b) #

sequenceA :: Applicative f => Stylized (f a) -> f (Stylized a) #

mapM :: Monad m => (a -> m b) -> Stylized a -> m (Stylized b) #

sequence :: Monad m => Stylized (m a) -> m (Stylized a) #

Eq a => Eq (Stylized a) Source # 
Instance details

Defined in Byline.Internal.Stylized

Methods

(==) :: Stylized a -> Stylized a -> Bool #

(/=) :: Stylized a -> Stylized a -> Bool #

Show a => Show (Stylized a) Source # 
Instance details

Defined in Byline.Internal.Stylized

Methods

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

show :: Stylized a -> String #

showList :: [Stylized a] -> ShowS #

IsString (Stylized Text) Source #

Since: 1.0.0.0

Instance details

Defined in Byline.Internal.Stylized

Semigroup (Stylized a) Source #

Since: 1.0.0.0

Instance details

Defined in Byline.Internal.Stylized

Methods

(<>) :: Stylized a -> Stylized a -> Stylized a #

sconcat :: NonEmpty (Stylized a) -> Stylized a #

stimes :: Integral b => b -> Stylized a -> Stylized a #

Monoid (Stylized a) Source #

Since: 1.0.0.0

Instance details

Defined in Byline.Internal.Stylized

Methods

mempty :: Stylized a #

mappend :: Stylized a -> Stylized a -> Stylized a #

mconcat :: [Stylized a] -> Stylized a #

ToStylizedText (Stylized Text) Source #

Since: 1.0.0.0

Instance details

Defined in Byline.Internal.Stylized

text :: Text -> Stylized Text 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.

Since: 1.0.0.0

fg :: Color -> Stylized Text Source #

Set the foreground color. For example:

    "Hello World!" <> fg magenta

Since: 1.0.0.0

bg :: Color -> Stylized Text Source #

Set the background color.

Since: 1.0.0.0

bold :: Stylized Text Source #

Produce bold text.

Since: 1.0.0.0

underline :: Stylized Text Source #

Produce underlined text.

Since: 1.0.0.0

swapFgBg :: Stylized Text Source #

Produce swapped foreground/background text.

Since: 1.0.0.0

class Monad m => MonadByline (m :: * -> *) Source #

A class of types that can lift Byline operations into a base monad.

Since: 1.0.0.0

Instances
MonadByline (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Eval

Methods

liftByline :: F PrimF a -> BylineT m a

Monad m => MonadByline (BylineT m) Source # 
Instance details

Defined in Byline.Internal.Simulation

Methods

liftByline :: F PrimF a -> BylineT m a

MonadByline m => MonadByline (IdentityT m) Source # 
Instance details

Defined in Byline.Internal.Eval

Methods

liftByline :: F PrimF a -> IdentityT m a

MonadByline m => MonadByline (ExceptT e m) Source # 
Instance details

Defined in Byline.Internal.Eval

Methods

liftByline :: F PrimF a -> ExceptT e m a

MonadByline m => MonadByline (StateT s m) Source # 
Instance details

Defined in Byline.Internal.Eval

Methods

liftByline :: F PrimF a -> StateT s m a

MonadByline m => MonadByline (StateT s m) Source # 
Instance details

Defined in Byline.Internal.Eval

Methods

liftByline :: F PrimF a -> StateT s m a

MonadByline m => MonadByline (ReaderT r m) Source # 
Instance details

Defined in Byline.Internal.Eval

Methods

liftByline :: F PrimF a -> ReaderT r m a

MonadByline m => MonadByline (ContT r m) Source # 
Instance details

Defined in Byline.Internal.Eval

Methods

liftByline :: F PrimF a -> ContT r m a

say Source #

Arguments

:: (MonadByline m, ToStylizedText a) 
=> a

The stylized text to output.

-> m () 

Output the given stylized text.

See also: sayLn.

Since: 1.0.0.0

sayLn Source #

Arguments

:: (MonadByline m, ToStylizedText a) 
=> a

The stylized text to output. An appropirate line ending character will be added to the end of this text.

-> m () 

Like say, but append a newline character.

Since: 1.0.0.0

askLn Source #

Arguments

:: (MonadByline m, ToStylizedText a) 
=> a

The prompt.

-> Maybe Text

The text to return if the user does not enter a response.

-> m Text

User input (or default answer).

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

Since: 1.0.0.0

askChar Source #

Arguments

:: (MonadByline m, ToStylizedText a) 
=> a

The prompt to display.

-> m Char 

Read a single character of input.

Since: 1.0.0.0

askPassword Source #

Arguments

:: (MonadByline m, ToStylizedText a) 
=> a

The prompt to display.

-> Maybe Char

Optional masking character that will be printed each time the user presses a key. When Nothing is given the default behavior will be used which is system dependent but usually results in no characters being echoed to the terminal.

-> m Text 

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

Since: 1.0.0.0

askUntil Source #

Arguments

:: (MonadByline m, ToStylizedText a, ToStylizedText e) 
=> a

The prompt to display.

-> Maybe Text

The default answer if the user presses enter without typing anything.

-> (Text -> m (Either e b))

A function to validate the user input. If the user input is acceptable the function should return Right. If the input is invalid then it should return Left with an error message to display. The error message will be printed with sayLn.

-> m b 

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

Since: 1.0.0.0