Skip to content

Commit 0f0b7fc

Browse files
committed
Core: Internal.Hash: take-out Truncated from HashAlgorythm & treewide change
M hnix-store-core/src/System/Nix/Hash.hs M hnix-store-core/src/System/Nix/Internal/Hash.hs M hnix-store-core/src/System/Nix/Internal/StorePath.hs M hnix-store-core/src/System/Nix/ReadonlyStore.hs M hnix-store-core/src/System/Nix/StorePath.hs M hnix-store-core/tests/Arbitrary.hs M hnix-store-core/tests/Hash.hs
1 parent e75957f commit 0f0b7fc

File tree

7 files changed

+65
-76
lines changed

7 files changed

+65
-76
lines changed

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module System.Nix.Hash
55
( Hash.Digest
66

77
, Hash.HashAlgorithm(..)
8+
, Hash.mkStorePathHash
89
, Hash.ValidAlgo(..)
910
, Hash.NamedAlgo(..)
1011
, Hash.SomeNamedDigest(..)

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

Lines changed: 7 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -22,18 +22,16 @@ import qualified Data.ByteString as BS
2222
import qualified Data.ByteString.Lazy as BSL
2323
import qualified Data.Hashable as DataHashable
2424
import Data.List (foldl')
25-
import Data.Proxy (Proxy(Proxy))
2625
import Data.Text (Text)
2726
import qualified Data.Text as T
28-
import qualified GHC.TypeLits as Kind
29-
(Nat, KnownNat, natVal)
3027
import System.Nix.Internal.Base
3128
( BaseEncoding(Base16,NixBase32,Base64)
3229
, encodeWith
3330
, decodeWith
3431
)
3532
import Data.Coerce (coerce)
36-
import System.Nix.Internal.Truncation (truncateInNixWay)
33+
import System.Nix.Internal.Truncation
34+
(truncateInNixWay)
3735

3836
-- | The universe of supported hash algorithms.
3937
--
@@ -43,10 +41,6 @@ data HashAlgorithm
4341
| SHA1
4442
| SHA256
4543
| SHA512
46-
| Truncated Kind.Nat HashAlgorithm
47-
-- ^ The hash algorithm obtained by truncating the result of the
48-
-- input 'HashAlgorithm' to the given number of bytes. See
49-
-- 'truncateDigest' for a description of the truncation algorithm.
5044

5145
-- | The result of running a 'HashAlgorithm'.
5246
newtype Digest (a :: HashAlgorithm) =
@@ -131,10 +125,14 @@ mkNamedDigest name sriHash =
131125
-- or
132126
-- > :set -XTypeApplications
133127
-- > let d = hash @SHA256 "Hello, sha-256!"
134-
hash :: forall a.ValidAlgo a => BS.ByteString -> Digest a
128+
hash :: forall a . ValidAlgo a => BS.ByteString -> Digest a
135129
hash bs =
136130
finalize $ update @a (initialize @a) bs
137131

132+
mkStorePathHash :: forall a . ValidAlgo a => BS.ByteString -> BS.ByteString
133+
mkStorePathHash bs =
134+
truncateInNixWay 20 $ coerce $ hash @a bs
135+
138136
-- | Hash an entire (lazy) 'BSL.ByteString' as a single call.
139137
--
140138
-- Use is the same as for 'hash'. This runs in constant space, but
@@ -181,26 +179,3 @@ instance ValidAlgo 'SHA512 where
181179
initialize = SHA512.init
182180
update = SHA512.update
183181
finalize = Digest . SHA512.finalize
184-
185-
-- | Reuses the underlying 'ValidAlgo' instance, but does a
186-
-- 'truncateDigest' at the end.
187-
instance (ValidAlgo a, Kind.KnownNat n) => ValidAlgo ('Truncated n a) where
188-
type AlgoCtx ('Truncated n a) = AlgoCtx a
189-
initialize = initialize @a
190-
update = update @a
191-
finalize = truncateDigestInNixWay @n . finalize @a
192-
193-
-- | Bytewise truncation of a 'Digest'.
194-
--
195-
-- When truncation length is greater than the length of the bytestring
196-
-- but less than twice the bytestring length, truncation splits the
197-
-- bytestring into a head part (truncation length) and tail part
198-
-- (leftover part), right-pads the leftovers with 0 to the truncation
199-
-- length, and combines the two strings bytewise with 'xor'.
200-
truncateDigestInNixWay
201-
:: forall n a .(Kind.KnownNat n) => Digest a -> Digest ('Truncated n a)
202-
-- 2021-06-07: NOTE: ^ This is why all the cookery with DataKinds, trunkation length (if allowed arbitrary) needs to be represented in type.
203-
truncateDigestInNixWay (Digest c) =
204-
Digest $ truncateInNixWay n c
205-
where
206-
n = fromIntegral $ Kind.natVal $ Proxy @n

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

Lines changed: 21 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE TypeApplications #-}
12
{-|
23
Description : Representation of Nix store paths.
34
-}
@@ -10,15 +11,10 @@ Description : Representation of Nix store paths.
1011
{-# LANGUAGE TypeInType #-} -- Needed for GHC 8.4.4 for some reason
1112

1213
module System.Nix.Internal.StorePath where
13-
import System.Nix.Hash ( HashAlgorithm
14-
( Truncated
15-
, SHA256
16-
)
14+
import System.Nix.Internal.Hash ( HashAlgorithm(SHA256)
1715
, Digest
18-
, BaseEncoding(..)
19-
, encodeDigestWith
20-
, decodeDigestWith
2116
, SomeNamedDigest
17+
, mkStorePathHash
2218
)
2319

2420

@@ -39,6 +35,11 @@ import qualified Data.Attoparsec.Text.Lazy as Parser.Text.Lazy
3935
import qualified System.FilePath as FilePath
4036
import Data.Hashable ( Hashable(..) )
4137
import Data.HashSet ( HashSet )
38+
import System.Nix.Internal.Base ( BaseEncoding(..)
39+
, encodeWith
40+
, decodeWith
41+
)
42+
import Data.Coerce ( coerce )
4243

4344
-- | A path in a Nix store.
4445
--
@@ -52,7 +53,7 @@ import Data.HashSet ( HashSet )
5253
data StorePath = StorePath
5354
{ -- | The 160-bit hash digest reflecting the "address" of the name.
5455
-- Currently, this is a truncated SHA256 hash.
55-
storePathHash :: !(Digest StorePathHashAlgo)
56+
storePathHash :: !StorePathHashPart
5657
, -- | The (typically human readable) name of the path. For packages
5758
-- this is typically the package name and version (e.g.
5859
-- hello-1.2.3).
@@ -80,7 +81,11 @@ newtype StorePathName = StorePathName
8081
} deriving (Eq, Hashable, Ord)
8182

8283
-- | The hash algorithm used for store path hashes.
83-
type StorePathHashAlgo = 'Truncated 20 'SHA256
84+
newtype StorePathHashPart = StorePathHashPart ByteString
85+
deriving (Eq, Hashable, Ord, Show)
86+
87+
mkStorePathHashPart :: ByteString -> StorePathHashPart
88+
mkStorePathHashPart = coerce . mkStorePathHash @'SHA256
8489

8590
-- | A set of 'StorePath's.
8691
type StorePathSet = HashSet StorePath
@@ -154,7 +159,7 @@ storePathToRawFilePath StorePath{..} =
154159
root <> "/" <> hashPart <> "-" <> name
155160
where
156161
root = Bytes.Char8.pack storePathRoot
157-
hashPart = Text.encodeUtf8 $ encodeDigestWith NixBase32 storePathHash
162+
hashPart = Text.encodeUtf8 $ encodeWith NixBase32 $ coerce storePathHash
158163
name = Text.encodeUtf8 $ unStorePathName storePathName
159164

160165
-- | Render a 'StorePath' as a 'FilePath'.
@@ -169,16 +174,16 @@ storePathToText = Text.pack . Bytes.Char8.unpack . storePathToRawFilePath
169174
-- can be used to query binary caches.
170175
storePathToNarInfo :: StorePath -> Bytes.Char8.ByteString
171176
storePathToNarInfo StorePath{..} =
172-
Text.encodeUtf8 $ encodeDigestWith NixBase32 storePathHash <> ".narinfo"
177+
Text.encodeUtf8 $ encodeWith NixBase32 (coerce storePathHash) <> ".narinfo"
173178

174179
-- | Parse `StorePath` from `Bytes.Char8.ByteString`, checking
175180
-- that store directory matches `expectedRoot`.
176181
parsePath :: FilePath -> Bytes.Char8.ByteString -> Either String StorePath
177182
parsePath expectedRoot x =
178183
let
179184
(rootDir, fname) = FilePath.splitFileName . Bytes.Char8.unpack $ x
180-
(digestPart, namePart) = Text.breakOn "-" $ Text.pack fname
181-
digest = decodeDigestWith NixBase32 digestPart
185+
(storeBasedHashPart, namePart) = Text.breakOn "-" $ Text.pack fname
186+
storeHash = decodeWith NixBase32 storeBasedHashPart
182187
name = makeStorePathName . Text.drop 1 $ namePart
183188
--rootDir' = dropTrailingPathSeparator rootDir
184189
-- cannot use ^^ as it drops multiple slashes /a/b/// -> /a/b
@@ -188,7 +193,7 @@ parsePath expectedRoot x =
188193
then Right rootDir'
189194
else Left $ "Root store dir mismatch, expected" <> expectedRoot <> "got" <> rootDir'
190195
in
191-
StorePath <$> digest <*> name <*> storeDir
196+
StorePath <$> coerce storeHash <*> name <*> storeDir
192197

193198
pathParser :: FilePath -> Parser StorePath
194199
pathParser expectedRoot = do
@@ -200,7 +205,7 @@ pathParser expectedRoot = do
200205
<?> "Expecting path separator"
201206

202207
digest <-
203-
decodeDigestWith NixBase32
208+
decodeWith NixBase32
204209
<$> Parser.Text.Lazy.takeWhile1 (`elem` Nix.Base32.digits32)
205210
<?> "Invalid Base32 part"
206211

@@ -219,4 +224,4 @@ pathParser expectedRoot = do
219224
either
220225
fail
221226
pure
222-
(StorePath <$> digest <*> name <*> pure expectedRoot)
227+
(StorePath <$> coerce digest <*> name <*> pure expectedRoot)

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

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -16,24 +16,25 @@ import System.Nix.Hash
1616
import System.Nix.Nar
1717
import System.Nix.StorePath
1818
import Control.Monad.State.Strict
19+
import Data.Coerce ( coerce )
1920

2021

2122
makeStorePath
22-
:: forall hashAlgo
23-
. (NamedAlgo hashAlgo)
23+
:: forall h
24+
. (NamedAlgo h)
2425
=> FilePath
2526
-> ByteString
26-
-> Digest hashAlgo
27+
-> Digest h
2728
-> StorePathName
2829
-> StorePath
29-
makeStorePath fp ty h nm = StorePath storeHash nm fp
30+
makeStorePath fp ty h nm = StorePath (coerce storeHash) nm fp
3031
where
31-
storeHash = hash s
32+
storeHash = mkStorePathHash @h s
3233

3334
s =
3435
BS.intercalate ":" $
3536
ty:fmap encodeUtf8
36-
[ algoName @hashAlgo
37+
[ algoName @h
3738
, encodeDigestWith Base16 h
3839
, T.pack fp
3940
, unStorePathName nm
@@ -44,7 +45,7 @@ makeTextPath
4445
makeTextPath fp nm h refs = makeStorePath fp ty h nm
4546
where
4647
ty =
47-
BS.intercalate ":" ("text" : sort (fmap storePathToRawFilePath (HS.toList refs)))
48+
BS.intercalate ":" $ "text" : sort (storePathToRawFilePath <$> HS.toList refs)
4849

4950
makeFixedOutputPath
5051
:: forall hashAlgo

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

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,8 @@ module System.Nix.StorePath
66
StorePath(..)
77
, StorePathName
88
, StorePathSet
9-
, StorePathHashAlgo
9+
, mkStorePathHashPart
10+
, StorePathHashPart(..)
1011
, ContentAddressableAddress(..)
1112
, NarHashMode(..)
1213
, -- * Manipulating 'StorePathName'

hnix-store-core/tests/Arbitrary.hs

Lines changed: 18 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE TypeApplications #-}
12
{-# LANGUAGE FlexibleInstances #-}
23
{-# LANGUAGE DataKinds #-}
34
{-# OPTIONS_GHC -Wno-orphans #-}
@@ -11,9 +12,10 @@ import qualified Data.Text as T
1112
import Test.Tasty.QuickCheck
1213

1314
import System.Nix.Hash
14-
import System.Nix.Internal.Hash
1515
import System.Nix.StorePath
1616
import System.Nix.Internal.StorePath
17+
import Control.Applicative ( liftA3 )
18+
import Data.Coerce ( coerce )
1719

1820
genSafeChar :: Gen Char
1921
genSafeChar = choose ('\1', '\127') -- ASCII without \NUL
@@ -22,7 +24,7 @@ nonEmptyString :: Gen String
2224
nonEmptyString = listOf1 genSafeChar
2325

2426
dir :: Gen String
25-
dir = ('/':) <$> (listOf1 $ elements $ '/':['a'..'z'])
27+
dir = ('/':) <$> listOf1 (elements $ '/':['a'..'z'])
2628

2729
instance Arbitrary StorePathName where
2830
arbitrary = StorePathName . T.pack <$> ((:) <$> s1 <*> listOf sn)
@@ -31,8 +33,8 @@ instance Arbitrary StorePathName where
3133
s1 = elements $ alphanum <> "+-_?="
3234
sn = elements $ alphanum <> "+-._?="
3335

34-
instance Arbitrary (Digest StorePathHashAlgo) where
35-
arbitrary = hash . BSC.pack <$> arbitrary
36+
instance Arbitrary StorePathHashPart where
37+
arbitrary = mkStorePathHashPart . BSC.pack <$> arbitrary
3638

3739
instance Arbitrary (Digest 'SHA256) where
3840
arbitrary = hash . BSC.pack <$> arbitrary
@@ -42,15 +44,19 @@ newtype NixLike = NixLike {getNixLike :: StorePath}
4244

4345
instance Arbitrary NixLike where
4446
arbitrary =
45-
NixLike
46-
<$> (StorePath
47-
<$> arbitraryTruncatedDigest
48-
<*> arbitrary
49-
<*> pure "/nix/store"
50-
)
47+
NixLike <$>
48+
(liftA3 StorePath
49+
arbitraryTruncatedDigest
50+
arbitrary
51+
(pure "/nix/store")
52+
)
5153
where
5254
-- 160-bit hash, 20 bytes, 32 chars in base32
53-
arbitraryTruncatedDigest = Digest . BSC.pack <$> replicateM 20 genSafeChar
55+
arbitraryTruncatedDigest = coerce . BSC.pack <$> replicateM 20 genSafeChar
5456

5557
instance Arbitrary StorePath where
56-
arbitrary = StorePath <$> arbitrary <*> arbitrary <*> dir
58+
arbitrary =
59+
liftA3 StorePath
60+
arbitrary
61+
arbitrary
62+
dir

hnix-store-core/tests/Hash.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -6,20 +6,23 @@
66

77
module Hash where
88

9-
import Control.Monad (forM_)
9+
import Control.Monad ( forM_ )
1010
import qualified Data.ByteString.Char8 as BSC
1111
import qualified Data.ByteString.Base16 as B16
1212
import qualified System.Nix.Base32 as B32
1313
import qualified Data.ByteString.Base64.Lazy as B64
1414
import qualified Data.ByteString.Lazy as BSL
15-
import Data.Text (Text)
1615

1716
import Test.Hspec
1817
import Test.Tasty.QuickCheck
1918

2019
import System.Nix.Hash
2120
import System.Nix.StorePath
2221
import Arbitrary
22+
import System.Nix.Internal.Base ( decodeWith
23+
, encodeWith
24+
)
25+
import Data.Coerce ( coerce )
2326

2427
spec_hash :: Spec
2528
spec_hash = do
@@ -42,20 +45,17 @@ spec_hash = do
4245
let exampleStr =
4346
"source:sha256:2bfef67de873c54551d884fdab3055d84d573e654efa79db3"
4447
<> "c0d7b98883f9ee3:/nix/store:myfile"
45-
shouldBe (encodeDigestWith32 @StorePathHashAlgo (hash exampleStr))
48+
shouldBe (encodeWith NixBase32 $ coerce $ mkStorePathHashPart exampleStr)
4649
"xv2iccirbrvklck36f1g7vldn5v58vck"
47-
where
48-
encodeDigestWith32 :: Digest a -> Text
49-
encodeDigestWith32 = encodeDigestWith NixBase32
5050

5151
-- | Test that Nix-like base32 encoding roundtrips
5252
prop_nixBase32Roundtrip :: Property
5353
prop_nixBase32Roundtrip = forAllShrink nonEmptyString genericShrink $
5454
\x -> pure (BSC.pack x) === (B32.decode . B32.encode . BSC.pack $ x)
5555

5656
-- | API variants
57-
prop_nixBase16Roundtrip :: Digest StorePathHashAlgo -> Property
58-
prop_nixBase16Roundtrip x = pure x === (decodeDigestWith Base16 . encodeDigestWith Base16 $ x)
57+
prop_nixBase16Roundtrip :: StorePathHashPart -> Property
58+
prop_nixBase16Roundtrip x = pure (coerce x) === decodeWith Base16 (encodeWith Base16 $ coerce x)
5959

6060
-- | Hash encoding conversion ground-truth.
6161
-- Similiar to nix/tests/hash.sh

0 commit comments

Comments
 (0)