[Haskell-cafe] Best bit LIST data structure

Ryan Ingram ryani.spam at gmail.com
Wed Oct 12 00:54:05 CEST 2011


On Sun, Oct 9, 2011 at 6:18 AM, Ryan Newton <rrnewton at gmail.com> wrote:

>
> Yep, it is simple.  But I prefer to only use well-tested data structure
> libraries where I can!  Here's an example simple implementation (partial --
> missing some common functions):
>
>
> module Data.BitList
>   ( BitList
>   , cons, head, tail, empty
>   , pack, unpack, length, drop
>   )
> where
>
> import Data.Int
> import Data.Bits
> import Prelude as P hiding (head,tail,drop,length)
> import qualified Data.List as L
> import Test.HUnit
>
> data BitList = One  {-# UNPACK #-} !Int {-# UNPACK #-} !Int64
>              | More {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 BitList
>

I suggest

data BitTail = Zero | More {-# UNPACK #-} !Int64 BitTail
data BitList = Head {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 BitTail
empty = Head 0 0 Zero

or else just
data BitList = Head {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 [Int64]
empty = Head 0 0 []
length (Head n _ xs) = n + 64 * List.length xs

unpack :: BitList -> [Bool]
> unpack (One 0 _)     = []
> unpack (One i bv)    = (bv `testBit` (i-1)) : unpack (One (i-1) bv)
> unpack (More 0 _ r)  =  unpack r
> unpack (More i bv r) = (bv `testBit` (i-1)) : unpack (More (i-1) bv r)
>

I'd implement as

view :: BitList -> Maybe (Bool, BitList)
view (One 0 _) = Nothing
view bl = Just (head bl, tail bl)

unpack = unfoldr view


> drop :: Int -> BitList -> BitList
> drop 0 bl           = bl
> drop n bl | n >= 64 = case bl of
>                 One _ _    -> error "drop: not enough elements in BitList"
>             More i _ r -> drop (n-i) r
> drop n bl = case bl of
>           One i  bv   -> One  (i-n) bv
>           More i bv r -> More (i-n) bv r
>

This is wrong.

drop 5 (More 1 0 (One 64 0))
->
More (-4) 0 (One 64 0)

Fixed version (also gives same behavior as List.drop when n > length l)

drop :: Int -> BitList -> BitList
drop n (One i bv)
   | n >= i = empty
   | otherwise = One (i - n) bv
drop n (More i bv r)
   | n >= i = drop (n - i) r
   | otherwise = More (i - n) bv r

  -- ryan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111011/f4efe1ce/attachment.htm>


More information about the Haskell-Cafe mailing list