Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data PubKey
- data PrvKey
- importPubKeyRaw :: Alg -> ByteString -> Maybe PubKey
- importPubKeyPem :: Alg -> ByteString -> Either SE PubKey
- derivePubKey :: PrvKey -> PubKey
- importPrvKeyRaw :: Alg -> ByteString -> Maybe PrvKey
- importPrvKeyPem :: Alg -> ByteString -> Either SE PrvKey
- newRandomPrvKey :: (MonadIO m, MonadFail m) => Alg -> m PrvKey
- newtype Sha256 = Sha256 ByteString
- data Sig
- importSigDer :: Alg -> ByteString -> Maybe Sig
- exportSigDer :: Sig -> ByteString
- class Signable a where
- data Alg = AlgSecp256k1
- data SE
Key
importPubKeyRaw :: Alg -> ByteString -> Maybe PubKey Source #
importPubKeyPem :: Alg -> ByteString -> Either SE PubKey Source #
derivePubKey :: PrvKey -> PubKey Source #
importPrvKeyRaw :: Alg -> ByteString -> Maybe PrvKey Source #
importPrvKeyPem :: Alg -> ByteString -> Either SE PrvKey Source #
Sha256
Signature
importSigDer :: Alg -> ByteString -> Maybe Sig Source #
exportSigDer :: Sig -> ByteString Source #
Class
class Signable a where Source #
toBinary :: a -> ByteString Source #
toSha256 :: a -> Sha256 Source #
Instances
Signable Bool Source # | |
Signable Double Source # | |
Signable Float Source # | |
Signable Int32 Source # | |
Signable Int64 Source # | |
Signable Word32 Source # | |
Signable Word64 Source # | |
Signable ByteString Source # | |
Defined in Data.Signable.Class toBinary :: ByteString -> ByteString Source # toSha256 :: ByteString -> Sha256 Source # | |
Signable ByteString Source # | |
Defined in Data.Signable.Class toBinary :: ByteString -> ByteString0 Source # toSha256 :: ByteString -> Sha256 Source # | |
Signable Text Source # | |
(Foldable f, Signable a) => Signable (f a) Source # | |