
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

On Mon, May 18, 2009 at 9:56 PM, aditya siram
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
There are a couple of ways, the first one I could think of was:
findMaybe xs f = mconcat $ map f xs
where mconcat is found in Data.Monoid Antoine

On Mon, May 18, 2009 at 9:56 PM, aditya siram
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.
Ah! I just thought I'd point out that 'filter' does not necessarily traverse the entire list if all you do with the result is grab the head - it only traverses enough of the list to figure out what the head of the list should be (or even that it exists). Haskell is lazy :-) Antoine

On Mon, May 18, 2009 at 7:56 PM, aditya siram
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
find doesn't traverse the entire list. The filter function can traverse the whole list, but only if you observe all of its values afterwards. If you only look at the first value, like find does, then filter only goes until it produces one value. This is because of laziness. We can test that filter doesn't examine the entire list by trying it on an infinite list. If it traversed the entire list, it couldn't possibly work on an infinite list! $ ghci GHCi, version 6.10.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer ... linking ... done. Loading package base ... linking ... done. Prelude> import Data.List Prelude Data.List> find (==3) [1..] Just 3 Prelude Data.List> But it does work! It only looks at values until it finds one that matches the predicate. Alex

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
Thanks to lazy evaluation, this is not necessarily the case, see also http://en.wikibooks.org/wiki/Haskell/Performance_Introduction#Time You will have to write orMaybe as orMaybe Nothing y = y orMaybe x _ = x though. (By the way, your original code for orMaybe doesn't seem to do what you want.) This function has already been implemented for you, it's called mplus Regards, apfelmus -- http://apfelmus.nfshost.com

You will have to write orMaybe as
orMaybe Nothing y = y orMaybe x _ = x
though. (By the way, your original code for orMaybe doesn't seem to do what you want.) This function has already been implemented for you, it's called
mplus
My function 'orMaybe' takes two arguments m1 m2, if one of them is Nothing, it returns Nothing, if m1 is Just , it returns m1, if m2 is Just, it returns m2. This seems to be what I want. Why is this incorrect? However, your function 'orMaybe' is much more concise and elegant. thanks ... -deech

aditya siram wrote:
You will have to write orMaybe as
orMaybe Nothing y = y orMaybe x _ = x
though. (By the way, your original code for orMaybe doesn't seem to do what you want.) This function has already been implemented for you, it's called
mplus
My function 'orMaybe' takes two arguments m1 m2, if one of them is Nothing, it returns Nothing, if m1 is Just , it returns m1, if m2 is Just, it returns m2. This seems to be what I want. Why is this incorrect?
Ah, you're right, my bad. I was confused by the fact that you were using it from right to left, i.e. findMaybe f = foldr (\a sofar -> sofar `orMaybe` a) Nothing . map f = foldr (flip orMaybe) Nothing . map f instead of findMaybe f = foldr orMaybe Nothing . map f Regards, apfelmus -- http://apfelmus.nfshost.com

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. 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 ------------------------------------------------------------------------
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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

Hi all, I'm experimenting a bit with the parallelization capabilities of Haskell. What I am trying to do is to process in parallel all the lines of a text file, calculating the edit distance of each of these lines with a given string. This is my testing code: import System.IO import Control.Monad import Control.Parallel import Control.Parallel.Strategies edist :: String -> String -> Int -- edist calculates the edit distance of 2 strings -- see for example http://www.csse.monash.edu.au/~lloyd/tildeFP/Haskell/1998/Edit01/ getLines :: FilePath -> IO [Int] getLines = liftM ((parMap rnf (edist longString)) . lines) . readFile main :: IO () main = do list <- getLines "input.txt" mapM_ ( putStrLn . show ) list I am testing this code in a 2xQuadCore linux (Ubuntu 8.10) machine (8 cores in total). The code has been compiled with ghc --make -threaded mytest.hs I've been trying input files of different lengths, but the more cores I try to use, the worst performance I am getting. Here are some examples: # input.txt -> 10 lines (strings) of ~1200 letters each $ time ./mytest +RTS -N1 > /dev/null real 0m4.775s user 0m4.700s sys 0m0.080s $ time ./mytest +RTS -N4 > /dev/null real 0m6.272s user 0m8.220s sys 0m0.290s $ time ./mytest +RTS -N8 > /dev/null real 0m7.090s user 0m10.960s sys 0m0.400s # input.txt -> 100 lines (strings) of ~1200 letters each $ time ./mytest +RTS -N1 > /dev/null real 0m49.854s user 0m49.730s sys 0m0.120s $ time ./mytest +RTS -N4 > /dev/null real 1m11.303s user 1m36.210s sys 0m1.070s $ time ./mytest +RTS -N8 > /dev/null real 1m19.488s user 2m6.250s sys 0m1.270s What is going wrong in this code? Is this a problem of the "grain size" of the parallelization? Any help / advice would be very welcome, M;

Hi Miguel, I don't think that you can expect a program to process each line of a text file in parallel to very efficient. Opening a new thread is usually fairly cheap, however, there is some bookkeeping involved that shouldn't be underestimated. You only have 2 or 4 cores, so opening 100 threads or more, depending on the size of your file, will do you no good. You should rather split up your file in 4 chunks and and then process these *4* threads in parallel. That should make it more efficient! Parallel /= faster. At least not automatically. Happy Hacking, Thomas Miguel Pignatelli wrote:
Hi all,
I'm experimenting a bit with the parallelization capabilities of Haskell. What I am trying to do is to process in parallel all the lines of a text file, calculating the edit distance of each of these lines with a given string. This is my testing code:
import System.IO import Control.Monad import Control.Parallel import Control.Parallel.Strategies
edist :: String -> String -> Int -- edist calculates the edit distance of 2 strings -- see for example http://www.csse.monash.edu.au/~lloyd/tildeFP/Haskell/1998/Edit01/ http://www.csse.monash.edu.au/%7Elloyd/tildeFP/Haskell/1998/Edit01/
getLines :: FilePath -> IO [Int] getLines = liftM ((parMap rnf (edist longString)) . lines) . readFile
main :: IO () main = do list <- getLines "input.txt" mapM_ ( putStrLn . show ) list
I am testing this code in a 2xQuadCore linux (Ubuntu 8.10) machine (8 cores in total). The code has been compiled with
ghc --make -threaded mytest.hs
I've been trying input files of different lengths, but the more cores I try to use, the worst performance I am getting. Here are some examples:
# input.txt -> 10 lines (strings) of ~1200 letters each $ time ./mytest +RTS -N1 > /dev/null
real 0m4.775s user 0m4.700s sys 0m0.080s
$ time ./mytest +RTS -N4 > /dev/null
real 0m6.272s user 0m8.220s sys 0m0.290s
$ time ./mytest +RTS -N8 > /dev/null
real 0m7.090s user 0m10.960s sys 0m0.400s
# input.txt -> 100 lines (strings) of ~1200 letters each $ time ./mytest +RTS -N1 > /dev/null
real 0m49.854s user 0m49.730s sys 0m0.120s
$ time ./mytest +RTS -N4 > /dev/null
real 1m11.303s user 1m36.210s sys 0m1.070s
$ time ./mytest +RTS -N8 > /dev/null
real 1m19.488s user 2m6.250s sys 0m1.270s
What is going wrong in this code? Is this a problem of the "grain size" of the parallelization? Any help / advice would be very welcome,
M;
------------------------------------------------------------------------
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Thomas, Thanks for your answer. I know that there is needed some tweak in the process of parallelization to get a performance gain. I agree with your reasoning regarding the 100 string input, but in the other example I gave, I use the 8-core machine to process a 10 strings (and each one takes half a second to be processed) why is this case failing too? M; El 23/05/2009, a las 0:02, Thomas Friedrich escribió:
Hi Miguel,
I don't think that you can expect a program to process each line of a text file in parallel to very efficient. Opening a new thread is usually fairly cheap, however, there is some bookkeeping involved that shouldn't be underestimated. You only have 2 or 4 cores, so opening 100 threads or more, depending on the size of your file, will do you no good. You should rather split up your file in 4 chunks and and then process these *4* threads in parallel.
That should make it more efficient! Parallel /= faster. At least not automatically.
Happy Hacking, Thomas
Miguel Pignatelli wrote:
Hi all,
I'm experimenting a bit with the parallelization capabilities of Haskell. What I am trying to do is to process in parallel all the lines of a text file, calculating the edit distance of each of these lines with a given string. This is my testing code:
import System.IO import Control.Monad import Control.Parallel import Control.Parallel.Strategies
edist :: String -> String -> Int -- edist calculates the edit distance of 2 strings -- see for example http://www.csse.monash.edu.au/~lloyd/tildeFP/Haskell/1998/Edit01/ <http://www.csse.monash.edu.au/%7Elloyd/tildeFP/Haskell/1998/ Edit01/>
getLines :: FilePath -> IO [Int] getLines = liftM ((parMap rnf (edist longString)) . lines) . readFile
main :: IO () main = do list <- getLines "input.txt" mapM_ ( putStrLn . show ) list
I am testing this code in a 2xQuadCore linux (Ubuntu 8.10) machine (8 cores in total). The code has been compiled with
ghc --make -threaded mytest.hs
I've been trying input files of different lengths, but the more cores I try to use, the worst performance I am getting. Here are some examples:
# input.txt -> 10 lines (strings) of ~1200 letters each $ time ./mytest +RTS -N1 > /dev/null real 0m4.775s user 0m4.700s sys 0m0.080s
$ time ./mytest +RTS -N4 > /dev/null
real 0m6.272s user 0m8.220s sys 0m0.290s
$ time ./mytest +RTS -N8 > /dev/null
real 0m7.090s user 0m10.960s sys 0m0.400s
# input.txt -> 100 lines (strings) of ~1200 letters each $ time ./mytest +RTS -N1 > /dev/null
real 0m49.854s user 0m49.730s sys 0m0.120s
$ time ./mytest +RTS -N4 > /dev/null
real 1m11.303s user 1m36.210s sys 0m1.070s
$ time ./mytest +RTS -N8 > /dev/null
real 1m19.488s user 2m6.250s sys 0m1.270s
What is going wrong in this code? Is this a problem of the "grain size" of the parallelization? Any help / advice would be very welcome,
M;
------------------------------------------------------------------------
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Awesome! This seems to be an analog of the Data.List.find function. I
originally didn't implement mine this way because I thought it went through
the entire list, but I was obviously mistaken!
Thanks for your help!
-deech
On Tue, May 19, 2009 at 8:39 AM, 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.
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 ------------------------------------------------------------------------
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (7)
-
aditya siram
-
Alexander Dunlap
-
Antoine Latter
-
Daniel Fischer
-
Heinrich Apfelmus
-
Miguel Pignatelli
-
Thomas Friedrich