14

Here's the code:

{-# LANGUAGE FlexibleContexts #-}

import Data.Int
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Generic as V

{-# NOINLINE f #-} -- Note the 'NO'
--f :: (Num r, V.Vector v r) => v r -> v r -> v r
--f :: (V.Vector v Int64) => v Int64 -> v Int64 -> v Int64
--f :: (U.Unbox r, Num r) => U.Vector r -> U.Vector r -> U.Vector r
f :: U.Vector Int64 -> U.Vector Int64 -> U.Vector Int64
f = V.zipWith (+) -- or U.zipWith, it doesn't make a difference

main = do
    let iters = 100
        dim = 221184
        y = U.replicate dim 0 :: U.Vector Int64
    let ans = iterate ((f y)) y !! iters
    putStr $ (show $ U.sum ans)

I compiled with ghc 7.6.2 and -O2, and it took 1.7 seconds to run.

I tried several different versions of f:

  1. f x = U.zipWith (+) x
  2. f x = (U.zipWith (+) x) . id
  3. f x y = U.zipWith (+) x y

Version 1 is the same as the original while versions 2 and 3 run in in under 0.09 seconds (and INLINING f doesn't change anything).

I also noticed that if I make f polymorphic (with any of the three signatures above), even with a "fast" definition (i.e. 2 or 3), it slows back down...to exactly 1.7 seconds. This makes me wonder if the original problem is perhaps due to (lack of) type inference, even though I'm explicitly giving the types for the Vector type and element type.

I'm also interested in adding integers modulo q:

newtype Zq q i = Zq {unZq :: i}

As when adding Int64s, if I write a function with every type specified,

h :: U.Vector (Zq Q17 Int64) -> U.Vector (Zq Q17 Int64) -> U.Vector (Zq Q17 Int64)

I get an order of magnitude better performance than if I leave any polymorphism

h :: (Modulus q) => U.Vector (Zq q Int64) -> U.Vector (Zq q Int64) -> U.Vector (Zq q Int64)

But I should at least be able to remove the specific phantom type! It should be compiled out, since I'm dealing with a newtype.

Here are my questions:

  1. Where is the slowdown coming from?
  2. What is going on in versions 2 and 3 of f that affect performance in any way? It seems like a bug to me that (what amounts to) coding style can affect performance like this. Are there other examples outside of Vector where partially applying a function or other stylistic choices affect performance?
  3. Why does polymorphism slow me down an order of magnitude independent of where the polymorphism is (i.e. in the vector type, in the Num type, both, or phantom type)? I know polymorphism makes code slower, but this is ridiculous. Is there a hack around it?

EDIT 1

I filed a issue with the Vector library page. I found a GHC issue relating to this problem.

EDIT2

I rewrote the question after gaining some insight from @kqr's answer. Below is the original for reference.

--------------ORIGINAL QUESTION--------------------

Here's the code:

{-# LANGUAGE FlexibleContexts #-}

import Control.DeepSeq
import Data.Int
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Generic as V

{-# NOINLINE f #-} -- Note the 'NO'
--f :: (Num r, V.Vector v r) => v r -> v r -> v r
--f :: (V.Vector v Int64) => v Int64 -> v Int64 -> v Int64
--f :: (U.Unbox r, Num r) => U.Vector r -> U.Vector r -> U.Vector r
f :: U.Vector Int64 -> U.Vector Int64 -> U.Vector Int64
f = V.zipWith (+)

main = do
    let iters = 100
        dim = 221184
        y = U.replicate dim 0 :: U.Vector Int64
    let ans = iterate ((f y)) y !! iters
    putStr $ (show $ U.sum ans)

I compiled with ghc 7.6.2 and -O2, and it took 1.7 seconds to run.

I tried several different versions of f:

  1. f x = U.zipWith (+) x
  2. f x = (U.zipWith (+) x) . U.force
  3. f x = (U.zipWith (+) x) . Control.DeepSeq.force)
  4. f x = (U.zipWith (+) x) . (\z -> z `seq` z)
  5. f x = (U.zipWith (+) x) . id
  6. f x y = U.zipWith (+) x y

Version 1 is the same as the original, version 2 runs in 0.111 seconds, and versions 3-6 run in in under 0.09 seconds (and INLINING f doesn't change anything).

So the order-of-magnitude slowdown appears to be due to laziness since force helped, but I'm not sure where the laziness is coming from. Unboxed types aren't allowed to be lazy, right?

I tried writing a strict version of iterate, thinking the vector itself must be lazy:

{-# INLINE iterate' #-}
iterate' :: (NFData a) => (a -> a) -> a -> [a]
iterate' f x =  x `seq` x : iterate' f (f x)

but with the point-free version of f, this didn't help at all.

I also noticed something else, which could be just a coincidence and red herring: If I make f polymorphic (with any of the three signatures above), even with a "fast" definition, it slows back down...to exactly 1.7 seconds. This makes me wonder if the original problem is perhaps due to (lack of) type inference, even though everything should be inferred nicely.

Here are my questions:

  1. Where is the slowdown coming from?
  2. Why does composing with force help, but using a strict iterate doesn't?
  3. Why is U.force worse than DeepSeq.force? I have no idea what U.force is supposed to do, but it sounds a lot like DeepSeq.force, and seems to have a similar effect.
  4. Why does polymorphism slow me down an order of magnitude independent of where the polymorphism is (i.e. in the vector type, in the Num type, or both)?
  5. Why are versions 5 and 6, neither of which should have any strictness implications at all, just as fast as a strict function?

As @kqr pointed out, the problem doesn't seem to be strictness. So something about the way I write the function is causing the generic zipWith to be used rather than the Unboxed-specific version. Is this just a fluke between GHC and the Vector library, or is there something more general that can be said here?

recursion.ninja
  • 5,377
  • 7
  • 46
  • 78
crockeea
  • 21,651
  • 10
  • 48
  • 101
  • 3 is a bit of a weird question isn't it? You can read about `Vector.force` [here](http://hackage.haskell.org/package/vector-0.10.9.1/docs/Data-Vector-Unboxed.html), it's not the same as `DeepSeq.force`. – ollanta Nov 06 '13 at 06:49
  • And yet it does *something* helpful here. What is it? – crockeea Nov 06 '13 at 06:54
  • Well, not really, `O2` is doing something when it's there, but it also does it with `id` there. What I'm trying to say is that question 3 is misleading, because `Vector.force` and `DeepSeq.force` are two unrelated functions, except for their name and type signature when applied to vectors. – ollanta Nov 06 '13 at 07:06
  • Most of the Vector magic sauce comes from rewrite rules, the behavior of which can be a bit difficult to predict. Use the debug flags mentioned [here](http://www.haskell.org/ghc/docs/7.2.2/html/users_guide/rewrite-rules.html) to see which are firing or not between versions. Try to use as many vector functions as possible, composed in as simple a way as possible (for instance, replace your `iterate`/`!!` with `V.iterateN` and see where that gets you). Re. Q4: perhaps related to a [SPECIALIZE](http://www.haskell.org/ghc/docs/7.2.2/html/users_guide/pragmas.html#specialize-pragma) pragma – jberryman Nov 06 '13 at 16:40
  • And why do you NOINLINE `f`? And finally why are you spinning your wheels like this without profiling your code first? – jberryman Nov 06 '13 at 16:42
  • @jberryman I NOINLINE f so that when I use the polymorphic functions, they stay polymorphic. Profiling reveals basically nothing about this code. In both the good and bad cases, all of the runtime is charged to "main.ans". – crockeea Nov 06 '13 at 16:52
  • @Eric by "stay polymorphic" you mean "so you can study the performance implications in isolation"? that's interesting & I'm sure you'll learn a lot if you can get to the bottom of it, but that's not of much practical use since you're actively subverting vector's rewrite rules. w/r/t profiling, you'll often need to add cost centers by hand [like this](http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/profiling.html#scc-pragma) or rearrange your code a bit to get the level of detail you want. Looking at core and what rules are firing is probably the most useful here though. Good luck! – jberryman Nov 06 '13 at 17:09
  • As I stated in the question, INLINING vs NOINLINING did not affect performance in the non-polymorphic signatures. Real code will have functions across multiple modules which cannot be inlined, so it is useful to know what will happen in this case. I tried adding cost centers, but even with the Vector profiling library, profiling didn't report any new insights. – crockeea Nov 06 '13 at 17:56
  • @jberryman Since Unboxed vectors aren't themselves Unboxed, I can't U.iterateN (U.zipWith (+)). – crockeea Nov 07 '13 at 04:17
  • I filed an issue with the Vector library, see link in the question. – crockeea Nov 07 '13 at 14:56
  • Added a link to a GHC issue, incidentally proposed by @jberryman – crockeea Nov 07 '13 at 19:34
  • 1
    Why do you say that functions across multiple modules can't be inlined? That's definitely false. One of the main features of the `INLINE` pragma is that it exports an unfolding in the interface file because that's required for inlining. Of course there are some situations where functions can't be inlined, but module boundaries are not a hindrance. – John L Nov 08 '13 at 02:25
  • @JohnL Interesting, you learn something new every day... – crockeea Nov 08 '13 at 04:35

1 Answers1

13

While I don't have the definitive answer you want, there are two things that might help you along.

The first thing is that x `seq` x is, both semantically and computationally, the same thing as just x. The wiki says about seq:

A common misconception regarding seq is that seq x "evaluates" x. Well, sort of. seq doesn't evaluate anything just by virtue of existing in the source file, all it does is introduce an artificial data dependency of one value on another: when the result of seq is evaluated, the first argument must also (sort of; see below) be evaluated.

As an example, suppose x :: Integer, then seq x b behaves essentially like if x == 0 then b else b – unconditionally equal to b, but forcing x along the way. In particular, the expression x `seq` x is completely redundant, and always has exactly the same effect as just writing x.

What the first paragraph says is that writing seq a b doesn't mean that a will magically get evaluated this instant, it means that a will get evaluated as soon as b needs to be evaluated. This might occur later in the program, or maybe never at all. When you view it in that light, it is obvious that seq x x is a redundancy, because all it says is, "evaluate x as soon as x needs to be evaluated." Which of course is what would happen anyway if you had just written x.

This has two implications for you:

  1. Your "strict" iterate' function isn't really any stricter than it would be without the seq. In fact, I have a hard time imagining how the iterate function could become any stricter than it already is. You can't make the tail of the list strict, because it is infinite. The main thing you can do is force the "accumulator", f x, but doing so doesn't give any significant performance increase on my system.[1]

    Scratch that. Your strict iterate' does exactly the same thing as my bang pattern version. See the comments.

  2. Writing (\z -> z `seq` z) does not give you a strict identity function, which I assume is what you were going for. In fact, the common identity function is as strict as you'll get – it will evaluate its result as soon as it is needed.

However, I peeked at the core GHC generates for

U.zipWith (+) y

and

U.zipWith (+) y . id

and there is only one big difference that my untrained eye can spot. The first one uses just a plain Data.Vector.Generic.zipWith (here's where your polymorphism coincidence might come into play – if GHC chooses a generic zipWith it will of course perform as if the code was polymorphic!) while the latter has exploded this single function call into almost 90 lines of state monad code and unpacked machine types.

The state monad code looks almost like the loops and destructive updates you would write in an imperative language, so I assume it's tailored pretty well to the machine it's running on. If I wasn't in such a hurry, I would take a longer look to see more exactly how it works and why GHC suddenly decided it needed a tight loop. I have attached the generated core as much for myself as anyone else who wants to take a look.[2]


[1]: Forcing the accumulator along the way: (This is what you already do, I misunderstood the code!)

{-# LANGUAGE BangPatterns #-}
iterate' f !x = x : iterate f (f x)

[2]: What core U.zipWith (+) y . id gets translated into.

kqr
  • 14,791
  • 3
  • 41
  • 72
  • I thought `f !x = blah` was sugar for `f x = x `seq` blah`. And why would GHC decide to use the Generic zipWith when I explicitly told it to use the Unboxed version?!? – crockeea Nov 06 '13 at 06:33
  • 1
    I also got suspicious at the seq, but then I looked it up and it's infixr 0, so it does *not* have just x as its second argument. – Ørjan Johansen Nov 06 '13 at 07:11
  • 1
    @Eric: nearly all the vector functions are defined in terms of `Data.Vector.Generic`, including both Unboxed and Storable. The difference is whether the function call remains a call to some `Data.Vector.Generic.function` or the call gets inlined (and turned into low-level array ops). – John L Nov 06 '13 at 08:18
  • @ØrjanJohansen You are correct. I was way too fast at assuming `(:)` is always lowest... – kqr Nov 06 '13 at 15:45
  • @jozefg I have a long way to go still, but I take any chance I can get! – kqr Nov 06 '13 at 15:48