Skip to content

Commit 9804fd1

Browse files
committed
treewide: migrate crypto(hash-* -> nite)
Reference: Main cause: haskell-hvr/cryptohash-sha512#7 The whole `cryptohash-*` package family is abandoned, there is no signs of maintainer activity there, so it stopped following Haskell ecosystem & `base` releases. Knowing the human history & situation around it - it would not be reviwed, which gives experience to not hardcode on the (specifically when emotional) dependency. Experience I drawn from this story is to keep things simplier when possible & have more flexible systems as a result code. It was "a bit too much" for what hashing is, for the code to have 2 hashing type systems (external & internal) & reinventment of `HashAlgorithm` type duplicate. The whole code was really rigid with a lot of type applicating the data kinds, those are dependent type features & should be used cautiously, since interface became rigid to changes, so afterwards it is easier & effective to dismantle and recreate the subsystem then to evolve it. Previous hashing history: #156 #142 #93 #92 #90 #83 #64 #38 #32 #31 #28 #27 #25 #18 #14
1 parent dd32819 commit 9804fd1

File tree

7 files changed

+78
-144
lines changed

7 files changed

+78
-144
lines changed

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

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -56,10 +56,9 @@ library
5656
, bytestring
5757
, cereal
5858
, containers
59-
, cryptohash-md5
60-
, cryptohash-sha1
61-
, cryptohash-sha256
62-
, cryptohash-sha512
59+
-- Required for cryptonite low-level type convertion
60+
, memory
61+
, cryptonite
6362
, directory
6463
, filepath
6564
, hashable
@@ -106,6 +105,7 @@ test-suite format-tests
106105
, binary
107106
, bytestring
108107
, containers
108+
, cryptonite
109109
, directory
110110
, filepath
111111
, process

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

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -2,16 +2,10 @@
22
Description : Cryptographic hashes for hnix-store.
33
-}
44
module System.Nix.Hash
5-
( Hash.Digest
6-
7-
, Hash.HashAlgorithm(..)
8-
, Hash.mkStorePathHash
9-
, Hash.ValidAlgo(..)
5+
( Hash.mkStorePathHash
106
, Hash.NamedAlgo(..)
117
, Hash.SomeNamedDigest(..)
128

13-
, Hash.hash
14-
, Hash.hashLazy
159
, Hash.mkNamedDigest
1610

1711
, Base.BaseEncoding(..)

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

Lines changed: 36 additions & 118 deletions
Original file line numberDiff line numberDiff line change
@@ -13,12 +13,7 @@ Description : Cryptographic hashing interface for hnix-store, on top
1313
{-# LANGUAGE CPP #-}
1414

1515
module System.Nix.Internal.Hash
16-
( HashAlgorithm(..)
17-
, ValidAlgo(..)
18-
, NamedAlgo(..)
19-
, hash
20-
, hashLazy
21-
, Digest
16+
( NamedAlgo(..)
2217
, SomeNamedDigest(..)
2318
, mkNamedDigest
2419
, encodeDigestWith
@@ -27,163 +22,86 @@ module System.Nix.Internal.Hash
2722
)
2823
where
2924

30-
import qualified Crypto.Hash.MD5 as MD5
31-
import qualified Crypto.Hash.SHA1 as SHA1
32-
import qualified Crypto.Hash.SHA256 as SHA256
33-
import qualified Crypto.Hash.SHA512 as SHA512
25+
import qualified Crypto.Hash as C
3426
import qualified Data.ByteString as BS
35-
import qualified Data.ByteString.Lazy as BSL
36-
import qualified Data.Hashable as DataHashable
37-
import Data.List (foldl')
3827
import Data.Text (Text)
3928
import qualified Data.Text as T
4029
import System.Nix.Internal.Base
41-
import Data.Coerce (coerce)
30+
import Data.ByteArray
4231
import System.Nix.Internal.Truncation
4332

44-
-- | The universe of supported hash algorithms.
45-
--
46-
-- Currently only intended for use at the type level.
47-
data HashAlgorithm
48-
= MD5
49-
| SHA1
50-
| SHA256
51-
| SHA512
52-
53-
-- | The result of running a 'HashAlgorithm'.
54-
newtype Digest (a :: HashAlgorithm) =
55-
Digest BS.ByteString deriving (Eq, Ord, DataHashable.Hashable)
56-
57-
instance Show (Digest a) where
58-
show = ("Digest " <>) . show . encodeDigestWith NixBase32
59-
60-
-- | The primitive interface for incremental hashing for a given
61-
-- 'HashAlgorithm'. Every 'HashAlgorithm' should have an instance.
62-
class ValidAlgo (a :: HashAlgorithm) where
63-
-- | The incremental state for constructing a hash.
64-
type AlgoCtx a
65-
66-
-- | Start building a new hash.
67-
initialize :: AlgoCtx a
68-
-- | Append a 'BS.ByteString' to the overall contents to be hashed.
69-
update :: AlgoCtx a -> BS.ByteString -> AlgoCtx a
70-
-- | Finish hashing and generate the output.
71-
finalize :: AlgoCtx a -> Digest a
72-
7333
-- | A 'HashAlgorithm' with a canonical name, for serialization
7434
-- purposes (e.g. SRI hashes)
75-
class ValidAlgo a => NamedAlgo (a :: HashAlgorithm) where
35+
class C.HashAlgorithm a => NamedAlgo a where
7636
algoName :: Text
77-
hashSize :: Int
7837

79-
instance NamedAlgo 'MD5 where
38+
instance NamedAlgo C.MD5 where
8039
algoName = "md5"
81-
hashSize = 16
8240

83-
instance NamedAlgo 'SHA1 where
41+
instance NamedAlgo C.SHA1 where
8442
algoName = "sha1"
85-
hashSize = 20
8643

87-
instance NamedAlgo 'SHA256 where
44+
instance NamedAlgo C.SHA256 where
8845
algoName = "sha256"
89-
hashSize = 32
9046

91-
instance NamedAlgo 'SHA512 where
47+
instance NamedAlgo C.SHA512 where
9248
algoName = "sha512"
93-
hashSize = 64
9449

9550
-- | A digest whose 'NamedAlgo' is not known at compile time.
96-
data SomeNamedDigest = forall a . NamedAlgo a => SomeDigest (Digest a)
51+
data SomeNamedDigest = forall a . NamedAlgo a => SomeDigest (C.Digest a)
9752

9853
instance Show SomeNamedDigest where
9954
show sd = case sd of
100-
SomeDigest (digest :: Digest hashType) -> T.unpack $ "SomeDigest " <> algoName @hashType <> ":" <> encodeDigestWith NixBase32 digest
55+
SomeDigest (digest :: C.Digest hashType) -> T.unpack $ "SomeDigest " <> algoName @hashType <> ":" <> encodeDigestWith NixBase32 digest
10156

10257
mkNamedDigest :: Text -> Text -> Either String SomeNamedDigest
10358
mkNamedDigest name sriHash =
10459
let (sriName, h) = T.breakOnEnd "-" sriHash in
105-
if sriName == "" || sriName == (name <> "-")
60+
if sriName == "" || sriName == name <> "-"
10661
then mkDigest h
10762
else Left $ T.unpack $ "Sri hash method " <> sriName <> " does not match the required hash type " <> name
10863
where
10964
mkDigest h = case name of
110-
"md5" -> SomeDigest <$> decodeGo @'MD5 h
111-
"sha1" -> SomeDigest <$> decodeGo @'SHA1 h
112-
"sha256" -> SomeDigest <$> decodeGo @'SHA256 h
113-
"sha512" -> SomeDigest <$> decodeGo @'SHA512 h
65+
"md5" -> SomeDigest <$> decodeGo C.MD5 h
66+
"sha1" -> SomeDigest <$> decodeGo C.SHA1 h
67+
"sha256" -> SomeDigest <$> decodeGo C.SHA256 h
68+
"sha512" -> SomeDigest <$> decodeGo C.SHA512 h
11469
_ -> Left $ "Unknown hash name: " <> T.unpack name
115-
decodeGo :: forall a . (NamedAlgo a, ValidAlgo a) => Text -> Either String (Digest a)
116-
decodeGo h
70+
decodeGo :: forall a . NamedAlgo a => a -> Text -> Either String (C.Digest a)
71+
decodeGo a h
11772
| size == base16Len = decodeDigestWith Base16 h
11873
| size == base32Len = decodeDigestWith NixBase32 h
11974
| size == base64Len = decodeDigestWith Base64 h
12075
| otherwise = Left $ T.unpack sriHash <> " is not a valid " <> T.unpack name <> " hash. Its length (" <> show size <> ") does not match any of " <> show [base16Len, base32Len, base64Len]
12176
where
12277
size = T.length h
123-
hsize = hashSize @a
78+
hsize = C.hashDigestSize a
12479
base16Len = hsize * 2
12580
base32Len = ((hsize * 8 - 1) `div` 5) + 1;
12681
base64Len = ((4 * hsize `div` 3) + 3) `div` 4 * 4;
12782

12883

129-
-- | Hash an entire (strict) 'BS.ByteString' as a single call.
130-
--
131-
-- For example:
132-
-- > let d = hash "Hello, sha-256!" :: Digest SHA256
133-
-- or
134-
-- > :set -XTypeApplications
135-
-- > let d = hash @SHA256 "Hello, sha-256!"
136-
hash :: forall a . ValidAlgo a => BS.ByteString -> Digest a
137-
hash bs =
138-
finalize $ update @a (initialize @a) bs
139-
140-
mkStorePathHash :: forall a . ValidAlgo a => BS.ByteString -> BS.ByteString
84+
mkStorePathHash :: forall a . C.HashAlgorithm a => BS.ByteString -> BS.ByteString
14185
mkStorePathHash bs =
142-
truncateInNixWay 20 $ coerce $ hash @a bs
143-
144-
-- | Hash an entire (lazy) 'BSL.ByteString' as a single call.
145-
--
146-
-- Use is the same as for 'hash'. This runs in constant space, but
147-
-- forces the entire bytestring.
148-
hashLazy :: forall a . ValidAlgo a => BSL.ByteString -> Digest a
149-
hashLazy bsl =
150-
finalize $ foldl' (update @a) (initialize @a) (BSL.toChunks bsl)
151-
86+
truncateInNixWay 20 $ convert $ C.hash @BS.ByteString @a bs
15287

15388
-- | Take BaseEncoding type of the output -> take the Digeest as input -> encode Digest
154-
encodeDigestWith :: BaseEncoding -> Digest a -> T.Text
155-
encodeDigestWith b = encodeWith b . coerce
89+
encodeDigestWith :: BaseEncoding -> C.Digest a -> T.Text
90+
encodeDigestWith b = encodeWith b . convert
15691

15792

15893
-- | Take BaseEncoding type of the input -> take the input itself -> decodeBase into Digest
159-
decodeDigestWith :: BaseEncoding -> T.Text -> Either String (Digest a)
160-
decodeDigestWith b x = Digest <$> decodeWith b x
161-
162-
163-
-- | Uses "Crypto.Hash.MD5" from cryptohash-md5.
164-
instance ValidAlgo 'MD5 where
165-
type AlgoCtx 'MD5 = MD5.Ctx
166-
initialize = MD5.init
167-
update = MD5.update
168-
finalize = Digest . MD5.finalize
169-
170-
-- | Uses "Crypto.Hash.SHA1" from cryptohash-sha1.
171-
instance ValidAlgo 'SHA1 where
172-
type AlgoCtx 'SHA1 = SHA1.Ctx
173-
initialize = SHA1.init
174-
update = SHA1.update
175-
finalize = Digest . SHA1.finalize
176-
177-
-- | Uses "Crypto.Hash.SHA256" from cryptohash-sha256.
178-
instance ValidAlgo 'SHA256 where
179-
type AlgoCtx 'SHA256 = SHA256.Ctx
180-
initialize = SHA256.init
181-
update = SHA256.update
182-
finalize = Digest . SHA256.finalize
183-
184-
-- | Uses "Crypto.Hash.SHA512" from cryptohash-sha512.
185-
instance ValidAlgo 'SHA512 where
186-
type AlgoCtx 'SHA512 = SHA512.Ctx
187-
initialize = SHA512.init
188-
update = SHA512.update
189-
finalize = Digest . SHA512.finalize
94+
decodeDigestWith :: C.HashAlgorithm a => BaseEncoding -> T.Text -> Either String (C.Digest a)
95+
decodeDigestWith b x =
96+
do
97+
bs <- decodeWith b x
98+
let
99+
toEither =
100+
maybeToRight
101+
("Cryptonite was not able to convert '(ByteString -> Digest a)' for: '" <> show bs <>"'.")
102+
(toEither . C.digestFromByteString) bs
103+
where
104+
-- To not depend on @extra@
105+
maybeToRight :: b -> Maybe a -> Either b a
106+
maybeToRight _ (Just r) = pure r
107+
maybeToRight y Nothing = Left y

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

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,9 @@ import qualified System.FilePath as FilePath
5151
import Data.Hashable ( Hashable(..) )
5252
import Data.HashSet ( HashSet )
5353
import Data.Coerce ( coerce )
54+
import Crypto.Hash ( SHA256
55+
, Digest
56+
)
5457

5558
-- | A path in a Nix store.
5659
--
@@ -96,7 +99,7 @@ newtype StorePathHashPart = StorePathHashPart ByteString
9699
deriving (Eq, Hashable, Ord, Show)
97100

98101
mkStorePathHashPart :: ByteString -> StorePathHashPart
99-
mkStorePathHashPart = coerce . mkStorePathHash @'SHA256
102+
mkStorePathHashPart = coerce . mkStorePathHash @SHA256
100103

101104
-- | A set of 'StorePath's.
102105
type StorePathSet = HashSet StorePath
@@ -114,7 +117,7 @@ data ContentAddressableAddress
114117
= -- | The path is a plain file added via makeTextPath or
115118
-- addTextToStore. It is addressed according to a sha256sum of the
116119
-- file contents.
117-
Text !(Digest 'SHA256)
120+
Text !(Digest SHA256)
118121
| -- | The path was added to the store via makeFixedOutputPath or
119122
-- addToStore. It is addressed according to some hash algorithm
120123
-- applied to the nar serialization via some 'NarHashMode'.
@@ -134,7 +137,7 @@ data NarHashMode
134137
makeStorePathName :: Text -> Either String StorePathName
135138
makeStorePathName n =
136139
if validStorePathName n
137-
then Right $ StorePathName n
140+
then pure $ StorePathName n
138141
else Left $ reasonInvalid n
139142

140143
reasonInvalid :: Text -> String

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

Lines changed: 17 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,15 @@ import System.Nix.Nar
1717
import System.Nix.StorePath
1818
import Control.Monad.State.Strict
1919
import Data.Coerce ( coerce )
20+
import Crypto.Hash ( Context
21+
, Digest
22+
, hash
23+
, hashlazy
24+
, hashInit
25+
, hashUpdate
26+
, hashFinalize
27+
, SHA256
28+
)
2029

2130

2231
makeStorePath
@@ -41,7 +50,7 @@ makeStorePath fp ty h nm = StorePath (coerce storeHash) nm fp
4150
]
4251

4352
makeTextPath
44-
:: FilePath -> StorePathName -> Digest 'SHA256 -> StorePathSet -> StorePath
53+
:: FilePath -> StorePathName -> Digest SHA256 -> StorePathSet -> StorePath
4554
makeTextPath fp nm h refs = makeStorePath fp ty h nm
4655
where
4756
ty =
@@ -61,7 +70,7 @@ makeFixedOutputPath fp recursive h =
6170
else makeStorePath fp "output:out" h'
6271
where
6372
h' =
64-
hash @'SHA256
73+
hash @ByteString @SHA256
6574
$ "fixed:out:"
6675
<> encodeUtf8 (algoName @hashAlgo)
6776
<> (if recursive then ":r:" else ":")
@@ -83,10 +92,10 @@ computeStorePathForPath name pth recursive _pathFilter _repair = do
8392
selectedHash <- if recursive then recursiveContentHash else flatContentHash
8493
pure $ makeFixedOutputPath "/nix/store" recursive selectedHash name
8594
where
86-
recursiveContentHash :: IO (Digest 'SHA256)
87-
recursiveContentHash = finalize <$> execStateT streamNarUpdate (initialize @'SHA256)
88-
streamNarUpdate :: StateT (AlgoCtx 'SHA256) IO ()
89-
streamNarUpdate = streamNarIO (modify . flip (update @'SHA256)) narEffectsIO pth
95+
recursiveContentHash :: IO (Digest SHA256)
96+
recursiveContentHash = hashFinalize <$> execStateT streamNarUpdate (hashInit @SHA256)
97+
streamNarUpdate :: StateT (Context SHA256) IO ()
98+
streamNarUpdate = streamNarIO (modify . flip (hashUpdate @ByteString @SHA256)) narEffectsIO pth
9099

91-
flatContentHash :: IO (Digest 'SHA256)
92-
flatContentHash = hashLazy <$> narReadFile narEffectsIO pth
100+
flatContentHash :: IO (Digest SHA256)
101+
flatContentHash = hashlazy <$> narReadFile narEffectsIO pth

hnix-store-core/tests/Arbitrary.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,10 @@ import System.Nix.Internal.Hash
1515
import System.Nix.Internal.StorePath
1616
import Control.Applicative ( liftA3 )
1717
import Data.Coerce ( coerce )
18+
import Crypto.Hash ( SHA256
19+
, Digest
20+
, hash
21+
)
1822

1923
genSafeChar :: Gen Char
2024
genSafeChar = choose ('\1', '\127') -- ASCII without \NUL
@@ -35,7 +39,7 @@ instance Arbitrary StorePathName where
3539
instance Arbitrary StorePathHashPart where
3640
arbitrary = mkStorePathHashPart . BSC.pack <$> arbitrary
3741

38-
instance Arbitrary (Digest 'SHA256) where
42+
instance Arbitrary (Digest SHA256) where
3943
arbitrary = hash . BSC.pack <$> arbitrary
4044

4145
newtype NixLike = NixLike {getNixLike :: StorePath}

hnix-store-core/tests/Hash.hs

Lines changed: 9 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
module Hash where
88

99
import Control.Monad ( forM_ )
10+
import Data.ByteString ( ByteString )
1011
import qualified Data.ByteString.Char8 as BSC
1112
import qualified Data.ByteString.Base16 as B16
1213
import qualified System.Nix.Base32 as B32
@@ -21,20 +22,25 @@ import System.Nix.StorePath
2122
import Arbitrary
2223
import System.Nix.Internal.Base
2324
import Data.Coerce ( coerce )
25+
import Crypto.Hash ( MD5
26+
, SHA1
27+
, SHA256
28+
, hash
29+
)
2430

2531
spec_hash :: Spec
2632
spec_hash = do
2733

2834
describe "hashing parity with nix-store" $ do
2935

3036
it "produces (base32 . sha256) of \"nix-output:foo\" the same as Nix does at the moment for placeholder \"foo\"" $
31-
shouldBe (encodeDigestWith NixBase32 (hash @'SHA256 "nix-output:foo"))
37+
shouldBe (encodeDigestWith NixBase32 (hash @ByteString @SHA256 "nix-output:foo"))
3238
"1x0ymrsy7yr7i9wdsqy9khmzc1yy7nvxw6rdp72yzn50285s67j5"
3339
it "produces (base16 . md5) of \"Hello World\" the same as the thesis" $
34-
shouldBe (encodeDigestWith Base16 (hash @'MD5 "Hello World"))
40+
shouldBe (encodeDigestWith Base16 (hash @ByteString @MD5 "Hello World"))
3541
"b10a8db164e0754105b7a99be72e3fe5"
3642
it "produces (base32 . sha1) of \"Hello World\" the same as the thesis" $
37-
shouldBe (encodeDigestWith NixBase32 (hash @'SHA1 "Hello World"))
43+
shouldBe (encodeDigestWith NixBase32 (hash @ByteString @SHA1 "Hello World"))
3844
"s23c9fs0v32pf6bhmcph5rbqsyl5ak8a"
3945

4046
-- The example in question:

0 commit comments

Comments
 (0)