Skip to content

Commit

Permalink
Added mkcsv.
Browse files Browse the repository at this point in the history
Much much faster than mkcsv.py.
  • Loading branch information
abhinav committed Mar 2, 2013
1 parent f735500 commit 8c91116
Show file tree
Hide file tree
Showing 3 changed files with 51 additions and 1 deletion.
2 changes: 1 addition & 1 deletion pl2-3/mkcsv.py
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@

PARSER = argparse.ArgumentParser()
PARSER.add_argument('--attr-len', '-a', metavar='SIZE', type=int,
dest='attr')
dest='attr', default=9)
PARSER.add_argument('tuples', metavar='COUNT', type=int)
PARSER.add_argument('file', metavar='FILE', type=argparse.FileType('w'))
args = PARSER.parse_args()
Expand Down
2 changes: 2 additions & 0 deletions pl4/.gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -10,3 +10,5 @@ csv2leveldb
query_leveldb
csv2idx_leveldb
query_idx_leveldb
*.hi
mkcsv
48 changes: 48 additions & 0 deletions pl4/mkcsv.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main (main) where

import Control.Monad (void, when)
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as BS
import System.Environment (getArgs, getProgName)
import System.Exit (exitFailure)
import System.Random

main :: IO ()
main = do
args <- getArgs

when (null args) $ do
prog <- getProgName
putStrLn $ "USAGE: " ++ prog ++ " <tuple count>"
exitFailure
let tupleCount = read (head args) :: Integer
void $ times tupleCount $
generateTuple 100 >>= BS.putStrLn . BS.intercalate ","

return ()

choices :: ByteString
choices = "ABCDEFGHIJKLMNOPQRSTUVWXYZ"

choice :: RandomGen g => ByteString -> g -> (Char, g)
choice l g = let (i, g') = randomR (0, BS.length l - 1) g
in (l `BS.index` i, g')

randomByteString :: forall g. RandomGen g => Int -> g -> (ByteString, g)
randomByteString len rand =
let (bs, Just rand') = BS.unfoldrN len step rand
in (bs, rand')
where
step :: g -> Maybe (Char, g)
step g = Just $ choice choices g

generateAttr :: Int -> IO ByteString
generateAttr len = getStdRandom (randomByteString len)

generateTuple :: Integer -> IO [ByteString]
generateTuple count = times count $ generateAttr 9

times :: Monad m => Integer -> m a -> m [a]
times c m = mapM (const m) [1..c]

0 comments on commit 8c91116

Please sign in to comment.