Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utilities shared by multiple cryptographic primitives.
Synopsis
- data CryptoParseError
- encodeBase58Check :: ByteString -> Text
- decodeBase58Check :: Text -> Maybe ByteString
- data B58CheckWithPrefixError
- decodeBase58CheckWithPrefix :: ByteString -> Text -> Either B58CheckWithPrefixError ByteString
- formatImpl :: ByteArrayAccess x => ByteString -> x -> Text
- parseImpl :: ByteString -> (ByteString -> Either CryptoParseError res) -> Text -> Either CryptoParseError res
- firstRight :: NonEmpty (Either e a) -> Either e a
- deterministic :: ByteString -> MonadPseudoRandom ChaChaDRG a -> a
- rnfCurve :: Curve -> ()
- publicKeyLengthBytes_ :: Integral n => Curve -> n
- mkSignature_ :: ByteArray ba => Curve -> ba -> Either CryptoParseError Signature
- mkSecretKey_ :: ByteArray ba => Curve -> ba -> KeyPair
- secretKeyToBytes_ :: ByteArray ba => KeyPair -> ba
- signatureToBytes_ :: ByteArray ba => Curve -> Signature -> ba
- mkPublicKey_ :: ByteArrayAccess ba => Curve -> ba -> Either CryptoParseError PublicKey
- publicKeyToBytes_ :: forall ba. (ByteArray ba, HasCallStack) => Curve -> PublicKey -> ba
- signatureLengthBytes_ :: Integral n => Curve -> n
Documentation
data CryptoParseError Source #
Error that can happen during parsing of cryptographic primitive types.
CryptoParseWrongBase58Check | |
CryptoParseWrongTag ByteString | |
CryptoParseCryptoError CryptoError | |
CryptoParseUnexpectedLength Builder Int | |
CryptoParseBinaryError Text |
Instances
Eq CryptoParseError Source # | |
Defined in Tezos.Crypto.Util (==) :: CryptoParseError -> CryptoParseError -> Bool # (/=) :: CryptoParseError -> CryptoParseError -> Bool # | |
Show CryptoParseError Source # | |
Defined in Tezos.Crypto.Util showsPrec :: Int -> CryptoParseError -> ShowS # show :: CryptoParseError -> String # showList :: [CryptoParseError] -> ShowS # | |
NFData CryptoParseError Source # | |
Defined in Tezos.Crypto.Util rnf :: CryptoParseError -> () # | |
Buildable CryptoParseError Source # | |
Defined in Tezos.Crypto.Util build :: CryptoParseError -> Builder # |
encodeBase58Check :: ByteString -> Text Source #
Encode a bytestring in Base58Check format.
decodeBase58Check :: Text -> Maybe ByteString Source #
Decode a bytestring from Base58Check format.
data B58CheckWithPrefixError Source #
Instances
Show B58CheckWithPrefixError Source # | |
Defined in Tezos.Crypto.Util showsPrec :: Int -> B58CheckWithPrefixError -> ShowS # show :: B58CheckWithPrefixError -> String # showList :: [B58CheckWithPrefixError] -> ShowS # |
decodeBase58CheckWithPrefix :: ByteString -> Text -> Either B58CheckWithPrefixError ByteString Source #
Parse a base58check encoded value expecting some prefix. If the actual prefix matches the expected one, it's stripped of and the resulting payload is returned.
formatImpl :: ByteArrayAccess x => ByteString -> x -> Text Source #
Template for 'format*' functions.
parseImpl :: ByteString -> (ByteString -> Either CryptoParseError res) -> Text -> Either CryptoParseError res Source #
Template for 'parse*' functions.
deterministic :: ByteString -> MonadPseudoRandom ChaChaDRG a -> a Source #
Do randomized action using specified seed.
ECDSA Utils
publicKeyLengthBytes_ :: Integral n => Curve -> n Source #
mkSignature_ :: ByteArray ba => Curve -> ba -> Either CryptoParseError Signature Source #
Make a Signature
from raw bytes.
secretKeyToBytes_ :: ByteArray ba => KeyPair -> ba Source #
Convert a PublicKey
to raw bytes.
signatureToBytes_ :: ByteArray ba => Curve -> Signature -> ba Source #
Convert a PublicKey
to raw bytes.
mkPublicKey_ :: ByteArrayAccess ba => Curve -> ba -> Either CryptoParseError PublicKey Source #
Make a PublicKey
from raw bytes.
Raw bytes are in the format of Compressed SEC Format. Refer to this article on how this is parsed: https://www.oreilly.com/library/view/programming-bitcoin/9781492031482/ch04.html
publicKeyToBytes_ :: forall ba. (ByteArray ba, HasCallStack) => Curve -> PublicKey -> ba Source #
Convert a PublicKey
to raw bytes.
signatureLengthBytes_ :: Integral n => Curve -> n Source #