Skip to content

Commit 500a934

Browse files
committed
Core: Internal: mv Base dec -> Base, Hash.decode(Base->DigestWith)
1 parent 58d7630 commit 500a934

File tree

5 files changed

+28
-24
lines changed

5 files changed

+28
-24
lines changed

hnix-store-core/src/System/Nix/Hash.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ module System.Nix.Hash
1515

1616
, Base.BaseEncoding(..)
1717
, Hash.encodeDigestWith
18-
, Hash.decodeBase
18+
, Hash.decodeDigestWith
1919
)
2020
where
2121

hnix-store-core/src/System/Nix/Internal/Base.hs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE CPP #-}
2+
13
module System.Nix.Internal.Base
24
( module System.Nix.Internal.Base
35
, Base32.encode
@@ -26,3 +28,18 @@ encodeWith :: BaseEncoding -> Bytes.ByteString -> T.Text
2628
encodeWith Base16 = T.decodeUtf8 . Base16.encode
2729
encodeWith NixBase32 = Base32.encode
2830
encodeWith Base64 = T.decodeUtf8 . Base64.encode
31+
32+
-- | Take the input & @Base@ encoding witness -> decode into @Text@.
33+
decodeWith :: BaseEncoding -> T.Text -> Either String Bytes.ByteString
34+
#if MIN_VERSION_base16_bytestring(1,0,0)
35+
decodeWith Base16 = Base16.decode . T.encodeUtf8
36+
#else
37+
decodeWith Base16 = lDecode -- this tacit sugar simply makes GHC pleased with number of args
38+
where
39+
lDecode t =
40+
case Base16.decode (T.encodeUtf8 t) of
41+
(x, "") -> pure $ x
42+
_ -> Left $ "Unable to decode base16 string" <> T.unpack t
43+
#endif
44+
decodeWith NixBase32 = Base32.decode
45+
decodeWith Base64 = Base64.decode . T.encodeUtf8

hnix-store-core/src/System/Nix/Internal/Hash.hs

Lines changed: 6 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -19,24 +19,21 @@ import qualified Crypto.Hash.SHA1 as SHA1
1919
import qualified Crypto.Hash.SHA256 as SHA256
2020
import qualified Crypto.Hash.SHA512 as SHA512
2121
import qualified Data.ByteString as BS
22-
import qualified Data.ByteString.Base16 as Base16
23-
import qualified System.Nix.Base32 as Base32 -- Nix has own Base32 encoding
24-
import qualified Data.ByteString.Base64 as Base64
2522
import Data.Bits (xor)
2623
import qualified Data.ByteString.Lazy as BSL
2724
import qualified Data.Hashable as DataHashable
2825
import Data.List (foldl')
2926
import Data.Proxy (Proxy(Proxy))
3027
import Data.Text (Text)
3128
import qualified Data.Text as T
32-
import qualified Data.Text.Encoding as T
3329
import Data.Word (Word8)
3430
import qualified GHC.TypeLits as Kind
3531
(Nat, KnownNat, natVal)
3632
import Data.Coerce (coerce)
3733
import System.Nix.Internal.Base
3834
( BaseEncoding(Base16,NixBase32,Base64)
3935
, encodeWith
36+
, decodeWith
4037
)
4138

4239
-- | The universe of supported hash algorithms.
@@ -116,9 +113,9 @@ mkNamedDigest name sriHash =
116113
_ -> Left $ "Unknown hash name: " <> T.unpack name
117114
decodeGo :: forall a . (NamedAlgo a, ValidAlgo a) => Text -> Either String (Digest a)
118115
decodeGo h
119-
| size == base16Len = decodeBase Base16 h
120-
| size == base32Len = decodeBase NixBase32 h
121-
| size == base64Len = decodeBase Base64 h
116+
| size == base16Len = decodeDigestWith Base16 h
117+
| size == base32Len = decodeDigestWith NixBase32 h
118+
| size == base64Len = decodeDigestWith Base64 h
122119
| 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]
123120
where
124121
size = T.length h
@@ -154,18 +151,8 @@ encodeDigestWith b = encodeWith b . coerce
154151

155152

156153
-- | Take BaseEncoding type of the input -> take the input itself -> decodeBase into Digest
157-
decodeBase :: BaseEncoding -> T.Text -> Either String (Digest a)
158-
#if MIN_VERSION_base16_bytestring(1,0,0)
159-
decodeBase Base16 = fmap Digest . Base16.decode . T.encodeUtf8
160-
#else
161-
decodeBase Base16 = lDecode -- this tacit sugar simply makes GHC pleased with number of args
162-
where
163-
lDecode t = case Base16.decode (T.encodeUtf8 t) of
164-
(x, "") -> Right $ Digest x
165-
_ -> Left $ "Unable to decode base16 string" <> T.unpack t
166-
#endif
167-
decodeBase NixBase32 = fmap Digest . Base32.decode
168-
decodeBase Base64 = fmap Digest . Base64.decode . T.encodeUtf8
154+
decodeDigestWith :: BaseEncoding -> T.Text -> Either String (Digest a)
155+
decodeDigestWith b x = Digest <$> decodeWith b x
169156

170157

171158
-- | Uses "Crypto.Hash.MD5" from cryptohash-md5.

hnix-store-core/src/System/Nix/Internal/StorePath.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ import System.Nix.Hash ( HashAlgorithm
1717
, Digest
1818
, BaseEncoding(..)
1919
, encodeDigestWith
20-
, decodeBase
20+
, decodeDigestWith
2121
, SomeNamedDigest
2222
)
2323

@@ -178,7 +178,7 @@ parsePath expectedRoot x =
178178
let
179179
(rootDir, fname) = FilePath.splitFileName . Bytes.Char8.unpack $ x
180180
(digestPart, namePart) = Text.breakOn "-" $ Text.pack fname
181-
digest = decodeBase NixBase32 digestPart
181+
digest = decodeDigestWith NixBase32 digestPart
182182
name = makeStorePathName . Text.drop 1 $ namePart
183183
--rootDir' = dropTrailingPathSeparator rootDir
184184
-- cannot use ^^ as it drops multiple slashes /a/b/// -> /a/b
@@ -200,7 +200,7 @@ pathParser expectedRoot = do
200200
<?> "Expecting path separator"
201201

202202
digest <-
203-
decodeBase NixBase32
203+
decodeDigestWith NixBase32
204204
<$> Parser.Text.Lazy.takeWhile1 (`elem` Nix.Base32.digits32)
205205
<?> "Invalid Base32 part"
206206

hnix-store-core/tests/Hash.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ prop_nixBase32Roundtrip = forAllShrink nonEmptyString genericShrink $
5555

5656
-- | API variants
5757
prop_nixBase16Roundtrip :: Digest StorePathHashAlgo -> Property
58-
prop_nixBase16Roundtrip x = pure x === (decodeBase Base16 . encodeDigestWith Base16 $ x)
58+
prop_nixBase16Roundtrip x = pure x === (decodeDigestWith Base16 . encodeDigestWith Base16 $ x)
5959

6060
-- | Hash encoding conversion ground-truth.
6161
-- Similiar to nix/tests/hash.sh

0 commit comments

Comments
 (0)