{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoStarIsType #-}
module Cardano.Crypto.KES.Simple
( SimpleKES
, SigKES (..)
, SignKeyKES (SignKeySimpleKES, ThunkySignKeySimpleKES)
)
where
import Data.List (unfoldr)
import Data.Proxy (Proxy (..))
import qualified Data.ByteString as BS
import Data.Vector ((!?), Vector)
import qualified Data.Vector as Vec
import GHC.Generics (Generic)
import GHC.TypeNats (Nat, KnownNat, natVal, type (*))
import NoThunks.Class (NoThunks)
import Cardano.Binary (FromCBOR (..), ToCBOR (..))
import Cardano.Crypto.DSIGN
import qualified Cardano.Crypto.DSIGN as DSIGN
import Cardano.Crypto.KES.Class
import Cardano.Crypto.Seed
import Cardano.Crypto.Util
import Data.Unit.Strict (forceElemsToWHNF)
data SimpleKES d (t :: Nat)
pattern VerKeySimpleKES :: Vector (VerKeyDSIGN d) -> VerKeyKES (SimpleKES d t)
pattern $bVerKeySimpleKES :: forall d (t :: Nat).
Vector (VerKeyDSIGN d) -> VerKeyKES (SimpleKES d t)
$mVerKeySimpleKES :: forall {r} {d} {t :: Nat}.
VerKeyKES (SimpleKES d t)
-> (Vector (VerKeyDSIGN d) -> r) -> ((# #) -> r) -> r
VerKeySimpleKES v <- ThunkyVerKeySimpleKES v
where
VerKeySimpleKES Vector (VerKeyDSIGN d)
v = forall d (t :: Nat).
Vector (VerKeyDSIGN d) -> VerKeyKES (SimpleKES d t)
ThunkyVerKeySimpleKES (forall (t :: Type -> Type) a. Foldable t => t a -> t a
forceElemsToWHNF Vector (VerKeyDSIGN d)
v)
{-# COMPLETE VerKeySimpleKES #-}
pattern SignKeySimpleKES :: Vector (SignKeyDSIGN d) -> SignKeyKES (SimpleKES d t)
pattern $bSignKeySimpleKES :: forall d (t :: Nat).
Vector (SignKeyDSIGN d) -> SignKeyKES (SimpleKES d t)
$mSignKeySimpleKES :: forall {r} {d} {t :: Nat}.
SignKeyKES (SimpleKES d t)
-> (Vector (SignKeyDSIGN d) -> r) -> ((# #) -> r) -> r
SignKeySimpleKES v <- ThunkySignKeySimpleKES v
where
SignKeySimpleKES Vector (SignKeyDSIGN d)
v = forall d (t :: Nat).
Vector (SignKeyDSIGN d) -> SignKeyKES (SimpleKES d t)
ThunkySignKeySimpleKES (forall (t :: Type -> Type) a. Foldable t => t a -> t a
forceElemsToWHNF Vector (SignKeyDSIGN d)
v)
{-# COMPLETE SignKeySimpleKES #-}
instance (DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) =>
KESAlgorithm (SimpleKES d t) where
type SeedSizeKES (SimpleKES d t) = SeedSizeDSIGN d * t
newtype VerKeyKES (SimpleKES d t) =
ThunkyVerKeySimpleKES (Vector (VerKeyDSIGN d))
deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall d (t :: Nat) x.
Rep (VerKeyKES (SimpleKES d t)) x -> VerKeyKES (SimpleKES d t)
forall d (t :: Nat) x.
VerKeyKES (SimpleKES d t) -> Rep (VerKeyKES (SimpleKES d t)) x
$cto :: forall d (t :: Nat) x.
Rep (VerKeyKES (SimpleKES d t)) x -> VerKeyKES (SimpleKES d t)
$cfrom :: forall d (t :: Nat) x.
VerKeyKES (SimpleKES d t) -> Rep (VerKeyKES (SimpleKES d t)) x
Generic
newtype SignKeyKES (SimpleKES d t) =
ThunkySignKeySimpleKES (Vector (SignKeyDSIGN d))
deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall d (t :: Nat) x.
Rep (SignKeyKES (SimpleKES d t)) x -> SignKeyKES (SimpleKES d t)
forall d (t :: Nat) x.
SignKeyKES (SimpleKES d t) -> Rep (SignKeyKES (SimpleKES d t)) x
$cto :: forall d (t :: Nat) x.
Rep (SignKeyKES (SimpleKES d t)) x -> SignKeyKES (SimpleKES d t)
$cfrom :: forall d (t :: Nat) x.
SignKeyKES (SimpleKES d t) -> Rep (SignKeyKES (SimpleKES d t)) x
Generic
newtype SigKES (SimpleKES d t) =
SigSimpleKES (SigDSIGN d)
deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall d (t :: Nat) x.
Rep (SigKES (SimpleKES d t)) x -> SigKES (SimpleKES d t)
forall d (t :: Nat) x.
SigKES (SimpleKES d t) -> Rep (SigKES (SimpleKES d t)) x
$cto :: forall d (t :: Nat) x.
Rep (SigKES (SimpleKES d t)) x -> SigKES (SimpleKES d t)
$cfrom :: forall d (t :: Nat) x.
SigKES (SimpleKES d t) -> Rep (SigKES (SimpleKES d t)) x
Generic
algorithmNameKES :: forall (proxy :: Type -> Type). proxy (SimpleKES d t) -> String
algorithmNameKES proxy (SimpleKES d t)
proxy = String
"simple_" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall v (proxy :: Type -> Type).
KESAlgorithm v =>
proxy v -> Period
totalPeriodsKES proxy (SimpleKES d t)
proxy)
deriveVerKeyKES :: SignKeyKES (SimpleKES d t) -> VerKeyKES (SimpleKES d t)
deriveVerKeyKES (SignKeySimpleKES Vector (SignKeyDSIGN d)
sks) =
forall d (t :: Nat).
Vector (VerKeyDSIGN d) -> VerKeyKES (SimpleKES d t)
VerKeySimpleKES (forall a b. (a -> b) -> Vector a -> Vector b
Vec.map forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> VerKeyDSIGN v
deriveVerKeyDSIGN Vector (SignKeyDSIGN d)
sks)
type ContextKES (SimpleKES d t) = DSIGN.ContextDSIGN d
type Signable (SimpleKES d t) = DSIGN.Signable d
signKES :: forall a.
(Signable (SimpleKES d t) a, HasCallStack) =>
ContextKES (SimpleKES d t)
-> Period
-> a
-> SignKeyKES (SimpleKES d t)
-> SigKES (SimpleKES d t)
signKES ContextKES (SimpleKES d t)
ctxt Period
j a
a (SignKeySimpleKES Vector (SignKeyDSIGN d)
sks) =
case Vector (SignKeyDSIGN d)
sks forall a. Vector a -> Int -> Maybe a
!? forall a b. (Integral a, Num b) => a -> b
fromIntegral Period
j of
Maybe (SignKeyDSIGN d)
Nothing -> forall a. HasCallStack => String -> a
error (String
"SimpleKES.signKES: period out of range " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Period
j)
Just SignKeyDSIGN d
sk -> forall d (t :: Nat). SigDSIGN d -> SigKES (SimpleKES d t)
SigSimpleKES (forall v a.
(DSIGNAlgorithm v, Signable v a, HasCallStack) =>
ContextDSIGN v -> a -> SignKeyDSIGN v -> SigDSIGN v
signDSIGN ContextKES (SimpleKES d t)
ctxt a
a SignKeyDSIGN d
sk)
verifyKES :: forall a.
(Signable (SimpleKES d t) a, HasCallStack) =>
ContextKES (SimpleKES d t)
-> VerKeyKES (SimpleKES d t)
-> Period
-> a
-> SigKES (SimpleKES d t)
-> Either String ()
verifyKES ContextKES (SimpleKES d t)
ctxt (VerKeySimpleKES Vector (VerKeyDSIGN d)
vks) Period
j a
a (SigSimpleKES SigDSIGN d
sig) =
case Vector (VerKeyDSIGN d)
vks forall a. Vector a -> Int -> Maybe a
!? forall a b. (Integral a, Num b) => a -> b
fromIntegral Period
j of
Maybe (VerKeyDSIGN d)
Nothing -> forall a b. a -> Either a b
Left String
"KES verification failed: out of range"
Just VerKeyDSIGN d
vk -> forall v a.
(DSIGNAlgorithm v, Signable v a, HasCallStack) =>
ContextDSIGN v
-> VerKeyDSIGN v -> a -> SigDSIGN v -> Either String ()
verifyDSIGN ContextKES (SimpleKES d t)
ctxt VerKeyDSIGN d
vk a
a SigDSIGN d
sig
updateKES :: HasCallStack =>
ContextKES (SimpleKES d t)
-> SignKeyKES (SimpleKES d t)
-> Period
-> Maybe (SignKeyKES (SimpleKES d t))
updateKES ContextKES (SimpleKES d t)
_ SignKeyKES (SimpleKES d t)
sk Period
t
| Period
tforall a. Num a => a -> a -> a
+Period
1 forall a. Ord a => a -> a -> Bool
< forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @t)) = forall a. a -> Maybe a
Just SignKeyKES (SimpleKES d t)
sk
| Bool
otherwise = forall a. Maybe a
Nothing
totalPeriodsKES :: forall (proxy :: Type -> Type). proxy (SimpleKES d t) -> Period
totalPeriodsKES proxy (SimpleKES d t)
_ = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @t))
seedSizeKES :: forall (proxy :: Type -> Type). proxy (SimpleKES d t) -> Period
seedSizeKES proxy (SimpleKES d t)
_ =
let seedSize :: Period
seedSize = forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Period
seedSizeDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy d)
duration :: Period
duration = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @t))
in Period
duration forall a. Num a => a -> a -> a
* Period
seedSize
genKeyKES :: Seed -> SignKeyKES (SimpleKES d t)
genKeyKES Seed
seed =
let seedSize :: Period
seedSize = forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Period
seedSizeDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy d)
duration :: Int
duration = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @t))
seeds :: [Seed]
seeds = forall a. Int -> [a] -> [a]
take Int
duration
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map ByteString -> Seed
mkSeedFromBytes
forall a b. (a -> b) -> a -> b
$ forall b a. (b -> Maybe (a, b)) -> b -> [a]
unfoldr (Period -> Seed -> Maybe (ByteString, Seed)
getBytesFromSeed Period
seedSize) Seed
seed
sks :: [SignKeyDSIGN d]
sks = forall a b. (a -> b) -> [a] -> [b]
map forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
genKeyDSIGN [Seed]
seeds
in forall d (t :: Nat).
Vector (SignKeyDSIGN d) -> SignKeyKES (SimpleKES d t)
SignKeySimpleKES (forall a. [a] -> Vector a
Vec.fromList [SignKeyDSIGN d]
sks)
sizeVerKeyKES :: forall (proxy :: Type -> Type). proxy (SimpleKES d t) -> Period
sizeVerKeyKES proxy (SimpleKES d t)
_ = forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Period
sizeVerKeyDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy d) forall a. Num a => a -> a -> a
* Period
duration
where
duration :: Period
duration = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @t))
sizeSignKeyKES :: forall (proxy :: Type -> Type). proxy (SimpleKES d t) -> Period
sizeSignKeyKES proxy (SimpleKES d t)
_ = forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Period
sizeSignKeyDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy d) forall a. Num a => a -> a -> a
* Period
duration
where
duration :: Period
duration = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @t))
sizeSigKES :: forall (proxy :: Type -> Type). proxy (SimpleKES d t) -> Period
sizeSigKES proxy (SimpleKES d t)
_ = forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Period
sizeSigDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy d)
rawSerialiseVerKeyKES :: VerKeyKES (SimpleKES d t) -> ByteString
rawSerialiseVerKeyKES (VerKeySimpleKES Vector (VerKeyDSIGN d)
vks) =
[ByteString] -> ByteString
BS.concat [ forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> ByteString
rawSerialiseVerKeyDSIGN VerKeyDSIGN d
vk | VerKeyDSIGN d
vk <- forall a. Vector a -> [a]
Vec.toList Vector (VerKeyDSIGN d)
vks ]
rawSerialiseSignKeyKES :: SignKeyKES (SimpleKES d t) -> ByteString
rawSerialiseSignKeyKES (SignKeySimpleKES Vector (SignKeyDSIGN d)
sks) =
[ByteString] -> ByteString
BS.concat [ forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> ByteString
rawSerialiseSignKeyDSIGN SignKeyDSIGN d
sk | SignKeyDSIGN d
sk <- forall a. Vector a -> [a]
Vec.toList Vector (SignKeyDSIGN d)
sks ]
rawSerialiseSigKES :: SigKES (SimpleKES d t) -> ByteString
rawSerialiseSigKES (SigSimpleKES SigDSIGN d
sig) =
forall v. DSIGNAlgorithm v => SigDSIGN v -> ByteString
rawSerialiseSigDSIGN SigDSIGN d
sig
rawDeserialiseVerKeyKES :: ByteString -> Maybe (VerKeyKES (SimpleKES d t))
rawDeserialiseVerKeyKES ByteString
bs
| let duration :: Int
duration = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy t))
sizeKey :: Int
sizeKey = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Period
sizeVerKeyDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy d))
, [ByteString]
vkbs <- [Int] -> ByteString -> [ByteString]
splitsAt (forall a. Int -> a -> [a]
replicate Int
duration Int
sizeKey) ByteString
bs
, forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [ByteString]
vkbs forall a. Eq a => a -> a -> Bool
== Int
duration
, Just [VerKeyDSIGN d]
vks <- forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
rawDeserialiseVerKeyDSIGN [ByteString]
vkbs
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! forall d (t :: Nat).
Vector (VerKeyDSIGN d) -> VerKeyKES (SimpleKES d t)
VerKeySimpleKES (forall a. [a] -> Vector a
Vec.fromList [VerKeyDSIGN d]
vks)
| Bool
otherwise
= forall a. Maybe a
Nothing
rawDeserialiseSignKeyKES :: ByteString -> Maybe (SignKeyKES (SimpleKES d t))
rawDeserialiseSignKeyKES ByteString
bs
| let duration :: Int
duration = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy t))
sizeKey :: Int
sizeKey = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Period
sizeSignKeyDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy d))
, [ByteString]
skbs <- [Int] -> ByteString -> [ByteString]
splitsAt (forall a. Int -> a -> [a]
replicate Int
duration Int
sizeKey) ByteString
bs
, forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [ByteString]
skbs forall a. Eq a => a -> a -> Bool
== Int
duration
, Just [SignKeyDSIGN d]
sks <- forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
rawDeserialiseSignKeyDSIGN [ByteString]
skbs
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! forall d (t :: Nat).
Vector (SignKeyDSIGN d) -> SignKeyKES (SimpleKES d t)
SignKeySimpleKES (forall a. [a] -> Vector a
Vec.fromList [SignKeyDSIGN d]
sks)
| Bool
otherwise
= forall a. Maybe a
Nothing
rawDeserialiseSigKES :: ByteString -> Maybe (SigKES (SimpleKES d t))
rawDeserialiseSigKES = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall d (t :: Nat). SigDSIGN d -> SigKES (SimpleKES d t)
SigSimpleKES forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. DSIGNAlgorithm v => ByteString -> Maybe (SigDSIGN v)
rawDeserialiseSigDSIGN
deriving instance DSIGNAlgorithm d => Show (VerKeyKES (SimpleKES d t))
deriving instance DSIGNAlgorithm d => Show (SignKeyKES (SimpleKES d t))
deriving instance DSIGNAlgorithm d => Show (SigKES (SimpleKES d t))
deriving instance DSIGNAlgorithm d => Eq (VerKeyKES (SimpleKES d t))
deriving instance DSIGNAlgorithm d => Eq (SigKES (SimpleKES d t))
instance DSIGNAlgorithm d => NoThunks (SigKES (SimpleKES d t))
instance DSIGNAlgorithm d => NoThunks (SignKeyKES (SimpleKES d t))
instance DSIGNAlgorithm d => NoThunks (VerKeyKES (SimpleKES d t))
instance (DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t))
=> ToCBOR (VerKeyKES (SimpleKES d t)) where
toCBOR :: VerKeyKES (SimpleKES d t) -> Encoding
toCBOR = forall v. KESAlgorithm v => VerKeyKES v -> Encoding
encodeVerKeyKES
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerKeyKES (SimpleKES d t)) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_size = forall v. KESAlgorithm v => Proxy (VerKeyKES v) -> Size
encodedVerKeyKESSizeExpr
instance (DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t))
=> FromCBOR (VerKeyKES (SimpleKES d t)) where
fromCBOR :: forall s. Decoder s (VerKeyKES (SimpleKES d t))
fromCBOR = forall v s. KESAlgorithm v => Decoder s (VerKeyKES v)
decodeVerKeyKES
instance (DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t))
=> ToCBOR (SignKeyKES (SimpleKES d t)) where
toCBOR :: SignKeyKES (SimpleKES d t) -> Encoding
toCBOR = forall v. KESAlgorithm v => SignKeyKES v -> Encoding
encodeSignKeyKES
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SignKeyKES (SimpleKES d t)) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_size = forall v. KESAlgorithm v => Proxy (SignKeyKES v) -> Size
encodedSignKeyKESSizeExpr
instance (DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t))
=> FromCBOR (SignKeyKES (SimpleKES d t)) where
fromCBOR :: forall s. Decoder s (SignKeyKES (SimpleKES d t))
fromCBOR = forall v s. KESAlgorithm v => Decoder s (SignKeyKES v)
decodeSignKeyKES
instance (DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t))
=> ToCBOR (SigKES (SimpleKES d t)) where
toCBOR :: SigKES (SimpleKES d t) -> Encoding
toCBOR = forall v. KESAlgorithm v => SigKES v -> Encoding
encodeSigKES
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigKES (SimpleKES d t)) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_size = forall v. KESAlgorithm v => Proxy (SigKES v) -> Size
encodedSigKESSizeExpr
instance (DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t))
=> FromCBOR (SigKES (SimpleKES d t)) where
fromCBOR :: forall s. Decoder s (SigKES (SimpleKES d t))
fromCBOR = forall v s. KESAlgorithm v => Decoder s (SigKES v)
decodeSigKES