Why does it apply the second argument? - haskell

I am trying to understand the Interchange law of applicative functor:
u <*> pure y = pure ($ y) <*> u
What make me confuse is, the function application $ y, consider following example:
($ 2) :: (a -> b) -> b
Why does the second argument get applied not the first?

That's an operator section. A few simple examples:
Prelude> (/2) <$> [1..8]
[0.5,1.0,1.5,2.0,2.5,3.0,3.5,4.0]
Prelude> (:"!") <$> ['a'..'e']
["a!","b!","c!","d!","e!"]
The section (:"!") is syntactic sugar for \c -> c:"!", i.e. it takes a character c and prepends it to the string "!".
Likewise, the section ($ 2) takes a function f and simply applies it to the number 2.
Note that this is different from ordinary partial application:
Prelude> ((/) 2) <$> [1..8]
[2.0,1.0,0.6666666666666666,0.5,0.4,0.3333333333333333,0.2857142857142857,0.25]
Here, I've simply applied the function (/) to one fixed argument 2, the dividend. This can also be written as a left section (2/). But the right section (/2) applies 2 as the divisor instead.

You can do that with operator sections. For example:
(5+ ) -- Same as \ x -> 5+x
( +5) -- Same as \ x -> x+5
It's only operators you can do this with; normal named functions can only be curried from left to right.

Haskell cheat sheet operator sections entry could be:
(a `op` b) = (a `op`) b = (`op` b) a = (op) a b
When op is an actual operator (not an alpha-numerical name), backticks aren't needed.
The above can be seen as partially applying implicitly defined lambda expressions:
(a `op`) b = (a `op` b) = (\y -> a `op` y) b = (\x y -> x `op` y) a b = op a b
(`op` b) a = (a `op` b) = (\x -> x `op` b) a = (\y x -> x `op` y) b a = flip op b a
If a function f expects more than two arguments eventually, we can similarly create its curried version by partially applying an explicit lambda expression:
(\y z x -> f x y z) b c -- = (\x -> f x b c)
(\x z y -> f x y z) a c -- = (\y -> f a y c)
(\x y z -> f x y z) a b -- = (\z -> f a b z)
The last case is equivalent to just f a b, and the second to (flip . f) a c:
g b c a = f a b c = flip f b a c = flip (flip f b) c a = (flip . flip f) b c a
g a c b = f a b c = flip (f a) c b = (flip . f) a c b
g a b c = f a b c

Related

Grouping parameters

Say I have functions which accept the same parameters and I want to test if their outputs are equivalent for the same input.
f :: a -> b -> c
g :: a -> b -> c
f a b == g a b
How can I package the parameters a and b in x so I can write the following instead.
f x == g x
What are the best ways to accomplish this without needing to wrap the functions themselves?
The only way to do exactly what you’re asking is to use uncurry:
let
x = (a, b)
in uncurry f x == uncurry g x
(Or uncurryN for N arguments.)
However, instead of packaging the arguments in a tuple, you could use the (->) x instance of Applicative (i.e., functions taking x as input) to implicitly “spread” the arguments to the parameters of both functions, so at least you only have to mention them once. This instance is commonly used in point-free code.
For example, using liftA2 specialised to this instance:
-- General type:
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
-- Specialised to ‘(->) x’ (using TypeApplications syntax):
liftA2 #((->) _) :: (a -> b -> c) -> (x -> a) -> (x -> b) -> (x -> c)
You get this pattern:
liftA2 h f g x
-- =
(h <$> f <*> g) x
-- =
h (f x) (g x)
To lift more arguments, you add another liftA2 or … <$> … <*> …:
liftA2 (liftA2 h) f g x y
-- =
(liftA2 h <$> f <*> g) x y
-- =
h (f x y) (g x y)
So in a case like yours:
f, g :: Int -> Char -> Bool
f i c = chr i == c
g i c = i == ord c
(liftA2 . liftA2) (==) f g :: Int -> Char -> Bool
-- =
liftA2 (liftA2 (==)) f g
-- =
(\ x y -> f x y == g x y)
The N in liftAN corresponds to the number of functions; the number of liftAN calls corresponds to the number of arguments.

A traversal as data

I heard about this construction which is loosely described as “a traversal represented in data, applied to some structure, without the need for the applicative”
It can be defined as:
data X a b r =
| Done r
| Step a (X a b (b -> r))
A word description would be as follows:
the type X a b r describes the shape of a structure
which contains things of type a
and for each a you get the opportunity to produce something of type b
and provided you do that for each a,
you get something of type r.
Thus a “traversal” of a list, [a], has type X a b [b], because if you can turn each a of the list into a b then you get a [b].
My question is: what is this thing called? Is there a reference to more information about it?
Example usage:
instance Functor (X a b) where
fmap f (Done r) = f r
fmap f (Step a next) = Step a (fmap (f .) next)
f :: [a] -> X a b [b]
f [] = Done []
f (a:as) = Step a (fmap (flip (:)) as)
g :: Applicative f => (a -> f b) -> X a b r -> f r
g f (Done r) = pure r
g f (Step a next) = g f next <*> f a
More generally:
instance Applicative (X a b) where
pure x = Done x
Done f <*> y = fmap (\y -> f y) y
Step a next <*> y = Step a (fmap flip next <*> y)
t :: Traversable t => t a -> X a b (t b)
t = traverse (\a -> Step a (Done id))
And, assuming I haven’t made any errors, we should find that:
flip g . t == traverse
Edit: I’ve thought about this some more. There is something this doesn’t have which a traversal has: a traversal can split up the computation into something that isn’t “one at a time,” for example to traverse a binary tree one can traverse the left and right half “in parallel.” Here is a structure that I think gives the same effect:
data Y a b r =
| Done r
| One a (b -> r)
| forall s t. Split (Y a b s) (Y a b t) (s -> t -> r)
(Slightly vague syntax as I don’t remember it and don’t want to write this as a gadt)
f1 :: X a b r -> Y a b r
f1 (Done x) = Done x
f1 (Step a next) = Split (One a id) (f1 next) (flip ($))
f2 :: Y a b r -> X a b r
f2 (Done x) = Done x
f2 (One a f) = Step a (Done f)
f2 (Split x y f) = f <$> f2 x <*> f2 y

Explain (.)(.) to me

Diving into Haskell, and while I am enjoying the language I'm finding the pointfree style completely illegible. I've come a across this function which only consists of these ASCII boobies as seen below.
f = (.)(.)
And while I understand its type signature and what it does, I can't for the life of me understand why it does it. So could someone please write out the de-pointfreed version of it for me, and maybe step by step work back to the pointfree version sorta like this:
f g x y = (g x) + y
f g x = (+) (g x)
f g = (+) . g
f = (.) (+)
Generally (?) (where ? stands for an arbitrary infix operator) is the same as \x y -> x ? y. So we can rewrite f as:
f = (\a b -> a . b) (\c d -> c . d)
Now if we apply the argument to the function, we get:
f = (\b -> (\c d -> c . d) . b)
Now b is just an argument to f, so we can rewrite this as:
f b = (\c d -> c . d) . b
The definition of . is f . g = \x -> f (g x). If replace the outer . with its definition, we get:
f b = \x -> (\c d -> c . d) (b x)
Again we can turn x into a regular parameter:
f b x = (\c d -> c . d) (b x)
Now let's replace the other .:
f b x = (\c d y -> c (d y)) (b x)
Now let's apply the argument:
f b x = \d y -> (b x) (d y)
Now let's move the parameters again:
f b x d y = (b x) (d y)
Done.
You can also gradually append arguments to f:
f = ((.) . )
f x = (.) . x
f x y = ((.) . x) y
= (.) (x y)
= ((x y) . )
f x y z = (x y) . z
f x y z t = ((x y) . z) t
= (x y) (z t)
= x y (z t)
= x y $ z t
The result reveals that x and z are actually (binary and unary, respectively) functions, so I'll use different identifiers:
f g x h y = g x (h y)
We can work backwards by "pattern matching" over the combinators' definitions. Given
f a b c d = a b (c d)
= (a b) (c d)
we proceed
= B (a b) c d
= B B a b c d -- writing B for (.)
so by eta-contraction
f = B B
because
a (b c) = B a b c -- bidirectional equation
by definition. Haskell's (.) is actually the B combinator (see BCKW combinators).
edit: Potentially, many combinators can match the same code. That's why there are many possible combinatory encodings for the same piece of code. For example, (ab)(cd) = (ab)(I(cd)) is a valid transformation, which might lead to some other combinator definition matching that. Choosing the "most appropriate" one is an art (or a search in a search space with somewhat high branching factor).
That's about going backwards, as you asked. But if you want to go "forward", personally, I like the combinatory approach much better over the lambda notation fidgeting. I would even just write many arguments right away, and get rid of the extra ones in the end:
BBabcdefg = B(ab)cdefg = (ab)(cd)efg
hence,
BBabcd = B(ab)cd = (ab)(cd)
is all there is to it.

Point Free problems in Haskell

I am trying to convert the following Haskell code to point free style, to no avail.
bar f g xs = filter f (map g xs )
I'm new to Haskell and any help would be great.
Converting to pointfree style can be done entirely mechanically, though it's hard without being comfortable with the fundamentals of Haskell syntax like left-associative function application and x + y being the same as (+) x y. I will assume you are comfortable with Haskell syntax; if not, I suggest going through the first few chapters of LYAH first.
You need the following combinators, which are in the standard library. I have also given their standard names from combinator calculus.
id :: a -> a -- I
const :: a -> b -> a -- K
(.) :: (b -> c) -> (a -> b) -> (a -> c) -- B
flip :: (a -> b -> c) -> (b -> a -> c) -- C
(<*>) :: (a -> b -> c) -> (a -> b) -> (a -> c) -- S
Work with one parameter at a time. Move parameters on the left to lambdas on the right, e.g.
f x y = Z
becomes
f = \x -> \y -> Z
I like to do this one argument at a time rather than all at once, it just looks cleaner.
Then eliminate the lambda you just created according to the following rules. I will use lowercase letters for literal variables, uppercase letters to denote more complex expressions.
If you have \x -> x, replace with id
If you have \x -> A, where A is any expression in which x does not occur, replace with const A
If you have \x -> A x, where x does not occur in A, replace with A. This is known as "eta contraction".
If you have \x -> A B, then
If x occurs in both A and B, replace with (\x -> A) <*> (\x -> B).
If x occurs in just A, replace with flip (\x -> A) B
If x occurs in just B, replace with A . (\x -> B),
If x does not occur in either A or B, well, there's another rule we should have used already.
And then work inward, eliminating the lambdas that you created. Lets work with this example:
f x y z = foo z (bar x y)
-- Move parameter to lambda:
f x y = \z -> foo z (bar x y)
-- Remember that application is left-associative, so this is the same as
f x y = \z -> (foo z) (bar x y)
-- z appears on the left and not on the right, use flip
f x y = flip (\z -> foo z) (bar x y)
-- Use rule (3)
f x y = flip foo (bar x y)
-- Next parameter
f x = \y -> flip foo (bar x y)
-- Application is left-associative
f x = \y -> (flip foo) (bar x y)
-- y occurs on the right but not the left, use (.)
f x = flip foo . (\y -> bar x y)
-- Use rule 3
f x = flip foo . bar x
-- Next parameter
f = \x -> flip foo . bar x
-- We need to rewrite this operator into normal application style
f = \x -> (.) (flip foo) (bar x)
-- Application is left-associative
f = \x -> ((.) (flip foo)) (bar x)
-- x appears on the right but not the left, use (.)
f = ((.) (flip foo)) . (\x -> bar x)
-- use rule (3)
f = ((.) (flip foo)) . bar
-- Redundant parentheses
f = (.) (flip foo) . bar
There you go, now try it on yours! There is not really any cleverness involved in deciding which rule to use: use any rule that applies and you will make progress.
Both of the existing answers don't really answer your specific question in a way that's elucidating: one is "here are the rules, work it out for yourself" and the other is "here is the answer, no information about how the rules generate it."
The first three steps are really easy and consist in removing a common x from something of the form h x = f (g x) by writing h = f . g. Essentially it's saying "if you can write the thing in the form a $ b $ c $ ... $ y $ z and you want to remove the z, change all the dollars to dots, a . b . c . ... . y:
bar f g xs = filter f (map g xs)
= filter f $ (map g xs)
= filter f $ map g $ xs -- because a $ b $ c == a $ (b $ c).
bar f g = filter f . map g
= (filter f .) (map g)
= (filter f .) $ map $ g
bar f = (filter f .) . map
So this last f is the only tricky part, and it's tricky because the f is not at the "end" of the expression. But looking at it, we see that this is a function section (. map) applied to the rest of the expression:
bar f = (.) (filter f) . map
bar f = (. map) $ (.) $ filter $ f
bar = (. map) . (.) . filter
and that's how you reduce an expression when you don't have complicated things like f x x and the like appearing in it. In general there is a function flip f x y = f y x which "flips arguments"; you can always use that to move the f to the other side. Here we have flip (.) map . (.) . filter if you include the explicit flip call.
I asked lambdabot, a robot who hangs out on various Haskell IRC channels, to automatically work out the point-free equivalent. The command is #pl (pointless).
10:41 <frase> #pl bar f g xs = filter f (map g xs )
10:41 <lambdabot> bar = (. map) . (.) . filter
The point free version of bar is:
bar = (. map) . (.) . filter
This is arguably less comprehensible than the original (non-point-free) code. Use your good judgement when deciding whether to use point-free style on a case-by-case basis.
Finally, if you don't care for IRC there are web-based point-free
converters such as pointfree.io, the pointfree command line program, and other tools.

Haskell function composition, type of (.)(.) and how it's presented

So i know that:
(.) = (f.g) x = f (g x)
And it's type is (B->C)->(A->B)->A->C
But what about:
(.)(.) = _? = _?
How this is represented? I thought of:
(.)(.) = (f.g)(f.g)x = f(g(f(g x))) // this
(.)(.) = (f.g.h)x = f(g(h x)) // or this
But as far as i tried to get type of it, it's not correct to what GHCi tells me.
So what are both "_?"
Also - what does function/operator $ do?
First off, you're being sloppy with your notation.
(.) = (f.g) x = f (g x) -- this isn't true
What is true:
(.) f g x = (f.g) x = f (g x)
(.) = \f g x -> f (g x)
And its type is given by
(.) :: (b -> c) -> (a -> b) -> a -> c
-- n.b. lower case, because they're type *variables*
Meanwhile
(.)(.) :: (a -> b -> d) -> a -> (c -> b) -> c -> d
-- I renamed the variables ghci gave me
Now let's work out
(.)(.) = (\f' g' x' -> f' (g' x')) (\f g x -> f (g x))
= \g' x' -> (\f g x -> f (g x)) (g' x')
= \g' x' -> \g x -> (g' x') (g x)
= \f y -> \g x -> (f y) (g x)
= \f y g x -> f y (g x)
= \f y g x -> (f y . g) x
= \f y g -> f y . g
And ($)?
($) :: (a -> b) -> a -> b
f $ x = f x
($) is just function application. But whereas function application via juxtaposition is high precedence, function application via ($) is low precedence.
square $ 1 + 2 * 3 = square (1 + 2 * 3)
square 1 + 2 * 3 = (square 1) + 2 * 3 -- these lines are different
As dave4420 mentions,
(.) :: (b -> c) -> (a -> b) -> a -> c
So what is the type of (.) (.)? dave4420 skips that part, so here it is: (.) accepts a value of type b -> c as its first argument, so
(.) :: ( b -> c ) -> (a -> b) -> a -> c
(.) :: (d -> e) -> ((f -> d) -> f -> e)
so we have b ~ d->e and c ~ (f -> d) -> f -> e, and the resulting type of (.)(.) is (a -> b) -> a -> c. Substituting, we get
(a -> d -> e) -> a -> (f -> d) -> f -> e
Renaming, we get (a -> b -> c) -> a -> (d -> b) -> d -> c. This is a function f that expects a binary function g, a value x, a unary function h and another value y:
f g x h y = g x (h y)
That's the only way this type can be realized: g x :: b -> c, h y :: b and so g x (h y) :: c, as needed.
Of course in Haskell, a "unary" function is such that expects one or more arguments; similarly a "binary" function is such that expects two or more arguments. But not less than two (so using e.g. succ is out of the question).
We can also tackle this by writing equations, combinators-style1. Equational reasoning is easy:
(.) (.) x y z w q =
((.) . x) y z w q =
(.) (x y) z w q =
(x y . z) w q =
x y (z w) q
We just throw as much variables as needed into the mix and then apply the definition back and forth. q here was an extra, so we can throw it away and get the final definition,
_BB x y z w = x y (z w)
(coincidentally, (.) is known as B-combinator).
1 a b c = (\x -> ... body ...) is equivalent to a b c x = ... body ..., and vice versa, provided that x does not appear among {a,b,c}.

Resources