
I'd like to see the following addition to Control.Monad.Cont in mtl: instance Monoid r => Monoid (Cont r a) where mempty = Cont mempty m `mappend` m' = Cont (runCont m `mappend` runCont m') What's the process for suggesting, discussing, and making such changes? Cheers, - Conal

On Sat, Sep 08, 2007 at 05:26:09PM -0700, Conal Elliott wrote:
I'd like to see the following addition to Control.Monad.Cont in mtl:
instance Monoid r => Monoid (Cont r a) where mempty = Cont mempty m `mappend` m' = Cont (runCont m `mappend` runCont m')
What's the process for suggesting, discussing, and making such changes?
http://haskell.org/haskellwiki/Library_submissions (My 2 cents: Why not mempty = return mempty; mappend = liftM2 mappend ? Instances are best if unambiguous.) (Why is there no liftM0 ?) Stefan

Hm. I hadn't considered the liftM2 version. It would need Monoid a instead
of Monoid r, and it would behave differently. The version I suggested is
motivated by a library for a Fran-like functional event-based programming
that I'm preparing to release, based on Cont. In the monoid def I gave
corresponds, mempty is the never-occurring event, and mappend is a sort of
union of two events.
I sure don't know how to resolve these situations of more than one credible
instance. I'm seeing more & more of them.
Thanks for the pointer on library submissions.
I'm with you about liftM0 (and liftA0).
Cheers, - Conal
On 9/8/07, Stefan O'Rear
On Sat, Sep 08, 2007 at 05:26:09PM -0700, Conal Elliott wrote:
I'd like to see the following addition to Control.Monad.Cont in mtl:
instance Monoid r => Monoid (Cont r a) where mempty = Cont mempty m `mappend` m' = Cont (runCont m `mappend` runCont m')
What's the process for suggesting, discussing, and making such changes?
http://haskell.org/haskellwiki/Library_submissions
(My 2 cents: Why not mempty = return mempty; mappend = liftM2 mappend ? Instances are best if unambiguous.)
(Why is there no liftM0 ?)
Stefan
-----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.6 (GNU/Linux)
iD8DBQFG40G1FBz7OZ2P+dIRAiIgAJ0bhthqmBvcpoqLnNF+RcbccUBKYACeO4QO sJ9sUvnkvkfZsgIBbgq6r9U= =cCFe -----END PGP SIGNATURE-----

Hi Conal Conal:
I'd like to see the following addition to Control.Monad.Cont in mtl:
instance Monoid r => Monoid (Cont r a) where mempty = Cont mempty m `mappend` m' = Cont (runCont m `mappend` runCont m')
Does newtype deriving work here? Stefan:
(My 2 cents: Why not mempty = return mempty; mappend = liftM2 mappend ? Instances are best if unambiguous.)
Conal:
I sure don't know how to resolve these situations of more than one credible instance. I'm seeing more & more of them.
My usual rule of thumb is that inherent natural monoidal structure should have a higher priority than just applicative lifting of monoidal structure from the value type. Here it's a bit harder to call because it's a choice of two lifts, but I'd suggest that (Cont r) has natural monoidal structure if r is a monoid, and hence this should take precedence over the applicative lifting (which is what liftM2 does, but with too restrictive a type). I guess my fairly feeble reason for this rule of thumb is that it fits with what one would expect for []. It may also be to do with the way I read types: when I see a type application (f t), I think of it as an f-like thing with t-like details, hence the natural properties of f are somehow the more significant. Moreover, preferring the f-specific thing is no big deal if you have a cheap and uniform way to get the other thing (eg, liftA2 or idiom brackets). The f-specific thing usually requires special consideration, hence benefits most from overloading. So I'm with you on this one. All the best Conor

On Sun, Sep 09, 2007 at 12:58:25PM +0100, Conor McBride wrote:
My usual rule of thumb is that inherent natural monoidal structure should have a higher priority than just applicative lifting of monoidal structure from the value type. Here it's a bit harder to call because it's a choice of two lifts, but I'd suggest that (Cont r) has natural monoidal structure if r is a monoid, and hence this should take precedence over the applicative lifting (which is what liftM2 does, but with too restrictive a type).
I guess my fairly feeble reason for this rule of thumb is that it fits with what one would expect for []. It may also be to do with the way I read types: when I see a type application (f t), I think of it as an f-like thing with t-like details, hence the natural properties of f are somehow the more significant. Moreover, preferring the f-specific thing is no big deal if you have a cheap and uniform way to get the other thing (eg, liftA2 or idiom brackets). The f-specific thing usually requires special consideration, hence benefits most from overloading.
Okay, conversion successful. I want your instance now. :) Stefan

Thanks, Conor. I like your reason of appealing to f structure over t
structure in (f t). And, yes I'd forgotten to mention that the monoid
instance I suggested is exactly the one that holds for the representation
(under the newtype).
Deriving works just fine here:
deriving instance Monoid (Cont r a)
Cheers, - Conal
On 9/9/07, Conor McBride
Hi Conal
Conal:
I'd like to see the following addition to Control.Monad.Cont in mtl:
instance Monoid r => Monoid (Cont r a) where mempty = Cont mempty m `mappend` m' = Cont (runCont m `mappend` runCont m')
Does newtype deriving work here?
Stefan:
(My 2 cents: Why not mempty = return mempty; mappend = liftM2 mappend ? Instances are best if unambiguous.)
Conal:
I sure don't know how to resolve these situations of more than one credible instance. I'm seeing more & more of them.
My usual rule of thumb is that inherent natural monoidal structure should have a higher priority than just applicative lifting of monoidal structure from the value type. Here it's a bit harder to call because it's a choice of two lifts, but I'd suggest that (Cont r) has natural monoidal structure if r is a monoid, and hence this should take precedence over the applicative lifting (which is what liftM2 does, but with too restrictive a type).
I guess my fairly feeble reason for this rule of thumb is that it fits with what one would expect for []. It may also be to do with the way I read types: when I see a type application (f t), I think of it as an f-like thing with t-like details, hence the natural properties of f are somehow the more significant. Moreover, preferring the f-specific thing is no big deal if you have a cheap and uniform way to get the other thing (eg, liftA2 or idiom brackets). The f-specific thing usually requires special consideration, hence benefits most from overloading.
So I'm with you on this one.
All the best
Conor

Conor McBride wrote:
My usual rule of thumb is that inherent natural monoidal structure should have a higher priority than just applicative lifting of monoidal structure from the value type.
Monoid is a bit ridiculous as a class, as there are frequently several useful monoids on a type, leading to a collection of ugly wrapper newtypes. Monoid ought to be a type, in my view. And each of those wrapper classes can be replaced by a value in that type. -- Ashley Yakeley Seattle WA

Ashley Yakeley wrote:
Conor McBride wrote:
My usual rule of thumb is that inherent natural monoidal structure should have a higher priority than just applicative lifting of monoidal structure from the value type.
Monoid is a bit ridiculous as a class, as there are frequently several useful monoids on a type, leading to a collection of ugly wrapper newtypes.
Monoid ought to be a type, in my view. And each of those wrapper classes can be replaced by a value in that type.
Would you care to elaborate this idea? Do you mean a record with two functions? Cheers Ben

Hi,
On 9/18/07, Benjamin Franksen
Ashley Yakeley wrote:
Conor McBride wrote:
My usual rule of thumb is that inherent natural monoidal structure should have a higher priority than just applicative lifting of monoidal structure from the value type.
Monoid is a bit ridiculous as a class, as there are frequently several useful monoids on a type, leading to a collection of ugly wrapper newtypes.
Monoid ought to be a type, in my view. And each of those wrapper classes can be replaced by a value in that type.
Would you care to elaborate this idea? Do you mean a record with two functions?
Here is how you can do that: data Monoid a = Monoid { mempty :: a, mappend :: a -> a -> a } int_add :: Monoid Int int_add = Monoid { mempty = 0, mappend = (+) } int_mul :: Monoid Int int_mul = Monoid { mempty = 1, mappend = (*) } -- etc... -Iavor

On 9/21/07, Iavor Diatchki
Hi,
On 9/18/07, Benjamin Franksen
wrote: Ashley Yakeley wrote:
Monoid ought to be a type, in my view. And each of those wrapper classes can be replaced by a value in that type.
Would you care to elaborate this idea? Do you mean a record with two functions?
Here is how you can do that:
data Monoid a = Monoid { mempty :: a, mappend :: a -> a -> a }
Alternatively,
class Monoid a where
type Carrier a
mempty :: a -> Carrier a
mappend :: a -> Carrier a -> Carrier a -> Carrier a
data Sum a
instance Num a => Monoid (Sum a) where
type Carrier (Sum a) = a
mempty _ = 0
mappend _ = (+)
data Lift f a
instance (Monoid a, Applicative f) => Monoid (Lift f a) where
type Carrier (Lift f a) = f (Carrier a)
mempty _ = pure (mempty (undefined::a))
mappend _ = liftA2 (mappend (undefined::a))
data Writer o a = Writer (Carrier o) a
instance (Monoid o) => Monad (Writer o) where
return a = Writer (mempty (undefined::o)) a
(Writer o1 a) >>= f =
let Writer o2 b = f a in Writer (mappend (undefined::o) o1 o2) b
--
Dave Menendez

On 9/8/07, Conal Elliott
I'd like to see the following addition to Control.Monad.Cont in mtl:
instance Monoid r => Monoid (Cont r a) where mempty = Cont mempty m `mappend` m' = Cont (runCont m `mappend` runCont m')
Alternatively, instance Monoid r => MonadPlus (Cont r a) where mzero = Cont mempty mplus a b = Cont $ runCont a `mappend` runCont b "Cont (Endo b) a" is the usual backtracking monad.

"Cont (Endo b) a" is the usual backtracking monad.
It is? Would you say more about that? A pointer would be fine. I'm
wondering what the role of Endo is here.
Cheers, - Conal
On 9/9/07, David Menendez
On 9/8/07, Conal Elliott
wrote: I'd like to see the following addition to Control.Monad.Cont in mtl:
instance Monoid r => Monoid (Cont r a) where mempty = Cont mempty m `mappend` m' = Cont (runCont m `mappend` runCont m')
Alternatively,
instance Monoid r => MonadPlus (Cont r a) where mzero = Cont mempty mplus a b = Cont $ runCont a `mappend` runCont b
"Cont (Endo b) a" is the usual backtracking monad.

On 9/9/07, Conal Elliott
"Cont (Endo b) a" is the usual backtracking monad.
It is? Would you say more about that? A pointer would be fine. I'm wondering what the role of Endo is here.
I don't know if there's anything written about it. Essentially, "Cont (Endo b) a" is isomorphic to "(a -> b -> b) -> b -> b", which is (one implementation of) a backtracking monad. The use of Endo b introduces the failure continuation. newtype Nondet a = Nondet { runNondet :: forall b. (a -> b -> b) -> b -> b) } toNondet :: (forall b. Cont (Endo b) a) -> Nondet a toNondet m = Nondet (\sk fk -> appEndo (runCont m (Endo . sk)) fk) fromNondet :: Nondet a -> Cont (Endo b) a fromNondet m = Cont $ \sk -> Endo $ \fk -> runNondet m (appEndo . sk) fk The Monad and MonadPlus instances you would write for Nondet are equivalent to the instances for Cont (Endo b). instance Monad Nondet where return a = Nondet (\k -> k a) m >>= f = Nondet (\k -> runNondet m (\a -> runNondet (f a) k)) instance MonadPlus Nondet where mzero = Nondet (\k -> id) mplus a b = Nondet (\k -> runNondet a k . runNondet b k) Note that id and (.) are the mempty and mappend for Endo. Interestingly, the backtracking monad transformer NondetT m a is equivalent to "forall b. Cont (Endo (m b)) a", not "ContT (Endo b) m a". newtype NondetT m a = NondetT { runNondetT :: forall b. (a -> m b -> m b) -> m b -> m b } toNondetT :: (forall b. Cont (Endo (m b)) a) -> NondetT m a toNondetT m = NondetT (\sk fk -> appEndo (runCont m (Endo . sk)) fk) fromNondetT :: NondetT m a -> Cont (Endo (m b)) a fromNondetT m = Cont $ \sk -> Endo $ \fk -> runNondetT m (appEndo . sk) fk Here's the lift for NondetT, after conversion: lift' :: Monad m => m a -> Cont (Endo (m b)) a lift' m = Cont $ \sk -> Endo $ \fk -> m >>= \a -> appEndo (sk a) fk
participants (7)
-
Ashley Yakeley
-
Benjamin Franksen
-
Conal Elliott
-
Conor McBride
-
David Menendez
-
Iavor Diatchki
-
Stefan O'Rear