Why is this version of 'fix' more efficient in Haskell? - haskell

In Haskell, this is a simple (naive) definition of a fixed point
fix :: (a -> a) -> a
fix f = f (fix f)
But, here is how Haskell actually implements it (more efficient)
fix f = let x = f x in x
My question is why is the second one more efficient than the first?

The slow fix calls f on each step of recursion, while the fast one calls f exactly once. It can be visualized with tracing:
import Debug.Trace
fix f = f (fix f)
fix' f = let x = f x in x
facf :: (Int -> Int) -> Int -> Int
facf f 0 = 1
facf f n = n * f (n - 1)
tracedFacf x = trace "called" facf x
fac = fix tracedFacf
fac' = fix' tracedFacf
Now try some running:
> fac 3
called
called
called
called
6
> fac' 3
called
6
In more detail, let x = f x in x results in a lazy thunk being allocated for x, and a pointer to this thunk is passed to f. On first evaluating fix' f, the thunk is evaluated and all references to it (here specifically: the one we pass to f) are redirected to the resulting value. It just happens that x is given a value that also contains a reference to x.
I admit this can be rather mind-bending. It's something that one should get used to when working with laziness.

I don't think this always (or necessarily ever) helps when you're calling fix with a function that takes two arguments to produce a function taking one argument. You'd have to run some benchmarks to see. But you can also call it with a function taking one argument!
fix (1 :)
is a circular linked list. Using the naive definition of fix, it would instead be an infinite list, with new pieces built lazily as the structure is forced.

I believe this has been asked already, but I couldn't find the answer. The reason is that the first version
fix f = f (fix f)
is a recursive function, so it can't be inlined and then optimized. From the GHC manual:
For example, for a self-recursive function, the loop breaker can only be the function itself, so an INLINE pragma is always ignored.
But
fix f = let x = f x in x
isn't recursive, the recursion is moved into the let binding, so it's possible to inline it.
Update: I did some tests and while the former version doesn't inline while the latter does, it doesn't seem to be crucial for performance. So the other explanations (a single object on heap vs creating one every iteration) seem to be more accurate.

Related

Generator, Selector Pattern to calculate approximations in Haskell

I am trying to implement a generator, selector pattern to approximately calculate square roots in haskell
My generator looks like this:
generator :: (Double -> Double) -> Double -> [Double]
generator f a = generator f (f a)
My selector:
selector :: Double -> [Double] -> Double
selector eps (a : b : r)
| abs(a - b) <= eps = b
| otherwise = selector eps (b : r)
And the approx function:
next :: Double -> Double -> Double
next n x = (x + n/x) / 2
Calling this like selector 0.1 (generator (next 5) 2)
should give me ...(next 5( next 5 (next 5 2))) so [2.25, 2.23611111111111, 2.2360679779158,...] since my eps parameter is 0.1 abs(a - b) <= eps should be true on the first execution giving me 2.23611111111111 as a result. I do however end in a endless loop.
Could somebody explain to me what is wrong in the implementation of those functions?
Thanks in advance
This definition
generator f a = generator f (f a)
never generates any list elements: it gets stuck into an infinite recursion instead. You probably want
generator f a = a : generator f (f a)
which makes a to be the first element, followed by all the others we generate using recursion.
It could also be beneficial to avoid putting unevaluated thunks in the list. To avoid that, one could use
generator f a = a `seq` (a : generator f (f a))
so that a is evaluated early. This should not matter much in your code, since the
selector immediately evaluates the thunks as soon as they are generated.
Your generator function is missing the a:, as chi's answer correctly points out. However, there's a better solution than just adding that. Get rid of generator altogether, and use the built-in method iterate instead (or iterate' from Data.List if you want to avoid unevaluated thunks). These methods have the same behavior that you want from generate, but support optimizations like list fusion that your own method won't. And of course, there's also the advantage that it's one less function that you have to write and maintain.

How to print variable inside function?

I have a function:
fold_wrap :: (a -> a -> a) -> (Prop -> a) -> a -> Wrapper -> a
fold_wrap v x z (Mrappe l r) = v ( v(v x z l) v(v x z r) )
fold_wrap v x z (Wrap f) = x f
fold_warp v x z (Wtail ) = z
Where I encounter the following error:
mast: mast.hs:(15,1)-(16,31): Non-exhaustive patterns in function fold_mast
So I added
fold_wrap v x z _ = z
Which fixed the error but
Which led me to believe that some patterns were indeed left unmatched.
Now my intuition to fixing this was to print what gets passed to the function.
So I added this
fold_wrap v x z g = print g
But that didnt work either since the the function has to return an a type and not IO
So my question is:
How do I print g and return some dummy value at the same time ?
Tips on how to fix this non exhaustive pattern matching are also appreciated.
I can't speak to your non-exhaustive pattern problem without seeing the definition of Wrapper that you're using. I can, however, answer the question you've asked.
Normally, in Haskell, to print a value, we need to have IO in our return type. This keeps the code functionality pure and gives us tons of benefits, so we should never try to break this rule in production code.
However, there's always that pesky little voice in your head that wants to print a value for debugging purposes only. Bear in mind, this should never be done in a finished product; it's only for debugging reasons. However, for this reason, Haskell provides a module Debug.Trace which breaks all sanity and normal functional rules to let you do this.
import Debug.Trace
fold_wrap v x z g = traceShow g someDummyValue
Now, there are a few considerations. First, Wrapper still has to have Show. There's nothing we can do about that; if Haskell doesn't know how to print something, then it can't print it, even for debugging. Second, Haskell is non-strict, so when you run the code, you need to make sure the fold_wrap call is actually evaluated. Just calling it and binding the result to a dummy variable won't do; you need to actually take that dummy value and use it in some context where it absolutely has to be evaluated, usually by printing it out in main.
I said this before, but I'll say it again because it's important. Debug.Trace is for debugging only. It can get addicting, especially if you're new to Haskell. But do not use that module in production code. It has a lot of problems, such as not guaranteeing print order, that don't matter when debugging but matter a lot when used in user-facing code. Not to mention the fact that it breaks every Haskell rule in the book.

Memoizing multiplication

My application multiplies vectors after a (costly) conversion using an FFT. As a result, when I write
f :: (Num a) => a -> [a] -> [a]
f c xs = map (c*) xs
I only want to compute the FFT of c once, rather than for every element of xs. There really isn't any need to store the FFT of c for the entire program, just in the local scope.
I attempted to define my Num instance like:
data Foo = Scalar c
| Vec Bool v -- the bool indicates which domain v is in
instance Num Foo where
(*) (Scalar c) = \x -> case x of
Scalar d -> Scalar (c*d)
Vec b v-> Vec b $ map (c*) v
(*) v1 = let Vec True v = fft v1
in \x -> case x of
Scalar d -> Vec True $ map (c*) v
v2 -> Vec True $ zipWith (*) v (fft v2)
Then, in an application, I call a function similar to f (which works on arbitrary Nums) where c=Vec False v, and I expected that this would be just as fast as if I hack f to:
g :: Foo -> [Foo] -> [Foo]
g c xs = let c' = fft c
in map (c'*) xs
The function g makes the memoization of fft c occur, and is much faster than calling f (no matter how I define (*)). I don't understand what is going wrong with f. Is it my definition of (*) in the Num instance? Does it have something to do with f working over all Nums, and GHC therefore being unable to figure out how to partially compute (*)?
Note: I checked the core output for my Num instance, and (*) is indeed represented as nested lambdas with the FFT conversion in the top level lambda. So it looks like this is at least capable of being memoized. I have also tried both judicious and reckless use of bang patterns to attempt to force evaluation to no effect.
As a side note, even if I can figure out how to make (*) memoize its first argument, there is still another problem with how it is defined: A programmer wanting to use the Foo data type has to know about this memoization capability. If she wrote
map (*c) xs
no memoization would occur. (It must be written as (map (c*) xs)) Now that I think about it, I'm not entirely sure how GHC would rewrite the (*c) version since I have curried (*). But I did a quick test to verify that both (*c) and (c*) work as expected: (c*) makes c the first arg to *, while (*c) makes c the second arg to *. So the problem is that it is not obvious how one should write the multiplication to ensure memoization. Is this just an inherent downside to the infix notation (and the implicit assumption that the arguments to * are symmetric)?
The second, less pressing issue is that the case where we map (v*) onto a list of scalars. In this case, (hopefully) the fft of v would be computed and stored, even though it is unnecessary since the other multiplicand is a scalar. Is there any way around this?
Thanks
I believe stable-memo package could solve your problem. It memoizes values not using equality but by reference identity:
Whereas most memo combinators memoize based on equality, stable-memo does it based on whether the exact same argument has been passed to the function before (that is, is the same argument in memory).
And it automatically drops memoized values when their keys are garbage collected:
stable-memo doesn't retain the keys it has seen so far, which allows them to be garbage collected if they will no longer be used. Finalizers are put in place to remove the corresponding entries from the memo table if this happens.
So if you define something like
fft = memo fft'
where fft' = ... -- your old definition
you'll get pretty much what you need: Calling map (c *) xs will memoize the computation of fft inside the first call to (*) and it gets reused on subsequent calls to (c *). And if c is garbage collected, so is fft' c.
See also this answer to How to add fields that only cache something to ADT?
I can see two problems that might prevent memoization:
First, f has an overloaded type and works for all Num instances. So f cannot use memoization unless it is either specialized (which usually requires a SPECIALIZE pragma) or inlined (which may happen automatically, but is more reliable with an INLINE pragma).
Second, the definition of (*) for Foo performs pattern matching on the first argument, but f multiplies with an unknown c. So within f, even if specialized, no memoization can occur. Once again, it very much depends on f being inlined, and a concrete argument for c to be supplied, so that inlining can actually appear.
So I think it'd help to see how exactly you're calling f. Note that if f is defined using two arguments, it has to be given two arguments, otherwise it cannot be inlined. It would furthermore help to see the actual definition of Foo, as the one you are giving mentions c and v which aren't in scope.

Evaluation strategy

How should one reason about function evaluation in examples like the following in Haskell:
let f x = ...
x = ...
in map (g (f x)) xs
In GHC, sometimes (f x) is evaluated only once, and sometimes once for each element in xs, depending on what exactly f and g are. This can be important when f x is an expensive computation. It has just tripped a Haskell beginner I was helping and I didn't know what to tell him other than that it is up to the compiler. Is there a better story?
Update
In the following example (f x) will be evaluated 4 times:
let f x = trace "!" $ zip x x
x = "abc"
in map (\i -> lookup i (f x)) "abcd"
With language extensions, we can create situations where f x must be evaluated repeatedly:
{-# LANGUAGE GADTs, Rank2Types #-}
module MultiEvG where
data BI where
B :: (Bounded b, Integral b) => b -> BI
foo :: [BI] -> [Integer]
foo xs = let f :: (Integral c, Bounded c) => c -> c
f x = maxBound - x
g :: (forall a. (Integral a, Bounded a) => a) -> BI -> Integer
g m (B y) = toInteger (m + y)
x :: (Integral i) => i
x = 3
in map (g (f x)) xs
The crux is to have f x polymorphic even as the argument of g, and we must create a situation where the type(s) at which it is needed can't be predicted (my first stab used an Either a b instead of BI, but when optimising, that of course led to only two evaluations of f x at most).
A polymorphic expression must be evaluated at least once for each type it is used at. That's one reason for the monomorphism restriction. However, when the range of types it can be needed at is restricted, it is possible to memoise the values at each type, and in some circumstances GHC does that (needs optimising, and I expect the number of types involved mustn't be too large). Here we confront it with what is basically an inhomogeneous list, so in each invocation of g (f x), it can be needed at an arbitrary type satisfying the constraints, so the computation cannot be lifted outside the map (technically, the compiler could still build a cache of the values at each used type, so it would be evaluated only once per type, but GHC doesn't, in all likelihood it wouldn't be worth the trouble).
Monomorphic expressions need only be evaluated once, they can be shared. Whether they are is up to the implementation; by purity, it doesn't change the semantics of the programme. If the expression is bound to a name, in practice you can rely on it being shared, since it's easy and obviously what the programmer wants. If it isn't bound to a name, it's a question of optimisation. With the bytecode generator or without optimisations, the expression will often be evaluated repeatedly, but with optimisations repeated evaluation would indicate a compiler bug.
Polymorphic expressions must be evaluated at least once for every type they're used at, but with optimisations, when GHC can see that it may be used multiple times at the same type, it will (usually) still be shared for that type during a larger computation.
Bottom line: Always compile with optimisations, help the compiler by binding expressions you want shared to a name, and give monomorphic type signatures where possible.
Your examples are indeed quite different.
In the first example, the argument to map is g (f x) and is passed once to map most likely as partially applied function.
Should g (f x), when applied to an argument within map evaluate its first argument, then this will be done only once and then the thunk (f x) will be updated with the result.
Hence, in your first example, f xwill be evaluated at most 1 time.
Your second example requires a deeper analysis before the compiler can arrive at the conclusion that (f x) is always constant in the lambda expression. Perhaps it will never optimize it at all, because it may have knowledge that trace is not quite kosher. So, this may evaluate 4 times when tracing, and 4 times or 1 time when not tracing.
This is really dependent on GHC's optimizations, as you've been able to tell.
The best thing to do is to study the GHC core that you get after optimizing the program. I would look at the generated Core and examine whether f x had its own let statement outside the map or not.
If you want to be sure, then you should factor f x out into its own variable assigned in a let, but there's not really a guaranteed way to figure it out other than reading through Core.
All that said, with the exception of things like trace that use unsafePerformIO, this will never change the semantics of your program: how it actually behaves.
In GHC without optimizations, the body of a function is evaluated every time the function is called. (A "call" means the function is applied to arguments and the result is evaluated.) In the following example, f x is inside a function, so it will execute each time the function is called.
(GHC may optimize this expression as discussed in the FAQ [1].)
let f x = trace "!" $ zip x x
x = "abc"
in map (\i -> lookup i (f x)) "abcd"
However, if we move f x out of the function, it will execute only once.
let f x = trace "!" $ zip x x
x = "abc"
in map ((\f_x i -> lookup i f_x) (f x)) "abcd"
This can be rewritten more readably as
let f x = trace "!" $ zip x x
x = "abc"
g f_x i = lookup i f_x
in map (g (f x)) "abcd"
The general rule is that, each time a function is applied to an argument, a new "copy" of the function body is created. Function application is the only thing that may cause an expression to re-execute. However, be warned that some functions and function calls do not look like functions syntactically.
[1] http://www.haskell.org/haskellwiki/GHC/FAQ#Subexpression_Elimination

Folding across Maybes in Haskell

In an attempt to learn Haskell, I have come across a situation in which I wish to do a fold over a list but my accumulator is a Maybe. The function I'm folding with however takes in the "extracted" value in the Maybe and if one fails they all fail. I have a solution I find kludgy, but knowing as little Haskell as I do, I believe there should be a better way. Say we have the following toy problem: we want to sum a list, but fours for some reason are bad, so if we attempt to sum in a four at any time we want to return Nothing. My current solution is as follows:
import Maybe
explodingFourSum :: [Int] -> Maybe Int
explodingFourSum numberList =
foldl explodingFourMonAdd (Just 0) numberList
where explodingFourMonAdd =
(\x y -> if isNothing x
then Nothing
else explodingFourAdd (fromJust x) y)
explodingFourAdd :: Int -> Int -> Maybe Int
explodingFourAdd _ 4 = Nothing
explodingFourAdd x y = Just(x + y)
So basically, is there a way to clean up, or eliminate, the lambda in the explodingFourMonAdd using some kind of Monad fold? Or somehow currying in the >>=
operator so that the fold behaves like a list of functions chained by >>=?
I think you can use foldM
explodingFourSum numberList = foldM explodingFourAdd 0 numberList
This lets you get rid of the extra lambda and that (Just 0) in the beggining.
BTW, check out hoogle to search around for functions you don't really remember the name for.
So basically, is there a way to clean up, or eliminate, the lambda in the explodingFourMonAdd using some kind of Monad fold?
Yapp. In Control.Monad there's the foldM function, which is exactly what you want here. So you can replace your call to foldl with foldM explodingFourAdd 0 numberList.
You can exploit the fact, that Maybe is a monad. The function sequence :: [m a] -> m [a] has the following effect, if m is Maybe: If all elements in the list are Just x for some x, the result is a list of all those justs. Otherwise, the result is Nothing.
So you first decide for all elements, whether it is a failure. For instance, take your example:
foursToNothing :: [Int] -> [Maybe Int]
foursToNothing = map go where
go 4 = Nothing
go x = Just x
Then you run sequence and fmap the fold:
explodingFourSum = fmap (foldl' (+) 0) . sequence . foursToNothing
Of course you have to adapt this to your specific case.
Here's another possibility not mentioned by other people. You can separately check for fours and do the sum:
import Control.Monad
explodingFourSum xs = guard (all (/=4) xs) >> return (sum xs)
That's the entire source. This solution is beautiful in a lot of ways: it reuses a lot of already-written code, and it nicely expresses the two important facts about the function (whereas the other solutions posted here mix those two facts up together).
Of course, there is at least one good reason not to use this implementation, as well. The other solutions mentioned here traverse the input list only once; this interacts nicely with the garbage collector, allowing only small portions of the list to be in memory at any given time. This solution, on the other hand, traverses xs twice, which will prevent the garbage collector from collecting the list during the first pass.
You can solve your toy example that way, too:
import Data.Traversable
explodingFour 4 = Nothing
explodingFour x = Just x
explodingFourSum = fmap sum . traverse explodingFour
Of course this works only because one value is enough to know when the calculation fails. If the failure condition depends on both values x and y in explodingFourSum, you need to use foldM.
BTW: A fancy way to write explodingFour would be
import Control.Monad
explodingFour x = mfilter (/=4) (Just x)
This trick works for explodingFourAdd as well, but is less readable:
explodingFourAdd x y = Just (x+) `ap` mfilter (/=4) (Just y)

Resources