| Copyright | This 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. | 
|---|---|
| License | BSD-2-Clause | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Byline.Simulation
Contents
Description
Synopsis
- data Simulated
- type SimulationFunction m = StateT (SimulationState m) m Simulated
- data SimulationState m = SimulationState {}
- data BylineT m a
- runBylineT :: Monad m => SimulationFunction m -> BylineT m a -> m (Maybe a)
- data Color
- black :: Color
- red :: Color
- green :: Color
- yellow :: Color
- blue :: Color
- magenta :: Color
- cyan :: Color
- white :: Color
- rgb :: Word8 -> Word8 -> Word8 -> Color
- class ToStylizedText a where- toStylizedText :: a -> Stylized Text
 
- data Stylized a
- text :: Text -> Stylized Text
- fg :: Color -> Stylized Text
- bg :: Color -> Stylized Text
- bold :: Stylized Text
- underline :: Stylized Text
- swapFgBg :: Stylized Text
- class Monad m => MonadByline (m :: * -> *)
- 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
Simulating User Interaction
This module provides a monad transformer that can simulate an
 interactive user session for testing MonadByline code.
Simulated Values
Simulated user input.
Since: 1.0.0.0
Constructors
| SimulatedInput Text | Simulate user input by providing the  If the asking function wants a single character of input then
 only the first character of the provided  | 
| SimulatedEOF | Simulate an end-of-file (EOF) character.  Usually this occurs
 when the user enters  | 
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
A monad transformer that implements the MonadByline class
 without actually doing anything.
Since: 1.0.0.0
Instances
| MonadTrans BylineT Source # | |
| Defined in Byline.Internal.Simulation | |
| 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.Simulation Methods throwError :: e -> BylineT m a # catchError :: BylineT m a -> (e -> BylineT m a) -> BylineT m a # | |
| Monad m => Monad (BylineT m) Source # | |
| Functor m => Functor (BylineT m) Source # | |
| Monad m => Applicative (BylineT m) Source # | |
| Defined in Byline.Internal.Simulation | |
| MonadIO m => MonadIO (BylineT m) Source # | |
| Defined in Byline.Internal.Simulation | |
| MonadThrow m => MonadThrow (BylineT m) Source # | |
| Defined in Byline.Internal.Simulation | |
| MonadCatch m => MonadCatch (BylineT m) Source # | |
| MonadCont m => MonadCont (BylineT m) Source # | |
| Monad m => MonadByline (BylineT m) Source # | |
| 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
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.
Methods
toStylizedText :: a -> Stylized Text Source #
Instances
| ToStylizedText (Stylized Text) Source # | Since: 1.0.0.0 | 
| Defined in Byline.Internal.Stylized | |
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
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
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
Arguments
| :: (MonadByline m, ToStylizedText a) | |
| => a | The stylized text to output. | 
| -> m () | 
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
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
Arguments
| :: (MonadByline m, ToStylizedText a) | |
| => a | The prompt to display. | 
| -> m Char | 
Read a single character of input.
Since: 1.0.0.0
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  | 
| -> 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
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  | 
| -> m b | 
Continue to prompt for a response until a confirmation function returns a valid result.
Since: 1.0.0.0