Skip to content

Instantly share code, notes, and snippets.

@snoyberg
Created January 15, 2014 13:26
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save snoyberg/8436149 to your computer and use it in GitHub Desktop.
Save snoyberg/8436149 to your computer and use it in GitHub Desktop.
import qualified Data.ByteString as S
import Data.Conduit
import Data.Conduit.Binary (sourceHandle)
import qualified Data.Conduit.List as CL
import qualified Data.Vector.Unboxed.Mutable as VM
import Data.Word (Word8)
import System.IO (IOMode (ReadMode), withFile)
type Freq = VM.IOVector Int
newFreq :: IO Freq
newFreq = VM.replicate 256 0
printFreq :: Freq -> IO ()
printFreq freq =
mapM_ go [0..255]
where
go i = do
x <- VM.read freq i
putStrLn $ show i ++ ": " ++ show x
addFreqWord8 :: Freq -> Word8 -> IO ()
addFreqWord8 f w = do
let index = fromIntegral w
oldCount <- VM.read f index
VM.write f index (oldCount + 1)
addFreqBS :: Freq -> S.ByteString -> IO ()
addFreqBS f bs =
loop (S.length bs - 1)
where
loop (-1) = return ()
loop i = do
addFreqWord8 f (S.index bs i)
loop (i - 1)
-- | The main entry point.
main :: IO ()
main = do
freq <- newFreq
withFile "random" ReadMode $ \h ->
sourceHandle h
$$ CL.mapM_ (addFreqBS freq)
printFreq freq
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment