{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Bcc.Api.KeysCole (
ColeKey,
ColeKeyLegacy,
AsType(..),
VerificationKey(..),
SigningKey(..),
Hash(..),
IsColeKey(..),
ColeKeyFormat(..),
SomeColeSigningKey(..),
toColeSigningKey
) where
import Bcc.Prelude (cborError, toCborError)
import Prelude
import qualified Codec.CBOR.Decoding as CBOR
import qualified Codec.CBOR.Read as CBOR
import Control.Monad
import qualified Data.ByteString.Lazy as LB
import Data.String (IsString)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Bcc.Crypto.DSIGN.Class as Crypto
import qualified Bcc.Crypto.Seed as Crypto
import qualified Bcc.Crypto.Signing as Crypto
import qualified Bcc.Crypto.Wallet as Crypto.HD
import Bcc.Binary (toStrictByteString)
import qualified Bcc.Chain.Common as Cole
import qualified Bcc.Crypto.Hashing as Cole
import qualified Bcc.Crypto.Signing as Cole
import qualified Bcc.Crypto.Wallet as Wallet
import Bcc.Api.HasTypeProxy
import Bcc.Api.Hash
import Bcc.Api.Key
import Bcc.Api.KeysSophie
import Bcc.Api.SerialiseCBOR
import Bcc.Api.SerialiseRaw
import Bcc.Api.SerialiseTextEnvelope
import Bcc.Api.SerialiseUsing
data ColeKey
data ColeKeyLegacy
class IsColeKey key where
coleKeyFormat :: ColeKeyFormat key
data ColeKeyFormat key where
ColeLegacyKeyFormat :: ColeKeyFormat ColeKeyLegacy
ColeModernKeyFormat :: ColeKeyFormat ColeKey
data SomeColeSigningKey
= AColeSigningKeyLegacy (SigningKey ColeKeyLegacy)
| AColeSigningKey (SigningKey ColeKey)
toColeSigningKey :: SomeColeSigningKey -> Cole.SigningKey
toColeSigningKey :: SomeColeSigningKey -> SigningKey
toColeSigningKey SomeColeSigningKey
bWit =
case SomeColeSigningKey
bWit of
AColeSigningKeyLegacy (ColeSigningKeyLegacy sKey) -> SigningKey
sKey
AColeSigningKey (ColeSigningKey sKey) -> SigningKey
sKey
instance Key ColeKey where
newtype VerificationKey ColeKey =
ColeVerificationKey Cole.VerificationKey
deriving stock VerificationKey ColeKey -> VerificationKey ColeKey -> Bool
(VerificationKey ColeKey -> VerificationKey ColeKey -> Bool)
-> (VerificationKey ColeKey -> VerificationKey ColeKey -> Bool)
-> Eq (VerificationKey ColeKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey ColeKey -> VerificationKey ColeKey -> Bool
$c/= :: VerificationKey ColeKey -> VerificationKey ColeKey -> Bool
== :: VerificationKey ColeKey -> VerificationKey ColeKey -> Bool
$c== :: VerificationKey ColeKey -> VerificationKey ColeKey -> Bool
Eq
deriving (Int -> VerificationKey ColeKey -> ShowS
[VerificationKey ColeKey] -> ShowS
VerificationKey ColeKey -> String
(Int -> VerificationKey ColeKey -> ShowS)
-> (VerificationKey ColeKey -> String)
-> ([VerificationKey ColeKey] -> ShowS)
-> Show (VerificationKey ColeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey ColeKey] -> ShowS
$cshowList :: [VerificationKey ColeKey] -> ShowS
show :: VerificationKey ColeKey -> String
$cshow :: VerificationKey ColeKey -> String
showsPrec :: Int -> VerificationKey ColeKey -> ShowS
$cshowsPrec :: Int -> VerificationKey ColeKey -> ShowS
Show, String -> VerificationKey ColeKey
(String -> VerificationKey ColeKey)
-> IsString (VerificationKey ColeKey)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey ColeKey
$cfromString :: String -> VerificationKey ColeKey
IsString) via UsingRawBytesHex (VerificationKey ColeKey)
deriving newtype (Typeable (VerificationKey ColeKey)
Typeable (VerificationKey ColeKey)
-> (VerificationKey ColeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey ColeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey ColeKey] -> Size)
-> ToCBOR (VerificationKey ColeKey)
VerificationKey ColeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey ColeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey ColeKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey ColeKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey ColeKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey ColeKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey ColeKey) -> Size
toCBOR :: VerificationKey ColeKey -> Encoding
$ctoCBOR :: VerificationKey ColeKey -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey ColeKey)
ToCBOR, Typeable (VerificationKey ColeKey)
Decoder s (VerificationKey ColeKey)
Typeable (VerificationKey ColeKey)
-> (forall s. Decoder s (VerificationKey ColeKey))
-> (Proxy (VerificationKey ColeKey) -> Text)
-> FromCBOR (VerificationKey ColeKey)
Proxy (VerificationKey ColeKey) -> Text
forall s. Decoder s (VerificationKey ColeKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey ColeKey) -> Text
$clabel :: Proxy (VerificationKey ColeKey) -> Text
fromCBOR :: Decoder s (VerificationKey ColeKey)
$cfromCBOR :: forall s. Decoder s (VerificationKey ColeKey)
$cp1FromCBOR :: Typeable (VerificationKey ColeKey)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey ColeKey)
HasTypeProxy (VerificationKey ColeKey)
-> (VerificationKey ColeKey -> ByteString)
-> (AsType (VerificationKey ColeKey)
-> ByteString -> Either DecoderError (VerificationKey ColeKey))
-> SerialiseAsCBOR (VerificationKey ColeKey)
AsType (VerificationKey ColeKey)
-> ByteString -> Either DecoderError (VerificationKey ColeKey)
VerificationKey ColeKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey ColeKey)
-> ByteString -> Either DecoderError (VerificationKey ColeKey)
$cdeserialiseFromCBOR :: AsType (VerificationKey ColeKey)
-> ByteString -> Either DecoderError (VerificationKey ColeKey)
serialiseToCBOR :: VerificationKey ColeKey -> ByteString
$cserialiseToCBOR :: VerificationKey ColeKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey ColeKey)
SerialiseAsCBOR
newtype SigningKey ColeKey =
ColeSigningKey Cole.SigningKey
deriving (Int -> SigningKey ColeKey -> ShowS
[SigningKey ColeKey] -> ShowS
SigningKey ColeKey -> String
(Int -> SigningKey ColeKey -> ShowS)
-> (SigningKey ColeKey -> String)
-> ([SigningKey ColeKey] -> ShowS)
-> Show (SigningKey ColeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey ColeKey] -> ShowS
$cshowList :: [SigningKey ColeKey] -> ShowS
show :: SigningKey ColeKey -> String
$cshow :: SigningKey ColeKey -> String
showsPrec :: Int -> SigningKey ColeKey -> ShowS
$cshowsPrec :: Int -> SigningKey ColeKey -> ShowS
Show, String -> SigningKey ColeKey
(String -> SigningKey ColeKey) -> IsString (SigningKey ColeKey)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey ColeKey
$cfromString :: String -> SigningKey ColeKey
IsString) via UsingRawBytesHex (SigningKey ColeKey)
deriving newtype (Typeable (SigningKey ColeKey)
Typeable (SigningKey ColeKey)
-> (SigningKey ColeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey ColeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey ColeKey] -> Size)
-> ToCBOR (SigningKey ColeKey)
SigningKey ColeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey ColeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey ColeKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey ColeKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey ColeKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey ColeKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey ColeKey) -> Size
toCBOR :: SigningKey ColeKey -> Encoding
$ctoCBOR :: SigningKey ColeKey -> Encoding
$cp1ToCBOR :: Typeable (SigningKey ColeKey)
ToCBOR, Typeable (SigningKey ColeKey)
Decoder s (SigningKey ColeKey)
Typeable (SigningKey ColeKey)
-> (forall s. Decoder s (SigningKey ColeKey))
-> (Proxy (SigningKey ColeKey) -> Text)
-> FromCBOR (SigningKey ColeKey)
Proxy (SigningKey ColeKey) -> Text
forall s. Decoder s (SigningKey ColeKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey ColeKey) -> Text
$clabel :: Proxy (SigningKey ColeKey) -> Text
fromCBOR :: Decoder s (SigningKey ColeKey)
$cfromCBOR :: forall s. Decoder s (SigningKey ColeKey)
$cp1FromCBOR :: Typeable (SigningKey ColeKey)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey ColeKey)
HasTypeProxy (SigningKey ColeKey)
-> (SigningKey ColeKey -> ByteString)
-> (AsType (SigningKey ColeKey)
-> ByteString -> Either DecoderError (SigningKey ColeKey))
-> SerialiseAsCBOR (SigningKey ColeKey)
AsType (SigningKey ColeKey)
-> ByteString -> Either DecoderError (SigningKey ColeKey)
SigningKey ColeKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey ColeKey)
-> ByteString -> Either DecoderError (SigningKey ColeKey)
$cdeserialiseFromCBOR :: AsType (SigningKey ColeKey)
-> ByteString -> Either DecoderError (SigningKey ColeKey)
serialiseToCBOR :: SigningKey ColeKey -> ByteString
$cserialiseToCBOR :: SigningKey ColeKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey ColeKey)
SerialiseAsCBOR
deterministicSigningKey :: AsType ColeKey -> Crypto.Seed -> SigningKey ColeKey
deterministicSigningKey :: AsType ColeKey -> Seed -> SigningKey ColeKey
deterministicSigningKey AsType ColeKey
AsColeKey Seed
seed =
SigningKey -> SigningKey ColeKey
ColeSigningKey ((VerificationKey, SigningKey) -> SigningKey
forall a b. (a, b) -> b
snd (Seed
-> (forall (m :: * -> *).
MonadRandom m =>
m (VerificationKey, SigningKey))
-> (VerificationKey, SigningKey)
forall a. Seed -> (forall (m :: * -> *). MonadRandom m => m a) -> a
Crypto.runMonadRandomWithSeed Seed
seed forall (m :: * -> *).
MonadRandom m =>
m (VerificationKey, SigningKey)
Cole.keyGen))
deterministicSigningKeySeedSize :: AsType ColeKey -> Word
deterministicSigningKeySeedSize :: AsType ColeKey -> Word
deterministicSigningKeySeedSize AsType ColeKey
AsColeKey = Word
32
getVerificationKey :: SigningKey ColeKey -> VerificationKey ColeKey
getVerificationKey :: SigningKey ColeKey -> VerificationKey ColeKey
getVerificationKey (ColeSigningKey sk) =
VerificationKey -> VerificationKey ColeKey
ColeVerificationKey (SigningKey -> VerificationKey
Cole.toVerification SigningKey
sk)
verificationKeyHash :: VerificationKey ColeKey -> Hash ColeKey
verificationKeyHash :: VerificationKey ColeKey -> Hash ColeKey
verificationKeyHash (ColeVerificationKey vkey) =
KeyHash -> Hash ColeKey
ColeKeyHash (VerificationKey -> KeyHash
Cole.hashKey VerificationKey
vkey)
instance HasTypeProxy ColeKey where
data AsType ColeKey = AsColeKey
proxyToAsType :: Proxy ColeKey -> AsType ColeKey
proxyToAsType Proxy ColeKey
_ = AsType ColeKey
AsColeKey
instance HasTextEnvelope (VerificationKey ColeKey) where
textEnvelopeType :: AsType (VerificationKey ColeKey) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey ColeKey)
_ = TextEnvelopeType
"PaymentVerificationKeyCole_ed25519_bip32"
instance HasTextEnvelope (SigningKey ColeKey) where
textEnvelopeType :: AsType (SigningKey ColeKey) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey ColeKey)
_ = TextEnvelopeType
"PaymentSigningKeyCole_ed25519_bip32"
instance SerialiseAsRawBytes (VerificationKey ColeKey) where
serialiseToRawBytes :: VerificationKey ColeKey -> ByteString
serialiseToRawBytes (ColeVerificationKey (Cole.VerificationKey xvk)) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xvk
deserialiseFromRawBytes :: AsType (VerificationKey ColeKey)
-> ByteString -> Maybe (VerificationKey ColeKey)
deserialiseFromRawBytes (AsVerificationKey AsColeKey) ByteString
bs =
(String -> Maybe (VerificationKey ColeKey))
-> (XPub -> Maybe (VerificationKey ColeKey))
-> Either String XPub
-> Maybe (VerificationKey ColeKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey ColeKey)
-> String -> Maybe (VerificationKey ColeKey)
forall a b. a -> b -> a
const Maybe (VerificationKey ColeKey)
forall a. Maybe a
Nothing) (VerificationKey ColeKey -> Maybe (VerificationKey ColeKey)
forall a. a -> Maybe a
Just (VerificationKey ColeKey -> Maybe (VerificationKey ColeKey))
-> (XPub -> VerificationKey ColeKey)
-> XPub
-> Maybe (VerificationKey ColeKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerificationKey -> VerificationKey ColeKey
ColeVerificationKey (VerificationKey -> VerificationKey ColeKey)
-> (XPub -> VerificationKey) -> XPub -> VerificationKey ColeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey
Cole.VerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey ColeKey) where
serialiseToRawBytes :: SigningKey ColeKey -> ByteString
serialiseToRawBytes (ColeSigningKey (Cole.SigningKey xsk)) =
Encoding -> ByteString
toStrictByteString (Encoding -> ByteString) -> Encoding -> ByteString
forall a b. (a -> b) -> a -> b
$ XPrv -> Encoding
Crypto.toCBORXPrv XPrv
xsk
deserialiseFromRawBytes :: AsType (SigningKey ColeKey)
-> ByteString -> Maybe (SigningKey ColeKey)
deserialiseFromRawBytes (AsSigningKey AsColeKey) ByteString
bs =
(DeserialiseFailure -> Maybe (SigningKey ColeKey))
-> (XPrv -> Maybe (SigningKey ColeKey))
-> Either DeserialiseFailure XPrv
-> Maybe (SigningKey ColeKey)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey ColeKey)
-> DeserialiseFailure -> Maybe (SigningKey ColeKey)
forall a b. a -> b -> a
const Maybe (SigningKey ColeKey)
forall a. Maybe a
Nothing) (SigningKey ColeKey -> Maybe (SigningKey ColeKey)
forall a. a -> Maybe a
Just (SigningKey ColeKey -> Maybe (SigningKey ColeKey))
-> (XPrv -> SigningKey ColeKey)
-> XPrv
-> Maybe (SigningKey ColeKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SigningKey -> SigningKey ColeKey
ColeSigningKey (SigningKey -> SigningKey ColeKey)
-> (XPrv -> SigningKey) -> XPrv -> SigningKey ColeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey
Cole.SigningKey)
((ByteString, XPrv) -> XPrv
forall a b. (a, b) -> b
snd ((ByteString, XPrv) -> XPrv)
-> Either DeserialiseFailure (ByteString, XPrv)
-> Either DeserialiseFailure XPrv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall s. Decoder s XPrv)
-> ByteString -> Either DeserialiseFailure (ByteString, XPrv)
forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure (ByteString, a)
CBOR.deserialiseFromBytes forall s. Decoder s XPrv
Cole.fromCBORXPrv (ByteString -> ByteString
LB.fromStrict ByteString
bs))
newtype instance Hash ColeKey = ColeKeyHash Cole.KeyHash
deriving (Hash ColeKey -> Hash ColeKey -> Bool
(Hash ColeKey -> Hash ColeKey -> Bool)
-> (Hash ColeKey -> Hash ColeKey -> Bool) -> Eq (Hash ColeKey)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash ColeKey -> Hash ColeKey -> Bool
$c/= :: Hash ColeKey -> Hash ColeKey -> Bool
== :: Hash ColeKey -> Hash ColeKey -> Bool
$c== :: Hash ColeKey -> Hash ColeKey -> Bool
Eq, Eq (Hash ColeKey)
Eq (Hash ColeKey)
-> (Hash ColeKey -> Hash ColeKey -> Ordering)
-> (Hash ColeKey -> Hash ColeKey -> Bool)
-> (Hash ColeKey -> Hash ColeKey -> Bool)
-> (Hash ColeKey -> Hash ColeKey -> Bool)
-> (Hash ColeKey -> Hash ColeKey -> Bool)
-> (Hash ColeKey -> Hash ColeKey -> Hash ColeKey)
-> (Hash ColeKey -> Hash ColeKey -> Hash ColeKey)
-> Ord (Hash ColeKey)
Hash ColeKey -> Hash ColeKey -> Bool
Hash ColeKey -> Hash ColeKey -> Ordering
Hash ColeKey -> Hash ColeKey -> Hash ColeKey
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Hash ColeKey -> Hash ColeKey -> Hash ColeKey
$cmin :: Hash ColeKey -> Hash ColeKey -> Hash ColeKey
max :: Hash ColeKey -> Hash ColeKey -> Hash ColeKey
$cmax :: Hash ColeKey -> Hash ColeKey -> Hash ColeKey
>= :: Hash ColeKey -> Hash ColeKey -> Bool
$c>= :: Hash ColeKey -> Hash ColeKey -> Bool
> :: Hash ColeKey -> Hash ColeKey -> Bool
$c> :: Hash ColeKey -> Hash ColeKey -> Bool
<= :: Hash ColeKey -> Hash ColeKey -> Bool
$c<= :: Hash ColeKey -> Hash ColeKey -> Bool
< :: Hash ColeKey -> Hash ColeKey -> Bool
$c< :: Hash ColeKey -> Hash ColeKey -> Bool
compare :: Hash ColeKey -> Hash ColeKey -> Ordering
$ccompare :: Hash ColeKey -> Hash ColeKey -> Ordering
$cp1Ord :: Eq (Hash ColeKey)
Ord)
deriving (Int -> Hash ColeKey -> ShowS
[Hash ColeKey] -> ShowS
Hash ColeKey -> String
(Int -> Hash ColeKey -> ShowS)
-> (Hash ColeKey -> String)
-> ([Hash ColeKey] -> ShowS)
-> Show (Hash ColeKey)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash ColeKey] -> ShowS
$cshowList :: [Hash ColeKey] -> ShowS
show :: Hash ColeKey -> String
$cshow :: Hash ColeKey -> String
showsPrec :: Int -> Hash ColeKey -> ShowS
$cshowsPrec :: Int -> Hash ColeKey -> ShowS
Show, String -> Hash ColeKey
(String -> Hash ColeKey) -> IsString (Hash ColeKey)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash ColeKey
$cfromString :: String -> Hash ColeKey
IsString) via UsingRawBytesHex (Hash ColeKey)
deriving (Typeable (Hash ColeKey)
Typeable (Hash ColeKey)
-> (Hash ColeKey -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash ColeKey) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash ColeKey] -> Size)
-> ToCBOR (Hash ColeKey)
Hash ColeKey -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash ColeKey] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash ColeKey) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash ColeKey] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash ColeKey] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash ColeKey) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash ColeKey) -> Size
toCBOR :: Hash ColeKey -> Encoding
$ctoCBOR :: Hash ColeKey -> Encoding
$cp1ToCBOR :: Typeable (Hash ColeKey)
ToCBOR, Typeable (Hash ColeKey)
Decoder s (Hash ColeKey)
Typeable (Hash ColeKey)
-> (forall s. Decoder s (Hash ColeKey))
-> (Proxy (Hash ColeKey) -> Text)
-> FromCBOR (Hash ColeKey)
Proxy (Hash ColeKey) -> Text
forall s. Decoder s (Hash ColeKey)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash ColeKey) -> Text
$clabel :: Proxy (Hash ColeKey) -> Text
fromCBOR :: Decoder s (Hash ColeKey)
$cfromCBOR :: forall s. Decoder s (Hash ColeKey)
$cp1FromCBOR :: Typeable (Hash ColeKey)
FromCBOR) via UsingRawBytes (Hash ColeKey)
deriving anyclass HasTypeProxy (Hash ColeKey)
HasTypeProxy (Hash ColeKey)
-> (Hash ColeKey -> ByteString)
-> (AsType (Hash ColeKey)
-> ByteString -> Either DecoderError (Hash ColeKey))
-> SerialiseAsCBOR (Hash ColeKey)
AsType (Hash ColeKey)
-> ByteString -> Either DecoderError (Hash ColeKey)
Hash ColeKey -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash ColeKey)
-> ByteString -> Either DecoderError (Hash ColeKey)
$cdeserialiseFromCBOR :: AsType (Hash ColeKey)
-> ByteString -> Either DecoderError (Hash ColeKey)
serialiseToCBOR :: Hash ColeKey -> ByteString
$cserialiseToCBOR :: Hash ColeKey -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash ColeKey)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash ColeKey) where
serialiseToRawBytes :: Hash ColeKey -> ByteString
serialiseToRawBytes (ColeKeyHash (Cole.KeyHash vkh)) =
AbstractHash Blake2b_224 VerificationKey -> ByteString
forall algo a. AbstractHash algo a -> ByteString
Cole.abstractHashToBytes AbstractHash Blake2b_224 VerificationKey
vkh
deserialiseFromRawBytes :: AsType (Hash ColeKey) -> ByteString -> Maybe (Hash ColeKey)
deserialiseFromRawBytes (AsHash AsColeKey) ByteString
bs =
KeyHash -> Hash ColeKey
ColeKeyHash (KeyHash -> Hash ColeKey)
-> (AbstractHash Blake2b_224 VerificationKey -> KeyHash)
-> AbstractHash Blake2b_224 VerificationKey
-> Hash ColeKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AbstractHash Blake2b_224 VerificationKey -> KeyHash
Cole.KeyHash (AbstractHash Blake2b_224 VerificationKey -> Hash ColeKey)
-> Maybe (AbstractHash Blake2b_224 VerificationKey)
-> Maybe (Hash ColeKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (AbstractHash Blake2b_224 VerificationKey)
forall algo a.
HashAlgorithm algo =>
ByteString -> Maybe (AbstractHash algo a)
Cole.abstractHashFromBytes ByteString
bs
instance CastVerificationKeyRole ColeKey PaymentExtendedKey where
castVerificationKey :: VerificationKey ColeKey -> VerificationKey PaymentExtendedKey
castVerificationKey (ColeVerificationKey vk) =
XPub -> VerificationKey PaymentExtendedKey
PaymentExtendedVerificationKey
(VerificationKey -> XPub
Cole.unVerificationKey VerificationKey
vk)
instance CastVerificationKeyRole ColeKey PaymentKey where
castVerificationKey :: VerificationKey ColeKey -> VerificationKey PaymentKey
castVerificationKey =
(VerificationKey PaymentExtendedKey -> VerificationKey PaymentKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey :: VerificationKey PaymentExtendedKey
-> VerificationKey PaymentKey)
(VerificationKey PaymentExtendedKey -> VerificationKey PaymentKey)
-> (VerificationKey ColeKey -> VerificationKey PaymentExtendedKey)
-> VerificationKey ColeKey
-> VerificationKey PaymentKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VerificationKey ColeKey -> VerificationKey PaymentExtendedKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey :: VerificationKey ColeKey
-> VerificationKey PaymentExtendedKey)
instance IsColeKey ColeKey where
coleKeyFormat :: ColeKeyFormat ColeKey
coleKeyFormat = ColeKeyFormat ColeKey
ColeModernKeyFormat
instance Key ColeKeyLegacy where
newtype VerificationKey ColeKeyLegacy =
ColeVerificationKeyLegacy Cole.VerificationKey
deriving stock (VerificationKey ColeKeyLegacy
-> VerificationKey ColeKeyLegacy -> Bool
(VerificationKey ColeKeyLegacy
-> VerificationKey ColeKeyLegacy -> Bool)
-> (VerificationKey ColeKeyLegacy
-> VerificationKey ColeKeyLegacy -> Bool)
-> Eq (VerificationKey ColeKeyLegacy)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKey ColeKeyLegacy
-> VerificationKey ColeKeyLegacy -> Bool
$c/= :: VerificationKey ColeKeyLegacy
-> VerificationKey ColeKeyLegacy -> Bool
== :: VerificationKey ColeKeyLegacy
-> VerificationKey ColeKeyLegacy -> Bool
$c== :: VerificationKey ColeKeyLegacy
-> VerificationKey ColeKeyLegacy -> Bool
Eq)
deriving (Int -> VerificationKey ColeKeyLegacy -> ShowS
[VerificationKey ColeKeyLegacy] -> ShowS
VerificationKey ColeKeyLegacy -> String
(Int -> VerificationKey ColeKeyLegacy -> ShowS)
-> (VerificationKey ColeKeyLegacy -> String)
-> ([VerificationKey ColeKeyLegacy] -> ShowS)
-> Show (VerificationKey ColeKeyLegacy)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKey ColeKeyLegacy] -> ShowS
$cshowList :: [VerificationKey ColeKeyLegacy] -> ShowS
show :: VerificationKey ColeKeyLegacy -> String
$cshow :: VerificationKey ColeKeyLegacy -> String
showsPrec :: Int -> VerificationKey ColeKeyLegacy -> ShowS
$cshowsPrec :: Int -> VerificationKey ColeKeyLegacy -> ShowS
Show, String -> VerificationKey ColeKeyLegacy
(String -> VerificationKey ColeKeyLegacy)
-> IsString (VerificationKey ColeKeyLegacy)
forall a. (String -> a) -> IsString a
fromString :: String -> VerificationKey ColeKeyLegacy
$cfromString :: String -> VerificationKey ColeKeyLegacy
IsString) via UsingRawBytesHex (VerificationKey ColeKeyLegacy)
deriving newtype (Typeable (VerificationKey ColeKeyLegacy)
Typeable (VerificationKey ColeKeyLegacy)
-> (VerificationKey ColeKeyLegacy -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey ColeKeyLegacy) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey ColeKeyLegacy] -> Size)
-> ToCBOR (VerificationKey ColeKeyLegacy)
VerificationKey ColeKeyLegacy -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey ColeKeyLegacy] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey ColeKeyLegacy) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey ColeKeyLegacy] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [VerificationKey ColeKeyLegacy] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey ColeKeyLegacy) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerificationKey ColeKeyLegacy) -> Size
toCBOR :: VerificationKey ColeKeyLegacy -> Encoding
$ctoCBOR :: VerificationKey ColeKeyLegacy -> Encoding
$cp1ToCBOR :: Typeable (VerificationKey ColeKeyLegacy)
ToCBOR, Typeable (VerificationKey ColeKeyLegacy)
Decoder s (VerificationKey ColeKeyLegacy)
Typeable (VerificationKey ColeKeyLegacy)
-> (forall s. Decoder s (VerificationKey ColeKeyLegacy))
-> (Proxy (VerificationKey ColeKeyLegacy) -> Text)
-> FromCBOR (VerificationKey ColeKeyLegacy)
Proxy (VerificationKey ColeKeyLegacy) -> Text
forall s. Decoder s (VerificationKey ColeKeyLegacy)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (VerificationKey ColeKeyLegacy) -> Text
$clabel :: Proxy (VerificationKey ColeKeyLegacy) -> Text
fromCBOR :: Decoder s (VerificationKey ColeKeyLegacy)
$cfromCBOR :: forall s. Decoder s (VerificationKey ColeKeyLegacy)
$cp1FromCBOR :: Typeable (VerificationKey ColeKeyLegacy)
FromCBOR)
deriving anyclass HasTypeProxy (VerificationKey ColeKeyLegacy)
HasTypeProxy (VerificationKey ColeKeyLegacy)
-> (VerificationKey ColeKeyLegacy -> ByteString)
-> (AsType (VerificationKey ColeKeyLegacy)
-> ByteString
-> Either DecoderError (VerificationKey ColeKeyLegacy))
-> SerialiseAsCBOR (VerificationKey ColeKeyLegacy)
AsType (VerificationKey ColeKeyLegacy)
-> ByteString
-> Either DecoderError (VerificationKey ColeKeyLegacy)
VerificationKey ColeKeyLegacy -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (VerificationKey ColeKeyLegacy)
-> ByteString
-> Either DecoderError (VerificationKey ColeKeyLegacy)
$cdeserialiseFromCBOR :: AsType (VerificationKey ColeKeyLegacy)
-> ByteString
-> Either DecoderError (VerificationKey ColeKeyLegacy)
serialiseToCBOR :: VerificationKey ColeKeyLegacy -> ByteString
$cserialiseToCBOR :: VerificationKey ColeKeyLegacy -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (VerificationKey ColeKeyLegacy)
SerialiseAsCBOR
newtype SigningKey ColeKeyLegacy =
ColeSigningKeyLegacy Cole.SigningKey
deriving (Int -> SigningKey ColeKeyLegacy -> ShowS
[SigningKey ColeKeyLegacy] -> ShowS
SigningKey ColeKeyLegacy -> String
(Int -> SigningKey ColeKeyLegacy -> ShowS)
-> (SigningKey ColeKeyLegacy -> String)
-> ([SigningKey ColeKeyLegacy] -> ShowS)
-> Show (SigningKey ColeKeyLegacy)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKey ColeKeyLegacy] -> ShowS
$cshowList :: [SigningKey ColeKeyLegacy] -> ShowS
show :: SigningKey ColeKeyLegacy -> String
$cshow :: SigningKey ColeKeyLegacy -> String
showsPrec :: Int -> SigningKey ColeKeyLegacy -> ShowS
$cshowsPrec :: Int -> SigningKey ColeKeyLegacy -> ShowS
Show, String -> SigningKey ColeKeyLegacy
(String -> SigningKey ColeKeyLegacy)
-> IsString (SigningKey ColeKeyLegacy)
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKey ColeKeyLegacy
$cfromString :: String -> SigningKey ColeKeyLegacy
IsString) via UsingRawBytesHex (SigningKey ColeKeyLegacy)
deriving newtype (Typeable (SigningKey ColeKeyLegacy)
Typeable (SigningKey ColeKeyLegacy)
-> (SigningKey ColeKeyLegacy -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey ColeKeyLegacy) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey ColeKeyLegacy] -> Size)
-> ToCBOR (SigningKey ColeKeyLegacy)
SigningKey ColeKeyLegacy -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey ColeKeyLegacy] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey ColeKeyLegacy) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey ColeKeyLegacy] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [SigningKey ColeKeyLegacy] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey ColeKeyLegacy) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigningKey ColeKeyLegacy) -> Size
toCBOR :: SigningKey ColeKeyLegacy -> Encoding
$ctoCBOR :: SigningKey ColeKeyLegacy -> Encoding
$cp1ToCBOR :: Typeable (SigningKey ColeKeyLegacy)
ToCBOR, Typeable (SigningKey ColeKeyLegacy)
Decoder s (SigningKey ColeKeyLegacy)
Typeable (SigningKey ColeKeyLegacy)
-> (forall s. Decoder s (SigningKey ColeKeyLegacy))
-> (Proxy (SigningKey ColeKeyLegacy) -> Text)
-> FromCBOR (SigningKey ColeKeyLegacy)
Proxy (SigningKey ColeKeyLegacy) -> Text
forall s. Decoder s (SigningKey ColeKeyLegacy)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (SigningKey ColeKeyLegacy) -> Text
$clabel :: Proxy (SigningKey ColeKeyLegacy) -> Text
fromCBOR :: Decoder s (SigningKey ColeKeyLegacy)
$cfromCBOR :: forall s. Decoder s (SigningKey ColeKeyLegacy)
$cp1FromCBOR :: Typeable (SigningKey ColeKeyLegacy)
FromCBOR)
deriving anyclass HasTypeProxy (SigningKey ColeKeyLegacy)
HasTypeProxy (SigningKey ColeKeyLegacy)
-> (SigningKey ColeKeyLegacy -> ByteString)
-> (AsType (SigningKey ColeKeyLegacy)
-> ByteString -> Either DecoderError (SigningKey ColeKeyLegacy))
-> SerialiseAsCBOR (SigningKey ColeKeyLegacy)
AsType (SigningKey ColeKeyLegacy)
-> ByteString -> Either DecoderError (SigningKey ColeKeyLegacy)
SigningKey ColeKeyLegacy -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (SigningKey ColeKeyLegacy)
-> ByteString -> Either DecoderError (SigningKey ColeKeyLegacy)
$cdeserialiseFromCBOR :: AsType (SigningKey ColeKeyLegacy)
-> ByteString -> Either DecoderError (SigningKey ColeKeyLegacy)
serialiseToCBOR :: SigningKey ColeKeyLegacy -> ByteString
$cserialiseToCBOR :: SigningKey ColeKeyLegacy -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (SigningKey ColeKeyLegacy)
SerialiseAsCBOR
deterministicSigningKey :: AsType ColeKeyLegacy -> Crypto.Seed -> SigningKey ColeKeyLegacy
deterministicSigningKey :: AsType ColeKeyLegacy -> Seed -> SigningKey ColeKeyLegacy
deterministicSigningKey AsType ColeKeyLegacy
_ Seed
_ = String -> SigningKey ColeKeyLegacy
forall a. HasCallStack => String -> a
error String
"Please generate a non legacy Cole key instead"
deterministicSigningKeySeedSize :: AsType ColeKeyLegacy -> Word
deterministicSigningKeySeedSize :: AsType ColeKeyLegacy -> Word
deterministicSigningKeySeedSize AsType ColeKeyLegacy
AsColeKeyLegacy = Word
32
getVerificationKey :: SigningKey ColeKeyLegacy -> VerificationKey ColeKeyLegacy
getVerificationKey :: SigningKey ColeKeyLegacy -> VerificationKey ColeKeyLegacy
getVerificationKey (ColeSigningKeyLegacy sk) =
VerificationKey -> VerificationKey ColeKeyLegacy
ColeVerificationKeyLegacy (SigningKey -> VerificationKey
Cole.toVerification SigningKey
sk)
verificationKeyHash :: VerificationKey ColeKeyLegacy -> Hash ColeKeyLegacy
verificationKeyHash :: VerificationKey ColeKeyLegacy -> Hash ColeKeyLegacy
verificationKeyHash (ColeVerificationKeyLegacy vkey) =
KeyHash -> Hash ColeKeyLegacy
ColeKeyHashLegacy (VerificationKey -> KeyHash
Cole.hashKey VerificationKey
vkey)
instance HasTypeProxy ColeKeyLegacy where
data AsType ColeKeyLegacy = AsColeKeyLegacy
proxyToAsType :: Proxy ColeKeyLegacy -> AsType ColeKeyLegacy
proxyToAsType Proxy ColeKeyLegacy
_ = AsType ColeKeyLegacy
AsColeKeyLegacy
instance HasTextEnvelope (VerificationKey ColeKeyLegacy) where
textEnvelopeType :: AsType (VerificationKey ColeKeyLegacy) -> TextEnvelopeType
textEnvelopeType AsType (VerificationKey ColeKeyLegacy)
_ = TextEnvelopeType
"PaymentVerificationKeyColeLegacy_ed25519_bip32"
instance HasTextEnvelope (SigningKey ColeKeyLegacy) where
textEnvelopeType :: AsType (SigningKey ColeKeyLegacy) -> TextEnvelopeType
textEnvelopeType AsType (SigningKey ColeKeyLegacy)
_ = TextEnvelopeType
"PaymentSigningKeyColeLegacy_ed25519_bip32"
newtype instance Hash ColeKeyLegacy = ColeKeyHashLegacy Cole.KeyHash
deriving (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
(Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool)
-> (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool)
-> Eq (Hash ColeKeyLegacy)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
$c/= :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
== :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
$c== :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
Eq, Eq (Hash ColeKeyLegacy)
Eq (Hash ColeKeyLegacy)
-> (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Ordering)
-> (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool)
-> (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool)
-> (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool)
-> (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool)
-> (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Hash ColeKeyLegacy)
-> (Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Hash ColeKeyLegacy)
-> Ord (Hash ColeKeyLegacy)
Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Ordering
Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Hash ColeKeyLegacy
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Hash ColeKeyLegacy
$cmin :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Hash ColeKeyLegacy
max :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Hash ColeKeyLegacy
$cmax :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Hash ColeKeyLegacy
>= :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
$c>= :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
> :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
$c> :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
<= :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
$c<= :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
< :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
$c< :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Bool
compare :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Ordering
$ccompare :: Hash ColeKeyLegacy -> Hash ColeKeyLegacy -> Ordering
$cp1Ord :: Eq (Hash ColeKeyLegacy)
Ord)
deriving (Int -> Hash ColeKeyLegacy -> ShowS
[Hash ColeKeyLegacy] -> ShowS
Hash ColeKeyLegacy -> String
(Int -> Hash ColeKeyLegacy -> ShowS)
-> (Hash ColeKeyLegacy -> String)
-> ([Hash ColeKeyLegacy] -> ShowS)
-> Show (Hash ColeKeyLegacy)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hash ColeKeyLegacy] -> ShowS
$cshowList :: [Hash ColeKeyLegacy] -> ShowS
show :: Hash ColeKeyLegacy -> String
$cshow :: Hash ColeKeyLegacy -> String
showsPrec :: Int -> Hash ColeKeyLegacy -> ShowS
$cshowsPrec :: Int -> Hash ColeKeyLegacy -> ShowS
Show, String -> Hash ColeKeyLegacy
(String -> Hash ColeKeyLegacy) -> IsString (Hash ColeKeyLegacy)
forall a. (String -> a) -> IsString a
fromString :: String -> Hash ColeKeyLegacy
$cfromString :: String -> Hash ColeKeyLegacy
IsString) via UsingRawBytesHex (Hash ColeKeyLegacy)
deriving (Typeable (Hash ColeKeyLegacy)
Typeable (Hash ColeKeyLegacy)
-> (Hash ColeKeyLegacy -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash ColeKeyLegacy) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash ColeKeyLegacy] -> Size)
-> ToCBOR (Hash ColeKeyLegacy)
Hash ColeKeyLegacy -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash ColeKeyLegacy] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash ColeKeyLegacy) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash ColeKeyLegacy] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [Hash ColeKeyLegacy] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash ColeKeyLegacy) -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (Hash ColeKeyLegacy) -> Size
toCBOR :: Hash ColeKeyLegacy -> Encoding
$ctoCBOR :: Hash ColeKeyLegacy -> Encoding
$cp1ToCBOR :: Typeable (Hash ColeKeyLegacy)
ToCBOR, Typeable (Hash ColeKeyLegacy)
Decoder s (Hash ColeKeyLegacy)
Typeable (Hash ColeKeyLegacy)
-> (forall s. Decoder s (Hash ColeKeyLegacy))
-> (Proxy (Hash ColeKeyLegacy) -> Text)
-> FromCBOR (Hash ColeKeyLegacy)
Proxy (Hash ColeKeyLegacy) -> Text
forall s. Decoder s (Hash ColeKeyLegacy)
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy (Hash ColeKeyLegacy) -> Text
$clabel :: Proxy (Hash ColeKeyLegacy) -> Text
fromCBOR :: Decoder s (Hash ColeKeyLegacy)
$cfromCBOR :: forall s. Decoder s (Hash ColeKeyLegacy)
$cp1FromCBOR :: Typeable (Hash ColeKeyLegacy)
FromCBOR) via UsingRawBytes (Hash ColeKeyLegacy)
deriving anyclass HasTypeProxy (Hash ColeKeyLegacy)
HasTypeProxy (Hash ColeKeyLegacy)
-> (Hash ColeKeyLegacy -> ByteString)
-> (AsType (Hash ColeKeyLegacy)
-> ByteString -> Either DecoderError (Hash ColeKeyLegacy))
-> SerialiseAsCBOR (Hash ColeKeyLegacy)
AsType (Hash ColeKeyLegacy)
-> ByteString -> Either DecoderError (Hash ColeKeyLegacy)
Hash ColeKeyLegacy -> ByteString
forall a.
HasTypeProxy a
-> (a -> ByteString)
-> (AsType a -> ByteString -> Either DecoderError a)
-> SerialiseAsCBOR a
deserialiseFromCBOR :: AsType (Hash ColeKeyLegacy)
-> ByteString -> Either DecoderError (Hash ColeKeyLegacy)
$cdeserialiseFromCBOR :: AsType (Hash ColeKeyLegacy)
-> ByteString -> Either DecoderError (Hash ColeKeyLegacy)
serialiseToCBOR :: Hash ColeKeyLegacy -> ByteString
$cserialiseToCBOR :: Hash ColeKeyLegacy -> ByteString
$cp1SerialiseAsCBOR :: HasTypeProxy (Hash ColeKeyLegacy)
SerialiseAsCBOR
instance SerialiseAsRawBytes (Hash ColeKeyLegacy) where
serialiseToRawBytes :: Hash ColeKeyLegacy -> ByteString
serialiseToRawBytes (ColeKeyHashLegacy (Cole.KeyHash vkh)) =
AbstractHash Blake2b_224 VerificationKey -> ByteString
forall algo a. AbstractHash algo a -> ByteString
Cole.abstractHashToBytes AbstractHash Blake2b_224 VerificationKey
vkh
deserialiseFromRawBytes :: AsType (Hash ColeKeyLegacy)
-> ByteString -> Maybe (Hash ColeKeyLegacy)
deserialiseFromRawBytes (AsHash AsColeKeyLegacy) ByteString
bs =
KeyHash -> Hash ColeKeyLegacy
ColeKeyHashLegacy (KeyHash -> Hash ColeKeyLegacy)
-> (AbstractHash Blake2b_224 VerificationKey -> KeyHash)
-> AbstractHash Blake2b_224 VerificationKey
-> Hash ColeKeyLegacy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AbstractHash Blake2b_224 VerificationKey -> KeyHash
Cole.KeyHash (AbstractHash Blake2b_224 VerificationKey -> Hash ColeKeyLegacy)
-> Maybe (AbstractHash Blake2b_224 VerificationKey)
-> Maybe (Hash ColeKeyLegacy)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (AbstractHash Blake2b_224 VerificationKey)
forall algo a.
HashAlgorithm algo =>
ByteString -> Maybe (AbstractHash algo a)
Cole.abstractHashFromBytes ByteString
bs
instance SerialiseAsRawBytes (VerificationKey ColeKeyLegacy) where
serialiseToRawBytes :: VerificationKey ColeKeyLegacy -> ByteString
serialiseToRawBytes (ColeVerificationKeyLegacy (Cole.VerificationKey xvk)) =
XPub -> ByteString
Crypto.HD.unXPub XPub
xvk
deserialiseFromRawBytes :: AsType (VerificationKey ColeKeyLegacy)
-> ByteString -> Maybe (VerificationKey ColeKeyLegacy)
deserialiseFromRawBytes (AsVerificationKey AsColeKeyLegacy) ByteString
bs =
(String -> Maybe (VerificationKey ColeKeyLegacy))
-> (XPub -> Maybe (VerificationKey ColeKeyLegacy))
-> Either String XPub
-> Maybe (VerificationKey ColeKeyLegacy)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerificationKey ColeKeyLegacy)
-> String -> Maybe (VerificationKey ColeKeyLegacy)
forall a b. a -> b -> a
const Maybe (VerificationKey ColeKeyLegacy)
forall a. Maybe a
Nothing) (VerificationKey ColeKeyLegacy
-> Maybe (VerificationKey ColeKeyLegacy)
forall a. a -> Maybe a
Just (VerificationKey ColeKeyLegacy
-> Maybe (VerificationKey ColeKeyLegacy))
-> (XPub -> VerificationKey ColeKeyLegacy)
-> XPub
-> Maybe (VerificationKey ColeKeyLegacy)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerificationKey -> VerificationKey ColeKeyLegacy
ColeVerificationKeyLegacy (VerificationKey -> VerificationKey ColeKeyLegacy)
-> (XPub -> VerificationKey)
-> XPub
-> VerificationKey ColeKeyLegacy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPub -> VerificationKey
Cole.VerificationKey)
(ByteString -> Either String XPub
Crypto.HD.xpub ByteString
bs)
instance SerialiseAsRawBytes (SigningKey ColeKeyLegacy) where
serialiseToRawBytes :: SigningKey ColeKeyLegacy -> ByteString
serialiseToRawBytes (ColeSigningKeyLegacy (Cole.SigningKey xsk)) =
XPrv -> ByteString
Crypto.HD.unXPrv XPrv
xsk
deserialiseFromRawBytes :: AsType (SigningKey ColeKeyLegacy)
-> ByteString -> Maybe (SigningKey ColeKeyLegacy)
deserialiseFromRawBytes (AsSigningKey AsColeKeyLegacy) ByteString
bs =
(DeserialiseFailure -> Maybe (SigningKey ColeKeyLegacy))
-> ((ByteString, SigningKey) -> Maybe (SigningKey ColeKeyLegacy))
-> Either DeserialiseFailure (ByteString, SigningKey)
-> Maybe (SigningKey ColeKeyLegacy)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigningKey ColeKeyLegacy)
-> DeserialiseFailure -> Maybe (SigningKey ColeKeyLegacy)
forall a b. a -> b -> a
const Maybe (SigningKey ColeKeyLegacy)
forall a. Maybe a
Nothing) (SigningKey ColeKeyLegacy -> Maybe (SigningKey ColeKeyLegacy)
forall a. a -> Maybe a
Just (SigningKey ColeKeyLegacy -> Maybe (SigningKey ColeKeyLegacy))
-> ((ByteString, SigningKey) -> SigningKey ColeKeyLegacy)
-> (ByteString, SigningKey)
-> Maybe (SigningKey ColeKeyLegacy)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SigningKey -> SigningKey ColeKeyLegacy
ColeSigningKeyLegacy (SigningKey -> SigningKey ColeKeyLegacy)
-> ((ByteString, SigningKey) -> SigningKey)
-> (ByteString, SigningKey)
-> SigningKey ColeKeyLegacy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString, SigningKey) -> SigningKey
forall a b. (a, b) -> b
snd)
((forall s. Decoder s SigningKey)
-> ByteString -> Either DeserialiseFailure (ByteString, SigningKey)
forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure (ByteString, a)
CBOR.deserialiseFromBytes forall s. Decoder s SigningKey
decodeLegacyDelegateKey (ByteString -> Either DeserialiseFailure (ByteString, SigningKey))
-> ByteString -> Either DeserialiseFailure (ByteString, SigningKey)
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
LB.fromStrict ByteString
bs)
where
enforceSize :: Text -> Int -> CBOR.Decoder s ()
enforceSize :: Text -> Int -> Decoder s ()
enforceSize Text
lbl Int
requestedSize = Decoder s Int
forall s. Decoder s Int
CBOR.decodeListLenCanonical Decoder s Int -> (Int -> Decoder s ()) -> Decoder s ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Text -> Int -> Decoder s ()
forall s. Int -> Text -> Int -> Decoder s ()
matchSize Int
requestedSize Text
lbl
matchSize :: Int -> Text -> Int -> CBOR.Decoder s ()
matchSize :: Int -> Text -> Int -> Decoder s ()
matchSize Int
requestedSize Text
lbl Int
actualSize =
Bool -> Decoder s () -> Decoder s ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
actualSize Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
requestedSize) (Decoder s () -> Decoder s ()) -> Decoder s () -> Decoder s ()
forall a b. (a -> b) -> a -> b
$
Text -> Decoder s ()
forall e s a. Buildable e => e -> Decoder s a
cborError ( Text
lbl Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" failed the size check. Expected " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (Int -> String
forall a. Show a => a -> String
show Int
requestedSize)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
", found " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (Int -> String
forall a. Show a => a -> String
show Int
actualSize)
)
decodeXPrv :: CBOR.Decoder s Wallet.XPrv
decodeXPrv :: Decoder s XPrv
decodeXPrv = Decoder s ByteString
forall s. Decoder s ByteString
CBOR.decodeBytesCanonical Decoder s ByteString
-> (ByteString -> Decoder s XPrv) -> Decoder s XPrv
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Either String XPrv -> Decoder s XPrv
forall e a s. Buildable e => Either e a -> Decoder s a
toCborError (Either String XPrv -> Decoder s XPrv)
-> (ByteString -> Either String XPrv)
-> ByteString
-> Decoder s XPrv
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
Wallet.xprv
decodeLegacyDelegateKey :: CBOR.Decoder s Cole.SigningKey
decodeLegacyDelegateKey :: Decoder s SigningKey
decodeLegacyDelegateKey = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"UserSecret" Int
4
ByteString
_ <- do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"vss" Int
1
Decoder s ByteString
forall s. Decoder s ByteString
CBOR.decodeBytes
SigningKey
pkey <- do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"pkey" Int
1
XPrv -> SigningKey
Cole.SigningKey (XPrv -> SigningKey) -> Decoder s XPrv -> Decoder s SigningKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s XPrv
forall s. Decoder s XPrv
decodeXPrv
[()]
_ <- do
Decoder s ()
forall s. Decoder s ()
CBOR.decodeListLenIndef
([()] -> () -> [()])
-> [()] -> ([()] -> [()]) -> Decoder s () -> Decoder s [()]
forall r a r' s.
(r -> a -> r) -> r -> (r -> r') -> Decoder s a -> Decoder s r'
CBOR.decodeSequenceLenIndef ((() -> [()] -> [()]) -> [()] -> () -> [()]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (:)) [] [()] -> [()]
forall a. [a] -> [a]
reverse Decoder s ()
forall s. Decoder s ()
CBOR.decodeNull
()
_ <- do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"wallet" Int
0
SigningKey -> Decoder s SigningKey
forall (f :: * -> *) a. Applicative f => a -> f a
pure SigningKey
pkey
instance CastVerificationKeyRole ColeKeyLegacy ColeKey where
castVerificationKey :: VerificationKey ColeKeyLegacy -> VerificationKey ColeKey
castVerificationKey (ColeVerificationKeyLegacy vk) =
VerificationKey -> VerificationKey ColeKey
ColeVerificationKey VerificationKey
vk
instance IsColeKey ColeKeyLegacy where
coleKeyFormat :: ColeKeyFormat ColeKeyLegacy
coleKeyFormat = ColeKeyFormat ColeKeyLegacy
ColeLegacyKeyFormat