prompt-0.1.0.0: Monad (and transformer) for deferred-effect pure prompt-response queries

Copyright(c) Justin Le 2015
LicenseMIT
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Prompt

Contents

Description

Provides the PromptT type, which allows you to program computations that can "ask" or "prompt" with values to get values in return. The computation doesn't care about the process of prompting, or how it works, and has nothing to do with the effectful monad where the prompting will eventually take place.

For example, sometimes you might want a computation to be able to query or database, or talk with stdio, but you don't want your type to involve arbitrary IO or be over IO, opening the door to a mess of IO. Prompt lets you write programs that can query "something", and then at a later point in time, run it, providing the method of fulfilling each prompt. Write your program independent of IO, or databases, or stdio, etc.; only later "fill in" what it means. You can even run the same Prompt with different ways to fulfill the prompts --- pure, effectful, etc.

For usage examples and a more detailed explanation, see the README.

Synopsis

Prompt

type Prompt a b = PromptT a b Identity Source

Prompt type, providing the ability to "prompt" or "query" by presenting/asking with an a and receiving a b response.

prompt :: a -> (Prompt a b) b

"Ask with an a, get a b."

Has a Monad, Applicative, Functor, etc. instance so it can be sequenced monadically or applicatively, so you can sequence and bind from prompt.

Note that we defer the process of specifying how prompt delivers its b. It can take place in IO, or in any other effectful setting...but Prompt doesn't care, and it never involves IO or any arbitrary IO itself.

Can be "constructed directly" using mkPrompt, but typically using prompt and the Applicative, Monad instances etc. is better.

runPromptM Source

Arguments

:: Monad m 
=> Prompt a b r 
-> (a -> m b)

"Prompt response function", effectfully responding to a given a with a b.

-> m r 

Run a Prompt a b r with a given effectful a -> m b "prompt response" function, to get the resulting r in m. Note that the Prompt itself in general has nothing to do with m, and cannot execute arbitrary m other than that given in the prompt response function.

runPrompt Source

Arguments

:: Prompt a b r 
-> (a -> b)

"Prompt response function", purely responding to a given a with a b.

-> r 

Run a Prompt a b r with a pure a -> b prompt response function. More or less reduces Prompt a b to a Reader (a -> b).

interactP :: Prompt String String r -> IO r Source

Run a Prompt String String in IO by sending the request to stdout and reading the response from stdin.

PromptT

data PromptT a b t r Source

Like Prompt, but can perform its "pure" computations in the context of a Traversable t, to absorb short-circuiting behvaior with Maybe or Either, logging with Writer, etc., but this is in general completely unrelated to the effectful monad where the prompting will eventually take place. Specify short-circuiting and logging logic, without worrying about IO or anything relating to the prompting effect.

prompt :: a -> (PromptT a b t) b

Implements several useful typeclasses for working with the underlying Traversable and integrating effects, like Alternative, MonadError, MonadWriter, etc.

Constructor is hidden, but a direct constructing function is exported as mkPrompT in the rare case it is needed or wanted.

runPromptTM Source

Arguments

:: Monad m 
=> PromptT a b t r 
-> (a -> m (t b))

"Prompt response function", effectfully responding to a given a with a b.

-> m (t r) 

Run a PromptT a b t r with a given effectful a -> m (t b) "prompt response" function, to get the resulting r in m and t. The "prompt response" function is able to interact with the underlying Traversable t.

Note that the PromptT in general has nothing to do with the m, and cannot execute arbitrary m other than that given in the prompt response function.

runPromptT Source

Arguments

:: PromptT a b t r 
-> (a -> t b)

"Prompt response function", "purely" responding to a given a with a b in context of Traversable t.

-> t r 

Run a PromptT a b t r with a given a -> t b function, with Traversable t. The effects take place in the same context as the underlying context of the PromptT.

interactPT :: Applicative t => PromptT String String t r -> IO (t r) Source

Run a PromptT String String in IO by sending the request to stdout and reading the response from stdin.

Prompting

class Applicative m => MonadPrompt a b m | m -> a b where Source

An Applicative (and possibly Monad) where you can, at any time, "prompt" with an a and receive a b in response.

Instances include PromptT and any transformers monad transformer over another MonadPrompt.

Minimal complete definition

prompt | prompts

Methods

prompt Source

Arguments

:: a

prompting value

-> m b 

Prompt with an a for a b in the context of the type.

prompts Source

Arguments

:: (b -> c)

mapping function

-> a

prompting value

-> m c 

Prompt with an a for a b in the context of the type, and apply the given function to receive a c.

Instances

(Monad m, MonadPrompt a b m) => MonadPrompt a b (MaybeT m) Source 
(Monad m, MonadPrompt a b m, Monoid w) => MonadPrompt a b (WriterT w m) Source 
(Monad m, MonadPrompt a b m, Monoid w) => MonadPrompt a b (WriterT w m) Source 
(Monad m, MonadPrompt a b m) => MonadPrompt a b (StateT s m) Source 
(Monad m, MonadPrompt a b m) => MonadPrompt a b (StateT s m) Source 
(Monad m, MonadPrompt a b m, Error e) => MonadPrompt a b (ErrorT e m) Source 
(Monad m, MonadPrompt a b m) => MonadPrompt a b (ExceptT e m) Source 
(Monad m, MonadPrompt a b m) => MonadPrompt a b (ReaderT r m) Source 
Applicative t => MonadPrompt a b (PromptT a b t) Source 
(Monad m, MonadPrompt a b m, Monoid w) => MonadPrompt a b (RWST r w s m) Source 
(Monad m, MonadPrompt a b m, Monoid w) => MonadPrompt a b (RWST r w s m) Source 

prompt' :: MonadPrompt a b m => a -> m b Source

A version of prompt strict on its prompting value.

prompts' :: MonadPrompt a b m => (b -> c) -> a -> m c Source

A version of prompts strict on its prompting value.

Specialized

promptP Source

Arguments

:: a

prompting value

-> PromptT a b t b 

Like prompt, but specialized to PromptT and without the Applicative constraint.

promptsP Source

Arguments

:: Functor t 
=> (b -> c)

to be applied to response value

-> a

prompting value

-> PromptT a b t c 

Like prompts, but specialized to PromptT and downgrading the Applicative constraint to a Functor constraint.

promptP' Source

Arguments

:: a

prompting value (strict)

-> PromptT a b t b 

Like prompt', but specialized to PromptT and without the Applicative constraint. Is a promptP strict on its argument.

promptsP' Source

Arguments

:: Functor t 
=> (b -> c)

to be applied to response value

-> a

prompting value (strict)

-> PromptT a b t c 

Like prompts', but specialized to PromptT and downgrading the Applicative constraint to a Functor constraint. Is a promptsP strict on its argument.

Low level

mapPromptT :: (t r -> t s) -> PromptT a b t r -> PromptT a b t s Source

Maps the underying t a returned by PromptT. Cannot change t.

hoistP Source

Arguments

:: (forall s. t s -> u s)

forward natural transformation

-> (forall s. u s -> t s)

backwards natural transformation

-> PromptT a b t r 
-> PromptT a b u r 

Swap out the Traversable t with a pair of natural transformations. The first maps the output t a, and the second maps the result of the prompting function.

liftP :: t r -> PromptT a b t r Source

Like lift, but without the Monad constraint.

mkPromptT :: (forall m. Monad m => (a -> m (t b)) -> m (t r)) -> PromptT a b t r Source

Directly construct a PromptT. Has to be able to take a (a - m (t b)) -> m (t r) that can work on any Monad.

Typically this won't be used, but is provided for completion; using prompt and its Applicative, Monad instances, etc., is more clear.

prompt r = mkPromptT $ g -> g r

mkPrompt :: (forall m. Monad m => (a -> m b) -> m r) -> Prompt a b r Source

Directly construct a Prompt. Has to be able to take a (a -> m b) -> m r that can work on any Monad.

Typically this won't be used, but is provided for completion; using prompt and its Applicative, Monad instances, etc., is more clear.