Filter a list of tuples by fst - haskell

What I'm trying to do is not really solve a problem, but more to learn how to write Haskell code that composes/utilizes basic functions to do it.
I have a function that takes a list of tuples (String, Int) and a String, and returns a tuple whose fst matches the given String.
This was fairly easy to do with filter and lambda, but what I want to do now, is remove the rightmost argument, ie. I want to refactor the function to be a composition of partially applied functions that'll do the same functionality.
Original code was:
getstat :: Player -> String -> Stat
getstat p n = head $ filter (\(n', v) -> n' == n) $ stats p
New code is:
getstat :: Player -> String -> Stat
getstat p = head . (flip filter $ stats p) . cmpfst
where cmpfst = (==) . fst . (flip (,)) 0 -- Wrong :-\
The idea is to flip the filter and partially apply by giving in the list of tuples (stats p) and then compose cmpfst.
cmpfst should be String -> (String, Int) -> Bool so that when String argument is applied, it becomes a -> Bool which is good for the filter to pass in tuples, but as you can see - I have problems composing (==) so that only fst's of given tuples are compared.
P.S. I know that the first code is likely cleaner; the point of this task was not to write clean code but to learn how to solve the problem through composition.
Edit:
I understand well that asking for a head on an possibly empty list is a bad programming that'll result in a crash. Like one earlier poster mentioned, it is very simply and elegantly resolved with Maybe monad - a task I've done before and am familiar with.
What I'd like the focus to be on, is how to make cmpfst composed primarily of basic functions.
So far, the furthest I got is this:
getstat :: Player -> String -> Stat
getstat p = head . (flip filter $ stats p) . (\n' -> (==(fst n')) . fst) . (flip (,)) 0
I can't get rid of the (a -> Bool) lambda by composing and partially applying around (==). This signals, to me, that I either don't understand what I'm doing, or it's impossible using (==) operator in the way I imagined.
Furthermore, unless there's no exact solution, I'll accept signature-change solution as correct one. I'd like not to change the signature of the function simply because its a mental exercise for me, not a production code.

If I were writing this function, I'd probably have given it this type signature:
getstat :: String -> Player -> Stat
This makes it easy to eta-reduce the definition to
getstat n = head . filter ((== n) . fst) . stats

In a comment, you reached
getstat p = head . (flip filter $ stats p) . (\n (n', v) -> n' == n)
I wonder if there's a nicer composition that can eliminate the anon f.
Well, here it is
\n (n', v) -> n' == n
-- for convenience, we flip the ==
\n (n', v) -> n == n'
-- prefix notation
\n (n', v) -> (==) n n'
-- let's remove pattern matching over (n', v)
\n (n', v) -> (==) n $ fst (n', v)
\n x -> (==) n $ fst x
-- composition, eta
\n -> (==) n . fst
-- prefix
\n -> (.) ((==) n) fst
-- composition
\n -> ((.) . (==) $ n) fst
-- let's force the application to be of the form (f n (g n))
\n -> ((.) . (==) $ n) (const fst $ n)
-- exploit f <*> g = \n -> f n (g n) -- AKA the S combinator
((.) . (==)) <*> (const fst)
-- remove unneeded parentheses
(.) . (==) <*> const fst
Removing p is left as an exercise.

Related

Function Composition Do Notation

Is there a "do notation" syntactic sugar for simple function composition?
(i.e. (.) :: (b -> c) -> (a -> b) -> a -> c)
I'd like to be able to store results of some compositions for later (while still continuing the chain.
I'd rather not use the RebindableSyntax extension if possible.
I'm looking for something like this:
composed :: [String] -> [String]
composed = do
fmap (++ "!!!")
maxLength <- maximum . fmap length
filter ((== maxLength) . length)
composed ["alice", "bob", "david"]
-- outputs: ["alice!!!", "david!!!"]
I'm not sure something like this is possible, since the result of the earlier function essentially has to pass "through" the bind of maxLength, but I'm open to hearing of any other similarly expressive options. Basically I need to collect information as I go through the composition in order to use it later.
Perhaps I could do something like this with a state monad?
Thanks for your help!
Edit
This sort of thing kinda works:
split :: (a -> b) -> (b -> a -> c) -> a -> c
split ab bac a = bac (ab a) a
composed :: [String] -> [String]
composed = do
fmap (++ "!!!")
split
(maximum . fmap length)
(\maxLength -> (filter ((== maxLength) . length)))
One possible way to achieve something like that are arrows. Basically, in “storing interstitial results” you're just splitting up the information flow through the composition chain. That's what the &&& (fanout) combinator does.
import Control.Arrow
composed = fmap (++ "!!!")
>>> ((. length) . (==) . maximum . fmap length &&& id)
>>> uncurry filter
This definitely isn't good human-comprehensible code though.
A state monad would seem to allow something related too, but the problem is that the state type is fixed through the do block's monadic chain. That's not really flexible enough to pick up different-typed values throughout the composition chain. While it is certainly possible to circumvent this (amongst them, indeed, RebindableSyntax), this too isn't a good idea IMO.
The type of (<*>) specialised to the function instance of Applicative is:
(<*>) :: (r -> a -> b) -> (r -> a) -> (r -> b)
The resulting r -> b function passes its argument to both the r -> a -> b and the r -> a functions, and then uses the a value produced by the r -> a function as the second argument of the r -> a -> b one.
What does this have to do with your function? filter is a function of two arguments, a predicate and a list. Now, a key aspect of what you are trying to do is that the predicate is generated from the list. That means the core of your function can be expressed in terms of (<*>):
-- Using the predicate-generating function from leftaroundabout's answer.
maxLengthOnly :: Foldable t => [t a] -> [t a]
maxLengthOnly = flip filter <*> ((. length) . (==) . maximum . fmap length)
composed :: [String] -> [String]
composed = maxLengthOnly . fmap (++ "!!!")
This maxLengthOnly definition would be a quite nice one-liner if the pointfree predicate-generating function weren't so clunky.
Since the Applicative instance of functions is equivalent in power to the Monad one, maxLengthOnly can also be phrased as:
maxLengthOnly = (. length) . (==) . maximum . fmap length >>= filter
(The split you added to your question, by the way, is (>>=) for functions.)
A different way of writing it with Applicative is:
maxLengthOnly = filter <$> ((. length) . (==) . maximum . fmap length) <*> id
It is no coincidence that this looks a lot like leftaroundabout's solution: for functions, (,) <$> f <*> g = liftA2 (,) f g = f &&& g.
Finally, it is also worth noting that, while it is tempting to replace id in the latest version of maxLengthOnly with fmap (++ "!!!"), that won't work because fmap (++ "!!!") changes the length of the strings, and therefore affects the result of the predicate. With a function that doesn't invalidate the predicate, though, it would work pretty well:
nicerComposed = filter
<$> ((. length) . (==) . maximum . fmap length) <*> fmap reverse
GHCi> nicerComposed ["alice","bob","david"]
["ecila","divad"]
As leftaroundabout mentioned, you can use Arrows to write your function. But, there is a feature in ghc Haskell compiler, which is proc-notation for Arrows. It is very similar to well-known do-notation, but, unfortunately, not many people aware of it.
With proc-notation you can write your desired function in next more redable and elegant way:
{-# LANGUAGE Arrows #-}
import Control.Arrow (returnA)
import Data.List (maximum)
composed :: [String] -> [String]
composed = proc l -> do
bangedL <- fmap (++"!!!") -< l
maxLen <- maximum . fmap length -< bangedL
returnA -< filter ((== maxLen) . length) bangedL
And this works in ghci as expected:
ghci> composed ["alice", "bob", "david"]
["alice!!!","david!!!"]
If you are interested, you can read some tutorials with nice pictures to understand what is arrow and how this powerful feature works so you can dive deeper into it:
https://www.haskell.org/arrows/index.html
https://en.wikibooks.org/wiki/Haskell/Understanding_arrows
What you have is essentially a filter, but one where the filtering function changes as you iterate over the list. I would model this not as a "forked" composition, but as a fold using the following function f :: String -> (Int, [String]):
The return value maintains the current maximum and all strings of that length.
If the first argument is shorter than the current maximum, drop it.
If the first argument is the same as the current maximum, add it to the list.
If the first argument is longer, make its length the new maximum, and replace the current output list with a new list.
Once the fold is complete, you just extract the list from the tuple.
-- Not really a suitable name anymore, but...
composed :: [String] -> [String]
composed = snd . foldr f (0, [])
where f curr (maxLen, result) = let currLen = length curr
in case compare currLen maxLen of
LT -> (maxLen, result) -- drop
EQ -> (maxLen, curr:result) -- keep
GT -> (length curr, [curr]) -- reset

Finding all palindromic word pairs

I came up with an unreal problem: finding all palindromic word pairs in a vocabulary, so I wrote the solution below,
import Data.List
findParis :: Ord a => [[a]] -> [[[a]]]
findPairs ss =
filter ((== 2) . length)
. groupBy ((==) . reverse)
. sortBy (compare . reverse)
$ ss
main = do
print . findPairs . permutations $ ['a'..'c']
-- malfunctioning: only got partial results [["abc","cba"]]
-- expected: [["abc","cba"],["bac","cab"],["bca","acb"]]
Could you help correct it if worthy of trying?
#Solution
Having benefited from #David Young #chi comments the tuned working code goes below,
import Data.List (delete)
import Data.Set hiding (delete, map)
findPairs :: Ord a => [[a]] -> [([a], [a])]
findPairs ss =
let
f [] = []
f (x : xs) =
let y = reverse x
in
if x /= y
then
let ss' = delete y xs
in (x, y) : f ss'
else f xs
in
f . toList
. intersection (fromList ss)
$ fromList (map reverse ss)
import Data.List
import Data.Ord
-- find classes of equivalence by comparing canonical forms (CF)
findEquivalentSets :: Ord b => (a->b) -> [a] -> [[a]]
findEquivalentSets toCanonical =
filter ((>=2) . length) -- has more than one
-- with the same CF?
. groupBy ((((== EQ) .) .) (comparing toCanonical)) -- group by CF
. sortBy (comparing toCanonical) -- compare CFs
findPalindromes :: Ord a => [[a]] -> [[[a]]]
findPalindromes = findEquivalentSets (\x -> min x (reverse x))
This function lets us find many kinds of equivalence as long as we can assign some effectively computable canonical form (CF) to our elements.
When looking for palindromic pairs, two strings are equivalent if one is a reverse of the other. The CF is the lexicographically smaller string.
findAnagrams :: Ord a => [[a]] -> [[[a]]]
findAnagrams = findEquivalentSets sort
In this example, two strings are equivalent if one is an anagram of the other. The CF is the sorted string (banana → aaabnn).
Likewise we can find SOUNDEX equivalents and whatnot.
This is not terribly efficient as one needs to compute the CF on each comparison. We can cache it, at the expense of readability.
findEquivalentSets :: Ord b => (a->b) -> [a] -> [[a]]
findEquivalentSets toCanonical =
map (map fst) -- strip CF
. filter ((>=2) . length) -- has more than one
-- with the same CF?
. groupBy ((((== EQ) .) .) (comparing snd)) -- group by CF
. sortBy (comparing snd) -- compare CFs
. map (\x -> (x, toCanonical x)) -- pair the element with its CF
Here's an approach you might want to consider.
Using sort implies that there's some keying function word2key that yields the same value for both words of a palindromic pair. The first one that comes to mind for me is
word2key w = min w (reverse w)
So, map the keying function over the list of words, sort, group by equality, take groups of length 2, and then recover the two words from the key (using the fact that the key is either equal to the word or its reverse.
Writing that, with a couple of local definitions for clarity, gives:
findPals :: (Ord a, Eq a) => [[a]] -> [[[a]]]
findPals = map (key2words . head) .
filter ((== 2) . length) .
groupBy (==) .
sort .
(map word2key)
where word2key w = min w (reverse w)
key2words k = [k, reverse k]
Edit:
I posted my answer in a stale window without refreshing, so missed the very nice response from n.m. above.
Mea culpa.
So I'll atone by mentioning that both answers are variations on the well-known (in Perl circles) "Schwartzian transform" which itself applies a common Mathematical pattern -- h = f' . g . f -- translate a task to an alternate representation in which the task is easier, do the work, then translate back to the original representation.
The Schwartzian transform tuples up a value with its corresponding key, sorts by the key, then pulls the original value back out of the key/value tuple.
The little hack I included above was based on the fact that key2words is the non-deterministic inverse relation of word2key. It is only valid when two words have the same key, but that's exactly the case in the question, and is insured by the filter.
overAndBack :: (Ord b, Eq c) => (a -> b) -> ([b] -> [c]) -> (c -> d) -> [a] -> [d]
overAndBack f g f' = map f' . g . sort . map f
findPalPairs :: (Ord a, Eq a) => [[a]] -> [[[a]]]
findPalPairs = overAndBack over just2 back
where over w = min w (reverse w)
just2 = filter ((== 2) . length) . groupBy (==)
back = (\k -> [k, reverse k]) . head
Which demos as
*Main> findPalPairs $ words "I saw no cat was on a chair"
[["no","on"],["saw","was"]]
Thanks for the nice question.

Point-free equivalent

I have this function from another SO question,
f :: Ord a => [a] -> [(a, Int)]
f xs = zipWith (\x ys -> (x, length $ filter (< x) ys)) xs (inits xs)
I'm trying to write it in point-free style,
f = flip (zipWith (\x -> (,) x . length . filter (< x))) =<< inits
Is it possible to get rid of that x ?
It's possible, but absolutely not worth the pain. To directly answer your question, LambdaBot on FreeNode reports:
f = flip (zipWith (liftM2 (.) (,) ((length .) . filter . flip (<)))) =<< inits
At this point the function has lost whatever clarity it had, and has become unmaintainable. Here you'd do much better to introduce real names. Remember, just because we can make things point free does not mean we should.
As a general rule: if a variable turns up more than once in an expression, it's probably not a good idea to make it point-free. If you're determined however, the least unreadable way is with the Arrow combinators, because that makes it pretty clear where the data flow is "split". For the xs I'd write
uncurry (zipWith (...)) . (id &&& inits)
For x, the same method yields
zipWith ( curry $ uncurry(,) . (fst &&& length . uncurry filter . first(>)) )
This is even longer than the (->)-monad solution that you've used and lambdabot suggests, but it looks far more organised.
The point of pointfree style is not just omitting names for values, but preferring names for functions. This is significantly easier to do when you use very small definitions. Of course any code is going to become unreadable if you inline everything and don’t use good names.
So let’s start with your original function, and split it into a few smaller definitions.
f xs = zipWith combine xs (inits xs)
combine x xs = (x, countWhere (< x) xs)
countWhere f xs = length (filter f xs)
Now we can easily make these definitions pointfree in a readable way.
f = zipWith combine <*> inits
where combine = compose (,) countLessThan
compose = liftA2 (.)
countLessThan = countWhere . flip (<)
countWhere = length .: filter
(.:) = (.) . (.)
Using names judiciously and preferring composition over application allows us to factor code into small, easily understood definitions. Named parameters are the equivalent of goto for data—powerful, but best used to build reusable higher-level structures that are easier to understand and use correctly. These compositional combinators such as (.) and <*> are to data flow what map, filter, and fold are to control flow.
My stab at it:
f :: Ord a => [a] -> [(a, Int)]
f = zip <*> ((zipWith $ (length .) . filter . (>)) <*> inits)
Here I replaced (<) with (>) to have (length .) . filter . (>) as a function with arguments in the right order: a->[a]->Int. Passing it to zipWith, we get [a]->[[a]]->[Int].
Assuming we have [a] on input, we can see this as f ([[a]]->[Int]) for Applicative ((->) [a]), which can be combined with inits :: f [[a]] with <*> :: f ([[a]]->[Int])->f [[a]]->f [Int]. This gives us [a]->[Int], now need to consume both [a] and [Int] in parallel. zip is already of the right type: [a]->[Int]->[(a,Int)] to apply with <*>.
Not saying I recommend this, but the King of Pointfree is Control.Arrow
import Control.Arrow
-- A special version of zipWith' more amenable to pointfree style
zipWith' :: ((a, b) -> c) -> ([a], [b]) -> [c]
zipWith' = uncurry . zipWith . curry
f :: Ord a => [a] -> [(a, Int)]
f = zipWith' (fst &&& (length <<< uncurry filter <<< first (>))) <<< id &&& inits
Let me reclarify here—I really don't recommend this unless your intention is to somehow generalize the kind of arrow your program is operating in (e.g. into Arrowized FRP perhaps).
With the well-known
(f .: g) x y = f (g x y)
it is a semi-readable
zipWith (curry (fst &&& uncurry (length .: (filter . flip (<))) )) <*> inits
-- \(x,ys) -> (x , length ( (filter . flip (<)) x ys) )
Using Control.Applicative (f <*> g $ x = f x (g x), the S combinator), and Control.Arrow (as others, but a little bit differently).

How do I re-write a Haskell function of two argument to point-free style

I have the following function in Haskell
agreeLen :: (Eq a) => [a] -> [a] -> Int
agreeLen x y = length $ takeWhile (\(a,b) -> a == b) (zip x y)
I'm trying to learn how to write 'idiomatic' Haskell, which seem to prefer using . and $ instead of parenthesis, and also to prefer pointfree code where possible. I just can't seem to get rid of mentioning x and y explicitly. Any ideas?
I think I'd have the same issue with pointfreeing any function of two arguments.
BTW, this is just in pursuit of writing good code; not some "use whatever it takes to make it pointfree" homework exercise.
Thanks.
(Added comment)
Thanks for the answers. You've convinced me this function doesn't benefit from pointfree. And you've also given me some great examples for practicing transforming expressions. It's still difficult for me, and they seem to be as essential to Haskell as pointers are to C.
and also to prefer pointfree code where possible.
Not "where possible", but "where it improves readability (or has other manifest advantages)".
To point-free your
agreeLen x y = length $ takeWhile (\(a,b) -> a == b) (zip x y)
A first step would be to move the ($) right, and replace the one you have with a (.):
agreeLen x y = length . takeWhile (\(a,b) -> a == b) $ zip x y
Now, you can move it even further right:
agreeLen x y = length . takeWhile (uncurry (==)) . zip x $ y
and there you can immediately chop off one argument,
agreeLen x = length . takeWhile (uncurry (==)) . zip x
Then you can rewrite that as a prefix application of the composition operator,
agreeLen x = (.) (length . takeWhile (uncurry (==))) (zip x)
and you can write
f (g x)
as
f . g $ x
generally, here with
f = (.) (length . takeWhile (uncurry (==)))
and g = zip, giving
agreeLen x = ((.) (length . takeWhile (uncurry (==)))) . zip $ x
from which the argument x is easily removed. Then you can transform the prefix application of (.) into a section and get
agreeLen = ((length . takeWhile (uncurry (==))) .) . zip
But, that is less readable than the original, so I don't recommend doing that except for practicing the transformation of expressions into point-free style.
You could also use:
agreeLen :: (Eq a) => [a] -> [a] -> Int
agreeLen x y = length $ takeWhile id $ zipWith (==) x y
Idiomatic Haskell is whatever is easier to read, not necessarily what is most point-free.
As pointed out in Daniel's excellent answer, your problem is to compose f and g when f as one argument and g two. this could be written f ??? g with the correct operator (and with a type signature of (c -> d) -> (a -> b -> c) -> a -> b -> d.
This correspond to the (.).(.) operator (see there) which is sometimes defines as .:. In that case your expression becomes
length . takeWhile (uncurry (==)) .: zip
If you are used to the .: operator, then this point free version is perfectly readable. I can also instead use (<$$$>) = fmap fmap fmap and get
length . takeWhile (uncurry (==)) <$$$> zip
Another concise, point-free solution:
agreeLen = ((length . takeWhile id) .) . zipWith (==)
Equivalently:
agreeLen = (.) (length . takeWhile id) . zipWith (==)

Confusion about currying and point free style in Haskell

I was trying to implement the function
every :: (a -> IO Bool) -> [a] -> IO Bool
which was the topic for this question. I tried to do this without explicit recursion. I came up with the following code
every f xs = liftM (all id) $ sequence $ map f xs
My function didn't work since it wasn't lazy (which was required in the question), so no upvotes there :-).
However, I did not stop there. I tried to make the function point-free so that it would be shorter (and perhaps even cooler). Since the arguments f and xs are the last ones in the expression I just dropped them:
every = liftM (all id) $ sequence $ map
But this did not work as expected, in fact it didn't work at all:
[1 of 1] Compiling Main ( stk.hs, interpreted )
stk.hs:53:42:
Couldn't match expected type `[m a]'
against inferred type `(a1 -> b) -> [a1] -> [b]'
In the second argument of `($)', namely `map'
In the second argument of `($)', namely `sequence $ map'
In the expression: liftM (all id) $ sequence $ map
Failed, modules loaded: none.
Why is that? I was under the impression that it was possible to simply drop trailing function arguments, which basically is what currying is about.
The definition of $ is
f $ x = f x
Let's fully parenthesize your function:
every f xs = (liftM (all id)) (sequence ((map f) xs))
and your curried version:
every = (liftM (all id)) (sequence map)
As you noticed, these are not identical. You can only drop trailing function arguments when they are the last thing applied. For example,
f x = g c x
is actually
f x = (g c) x
and the application of (g c) to x comes last, so you can write
f = g c
One pattern with the application operator $ is that it often becomes the composition operator . in points-free versions. This is because
f $ g $ x
is equivalent to
(f . g) $ x
For example,
every f xs = liftM (all id) $ sequence $ map f xs
can become
every f xs = (liftM (all id) . sequence . map f) xs
at which point you can drop xs:
every f = liftM (all id) . sequence . map f
Eliminating the argument f is more difficult, because it is applied before the composition operator. Let's use the definition of dot from http://www.haskell.org/haskellwiki/Pointfree:
dot = ((.) . (.))
With points, this is
(f `dot` g) x = f . g x
and is exactly what we need to make every fully points-free:
every = (liftM (all id) . sequence) `dot` map
Sadly, due to restrictions in the Haskell type system, this one needs an explicit type signature:
every :: (Monad m) => (a -> m Bool) -> [a] -> m Bool

Resources