-- | Ed25519 cryptographic primitives. module Tezos.Crypto.Ed25519 ( -- * Cryptographic primitive types PublicKey (..) , SecretKey , Signature (..) , detSecretKey , toPublic -- * Raw bytes (no checksums, tags or anything) , publicKeyToBytes , mkPublicKey , publicKeyLengthBytes , signatureToBytes , mkSignature , signatureLengthBytes -- * Formatting and parsing , formatPublicKey , mformatPublicKey , parsePublicKey , formatSecretKey , parseSecretKey , formatSignature , mformatSignature , parseSignature -- * Signing , sign , checkSignature ) where import Crypto.Error (onCryptoFailure) import qualified Crypto.PubKey.Ed25519 as Ed25519 import Data.ByteArray (ByteArray, ByteArrayAccess, convert) import qualified Data.ByteString as BS import Fmt (Buildable, build) import Test.QuickCheck (Arbitrary(..), vector) import Michelson.Text import Tezos.Crypto.Hash import Tezos.Crypto.Util ---------------------------------------------------------------------------- -- Types, instances, conversions ---------------------------------------------------------------------------- -- | ED25519 public cryptographic key. newtype PublicKey = PublicKey { unPublicKey :: Ed25519.PublicKey } deriving stock (Show, Eq, Generic) instance Arbitrary PublicKey where arbitrary = toPublic <$> arbitrary instance NFData PublicKey -- | ED25519 secret cryptographic key. newtype SecretKey = SecretKey { unSecretKey :: Ed25519.SecretKey } deriving stock (Show, Eq, Generic) instance NFData SecretKey -- | Deterministicaly generate a secret key from seed. detSecretKey :: ByteString -> SecretKey detSecretKey seed = SecretKey $ deterministic seed Ed25519.generateSecretKey instance Arbitrary SecretKey where arbitrary = detSecretKey . BS.pack <$> vector 32 -- | Create a public key from a secret key. toPublic :: SecretKey -> PublicKey toPublic = PublicKey . Ed25519.toPublic . unSecretKey -- | ED25519 cryptographic signature. newtype Signature = Signature { unSignature :: Ed25519.Signature } deriving stock (Show, Eq, Generic) instance Arbitrary Signature where arbitrary = sign <$> arbitrary <*> (encodeUtf8 @String <$> arbitrary) instance NFData Signature ---------------------------------------------------------------------------- -- Conversion to/from raw bytes (no checksums, tags or anything) ---------------------------------------------------------------------------- -- | Convert a 'PublicKey' to raw bytes. publicKeyToBytes :: ByteArray ba => PublicKey -> ba publicKeyToBytes = convert . unPublicKey -- | Make a 'PublicKey' from raw bytes. mkPublicKey :: ByteArrayAccess ba => ba -> Either CryptoParseError PublicKey mkPublicKey = onCryptoFailure (Left . CryptoParseCryptoError) (Right . PublicKey) . Ed25519.publicKey publicKeyLengthBytes :: Integral n => n publicKeyLengthBytes = fromIntegral Ed25519.publicKeySize -- | Convert a 'Signature' to raw bytes. signatureToBytes :: ByteArray ba => Signature -> ba signatureToBytes = convert . unSignature -- | Make a 'Signature' from raw bytes. mkSignature :: ByteArrayAccess ba => ba -> Either CryptoParseError Signature mkSignature = onCryptoFailure (Left . CryptoParseCryptoError) (Right . Signature) . Ed25519.signature signatureLengthBytes :: Integral n => n signatureLengthBytes = fromIntegral Ed25519.signatureSize mkSecretKey :: ByteArrayAccess ba => ba -> Either CryptoParseError SecretKey mkSecretKey = onCryptoFailure (Left . CryptoParseCryptoError) (Right . SecretKey) . Ed25519.secretKey ---------------------------------------------------------------------------- -- Magic bytes ---------------------------------------------------------------------------- publicKeyTag :: ByteString publicKeyTag = "\13\15\37\217" secretKeyTag :: ByteString secretKeyTag = "\13\15\58\7" signatureTag :: ByteString signatureTag = "\9\245\205\134\18" ---------------------------------------------------------------------------- -- Formatting ---------------------------------------------------------------------------- formatPublicKey :: PublicKey -> Text formatPublicKey = formatImpl publicKeyTag . unPublicKey mformatPublicKey :: PublicKey -> MText mformatPublicKey = mkMTextUnsafe . formatPublicKey instance Buildable PublicKey where build = build . formatPublicKey parsePublicKey :: Text -> Either CryptoParseError PublicKey parsePublicKey = parseImpl publicKeyTag mkPublicKey formatSecretKey :: SecretKey -> Text formatSecretKey = formatImpl secretKeyTag . unSecretKey instance Buildable SecretKey where build = build . formatSecretKey parseSecretKey :: Text -> Either CryptoParseError SecretKey parseSecretKey = parseImpl secretKeyTag mkSecretKey formatSignature :: Signature -> Text formatSignature = formatImpl signatureTag . unSignature mformatSignature :: Signature -> MText mformatSignature = mkMTextUnsafe . formatSignature instance Buildable Signature where build = build . formatSignature parseSignature :: Text -> Either CryptoParseError Signature parseSignature = parseImpl signatureTag mkSignature ---------------------------------------------------------------------------- -- Signing ---------------------------------------------------------------------------- -- | Sign a message using the secret key. sign :: SecretKey -> ByteString -> Signature sign sk = Signature . Ed25519.sign (unSecretKey sk) (unPublicKey (toPublic sk)) . blake2b -- | Check that a sequence of bytes has been signed with a given key. checkSignature :: PublicKey -> Signature -> ByteString -> Bool checkSignature (PublicKey pk) (Signature sig) bytes = Ed25519.verify pk (blake2b bytes) sig