Make 'nix flake check' work

This commit is contained in:
Alexander Kobjolke 2023-08-19 01:10:47 +02:00
parent da3b61b467
commit 7a69fb2363
6 changed files with 27 additions and 20 deletions

View file

@ -1,6 +1,6 @@
module HCat (
runHCat,
defaultMain,
runHCat,
defaultMain,
) where
import System.Environment qualified as Env
@ -15,16 +15,16 @@ import HCat.Internal (parseArgs)
runHCat :: IO ()
runHCat = do
fileNameOrError <- parseArgs <$> Env.getArgs
fileName <- eitherToError fileNameOrError
TextIO.readFile fileName >>= TextIO.putStr
fileNameOrError <- parseArgs <$> Env.getArgs
fileName <- eitherToError fileNameOrError
TextIO.readFile fileName >>= TextIO.putStr
eitherToError :: Show a => Either a b -> IO b
eitherToError = either (Exception.throwIO . IOError.userError . show) return
handleError :: IOError -> IO ()
handleError e = do
hPutStrLn stderr $ "I ran into an issue: " <> show e
hPutStrLn stderr $ "I ran into an issue: " <> show e
defaultMain :: IO ()
defaultMain = Exception.catch runHCat handleError

View file

@ -7,9 +7,9 @@ module HCat.Internal where
-- Right "foo"
parseArgs :: [String] -> Either String FilePath
parseArgs args = case args of
[] -> Left "No filename given!"
[arg] -> Right arg
_ -> Left "Only a single file is supported"
[] -> Left "No filename given!"
[arg] -> Right arg
_ -> Left "Only a single file is supported"
-- | @chunksOf n@ splits a list into chunks of at most @n@ items.
--
@ -24,7 +24,7 @@ parseArgs args = case args of
chunksOf :: Int -> [a] -> [[a]]
chunksOf _ [] = []
chunksOf n xs@(_ : _)
| n <= 0 = []
| otherwise =
let (chunk, rest) = splitAt n xs
in chunk : chunksOf n rest
| n <= 0 = []
| otherwise =
let (chunk, rest) = splitAt n xs
in chunk : chunksOf n rest