Fix warnings

This commit is contained in:
John Ericson 2019-03-10 18:12:55 -04:00
parent 3db28b3092
commit cc60e2a12d
7 changed files with 51 additions and 60 deletions

View File

@ -11,8 +11,8 @@ module System.Nix.Build (
) where ) where
import Data.Text (Text) import Data.Text (Text)
import Data.HashSet (HashSet) --import Data.HashSet (HashSet)
import System.Nix.Path (Path) --import System.Nix.Path (Path)
data BuildMode = Normal | Repair | Check data BuildMode = Normal | Repair | Check
deriving (Eq, Ord, Enum, Show) deriving (Eq, Ord, Enum, Show)
@ -37,14 +37,17 @@ data BuildStatus =
-- | Result of the build -- | Result of the build
data BuildResult = BuildResult data BuildResult = BuildResult
{ -- | build status, MiscFailure should be default { -- | build status, MiscFailure should be default
status :: !BuildStatus _buildResult_status :: !BuildStatus
, -- | possible build error message , -- | possible build error message
error :: !(Maybe Text) _buildResult_error :: !(Maybe Text)
, -- | How many times this build was performed , -- | How many times this build was performed
timesBuilt :: !Integer _buildResult_timesBuilt :: !Integer
, -- | If timesBuilt > 1, whether some builds did not produce the same result , -- | If timesBuilt > 1, whether some builds did not produce the same result
isNonDeterministic :: !Bool _buildResult_isNonDeterministic :: !Bool
-- XXX: | startTime stopTime time_t -- XXX: | startTime stopTime time_t
} deriving (Eq, Ord, Show) } deriving (Eq, Ord, Show)
buildSuccess BuildResult{..} = status == Built || status == Substituted || status == AlreadyValid buildSuccess :: BuildResult -> Bool
buildSuccess BuildResult{..} = _buildResult_status == Built
|| _buildResult_status == Substituted
|| _buildResult_status == AlreadyValid

View File

@ -28,10 +28,6 @@ import qualified Data.Hashable as DataHashable
import Data.Kind (Type) import Data.Kind (Type)
import Data.List (foldl') import Data.List (foldl')
import Data.Proxy (Proxy(Proxy)) import Data.Proxy (Proxy(Proxy))
import qualified Data.Map as Map
import qualified Data.Maybe as Maybe
import Data.Monoid
import Data.Proxy (Proxy(Proxy))
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
@ -110,26 +106,26 @@ printAsBase32 :: Digest a -> T.Text
printAsBase32 (Digest bs) = printHashBytes32 bs printAsBase32 (Digest bs) = printHashBytes32 bs
instance HasDigest MD5 where instance HasDigest 'MD5 where
type AlgoCtx 'MD5 = MD5.Ctx type AlgoCtx 'MD5 = MD5.Ctx
initialize = MD5.init initialize = MD5.init
update = MD5.update update = MD5.update
finalize = Digest . MD5.finalize finalize = Digest . MD5.finalize
instance HasDigest 'SHA1 where instance HasDigest 'SHA1 where
type AlgoCtx SHA1 = SHA1.Ctx type AlgoCtx 'SHA1 = SHA1.Ctx
initialize = SHA1.init initialize = SHA1.init
update = SHA1.update update = SHA1.update
finalize = Digest . SHA1.finalize finalize = Digest . SHA1.finalize
instance HasDigest 'SHA256 where instance HasDigest 'SHA256 where
type AlgoCtx SHA256 = SHA256.Ctx type AlgoCtx 'SHA256 = SHA256.Ctx
initialize = SHA256.init initialize = SHA256.init
update = SHA256.update update = SHA256.update
finalize = Digest . SHA256.finalize finalize = Digest . SHA256.finalize
instance (HasDigest a, KnownNat n) => HasDigest (Truncated n a) where instance (HasDigest a, KnownNat n) => HasDigest ('Truncated n a) where
type AlgoCtx (Truncated n a) = AlgoCtx a type AlgoCtx ('Truncated n a) = AlgoCtx a
initialize = initialize @a initialize = initialize @a
update = update @a update = update @a
finalize = truncateDigest @n . finalize @a finalize = truncateDigest @n . finalize @a
@ -162,8 +158,7 @@ printHashBytes32 c = T.pack $ concatMap char32 [nChar - 1, nChar - 2 .. 0]
char32 i = [digits32 V.! digitInd] char32 i = [digits32 V.! digitInd]
where where
byte j = BS.index c (fromIntegral j) byte j = BS.index c (fromIntegral j)
digitInd = fromIntegral $ digitInd = sum [fromIntegral (byte j) * (256^j)
sum [fromIntegral (byte j) * (256^j)
| j <- [0 .. BS.length c - 1]] | j <- [0 .. BS.length c - 1]]
`div` (32^i) `div` (32^i)
`mod` 32 `mod` 32
@ -179,7 +174,7 @@ parseHashBytes32 b = BS.pack $ map word32 [nChar -1, nChar - 2 .. 0]
word32 i = fromIntegral wordInd word32 i = fromIntegral wordInd
where where
word :: Int -> Char word :: Int -> Char
word j = T.index b i word j = T.index b j
wordInd :: Int wordInd :: Int
wordInd = fromIntegral $ wordInd = fromIntegral $
@ -187,9 +182,9 @@ parseHashBytes32 b = BS.pack $ map word32 [nChar -1, nChar - 2 .. 0]
| j <- [0 .. T.length b - 1]] | j <- [0 .. T.length b - 1]]
`div` (32^i) `div` (32^i)
roundtrip :: (Digest SHA256, T.Text, BS.ByteString) roundtrip :: (Digest 'SHA256, T.Text, BS.ByteString)
roundtrip = roundtrip =
let d = hash @SHA256 (BSC.pack "hello") let d = hash @'SHA256 (BSC.pack "hello")
encoded = printAsBase32 d :: T.Text encoded = printAsBase32 d :: T.Text
decoded = parseHashBytes32 encoded decoded = parseHashBytes32 encoded
in (d, encoded, decoded) in (d, encoded, decoded)
@ -200,7 +195,7 @@ roundtrip =
-- bytestring into a head part (truncation length) and tail part (leftover -- bytestring into a head part (truncation length) and tail part (leftover
-- part) right-pads the leftovers with 0 to the truncation length, and -- part) right-pads the leftovers with 0 to the truncation length, and
-- combines the two strings bytewise with `xor` -- combines the two strings bytewise with `xor`
truncateDigest :: forall n a.(HasDigest a, KnownNat n) => Digest a -> Digest (Truncated n a) truncateDigest :: forall n a.(HasDigest a, KnownNat n) => Digest a -> Digest ('Truncated n a)
truncateDigest (Digest c) = Digest $ BS.pack $ map truncOutputByte [0.. n-1] truncateDigest (Digest c) = Digest $ BS.pack $ map truncOutputByte [0.. n-1]
where where
@ -225,14 +220,14 @@ digits32 = V.fromList "0123456789abcdfghijklmnpqrsvwxyz"
class AlgoVal (a :: HashAlgorithm) where class AlgoVal (a :: HashAlgorithm) where
algoVal :: HashAlgorithm' Integer algoVal :: HashAlgorithm' Integer
instance AlgoVal MD5 where instance AlgoVal 'MD5 where
algoVal = MD5 algoVal = MD5
instance AlgoVal SHA1 where instance AlgoVal 'SHA1 where
algoVal = SHA1 algoVal = SHA1
instance AlgoVal SHA256 where instance AlgoVal 'SHA256 where
algoVal = SHA256 algoVal = SHA256
instance forall a n.(AlgoVal a, KnownNat n) => AlgoVal (Truncated n a) where instance forall a n.(AlgoVal a, KnownNat n) => AlgoVal ('Truncated n a) where
algoVal = Truncated (natVal (Proxy @n)) (algoVal @a) algoVal = Truncated (natVal (Proxy @n)) (algoVal @a)

View File

@ -21,12 +21,10 @@ module System.Nix.Nar (
) where ) where
import Control.Applicative import Control.Applicative
import Control.Monad (replicateM, replicateM_, (<=<))
import qualified Data.Binary as B import qualified Data.Binary as B
import qualified Data.Binary.Get as B import qualified Data.Binary.Get as B
import qualified Data.Binary.Put as B import qualified Data.Binary.Put as B
import Data.Bool (bool) import Data.Bool (bool)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC import qualified Data.ByteString.Char8 as BSC
import qualified Data.ByteString.Lazy as BSL import qualified Data.ByteString.Lazy as BSL
import Data.Foldable (forM_) import Data.Foldable (forM_)
@ -151,32 +149,32 @@ getNar = fmap Nar $ header >> parens getFile
getFile = getRegularFile <|> getDirectory <|> getSymLink getFile = getRegularFile <|> getDirectory <|> getSymLink
getRegularFile = do getRegularFile = do
assertStr "type" _ <- assertStr "type"
assertStr "regular" _ <- assertStr "regular"
mExecutable <- optional $ Executable <$ (assertStr "executable" mExecutable <- optional $ Executable <$ (assertStr "executable"
>> assertStr "") >> assertStr "")
assertStr "contents" _ <- assertStr "contents"
(fSize, contents) <- sizedStr (fSize, contents) <- sizedStr
return $ Regular (fromMaybe NonExecutable mExecutable) fSize contents return $ Regular (fromMaybe NonExecutable mExecutable) fSize contents
getDirectory = do getDirectory = do
assertStr "type" _ <- assertStr "type"
assertStr "directory" _ <- assertStr "directory"
fs <- many getEntry fs <- many getEntry
return $ Directory (Map.fromList fs) return $ Directory (Map.fromList fs)
getSymLink = do getSymLink = do
assertStr "type" _ <- assertStr "type"
assertStr "symlink" _ <- assertStr "symlink"
assertStr "target" _ <- assertStr "target"
fmap (SymLink . E.decodeUtf8 . BSL.toStrict) str fmap (SymLink . E.decodeUtf8 . BSL.toStrict) str
getEntry = do getEntry = do
assertStr "entry" _ <- assertStr "entry"
parens $ do parens $ do
assertStr "name" _ <- assertStr "name"
name <- E.decodeUtf8 . BSL.toStrict <$> str name <- E.decodeUtf8 . BSL.toStrict <$> str
assertStr "node" _ <- assertStr "node"
file <- parens getFile file <- parens getFile
maybe (fail $ "Bad FilePathPart: " ++ show name) maybe (fail $ "Bad FilePathPart: " ++ show name)
(return . (,file)) (return . (,file))
@ -189,6 +187,7 @@ getNar = fmap Nar $ header >> parens getFile
n <- B.getInt64le n <- B.getInt64le
s <- B.getLazyByteString n s <- B.getLazyByteString n
p <- B.getByteString . fromIntegral $ padLen n p <- B.getByteString . fromIntegral $ padLen n
_ <- pure p
return (n,s) return (n,s)
parens m = assertStr "(" *> m <* assertStr ")" parens m = assertStr "(" *> m <* assertStr ")"
@ -207,7 +206,7 @@ padLen n = (8 - n) `mod` 8
-- | Unpack a NAR into a non-nix-store directory (e.g. for testing) -- | Unpack a NAR into a non-nix-store directory (e.g. for testing)
localUnpackNar :: Monad m => NarEffects m -> FilePath -> Nar -> m () localUnpackNar :: Monad m => NarEffects m -> FilePath -> Nar -> m ()
localUnpackNar effs basePath (Nar fso) = localUnpackFSO basePath fso localUnpackNar effs basePath0 (Nar fso0) = localUnpackFSO basePath0 fso0
where where
@ -222,8 +221,8 @@ localUnpackNar effs basePath (Nar fso) = localUnpackFSO basePath fso
Directory contents -> do Directory contents -> do
narCreateDir effs basePath narCreateDir effs basePath
forM_ (Map.toList contents) $ \(FilePathPart path', fso) -> forM_ (Map.toList contents) $ \(FilePathPart path', fso') ->
localUnpackFSO (basePath </> BSC.unpack path') fso localUnpackFSO (basePath </> BSC.unpack path') fso'
-- | Pack a NAR from a filepath -- | Pack a NAR from a filepath

View File

@ -19,24 +19,19 @@ module System.Nix.Path
, Roots , Roots
) where ) where
import System.Nix.Hash (Digest(..), import System.Nix.Hash (Digest,
HashAlgorithm'(Truncated, SHA256)) HashAlgorithm'(Truncated, SHA256))
import System.Nix.Internal.Hash import System.Nix.Internal.Hash
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC import qualified Data.ByteString.Char8 as BSC
import Data.Hashable (Hashable (..), hashPtrWithSalt) import Data.Hashable (Hashable (..))
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet) import Data.HashSet (HashSet)
import Data.Map.Strict (Map) import Data.Map.Strict (Map)
import Data.Monoid
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T
import System.IO.Unsafe (unsafeDupablePerformIO)
import Text.Regex.Base.RegexLike (makeRegex, matchTest) import Text.Regex.Base.RegexLike (makeRegex, matchTest)
import Text.Regex.TDFA.Text (Regex) import Text.Regex.TDFA.Text (Regex)
-- | The hash algorithm used for store path hashes. -- | The hash algorithm used for store path hashes.
type PathHashAlgo = Truncated 20 SHA256 type PathHashAlgo = 'Truncated 20 'SHA256
-- | The name portion of a Nix path. -- | The name portion of a Nix path.
@ -125,4 +120,4 @@ filePathPart p = case BSC.any (`elem` ['/', '\NUL']) p of
type Roots = Map Path Path type Roots = Map Path Path
instance Hashable Path where instance Hashable Path where
hashWithSalt s (Path hash name) = s `hashWithSalt` hash `hashWithSalt` name hashWithSalt s (Path hash' name) = s `hashWithSalt` hash' `hashWithSalt` name

View File

@ -5,7 +5,6 @@
module System.Nix.ReadonlyStore where module System.Nix.ReadonlyStore where
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.ByteString.Base16 as Base16
import qualified Data.HashSet as HS import qualified Data.HashSet as HS
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T

View File

@ -13,16 +13,16 @@ module System.Nix.Store
import qualified Data.ByteString.Lazy as BS import qualified Data.ByteString.Lazy as BS
import Data.Text (Text) import Data.Text (Text)
import Text.Regex.Base.RegexLike (makeRegex, matchTest) --import Text.Regex.Base.RegexLike (makeRegex, matchTest)
import Text.Regex.TDFA.Text (Regex) --import Text.Regex.TDFA.Text (Regex)
import Data.Hashable (Hashable(..), hashPtrWithSalt) --import Data.Hashable (Hashable(..), hashPtrWithSalt)
import Data.HashSet (HashSet) import Data.HashSet (HashSet)
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import System.IO.Unsafe (unsafeDupablePerformIO) --import System.IO.Unsafe (unsafeDupablePerformIO)
import System.Nix.Hash (Digest) import System.Nix.Hash (Digest)
import System.Nix.Path import System.Nix.Path
import System.Nix.Nar --import System.Nix.Nar
-- | Interactions with the Nix store. -- | Interactions with the Nix store.

View File

@ -18,16 +18,16 @@ getInt = fromIntegral <$> getWord64le
-- length prefixed string packing with padding to 8 bytes -- length prefixed string packing with padding to 8 bytes
putByteStringLen :: LBS.ByteString -> Put putByteStringLen :: LBS.ByteString -> Put
putByteStringLen x = do putByteStringLen x = do
putInt $ fromIntegral $ len putInt len
putLazyByteString x putLazyByteString x
when (len `mod` 8 /= 0) $ when (len `mod` 8 /= 0) $
pad $ fromIntegral $ 8 - (len `mod` 8) pad $ fromIntegral $ 8 - (len `mod` 8)
where len = LBS.length x where len = LBS.length x
pad x = forM_ (take x $ cycle [0]) putWord8 pad x' = forM_ (take x' $ cycle [0]) putWord8
putByteStrings :: Foldable t => t LBS.ByteString -> Put putByteStrings :: Foldable t => t LBS.ByteString -> Put
putByteStrings xs = do putByteStrings xs = do
putInt $ fromIntegral $ length xs putInt $ length xs
mapM_ putByteStringLen xs mapM_ putByteStringLen xs
getByteStringLen :: Get LBS.ByteString getByteStringLen :: Get LBS.ByteString