[Haskell-cafe] Bloom Filter

Dom dominic.steinitz at blueyonder.co.uk
Tue May 1 16:19:35 EDT 2007


> 
> Reminds me of this code from Data.Binary:
> 
>     unroll :: Integer -> [Word8]
>     unroll = unfoldr step
>       where
>         step 0 = Nothing
>         step i = Just (fromIntegral i, i `shiftR` 8)
> 
>     roll :: [Word8] -> Integer
>     roll   = foldr unstep 0
>       where
>         unstep b a = a `shiftL` 8 .|. fromIntegral b
> 
> Which is a bit stream-fusion inspired, I must admit.
> 

But better than what is in Codec.Utils:

> toBase x =
>    map fromIntegral .
>    reverse .
>    map (flip mod x) .
>    takeWhile (/=0) .
>    iterate (flip div x)
> 
> -- | Take a number a convert it to base n as a list of octets.
> 
> toOctets :: (Integral a, Integral b) => a -> b -> [Octet]
> toOctets n x = (toBase n . fromIntegral) x

> powersOf n = 1 : (map (*n) (powersOf n))

> -- | Take a list of octets (a number expressed in base n) and convert it
> --   to a number.
> 
> fromOctets :: (Integral a, Integral b) => a -> [Octet] -> b
> fromOctets n x =
>    fromIntegral $
>    sum $
>    zipWith (*) (powersOf n) (reverse (map fromIntegral x))

It seems a shame that everyone has to roll their own.

Dominic.



More information about the Haskell-Cafe mailing list