Skip to content

Commit 9f98592

Browse files
authored
Merge pull request #29 from haskell-nix/fewer-deps-3
Fewer deps 3
2 parents a571a32 + 6584d76 commit 9f98592

File tree

5 files changed

+233
-19
lines changed

5 files changed

+233
-19
lines changed

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

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ library
2121
, System.Nix.Derivation
2222
, System.Nix.GC
2323
, System.Nix.Hash
24+
, System.Nix.Internal.Hash
2425
, System.Nix.Nar
2526
, System.Nix.Path
2627
, System.Nix.Store
@@ -30,6 +31,9 @@ library
3031
, binary
3132
, bytestring
3233
, containers
34+
, cryptohash-md5
35+
, cryptohash-sha1
36+
, cryptohash-sha256
3337
, directory
3438
, filepath
3539
, hashable
@@ -39,6 +43,7 @@ library
3943
, text
4044
, unix
4145
, unordered-containers
46+
, vector
4247
hs-source-dirs: src
4348
default-language: Haskell2010
4449

@@ -54,6 +59,7 @@ test-suite format-tests
5459
main-is: Driver.hs
5560
other-modules:
5661
NarFormat
62+
Hash
5763
hs-source-dirs:
5864
tests
5965
build-depends:
@@ -70,5 +76,6 @@ test-suite format-tests
7076
, tasty-hspec
7177
, tasty-hunit
7278
, tasty-quickcheck
79+
, temporary
7380
, text
7481
default-language: Haskell2010
Lines changed: 12 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,30 +1,25 @@
11
{-|
2-
Description : Trunctions of cryptographic hashes.
3-
Maintainer : Shea Levy <[email protected]>
2+
Description : Cryptographic hashes for hnix-store.
3+
Maintainer : Shea Levy <[email protected]>; Greg Hale <[email protected]>
44
-}
55
{-# LANGUAGE DataKinds #-}
66
{-# LANGUAGE TypeApplications #-}
77
{-# LANGUAGE ScopedTypeVariables #-}
88
{-# LANGUAGE FlexibleContexts #-}
9+
{-# LANGUAGE TypeApplications #-}
910
{-# LANGUAGE TypeFamilies #-}
1011
{-# LANGUAGE TypeOperators #-}
1112
{-# LANGUAGE CPP #-}
12-
module System.Nix.Hash where
13+
module System.Nix.Hash (
14+
HNix.Digest
1315

14-
import Control.Monad (void)
15-
import Data.Coerce (coerce)
16-
import qualified Data.ByteString as BS
17-
import Data.Hashable (Hashable (..))
18-
import Data.Proxy (Proxy(..))
19-
import Data.Word (Word8)
20-
import GHC.TypeLits (Nat, KnownNat, natVal, type (<=))
21-
import Foreign.Ptr (castPtr, Ptr)
22-
import Foreign.Marshal.Utils (copyBytes)
16+
, HNix.HashAlgorithm(..)
17+
, HNix.HasDigest(..)
18+
, HNix.hash
19+
, HNix.hashLazy
2320

24-
data HashAlgorithm = TruncatedSHA256 | MD5
21+
, HNix.printAsBase32
22+
) where
2523

26-
newtype Digest (algo :: HashAlgorithm) = Digest { getDigestBytes :: BS.ByteString }
27-
deriving (Eq, Ord, Show)
24+
import qualified System.Nix.Internal.Hash as HNix
2825

29-
instance Hashable (Digest algo) where
30-
hashWithSalt s (Digest bytes) = hashWithSalt s bytes
Lines changed: 166 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,166 @@
1+
{-|
2+
Description : Cryptographic hashes for hnix-store.
3+
Maintainer : Greg Hale <[email protected]>
4+
-}
5+
{-# LANGUAGE AllowAmbiguousTypes #-}
6+
{-# LANGUAGE DataKinds #-}
7+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
8+
{-# LANGUAGE PolyKinds #-}
9+
{-# LANGUAGE RankNTypes #-}
10+
{-# LANGUAGE TypeFamilies #-}
11+
{-# LANGUAGE KindSignatures #-}
12+
{-# LANGUAGE ScopedTypeVariables #-}
13+
{-# LANGUAGE TypeApplications #-}
14+
15+
module System.Nix.Internal.Hash where
16+
17+
import qualified Crypto.Hash.MD5 as MD5
18+
import qualified Crypto.Hash.SHA1 as SHA1
19+
import qualified Crypto.Hash.SHA256 as SHA256
20+
import qualified Data.ByteString as BS
21+
import qualified Data.ByteString.Char8 as BSC
22+
import Data.Bits (xor)
23+
import qualified Data.ByteString as BS
24+
import qualified Data.ByteString.Lazy as BSL
25+
import qualified Data.Hashable as DataHashable
26+
import Data.List (foldl')
27+
import Data.Proxy (Proxy(Proxy))
28+
import qualified Data.Text as T
29+
import qualified Data.Text.Encoding as T
30+
import qualified Data.Vector as V
31+
import Data.Word (Word8)
32+
import GHC.TypeLits
33+
34+
-- | A tag for different hashing algorithms
35+
-- Also used as a type-level tag for hash digests
36+
-- (e.g. @Digest SHA256@ is the type for a sha256 hash)
37+
data HashAlgorithm
38+
= MD5
39+
| SHA1
40+
| SHA256
41+
| Truncated Nat HashAlgorithm
42+
43+
44+
-- | Types with kind @HashAlgorithm@ may be a @HasDigest@ instance
45+
-- if they are able to hash bytestrings via the init/update/finalize
46+
-- API of cryptonite
47+
--
48+
-- Each instance defined here simply defers to one of the underlying
49+
-- monomorphic hashing libraries, such as `cryptohash-sha256`.
50+
class HasDigest (a :: HashAlgorithm) where
51+
52+
type AlgoCtx a :: *
53+
54+
initialize :: AlgoCtx a
55+
update :: AlgoCtx a -> BS.ByteString -> AlgoCtx a
56+
finalize :: AlgoCtx a -> Digest a
57+
58+
59+
-- | The cryptographic hash of of a strict bytestring, where hash
60+
-- algorithm is chosen by the type of the digest
61+
-- For example:
62+
-- > let d = hash "Hello, sha-256!" :: Digest SHA256
63+
-- or
64+
-- > :set -XTypeApplications
65+
-- > let d = hash @SHA256 "Hello, sha-256!"
66+
hash :: forall a.HasDigest a => BS.ByteString -> Digest a
67+
hash bs =
68+
finalize $ update @a (initialize @a) bs
69+
70+
-- | The cryptographic hash of a lazy bytestring. Use is the same
71+
-- as for @hash@. This runs in constant space, but forces the
72+
-- entire bytestring
73+
hashLazy :: forall a.HasDigest a => BSL.ByteString -> Digest a
74+
hashLazy bsl =
75+
finalize $ foldl' (update @a) (initialize @a) (BSL.toChunks bsl)
76+
77+
78+
79+
80+
-- | Convert any Digest to a base32-encoded string.
81+
-- This is not used in producing store path hashes
82+
printAsBase32 :: Digest a -> T.Text
83+
printAsBase32 (Digest bs) = printHashBytes32 bs
84+
85+
86+
instance HasDigest MD5 where
87+
type AlgoCtx 'MD5 = MD5.Ctx
88+
initialize = MD5.init
89+
update = MD5.update
90+
finalize = Digest . MD5.finalize
91+
92+
instance HasDigest 'SHA1 where
93+
type AlgoCtx SHA1 = SHA1.Ctx
94+
initialize = SHA1.init
95+
update = SHA1.update
96+
finalize = Digest . SHA1.finalize
97+
98+
instance HasDigest 'SHA256 where
99+
type AlgoCtx SHA256 = SHA256.Ctx
100+
initialize = SHA256.init
101+
update = SHA256.update
102+
finalize = Digest . SHA256.finalize
103+
104+
instance (HasDigest a, KnownNat n) => HasDigest (Truncated n a) where
105+
type AlgoCtx (Truncated n a) = AlgoCtx a
106+
initialize = initialize @a
107+
update = update @a
108+
finalize = truncateDigest @n . finalize @a
109+
110+
-- | A raw hash digest, with a type-level tag
111+
newtype Digest (a :: HashAlgorithm) = Digest
112+
{ digestBytes :: BS.ByteString
113+
-- ^ The bytestring in a Digest is an opaque string of bytes,
114+
-- not some particular text encoding.
115+
} deriving (Show, Eq, Ord, DataHashable.Hashable)
116+
117+
118+
-- instance DataHashable.Hashable (Digest a) where
119+
-- hashWithSalt a (Digest bs) = DataHashable.hashWithSalt a bs
120+
-- hashWithSalt = coerce . DataHash
121+
122+
123+
-- | Internal function for encoding bytestrings into base32 according to
124+
-- nix's convention
125+
printHashBytes32 :: BS.ByteString -> T.Text
126+
printHashBytes32 c = T.pack $ concatMap char32 [nChar - 1, nChar - 2 .. 0]
127+
where
128+
-- The base32 encoding is 8/5's as long as the base256 digest
129+
nChar = fromIntegral $ BS.length c * 8 `div` 5
130+
131+
char32 :: Integer -> [Char]
132+
char32 i = [digits32 V.! digitInd]
133+
where
134+
byte j = BS.index c (fromIntegral j)
135+
digitInd = fromIntegral $
136+
sum [fromIntegral (byte j) * (256^j)
137+
| j <- [0 .. BS.length c - 1]]
138+
`div` (32^i)
139+
`mod` 32
140+
141+
142+
-- | Internal function for producing the bitwise truncation of bytestrings.
143+
-- When truncation length is greater than the length of the bytestring,
144+
-- but less than twice the bytestring length, truncation splits the
145+
-- bytestring into a head part (truncation length) and tail part (leftover
146+
-- part) right-pads the leftovers with 0 to the truncation length, and
147+
-- combines the two strings bytewise with `xor`
148+
truncateDigest :: forall n a.(HasDigest a, KnownNat n) => Digest a -> Digest (Truncated n a)
149+
truncateDigest (Digest c) = Digest $ BS.pack $ map truncOutputByte [0.. n-1]
150+
where
151+
152+
n = fromIntegral $ natVal (Proxy @n)
153+
154+
truncOutputByte :: Int -> Word8
155+
truncOutputByte i = foldl' (aux i) 0 [0 .. BS.length c - 1]
156+
157+
inputByte :: Int -> Word8
158+
inputByte j = BS.index c (fromIntegral j)
159+
160+
aux :: Int -> Word8 -> Int -> Word8
161+
aux i x j = if j `mod` fromIntegral n == fromIntegral i
162+
then xor x (inputByte $ fromIntegral j)
163+
else x
164+
165+
digits32 :: V.Vector Char
166+
digits32 = V.fromList "0123456789abcdfghijklmnpqrsvwxyz"

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

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module System.Nix.Path
1818
) where
1919

2020
import System.Nix.Hash (Digest(..),
21-
HashAlgorithm(TruncatedSHA256))
21+
HashAlgorithm(Truncated, SHA256))
2222
import qualified Data.ByteString as BS
2323
import qualified Data.ByteString.Char8 as BSC
2424
import Data.Hashable (Hashable (..), hashPtrWithSalt)
@@ -32,7 +32,8 @@ import Text.Regex.Base.RegexLike (makeRegex, matchTest)
3232
import Text.Regex.TDFA.Text (Regex)
3333

3434
-- | The hash algorithm used for store path hashes.
35-
type PathHashAlgo = TruncatedSHA256
35+
type PathHashAlgo = Truncated 20 SHA256
36+
3637

3738
-- | The name portion of a Nix path.
3839
--

hnix-store-core/tests/Hash.hs

Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,45 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE ScopedTypeVariables #-}
4+
{-# LANGUAGE TypeApplications #-}
5+
6+
module Hash where
7+
8+
import Control.Monad.IO.Class (liftIO)
9+
import Control.Exception (bracket)
10+
import qualified Data.ByteString as BS
11+
import qualified Data.ByteString.Base64.Lazy as B64
12+
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
20+
import Test.Tasty.Hspec
21+
import qualified Test.Tasty.HUnit as HU
22+
import Test.Tasty.QuickCheck
23+
import Text.Read (readMaybe)
24+
25+
import System.Nix.Hash
26+
import System.Nix.Path
27+
import NarFormat -- TODO: Move the fixtures into a common module
28+
29+
spec_hash :: Spec
30+
spec_hash = do
31+
32+
describe "hashing parity with nix-store" $ do
33+
34+
it "produces (base32 . sha1) of \"Hello World\" the same as the thesis" $
35+
shouldBe (printAsBase32 (hash @SHA1 "Hello World"))
36+
"s23c9fs0v32pf6bhmcph5rbqsyl5ak8a"
37+
38+
-- The example in question:
39+
-- https://nixos.org/nixos/nix-pills/nix-store-paths.html
40+
it "produces same base32 as nix pill flat file example" $ do
41+
let exampleStr =
42+
"source:sha256:2bfef67de873c54551d884fdab3055d84d573e654efa79db3"
43+
<> "c0d7b98883f9ee3:/nix/store:myfile"
44+
shouldBe (printAsBase32 @PathHashAlgo (hash exampleStr))
45+
"xv2iccirbrvklck36f1g7vldn5v58vck"

0 commit comments

Comments
 (0)