11{-# LANGUAGE OverloadedStrings #-}
2+ {-# LANGUAGE NamedFieldPuns #-}
23{-|
34Description : 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 )
1318import 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
1722import qualified Data.Attoparsec.Text
18- import qualified Data.Char
1923import 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
3840instance 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
4446signatureParser :: Data.Attoparsec.Text. Parser NarSignature
4547signatureParser = 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)
0 commit comments