Skip to content

Commit

Permalink
Refactoring
Browse files Browse the repository at this point in the history
  • Loading branch information
sol committed Sep 2, 2023
1 parent d884776 commit 85124dd
Show file tree
Hide file tree
Showing 7 changed files with 24 additions and 24 deletions.
4 changes: 2 additions & 2 deletions src/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module Config (
import Imports

import GHC.Generics
import Data.ByteString qualified as B
import Data.ByteString qualified as ByteString
import System.Directory
import System.Process
import Text.Casing
Expand Down Expand Up @@ -72,7 +72,7 @@ data Config = Config {
}

tryReadFile :: FilePath -> IO (Maybe ByteString)
tryReadFile = fmap (either (const Nothing) Just) . tryJust (guard . isDoesNotExistError) . B.readFile
tryReadFile = fmap (either (const Nothing) Just) . tryJust (guard . isDoesNotExistError) . ByteString.readFile

readConfigFile :: FilePath -> IO (Either String ConfigFile)
readConfigFile path = tryReadFile path >>= \ case
Expand Down
4 changes: 2 additions & 2 deletions src/Input.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Input (watch) where
import Imports

import System.IO
import qualified Data.ByteString as B
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Char8 as Char8

watch :: Handle -> (Char -> IO ()) -> IO () -> IO ()
Expand All @@ -23,7 +23,7 @@ forEachInputChar handle action = do
inputDelay = 100_000

go :: IO ()
go = B.hGetNonBlocking handle chunkSize >>= \ case
go = ByteString.hGetNonBlocking handle chunkSize >>= \ case
"" -> threadDelay inputDelay >> go
cs -> consume (Char8.unpack cs)

Expand Down
4 changes: 2 additions & 2 deletions src/Language/Haskell/GhciWrapper.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module Language.Haskell.GhciWrapper (

import Imports

import qualified Data.ByteString as B
import qualified Data.ByteString as ByteString
import Data.Text.Encoding (decodeUtf8)
import qualified Data.Text as T
import System.IO hiding (stdin, stdout, stderr)
Expand Down Expand Up @@ -144,7 +144,7 @@ close Interpreter{..} = do
putExpression :: Interpreter -> String -> IO ()
putExpression Interpreter{hIn = stdin} e = do
hPutStrLn stdin e
B.hPut stdin ReadHandle.marker
ByteString.hPut stdin ReadHandle.marker
hFlush stdin

getResult :: Interpreter -> IO String
Expand Down
20 changes: 10 additions & 10 deletions src/ReadHandle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module ReadHandle (

import Imports

import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Char8 as ByteString
import Data.IORef
import System.IO hiding (stdin, stdout, stderr, isEOF)

Expand All @@ -27,7 +27,7 @@ marker :: ByteString
marker = pack (show @String "be77d2c8427d29cd1d62b7612d8e98cc") <> "\n"

partialMarkers :: [ByteString]
partialMarkers = reverse . drop 1 . init $ B.inits marker
partialMarkers = reverse . drop 1 . init $ ByteString.inits marker

data ReadHandle = ReadHandle {
getChunk :: IO ByteString
Expand Down Expand Up @@ -56,7 +56,7 @@ emptyBuffer old = case old of

mkBufferChunk :: ByteString -> Buffer
mkBufferChunk chunk
| B.null chunk = BufferEmpty
| ByteString.null chunk = BufferEmpty
| otherwise = BufferChunk chunk

data Buffer =
Expand All @@ -68,7 +68,7 @@ data Buffer =
toReadHandle :: Handle -> Int -> IO ReadHandle
toReadHandle h n = do
hSetBinaryMode h True
ReadHandle (B.hGetSome h n) <$> newEmptyBuffer
ReadHandle (ByteString.hGetSome h n) <$> newEmptyBuffer

newEmptyBuffer :: IO (IORef Buffer)
newEmptyBuffer = newIORef BufferEmpty
Expand Down Expand Up @@ -99,7 +99,7 @@ nextChunk ReadHandle {..} = go
getSome :: IO (Maybe ByteString)
getSome = do
chunk <- getChunk
if B.null chunk then do
if ByteString.null chunk then do
putBuffer BufferEOF
return Nothing
else do
Expand Down Expand Up @@ -127,7 +127,7 @@ nextChunk ReadHandle {..} = go
NoMarker -> case splitPartialMarker chunk of
Just (prefix, partialMarker) -> do
putBuffer (BufferPartialMarker partialMarker)
if B.null prefix then do
if ByteString.null prefix then do
go
else do
return (Chunk prefix)
Expand All @@ -136,10 +136,10 @@ nextChunk ReadHandle {..} = go
splitPartialMarker :: ByteString -> Maybe (ByteString, ByteString)
splitPartialMarker chunk = split <$> findPartialMarker chunk
where
split partialMarker = (dropEnd (B.length partialMarker) chunk, partialMarker)
split partialMarker = (dropEnd (ByteString.length partialMarker) chunk, partialMarker)

findPartialMarker :: ByteString -> Maybe ByteString
findPartialMarker chunk = find (`B.isSuffixOf` chunk) partialMarkers
findPartialMarker chunk = find (`ByteString.isSuffixOf` chunk) partialMarkers

data StripMarker =
NoMarker
Expand All @@ -152,5 +152,5 @@ stripMarker input = case brakeAtMarker input of
("", dropMarker -> ys) -> StrippedMarker ys
(xs, ys) -> PrefixBeforeMarker xs ys
where
brakeAtMarker = B.breakSubstring marker
dropMarker = B.drop (B.length marker)
brakeAtMarker = ByteString.breakSubstring marker
dropMarker = ByteString.drop (ByteString.length marker)
4 changes: 2 additions & 2 deletions src/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module Run (

import Imports

import qualified Data.ByteString as B
import qualified Data.ByteString as ByteString
import Data.IORef
import System.IO
import qualified System.FSNotify as FSNotify
Expand Down Expand Up @@ -163,5 +163,5 @@ defaultSessionConfig startupFile = Session.Config {
configIgnoreDotGhci = False
, configStartupFile = startupFile
, configWorkingDirectory = Nothing
, configEcho = \ string -> B.putStr string >> hFlush stdout
, configEcho = \ string -> ByteString.putStr string >> hFlush stdout
}
4 changes: 2 additions & 2 deletions test/Language/Haskell/GhciWrapperSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
module Language.Haskell.GhciWrapperSpec (main, spec) where

import Helper
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Char8 as ByteString

import Language.Haskell.GhciWrapper (Config(..), Interpreter(..))
import qualified Language.Haskell.GhciWrapper as Interpreter
Expand All @@ -24,7 +24,7 @@ spec = do
result <- withSpy $ \ spy -> do
Interpreter.withInterpreter ghciConfig {configEcho = spy} [] $ \ _ghci -> do
pass
last (B.lines $ mconcat result) `shouldBe` "Leaving GHCi."
last (ByteString.lines $ mconcat result) `shouldBe` "Leaving GHCi."

context "when .ghci is writable by others" $ do
let
Expand Down
8 changes: 4 additions & 4 deletions test/ReadHandleSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ module ReadHandleSpec (spec) where

import Helper
import Test.QuickCheck
import qualified Data.ByteString as B
import qualified Data.ByteString as ByteString

import ReadHandle

Expand All @@ -12,7 +12,7 @@ chunkByteString size = go
go "" = return []
go xs = do
n <- chooseInt size
let (chunk, rest) = B.splitAt n xs
let (chunk, rest) = ByteString.splitAt n xs
(chunk :) <$> go rest

fakeHandle :: [ByteString] -> IO ReadHandle
Expand All @@ -26,13 +26,13 @@ withRandomChunkSizes (mconcat -> input) action = property $ do
let
maxChunkSize = case chunkSizes of
SmallChunks -> 4
BigChunks -> B.length input
BigChunks -> ByteString.length input

chunks <- chunkByteString (1, maxChunkSize) input
return $ fakeHandle chunks >>= action

partialMarker :: ByteString
partialMarker = B.take 5 marker
partialMarker = ByteString.take 5 marker

spec :: Spec
spec = do
Expand Down

0 comments on commit 85124dd

Please sign in to comment.