Skip to content

Commit 7e61a7c

Browse files
authored
Merge pull request #57 from sorki/b32
Base16/Base32 decoding, props/tests
2 parents e0997b4 + d82ba9f commit 7e61a7c

File tree

8 files changed

+200
-51
lines changed

8 files changed

+200
-51
lines changed

default.nix

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@
1010
in {
1111
haskellPackages =
1212
pkgs.haskellPackages.override overrideHaskellPackages;
13-
haskell844Packages =
14-
pkgs.haskell.packages.ghc844.override overrideHaskellPackages;
13+
haskell865Packages =
14+
pkgs.haskell.packages.ghc865.override overrideHaskellPackages;
1515
inherit pkgs;
1616
}

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

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ cabal-version: >=1.10
1919
library
2020
exposed-modules: System.Nix.Base32
2121
, System.Nix.Hash
22+
, System.Nix.Internal.Base32
2223
, System.Nix.Internal.Hash
2324
, System.Nix.Internal.Signature
2425
, System.Nix.Internal.StorePath
@@ -63,13 +64,15 @@ test-suite format-tests
6364
type: exitcode-stdio-1.0
6465
main-is: Driver.hs
6566
other-modules:
67+
Arbitrary
6668
NarFormat
6769
Hash
6870
hs-source-dirs:
6971
tests
7072
build-depends:
7173
hnix-store-core
7274
, base
75+
, base16-bytestring
7376
, base64-bytestring
7477
, binary
7578
, bytestring
Lines changed: 5 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -1,39 +1,9 @@
11
{-|
22
Description: Implementation of Nix's base32 encoding.
33
-}
4-
module System.Nix.Base32 where
4+
module System.Nix.Base32 (
5+
encode
6+
, decode
7+
) where
58

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 'BS.ByteString' in Nix's base32 encoding
11-
encode :: BS.ByteString -> T.Text
12-
encode c = T.pack $ map char32 [nChar - 1, nChar - 2 .. 0]
13-
where
14-
digits32 = V.fromList "0123456789abcdfghijklmnpqrsvwxyz"
15-
-- Each base32 character gives us 5 bits of information, while
16-
-- each byte gives is 8. Because 'div' rounds down, we need to add
17-
-- one extra character to the result, and because of that extra 1
18-
-- we need to subtract one from the number of bits in the
19-
-- bytestring to cover for the case where the number of bits is
20-
-- already a factor of 5. Thus, the + 1 outside of the 'div' and
21-
-- the - 1 inside of it.
22-
nChar = fromIntegral $ ((BS.length c * 8 - 1) `div` 5) + 1
23-
24-
byte = BS.index c . fromIntegral
25-
26-
-- May need to switch to a more efficient calculation at some
27-
-- point.
28-
bAsInteger :: Integer
29-
bAsInteger = sum [fromIntegral (byte j) * (256 ^ j)
30-
| j <- [0 .. BS.length c - 1]
31-
]
32-
33-
char32 :: Integer -> Char
34-
char32 i = digits32 V.! digitInd
35-
where
36-
digitInd = fromIntegral $
37-
bAsInteger
38-
`div` (32^i)
39-
`mod` 32
9+
import System.Nix.Internal.Base32

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

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,9 @@ module System.Nix.Hash (
1212
, HNix.hashLazy
1313

1414
, HNix.encodeBase32
15+
, HNix.decodeBase32
1516
, HNix.encodeBase16
17+
, HNix.decodeBase16
1618
) where
1719

1820
import qualified System.Nix.Internal.Hash as HNix
Lines changed: 82 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,82 @@
1+
2+
module System.Nix.Internal.Base32 where
3+
4+
import Data.Bits (shiftR)
5+
import Data.Char (chr, ord)
6+
import Data.Word (Word8)
7+
import Data.List (unfoldr)
8+
import Data.Maybe (isJust, catMaybes)
9+
import qualified Data.ByteString as BS
10+
import qualified Data.ByteString.Char8 as BSC
11+
import qualified Data.Text as T
12+
import qualified Data.Vector as V
13+
import Numeric (readInt)
14+
15+
-- omitted: E O U T
16+
digits32 = V.fromList "0123456789abcdfghijklmnpqrsvwxyz"
17+
18+
-- | Encode a 'BS.ByteString' in Nix's base32 encoding
19+
encode :: BS.ByteString -> T.Text
20+
encode c = T.pack $ map char32 [nChar - 1, nChar - 2 .. 0]
21+
where
22+
-- Each base32 character gives us 5 bits of information, while
23+
-- each byte gives is 8. Because 'div' rounds down, we need to add
24+
-- one extra character to the result, and because of that extra 1
25+
-- we need to subtract one from the number of bits in the
26+
-- bytestring to cover for the case where the number of bits is
27+
-- already a factor of 5. Thus, the + 1 outside of the 'div' and
28+
-- the - 1 inside of it.
29+
nChar = fromIntegral $ ((BS.length c * 8 - 1) `div` 5) + 1
30+
31+
byte = BS.index c . fromIntegral
32+
33+
-- May need to switch to a more efficient calculation at some
34+
-- point.
35+
bAsInteger :: Integer
36+
bAsInteger = sum [fromIntegral (byte j) * (256 ^ j)
37+
| j <- [0 .. BS.length c - 1]
38+
]
39+
40+
char32 :: Integer -> Char
41+
char32 i = digits32 V.! digitInd
42+
where
43+
digitInd = fromIntegral $
44+
bAsInteger
45+
`div` (32^i)
46+
`mod` 32
47+
48+
-- | Decode Nix's base32 encoded text
49+
decode :: T.Text -> Either String BS.ByteString
50+
decode what = case T.all (flip elem digits32) what of
51+
True -> unsafeDecode what
52+
False -> Left "Invalid base32 string"
53+
54+
-- | Decode Nix's base32 encoded text
55+
-- Doesn't check if all elements match `digits32`
56+
unsafeDecode :: T.Text -> Either String BS.ByteString
57+
unsafeDecode what =
58+
case readInt 32
59+
(flip elem digits32)
60+
(\c -> maybe (error "character not in digits32") id $
61+
V.findIndex (==c) digits32)
62+
(T.unpack what)
63+
of
64+
[(i, _)] -> Right $ padded $ integerToBS i
65+
x -> Left $ "Can't decode: readInt returned " ++ show x
66+
where
67+
padded x | BS.length x < decLen = x `BS.append`
68+
(BSC.pack $ take (decLen - BS.length x) (cycle "\NUL"))
69+
padded x | otherwise = x
70+
71+
decLen = T.length what * 5 `div` 8
72+
73+
-- | Encode an Integer to a bytestring
74+
-- Similar to Data.Base32String (integerToBS) without `reverse`
75+
integerToBS :: Integer -> BS.ByteString
76+
integerToBS 0 = BS.pack [0]
77+
integerToBS i
78+
| i > 0 = BS.pack $ unfoldr f i
79+
| otherwise = error "integerToBS not defined for negative values"
80+
where
81+
f 0 = Nothing
82+
f x = Just (fromInteger x :: Word8, x `shiftR` 8)

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

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -99,10 +99,20 @@ hashLazy bsl =
9999
encodeBase32 :: Digest a -> T.Text
100100
encodeBase32 (Digest bs) = Base32.encode bs
101101

102+
-- | Decode a 'Digest' in the special Nix base-32 encoding.
103+
decodeBase32 :: T.Text -> Either String (Digest a)
104+
decodeBase32 t = Digest <$> Base32.decode t
105+
102106
-- | Encode a 'Digest' in hex.
103107
encodeBase16 :: Digest a -> T.Text
104108
encodeBase16 (Digest bs) = T.decodeUtf8 (Base16.encode bs)
105109

110+
-- | Decode a 'Digest' in hex
111+
decodeBase16 :: T.Text -> Either String (Digest a)
112+
decodeBase16 t = case Base16.decode (T.encodeUtf8 t) of
113+
(x, "") -> Right $ Digest x
114+
_ -> Left $ "Unable to decode base16 string " ++ T.unpack t
115+
106116
-- | Uses "Crypto.Hash.MD5" from cryptohash-md5.
107117
instance ValidAlgo 'MD5 where
108118
type AlgoCtx 'MD5 = MD5.Ctx

hnix-store-core/tests/Arbitrary.hs

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,37 @@
1+
{-# LANGUAGE FlexibleInstances #-}
2+
{-# LANGUAGE DataKinds #-}
3+
4+
module Arbitrary where
5+
6+
import Control.Monad (replicateM)
7+
import qualified Data.ByteString.Char8 as BSC
8+
import qualified Data.Text as T
9+
10+
import Test.Tasty.QuickCheck
11+
12+
import System.Nix.Hash
13+
import System.Nix.Internal.Hash
14+
import System.Nix.StorePath
15+
import System.Nix.Internal.StorePath
16+
17+
genSafeChar :: Gen Char
18+
genSafeChar = choose ('\1', '\127') -- ASCII without \NUL
19+
20+
nonEmptyString :: Gen String
21+
nonEmptyString = listOf1 genSafeChar
22+
23+
dir = ('/':) <$> (listOf1 $ elements $ ('/':['a'..'z']))
24+
25+
instance Arbitrary StorePathName where
26+
arbitrary = StorePathName . T.pack
27+
<$> ((:) <$> s1 <*> listOf sn)
28+
where
29+
alphanum = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9']
30+
s1 = elements $ alphanum ++ "+-_?="
31+
sn = elements $ alphanum ++ "+-._?="
32+
33+
instance Arbitrary (Digest StorePathHashAlgo) where
34+
arbitrary = hash . BSC.pack <$> arbitrary
35+
36+
instance Arbitrary (Digest SHA256) where
37+
arbitrary = hash . BSC.pack <$> arbitrary

hnix-store-core/tests/Hash.hs

Lines changed: 59 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -5,26 +5,20 @@
55

66
module Hash where
77

8-
import Control.Monad.IO.Class (liftIO)
9-
import Control.Exception (bracket)
10-
import qualified Data.ByteString as BS
8+
import Control.Monad (forM_)
9+
import qualified Data.ByteString.Char8 as BSC
10+
import qualified Data.ByteString.Base16 as B16
1111
import qualified Data.ByteString.Base64.Lazy as B64
1212
import qualified Data.ByteString.Lazy as BSL
13-
import Data.Monoid ((<>))
14-
import qualified Data.Text as T
15-
import System.Directory (removeFile)
16-
import System.IO.Temp (withSystemTempFile, writeSystemTempFile)
17-
import qualified System.IO as IO -- (hGetContents, hPutStr, openFile)
18-
import qualified System.Process as P
19-
import Test.Tasty as T
13+
2014
import Test.Tasty.Hspec
21-
import qualified Test.Tasty.HUnit as HU
2215
import Test.Tasty.QuickCheck
23-
import Text.Read (readMaybe)
2416

17+
import System.Nix.Base32
2518
import System.Nix.Hash
19+
import System.Nix.Internal.Hash
2620
import System.Nix.StorePath
27-
import NarFormat -- TODO: Move the fixtures into a common module
21+
import Arbitrary
2822

2923
spec_hash :: Spec
3024
spec_hash = do
@@ -34,7 +28,9 @@ spec_hash = do
3428
it "produces (base32 . sha256) of \"nix-output:foo\" the same as Nix does at the moment for placeholder \"foo\"" $
3529
shouldBe (encodeBase32 (hash @SHA256 "nix-output:foo"))
3630
"1x0ymrsy7yr7i9wdsqy9khmzc1yy7nvxw6rdp72yzn50285s67j5"
37-
31+
it "produces (base16 . md5) of \"Hello World\" the same as the thesis" $
32+
shouldBe (encodeBase16 (hash @MD5 "Hello World"))
33+
"b10a8db164e0754105b7a99be72e3fe5"
3834
it "produces (base32 . sha1) of \"Hello World\" the same as the thesis" $
3935
shouldBe (encodeBase32 (hash @SHA1 "Hello World"))
4036
"s23c9fs0v32pf6bhmcph5rbqsyl5ak8a"
@@ -47,3 +43,52 @@ spec_hash = do
4743
<> "c0d7b98883f9ee3:/nix/store:myfile"
4844
shouldBe (encodeBase32 @StorePathHashAlgo (hash exampleStr))
4945
"xv2iccirbrvklck36f1g7vldn5v58vck"
46+
47+
-- | Test that Nix-like base32 encoding roundtrips
48+
prop_nixBase32Roundtrip = forAllShrink nonEmptyString genericShrink $
49+
\x -> Right (BSC.pack x) === (decode . encode . BSC.pack $ x)
50+
51+
-- | API variants
52+
prop_nixBase16Roundtrip =
53+
\(x :: Digest StorePathHashAlgo) -> Right x === (decodeBase16 . encodeBase16 $ x)
54+
55+
-- | Hash encoding conversion ground-truth.
56+
-- Similiar to nix/tests/hash.sh
57+
spec_nixhash :: Spec
58+
spec_nixhash = do
59+
60+
describe "hashing parity with nix-nash" $ do
61+
62+
let
63+
samples = [
64+
( "800d59cfcd3c05e900cb4e214be48f6b886a08df"
65+
, "vw46m23bizj4n8afrc0fj19wrp7mj3c0"
66+
, "gA1Zz808BekAy04hS+SPa4hqCN8="
67+
)
68+
, ( "ba7816bf8f01cfea414140de5dae2223b00361a396177a9cb410ff61f20015ad"
69+
, "1b8m03r63zqhnjf7l5wnldhh7c134ap5vpj0850ymkq1iyzicy5s"
70+
, "ungWv48Bz+pBQUDeXa4iI7ADYaOWF3qctBD/YfIAFa0="
71+
)
72+
, ( "204a8fc6dda82f0a0ced7beb8e08a41657c16ef468b228a8279be331a703c33596fd15c13b1b07f9aa1d3bea57789ca031ad85c7a71dd70354ec631238ca3445"
73+
, "12k9jiq29iyqm03swfsgiw5mlqs173qazm3n7daz43infy12pyrcdf30fkk3qwv4yl2ick8yipc2mqnlh48xsvvxl60lbx8vp38yji0"
74+
, "IEqPxt2oLwoM7XvrjgikFlfBbvRosiioJ5vjMacDwzWW/RXBOxsH+aodO+pXeJygMa2Fx6cd1wNU7GMSOMo0RQ=="
75+
)
76+
]
77+
78+
it "b16 encoded . b32 decoded should equal original b16" $
79+
forM_ samples $ \(b16, b32, b64) -> shouldBe (B16.encode <$> decode b32) (Right b16)
80+
81+
it "b64 encoded . b32 decoded should equal original b64" $
82+
forM_ samples $ \(b16, b32, b64) -> shouldBe (B64.encode . BSL.fromStrict <$> decode b32) (Right b64)
83+
84+
it "b32 encoded . b64 decoded should equal original b32" $
85+
forM_ samples $ \(b16, b32, b64) -> shouldBe (encode . BSL.toStrict <$> B64.decode b64 ) (Right b32)
86+
87+
it "b16 encoded . b64 decoded should equal original b16" $
88+
forM_ samples $ \(b16, b32, b64) -> shouldBe (B16.encode . BSL.toStrict <$> B64.decode b64 ) (Right b16)
89+
90+
it "b32 encoded . b16 decoded should equal original b32" $
91+
forM_ samples $ \(b16, b32, b64) -> shouldBe (encode $ fst $ B16.decode b16 ) b32
92+
93+
it "b64 encoded . b16 decoded should equal original b64" $
94+
forM_ samples $ \(b16, b32, b64) -> shouldBe (B64.encode $ BSL.fromStrict $ fst $ B16.decode b16 ) b64

0 commit comments

Comments
 (0)