Skip to content

Commit c93cd17

Browse files
committed
List Functor: mix unrolled and reverse map
Addresses #131 The relevant chunk sizes (5 for the initial list segment), (3 for the tail-recursive remainder) were arrived at through benchmarked experimentation, mapping a simple (_ + 1) through lists of various sizes. Relevant figures: list of 1000 elems: 142.61 μs -> 36.97 μs list of 2000 elems: 275.17 μs -> 55.33 μs list of 10000 elems: 912.73 μs -> 208.39 μs list of 100000 elems: 34.56 ms -> 1.24 ms The ~30x speed increase for long lists is probably explained by the lack of GC thrashing with this approach. Benchmarked on 2017 Macbook Pro, 2.3 GHz Intel Core i5, 8 GB RAM. macOS Sierra 10.12.6 node v8.9.1
1 parent 6c8aaad commit c93cd17

File tree

1 file changed

+46
-3
lines changed

1 file changed

+46
-3
lines changed

src/Data/List/Types.purs

Lines changed: 46 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,8 @@
1-
module Data.List.Types where
1+
module Data.List.Types
2+
( List(..)
3+
, (:)
4+
, NonEmptyList(..)
5+
) where
26

37
import Prelude
48

@@ -10,7 +14,6 @@ import Control.Extend (class Extend)
1014
import Control.MonadPlus (class MonadPlus)
1115
import Control.MonadZero (class MonadZero)
1216
import Control.Plus (class Plus)
13-
1417
import Data.Eq (class Eq1, eq1)
1518
import Data.Foldable (class Foldable, foldl, foldr, intercalate)
1619
import Data.Maybe (Maybe(..))
@@ -65,7 +68,47 @@ instance monoidList :: Monoid (List a) where
6568
mempty = Nil
6669

6770
instance functorList :: Functor List where
68-
map f = foldr (\x acc -> f x : acc) Nil
71+
map = listMap
72+
73+
-- chunked list Functor inspired by OCaml
74+
-- https://discuss.ocaml.org/t/a-new-list-map-that-is-both-stack-safe-and-fast/865
75+
-- chunk sizes determined through experimentation
76+
listMap :: forall a b. (a -> b) -> List a -> List b
77+
listMap f = startUnrolledMap unrollLimit
78+
where
79+
-- iterate the unrolled map up to 1000 times,
80+
-- which hits up to 5000 elements
81+
unrollLimit = 1000
82+
83+
startUnrolledMap :: Int -> List a -> List b
84+
startUnrolledMap 0 (x : xs) = f x : chunkedRevMap xs
85+
startUnrolledMap n (x1 : x2 : x3 : x4 : x5 : xs) =
86+
f x1 : f x2 : f x3 : f x4 : f x5 : startUnrolledMap (n - 1) xs
87+
startUnrolledMap n (x1 : x2 : x3 : x4 : xs) =
88+
f x1 : f x2 : f x3 : f x4 : startUnrolledMap (n - 1) xs
89+
startUnrolledMap n (x1 : x2 : x3 : xs) =
90+
f x1 : f x2 : f x3 : startUnrolledMap (n - 1) xs
91+
startUnrolledMap n (x1 : x2 : xs) =
92+
f x1 : f x2 : startUnrolledMap (n - 1) xs
93+
startUnrolledMap n (x : xs) = f x : startUnrolledMap (n - 1) xs
94+
95+
startUnrolledMap _ Nil = Nil
96+
97+
chunkedRevMap :: List a -> List b
98+
chunkedRevMap = go Nil
99+
where
100+
go :: List (List a) -> List a -> List b
101+
go chunksAcc chunk@(x1 : x2 : x3 : x4 : x5 : xs) =
102+
go (chunk : chunksAcc) xs
103+
go chunksAcc finalChunk =
104+
reverseUnrolledMap chunksAcc $ startUnrolledMap 0 finalChunk
105+
106+
reverseUnrolledMap :: List (List a) -> List b -> List b
107+
reverseUnrolledMap ((x1 : x2 : x3 : _) : cs) acc =
108+
reverseUnrolledMap cs (f x1 : f x2 : f x3 : acc)
109+
-- if we pattern match on Nil, we need a Partial constraint,
110+
-- which kills TCO
111+
reverseUnrolledMap _ acc = acc
69112

70113
instance foldableList :: Foldable List where
71114
foldr f b = foldl (flip f) b <<< rev Nil

0 commit comments

Comments
 (0)