55
66module 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
1111import qualified Data.ByteString.Base64.Lazy as B64
1212import 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+
2014import Test.Tasty.Hspec
21- import qualified Test.Tasty.HUnit as HU
2215import Test.Tasty.QuickCheck
23- import Text.Read (readMaybe )
2416
17+ import System.Nix.Base32
2518import System.Nix.Hash
19+ import System.Nix.Internal.Hash
2620import System.Nix.StorePath
27- import NarFormat -- TODO: Move the fixtures into a common module
21+ import Arbitrary
2822
2923spec_hash :: Spec
3024spec_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