mirror of
https://github.com/haskell-nix/hnix-store.git
synced 2024-12-14 19:47:56 +03:00
Core: Internal: mv Base dec -> Base, Hash.decode(Base->DigestWith)
This commit is contained in:
parent
f5ba0fcfa4
commit
49699e9ce3
@ -15,7 +15,7 @@ module System.Nix.Hash
|
|||||||
|
|
||||||
, Base.BaseEncoding(..)
|
, Base.BaseEncoding(..)
|
||||||
, Hash.encodeDigestWith
|
, Hash.encodeDigestWith
|
||||||
, Hash.decodeBase
|
, Hash.decodeDigestWith
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
@ -1,3 +1,5 @@
|
|||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module System.Nix.Internal.Base
|
module System.Nix.Internal.Base
|
||||||
( module System.Nix.Internal.Base
|
( module System.Nix.Internal.Base
|
||||||
, Base32.encode
|
, Base32.encode
|
||||||
@ -26,3 +28,18 @@ encodeWith :: BaseEncoding -> Bytes.ByteString -> T.Text
|
|||||||
encodeWith Base16 = T.decodeUtf8 . Base16.encode
|
encodeWith Base16 = T.decodeUtf8 . Base16.encode
|
||||||
encodeWith NixBase32 = Base32.encode
|
encodeWith NixBase32 = Base32.encode
|
||||||
encodeWith Base64 = T.decodeUtf8 . Base64.encode
|
encodeWith Base64 = T.decodeUtf8 . Base64.encode
|
||||||
|
|
||||||
|
-- | Take the input & @Base@ encoding witness -> decode into @Text@.
|
||||||
|
decodeWith :: BaseEncoding -> T.Text -> Either String Bytes.ByteString
|
||||||
|
#if MIN_VERSION_base16_bytestring(1,0,0)
|
||||||
|
decodeWith Base16 = Base16.decode . T.encodeUtf8
|
||||||
|
#else
|
||||||
|
decodeWith Base16 = lDecode -- this tacit sugar simply makes GHC pleased with number of args
|
||||||
|
where
|
||||||
|
lDecode t =
|
||||||
|
case Base16.decode (T.encodeUtf8 t) of
|
||||||
|
(x, "") -> pure $ x
|
||||||
|
_ -> Left $ "Unable to decode base16 string" <> T.unpack t
|
||||||
|
#endif
|
||||||
|
decodeWith NixBase32 = Base32.decode
|
||||||
|
decodeWith Base64 = Base64.decode . T.encodeUtf8
|
||||||
|
@ -19,9 +19,6 @@ import qualified Crypto.Hash.SHA1 as SHA1
|
|||||||
import qualified Crypto.Hash.SHA256 as SHA256
|
import qualified Crypto.Hash.SHA256 as SHA256
|
||||||
import qualified Crypto.Hash.SHA512 as SHA512
|
import qualified Crypto.Hash.SHA512 as SHA512
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
import qualified Data.ByteString.Base16 as Base16
|
|
||||||
import qualified System.Nix.Base32 as Base32 -- Nix has own Base32 encoding
|
|
||||||
import qualified Data.ByteString.Base64 as Base64
|
|
||||||
import Data.Bits (xor)
|
import Data.Bits (xor)
|
||||||
import qualified Data.ByteString.Lazy as BSL
|
import qualified Data.ByteString.Lazy as BSL
|
||||||
import qualified Data.Hashable as DataHashable
|
import qualified Data.Hashable as DataHashable
|
||||||
@ -29,7 +26,6 @@ import Data.List (foldl')
|
|||||||
import Data.Proxy (Proxy(Proxy))
|
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 Data.Word (Word8)
|
import Data.Word (Word8)
|
||||||
import qualified GHC.TypeLits as Kind
|
import qualified GHC.TypeLits as Kind
|
||||||
(Nat, KnownNat, natVal)
|
(Nat, KnownNat, natVal)
|
||||||
@ -37,6 +33,7 @@ import Data.Coerce (coerce)
|
|||||||
import System.Nix.Internal.Base
|
import System.Nix.Internal.Base
|
||||||
( BaseEncoding(Base16,NixBase32,Base64)
|
( BaseEncoding(Base16,NixBase32,Base64)
|
||||||
, encodeWith
|
, encodeWith
|
||||||
|
, decodeWith
|
||||||
)
|
)
|
||||||
|
|
||||||
-- | The universe of supported hash algorithms.
|
-- | The universe of supported hash algorithms.
|
||||||
@ -116,9 +113,9 @@ mkNamedDigest name sriHash =
|
|||||||
_ -> Left $ "Unknown hash name: " <> T.unpack name
|
_ -> Left $ "Unknown hash name: " <> T.unpack name
|
||||||
decodeGo :: forall a . (NamedAlgo a, ValidAlgo a) => Text -> Either String (Digest a)
|
decodeGo :: forall a . (NamedAlgo a, ValidAlgo a) => Text -> Either String (Digest a)
|
||||||
decodeGo h
|
decodeGo h
|
||||||
| size == base16Len = decodeBase Base16 h
|
| size == base16Len = decodeDigestWith Base16 h
|
||||||
| size == base32Len = decodeBase NixBase32 h
|
| size == base32Len = decodeDigestWith NixBase32 h
|
||||||
| size == base64Len = decodeBase Base64 h
|
| size == base64Len = decodeDigestWith Base64 h
|
||||||
| otherwise = Left $ T.unpack sriHash <> " is not a valid " <> T.unpack name <> " hash. Its length (" <> show size <> ") does not match any of " <> show [base16Len, base32Len, base64Len]
|
| otherwise = Left $ T.unpack sriHash <> " is not a valid " <> T.unpack name <> " hash. Its length (" <> show size <> ") does not match any of " <> show [base16Len, base32Len, base64Len]
|
||||||
where
|
where
|
||||||
size = T.length h
|
size = T.length h
|
||||||
@ -154,18 +151,8 @@ encodeDigestWith b = encodeWith b . coerce
|
|||||||
|
|
||||||
|
|
||||||
-- | Take BaseEncoding type of the input -> take the input itself -> decodeBase into Digest
|
-- | Take BaseEncoding type of the input -> take the input itself -> decodeBase into Digest
|
||||||
decodeBase :: BaseEncoding -> T.Text -> Either String (Digest a)
|
decodeDigestWith :: BaseEncoding -> T.Text -> Either String (Digest a)
|
||||||
#if MIN_VERSION_base16_bytestring(1,0,0)
|
decodeDigestWith b x = Digest <$> decodeWith b x
|
||||||
decodeBase Base16 = fmap Digest . Base16.decode . T.encodeUtf8
|
|
||||||
#else
|
|
||||||
decodeBase Base16 = lDecode -- this tacit sugar simply makes GHC pleased with number of args
|
|
||||||
where
|
|
||||||
lDecode t = case Base16.decode (T.encodeUtf8 t) of
|
|
||||||
(x, "") -> Right $ Digest x
|
|
||||||
_ -> Left $ "Unable to decode base16 string" <> T.unpack t
|
|
||||||
#endif
|
|
||||||
decodeBase NixBase32 = fmap Digest . Base32.decode
|
|
||||||
decodeBase Base64 = fmap Digest . Base64.decode . T.encodeUtf8
|
|
||||||
|
|
||||||
|
|
||||||
-- | Uses "Crypto.Hash.MD5" from cryptohash-md5.
|
-- | Uses "Crypto.Hash.MD5" from cryptohash-md5.
|
||||||
|
@ -17,7 +17,7 @@ import System.Nix.Hash ( HashAlgorithm
|
|||||||
, Digest
|
, Digest
|
||||||
, BaseEncoding(..)
|
, BaseEncoding(..)
|
||||||
, encodeDigestWith
|
, encodeDigestWith
|
||||||
, decodeBase
|
, decodeDigestWith
|
||||||
, SomeNamedDigest
|
, SomeNamedDigest
|
||||||
)
|
)
|
||||||
|
|
||||||
@ -178,7 +178,7 @@ parsePath expectedRoot x =
|
|||||||
let
|
let
|
||||||
(rootDir, fname) = FilePath.splitFileName . Bytes.Char8.unpack $ x
|
(rootDir, fname) = FilePath.splitFileName . Bytes.Char8.unpack $ x
|
||||||
(digestPart, namePart) = Text.breakOn "-" $ Text.pack fname
|
(digestPart, namePart) = Text.breakOn "-" $ Text.pack fname
|
||||||
digest = decodeBase NixBase32 digestPart
|
digest = decodeDigestWith NixBase32 digestPart
|
||||||
name = makeStorePathName . Text.drop 1 $ namePart
|
name = makeStorePathName . Text.drop 1 $ namePart
|
||||||
--rootDir' = dropTrailingPathSeparator rootDir
|
--rootDir' = dropTrailingPathSeparator rootDir
|
||||||
-- cannot use ^^ as it drops multiple slashes /a/b/// -> /a/b
|
-- cannot use ^^ as it drops multiple slashes /a/b/// -> /a/b
|
||||||
@ -200,7 +200,7 @@ pathParser expectedRoot = do
|
|||||||
<?> "Expecting path separator"
|
<?> "Expecting path separator"
|
||||||
|
|
||||||
digest <-
|
digest <-
|
||||||
decodeBase NixBase32
|
decodeDigestWith NixBase32
|
||||||
<$> Parser.Text.Lazy.takeWhile1 (`elem` Nix.Base32.digits32)
|
<$> Parser.Text.Lazy.takeWhile1 (`elem` Nix.Base32.digits32)
|
||||||
<?> "Invalid Base32 part"
|
<?> "Invalid Base32 part"
|
||||||
|
|
||||||
|
@ -55,7 +55,7 @@ prop_nixBase32Roundtrip = forAllShrink nonEmptyString genericShrink $
|
|||||||
|
|
||||||
-- | API variants
|
-- | API variants
|
||||||
prop_nixBase16Roundtrip :: Digest StorePathHashAlgo -> Property
|
prop_nixBase16Roundtrip :: Digest StorePathHashAlgo -> Property
|
||||||
prop_nixBase16Roundtrip x = pure x === (decodeBase Base16 . encodeDigestWith Base16 $ x)
|
prop_nixBase16Roundtrip x = pure x === (decodeDigestWith Base16 . encodeDigestWith Base16 $ x)
|
||||||
|
|
||||||
-- | Hash encoding conversion ground-truth.
|
-- | Hash encoding conversion ground-truth.
|
||||||
-- Similiar to nix/tests/hash.sh
|
-- Similiar to nix/tests/hash.sh
|
||||||
|
Loading…
Reference in New Issue
Block a user