Skip to content

Commit 3710c6a

Browse files
committed
add signature decoding
- add NarSignature decoding - use cryptonite instead of saltine for signature - remove saltine dependency - add signature decode and verify tests taken from tvix - start decoding signatures in queryPathInfoUncached Closes #240 and #246
1 parent 4d9d595 commit 3710c6a

File tree

4 files changed

+128
-25
lines changed

4 files changed

+128
-25
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,6 @@ library
8585
-- Required for cryptonite low-level type convertion
8686
, memory
8787
, nix-derivation >= 1.1.1 && <2
88-
, saltine >= 0.2 && < 0.3
8988
, some > 1.0.5 && < 2
9089
, time
9190
, text
@@ -100,6 +99,7 @@ test-suite core
10099
other-modules:
101100
Derivation
102101
Hash
102+
Signature
103103
hs-source-dirs:
104104
tests
105105
build-tool-depends:
Lines changed: 45 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,37 +1,61 @@
1+
{-# LANGUAGE OverloadedStrings #-}
12
{-|
23
Description : Nix-relevant interfaces to NaCl signatures.
34
-}
45

56
module System.Nix.Signature
6-
( Signature
7+
( Signature(..)
78
, NarSignature(..)
9+
, signatureParser
10+
, parseSignature
811
) where
912

10-
import Crypto.Saltine.Core.Sign (PublicKey)
11-
import Crypto.Saltine.Class (IsEncoding(..))
12-
import Data.ByteString (ByteString)
1313
import GHC.Generics (Generic)
1414

15-
import qualified Data.ByteString
16-
import qualified Data.Coerce
15+
import qualified Crypto.PubKey.Ed25519
16+
import Crypto.Error (CryptoFailable(..))
17+
import qualified Data.Attoparsec.Text
18+
import qualified Data.Char
19+
import qualified Data.ByteArray
20+
import qualified Data.ByteString as BS
21+
import Data.Text (Text)
22+
import qualified System.Nix.Base
23+
import System.Nix.Base (BaseEncoding(Base64))
1724

18-
import qualified Crypto.Saltine.Internal.Sign as NaClSizes
25+
-- | An ed25519 signature.
26+
newtype Signature = Signature Crypto.PubKey.Ed25519.Signature
27+
deriving (Eq, Generic, Show)
1928

20-
-- | A NaCl signature.
21-
newtype Signature = Signature ByteString
22-
deriving (Eq, Generic, Ord, Show)
23-
24-
instance IsEncoding Signature where
25-
decode s
26-
| Data.ByteString.length s == NaClSizes.sign_bytes = Just $ Signature s
27-
| otherwise = Nothing
28-
encode = Data.Coerce.coerce
29-
30-
-- | A detached NaCl signature attesting to a nix archive's validity.
29+
-- | A detached signature attesting to a nix archive's validity.
3130
data NarSignature = NarSignature
32-
{ -- | The public key used to sign the archive.
33-
publicKey :: PublicKey
31+
{ -- | The name of the public key used to sign the archive.
32+
publicKey :: !Text
3433
, -- | The archive's signature.
35-
sig :: Signature
34+
sig :: !Signature
3635
}
3736
deriving (Eq, Generic, Ord, Show)
37+
38+
instance Ord Signature where
39+
compare (Signature x) (Signature y) = let
40+
xBS = Data.ByteArray.convert x :: BS.ByteString
41+
yBS = Data.ByteArray.convert y :: BS.ByteString
42+
in compare xBS yBS
43+
44+
signatureParser :: Data.Attoparsec.Text.Parser NarSignature
45+
signatureParser = do
46+
publicKey <- Data.Attoparsec.Text.takeWhile1 (/= ':')
47+
_ <- Data.Attoparsec.Text.string ":"
48+
encodedSig <- Data.Attoparsec.Text.takeWhile1 (\c -> Data.Char.isAlphaNum c || c == '+' || c == '/' || c == '=')
49+
decodedSig <- case System.Nix.Base.decodeWith Base64 encodedSig of
50+
Left e -> fail e
51+
Right decodedSig -> pure decodedSig
52+
sig <- case Crypto.PubKey.Ed25519.signature decodedSig of
53+
CryptoFailed e -> (fail . show) e
54+
CryptoPassed sig -> pure sig
55+
pure $ NarSignature publicKey (Signature sig)
56+
57+
parseSignature
58+
:: Text -> Either String NarSignature
59+
parseSignature =
60+
Data.Attoparsec.Text.parseOnly signatureParser
61+

hnix-store-core/tests/Signature.hs

Lines changed: 75 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,75 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
3+
module Signature where
4+
5+
import qualified Data.ByteString as BS
6+
import Test.Hspec
7+
import Data.Text (Text)
8+
import qualified Crypto.PubKey.Ed25519
9+
import qualified System.Nix.Base
10+
import System.Nix.Base (BaseEncoding(Base64))
11+
import Crypto.Error (CryptoFailable(..))
12+
13+
import System.Nix.Signature
14+
15+
spec_signature :: Spec
16+
spec_signature = do
17+
18+
describe "signature parser" $ do
19+
20+
it "parses names" $ do
21+
shouldParseName "cache.nixos.org-1:TsTTb3WGTZKphvYdBHXwo6weVILmTytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ==" "cache.nixos.org-1"
22+
23+
it "fails on invalid signatures" $ do
24+
shouldNotParse ""
25+
shouldNotParse "asdf"
26+
shouldNotParse "cache.nixos.org-1:"
27+
shouldNotParse ":TsTTb3WGTZKphvYdBHXwo6weVILmTytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ=="
28+
shouldNotParse "cache.nixos.org-1TsTTb3WGTZKphvYdBHXwo6weVILmTytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ=="
29+
shouldNotParse "cache.nixos.org-1:sTTb3WGTZKphvYdBHXwo6weVILmTytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ=="
30+
31+
it "parses verifying signatures" $ do
32+
shouldVerify "cache.nixos.org-1:TsTTb3WGTZKphvYdBHXwo6weVILmTytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ==" pubkeyNixosOrg fingerprint
33+
shouldVerify "cache.nixos.org-2:TsTTb3WGTZKphvYdBHXwo6weVILmTytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ==" pubkeyNixosOrg fingerprint
34+
35+
it "parses non-verifying signatures" $ do
36+
shouldNotVerify "cache.nixos.org-1:TsTTb000000000000000000000000ytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ==" pubkeyNixosOrg fingerprint
37+
38+
fingerprint :: BS.ByteString
39+
fingerprint = "1;/nix/store/syd87l2rxw8cbsxmxl853h0r6pdwhwjr-curl-7.82.0-bin;sha256:1b4sb93wp679q4zx9k1ignby1yna3z7c4c2ri3wphylbc2dwsys0;196040;/nix/store/0jqd0rlxzra1rs38rdxl43yh6rxchgc6-curl-7.82.0,/nix/store/6w8g7njm4mck5dmjxws0z1xnrxvl81xa-glibc-2.34-115,/nix/store/j5jxw3iy7bbz4a57fh9g2xm2gxmyal8h-zlib-1.2.12,/nix/store/yxvjs9drzsphm9pcf42a4byzj1kb9m7k-openssl-1.1.1n";
40+
41+
forceDecodeB64Pubkey :: Text -> Crypto.PubKey.Ed25519.PublicKey
42+
forceDecodeB64Pubkey b64EncodedPubkey = let
43+
decoded = case System.Nix.Base.decodeWith Base64 b64EncodedPubkey of
44+
Left err -> error err
45+
Right x -> x
46+
in case Crypto.PubKey.Ed25519.publicKey decoded of
47+
CryptoFailed err -> (error . show) err
48+
CryptoPassed x -> x
49+
50+
pubkeyNixosOrg :: Crypto.PubKey.Ed25519.PublicKey
51+
pubkeyNixosOrg = forceDecodeB64Pubkey "6NCHdD59X431o0gWypbMrAURkbJ16ZPMQFGspcDShjY="
52+
53+
shouldNotParse :: Text -> Expectation
54+
shouldNotParse encoded = case parseSignature encoded of
55+
Left _ -> pure ()
56+
Right _ -> expectationFailure "should not have parsed"
57+
58+
shouldParseName :: Text -> Text -> Expectation
59+
shouldParseName encoded name = case parseSignature encoded of
60+
Left err -> expectationFailure err
61+
Right narSig -> shouldBe name (publicKey narSig)
62+
63+
shouldVerify :: Text -> Crypto.PubKey.Ed25519.PublicKey -> BS.ByteString -> Expectation
64+
shouldVerify encoded pubkey msg = case parseSignature encoded of
65+
Left err -> expectationFailure err
66+
Right narSig -> let
67+
(Signature sig') = sig narSig
68+
in sig' `shouldSatisfy` Crypto.PubKey.Ed25519.verify pubkey msg
69+
70+
shouldNotVerify :: Text -> Crypto.PubKey.Ed25519.PublicKey -> BS.ByteString -> Expectation
71+
shouldNotVerify encoded pubkey msg = case parseSignature encoded of
72+
Left err -> expectationFailure err
73+
Right narSig -> let
74+
(Signature sig') = sig narSig
75+
in sig' `shouldNotSatisfy` Crypto.PubKey.Ed25519.verify pubkey msg

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

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,7 @@ import System.Nix.Store.Remote.Binary
7272
import System.Nix.Store.Remote.Types
7373
import System.Nix.Store.Remote.Protocol
7474
import System.Nix.Store.Remote.Util
75+
import qualified System.Nix.Signature
7576
import Crypto.Hash ( SHA256 )
7677
import System.Nix.Nar ( NarSource )
7778

@@ -252,12 +253,15 @@ queryPathInfoUncached path = do
252253
narBytes <- Just <$> sockGetInt
253254
ultimate <- sockGetBool
254255

255-
_sigStrings <- fmap bsToText <$> sockGetStrings
256+
sigStrings <- fmap bsToText <$> sockGetStrings
256257
caString <- bsToText <$> sockGetStr
257258

258259
let
259-
-- XXX: signatures need pubkey from config
260-
sigs = Data.Set.empty
260+
sigs = case
261+
Data.Set.fromList <$> mapM (Data.Attoparsec.Text.parseOnly System.Nix.Signature.signatureParser) sigStrings
262+
of
263+
Left e -> error e
264+
Right x -> x
261265

262266
contentAddress =
263267
if Data.Text.null caString then Nothing else

0 commit comments

Comments
 (0)