
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.