├── Setup.hs ├── test ├── Spec.hs └── Data │ └── Vector │ └── HashTablesSpec.hs ├── .gitignore ├── src └── Data │ ├── Vector │ ├── Hashtables │ │ └── Internal │ │ │ └── Mask.hs │ └── Hashtables.hs │ └── Primitive │ └── PrimArray │ └── Utils.hs ├── charts ├── readme.md ├── results.csv ├── toList.svg └── fromList.svg ├── LICENSE ├── gen └── GenPrimes.hs ├── changelog.md ├── vector-hashtables.cabal ├── scripts └── Plot.hs ├── .github └── workflows │ └── haskell-ci.yml ├── bench └── Main.hs └── README.md /Setup.hs: -------------------------------------------------------------------------------- 1 | import Distribution.Simple 2 | main = defaultMain 3 | -------------------------------------------------------------------------------- /test/Spec.hs: -------------------------------------------------------------------------------- 1 | {-# OPTIONS_GHC -F -pgmF hspec-discover #-} 2 | -------------------------------------------------------------------------------- /.gitignore: -------------------------------------------------------------------------------- 1 | dist 2 | dist-* 3 | cabal-dev 4 | *.o 5 | *.hi 6 | *.chi 7 | *.chs.h 8 | *.dyn_o 9 | *.dyn_hi 10 | .hpc 11 | .hsenv 12 | .cabal-sandbox/ 13 | cabal.sandbox.config 14 | *.prof 15 | *.aux 16 | *.hp 17 | *.eventlog 18 | .stack-work/ 19 | cabal.project.local 20 | .HTF/ 21 | -------------------------------------------------------------------------------- /src/Data/Vector/Hashtables/Internal/Mask.hs: -------------------------------------------------------------------------------- 1 | {-| 2 | Module : Data.Vector.Hashtables.Internal.Mask 3 | Description : Provides arch-dependent mask for hashtables. 4 | Copyright : (c) klapaucius, swamp_agr, 2016-2021 5 | License : BSD3 6 | -} 7 | module Data.Vector.Hashtables.Internal.Mask where 8 | 9 | -- | 'Int' mask. For 32-bit it is equal to @0x7FFFFFFF@. Otherwise, @0x7FFFFFFFFFFFFFFF@. 10 | mask = maxBound :: Int 11 | {-# INLINE mask #-} 12 | -------------------------------------------------------------------------------- /charts/readme.md: -------------------------------------------------------------------------------- 1 | ## Benchmarking charts 2 | 3 | The charts below were produced by running `../scripts/Plots.hs` in the current directory. 4 | The script requires `results.csv` in the same directory, 5 | which can be produced by `cabal bench --benchmark-options="--csv results.csv"`. 6 | 7 | ![](./find.svg) 8 | ![](./fromList.svg) 9 | ![](./insert__resize_.svg) 10 | ![](./insert,_delete.svg) 11 | ![](./insert.svg) 12 | ![](./lookupIndex.svg) 13 | ![](./toList.svg) 14 | -------------------------------------------------------------------------------- /LICENSE: -------------------------------------------------------------------------------- 1 | Copyright Author name here (c) 2017 2 | 3 | All rights reserved. 4 | 5 | Redistribution and use in source and binary forms, with or without 6 | modification, are permitted provided that the following conditions are met: 7 | 8 | * Redistributions of source code must retain the above copyright 9 | notice, this list of conditions and the following disclaimer. 10 | 11 | * Redistributions in binary form must reproduce the above 12 | copyright notice, this list of conditions and the following 13 | disclaimer in the documentation and/or other materials provided 14 | with the distribution. 15 | 16 | * Neither the name of Author name here nor the names of other 17 | contributors may be used to endorse or promote products derived 18 | from this software without specific prior written permission. 19 | 20 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 21 | "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 22 | LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR 23 | A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT 24 | OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, 25 | SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT 26 | LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, 27 | DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY 28 | THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT 29 | (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE 30 | OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -------------------------------------------------------------------------------- /gen/GenPrimes.hs: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env cabal 2 | {- cabal: 3 | build-depends: arithmoi, base, quote-quot 4 | -} 5 | 6 | import Data.Bits (FiniteBits) 7 | import Data.Int (Int32, Int64) 8 | import Math.NumberTheory.Primes (nextPrime, unPrime) 9 | import Numeric.QuoteQuot (AST (..), assumeNonNegArg, astQuot) 10 | 11 | -- | For a given bitness, expressed as a ~ Int32 or a ~ Int64, 12 | -- generate a list of primes such that each prime is at least 20% larger 13 | -- than the previous. Additionally, for each of selected primes 14 | -- there exist numbers m and s such that (assuming Int64) for every n >= 0 15 | -- 16 | -- n `quot` p = (n * m) `shiftR` (64 + s) 17 | -- 18 | -- The function returns a list of tuples (p, m, s). 19 | -- 20 | genPrimes :: (FiniteBits a, Integral a, Show a, Bounded a) => [(a, a, Int)] 21 | genPrimes = go 3 22 | where 23 | go n 24 | | n < 0 = [] 25 | | n >= maxBound `quot` 2 = [] 26 | | p < n = [] 27 | | otherwise = case assumeNonNegArg (astQuot p) of 28 | Shr (MulHi Arg mul) shft -> (p, mul, shft) : go p' 29 | _ -> go (p + 1) 30 | where 31 | p = fromInteger (unPrime (nextPrime (toInteger n))) 32 | p' = ceiling (fromIntegral p * 1.2 :: Double) 33 | 34 | main :: IO () 35 | main = do 36 | putStrLn "-- | This data is auto-generated by GenPrimes.hs." 37 | putStrLn "-- The vector contains tuples (p, m, s) such that p is prime" 38 | putStrLn "-- and (assuming 64-bit architecture) for every n >= 0" 39 | putStrLn "-- it holds that n `quot` p = (n * m) `shiftR` (64 + s)," 40 | putStrLn "-- enabling faster computation of remainders." 41 | putStrLn "primesWithFastRem :: UI.Vector (Int, Int, Int)" 42 | putStrLn "primesWithFastRem = UI.fromList $" 43 | putStrLn " if finiteBitSize (0 :: Int) == 32" 44 | putStrLn $ " then " ++ show (genPrimes :: [(Int32, Int32, Int)]) 45 | putStrLn $ " else " ++ show (genPrimes :: [(Int64, Int64, Int)]) 46 | -------------------------------------------------------------------------------- /src/Data/Primitive/PrimArray/Utils.hs: -------------------------------------------------------------------------------- 1 | {-| 2 | Module : Data.Primitive.PrimArray.Utils 3 | Description : Provides useful utilities for operating with mutable primitive arrays. 4 | Copyright : (c) klapaucius, swamp_agr, 2016-2021 5 | License : BSD3 6 | -} 7 | module Data.Primitive.PrimArray.Utils where 8 | 9 | import Data.Primitive.PrimArray 10 | import Control.Monad.Primitive 11 | import Data.Primitive 12 | 13 | replicate :: (PrimMonad m, Prim a) 14 | => Int -> a -> m (MutablePrimArray (PrimState m) a) 15 | replicate n x = do 16 | xs <- newPrimArray n 17 | sz <- getSizeofMutablePrimArray xs 18 | setPrimArray xs 0 sz x 19 | return xs 20 | 21 | {-# INLINE replicate #-} 22 | 23 | clone :: (PrimMonad m, Prim a) 24 | => MutablePrimArray (PrimState m) a -> m (MutablePrimArray (PrimState m) a) 25 | clone xs = do 26 | sz <- getSizeofMutablePrimArray xs 27 | cloneMutablePrimArray xs 0 sz 28 | 29 | {-# INLINE clone #-} 30 | 31 | unsafeFreeze :: PrimMonad m 32 | => MutablePrimArray (PrimState m) a -> m (PrimArray a) 33 | unsafeFreeze = unsafeFreezePrimArray 34 | 35 | {-# INLINE unsafeFreeze #-} 36 | 37 | unsafeThaw :: PrimMonad m 38 | => PrimArray a -> m (MutablePrimArray (PrimState m) a) 39 | unsafeThaw = unsafeThawPrimArray 40 | 41 | {-# INLINE unsafeThaw #-} 42 | 43 | growWith :: (PrimMonad m, Prim a) 44 | => a -> MutablePrimArray (PrimState m) a -> Int -> m (MutablePrimArray (PrimState m) a) 45 | growWith a xs delta = do 46 | r <- growNoZ xs delta 47 | sz <- getSizeofMutablePrimArray xs 48 | setPrimArray r sz delta a 49 | return r 50 | 51 | {-# INLINE growWith #-} 52 | 53 | growNoZ :: (PrimMonad m, Prim a) 54 | => MutablePrimArray (PrimState m) a -> Int -> m (MutablePrimArray (PrimState m) a) 55 | growNoZ xs delta = do 56 | sz <- getSizeofMutablePrimArray xs 57 | resizeMutablePrimArray xs (sz + delta) 58 | 59 | {-# INLINE growNoZ #-} 60 | 61 | freeze :: (PrimMonad m, Prim a) 62 | => MutablePrimArray (PrimState m) a -> m (PrimArray a) 63 | freeze xs = do 64 | r <- unsafeFreezePrimArray xs 65 | return $ clonePrimArray r 0 (sizeofPrimArray r) 66 | 67 | {-# INLINE freeze #-} 68 | 69 | length :: (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> m Int 70 | length = getSizeofMutablePrimArray 71 | 72 | {-# INLINE length #-} 73 | -------------------------------------------------------------------------------- /changelog.md: -------------------------------------------------------------------------------- 1 | # 0.1.2.1 (2025-06-17) 2 | 3 | * Bump `QuickCheck` version (see [#34](https://github.com/klapaucius/vector-hashtables/pull/34)). 4 | 5 | # 0.1.2.0 (2024-04-26) 6 | 7 | * Add `upsert` function to public interface (see [#21](https://github.com/klapaucius/vector-hashtables/pull/21)). 8 | * Simplify support of 32-bit architectures via `maxBound` (see [#22](https://github.com/klapaucius/vector-hashtables/pull/22)). 9 | * Improve performance via strictness annotations and bang patterns (see [#24](https://github.com/klapaucius/vector-hashtables/pull/24)). 10 | * Suggest using strict boxed vectors to avoid accumulation of thunks (see [#27](https://github.com/klapaucius/vector-hashtables/pull/27)). 11 | * Speed up division by bucket's size (see [#28](https://github.com/klapaucius/vector-hashtables/pull/28)). 12 | * Avoid deprecated `sizeofMutablePrimArray` (see [#29](https://github.com/klapaucius/vector-hashtables/pull/29)). 13 | * Introduce `findEntry_` and avoid examining `MutVar` twice in `at` (see [#32](https://github.com/klapaucius/vector-hashtables/pull/32)). 14 | * Bump `QuickCheck` boundary (see [#33](https://github.com/klapaucius/vector-hashtables/pull/33)). 15 | 16 | # 0.1.1.4 (2023-12-13) 17 | 18 | * Add `wasm32` support (see [#20](https://github.com/klapaucius/vector-hashtables/pull/20)). 19 | 20 | # 0.1.1.3 (2023-04-23) 21 | 22 | * cleanup the cabal file 23 | * CI based on Haskell-CI (see [#15](https://github.com/klapaucius/vector-hashtables/pull/15)) 24 | * readme: minimal improvement of benchmark data presentation (see [#16](https://github.com/klapaucius/vector-hashtables/pull/16)) 25 | * bump hspec to <2.12 (see [#17](https://github.com/klapaucius/vector-hashtables/pull/17)) 26 | 27 | 28 | # 0.1.1.2 (2023-01-31) 29 | 30 | - Relax `hspec` boundaries (see [#14](https://github.com/klapaucius/vector-hashtables/pull/14)). 31 | - Set lower bound for `primtive` (see [#12](https://github.com/klapaucius/vector-hashtables/pull/12)). 32 | 33 | # 0.1.1.1 (2021-09-10) 34 | 35 | - Optimise `insertWithIndex` function ([#10](https://github.com/klapaucius/vector-hashtables/pull/10)). 36 | 37 | # 0.1.1.0 (2021-09-10) 38 | 39 | - Add `alter` function to public interface ([#9](https://github.com/klapaucius/vector-hashtables/pull/9)). 40 | 41 | # 0.1.0.1 (2021-09-10) 42 | 43 | - Remove outdated executable in favor of benchmark. 44 | 45 | # 0.1.0.0 (2021-09-07) 46 | 47 | - Release vector-hastables to the world. 48 | -------------------------------------------------------------------------------- /src/Data/Vector/Hashtables.hs: -------------------------------------------------------------------------------- 1 | {-| 2 | Module : Data.Vector.Hashtables 3 | Description : Provides hashtables, basic interface and set of utilities. 4 | Copyright : (c) klapaucius, swamp_agr, 2016-2021 5 | License : BSD3 6 | -} 7 | module Data.Vector.Hashtables 8 | ( -- * Documentation 9 | -- $doc 10 | 11 | -- ** Usage 12 | -- $usage 13 | 14 | -- ** Types 15 | Dictionary (..) 16 | , FrozenDictionary (..) 17 | , findElem 18 | 19 | -- ** Construction 20 | , initialize 21 | , clone 22 | 23 | -- ** Basic interface 24 | , null 25 | , size 26 | , keys 27 | , values 28 | , lookup 29 | , lookup' 30 | , insert 31 | , delete 32 | , upsert 33 | , alter 34 | , alterM 35 | , findEntry 36 | 37 | -- ** Combine 38 | 39 | -- *** Union 40 | , union 41 | , unionWith 42 | , unionWithKey 43 | 44 | -- *** Difference 45 | , difference 46 | , differenceWith 47 | 48 | -- *** Intersection 49 | , intersection 50 | , intersectionWith 51 | , intersectionWithKey 52 | 53 | -- ** Conversions 54 | 55 | -- *** Mutable 56 | , unsafeFreeze 57 | , unsafeThaw 58 | 59 | -- *** List 60 | , fromList 61 | , toList 62 | 63 | -- ** Low-level interface 64 | , Dictionary_ (..) 65 | , findEntry_ 66 | 67 | , module Control.Monad.Primitive 68 | ) where 69 | 70 | import Prelude hiding (null, lookup) 71 | import Control.Monad.Primitive 72 | import Data.Vector.Hashtables.Internal 73 | 74 | -- $doc 75 | -- 76 | -- - This package provides hashtable implementation similar to .NET Generic Dictionary implementation (at the time of 2015) . 77 | -- 78 | -- - It was originated as response to . 79 | -- 80 | -- - For more hashtables implementations see . 81 | 82 | -- $usage 83 | -- 84 | -- >>> import qualified Data.Vector.Storable.Mutable as VM 85 | -- >>> import qualified Data.Vector.Unboxed.Mutable as UM 86 | -- >>> import Data.Vector.Hashtables 87 | -- >>> type HashTable k v = Dictionary (PrimState IO) VM.MVector k UM.MVector v 88 | -- >>> ht <- initialize 0 :: IO (HashTable Int Int) 89 | -- >>> insert ht 0 1 90 | -- 91 | -------------------------------------------------------------------------------- /vector-hashtables.cabal: -------------------------------------------------------------------------------- 1 | cabal-version: 2.0 2 | name: vector-hashtables 3 | version: 0.1.2.1 4 | synopsis: Efficient vector-based mutable hashtables implementation. 5 | description: 6 | This package provides efficient vector-based hashtable implementation similar to .NET Generic Dictionary implementation (at the time of 2015). 7 | . 8 | See "Data.Vector.Hashtables" for documentation. 9 | homepage: https://github.com/klapaucius/vector-hashtables#readme 10 | license: BSD3 11 | license-file: LICENSE 12 | author: klapaucius 13 | maintainer: klapaucius, swamp_agr, ArtemPelenitsyn 14 | copyright: 2016-2024 klapaucius, swamp_agr 15 | category: Data 16 | build-type: Simple 17 | extra-doc-files: README.md, 18 | changelog.md 19 | extra-source-files: gen/GenPrimes.hs 20 | tested-with: 21 | GHC == 9.12.2 22 | GHC == 9.10.2 23 | GHC == 9.8.4 24 | GHC == 9.6.7 25 | GHC == 9.4.8 26 | GHC == 9.2.8 27 | GHC == 9.0.2 28 | GHC == 8.10.7 29 | GHC == 8.8.4 30 | GHC == 8.6.5 31 | 32 | library 33 | hs-source-dirs: src 34 | exposed-modules: Data.Vector.Hashtables, 35 | Data.Vector.Hashtables.Internal, 36 | Data.Vector.Hashtables.Internal.Mask, 37 | Data.Primitive.PrimArray.Utils 38 | ghc-options: -O2 39 | build-depends: base >= 4.7 && < 5 40 | , primitive >= 0.7.1.0 41 | , vector 42 | , hashable 43 | default-language: Haskell2010 44 | 45 | benchmark vector-hashtables-bench 46 | type: exitcode-stdio-1.0 47 | hs-source-dirs: bench 48 | main-is: Main.hs 49 | ghc-options: -O2 -rtsopts 50 | build-depends: base 51 | , vector-hashtables 52 | , vector 53 | , primitive 54 | , criterion 55 | , hashtables 56 | , unordered-containers 57 | default-language: Haskell2010 58 | 59 | test-suite vector-hashtables-test 60 | type: exitcode-stdio-1.0 61 | hs-source-dirs: test 62 | main-is: Spec.hs 63 | ghc-options: -threaded -rtsopts -with-rtsopts=-N 64 | default-language: Haskell2010 65 | other-modules: Data.Vector.HashTablesSpec 66 | build-depends: base 67 | , primitive 68 | , containers 69 | , hashable 70 | , vector 71 | , vector-hashtables 72 | 73 | -- Additional dependencies 74 | build-depends: 75 | hspec >= 2.6.0 && < 2.12 76 | , QuickCheck >= 2.12.6.1 && < 2.17 77 | , quickcheck-instances >= 0.3.19 && < 0.4 78 | 79 | build-tool-depends: 80 | hspec-discover:hspec-discover >= 2.6.0 && < 2.12 81 | 82 | source-repository head 83 | type: git 84 | location: https://github.com/klapaucius/vector-hashtables 85 | -------------------------------------------------------------------------------- /scripts/Plot.hs: -------------------------------------------------------------------------------- 1 | #! /usr/bin/env cabal 2 | {- cabal: 3 | build-depends: base, bytestring, cassava, Chart, Chart-diagrams, containers, split, text, vector 4 | -} 5 | 6 | {-# LANGUAGE OverloadedStrings #-} 7 | {-# LANGUAGE ScopedTypeVariables #-} 8 | {-# LANGUAGE LambdaCase #-} 9 | {-# LANGUAGE BlockArguments #-} 10 | 11 | import qualified Data.ByteString.Lazy as BL 12 | import Data.Csv hiding ((.=)) 13 | import qualified Data.Vector as V 14 | import Data.Text (Text) 15 | import qualified Data.Text as T 16 | import Data.List.Split (splitOn) 17 | import Data.Maybe (mapMaybe) 18 | import qualified Data.Map as Map 19 | import Data.Functor (void) 20 | import Graphics.Rendering.Chart.Easy 21 | import Graphics.Rendering.Chart.Backend.Diagrams 22 | 23 | -- | Represents a single data point extracted from the CSV. 24 | data PlotPoint = PlotPoint 25 | { ppExperiment :: Text -- ^ Experiment name (find, insert, etc). 26 | , ppBaseline :: Text -- ^ Baseline name. 27 | , ppN :: Double -- ^ Number of elements in the experiment (X-axis). 28 | , ppValue :: Double -- ^ Time measurement (Y-axis). 29 | , ppStdev :: Double -- ^ Standard deviation of the measurement. 30 | } deriving (Show) 31 | 32 | -- | A helper type to decode the one row (= 7 columns) of the CSV. 33 | type CsvRow = (Text, Double, Double, Double, Double, Double, Double) 34 | 35 | type SeriesData = (Double, Double, Double) -- (n, time, stdev) 36 | 37 | -- | Parses the "Comparison/..." string and creates a PlotPoint. 38 | -- Returns Nothing if the string format is invalid. 39 | parsePlotPoint :: CsvRow -> Maybe PlotPoint 40 | parsePlotPoint (key, val, _, _, stdev, _, _) = 41 | case splitOn "/" (T.unpack key) of 42 | ["Comparison", nStr, expName, baseName] -> 43 | case reads nStr of 44 | [(n, "")] -> Just $ PlotPoint (T.pack expName) (T.pack baseName) n val stdev 45 | _ -> Nothing -- 'n' is not a valid integer 46 | _ -> Nothing -- The key format is wrong 47 | 48 | -- | Reads and parses the CSV file from the given path. 49 | -- It only decodes the first two columns and skips rows that don't match the format. 50 | readCsvData :: FilePath -> IO [PlotPoint] 51 | readCsvData path = do 52 | csvData <- BL.readFile path 53 | case decode HasHeader csvData of 54 | Left err -> do 55 | putStrLn $ "Error parsing CSV: " ++ err 56 | return [] 57 | Right (rows :: V.Vector CsvRow) -> 58 | return $ mapMaybe parsePlotPoint (V.toList rows) 59 | 60 | -- | Groups the data points first by experiment name, then by baseline name. 61 | -- The result is a map where each key is an experiment, and the value is 62 | -- another map of baselines to their corresponding (x, y) data series. 63 | groupData :: [PlotPoint] -> Map.Map Text (Map.Map Text [SeriesData]) 64 | groupData = foldr addPoint Map.empty 65 | where 66 | addPoint (PlotPoint expName baseName n val stdev) = 67 | Map.alter (Just . addBaselineData) expName 68 | where 69 | addBaselineData Nothing = Map.singleton baseName [(n, val, stdev)] 70 | addBaselineData (Just baselineMap) = 71 | Map.alter (Just . addDataPoint) baseName baselineMap 72 | addDataPoint Nothing = [(n, val, stdev)] 73 | addDataPoint (Just series) = (n, val, stdev) : series 74 | 75 | mycolors :: String -> Colour Double 76 | mycolors = \case 77 | "hashtables" -> green 78 | "hashtables basic" -> darkgreen 79 | "vector-hashtables" -> orange 80 | "vector-hashtables unboxed" -> red 81 | "vector-hashtables unboxed keys" -> indianred 82 | "vector-hashtables boxed" -> darkkhaki 83 | "vector-hashtables (frozen)" -> sienna 84 | "mutable vector boxed" -> dodgerblue 85 | "mutable vector" -> darkorchid 86 | b -> error $ "mycolors: Unknown baseline: " ++ show b 87 | 88 | -- | Generates a plot for a single experiment and saves it to a PNG file. 89 | generatePlot :: Text -> Map.Map Text [SeriesData] -> IO () 90 | generatePlot experimentName baselineData = do 91 | let fileName = T.unpack (sanitizeName experimentName) ++ ".svg" 92 | toFile (def {_fo_format = SVG_EMBEDDED} {- default is PNG -}) fileName $ do 93 | layout_title .= T.unpack experimentName 94 | layout_x_axis . laxis_title .= "# elements" 95 | layout_x_axis . laxis_generate .= autoScaledLogAxis def 96 | layout_y_axis . laxis_title .= "time (s)" 97 | layout_y_axis . laxis_generate .= autoScaledLogAxis def 98 | 99 | setShapes $ repeat PointShapeCross 100 | -- Create a line plot for each baseline 101 | mapM_ (\(baseline, series') -> do 102 | let color = mycolors (T.unpack baseline) 103 | series = map (\(n,t,_)->(n,t)) series' 104 | setColors [opaque color] 105 | plot (line (T.unpack baseline) [series]) 106 | plot $ liftEC do 107 | plot_fillbetween_style .= solidFillStyle (withOpacity color 0.4) 108 | plot_fillbetween_values .= [(n, (time - stdev, time + stdev)) | (n, time, stdev) <- series'] 109 | plot_fillbetween_title .= (T.unpack baseline) ++ " (st. dev.)" 110 | 111 | setColors [opaque red] 112 | plot (points "" series) 113 | ) 114 | (Map.toList baselineData) 115 | 116 | sanitizeName :: Text -> Text 117 | sanitizeName 118 | = T.replace " " "_" 119 | . T.replace "(" "_" 120 | . T.replace ")" "_" 121 | 122 | main :: IO () 123 | main = do 124 | putStrLn "Processing CSV file: results.csv" 125 | points <- readCsvData "results.csv" 126 | 127 | if null points 128 | then putStrLn "No valid data points found. Exiting." 129 | else do 130 | let grouped = groupData points 131 | putStrLn $ "Found data for experiments: " ++ show (Map.keys grouped) 132 | 133 | void $ Map.traverseWithKey generatePlot grouped 134 | 135 | putStrLn "Plots generated successfully." 136 | -------------------------------------------------------------------------------- /.github/workflows/haskell-ci.yml: -------------------------------------------------------------------------------- 1 | # This GitHub workflow config has been generated by a script via 2 | # 3 | # haskell-ci 'github' 'vector-hashtables.cabal' 4 | # 5 | # To regenerate the script (for example after adjusting tested-with) run 6 | # 7 | # haskell-ci regenerate 8 | # 9 | # For more information, see https://github.com/haskell-CI/haskell-ci 10 | # 11 | # version: 0.19.20250531 12 | # 13 | # REGENDATA ("0.19.20250531",["github","vector-hashtables.cabal"]) 14 | # 15 | name: Haskell-CI 16 | on: 17 | - push 18 | - pull_request 19 | jobs: 20 | linux: 21 | name: Haskell-CI - Linux - ${{ matrix.compiler }} 22 | runs-on: ubuntu-24.04 23 | timeout-minutes: 24 | 60 25 | container: 26 | image: buildpack-deps:jammy 27 | continue-on-error: ${{ matrix.allow-failure }} 28 | strategy: 29 | matrix: 30 | include: 31 | - compiler: ghc-9.12.2 32 | compilerKind: ghc 33 | compilerVersion: 9.12.2 34 | setup-method: ghcup 35 | allow-failure: false 36 | - compiler: ghc-9.10.2 37 | compilerKind: ghc 38 | compilerVersion: 9.10.2 39 | setup-method: ghcup 40 | allow-failure: false 41 | - compiler: ghc-9.8.4 42 | compilerKind: ghc 43 | compilerVersion: 9.8.4 44 | setup-method: ghcup 45 | allow-failure: false 46 | - compiler: ghc-9.6.7 47 | compilerKind: ghc 48 | compilerVersion: 9.6.7 49 | setup-method: ghcup 50 | allow-failure: false 51 | - compiler: ghc-9.4.8 52 | compilerKind: ghc 53 | compilerVersion: 9.4.8 54 | setup-method: ghcup 55 | allow-failure: false 56 | - compiler: ghc-9.2.8 57 | compilerKind: ghc 58 | compilerVersion: 9.2.8 59 | setup-method: ghcup 60 | allow-failure: false 61 | - compiler: ghc-9.0.2 62 | compilerKind: ghc 63 | compilerVersion: 9.0.2 64 | setup-method: ghcup 65 | allow-failure: false 66 | - compiler: ghc-8.10.7 67 | compilerKind: ghc 68 | compilerVersion: 8.10.7 69 | setup-method: ghcup 70 | allow-failure: false 71 | - compiler: ghc-8.8.4 72 | compilerKind: ghc 73 | compilerVersion: 8.8.4 74 | setup-method: ghcup 75 | allow-failure: false 76 | - compiler: ghc-8.6.5 77 | compilerKind: ghc 78 | compilerVersion: 8.6.5 79 | setup-method: ghcup 80 | allow-failure: false 81 | fail-fast: false 82 | steps: 83 | - name: apt-get install 84 | run: | 85 | apt-get update 86 | apt-get install -y --no-install-recommends gnupg ca-certificates dirmngr curl git software-properties-common libtinfo5 87 | - name: Install GHCup 88 | run: | 89 | mkdir -p "$HOME/.ghcup/bin" 90 | curl -sL https://downloads.haskell.org/ghcup/0.1.50.1/x86_64-linux-ghcup-0.1.50.1 > "$HOME/.ghcup/bin/ghcup" 91 | chmod a+x "$HOME/.ghcup/bin/ghcup" 92 | - name: Install cabal-install 93 | run: | 94 | "$HOME/.ghcup/bin/ghcup" install cabal 3.14.2.0 || (cat "$HOME"/.ghcup/logs/*.* && false) 95 | echo "CABAL=$HOME/.ghcup/bin/cabal-3.14.2.0 -vnormal+nowrap" >> "$GITHUB_ENV" 96 | - name: Install GHC (GHCup) 97 | if: matrix.setup-method == 'ghcup' 98 | run: | 99 | "$HOME/.ghcup/bin/ghcup" install ghc "$HCVER" || (cat "$HOME"/.ghcup/logs/*.* && false) 100 | HC=$("$HOME/.ghcup/bin/ghcup" whereis ghc "$HCVER") 101 | HCPKG=$(echo "$HC" | sed 's#ghc$#ghc-pkg#') 102 | HADDOCK=$(echo "$HC" | sed 's#ghc$#haddock#') 103 | echo "HC=$HC" >> "$GITHUB_ENV" 104 | echo "HCPKG=$HCPKG" >> "$GITHUB_ENV" 105 | echo "HADDOCK=$HADDOCK" >> "$GITHUB_ENV" 106 | env: 107 | HCKIND: ${{ matrix.compilerKind }} 108 | HCNAME: ${{ matrix.compiler }} 109 | HCVER: ${{ matrix.compilerVersion }} 110 | - name: Set PATH and environment variables 111 | run: | 112 | echo "$HOME/.cabal/bin" >> $GITHUB_PATH 113 | echo "LANG=C.UTF-8" >> "$GITHUB_ENV" 114 | echo "CABAL_DIR=$HOME/.cabal" >> "$GITHUB_ENV" 115 | echo "CABAL_CONFIG=$HOME/.cabal/config" >> "$GITHUB_ENV" 116 | HCNUMVER=$(${HC} --numeric-version|perl -ne '/^(\d+)\.(\d+)\.(\d+)(\.(\d+))?$/; print(10000 * $1 + 100 * $2 + ($3 == 0 ? $5 != 1 : $3))') 117 | echo "HCNUMVER=$HCNUMVER" >> "$GITHUB_ENV" 118 | echo "ARG_TESTS=--enable-tests" >> "$GITHUB_ENV" 119 | echo "ARG_BENCH=--enable-benchmarks" >> "$GITHUB_ENV" 120 | echo "HEADHACKAGE=false" >> "$GITHUB_ENV" 121 | echo "ARG_COMPILER=--$HCKIND --with-compiler=$HC" >> "$GITHUB_ENV" 122 | env: 123 | HCKIND: ${{ matrix.compilerKind }} 124 | HCNAME: ${{ matrix.compiler }} 125 | HCVER: ${{ matrix.compilerVersion }} 126 | - name: env 127 | run: | 128 | env 129 | - name: write cabal config 130 | run: | 131 | mkdir -p $CABAL_DIR 132 | cat >> $CABAL_CONFIG <> $CABAL_CONFIG < cabal-plan.xz 165 | echo 'f62ccb2971567a5f638f2005ad3173dba14693a45154c1508645c52289714cb2 cabal-plan.xz' | sha256sum -c - 166 | xz -d < cabal-plan.xz > $HOME/.cabal/bin/cabal-plan 167 | rm -f cabal-plan.xz 168 | chmod a+x $HOME/.cabal/bin/cabal-plan 169 | cabal-plan --version 170 | - name: checkout 171 | uses: actions/checkout@v4 172 | with: 173 | path: source 174 | - name: initial cabal.project for sdist 175 | run: | 176 | touch cabal.project 177 | echo "packages: $GITHUB_WORKSPACE/source/." >> cabal.project 178 | cat cabal.project 179 | - name: sdist 180 | run: | 181 | mkdir -p sdist 182 | $CABAL sdist all --output-dir $GITHUB_WORKSPACE/sdist 183 | - name: unpack 184 | run: | 185 | mkdir -p unpacked 186 | find sdist -maxdepth 1 -type f -name '*.tar.gz' -exec tar -C $GITHUB_WORKSPACE/unpacked -xzvf {} \; 187 | - name: generate cabal.project 188 | run: | 189 | PKGDIR_vector_hashtables="$(find "$GITHUB_WORKSPACE/unpacked" -maxdepth 1 -type d -regex '.*/vector-hashtables-[0-9.]*')" 190 | echo "PKGDIR_vector_hashtables=${PKGDIR_vector_hashtables}" >> "$GITHUB_ENV" 191 | rm -f cabal.project cabal.project.local 192 | touch cabal.project 193 | touch cabal.project.local 194 | echo "packages: ${PKGDIR_vector_hashtables}" >> cabal.project 195 | echo "package vector-hashtables" >> cabal.project 196 | echo " ghc-options: -Werror=missing-methods" >> cabal.project 197 | cat >> cabal.project <> cabal.project.local 200 | cat cabal.project 201 | cat cabal.project.local 202 | - name: dump install plan 203 | run: | 204 | $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH --dry-run all 205 | cabal-plan 206 | - name: restore cache 207 | uses: actions/cache/restore@v4 208 | with: 209 | key: ${{ runner.os }}-${{ matrix.compiler }}-${{ github.sha }} 210 | path: ~/.cabal/store 211 | restore-keys: ${{ runner.os }}-${{ matrix.compiler }}- 212 | - name: install dependencies 213 | run: | 214 | $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks --dependencies-only -j2 all 215 | $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH --dependencies-only -j2 all 216 | - name: build w/o tests 217 | run: | 218 | $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks all 219 | - name: build 220 | run: | 221 | $CABAL v2-build $ARG_COMPILER $ARG_TESTS $ARG_BENCH all --write-ghc-environment-files=always 222 | - name: tests 223 | run: | 224 | $CABAL v2-test $ARG_COMPILER $ARG_TESTS $ARG_BENCH all --test-show-details=direct 225 | - name: cabal check 226 | run: | 227 | cd ${PKGDIR_vector_hashtables} || false 228 | ${CABAL} -vnormal check 229 | - name: haddock 230 | run: | 231 | $CABAL v2-haddock --disable-documentation --haddock-all $ARG_COMPILER --with-haddock $HADDOCK $ARG_TESTS $ARG_BENCH all 232 | - name: unconstrained build 233 | run: | 234 | rm -f cabal.project.local 235 | $CABAL v2-build $ARG_COMPILER --disable-tests --disable-benchmarks all 236 | - name: save cache 237 | if: always() 238 | uses: actions/cache/save@v4 239 | with: 240 | key: ${{ runner.os }}-${{ matrix.compiler }}-${{ github.sha }} 241 | path: ~/.cabal/store 242 | -------------------------------------------------------------------------------- /bench/Main.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE BangPatterns #-} 2 | {-# LANGUAGE TypeFamilies #-} 3 | 4 | module Main (main) where 5 | 6 | import qualified Data.Vector.Storable as V 7 | import qualified Data.Vector.Storable.Mutable as VM 8 | import qualified Data.Vector.Mutable as BV 9 | import Control.Monad.Primitive (PrimMonad(PrimState)) 10 | import qualified Data.HashTable.IO as H 11 | 12 | import Criterion.Main (bench, bgroup, defaultMain, nfIO) 13 | import Criterion (Benchmark) 14 | 15 | import qualified Data.Vector.Hashtables.Internal as VH 16 | 17 | vh :: Int -> IO (VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int) 18 | vh n = do 19 | ht <- VH.initialize n :: IO (VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int) 20 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 21 | | otherwise = return () 22 | go 0 23 | return ht 24 | 25 | fvh :: Int -> IO (VH.FrozenDictionary V.Vector Int V.Vector Int) 26 | fvh n = do 27 | h <- vh n 28 | c <- VH.clone h 29 | VH.unsafeFreeze c 30 | 31 | bh :: Int -> IO (H.BasicHashTable Int Int) 32 | bh n = do 33 | ht <- H.newSized n :: IO (H.BasicHashTable Int Int) 34 | let go !i | i <= n = H.insert ht i i >> go (i + 1) 35 | | otherwise = return () 36 | go 0 37 | return ht 38 | 39 | fl :: Int -> [(Int, Int)] 40 | fl n = mkPair <$> [0 .. n] 41 | where 42 | mkPair !x = (x, x) 43 | 44 | vhfind :: Int -> VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int -> IO Int 45 | vhfind n ht = do 46 | let go !i !s | i <= n = do 47 | x <- VH.findEntry ht i 48 | go (i + 1) (s + x) 49 | | otherwise = return s 50 | go 0 0 51 | 52 | fvhfind :: Int -> VH.FrozenDictionary V.Vector Int V.Vector Int -> IO Int 53 | fvhfind n ht = return $ go 0 0 where 54 | go !i !s | i <= n = go (i + 1) (s + VH.findElem ht i) 55 | | otherwise = s 56 | 57 | bhfind :: Int -> H.BasicHashTable Int Int -> IO Int 58 | bhfind n ht = do 59 | let go !i !s | i <= n = do 60 | Just x <- H.lookup ht i 61 | go (i + 1) (s + x) 62 | | otherwise = return s 63 | go 0 0 64 | 65 | htb :: Int -> IO () 66 | htb n = do 67 | ht <- H.newSized n :: IO (H.BasicHashTable Int Int) 68 | let go !i | i <= n = H.insert ht i i >> go (i + 1) 69 | | otherwise = return () 70 | go 0 71 | 72 | 73 | vht :: Int -> IO () 74 | vht n = do 75 | ht <- VH.initialize n :: IO (VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int) 76 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 77 | | otherwise = return () 78 | go 0 79 | 80 | vhtd :: Int -> IO () 81 | vhtd n = do 82 | ht <- VH.initialize n :: IO (VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int) 83 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 84 | | otherwise = return () 85 | go 0 86 | let go1 !i | i <= n = VH.delete ht i >> go1 (i + 1) 87 | | otherwise = return () 88 | go1 0 89 | 90 | htbd :: Int -> IO () 91 | htbd n = do 92 | ht <- H.newSized n :: IO (H.BasicHashTable Int Int) 93 | let go !i | i <= n = H.insert ht i i >> go (i + 1) 94 | | otherwise = return () 95 | go 0 96 | let go1 !i | i <= n = H.delete ht i >> go1 (i + 1) 97 | | otherwise = return () 98 | go1 0 99 | 100 | vhtb :: Int -> IO () 101 | vhtb n = do 102 | ht <- VH.initialize n :: IO (VH.Dictionary (PrimState IO) BV.MVector Int BV.MVector Int) 103 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 104 | | otherwise = return () 105 | go 0 106 | 107 | vhtk :: Int -> IO () 108 | vhtk n = do 109 | ht <- VH.initialize n :: IO (VH.Dictionary (PrimState IO) VM.MVector Int BV.MVector Int) 110 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 111 | | otherwise = return () 112 | go 0 113 | 114 | htbg :: Int -> IO () 115 | htbg n = do 116 | ht <- H.newSized 1 :: IO (H.BasicHashTable Int Int) 117 | let go !i | i <= n = H.insert ht i i >> go (i + 1) 118 | | otherwise = return () 119 | go 0 120 | 121 | vhtg :: Int -> IO () 122 | vhtg n = do 123 | ht <- VH.initialize 1 :: IO (VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int) 124 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 125 | | otherwise = return () 126 | go 0 127 | 128 | vhtbg :: Int -> IO () 129 | vhtbg n = do 130 | ht <- VH.initialize 1 :: IO (VH.Dictionary (PrimState IO) BV.MVector Int BV.MVector Int) 131 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 132 | | otherwise = return () 133 | go 0 134 | 135 | vhtkg :: Int -> IO () 136 | vhtkg n = do 137 | ht <- VH.initialize 1 :: IO (VH.Dictionary (PrimState IO) VM.MVector Int BV.MVector Int) 138 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 139 | | otherwise = return () 140 | go 0 141 | 142 | mvb :: Int -> IO () 143 | mvb n = do 144 | ht <- BV.new (n+1) 145 | let go !i | i <= n = BV.write ht i i >> go (i + 1) 146 | | otherwise = return () 147 | go 0 148 | 149 | mv :: Int -> IO () 150 | mv n = do 151 | ht <- VM.new (n+1) 152 | let go !i | i <= n = VM.write ht i i >> go (i + 1) 153 | | otherwise = return () 154 | go 0 155 | 156 | bhfromList l = do 157 | _bht <- H.fromList l :: IO (H.BasicHashTable Int Int) 158 | return () 159 | 160 | vhfromList l = do 161 | _ht <- VH.fromList l :: IO (VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int) 162 | return () 163 | 164 | bhlookupIndex :: Int -> H.BasicHashTable Int Int -> IO Int 165 | bhlookupIndex n ht = do 166 | let go !i !s | i <= n = do 167 | Just x <- H.lookupIndex ht i 168 | go (i + 1) (s + fromIntegral x) 169 | | otherwise = return s 170 | go 0 0 171 | 172 | vhlookupIndex :: Int -> VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int -> IO Int 173 | vhlookupIndex n ht = do 174 | let go !i !s | i <= n = do 175 | Just x <- VH.lookupIndex ht i 176 | go (i + 1) (s + x) 177 | | otherwise = return s 178 | go 0 0 179 | 180 | bhtoList = H.toList 181 | 182 | vhtoList = VH.toList 183 | 184 | bgc :: Int -> IO Benchmark 185 | bgc n = do 186 | h <- vh n 187 | h2 <- bh n 188 | fh <- fvh n 189 | let l = fl n 190 | return $ bgroup (show n) 191 | [ bgroup "insert" 192 | [ bench "hashtables basic" $ nfIO (htb n) 193 | , bench "vector-hashtables boxed" $ nfIO (vhtb n) 194 | , bench "vector-hashtables unboxed keys" $ nfIO (vhtk n) 195 | , bench "vector-hashtables" $ nfIO (vht n) 196 | , bench "mutable vector boxed" $ nfIO (mvb n) 197 | , bench "mutable vector" $ nfIO (mv n) ] 198 | , bgroup "insert (resize)" 199 | [ bench "hashtables basic" $ nfIO (htbg n) 200 | , bench "vector-hashtables boxed" $ nfIO (vhtbg n) 201 | , bench "vector-hashtables unboxed keys" $ nfIO (vhtkg n) 202 | , bench "vector-hashtables" $ nfIO (vhtg n) ] 203 | , bgroup "insert, delete" 204 | [ bench "hashtables basic" $ nfIO (htbd n) 205 | , bench "vector-hashtables" $ nfIO (vhtd n) ] 206 | , bgroup "find" 207 | [ bench "hashtables basic" $ nfIO (bhfind n h2) 208 | , bench "vector-hashtables" $ nfIO (vhfind n h) 209 | , bench "vector-hashtables (frozen)" $ nfIO (fvhfind n fh) ] 210 | , bgroup "lookupIndex" 211 | [ bench "hashtables basic" $ nfIO (bhlookupIndex n h2) 212 | , bench "vector-hashtables" $ nfIO (vhlookupIndex n h) ] 213 | , bgroup "fromList" 214 | [ bench "hashtables basic" $ nfIO (bhfromList l) 215 | , bench "vector-hashtables" $ nfIO (vhfromList l) ] 216 | , bgroup "toList" 217 | [ bench "hashtables basic" $ nfIO (bhtoList h2) 218 | , bench "vector-hashtables" $ nfIO (vhtoList h) ]] 219 | 220 | main :: IO () 221 | main = do 222 | let inputs = [1000,10000,100000,1000000] 223 | comparisonBench <- mapM bgc inputs 224 | utilitiesBench <- mapM utilities inputs 225 | defaultMain 226 | [ bgroup "Comparison" comparisonBench 227 | , bgroup "Utilities" utilitiesBench ] 228 | 229 | -- ** Utilities benchmark 230 | 231 | utilities n = do 232 | -- utilities input data 233 | hAt' <- vh n 234 | hInsert <- vh n 235 | hDelete <- vh n 236 | hLookup <- vh n 237 | hLookup' <- vh n 238 | hLookupIndex <- vh n 239 | hNull <- vh n 240 | hLength <- vh n 241 | hSize <- vh n 242 | hMember <- vh n 243 | hFindWithDefault <- vh n 244 | hUpsert <- vh n 245 | hAlter <- vh n 246 | hAlterM <- vh n 247 | hUnion1 <- vh n 248 | hUnion2 <- vh n 249 | hDifference1 <- vh n 250 | hDifference2 <- vh n 251 | hIntersection1 <- vh n 252 | hIntersection2 <- vh n 253 | hFromList <- VH.toList =<< vh n 254 | hToList <- vh n 255 | 256 | return $ bgroup (show n) 257 | [ bench "at'" $ nfIO (bhuat' n hAt') 258 | , bench "insert" $ nfIO (bhuinsert n hInsert) 259 | , bench "delete" $ nfIO (bhudelete n hDelete) 260 | , bench "lookup" $ nfIO (bhulookup n hLookup) 261 | , bench "lookup'" $ nfIO (bhulookup' n hLookup') 262 | , bench "lookupIndex" $ nfIO (bhulookupIndex n hLookupIndex) 263 | , bench "null" $ nfIO (bhunull hNull) 264 | , bench "length" $ nfIO (bhulength hLength) 265 | , bench "size" $ nfIO (bhusize hSize) 266 | , bench "member" $ nfIO (bhumember n hMember) 267 | , bench "findWithDefault" $ nfIO (bhufindWithDefault n hFindWithDefault) 268 | , bench "upsert" $ nfIO (bhuupsert n hUpsert) 269 | , bench "alter" $ nfIO (bhualter n hAlter) 270 | , bench "alterM" $ nfIO (bhualterM n hAlterM) 271 | , bench "union" $ nfIO (bhuunion hUnion1 hUnion2) 272 | , bench "difference" $ nfIO (bhudifference hDifference1 hDifference2) 273 | , bench "intersection" $ nfIO (bhuintersection hIntersection1 hIntersection2) 274 | , bench "fromList" $ nfIO (bhufromList hFromList) 275 | , bench "toList" $ nfIO (VH.toList hToList) ] 276 | 277 | bhuat' n ht = do 278 | let go !i | i <= n = VH.at' ht i >> go (i + 1) 279 | | otherwise = return () 280 | go 0 281 | 282 | bhuinsert n ht = do 283 | let go !i | i <= n = VH.insert ht i i >> go (i + 1) 284 | | otherwise = return () 285 | go 0 286 | 287 | bhudelete n ht = do 288 | let go !i | i <= n = VH.delete ht i >> go (i + 1) 289 | | otherwise = return () 290 | go 0 291 | 292 | bhulookup n ht = do 293 | let go !i | i <= n = VH.lookup ht i >> go (i + 1) 294 | | otherwise = return () 295 | go 0 296 | 297 | bhulookup' n ht = do 298 | let go !i | i <= n = VH.lookup' ht i >> go (i + 1) 299 | | otherwise = return () 300 | go 0 301 | 302 | bhulookupIndex n ht = do 303 | let go !i | i <= n = VH.lookupIndex ht i >> go (i + 1) 304 | | otherwise = return () 305 | go 0 306 | 307 | bhunull = VH.null 308 | 309 | bhulength = VH.length 310 | 311 | bhusize = VH.size 312 | 313 | bhumember n ht = do 314 | let go !i | i <= n = VH.member ht i >> go (i + 1) 315 | | otherwise = return () 316 | go 0 317 | 318 | bhufindWithDefault n ht = do 319 | let go !i | i <= n = VH.findWithDefault ht 0 i >> go (i + 1) 320 | | otherwise = return () 321 | go 0 322 | 323 | bhuupsert n ht = do 324 | let go !i | i <= n = VH.upsert ht (maybe minBound succ) i >> go (i + 1) 325 | | otherwise = return () 326 | go 0 327 | 328 | bhualter n ht = do 329 | let go !i | i <= n = VH.alter ht (fmap succ) i >> go (i + 1) 330 | | otherwise = return () 331 | go 0 332 | 333 | bhualterM :: Int -> VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int -> IO () 334 | bhualterM n ht = do 335 | let f = return . fmap succ 336 | go !i | i <= n = VH.alterM ht f i >> go (i + 1) 337 | | otherwise = return () 338 | go 0 339 | 340 | bhuunion ht1 ht2 = VH.union ht1 ht2 >> return () 341 | 342 | bhudifference ht1 ht2 = VH.difference ht1 ht2 >> return () 343 | 344 | bhuintersection ht1 ht2 = VH.intersection ht1 ht2 >> return () 345 | 346 | bhufromList htlist = do 347 | ht <- VH.fromList htlist :: IO (VH.Dictionary (PrimState IO) VM.MVector Int VM.MVector Int) 348 | return () 349 | 350 | bhutoList ht = VH.toList ht >> return () 351 | -------------------------------------------------------------------------------- /README.md: -------------------------------------------------------------------------------- 1 | # vector-hashtables 2 | 3 | 4 | [![Hackage](https://img.shields.io/hackage/v/vector-hashtables.svg?label=Hackage)](https://hackage.haskell.org/package/vector-hashtables) 5 | [![Stackage Nightly Version](https://www.stackage.org/package/vector-hashtables/badge/nightly?label=Stackage/Nightly)](https://www.stackage.org/package/vector-hashtables) 6 | [![Stackage LTS Version](https://www.stackage.org/package/vector-hashtables/badge/lts?label=Stackage/LTS)](https://www.stackage.org/package/vector-hashtables) 7 | [![Build Status](https://github.com/klapaucius/vector-hashtables/workflows/Haskell-CI/badge.svg)](https://github.com/klapaucius/vector-hashtables/actions?query=workflow%3Ahaskell-ci) 8 | 9 | A brief history of this library is given in [this blog post](https://an-pro.org/posts/12-vector-hashtables.html). 10 | 11 | ## Benchmarks vs `hashtables` 12 | 13 | (and `vector` where relevant) 14 | 15 | Benchmarks below are produced under GHC 9.4.8, and can be reproduced locally with 16 | 17 | ```shellsession 18 | cabal bench --benchmark-options="--csv results.csv" 19 | bench-show report results.csv 20 | ``` 21 | (You will need the `bench-show` tool, which is available from Hackage.) 22 | 23 | You can also see the plots produced from the same numbers in [./charts/readme.md](./charts/readme.md). 24 | 25 | 26 | | Benchmark | v.0.1.1.4 (ns) | current (ns) | 27 | | ----------------------------------------------------------------- | ------------ | ------------ | 28 | | Comparison/1000/insert/hashtables basic | 36083.57 | 36907.68 | 29 | | Comparison/1000/insert/vector-hashtables boxed | 25735.13 | 17055.86 | 30 | | Comparison/1000/insert/vector-hashtables unboxed keys | 23601.08 | 15333.05 | 31 | | Comparison/1000/insert/vector-hashtables | 25298.67 | 13881.72 | 32 | | Comparison/1000/insert/mutable vector boxed | 6458.14 | 3658.16 | 33 | | Comparison/1000/insert/mutable vector | 2526.35 | 1282.13 | 34 | | Comparison/1000/insert (resize)/hashtables basic | 318207.51 | 159834.87 | 35 | | Comparison/1000/insert (resize)/vector-hashtables boxed | 106490.84 | 25900.28 | 36 | | Comparison/1000/insert (resize)/vector-hashtables unboxed keys | 66848.40 | 25382.56 | 37 | | Comparison/1000/insert (resize)/vector-hashtables | 65694.66 | 21393.31 | 38 | | Comparison/1000/insert, delete/hashtables basic | 96776.41 | 72615.51 | 39 | | Comparison/1000/insert, delete/vector-hashtables | 79701.44 | 20920.26 | 40 | | Comparison/1000/find/hashtables basic | 22841.85 | 23678.93 | 41 | | Comparison/1000/find/vector-hashtables | 16398.19 | 5586.93 | 42 | | Comparison/1000/find/vector-hashtables (frozen) | 11967.63 | 3128.18 | 43 | | Comparison/1000/lookupIndex/hashtables basic | 19744.27 | 19209.79 | 44 | | Comparison/1000/lookupIndex/vector-hashtables | 13624.09 | 4978.75 | 45 | | Comparison/1000/fromList/hashtables basic | 167277.66 | 162920.75 | 46 | | Comparison/1000/fromList/vector-hashtables | 48670.75 | 25283.17 | 47 | | Comparison/1000/toList/hashtables basic | 9296.91 | 9286.65 | 48 | | Comparison/1000/toList/vector-hashtables | 9753.58 | 10022.51 | 49 | | Comparison/10000/insert/hashtables basic | 384031.02 | 373885.01 | 50 | | Comparison/10000/insert/vector-hashtables boxed | 246923.90 | 175892.73 | 51 | | Comparison/10000/insert/vector-hashtables unboxed keys | 229812.05 | 147689.46 | 52 | | Comparison/10000/insert/vector-hashtables | 216924.38 | 128417.71 | 53 | | Comparison/10000/insert/mutable vector boxed | 43104.20 | 42712.36 | 54 | | Comparison/10000/insert/mutable vector | 12298.81 | 12193.85 | 55 | | Comparison/10000/insert (resize)/hashtables basic | 1342541.64 | 1378595.70 | 56 | | Comparison/10000/insert (resize)/vector-hashtables boxed | 487188.49 | 273187.43 | 57 | | Comparison/10000/insert (resize)/vector-hashtables unboxed keys | 441635.60 | 242659.06 | 58 | | Comparison/10000/insert (resize)/vector-hashtables | 412651.12 | 188011.22 | 59 | | Comparison/10000/insert, delete/hashtables basic | 722883.16 | 736250.66 | 60 | | Comparison/10000/insert, delete/vector-hashtables | 407113.19 | 200643.92 | 61 | | Comparison/10000/find/hashtables basic | 228154.09 | 232874.24 | 62 | | Comparison/10000/find/vector-hashtables | 164343.06 | 55693.39 | 63 | | Comparison/10000/find/vector-hashtables (frozen) | 119669.00 | 31291.02 | 64 | | Comparison/10000/lookupIndex/hashtables basic | 197212.48 | 191707.57 | 65 | | Comparison/10000/lookupIndex/vector-hashtables | 136205.70 | 49762.50 | 66 | | Comparison/10000/fromList/hashtables basic | 1391968.88 | 1562065.86 | 67 | | Comparison/10000/fromList/vector-hashtables | 430590.93 | 233128.12 | 68 | | Comparison/10000/toList/hashtables basic | 112894.13 | 114543.83 | 69 | | Comparison/10000/toList/vector-hashtables | 152214.13 | 154034.89 | 70 | | Comparison/100000/insert/hashtables basic | 4492224.86 | 4546924.57 | 71 | | Comparison/100000/insert/vector-hashtables boxed | 2414664.98 | 1767261.44 | 72 | | Comparison/100000/insert/vector-hashtables unboxed keys | 2243027.45 | 1476174.02 | 73 | | Comparison/100000/insert/vector-hashtables | 2144269.70 | 1272101.52 | 74 | | Comparison/100000/insert/mutable vector boxed | 667945.33 | 666673.13 | 75 | | Comparison/100000/insert/mutable vector | 121264.87 | 123138.53 | 76 | | Comparison/100000/insert (resize)/hashtables basic | 18217163.16 | 18777839.68 | 77 | | Comparison/100000/insert (resize)/vector-hashtables boxed | 9452674.69 | 7287443.14 | 78 | | Comparison/100000/insert (resize)/vector-hashtables unboxed keys | 7721635.33 | 5698107.38 | 79 | | Comparison/100000/insert (resize)/vector-hashtables | 4722092.98 | 2574932.04 | 80 | | Comparison/100000/insert, delete/hashtables basic | 8699786.66 | 8790937.73 | 81 | | Comparison/100000/insert, delete/vector-hashtables | 4073127.47 | 2010559.30 | 82 | | Comparison/100000/find/hashtables basic | 2283995.01 | 2346364.66 | 83 | | Comparison/100000/find/vector-hashtables | 1676135.49 | 588427.30 | 84 | | Comparison/100000/find/vector-hashtables (frozen) | 1201572.29 | 319639.97 | 85 | | Comparison/100000/lookupIndex/hashtables basic | 1963727.73 | 1931036.13 | 86 | | Comparison/100000/lookupIndex/vector-hashtables | 1363501.76 | 499992.98 | 87 | | Comparison/100000/fromList/hashtables basic | 20681183.31 | 30059346.94 | 88 | | Comparison/100000/fromList/vector-hashtables | 5262183.79 | 3945839.47 | 89 | | Comparison/100000/toList/hashtables basic | 2675794.96 | 2702739.12 | 90 | | Comparison/100000/toList/vector-hashtables | 5155629.15 | 5118781.70 | 91 | | Comparison/1000000/insert/hashtables basic | 86723317.72 | 85752701.43 | 92 | | Comparison/1000000/insert/vector-hashtables boxed | 68162021.23 | 75667649.90 | 93 | | Comparison/1000000/insert/vector-hashtables unboxed keys | 50777620.44 | 46615543.58 | 94 | | Comparison/1000000/insert/vector-hashtables | 23334885.43 | 16025927.63 | 95 | | Comparison/1000000/insert/mutable vector boxed | 30281652.62 | 32068295.04 | 96 | | Comparison/1000000/insert/mutable vector | 1283399.43 | 1393859.51 | 97 | | Comparison/1000000/insert (resize)/hashtables basic | 228726522.46 | 282346897.14 | 98 | | Comparison/1000000/insert (resize)/vector-hashtables boxed | 104556190.01 | 84385042.40 | 99 | | Comparison/1000000/insert (resize)/vector-hashtables unboxed keys | 79183320.30 | 62413398.66 | 100 | | Comparison/1000000/insert (resize)/vector-hashtables | 45925222.08 | 28777902.04 | 101 | | Comparison/1000000/insert, delete/hashtables basic | 130189177.30 | 134399640.44 | 102 | | Comparison/1000000/insert, delete/vector-hashtables | 42722592.04 | 23648387.28 | 103 | | Comparison/1000000/find/hashtables basic | 23094297.73 | 24583079.42 | 104 | | Comparison/1000000/find/vector-hashtables | 16709242.48 | 6178348.57 | 105 | | Comparison/1000000/find/vector-hashtables (frozen) | 12176361.82 | 3425505.60 | 106 | | Comparison/1000000/lookupIndex/hashtables basic | 20222788.08 | 19753759.16 | 107 | | Comparison/1000000/lookupIndex/vector-hashtables | 14041315.59 | 5357116.98 | 108 | | Comparison/1000000/fromList/hashtables basic | 210947448.60 | 222974094.62 | 109 | | Comparison/1000000/fromList/vector-hashtables | 56875691.60 | 49212505.34 | 110 | | Comparison/1000000/toList/hashtables basic | 62256321.15 | 66351583.99 | 111 | | Comparison/1000000/toList/vector-hashtables | 95883670.57 | 98441804.39 | 112 | 113 |
Utilities benchmark: 114 | 115 | | Benchmark | v.0.1.1.4 (ns) | current (ns) | 116 | | --------- | -------------- | ------------ | 117 | | Utilities/1000/at' | 14554.08 | 4755.41 | 118 | | Utilities/1000/insert | 16704.55 | 6842.45 | 119 | | Utilities/1000/delete | 11166.80 | 3959.44 | 120 | | Utilities/1000/lookup | 14510.59 | 5161.87 | 121 | | Utilities/1000/lookup' | 14181.87 | 4739.19 | 122 | | Utilities/1000/lookupIndex | 17171.76 | 4196.40 | 123 | | Utilities/1000/null | 7.19 | 7.92 | 124 | | Utilities/1000/length | 7.31 | 7.41 | 125 | | Utilities/1000/size | 6.85 | 6.53 | 126 | | Utilities/1000/member | 17364.48 | 4344.27 | 127 | | Utilities/1000/findWithDefault | 15747.10 | 4802.97 | 128 | | Utilities/1000/upsert | 32633.25 | 12708.79 | 129 | | Utilities/1000/alter | 31908.54 | 11109.48 | 130 | | Utilities/1000/alterM | 32564.14 | 11110.53 | 131 | | Utilities/1000/union | 46432.10 | 29468.82 | 132 | | Utilities/1000/difference | 25741.68 | 16296.53 | 133 | | Utilities/1000/intersection | 58828.38 | 38587.57 | 134 | | Utilities/1000/fromList | 45355.85 | 26156.93 | 135 | | Utilities/1000/toList | 9626.89 | 10101.05 | 136 | | Utilities/10000/at' | 147509.66 | 48699.88 | 137 | | Utilities/10000/insert | 171201.56 | 68568.34 | 138 | | Utilities/10000/delete | 111650.42 | 39392.43 | 139 | | Utilities/10000/lookup | 149138.47 | 49800.41 | 140 | | Utilities/10000/lookup' | 144283.31 | 46886.69 | 141 | | Utilities/10000/lookupIndex | 172630.09 | 40088.94 | 142 | | Utilities/10000/null | 7.20 | 7.24 | 143 | | Utilities/10000/length | 7.30 | 6.77 | 144 | | Utilities/10000/size | 6.87 | 6.43 | 145 | | Utilities/10000/member | 170650.68 | 43369.07 | 146 | | Utilities/10000/findWithDefault | 157236.92 | 49471.03 | 147 | | Utilities/10000/upsert | 329212.06 | 125290.78 | 148 | | Utilities/10000/alter | 322814.62 | 111817.84 | 149 | | Utilities/10000/alterM | 330094.30 | 112444.63 | 150 | | Utilities/10000/union | 478541.46 | 329790.79 | 151 | | Utilities/10000/difference | 295042.17 | 193790.26 | 152 | | Utilities/10000/intersection | 644396.71 | 419483.32 | 153 | | Utilities/10000/fromList | 494164.34 | 331449.21 | 154 | | Utilities/10000/toList | 151375.79 | 167580.99 | 155 | | Utilities/100000/at' | 1491045.70 | 495418.68 | 156 | | Utilities/100000/insert | 1741058.94 | 765507.51 | 157 | | Utilities/100000/delete | 1127146.84 | 436707.82 | 158 | | Utilities/100000/lookup | 1601916.69 | 562205.51 | 159 | | Utilities/100000/lookup' | 1441526.57 | 488540.28 | 160 | | Utilities/100000/lookupIndex | 1763172.42 | 405596.28 | 161 | | Utilities/100000/null | 7.19 | 7.26 | 162 | | Utilities/100000/length | 7.38 | 7.17 | 163 | | Utilities/100000/size | 6.92 | 6.83 | 164 | | Utilities/100000/member | 1740066.09 | 464281.90 | 165 | | Utilities/100000/findWithDefault | 1577458.36 | 489790.85 | 166 | | Utilities/100000/upsert | 3383104.75 | 1265454.18 | 167 | | Utilities/100000/alter | 3329820.09 | 1211692.27 | 168 | | Utilities/100000/alterM | 3356140.57 | 1220060.24 | 169 | | Utilities/100000/union | 5563999.76 | 3705665.39 | 170 | | Utilities/100000/difference | 6372930.19 | 5630405.29 | 171 | | Utilities/100000/intersection | 12353680.59 | 9595098.36 | 172 | | Utilities/100000/fromList | 5161712.37 | 3685646.90 | 173 | | Utilities/100000/toList | 5109243.49 | 5118785.28 | 174 | | Utilities/1000000/at' | 14831244.23 | 5055419.26 | 175 | | Utilities/1000000/insert | 17633535.06 | 7209602.12 | 176 | | Utilities/1000000/delete | 11251853.98 | 4072535.57 | 177 | | Utilities/1000000/lookup | 15169518.90 | 5208497.64 | 178 | | Utilities/1000000/lookup' | 14532451.21 | 4929673.79 | 179 | | Utilities/1000000/lookupIndex | 17529914.96 | 4216663.23 | 180 | | Utilities/1000000/null | 7.20 | 7.25 | 181 | | Utilities/1000000/length | 7.30 | 6.81 | 182 | | Utilities/1000000/size | 6.86 | 6.43 | 183 | | Utilities/1000000/member | 17461069.35 | 4604944.15 | 184 | | Utilities/1000000/findWithDefault | 15945541.78 | 5058608.89 | 185 | | Utilities/1000000/upsert | 34444162.79 | 12052143.01 | 186 | | Utilities/1000000/alter | 33820504.88 | 11842773.92 | 187 | | Utilities/1000000/alterM | 33991841.71 | 11908234.12 | 188 | | Utilities/1000000/union | 59911378.73 | 44470700.12 | 189 | | Utilities/1000000/difference | 117323371.53 | 107670945.26 | 190 | | Utilities/1000000/intersection | 195009586.71 | 161847790.47 | 191 | | Utilities/1000000/fromList | 97086662.77 | 52734408.34 | 192 | | Utilities/1000000/toList | 166554860.99 | 99619875.06 | 193 | 194 |
195 | -------------------------------------------------------------------------------- /test/Data/Vector/HashTablesSpec.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE DeriveGeneric #-} 2 | {-# LANGUAGE DerivingStrategies #-} 3 | {-# LANGUAGE FlexibleContexts #-} 4 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} 5 | {-# LANGUAGE InstanceSigs #-} 6 | {-# LANGUAGE MultiParamTypeClasses #-} 7 | {-# LANGUAGE RankNTypes #-} 8 | {-# LANGUAGE RecordWildCards #-} 9 | {-# LANGUAGE ScopedTypeVariables #-} 10 | {-# LANGUAGE StandaloneDeriving #-} 11 | {-# LANGUAGE TypeApplications #-} 12 | {-# LANGUAGE TypeFamilies #-} 13 | module Data.Vector.HashTablesSpec where 14 | 15 | import Control.Monad.Primitive 16 | import Data.Hashable (Hashable (hashWithSalt)) 17 | import qualified Data.List as L 18 | import Data.Primitive.MutVar 19 | import Data.Proxy (Proxy (..)) 20 | import qualified Data.Set as Set 21 | import Data.Vector.Generic (Mutable, Vector) 22 | import qualified Data.Vector.Generic as VI 23 | import Data.Vector.Generic.Mutable (MVector) 24 | import qualified Data.Vector.Mutable as M 25 | import qualified Data.Vector.Storable.Mutable as SM 26 | import qualified Data.Vector.Unboxed as U 27 | import qualified Data.Vector.Unboxed.Mutable as UM 28 | import GHC.Generics (Generic) 29 | import Test.Hspec.QuickCheck (modifyMaxSuccess) 30 | import Test.QuickCheck (Arbitrary (..), Gen, 31 | NonNegative (..), 32 | Positive (..), Property, 33 | choose, elements, forAll, 34 | generate, property, shuffle, 35 | vector) 36 | 37 | import Test.Hspec (Spec, describe, errorCall, it, 38 | shouldBe, shouldThrow) 39 | 40 | import qualified Data.Vector.Hashtables.Internal as VH 41 | 42 | newtype AlwaysCollide = AC Int 43 | deriving newtype (Arbitrary, SM.Storable, Num, Eq, Ord, Show) 44 | deriving stock Generic 45 | 46 | instance Hashable AlwaysCollide where 47 | hashWithSalt _ _ = 1 48 | 49 | listN :: Int -> Gen [(Int, Int)] 50 | listN n = do 51 | keys <- vector n 52 | vals <- vector n 53 | let keys' = Set.toList (Set.fromList keys) 54 | return (zip keys' vals) 55 | 56 | shuffledListN :: Int -> Gen ([(Int, Int)], [(Int, Int)]) 57 | shuffledListN n = do 58 | testData <- listN n 59 | shuffledTestData <- shuffle testData 60 | return (testData, shuffledTestData) 61 | 62 | listsForRemoveN :: Int -> Gen ([(Int, Int)], [Int]) 63 | listsForRemoveN n = do 64 | testData <- listN n 65 | dropCount <- min (n - 1) <$> choose (1, n) 66 | let deleteData = fst <$> take dropCount testData 67 | return (testData, deleteData) 68 | 69 | twoListsN :: Int -> Gen ([(Int, Int)], [(Int, Int)]) 70 | twoListsN n = do 71 | list1 <- listN n 72 | list2 <- listN n 73 | return (list1, list2) 74 | 75 | spec :: Spec 76 | spec = mutableSpec 77 | *> storableMutableSpec 78 | *> storableKeysSpec 79 | *> unboxedKeysSpec 80 | 81 | class HashTableTest ks vs where 82 | 83 | specDescription :: Proxy ks -> Proxy vs -> String 84 | 85 | testInit :: Proxy ks -> Proxy vs -> Int -> IO (VH.Dictionary (PrimState IO) ks Int vs Int) 86 | 87 | testInsert :: (VH.Dictionary (PrimState IO) ks Int vs Int) -> Int -> Int -> IO () 88 | 89 | testAt :: (VH.Dictionary (PrimState IO) ks Int vs Int) -> Int -> IO Int 90 | 91 | testAt' :: (VH.Dictionary (PrimState IO) ks Int vs Int) -> Int -> IO (Maybe Int) 92 | 93 | testDelete :: (VH.Dictionary (PrimState IO) ks Int vs Int) -> Int -> IO () 94 | 95 | testInitCollide 96 | :: Proxy ks 97 | -> Proxy vs 98 | -> Int 99 | -> IO (VH.Dictionary (PrimState IO) ks AlwaysCollide vs Int) 100 | 101 | testInsertCollide 102 | :: (VH.Dictionary (PrimState IO) ks AlwaysCollide vs Int) -> AlwaysCollide -> Int -> IO () 103 | 104 | testAtCollide 105 | :: (VH.Dictionary (PrimState IO) ks AlwaysCollide vs Int) -> AlwaysCollide -> IO Int 106 | 107 | testFromList 108 | :: Proxy ks -> Proxy vs -> [(Int, Int)] -> IO (VH.Dictionary (PrimState IO) ks Int vs Int) 109 | 110 | testToList :: VH.Dictionary (PrimState IO) ks Int vs Int -> IO [(Int, Int)] 111 | 112 | testLength :: VH.Dictionary (PrimState IO) ks Int vs Int -> IO Int 113 | 114 | testNull :: VH.Dictionary (PrimState IO) ks Int vs Int -> IO Bool 115 | 116 | testMember :: VH.Dictionary (PrimState IO) ks Int vs Int -> Int -> IO Bool 117 | 118 | testAlter :: VH.Dictionary (PrimState IO) ks Int vs Int -> (Maybe Int -> Maybe Int) -> Int -> IO () 119 | 120 | testUpsert :: VH.Dictionary (PrimState IO) ks Int vs Int -> (Maybe Int -> Int) -> Int -> IO () 121 | 122 | testUnion 123 | :: VH.Dictionary (PrimState IO) ks Int vs Int 124 | -> VH.Dictionary (PrimState IO) ks Int vs Int 125 | -> IO (VH.Dictionary (PrimState IO) ks Int vs Int) 126 | 127 | testDifference 128 | :: VH.Dictionary (PrimState IO) ks Int vs Int 129 | -> VH.Dictionary (PrimState IO) ks Int vs Int 130 | -> IO (VH.Dictionary (PrimState IO) ks Int vs Int) 131 | 132 | testIntersection 133 | :: VH.Dictionary (PrimState IO) ks Int vs Int 134 | -> VH.Dictionary (PrimState IO) ks Int vs Int 135 | -> IO (VH.Dictionary (PrimState IO) ks Int vs Int) 136 | 137 | mkSpec 138 | :: forall ks vs. (HashTableTest ks vs) 139 | => Proxy ks -> Proxy vs -> Spec 140 | mkSpec ksp vsp = describe (specDescription ksp vsp) $ 141 | modifyMaxSuccess (const 1000) $ do 142 | it "lookup for inserted value at specific index returns value" $ 143 | property prop_insertLookup 144 | 145 | it "lookup for inserted value at specific index returns nothing" $ 146 | property prop_insertLookupNothing 147 | 148 | it "lookup for inserted value at specific index throws error" $ 149 | property prop_insertLookupError 150 | 151 | it "lookup for updated value at specific index returns updated value" $ 152 | property prop_insertUpdateLookup 153 | 154 | it "lookup for deleted value at specific index returns nothing" $ 155 | property prop_insertDeleteLookupNothing 156 | 157 | it "lookup for deleted value at specific index throws error" $ 158 | property prop_insertDeleteLookupError 159 | 160 | it "table size increases when multiple elements added" $ 161 | property prop_insertMultipleElements 162 | 163 | it "lookup for inserted value with hash collision returns value" $ 164 | property prop_insertLookupHashCollisions 165 | 166 | it "fromList . toList === id" $ property prop_fromListToList 167 | 168 | it "deleted entries are not present in key-value list after deleting from hashtable" $ 169 | property prop_insertDeleteKeysSize 170 | 171 | it "new table is null" $ property prop_newIsNull 172 | 173 | it "non-empty table is not null" $ property prop_fromListIsNotNull 174 | 175 | it "inserted key is table member" $ property prop_isMember 176 | 177 | it "deleted key is not a member" $ property prop_isNotMember 178 | 179 | it "when altering is nothing - key deleted from table" $ property prop_alterDelete 180 | 181 | it "when altering is just a result - key updated with result" $ property prop_alterUpdate 182 | 183 | it "when upserting a new key - key is set to value" $ property prop_upsertInsert 184 | 185 | it "when upserting an existing key - key updated with result" $ property prop_upsertUpdate 186 | 187 | it "intersection + symmetric difference of two tables is equal to union of two tables" $ property prop_union 188 | 189 | where 190 | prop_insertLookup 191 | :: HashTableTest ks vs => (Int, Int) -> IO () 192 | prop_insertLookup (x, y) = do 193 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 194 | testInsert ht x y 195 | v <- testAt ht x 196 | v `shouldBe` y 197 | 198 | prop_insertLookupNothing :: HashTableTest ks vs => (Int, Int) -> IO () 199 | prop_insertLookupNothing (x, y) = do 200 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 201 | testInsert ht (x + 1) y 202 | v <- testAt' ht x 203 | v `shouldBe` Nothing 204 | 205 | prop_insertLookupError :: HashTableTest ks vs => (Int, Int) -> IO () 206 | prop_insertLookupError (x, y) = do 207 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 208 | testInsert ht (x + 1) y 209 | testAt ht x `shouldThrow` errorCall "KeyNotFoundException!" 210 | 211 | prop_insertUpdateLookup :: HashTableTest ks vs => (Int, Int) -> IO () 212 | prop_insertUpdateLookup (x, y) = do 213 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 214 | testInsert ht x y 215 | testInsert ht x (y + 1) 216 | v <- testAt ht x 217 | v `shouldBe` (y + 1) 218 | 219 | prop_insertDeleteLookupNothing :: HashTableTest ks vs => (Int, Int) -> IO () 220 | prop_insertDeleteLookupNothing (x, y) = do 221 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 222 | testInsert ht x y 223 | testDelete ht x 224 | v <- testAt' ht x 225 | v `shouldBe` Nothing 226 | 227 | prop_insertDeleteLookupError :: HashTableTest ks vs => (Int, Int) -> IO () 228 | prop_insertDeleteLookupError (x, y) = do 229 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 230 | testInsert ht 0 1 231 | testDelete ht 0 232 | testAt ht 0 `shouldThrow` errorCall "KeyNotFoundException!" 233 | 234 | prop_insertMultipleElements 235 | :: HashTableTest ks vs 236 | => (NonNegative Int) -> Property 237 | prop_insertMultipleElements (NonNegative n) = forAll (listN n) $ \xs -> do 238 | ht <- testInit (Proxy @ks) (Proxy @vs) 2 239 | mapM_ (uncurry (testInsert ht)) xs 240 | htl <- testLength ht 241 | htl `shouldBe` (length . Set.toList . Set.fromList) (fst <$> xs) 242 | 243 | prop_insertLookupHashCollisions 244 | :: HashTableTest ks vs => (AlwaysCollide, Int) -> (AlwaysCollide, Int) -> IO () 245 | prop_insertLookupHashCollisions (x1, y1) (x2, y2) = do 246 | ht <- testInitCollide (Proxy @ks) (Proxy @vs) 10 247 | let x2' = if x1 /= x2 then x2 else x2 + 1 248 | testInsertCollide ht x1 y1 249 | testInsertCollide ht x2' y2 250 | v <- testAtCollide ht x1 251 | v `shouldBe` y1 252 | 253 | prop_fromListToList :: NonNegative Int -> Property 254 | prop_fromListToList (NonNegative n) = forAll (shuffledListN n) $ \(xs, ys) -> do 255 | ht <- testFromList (Proxy @ks) (Proxy @vs) xs 256 | xs' <- testToList ht 257 | L.sort xs' `shouldBe` L.sort ys 258 | 259 | prop_insertDeleteKeysSize :: NonNegative Int -> Property 260 | prop_insertDeleteKeysSize (NonNegative n) = forAll (listsForRemoveN n) go 261 | where 262 | go (insertData, deleteData) = do 263 | ht <- testInit (Proxy @ks) (Proxy @vs) 2 264 | mapM_ (uncurry (testInsert ht)) insertData 265 | mapM_ (testDelete ht) deleteData 266 | kvs <- testToList ht 267 | L.length insertData - L.length deleteData `shouldBe` L.length kvs 268 | 269 | prop_newIsNull :: IO () 270 | prop_newIsNull = do 271 | ht <- testInit (Proxy @ks) (Proxy @vs) 2 272 | result <- testNull ht 273 | result `shouldBe` True 274 | 275 | prop_fromListIsNotNull :: Positive Int -> Property 276 | prop_fromListIsNotNull (Positive n) = forAll (listN n) $ \xs -> do 277 | ht <- testFromList (Proxy @ks) (Proxy @vs) xs 278 | result <- testNull ht 279 | result `shouldBe` False 280 | 281 | prop_isMember :: HashTableTest ks vs => (Int, Int) -> IO () 282 | prop_isMember (x, y) = do 283 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 284 | testInsert ht x y 285 | v <- testMember ht x 286 | v `shouldBe` True 287 | 288 | prop_isNotMember :: HashTableTest ks vs => (Int, Int) -> IO () 289 | prop_isNotMember (x, y) = do 290 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 291 | testInsert ht x y 292 | testDelete ht x 293 | v <- testMember ht x 294 | v `shouldBe` False 295 | 296 | prop_alterDelete :: HashTableTest ks vs => (Int, Int) -> IO () 297 | prop_alterDelete (x, y) = do 298 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 299 | testInsert ht x y 300 | testAlter ht (const Nothing) x 301 | v <- testMember ht x 302 | v `shouldBe` False 303 | 304 | prop_alterUpdate :: HashTableTest ks vs => (Int, Int) -> IO () 305 | prop_alterUpdate (x, y) = do 306 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 307 | testInsert ht x y 308 | testAlter ht (fmap negate) x 309 | v <- testAt ht x 310 | v `shouldBe` (negate y) 311 | 312 | prop_upsertInsert :: HashTableTest ks vs => (Int, Int) -> IO () 313 | prop_upsertInsert (x, y) = do 314 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 315 | testUpsert ht (maybe 0 negate) x 316 | v <- testAt ht x 317 | v `shouldBe` 0 318 | 319 | prop_upsertUpdate :: HashTableTest ks vs => (Int, Int) -> IO () 320 | prop_upsertUpdate (x, y) = do 321 | ht <- testInit (Proxy @ks) (Proxy @vs) 10 322 | testInsert ht x y 323 | testUpsert ht (maybe 0 negate) x 324 | v <- testAt ht x 325 | v `shouldBe` (negate y) 326 | 327 | prop_union :: Positive Int -> Property 328 | prop_union (Positive n) = forAll (twoListsN n) $ \(xs, ys) -> do 329 | ht1 <- testFromList (Proxy @ks) (Proxy @vs) xs 330 | ht2 <- testFromList (Proxy @ks) (Proxy @vs) ys 331 | u1 <- testUnion ht1 ht2 332 | d1 <- testDifference ht1 ht2 333 | d2 <- testDifference ht2 ht1 334 | i <- testIntersection ht1 ht2 335 | 336 | res <- do 337 | u2 <- testUnion d1 d2 338 | testUnion i u2 339 | 340 | resultList <- testToList res 341 | unionList <- testToList u1 342 | 343 | Set.fromList resultList `shouldBe` Set.fromList unionList 344 | 345 | 346 | instance HashTableTest M.MVector M.MVector where 347 | specDescription _ _ = "Data.Vector.HashTables.Mutable keys and values" 348 | testInit _ _ n = VH.initialize n 349 | testInitCollide _ _ n = VH.initialize n 350 | testInsert = VH.insert 351 | testAt = VH.at 352 | testAt' = VH.at' 353 | testDelete = VH.delete 354 | testInsertCollide = VH.insert 355 | testAtCollide = VH.at 356 | testLength = VH.length 357 | testFromList _ _ = VH.fromList 358 | testToList = VH.toList 359 | testNull = VH.null 360 | testMember = VH.member 361 | testAlter = VH.alter 362 | testUpsert = VH.upsert 363 | testUnion = VH.union 364 | testDifference = VH.difference 365 | testIntersection = VH.intersection 366 | 367 | mutableSpec :: Spec 368 | mutableSpec = mkSpec (Proxy :: Proxy M.MVector) (Proxy :: Proxy M.MVector) 369 | 370 | 371 | instance HashTableTest SM.MVector SM.MVector where 372 | specDescription _ _ = "Data.Vector.HashTables.Storable.Mutable keys and values" 373 | testInit _ _ n = VH.initialize n 374 | testInitCollide _ _ n = VH.initialize n 375 | testInsert = VH.insert 376 | testAt = VH.at 377 | testAt' = VH.at' 378 | testDelete = VH.delete 379 | testInsertCollide = VH.insert 380 | testAtCollide = VH.at 381 | testLength = VH.length 382 | testFromList _ _ = VH.fromList 383 | testToList = VH.toList 384 | testNull = VH.null 385 | testMember = VH.member 386 | testAlter = VH.alter 387 | testUpsert = VH.upsert 388 | testUnion = VH.union 389 | testDifference = VH.difference 390 | testIntersection = VH.intersection 391 | 392 | storableMutableSpec :: Spec 393 | storableMutableSpec = mkSpec (Proxy @SM.MVector) (Proxy @SM.MVector) 394 | 395 | 396 | instance HashTableTest SM.MVector M.MVector where 397 | specDescription _ _ = "Data.Vector.HashTables.Mutable keys and Data.Vector.HashTables.Storable.Mutable values" 398 | testInit _ _ n = VH.initialize n 399 | testInitCollide _ _ n = VH.initialize n 400 | testInsert = VH.insert 401 | testAt = VH.at 402 | testAt' = VH.at' 403 | testDelete = VH.delete 404 | testInsertCollide = VH.insert 405 | testAtCollide = VH.at 406 | testLength = VH.length 407 | testFromList _ _ = VH.fromList 408 | testToList = VH.toList 409 | testNull = VH.null 410 | testMember = VH.member 411 | testAlter = VH.alter 412 | testUpsert = VH.upsert 413 | testUnion = VH.union 414 | testDifference = VH.difference 415 | testIntersection = VH.intersection 416 | 417 | storableKeysSpec :: Spec 418 | storableKeysSpec = mkSpec (Proxy @SM.MVector) (Proxy @M.MVector) 419 | 420 | 421 | instance HashTableTest M.MVector UM.MVector where 422 | specDescription _ _ = "Data.Vector.HashTables.Mutable keys and Data.Vector.HashTables.Unboxed.Mutable values" 423 | testInit _ _ n = VH.initialize n 424 | testInitCollide _ _ n = VH.initialize n 425 | testInsert = VH.insert 426 | testAt = VH.at 427 | testAt' = VH.at' 428 | testDelete = VH.delete 429 | testInsertCollide = VH.insert 430 | testAtCollide = VH.at 431 | testLength = VH.length 432 | testFromList _ _ = VH.fromList 433 | testToList = VH.toList 434 | testNull = VH.null 435 | testMember = VH.member 436 | testAlter = VH.alter 437 | testUpsert = VH.upsert 438 | testUnion = VH.union 439 | testDifference = VH.difference 440 | testIntersection = VH.intersection 441 | 442 | unboxedKeysSpec :: Spec 443 | unboxedKeysSpec = mkSpec (Proxy @M.MVector) (Proxy @UM.MVector) 444 | -------------------------------------------------------------------------------- /charts/results.csv: -------------------------------------------------------------------------------- 1 | Name,Mean,MeanLB,MeanUB,Stddev,StddevLB,StddevUB 2 | Comparison/1000/insert/hashtables basic,2.6265910693374302e-5,2.6158068920271846e-5,2.6427436233658147e-5,4.4718925810469537e-7,3.5301244242040614e-7,5.839216244488787e-7 3 | Comparison/1000/insert/vector-hashtables boxed,1.9575860810916178e-5,1.926647603637609e-5,1.9740314304255806e-5,7.454474339428102e-7,3.7466220434043524e-7,1.3834671459430294e-6 4 | Comparison/1000/insert/vector-hashtables unboxed keys,8.826795648317215e-6,8.770576966261804e-6,8.909366150634212e-6,2.352375433804522e-7,1.7612220351373926e-7,2.9829914583274947e-7 5 | Comparison/1000/insert/vector-hashtables,2.0635037453555934e-5,2.0455663823614313e-5,2.0896553906998486e-5,7.007840744644399e-7,4.829873456743934e-7,9.81032007812722e-7 6 | Comparison/1000/insert/mutable vector boxed,2.265952794028665e-6,2.2173455978514867e-6,2.3394235727800144e-6,1.9261798702538282e-7,1.4523974686472908e-7,2.530309839697052e-7 7 | Comparison/1000/insert/mutable vector,5.264331655956335e-7,5.148325770818036e-7,5.559707205963797e-7,5.9344513371319815e-8,3.0827396782838076e-8,1.1270431216154575e-7 8 | Comparison/1000/insert (resize)/hashtables basic,8.932069244749132e-5,8.820194955781247e-5,9.090470499293483e-5,4.53752940067964e-6,3.351205191408819e-6,6.2370752647305626e-6 9 | Comparison/1000/insert (resize)/vector-hashtables boxed,1.3910402498670035e-5,1.3765434273402642e-5,1.410125571936111e-5,5.396371484589965e-7,4.250089153567818e-7,6.78481772326404e-7 10 | Comparison/1000/insert (resize)/vector-hashtables unboxed keys,1.331534990508627e-5,1.313324421262183e-5,1.3595816607217832e-5,7.93574111586542e-7,5.556664887184433e-7,1.2135931662721414e-6 11 | Comparison/1000/insert (resize)/vector-hashtables,1.0987076453458678e-5,1.0850785328155451e-5,1.1167765740536372e-5,5.083339185362349e-7,4.068757695525665e-7,6.746492999009997e-7 12 | "Comparison/1000/insert, delete/hashtables basic",4.730121532164581e-5,4.695991571261143e-5,4.765133575003976e-5,1.159392848129342e-6,9.728949797939497e-7,1.4321771026439375e-6 13 | "Comparison/1000/insert, delete/vector-hashtables",1.1570315465434165e-5,1.1529724449670008e-5,1.1636304446970008e-5,1.694508489487887e-7,1.1277090925892206e-7,2.5628073275205104e-7 14 | Comparison/1000/find/hashtables basic,9.074698461211113e-6,9.0533309081796e-6,9.101500897738992e-6,8.432899268159116e-8,6.986485174266875e-8,9.95647961317774e-8 15 | Comparison/1000/find/vector-hashtables,2.8342599424532434e-6,2.8267377366559826e-6,2.8440302666553868e-6,2.888558635314647e-8,2.1847423687085995e-8,4.303598561664496e-8 16 | Comparison/1000/find/vector-hashtables (frozen),1.5429894619247125e-6,1.5397052640675597e-6,1.5463156490790096e-6,1.128836030862139e-8,9.454797086149399e-9,1.3530492198185908e-8 17 | Comparison/1000/lookupIndex/hashtables basic,9.594605385648414e-6,9.564608909103947e-6,9.628334987248091e-6,1.016795750640212e-7,8.38679450409373e-8,1.2723801288875722e-7 18 | Comparison/1000/lookupIndex/vector-hashtables,2.6381899684128308e-6,2.633842862242062e-6,2.644203882335658e-6,1.7562201820026026e-8,1.4615648137521927e-8,2.211170299483845e-8 19 | Comparison/1000/fromList/hashtables basic,8.798663532440132e-5,8.725809928559993e-5,8.880296845966857e-5,2.614836915802247e-6,2.119924915774629e-6,3.462410531236417e-6 20 | Comparison/1000/fromList/vector-hashtables,1.6723201949785347e-5,1.6419600646318527e-5,1.7086668236771075e-5,1.1430378912859617e-6,9.345989884798463e-7,1.4188092726249213e-6 21 | Comparison/1000/toList/hashtables basic,3.5285367857832303e-6,3.516262533741015e-6,3.539695014461875e-6,4.0641624757585494e-8,3.477241389727497e-8,4.988084071337804e-8 22 | Comparison/1000/toList/vector-hashtables,4.5532829009632945e-6,4.526570858193092e-6,4.5808507880293415e-6,9.27869858325269e-8,7.867538723687633e-8,1.2266956722527248e-7 23 | Comparison/10000/insert/hashtables basic,2.6275961997376606e-4,2.617682372760563e-4,2.63991158986301e-4,3.772524013388728e-6,2.9677422174798028e-6,5.064887342985125e-6 24 | Comparison/10000/insert/vector-hashtables boxed,1.861334542715329e-4,1.7718416168489433e-4,1.9166438441918483e-4,2.2212872773177097e-5,1.609130427624589e-5,2.9722428828644792e-5 25 | Comparison/10000/insert/vector-hashtables unboxed keys,8.162779364011212e-5,8.062720228892609e-5,8.318489512688327e-5,4.191722432259175e-6,2.859940047160556e-6,5.981273864365325e-6 26 | Comparison/10000/insert/vector-hashtables,2.049789096913006e-4,2.0286546271091883e-4,2.0764854760691844e-4,7.715794362279534e-6,6.174102903002859e-6,9.91675176570173e-6 27 | Comparison/10000/insert/mutable vector boxed,2.2190313373627347e-5,2.208151426619383e-5,2.233090318635047e-5,4.006021414554521e-7,3.2249227426983025e-7,5.408204163095073e-7 28 | Comparison/10000/insert/mutable vector,4.9395955369523e-6,4.897978158409461e-6,4.989705625957669e-6,1.548397802599445e-7,1.248194526482811e-7,2.0073717890306102e-7 29 | Comparison/10000/insert (resize)/hashtables basic,7.786852070594427e-4,7.73214666283881e-4,7.866362532080302e-4,2.134905785096809e-5,1.5676974969432405e-5,3.114659077822427e-5 30 | Comparison/10000/insert (resize)/vector-hashtables boxed,1.4267097832349108e-4,1.411972926493907e-4,1.450834845669146e-4,5.9568948698088e-6,4.027355017715671e-6,1.0632562967226956e-5 31 | Comparison/10000/insert (resize)/vector-hashtables unboxed keys,1.2075045980825741e-4,1.2015483630710153e-4,1.2157868391533687e-4,2.318057130012277e-6,1.6011286663974935e-6,3.4295470134166548e-6 32 | Comparison/10000/insert (resize)/vector-hashtables,9.275852901515633e-5,9.209060034682864e-5,9.357127705347608e-5,2.3723687096815975e-6,2.000332776655767e-6,2.8402942518194118e-6 33 | "Comparison/10000/insert, delete/hashtables basic",4.7977657725485477e-4,4.7688087446990995e-4,4.821980207278067e-4,9.419121358275951e-6,7.969452208800688e-6,1.1319538019118395e-5 34 | "Comparison/10000/insert, delete/vector-hashtables",1.09584917535346e-4,1.0839856084882338e-4,1.1099975104651575e-4,4.251464344658462e-6,3.5811044741244243e-6,5.205605380950741e-6 35 | Comparison/10000/find/hashtables basic,9.497344034651084e-5,9.388757332973189e-5,9.699647758862355e-5,4.846190274568895e-6,3.1932047546801457e-6,8.197268490851757e-6 36 | Comparison/10000/find/vector-hashtables,2.876508366011716e-5,2.868279607834505e-5,2.886093400738746e-5,2.8617353278983623e-7,2.4216434307135286e-7,3.438627407992029e-7 37 | Comparison/10000/find/vector-hashtables (frozen),1.5470918337188902e-5,1.544073817692524e-5,1.5504665376353108e-5,1.0742378986458252e-7,9.125371289440086e-8,1.3267394848867905e-7 38 | Comparison/10000/lookupIndex/hashtables basic,9.760857498818325e-5,9.706631780904595e-5,9.836254373867276e-5,2.154358384907353e-6,1.54537661429576e-6,3.2190243393294207e-6 39 | Comparison/10000/lookupIndex/vector-hashtables,2.7862260985718885e-5,2.771806374689272e-5,2.8010067158611298e-5,4.92947740983751e-7,3.795840804809102e-7,6.416527326068737e-7 40 | Comparison/10000/fromList/hashtables basic,7.856378900340298e-4,7.762193150795441e-4,8.282449228567954e-4,5.247210316044077e-5,1.4532822542126237e-5,1.1484431838597381e-4 41 | Comparison/10000/fromList/vector-hashtables,1.4150556361826384e-4,1.402583904060798e-4,1.4330247922603873e-4,4.913302698393713e-6,3.776071601076066e-6,7.210018581006078e-6 42 | Comparison/10000/toList/hashtables basic,4.7827664768121966e-5,4.744197251279455e-5,4.83006679335944e-5,1.3702582801173146e-6,1.0086350101512542e-6,1.9478187374367174e-6 43 | Comparison/10000/toList/vector-hashtables,6.819735254710253e-5,6.748745485533193e-5,6.947671616751117e-5,2.981718578460447e-6,1.8277695928570463e-6,5.489560557683937e-6 44 | Comparison/100000/insert/hashtables basic,2.9135340730342884e-3,2.8898013107514294e-3,2.9442179599259207e-3,8.516400742543829e-5,6.926352271199839e-5,1.0770898363926531e-4 45 | Comparison/100000/insert/vector-hashtables boxed,1.8997681512565073e-3,1.885988830454903e-3,1.91365901700979e-3,4.664113877206801e-5,3.9204314361692676e-5,5.876937118380217e-5 46 | Comparison/100000/insert/vector-hashtables unboxed keys,1.0919884581159212e-3,1.0835270906820785e-3,1.1060423497330051e-3,3.657159709702544e-5,2.427179645877365e-5,5.9910868405328117e-5 47 | Comparison/100000/insert/vector-hashtables,1.9553974860204216e-3,1.9450590965110943e-3,1.9679247043580877e-3,3.797925211245962e-5,3.217827468946792e-5,4.6034523958893444e-5 48 | Comparison/100000/insert/mutable vector boxed,3.603179705811654e-4,3.546947131745201e-4,3.668937407208655e-4,2.0163713394486866e-5,1.6340781914554415e-5,2.5347270510590842e-5 49 | Comparison/100000/insert/mutable vector,4.7781380324446424e-5,4.76639274556985e-5,4.792138588140055e-5,4.2457499758018937e-7,3.5173295831093147e-7,5.487394457601031e-7 50 | Comparison/100000/insert (resize)/hashtables basic,1.1623392335200176e-2,1.1258500881570476e-2,1.205214425833595e-2,1.0519656888655679e-3,8.148097469446313e-4,1.4793390634027298e-3 51 | Comparison/100000/insert (resize)/vector-hashtables boxed,4.490964565241779e-3,4.279487613991628e-3,4.837993848051393e-3,7.953794652738661e-4,5.23488248801789e-4,1.2640614326360484e-3 52 | Comparison/100000/insert (resize)/vector-hashtables unboxed keys,3.3439346011551775e-3,3.1539207153974806e-3,3.668105732055993e-3,7.410392568321323e-4,5.166742395652956e-4,1.0832481536382252e-3 53 | Comparison/100000/insert (resize)/vector-hashtables,1.6032246461601188e-3,1.4725934176706677e-3,1.8723557841726704e-3,6.162047656214918e-4,4.0172581247084073e-4,1.0784236871695877e-3 54 | "Comparison/100000/insert, delete/hashtables basic",5.216299941876864e-3,5.187613470993173e-3,5.254269146359217e-3,9.945655677428071e-5,6.954118948260116e-5,1.6195276928620945e-4 55 | "Comparison/100000/insert, delete/vector-hashtables",1.0376104514345946e-3,1.0334719077453502e-3,1.0430315515512329e-3,1.571616020766764e-5,1.1621223993851683e-5,2.2267562791821157e-5 56 | Comparison/100000/find/hashtables basic,9.252486586216895e-4,9.212232925711216e-4,9.297291316675767e-4,1.4584739760046791e-5,1.240291407881786e-5,1.7740901679427154e-5 57 | Comparison/100000/find/vector-hashtables,2.869564228467935e-4,2.8650696712906917e-4,2.875244274542984e-4,1.7849279290591234e-6,1.4023751775229884e-6,2.426312827913018e-6 58 | Comparison/100000/find/vector-hashtables (frozen),1.5649523580728677e-4,1.5605616584514373e-4,1.5721356913025807e-4,1.9705661322794016e-6,1.3602709463420232e-6,2.88141627299565e-6 59 | Comparison/100000/lookupIndex/hashtables basic,9.71810198264501e-4,9.673733892046277e-4,9.763669167083512e-4,1.513550190085508e-5,1.2134268238624573e-5,2.0029849866449507e-5 60 | Comparison/100000/lookupIndex/vector-hashtables,2.641034250464948e-4,2.6377676549750535e-4,2.644970930400751e-4,1.2051861920331162e-6,1.0114001510872198e-6,1.4456327007723865e-6 61 | Comparison/100000/fromList/hashtables basic,1.0429499890171647e-2,1.0157435504688518e-2,1.0737524788548862e-2,8.547088431855836e-4,6.964637585327324e-4,1.0482086748908326e-3 62 | Comparison/100000/fromList/vector-hashtables,3.0954242315241205e-3,2.7719374964607297e-3,3.641680490133116e-3,1.393886890620583e-3,9.736366596243073e-4,2.231631880410737e-3 63 | Comparison/100000/toList/hashtables basic,1.4174977906645503e-3,1.3986255330867142e-3,1.4425937187968424e-3,7.232182312946139e-5,5.8283366869380914e-5,9.380903866104158e-5 64 | Comparison/100000/toList/vector-hashtables,3.192894242895358e-3,3.104175685641562e-3,3.3183441545527005e-3,3.564382378547826e-4,2.395523569646384e-4,5.388860659490742e-4 65 | Comparison/1000000/insert/hashtables basic,5.959345010568615e-2,5.841862315304482e-2,6.139210817932125e-2,2.655628910850536e-3,1.4808446334325903e-3,4.105383924254537e-3 66 | Comparison/1000000/insert/vector-hashtables boxed,4.234336754857981e-2,4.078179981089696e-2,4.4139891905172104e-2,3.3076444405204792e-3,2.3463397509283445e-3,4.463159730036379e-3 67 | Comparison/1000000/insert/vector-hashtables unboxed keys,3.0126393098609823e-2,2.8895239060670274e-2,3.1372384337021414e-2,2.543764192437888e-3,2.1464165849167443e-3,3.1291317688061163e-3 68 | Comparison/1000000/insert/vector-hashtables,2.20307146420291e-2,2.134154102218915e-2,2.2666192814038203e-2,1.544191408081723e-3,9.5976484221556e-4,2.5911286497008047e-3 69 | Comparison/1000000/insert/mutable vector boxed,1.881407369901629e-2,1.8246262757814654e-2,1.9738770708230484e-2,1.7199038388880992e-3,1.0477176057692844e-3,2.417778437327696e-3 70 | Comparison/1000000/insert/mutable vector,4.6200375642488324e-4,4.60025463162741e-4,4.6468255080091134e-4,7.4362820095991315e-6,5.936592444180921e-6,1.0276492721871543e-5 71 | Comparison/1000000/insert (resize)/hashtables basic,0.1408429011026616,0.13799772619053588,0.1447944767239779,4.916000974684619e-3,3.1294204064902112e-3,6.6301681730114225e-3 72 | Comparison/1000000/insert (resize)/vector-hashtables boxed,5.1254047756802944e-2,4.8907730128544685e-2,5.312899526475661e-2,4.328054898114785e-3,3.2534683627430915e-3,6.154363221947912e-3 73 | Comparison/1000000/insert (resize)/vector-hashtables unboxed keys,3.60868054625934e-2,3.4455406080023225e-2,3.77050623861469e-2,3.354844751305931e-3,2.733770741513534e-3,4.3062661968134e-3 74 | Comparison/1000000/insert (resize)/vector-hashtables,1.6167291911376176e-2,1.5364412353240165e-2,1.7075586454483496e-2,2.0964786719302802e-3,1.648367509788485e-3,2.9534604699139127e-3 75 | "Comparison/1000000/insert, delete/hashtables basic",8.507715122133035e-2,8.429327628050473e-2,8.705149191625727e-2,2.0513949122097953e-3,6.214650630189454e-4,3.420432191825506e-3 76 | "Comparison/1000000/insert, delete/vector-hashtables",1.3563956277684712e-2,1.3158619697835418e-2,1.4238055941330726e-2,1.2426989226078822e-3,8.662156127708506e-4,1.9162183621908326e-3 77 | Comparison/1000000/find/hashtables basic,9.378407643588275e-3,9.341418939280829e-3,9.429398314445916e-3,1.2215919506405572e-4,8.96399978763046e-5,1.7034787761257536e-4 78 | Comparison/1000000/find/vector-hashtables,2.8769133885813056e-3,2.8694519322464197e-3,2.888310529586202e-3,3.0666017819763034e-5,1.773331473761632e-5,5.1602515452668854e-5 79 | Comparison/1000000/find/vector-hashtables (frozen),1.6028880723148132e-3,1.5890290032043724e-3,1.6203718742824854e-3,5.286100295149251e-5,3.9863283148322207e-5,7.585925277379133e-5 80 | Comparison/1000000/lookupIndex/hashtables basic,9.90792762867282e-3,9.782039924763066e-3,1.0078534358832452e-2,3.9195517326631496e-4,3.151200207690431e-4,4.892467540338712e-4 81 | Comparison/1000000/lookupIndex/vector-hashtables,2.7131561977089894e-3,2.701364955634495e-3,2.72752185680879e-3,4.246380083032581e-5,3.601794247085675e-5,5.314396359388008e-5 82 | Comparison/1000000/fromList/hashtables basic,0.13242595298752782,0.1262908287679325,0.14207934228979865,1.1387212098169088e-2,7.763348381670392e-3,1.4482110141846347e-2 83 | Comparison/1000000/fromList/vector-hashtables,2.7158847731942336e-2,2.520800030542757e-2,2.91582967762132e-2,4.280599036655403e-3,3.227438199177293e-3,6.222282919602584e-3 84 | Comparison/1000000/toList/hashtables basic,3.829266015909298e-2,3.733084402964917e-2,4.017353650507709e-2,2.7088474651475684e-3,1.6930693360666432e-3,4.466386367218294e-3 85 | Comparison/1000000/toList/vector-hashtables,6.1491157528219376e-2,5.9915272490161924e-2,6.404034390458643e-2,3.5976627771831327e-3,2.4816409950662124e-3,5.0625228037029365e-3 86 | Utilities/1000/at',2.44912157126593e-6,2.4452879086505737e-6,2.454823532948698e-6,1.5029820272378378e-8,1.1412846730240375e-8,2.290840961507433e-8 87 | Utilities/1000/insert,4.196212084945842e-6,4.184634509103401e-6,4.218340600419069e-6,5.235326869608885e-8,3.527614754639248e-8,8.443486300507326e-8 88 | Utilities/1000/delete,2.4411439797455417e-6,2.4243013195642333e-6,2.4644713265035283e-6,6.522121492689101e-8,4.853129376838587e-8,8.696454746046243e-8 89 | Utilities/1000/lookup,2.4653950838072726e-6,2.4475486526221463e-6,2.5079618102252995e-6,8.719628406983634e-8,4.112662173745885e-8,1.6452815338886475e-7 90 | Utilities/1000/lookup',2.5188108484175604e-6,2.509277830056153e-6,2.5326118782181332e-6,3.724749744541159e-8,2.793043440073375e-8,5.153956133060389e-8 91 | Utilities/1000/lookupIndex,2.319683704279982e-6,2.3096431469113946e-6,2.342084708574259e-6,4.9086411323088e-8,2.5971896626366497e-8,9.822847170897489e-8 92 | Utilities/1000/null,5.608117707677857e-9,5.466536356314475e-9,5.764558097322318e-9,4.723229555835688e-10,4.0834098798005283e-10,6.238449165918608e-10 93 | Utilities/1000/length,4.8619095767970926e-9,4.727235933940077e-9,5.01302943115641e-9,4.663834481772115e-10,3.9717312129933327e-10,6.589954283126102e-10 94 | Utilities/1000/size,5.411491110802043e-9,5.2734075929670585e-9,5.547270432777567e-9,4.4148701062027964e-10,3.7598441792850423e-10,5.884357266925157e-10 95 | Utilities/1000/member,2.3100813610630897e-6,2.302948206010471e-6,2.318276793945321e-6,2.6170589219406254e-8,2.30722911096838e-8,3.1078420072204176e-8 96 | Utilities/1000/findWithDefault,2.443414235679636e-6,2.43606408525766e-6,2.452301881530018e-6,2.7170666044984932e-8,2.205806571590045e-8,4.010674955874783e-8 97 | Utilities/1000/upsert,9.83649324654703e-6,9.794300302181029e-6,9.895257237008347e-6,1.6013630869779962e-7,1.3165061993980986e-7,2.0580205252575992e-7 98 | Utilities/1000/alter,6.796431176703424e-6,6.773681957296808e-6,6.819390365745283e-6,7.672707580412292e-8,6.25782541971991e-8,8.769073894762808e-8 99 | Utilities/1000/alterM,6.652878164590055e-6,6.639543255991888e-6,6.66820886607659e-6,4.9298675399623966e-8,4.001281107416234e-8,6.838769028641521e-8 100 | Utilities/1000/union,1.843721126874428e-5,1.829347705382839e-5,1.858866883241077e-5,4.885386218035924e-7,4.2591547458131854e-7,5.911286378477404e-7 101 | Utilities/1000/difference,7.929967272376326e-6,7.900005658822734e-6,7.965707192302095e-6,1.1210674919513424e-7,9.66750334834804e-8,1.3652924850878232e-7 102 | Utilities/1000/intersection,2.13542414674394e-5,2.1093682772789603e-5,2.1890301983602633e-5,1.1924925506029959e-6,8.053227542292904e-7,2.0262135616332386e-6 103 | Utilities/1000/fromList,1.607182316652602e-5,1.5930168715634716e-5,1.6290560506890286e-5,5.902260918060728e-7,4.3803658144619367e-7,8.121394896107936e-7 104 | Utilities/1000/toList,4.516674540046965e-6,4.485354685133656e-6,4.557603507875245e-6,1.208163499655316e-7,9.450733337382811e-8,1.6893679034370885e-7 105 | Utilities/10000/at',2.5165903727004978e-5,2.497956469623628e-5,2.592632782456216e-5,9.778373924730496e-7,3.2993823637700527e-7,2.11456038485218e-6 106 | Utilities/10000/insert,4.0657184589009876e-5,4.053367906085615e-5,4.077843041498228e-5,4.177611055872763e-7,3.60130193347495e-7,5.034891501225624e-7 107 | Utilities/10000/delete,2.3736531650002394e-5,2.3686256272085638e-5,2.380027763793913e-5,1.848487351614745e-7,1.5364024544857868e-7,2.4656792135636835e-7 108 | Utilities/10000/lookup,2.4116306309352266e-5,2.406145079512061e-5,2.4179093134200794e-5,1.9170560575839924e-7,1.5470624021391243e-7,2.502657647064564e-7 109 | Utilities/10000/lookup',2.431650154768217e-5,2.4276027715356166e-5,2.442670081180333e-5,2.1800935479050664e-7,1.042399418921652e-7,4.185705181325517e-7 110 | Utilities/10000/lookupIndex,2.2677876740733636e-5,2.2651420704598553e-5,2.271452097857448e-5,1.0623042278792772e-7,7.984594739347119e-8,1.5747274089568788e-7 111 | Utilities/10000/null,5.997618002371869e-9,5.8756236110358086e-9,6.045299605926703e-9,2.437647653973336e-10,1.0526974191263516e-10,4.309413667060262e-10 112 | Utilities/10000/length,5.800253354702139e-9,5.629005600770066e-9,5.918608003045456e-9,4.5644227364430777e-10,3.111102239777257e-10,7.630148825275387e-10 113 | Utilities/10000/size,5.27587919537224e-9,5.159086033349521e-9,5.363752782702644e-9,3.36287923290889e-10,2.1734287002770154e-10,5.028613170876084e-10 114 | Utilities/10000/member,2.2757420650968694e-5,2.270659252738286e-5,2.284003360707709e-5,2.0953639843345097e-7,1.4518251200793923e-7,2.9695590679602553e-7 115 | Utilities/10000/findWithDefault,2.4031197562785383e-5,2.4006187518372216e-5,2.4059326901624424e-5,8.63972125768272e-8,7.25315892170015e-8,1.100063311879381e-7 116 | Utilities/10000/upsert,9.758390247350745e-5,9.737268798619701e-5,9.781579317124092e-5,7.190234761584978e-7,6.413195134781656e-7,8.383783973540735e-7 117 | Utilities/10000/alter,6.683232964295798e-5,6.670834613886536e-5,6.702996686044125e-5,5.113061731837181e-7,3.455551344503306e-7,7.298240030538905e-7 118 | Utilities/10000/alterM,6.63874583369905e-5,6.626789021912134e-5,6.654272538700426e-5,4.482185214929184e-7,3.441582282245073e-7,5.625712096549504e-7 119 | Utilities/10000/union,1.627688756874991e-4,1.616866298651368e-4,1.6442853583929128e-4,4.235598037105688e-6,3.3762316788572616e-6,5.782799157164947e-6 120 | Utilities/10000/difference,8.85759641103985e-5,8.813273608842254e-5,8.912731965481717e-5,1.6396481431884432e-6,1.268121653971038e-6,2.229295248829731e-6 121 | Utilities/10000/intersection,2.100728174059028e-4,2.079864691631816e-4,2.1313723194009375e-4,8.54459985057129e-6,5.624287505417623e-6,1.1764964059353913e-5 122 | Utilities/10000/fromList,1.4033559479264228e-4,1.396593258788622e-4,1.4121053061209133e-4,2.5899727390636284e-6,1.9180136553696297e-6,3.7583485012582245e-6 123 | Utilities/10000/toList,6.53961972870231e-5,6.485609883136374e-5,6.676102386930094e-5,2.638054352547212e-6,9.300480171186176e-7,4.491959137393042e-6 124 | Utilities/100000/at',2.46988131338066e-4,2.4589032320407247e-4,2.490415815491426e-4,4.8486011231639386e-6,2.7475832927102254e-6,8.013890766057713e-6 125 | Utilities/100000/insert,4.0179052939886395e-4,4.010477247746414e-4,4.0263693376469637e-4,2.674001661218656e-6,2.228438624148798e-6,3.324451238555031e-6 126 | Utilities/100000/delete,2.3654003139768278e-4,2.360868085607635e-4,2.371133660753429e-4,1.6369702982980137e-6,1.3064525700245244e-6,1.9793423470395194e-6 127 | Utilities/100000/lookup,2.415778389985774e-4,2.4106973044284443e-4,2.42211587834062e-4,1.9562106559698047e-6,1.62271703981848e-6,2.4770154503463773e-6 128 | Utilities/100000/lookup',2.441901726495694e-4,2.437035725718278e-4,2.44917850276408e-4,1.961154438665316e-6,1.3122404164403525e-6,2.9162733496488727e-6 129 | Utilities/100000/lookupIndex,2.2742450224771843e-4,2.2685357412423544e-4,2.281949473064906e-4,2.197053979371573e-6,1.6221638883101923e-6,3.0438841423414026e-6 130 | Utilities/100000/null,5.256206365623004e-9,5.1410210099267526e-9,5.350948485709337e-9,3.507554113264968e-10,2.415782622744773e-10,5.516018520199517e-10 131 | Utilities/100000/length,5.285985759087751e-9,5.0800616173255325e-9,5.53127240872829e-9,6.957806438653174e-10,5.379718478162429e-10,8.565918570133407e-10 132 | Utilities/100000/size,5.349775781111994e-9,5.1658216662577436e-9,5.509077967974695e-9,5.549010504321772e-10,4.5612130223267765e-10,6.998662503189665e-10 133 | Utilities/100000/member,2.2863005148264907e-4,2.2833576888897487e-4,2.2898613101115592e-4,1.1223178173089061e-6,9.386917368305265e-7,1.38391103067165e-6 134 | Utilities/100000/findWithDefault,2.4251087520074917e-4,2.4211815339244072e-4,2.4292776307680721e-4,1.395874396801164e-6,1.21477839012363e-6,1.675926505926277e-6 135 | Utilities/100000/upsert,1.0016555904244517e-3,9.989110427143484e-4,1.0058843425255815e-3,1.140013863871747e-5,8.927583023319387e-6,1.542725394240647e-5 136 | Utilities/100000/alter,6.700042580418115e-4,6.686363973208017e-4,6.720403604697353e-4,5.497835567094349e-6,4.222948854261761e-6,7.708088748140355e-6 137 | Utilities/100000/alterM,6.630126429893313e-4,6.619649603081506e-4,6.644867372500015e-4,4.191331325934773e-6,3.3392203185700095e-6,5.391202606707149e-6 138 | Utilities/100000/union,2.8302500370732874e-3,2.500072885465377e-3,3.2332218842458706e-3,1.28561907622965e-3,1.0611809019194173e-3,1.9331866458196375e-3 139 | Utilities/100000/difference,3.3861856422043243e-3,3.334389547819083e-3,3.525465840838219e-3,2.448136507354012e-4,1.3189869294030128e-4,4.6164070086629065e-4 140 | Utilities/100000/intersection,5.912762498167072e-3,5.706381519087606e-3,6.249841569829586e-3,7.540752058335345e-4,5.317186779409622e-4,1.1140286294506932e-3 141 | Utilities/100000/fromList,2.6672758937889038e-3,2.515320398390631e-3,2.87643230573234e-3,5.582350099210612e-4,4.202750232980136e-4,7.870293016521304e-4 142 | Utilities/100000/toList,2.9423543812440267e-3,2.8981321922357207e-3,3.026937404310888e-3,1.890319982144888e-4,1.143102422409107e-4,3.2861803317334073e-4 143 | Utilities/1000000/at',2.4590231269401358e-3,2.454486079410825e-3,2.4655290267981624e-3,1.6878153128501737e-5,1.3739335853348601e-5,2.3844059280435294e-5 144 | Utilities/1000000/insert,4.014636726136345e-3,4.007165293501399e-3,4.027024926481628e-3,3.0637849817307045e-5,2.19272286585694e-5,4.8720130837966154e-5 145 | Utilities/1000000/delete,2.359877495514612e-3,2.3566646333065744e-3,2.3630564660418827e-3,1.070639425590287e-5,9.185170899143479e-6,1.2303980261695567e-5 146 | Utilities/1000000/lookup,2.4078008348572258e-3,2.4039489924587666e-3,2.412626888104086e-3,1.3994435884143378e-5,1.1450723023270394e-5,1.8154322320347712e-5 147 | Utilities/1000000/lookup',2.436286053428426e-3,2.4322960847239735e-3,2.442085839118424e-3,1.685740522829743e-5,1.183105983370414e-5,2.775336195667938e-5 148 | Utilities/1000000/lookupIndex,2.277631277571108e-3,2.273460411482701e-3,2.2827937625837917e-3,1.5618837666201894e-5,1.3303608509985559e-5,2.1724384834577962e-5 149 | Utilities/1000000/null,5.890527359420102e-9,5.739100943957048e-9,5.977535741289844e-9,3.615869035898788e-10,2.56327131632324e-10,5.039381378305672e-10 150 | Utilities/1000000/length,6.4946954923512744e-9,6.38940640330663e-9,6.535809602154295e-9,2.2669408776905004e-10,7.302339092973336e-11,4.211385490980336e-10 151 | Utilities/1000000/size,5.841103779546308e-9,5.662104461824458e-9,6.025411971951116e-9,6.030660958906693e-10,5.22743488713068e-10,6.990218740840723e-10 152 | Utilities/1000000/member,2.2901944140088903e-3,2.2867117975997673e-3,2.2950143882315525e-3,1.3411146769711238e-5,1.0481449658744994e-5,1.8587409647742286e-5 153 | Utilities/1000000/findWithDefault,2.4224564227738063e-3,2.418049239822276e-3,2.4294500142784427e-3,1.7306989672577535e-5,1.257600367765715e-5,2.3226808071262645e-5 154 | Utilities/1000000/upsert,9.740271993208293e-3,9.716068768231553e-3,9.770614269249332e-3,7.1127343018137e-5,5.2306535207409834e-5,9.819336853973057e-5 155 | Utilities/1000000/alter,6.717599543450785e-3,6.706572189030866e-3,6.7344055760466225e-3,3.8837082112855084e-5,2.7180852871116833e-5,5.417485978971991e-5 156 | Utilities/1000000/alterM,6.6665933600959185e-3,6.649189201508039e-3,6.68585634334892e-3,5.296503456838353e-5,4.331269575494059e-5,6.270541663379713e-5 157 | Utilities/1000000/union,2.5798049602704088e-2,2.3714180252520964e-2,2.9476137735778063e-2,6.3234643205559785e-3,3.682397765651517e-3,9.452455493416815e-3 158 | Utilities/1000000/difference,6.401588312831208e-2,6.260641064623068e-2,6.639580928368936e-2,3.362264882307253e-3,1.7694708655856435e-3,5.569576993582116e-3 159 | Utilities/1000000/intersection,0.1003431909012506,9.12854957353033e-2,0.10535882838808305,1.1635974780578023e-2,2.2464721433707834e-3,2.1311566056817766e-2 160 | Utilities/1000000/fromList,3.474332880623061e-2,3.309518878014333e-2,3.568959807725471e-2,2.497230937410042e-3,1.4704499491403709e-3,4.032968763721831e-3 161 | Utilities/1000000/toList,6.676242264986171e-2,6.2355265660197334e-2,7.60738547051777e-2,1.0195140780607534e-2,5.637073367357237e-3,1.5213606855185568e-2 162 | -------------------------------------------------------------------------------- /charts/toList.svg: -------------------------------------------------------------------------------- 1 | 2 | <font horiz-adv-x="0.0"><font-face font-family="sans-serif" font-style="all" font-weight="400" font-stretch="normal" font-variant="normal" units-per-em="1000.0" panose-1="2 11 5 3 3 4 3 2 2 4" ascent="750.0" descent="-250.0" x-height="486.0" cap-height="656.0" bbox="-192.0 -323.0 1160.0 952.0" underline-thickness="50.0" underline-position="-50.0" unicode-range="U+000D-FB02" /><missing-glyph d="M89 660h476v-660h-476v660zM281 340l-127 232v-462zM498 110v462l-126 -232zM454 58l-73 132l-52 103h-4l-54 -103l-74 -132h257zM329 387l49 94l66 119h-235l66 -119l50 -94h4z"></missing-glyph><glyph glyph-name="space" horiz-adv-x="202.0" d="" unicode=" "></glyph><glyph glyph-name="numbersign" horiz-adv-x="497.0" d="M115 204h-80v57h87l18 148h-85v58h92l23 183h53l-23 -183h133l24 183h53l-24 -183h81v-58h-87l-18 -148h85v-57h-92l-25 -204h-53l24 204h-132l-25 -204h-54zM308 261l18 148h-132l-18 -148h132z" unicode="#"></glyph><glyph glyph-name="parenleft" horiz-adv-x="303.0" d="M214 -176q-62 100 -97 211t-35 243t35 242.5t97 211.5l51 -24q-58 -96 -86.5 -205.5t-28.5 -224.5t28.5 -224.5t86.5 -205.5l-51 -24v0z" unicode="("></glyph><glyph glyph-name="parenright" horiz-adv-x="303.0" d="M38 -152q58 96 86.5 205.5t28.5 224.5t-28.5 224.5t-86.5 205.5l51 24q62 -101 97 -211.5t35 -242.5t-35 -243t-97 -211l-51 24v0z" unicode=")"></glyph><glyph glyph-name="hyphen" horiz-adv-x="311.0" d="M41 282h230v-63h-230v63z" unicode="-"></glyph><glyph glyph-name="period" horiz-adv-x="249.0" d="M65 50q0 29 17.5 46.5t42.5 17.5q24 0 41.5 -17.5t17.5 -46.5q0 -27 -17.5 -44.5t-41.5 -17.5q-25 0 -42.5 17.5t-17.5 44.5z" unicode="."></glyph><glyph glyph-name=".notdef" horiz-adv-x="653.0" d="M89 660h476v-660h-476v660zM281 340l-127 232v-462zM498 110v462l-126 -232zM454 58l-73 132l-52 103h-4l-54 -103l-74 -132h257zM329 387l49 94l66 119h-235l66 -119l50 -94h4z"></glyph><glyph glyph-name="zero" horiz-adv-x="497.0" d="M249 -12q-97 0 -151 86t-54 247t54 245t151 84q96 0 150 -84t54 -245t-54 -247t-150 -86zM249 54q28 0 50.5 15.5t39 48t25.5 83t9 120.5t-9 120t-25.5 81.5t-39 46.5t-50.5 15t-51 -15t-39.5 -46.5t-25.5 -81.5t-9 -120q0 -140 34.5 -203.5t90.5 -63.5z" unicode="0"></glyph><glyph glyph-name="one" horiz-adv-x="497.0" d="M79 68h146v470h-116v53q44 8 76.5 19.5t58.5 27.5h63v-570h132v-68h-360v68z" unicode="1"></glyph><glyph glyph-name="two" horiz-adv-x="497.0" d="M40 49q72 72 128 130t94 107.5t58 91t20 80.5q0 55 -30 90t-91 35q-40 0 -74 -22.5t-62 -54.5l-47 47q40 44 85 70.5t108 26.5q89 0 140 -51.5t51 -136.5q0 -45 -19.5 -90.5t-54 -94t-82 -101t-104.5 -111.5q26 2 54 4t53 2h185v-71h-412v49z" unicode="2"></glyph><glyph glyph-name="three" horiz-adv-x="497.0" d="M68 132q29 -30 67.5 -53t95.5 -23q58 0 95 31.5t37 85.5q0 28 -10.5 51.5t-34.5 40.5t-63 26t-96 9v63q51 0 85.5 9t56 25t30.5 38t9 47q0 47 -29.5 74t-80.5 27q-40 0 -73.5 -18t-62.5 -47l-44 52q37 35 81.5 57.5t101.5 22.5q42 0 77 -11t60.5 -31.5t39.5 -50.5t14 -69 4 | q0 -58 -32 -95t-84 -57v-4q29 -7 54 -20.5t44 -34t29.5 -47.5t10.5 -60q0 -42 -16.5 -76t-45 -57.5t-66.5 -36t-82 -12.5q-38 0 -69.5 7.5t-57.5 20t-46.5 28.5t-36.5 34z" unicode="3"></glyph><glyph glyph-name="four" horiz-adv-x="497.0" d="M304 242v185q0 26 1.5 61.5t3.5 61.5h-4q-12 -23 -25 -45t-27 -45l-149 -218h200zM469 176h-87v-176h-78v176h-287v54l273 408h92v-396h87v-66z" unicode="4"></glyph><glyph glyph-name="five" horiz-adv-x="497.0" d="M65 129q28 -29 66.5 -51t94.5 -22q29 0 54.5 10.5t44.5 29.5t30 46t11 60q0 66 -37 103t-99 37q-33 0 -56.5 -10t-52.5 -29l-44 28l21 307h319v-71h-247l-17 -189q23 12 46 19t52 7q41 0 77 -12t63 -36.5t42.5 -62t15.5 -89.5t-18 -92t-48 -67.5t-68.5 -42t-80.5 -14.5 5 | q-38 0 -69.5 7.5t-57 19.5t-46 27.5t-36.5 32.5z" unicode="5"></glyph><glyph glyph-name="six" horiz-adv-x="497.0" d="M268 53q24 0 44 10t35 28.5t23.5 44t8.5 57.5q0 63 -29 99t-89 36q-30 0 -65.5 -19.5t-67.5 -64.5q8 -94 43.5 -142.5t96.5 -48.5zM399 531q-20 23 -47.5 36.5t-57.5 13.5q-33 0 -63 -14t-53 -46t-37 -83.5t-15 -127.5q30 37 70 58.5t79 21.5q83 0 132.5 -49t49.5 -148 6 | q0 -46 -15 -83.5t-41 -64.5t-60 -42t-73 -15q-47 0 -87 19t-69.5 57.5t-46.5 96t-17 134.5q0 96 20 163.5t54 110t77.5 62t91.5 19.5q52 0 89.5 -19.5t64.5 -48.5z" unicode="6"></glyph><glyph glyph-name="a" horiz-adv-x="512.0" d="M58 126q0 80 71.5 122.5t227.5 59.5q0 23 -4.5 45t-16 39t-30.5 27.5t-49 10.5q-43 0 -79.5 -16t-65.5 -36l-33 57q34 22 83 42.5t108 20.5q89 0 129 -54.5t40 -145.5v-298h-68l-7 58h-2q-35 -29 -75.5 -49.5t-85.5 -20.5q-62 0 -102.5 36t-40.5 102zM139 132 7 | q0 -42 24.5 -60t60.5 -18q35 0 66.5 16.5t66.5 48.5v135q-61 -8 -103 -19t-67.5 -26t-36.5 -34.5t-11 -42.5z" unicode="a"></glyph><glyph glyph-name="b" horiz-adv-x="555.0" d="M82 712h82v-194l-2 -88q33 29 72 48.5t80 19.5q47 0 83 -17.5t60.5 -50t37 -78t12.5 -101.5q0 -62 -17 -111t-46 -83t-67 -51.5t-80 -17.5q-34 0 -70.5 15.5t-68.5 44.5h-3l-7 -48h-66v712zM164 108q32 -28 63.5 -39.5t55.5 -11.5q30 0 55.5 13.5t44 38t29 60.5t10.5 81 8 | q0 40 -7 73t-22.5 56.5t-40 36.5t-58.5 13q-59 0 -130 -66v-255z" unicode="b"></glyph><glyph glyph-name="c" horiz-adv-x="456.0" d="M46 242q0 61 19 108.5t51 80.5t74.5 50t89.5 17q48 0 82.5 -17.5t59.5 -40.5l-41 -53q-22 19 -45.5 31t-52.5 12q-33 0 -61 -13.5t-48 -38.5t-31.5 -59.5t-11.5 -76.5t11 -76t30.5 -58.5t47.5 -38t61 -13.5q35 0 63.5 14.5t50.5 34.5l37 -54q-33 -29 -73.5 -46t-84.5 -17 9 | q-48 0 -90 17t-72.5 49.5t-48 80t-17.5 107.5z" unicode="c"></glyph><glyph glyph-name="d" horiz-adv-x="555.0" d="M47 242q0 59 17.5 106.5t46.5 80.5t67 51t80 18t73 -15t63 -41l-4 83v187h83v-712h-68l-7 57h-3q-29 -28 -66.5 -48.5t-80.5 -20.5q-92 0 -146.5 66t-54.5 188zM132 243q0 -88 35 -137t99 -49q34 0 64 16.5t60 50.5v254q-31 28 -59.5 39.5t-58.5 11.5q-29 0 -54.5 -13.5 10 | t-44.5 -38t-30 -58.5t-11 -76z" unicode="d"></glyph><glyph glyph-name="e" horiz-adv-x="496.0" d="M46 242q0 60 18.5 107.5t49 80.5t69.5 50.5t81 17.5q46 0 82.5 -16t61 -46t37.5 -72t13 -94q0 -27 -3 -45h-328q5 -79 48.5 -125t113.5 -46q35 0 64.5 10.5t56.5 27.5l29 -54q-32 -20 -71 -35t-89 -15q-49 0 -91.5 17.5t-74 50t-49.5 79.5t-18 107zM386 279 11 | q0 75 -31.5 114.5t-88.5 39.5q-26 0 -49.5 -10.5t-42.5 -30t-31.5 -48t-16.5 -65.5h260z" unicode="e"></glyph><glyph glyph-name="h" horiz-adv-x="544.0" d="M82 712h82v-194l-3 -100q35 33 73 56.5t89 23.5q77 0 112.5 -48t35.5 -142v-308h-82v297q0 69 -22 99.5t-70 30.5q-38 0 -67 -19t-66 -56v-352h-82v712z" unicode="h"></glyph><glyph glyph-name="i" horiz-adv-x="246.0" d="M124 586q-24 0 -40.5 15t-16.5 38q0 24 16.5 38.5t40.5 14.5t40.5 -14.5t16.5 -38.5q0 -23 -16.5 -38t-40.5 -15zM82 486h82v-486h-82v486z" unicode="i"></glyph><glyph glyph-name="l" horiz-adv-x="255.0" d="M82 712h82v-620q0 -20 7 -28t16 -8h7.5t10.5 2l11 -62q-8 -4 -19 -6t-28 -2q-47 0 -67 28t-20 82v614z" unicode="l"></glyph><glyph glyph-name="m" horiz-adv-x="829.0" d="M82 486h68l7 -70h3q32 35 69.5 58.5t81.5 23.5q56 0 87.5 -24.5t46.5 -68.5q38 42 76.5 67.5t83.5 25.5q75 0 111.5 -48t36.5 -142v-308h-82v297q0 69 -22 99.5t-68 30.5q-55 0 -122 -75v-352h-82v297q0 69 -22 99.5t-69 30.5q-55 0 -122 -75v-352h-82v486z" unicode="m"></glyph><glyph glyph-name="n" horiz-adv-x="547.0" d="M82 486h68l7 -70h3q35 35 73.5 58.5t89.5 23.5q77 0 112.5 -48t35.5 -142v-308h-82v297q0 69 -22 99.5t-70 30.5q-38 0 -67 -19t-66 -56v-352h-82v486z" unicode="n"></glyph><glyph glyph-name="o" horiz-adv-x="542.0" d="M46 242q0 61 18.5 108.5t49.5 80.5t71.5 50t85.5 17t85.5 -17t71.5 -50t49.5 -80.5t18.5 -108.5q0 -60 -18.5 -107.5t-49.5 -80t-71.5 -49.5t-85.5 -17t-85.5 17t-71.5 49.5t-49.5 80t-18.5 107.5zM131 242q0 -42 10 -76t28.5 -58.5t44.5 -38t57 -13.5t57 13.5t44.5 38 12 | t28.5 58.5t10 76t-10 76.5t-28.5 59.5t-44.5 38.5t-57 13.5t-57 -13.5t-44.5 -38.5t-28.5 -59.5t-10 -76.5z" unicode="o"></glyph><glyph glyph-name="r" horiz-adv-x="347.0" d="M82 486h68l7 -88h3q25 46 60.5 73t77.5 27q29 0 52 -10l-16 -72q-12 4 -22 6t-25 2q-31 0 -64.5 -25t-58.5 -87v-312h-82v486z" unicode="r"></glyph><glyph glyph-name="s" horiz-adv-x="419.0" d="M69 110q32 -26 65.5 -42t77.5 -16q48 0 72 22t24 54q0 19 -10 33t-25.5 24.5t-35.5 18.5l-40 16q-26 9 -52 20.5t-46.5 28t-33.5 38.5t-13 53q0 29 11.5 54.5t33 44t52.5 29t70 10.5q46 0 84.5 -16t66.5 -39l-39 -52q-25 19 -52 31t-59 12q-46 0 -67.5 -21t-21.5 -49 13 | q0 -17 9 -29.5t24 -22t34.5 -17t40.5 -15.5q26 -10 52.5 -21t47.5 -27.5t34.5 -40.5t13.5 -58q0 -30 -11.5 -56t-34 -46t-56 -31.5t-76.5 -11.5q-52 0 -99 19t-82 48z" unicode="s"></glyph><glyph glyph-name="t" horiz-adv-x="338.0" d="M96 419h-72v62l76 5l10 136h69v-136h131v-67h-131v-270q0 -45 16.5 -69.5t58.5 -24.5q13 0 28 4t27 9l16 -62q-20 -7 -43.5 -12.5t-46.5 -5.5q-39 0 -65.5 12t-43 33t-23.5 51t-7 66v269z" unicode="t"></glyph><glyph glyph-name="v" horiz-adv-x="467.0" d="M12 486h85l92 -276q11 -36 22.5 -72t22.5 -71h4q11 35 22 71l22 72l92 276h81l-172 -486h-96z" unicode="v"></glyph><hkern k="10" g1="c" g2="a" /><hkern k="21" g1="c" g2="c,d,e,o" /><hkern k="-6" g1="c" g2="v" /><hkern k="14" g1="e" g2="a" /><hkern k="14" g1="e" g2="t" /><hkern k="-5" g1="e" g2="v" /><hkern k="14" g1="b,o" g2="a" /><hkern k="4" g1="b,o" g2="v" /><hkern k="25" g1="r" g2="a" /><hkern k="10" g1="r" g2="c,d,e,o" /><hkern k="-19" g1="r" g2="v" /><hkern k="10" g1="r" g2="s" /><hkern k="18" g1="t" g2="a" /><hkern k="10" g1="t" g2="c,d,e,o" /><hkern k="20" g1="v" g2="a" /><hkern k="4" g1="v" g2="c,d,e,o" /></font><font horiz-adv-x="0.0"><font-face font-family="sans-serif" font-style="all" font-weight="700" font-stretch="normal" font-variant="normal" units-per-em="1000.0" panose-1="2 11 7 3 3 4 3 2 2 4" ascent="750.0" descent="-250.0" x-height="496.0" cap-height="652.0" bbox="-231.0 -383.0 1223.0 974.0" underline-thickness="50.0" underline-position="-50.0" unicode-range="U+000D-FB02" /><missing-glyph d="M80 660h530v-660h-530v660zM273 340l-95 186v-371zM511 155v371l-94 -186zM427 91l-39 77l-41 98h-4l-41 -98l-39 -77h164zM347 414l42 95l32 59h-152l31 -59l43 -95h4z"></missing-glyph><glyph glyph-name=".notdef" horiz-adv-x="690.0" d="M80 660h530v-660h-530v660zM273 340l-95 186v-371zM511 155v371l-94 -186zM427 91l-39 77l-41 98h-4l-41 -98l-39 -77h164zM347 414l42 95l32 59h-152l31 -59l43 -95h4z"></glyph><glyph glyph-name="L" horiz-adv-x="518.0" d="M77 652h147v-528h258v-124h-405v652z" unicode="L"></glyph><glyph glyph-name="i" horiz-adv-x="276.0" d="M138 569q-37 0 -61 21.5t-24 55.5t24 55t61 21q38 0 61.5 -21t23.5 -55t-23.5 -55.5t-61.5 -21.5zM65 496h147v-496h-147v496z" unicode="i"></glyph><glyph glyph-name="o" horiz-adv-x="555.0" d="M36 248q0 62 20 110.5t53.5 81.5t77.5 50.5t91 17.5t90.5 -17.5t77 -50.5t53.5 -81.5t20 -110.5t-20 -110.5t-53.5 -81.5t-77 -50.5t-90.5 -17.5t-91 17.5t-77.5 50.5t-53.5 81.5t-20 110.5zM187 248q0 -65 22.5 -103t68.5 -38q45 0 68 38t23 103t-23 103t-68 38 14 | q-46 0 -68.5 -38t-22.5 -103z" unicode="o"></glyph><glyph glyph-name="s" horiz-adv-x="443.0" d="M87 149q34 -26 65 -39t63 -13q33 0 48 11t15 31q0 12 -8.5 21.5t-23 17.5t-32.5 14.5t-37 14.5q-23 9 -46 21t-42 29.5t-31 41t-12 54.5q0 34 13.5 63t38.5 49t60 31.5t78 11.5q57 0 100 -19.5t75 -43.5l-66 -88q-27 20 -53 31t-52 11q-56 0 -56 -39q0 -12 8 -20.5 15 | t21.5 -15.5t31 -13.5t36.5 -13.5q24 -9 47.5 -20.5t43 -28.5t31.5 -41.5t12 -58.5t-13 -63t-39 -50.5t-64 -34t-88 -12.5q-49 0 -100.5 19t-89.5 50z" unicode="s"></glyph><glyph glyph-name="t" horiz-adv-x="383.0" d="M85 381h-68v109l76 6l17 132h122v-132h119v-115h-119v-199q0 -42 17.5 -60.5t46.5 -18.5q12 0 24.5 3t22.5 7l23 -107q-20 -6 -47 -12t-63 -6q-46 0 -78.5 14t-53 39t-30 60.5t-9.5 78.5v201z" unicode="t"></glyph><hkern k="14" g1="L" g2="o" /><hkern k="27" g1="L" g2="t" /><hkern k="5" g1="o" g2="s" /><hkern k="10" g1="t" g2="o" /></font>toListtime (s)0.0000010.000010.00010.0010.010.15.0e21.0e35.0e31.0e45.0e41.0e55.0e51.0e6# elementshashtables basichashtables basic (st. dev.)vector-hashtablesvector-hashtables (st. dev.) -------------------------------------------------------------------------------- /charts/fromList.svg: -------------------------------------------------------------------------------- 1 | 2 | <font horiz-adv-x="0.0"><font-face font-family="sans-serif" font-style="all" font-weight="400" font-stretch="normal" font-variant="normal" units-per-em="1000.0" panose-1="2 11 5 3 3 4 3 2 2 4" ascent="750.0" descent="-250.0" x-height="486.0" cap-height="656.0" bbox="-192.0 -323.0 1160.0 952.0" underline-thickness="50.0" underline-position="-50.0" unicode-range="U+000D-FB02" /><missing-glyph d="M89 660h476v-660h-476v660zM281 340l-127 232v-462zM498 110v462l-126 -232zM454 58l-73 132l-52 103h-4l-54 -103l-74 -132h257zM329 387l49 94l66 119h-235l66 -119l50 -94h4z"></missing-glyph><glyph glyph-name="space" horiz-adv-x="202.0" d="" unicode=" "></glyph><glyph glyph-name="numbersign" horiz-adv-x="497.0" d="M115 204h-80v57h87l18 148h-85v58h92l23 183h53l-23 -183h133l24 183h53l-24 -183h81v-58h-87l-18 -148h85v-57h-92l-25 -204h-53l24 204h-132l-25 -204h-54zM308 261l18 148h-132l-18 -148h132z" unicode="#"></glyph><glyph glyph-name="parenleft" horiz-adv-x="303.0" d="M214 -176q-62 100 -97 211t-35 243t35 242.5t97 211.5l51 -24q-58 -96 -86.5 -205.5t-28.5 -224.5t28.5 -224.5t86.5 -205.5l-51 -24v0z" unicode="("></glyph><glyph glyph-name="parenright" horiz-adv-x="303.0" d="M38 -152q58 96 86.5 205.5t28.5 224.5t-28.5 224.5t-86.5 205.5l51 24q62 -101 97 -211.5t35 -242.5t-35 -243t-97 -211l-51 24v0z" unicode=")"></glyph><glyph glyph-name="hyphen" horiz-adv-x="311.0" d="M41 282h230v-63h-230v63z" unicode="-"></glyph><glyph glyph-name="period" horiz-adv-x="249.0" d="M65 50q0 29 17.5 46.5t42.5 17.5q24 0 41.5 -17.5t17.5 -46.5q0 -27 -17.5 -44.5t-41.5 -17.5q-25 0 -42.5 17.5t-17.5 44.5z" unicode="."></glyph><glyph glyph-name=".notdef" horiz-adv-x="653.0" d="M89 660h476v-660h-476v660zM281 340l-127 232v-462zM498 110v462l-126 -232zM454 58l-73 132l-52 103h-4l-54 -103l-74 -132h257zM329 387l49 94l66 119h-235l66 -119l50 -94h4z"></glyph><glyph glyph-name="zero" horiz-adv-x="497.0" d="M249 -12q-97 0 -151 86t-54 247t54 245t151 84q96 0 150 -84t54 -245t-54 -247t-150 -86zM249 54q28 0 50.5 15.5t39 48t25.5 83t9 120.5t-9 120t-25.5 81.5t-39 46.5t-50.5 15t-51 -15t-39.5 -46.5t-25.5 -81.5t-9 -120q0 -140 34.5 -203.5t90.5 -63.5z" unicode="0"></glyph><glyph glyph-name="one" horiz-adv-x="497.0" d="M79 68h146v470h-116v53q44 8 76.5 19.5t58.5 27.5h63v-570h132v-68h-360v68z" unicode="1"></glyph><glyph glyph-name="two" horiz-adv-x="497.0" d="M40 49q72 72 128 130t94 107.5t58 91t20 80.5q0 55 -30 90t-91 35q-40 0 -74 -22.5t-62 -54.5l-47 47q40 44 85 70.5t108 26.5q89 0 140 -51.5t51 -136.5q0 -45 -19.5 -90.5t-54 -94t-82 -101t-104.5 -111.5q26 2 54 4t53 2h185v-71h-412v49z" unicode="2"></glyph><glyph glyph-name="three" horiz-adv-x="497.0" d="M68 132q29 -30 67.5 -53t95.5 -23q58 0 95 31.5t37 85.5q0 28 -10.5 51.5t-34.5 40.5t-63 26t-96 9v63q51 0 85.5 9t56 25t30.5 38t9 47q0 47 -29.5 74t-80.5 27q-40 0 -73.5 -18t-62.5 -47l-44 52q37 35 81.5 57.5t101.5 22.5q42 0 77 -11t60.5 -31.5t39.5 -50.5t14 -69 4 | q0 -58 -32 -95t-84 -57v-4q29 -7 54 -20.5t44 -34t29.5 -47.5t10.5 -60q0 -42 -16.5 -76t-45 -57.5t-66.5 -36t-82 -12.5q-38 0 -69.5 7.5t-57.5 20t-46.5 28.5t-36.5 34z" unicode="3"></glyph><glyph glyph-name="four" horiz-adv-x="497.0" d="M304 242v185q0 26 1.5 61.5t3.5 61.5h-4q-12 -23 -25 -45t-27 -45l-149 -218h200zM469 176h-87v-176h-78v176h-287v54l273 408h92v-396h87v-66z" unicode="4"></glyph><glyph glyph-name="five" horiz-adv-x="497.0" d="M65 129q28 -29 66.5 -51t94.5 -22q29 0 54.5 10.5t44.5 29.5t30 46t11 60q0 66 -37 103t-99 37q-33 0 -56.5 -10t-52.5 -29l-44 28l21 307h319v-71h-247l-17 -189q23 12 46 19t52 7q41 0 77 -12t63 -36.5t42.5 -62t15.5 -89.5t-18 -92t-48 -67.5t-68.5 -42t-80.5 -14.5 5 | q-38 0 -69.5 7.5t-57 19.5t-46 27.5t-36.5 32.5z" unicode="5"></glyph><glyph glyph-name="six" horiz-adv-x="497.0" d="M268 53q24 0 44 10t35 28.5t23.5 44t8.5 57.5q0 63 -29 99t-89 36q-30 0 -65.5 -19.5t-67.5 -64.5q8 -94 43.5 -142.5t96.5 -48.5zM399 531q-20 23 -47.5 36.5t-57.5 13.5q-33 0 -63 -14t-53 -46t-37 -83.5t-15 -127.5q30 37 70 58.5t79 21.5q83 0 132.5 -49t49.5 -148 6 | q0 -46 -15 -83.5t-41 -64.5t-60 -42t-73 -15q-47 0 -87 19t-69.5 57.5t-46.5 96t-17 134.5q0 96 20 163.5t54 110t77.5 62t91.5 19.5q52 0 89.5 -19.5t64.5 -48.5z" unicode="6"></glyph><glyph glyph-name="a" horiz-adv-x="512.0" d="M58 126q0 80 71.5 122.5t227.5 59.5q0 23 -4.5 45t-16 39t-30.5 27.5t-49 10.5q-43 0 -79.5 -16t-65.5 -36l-33 57q34 22 83 42.5t108 20.5q89 0 129 -54.5t40 -145.5v-298h-68l-7 58h-2q-35 -29 -75.5 -49.5t-85.5 -20.5q-62 0 -102.5 36t-40.5 102zM139 132 7 | q0 -42 24.5 -60t60.5 -18q35 0 66.5 16.5t66.5 48.5v135q-61 -8 -103 -19t-67.5 -26t-36.5 -34.5t-11 -42.5z" unicode="a"></glyph><glyph glyph-name="b" horiz-adv-x="555.0" d="M82 712h82v-194l-2 -88q33 29 72 48.5t80 19.5q47 0 83 -17.5t60.5 -50t37 -78t12.5 -101.5q0 -62 -17 -111t-46 -83t-67 -51.5t-80 -17.5q-34 0 -70.5 15.5t-68.5 44.5h-3l-7 -48h-66v712zM164 108q32 -28 63.5 -39.5t55.5 -11.5q30 0 55.5 13.5t44 38t29 60.5t10.5 81 8 | q0 40 -7 73t-22.5 56.5t-40 36.5t-58.5 13q-59 0 -130 -66v-255z" unicode="b"></glyph><glyph glyph-name="c" horiz-adv-x="456.0" d="M46 242q0 61 19 108.5t51 80.5t74.5 50t89.5 17q48 0 82.5 -17.5t59.5 -40.5l-41 -53q-22 19 -45.5 31t-52.5 12q-33 0 -61 -13.5t-48 -38.5t-31.5 -59.5t-11.5 -76.5t11 -76t30.5 -58.5t47.5 -38t61 -13.5q35 0 63.5 14.5t50.5 34.5l37 -54q-33 -29 -73.5 -46t-84.5 -17 9 | q-48 0 -90 17t-72.5 49.5t-48 80t-17.5 107.5z" unicode="c"></glyph><glyph glyph-name="d" horiz-adv-x="555.0" d="M47 242q0 59 17.5 106.5t46.5 80.5t67 51t80 18t73 -15t63 -41l-4 83v187h83v-712h-68l-7 57h-3q-29 -28 -66.5 -48.5t-80.5 -20.5q-92 0 -146.5 66t-54.5 188zM132 243q0 -88 35 -137t99 -49q34 0 64 16.5t60 50.5v254q-31 28 -59.5 39.5t-58.5 11.5q-29 0 -54.5 -13.5 10 | t-44.5 -38t-30 -58.5t-11 -76z" unicode="d"></glyph><glyph glyph-name="e" horiz-adv-x="496.0" d="M46 242q0 60 18.5 107.5t49 80.5t69.5 50.5t81 17.5q46 0 82.5 -16t61 -46t37.5 -72t13 -94q0 -27 -3 -45h-328q5 -79 48.5 -125t113.5 -46q35 0 64.5 10.5t56.5 27.5l29 -54q-32 -20 -71 -35t-89 -15q-49 0 -91.5 17.5t-74 50t-49.5 79.5t-18 107zM386 279 11 | q0 75 -31.5 114.5t-88.5 39.5q-26 0 -49.5 -10.5t-42.5 -30t-31.5 -48t-16.5 -65.5h260z" unicode="e"></glyph><glyph glyph-name="h" horiz-adv-x="544.0" d="M82 712h82v-194l-3 -100q35 33 73 56.5t89 23.5q77 0 112.5 -48t35.5 -142v-308h-82v297q0 69 -22 99.5t-70 30.5q-38 0 -67 -19t-66 -56v-352h-82v712z" unicode="h"></glyph><glyph glyph-name="i" horiz-adv-x="246.0" d="M124 586q-24 0 -40.5 15t-16.5 38q0 24 16.5 38.5t40.5 14.5t40.5 -14.5t16.5 -38.5q0 -23 -16.5 -38t-40.5 -15zM82 486h82v-486h-82v486z" unicode="i"></glyph><glyph glyph-name="l" horiz-adv-x="255.0" d="M82 712h82v-620q0 -20 7 -28t16 -8h7.5t10.5 2l11 -62q-8 -4 -19 -6t-28 -2q-47 0 -67 28t-20 82v614z" unicode="l"></glyph><glyph glyph-name="m" horiz-adv-x="829.0" d="M82 486h68l7 -70h3q32 35 69.5 58.5t81.5 23.5q56 0 87.5 -24.5t46.5 -68.5q38 42 76.5 67.5t83.5 25.5q75 0 111.5 -48t36.5 -142v-308h-82v297q0 69 -22 99.5t-68 30.5q-55 0 -122 -75v-352h-82v297q0 69 -22 99.5t-69 30.5q-55 0 -122 -75v-352h-82v486z" unicode="m"></glyph><glyph glyph-name="n" horiz-adv-x="547.0" d="M82 486h68l7 -70h3q35 35 73.5 58.5t89.5 23.5q77 0 112.5 -48t35.5 -142v-308h-82v297q0 69 -22 99.5t-70 30.5q-38 0 -67 -19t-66 -56v-352h-82v486z" unicode="n"></glyph><glyph glyph-name="o" horiz-adv-x="542.0" d="M46 242q0 61 18.5 108.5t49.5 80.5t71.5 50t85.5 17t85.5 -17t71.5 -50t49.5 -80.5t18.5 -108.5q0 -60 -18.5 -107.5t-49.5 -80t-71.5 -49.5t-85.5 -17t-85.5 17t-71.5 49.5t-49.5 80t-18.5 107.5zM131 242q0 -42 10 -76t28.5 -58.5t44.5 -38t57 -13.5t57 13.5t44.5 38 12 | t28.5 58.5t10 76t-10 76.5t-28.5 59.5t-44.5 38.5t-57 13.5t-57 -13.5t-44.5 -38.5t-28.5 -59.5t-10 -76.5z" unicode="o"></glyph><glyph glyph-name="r" horiz-adv-x="347.0" d="M82 486h68l7 -88h3q25 46 60.5 73t77.5 27q29 0 52 -10l-16 -72q-12 4 -22 6t-25 2q-31 0 -64.5 -25t-58.5 -87v-312h-82v486z" unicode="r"></glyph><glyph glyph-name="s" horiz-adv-x="419.0" d="M69 110q32 -26 65.5 -42t77.5 -16q48 0 72 22t24 54q0 19 -10 33t-25.5 24.5t-35.5 18.5l-40 16q-26 9 -52 20.5t-46.5 28t-33.5 38.5t-13 53q0 29 11.5 54.5t33 44t52.5 29t70 10.5q46 0 84.5 -16t66.5 -39l-39 -52q-25 19 -52 31t-59 12q-46 0 -67.5 -21t-21.5 -49 13 | q0 -17 9 -29.5t24 -22t34.5 -17t40.5 -15.5q26 -10 52.5 -21t47.5 -27.5t34.5 -40.5t13.5 -58q0 -30 -11.5 -56t-34 -46t-56 -31.5t-76.5 -11.5q-52 0 -99 19t-82 48z" unicode="s"></glyph><glyph glyph-name="t" horiz-adv-x="338.0" d="M96 419h-72v62l76 5l10 136h69v-136h131v-67h-131v-270q0 -45 16.5 -69.5t58.5 -24.5q13 0 28 4t27 9l16 -62q-20 -7 -43.5 -12.5t-46.5 -5.5q-39 0 -65.5 12t-43 33t-23.5 51t-7 66v269z" unicode="t"></glyph><glyph glyph-name="v" horiz-adv-x="467.0" d="M12 486h85l92 -276q11 -36 22.5 -72t22.5 -71h4q11 35 22 71l22 72l92 276h81l-172 -486h-96z" unicode="v"></glyph><hkern k="10" g1="c" g2="a" /><hkern k="21" g1="c" g2="c,d,e,o" /><hkern k="-6" g1="c" g2="v" /><hkern k="14" g1="e" g2="a" /><hkern k="14" g1="e" g2="t" /><hkern k="-5" g1="e" g2="v" /><hkern k="14" g1="b,o" g2="a" /><hkern k="4" g1="b,o" g2="v" /><hkern k="25" g1="r" g2="a" /><hkern k="10" g1="r" g2="c,d,e,o" /><hkern k="-19" g1="r" g2="v" /><hkern k="10" g1="r" g2="s" /><hkern k="18" g1="t" g2="a" /><hkern k="10" g1="t" g2="c,d,e,o" /><hkern k="20" g1="v" g2="a" /><hkern k="4" g1="v" g2="c,d,e,o" /></font><font horiz-adv-x="0.0"><font-face font-family="sans-serif" font-style="all" font-weight="700" font-stretch="normal" font-variant="normal" units-per-em="1000.0" panose-1="2 11 7 3 3 4 3 2 2 4" ascent="750.0" descent="-250.0" x-height="496.0" cap-height="652.0" bbox="-231.0 -383.0 1223.0 974.0" underline-thickness="50.0" underline-position="-50.0" unicode-range="U+000D-FB02" /><missing-glyph d="M80 660h530v-660h-530v660zM273 340l-95 186v-371zM511 155v371l-94 -186zM427 91l-39 77l-41 98h-4l-41 -98l-39 -77h164zM347 414l42 95l32 59h-152l31 -59l43 -95h4z"></missing-glyph><glyph glyph-name=".notdef" horiz-adv-x="690.0" d="M80 660h530v-660h-530v660zM273 340l-95 186v-371zM511 155v371l-94 -186zM427 91l-39 77l-41 98h-4l-41 -98l-39 -77h164zM347 414l42 95l32 59h-152l31 -59l43 -95h4z"></glyph><glyph glyph-name="L" horiz-adv-x="518.0" d="M77 652h147v-528h258v-124h-405v652z" unicode="L"></glyph><glyph glyph-name="f" horiz-adv-x="341.0" d="M345 587q-28 10 -51 10q-27 0 -42 -16.5t-15 -54.5v-30h89v-115h-89v-381h-147v381h-66v109l66 5v27q0 39 9.5 74t31.5 61t57 41t85 15q31 0 56.5 -6t42.5 -12z" unicode="f"></glyph><glyph glyph-name="i" horiz-adv-x="276.0" d="M138 569q-37 0 -61 21.5t-24 55.5t24 55t61 21q38 0 61.5 -21t23.5 -55t-23.5 -55.5t-61.5 -21.5zM65 496h147v-496h-147v496z" unicode="i"></glyph><glyph glyph-name="m" horiz-adv-x="857.0" d="M65 496h120l10 -64h4q31 31 66 53.5t84 22.5q53 0 85.5 -21.5t51.5 -61.5q33 34 69.5 58.5t86.5 24.5q80 0 117.5 -53.5t37.5 -146.5v-308h-147v289q0 54 -14.5 74t-46.5 20q-37 0 -85 -48v-335h-147v289q0 54 -14.5 74t-46.5 20q-38 0 -84 -48v-335h-147v496z" unicode="m"></glyph><glyph glyph-name="o" horiz-adv-x="555.0" d="M36 248q0 62 20 110.5t53.5 81.5t77.5 50.5t91 17.5t90.5 -17.5t77 -50.5t53.5 -81.5t20 -110.5t-20 -110.5t-53.5 -81.5t-77 -50.5t-90.5 -17.5t-91 17.5t-77.5 50.5t-53.5 81.5t-20 110.5zM187 248q0 -65 22.5 -103t68.5 -38q45 0 68 38t23 103t-23 103t-68 38 14 | q-46 0 -68.5 -38t-22.5 -103z" unicode="o"></glyph><glyph glyph-name="r" horiz-adv-x="398.0" d="M65 496h120l10 -87h4q27 51 65 75t76 24q21 0 34.5 -2.5t24.5 -7.5l-24 -127q-14 4 -26 6t-28 2q-28 0 -58.5 -20t-50.5 -71v-288h-147v496z" unicode="r"></glyph><glyph glyph-name="s" horiz-adv-x="443.0" d="M87 149q34 -26 65 -39t63 -13q33 0 48 11t15 31q0 12 -8.5 21.5t-23 17.5t-32.5 14.5t-37 14.5q-23 9 -46 21t-42 29.5t-31 41t-12 54.5q0 34 13.5 63t38.5 49t60 31.5t78 11.5q57 0 100 -19.5t75 -43.5l-66 -88q-27 20 -53 31t-52 11q-56 0 -56 -39q0 -12 8 -20.5 15 | t21.5 -15.5t31 -13.5t36.5 -13.5q24 -9 47.5 -20.5t43 -28.5t31.5 -41.5t12 -58.5t-13 -63t-39 -50.5t-64 -34t-88 -12.5q-49 0 -100.5 19t-89.5 50z" unicode="s"></glyph><glyph glyph-name="t" horiz-adv-x="383.0" d="M85 381h-68v109l76 6l17 132h122v-132h119v-115h-119v-199q0 -42 17.5 -60.5t46.5 -18.5q12 0 24.5 3t22.5 7l23 -107q-20 -6 -47 -12t-63 -6q-46 0 -78.5 14t-53 39t-30 60.5t-9.5 78.5v201z" unicode="t"></glyph><hkern k="18" g1="L" g2="f" /><hkern k="14" g1="L" g2="o" /><hkern k="27" g1="L" g2="t" /><hkern k="10" g1="f" g2="o" /><hkern k="8" g1="f" g2="s" /><hkern k="5" g1="o" g2="f" /><hkern k="5" g1="o" g2="s" /><hkern k="10" g1="r" g2="o" /><hkern k="10" g1="r" g2="s" /><hkern k="10" g1="t" g2="o" /></font>fromListtime (s)0.000010.00010.0010.010.115.0e21.0e35.0e31.0e45.0e41.0e55.0e51.0e6# elementshashtables basichashtables basic (st. dev.)vector-hashtablesvector-hashtables (st. dev.) --------------------------------------------------------------------------------