[Haskell-beginners] Searching Maybe lists

Daniel Fischer daniel.is.fischer at web.de
Tue May 19 11:02:28 EDT 2009


Am Dienstag 19 Mai 2009 15:39:16 schrieb Thomas Friedrich:
> Hi Aditya,
>
> Please try the following:
>
> findJust :: (Eq a) => [Maybe a] -> Maybe a
> findJust xs = case (dropWhile (==Nothing) xs) of
>               [] -> Nothing
>               cs -> head cs
>
> yourFunction :: (Eq b) => (a -> Maybe b) -> [a] -> Maybe b
> yourFunction f xs = findJust (map f xs)
>
> It only uses functions from the Prelude, and as Haskell evaluates lazy,
> it just does exactly what you wants.

No need for the Eq constraint,

findJust xs = case dropWhile isNothing xs of
                [] -> Nothing
                (x:_) -> x

isNothing could be imported from Data.Maybe or defined as

isNothing Nothing = True
isNothing _ = False

if you don't want the import.

Another method to define findJust is

import Data.Maybe

findJust = listToMaybe . catMaybes

or

import Control.Monad

findJust = msum

So for the original problem, we could use any of

findMaybe :: [a] -> (a -> Maybe b) -> Maybe b
findMaybe xs f = msum $ map f xs
  -- this indicates that the parameter order should be different
findMaybe xs f = foldr mplus Nothing (map f xs)
findMaybe xs f = listToMaybe . catMaybes $ map f xs
findMaybe xs f = head (dropWhile isNothing (map f xs) ++ [Nothing])
findMaybe xs f = find isJust (map f xs) >>= id

I find the first two best, but they bring Control.Monad into the game, if one wants to 
avoid that, I'd recommend defining 'mplus' for Maybe oneself,

orMaybe m1@(Just _) _ = m1
orMaybe _ m2 = m2

findMaybe xs f = foldr orMaybe Nothing (map f xs).

>
> Happy Hacking,
> Thomas
>
> aditya siram wrote:
> > Hi all,
> > I would like to define a function that takes a list and a function
> > that evaluates each member of the list to a Maybe value and output the
> > first element in the list that evaluates to 'Just y', or 'Nothing'
> > once the list has been completely processed. So something like:
> >
> > findMaybe :: [a] -> (a -> Maybe b) -> Maybe b
> >
> > The problem is that I don't want it to go through the entire list, but
> > short-circuit when it hits a 'Just ...'. So far I have:
> >
> > orMaybe :: Maybe a -> Maybe a -> Maybe a
> > orMaybe m1 m2 = case (m1,m2) of
> >                   (_, Just a) -> Just a
> >                   (Just a, _) -> Just a
> >                   _           -> Nothing
> >
> > findMaybe :: [a] -> (a -> Maybe b) -> Maybe b
> > findMaybe as f = foldr (\a sofar -> sofar `orMaybe` (f a)) Nothing as
> >
> > 'findMaybe', as far as I can tell, traverses the entire input list
> > which is undesirable for long lists. How can I fix it?
> >
> > Curiously, the regular 'Data.List.find' function that applies a
> > Boolean predicate to each member of the list also seems to first
> > traverse the entire list using 'filter' and then grabs the head of the
> > result.
> >
> > Thanks ...
> > -deech



More information about the Beginners mailing list