Skip to content

Instantly share code, notes, and snippets.

Created June 24, 2013 15:16
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 anonymous/5850805 to your computer and use it in GitHub Desktop.
Save anonymous/5850805 to your computer and use it in GitHub Desktop.
{-# LANGUAGE BangPatterns #-}
module Main where
import qualified Data.ByteString as Byte
import qualified Data.ByteString.Char8 as B
import System.Environment (getArgs)
import Data.List (sortBy)
import qualified Data.HashMap.Strict as HM
import Data.Ord (comparing)
-- | equivalent to a-zA-Z ranges in D, doesn't handle unicode data (unlike Data.Char.isLetter)
rn c | (c >= 97) && (c <= 122) = c
| (c >= 65) && (c <= 90) = c+32
| otherwise = 32
createReport :: Int -> B.ByteString -> B.ByteString
createReport n =
B.unlines
. map (\(w, count) -> B.append w $ B.pack (" " ++ show count))
. take n
. sortBy (flip $ comparing snd)
. HM.toList
. HM.fromListWith (\ !old !new -> old+new)
. map (\w -> (w, 1))
. B.words
. Byte.map rn
main = getArgs >>= \[n] -> B.interact $ createReport (read n)
{-# LANGUAGE BangPatterns #-}
module Main where
import qualified Data.Text as T
import qualified Data.Text.IO as T
import System.Environment (getArgs)
import Data.List (sortBy)
import qualified Data.HashMap.Strict as HM
import Data.Ord (comparing)
createReport :: Int -> T.Text -> T.Text
createReport n =
T.unlines
. map (\(w, count) -> T.append w $ T.pack (" " ++ show count))
. take n
. sortBy (flip $ comparing snd)
. HM.toList
. HM.fromListWith (\ !old !new -> old+new)
. map (\w -> (w, 1))
. T.words
. T.map rnl
main = getArgs >>= \[n] -> T.interact $ createReport (read n)
-- | equivalent to a-zA-Z ranges in D, doesn't handle unicode data (unlike Data.Char.isLetter)
-- (I integrated the conversion to lower case since I was in ghci anyway)
rnl :: Char -> Char
rnl = \n -> case n of
'a' -> 'a'
'b' -> 'b'
'c' -> 'c'
'd' -> 'd'
'e' -> 'e'
'f' -> 'f'
'g' -> 'g'
'h' -> 'h'
'i' -> 'i'
'j' -> 'j'
'k' -> 'k'
'l' -> 'l'
'm' -> 'm'
'n' -> 'n'
'o' -> 'o'
'p' -> 'p'
'q' -> 'q'
'r' -> 'r'
's' -> 's'
't' -> 't'
'u' -> 'u'
'v' -> 'v'
'w' -> 'w'
'x' -> 'x'
'y' -> 'y'
'z' -> 'z'
'A' -> 'a'
'B' -> 'b'
'C' -> 'c'
'D' -> 'd'
'E' -> 'e'
'F' -> 'f'
'G' -> 'g'
'H' -> 'h'
'I' -> 'i'
'J' -> 'j'
'K' -> 'k'
'L' -> 'l'
'M' -> 'm'
'N' -> 'n'
'O' -> 'o'
'P' -> 'p'
'Q' -> 'q'
'R' -> 'r'
'S' -> 's'
'T' -> 't'
'U' -> 'u'
'V' -> 'v'
'W' -> 'w'
'X' -> 'x'
'Y' -> 'y'
'Z' -> 'z'
_ -> '\n'
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment