[Haskell-cafe] Why is this strict in its arguments?

Alistair Bayley alistair at abayley.org
Thu Dec 6 04:30:38 EST 2007


> Use of isNothing and fromJust and a cascade of ifs is generally a poor
> sign, much better to use case:
>
> findAllPath pred (Branch lf r rt)
>      | pred r =
>          case (findAllPath pred lf,findAllPath pred rt) of
>            (Nothing,Nothing)           -> Nothing
>            (Nothing,Just rtpaths)      -> Just (map (r:) rtpaths)
>            (Just lfpaths,Nothing)      -> Just (map (r:) lfpaths)
>            (Just lfpaths,Just rtpaths) -> Just (map (r:) $ rtpaths ++
> lfpaths)
>      | otherwise = Nothing
>
> the general pattern is : replace isNothing with a case match on Nothing,
> replace fromJust with a case match on Just, don't be afraid to case two
> expressions at once.


Nested Maybe cases put me in mind of the Maybe monad. Although in this
case it''s not trivial; we also need to involve the Maybe [a] instance
of Data.Monoid too (for the mappend function). I do wonder if I'm
abusing the monadic instances of Maybe though; is this really any
clearer than Jules' code?

(BTW, this has probably come up before, but wouldn't it be a little
bit nicer if "when" returned mzero rather than () in the "do nothing"
case?)

> when' :: MonadPlus m => Bool -> m a -> m a
> when' pred action = if pred then action else mzero
>
> findAllPath :: (a -> Bool) -> (BTree a) -> Maybe [[a]]
> findAllPath pred (Leaf l) = when' (pred l) (return [[l]])
> findAllPath pred (Branch lf r rt) =
>   when' (pred r) $ do
>     x <- mappend (findAllPath pred lf) (findAllPath pred rt)
>     return (map (r:) x)


Alistair


More information about the Haskell-Cafe mailing list