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

Luke Palmer lrpalmer at gmail.com
Thu Dec 6 04:56:48 EST 2007


On Dec 6, 2007 9:30 AM, Alistair Bayley <alistair at abayley.org> wrote:
> > 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.

I have actually seen this pattern a lot recently.  Recently I have
started using a function:

mergeMaybes :: (a -> a -> a) -> Maybe a -> Maybe a -> Maybe a
mergeMaybes f Nothing y = y
mergeMaybes f x Nothing = x
mergeMaybes f (Just x) (Just y) = Just (f x y)

With which findAllPath could be written:

finaAllPath pred (Branch lf r rt)
    | pred r    = fmap (map (r:)) $ mergeMaybes (++) (findAllPath lf)
(findAllPath rt)
    | otherwise = Nothing

Or this more search-like feel:

findAllPath pred (Branch lf r rt) = do
    guard (pred r)
    subpaths <- mergeMaybes (++) (findAllPath lf) (findAllPath rt)
    return $ map (r:) subpaths

Luke


More information about the Haskell-Cafe mailing list