Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Implementation of monads that allow the computation
to prompt
for further input.
(c) 2008 Bertram Felgenhauer & Ryan Ingram Released as open source under a 3 clause BSD license. See the LICENSE file in the source code distribution for further information.
RecPromptT added by Cale Gibbard, contributed under the same license.
MonadPrompt monads allow you to pass some object of the prompt type in, and get a result of the prompt's answer type out.
- class Monad m => MonadPrompt p m | m -> p where
- prompt :: p a -> m a
- data Prompt p r
- runPromptC :: forall p r b. (r -> b) -> (forall a. p a -> (a -> b) -> b) -> Prompt p r -> b
- runPrompt :: (forall a. p a -> a) -> Prompt p r -> r
- runPromptM :: Monad m => (forall a. p a -> m a) -> Prompt p r -> m r
- data RecPrompt p r
- unRecPrompt :: RecPrompt p r -> Prompt (p (RecPrompt p)) r
- runRecPromptC :: forall p r b. (r -> b) -> (forall a. p (RecPrompt p) a -> (a -> b) -> b) -> RecPrompt p r -> b
- runRecPrompt :: (forall a. p (RecPrompt p) a -> a) -> RecPrompt p r -> r
- runRecPromptM :: Monad m => (forall a. p (RecPrompt p) a -> m a) -> RecPrompt p r -> m r
- data PromptT p m a
- runPromptT :: forall p m r b. (r -> b) -> (forall a. p a -> (a -> b) -> b) -> (forall a. m a -> (a -> b) -> b) -> PromptT p m r -> b
- runPromptTM :: forall p m r n. Monad n => (forall a. p a -> n a) -> (forall a. m a -> n a) -> PromptT p m r -> n r
- runPromptTM' :: forall p m r. Monad m => (forall a. p a -> m a) -> PromptT p m r -> m r
- data Lift p m a
- unPromptT :: PromptT p m a -> Prompt (Lift p m) a
- liftP :: MonadPrompt p m => Prompt p r -> m r
- data RecPromptT p m a
- unRecPromptT :: RecPromptT p m a -> Prompt (Lift (p (RecPromptT p m)) m) a
- runRecPromptT :: forall p r b m. (r -> b) -> (forall a. p (RecPromptT p m) a -> (a -> b) -> b) -> (forall a. m a -> (a -> b) -> b) -> RecPromptT p m r -> b
Documentation
class Monad m => MonadPrompt p m | m -> p where Source
You can construct a monad very simply with prompt, by putting all of its effects as terms in a GADT, like the following example:
data PromptState s a where Put :: s -> PromptState s () Get :: PromptState s s
You then use prompt
to access effects:
postIncrement :: MonadPrompt (PromptState Int) m => m Int postIncrement = do x <- prompt Get prompt (Put (x+1)) return x
The advantage of Prompt over implementing effects directly:
- Prompt is pure; it is only through the observation function runPromptC that you can cause effects.
- You don't have to worry about the monad laws; they are correct by construction and you cannot break them.
- You can implement several observation functions for the same type. See, for example, http://paste.lisp.org/display/53766 where a guessing game is implemented with an IO observation function for the user, and an AI observation function that plays the game automatically.
In these ways Prompt is similar to Unimo, but bind and return are inlined into the computation, whereas in Unimo they are handled as a term calculus. See http://sneezy.cs.nott.ac.uk/fplunch/weblog/?p=89
MonadPrompt p (Prompt p) | |
MonadPrompt p (PromptT p m) | |
MonadPrompt (p (RecPrompt p)) (RecPrompt p) | |
MonadPrompt (p (RecPromptT p m)) (RecPromptT p m) |
MonadPrompt p (Prompt p) | |
Monad (Prompt p) | |
Functor (Prompt p) | |
Applicative (Prompt p) |
:: (r -> b) | handler when there is no further computation |
-> (forall a. p a -> (a -> b) -> b) | handler for prompts |
-> Prompt p r | a prompt-based computation |
-> b | answer |
runPromptC
is the observation function for prompts. It takes
two functions as arguments:
ret
will be called with the final result of the computation, to convert it to the answer type.prm
will be called if there are any effects; it is passed a prompt and a continuation function. prm can apply the effect requested by the prompt and call the continuation.
In some cases prm can return the answer type directly; it may be useful to abort the remainder of the computation, or save off the continuation to be called later. There is a great example of using this to implement a UI for peg solitaire in Bertram Felgenhauer's post to Haskell-Cafe at http://www.haskell.org/pipermail/haskell-cafe/2008-January/038301.html
runPrompt :: (forall a. p a -> a) -> Prompt p r -> r Source
runPrompt
takes a way of converting prompts to an element in a pure
fashion and calculates the result of the prompt
runPromptM :: Monad m => (forall a. p a -> m a) -> Prompt p r -> m r Source
runPromptM
is similar to runPrompt
but allows the computation to happen in any monad.
RecPrompt
is for prompts which are dependent on the prompt monad.
For example, a MonadPlus
prompt:
data PromptPlus m a where PromptZero :: PromptPlus m a PromptPlus :: m a -> m a -> PromptPlus m a instance MonadPlus (RecPrompt PromptPlus) where mzero = prompt PromptZero mplus x y = prompt (PromptPlus x y)
Monad (RecPrompt p) | |
Functor (RecPrompt p) | |
Applicative (RecPrompt p) | |
MonadPrompt (p (RecPrompt p)) (RecPrompt p) |
unRecPrompt :: RecPrompt p r -> Prompt (p (RecPrompt p)) r Source
:: (r -> b) | handler when there is no further computation |
-> (forall a. p (RecPrompt p) a -> (a -> b) -> b) | handler for prompts |
-> RecPrompt p r | a prompt-based computation |
-> b | answer |
Runs a recursive prompt computation. This is similar to runPromptC
, but for recursive prompt types.
runRecPrompt :: (forall a. p (RecPrompt p) a -> a) -> RecPrompt p r -> r Source
Run a recursive prompt computation in a pure fashion, similar to runPrompt
.
runRecPromptM :: Monad m => (forall a. p (RecPrompt p) a -> m a) -> RecPrompt p r -> m r Source
Run a recursive prompt computation in an arbitrary monad, similar to runPromptM
.
Prompt can also be used to define monad transformers.
You will notice the lack of a Monad m
constraint; this is allowed
because Prompt doesn't use the underlying monad at all; instead
the observation function (generally implemented via runPromptT
)
will have the constraint.
MonadPrompt p (PromptT p m) | |
MonadTrans (PromptT p) | |
Monad (PromptT p m) | |
Functor (PromptT p m) | |
Applicative (PromptT p m) |
:: (r -> b) | handler when there is no further computation |
-> (forall a. p a -> (a -> b) -> b) | handler for prompts |
-> (forall a. m a -> (a -> b) -> b) | handler for lifted computations |
-> PromptT p m r | a prompt-based computation |
-> b | answer |
runPromptT
runs a prompt monad transformer.
:: Monad n | |
=> (forall a. p a -> n a) | interpretation for prompts |
-> (forall a. m a -> n a) | interpretation for lifted computations |
-> PromptT p m r | a prompt-based computation |
-> n r | resulting interpretation |
runPromptTM
is a useful variant of runPromptT when interpreting into another monad
:: Monad m | |
=> (forall a. p a -> m a) | interpretation for prompts |
-> PromptT p m r | a prompt-based computation |
-> m r | resulting interpretation |
runPromptTM'
specialises runPromptTM further for the case that you're interpreting to the base monad by supplying the identity function as the interpretation
for lifted computations
liftP :: MonadPrompt p m => Prompt p r -> m r Source
You can also lift any Prompt computation into a PromptT (or more generally, any appropriate MonadPrompt instance). This is the kind of place where the advantage of being able to use multiple observation functions on Prompt really shows.
data RecPromptT p m a Source
A recursive variant of the prompt monad transformer.
MonadTrans (RecPromptT p) | |
MonadPrompt (p (RecPromptT p m)) (RecPromptT p m) | |
Monad (RecPromptT p m) | |
Functor (RecPromptT p m) | |
Applicative (RecPromptT p m) |
unRecPromptT :: RecPromptT p m a -> Prompt (Lift (p (RecPromptT p m)) m) a Source
:: (r -> b) | handler when there is no further computation |
-> (forall a. p (RecPromptT p m) a -> (a -> b) -> b) | handler for prompts |
-> (forall a. m a -> (a -> b) -> b) | handler for lifted computations |
-> RecPromptT p m r | a prompt-based computation |
-> b | answer |
Run a recursive prompt monad transformer.