Haskell FFT 11: Optimisation Part 1

10 Jan 2014data-analysishaskell

Based on what we saw concerning the performance of our FFT code in the last article, we have a number of avenues of optimisation to explore. Now that we’ve got reasonable looking $O(N \log N)$ scaling for all input sizes, we’re going to try to make the basic Danielson-Lanczos step part of the algorithm faster, since this will provide benefits for all input sizes. We can do this by looking at the performance for a single input length (we’ll use $N=256$). We’ll follow the usual approach of profiling to find parts of the code to concentrate on, modifying the code, then looking at benchmarks to see if we’ve made a positive difference.

Once we’ve got some way with this “normal” kind of optimisation, there are some algorithm-specific things we can do: we can include more hard-coded base transforms for one thing, but we can also try to determine empirically what the best decomposition of our input vector length is–for example, for $N=256$, we could decompose as $2 \times 2 \times 2 \times 2 \times 2 \times 2 \times 2 \times 2$, using length-2 base transforms and seven Danielson-Lanczos steps to form the final transform, or as $16 \times 16$, using a length-16 base transform and a single Danielson-Lanczos step to form the final result.

Basic optimisation

The first thing we need to do is set up some basic benchmarking code to run our $N=256$ test case, which we’re going to use to look at optimisations of the basic Danielson-Lanczos steps in our algorithm. The code to do this benchmarking is more or less identical to the earlier benchmarking code, but we’re also going to use this program:

module Main where

import Criterion.Main
import Data.Complex
import Data.Vector
import qualified Numeric.FFT as FFT

tstvec :: Int -> Vector (Complex Double)
tstvec sz = generate sz (\i -> let ii = fromIntegral i
                               in sin (2*pi*ii/1024) + sin (2*pi*ii/511))

main :: IO ()
main = run (nf (FFT.fftWith $ FFT.plan 256) $ tstvec 256) 1000

This does nothing but run the $N=256$ FFT calculation 1000 times–we use the run and nf functions from the Criterion package to make sure our test function really does get invoked 1000 times. This allows us to get memory usage information without any of the overhead associated with benchmarking. We’ll also use this code for profiling.

The first issue we want to look at is allocation. By running our benchmarking program as ./profile-256 +RTS -s, we can get a report on total memory allocation and garbage collection statistics:

 5,945,672,488 bytes allocated in the heap
 7,590,713,336 bytes copied during GC
     2,011,440 bytes maximum residency (2002 sample(s))
        97,272 bytes maximum slop
             6 MB total memory in use (0 MB lost due to fragmentation)

                                  Tot time (elapsed)  Avg pause  Max pause
Gen  0      9232 colls,     0 par    2.94s    2.95s     0.0003s    0.0010s
Gen  1      2002 colls,     0 par    1.98s    1.98s     0.0010s    0.0026s

INIT    time    0.00s  (  0.00s elapsed)
MUT     time    2.14s  (  2.14s elapsed)
GC      time    4.92s  (  4.92s elapsed)
EXIT    time    0.00s  (  0.00s elapsed)
Total   time    7.07s  (  7.07s elapsed)

%GC     time      69.7%  (69.7% elapsed)

Alloc rate    2,774,120,352 bytes per MUT second

Productivity  30.3% of total user, 30.3% of total elapsed

For 1000 $N=256$ FFTs, this seems like a lot of allocation. The ideal would be to allocate only the amount of space needed for the output vector. In this case, for a Vector (Complex Double) of length 256, this is 16,448 bytes, as reported by the recursiveSize function from the ghc-datasize package. So for 1000 samples, we’d hope to have only about 16,448,000 bytes of allocation–that’s actually pretty unrealistic since we’re almost certainly going to have to do some copying somewhere and there will be other overhead, but the numbers here give us a baseline to work from.

Profiling

To get some sort of idea where to focus our optimisation efforts, we need a bit more information, which we can obtain from building a profiling version of our library and test program. This can end up being a bit inconvenient because of the way that GHC and Cabal manage profiled libraries, since you need to have installed profiling versions of all the libraries in the transitive dependencies of your code in order to profile. The easiest way to deal with this issue is to use sandboxes. I use hsenv for this, but you could use the built-in sandboxes recently added to Cabal instead. Basically, you do something like this:

hsenv --name=profiling
source .hsenv_profiling/bin/activate
cabal install --only-dependencies -p --enable-executable-profiling

This will give you a hsenv sandbox with profiling versions of all dependent libraries installed.

To build our own library with profiling enabled, we add a ghc-prof-options line to the Cabal file, setting a couple of profiling options (prof-all and caf-all). Then, if we build our library with the -p option to Cabal, we’ll get a profiling version of the library built with the appropriate options as well as the “vanilla” library.

A second minor problem is that we really want to profile our library code, not just the code in the test program that we’re going to use. The simplest way to do this is to add the test program into our Cabal project. We add an Executable section for the test program and this then gets built when we build the library. This isn’t very pretty, but it saves some messing around.

Once we have all this set up, we can build a profiling version of the library and test program (in the sandbox with the profiling versions of the dependencies installed) by doing:

cabal install -p --enable-executable-profiling

and we can then run our profiling test program as:

./dist_profiling/build/profile-256/profile-256 +RTS -p

The result of this is a file called profile-256.prof that contains information about the amount of run time and memory allocation ascribed to different “cost centres” in our code (based on the profiling options we put in the Cabal file, there’s one cost centre for each top level function or constant definition, plus some others).

Aside from some header information, the contents of the profile file come in two parts–a kind of flat “Top Ten” of cost centres ordered by time spent in them, and a hierarchical call graph breakdown of runtime and allocation for each cost centre. For our profile-256 test program, the flat part of the profiling report looks like this:

COST CENTRE      MODULE              %time %alloc

dl.doone.mult    Numeric.FFT.Execute  26.2   23.8
dl.ds            Numeric.FFT.Execute  21.6   21.6
dl.d             Numeric.FFT.Execute  19.7   24.7
dl.doone.single  Numeric.FFT.Execute  14.0   13.9
dl.doone         Numeric.FFT.Execute   5.7    5.7
slicevecs        Numeric.FFT.Utils     2.7    3.3
dl               Numeric.FFT.Execute   2.1    1.9
special2.\       Numeric.FFT.Special   1.5    0.8
special2         Numeric.FFT.Special   1.4    2.4
slicevecs.\      Numeric.FFT.Utils     1.2    0.9
execute.multBase Numeric.FFT.Execute   1.1    0.6

and the first half or so of the hierarchical report like this:

                                                            individual    inherited
COST CENTRE             MODULE               no.  entries  %time %alloc  %time %alloc

MAIN                    MAIN                 235        0    0.3    0.0  100.0  100.0
 fftWith                Numeric.FFT          471        0    0.0    0.0   99.7  100.0
  execute               Numeric.FFT.Execute  473     1000    0.0    0.0   99.7  100.0
   execute.sign         Numeric.FFT.Execute  528     1000    0.0    0.0    0.0    0.0
   execute.bsize        Numeric.FFT.Execute  503     1000    0.0    0.0    0.0    0.0
    baseSize            Numeric.FFT.Types    504     1000    0.0    0.0    0.0    0.0
   execute.fullfft      Numeric.FFT.Execute  489     1000    0.4    0.1   99.7   99.9
    execute.recomb      Numeric.FFT.Execute  490        0    0.0    0.0   99.4   99.8
     dl                 Numeric.FFT.Execute  514     7000    2.1    1.9   93.5   95.3
      dl.ws             Numeric.FFT.Execute  527     7000    0.1    0.0    0.1    0.0
      dl.ns             Numeric.FFT.Execute  522     7000    0.0    0.0    0.0    0.0
      dl.doone          Numeric.FFT.Execute  516   127000    5.7    5.7   90.8   92.6
       dl.doone.vs      Numeric.FFT.Execute  523   127000    0.8    0.2    3.6    2.9
        slicevecs       Numeric.FFT.Utils    525   127000    1.9    2.3    2.8    2.7
         slicevecs.\    Numeric.FFT.Utils    526   254000    0.8    0.4    0.8    0.4
       dl.doone.single  Numeric.FFT.Execute  517   254000   14.0   13.9   81.5   84.0
        dl.doone.mult   Numeric.FFT.Execute  518   508000   26.2   23.8   67.5   70.1
         dl.d           Numeric.FFT.Execute  520   508000   19.7   24.7   41.3   46.3
          dl.ds         Numeric.FFT.Execute  521        0   21.6   21.6   21.6   21.6
         dl.ds          Numeric.FFT.Execute  519   508000    0.0    0.0    0.0    0.0
      slicevecs         Numeric.FFT.Utils    515     7000    0.4    0.6    0.5    0.8
       slicevecs.\      Numeric.FFT.Utils    524   127000    0.1    0.2    0.1    0.2
     execute.multBase   Numeric.FFT.Execute  502     1000    1.1    0.6    5.8    4.5
      applyBase         Numeric.FFT.Execute  512   128000    0.6    0.1    4.1    3.2
       special2         Numeric.FFT.Special  513   128000    1.4    2.4    3.5    3.1
        special2.b      Numeric.FFT.Special  536   128000    0.4    0.0    0.4    0.0
        special2.a      Numeric.FFT.Special  534   128000    0.3    0.0    0.3    0.0
        special2.\      Numeric.FFT.Special  533   256000    1.5    0.8    1.5    0.8
      slicevecs         Numeric.FFT.Utils    511     1000    0.4    0.5    0.6    0.7
       slicevecs.\      Numeric.FFT.Utils    535   128000    0.3    0.2    0.3    0.2
   execute.recomb       Numeric.FFT.Execute  488     1000    0.0    0.0    0.0    0.0
   execute.rescale      Numeric.FFT.Execute  476     1000    0.0    0.0    0.0    0.0
   execute.(...)        Numeric.FFT.Execute  475     1000    0.0    0.0    0.0    0.0
   execute.n            Numeric.FFT.Execute  474     1000    0.0    0.0    0.0    0.0

It’s clear from this that the vast majority of the allocation (89.7%) and time (87.2%) is spent in the Danielson-Lanczos step function dl in Numeric.FFT.Execute. Here’s the code for this function from version pre-release-1 of the repository:

-- | Single Danielson-Lanczos step: process all duplicates and
-- concatenate into a single vector.
dl :: WMap -> Int -> (Int, Int) -> VCD -> VCD
dl wmap sign (wfac, split) h = concatMap doone $ slicevecs wfac h
  where
    -- Size of each diagonal sub-matrix.
    ns = wfac `div` split

    -- Roots of unity for the size of diagonal matrix we need.
    ws = wmap IM.! (sign * wfac)

    -- Basic diagonal entries for a given column.
    ds c = map ((ws !) . (`mod` wfac) . (c *)) $ enumFromN 0 ns

    -- Twiddled diagonal entries in row r, column c (both
    -- zero-indexed), where each row and column if a wfac x wfac
    -- matrix.
    d r c = map ((ws ! ((ns * r * c) `mod` wfac)) *) (ds c)

    -- Process one duplicate by processing all rows and concatenating
    -- the results into a single vector.
    doone v = concatMap single $ enumFromN 0 split
      where vs :: VVCD
            vs = slicevecs ns v
            -- Multiply a single block by its appropriate diagonal
            -- elements.
            mult :: Int -> Int -> VCD
            mult r c = zipWith (*) (d r c) (vs!c)
            -- Multiply all blocks by the corresponding diagonal
            -- elements in a single row.
            single :: Int -> VCD
            single r = foldl1' (zipWith (+)) $ map (mult r) $ enumFromN 0 split

In particular, the mult, ds, d and single local functions defined within dl take most of the time, and are responsible for a most of the allocation. It’s pretty clear what’s happening here: although the vector package has rewrite rules to perform fusion to eliminate many intermediate vectors in chains of calls to vector transformation functions, we’re still ending up allocating a lot of temporary intermediate values. Starting from the top of the dl function:

So, what can we do about this? There’s no reason why we need to perform all this allocation. It seems as though it ought to be possible to either perform the Danielson-Lanczos steps in place on a single mutable vector or (more simply) to use two mutable vectors in a “ping-pong” fashion. We’ll start with the latter approach, since it means we don’t need to worry about the exact order in which the Danielson-Lanczos steps access input vector elements. If we do things this way, we should be able to get away with just two vector allocations, one for the initial permutation of the input vector elements, and one for the other “working” vector. Once we’ve finished the composition of the Danielson-Lanczos steps, we can freeze the final result as a return value (if we use unsafeFreeze, this is an $O(1)$ operation). Another thing we can do is to use unboxed vectors, which both reduces the amount of allocation needed and speeds up access to vector elements. Below, I’ll describe a little how mutable and unboxed vectors work, then I’ll show the changes to our FFT algorithm needed to exploit these things. The code changes I’m going to describe here are included in the pre-release-2 version of the arb-fft package on GitHub.

Mutable vectors

A “normal” Vector, as implemented by the Data.Vector class, is immutable. This means that you allocate it once, setting its values somehow, and thereafter it always has the same value. Calculations on immmutable vectors are done by functions with types that are something like ... -> Vector a -> Vector a that create new vectors from old, allocating new storage each time. This sounds like it would be horribly inefficient, but the vector package uses GHC rewrite rules to implement vector fusion. This is a mechanism that allows intermediate vectors generated by chains of calls to vector transformation functions to be elided and for very efficient code to be produced.

In our case, the pattern of access to the input vectors to the execute and dl functions is not simple, and it’s hard to see how we might structure things so that creation of intermediate vectors could be avoided. Instead, we can fall back on mutable vectors. A mutable vector, as defined in Data.Vector.Mutable, is a linear collection of elements providing a much reduced API compared to Data.Vector‘s immutable vectors: you can create and initialise mutable vectors, read and write individual values, and that’s about it. There are functions to convert between immutable and mutable vectors (thaw turns an immutable vector into a mutable vector, and freeze goes the other way).

Now, the bad news. As soon as we introduce mutability, our code is going to become less readable and harder to reason about. This is pretty much unavoidable, since we’re going to be explicitly controlling the order of evaluation to control the sequence of mutations we perform on our working vectors. The vector package provides a clean monadic interface for doing this, but it’s still going to be messier than pure functional code. This is something that often happens when we come to optimise Haskell code: in order to control allocation in the guts of an algorithm, we quite often need to switch over to writing mutating code that’s harder to understandNote that this is advice aimed at mortals. There are some people–I’m not one of them–who are skilled enough Haskell programmers that they can rewrite this sort of code to be more efficient without needing to drop into the kind of stateful computation using mutation that we’re going to use. For the moment, let’s mutate!. However, this is often less of a problem than you might think, because you almost never sit down to write that mutating code from nothing. It’s almost invariably a good idea to write pure code to start with, code that’s easier to understand and easier to reason about. Then you profile, figure out where in the code the slowdowns are, and attack those. You can use your pure code both as a template to guide the development of the mutating code, and as a comparison for testing the mutating code.

I worked this way for all of the changes I’m going to describe in this section: start from a known working code (tested using the QuickCheck tests I described above), make some changes, get the changes to compile, and retest. Writing code with mutation means that the compiler has fewer opportunities to protect you from yourself: the (slightly silly) Haskell adage that “if it compiles, it works” doesn’t apply so much here, so it’s important to test as you go.

Since we have to sequence modifications to mutable vectors explicitly, we need a monadic interface to control this sequencing. The vector package provides two options–you can either do everything in the IO monad, or you can use an ST monad instance. We’ll take the second option, since this allows us to write functions that still have pure interfaces–the ST monad encapsulates the mutation and doesn’t allow any of that impurity to escape into the surrounding code. If you use the IO monad, of course, all bets are off and you can do whatever you like, which makes things even harder to reason about.

Given these imports and type synonyms:

import Data.Vector
import qualified Data.Vector.Mutable as MV
import Data.Complex

type VCD = Vector (Complex Double)
type MVCD s = MV.MVector s (Complex Double)
type VVCD = Vector VCD
type VVVCD = Vector VVCD

a version of the dl function using mutable vectors will have a type signature something like

dl :: WMap -> Int -> (Int, Int, VVVCD, VVVCD) -> MVCD s -> MVCD s -> ST s ()
dl wmap sign (wfac, split, dmatp, dmatm) mhin mhout = ...

Here, the first two arguments are the collected powers of $\omega_N$ and the direction of the transform and the four-element tuple gives the sizing information for the Danielson-Lanczos step and the entries in the diagonal matrices in the “$I+D$” matrixI moved the calculation of these out into the FFT planning stage on the basis of profiling information I collected, after I’d switched over to using mutable vectors, that indicated that a lot of time was being spent recalculating these diagonal matrix entries on each call to dl.. The interesting types are those of mhin, mhout and the return type. Both mhin and mhout have type MVCD s, or MV.Vector s (Complex Double) showing them to be mutable vectors of complex values. The return type of dl is ST s (), showing that it is a monadic computation in the ST monad that doesn’t return a value. The type variable s that appears in both the types for mhin, mhout and the return type is a kind of tag that prevents internal state from leaking from instances of the ST monad. This type variable is never instantiated, but it serves to distinguish different invocations of runST (which is used to evaluate ST s a computations). This is the mechanism that allows the ST monad to cleanly encapsulate stateful computation while maintaining a pure interface.

When I made the changes need to use mutable vectors in the FFT algorithm, I started by just trying to rewrite the dl function to use mutable vectors. This allowed me to get some of the types right, to figure out that I needed to be able to slice up mutable vectors (the slicemvecs function) and to get some sort of feeling for how the execute driver function would need to interface with dl if everything was rewritten to use mutable vectors from the top. Once a mutable vector-based version of dl was working, I moved the allocation of vectors into execute function and set things up to bounce back and forth between just two vector buffers.

Here’s part of the new dl function to give an impression of what code using mutable vectors looks like (if you’re really interested in how this works, I’d recommend browsing through the pre-release-2 version of the code on GitHub, although what you’ll see there is a little different to the examples I’m showing here as it’s a bit further along in the optimisation process):

-- Multiply a single block by its appropriate diagonal
-- elements and accumulate the result.
mult :: VMVCD s -> MVCD s -> Int -> Bool -> Int -> ST s ()
mult vins vo r first c = do
  let vi = vins V.! c
      dvals = d r c
  forM_ (enumFromN 0 ns) $ \i -> do
    xi <- MV.read vi i
    xo <- if first then return 0 else MV.read vo i
    MV.write vo i (xo + xi * dvals ! i)

This code performs a single multiplication of blocks of the current input vector by the appropriate diagonal matrix elements in the Danielson-Lanczos $I+D$ matrix. The return type of this function is ST s (), i.e. a computation in the ST monad tagged by a type s with no return value. Take a look at lines 7-10 in this listing–these are the lines that do the actual computation. We loop over the number of entries we need to process (using the call to forM_ in line 7). Values are read from an input vector vi (line 8) and accumulated into the output vector vo (lines 9 and 10) using the read and write functions from Data.Vector.Mutable. This looks (apart from syntax) exactly like code you might write in C to perform a similar task!

We certainly wouldn’t want to write code like this all the time, but here, since we’re using it down in the depths of our algorithm and we have clean pure code that we’ve already written that we can test it against if we need to, it’s not such a problem.

Here is the most important part of the new execute function:

-- Apply Danielson-Lanczos steps and base transform to digit
-- reversal ordered input vector.
fullfft = runST $ do
  mhin <- thaw $ case perm of
        Nothing -> h
        Just p -> backpermute h p
  mhtmp <- MV.replicate n 0
  multBase mhin mhtmp
  mhr <- newSTRef (mhtmp, mhin)
  V.forM_ dlinfo $ \dlstep -> do
    (mh0, mh1) <- readSTRef mhr
    dl wmap sign dlstep mh0 mh1
    writeSTRef mhr (mh1, mh0)
  mhs <- readSTRef mhr
  unsafeFreeze $ fst mhs

-- Multiple base transform application for "bottom" of algorithm.
multBase :: MVCD s -> MVCD s -> ST s ()
multBase xmin xmout =
  V.zipWithM_ (applyBase wmap base sign)
              (slicemvecs bsize xmin) (slicemvecs bsize xmout)

These illustrate a couple more features of working with mutable vectors in the ST monad. First, in the multBase function (lines 18-21), which applies the “base transform” at the “bottom” of the FFT algorithm to subvectors of the permuted input vector, we see how we can use monadic versions of common list and vector manipulation functions (here zipWithM_, a monadic, void return value version of zipWith) to compose simpler functions. The code here splits each of the xmin and xmout mutable vectors into subvectors (using the slicemvecs function in Numeric.FFT.Utils), then uses a partial application of applyBase to zip the vectors of input and output subvectors together. The result is that applyBase is applied to each of the input and output subvector pairs in turn.

The calculation of fullfft (lines 3-15) demonstrates a couple more techniques:

We apply similar speedups to the Rader’s algorithm code for prime-length FFTs, although I won’t show that here since it’s not all that interesting. (We also fold the index permutation involved in the first step of Rader’s algorithm into the main input vector index permutation, since there’s little point in permuting the input then permuting it again!) In fact, a more important issue for speeding up Rader’s algorithm is to get transforms of lengths that are powers of two as fast as possible (recall that we pad the input to a power of two length to make the convolution in the Rader transform efficient). We’ll address this more directly in the next section.

Unboxing

Until now, all the vectors we’ve been dealing with have been boxed. This means that there’s an extra level of indirection in each element in the vector allowing values of composite data types to be stored. However, all of our vectors are just plain Vector (Complex Double), so we might hope to be able to get away without that extra level of indirection.

In fact, apart from one small issue, getting this to work is very easy: just replace imports of Data.Vector with Data.Vector.Unboxed (and the equivalent for mutable vectors). This simplicity is the result of some very clever stuff: Data.Vector.Unboxed is one of those pieces of the Haskell ecosystem that make you sit back and say “Wow!”. There’s some very smart type system stuff going on that allows the unboxed vector implementation to select an efficient specialised representation for every different element type. For our purposes, in particular, although Complex Double is a composite type (and so not, on the face of it, a good candidate for unboxing), Data.Vector.Unboxed has an instance of its Unbox type class for Complex a that leads to efficient memory layout and access of vectors of complex values. It’s really very neat, and is one of those things where the Haskell type system (and the implementor’s clever use of it!) allows you to write code at a high level while still maintaining an efficient low-level representation internally.

The “small issue” mentioned above is just that we sometimes want to have Vectors of Vectors, and a Vector is not itself unboxable (because you can’t tell how much memory it occupies in advance without knowing the length of the vector). This just means that you need to use the “normal” boxed vectors in this case, by importing Data.Vector qualified, as shown here (compare with the other listing of type synonyms above, which is without unboxing):

import Data.Vector.Unboxed
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed.Mutable as MV
import Data.Complex

type VCD = Vector (Complex Double)
type MVCD s = MV.MVector s (Complex Double)
type VVCD = V.Vector VCD
type VVVCD = V.Vector VVCD
type VMVCD a = V.Vector (MVCD a)
type VI = Vector Int

More hard-coded base transforms for prime lengths

Although they’re very tedious to write, the specialised transforms for small prime input lengths make a big difference to performance. I’ve converted “codelets” for all prime lengths up to 13 from the FFTW code.

The more I think about it, the more attractive is the idea of writing something comparable to FFTW’s genfft in order to generate these “straight line” transforms programmatically. There are a number of reasons for this:

  1. Copying the FFTW codelets by hand is not a very classy thing to do. It’s also very tedious involving boring editing (Emacs keyboard macros help, but it’s still dull).

  2. If we have a programmatic way of generating straight line codelets, we can use it for other input length sizes. Most of FFTW is implemented in C, which isn’t an ideal language for the kind of algebraic metaprogramming that’s needed for this task, so the FFTW folks wrote genfft in OCaml. In Haskell, we can do metaprogramming with Template Haskell, i.e. in Haskell itself, which is much nicer and means that, if we know our input length at compile time, we could provide a Template Haskell function to generate the optimum FFT decomposition with any necessary straight line code at the bottom generated automatically, allowing us to handle awkward prime input length factors efficiently (within reason, of course–if the straight line code gets too big, it won’t fit in the machine’s cache any more and a lot of the benefit of doing this would be lost).

  3. We’ve only been specialising the primitive transforms at the bottom of the FFT decomposition. Let’s call those specialised bits of straight line code “bottomlets”. It’s also possible to write specialised “twiddlets” to do the Danielson-Lanczos $I+D$ matrix multiplication–there are often algebraic optimisations that could be done here to make things quicker. If we had a Template Haskell genfft equivalent, we could extend it to generate these “twiddlets” as well as the “bottomlets”, giving us the capability to produce optimal code for all steps in the FFT decomposition.

This seems like it would be an interesting task, although probably quite a big piece of work. I’m going to leave it to one side for the moment, but will probably have a go at it at some point in the future.

Strictness/laziness

One topic we’ve not looked at which usually turns up in discussions of Haskell optimisation is strictness (or, if you prefer, laziness). We can tell just from thinking about the basic DFT algorithm that any FFT computation is strict in its input vector, and strict in all of the elements of that input vector. There shouldn’t be any laziness going on anywhere once we get into executing the FFT. (It matters less at the planning stage, since we’ll only do that once.)

To some extent, the behaviour of the Vector types helps us here. The data structures used to implement the various flavours of Vector are all strict in the arrays that are used to implement them, and since we’re now using unboxed vectors, the arrays inside the vectors are necessarily strict in their contents.

I’m actually going to sidestep this issue for a little while, since we’ll be coming back to this kind of question when we do a final “kicking the tyres” examination of the whole FFT code after we’ve done the empirical optimisation described in the next section.

Profiling and benchmarking check

Let’s see where we’ve got to in terms of performance. Here’s a view of the performance of the current optimised code (which is tagged pre-release-2 in the GitHub repository) in the same format as we’ve used previously:

Size FFT FFTW 8 5.007572446252795 0.8791249777589538 9 2.848346464806221 0.26211304761789656 10 2.318941285587859 0.275921030728833 11 0.5166611553175923 0.3138257236224645 12 5.322221410285708 0.3141506774669159 13 0.5888924282121375 0.3510386123549407 14 2.563849876613535 0.3777006394857711 15 3.0438069762633075 0.3816526948722123 16 9.392476663975932 0.41541233774600855 17 21.155691629486714 0.5541921443663212 18 6.660291168091356 0.475717090003201 19 69.64984625459664 0.5992282098758172 20 5.735583257462298 0.4875075175163472 21 3.476634118381854 0.5480598431411812 22 3.062660448813208 0.577231142491509 23 69.4821585206285 0.7666534556866154 24 10.021138029822978 0.5950064602800773 25 4.987665615828751 0.6291999565326564 26 3.3758259864973916 0.650288244927084 27 9.120353623515076 0.6753972970984096 28 6.360569742086915 0.6788467108220844 29 70.02336869518908 1.7255109335694967 30 7.38796655685355 0.7153962686285501 31 70.92432601466068 1.8518727804933244 32 17.56736270728564 0.717217976832759 33 4.1475860066875345 0.817646725900118 34 43.56262783843034 1.0278785504497494 35 5.647980092217851 0.8373959659570412 36 12.708588524972566 1.6897481467042625 37 135.14617595171174 2.157048561743323 38 140.64543293345537 1.1652593997710574 39 4.699784967096109 0.9358255431627627 40 10.98316492778914 1.8375676657472308 41 133.99785321738037 2.3787778403077753 42 8.245879439744938 0.9818458475635512 43 134.00309842612054 2.3382466818605097 44 7.487816777566775 1.0240262466845378 45 10.167156293810837 1.0351243551775837 46 141.47565940779356 1.4864354080079007 47 134.1392548193061 2.7745526816163717 48 18.876249303857072 1.9043248678956681 49 8.466387316951609 1.1412712608343452 50 11.249107652652619 1.1280293249408644 51 64.9399169797736 1.5164419431576106 52 8.103938607232914 1.195918598968394 53 135.0253772049669 2.9128354574952784 54 17.452912049330017 2.118901589087073 55 7.109444248691153 1.284627973451782 56 12.287259874077995 1.242910637404444 57 210.16785770299882 1.7004197261222642 58 142.79464396929 2.8270047690187154 59 128.6071103598392 3.4111302878175462 60 14.302251830796076 2.1522801901612922 61 128.43068061130407 3.420667030981609 62 143.11518450341538 2.950982430151529 63 11.580231768704168 1.4576101978555545 64 33.38998921762102 1.3428978791692916 65 7.922832198253197 1.4822704150090722 66 9.927279226975156 1.5272036559292157 67 269.0642636801512 4.00956092136247 68 88.31973275815955 1.9296214310041204 69 211.84552977127677 2.156026967851017 70 13.092977740436702 1.5443457416007287 71 268.6041158224852 4.486398079565597 72 24.357169586350548 2.493218758276526 73 269.1334050680907 5.025224068335129 74 273.16176020673333 3.5422605063234074 75 15.931497490439648 1.6474132840024291 76 283.1791552262646 2.1992644463557625 77 10.869750549119573 1.7786885550038518 78 10.907090811667087 1.754865563618682 79 269.1977780844481 4.929856636694504 80 21.0595020648147 2.700642922094887 81 25.291429546528622 1.8358364786356332 82 275.1191767411572 3.8927358176027043 83 269.93687567966293 5.394772865942552 84 16.157148127213016 2.7650159384523088 85 109.06770462613727 2.4105187315492764 86 274.6270807938916 4.131154396704269 87 216.54317050817465 3.752068855932783 88 14.93591089538986 1.9380788011170014 89 269.3122190024169 4.300545580636925 90 20.18132733269817 2.967671730688639 91 12.138709732590842 2.0705304654320535 92 285.6038721757274 2.790388624096958 93 215.9296400312866 4.083470680883956 94 267.77203498142075 4.638985970190597 95 354.0985177404116 2.7764444157611123 96 36.49260939858038 3.024892189673013 97 271.4556020285399 5.823926308325365 98 19.055833513592642 2.1706924186332626 99 14.315531191190221 2.277401440830796 100 22.401752640214575 3.070191719702311 101 270.2348989035399 6.56779227512224 102 130.85430425192627 2.8677027743904526 103 269.8367398764403 5.220844518843587 104 16.179720509408977 2.2562288873331227 105 18.97619463245332 2.3190693213852915 106 268.4491437460692 5.268411019018723 107 270.74749884860825 5.303928313707692 108 34.12642291791384 3.368214943579265 109 270.8476346518309 6.551102974585132 110 16.176002017481444 2.4390303217938967 111 403.44412741916466 4.894093849829269 112 23.998687395445106 3.477887489965984 113 270.0227063681395 5.246505530004047 114 427.98100450918787 3.310748808007613 115 362.841327036066 3.5560147181271238 116 290.52244746259265 4.77965293186052 117 15.885821619314692 2.6768902505754957 118 269.2502301718505 6.07188163059099 119 154.02845494183038 3.438418408174781 120 28.198138599676938 3.9261144186769243 121 20.658272070038983 2.8955864778687674 122 269.01657996433096 6.305531838110522 123 403.9734166647701 5.478219368628099 124 290.91440760663573 5.010918953589036 125 26.868205057075304 2.904834402785722 126 23.278188333919424 3.849820473364423 127 270.24920401828604 7.056550362280444 128 65.85682464161312 4.474477150610519 129 404.4645589377194 5.845383980444506 130 17.984780554949253 2.9115274683164323 131 530.7954114462641 8.382157662085133 132 19.90977786568624 4.004792549780439 133 498.98603100861806 3.955491676430136 134 545.0051587607172 7.650212624243336 135 29.490773549594813 3.971413948706221 136 176.90172595333073 4.653291084936692 137 526.6040128256586 8.23672232883318 138 431.4531737495034 4.229535273244939 139 527.7007382895258 6.720073036323162 140 26.11290808642526 4.011945107153487 141 405.4420751120358 6.357983925512866 142 545.8563130881098 7.764653542212087 143 23.499806649000433 3.4104094940928205 144 48.070571215434384 4.002408363989424 145 361.1402104741763 5.573586800268724 146 545.3246396567133 8.546666481665213 147 27.988050836924614 3.439149044330478 148 544.0729421164301 6.1648648764406 149 527.7150434042719 8.420304634741383 150 32.6235502482133 4.181222298315596 151 527.2882741476801 8.29155860202654 152 568.7957856981526 5.206422188452318 153 198.31852631605386 4.389369803999055 154 24.216443031024525 3.6226974480284895 155 360.1740191823672 6.002740242651537 156 22.421738526650827 4.557923653296066 157 528.9285939718989 6.9999109978110114 158 546.9816487814693 8.711175301245289 159 410.2533620383052 7.478551247290211 160 41.98175523607503 4.271821358374191 161 501.78585985586733 4.904873368594212 162 49.91805379305568 4.736737587622239 163 528.2443326498775 9.950951912573416 164 541.7936605002193 6.9659513022218515 165 23.951751659480802 3.6524842638340704 166 548.4073918844965 9.87704215305193 167 528.3158582236078 8.710141381895054 168 32.536025532990465 4.70812735813005 169 30.583663686577736 3.9929522632068037 170 221.58413399897856 4.7653225843969915 171 636.155285526599 5.037414153148122 172 552.1696370627193 7.230595925024585 173 529.0668767477778 8.974813581222579 174 434.93170081859523 6.539182045630054 175 31.654329284097702 4.0473246792971205 176 29.55071879234039 4.865483620337082 177 414.2444890524654 8.61819205539568 178 546.3212293173578 8.42462295895727 179 528.6949437643793 8.941270529190794 180 40.55092587002685 4.8392575766359105 181 530.003861763647 10.277585365942555 182 27.44521508114293 4.368563622374085 183 412.8306668783932 9.018735268286306 184 574.5543891120521 6.405667641333179 185 674.974278786352 7.483319618872242 186 437.7617293525309 7.051781990698413 187 250.63501917890133 5.612457911258127 188 551.2970250632076 8.174733498266773 189 34.77088158270195 5.456761696508958 190 710.4536673320196 5.535442890788748 191 530.2017491843013 10.034398415258961 192 71.54110343892043 4.93700919406755 193 530.0515454794673 10.27520118015154 194 548.1141370322017 10.458783486059742 195 26.939678800679893 4.387765751820426 196 38.50778428771132 5.5449765707765355 197 530.1588338400629 8.940446582630663 198 29.31031339174628 5.735711434057787 199 530.8168691183834 9.039114700265653 200 45.3035682873436 5.230264046362473 201 822.3193448569085 10.24182257907732 202 549.1584104086664 11.908368446997246 203 511.68897290314925 7.542924263647633 204 269.9426325517041 6.696538307837085 205 678.331212380102 8.498982765844898 206 549.5208066489008 12.041882851294119 207 650.4854342234985 6.4457248978018304 208 32.85356143531494 5.611733772924975 209 784.4441693808344 6.360656665527215 210 37.888864557524855 5.52113471286638 211 531.0028356100825 11.824921944311699 212 551.0180753256587 9.46934638278826 213 827.2665303732659 11.0929769064699 214 549.0606587912349 12.285069801977713 215 683.20925650852 9.049729683569508 216 69.18678439207494 5.72855887668474 217 509.56784227774216 8.208112099340992 218 550.5412381674556 11.820153572729666 219 822.240666725805 12.299374916723808 220 33.39952596078508 5.909756996801928 221 300.5574534780211 6.579027639019376 222 815.5864041830804 8.67779670017107 223 530.7501119162348 12.862042763403496 224 47.987583210016375 5.802468636206225 225 48.81675069246978 5.9359830405031 226 550.0238698508052 11.989430763891775 227 529.6748441244869 12.208775856665213 228 851.0535520102288 7.504777290991383 229 530.7548802878168 10.755879303861965 230 715.8082288290765 7.736043312719898 231 36.113523857808936 5.556013953150647 232 584.1412001777258 8.363084175757008 233 530.3829473044184 10.76132284310163 234 32.967666145342186 6.41043601291521 235 684.6493047262934 10.170297005346852 236 554.9639028097895 11.231259682348806 237 825.3544133688714 11.956052162817556 238 316.92846521202995 7.098368873999165 239 531.6394132162836 10.94512535088924 240 56.74814438181268 5.947903969458178 241 531.4248364950923 14.819459297827324 242 45.05385090121811 6.942109444311694 243 74.30661871027539 6.658391335180835 244 553.2520574118403 11.443452217749197 245 48.449565056752384 5.917062295704896 246 819.7706502463129 9.87704215305193 247 930.4993909384515 7.561014489495774 248 582.7241990892655 8.949593880346853 249 827.5526326681878 12.306421559836183 250 55.57284915892338 6.977872231176929 251 544.957475044897 12.437657692602714 252 47.653247002553144 6.484345772436695 253 790.0374692465571 8.260786243137863 254 551.966981270483 12.628392555883963 255 338.5667394048402 7.136254725275984 256 133.9713021758057 6.443814613989428 257 265.4593747641356 14.743165352514824 258 824.1909307028559 10.647134163549977 259 960.8429235007073 10.110692360571461 260 38.17705301501386 6.882504799536304 261 646.6501515890865 9.335831978491385 262 1070.8730977560783 15.837506630590996 263 1113.7312215353752 13.556709177967509 264 41.761869540795914 7.001714089087085 265 692.0760434653071 12.013272621801931 266 994.8867124106196 8.062480809517144 267 820.3142446066644 12.858033985307138 268 1084.7681325461176 13.748959877661308 269 1115.044907906225 13.410933246745412 270 60.258335356606906 7.168607094458179 271 1113.5547917868403 14.523820259741386 272 366.8318580037784 8.417920448950367 273 41.70407706428141 6.555238484580947 274 1070.7038205649164 14.88144812839373 275 41.269916831737454 6.543594202364736 276 850.8890431906489 9.199933388403494 277 1112.889603951147 13.438281898848711 278 1071.4095395590568 15.141324379614431 279 649.8497289206293 10.253743508032398 280 53.87676609506519 6.899194100073413 281 1116.1368649985102 13.489557153412289 282 824.229077675512 11.808232643774588 283 1115.3023999716547 13.816724513114734 284 1100.8923810507563 13.977841713598808 285 1053.394631722143 8.262890927551107 286 52.18165434808245 8.041219093969898 287 961.9158071066644 11.762933113745293 288 95.92198073700237 7.314042427710132 289 411.0854428793697 10.202976237738975 290 721.9665807272698 10.18221793430193 291 823.7474721457269 15.248612740210135 292 1084.055260994604 16.064004280737482 293 1114.3582623984125 16.29288611667498 294 58.436703879614264 7.798032143286306 295 695.7786839987544 13.565377571753103 296 1102.3300450827387 11.057214119604668 297 44.69494579017772 7.414842533366714 298 1076.280431130102 15.663461067846855 299 948.6978810812737 10.358647682837086 300 67.64232883215847 7.304505684546069 301 960.6140416647698 12.323216774633963 302 1074.1442006613518 15.386895516089043 303 822.5076955343989 17.494515755346857 304 1133.0192845846918 9.574250557592947 305 695.1683324362544 14.921979286840996 306 409.3875342536538 9.93664679782732 307 1115.4764455343989 18.35282264011248 308 50.97071950350483 8.203343727758961 309 823.0536740805414 17.422990181616388 310 721.1631101156976 11.011914589575367 311 1115.4454511191157 16.977744429583993 312 46.156345123609356 8.00784049289568 313 1118.7332433249262 17.167505470499897 314 1087.9033368613032 15.529946663549982 315 57.8432442644587 8.23195395725115 316 1087.1976178671623 15.50372061984881 317 1115.7625478293207 15.479878761938652 318 832.7143949057368 13.853864052465994 319 799.8007100607659 11.538819649389822 320 81.35918485976399 7.728890755346852 321 825.0444692160395 17.53027854221209 322 1002.897576668432 10.27248131503638 323 1231.9677632834223 11.683594198251258 324 105.00087971311237 8.286790230444508 325 48.09578856514707 7.920354514980184 326 1074.5423596884516 18.677071907690603 327 824.5485585715082 17.380074837378107 328 1096.715287544897 12.657002785376152 329 965.3061193014886 13.717965462378103 330 50.34720723543843 8.718327858618336 331 1117.321805336645 18.698529579809748 332 1087.5457089926508 17.60657248752459 333 1220.475987770727 12.709454872778496 334 1078.6813062216545 18.956021645239435 335 1353.0200284506598 17.25848136203631 336 66.04843788913321 8.246259071997242 337 1118.9239781882075 17.722495342699858 338 67.49890123430949 9.192780831030447 339 825.1660626913812 17.420605995825373 340 461.2920536526611 10.246590950659352 341 798.7588208700922 12.766675331762869 342 1263.8490956808835 10.964230873755056 343 71.1036697680515 8.366432382995864 344 1099.654988625219 13.44855246799334 345 1077.6203435446525 11.44822058933123 346 1072.1891683127192 19.44954810397967 347 1118.993119576147 18.681840279272638 348 868.2196897055413 12.051419594458181 349 1118.7713902975825 17.8035917193914 350 65.64325178812321 9.078339913061695 351 50.606034444911096 8.710575978655704 352 60.7733406711902 8.799390175512867 353 1118.428067543676 17.620816843788567 354 835.9974187399653 16.545609810522638 355 1354.3480199362552 17.380074837378107 356 1090.1158612753654 18.395737984350763 357 484.08328035757637 10.692962117766314 358 1074.342088082006 19.41140113132342 359 1118.6760228659416 17.74925189574807 360 83.49779951430504 9.056882240942556 361 1375.8867543722909 13.45337699379426 362 1078.1758588339592 19.79763922946795 363 68.72915317496609 9.948567726782398 364 58.400032831495274 9.488419869116385 365 1353.7138265158453 19.84532294528826 366 836.3669675375726 17.017678597143732 367 1119.7250646139887 20.38414893405778 368 1142.8635877157953 11.903600075415213 369 1238.2405560995844 14.514283516577324 370 1358.7301534201422 13.989762642553885 371 975.3435414816645 16.176061012915216 372 866.9679921652581 13.171986916235525 373 1119.7965901877192 19.38644786641983 374 518.3678720323811 12.311295845678885 375 84.1197541143213 9.55040869968279 376 1101.91042838352 15.456036904028498 377 953.0680936362054 13.553456642798027 378 71.51759091232505 9.824590065649586 379 1133.8942807699946 18.977479317358576 380 1410.6219571615977 11.67710242526873 381 829.3526929404046 18.19069800632342 382 1075.052575447729 18.882111885717947 383 1140.4150289084223 18.01647620134745 384 146.94074305986604 9.044961311987478 385 63.93059870494262 9.560106893211536 386 1079.782800057104 19.409016945532404 387 1230.735139229467 15.39404807346209 388 1092.9411214377192 19.480542519262873 389 1121.8398374106196 20.40799079196794 390 57.26432060556753 9.93664679782732 391 1253.5684865500239 15.221428922402168 392 79.21580183364098 9.905652382544117 393 1615.0110524679956 21.862344124487457 394 1076.4807027365473 19.3327230002199 395 1356.8490308310306 19.075230934790216 396 61.27759596598995 10.430173256567555 397 1125.9024899985102 19.426903336429284 398 1076.7715734030512 19.473389961889826 399 1486.4986699606702 12.315300540275565 400 93.1771707093837 9.390668251684742 401 1121.2771695639399 23.118810036352684 402 1630.3675931479272 19.456700661352716 403 953.4543317343499 14.986352303198416 404 1092.4523633505607 22.768334725073387 405 90.61417098404193 10.430173256567555 406 1015.1928227926994 14.46183142917498 407 1505.047635414772 15.804128029516777 408 541.8060078152588 12.707070686987478 409 1129.7910970236567 22.413091042212063 410 1354.111985542945 15.928105690649593 411 1632.8137677695092 21.82896552341324 412 1101.1093419577387 23.593263008764787 413 971.9961446310786 18.925027229956232 414 1269.9740689780026 13.86816916721209 415 1349.3459981467047 21.93625388400894 416 67.10601251264264 10.518388130835133 417 1630.930260994607 21.93625388400894 418 1560.4918759848406 13.882474281958183 419 1122.6170819784907 21.040553868489166 420 80.33763345197904 10.513619759253103 421 1124.4338315512446 22.150053796643498 422 1088.4230893637446 22.58952079074722 423 1220.03729758518 17.685250618628107 424 1112.0432179953364 18.11917243259295 425 569.471305005607 13.484315254858574 426 1636.6093915488061 20.491437294653483 427 974.0274709250239 19.895390846899588 428 1103.3528607870844 23.357228615454243 429 78.09769090131985 11.782006600073418 430 1357.6954167868412 16.781644203833185 431 1123.580293038061 21.88396163246766 432 142.05051309296064 10.544614174536305 433 1124.6197980429438 24.43249640720228 434 1017.4935620810297 15.649155953100763 435 1082.9513829733637 14.86475882785662 436 1106.480912544897 22.243813851049953 437 1385.7930463339608 17.413453438452326 438 1628.2647412802514 22.951917030981587 439 1123.129681923559 23.1349803732483 440 70.1049608311483 10.935620644262867 441 87.36742083363383 11.545972206762869 442 603.560761788061 14.244870522192556 443 1124.0022939230705 23.466382198199472 444 1635.9847348715602 16.428784706762873 445 1363.5462087179935 22.711114266089012 446 1089.088277199438 24.12493644016127 447 1630.8325093771753 23.044900276831196 448 98.74008834198281 10.606603005102713 449 1123.3299535300043 23.379313567100652 450 100.88299348772988 11.071519234350758 451 1500.1982015158462 18.138245918921076 452 1150.3237050558832 22.503690102270657 453 1637.2721951987085 22.651509621313625 454 1115.9342092062736 23.226098396948384 455 72.6968725626709 11.71035618654319 456 1756.383733132059 14.333085396460135 457 1161.1431401755121 24.079636910131974 458 1117.6245969321037 24.198846199682755 459 621.0288187755001 14.936284401587088 460 1461.0260289694593 14.800385811499197 461 1190.3446477438715 23.263813466543247 462 76.35276492552028 11.967973091772636 463 1133.660630562475 22.556904655180855 464 1159.6387189413813 15.720681526831228 465 1083.5688870932365 16.850785591772638 466 1089.6032613302973 23.717240669897603 467 1125.8142751242426 23.531271904867616 468 68.93631242925214 11.786774971655447 469 1892.2322553183387 23.4883588339601 470 1380.5526059653084 19.113377907446466 471 1637.813405373269 22.975758888891747 472 1113.962487557104 21.13039908664567 473 1508.6835187460708 19.4853108908449 474 1662.7043050314724 23.145036080053853 475 1791.1618512656041 15.475110390356619 476 650.3027242209223 15.377358772924978 477 1267.279939034155 21.30206046359879 478 1137.2726720358635 23.79830298679213 479 1135.9089177634028 23.52875276516391 480 115.25798531902302 11.72478614108904 481 1853.9446157004188 18.78436026828631 482 1099.645451882055 28.764561989477645 483 1605.5291455771262 17.518409517355806 484 103.96514966906534 14.47852072971209 485 1480.1805776144788 26.645020821264765 486 166.08736864956364 13.470010140112478 487 1256.191090920141 29.677705147436622 488 1154.915646889379 22.656277992895657 489 1636.6332334067163 27.61061606662609 490 100.14620776196102 12.919263222387869 491 1127.2996228720451 26.521046873853077 492 1641.4039891745385 18.896417000464044 493 1279.1484159018307 20.276860573462084 494 1850.2729695822547 16.295270302465998 495 78.35008957404266 13.222054817846853 496 1159.896211006811 17.06297812717303 497 1892.3896115805458 23.8245290304933 498 1632.000760414773 27.808503487280387 499 1148.9647191550043 25.81635595590872 500 119.90454668154965 13.214902260473806 501 1783.4466260458776 31.129674294165135 502 1191.8276113058832 26.954964974096796 503 1223.3370107199457 26.928738930395625 504 102.97964523945538 13.05993018405779 505 1457.0921224142835 31.26557288425302 506 1570.5674451376728 17.554120400122248 507 101.82196532509147 13.37225852268084 508 1122.3238271261955 24.19169364230971 509 1176.0681432272697 24.440649992862006 510 686.5351956869869 15.589551308325369 511 1911.0792439963175 28.313950874975692 512 278.93816554120605 12.282685616186699 513 1895.276860573466 16.416863777807794 514 576.1354726340082 28.397397377661243 515 1376.532868721656 28.483228066137805 516 1632.3703092123803 21.583394386938632 517 1556.1145108725361 21.826581337622223 518 1924.554662087138 20.2792447592531 519 1634.1989797140893 28.36640296237804 520 82.57766274469242 13.86101660983904 521 2712.079839089092 30.73151526706553 522 1384.5794957663338 18.7676709677492 523 2643.8086789633594 28.854052139470326 524 2181.040601113018 28.88138709323741 525 101.33554967386384 13.079003670385916 526 2318.0764478232236 28.414086678198352 527 1262.4448102499748 22.010163643530426 528 85.36350436863442 13.048009255102714 529 1688.7443822409452 22.96622214572768 530 1372.010068276099 22.730187752417137 531 1238.9510434653068 24.272755959204236 532 2004.188851692851 17.613725044897638 533 1797.3511975790807 21.673993446997223 534 1636.893109657937 26.437596657446406 535 1379.6346944357674 28.797940590551864 536 2170.812444069561 25.669888832739385 537 1632.8185361410913 28.516606667212024 538 2337.5647824789853 28.609589913061633 539 94.9255744752648 13.513767633885383 540 124.71454900290287 14.917210915258963 541 2560.891465523419 31.065301277807716 542 2323.1094640280576 28.54044852512218 543 1638.4499829794702 28.368787148169055 544 713.2738393332269 16.72442374484881 545 1383.5161489035409 27.30544028537609 546 87.24906303900842 13.996915199926931 547 2541.0002034689755 32.04758115448898 548 2169.6561139609184 28.216199257544055 549 1237.9377645041252 25.445775368383917 550 90.7633528949655 13.80141196506365 551 1419.4172185446544 22.804097511938622 552 1693.9991277243437 18.033341744116388 553 1898.3619969870401 27.238683083227656 554 2335.2640431906552 28.91953406589366 555 2042.438344338115 20.496205666235518 556 2223.853425362285 29.918507912329204 557 2543.234185555157 30.50122213020974 558 1292.3925679709228 21.490411141089023 559 1842.8939145590614 22.60621009128433 560 111.87417544908337 13.620213844946464 561 760.9289449240472 18.021420815161306 562 2308.556393959698 28.945760109594833 563 2553.0308049704404 30.409498914544074 564 1662.4372762228786 22.789792397192528 565 1381.3203137900155 27.927712776831164 566 2307.5741094137993 29.11026892917491 567 106.65292178413692 14.681176521948416 568 2168.263749458965 26.56634269016125 569 2544.5478719260063 30.81257758396006 570 2111.951665260967 17.718629219702326 571 2590.1454251791797 28.938948071631422 572 110.60093477190951 15.734986641577326 573 1632.3560040976342 27.620152809790156 574 1928.0498784567667 22.44646964328628 575 1785.6877606894323 18.889264443090994 576 194.61282040087545 14.201955177954275 577 2563.063458779034 31.430081703833107 578 820.4763692404534 21.600083687475742 579 1633.3597463156518 28.27341971652843 580 1438.1855290915294 19.29696021335467 581 1902.2196095969034 30.55508551853037 582 1636.7071431662378 29.248551705053817 583 1546.012715676003 26.335076668432734 584 2173.6400884177056 30.69098410861826 585 87.45631690384174 15.849427559546074 586 2523.0830472494936 35.45220313327645 587 2756.2468808676554 30.913038953606563 588 124.6432618477515 16.14029822604998 589 1554.5194905783467 26.07758460300305 590 1495.2319425131607 28.08983741062023 591 1721.0953992392365 31.134442665747166 592 2213.9089864279595 21.435574867895664 593 2551.0924619223447 30.65536807424255 594 94.19234564507397 15.284375527075369 595 790.6883519675043 18.43865332858904 596 2179.5743268515434 30.083016731909282 597 1651.9707006003202 30.199841835669044 598 1970.903233864482 20.38414893405778 599 2543.8636106039853 32.169206842247924 600 142.106938823348 14.426068642309744 601 2544.86020026463 36.81118903415535 602 1916.7035382773233 24.24891410129408 603 2518.7557500388 30.669526436499115 604 2179.838971474346 29.76115165012217 605 127.3269013741186 16.95330558078631 606 1774.839715340311 34.73694739597176 607 2570.8764356161923 35.49042645461703 608 2356.2162679221005 18.421964028051935 609 1525.294141152077 21.557168343237464 610 1386.6084378744881 27.808503487280387 611 1810.380772926981 25.677041390112432 612 805.0649922873284 18.72475562351092 613 2538.196400978741 37.27372107761238 614 2311.8990224387016 36.060170509985426 615 2043.3419507529097 23.595647194555806 616 105.85302745125121 15.49179969089373 617 2537.2165006186333 36.15447575492522 618 1666.8504041220488 33.71890006320809 619 2541.243390419659 39.038265626212294 620 1480.640725472145 21.28060279147965 621 1899.5087903525186 21.64538321750504 622 2313.0672734762998 36.21514258640144 623 1912.3309415366007 33.50432334201669 624 98.45838762082896 15.336827614477713 625 148.40198404022624 17.11066184299334 626 2321.7647832419243 36.25567374484871 627 2345.0368207480283 20.603494026831218 628 2205.6859296347466 30.18315253513194 629 2337.4121945883603 27.460412361792105 630 129.48816579367434 15.429810860327322 631 2539.69605384129 31.942681648901463 632 2164.737538674053 30.309514382055767 633 1633.3406728293237 33.74989447849129 634 2327.219800331768 30.574159004858497 635 1381.587342598609 29.682473519018654 636 1653.1461041952907 26.978806832006956 637 109.66136688810013 16.246868803032807 638 1607.4269574667749 23.79115042941908 639 2466.885403969464 30.676678993872162 640 185.20704857738974 15.799359657934748 641 2720.0430196310836 35.840825417211995 642 1681.3462537314238 34.05745444553231 643 2572.9959767844052 37.855606878898556 644 2090.0505345846973 21.175698616674968 645 2074.467496254619 25.028542854956182 646 2468.3039945151186 24.53024802463392 647 2548.145608284649 35.022444843637736 648 207.59055286291093 16.044930794409357 649 1537.6704495932393 30.133084633520607 650 101.51599481524453 16.078309395483576 651 1525.6970685507588 23.431138374975728 652 2206.7778867270317 35.33537802951668 653 2574.0903180624814 37.0329183127198 654 1657.3565763022243 36.07447562473152 655 2718.633965828594 36.61330161350105 656 2169.7014134909477 24.747208931616342 657 2482.4660581137514 35.64293799655769 658 1931.8526547934366 27.30544028537609 659 2540.6902593161435 36.15693006382772 660 107.17068746508582 16.514615395239435 661 2552.7303975607724 36.32319196119529 662 2314.8649495627255 36.88986716525886 663 902.8142255331782 21.273450234106605 664 2186.3263410116997 35.595254280737386 665 2524.2703717734194 20.908669808081218 666 2452.081994393048 25.20258841770032 667 1747.4883359457797 29.482201912573345 668 2221.8411725546684 35.63816962497567 669 1639.6873754050073 36.517934181860426 670 2693.9290326620894 32.221631386450284 671 1533.219174721413 32.61740622775888 672 139.02021295257978 16.621903755835138 673 2539.6388333823056 38.20330675739745 674 2329.5181554343076 37.01622901218269 675 153.01905028255914 16.829327919653494 676 142.26191089976405 17.632798531225763 677 2544.786290505108 37.204579689672926 678 1703.4142774130644 33.26352057712411 679 1919.1973966147257 34.87761435764168 680 901.5696805502679 20.613030769995284 681 1651.7942708517849 34.1480535055909 682 1603.7600797201928 25.083379128149538 683 2585.9468740012016 36.354326622701485 684 2542.2423642660947 22.243813851049953 685 2783.1238072897745 35.476044991186605 686 150.32231324012324 17.23702368991717 687 1637.3294156576928 34.43415580051278 688 2170.037583687481 26.497201302221796 689 1864.3706601645301 31.580285408667084 690 2129.8878949667774 22.358254769018703 691 2540.2968686606255 36.902338739077535 692 2212.2185987021294 36.10308585422371 693 116.56278517919708 18.09294638889178 694 2324.330167153057 36.67767462985847 695 2698.5400479819136 35.54518637912605 696 1745.9862988974396 23.826913216284318 697 2397.8703778769345 32.71515784519052 698 2368.1395810629692 36.74920020358894 699 1737.1648114706818 34.663037636450284 700 140.43165094086103 17.222718575171076 701 2547.8761952902646 36.70047498046061 702 107.14871921129041 17.766312935522638 703 2638.196305611309 31.22504172580576 704 124.44775861288822 17.506436684301935 705 2057.9212468649707 28.487996437719836 706 2313.9875691916313 37.51929221408698 707 1923.7201970602825 39.23352179782721 708 1663.9512342001738 31.678037026098725 709 2545.337037422833 36.681545990241055 710 2701.5107434775196 33.38272986667489 711 2426.242188790021 34.57959113376473 712 2177.368954994854 35.154179909399495 713 1739.2199796225373 31.072453835180763 714 953.1276982809808 23.564652779272603 715 140.2387968013211 18.965558388403498 716 2213.1102841879692 37.35001502292488 717 1638.9935773398217 34.99205527561043 718 2319.2041677023735 37.20934806125496 719 2528.7764829184384 37.58219023481076 720 170.27429692181096 17.079667427710138 721 1937.9585546042279 39.00940833347175 722 2746.6243070151168 27.851418831518668 723 1641.6590970541772 42.37349448459479 724 2235.5883878256645 37.6885694052491 725 1811.0435765768834 25.233582832983526 726 144.0730973723389 19.192056038549982 727 2528.9791387106748 46.51005683200689 728 120.83261769797117 17.980889656714044 729 240.32979478083894 19.79525504367693 730 2710.3679936911426 37.84830985324714 731 2353.5984319235654 33.64022193210458 732 1661.9056027914824 34.66780600803231 733 2562.9561704184384 40.237264015844794 734 2325.0025075461235 40.49237189548346 735 152.40184418590997 18.35282264011248 736 2304.4222157980766 23.407296517065568 737 2989.3868726279084 37.44299826877449 738 2442.161397316632 30.085400917700294 739 2527.582005837139 39.79634713673376 740 2715.9016889120894 26.90012870090344 741 2782.7971738364054 24.334744789770642 742 1938.0253118063763 32.417134621313565 743 2543.7515538718076 39.629377222143596 744 1735.712842323953 26.220635750463988 745 2702.557401039775 38.12487540500495 746 2325.6414693381157 40.65688071506354 747 2427.019433357892 39.27882132785651 748 1010.4554456259515 25.209740975073366 749 1944.7749417807413 40.18719611423346 750 173.4981304376709 18.007115700415216 751 2552.437142708477 41.04073462741706 752 2182.0205014731255 30.05679068820811 753 1645.6478398825466 38.787679054907294 754 1904.875592568095 27.181462624243277 755 2708.808736183818 36.8040364767823 756 150.61503827335338 18.59839377658709 757 2533.9358609701962 38.98611156203383 758 2314.9460118796196 37.199811318090894 759 2371.9375890280576 26.087121346167116 760 2823.3402532126256 23.36199698703627 761 2538.6756223227353 39.29143811357187 762 1661.6624158407985 35.49273429172371 763 1941.3226407553507 38.5587972189698 764 2212.1995252158013 36.66098532932136 765 1014.0221875693109 23.722009041479634 766 2320.758656838116 37.254647591284254 767 1829.294518807108 35.619096138647535 768 306.4088414556212 18.16685614841326 769 2530.993775704083 41.152791359594794 770 133.83072179343017 19.375638344458185 771 856.7732137228753 42.55230841892096 772 2217.418507912334 37.4906819845948 773 2530.977086403546 39.51055247868811 774 2444.326238014874 30.91986594455576 775 1808.54733405369 27.503327706030387 776 2183.610753395733 38.32753119724128 777 2858.4283154990026 31.663731911352627 778 2319.788293221173 40.34216819064948 779 2637.945966103252 35.52611289279793 780 119.92519658591064 19.327954628637873 781 3005.9188169028107 37.84830985324714 782 2494.8685925986147 31.029538490942482 783 1953.071908333476 27.78943000095226 784 166.02269760998234 19.0728467489992 785 2736.0957425619918 37.86976752536628 786 3257.223920204811 42.92900977390142 787 2573.863820412335 41.46367166368733 788 2217.499570229229 38.563565590551825 789 3455.5810254599373 42.251901009253 790 2712.261037209209 38.64462790744635 791 1954.2449277426556 39.21921668308112 792 127.4806813576392 19.563989021948416 793 1831.5261167074987 37.40008292453621 794 2321.2807935263486 40.351704933813544 795 2071.6517728354297 35.290078499487386 796 2212.6978200461235 38.217858650854566 797 2527.8847974325986 41.23534613776774 798 2968.0627149130646 25.195435860327272 799 2377.6095670248837 37.903146126440504 800 192.05322665523508 18.719987251928888 801 2437.2905057455873 40.54959235446784 802 2325.224236824688 45.91401038425299 803 3033.186749794656 41.903809883764715 804 3248.3094495322034 39.11431250827643 805 2503.7282269980287 26.58303199069836 806 1910.9028142477823 29.432134010962017 807 3436.848477699927 42.69297538059087 808 2184.1448110129204 44.161633827856505 809 2536.80880484837 47.14186606662604 810 189.90030688594808 20.064668038061694 811 2592.2148984457817 45.05808768527838 812 2026.6478818442185 28.466538765600692 813 3444.8593419577396 42.559460976294005 814 3007.02031073826 31.937913277319428 815 2741.9608396078906 44.14494452731939 816 1069.9027341391352 24.587468483618295 817 2643.2603162314263 37.98182425754401 818 2326.3042729880185 44.47634635227057 819 134.43303949066575 21.247224190405433 820 2722.1649449850875 31.05814872043467 821 2545.859174111065 44.82558318783366 822 3246.6119092490003 42.00632987277839 823 2609.3571942831836 44.48394534767284 824 2241.2532132651177 43.95182547824712 825 141.13816466359867 22.30103431003433 826 1953.067139961894 38.04619727390144 827 2550.381974556622 44.59343413433069 828 2571.6274541403623 26.79522452609875 829 2560.1261418845024 44.560408745966264 830 2711.1786168600875 42.17322287814948 831 3441.6001599814213 42.72873816745611 832 138.69543386593705 20.348386147192553 833 1142.9661077048088 26.27801541354715 834 3268.5797971274187 42.20183310764167 835 2747.4230092551074 47.32306418674322 836 3148.545579292946 27.18623099582531 837 1948.830441811259 30.57654319064951 838 2352.334813454327 44.504956581762755 839 2543.5798924948544 43.95067530570838 840 169.37992922695622 20.379380562475752 841 2250.880555489239 37.707642891577215 842 2328.545407631573 44.38336310642095 843 3446.3828366781986 43.2604115988526 844 2211.4437383200493 44.34044776218268 845 175.04151282565945 22.193745949438625 846 2463.063554146466 35.030202248266676 847 171.2387364889896 22.68727240817886 848 2207.938985207256 35.82175193088386 849 3443.3263104941166 43.02676139133306 850 1126.7035764242912 25.66750464694837 851 3234.528855660133 39.250211098364325 852 3257.4480336691663 39.79142127292487 853 2547.456578591046 46.194547347763866 854 1946.1386960532022 39.82241568820807 855 3178.5553258444597 26.73561988132336 856 2204.2458814169727 44.907883980444396 857 2543.7753957297177 45.86605952766838 858 165.97739807995302 22.470311501196438 859 2554.373101570782 45.804688819344086 860 2734.603242256816 33.28259406345224 861 2877.4779599692174 34.21957907932137 862 2343.012647011456 45.15822348850103 863 2545.5802243735166 45.8216430294135 864 293.38343843285503 20.460442879370284 865 2744.7002690817676 45.949773171118224 866 2324.578122475323 47.86904273288579 867 1216.2249845053461 32.574490883520596 868 2059.9406522299605 31.103448250463966 869 3007.5805943991486 42.33057914035651 870 2169.0910619284477 30.249909737280376 871 3543.7434476401127 44.21885428684087 872 2204.0336888815727 43.22703299777837 873 2440.175370552716 43.78254828708502 874 2773.846940376933 34.88476691501473 875 168.96422324436065 22.923306801489403 876 3260.769204476051 44.729070046118224 877 2543.556050636944 48.236207344702194 878 2322.3679822470517 48.42455802219243 879 3450.581387856177 46.93444190280766 880 155.8287227792399 21.414117195776523 881 2551.924542763409 47.521658286779804 882 185.50080290558384 22.215203621557766 883 2547.196702339825 47.329181133882045 884 1208.4120076681877 28.020696022680774 885 2083.274678566631 39.7651952292237 886 2338.764027931866 48.579530098608444 887 2545.484856941876 48.37125372346287 888 3248.681382515602 34.00261817233895 889 1954.0518086935836 40.76893744724128 890 2715.870694496806 44.06388221042486 891 138.85252521861167 22.980527260473778 892 2222.7519315268364 48.02401480930181 893 2689.461068489726 42.75496421115729 894 3261.958913185768 43.7038701559815 895 2747.699574806865 46.77231726901861 896 204.77363735082602 21.309213020971836 897 2819.1726964499303 30.80304084079599 898 2321.16635260838 48.74165473239751 899 2238.9548581625786 40.988282540014715 900 210.14918158096918 21.96486411350113 901 2405.797795632062 44.92218909519049 902 3019.0461438681423 36.577538826635816 903 2865.2828496481725 36.19845328586433 904 2211.6201680685845 43.906525948217826 905 2735.2565091635543 46.96782050388188 906 3250.4289907004163 43.80639014499518 907 2543.842152931866 56.48549018161625 908 2221.4477818991504 46.31932196872564 909 2443.5132306601377 51.764802315405326 910 153.552213830075 22.81125006931167 911 2540.5305188681455 56.10939933398328 912 3388.578252175025 27.70598349826672 913 3010.0291532065216 48.93477378146977 914 2321.502522804913 47.14901862399907 915 2078.8663190390425 41.70115409152839 916 2222.1678060080376 48.17183432834478 917 3807.226971962621 50.61800894992681 918 1207.4130338217524 28.92191825168468 919 2547.0512670065727 56.18274004585073 920 2856.358842232401 29.827908852270607 921 3448.6621182944095 53.65307746188969 922 2341.2435811545224 47.21100745456548 923 3561.333970406226 44.26415381687017 924 160.70387713345028 23.33100257175307 925 3396.5915006186287 34.772710182836995 926 2322.5134175803037 47.66638694064947 927 2462.8823560263486 50.61800894992681 928 2320.5226224448056 31.08675894992685 929 2546.874837258038 55.46393521710652 930 2179.6959203268852 32.755689003637784 931 3514.634923317603 29.78499350803233 932 2228.319005348858 45.91401038425299 933 3444.7425168539794 53.97255835788578 934 2330.514745094952 48.016862251928764 935 1270.81330237644 29.78260932224131 936 146.30125144880918 23.073510506323387 937 2547.5519460226865 58.551564188553165 938 3794.414357521703 47.27776465671392 939 3438.109711983374 54.16329322116703 940 2752.355889656718 37.72433219211433 941 2534.2934888388486 50.813512184790085 942 3280.2170079733655 44.521645882299865 943 3295.108632424049 44.65754447238775 944 2252.6996892477837 42.03494010227057 945 183.93950181043877 25.462464668921022 946 3027.6077550436794 38.86158881442878 947 2541.150407173809 51.180623220545876 948 3286.1893933798597 45.15583930271002 949 3567.404107430151 51.09246192233892 950 3563.7729924704345 29.403523781469833 951 3459.801034310035 45.613602974585014 952 1274.5946210409907 29.24139914768077 953 2530.512170174298 51.180097633706644 954 2481.40747962254 41.57002387302253 955 2760.469273903544 46.05706153171393 956 2221.8173306967583 46.32170615451666 957 2407.57878241795 34.62727484958505 958 2379.1092198874326 48.26243338840337 959 3798.0001729513906 49.95282111423345 960 235.2467106743936 22.708730080298 961 2398.7572949911923 44.41435752170416 962 3579.7470372702387 37.38100943820808 963 2477.9217999960756 51.39286933200689 964 2245.301560738262 56.084946968725625 965 2769.7318357016397 47.036961891821335 966 3009.726361611062 31.945065834692475 967 2529.1221898581357 58.941201546362336 968 196.87064434496725 24.902181008032358 969 3668.27423987644 37.20696387546394 970 2725.4956525351367 47.745065071752975 971 2533.0060285116997 58.97405394384643 972 312.4802869345457 24.23222480075697 973 3799.6881764914297 49.92182669895024 974 2379.030541756329 55.38876471774906 975 152.54195151584514 24.365739205053845 976 2254.094437935528 44.08295569675299 977 2532.1644109274716 53.14047751682133 978 3278.0497830893323 53.99878440158695 979 3011.121110298807 50.74913916843266 980 210.0975242221639 23.919896462133927 981 2468.6902326132627 49.27332816379399 982 2381.4051908041806 53.3192914511475 983 2531.120137551007 53.50690631670242 984 3286.9356435324476 38.017587044409254 985 2760.3929799582315 47.427968361547904 986 2527.009801247296 40.95490393894049 987 2894.2459386374303 44.13779196994634 988 3703.948811867407 31.983212807348725 989 3246.0444730307386 47.64969764011235 990 161.93560711773375 24.91648612277845 991 2545.618371346173 53.308604255040954 992 2319.821671822247 34.052686073950284 993 3451.906995155982 54.63059363620609 994 3804.170445778539 47.385053017309616 995 2762.8677648093058 48.033551552465866 996 3271.5290349509046 50.911263802221725 997 2532.150105812725 53.19543001463724 998 2379.171208717999 53.703145363501015 999 3662.54504142063 38.06765494602058 1000 238.7574824052196 24.027184822729627 1001 199.32682929294447 26.802377083471796 1002 3284.5037740256116 54.41363272922367 1003 2413.4128850485654 52.084283211401406 1004 2216.8534558798638 46.996430733374076 1005 4055.8713239218487 48.22667060153813 1006 2369.1600125815244 49.18034491794438 1007 2697.820023873027 50.49879966037603 1008 206.45091205480554 24.12493644016127 1009 2533.6473744894834 58.893517830542024 1010 2726.0678571249805 55.21471915500493 1011 3434.821919777564 55.479363777807656 1012 3165.931062081032 34.44846091525888 1013 2561.139420845684 59.057273381218614 1014 211.23345313327644 26.29216132419446 1015 2539.526776650128 35.75737891452645 1016 2223.0308812643852 46.402768471411186 1017 2472.471551277814 49.945668556860404 1018 2367.8224843527646 51.49777350681157 1019 2551.6956609274716 51.87447486179203 1020 1345.3191083456793 30.9413236166749 1021 2531.5039914633603 51.37560086856995 1022 3798.2028287436274 52.5396626974854 1023 2404.4554990317197 38.081960060766676 1024 549.2323201681879 23.652867653540177

The overall performance and scaling behaviour of our code isn’t all that different to what we saw before (last article), but everything is faster! We can get some idea of how much faster from the plot stack below. Each of the three panels in this plot is a histogram of execution time ratios for all problem sizes in the range $8 \leq N \leq 1024$. The tab labelled “pre-release-1” shows the execution time ratios between the pre-release-1 version of our code and FFTW–larger values represent slower execution relative to FFTW. The tab labelled “pre-release-2” shows the same ratios for the pre-release-2 version of our code–much better!–and finally, the tab labelled “Speed-up” shows execution time ratios between the pre-release-1 and pre-release-2 versions of our code, which gives a measure of the speed-up we’ve achieved with our optimisations.

rel2,rel3,speedup 31.0035623439637,21.1433970940118,1.4663472575438 23.0236843367442,10.9284704465462,2.10676182448025 20.8464275202564,8.43711760729872,2.47079968426927 280.324183098903,1.67440325644213,167.417366169337 31.3217344925748,16.997410745701,1.84273563551417 238.564872414651,1.63349471368707,146.045696025652 220.196265658982,6.80582459796996,32.3540906012569 24.4004823296537,8.05938108991602,3.0275876096967 41.613223688593,22.845840851164,1.82147919000638 75.6522121597436,38.3947173570711,1.97038075462771 31.659967533097,13.6679428291178,2.31636669313905 428.745816685474,117.821087628618,3.63895653413859 31.1467155085507,11.7470316558796,2.65145412228128 243.187456369924,6.3462483275987,38.3198771646463 297.173923636788,5.33583647241035,55.6939713526389 338.913321074374,91.1426420009795,3.71849349145191 39.9146205525711,17.0613062579703,2.3394820976222 30.844757712075,8.00933754987466,3.85109973452895 254.636204069331,5.17769308272402,49.1794704709235 35.8707950145261,13.4528482806725,2.66640894672551 256.327406474509,9.2896462837598,27.592805866314 136.255087213481,36.4046594898679,3.74279251949612 34.4694643926202,10.3983137298377,3.3149090600826 140.631775111143,37.3827650533443,3.76194149658179 55.796267061807,24.8742425738626,2.24313431438659 365.283997243452,5.1307018977268,71.1957163999908 99.4332853296993,42.8177133412736,2.32224650898982 296.647448889548,6.73751616465583,44.0292003224754 22.1364583157872,7.19578180143054,3.07631038942653 312.918980821529,62.034049688856,5.0443100586055 531.142250661184,122.788477860653,4.32566849850482 357.94137972657,5.04889819775385,70.8949488991104 20.4687655988403,6.01579563844752,3.40250348067385 279.270424648104,54.1054863143249,5.161591618005 318.924524672781,8.48163644377719,37.6017678648286 281.747643338043,54.2643223327939,5.19213419104605 424.1869719843,7.39256837178648,57.3801892185667 40.0534922145836,9.92223498086788,4.03674094514139 427.682735934799,97.7607931881241,4.37478790819338 256.424329809441,48.9762335847427,5.2356890483576 30.1298650675711,9.83801882374295,3.06259477719803 371.29467467343,7.46464578926852,49.7404277651349 45.9285788055788,10.1380076754654,4.5303357696926 108.93295754923,43.7222057457359,2.49147900228831 418.450271063551,6.84958007768998,61.0913758679164 233.262880194168,44.0468043597988,5.29579576962603 30.8789814952158,8.36830377726286,3.68999289666273 519.369414156701,5.59410641161449,92.8422478840204 338.902214071608,9.98240210504665,33.9499662010483 481.308370331345,125.049713257737,3.84893621738526 228.591352563704,50.1711130647591,4.55623442654434 211.712173908992,37.4137320631106,5.65867563149993 26.415368131313,6.39692512049681,4.12938523333246 217.957897546566,38.7325048772451,5.62726057189796 217.582717709118,47.0886452274134,4.6207045596302 399.561169721661,8.02274355230238,49.8035574883849 77.1386234280048,25.301599237488,3.04876473237758 481.857605313242,5.39551211417611,89.30711211772 524.756015432184,6.6090888477682,79.3991467688299 493.973069731807,64.4965841864878,7.65890280799236 129.768483217381,46.2463934891008,2.80602385238893 451.222572680023,99.8304279468651,4.51989019740742 412.985101384841,8.51042365714818,48.5269732768194 446.168666714429,58.1996536549202,7.66617391505232 43.3313245255458,10.5238232000538,4.11745082579154 422.209119515195,55.1787943807507,7.65165539141399 438.762564712467,77.6886538679287,5.64770456002967 56.3774648955331,9.7944617910825,5.75605542173463 546.277651021967,130.339618231458,4.19118652052427 555.351526550351,6.14181768791621,90.4213629855838 483.562604732599,6.27519830788696,77.0593343838769 421.277925273441,54.7106115834114,7.70011361746823 32.5702339374315,7.49344519937004,4.34649658079432 60.8374213913291,13.8272629245088,4.3998166320751 391.400568530886,68.7371305925086,5.69416507725947 376.43862980617,48.597104267363,7.7461123554841 258.660069203734,5.6156838816292,46.0602973130127 147.352980120585,45.658942380548,3.22725346751266 371.070479141964,64.575255372499,5.74632615854886 242.132373957657,55.6264398722664,4.35282887982152 551.401191875935,7.7845570955556,70.8326992926475 502.646686053713,64.8536851941561,7.75047222912485 35.490493816823,6.55787522061015,5.41188915966001 478.318094027619,5.89864068132478,81.0895458579099 460.329737004008,102.458861238314,4.49282503670722 231.280967852096,51.1460083431805,4.52197493693433 349.468105493579,58.8400635419965,5.9392883769432 602.254428424729,128.260463996779,4.69555784890856 48.3820658264393,12.2081371707418,3.9630997874428 361.023447620726,46.5526444197923,7.75516519244679 448.542659597839,8.87771548708946,50.5245589645375 516.505095013952,6.34157191464685,81.4474868322478 39.1023293337295,6.88974300774294,5.67544091119 307.671136213038,38.8597684111634,7.91747220306779 149.505035197283,46.075330596926,3.24479571302864 406.730452669845,51.7136370689051,7.86505215496451 500.501671424073,7.1964546876157,69.5483669598283 425.162572970627,8.26008888378508,51.4719125850135 305.97788291228,50.1146474035824,6.10555793096147 383.150072000661,48.8880148394464,7.83730068113766 49.2275128714945,9.94858775910732,4.94819104615424 326.228891955307,41.6007302348353,7.84190301741704 565.622120091478,6.69114998478339,84.5328712370493 639.112844687001,81.168333235561,7.87391854939552 273.996433022369,6.80229169805695,40.2800181445666 409.337945427271,51.800080694032,7.9022646286038 613.23874996535,131.195368903918,4.67424082944926 500.922741873498,103.062512997025,4.86037771937463 296.500529084055,61.0563233119128,4.85618053955443 451.719074313888,5.90449402102723,76.5042817733773 259.845133913181,42.4912736635492,6.11525876985154 154.671595437838,45.5662127927479,3.3944360515837 46.499174900736,7.77200992661668,5.98290215012349 610.328310244978,7.23088898520026,84.4057088269728 259.930403508287,42.3111221177822,6.14331151002599 573.313354046854,72.5721356937633,7.89991018682564 289.453788865766,57.1845845523218,5.06174506874184 71.0629719495507,9.3338918146885,7.61343428447722 297.680059140862,6.03523526140875,49.3236876852713 307.710885330496,38.5446683960375,7.98322824233014 56.4045482855623,14.5552186478495,3.87521133486346 549.339852550991,69.1365616761042,7.94572132650415 497.35505670896,6.24090340111878,79.6927984207865 695.928907841214,63.5045028887033,10.9587332580319 395.531989644992,4.81100614498461,82.213985541741 617.28480992687,129.310478969256,4.77366424474872 618.695555789857,73.8401929815087,8.37884532540148 49.9844159596429,7.16745433189526,6.97380320056057 188.083940308365,47.0303288477974,3.99920529828857 719.295889668846,65.2745882897077,11.0195392803766 502.525446836379,104.136793894818,4.82562817656885 872.942812789777,78.9107823330417,11.0624022089343 332.551356100159,6.31357018970745,52.6724731186632 491.668951166375,61.4190295096897,8.00515662802533 587.18482651983,69.7214558518479,8.42186697546229 523.972874511054,6.91180732267227,75.8083739968135 67.7299881544339,11.7855365164878,5.74687355638674 312.101861576098,63.3047183275752,4.93015165095756 546.709253613293,64.7808240477973,8.43936861948396 417.177229780238,8.21961300603236,50.7538772779293 662.169036336561,88.94069268714,7.44506273035025 701.786347622189,63.4072655614918,11.0679169241513 65.1752883721421,7.82904165164072,8.32481052881912 700.753969942058,63.1930609406903,11.0890968013046 503.801432706304,106.754162305161,4.71926735058973 181.329392680331,45.6179916730402,3.97495343460056 541.043311835516,6.7733796405604,79.8778956070373 288.826578404247,57.9968071324767,4.98004274174107 386.526618980629,5.1200721854183,75.4924159236342 834.542331338152,74.9788400355254,11.1303713280006 538.769792982785,63.520429375299,8.48183487236147 435.714709146841,54.1319802229049,8.04911823570195 63.7782579786892,9.44778124063422,6.75060697895751 544.872701910037,102.021135670363,5.34078255774918 65.8962179141201,10.438496503251,6.31280739458956 602.396566061772,53.4945470807782,11.2608966508705 578.970676300861,77.511291882606,7.46950105254001 545.964865486633,6.56834209949459,83.1206501148354 481.151118987848,56.1738825920493,8.5653883403806 698.678541154153,61.2400270808084,11.4088542160868 344.667718728519,6.70343193802766,51.4166059885334 517.912065422364,7.51625390368988,68.9056107016436 187.773527222397,46.6720928525767,4.02325063535329 684.342512136198,126.457817886072,5.41162676674314 542.342627134465,74.2115749812465,7.30805979082801 691.446918204287,61.0825018530708,11.3198853555067 323.690545705247,65.8387535287987,4.91641363720018 416.771335598153,7.87146289814131,52.9471257111007 426.574487709098,5.73881034117797,74.3315186160234 396.512956199167,48.6581538550381,8.14895191832502 474.673162247135,55.2052082787555,8.59834021185647 682.272685691075,60.2859089164548,11.3172828933637 65.140155932268,8.45022076585624,7.70869279480504 563.065132198392,50.0589055394726,11.2480511934965 457.635660262831,6.21027567828894,73.6900717407313 372.875240298742,45.5936126612695,8.17823415461635 447.231871511689,85.7367141071047,5.21634023614428 664.294696626511,89.1173620771969,7.45415574634124 299.688065640459,61.577859112325,4.86681528004723 193.714881150811,44.9039662771721,4.31398153016362 478.597326529552,65.9573213439587,7.25616681783862 307.919880322086,6.3085901320171,48.8096189288545 654.515562164685,129.048328581469,5.07186392384372 584.268659113577,51.8524189087388,11.2679151987471 84.3939794660343,14.1689673051948,5.95625479600711 592.160682445265,52.1416729068318,11.3567641664155 505.150491642247,53.2688509039529,9.48303714215771 536.307975198127,6.16478620689093,86.9953891667238 347.849331181805,6.87945754703953,50.5634824843852 674.131604545726,59.6089777987365,11.3092294053735 432.409036710015,5.03267687121908,85.920286117092 672.32728119474,59.6019086890932,11.2802978290823 74.1495001282507,8.40499176873767,8.82207885129042 747.263302135204,75.6245692837878,9.88122390926992 424.436484409191,44.6576810780702,9.50422131563874 351.113850141492,66.947530326227,5.24461243649404 151.827104640608,40.5122543209585,3.74768344012055 588.799652391248,79.3229822436328,7.4228128562137 407.659571435643,42.7477496665414,9.53639839794227 520.313314974387,100.843822193035,5.15959533920088 402.793691683496,5.81729065158884,69.2407713156783 627.466437344979,124.029144933817,5.05902413243115 354.025897583459,6.89517409824912,51.3440114113081 511.040444728673,45.0595618605971,11.3414428287098 422.391924997952,58.1452871916849,7.26442237021672 736.175247364266,75.1404386590854,9.79732432364838 408.079797739854,42.6882024253524,9.55954513318877 542.166398734392,74.1273423556506,7.31398673559843 90.6417415134905,11.7449717126415,7.71749338620628 328.04316595483,62.1165272434896,5.28109314078263 451.260037872095,47.0698921479371,9.58702085940242 670.902993282901,67.8380831068438,9.88976932361488 463.914388694385,5.54635448950323,83.6431190203163 213.42503126647,45.6457095482758,4.67568657336233 632.89136298718,91.4959676997342,6.91715032802498 466.967602378254,41.0894191679232,11.3646678837163 379.99709156789,8.18933796396264,46.4014421239025 75.685162555707,7.49524385478475,10.0977585282154 448.964506679869,46.5794012909795,9.63869208784387 502.185119847148,44.0905307686089,11.3898633355688 569.731831319062,112.471454319951,5.06556827920378 555.812350340781,48.9358046455967,11.3579893978671 457.060724940688,90.656166706744,5.04169480736148 578.855477893771,6.52443242570754,88.7212005772284 357.783442762585,69.6880257673361,5.13407344838693 562.08338002122,49.4548542172989,11.3655856218176 388.464908783067,4.91953315586009,78.9637749102946 492.16793745969,67.035159701543,7.3419372706941 361.390406862752,50.1142330716085,7.21133268359827 662.478082979693,67.040012647546,9.88183111573359 190.842998544489,44.7711243498215,4.26263582422741 546.493120794215,48.0224292774499,11.3799557626885 83.1914014040263,9.15541054786598,9.08658338903406 421.258869670249,36.6920873334053,11.4809186471854 617.866795051413,6.42586811406284,96.1530464186199 89.7270342015239,12.7785993510038,7.02166424792678 343.105586126694,47.4758566125546,7.22694882425697 450.304106696642,8.20005732096406,54.9147510890449 579.070826575427,81.9876416391073,7.06290381084966 677.300422052894,123.677323376185,5.47635090705168 335.336750312789,64.595020569732,5.191371522992 553.810902657188,55.7702367480308,9.93022326871766 78.8365200760403,8.04099643955753,9.80432222158507 523.399742696637,43.514572243887,12.0281486340513 377.449894087009,6.99156277809295,53.9864842907072 576.834639475515,97.0521583821844,5.94355292134752 417.632242312575,43.1059302025623,9.6885101504607 189.178267404063,47.2738410924015,4.00175367671721 110.734191742325,20.9688836107923,5.28088160522443 158.04862300712,18.2146327484694,8.67701398044388 549.7790952933,77.4611462943067,7.09748204867074 771.640801166783,91.2035197775412,8.46064716634762 430.246987615493,5.68475837276371,75.6843051899713 346.359379184053,66.7258427625635,5.19078313355343 975.801001719577,71.3994053121659,13.6667945265548 1315.66173593951,83.0378468836715,15.8441215098295 576.222160143937,5.90215529143509,97.6291086376736 412.358846415636,56.5980015135142,7.28574923828671 660.267723190285,123.70882185127,5.33727274506016 589.265515745625,58.2098683636588,10.1231205689088 836.299919499441,77.8448566090602,10.7431621808923 1319.61240409077,83.4934365050551,15.804983712832 76.9386078845709,8.46206355983584,9.09218033409141 1203.06911393861,75.9597885795692,15.8382367359853 158.813219162244,42.5409229644907,3.73318696669575 531.625846529593,6.32596735144338,84.0386642855962 940.392060345556,71.467644016007,13.1582910461541 675.192450291204,6.14296406181006,109.913136964089 527.43144793996,91.398309878871,5.77069147820083 1319.80680856013,82.6711780290045,15.9645337108548 955.268634472655,71.892301339402,13.287495554814 325.468398428997,63.3027727130591,5.14145565004381 400.933471805248,7.5482107724676,53.1163588154783 1325.77960338102,83.2427383282815,15.9266697613021 489.345546650158,68.3517074502064,7.15922929952616 1293.72834674038,81.2305586752933,15.9266213090059 806.928750634983,77.607753053516,10.3975275521577 695.647937109771,127.695356521486,5.44771521893767 538.657203479221,6.36651585320193,84.6078476673096 727.55331718038,83.139592444711,8.75098488922969 109.277615313159,13.1618302590689,8.30261545409795 223.571813289553,40.4185313122334,5.53141853578151 382.752054496402,71.0705423265311,5.38552319944121 561.479960811569,55.5584343634836,10.1061156104249 753.966911082262,70.474649656163,10.6984130429988 1103.35906346806,69.5140112786083,15.872470070039 391.558967307844,7.42784577153832,52.7150104284882 370.546474356103,50.5880958500717,7.3247760788288 809.916210213678,98.5242040176235,8.22047960995254 661.862949786433,6.08029309373422,108.853790365548 940.101921882978,69.7529772080382,13.4775884773939 558.638305291894,91.1647983315081,6.12778523636375 101.182083440555,8.94212700969071,11.3152143031409 699.758177310983,78.620365021328,8.90046970808586 940.827322153705,69.7006893710145,13.4981064124877 481.038853666049,47.5659738710599,10.1130874555419 652.219475009659,119.289912777021,5.4675157339481 353.135312599842,48.0293392092815,7.35249158979892 169.682263138503,41.2093465297927,4.11756743135516 905.898978825545,59.9460529795139,15.1119036833856 626.613220392914,6.20974192557486,100.908093750596 460.96160034408,45.562166217805,10.1172011475596 384.06120650799,65.2346770132348,5.88737806473805 998.025430316007,65.8651797614039,15.152550010967 516.468589757692,5.69433067242997,90.6987351925765 970.632427693536,64.2821375400282,15.0995667667262 925.845936398627,69.2122160304845,13.3769150808701 421.336899752695,7.02457453283698,59.9804155800638 738.784541906404,68.5126163507761,10.7831897430966 1096.9846367387,71.7794093418145,15.2827203065275 452.321710322474,59.9931217217398,7.53955949184364 409.605786037976,68.6608697458189,5.96563643242983 102.287460999453,10.674709466901,9.58222435154934 472.127167529192,46.6828273457502,10.1135084221109 540.059488113134,97.7255288970729,5.5262887211584 622.636523327125,105.987284629482,5.87463416487915 122.590179913927,12.6561958210767,9.68617913684411 591.747207938315,6.08393748120438,97.2638541678722 779.196514122214,57.5324701688545,13.5435956745003 489.872495455394,48.1889586430916,10.1656584671938 726.483441465791,86.0647587690553,8.44112563442167 613.982257355448,69.9663589213899,8.77539244317805 634.252608881127,5.8744205711112,107.968539399479 901.985690895881,59.6630014513574,15.118007290184 659.708705342733,60.8462260790245,10.8422288094899 752.99016577877,95.4910222645841,7.88545507128831 775.2938758776,57.4460831415089,13.4960267694456 846.09125333199,77.1395976186018,10.968313025371 494.73393126766,7.81731829032949,63.2869115588751 979.880865238625,64.0768000205212,15.2922877691272 589.055704975882,7.28772686965803,80.8284552249587 487.216641835129,47.8119998361131,10.190258585819 198.591406523838,44.5112636595195,4.46159893466349 409.586472040896,62.6591708845998,6.5367362232615 609.139831752487,113.662881318642,5.35917992475334 562.070367675752,8.50226519137423,66.1083082007354 695.329369579615,81.6512815173554,8.51584147435357 523.856265790079,94.7012744878013,5.53167070478612 784.839938486554,56.4056320276743,13.914212291806 933.457314250363,59.6383571229779,15.6519622484824 427.456671139366,72.0852773995592,5.92987481715621 950.074101468039,62.228181366618,15.2675858526327 494.113338108466,7.06192602390629,69.9686369463196 574.903207511164,5.91474290344069,97.1983426662104 638.893719088529,6.88038266124594,92.8572945058894 968.134511027729,62.7420145393862,15.4304020700512 381.673866122807,51.9642933050243,7.34492556037328 881.13644748383,77.6162225271661,11.3524778557141 618.922357178502,58.1510260647968,10.6433609011275 198.607151994154,45.4503059530138,4.3697649076218 781.547601605375,55.564106615445,14.0656918505755 959.608426416626,62.7286731561438,15.2977638157271 109.74304887471,9.28518471443831,11.8191562418851 751.637490270261,102.935646559292,7.30201359193201 783.005691204304,55.4750838501113,14.1145472320495 621.147351103776,6.8623477993499,90.5152827087284 559.608020154014,6.13325067010664,91.2416677964157 796.609802272414,69.729247557988,11.424328100055 374.941868803699,49.0985824816448,7.63651107328544 840.824731314084,54.9181187445168,15.3105159196305 513.812163735259,96.2599503322778,5.33775637699418 674.572209462169,83.9598507270688,8.03446175309463 801.260072138537,97.3383105564402,8.23170309365436 540.62672699841,59.8366121923846,9.03504906427866 390.405340803122,65.794885131574,5.93367311185975 900.6418234615,56.9445552347635,15.8161183233138 216.000750046229,41.0630744058015,5.26021865561318 149.916344129949,8.89898911774579,16.8464465060414 620.918231999434,71.9812796709577,8.62610716060881 476.307825573929,70.0109158741616,6.80333658868355 451.850366440746,7.15780212496362,63.1269708986321 923.209964002848,59.8093449566058,15.4358815444756 611.099378902982,120.090562678799,5.0886544726871 494.253379913041,47.8183936307747,10.3360515145986 816.215954231671,56.7056306940517,14.3939136950167 976.669541180908,63.5312474547884,15.3730578307304 152.641402495647,16.1560274816611,9.44795387782743 675.67591693434,6.71470939529784,100.626233714225 787.938100127915,55.0312002809252,14.3180249768426 682.843173868159,79.81240775184,8.55560173038905 638.418893624038,55.8375115065734,11.4335126404922 851.727837497005,54.5814489835081,15.604712834838 556.42205513466,5.72853684600739,97.1316184380431 523.733161797886,82.8001679059623,6.32526690516739 485.807529115287,7.9835194976977,60.851298635318 1060.21601867565,74.1627232247536,14.2958075509527 831.571970107557,56.3768382232901,14.7502413458161 819.216150348264,70.1751379253456,11.6738801599474 628.65757491269,6.0649184598897,103.654744753835 914.596515194875,58.0091171215156,15.7664270821259 824.264738519433,55.737868177951,14.7882358164086 675.839046197227,120.572777006213,5.60523745888677 156.70936927354,9.91971819988686,15.797764222307 764.497773429644,48.721566606234,15.6911574623265 1022.25299664792,83.2536485481053,12.2787771404066 434.342447179386,65.007012896082,6.68147062646474 545.515295272911,46.2333460349978,11.7991740173849 127.87834857968,8.30238232333056,15.4026089861375 386.998118999461,69.7150064650418,5.55114513535215 848.052117943561,94.0531927124124,9.01672865626858 188.738867582271,42.5261962043961,4.43817892094382 793.507881855528,50.5526687177454,15.6966566154199 694.736328914123,85.0645347448852,8.16716779792764 1087.24836606028,75.9868796625336,14.3083696934112 579.225239637382,48.4729453723631,11.9494541787763 449.896522495776,51.2246357415915,8.78281545554233 481.608974102715,90.6393091945257,5.31346695360519 683.947511404036,58.4680364775852,11.6978019548551 560.362439390747,6.47076683526613,86.5990776142222 1091.42931780311,75.0828155050596,14.5363397797671 647.620097051185,109.896538878635,5.89299812040841 855.774804797403,53.5307318824461,15.9866075934977 492.476568201643,7.66731819570513,64.2306156639626 831.529675540752,52.2616955519248,15.9108820859932 686.189350142989,47.4069543911851,14.4744449196378 608.430142029746,69.4163305316891,8.76494244754111 525.783827437897,61.2366088308765,8.58610294521711 194.488630624881,44.8892086519192,4.33263665067006 987.814650377906,79.4700824475372,12.4300191965954 430.692521759793,48.7818861791395,8.82894359964229 584.783053385078,47.7054985635232,12.258189747381 564.437273863266,6.6730755264118,84.5842777635654 658.774352361513,79.6138132611402,8.27462377917606 832.205734282893,52.2014353943096,15.9422002095676 149.789830487304,13.3685153420455,11.2046720712657 731.316001578312,45.6243880630243,16.0290588570326 390.388355988516,64.6347198356788,6.03991719900701 391.03670022181,72.021532632032,5.42944152854495 599.785054162366,49.5307870113796,12.1093382591431 562.314650063609,78.358359209901,7.17619224972946 892.027263732429,71.275373556032,12.5152239718698 801.909006806316,50.2377551387824,15.9622778643479 623.218920572504,6.31429004280493,98.6997613900641 472.803385486657,7.44995293178745,63.4639426336911 284.931102399285,41.2651205715363,6.90488961265325 783.428649920795,48.9830053696758,15.9938869411593 898.468106781393,98.4794889285075,9.12340342701868 766.860466046303,59.6689491716717,12.8519184046629 663.550758009001,45.4128141986823,14.611531342364 1065.54188317982,72.4616430773098,14.7049092171838 492.35403534789,9.13873815618296,53.8754942896334 809.662746988605,49.0593585086104,16.5037369342386 147.451863291934,9.04178160260736,16.3078328776946 756.091147986454,82.0508780840077,9.21490623430418 595.314067501916,50.7673366427541,11.7263206398062 1058.42510903773,72.0002936962663,14.7002887724695 689.063268549226,48.3791422500689,14.2429823370472 600.91663917742,6.56098015467946,91.5894614844751 674.309731096883,122.703168171923,5.49545493521478 750.736157491946,48.4125456449858,15.5070580877356 661.960722893855,48.287719364983,13.7086764833605 189.440774013471,42.4041053006123,4.4675102250238 551.772203810844,98.9060974810269,5.57874810414687 811.473144674888,53.4224307023717,15.1897458428237 633.814173185857,6.42709099782335,98.6160260373643 810.681501264912,50.5886703071587,16.0249616434412 391.236056774239,73.5306370495092,5.3207217082971 380.206821299068,66.6711952287236,5.70271494300832 652.613015692748,46.9561146515852,13.8983606402519 785.84208906336,49.0524253711958,16.0204532827202 542.084077773696,5.82618705323874,93.0426834600779 1038.32601978614,80.5356493964548,12.8927503232108 608.355664929834,72.112431863044,8.43621063959157 944.885671612098,68.5799131861061,13.7778779195586 460.496214669603,52.6945104701918,8.73897889098137 684.112195487549,74.8173881698008,9.14375938832469 864.527279588159,71.4628213805983,12.0975811322064 771.698207770463,118.258424045733,6.52552419836095 266.473262695194,43.5243418403183,6.1223961449625 508.686673582495,60.9925635808997,8.34014253078213 655.437300677378,48.1739196744184,13.6056460654878 785.891318553757,49.3860125708016,15.913236919605 148.789986940107,10.0929218526121,14.7420131764519 971.222766756003,99.9003617302838,9.72191441486629 554.715783997261,39.3578003692069,14.0941764731157 694.26212830919,101.929976395534,6.81116736076875 646.186870301022,8.03686871721027,80.4028152055374 724.487746474418,60.3878074345335,11.9972520489312 168.409212113894,13.1270404319701,12.8291836219034 687.822122514261,47.5709651200887,14.4588641575363 424.012366373052,50.2196389805953,8.44315839341037 797.536079428995,56.8267552975848,14.0345172842006 490.169254027678,7.87370771253394,62.2539306669196 688.379490586977,42.6957780437089,16.1228936941321 819.768972919284,86.873858351875,9.4363136215141 450.75665922744,62.8180101132078,7.17559595433072 783.673478318083,109.632253553535,7.14820185590189 627.791370972855,6.19138606602416,101.397548832873 430.758887795221,67.6838867499938,6.36427528735648 1002.35062404769,79.3030804865309,12.6394916552823 763.618257042825,61.6856227732873,12.379193444303 728.733682452732,45.9237476785488,15.8683408756975 177.537235352487,9.44130848190336,18.8043040530644 837.000531352696,64.154969239939,13.0465424778293 664.732949242104,49.0868390659143,13.5419791107244 740.496411688008,48.22067133726,15.3564102521283 488.327379387896,8.35004318356584,58.4820184342278 583.733087791724,50.3344312980823,11.5970931375947 600.164605506714,87.8704233293505,6.83010941300708 603.505737174284,7.46139003507929,80.8838211562372 542.214598197208,46.4614830871159,11.6701956582089 773.371742646601,49.7436774840716,15.5471364756706 253.479245875098,43.5780967096335,5.81666628453423 909.571298558846,71.5378573531888,12.7145448887043 191.836498116332,22.5651872729286,8.50143611910007 732.721224371974,113.793831880242,6.43902408649969 203.959819983088,20.4895361468669,9.95434052392036 575.122412159116,46.1306062796217,12.4672632454254 759.434785432332,80.5701144943405,9.4257627682244 634.635289856642,70.9995174605753,8.93858595882773 867.797608652772,96.9890334618263,8.94737866414894 824.111659460536,58.0640827899487,14.1931400594378 565.18307163623,6.34262695477383,89.1086730571219 1498.25459791786,93.8805800580519,15.9591536076087 520.869833196188,75.0132414844064,6.94370517643162 1551.39940316362,95.7644660369917,16.2001571915448 1072.27513227212,75.6981942869734,14.1651348803262 496.446050570955,7.66823526748175,64.7405867522357 1240.86848905617,81.4928381299503,15.22671829244 410.132072917508,57.5129104665659,7.13113055121651 626.510905262879,6.53029308002931,95.9391711191111 653.465571117176,77.2189074983664,8.46250733514975 576.432722269123,60.158581840955,9.58188681696443 448.798779660079,50.9876196699892,8.80211279845717 795.055841530106,118.467561660658,6.71116911992741 896.232103806864,83.7927750347928,10.6958159988701 777.302708365584,60.4860427736473,12.8509433370345 587.686567138934,47.0503200453457,12.4905965904704 1104.59737008177,84.4251040239214,13.0837549192571 804.759193188106,56.5678650878167,14.2264374294272 1261.51856059997,81.6645920745591,15.4475584650961 726.098874970669,7.02983889760617,103.288124457294 170.061347621322,9.29978274282745,18.2865936037574 1385.49522203287,83.0859707164115,16.6754412337774 1260.903377379,81.0717989774694,15.5529221416366 807.992663068268,56.8568884866946,14.2109898127357 234.526631063782,43.810091969211,5.35325584864336 637.435073965456,50.2947352583065,12.6739920329967 573.25506277815,6.2451177435054,91.792514780735 1400.76348486921,83.3852900939191,16.7986881534081 1098.34495754179,77.1284021549183,14.2404733775722 428.21642409432,48.4320691929036,8.84158846050425 681.193482488049,6.47126357142032,105.264369928691 535.035858791042,61.772294714982,8.66142113158824 650.750667048643,94.0361335946807,6.92021930477854 939.947384473715,70.7209785931449,13.2909272916202 1256.47507964087,80.597370150133,15.5895295007811 916.245660731232,99.0844578160283,9.24711787223421 1098.05693562896,78.6683294345548,13.9580558468888 1386.65889150992,83.1122571422379,16.6841683668487 524.108548674871,65.1621805653577,8.04314011789691 799.13154953098,80.5612121795083,9.91955716543015 540.523334755136,8.36460128406366,64.6203347175612 266.762661882614,41.5527383014719,6.41985757827095 1286.22687536678,80.0974208709277,16.0582807958257 1445.42082564087,84.1368107470823,17.1794106860771 726.396844237268,72.801627819168,9.97775552548859 631.584554468889,49.0874666776297,12.8665135362693 1267.22683419539,79.2828905474395,15.9836104037748 475.20381990524,7.2340220985345,65.6901255529078 1010.87332174474,81.0421444376963,12.4734276068161 1457.87210841751,85.7598283108834,16.9994755951779 796.256209167334,117.563981861585,6.77296053228967 1503.79701598318,91.2178741756999,16.4857713422112 606.443552778871,7.27475599514331,83.3627345279674 857.184394886198,59.02359696664,14.5227407162372 823.574399805857,85.3422292450688,9.6502564684698 677.600101062989,93.9648737357186,7.21120642346391 190.063066625296,14.1891008168977,13.3950043119682 1366.23434339652,82.0708595131974,16.6470090785003 268.390001282356,37.6440227774429,7.12968438227546 837.415055509825,57.7213258131206,14.5078971023821 471.591710735791,72.6440214218826,6.49181724118777 814.489698512036,61.5018355309987,13.2433396740087 753.861098194257,57.7034892701785,13.0643936394303 568.744369625575,59.7052652997102,9.52586621582828 918.716211917827,73.6198469987108,12.4791920843562 566.157202838182,5.93292002811226,95.4264005170354 1197.6385242667,81.2309632824858,14.7436208543021 1395.09553251849,90.2192350193165,15.4633935016162 518.813606204685,8.55386143462766,60.6525614390278 559.276920152753,62.2757875672411,8.98064788901922 489.068368362511,56.4398049188461,8.66530933382451 823.379947292871,60.0577346074983,13.7098069494961 929.258609434265,99.8499358875031,9.3065518888387 1388.42007465563,82.9137672686988,16.7453502644039 748.249202000277,6.18772124829936,120.924840013749 259.623375175152,42.4755125078284,6.11230706462463 1064.27412315248,73.553557769447,14.4693765390443 825.71323631448,57.6024929672895,14.3346788268934 671.715852046562,96.3496006886579,6.97165164406991 1373.58178467059,81.9204734464161,16.7672588656246 190.421089625676,9.88988134161305,19.2541328908016 1204.97073943955,71.5421375775616,16.842811526748 790.150694961337,78.8178840746388,10.0250178527132 1083.42056362943,83.6802035881233,12.9471549682415 1039.35736325981,73.5210808794604,14.1368618473369 699.591073980053,7.86896106012619,88.9051386370483 635.103150356197,51.2836793789716,12.3841182623222 1228.3312046364,73.5398233579508,16.7029392858013 787.869923321634,127.98485805045,6.15596200459174 485.792080496192,70.3045493686689,6.90982425545116 469.539917738897,49.8113686892583,9.42636048947099 718.89456610235,69.8120145708156,10.2975765779273 246.301311426979,42.7658143977589,5.75930366100748 1129.94223342683,66.8936594794297,16.8916193585477 1022.32627451459,62.8733474353923,16.2600897870932 809.708663900494,86.7206608437897,9.3369752492895 697.438607682519,6.74048514522901,103.470090454271 1197.24461561026,70.5556171877704,16.9688065008917 687.922357513737,49.5667836108156,13.878696727936 1163.18878738785,67.6548314620544,17.1929892108333 483.72726147557,68.2013947559444,7.09263004380725 691.039050680961,90.8165122702391,7.60917847874033 1060.45527363896,62.2272775529768,17.0416466112654 829.186845320996,59.7960271311761,13.8669220197855 623.082918985416,6.37117422940118,97.7971872296418 185.411126618826,8.91144111877534,20.8059643942647 1067.68237278954,62.7146831453231,17.024440198725 831.675785680329,112.682603513566,7.38069373397292 1021.10184670803,72.2659634634344,14.1297755924155 948.257944091708,84.5903180385032,11.210005661169 520.458170342153,8.37263112734814,62.1618416512036 1350.03416524413,79.6682835367982,16.9456916267132 947.673534642313,72.1473052147697,13.1352589236875 691.70739238333,48.3475083817778,14.3069915190094 1244.82851268428,76.7816357127285,16.2125813175131 588.117229793036,45.8022913658073,12.8403451498953 628.303008148543,61.1350930521817,10.2772888169526 645.333590863415,6.7692682832159,95.3328430583097 535.273235513216,69.4213539817291,7.7104983526264 1059.02619837487,80.4780128441959,13.159199152011 186.796588030041,12.413616081296,15.0477175068669 1201.03553075966,76.1250936922421,15.777130411362 645.032398916213,49.4890852217642,13.0338315211481 1221.92995714235,73.1104301184965,16.7134833588294 646.63197032523,98.4562076970376,6.56771152830707 781.860362175706,80.738041457209,9.68391538937801 750.451534889,100.087534810785,7.49795203076715 1221.86908164988,72.5579274649693,16.8399115622451 214.863474871702,13.1311871077394,16.3628370465503 539.598795341489,50.7441197441833,10.6337206766375 614.168829833405,6.26550613776013,98.0238174426185 458.988628167404,64.7318509106236,7.09061492465491 821.63896723908,59.4250012825059,13.8264863189992 1144.02233995556,68.72051579904,16.6474643947819 673.971344075337,50.2463060302811,13.4133510962809 1124.27020602021,75.5312736560387,14.8848305026606 843.02688487024,87.1871432947804,9.66916512013657 999.578910478347,73.2802522853343,13.6404949397042 713.000242574187,70.2465873873862,10.1499627112451 1200.67169165136,71.0101614236458,16.9084489822262 696.580426121324,6.50349915142131,107.108559546608 1191.60035759226,70.8264267665393,16.8242337216877 1021.86302922336,62.496108912326,16.3508264275606 286.589693627204,42.2867400231959,6.77729457201001 822.662777572089,62.7112493377901,13.1182648449701 771.799655220865,119.21900638368,6.4737970784373 939.315204610539,97.3406027684449,9.649777974408 568.141191887983,61.1109070922075,9.29688690483256 842.787494589472,61.1337067088151,13.7859707837403 635.985171234099,44.4452157574178,14.3094180193726 1116.34581408648,81.7904540199775,13.6488521486115 510.454282219038,48.4583090978803,10.5338855548587 518.090150540254,8.60938204691003,60.1773910969836 1162.49495229153,68.8656583754022,16.8806191607797 1018.37232837763,62.4415602715829,16.3092069440342 184.206884561851,9.2376268690662,19.9409314938558 763.245320149297,8.0267518351911,95.0876937297421 1149.83369661697,68.0985629876674,16.8848452327137 658.714126920765,51.2279254784001,12.8584970164077 749.831736234241,56.3792616546344,13.2997792845803 246.728031639254,43.9563120682323,5.61302848283232 685.366494014556,48.1061058560666,14.2469751358626 475.116569315815,63.4724268280181,7.48540103253289 1184.62454049305,71.3951694742693,16.5925026751283 769.438729510337,118.611996861639,6.48702281277573 1139.44056987355,78.2927761952311,14.55358495696 559.3982097035,8.67168254959612,64.5086125448116 668.919915625723,47.7976798036393,13.9948197982361 795.073583813363,81.3549355590867,9.77289918982131 615.794581609889,61.188438031663,10.0639042508527 661.073178425251,94.4058029251923,7.00246338616588 1164.93615155336,68.9953018857477,16.8842822585577 831.058130277,59.8790608946116,13.8789439557123 736.425280665839,6.45262047955474,114.128094624381 1023.31218976872,62.7233868586514,16.314683262796 1158.03252705707,75.2421438436155,15.3907433773278 514.28870148554,72.6380631298102,7.08015438911778 856.225019097665,75.8489980173457,11.2885475283649 1016.98754809235,63.3836231555183,16.0449576319905 665.588439830414,50.1846979353361,13.2627766473365 526.391986344262,8.18896773719224,64.2806276978625 1165.37448932601,69.1954920400985,16.8417689500738 678.216658066484,5.9534827905057,113.919311087632 912.726735088656,84.5864382469383,10.7904618518642 792.667262489475,7.14661383679676,110.915082386033 721.328206250743,71.8890459649233,10.0339098477214 1006.81905594603,61.3935914151165,16.3994161725833 632.417690190266,47.3436575591716,13.3580234987094 483.788170621505,52.4715563853961,9.22000801859486 1180.0578098656,69.9190697306579,16.8774815570548 1094.1049679917,81.2909824143276,13.459118533163 983.484023434481,71.1299779788995,13.8265756770827 839.796815738163,59.6634792260851,14.0755588951809 498.163250755859,54.2093024789969,9.18962665031283 249.375683499672,42.8030920045317,5.82611376470815 648.673776919271,7.39622382802273,87.7033729646719 810.439719305663,58.4031444393286,13.8766452917202 664.880282833152,46.8516894395951,14.1911698550458 1040.49619508955,61.6255522124732,16.884168299249 1142.49809814831,66.9715190953219,17.0594621949992 183.427577741298,9.8851986172903,18.5557807023182 647.524237020807,48.0777269658202,13.468278928435 767.783152354092,98.6167703646603,7.78552318753718 558.192381813456,39.5889793212036,14.0996911611331 818.244915678415,59.4074895986261,13.7734302729624 513.802585053426,71.7370609943206,7.16230324928009 748.129377662551,7.53120916354137,99.3372194845218 930.797796519286,54.6521556210864,17.03130985304 684.647624065403,6.64426433783528,103.043405447722 219.996001887404,12.9669019934028,16.9659647307686 1011.95963548093,74.4533618991633,13.5918595167198 794.028616515608,69.9240196232087,11.3555916950183 467.282532768426,49.7264603143139,9.39706003232082 1069.25759805572,63.1904956903516,16.9211775659323 931.874988870851,58.0435981476657,16.0547419286467 544.254437821785,8.33319542007282,65.3116134191209 641.717463267959,98.9423880229356,6.48576890138536 1165.98758881702,81.5571137613269,14.2965773927364 817.687504453665,83.8314597069511,9.75394568234942 1072.7956761926,62.9961920574628,17.0295321217835 953.010948098821,100.013647284092,9.5288090573456 849.048333348047,115.121513391523,7.37523602960702 638.561325896524,59.512470950528,10.7298741876699 1101.80914542846,64.3498899688104,17.1221605190388 470.074441260341,66.4803664170669,7.07087620894434 1160.7361991702,74.0351566646166,15.6781757676073 963.431883446816,57.8117962143235,16.6649705861953 866.168298826463,62.0492772235082,13.9593616168393 283.192328350644,41.9546305852878,6.74996596084797 671.166116811921,47.4470090904559,14.1455937830005 243.898551471721,9.57031287995734,25.4849088562722 1039.24436450975,60.5705285178617,17.1575911576087 698.067699980212,71.6922080710728,9.73700934539742 619.866164920823,42.1574987032138,14.7035802404844 579.504392641967,67.2994176895732,8.61083814001188 1154.57758197929,72.4600708084859,15.9339836284576 520.387945916268,8.02724635522299,64.8277034101082 1101.42467261315,64.5415786759302,17.0653506655534 1068.15167862711,62.4580946256031,17.1018934379924 736.558970969195,90.625270250313,8.12752302900471 841.498250114011,120.213504361482,7.00003094147915 1088.83706609367,63.1557588438938,17.2405032577475 614.669904182212,43.5437995080733,14.1161293025945 703.795711843656,48.2382208448075,14.5900014452837 898.560993838497,60.8684178808444,14.7623517272539 250.019721989229,42.7889211230133,5.8430947877945 1076.33731223984,62.1988164588513,17.3047876715131 578.379875701866,50.806103605049,11.3840628322536 261.407844067136,17.0475161812426,15.3340722066458 1058.46047755996,61.5379004633803,17.2001395821073 828.635444204477,6.62741964292048,125.031383079784 258.596043228279,20.391622658073,12.6814843313071 830.785979683635,59.4671886175136,13.9704936284639 1081.6329280676,63.7246998881981,16.9735272188848 737.43211989366,76.9066810037613,9.58866135255004 504.162201253966,65.928677371904,7.64708502204564 750.254809125945,53.629549479705,13.9895788125139 988.268425641431,95.6088036908753,10.3365839492849 953.815990154617,57.6048421325237,16.5579134469339 868.741963483235,71.9830718360616,12.0686981164371 715.504137445214,5.88048483695352,121.674344426316 1148.47685489369,79.3051033506894,14.4817521996674 657.222686080398,80.6444860207,8.14962954704306 494.965452359725,70.4198767812463,7.02877475769087 557.261352455066,8.67534859644307,64.2350386569533 1102.54097434532,72.6617043231293,15.1736184089804 1166.32732004847,77.457596953738,15.0576233438415 1074.62700041157,61.8202585768605,17.3830880871438 854.61724157712,59.2685135332212,14.4194141312164 1351.62926970938,78.8829015443229,17.1346292193616 1047.1671153504,72.7007903467445,14.4037927284691 694.924970297679,49.9805842032134,13.9038985113143 828.658324291027,6.54878453558459,126.536202220166 583.586339299211,48.837209781703,11.949624925498 956.992678411413,57.3228920586925,16.6947731358626 630.877350374125,61.508339625229,10.2567774421821 840.838421331531,58.9485967373145,14.2639259943448 1063.22014224949,61.6054892576995,17.2585293138729 796.297391599454,113.722727017276,7.00209546925907 715.927689486895,62.7876734360521,11.4023605320565 261.285513892916,10.2279566377918,25.5462086070524 840.624134476516,59.7026155341914,14.0801894013353 873.391146435482,51.2820427740642,17.0311301810543 1031.80263140242,71.873214572487,14.3558714820221 1154.10913902807,84.6616418924636,13.6320193328404 694.861207698147,93.8231014863426,7.4060779988103 564.497626576878,62.5589730694249,9.02344777863324 1383.46235940519,79.8237807207021,17.3314562015776 673.43442131044,49.9568423658024,13.4803240040535 948.197174728681,55.4210047776065,17.1089856370091 208.623502843133,9.42517999766412,22.1346969389271 1057.66977184788,57.7013963461834,18.3300550562472 593.651575758216,72.0019313622938,8.24493960823253 1396.12970397736,81.0329169812247,17.2291675529938 977.665387314612,94.236257687239,10.374620250301 944.894761745995,62.4125754739313,15.1394931962175 252.951492564745,43.6877033725035,5.78999290505048 784.156766770674,69.6144817064223,11.2642764486506 869.600167578196,52.337882303881,16.6151194755871 710.005098724058,6.37643505889638,111.348283510464 867.109088620376,86.9595847496019,9.9714032802387 996.9140740984,56.6607993148479,17.5944230606214 1126.36882497793,74.0360617575447,15.2137863392382 1003.32995882055,58.0920699145605,17.2713755990483 651.138598600569,50.5763018326244,12.8743813803434 844.515428048511,6.81704894266282,123.882846544246 576.106357758339,51.5439471193834,11.1769934193047 992.109951666725,56.0834774215358,17.6898793954913 644.278867143651,95.6581598070878,6.73522121315064 995.569189170372,56.5440859269078,17.6069552252963 888.341440629926,62.7021171648371,14.1676466568836 1359.79569761804,79.9695690320788,17.0039142898542 717.403415146655,6.74802007858124,106.313171388412 282.673947745812,43.3047170068405,6.52755559402827 1172.80276287497,77.6088384333847,15.1117164816433 917.107055683623,60.1444149546947,15.2484159397752 816.923640135252,115.570414868327,7.06862254553642 464.807691998318,64.5819738145042,7.19717383264506 871.791737168063,52.7481014191027,16.5274524336215 1022.18824326786,57.4629575852742,17.7886465685471 517.664181967137,7.84160601803337,66.0150715015092 614.596857512926,59.4185800524888,10.3435130386826 866.811056971428,52.103232017142,16.6364162723389 1385.64909866304,80.2630072273835,17.2638572429454 721.138910002951,49.6764411325895,14.516718459726 766.459058456285,7.9201304652722,96.773539503802 704.343411540687,70.31242095699,10.0173397808551 853.05006857076,7.5708365767801,112.675800080942 627.915550526086,61.5629413568015,10.1995703370777 1361.37466659606,78.7703521294047,17.282830783333 264.582605698173,43.3762290224228,6.09971432881822 938.370400044133,82.6336534406288,11.3557898141142 1126.48315768714,81.1192758514413,13.8867506626926 979.827315102371,55.227127045617,17.7417759626179 505.472876614513,48.6171088556024,10.3970163696039 791.750397920969,118.739836310455,6.66794247425838 676.154932193,49.4776550198178,13.6658645589039 980.277431315768,55.2132655266126,17.7543824290428 734.001552531788,7.31432028962465,100.351300389862 976.72574024949,55.3406022216021,17.6493514894969 846.300973131295,82.0689173084518,10.3120767385113 838.113161688194,84.6487445586878,9.90107019374778 854.539016707292,51.5469683862906,16.5778714725455 961.92479533997,54.1016574892609,17.7799505593874 265.61340634876,14.0364161778449,18.9231640743173 894.324214970059,59.0129548026464,15.1547099778497 814.037656409623,48.7749022058312,16.6896830048857 354.813887078032,37.2303720744981,9.53022672908153 537.911300179912,66.8330427169206,8.04858313062746 1027.66604448814,69.6492515403915,14.7548756341218 563.239265660982,72.0976166374446,7.81217593493179 1155.46921480469,80.3054065706974,14.3884361482867 679.536842775566,51.2274673910366,13.2650876059992 796.368567195073,56.06359679384,14.204735563498 677.264357933236,79.1411804780015,8.55767318408262 547.431218112839,7.42565928183948,73.7215642861047 1031.71986009956,73.5590367781098,14.025739124504 930.584545334349,52.1410045020415,17.8474610188592 843.986776560976,48.3968403371198,17.4388817675283 1293.52419141863,74.4264309602821,17.3799035467511 782.904081094442,7.17621923971997,109.097012638788 934.64249263278,52.1322456718868,17.9282990898818 623.226757624836,7.96708629603804,78.2251797542046 970.418087129436,52.8482402625969,18.3623538325503 303.442999442797,40.0263935113363,7.58107270785853 577.747766711815,52.0150641858955,11.1073162314481 846.511407749841,47.2273808778857,17.9241658549441 926.231749745451,51.7643765906155,17.8932271718572 993.086757584895,98.3343468603706,10.0990832734672 658.641755700138,46.2528045804751,14.2400393159764 872.453537277444,60.9129550684073,14.3229553762028 797.358096929358,6.02279193921707,132.390111592168 666.490000569727,45.6473048186752,14.6008620490788 721.157101755568,62.6941919092202,11.502773698715 1122.95075245574,73.0788407740893,15.3662912624347 872.8020371521,57.146937070571,15.2729451811962 540.599731505117,9.32173850477438,57.9934452385931 706.755078699019,87.5836971871925,8.06948212277991 830.819157805731,46.0386176000118,18.046136072633 566.615005602821,53.3184790931194,10.6269911527904 271.187799297243,9.40516272167397,28.8339295472578 640.227831174316,52.0894631889877,12.2909277995721 868.025803785126,79.2030590991386,10.9594984544551 819.601359106328,79.0193612549607,10.3721587480546 643.576442058412,47.7078812039502,13.4899397293947 909.228848969586,57.9923914643411,15.6784161854864 1100.01551637581,68.7828585085853,15.9925821669436 807.99126506455,44.8761511942584,18.0049144938242 711.79127060755,48.7370167440546,14.6047361566172 669.293105264384,46.9639768028139,14.2512016832502 750.572267105405,6.75824435303759,111.060244036315 805.286978853394,44.9236051433011,17.9256979996289 796.653528995929,117.657336544635,6.7709634808341 906.049765633183,61.2038123758745,14.8038125479636 860.082070314086,48.7079325305222,17.6579465731814 528.897388614536,48.6037488583184,10.88182292597 725.916567325999,48.9962859475011,14.8157468119892 1171.23104351,72.407903233399,16.1754586337718 271.115300648325,42.4969209311526,6.37964574157141 818.176466723655,45.1780603639039,18.1100396992111 706.895049202311,96.524864281297,7.32345033029258 1129.85449184923,63.9671382305525,17.66304579356 830.569449354848,47.519961170012,17.4783276102294 1161.48155942179,79.9866503158027,14.5209426177498 799.323463012984,6.90137479443283,115.820903344907 1026.06950758535,97.5591906233855,10.5174048803495 867.636345570733,48.9396801888697,17.728688504345 677.359690770258,47.7387610079239,14.1888829217379 574.472527508353,74.577841724733,7.70299212504342 813.483449106188,45.6055738448501,17.8373689995362 531.893023362667,66.3458970068103,8.01696935845285 817.296013892808,113.71271909021,7.18737552344021 713.33088051632,48.6485667886468,14.6629372169457 1128.85728471138,63.1626101015632,17.8722393342552 865.10116525594,48.7652927321721,17.7400999109599 322.616153216964,42.1966225097395,7.64554445423921 720.972783584823,6.3669539185474,113.236689444944 778.06898147789,43.1555333145594,18.0294141149078 1225.72719274588,81.8174032837245,14.9812526864893 1168.23272198486,63.0740797395287,18.5215975692266 765.901421943323,73.1537339032923,10.4697515912972 873.780025960545,47.9831673991481,18.2101364566454 1112.44187725866,69.3257667645434,16.0465859834907 882.998832097523,73.7073332607817,11.9797962161161 575.434546744269,53.5303055059797,10.7496966681796 561.337326365201,7.73217598042469,72.5975880251977 860.873094722788,77.998232494422,11.0370846516856 916.186682340258,50.284116297159,18.2202005286513 1053.07552206902,73.0791080555573,14.4100762870345 1059.71160884098,70.4403743270742,15.044093944198 885.428522146107,120.956741193437,7.32020814557256 1346.16794720647,75.6208264521117,17.8015503184028 276.925778486357,43.6241594432985,6.34799115949267 906.203977861731,49.9900889756839,18.1276728333596 612.51743960058,56.8148480360228,10.7809395039167 910.89966686315,57.7015056003705,15.7864107250834 697.293608862074,44.1098210401989,15.8081260004797 574.775710556546,69.1378969375409,8.31346824268891 856.841283734152,49.4613361998274,17.3234560480221 1216.39447043105,76.5578086193727,15.8885748216577 265.643639706113,10.4580923495948,25.4007739486452 574.173781708331,53.6685579165926,10.6985133194871 1030.97988591845,93.2652240932573,11.0542798341165 655.361295957022,46.169724910925,14.1946112354234 591.623032423643,40.6332728528505,14.5600634870381 921.532980372998,60.0312093682118,15.3508981423415 679.377025302583,93.9909920884108,7.22810782402999 758.56647143844,42.2713988153294,17.9451471372495 836.087844217789,7.85908406826307,106.384896376681 861.816646050012,98.7807620877275,8.72453935195023 837.305406645717,57.6194249958519,14.5316515516424 773.056494583846,42.737458434722,18.0884994779142 269.738705701556,12.9807674723294,20.7798734763986 1200.69158015954,76.2948355310129,15.7375210497894 780.18977261685,45.262109330312,17.2371501054715 733.226488871681,6.34303911199887,115.595454469872 555.196730673397,50.9950281247519,10.8872717809899 857.108003346016,47.6567365163975,17.9850335125467 952.428525591511,62.3578627278814,15.2735915556911 895.483515207574,58.7400426765796,15.2448563944373 691.721941873944,8.6454761363177,80.0096988259763 726.616137700927,49.6097878988998,14.6466285883283 764.194888551527,43.3168828279521,17.6419640255923 915.523888569179,47.2805325943979,19.3636543061627 892.514888148552,83.6565876639131,10.6687938520059 1005.63589199243,58.8465912502789,17.0891103567136 568.845855194287,61.505211695239,9.24874233443733 745.562092716827,70.1827698666766,10.6231500143574 1041.59114555383,107.216987598629,9.71479584422818 881.607367727917,65.1500228366785,13.5319579232992 794.837361604731,6.21372148853755,127.916476956839 865.27837268516,45.6799651877453,18.9421854664042 557.587178042882,67.0585547696638,8.31492983942334 1162.79627857404,61.3911671517486,18.9407749114755 1185.59999212125,78.620515928558,15.0800332218451 942.413740908592,55.5241193604162,16.9730515632536 934.298073132544,62.1577037431685,15.0310905466039 870.93256880831,45.8056264381727,19.0136591622401 812.641234560375,44.0927529634965,18.4302675596859 1002.54718922372,90.5087014182687,11.0768044786173 291.449573656779,9.40146218628018,31.0004516193343 776.653452684421,7.01681873769525,110.684554029042 951.175605458871,57.9690500654482,16.4083352131004 593.159494315019,44.69377577632,13.2716353454588 728.070226435854,47.3049932140099,15.390980464621 1206.14720083557,76.6329068676918,15.7392855123974 878.910059385352,45.3478977152565,19.3814951445844 682.884348313215,52.4234496213667,13.0263146215179 559.048888273261,7.92329280311353,70.5576459390188 772.817533157271,40.0715773659901,19.2859274317757 730.999061202589,46.8033904091955,15.6185065827832 1131.82282383852,59.0879640748468,19.1548793660386 709.310865376529,84.6610011363411,8.37824802277296 806.677018536328,42.4259980868468,19.0137428678766 812.985332707849,7.71235725583688,105.413339364247 613.07278843776,67.7072707540518,9.05475559138635 668.043216728699,45.6798726894806,14.624454434667 741.805247009802,48.3131230196996,15.3541150032328 846.833273326224,45.6095313277354,18.5670242309914 909.122842257941,48.030791127037,18.9279172989967 295.142025029424,43.3260137664673,6.81212046463072 930.461123973853,48.2419027186448,19.2874051714018 1030.02961536967,68.6798592033116,14.9975498977145 559.605990143784,62.131373927552,9.0068182106565 319.068029697597,22.6341223959371,14.0967705359263

Concentrating on the “Speed-up” tab showing the speed-up between the unoptimised and optimised versions of our code, we can see that for most input vector lengths the optimised code is around 10-20 times faster. For some input vector lengths though, we get speed-up factors of 50-100 times compared to the unoptimised code. This is definitely good news. A lot of this improvement in performance comes from using specialised straight line code for small prime length transforms. In the next article, we’ll think about how to exploit this kind of specialised code for other input sizes (especially powers of two, which will also give us a speed-up for the convolution in Rader’s algorithm).

Looking at the “pre-release-2” tab, we appear to be getting to within a factor of 10 of the performance of FFTW for some input vector lengths, which is really not bad, considering the limited amount of optimisation that we’ve done, and my own relative lack of experience with optimising this kind of Haskell code!