repl-toolkit-1.1.0.0: Toolkit for quickly whipping up config files and command-line interfaces.

Safe HaskellSafe
LanguageHaskell2010

System.REPL.Types

Description

Synopsis

Documentation

type TypeError = SomeException Source #

An error message indicating that a value wasn't able to be parsed.

type PredicateError = SomeException Source #

An error message indicating that a value failed a predicate.

type PromptMsg = Text Source #

A prompt.

type Predicate m a b = a -> m (Either PredicateError b) Source #

A predicate which a value has to fulfil.

type Predicate' m a = Predicate m a a Source #

A predicate which does not change the type of its input.

type Parser a = Text -> Either TypeError a Source #

A parser which either returns a parsed value or an error message.

data Asker m a b Source #

The description of an 'ask for user input'-action. The type parameters are the used monad (typically IO or ExceptT), the type of the read value and the type of the error that is thrown in case of failures.

The components are a prompt, a parser, and a predicate that the parsed value must fulfil. The predicate

  • is monadic and
  • can change the returned type (useful for adjoining additional information)

Constructors

Asker 

Fields

type Asker' m a = Asker m a a Source #

An Asker which does not convert its argument into a different type after parsing.

data SomeAskerError Source #

Generic error related to Askers. Either the input was incorrect in some way, or the process was aborted by the user.

Constructors

Exception e => SomeAskerError e 

genericTypeError :: Text -> SomeException Source #

Constructor for GenericTypeError which wraps the value into a SomeException.

genericPredicateError :: Text -> SomeException Source #

Constructor for GenericTypeError which wraps the value into a SomeException.

newtype Verbatim Source #

A verbatim Text whose Read instance simply returns the read string, as-is. This is useful for askers which ask for strings without quotes.

Constructors

Verbatim 

Fields

Instances

Read Verbatim Source #

Read-instance for Verbatim. Wraps the given value into quotes and reads it a a Text.

data PathExistenceType Source #

Indicates whether the target of a path exists and what form it has.

Instances

Bounded PathExistenceType Source # 
Enum PathExistenceType Source # 
Eq PathExistenceType Source # 
Ord PathExistenceType Source # 
Read PathExistenceType Source # 
Show PathExistenceType Source # 

data Command m i a Source #

A REPL command, possibly with parameters.

Constructors

Command 

Fields

  • commandName :: Text

    The short name of the command. Purely informative.

  • commandTest :: i -> Bool

    Returns whether the first part of an input (the command name) matches a the command. defCommandTest is appropriate for most cases.

  • commandDesc :: Text

    A description of the command.

  • runPartialCommand :: [i] -> m (a, [i])

    Runs the command with the input text as parameter, returning the unconsumed input.

Instances

Functor m => Functor (Command m i) Source # 

Methods

fmap :: (a -> b) -> Command m i a -> Command m i b #

(<$) :: a -> Command m i b -> Command m i a #

Monad m => Apply (Command m i) Source # 

Methods

(<.>) :: Command m i (a -> b) -> Command m i a -> Command m i b #

(.>) :: Command m i a -> Command m i b -> Command m i b #

(<.) :: Command m i a -> Command m i b -> Command m i a #

Monad m => Bind (Command m i) Source # 

Methods

(>>-) :: Command m i a -> (a -> Command m i b) -> Command m i b #

join :: Command m i (Command m i a) -> Command m i a #