Add instance Monad ZipList

instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys instance MonadFail ZipList where fail _ = empty instance MonadPlus ZipList

I don't remember why right now, but it's moderately well-known that there
is no possible Monad instance compatible with the Applicative instance for
ZipList. See the answers to
https://stackoverflow.com/questions/6463058/help-on-writing-the-colist-monad...
by pigworker (Conor McBride) and C. A. McCann.
On Thu, Jun 4, 2020, 2:53 AM Dannyu NDos
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

David is right. This can't happen, unfortunately
On Thu, Jun 4, 2020, 12:48 AM David Feuer
I don't remember why right now, but it's moderately well-known that there is no possible Monad instance compatible with the Applicative instance for ZipList. See the answers to https://stackoverflow.com/questions/6463058/help-on-writing-the-colist-monad... by pigworker (Conor McBride) and C. A. McCann.
On Thu, Jun 4, 2020, 2:53 AM Dannyu NDos
wrote: instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

This sounds worth documenting though.
Dannyu, would you be interested in updating the ZipList docs to say
why it doesn't have a Monad instance?
Cheers,
Simon
Am Do., 4. Juni 2020 um 17:21 Uhr schrieb chessai .
David is right. This can't happen, unfortunately
On Thu, Jun 4, 2020, 12:48 AM David Feuer
wrote: I don't remember why right now, but it's moderately well-known that there is no possible Monad instance compatible with the Applicative instance for ZipList. See the answers to https://stackoverflow.com/questions/6463058/help-on-writing-the-colist-monad... by pigworker (Conor McBride) and C. A. McCann.
On Thu, Jun 4, 2020, 2:53 AM Dannyu NDos
wrote: instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Agreed, that would be a great addition.
On Thu, Jun 4, 2020, 8:31 AM Simon Jakobi
This sounds worth documenting though.
Dannyu, would you be interested in updating the ZipList docs to say why it doesn't have a Monad instance?
Cheers, Simon
:
David is right. This can't happen, unfortunately
On Thu, Jun 4, 2020, 12:48 AM David Feuer
wrote: I don't remember why right now, but it's moderately well-known that
Am Do., 4. Juni 2020 um 17:21 Uhr schrieb chessai .
https://stackoverflow.com/questions/6463058/help-on-writing-the-colist-monad... by pigworker (Conor McBride) and C. A. McCann. On Thu, Jun 4, 2020, 2:53 AM Dannyu NDos
wrote: instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList .
fmap snd . uncons . getZipList . f
head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

To add documentation, we need an explanation of *why* it's impossible.
On Thu, Jun 4, 2020, 11:35 AM chessai .
Agreed, that would be a great addition.
On Thu, Jun 4, 2020, 8:31 AM Simon Jakobi
wrote: This sounds worth documenting though.
Dannyu, would you be interested in updating the ZipList docs to say why it doesn't have a Monad instance?
Cheers, Simon
Am Do., 4. Juni 2020 um 17:21 Uhr schrieb chessai . < chessai1996@gmail.com>:
David is right. This can't happen, unfortunately
On Thu, Jun 4, 2020, 12:48 AM David Feuer
I don't remember why right now, but it's moderately well-known that
wrote: there is no possible Monad instance compatible with the Applicative instance for ZipList. See the answers to https://stackoverflow.com/questions/6463058/help-on-writing-the-colist-monad... by pigworker (Conor McBride) and C. A. McCann.
On Thu, Jun 4, 2020, 2:53 AM Dannyu NDos
wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList
. fmap snd . uncons . getZipList . f
head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I know of counterexamples that show why the “obvious” instances don’t work. One nice one is here:
https://www.reddit.com/r/haskell/comments/nfyvy/instance_monad_ziplist_where/c38x9q9?utm_source=share&utm_medium=web2x
But I don’t know of a simple full proof of why no such instance is possible. My guess would be that we should consider the action of the operations on lengths of lists, and show that the requirements for monad and ziplist conflict.
-g
On Jun 4, 2020, 11:57 AM -0400, David Feuer
To add documentation, we need an explanation of *why* it's impossible.
On Thu, Jun 4, 2020, 11:35 AM chessai .
wrote: Agreed, that would be a great addition.
On Thu, Jun 4, 2020, 8:31 AM Simon Jakobi
wrote: This sounds worth documenting though.
Dannyu, would you be interested in updating the ZipList docs to say why it doesn't have a Monad instance?
Cheers, Simon
Am Do., 4. Juni 2020 um 17:21 Uhr schrieb chessai .
: David is right. This can't happen, unfortunately
On Thu, Jun 4, 2020, 12:48 AM David Feuer
wrote: > > I don't remember why right now, but it's moderately well-known that there is no possible Monad instance compatible with the Applicative instance for ZipList. See the answers to https://stackoverflow.com/questions/6463058/help-on-writing-the-colist-monad... by pigworker (Conor McBride) and C. A. McCann. > > On Thu, Jun 4, 2020, 2:53 AM Dannyu NDos wrote: >> >> instance Monad ZipList where >> ZipList [] >>= _ = ZipList [] >> ZipList (x:xs) >>= f = ZipList $ do >> let ZipList y' = f x >> guard (not (null y')) >> let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f >> head y' : ys >> >> instance MonadFail ZipList where >> fail _ = empty >> >> instance MonadPlus ZipList >> _______________________________________________ >> Libraries mailing list >> Libraries@haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > _______________________________________________ > Libraries mailing list > Libraries@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I think that the counterexample I linked should be enough to rule out any instance for monad, in fact, in conjunction with the fact that to make liftA2 (,) correspond to zip, we need to have the join operation result in something which is the minimum of the length of the enclosing ziplist and all “enclosed” ziplists.
I think but haven’t proven that it is the case that not only is infinite ziplist (i.e. “stream”) a monad, and every fixed-size ziplist a monad, but also ziplist is “categorically” a monad if we consider only functions a -> m b which are natural with regards to list length. I.e. ZipVect N is a graded monad under the min monoid.
At one point I think I worked out, but haven’t found the code, that a cps-transformed ziplist can be made a monad (or at least overcome the counterexample), through fixing associativity by forcing reassociation of all binds (a la Voigtlander’s codensity trick). If that works, it’s a nice curiosity, but I don’t think people are really crying out with a use case for a “proper” monad for ziplist anyway.
-g
On Jun 4, 2020, 12:43 PM -0400, Gershom B
I know of counterexamples that show why the “obvious” instances don’t work. One nice one is here:
But I don’t know of a simple full proof of why no such instance is possible. My guess would be that we should consider the action of the operations on lengths of lists, and show that the requirements for monad and ziplist conflict.
-g On Jun 4, 2020, 11:57 AM -0400, David Feuer
, wrote: To add documentation, we need an explanation of *why* it's impossible.
On Thu, Jun 4, 2020, 11:35 AM chessai .
wrote: Agreed, that would be a great addition.
On Thu, Jun 4, 2020, 8:31 AM Simon Jakobi
wrote: This sounds worth documenting though.
Dannyu, would you be interested in updating the ZipList docs to say why it doesn't have a Monad instance?
Cheers, Simon
Am Do., 4. Juni 2020 um 17:21 Uhr schrieb chessai .
: > > David is right. This can't happen, unfortunately > > On Thu, Jun 4, 2020, 12:48 AM David Feuer wrote: >> >> I don't remember why right now, but it's moderately well-known that there is no possible Monad instance compatible with the Applicative instance for ZipList. See the answers to https://stackoverflow.com/questions/6463058/help-on-writing-the-colist-monad... by pigworker (Conor McBride) and C. A. McCann. >> >> On Thu, Jun 4, 2020, 2:53 AM Dannyu NDos wrote: >>> >>> instance Monad ZipList where >>> ZipList [] >>= _ = ZipList [] >>> ZipList (x:xs) >>= f = ZipList $ do >>> let ZipList y' = f x >>> guard (not (null y')) >>> let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f >>> head y' : ys >>> >>> instance MonadFail ZipList where >>> fail _ = empty >>> >>> instance MonadPlus ZipList >>> _______________________________________________ >>> Libraries mailing list >>> Libraries@haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> _______________________________________________ >> Libraries mailing list >> Libraries@haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > _______________________________________________ > Libraries mailing list > Libraries@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Thu, Jun 4, 2020, 2:10 PM Gershom B
I think that the counterexample I linked should be enough to rule out any instance for monad, in fact, in conjunction with the fact that to make liftA2 (,) correspond to zip, we need to have the join operation result in something which is the minimum of the length of the enclosing ziplist and all “enclosed” ziplists.
That's not so obvious to me. We know what has to happen for very specific shapes, but how do you know which features of that extend to general shapes?

Here's my thoughts on why it's impossible:
ZipList is basically ReaderT Natural Maybe with the requirement that
f m === Nothing -> forall n > m. f n === Nothing
The Applicative and Alternative instances are derived straightforwardly in
this manner and satisfy the requirements, but there is no way to verify the
requirement for the Monad instance. I'm pretty sure that this:
ZipList [0..] >>= (\n -> if even n then pure (div n 2) else empty)
would produce nonsense no matter the definition of (>>=).
On Thu, Jun 4, 2020, 10:57 David Feuer
To add documentation, we need an explanation of *why* it's impossible.
On Thu, Jun 4, 2020, 11:35 AM chessai .
wrote: Agreed, that would be a great addition.
On Thu, Jun 4, 2020, 8:31 AM Simon Jakobi
wrote: This sounds worth documenting though.
Dannyu, would you be interested in updating the ZipList docs to say why it doesn't have a Monad instance?
Cheers, Simon
Am Do., 4. Juni 2020 um 17:21 Uhr schrieb chessai . < chessai1996@gmail.com>:
David is right. This can't happen, unfortunately
On Thu, Jun 4, 2020, 12:48 AM David Feuer
I don't remember why right now, but it's moderately well-known that
wrote: there is no possible Monad instance compatible with the Applicative instance for ZipList. See the answers to https://stackoverflow.com/questions/6463058/help-on-writing-the-colist-monad... by pigworker (Conor McBride) and C. A. McCann.
On Thu, Jun 4, 2020, 2:53 AM Dannyu NDos
wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList
. fmap snd . uncons . getZipList . f
head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On 04/06/2020 09.53, Dannyu NDos wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList
While others have commented on the general feasibility of the idea, the problem with this specific instance is that it appears to violate the associativity law: % ./ziplist --smallcheck-depth=3 Monad laws Right identity: OK 21 tests completed Left identity: OK 98 tests completed Associativity: FAIL (0.04s) there exist {True->ZipList {getZipList = [True]};False->ZipList {getZipList = [False,True]}} {True->ZipList {getZipList = [True,True]};False->ZipList {getZipList = []}} ZipList {getZipList = [True,False]} such that condition is false 1 out of 3 tests failed (0.05s) Here's the code I used for testing: {-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-} import Control.Applicative import Control.Monad import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys instance Serial m a => Serial m (ZipList a) where series = ZipList <$> series main = defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: ZipList Int) -> (z >>= return) == z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> ZipList Bool) -> (return b >>= f) == f b , testProperty "Associativity" $ \(f1 :: Bool -> ZipList Bool) (f2 :: Bool -> ZipList Bool) (z :: ZipList Bool) -> (z >>= (\x -> f1 x >>= f2)) == ((z >>= f1) >>= f2) ] Roman

ONe point worth mentioning, is that for *sized* lists, I believe a ziplist
monad instance *is* possible? I think ?
i have an example of the functor/ applicative sized list stuff here
https://github.com/wellposed/numerical/blob/master/src/Numerical/Array/Shape...
*i believe* the way to write the monad instance would be to implement a
join :: SizedLIst n (SizedList n a) -> SizedList n a
that picks the diagonal. But i could be wrong? it wasn't a priority for me
at the time, but would that "diagonal" / trace be the right way to induce a
bind?
On Thu, Jun 4, 2020 at 4:04 PM Roman Cheplyaka
On 04/06/2020 09.53, Dannyu NDos wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList
While others have commented on the general feasibility of the idea, the problem with this specific instance is that it appears to violate the associativity law:
% ./ziplist --smallcheck-depth=3
Monad laws Right identity: OK 21 tests completed Left identity: OK 98 tests completed Associativity: FAIL (0.04s) there exist {True->ZipList {getZipList = [True]};False->ZipList {getZipList = [False,True]}} {True->ZipList {getZipList = [True,True]};False->ZipList {getZipList = []}} ZipList {getZipList = [True,False]} such that condition is false
1 out of 3 tests failed (0.05s)
Here's the code I used for testing:
{-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-} import Control.Applicative import Control.Monad import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance Serial m a => Serial m (ZipList a) where series = ZipList <$> series
main = defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: ZipList Int) -> (z >>= return) == z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> ZipList Bool) -> (return b >>= f) == f b , testProperty "Associativity" $ \(f1 :: Bool -> ZipList Bool) (f2 :: Bool -> ZipList Bool) (z :: ZipList Bool) -> (z >>= (\x -> f1 x >>= f2)) == ((z >>= f1) >>= f2) ]
Roman _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Yes, for length-indexed lists that's fine, basically a special case of
Reader.
On Thu, Jun 4, 2020, 7:48 PM Carter Schonwald
ONe point worth mentioning, is that for *sized* lists, I believe a ziplist monad instance *is* possible? I think ? i have an example of the functor/ applicative sized list stuff here
https://github.com/wellposed/numerical/blob/master/src/Numerical/Array/Shape...
*i believe* the way to write the monad instance would be to implement a join :: SizedLIst n (SizedList n a) -> SizedList n a that picks the diagonal. But i could be wrong? it wasn't a priority for me at the time, but would that "diagonal" / trace be the right way to induce a bind?
On Thu, Jun 4, 2020 at 4:04 PM Roman Cheplyaka
wrote: On 04/06/2020 09.53, Dannyu NDos wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList
While others have commented on the general feasibility of the idea, the problem with this specific instance is that it appears to violate the associativity law:
% ./ziplist --smallcheck-depth=3
Monad laws Right identity: OK 21 tests completed Left identity: OK 98 tests completed Associativity: FAIL (0.04s) there exist {True->ZipList {getZipList = [True]};False->ZipList {getZipList = [False,True]}} {True->ZipList {getZipList = [True,True]};False->ZipList {getZipList = []}} ZipList {getZipList = [True,False]} such that condition is false
1 out of 3 tests failed (0.05s)
Here's the code I used for testing:
{-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-} import Control.Applicative import Control.Monad import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance Serial m a => Serial m (ZipList a) where series = ZipList <$> series
main = defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: ZipList Int) -> (z >>= return) == z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> ZipList Bool) -> (return b >>= f) == f b , testProperty "Associativity" $ \(f1 :: Bool -> ZipList Bool) (f2 :: Bool -> ZipList Bool) (z :: ZipList Bool) -> (z >>= (\x -> f1 x >>= f2)) == ((z >>= f1) >>= f2) ]
Roman _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Thu, 4 Jun 2020, Carter Schonwald wrote:
*i believe* the way to write the monad instance would be to implement a join :: SizedLIst n (SizedList n a) -> SizedList n a that picks the diagonal. But i could be wrong? it wasn't a priority for me at the time, but would that "diagonal" / trace be the right way to induce a bind?
Sure, that's analogous to instance Monad ((->) a).

david, henning, could you expand on that intuition? i'm a bit derped up from nyc being crazy stresses and doing my best to not engaged unconstructively on interpersonal frustractionsl on the internet, and i"m sure the exposition would benefit other please :) -Carter On Thu, Jun 4, 2020 at 7:52 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Thu, 4 Jun 2020, Carter Schonwald wrote:
*i believe* the way to write the monad instance would be to implement a join :: SizedLIst n (SizedList n a) -> SizedList n a that picks the diagonal. But i could be wrong? it wasn't a priority for me at the time, but would that "diagonal" / trace be the right way to induce a bind?
Sure, that's analogous to instance Monad ((->) a).

You can find it all in
https://hackage.haskell.org/package/adjunctions-4.4/docs/Data-Functor-Rep.ht...
Length-indexed vectors are representable functors and thus can be treated
essentially as functions, winning loads of instances for free. Whether
those are the instances you want is another question, but they're valid.
On Thu, Jun 4, 2020, 8:12 PM Carter Schonwald
david, henning, could you expand on that intuition? i'm a bit derped up from nyc being crazy stresses and doing my best to not engaged unconstructively on interpersonal frustractionsl on the internet, and i"m sure the exposition would benefit other please :)
-Carter
On Thu, Jun 4, 2020 at 7:52 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Thu, 4 Jun 2020, Carter Schonwald wrote:
*i believe* the way to write the monad instance would be to implement a join :: SizedLIst n (SizedList n a) -> SizedList n a that picks the diagonal. But i could be wrong? it wasn't a priority for me at the time, but would that "diagonal" / trace be the right way to induce a bind?
Sure, that's analogous to instance Monad ((->) a).
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Using Roman’s smallcheck code (thanks!) here’s some evidence that codensity turns a bad diagonalizing ziplist instance into a good one, by fixing associativity. I’ve been pondering this for some time, and I’m glad this thread kicked me into making it work out. Also, as David noted, this works with or without the “take i” in the code, which enforces that minimum criteria I mentioned. So I suppose there’s a range of possibilities here.
If this works out, it looks like this also shows that a “purely algebraic” argument as to why ZipList can’t be a monad doesn't exist. I.e. there’s no conflict in the laws. It’s just that using a plain list as the underlying datastructure can’t force a uniform associativity.
To make a real “monadic ziplist” out of this, I think the codensity stuff would just need to be inlined under the ziplist constructor.
Cheers,
Gershom
import Data.List
import Data.Maybe
import Test.SmallCheck.Series
import Test.Tasty
import Test.Tasty.SmallCheck
import Control.Monad
import Control.Applicative
import System.Environment
data ZL a = ZL {unZL :: [a]} deriving (Eq, Show)
instance Functor ZL where
fmap f (ZL xs) = ZL (fmap f xs)
joinZL :: ZL (ZL a) -> ZL a
joinZL (ZL []) = ZL []
joinZL (ZL zs) = ZL (chop . diag (0,[]) $ map unZL zs)
where diag :: (Int,[a]) -> [[a]] -> (Int,[a])
diag (i,acc) [] = (i,acc)
diag (i,acc) (x:xs) = case drop i x of
[] -> (length x, acc)
(y:_) ->diag (i+1, (y : acc)) xs
chop (i,acc) = take i $ reverse acc
instance Applicative ZL where
pure = return
f <*> x = joinZL $ fmap (\g -> fmap g x) f
instance Monad ZL where
return x = ZL (repeat x)
x >>= f = joinZL $ fmap (f $) x
newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }
instance Functor (Codensity k) where fmap f (Codensity m) = Codensity (\k -> m (\x -> k (f x)))
instance Applicative (Codensity f) where
pure x = Codensity (\k -> k x)
Codensity f <*> Codensity g = Codensity (\bfr -> f (\ab -> g (\x -> bfr (ab x))))
instance Monad (Codensity f) where
return = pure
m >>= k = Codensity (\c -> runCodensity m (\a -> runCodensity (k a) c))
lowerCodensity :: Monad m => Codensity m a -> m a
lowerCodensity a = runCodensity a return
lift m = Codensity (m >>=)
-- tests
instance Serial m a => Serial m (ZL a) where
series = ZL <$> series
instance Serial m a => Serial m (Codensity ZL a) where
series = lift <$> series
instance Show (Codensity ZL Int) where
show x = show (lowerCodensity x)
instance Show (Codensity ZL Bool) where
show x = show (lowerCodensity x)
main = do
setEnv "TASTY_SMALLCHECK_DEPTH" "4"
defaultMain $ testGroup "Monad laws"
[ testProperty "Right identity" $ \(z :: Codensity ZL Int) ->
lowerCodensity (z >>= return) == lowerCodensity z
, testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> Codensity ZL Bool) ->
lowerCodensity (return b >>= f) == lowerCodensity (f b)
, testProperty "Associativity" $
\(f1 :: Bool -> Codensity ZL Bool)
(f2 :: Bool -> Codensity ZL Bool)
(z :: Codensity ZL Bool) ->
lowerCodensity (z >>= (\x -> f1 x >>= f2)) == lowerCodensity ((z >>= f1) >>= f2)
]
On Jun 4, 2020, 4:04 PM -0400, Roman Cheplyaka
On 04/06/2020 09.53, Dannyu NDos wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList
While others have commented on the general feasibility of the idea, the problem with this specific instance is that it appears to violate the associativity law:
% ./ziplist --smallcheck-depth=3 Monad laws Right identity: OK 21 tests completed Left identity: OK 98 tests completed Associativity: FAIL (0.04s) there exist {True->ZipList {getZipList = [True]};False->ZipList {getZipList = [False,True]}} {True->ZipList {getZipList = [True,True]};False->ZipList {getZipList = []}} ZipList {getZipList = [True,False]} such that condition is false
1 out of 3 tests failed (0.05s)
Here's the code I used for testing:
{-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-} import Control.Applicative import Control.Monad import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance Serial m a => Serial m (ZipList a) where series = ZipList <$> series
main = defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: ZipList Int) -> (z >>= return) == z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> ZipList Bool) -> (return b >>= f) == f b , testProperty "Associativity" $ \(f1 :: Bool -> ZipList Bool) (f2 :: Bool -> ZipList Bool) (z :: ZipList Bool) -> (z >>= (\x -> f1 x >>= f2)) == ((z >>= f1) >>= f2) ]
Roman _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I'm not really sure what you're getting at here. Codensity will turn
anything into a Monad. How does that relate to the question of whether
there's a valid `Monad ZipList` instance?
On Fri, Jun 5, 2020 at 1:42 AM Gershom B
Using Roman’s smallcheck code (thanks!) here’s some evidence that codensity turns a bad diagonalizing ziplist instance into a good one, by fixing associativity. I’ve been pondering this for some time, and I’m glad this thread kicked me into making it work out. Also, as David noted, this works with or without the “take i” in the code, which enforces that minimum criteria I mentioned. So I suppose there’s a range of possibilities here.
If this works out, it looks like this also shows that a “purely algebraic” argument as to why ZipList can’t be a monad doesn't exist. I.e. there’s no conflict in the laws. It’s just that using a plain list as the underlying datastructure can’t force a uniform associativity.
To make a real “monadic ziplist” out of this, I think the codensity stuff would just need to be inlined under the ziplist constructor.
Cheers, Gershom
import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck import Control.Monad import Control.Applicative import System.Environment
data ZL a = ZL {unZL :: [a]} deriving (Eq, Show)
instance Functor ZL where fmap f (ZL xs) = ZL (fmap f xs)
joinZL :: ZL (ZL a) -> ZL a joinZL (ZL []) = ZL [] joinZL (ZL zs) = ZL (chop . diag (0,[]) $ map unZL zs) where diag :: (Int,[a]) -> [[a]] -> (Int,[a]) diag (i,acc) [] = (i,acc) diag (i,acc) (x:xs) = case drop i x of [] -> (length x, acc) (y:_) ->diag (i+1, (y : acc)) xs chop (i,acc) = take i $ reverse acc
instance Applicative ZL where pure = return f <*> x = joinZL $ fmap (\g -> fmap g x) f
instance Monad ZL where return x = ZL (repeat x) x >>= f = joinZL $ fmap (f $) x
newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }
instance Functor (Codensity k) where fmap f (Codensity m) = Codensity (\k -> m (\x -> k (f x)))
instance Applicative (Codensity f) where pure x = Codensity (\k -> k x) Codensity f <*> Codensity g = Codensity (\bfr -> f (\ab -> g (\x -> bfr (ab x))))
instance Monad (Codensity f) where return = pure m >>= k = Codensity (\c -> runCodensity m (\a -> runCodensity (k a) c))
lowerCodensity :: Monad m => Codensity m a -> m a lowerCodensity a = runCodensity a return
lift m = Codensity (m >>=)
-- tests
instance Serial m a => Serial m (ZL a) where series = ZL <$> series
instance Serial m a => Serial m (Codensity ZL a) where series = lift <$> series
instance Show (Codensity ZL Int) where show x = show (lowerCodensity x)
instance Show (Codensity ZL Bool) where show x = show (lowerCodensity x)
main = do setEnv "TASTY_SMALLCHECK_DEPTH" "4" defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: Codensity ZL Int) -> lowerCodensity (z >>= return) == lowerCodensity z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> Codensity ZL Bool) -> lowerCodensity (return b >>= f) == lowerCodensity (f b) , testProperty "Associativity" $ \(f1 :: Bool -> Codensity ZL Bool) (f2 :: Bool -> Codensity ZL Bool) (z :: Codensity ZL Bool) -> lowerCodensity (z >>= (\x -> f1 x >>= f2)) == lowerCodensity ((z >>= f1) >>= f2) ] On Jun 4, 2020, 4:04 PM -0400, Roman Cheplyaka
, wrote: On 04/06/2020 09.53, Dannyu NDos wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList
While others have commented on the general feasibility of the idea, the problem with this specific instance is that it appears to violate the associativity law:
% ./ziplist --smallcheck-depth=3 Monad laws Right identity: OK 21 tests completed Left identity: OK 98 tests completed Associativity: FAIL (0.04s) there exist {True->ZipList {getZipList = [True]};False->ZipList {getZipList = [False,True]}} {True->ZipList {getZipList = [True,True]};False->ZipList {getZipList = []}} ZipList {getZipList = [True,False]} such that condition is false
1 out of 3 tests failed (0.05s)
Here's the code I used for testing:
{-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-} import Control.Applicative import Control.Monad import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance Serial m a => Serial m (ZipList a) where series = ZipList <$> series
main = defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: ZipList Int) -> (z >>= return) == z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> ZipList Bool) -> (return b >>= f) == f b , testProperty "Associativity" $ \(f1 :: Bool -> ZipList Bool) (f2 :: Bool -> ZipList Bool) (z :: ZipList Bool) -> (z >>= (\x -> f1 x >>= f2)) == ((z >>= f1) >>= f2) ]
Roman _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Anything of kind (* -> *) gives a codensity monad. What’s important is that only monad-like things (like the “bad” ziplist monad instance) can be lifted _into_ codensity in a universal way (otherwise you only get the “free” pure from codensity itself). And furthermore, only at least applicatives can be lowered back into the underlying functor via lowerCodensity. Note in particular:
instance Serial m a => Serial m (Codensity ZL a) where series = lift <$> series
where lift in turn packs in the “bad” bind.
So in particular, with codensity over ziplist, we get back something that zips like a ziplist but also has a valid monad instance. So that doesn’t say that ZipList [a] has a monad instance. But it does say that we can get something which acts as an applicative just like ZipList [a], but does have a valid monad instance. We just need a richer underlying type to express that algebraic structure.
You might see this more clearly if you change the tests to not operate directly on “Codensity ZL” but instead to take arguments of “ZL” and manually lift them.
More generally if you have something that is “almost a monad” but whose candidate bind does not associate, I think you can create something else which behaves the same in all other respects, but which is a monad, by using codensity to reassociate the bind.
Maybe to highlight that something is happening at all, note that this trick can’t be done with the Const applicative, since there’s no good candidate bind operator that yields the desired <*>.
-g
On Jun 5, 2020, 1:50 AM -0400, David Feuer
I'm not really sure what you're getting at here. Codensity will turn anything into a Monad. How does that relate to the question of whether there's a valid `Monad ZipList` instance?
On Fri, Jun 5, 2020 at 1:42 AM Gershom B
wrote: Using Roman’s smallcheck code (thanks!) here’s some evidence that codensity turns a bad diagonalizing ziplist instance into a good one, by fixing associativity. I’ve been pondering this for some time, and I’m glad this thread kicked me into making it work out. Also, as David noted, this works with or without the “take i” in the code, which enforces that minimum criteria I mentioned. So I suppose there’s a range of possibilities here.
If this works out, it looks like this also shows that a “purely algebraic” argument as to why ZipList can’t be a monad doesn't exist. I.e. there’s no conflict in the laws. It’s just that using a plain list as the underlying datastructure can’t force a uniform associativity.
To make a real “monadic ziplist” out of this, I think the codensity stuff would just need to be inlined under the ziplist constructor.
Cheers, Gershom
import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck import Control.Monad import Control.Applicative import System.Environment
data ZL a = ZL {unZL :: [a]} deriving (Eq, Show)
instance Functor ZL where fmap f (ZL xs) = ZL (fmap f xs)
joinZL :: ZL (ZL a) -> ZL a joinZL (ZL []) = ZL [] joinZL (ZL zs) = ZL (chop . diag (0,[]) $ map unZL zs) where diag :: (Int,[a]) -> [[a]] -> (Int,[a]) diag (i,acc) [] = (i,acc) diag (i,acc) (x:xs) = case drop i x of [] -> (length x, acc) (y:_) ->diag (i+1, (y : acc)) xs chop (i,acc) = take i $ reverse acc
instance Applicative ZL where pure = return f <*> x = joinZL $ fmap (\g -> fmap g x) f
instance Monad ZL where return x = ZL (repeat x) x >>= f = joinZL $ fmap (f $) x
newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }
instance Functor (Codensity k) where fmap f (Codensity m) = Codensity (\k -> m (\x -> k (f x)))
instance Applicative (Codensity f) where pure x = Codensity (\k -> k x) Codensity f <*> Codensity g = Codensity (\bfr -> f (\ab -> g (\x -> bfr (ab x))))
instance Monad (Codensity f) where return = pure m >>= k = Codensity (\c -> runCodensity m (\a -> runCodensity (k a) c))
lowerCodensity :: Monad m => Codensity m a -> m a lowerCodensity a = runCodensity a return
lift m = Codensity (m >>=)
-- tests
instance Serial m a => Serial m (ZL a) where series = ZL <$> series
instance Serial m a => Serial m (Codensity ZL a) where series = lift <$> series
instance Show (Codensity ZL Int) where show x = show (lowerCodensity x)
instance Show (Codensity ZL Bool) where show x = show (lowerCodensity x)
main = do setEnv "TASTY_SMALLCHECK_DEPTH" "4" defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: Codensity ZL Int) -> lowerCodensity (z >>= return) == lowerCodensity z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> Codensity ZL Bool) -> lowerCodensity (return b >>= f) == lowerCodensity (f b) , testProperty "Associativity" $ \(f1 :: Bool -> Codensity ZL Bool) (f2 :: Bool -> Codensity ZL Bool) (z :: Codensity ZL Bool) -> lowerCodensity (z >>= (\x -> f1 x >>= f2)) == lowerCodensity ((z >>= f1) >>= f2) ] On Jun 4, 2020, 4:04 PM -0400, Roman Cheplyaka
, wrote: On 04/06/2020 09.53, Dannyu NDos wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList
While others have commented on the general feasibility of the idea, the problem with this specific instance is that it appears to violate the associativity law:
% ./ziplist --smallcheck-depth=3 Monad laws Right identity: OK 21 tests completed Left identity: OK 98 tests completed Associativity: FAIL (0.04s) there exist {True->ZipList {getZipList = [True]};False->ZipList {getZipList = [False,True]}} {True->ZipList {getZipList = [True,True]};False->ZipList {getZipList = []}} ZipList {getZipList = [True,False]} such that condition is false
1 out of 3 tests failed (0.05s)
Here's the code I used for testing:
{-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-} import Control.Applicative import Control.Monad import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance Serial m a => Serial m (ZipList a) where series = ZipList <$> series
main = defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: ZipList Int) -> (z >>= return) == z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> ZipList Bool) -> (return b >>= f) == f b , testProperty "Associativity" $ \(f1 :: Bool -> ZipList Bool) (f2 :: Bool -> ZipList Bool) (z :: ZipList Bool) -> (z >>= (\x -> f1 x >>= f2)) == ((z >>= f1) >>= f2) ]
Roman _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Does this add anything in the sized list case?
On Fri, Jun 5, 2020 at 2:50 AM Gershom B
Anything of kind (* -> *) gives a codensity monad. What’s important is that only monad-like things (like the “bad” ziplist monad instance) can be lifted _into_ codensity in a universal way (otherwise you only get the “free” pure from codensity itself). And furthermore, only at least applicatives can be lowered back into the underlying functor via lowerCodensity. Note in particular:
instance Serial m a => Serial m (Codensity ZL a) where
series = lift <$> series
where lift in turn packs in the “bad” bind.
So in particular, with codensity over ziplist, we get back something that zips like a ziplist but also has a valid monad instance. So that doesn’t say that ZipList [a] has a monad instance. But it does say that we can get something which acts as an applicative just like ZipList [a], but does have a valid monad instance. We just need a richer underlying type to express that algebraic structure.
You might see this more clearly if you change the tests to not operate directly on “Codensity ZL” but instead to take arguments of “ZL” and manually lift them.
More generally if you have something that is “almost a monad” but whose candidate bind does not associate, I think you can create something else which behaves the same in all other respects, but which is a monad, by using codensity to reassociate the bind.
Maybe to highlight that something is happening at all, note that this trick can’t be done with the Const applicative, since there’s no good candidate bind operator that yields the desired <*>.
-g On Jun 5, 2020, 1:50 AM -0400, David Feuer
, wrote: I'm not really sure what you're getting at here. Codensity will turn anything into a Monad. How does that relate to the question of whether there's a valid `Monad ZipList` instance?
On Fri, Jun 5, 2020 at 1:42 AM Gershom B
wrote: Using Roman’s smallcheck code (thanks!) here’s some evidence that codensity turns a bad diagonalizing ziplist instance into a good one, by fixing associativity. I’ve been pondering this for some time, and I’m glad this thread kicked me into making it work out. Also, as David noted, this works with or without the “take i” in the code, which enforces that minimum criteria I mentioned. So I suppose there’s a range of possibilities here.
If this works out, it looks like this also shows that a “purely algebraic” argument as to why ZipList can’t be a monad doesn't exist. I.e. there’s no conflict in the laws. It’s just that using a plain list as the underlying datastructure can’t force a uniform associativity.
To make a real “monadic ziplist” out of this, I think the codensity stuff would just need to be inlined under the ziplist constructor.
Cheers, Gershom
import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck import Control.Monad import Control.Applicative import System.Environment
data ZL a = ZL {unZL :: [a]} deriving (Eq, Show)
instance Functor ZL where fmap f (ZL xs) = ZL (fmap f xs)
joinZL :: ZL (ZL a) -> ZL a joinZL (ZL []) = ZL [] joinZL (ZL zs) = ZL (chop . diag (0,[]) $ map unZL zs) where diag :: (Int,[a]) -> [[a]] -> (Int,[a]) diag (i,acc) [] = (i,acc) diag (i,acc) (x:xs) = case drop i x of [] -> (length x, acc) (y:_) ->diag (i+1, (y : acc)) xs chop (i,acc) = take i $ reverse acc
instance Applicative ZL where pure = return f <*> x = joinZL $ fmap (\g -> fmap g x) f
instance Monad ZL where return x = ZL (repeat x) x >>= f = joinZL $ fmap (f $) x
newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }
instance Functor (Codensity k) where fmap f (Codensity m) = Codensity (\k -> m (\x -> k (f x)))
instance Applicative (Codensity f) where pure x = Codensity (\k -> k x) Codensity f <*> Codensity g = Codensity (\bfr -> f (\ab -> g (\x -> bfr (ab x))))
instance Monad (Codensity f) where return = pure m >>= k = Codensity (\c -> runCodensity m (\a -> runCodensity (k a) c))
lowerCodensity :: Monad m => Codensity m a -> m a lowerCodensity a = runCodensity a return
lift m = Codensity (m >>=)
-- tests
instance Serial m a => Serial m (ZL a) where series = ZL <$> series
instance Serial m a => Serial m (Codensity ZL a) where series = lift <$> series
instance Show (Codensity ZL Int) where show x = show (lowerCodensity x)
instance Show (Codensity ZL Bool) where show x = show (lowerCodensity x)
main = do setEnv "TASTY_SMALLCHECK_DEPTH" "4" defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: Codensity ZL Int) -> lowerCodensity (z >>= return) == lowerCodensity z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> Codensity ZL Bool) -> lowerCodensity (return b >>= f) == lowerCodensity (f b) , testProperty "Associativity" $ \(f1 :: Bool -> Codensity ZL Bool) (f2 :: Bool -> Codensity ZL Bool) (z :: Codensity ZL Bool) -> lowerCodensity (z >>= (\x -> f1 x >>= f2)) == lowerCodensity ((z >>= f1)
= f2) ] On Jun 4, 2020, 4:04 PM -0400, Roman Cheplyaka
, wrote: On 04/06/2020 09.53, Dannyu NDos wrote:
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance MonadFail ZipList where fail _ = empty
instance MonadPlus ZipList
While others have commented on the general feasibility of the idea, the problem with this specific instance is that it appears to violate the associativity law:
% ./ziplist --smallcheck-depth=3 Monad laws Right identity: OK 21 tests completed Left identity: OK 98 tests completed Associativity: FAIL (0.04s) there exist {True->ZipList {getZipList = [True]};False->ZipList {getZipList = [False,True]}} {True->ZipList {getZipList = [True,True]};False->ZipList {getZipList = []}} ZipList {getZipList = [True,False]} such that condition is false
1 out of 3 tests failed (0.05s)
Here's the code I used for testing:
{-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-} import Control.Applicative import Control.Monad import Data.List import Data.Maybe import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck
instance Monad ZipList where ZipList [] >>= _ = ZipList [] ZipList (x:xs) >>= f = ZipList $ do let ZipList y' = f x guard (not (null y')) let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f head y' : ys
instance Serial m a => Serial m (ZipList a) where series = ZipList <$> series
main = defaultMain $ testGroup "Monad laws" [ testProperty "Right identity" $ \(z :: ZipList Int) -> (z >>= return) == z , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> ZipList Bool) -> (return b >>= f) == f b , testProperty "Associativity" $ \(f1 :: Bool -> ZipList Bool) (f2 :: Bool -> ZipList Bool) (z :: ZipList Bool) -> (z >>= (\x -> f1 x >>= f2)) == ((z >>= f1) >>= f2) ]
Roman _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (9)
-
Carter Schonwald
-
chessai .
-
Dannyu NDos
-
David Feuer
-
Gershom B
-
Henning Thielemann
-
Roman Cheplyaka
-
Simon Jakobi
-
Zemyla