Skip to content

Instantly share code, notes, and snippets.

@clrnd
Created October 16, 2019 18:23
Show Gist options
  • Save clrnd/471c9c544995a15beaf84cf875bd027f to your computer and use it in GitHub Desktop.
Save clrnd/471c9c544995a15beaf84cf875bd027f to your computer and use it in GitHub Desktop.
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
module Lib
( someFunc
) where
import Data.Char
import Data.IORef
import System.IO
import GHC.IO.Handle
import Control.Monad.Loops
import qualified Data.ByteString.Lazy.Char8 as B
data Counts = Counts
{ wcount :: !Int
, ccount :: !Int
, lcount :: !Int
} deriving Show
someFunc :: IO ()
someFunc = do
counts <- newIORef (Counts 0 0 0)
h <- openFile "example.txt" ReadMode
whileM_ (getWord h counts) (pure ())
readIORef counts >>= print
getWord :: Handle -> IORef Counts -> IO Bool
getWord h counts = hIsEOF h >>= \case
True -> pure False
False -> do
c <- newIORef undefined
loop <- newIORef True
whileM_ ((&&) <$> readIORef loop <*> (not <$> hIsEOF h)) (do
c' <- B.head <$> B.hGet h 1
if isAlpha c'
then do
modifyIORef' counts (\cs -> cs { wcount = wcount cs + 1 })
writeIORef c c'
writeIORef loop False
else do
count c' counts)
writeIORef loop True
whileM_ ((&&) <$> readIORef loop <*> (not <$> hIsEOF h)) (do
c' <- readIORef c
count c' counts
if not (isAlpha c')
then do
writeIORef loop False
else do
B.head <$> B.hGet h 1 >>= writeIORef c)
not <$> hIsEOF h
count :: Char -> IORef Counts -> IO ()
count c counts = modifyIORef' counts
(\cs -> cs { ccount = ccount cs + 1
, lcount = lcount cs + if c == '\n' then 1 else 0 })
@clrnd
Copy link
Author

clrnd commented Oct 16, 2019

Transliteration of GNU wc in Haskell.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment