Skip to content

Commit b7c2216

Browse files
committed
Move bytestring-level base32 encoding to its own module.
1 parent 71025ed commit b7c2216

File tree

3 files changed

+35
-32
lines changed

3 files changed

+35
-32
lines changed

hnix-store-core/hnix-store-core.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,8 @@ extra-source-files: ChangeLog.md, README.md
1717
cabal-version: >=1.10
1818

1919
library
20-
exposed-modules: System.Nix.Build
20+
exposed-modules: System.Nix.Base32
21+
, System.Nix.Build
2122
, System.Nix.Derivation
2223
, System.Nix.GC
2324
, System.Nix.Hash
Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,31 @@
1+
{-|
2+
Description: Implementation of Nix's base32 encoding.
3+
-}
4+
module System.Nix.Base32 where
5+
6+
import qualified Data.ByteString as BS
7+
import qualified Data.Text as T
8+
import qualified Data.Vector as V
9+
10+
-- | Encode a 'ByteString' in Nix's base32 encoding
11+
encode :: BS.ByteString -> T.Text
12+
encode c = T.pack $ concatMap char32 [nChar - 1, nChar - 2 .. 0]
13+
where
14+
digits32 = V.fromList "0123456789abcdfghijklmnpqrsvwxyz"
15+
-- The base32 encoding is 8/5's as long as the base256 digest. This `+ 1`
16+
-- `- 1` business is a bit odd, but has always been used in C++ since the
17+
-- base32 truncation was added in was first added in
18+
-- d58a11e019813902b6c4547ca61a127938b2cc20.
19+
nChar = fromIntegral $ ((BS.length c * 8 - 1) `div` 5) + 1
20+
21+
char32 :: Integer -> [Char]
22+
char32 i = [digits32 V.! digitInd]
23+
where
24+
byte j = BS.index c (fromIntegral j)
25+
fromIntegral' :: Num b => Integer -> b
26+
fromIntegral' = fromIntegral
27+
digitInd = fromIntegral' $
28+
sum [fromIntegral (byte j) * (256^j)
29+
| j <- [0 .. BS.length c - 1]]
30+
`div` (32^i)
31+
`mod` 32

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

Lines changed: 2 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ import qualified Data.Text.Encoding as T
3535
import qualified Data.Vector as V
3636
import Data.Word (Word8)
3737
import GHC.TypeLits
38+
import qualified System.Nix.Base32 as Base32
3839

3940
-- | A tag for different hashing algorithms
4041
-- Also used as a type-level tag for hash digests
@@ -92,7 +93,7 @@ hashLazy bsl =
9293

9394
-- | Encode a Digest in the special Nix base-32 encoding.
9495
encodeBase32 :: Digest a -> T.Text
95-
encodeBase32 (Digest bs) = printHashBytes32 bs
96+
encodeBase32 (Digest bs) = Base32.encode bs
9697

9798
-- | Encode a Digest in hex.
9899
encodeBase16 :: Digest a -> T.Text
@@ -131,33 +132,6 @@ newtype Digest (a :: HashAlgorithm) = Digest
131132
} deriving (Show, Eq, Ord, DataHashable.Hashable)
132133

133134

134-
-- instance DataHashable.Hashable (Digest a) where
135-
-- hashWithSalt a (Digest bs) = DataHashable.hashWithSalt a bs
136-
-- hashWithSalt = coerce . DataHash
137-
138-
139-
-- | Internal function for encoding bytestrings into base32 according to
140-
-- nix's convention
141-
printHashBytes32 :: BS.ByteString -> T.Text
142-
printHashBytes32 c = T.pack $ concatMap char32 [nChar - 1, nChar - 2 .. 0]
143-
where
144-
-- The base32 encoding is 8/5's as long as the base256 digest. This `+ 1`
145-
-- `- 1` business is a bit odd, but has always been used in C++ since the
146-
-- base32 truncation was added in was first added in
147-
-- d58a11e019813902b6c4547ca61a127938b2cc20.
148-
nChar = fromIntegral $ ((BS.length c * 8 - 1) `div` 5) + 1
149-
150-
char32 :: Integer -> [Char]
151-
char32 i = [digits32 V.! digitInd]
152-
where
153-
byte j = BS.index c (fromIntegral j)
154-
digitInd = fromIntegral $
155-
sum [fromIntegral (byte j) * (256^j)
156-
| j <- [0 .. BS.length c - 1]]
157-
`div` (32^i)
158-
`mod` 32
159-
160-
161135
-- | Internal function for producing the bitwise truncation of bytestrings.
162136
-- When truncation length is greater than the length of the bytestring,
163137
-- but less than twice the bytestring length, truncation splits the
@@ -180,6 +154,3 @@ truncateDigest (Digest c) = Digest $ BS.pack $ map truncOutputByte [0.. n-1]
180154
aux i x j = if j `mod` fromIntegral n == fromIntegral i
181155
then xor x (inputByte $ fromIntegral j)
182156
else x
183-
184-
digits32 :: V.Vector Char
185-
digits32 = V.fromList "0123456789abcdfghijklmnpqrsvwxyz"

0 commit comments

Comments
 (0)