Downsides of the Prompt Monad

Could someone outline for me the downsides of using the Prompt monad?

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. 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) prompt :: (MonadFree (PromptF a b) m) => a -> m b prompt = liftF . PromptF id Now the kinds of extra effects that you allow depends on which free monad implementation you use. If you use F, you get the equivalent of Prompt, if you use FT, you get PromptT. In the F case the iter function corresponds to runPrompt, iterM corresponds to runPromptM. In the FT case there are iterT and iterTM. Greets ertes

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-C... 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. Cheers, Bertram P.S. it may be worth noting that MonadPrompt predates the advent of free monads in the Haskell community.

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

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).
Are we talking about the same PromptT here? I was assuming this one: https://hackage.haskell.org/package/prompt-0.1.1.2/docs/Control-Monad-Prompt.... Even if not, it seems to me that it should be an abstraction layer above free monads. It could be a very thin layer around F/FT. That would facilitate reuse. Greets ertes

Ertugrul Söylemez wrote:
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).
Are we talking about the same PromptT here? I was assuming this one: https://hackage.haskell.org/package/prompt-0.1.1.2/docs/Control-Monad-Prompt....
No, I'm talking about https://hackage.haskell.org/package/MonadPrompt-1.0.0.5/docs/src/Control-Mon... (FWIW, I did mention the package name in my mail.) The type in the prompt package does not seem to offer the main benefit I mentioned, namely that the prompt value encodes the type of the return value of the `prompt` action; indeed, `prompt` in the prompt package has type prompt :: MonadPrompt a b m => a -> m b in contrast to prompt :: MonadPrompt p m => p a -> m a in MonadPrompt.
Even if not, it seems to me that it should be an abstraction layer above free monads. It could be a very thin layer around F/FT. That would facilitate reuse.
MonadPrompt is a very thin standalone package... I would be quite sad to lose that property. Cheers, Bertram

Ertugrul Söylemez wrote:
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).
Are we talking about the same PromptT here? I was assuming this one: https://hackage.haskell.org/package/prompt-0.1.1.2/docs/Control-Monad-Prompt....
I've looked a bit more closely at the difference between the prompt and MonadPrompt packages. PromptT a b t r from the prompt package is a newtype for forall m. Monad m => (a -> m (t b)) -> m (t r) using the "universal" Cont/Codensity monad, this becomes forall x. (a -> (t b -> x) -> x) -> (t r -> x) -> x) which is quite similar to the Prompt type from MonadPrompt: forall x. (p a -> (a -> x) -> x) -> (r -> x) -> x) The main innovation in prompt seems to be the 't' argument, which according to the package's readme, can be used for short-circuiting evaluation and nondeterminism (branching computations). As I explained in my previous email, the 'p' argument in MonadPrompt is meant to describe the API of a monadic DSL. It appears that the two ideas could be combined in a single type, forall x. (p a -> (t a -> x) -> x) -> (t r -> x) -> x) or forall m. Monad m => (p a -> m (t a)) -> m (t r) or, using the free monad defined by the functor data PromptF a b x = forall a. PromptF (t a -> x) (p a) Perhaps this is worth investigating further. Cheers, Bertram
participants (5)
-
Bertram Felgenhauer
-
David Feuer
-
David Menendez
-
Ertugrul Söylemez
-
Michael Litchard