core: split signature/narSignature parser/builder

This commit is contained in:
sorki 2023-12-02 15:12:54 +01:00
parent 8b1db174bc
commit 265d25256d
4 changed files with 46 additions and 27 deletions

View File

@ -6,13 +6,17 @@ Description : Nix-relevant interfaces to NaCl signatures.
module System.Nix.Signature
( Signature(..)
, NarSignature(..)
, signatureParser
, parseSignature
, signatureToText
, NarSignature(..)
, narSignatureParser
, parseNarSignature
, narSignatureToText
) where
import Crypto.Error (CryptoFailable(..))
import Data.Attoparsec.Text (Parser)
import Data.ByteString (ByteString)
import Data.Text (Text)
import GHC.Generics (Generic)
@ -28,6 +32,26 @@ import qualified Data.Text
newtype Signature = Signature Ed25519.Signature
deriving (Eq, Generic, Show)
signatureParser :: Parser Signature
signatureParser = do
encodedSig <-
Data.Attoparsec.Text.takeWhile1
(\c -> Data.Char.isAlphaNum c || c == '+' || c == '/' || c == '=')
decodedSig <- case decodeWith Base64 encodedSig of
Left e -> fail e
Right decodedSig -> pure decodedSig
sig <- case Ed25519.signature decodedSig of
CryptoFailed e -> (fail . show) e
CryptoPassed sig -> pure sig
pure $ Signature sig
parseSignature :: Text -> Either String Signature
parseSignature = Data.Attoparsec.Text.parseOnly signatureParser
signatureToText :: Signature -> Text
signatureToText (Signature sig) =
encodeWith Base64 (Data.ByteArray.convert sig :: ByteString)
-- | A detached signature attesting to a nix archive's validity.
data NarSignature = NarSignature
{ -- | The name of the public key used to sign the archive.
@ -43,26 +67,19 @@ instance Ord Signature where
yBS = Data.ByteArray.convert y :: ByteString
in compare xBS yBS
signatureParser :: Data.Attoparsec.Text.Parser NarSignature
signatureParser = do
narSignatureParser :: Parser NarSignature
narSignatureParser = do
publicKey <- Data.Attoparsec.Text.takeWhile1 (/= ':')
_ <- Data.Attoparsec.Text.string ":"
encodedSig <- Data.Attoparsec.Text.takeWhile1 (\c -> Data.Char.isAlphaNum c || c == '+' || c == '/' || c == '=')
decodedSig <- case decodeWith Base64 encodedSig of
Left e -> fail e
Right decodedSig -> pure decodedSig
sig <- case Ed25519.signature decodedSig of
CryptoFailed e -> (fail . show) e
CryptoPassed sig -> pure sig
pure $ NarSignature publicKey (Signature sig)
sig <- signatureParser
pure $ NarSignature {..}
parseSignature :: Text -> Either String NarSignature
parseSignature = Data.Attoparsec.Text.parseOnly signatureParser
parseNarSignature :: Text -> Either String NarSignature
parseNarSignature = Data.Attoparsec.Text.parseOnly narSignatureParser
signatureToText :: NarSignature -> Text
signatureToText NarSignature {publicKey, sig=Signature sig'} = let
b64Encoded = encodeWith Base64 (Data.ByteArray.convert sig' :: ByteString)
in mconcat [ publicKey, ":", b64Encoded ]
narSignatureToText :: NarSignature -> Text
narSignatureToText NarSignature {..} =
mconcat [ publicKey, ":", signatureToText sig ]
instance Show NarSignature where
show narSig = Data.Text.unpack (signatureToText narSig)
show narSig = Data.Text.unpack (narSignatureToText narSig)

View File

@ -48,19 +48,19 @@ exampleMetadata = Metadata
, registrationTime = UTCTime (fromOrdinalDate 0 0) 0
, narBytes = Just 196040
, trust = BuiltElsewhere
, sigs = Set.fromList $ forceRight . parseSignature <$> ["cache.nixos.org-1:TsTTb3WGTZKphvYdBHXwo6weVILmTytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ==", "test1:519iiVLx/c4Rdt5DNt6Y2Jm6hcWE9+XY69ygiWSZCNGVcmOcyL64uVAJ3cV8vaTusIZdbTnYo9Y7vDNeTmmMBQ=="]
, sigs = Set.fromList $ forceRight . parseNarSignature <$> ["cache.nixos.org-1:TsTTb3WGTZKphvYdBHXwo6weVILmTytUjLB+vcX89fOjjRicCHmKA4RCPMVLkj6TMJ4GMX3HPVWRdD1hkeKZBQ==", "test1:519iiVLx/c4Rdt5DNt6Y2Jm6hcWE9+XY69ygiWSZCNGVcmOcyL64uVAJ3cV8vaTusIZdbTnYo9Y7vDNeTmmMBQ=="]
, contentAddress = Nothing
}
pubkey :: Ed25519.PublicKey
pubkey = forceDecodeB64Pubkey "6NCHdD59X431o0gWypbMrAURkbJ16ZPMQFGspcDShjY="
forceDecodeB64Pubkey :: Text -> Ed25519.PublicKey
forceDecodeB64Pubkey b64EncodedPubkey = let
decoded = forceRight $ decodeWith Base64 b64EncodedPubkey
in case Ed25519.publicKey decoded of
in case Ed25519.publicKey decoded of
CryptoFailed err -> (error . show) err
CryptoPassed x -> x
CryptoPassed x -> x
forceRight :: Either a b -> b
forceRight = \case

View File

@ -54,24 +54,24 @@ pubkeyNixosOrg :: Crypto.PubKey.Ed25519.PublicKey
pubkeyNixosOrg = forceDecodeB64Pubkey "6NCHdD59X431o0gWypbMrAURkbJ16ZPMQFGspcDShjY="
shouldNotParse :: Text -> Expectation
shouldNotParse encoded = case parseSignature encoded of
shouldNotParse encoded = case parseNarSignature encoded of
Left _ -> pure ()
Right _ -> expectationFailure "should not have parsed"
shouldParseName :: Text -> Text -> Expectation
shouldParseName encoded name = case parseSignature encoded of
shouldParseName encoded name = case parseNarSignature encoded of
Left err -> expectationFailure err
Right narSig -> shouldBe name (publicKey narSig)
shouldVerify :: Text -> Crypto.PubKey.Ed25519.PublicKey -> BS.ByteString -> Expectation
shouldVerify encoded pubkey msg = case parseSignature encoded of
shouldVerify encoded pubkey msg = case parseNarSignature encoded of
Left err -> expectationFailure err
Right narSig -> let
(Signature sig') = sig narSig
in sig' `shouldSatisfy` Crypto.PubKey.Ed25519.verify pubkey msg
shouldNotVerify :: Text -> Crypto.PubKey.Ed25519.PublicKey -> BS.ByteString -> Expectation
shouldNotVerify encoded pubkey msg = case parseSignature encoded of
shouldNotVerify encoded pubkey msg = case parseNarSignature encoded of
Left err -> expectationFailure err
Right narSig -> let
(Signature sig') = sig narSig

View File

@ -4,10 +4,12 @@ import Test.Hspec (Spec, describe)
import Test.Hspec.Nix (roundtrips)
import Test.Hspec.QuickCheck (prop)
import System.Nix.Signature (signatureToText, parseSignature)
import System.Nix.Signature (signatureToText, parseSignature, narSignatureToText, parseNarSignature)
import System.Nix.Arbitrary ()
spec :: Spec
spec = do
describe "Signature" $ do
prop "roundtrips" $ roundtrips signatureToText parseSignature
describe "NarSignature" $ do
prop "roundtrips" $ roundtrips narSignatureToText parseNarSignature