Skip to content

Commit b00b303

Browse files
committed
Core: Internal: Base: (-> Nix)Base32
To name it honestly. It is not a standard Base32 encoding. NixBase32 needs specific treatment over the stack (now & in the future), so it is better to distinquish it from default encoding.
1 parent 2f30c61 commit b00b303

File tree

4 files changed

+14
-14
lines changed

4 files changed

+14
-14
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,6 @@ import System.Nix.Internal.Base32
1010
-- | Constructors to indicate the base encodings
1111
data BaseEncoding
1212
= Base16
13-
| Base32
13+
| NixBase32
1414
-- | ^ Nix has a special map of Base32 encoding
1515
| Base64

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

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ import qualified GHC.TypeLits as Kind
3535
(Nat, KnownNat, natVal)
3636
import Data.Coerce (coerce)
3737
import System.Nix.Internal.Base
38-
(BaseEncoding(Base16,Base32,Base64))
38+
(BaseEncoding(Base16,NixBase32,Base64))
3939

4040
-- | The universe of supported hash algorithms.
4141
--
@@ -55,7 +55,7 @@ newtype Digest (a :: HashAlgorithm) =
5555
Digest BS.ByteString deriving (Eq, Ord, DataHashable.Hashable)
5656

5757
instance Show (Digest a) where
58-
show = ("Digest " <>) . show . encodeInBase Base32
58+
show = ("Digest " <>) . show . encodeInBase NixBase32
5959

6060
-- | The primitive interface for incremental hashing for a given
6161
-- 'HashAlgorithm'. Every 'HashAlgorithm' should have an instance.
@@ -97,7 +97,7 @@ data SomeNamedDigest = forall a . NamedAlgo a => SomeDigest (Digest a)
9797

9898
instance Show SomeNamedDigest where
9999
show sd = case sd of
100-
SomeDigest (digest :: Digest hashType) -> T.unpack $ "SomeDigest " <> algoName @hashType <> ":" <> encodeInBase Base32 digest
100+
SomeDigest (digest :: Digest hashType) -> T.unpack $ "SomeDigest " <> algoName @hashType <> ":" <> encodeInBase NixBase32 digest
101101

102102
mkNamedDigest :: Text -> Text -> Either String SomeNamedDigest
103103
mkNamedDigest name sriHash =
@@ -115,7 +115,7 @@ mkNamedDigest name sriHash =
115115
decodeGo :: forall a . (NamedAlgo a, ValidAlgo a) => Text -> Either String (Digest a)
116116
decodeGo h
117117
| size == base16Len = decodeBase Base16 h
118-
| size == base32Len = decodeBase Base32 h
118+
| size == base32Len = decodeBase NixBase32 h
119119
| size == base64Len = decodeBase Base64 h
120120
| 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]
121121
where
@@ -149,7 +149,7 @@ hashLazy bsl =
149149
-- | Take BaseEncoding type of the output -> take the Digeest as input -> encode Digest
150150
encodeInBase :: BaseEncoding -> Digest a -> T.Text
151151
encodeInBase Base16 = T.decodeUtf8 . Base16.encode . coerce
152-
encodeInBase Base32 = Base32.encode . coerce
152+
encodeInBase NixBase32 = Base32.encode . coerce
153153
encodeInBase Base64 = T.decodeUtf8 . Base64.encode . coerce
154154

155155

@@ -164,7 +164,7 @@ decodeBase Base16 = lDecode -- this tacit sugar simply makes GHC pleased with n
164164
(x, "") -> Right $ Digest x
165165
_ -> Left $ "Unable to decode base16 string" <> T.unpack t
166166
#endif
167-
decodeBase Base32 = fmap Digest . Base32.decode
167+
decodeBase NixBase32 = fmap Digest . Base32.decode
168168
decodeBase Base64 = fmap Digest . Base64.decode . T.encodeUtf8
169169

170170

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

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -154,7 +154,7 @@ storePathToRawFilePath StorePath{..} =
154154
root <> "/" <> hashPart <> "-" <> name
155155
where
156156
root = Bytes.Char8.pack storePathRoot
157-
hashPart = Text.encodeUtf8 $ encodeInBase Base32 storePathHash
157+
hashPart = Text.encodeUtf8 $ encodeInBase NixBase32 storePathHash
158158
name = Text.encodeUtf8 $ unStorePathName storePathName
159159

160160
-- | Render a 'StorePath' as a 'FilePath'.
@@ -169,7 +169,7 @@ storePathToText = Text.pack . Bytes.Char8.unpack . storePathToRawFilePath
169169
-- can be used to query binary caches.
170170
storePathToNarInfo :: StorePath -> Bytes.Char8.ByteString
171171
storePathToNarInfo StorePath{..} =
172-
Text.encodeUtf8 $ encodeInBase Base32 storePathHash <> ".narinfo"
172+
Text.encodeUtf8 $ encodeInBase NixBase32 storePathHash <> ".narinfo"
173173

174174
-- | Parse `StorePath` from `Bytes.Char8.ByteString`, checking
175175
-- that store directory matches `expectedRoot`.
@@ -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 Base32 digestPart
181+
digest = decodeBase 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 Base32
203+
decodeBase NixBase32
204204
<$> Parser.Text.Lazy.takeWhile1 (`elem` Nix.Base32.digits32)
205205
<?> "Invalid Base32 part"
206206

hnix-store-core/tests/Hash.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -27,13 +27,13 @@ spec_hash = do
2727
describe "hashing parity with nix-store" $ do
2828

2929
it "produces (base32 . sha256) of \"nix-output:foo\" the same as Nix does at the moment for placeholder \"foo\"" $
30-
shouldBe (encodeInBase Base32 (hash @'SHA256 "nix-output:foo"))
30+
shouldBe (encodeInBase NixBase32 (hash @'SHA256 "nix-output:foo"))
3131
"1x0ymrsy7yr7i9wdsqy9khmzc1yy7nvxw6rdp72yzn50285s67j5"
3232
it "produces (base16 . md5) of \"Hello World\" the same as the thesis" $
3333
shouldBe (encodeInBase Base16 (hash @'MD5 "Hello World"))
3434
"b10a8db164e0754105b7a99be72e3fe5"
3535
it "produces (base32 . sha1) of \"Hello World\" the same as the thesis" $
36-
shouldBe (encodeInBase Base32 (hash @'SHA1 "Hello World"))
36+
shouldBe (encodeInBase NixBase32 (hash @'SHA1 "Hello World"))
3737
"s23c9fs0v32pf6bhmcph5rbqsyl5ak8a"
3838

3939
-- The example in question:
@@ -46,7 +46,7 @@ spec_hash = do
4646
"xv2iccirbrvklck36f1g7vldn5v58vck"
4747
where
4848
encodeInBase32 :: Digest a -> Text
49-
encodeInBase32 = encodeInBase Base32
49+
encodeInBase32 = encodeInBase NixBase32
5050

5151
-- | Test that Nix-like base32 encoding roundtrips
5252
prop_nixBase32Roundtrip :: Property

0 commit comments

Comments
 (0)