Copyright | (c) Justin Le 2015 |
---|---|
License | MIT |
Maintainer | justin@jle.im |
Stability | unstable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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.
- type Prompt a b = PromptT a b Identity
- runPromptM :: Monad m => Prompt a b r -> (a -> m b) -> m r
- runPrompt :: Prompt a b r -> (a -> b) -> r
- interactP :: Prompt String String r -> IO r
- data PromptT a b t r
- runPromptTM :: Monad m => PromptT a b t r -> (a -> m (t b)) -> m (t r)
- runPromptT :: PromptT a b t r -> (a -> t b) -> t r
- interactPT :: Applicative t => PromptT String String t r -> IO (t r)
- class Applicative m => MonadPrompt a b m | m -> a b where
- prompt' :: MonadPrompt a b m => a -> m b
- prompts' :: MonadPrompt a b m => (b -> c) -> a -> m c
- promptP :: a -> PromptT a b t b
- promptsP :: Functor t => (b -> c) -> a -> PromptT a b t c
- promptP' :: a -> PromptT a b t b
- promptsP' :: Functor t => (b -> c) -> a -> PromptT a b t c
- mapPromptT :: (t r -> t s) -> PromptT a b t r -> PromptT a b t s
- hoistP :: (forall s. t s -> u s) -> (forall s. u s -> t s) -> PromptT a b t r -> PromptT a b u r
- liftP :: t r -> PromptT a b t r
- mkPromptT :: (forall m. Monad m => (a -> m (t b)) -> m (t r)) -> PromptT a b t r
- mkPrompt :: (forall m. Monad m => (a -> m b) -> m r) -> Prompt a b r
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.
:: Monad m | |
=> Prompt a b r | |
-> (a -> m b) | "Prompt response function", effectfully
responding to a given |
-> m r |
Run a
with a given effectful Prompt
a b ra -> 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.
Effectively treats a
as a Prompt
a bforall m. ReaderT (a -> m b) m
:: Prompt a b r | |
-> (a -> b) | "Prompt response function", purely responding
to a given |
-> r |
interactP :: Prompt String String r -> IO r Source #
Run a
in IO by sending the request to stdout
and reading the response from stdin.Prompt
String String
PromptT
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.
Applicative t => MonadPrompt a b (PromptT a b t) Source # | |
(MonadError e t, Traversable t) => MonadError e (PromptT a b t) Source # | |
(MonadReader r t, Traversable t) => MonadReader r (PromptT a b t) Source # | |
(MonadState s t, Traversable t) => MonadState s (PromptT a b t) Source # | |
(MonadWriter w t, Traversable t) => MonadWriter w (PromptT a b t) Source # | |
MonadTrans (PromptT a b) Source # | |
(Monad t, Traversable t) => Monad (PromptT a b t) Source # | |
Functor t => Functor (PromptT a b t) Source # | |
Applicative t => Applicative (PromptT a b t) Source # | |
(Alternative t, Traversable t) => Alternative (PromptT a b t) Source # | |
(MonadPlus t, Traversable t) => MonadPlus (PromptT a b t) Source # | |
:: Monad m | |
=> PromptT a b t r | |
-> (a -> m (t b)) | "Prompt response function",
effectfully responding to a given |
-> m (t r) |
Run a
with a given effectful PromptT
a b t ra -> 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.
:: PromptT a b t r | |
-> (a -> t b) | "Prompt response function", "purely"
responding to a given |
-> t r |
Run a
with a given PromptT
a b t ra -> 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
in IO by sending the request to stdout
and reading the response from stdin.PromptT
String String
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
.
Prompt with an a
for a b
in the context of the type.
prompts :: (b -> c) -> a -> m c Source #
Prompt with an a
for a b
in the context of the type, and
apply the given function to receive a c
.
(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) => 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
:: a | prompting value |
-> PromptT a b t b |
Like prompt
, but specialized to PromptT
and without
the Applicative
constraint.
Like prompts
, but specialized to PromptT
and downgrading the
Applicative
constraint to a Functor
constraint.
:: 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.
:: 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
.
:: (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.
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.