[Haskell-cafe] What's your favorite flavor of Iterator type
Silvio Frischknecht
silvio.frischi at gmail.com
Wed May 18 21:53:19 UTC 2016
Hello,
We know about Foldable, but sometimes you just want more functionality
like: give me the rest of the string! Or a function to build pieces back
together. I've been experimenting a bit and come up with 6 flavors of
Iterators that do the same thing. Of course they all work for containers
like ByteStrings, Text.
1) Haskell98 version (I like)
data Iterator98 list ele = Iterator98 {
next98 :: Maybe (ele, Iterator98 list ele),
...
rest98 :: list,
concat98 :: [list] -> list
}
-- How we can create an Iterator98
listIter98 :: [a] -> Iterator98 [a] a
-- How the sum type looks
sum98 :: (Num n) => Iterator98 listN n -> n
Performance: *3
I'll also usually give the type of the constructor and sum functions. I
also benchmarked the sum functions for [] and compared them to the best
sum function I could come up with (which is significantly faster than
the sum in Prelude!!! because it's strict. Whoever came up with the idea
of making it non-strict, must have been drunk at the time :)).
I like how handy and simple typed the Haskell98 version is. There are
absolutely no superfluous Types or Contexts. However, *3 is quite a
heavy penalty and it might even get worse when more functions are added.
2) Haskell98 Explicit (ambivalent)
data IteratorExplicit98 iter list ele = IteratorExplicit98 {
iterExplicit98 :: iter,
nextExplicit98 :: iter -> Maybe (ele, iter)
...
restExplicit98 :: iter -> list
}
listIterExplicit98 :: [a] -> IteratorExplicit98 [a] [a] a
sumExplicit98 :: (Num n) => IteratorExplicit98 it list n -> n
Performance: *1
It is explicit and it is still quite nice to use. There is however
always that extra argument. Note: `iter` and `list` could potentially be
different (in all examples). They are in Haskell however usually the
same. Performance could be different, if you create and destroy a lot of
data of type IteratorExplicit98. However, that won't usually be the case.
3) TypeFamilies (I don't like)
class IteratorTF i where
type ListTF i
type ElemTF i
nextTF :: i -> Maybe (ElemTF i, i)
...
restTF :: i -> ListTF i
instance IteratorTF2Class [ele] ele where
...
sumTF :: (Num n, IteratorTF it, ElemTF it ~ n) => it -> n
Performance: *1
I used to like type families. But now I'm a bit fed up with ~ contexts.
This would be the "Rust" version. Interesting point: List and Elem
functions could be separated into two classes. I.e. Note that no list
type exists in the type of "sum".
4) TypeFamilies2 (ambivalent)
class IteratorTF2Class list ele where
data IteratorTF2 list ele
nextTF2 :: IteratorTF2 list ele -> Maybe (ele, IteratorTF2 list
ele)
...
restTF2 :: IteratorTF2 list ele -> list
instance IteratorTF2Class [ele] ele where
data IteratorTF2 [ele] ele = ListIterTF2 [ele]
sumTF2 :: (Num n, IteratorTF2Class list n) => IteratorTF2 list n -> n
Performance: *1
Better than the last. However, IteratorTF2Class, IteratorTF2 are two
Type-ish things where one would be preferred. This is my preferred
method where all functions are carried in the type.
5) MultiParameterTypeClasses and Functional Dependencies (ambivalent)
class IteratorMPTC iter list ele | iter -> list, iter -> ele where
nextMPTC :: iter -> Maybe (ele, iter)
...
restMPTC :: iter -> list
instance IteratorMPTC [a] [a] a where
sumMPTC :: (Num n, IteratorMPTC it list n) => it -> n
Performance: *1
About the same as 3). The user will still be exposed to various
individual types ":: it". That is not as bad as it is in "Rust", since
(as already stated) in Haskell usually "list == it". This is similar to
the parsec approach.
class (Monad m) => Stream iter m ele | iter -> ele
Parsec has no "rest" function so the "list" type is not needed. But they
have an additional monad type.
6) Existential Quantification (my favorite)
data IteratorEQ list ele = forall iter . IteratorEQ {
iterEQ :: iter,
nextEQ :: iter -> Maybe (ele, iter)
...
restEQ :: iter -> list
}
listIterEQ :: [a] -> IteratorEQ [a] a
sumEQ :: (Num n) => IteratorEQ list n -> n
Performance: *1
Looks as nice as Haskell98 and is as fast as Haskell98Explicit. Btw.
This is probably how It would be done in "C" with iter = void*.
Additional thoughts:
* Do we really need the "list" type. Couldn't we simply return iterators
instead of the original "list" type. In 3) and 5), they will *usually*
be the same anyway.
* In 3) and 5) the typeclasses could be split to separate ele and list.
* On the other hand combining Iterators will be very annoying for 3) and 5)
data ZipIterator ...
instance IteratorMPTC (ZipIterator (?) (elem, elem')) ? (elem,
elem') where
zip :: (IteratorMPTC iter list elem, IteratorMPTC iter' list'
elem') -> ZipIterator ? (elem, elem')
Which is your favorite? Why? Did I forget any good ones?
Cheers
Silvio
-------------- next part --------------
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
import Criterion.Main
import Data.Foldable
import Data.Word
import qualified Data.ByteString as BS
listNext :: [a] -> Maybe (a,[a])
listNext (a:as) = Just (a,as)
listNext [] = Nothing
data Iterator98 list ele = Iterator98 {
next98 :: Maybe (ele, Iterator98 list ele)
}
listIter98 :: [a] -> Iterator98 [a] a
listIter98 (x:xs) = Iterator98 $ Just (x, listIter98 xs)
listIter98 [] = Iterator98 $ Nothing
sum98 :: (Num n) => Iterator98 listN n -> n
sum98 iter = rec iter 0 where
rec (Iterator98 iter') sum' = case iter' of
(Just (ele,rest)) -> rec rest $! (sum' + ele)
Nothing -> sum'
data IteratorExplicit98 iter list ele = IteratorExplicit98 {
iterExplicit98 :: iter,
nextExplicit98 :: iter -> Maybe (ele, iter)
}
listIterExplicit98 :: [a] -> IteratorExplicit98 [a] [a] a
listIterExplicit98 list = IteratorExplicit98 list listNext
sumExplicit98 :: (Num n) => IteratorExplicit98 it list n -> n
sumExplicit98 (IteratorExplicit98 iter nextF) = rec iter 0 where
rec iter' sum' = case nextF iter' of
(Just (ele,rest)) -> rec rest $! (sum' + ele)
Nothing -> sum'
class IteratorTF i where
type ListTF i
type ElemTF i
nextTF :: i -> Maybe (ElemTF i, i)
instance IteratorTF [a] where
type ListTF [a] = [a]
type ElemTF [a] = a
nextTF (c:str) = Just (c,str)
nextTF [] = Nothing
sumTF :: (Num n, IteratorTF it, ElemTF it ~ n) => it -> n
sumTF it' = rec it' 0 where
rec it sum' = case nextTF it of
(Just (c,n)) -> rec n $! (sum' + c)
Nothing -> sum'
class IteratorTF2Class list ele where
data IteratorTF2 list ele
nextTF2 :: IteratorTF2 list ele -> Maybe (ele, IteratorTF2 list ele)
instance IteratorTF2Class [ele] ele where
data IteratorTF2 [ele] ele = ListIterTF2 [ele]
nextTF2 (ListIterTF2 []) = Nothing
nextTF2 (ListIterTF2 (x:xs)) = Just (x, ListIterTF2 xs)
sumTF2 :: (Num n, IteratorTF2Class list n) => IteratorTF2 list n -> n
sumTF2 it' = rec it' 0 where
rec it sum' = case nextTF2 it of
(Just (c,n)) -> rec n $! (sum' + c)
Nothing -> sum'
class IteratorMPTC iter list ele | iter -> list, iter -> ele where
nextMPTC :: iter -> Maybe (ele, iter)
instance IteratorMPTC [a] [a] a where
nextMPTC (c:str) = Just (c,str)
nextMPTC [] = Nothing
sumMPTC :: (Num n, IteratorMPTC it list n) => it -> n
sumMPTC it' = rec it' 0 where
rec it sum' = case nextMPTC it of
(Just (c,n)) -> rec n $! (sum' + c)
Nothing -> sum'
data IteratorEQ list ele = forall iter . IteratorEQ {
iterEQ :: iter,
nextEQ :: iter -> Maybe (ele, iter)
}
listIterEQ :: [a] -> IteratorEQ [a] a
listIterEQ list = IteratorEQ list listNext
sumEQ :: (Num n) => IteratorEQ list n -> n
sumEQ (IteratorEQ iter nextF) = rec iter 0 where
rec iter' sum' = case nextF iter' of
(Just (c,n)) -> rec n $! (sum' + c)
Nothing -> sum'
explicitSum :: (Num n) => [n] -> n
explicitSum l' = rec l' 0 where
rec (c:n) s = rec n $! (s + c)
rec [] s = s
n = 1000000
l = replicate n 5
bs = BS.pack l
main = do
last l `seq` return ()
defaultMain [
bgroup "list" [
bench "Prelude sum" $ whnf sum l,
bench "Prelude foldl'" $ whnf (foldl' (+) 0) l,
bench "explicit sum" $ whnf explicitSum l,
bench "Iterator 98" $ whnf (sum98 . listIter98) l,
bench "Iterator explicit 98" $ whnf (sumExplicit98 . listIterExplicit98) l,
bench "Iterator type families" $ whnf sumTF l,
bench "Iterator type families 2" $ whnf (sumTF2 . ListIterTF2) l,
bench "Iterator multiparameter typeclasse" $ whnf sumMPTC l,
bench "Iterator Existential Quantification" $ whnf (sumEQ . listIterEQ) l
],
bgroup "bytestring" [
bench "foldl'" $ whnf (BS.foldl' (+) 0) bs
]
]
More information about the Haskell-Cafe
mailing list