Skip to content

Commit 7850a38

Browse files
committed
core: add signatureToText function and tests
- make NarSignature's Show instance more legible - add Arbitrary instance for NarSignature - add roundtrip quickcheck tests for NarSignature encoding
1 parent ee10c59 commit 7850a38

File tree

5 files changed

+76
-17
lines changed

5 files changed

+76
-17
lines changed
Lines changed: 24 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
23
{-|
34
Description : Nix-relevant interfaces to NaCl signatures.
45
-}
@@ -8,22 +9,23 @@ module System.Nix.Signature
89
, NarSignature(..)
910
, signatureParser
1011
, parseSignature
12+
, signatureToText
1113
) where
1214

15+
import Crypto.Error (CryptoFailable(..))
16+
import Data.ByteString (ByteString)
17+
import Data.Text (Text)
1318
import GHC.Generics (Generic)
19+
import System.Nix.Base (decodeWith, encodeWith, BaseEncoding(Base64))
1420

15-
import qualified Crypto.PubKey.Ed25519
16-
import Crypto.Error (CryptoFailable(..))
21+
import qualified Crypto.PubKey.Ed25519 as Ed25519
1722
import qualified Data.Attoparsec.Text
18-
import qualified Data.Char
1923
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))
24+
import qualified Data.Char
25+
import qualified Data.Text
2426

2527
-- | An ed25519 signature.
26-
newtype Signature = Signature Crypto.PubKey.Ed25519.Signature
28+
newtype Signature = Signature Ed25519.Signature
2729
deriving (Eq, Generic, Show)
2830

2931
-- | A detached signature attesting to a nix archive's validity.
@@ -33,29 +35,34 @@ data NarSignature = NarSignature
3335
, -- | The archive's signature.
3436
sig :: !Signature
3537
}
36-
deriving (Eq, Generic, Ord, Show)
38+
deriving (Eq, Generic, Ord)
3739

3840
instance Ord Signature where
3941
compare (Signature x) (Signature y) = let
40-
xBS = Data.ByteArray.convert x :: BS.ByteString
41-
yBS = Data.ByteArray.convert y :: BS.ByteString
42+
xBS = Data.ByteArray.convert x :: ByteString
43+
yBS = Data.ByteArray.convert y :: ByteString
4244
in compare xBS yBS
4345

4446
signatureParser :: Data.Attoparsec.Text.Parser NarSignature
4547
signatureParser = do
4648
publicKey <- Data.Attoparsec.Text.takeWhile1 (/= ':')
4749
_ <- Data.Attoparsec.Text.string ":"
4850
encodedSig <- Data.Attoparsec.Text.takeWhile1 (\c -> Data.Char.isAlphaNum c || c == '+' || c == '/' || c == '=')
49-
decodedSig <- case System.Nix.Base.decodeWith Base64 encodedSig of
51+
decodedSig <- case decodeWith Base64 encodedSig of
5052
Left e -> fail e
5153
Right decodedSig -> pure decodedSig
52-
sig <- case Crypto.PubKey.Ed25519.signature decodedSig of
54+
sig <- case Ed25519.signature decodedSig of
5355
CryptoFailed e -> (fail . show) e
5456
CryptoPassed sig -> pure sig
5557
pure $ NarSignature publicKey (Signature sig)
5658

57-
parseSignature
58-
:: Text -> Either String NarSignature
59-
parseSignature =
60-
Data.Attoparsec.Text.parseOnly signatureParser
59+
parseSignature :: Text -> Either String NarSignature
60+
parseSignature = Data.Attoparsec.Text.parseOnly signatureParser
61+
62+
signatureToText :: NarSignature -> Text
63+
signatureToText NarSignature {publicKey, sig=Signature sig'} = let
64+
b64Encoded = encodeWith Base64 (Data.ByteArray.convert sig' :: ByteString)
65+
in mconcat [ publicKey, ":", b64Encoded ]
6166

67+
instance Show NarSignature where
68+
show narSig = Data.Text.unpack (signatureToText narSig)

hnix-store-tests/hnix-store-tests.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ library
4141
, System.Nix.Arbitrary.Derivation
4242
, System.Nix.Arbitrary.DerivedPath
4343
, System.Nix.Arbitrary.Hash
44+
, System.Nix.Arbitrary.Signature
4445
, System.Nix.Arbitrary.Store.Types
4546
, System.Nix.Arbitrary.StorePath
4647
, Test.Hspec.Nix
@@ -67,6 +68,7 @@ test-suite props
6768
DerivationSpec
6869
DerivedPathSpec
6970
StorePathSpec
71+
SignatureSpec
7072
hs-source-dirs:
7173
tests
7274
build-tool-depends:

hnix-store-tests/src/System/Nix/Arbitrary.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,5 +5,6 @@ import System.Nix.Arbitrary.ContentAddress ()
55
import System.Nix.Arbitrary.Derivation ()
66
import System.Nix.Arbitrary.DerivedPath ()
77
import System.Nix.Arbitrary.Hash ()
8+
import System.Nix.Arbitrary.Signature ()
89
import System.Nix.Arbitrary.Store.Types ()
910
import System.Nix.Arbitrary.StorePath ()
Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,36 @@
1+
-- due to recent generic-arbitrary
2+
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
3+
{-# OPTIONS_GHC -Wno-orphans #-}
4+
{-# LANGUAGE OverloadedStrings #-}
5+
module System.Nix.Arbitrary.Signature where
6+
7+
import qualified Crypto.PubKey.Ed25519
8+
import Crypto.Random (drgNewTest, withDRG)
9+
import qualified Data.ByteString as BS
10+
import qualified Data.Text as Text
11+
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
12+
import Test.QuickCheck.Instances ()
13+
import Test.QuickCheck
14+
15+
import System.Nix.Signature
16+
17+
instance Arbitrary Crypto.PubKey.Ed25519.Signature where
18+
arbitrary = do
19+
seeds <- (,,,,) <$> arbitraryBoundedRandom <*> arbitraryBoundedRandom <*> arbitraryBoundedRandom <*> arbitraryBoundedRandom <*> arbitraryBoundedRandom
20+
let drg = drgNewTest seeds
21+
(secretKey, _) = withDRG drg Crypto.PubKey.Ed25519.generateSecretKey
22+
publicKey = Crypto.PubKey.Ed25519.toPublic secretKey
23+
msg :: BS.ByteString = "msg"
24+
pure $ Crypto.PubKey.Ed25519.sign secretKey publicKey msg
25+
26+
deriving via GenericArbitrary Signature
27+
instance Arbitrary Signature
28+
29+
instance Arbitrary NarSignature where
30+
arbitrary = do
31+
name <- Text.pack . getPrintableString <$> suchThat arbitrary (\(PrintableString str) -> validName str)
32+
NarSignature name <$> arbitrary
33+
34+
validName :: String -> Bool
35+
validName txt = not (null txt) && not (elem ':' txt)
36+
Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
module SignatureSpec where
2+
3+
import Test.Hspec (Spec, describe)
4+
import Test.Hspec.Nix (roundtrips)
5+
import Test.Hspec.QuickCheck (prop)
6+
7+
import System.Nix.Signature (signatureToText, parseSignature)
8+
import System.Nix.Arbitrary ()
9+
10+
spec :: Spec
11+
spec = do
12+
describe "Signature" $ do
13+
prop "roundtrips" $ roundtrips signatureToText parseSignature

0 commit comments

Comments
 (0)