<div dir="auto">Yes, for length-indexed lists that's fine, basically a special case of Reader.</div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Thu, Jun 4, 2020, 7:48 PM Carter Schonwald <<a href="mailto:carter.schonwald@gmail.com">carter.schonwald@gmail.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div dir="ltr">ONe point worth mentioning, is that for *sized* lists, I believe a ziplist monad instance *is* possible? I think ?<div>i have an example of the functor/ applicative sized list stuff here </div><div><a href="https://github.com/wellposed/numerical/blob/master/src/Numerical/Array/Shape.hs#L252-L271" target="_blank" rel="noreferrer">https://github.com/wellposed/numerical/blob/master/src/Numerical/Array/Shape.hs#L252-L271</a><br></div><div><br></div><div>*i believe* the way to write the monad instance would be to implement a join :: SizedLIst n (SizedList n a) -> SizedList n a </div><div>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? </div></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Thu, Jun 4, 2020 at 4:04 PM Roman Cheplyaka <<a href="mailto:roma@ro-che.info" target="_blank" rel="noreferrer">roma@ro-che.info</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-style:solid;border-left-color:rgb(204,204,204);padding-left:1ex">On 04/06/2020 09.53, Dannyu NDos wrote:<br>
> instance Monad ZipList where<br>
>     ZipList [] >>= _ = ZipList []<br>
>     ZipList (x:xs) >>= f = ZipList $ do<br>
>         let ZipList y' = f x<br>
>         guard (not (null y'))<br>
>         let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f<br>
>         head y' : ys<br>
> <br>
> instance MonadFail ZipList where<br>
>     fail _ = empty<br>
> <br>
> instance MonadPlus ZipList<br>
<br>
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:<br>
<br>
% ./ziplist --smallcheck-depth=3                                                           <br>
Monad laws<br>
  Right identity: OK<br>
    21 tests completed<br>
  Left identity:  OK<br>
    98 tests completed<br>
  Associativity:  FAIL (0.04s)<br>
    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<br>
      condition is false<br>
<br>
1 out of 3 tests failed (0.05s)<br>
<br>
<br>
Here's the code I used for testing:<br>
<br>
{-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses #-}<br>
import Control.Applicative<br>
import Control.Monad<br>
import Data.List<br>
import Data.Maybe<br>
import Test.SmallCheck.Series<br>
import Test.Tasty<br>
import Test.Tasty.SmallCheck<br>
<br>
instance Monad ZipList where<br>
    ZipList [] >>= _ = ZipList []<br>
    ZipList (x:xs) >>= f = ZipList $ do<br>
        let ZipList y' = f x<br>
        guard (not (null y'))<br>
        let ZipList ys = ZipList xs >>= ZipList . join . maybeToList . fmap snd . uncons . getZipList . f<br>
        head y' : ys<br>
<br>
instance Serial m a => Serial m (ZipList a) where<br>
  series = ZipList <$> series<br>
<br>
main = defaultMain $ testGroup "Monad laws"<br>
  [ testProperty "Right identity" $ \(z :: ZipList Int) -><br>
      (z >>= return) == z<br>
  , testProperty "Left identity" $ \(b :: Bool) (f :: Bool -> ZipList Bool) -><br>
      (return b >>= f) == f b<br>
  , testProperty "Associativity" $<br>
      \(f1 :: Bool -> ZipList Bool)<br>
       (f2 :: Bool -> ZipList Bool)<br>
       (z :: ZipList Bool) -><br>
         (z >>= (\x -> f1 x >>= f2)) == ((z >>= f1) >>= f2)<br>
  ]<br>
<br>
Roman<br>
_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" target="_blank" rel="noreferrer">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
</blockquote></div>
_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" target="_blank" rel="noreferrer">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
</blockquote></div>