
Hi, I have written a small "wrapper" to speed random-access to a list. The usage scenario I have in mind is a "stream" computation yielding an infinite list, and I want to randomly access elements w/o having to traverse the entire list from the beginning for each access. I suspected something similar must already exist, but nothing I looked at seemed to do the trick. IntMap seems to want a finite input list. Ditto for the various array types, except possibly dynamic array. Attached is the list indexer I came up with, and a small test program (I swap the commented-out lines to switch btw. list & list index tests). I am interested to hear any feedback on this -- whether it duplicates something that already exists, or whether there's a better approach, and comments on the code, etc. Also if somebody can suggest a better name (so as not to overlay the word index too much.) I'll publish it on hackage (or at least github) if people think it's useful. It sped up the program I initally wrote it for enormously. Thanks, Alex

Hi
I find it useful. I benchmarked it with criterion and your test file (see
below) and it is a *lot* faster:
warming up
estimating clock resolution...
mean is 3.776987 us (160001 iterations)
found 887 outliers among 159999 samples (0.6%)
662 (0.4%) high severe
estimating cost of a clock call...
mean is 1.404134 us (27 iterations)
found 5 outliers among 27 samples (18.5%)
1 (3.7%) low mild
1 (3.7%) high mild
3 (11.1%) high severe
benchmarking randAccess IndexList
mean: 2.614148 ms, lb 2.603860 ms, ub 2.642045 ms, ci 0.950
std dev: 79.90122 us, lb 33.73238 us, ub 165.6168 us, ci 0.950
found 13 outliers among 100 samples (13.0%)
12 (12.0%) high severe
variance introduced by outliers: 25.781%
variance is moderately inflated by outliers
benchmarking randAccess list
mean: 42.62869 ms, lb 42.38446 ms, ub 43.48986 ms, ci 0.950
std dev: 2.088308 ms, lb 598.3515 us, ub 4.751391 ms, ci 0.950
found 3 outliers among 100 samples (3.0%)
2 (2.0%) high severe
variance introduced by outliers: 47.437%
variance is moderately inflated by outliers
benchmarking seqAccess IndexList
mean: 6.347177 ms, lb 6.325560 ms, ub 6.369031 ms, ci 0.950
std dev: 111.3361 us, lb 102.5431 us, ub 123.4909 us, ci 0.950
variance introduced by outliers: 10.386%
variance is moderately inflated by outliers
benchmarking seqAccess list
collecting 100 samples, 1 iterations each, in estimated 207.9468 s
mean: 1.919024 s, lb 1.916933 s, ub 1.927423 s, ci 0.950
std dev: 19.69444 ms, lb 1.966086 ms, ub 46.74818 ms, ci 0.950
Maybe an elevator list is a nice name?
Greets,
Edgar
module Main where
import Criterion.Main
import System.Random
-- | Type of index wrapping an underlying list
data LI a = LI Int [LInode a]
data LInode a = LiNonLeaf (LInode a) (LInode a) | LiLeaf (LInode a) [a]
-- | Constructs index from specified list and fanout
fromList :: [a] -> Int -> LI a
fromList l fo =
let topLevel = mkTopLevelNode l
mkTopLevelNode l = LiLeaf (mkTopLevelNode (drop fo l)) l
mkLevel plv = let lv = mkMidLevelNode plv
in lv : mkLevel lv
mkMidLevelNode l = LiNonLeaf (mkMidLevelNode (nodeDrop fo l)) l
in LI fo (topLevel : mkLevel topLevel)
-- drop i nodes from a linear node stream
nodeDrop :: Int -> LInode a -> LInode a
nodeDrop 0 n = n
nodeDrop i n = let i' = i - 1
in case n of
LiNonLeaf n' _ -> nodeDrop i' n'
LiLeaf n' _ -> nodeDrop i' n'
-- | access specified element of underlying list using index to speed access
(!) :: LI a -> Int -> a
(!) (LI fo ns) i =
let getLevel k (n : ns) = let (q,r) = k `quotRem` fo
l = if q == 0
then n
else parent $ getLevel q ns
in nodeDrop r l
parent (LiNonLeaf _ p) = p
(q, r) = i `quotRem` fo
(LiLeaf _ l) = getLevel q ns
in l !! r
a = [1 :: Int ..]
b = fromList a 4
testSequential hi = [(!) b n | n <- [1,3..hi :: Int]]
testSequentialList hi = [a!!n | n <- [1,3..hi :: Int]]
randAccess hi =
let seed = 12345813
g = mkStdGen seed
lst = [1,3..hi]
lst' = fromList lst 32
nIter = 1000
randR _ 0 = []
randR g n = let (a,g') = randomR (0, hi `div` 2 - 1) g
n' = n - 1
--in (lst!!a) : randR g' n'
in (lst'!a) : randR g' n'
in sum $ randR g nIter
-- main = putStrLn $ show $ randAccess
randAccessList hi =
let seed = 12345813
g = mkStdGen seed
lst = [1,3..hi]
nIter = 1000
randR _ 0 = []
randR g n = let (a,g') = randomR (0, hi `div` 2 - 1) g
n' = n - 1
in (lst!!a) : randR g' n'
in sum $ randR g nIter
main = let hi = 50000 in defaultMain [ bench "randAccess IndexList" (nf
(randAccess) hi),
bench "randAccess list" (nf (randAccessList) hi),
bench "seqAccess IndexList" (nf (testSequential) hi),
bench "seqAccess list" (nf (testSequentialList) hi)
]
On Sat, Sep 8, 2012 at 8:55 AM, Alex Stangl
Hi,
I have written a small "wrapper" to speed random-access to a list. The usage scenario I have in mind is a "stream" computation yielding an infinite list, and I want to randomly access elements w/o having to traverse the entire list from the beginning for each access.
I suspected something similar must already exist, but nothing I looked at seemed to do the trick. IntMap seems to want a finite input list. Ditto for the various array types, except possibly dynamic array.
Attached is the list indexer I came up with, and a small test program (I swap the commented-out lines to switch btw. list & list index tests). I am interested to hear any feedback on this -- whether it duplicates something that already exists, or whether there's a better approach, and comments on the code, etc. Also if somebody can suggest a better name (so as not to overlay the word index too much.) I'll publish it on hackage (or at least github) if people think it's useful. It sped up the program I initally wrote it for enormously.
Thanks,
Alex
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Sep 17, 2012 at 10:24:07AM +0200, Edgar Klerks wrote:
I find it useful. I benchmarked it with criterion and your test file (see below) and it is a *lot* faster:
Maybe an elevator list is a nice name?
Hi Edgar, Thanks for your input. I made a separate unit test and benchmark (using Criterion) and put it all on github, along with the latest version of the list index code. http://github.com/astangl/list-index Regards, Alex
participants (2)
-
Alex Stangl
-
Edgar Klerks