Grouping parameters - haskell

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.

Related

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

Why does it apply the second argument?

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

Composition of Applicative functions

I can compose pure functions:
let f x = x + 1
let g x = x + 2
let z = f . g
z 1 == 4
I seem to be able to compose monadic functions also:
let f x = Just (x + 1)
let g x = Just (x + 2)
let z x = f x >>= g
z 1 == Just 4
I think I should be able to treat f and g from the last example as applicatives and compose those also, just not sure how:
let f x = Just (x + 1)
let g x = Just (x + 2)
let z x = f <*> g -- this doesn't work
z 1 == Just 4
Is this doable?
Bonus points, can z x = f x >>= g be written as a point-free function? Something like z = f >>= g?
{-# LANGUAGE TypeOperators #-}
The (type-level) composition of any two applicative functors,
newtype (f :. g) a = Compose { getCompose :: f (g a)) }
is an applicative functor.
instance (Functor f, Functor g) => Functor (f :. g) where
fmap f = Compose . fmap (fmap f) . getCompose
instance (Applicative f, Applicative g) => Applicative (f :. g) where
pure = Compose . pure . pure
Compose fgf <*> Compose fgx = Compose ((<*>) <$> fgf <*> fgx)
Your example is the composition of the Maybe applicative with the "function" or "reader" applicative (->) r.
type ReaderWithMaybe r = ((->) r) :. Maybe
x, y :: ReaderWithMaybe Int Int
x = Compose $ \x -> Just (x + 1)
y = Compose $ \x -> Just (x + 2)
Since ReaderWithMaybe r is an Applicative you can do all the usual Applicative stuff. Here I'm smashing my two values together with +.
ghci> let z = (+) <$> x <*> y
ghci> getCompose z 3
Just 9 -- (3 + 1) + (3 + 2) == 9
Note that x and y both get the same input 3. That's the behaviour of (->) r's Applicative instance. If you want to take the result of f x = Just (x + 1) and feed it into g x = Just (x + 2) (to get something equivalent to h x = Just (x + 3)), well, that's what Monad is for.
Bonus points, can z x = f x >>= g be written as a point-free function? Something like z = f >>= g?
You can easily define Kleisli composition by hand.
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
f >=> g = \x -> f x >>= g
It happens that >=> already exists in the standard library, along with its sister <=<. They are lovingly known as the "fish" operators, and they live in Control.Monad.
Applicative functions aren't
let f x = Just $ x + 1
let g x = Just $ x + 2
, they're
let f = Just $ \x -> x + 1
let g = Just $ \x -> x + 2
. Composition then works like liftA2 (.) f g or (.) <$> f <*> g.
Maybe you will be interested by Kleisli composition of monads:
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c

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}.

How can I understand "(.) . (.)"?

I believe I understand fmap . fmap for Functors, but on functions it's hurting my head for months now.
I've seen that you can just apply the definition of (.) to (.) . (.), but I've forgot how to do that.
When I try it myself it always turns out wrong:
(.) f g = \x -> f (g x)
(.) (.) (.) = \x -> (.) ((.) x)
\x f -> (.) ((.) x) f
\x f y -> (((.)(f y)) x)
\x f y g-> (((.)(f y) g) x)
\x f y g-> ((f (g y)) x)
\x f y g-> ((f (g y)) x):: t2 -> (t1 -> t2 -> t) -> t3 -> (t3 -> t1) -> t
If "just applying the definition" is the only way of doing it, how did anybody come up with (.) . (.)?
There must be some deeper understanding or intuition I'm missing.
Coming up with (.) . (.) is actually pretty straightforward, it's the intuition behind what it does that is quite tricky to understand.
(.) gets you very far when rewriting expression into the "pipe" style computations (think of | in shell). However, it becomes awkward to use once you try to compose a function that takes multiple arguments with a function that only takes one. As an example, let's have a definition of concatMap:
concatMap :: (a -> [b]) -> [a] -> [b]
concatMap f xs = concat (map f xs)
Getting rid of xs is just a standard operation:
concatMap f = concat . map f
However, there's no "nice" way of getting rid of f. This is caused by the fact, that map takes two arguments and we'd like to apply concat on its final result.
You can of course apply some pointfree tricks and get away with just (.):
concatMap f = (.) concat (map f)
concatMap f = (.) concat . map $ f
concatMap = (.) concat . map
concatMap = (concat .) . map
But alas, readability of this code is mostly gone. Instead, we introduce a new combinator, that does exactly what we need: apply the second function to the final result of first one.
-- .: is fairly standard name for this combinator
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(f .: g) x y = f (g x y)
concatMap = concat .: map
Fine, that's it for motivation. Let's get to the pointfree business.
(.:) = \f g x y -> f (g x y)
= \f g x y -> f ((g x) y)
= \f g x y -> f . g x $ y
= \f g x -> f . g x
Now, here comes the interesting part. This is yet another of the pointfree tricks that usually helps when you get stuck: we rewrite . into its prefix form and try to continue from there.
= \f g x -> (.) f (g x)
= \f g x -> (.) f . g $ x
= \f g -> (.) f . g
= \f g -> (.) ((.) f) g
= \f -> (.) ((.) f)
= \f -> (.) . (.) $ f
= (.) . (.)
As for intuition, there's this very nice article that you should read. I'll paraphrase the part about (.):
Let's think again about what our combinator should do: it should apply f to the result of result of g (I've been using final result in the part before on purpose, it's really what you get when you fully apply - modulo unifying type variables with another function type - the g function, result here is just application g x for some x).
What it means for us to apply f to the result of g? Well, once we apply g to some value, we'll take the result and apply f to it. Sounds familiar: that's what (.) does.
result :: (b -> c) -> ((a -> b) -> (a -> c))
result = (.)
Now, it turns out that composition (our of word) of those combinators is just a function composition, that is:
(.:) = result . result -- the result of result
You can also use your understanding of fmap . fmap.
If you have two Functors foo and bar, then
fmap . fmap :: (a -> b) -> foo (bar a) -> foo (bar b)
fmap . fmap takes a function and produces an induced function for the composition of the two Functors.
Now, for any type t, (->) t is a Functor, and the fmap for that Functor is (.).
So (.) . (.) is fmap . fmap for the case where the two Functors are (->) s and (->) t, and thus
(.) . (.) :: (a -> b) -> ((->) s) ((->) t a) -> ((->) s) ((->) t b)
= (a -> b) -> (s -> (t -> a)) -> (s -> (t -> b))
= (a -> b) -> (s -> t -> a ) -> (s -> t -> b )
it "composes" a function f :: a -> b with a function of two arguments, g :: s -> t -> a,
((.) . (.)) f g = \x y -> f (g x y)
That view also makes it clear that, and how, the pattern extends to functions taking more arguments,
(.) :: (a -> b) -> (s -> a) -> (s -> b)
(.) . (.) :: (a -> b) -> (s -> t -> a) -> (s -> t -> b)
(.) . (.) . (.) :: (a -> b) -> (s -> t -> u -> a) -> (s -> t -> u -> b)
etc.
Your solution diverges when you introduce y. It should be
\x f y -> ((.) ((.) x) f) y :: (c -> d) -> (a -> b -> c) -> a -> b -> d
\x f y z -> ((.) ((.) x) f) y z :: (c -> d) -> (a -> b -> c) -> a -> b -> d
\x f y z -> ((.) x (f y)) z :: (c -> d) -> (a -> b -> c) -> a -> b -> d
-- Or alternately:
\x f y z -> (x . f y) z :: (c -> d) -> (a -> b -> c) -> a -> b -> d
\x f y z -> (x (f y z)) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
Which matches the original type signature: (.) . (.) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(It's easiest to do the expansion in ghci, where you can check each step with :t expression)
Edit:
The deeper intution is this:
(.) is simply defined as
\f g -> \x -> f (g x)
Which we can simplify to
\f g x -> f (g x)
So when you supply it two arguments, it's curried and still needs another argument to resolve.
Each time you use (.) with 2 arguments, you create a "need" for one more argument.
(.) . (.) is of course just (.) (.) (.), so let's expand it:
(\f0 g0 x0 -> f0 (g0 x0)) (\f1 g1 x1 -> f1 (g1 x1)) (\f2 g2 x2 -> f2 (g2 x2))
We can beta-reduce on f0 and g0 (but we don't have an x0!):
\x0 -> (\f1 g1 x1 -> f1 (g1 x1)) ((\f2 g2 x2 -> f2 (g2 x2)) x0)
Substitute the 2nd expression for f1...
\x0 -> \g1 x1 -> ((\f2 g2 x2 -> f2 (g2 x2)) x0) (g1 x1)
Now it "flips back"! (beta-reduction on f2):
This is the interesting step - x0 is substituted for f2 -- This means that x, which could have been data, is instead a function.
This is what (.) . (.) provides -- the "need" for the extra argument.
\x0 -> \g1 x1 -> (\g2 x2 -> x0 (g2 x2)) (g1 x1)
This is starting to look normal...
Let's beta-reduce a last time (on g2):
\x0 -> \g1 x1 -> (\x2 -> x0 ((g1 x1) x2))
So we're left with simply
\x0 g1 x1 x2 -> x0 ((g1 x1) x2)
, where the arguments are nicely still in order.
So, this is what I get when I do a slightly more incremental expansion
(.) f g = \x -> f (g x)
(.) . g = \x -> (.) (g x)
= \x -> \y -> (.) (g x) y
= \x -> \y -> \z -> (g x) (y z)
= \x y z -> (g x) (y z)
(.) . (.) = \x y z -> ((.) x) (y z)
= \x y z -> \k -> x (y z k)
= \x y z k -> x (y z k)
Which, according to ghci has the correct type
Prelude> :t (.) . (.)
(.) . (.) :: (b -> c) -> (a -> a1 -> b) -> a -> a1 -> c
Prelude> :t \x y z k -> x (y z k)
\x y z k -> x (y z k)
:: (t1 -> t) -> (t2 -> t3 -> t1) -> t2 -> t3 -> t
Prelude>
While I don't know the origins of this combinator, it is likely that it was
developed for use in combinatory logic, where you work strictly with combinators,
so you can't define things using more convenient lambda expressions. There may be
some intuition that goes with figuring these things out, but I haven't found it.
Most likely, you would develop some level of intuition if you had to do it enough.
It's easiest to write equations, combinators-style, instead of lambda-expressions: 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}. So,
-- _B = (.)
_B f g x = f (g x)
_B _B _B f g x y = _B (_B f) g x y
= (_B f) (g x) y
= _B f (g x) y
= f ((g x) y)
= f (g x y)
You discover this if, given f (g x y), you want to convert it into a combinatory form (get rid of all the parentheses and variable repetitions). Then you apply patterns corresponding to the combinators' definitions, hopefully tracing this derivation backwards. This is much less mechanical/automatic though.

Resources