Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Efficient alternative to Data.Vector.dropWhile

Consider the following:

module Main where

import           Criterion.Main
import qualified Data.Vector    as V

f1 :: V.Vector Double -> Double
f1 xs
  | V.null xs = 0
  | otherwise = V.last xss / V.head xss
    where xss = V.dropWhile (< 10) xs

f2 :: V.Vector Double -> Double
f2 xs
  | V.null xs = 0
  | otherwise = V.last xs / V.head xs

setupEnv :: IO (V.Vector Double)
setupEnv = return $ V.enumFromN 0 10000000

main :: IO ()
main = defaultMain [
  env setupEnv $ \v ->
    bgroup "funcs" [bench "f1" $ nf f1 v , bench "f2" $ nf f2 v]
  ]

Compiling with --make -O2 and running gives the following result:

app $ ./A
benchmarking funcs/f1
time                 81.87 ms   (78.34 ms .. 86.06 ms)
                     0.998 R²   (0.996 R² .. 1.000 R²)
mean                 85.87 ms   (84.16 ms .. 87.13 ms)
std dev              2.351 ms   (1.169 ms .. 3.115 ms)

benchmarking funcs/f2
time                 27.50 ns   (27.11 ns .. 27.95 ns)
                     0.998 R²   (0.996 R² .. 0.999 R²)
mean                 27.62 ns   (27.21 ns .. 28.05 ns)
std dev              1.391 ns   (1.154 ns .. 1.744 ns)
variance introduced by outliers: 73% (severely inflated)

The mean execution time of simply taking the first and last elements and dividing them is ~27ns. Dropping the first 9 elements and performing the same operation has a mean of ~85ms or 3000x slower.

Using an unboxed vector improves the performance of f1 by more than half, yet I need to support elements which have no instances of the "Unboxed" class.

According to the dropWhile documentation it has a complexity of O(n) yet it does no copying. Is there a data structure in the Haskell libraries which supports an efficient dropWhile-type operation and O(1) access to the first and last elements?

like image 296
Nickolay Kolev Avatar asked Feb 15 '16 22:02

Nickolay Kolev


1 Answers

There's something wrong with Vector's dropWhile. I think it's most probable that stream fusion fails to kick in correctly and we pay for costly stream/bundle building. Some further investigation is probably due.

As a stopgap measure, you can implement a custom dropWhile. I used your benchmark with the following code:

dropWhile' :: (a -> Bool) -> V.Vector a -> V.Vector a
dropWhile' p v = V.drop (go 0) v where
  go n | n == V.length v       = n
       | p (V.unsafeIndex v n) = go (n + 1)
       | otherwise             = n

And got the following results:

benchmarking funcs/f1
time                 57.70 ns   (56.35 ns .. 59.46 ns)

benchmarking funcs/f2
time                 19.68 ns   (19.44 ns .. 19.91 ns)
like image 50
András Kovács Avatar answered Sep 30 '22 08:09

András Kovács