
On Thu, Apr 6, 2017 at 1:53 PM, Bertram Felgenhauer via Haskell-Cafe < haskell-cafe@haskell.org> wrote:
Ertugrul Söylemez wrote:
Could someone outline for me the downsides of using the Prompt monad?
For one thing I find its definition to be overcomplicated for what it does.
I'm assuming that this is referring to the MonadPrompt package... If you mean the type, it's essentially the same as
http://hackage.haskell.org/package/free-4.12.4/docs/src/ Control-Monad-Free-Church.html#F
after plugging in PromptF' p (see below). The point is to make left associative use of >=> efficient.
For another the same can be achieved with free monads in a more transparent and flexible manner:
import Control.Monad.Free.Class
data PromptF a b x = PromptF (b -> x) a deriving (Functor)
More accurately,
data PromptF' p x = forall a. PromptF (a -> x) (p a)
(with the obvious Functor instance).
The existential highlights an important design idea of the Prompt monad, namely that a monadic DSL would be specified by a GADT (p a), where `a` represents the result type of the corresponding operation. So, for a state monad, one would use
data PromptState s a where Get :: PromptState s s Put :: s -> PromptState s ()
which defines a "get" operation without arguments that returns a value of type s, and a "put" operation that takes a value of type s, but returns nothing.
This is slightly less expressive than free monads (the main loss, I believe, is that a prompt GADT cannot express that an operation is necessarily a leaf of computations; while free monads can also express non-determinism, that does not give rise to any useful guarantees for the resulting behavior, as far as I can see). I would argue that prompt GADTs are sufficient for many applications, and that thinking in terms of interfaces is more natural to many programmers than thinking in terms of unfolding computations.
It’s worth noting that Prompt p is the free monad for a type constructor p,
just as Free f is the free monad for a Functor f. As such, when p is a
Functor, they are isomorphic.
data Free f a = Var a | Wrap (f (Free f a))
newtype Prompt p a = Prompt { unPrompt :: forall b. (forall i. p i -> (i ->
b) -> b) -> (a -> b) -> b }
-- equivalently, Prompt p a = Done a | forall i. Prompt (p i) (i -> Prompt
p a)
prompt :: p a -> Prompt p a
prompt p = Prompt $ \c -> c p
promptFree :: Free f a -> Prompt f a
promptFree (Var a) = return a
promptFree (Wrap f) = prompt f >>= promptFree
freePrompt :: Functor f => Prompt f a -> Free f a
freePrompt m = unPrompt m (\f k -> Wrap (fmap k f)) Var
Thus, it’s entirely possible to do non-determinism and halting with Prompt.
Just to have a concrete example, here’s an interface that prints strings
and has non-determinism.
data W a where
Print :: String -> W ()
End :: W a
Choose :: a -> a -> W a
Note that End and Choose are fully polymorphic. This means that an
interpreter has to pass one of the two provided values to the continuation
when it receives Choose, and it can’t call the continuation when it
receives End.
--
Dave Menendez