
Hi, A simple example of something I was trying to do but it had some questions along the lines of "the best way to do this". Given a list l = [a] and an a-list alist = [ (a,b) ] the idea is to find all the items in l which are in alist and then create a list [b] so the overall function should be [a] -> [ (a,b) ] -> [b] the solution is straightforward: l1 = filter (\x -> isJust (lookup x alist)) l l2 = map (\x -> fromJust (lookup x alist)) l1 `fromJust` used in the construction of l2 won't fail, because only the elements for which the lookup succeeded are in l1. This would be something called `filterMap` but I couldn't find such a function in the list library, but it seems like there just has to be one defined in a library somewhere. the above seems clumsy, i'm wondering how to make it "more pretty". generally i was also wondering if the above construction is as inefficient as it looks because of the double-lookup, or would the compiler actually be able to optimize that code into something more efficient ? this code is not being used on large sets of data so efficiency doesn't matter, I'm just curious. Thanks, Brian

I think you're looking for `mapMaybe` :-)
- Lyndon
On Sun, May 31, 2015 at 11:30 AM,
Hi,
A simple example of something I was trying to do but it had some questions along the lines of "the best way to do this".
Given a list
l = [a]
and an a-list
alist = [ (a,b) ]
the idea is to find all the items in l which are in alist and then create a list [b]
so the overall function should be
[a] -> [ (a,b) ] -> [b]
the solution is straightforward:
l1 = filter (\x -> isJust (lookup x alist)) l l2 = map (\x -> fromJust (lookup x alist)) l1
`fromJust` used in the construction of l2 won't fail, because only the elements for which the lookup succeeded are in l1.
This would be something called `filterMap` but I couldn't find such a function in the list library, but it seems like there just has to be one defined in a library somewhere.
the above seems clumsy, i'm wondering how to make it "more pretty".
generally i was also wondering if the above construction is as inefficient as it looks because of the double-lookup, or would the compiler actually be able to optimize that code into something more efficient ? this code is not being used on large sets of data so efficiency doesn't matter, I'm just curious.
Thanks,
Brian _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

On Sun, 31 May 2015 11:47:01 +1000
Lyndon Maydwell
I think you're looking for `mapMaybe` :-)
yes. yes i am. lol. i even had the Maybe module open and just didn't get all the way to the end. although after looking at my problem, i realized i need to save those elements of the list that weren't matched. that makes it slightly more complicated. but i did find partition which works nicely. thanks! Brian

f as alist = [ b | (a, b) <- alist, a `elem` as ]
perhaps?
On Sat, 30 May 2015 6:47 pm Lyndon Maydwell
I think you're looking for `mapMaybe` :-)
- Lyndon
On Sun, May 31, 2015 at 11:30 AM,
wrote: Hi,
A simple example of something I was trying to do but it had some questions along the lines of "the best way to do this".
Given a list
l = [a]
and an a-list
alist = [ (a,b) ]
the idea is to find all the items in l which are in alist and then create a list [b]
so the overall function should be
[a] -> [ (a,b) ] -> [b]
the solution is straightforward:
l1 = filter (\x -> isJust (lookup x alist)) l l2 = map (\x -> fromJust (lookup x alist)) l1
`fromJust` used in the construction of l2 won't fail, because only the elements for which the lookup succeeded are in l1.
This would be something called `filterMap` but I couldn't find such a function in the list library, but it seems like there just has to be one defined in a library somewhere.
the above seems clumsy, i'm wondering how to make it "more pretty".
generally i was also wondering if the above construction is as inefficient as it looks because of the double-lookup, or would the compiler actually be able to optimize that code into something more efficient ? this code is not being used on large sets of data so efficiency doesn't matter, I'm just curious.
Thanks,
Brian _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Note that all proposed solutions are in O(n²) while this can be realized in
O(n log n) (sort both list then match them in order). It depends on your
use case if this is worthwhile.
--
Jedaï
Le dim. 31 mai 2015 à 07:17, Alex Hammel
f as alist = [ b | (a, b) <- alist, a `elem` as ]
perhaps?
On Sat, 30 May 2015 6:47 pm Lyndon Maydwell
wrote: I think you're looking for `mapMaybe` :-)
- Lyndon
On Sun, May 31, 2015 at 11:30 AM,
wrote: Hi,
A simple example of something I was trying to do but it had some questions along the lines of "the best way to do this".
Given a list
l = [a]
and an a-list
alist = [ (a,b) ]
the idea is to find all the items in l which are in alist and then create a list [b]
so the overall function should be
[a] -> [ (a,b) ] -> [b]
the solution is straightforward:
l1 = filter (\x -> isJust (lookup x alist)) l l2 = map (\x -> fromJust (lookup x alist)) l1
`fromJust` used in the construction of l2 won't fail, because only the elements for which the lookup succeeded are in l1.
This would be something called `filterMap` but I couldn't find such a function in the list library, but it seems like there just has to be one defined in a library somewhere.
the above seems clumsy, i'm wondering how to make it "more pretty".
generally i was also wondering if the above construction is as inefficient as it looks because of the double-lookup, or would the compiler actually be able to optimize that code into something more efficient ? this code is not being used on large sets of data so efficiency doesn't matter, I'm just curious.
Thanks,
Brian _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

On Sun, 31 May 2015 05:17:10 +0000
Alex Hammel
f as alist = [ b | (a, b) <- alist, a `elem` as ]
perhaps?
perhaps. i have no idea how that works. but don't spoil it for me though, i'm going to go of and study it :-) @Chaddai . this is for very small lists, so optimization in the form of sorting and binary lookup is definitely not worth the effort. Here's what I finally wrote. partitionMaybe is a modified version of partition from the List library. unsure what the ~(ts, fs) syntax is though, removing the `~` doesn't seem to matter. this seems fairly clean. i noticed that partition simply uses foldr. it looks like select is just a helper so that partition isn't cluttered. i'm unsure why select was broken out as a separate function instead of just being in a where clause. possibly to be able to assign it a an explicit type signature ? more likely it has something to do with the fact that in the library partition is declared inline. extract :: [(String,b)] -> [String] -> ([b], [String]) extract alist l = let inList s = lookup (uppercase s) alist (l1, l2) = partitionMaybe inList l in (l1, l2) partitionMaybe :: (a -> Maybe b) -> [a] -> ([b],[a]) partitionMaybe p xs = foldr (select p) ([],[]) xs select :: (a -> Maybe b) -> a -> ([b], [a]) -> ([b], [a]) select p x ~(ts,fs) | isJust y = ((fromJust y):ts,fs) | otherwise = (ts, x:fs) where y = p x

f as alist = [ b | (a, b) <- alist, a `elem` as ]
perhaps?
perhaps. i have no idea how that works. but don't spoil it for me though, i'm going to go of and study it :-)
It's a list comprehension https://wiki.haskell.org/List_comprehension. I hope that's not too much of a spoiler :)
unsure what the ~(ts, fs) syntax is though, removing the `~` doesn't seem to matter.
Makes it lazier http://en.wikibooks.org/wiki/Haskell/Laziness#Lazy_pattern_matching
this seems fairly clean. i noticed that partition simply uses foldr. it looks like select is just a helper so that partition isn't cluttered. i'm unsure why select was broken out as a separate function instead of just being in a where clause. possibly to be able to assign it a an explicit type signature ?
You can assign type signatures in `let` and `where` clauses: f = let i :: Int i = 1 in increment i where increment :: Int -> Int increment = (+) 1 This is often quite a good idea. Type signatures are excellent, machine-checkable documentation.
extract :: [(String,b)] -> [String] -> ([b], [String]) extract alist l = let inList s = lookup (uppercase s) alist (l1, l2) = partitionMaybe inList l in (l1, l2)
partitionMaybe :: (a -> Maybe b) -> [a] -> ([b],[a]) partitionMaybe p xs = foldr (select p) ([],[]) xs
select :: (a -> Maybe b) -> a -> ([b], [a]) -> ([b], [a]) select p x ~(ts,fs) | isJust y = ((fromJust y):ts,fs) | otherwise = (ts, x:fs) where y = p x
Couple of things: `fromJust` is a code smell. In general, you should at least consider replacing it with `fromMaybe (error msg)` where `msg` is a more useful error message than '*** Exception: Maybe.fromJust: Nothing'. Of course in this particular case, that will never come up because you can prove that `y` is never Nothing using the guard condition. But in that case, it's better practice to use pattern matching and let the compiler prove it for you: select p y ~(xs,ys) = acc $ p y where acc (Just x) = (x:xs, ys) acc Nothing = ( xs, y:ys) The `partitionMaybe` function looks a bit odd to me. The computation you're trying to express is 'If this computation succedes, return whatever value it returned, but if it fails return some default value'. This is not a natural use of the Maybe data type: that's what Either is for. There's even a `partitionEithers` library function. `lookup` returns Maybe, not Either, but we can fix that. Here's my go (I've changed around the API a little bit as well) toEither :: a -> (Maybe b) -> Either a b toEither _ (Just x) = Right x toEither y Nothing = Left y lookupEither :: Eq a => a -> [(a,b)] -> Either a b lookupEither key assocs = toEither key $ lookup key assocs uppercase :: String -> String uppercase = map toUpper extract :: [String] -> [(String,b)] -> ([String],[b]) extract xs assocs = let xs' = map uppercase xs eithers = map (\x -> lookupEither x assocs) xs' -- spoilers: same as [ lookupEither x assocs | x <- xs' ] in partitionEithers eithers main :: IO ()main = print $ extract ["Foo", "Bar"] [("FOO",1), ("BAZ",2)] This differs slightly from your algorithm in that it returns '(["BAR"],[1]), where yours would return (["Bar"],[1]). If preserving the original case in the output, I would either write a `caseInsensitiveLookup` function, or use a case insensitive text https://hackage.haskell.org/package/case-insensitive-0.2.0.1/docs/Data-CaseI... data type.

On Mon, 01 Jun 2015 16:10:47 +0000
Alex Hammel
extract :: [String] -> [(String,b)] -> ([String],[b]) extract xs assocs = let xs' = map uppercase xs eithers = map (\x -> lookupEither x assocs) xs' -- spoilers: same as [ lookupEither x assocs | x <- xs' ] in partitionEithers eithers
This differs slightly from your algorithm in that it returns '(["BAR"],[1]), where yours would return (["Bar"],[1]). If preserving the original case in the output, I would either write a
ok. big surprise, i like your version much better. however, i'm unclear why you didn't just use eithers = map (\x -> lookupEither (uppercase x) assocs) xs instead of mapping everything to uppercase first. meanwhile i need to get with the list comprehension program. i use python list comprehensions all the time, and yet i continue to use map in haskell. how weird is that ? Brian

Thank you so much for all the info ! Really appreciate it.
My pleasure! however, i'm unclear why you didn't just use
eithers = map (\x -> lookupEither (uppercase x) assocs) xs
instead of mapping everything to uppercase first.
Two reasons: 1) I thought it would be slightly more readable. 2) There's no performance penalty. My version looks like it traverses the list twice, but it doesn't because laziness. Where the compiler for a strict language might make an intermediate, uppercased list, Haskell will produce the uppercase values as they are needed. To prove that to myself, I ran a quick criterion https://hackage.haskell.org/package/criterion benchmark. If anything, inlining the call to uppercase *decreases* performance slightly. Incidentally, that's the same reason why the `filterMap` function you asked about earlier doesn't exist. You can just do `(map f . filter p) xs`. The values will be created lazily, with no intermediate list.
meanwhile i need to get with the list comprehension program. i use python list comprehensions all the time, and yet i continue to use map in haskell. how weird is that ?
Not super weird. In my experience listcomps (and their relatives) are much more common in idiomatic Python than idiomatic Haskell. Still something you'll want to know how to do, though. Think '|' = 'for', '<-' = 'in' and ',' = 'if' and you'll be fine.

On Tue, 02 Jun 2015 15:49:06 +0000
Alex Hammel
My version looks like it traverses the list twice, but it doesn't because laziness. Where the compiler for a strict language might make an intermediate, uppercased list, Haskell will produce the uppercase values as they are needed.
ok that's cool to know. that's why i like going over these "simple" examples. in thinking about my problem i realized that it's perfectly fine if the uneaten list comes back upper case. so i went back to the map version. actually the list comp version :-)
Incidentally, that's the same reason why the `filterMap` function you asked about earlier doesn't exist. You can just do `(map f . filter p) xs`. The values will be created lazily, with no intermediate list.
precisely what i was wondering. haven't tried out criterion yet, just installed it to try out. seems like a valuable learning tool. should be a good learning tool. Brian
participants (4)
-
Alex Hammel
-
briand@aracnet.com
-
Chaddaï Fouché
-
Lyndon Maydwell