Copyright | This file is part of the package addy. 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. |
---|---|
License | BSD-2-Clause |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class Monad m => MonadByline (m :: * -> *)
- data BylineT m a
- runBylineT :: (MonadIO m, MonadMask m) => BylineT m a -> m (Maybe a)
- say :: (MonadByline m, ToStylizedText a) => a -> m ()
- sayLn :: (MonadByline m, ToStylizedText a) => a -> m ()
- askLn :: (MonadByline m, ToStylizedText a) => a -> Maybe Text -> m Text
- askChar :: (MonadByline m, ToStylizedText a) => a -> m Char
- askPassword :: (MonadByline m, ToStylizedText a) => a -> Maybe Char -> m Text
- askUntil :: (MonadByline m, ToStylizedText a, ToStylizedText e) => a -> Maybe Text -> (Text -> m (Either e b)) -> m b
- data Stylized a
- class ToStylizedText a where
- toStylizedText :: a -> Stylized Text
- text :: Text -> Stylized Text
- fg :: Color -> Stylized Text
- bg :: Color -> Stylized Text
- bold :: Stylized Text
- underline :: Stylized Text
- swapFgBg :: Stylized Text
- data Color
- black :: Color
- red :: Color
- green :: Color
- yellow :: Color
- blue :: Color
- magenta :: Color
- cyan :: Color
- white :: Color
- rgb :: Word8 -> Word8 -> Word8 -> Color
How to Use this Library
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 Semigroup
(<>)
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 #-} example :: MonadByline m => m Text example = do sayLn ("Hey, I like " <> (Haskell <> fg magenta) <> "!") let question = "What's " <> ("your" <> bold) <> " favorite " <> ("language" <> fg green <> underline) <> "? " askLn question (Just Haskell)
More complete examples can be found in the examples
directory of the distribution tarball or in the
repository.
Byline Class and Transformer
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 # | |
Defined in Byline.Internal.Eval liftByline :: F PrimF a -> BylineT m a | |
Monad m => MonadByline (BylineT m) Source # | |
Defined in Byline.Internal.Simulation liftByline :: F PrimF a -> BylineT m a | |
MonadByline m => MonadByline (IdentityT m) Source # | |
Defined in Byline.Internal.Eval liftByline :: F PrimF a -> IdentityT m a | |
MonadByline m => MonadByline (ExceptT e m) Source # | |
Defined in Byline.Internal.Eval liftByline :: F PrimF a -> ExceptT e m a | |
MonadByline m => MonadByline (ReaderT r m) Source # | |
Defined in Byline.Internal.Eval liftByline :: F PrimF a -> ReaderT r m a | |
MonadByline m => MonadByline (StateT s m) Source # | |
Defined in Byline.Internal.Eval liftByline :: F PrimF a -> StateT s m a | |
MonadByline m => MonadByline (StateT s m) Source # | |
Defined in Byline.Internal.Eval liftByline :: F PrimF a -> StateT s m a | |
MonadByline m => MonadByline (ContT r m) Source # | |
Defined in Byline.Internal.Eval liftByline :: F PrimF a -> ContT r m a |
A monad transformer that implements MonadByline
.
Since: 1.0.0.0
Instances
MonadTrans BylineT Source # | |
Defined in Byline.Internal.Eval | |
MonadState s m => MonadState s (BylineT m) Source # | |
MonadReader r m => MonadReader r (BylineT m) Source # | |
MonadError e m => MonadError e (BylineT m) Source # | |
Defined in Byline.Internal.Eval throwError :: e -> BylineT m a # catchError :: BylineT m a -> (e -> BylineT m a) -> BylineT m a # | |
Monad (BylineT m) Source # | |
Functor (BylineT m) Source # | |
Applicative (BylineT m) Source # | |
MonadIO m => MonadIO (BylineT m) Source # | |
Defined in Byline.Internal.Eval | |
MonadThrow m => MonadThrow (BylineT m) Source # | |
Defined in Byline.Internal.Eval | |
MonadCatch m => MonadCatch (BylineT m) Source # | |
MonadCont m => MonadCont (BylineT m) Source # | |
MonadByline (BylineT m) Source # | |
Defined in Byline.Internal.Eval liftByline :: F PrimF a -> BylineT m a |
runBylineT :: (MonadIO m, MonadMask m) => BylineT m a -> m (Maybe a) Source #
Discharge the MonadByline
effect by running all operations and
returning the result in the base monad.
The result is wrapped in a Maybe
where a Nothing
value
indicates that an end-of-file (EOF) signal was received while
reading user input.
Since: 1.0.0.0
Basic User Interaction
:: (MonadByline m, ToStylizedText a) | |
=> a | The stylized text to output. |
-> m () |
:: (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
:: (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
:: (MonadByline m, ToStylizedText a) | |
=> a | The prompt to display. |
-> m Char |
Read a single character of input.
Since: 1.0.0.0
:: (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 |
-> 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
:: (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 |
-> m b |
Continue to prompt for a response until a confirmation function returns a valid result.
Since: 1.0.0.0
Stylizing Modifiers
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
class ToStylizedText a where Source #
A class for types that can be converted to Stylized
text.
toStylizedText :: a -> Stylized Text Source #
Instances
ToStylizedText (Stylized Text) Source # | Since: 1.0.0.0 |
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. However, if you are not
using any of the other stylized modifiers then this function can be
helpful for avoiding "Ambiguous type variable" compile errors.
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
Colors
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