Haskell school of expression fix function [duplicate] - haskell

This question already has answers here:
How do I use fix, and how does it work?
(5 answers)
Closed 6 years ago.
So I am reading Paul Hudak's book "The Haskell School of Expression" and am stuck on an exercise in there.
Here it goes
Suppose function fix is defined as
fix f = f (fix f)
What is the principal type of fix? That one I know, it's b -> b -> b
But I don't understand the way fix is defined, won't it go into an infinite recursion?
Also, let the remainder function be defined as
remainder :: Integer -> Integer -> Integer
remainder a b = if a < b then a
else remainder (a - b) b
Rewrite remainder using fix so that it is non-recursive.

First of all the principal type of fix is actually (b -> b) -> b (remember that only b -> (b -> b) is the same as b -> b -> b).
In a strict language, such a definition would go into infinite recursion, but because Haskell is lazy, the arguments to a function are evaluated only if they are at any point needed. For example you can define factorial.
-- with recursion
factorial :: Int -> Int
factorial n = if n == 0 then 1 else n * factorial (n-1)
-- with `fix`
factorial' :: Int -> Int
factorial' = fix (\f n -> if n == 0 then 1 else n * f (n - 1))
Following the same pattern, you should be able to define remainder.

Playing with it a little gives us
fix f = f (fix f) -- definition
fix f a = f (fix f) a -- eta expansion
fix f a b = f (fix f) a b -- eta expansion
remainder a b = if a < b then a else remainder (a - b) b -- definition
-- we want remainder = fix f: -- equation
fix f a b = if a < b then a else (fix f) (a - b) b -- substitution
= (\g -> if a < b then a else g (a - b) b) (fix f) -- abstraction
= fix (\g -> \a b -> if a < b then a else g (a - b) b) a b -- abstraction
thus
remainder =
fix (\g a b -> if a < b then a else g (a - b) b) -- eta reduction

Related

How to implement Factorial via Control.Arrow.loop?

I wonder whether it is possible to implement factorial using Control.Arrow.loop.
loop :: ArrowLoop a => a (b, d) (c, d) -> a b c
One of the evident ideas is to implement a somehow terminating branch (a branch where the first element of the pair (type c) wouldn't depend on the second element of the pair (type d)).
It seems to me that it can't be done since we can't apply any boolean function to the second element of the pair (type d) during the first iteration because it would cause infinite recursion, so it only leaves us with the argument (type b), but the result of any boolean function wouldn't differ depending on the iteration (the argument doesn't change), thus, it would either terminate instantly or never terminate at all.
The other idea I had is to create an endless stream of factorials, but this doesn't seem real either, since, once again, the argument can't be changed.
So, I have 3 questions:
Am I right about the points above?
Am I missing any other concept which would help to implement factorial via Control.Arrow.loop?
What is the correct idea behind this implementation?
I've never actually used ArrowLoop before, loop is pretty cool.
Here is a factorial implemented using loop:
fact :: Integer -> Integer
fact =
loop $ \(n, f) ->
( f n 1
, \i acc ->
if i > 0
then f (i - 1) (i * acc)
else acc)
Let's give it a try:
λ> fact <$> [1..11]
[1,2,6,24,120,720,5040,40320,362880,3628800,39916800]
I don't know if I can answer the first question you have, but for the 3rd one it's obviously possible. For the concepts that could help you, I think the fix point is the one you are looking for. For example you can start by trying this ;)
λ> import Data.Function
λ> fix error
Once you press enough Ctrl+C you can write factorial using fix point:
λ> let fact = fix $ \ f i -> if i > 1 then i * f (i - 1) else i
λ> fact <$> [1..11]
[1,2,6,24,120,720,5040,40320,362880,3628800,39916800]
Edit
It seems like a bit of expansion on the answer could be helpful.
First of all let's look at an alternative and better (due to tail recursion) implementation of fact using fix, so we can see how it compares with our implementation using loop:
factFix :: Integer -> Integer
factFix n =
fix
(\f ->
\i acc ->
if i > 0
then f (i - 1) (i * acc)
else acc)
n
1
We can see it is not far off. In both cases we get f as an argument and we return back a function that uses that f, in fact, the returned non-recursive function is identical in both cases. Just for clarity let's extract it an reuse in both places:
factNoRec :: (Ord p, Num p) => (p -> p -> p) -> p -> p -> p
factNoRec f i acc =
if i > 0
then f (i - 1) (i * acc)
else acc
factLoop :: Integer -> Integer
factLoop n = loop (\(k, f) -> (f k 1, factNoRec f)) n
factFix :: Integer -> Integer
factFix n = fix (\f -> factNoRec f) n 1
Hopefully now it is much more apparent that they are really related concepts.
Looking into implementations of fix and loop (at least for functions, cause there are also mfix and loop for Kleisli) provides even more insight into their relation:
λ> fix f = let x = f x in x
λ> loop f b = let (c,d) = f (b,d) in c
They are really close to each other.
How about type signatures:
λ> :t fix
fix :: (t -> t) -> t
λ> :t loop
loop :: ((b, d) -> (c, d)) -> b -> c
Those look different. But if you do a bit of unification in the fact case you'll see that fix and loop acquire types:
λ> :t fix :: ((a -> b -> c) -> (a -> b -> c)) -> a -> b -> c
λ> :t loop :: ((b, a -> b -> c) -> (c, a -> b -> c)) -> b -> c
All of a b and c become all Integer in the end, but looking at type variables instead gives a better insight into what's going on. And really what's going on is just recursion by the means of fixed point combinators.

How to fix "Illegal type signature" error in Haskell

I ran into the following error in Haskell:
"Type signatures are only allowed in patterns with ScopedTypeVariables"
How should I re-use the defined variables. Thanks in advance
sum :: (Double -> Double) -> (Double -> Double) -> Int ->
(Double -> Double)
sum f g n = (\x -> helper f g n x)
where
helper :: (Double -> Double) -> (Double -> Double) -> Int -> Double ->
Double
|n == 0 = 0
|mod n 2 == 1 = f(x) + helper f g n-1 f(x)
|otherwise = g(x) + helper f g n-1 g(x)
This actually looks more like a syntactical error: you never defined a function body for helper, indeed you defined the signature of helper, followed by guards (the | ... part), but you should again state helper f g n x = ....
Furthermore I don't think it is useful to define helper here with a variable for f, an g, since these remain fixed throughout the recursion.
You can probably define the function as:
sumfg :: (Double -> Double) -> (Double -> Double) -> Int -> Double -> Double
sumfg f g = helperf
where helperf 0 _ = 0
helperf i x = let fx = f x in fx + helperg (i-1) fx
helperg 0 _ = 0
helperg i x = let gx = g x in gx + helperf (i-1) gx
We here defined two "helper" functions helperf and helperg, helperf will sum up f x with helperg (i-1) (f x), and helperg does the same, except that we use g instead of f. We here thus use mutual recursion to solve the problem.
We can however solve this problem more elegantly, by making use of scanl :: (b -> a -> b) -> b -> [a] -> [b], take :: Int -> [a] and sum :: Num a => [a] -> a:
sumfg :: Num a => (a -> a) -> (a -> a) -> Int -> a -> a
sumfg f g n x = sum (take n (scanl (flip ($)) (f x) (cycle [g, f])))
Here we thus make an infinite list of g and f, like [g, f, g, f, g, f, ...] with cycle [f, g]. We then use scanl (flip ($)) to each time apply the accumulator to one of the functions, and yield that element. We take the first n items of that list with take n, and finally we use sum to sum up these values.
For example:
Prelude> sumfg (2+) (3*) 5 1
91
Since (2+1) + (3*(2+1)) + (2+(3*(2+1))) + (3*(2+(3*(2+1)))) + (2+(3*(2+(3*(2+1))))) is 91.
We also generalized the signature: we can now work with any numerical type a, with the two functions f and g of type f, g :: a -> a.

Can't properly understand lambdas in Haskell

I have following code, implmenting inverse function calculation, basing on this formulas:
derivation :: (Fractional a) => (a -> a) -> (a -> a)
derivation f = \ x -> ( ( f (x + dx) - f (x) ) / dx ) where dx = 0.1
evalA k f
| k == 0 = \x -> x
| otherwise = \x -> (derivation (evalA (k-1) f) x) / (derivation f x)
inverseFun f x =
let
x0 = 3.0
eps = 0.001
iter k prev sum =
let
elemA = evalA k f x0
elemB = prev * (x - (f x0)) / (if k == 0 then 1 else k)
newItem = elemA * elemB
in
if abs (newItem) < eps
then sum
else iter (k + 1) elemB (sum + newItem)
in
iter 0 1.0 0.0
f1 = \x -> 1.0 * x * x
main = do
print $ inverseFun f1 2.5
I need to optimise it by moving evalA inside the inverseFun and store previous step calculation A'n/F' to reuse it on the next iteration, if possible. As far as I understand, each time evalA returns some sort of function and x applies afterwards, right before declaring elemA.
How can I convert my evalA or rewrite it to store previous results (by passing these results in iter, obviously)?
Don't mind if this calculations are not too precise, it requires good x0 and eps choice. My main question is in lambda conversion.
If you change your definition of inverseFun such that the (if k == 0 then 1 else k) is instead fromIntegral (if k == 0 then 1 :: Int else k), then you can provide type signatures to all of your functions:
derivation :: (Fractional a) => (a -> a) -> a -> a
evalA :: (Fractional a) => Int -> (a -> a) -> a -> a
inverseFun :: (Fractional a, Ord a) => (a -> a) -> a -> a
f1 :: (Fractional a) => a -> a
Which certainly helps out.
This is actually important for my solution to your problem, since we need k to be an Int, and you've used it as a Fractional a => a. The fromIntegral fixes that, but it needs to know that it's an Int, so I just added the inline type signature to help the compiler along.
Since your function only depends on the previous single value, you can use our handy friend from Prelude, iterate :: (a -> a) -> a -> [a]. This applies a function over and over again, producing an infinite list of values. We can then index it at any point to get the desired result (this is why having k an Int is important!).
Our function will look like
evalA :: Fractional a => Int -> (a -> a) -> a -> a
evalA k f = iterate go id !! k
where
go = ???
Here id is the same as your base case of \x -> x, just shorter and with more optimization rules. It serves as the initial value for generating this list. To implement go, the actual computation, we need it to accept the previous result as its argument:
where
go prev = \x -> derivation prev x / derivation f x
But this is considered "poor style" by hlint, and so it is suggested to convert this to the form
where
go prev x = derivation prev x / derivation f x
And that's it! I tested it and got the exact same result for your example input. The full code can be viewed here.

Why is the type of this function (a -> a) -> a?

Why is the type of this function (a -> a) -> a?
Prelude> let y f = f (y f)
Prelude> :t y
y :: (t -> t) -> t
Shouldn't it be an infinite/recursive type?
I was going to try and put into words what I think it's type should be, but I just can't do it for some reason.
y :: (t -> t) -> ?WTFIsGoingOnOnTheRHS?
I don't get how f (y f) resolves to a value. The following makes a little more sense to me:
Prelude> let y f x = f (y f) x
Prelude> :t y
y :: ((a -> b) -> a -> b) -> a -> b
But it's still ridiculously confusing. What's going on?
Well, y has to be of type (a -> b) -> c, for some a, b and c we don't know yet; after all, it takes a function, f, and applies it to an argument, so it must be a function taking a function.
Since y f = f x (again, for some x), we know that the return type of y must be the return type of f itself. So, we can refine the type of y a bit: it must be (a -> b) -> b for some a and b we don't know yet.
To figure out what a is, we just have to look at the type of the value passed to f. It's y f, which is the expression we're trying to figure out the type of right now. We're saying that the type of y is (a -> b) -> b (for some a, b, etc.), so we can say that this application of y f must be of type b itself.
So, the type of the argument to f is b. Put it all back together, and we get (b -> b) -> b — which is, of course, the same thing as (a -> a) -> a.
Here's a more intuitive, but less precise view of things: we're saying that y f = f (y f), which we can expand to the equivalent y f = f (f (y f)), y f = f (f (f (y f))), and so on. So, we know that we can always apply another f around the whole thing, and since the "whole thing" in question is the result of applying f to an argument, f has to have the type a -> a; and since we just concluded that the whole thing is the result of applying f to an argument, the return type of y must be that of f itself — coming together, again, as (a -> a) -> a.
Just two points to add to other people's answers.
The function you're defining is usually called fix, and it is a fixed-point combinator: a function that computes the fixed point of another function. In mathematics, the fixed point of a function f is an argument x such that f x = x. This already allows you to infer that the type of fix has to be (a -> a) -> a; "function that takes a function from a to a, and returns an a."
You've called your function y, which seems to be after the Y combinator, but this is an inaccurate name: the Y combinator is one specific fixed point combinator, but not the same as the one you've defined here.
I don't get how f (y f) resolves to a value.
Well, the trick is that Haskell is a non-strict (a.k.a. "lazy") language. The calculation of f (y f) can terminate if f doesn't need to evaluate its y f argument in all cases. So, if you're defining factorial (as John L illustrates), fac (y fac) 1 evaluates to 1 without evaluating y fac.
Strict languages can't do this, so in those languages you cannot define a fixed-point combinator in this way. In those languages, the textbook fixed-point combinator is the Y combinator proper.
#ehird's done a good job of explaining the type, so I'd like to show how it can resolve to a value with some examples.
f1 :: Int -> Int
f1 _ = 5
-- expansion of y applied to f1
y f1
f1 (y f1) -- definition of y
5 -- definition of f1 (the argument is ignored)
-- here's an example that uses the argument, a factorial function
fac :: (Int -> Int) -> (Int -> Int)
fac next 1 = 1
fac next n = n * next (n-1)
y fac :: Int -> Int
fac (y fac) -- def. of y
-- at this point, further evaluation requires the next argument
-- so let's try 3
fac (y fac) 3 :: Int
3 * (y fac) 2 -- def. of fac
3 * (fac (y fac) 2) -- def. of y
3 * (2 * (y fac) 1) -- def. of fac
3 * (2 * (fac (y fac) 1) -- def. of y
3 * (2 * 1) -- def. of fac
You can follow the same steps with any function you like to see what will happen. Both of these examples converge to values, but that doesn't always happen.
Let me tell about a combinator. It's called the "fixpoint combinator" and it has the following property:
The Property: the "fixpoint combinator" takes a function f :: (a -> a) and discovers a "fixed point" x :: a of that function such that f x == x. Some implementations of the fixpoint combinator might be better or worse at "discovering", but assuming it terminates, it will produce a fixed point of the input function. Any function that satisfies The Property can be called a "fixpoint combinator".
Call this "fixpoint combinator" y. Based on what we just said, the following are true:
-- as we said, y's input is f :: a -> a, and its output is x :: a, therefore
y :: (a -> a) -> a
-- let x be the fixed point discovered by applying f to y
y f == x -- because y discovers x, a fixed point of f, per The Property
f x == x -- the behavior of a fixed point, per The Property
-- now, per substitution of "x" with "f x" in "y f == x"
y f == f x
-- again, per substitution of "x" with "y f" in the previous line
y f == f (y f)
So there you go. You have defined y in terms of the essential property of the fixpoint combinator:
y f == f (y f). Instead of assuming that y f discovers x, you can assume that x represents a divergent computation, and still come to the same conclusion (iinm).
Since your function satisfies The Property, we can conclude that it is a fixpoint combinator, and that the other properties we have stated, including the type, are applicable to your function.
This isn't exactly a solid proof, but I hope it provides additional insight.

Transforming a function that computes a fixed point

I have a function which computes a fixed point in terms of iterate:
equivalenceClosure :: (Ord a) => Relation a -> Relation a
equivalenceClosure = fst . List.head -- "guaranteed" to exist
. List.dropWhile (uncurry (/=)) -- removes pairs that are not equal
. U.List.pairwise (,) -- applies (,) to adjacent list elements
. iterate ( reflexivity
. symmetry
. transitivity
)
Notice that we can abstract from this to:
findFixedPoint :: (a -> a) -> a -> a
findFixedPoint f = fst . List.head
. List.dropWhile (uncurry (/=)) -- dropWhile we have not reached the fixed point
. U.List.pairwise (,) -- applies (,) to adjacent list elements
. iterate
$ f
Can this function be written in terms of fix? It seems like there should be a transformation from this scheme to something with fix in it, but I don't see it.
There's quite a bit going on here, from the mechanics of lazy evaluation, to the definition of a fixed point to the method of finding a fixed point. In short, I believe you may be incorrectly interchanging the fixed point of function application in the lambda calculus with your needs.
It may be helpful to note that your implementation of finding the fixed-point (utilizing iterate) requires a starting value for the sequence of function application. Contrast this to the fix function, which requires no such starting value (As a heads up, the types give this away already: findFixedPoint is of type (a -> a) -> a -> a, whereas fix has type (a -> a) -> a). This is inherently because the two functions do subtly different things.
Let's dig into this a little deeper. First, I should say that you may need to give a little bit more information (your implementation of pairwise, for example), but with a naive first-try, and my (possibly flawed) implementation of what I believe you want out of pairwise, your findFixedPoint function is equivalent in result to fix, for a certain class of functions only
Let's take a look at some code:
{-# LANGUAGE RankNTypes #-}
import Control.Monad.Fix
import qualified Data.List as List
findFixedPoint :: forall a. Eq a => (a -> a) -> a -> a
findFixedPoint f = fst . List.head
. List.dropWhile (uncurry (/=)) -- dropWhile we have not reached the fixed point
. pairwise (,) -- applies (,) to adjacent list elements
. iterate f
pairwise :: (a -> a -> b) -> [a] -> [b]
pairwise f [] = []
pairwise f (x:[]) = []
pairwise f (x:(xs:xss)) = f x xs:pairwise f xss
contrast this to the definition of fix:
fix :: (a -> a) -> a
fix f = let x = f x in x
and you'll notice that we're finding a very different kind of fixed-point (i.e. we abuse lazy evaluation to generate a fixed point for function application in the mathematical sense, where we only stop evaluation iff* the resulting function, applied to itself, evaluates to the same function).
For illustration, let's define a few functions:
lambdaA = const 3
lambdaB = (*)3
and let's see the difference between fix and findFixedPoint:
*Main> fix lambdaA -- evaluates to const 3 (const 3) = const 3
-- fixed point after one iteration
3
*Main> findFixedPoint lambdaA 0 -- evaluates to [const 3 0, const 3 (const 3 0), ... thunks]
-- followed by grabbing the head.
3
*Main> fix lambdaB -- does not stop evaluating
^CInterrupted.
*Main> findFixedPoint lambdaB 0 -- evaluates to [0, 0, ...thunks]
-- followed by grabbing the head
0
now if we can't specify the starting value, what is fix used for? It turns out that by adding fix to the lambda calculus, we gain the ability to specify the evaluation of recursive functions. Consider fact' = \rec n -> if n == 0 then 1 else n * rec (n-1), we can compute the fixed point of fact' as:
*Main> (fix fact') 5
120
where in evaluating (fix fact') repeatedly applies fact' itself until we reach the same function, which we then call with the value 5. We can see this in:
fix fact'
= fact' (fix fact')
= (\rec n -> if n == 0 then 1 else n * rec (n-1)) (fix fact')
= \n -> if n == 0 then 1 else n * fix fact' (n-1)
= \n -> if n == 0 then 1 else n * fact' (fix fact') (n-1)
= \n -> if n == 0 then 1
else n * (\rec n' -> if n' == 0 then 1 else n' * rec (n'-1)) (fix fact') (n-1)
= \n -> if n == 0 then 1
else n * (if n-1 == 0 then 1 else (n-1) * fix fact' (n-2))
= \n -> if n == 0 then 1
else n * (if n-1 == 0 then 1
else (n-1) * (if n-2 == 0 then 1
else (n-2) * fix fact' (n-3)))
= ...
So what does all this mean? depending on the function you're dealing with, you won't necessarily be able to use fix to compute the kind of fixed point you want. This is, to my knowledge, dependent on the function(s) in question. Not all functions have the kind of fixed point computed by fix!
*I've avoided talking about domain theory, as I believe it would only confuse an already subtle topic. If you're curious, fix finds a certain kind of fixed point, namely the least available fixed point of the poset the function is specified over.
Just for the record, it is possible to define the function findFixedPoint using fix.
As Raeez has pointed out, recursive functions can be defined in terms of fix.
The function that you are interested in can be recursively defined as:
findFixedPoint :: Eq a => (a -> a) -> a -> a
findFixedPoint f x =
case (f x) == x of
True -> x
False -> findFixedPoint f (f x)
This means that we can define it as fix ffp where ffp is:
ffp :: Eq a => ((a -> a) -> a -> a) -> (a -> a) -> a -> a
ffp g f x =
case (f x) == x of
True -> x
False -> g f (f x)
For a concrete example, let us assume that f is defined as
f = drop 1
It is easy to see that for every finite list l we have findFixedPoint f l == [].
Here is how fix ffp would work when the "value argument" is []:
(fix ffp) f []
= { definition of fix }
ffp (fix ffp) f []
= { f [] = [] and definition of ffp }
[]
On the other hand, if the "value argument" is [42], we would have:
fix ffp f [42]
= { definition of fix }
ffp (fix ffp) f [42]
= { f [42] =/= [42] and definition of ffp }
(fix ffp) f (f [42])
= { f [42] = [] }
(fix ffp) f []
= { see above }
[]

Resources