Skip to content

Commit 474725b

Browse files
authored
Merge pull request #73 from layus/sha512
Sha512 and base64 support
2 parents 0adc9d5 + f0d0d12 commit 474725b

File tree

6 files changed

+121
-57
lines changed

6 files changed

+121
-57
lines changed

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

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,7 @@ library
3737
, attoparsec
3838
, algebraic-graphs >= 0.5 && < 0.6
3939
, base16-bytestring
40+
, base64-bytestring
4041
, bytestring
4142
, binary
4243
, bytestring
@@ -45,6 +46,7 @@ library
4546
, cryptohash-md5
4647
, cryptohash-sha1
4748
, cryptohash-sha256
49+
, cryptohash-sha512
4850
, directory
4951
, filepath
5052
, hashable

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module System.Nix.Hash (
1010
, HNix.SomeNamedDigest(..)
1111
, HNix.hash
1212
, HNix.hashLazy
13+
, HNix.mkNamedDigest
1314

1415
, HNix.encodeBase32
1516
, HNix.decodeBase32

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

Lines changed: 64 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,8 +16,10 @@ module System.Nix.Internal.Hash where
1616
import qualified Crypto.Hash.MD5 as MD5
1717
import qualified Crypto.Hash.SHA1 as SHA1
1818
import qualified Crypto.Hash.SHA256 as SHA256
19+
import qualified Crypto.Hash.SHA512 as SHA512
1920
import qualified Data.ByteString as BS
2021
import qualified Data.ByteString.Base16 as Base16
22+
import qualified Data.ByteString.Base64 as Base64
2123
import Data.Bits (xor)
2224
import qualified Data.ByteString.Lazy as BSL
2325
import qualified Data.Hashable as DataHashable
@@ -37,14 +39,18 @@ data HashAlgorithm
3739
= MD5
3840
| SHA1
3941
| SHA256
42+
| SHA512
4043
| Truncated Nat HashAlgorithm
4144
-- ^ The hash algorithm obtained by truncating the result of the
4245
-- input 'HashAlgorithm' to the given number of bytes. See
4346
-- 'truncateDigest' for a description of the truncation algorithm.
4447

4548
-- | The result of running a 'HashAlgorithm'.
4649
newtype Digest (a :: HashAlgorithm) =
47-
Digest BS.ByteString deriving (Show, Eq, Ord, DataHashable.Hashable)
50+
Digest BS.ByteString deriving (Eq, Ord, DataHashable.Hashable)
51+
52+
instance Show (Digest a) where
53+
show = ("Digest " ++) . show . encodeBase32
4854

4955
-- | The primitive interface for incremental hashing for a given
5056
-- 'HashAlgorithm'. Every 'HashAlgorithm' should have an instance.
@@ -61,21 +67,60 @@ class ValidAlgo (a :: HashAlgorithm) where
6167

6268
-- | A 'HashAlgorithm' with a canonical name, for serialization
6369
-- purposes (e.g. SRI hashes)
64-
class NamedAlgo (a :: HashAlgorithm) where
70+
class ValidAlgo a => NamedAlgo (a :: HashAlgorithm) where
6571
algoName :: Text
72+
hashSize :: Int
6673

6774
instance NamedAlgo 'MD5 where
6875
algoName = "md5"
76+
hashSize = 16
6977

7078
instance NamedAlgo 'SHA1 where
7179
algoName = "sha1"
80+
hashSize = 20
7281

7382
instance NamedAlgo 'SHA256 where
7483
algoName = "sha256"
84+
hashSize = 32
85+
86+
instance NamedAlgo 'SHA512 where
87+
algoName = "sha512"
88+
hashSize = 64
7589

7690
-- | A digest whose 'NamedAlgo' is not known at compile time.
7791
data SomeNamedDigest = forall a . NamedAlgo a => SomeDigest (Digest a)
7892

93+
instance Show SomeNamedDigest where
94+
show sd = case sd of
95+
SomeDigest (digest :: Digest hashType) -> T.unpack $ "SomeDigest " <> algoName @hashType <> ":" <> encodeBase32 digest
96+
97+
mkNamedDigest :: Text -> Text -> Either String SomeNamedDigest
98+
mkNamedDigest name sriHash =
99+
let (sriName, hash) = T.breakOnEnd "-" sriHash in
100+
if sriName == "" || sriName == (name <> "-")
101+
then mkDigest name hash
102+
else Left $ T.unpack $ "Sri hash method " <> sriName <> " does not match the required hash type " <> name
103+
where
104+
mkDigest name hash = case name of
105+
"md5" -> SomeDigest <$> decode @'MD5 hash
106+
"sha1" -> SomeDigest <$> decode @'SHA1 hash
107+
"sha256" -> SomeDigest <$> decode @'SHA256 hash
108+
"sha512" -> SomeDigest <$> decode @'SHA512 hash
109+
_ -> Left $ "Unknown hash name: " ++ T.unpack name
110+
decode :: forall a . (NamedAlgo a, ValidAlgo a) => Text -> Either String (Digest a)
111+
decode hash
112+
| size == base16Len = decodeBase16 hash
113+
| size == base32Len = decodeBase32 hash
114+
| size == base64Len = decodeBase64 hash
115+
| 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]
116+
where
117+
size = T.length hash
118+
hsize = hashSize @a
119+
base16Len = hsize * 2
120+
base32Len = ((hsize * 8 - 1) `div` 5) + 1;
121+
base64Len = ((4 * hsize `div` 3) + 3) `div` 4 * 4;
122+
123+
79124
-- | Hash an entire (strict) 'BS.ByteString' as a single call.
80125
--
81126
-- For example:
@@ -113,6 +158,16 @@ decodeBase16 t = case Base16.decode (T.encodeUtf8 t) of
113158
(x, "") -> Right $ Digest x
114159
_ -> Left $ "Unable to decode base16 string " ++ T.unpack t
115160

161+
-- | Encode a 'Digest' in hex.
162+
encodeBase64 :: Digest a -> T.Text
163+
encodeBase64 (Digest bs) = T.decodeUtf8 (Base64.encode bs)
164+
165+
-- | Decode a 'Digest' in hex
166+
decodeBase64 :: T.Text -> Either String (Digest a)
167+
decodeBase64 t = case Base64.decode (T.encodeUtf8 t) of
168+
Right x -> Right $ Digest x
169+
Left e -> Left $ "Unable to decode base64 string " ++ T.unpack t ++ ": " ++ e
170+
116171
-- | Uses "Crypto.Hash.MD5" from cryptohash-md5.
117172
instance ValidAlgo 'MD5 where
118173
type AlgoCtx 'MD5 = MD5.Ctx
@@ -134,6 +189,13 @@ instance ValidAlgo 'SHA256 where
134189
update = SHA256.update
135190
finalize = Digest . SHA256.finalize
136191

192+
-- | Uses "Crypto.Hash.SHA512" from cryptohash-sha512.
193+
instance ValidAlgo 'SHA512 where
194+
type AlgoCtx 'SHA512 = SHA512.Ctx
195+
initialize = SHA512.init
196+
update = SHA512.update
197+
finalize = Digest . SHA512.finalize
198+
137199
-- | Reuses the underlying 'ValidAlgo' instance, but does a
138200
-- 'truncateDigest' at the end.
139201
instance (ValidAlgo a, KnownNat n) => ValidAlgo ('Truncated n a) where

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

Lines changed: 17 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,12 @@ import Data.Text.Encoding
1212
import System.Nix.Hash
1313
import System.Nix.StorePath
1414

15-
makeStorePath :: forall hashAlgo . (NamedAlgo hashAlgo) => FilePath -> ByteString -> Digest hashAlgo -> StorePathName -> StorePath
15+
makeStorePath :: forall hashAlgo . (NamedAlgo hashAlgo)
16+
=> FilePath
17+
-> ByteString
18+
-> Digest hashAlgo
19+
-> StorePathName
20+
-> StorePath
1621
makeStorePath fp ty h nm = StorePath storeHash nm fp
1722
where
1823
s = BS.intercalate ":"
@@ -29,14 +34,18 @@ makeTextPath fp nm h refs = makeStorePath fp ty h nm
2934
where
3035
ty = BS.intercalate ":" ("text" : map storePathToRawFilePath (HS.toList refs))
3136

32-
makeFixedOutputPath :: forall hashAlgo. (ValidAlgo hashAlgo, NamedAlgo hashAlgo) => FilePath -> Bool -> Digest hashAlgo -> StorePathName -> StorePath
37+
makeFixedOutputPath :: forall hashAlgo . (ValidAlgo hashAlgo, NamedAlgo hashAlgo)
38+
=> FilePath
39+
-> Bool
40+
-> Digest hashAlgo
41+
-> StorePathName
42+
-> StorePath
3343
makeFixedOutputPath fp recursive h nm =
34-
makeStorePath fp ty h' nm
35-
where
36-
(ty, h') =
37-
if recursive && algoName @hashAlgo == algoName @'SHA256
38-
then ("source", h)
39-
else ("output:out", hash ("fixed:out:" <> encodeUtf8 (encodeBase16 h) <> ":"))
44+
if recursive && (algoName @hashAlgo) == "sha256"
45+
then makeStorePath fp "source" h nm
46+
else makeStorePath fp "output:out" h' nm
47+
where
48+
h' = hash @'SHA256 $ "fixed:out:" <> encodeUtf8 (algoName @hashAlgo) <> (if recursive then ":r:" else ":") <> encodeUtf8 (encodeBase16 h) <> ":"
4049

4150
computeStorePathForText :: FilePath -> StorePathName -> ByteString -> StorePathSet -> StorePath
4251
computeStorePathForText fp nm s refs = makeTextPath fp nm (hash s) refs

hnix-store-remote/src/System/Nix/Store/Remote.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -264,8 +264,7 @@ querySubstitutablePaths ps = do
264264
putPaths ps
265265
sockGetPaths
266266

267-
queryPathInfoUncached :: forall a . NamedAlgo a
268-
=> StorePath
267+
queryPathInfoUncached :: StorePath
269268
-> MonadStore StorePathMetadata
270269
queryPathInfoUncached path = do
271270
runOpArgs QueryPathInfo $ do
@@ -277,9 +276,9 @@ queryPathInfoUncached path = do
277276
deriverPath <- sockGetPathMay
278277

279278
narHashText <- Data.Text.Encoding.decodeUtf8 <$> sockGetStr
280-
let narHash = case System.Nix.Hash.decodeBase32 narHashText of
279+
let narHash = case System.Nix.Hash.decodeBase32 @'System.Nix.Hash.SHA256 narHashText of
281280
Left e -> error e
282-
Right x -> SomeDigest @a x
281+
Right x -> SomeDigest x
283282

284283
references <- sockGetPaths
285284
registrationTime <- sockGet getTime
@@ -294,7 +293,7 @@ queryPathInfoUncached path = do
294293
sigs = Data.Set.empty
295294

296295
contentAddressableAddress =
297-
case System.Nix.Store.Remote.Parsers.parseContentAddressableAddress @a caString of
296+
case System.Nix.Store.Remote.Parsers.parseContentAddressableAddress caString of
298297
Left e -> error e
299298
Right x -> Just x
300299

hnix-store-remote/src/System/Nix/Store/Remote/Parsers.hs

Lines changed: 33 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -2,63 +2,54 @@
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE ScopedTypeVariables #-}
44
{-# LANGUAGE RankNTypes #-}
5+
{-# LANGUAGE DataKinds #-}
56
{-# LANGUAGE TypeApplications #-}
67

7-
module System.Nix.Store.Remote.Parsers (
8-
parseContentAddressableAddress
9-
) where
8+
module System.Nix.Store.Remote.Parsers
9+
( parseContentAddressableAddress
10+
)
11+
where
1012

11-
import Control.Applicative ((<|>))
12-
import Data.Attoparsec.ByteString.Char8 (Parser, (<?>))
13-
import Data.ByteString (ByteString)
14-
import System.Nix.Hash (Digest, NamedAlgo, SomeNamedDigest(SomeDigest))
15-
import System.Nix.StorePath (ContentAddressableAddress(..), NarHashMode(..))
16-
17-
import qualified Data.Attoparsec.ByteString.Char8
18-
import qualified Data.ByteString.Char8
13+
import Control.Applicative ( (<|>) )
14+
import Data.Attoparsec.ByteString.Char8
15+
import Data.ByteString.Char8
1916
import qualified Data.Text
20-
21-
import qualified System.Nix.Internal.Base32
22-
import qualified System.Nix.Hash
17+
import Data.Text.Encoding ( decodeUtf8 )
18+
import System.Nix.Hash
19+
import System.Nix.StorePath ( ContentAddressableAddress(..)
20+
, NarHashMode(..)
21+
)
2322

2423
-- | Parse `ContentAddressableAddress` from `ByteString`
25-
parseContentAddressableAddress :: forall hashAlgo . NamedAlgo hashAlgo
26-
=> ByteString
27-
-> Either String ContentAddressableAddress
24+
parseContentAddressableAddress
25+
:: ByteString -> Either String ContentAddressableAddress
2826
parseContentAddressableAddress =
29-
Data.Attoparsec.ByteString.Char8.parseOnly
30-
(contentAddressableAddressParser @hashAlgo)
27+
Data.Attoparsec.ByteString.Char8.parseOnly contentAddressableAddressParser
3128

3229
-- | Parser for content addressable field
33-
contentAddressableAddressParser :: forall hashAlgo . NamedAlgo hashAlgo
34-
=> Parser ContentAddressableAddress
35-
contentAddressableAddressParser =
36-
caText
37-
<|> caFixed @hashAlgo
30+
contentAddressableAddressParser :: Parser ContentAddressableAddress
31+
contentAddressableAddressParser = caText <|> caFixed
3832

3933
-- | Parser for @text:sha256:<h>@
4034
caText :: Parser ContentAddressableAddress
4135
caText = do
42-
_ <- "text:sha256:"
43-
digest <- parseDigest
44-
either fail return
45-
$ Text <$> digest
36+
_ <- "text:sha256:"
37+
digest <- decodeBase32 @'SHA256 <$> parseHash
38+
either fail return $ Text <$> digest
4639

4740
-- | Parser for @fixed:<r?>:<ht>:<h>@
48-
caFixed :: forall hashAlgo . NamedAlgo hashAlgo => Parser ContentAddressableAddress
41+
caFixed :: Parser ContentAddressableAddress
4942
caFixed = do
50-
_ <- "fixed:"
51-
narHashMode <- (pure Recursive <$> "true") <|> (pure RegularFile <$> "false")
52-
<?> "Invalid Base32 part"
53-
digest <- parseDigest
43+
_ <- "fixed:"
44+
narHashMode <- (pure Recursive <$> "r:") <|> (pure RegularFile <$> "")
45+
digest <- parseTypedDigest
46+
either fail return $ Fixed narHashMode <$> digest
47+
48+
parseTypedDigest :: Parser (Either String SomeNamedDigest)
49+
parseTypedDigest = mkNamedDigest <$> parseHashType <*> parseHash
5450

55-
either fail return
56-
$ Fixed <$> pure narHashMode <*> (SomeDigest @hashAlgo <$> digest)
51+
parseHashType :: Parser Data.Text.Text
52+
parseHashType = decodeUtf8 <$> ("sha256" <|> "sha512" <|> "sha1" <|> "md5") <* (":" <|> "-")
5753

58-
parseDigest :: forall a . Parser (Either String (Digest a))
59-
parseDigest =
60-
System.Nix.Hash.decodeBase32
61-
. Data.Text.pack
62-
. Data.ByteString.Char8.unpack
63-
<$> Data.Attoparsec.ByteString.Char8.takeWhile1
64-
(\c -> c `elem` System.Nix.Internal.Base32.digits32)
54+
parseHash :: Parser Data.Text.Text
55+
parseHash = decodeUtf8 <$> takeWhile1 (/= ':')

0 commit comments

Comments
 (0)