Skip to content

Instantly share code, notes, and snippets.

@erszcz
Created June 5, 2012 18:17
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 erszcz/2876666 to your computer and use it in GitHub Desktop.
Save erszcz/2876666 to your computer and use it in GitHub Desktop.
Populating map from text data
module HMTTest where
--{ imports
import Control.Monad (forM_)
import qualified Data.HashMap.Strict as HM
import Data.Hashable (Hashable)
import Data.Hashable
import Data.Bits (shiftL)
import qualified Data.Text as T
import qualified Data.Text.Array as TA
import qualified Data.Text.Internal as T
import qualified Data.Text.IO as T
import System (getArgs)
--}
-- got from: http://hackage.haskell.org/packages/archive/hashable/1.1.1.0/doc/html/src/Data-Hashable.html
instance Hashable T.Text where
hash (T.Text arr off len) = hashByteArray (TA.aBA arr)
(off `shiftL` 1) (len `shiftL` 1)
hashWithSalt salt (T.Text arr off len) =
hashByteArrayWithSalt (TA.aBA arr) (off `shiftL` 1) (len `shiftL` 1)
salt
{-buildDict words = HM.fromListWith (+) words-}
{-getWords file = do contents <- T.readFile file-}
{-return (buildDict $-}
{-map (\w -> (w,1)) (T.lines contents))-}
getWords file = do contents <- T.readFile file
return (foldl (\ a e -> HM.insertWith (+) e 1 a) HM.empty (T.lines contents))
main = do args <- getArgs
words <- getWords (args !! 0)
case HM.lookup (T.pack (args !! 1)) words of
Nothing -> return ()
Just v -> print v
module HTTTest where
import Control.Monad (forM_)
import qualified Data.HashTable as HT
import Data.Hashable (Hashable)
import Data.Hashable
import Data.Bits (shiftL)
import qualified Data.Text as T
import qualified Data.Text.Array as TA
import qualified Data.Text.Internal as T
import qualified Data.Text.IO as T
import System (getArgs)
-- got from: http://hackage.haskell.org/packages/archive/hashable/1.1.1.0/doc/html/src/Data-Hashable.html
instance Hashable T.Text where
hash (T.Text arr off len) = hashByteArray (TA.aBA arr)
(off `shiftL` 1) (len `shiftL` 1)
hashWithSalt salt (T.Text arr off len) =
hashByteArrayWithSalt (TA.aBA arr) (off `shiftL` 1) (len `shiftL` 1)
salt
sizeHint = 1500000
getWords file = do contents <- T.readFile file
return (T.lines contents)
type HTTextInt = HT.HashTable T.Text Int
emptyHTTextInt :: () -> IO HTTextInt
emptyHTTextInt _ = do HT.new (==) (fromIntegral . hash) >>= return
main =
{-do ht <- HT.newHint (==) (fromIntegral . hashByteString) sizeHint-}
do args <- getArgs
words <- getWords (args !! 0)
ht <- emptyHTTextInt ()
forM_ words $ \word ->
HT.insert ht word 1
maybeVal <- HT.lookup ht (T.pack $ args !! 1)
case maybeVal of
Nothing -> print "nothing"
Just v -> print v
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment