Gregory Crosswhite <gcr...@phys.washington.edu> wrote:

> Or even better,
>
>      filter isJust

To make it worse again the original function can be generalized in a few
ways.  Here is a generalization from the inner Maybe type:

    import Data.Foldable as F

    catFoldables :: Foldable t => [t a] -> [a]
    catFoldables = concatMap F.toList

Here is a generalization from the outer list type:

    joinMaybes :: (Alternative m, Monad m) => m (Maybe a) -> m a
    joinMaybes = (>>= maybe empty pure)

And finally the generalization from everything:

    import Data.Foldable as F

    joinFoldables :: (Alternative m, Foldable t, Monad m) => m (t a) -> m a
    joinFoldables = (>>= F.foldr (\x _ -> pure x) empty)

The final function looks a bit scary, but is actually surprisingly easy
to understand, once you realize that 'foldr' is just a generalization of
the 'maybe' function.  The structure of Maybe is a list structure with
at most one element after all.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to