treewide: hlint refactor

This commit is contained in:
Anton-Latukha 2021-08-06 19:18:38 +03:00
parent 2b58d3e510
commit 75c810423a
No known key found for this signature in database
GPG Key ID: 3D84C07E91802E41
10 changed files with 32 additions and 34 deletions

View File

@ -25,9 +25,9 @@ data BaseEncoding
-- | Encode @ByteString@ with @Base@ encoding, produce @Text@.
encodeWith :: BaseEncoding -> Bytes.ByteString -> T.Text
encodeWith Base16 = T.decodeUtf8 . Base16.encode
encodeWith Base16 = decodeUtf8 . Base16.encode
encodeWith NixBase32 = Base32.encode
encodeWith Base64 = T.decodeUtf8 . Base64.encode
encodeWith Base64 = decodeUtf8 . Base64.encode
-- | Take the input & @Base@ encoding witness -> decode into @Text@.
decodeWith :: BaseEncoding -> T.Text -> Either String Bytes.ByteString

View File

@ -81,9 +81,9 @@ runParser
-> m (Either String a)
runParser effs (NarParser action) h target = do
unpackResult <-
Reader.runReaderT (Except.runExceptT $ State.evalStateT action state0) effs
runReaderT (runExceptT $ State.evalStateT action state0) effs
`Exception.Lifted.catch` exceptionHandler
when (Either.isLeft unpackResult) cleanup
when (isLeft unpackResult) cleanup
pure unpackResult
where
@ -209,7 +209,7 @@ parseFile = do
-- Set up for defining `getChunk`
narHandle <- State.gets handle
bytesLeftVar <- IO.liftIO $ IORef.newIORef fSize
bytesLeftVar <- IO.liftIO $ newIORef fSize
let
-- getChunk tracks the number of total bytes we still need to get from the
@ -217,13 +217,13 @@ parseFile = do
-- chunk we read)
getChunk :: m (Maybe ByteString)
getChunk = do
bytesLeft <- IO.liftIO $ IORef.readIORef bytesLeftVar
bytesLeft <- IO.liftIO $ readIORef bytesLeftVar
if bytesLeft == 0
then pure Nothing
else do
chunk <- IO.liftIO $ Bytes.hGetSome narHandle $ fromIntegral $ min 10000 bytesLeft
when (Bytes.null chunk) (Fail.fail "ZERO BYTES")
IO.liftIO $ IORef.modifyIORef bytesLeftVar $ \n -> n - fromIntegral (Bytes.length chunk)
IO.liftIO $ modifyIORef bytesLeftVar $ \n -> n - fromIntegral (Bytes.length chunk)
-- This short pause is necessary for letting the garbage collector
-- clean up chunks from previous runs. Without it, heap memory usage can
@ -296,7 +296,7 @@ parseStr = do
strBytes <- consume $ fromIntegral len
expectRawString
(Bytes.replicate (fromIntegral $ padLen $ fromIntegral len) 0)
pure $ Text.decodeUtf8 strBytes
pure $ decodeUtf8 strBytes
-- | Get an Int64 describing the length of the upcoming string,
@ -436,7 +436,7 @@ consume n = do
popStr :: Monad m => NarParser m (Maybe Text)
popStr = do
s <- State.get
case List.uncons (tokenStack s) of
case uncons (tokenStack s) of
Nothing -> pure Nothing
Just (x, xs) -> do
State.put $ s { tokenStack = xs }

View File

@ -59,7 +59,7 @@ streamNarIO yield effs basePath = do
when isDir $ do
fs <- IO.liftIO (Nar.narListDir effs path)
yield $ strs ["type", "directory"]
forM_ (List.sort fs) $ \f -> do
forM_ (sort fs) $ \f -> do
yield $ str "entry"
parens $ do
let fullName = path </> f

View File

@ -169,8 +169,8 @@ storePathToRawFilePath StorePath{..} =
root <> "/" <> hashPart <> "-" <> name
where
root = Bytes.Char8.pack storePathRoot
hashPart = Text.encodeUtf8 $ encodeWith NixBase32 $ coerce storePathHash
name = Text.encodeUtf8 $ unStorePathName storePathName
hashPart = encodeUtf8 $ encodeWith NixBase32 $ coerce storePathHash
name = encodeUtf8 $ unStorePathName storePathName
-- | Render a 'StorePath' as a 'FilePath'.
storePathToFilePath :: StorePath -> FilePath
@ -184,7 +184,7 @@ storePathToText = toText . Bytes.Char8.unpack . storePathToRawFilePath
-- can be used to query binary caches.
storePathToNarInfo :: StorePath -> Bytes.Char8.ByteString
storePathToNarInfo StorePath{..} =
Text.encodeUtf8 $ encodeWith NixBase32 (coerce storePathHash) <> ".narinfo"
encodeUtf8 $ encodeWith NixBase32 (coerce storePathHash) <> ".narinfo"
-- | Parse `StorePath` from `Bytes.Char8.ByteString`, checking
-- that store directory matches `expectedRoot`.

View File

@ -13,7 +13,7 @@ import Arbitrary
-- | Test that Nix(OS) like paths roundtrip
prop_storePathRoundtrip :: NixLike -> NixLike -> Property
prop_storePathRoundtrip (_ :: NixLike) (NixLike x) =
(parsePath "/nix/store" $ storePathToRawFilePath x) === Right x
parsePath "/nix/store" (storePathToRawFilePath x) === Right x
-- | Test that any `StorePath` roundtrips
prop_storePathRoundtrip' :: StorePath -> Property
@ -22,7 +22,7 @@ prop_storePathRoundtrip' x =
prop_storePathRoundtripParser :: NixLike -> NixLike -> Property
prop_storePathRoundtripParser (_ :: NixLike) (NixLike x) =
(Data.Attoparsec.Text.parseOnly (pathParser $ storePathRoot x) $ storePathToText x) === Right x
Data.Attoparsec.Text.parseOnly (pathParser $ storePathRoot x) (storePathToText x) === Right x
prop_storePathRoundtripParser' :: StorePath -> Property
prop_storePathRoundtripParser' x =

View File

@ -87,7 +87,7 @@ addToStore
addToStore name pth recursive _pathFilter _repair = do
runOpArgsIO AddToStore $ \yield -> do
yield $ BSL.toStrict $ Data.Binary.Put.runPut $ do
yield $ toStrict $ Data.Binary.Put.runPut $ do
putText $ System.Nix.StorePath.unStorePathName name
putBool $ not $ System.Nix.Hash.algoName @a == "sha256" && recursive
@ -176,7 +176,7 @@ findRoots = do
getSocketIncremental
$ getMany
$ (,)
<$> (BSL.fromStrict <$> getByteStringLen)
<$> (fromStrict <$> getByteStringLen)
<*> getPath sd
r <- catRights res
@ -224,7 +224,7 @@ queryPathInfoUncached path = do
deriverPath <- sockGetPathMay
narHashText <- Data.Text.Encoding.decodeUtf8 <$> sockGetStr
narHashText <- decodeUtf8 <$> sockGetStr
let
narHash =
case
@ -280,9 +280,7 @@ queryPathFromHashPart :: StorePathHashPart -> MonadStore StorePath
queryPathFromHashPart storePathHash = do
runOpArgs QueryPathFromHashPart
$ putByteStringLen
$ BSL.fromStrict
$ Data.Text.Encoding.encodeUtf8
$ encodeWith NixBase32 $ coerce storePathHash
$ encodeUtf8 (encodeWith NixBase32 $ coerce storePathHash)
sockGetPath
queryMissing

View File

@ -45,7 +45,7 @@ getByteStringLen = do
when (len `mod` 8 /= 0) $ do
pads <- unpad $ fromIntegral $ 8 - (len `mod` 8)
unless (all (== 0) pads) $ fail $ "No zeroes" <> show (st, len, pads)
pure $ BSL.toStrict st
pure $ toStrict st
where unpad x = replicateM x getWord8
getByteStrings :: Get [ByteString]

View File

@ -119,7 +119,7 @@ opNum QueryMissing = 40
simpleOp :: WorkerOp -> MonadStore Bool
simpleOp op = simpleOpArgs op $ pass
simpleOp op = simpleOpArgs op pass
simpleOpArgs :: WorkerOp -> Put -> MonadStore Bool
simpleOpArgs op args = do
@ -134,13 +134,13 @@ simpleOpArgs op args = do
err
runOp :: WorkerOp -> MonadStore ()
runOp op = runOpArgs op $ pass
runOp op = runOpArgs op pass
runOpArgs :: WorkerOp -> Put -> MonadStore ()
runOpArgs op args =
runOpArgsIO
op
(\encode -> encode $ Data.ByteString.Lazy.toStrict $ runPut args)
(\encode -> encode $ toStrict $ runPut args)
runOpArgsIO
:: WorkerOp
@ -187,7 +187,7 @@ runStoreOpts sockPath storeRootDir code = do
vermagic <- liftIO $ recv soc 16
let
(magic2, _daemonProtoVersion) =
flip runGet (Data.ByteString.Lazy.fromStrict vermagic)
flip runGet (fromStrict vermagic)
$ (,)
<$> (getInt :: Get Int)
<*> (getInt :: Get Int)

View File

@ -49,7 +49,7 @@ getSocketIncremental = genericIncremental sockGet8
sockPut :: Put -> MonadStore ()
sockPut p = do
soc <- asks storeSocket
liftIO $ sendAll soc $ BSL.toStrict $ runPut p
liftIO $ sendAll soc $ toStrict $ runPut p
sockGet :: Get a -> MonadStore a
sockGet = getSocketIncremental
@ -91,10 +91,10 @@ sockGetPaths = do
getSocketIncremental (getPaths sd)
bsToText :: ByteString -> Text
bsToText = T.decodeUtf8
bsToText = decodeUtf8
textToBS :: Text -> ByteString
textToBS = T.encodeUtf8
textToBS = encodeUtf8
bslToText :: BSL.ByteString -> Text
bslToText = toText . TL.decodeUtf8
@ -116,11 +116,11 @@ getPaths sd =
Data.HashSet.fromList . rights . fmap (parsePath sd) <$> getByteStrings
putPath :: StorePath -> Put
putPath = putByteStringLen . BSL.fromStrict . storePathToRawFilePath
putPath = putByteStringLen . fromStrict . storePathToRawFilePath
putPaths :: StorePathSet -> Put
putPaths = putByteStrings . Data.HashSet.toList . Data.HashSet.map
(BSL.fromStrict . storePathToRawFilePath)
(fromStrict . storePathToRawFilePath)
putBool :: Bool -> Put
putBool True = putInt (1 :: Int)

View File

@ -51,7 +51,7 @@ mockedEnv mEnvPath fp =
, ("NIX_STATE_DIR" , fp </> "var" </> "nix")
, ("NIX_CONF_DIR" , fp </> "etc")
-- , ("NIX_REMOTE", "daemon")
] <> maybe [] (\x -> [("PATH", x)]) mEnvPath
] <> foldMap (\x -> [("PATH", x)]) mEnvPath
waitSocket :: FilePath -> Int -> IO ()
waitSocket _ 0 = fail "No socket"
@ -59,7 +59,7 @@ waitSocket fp x = do
ex <- doesFileExist fp
bool
(threadDelay 100000 >> waitSocket fp (x - 1))
(pass)
pass
ex
writeConf :: FilePath -> IO ()
@ -195,7 +195,7 @@ spec_protocol = Hspec.around withNixDaemon $
verifyStore True True `shouldReturn` False
context "addTextToStore" $
itRights "adds text to store" $ withPath $ pure
itRights "adds text to store" $ withPath pure
context "isValidPathUncached" $ do
itRights "validates path" $ withPath $ \path -> do