Skip to content

Commit

Permalink
KES secure forgetting
Browse files Browse the repository at this point in the history
  • Loading branch information
tdammers committed Apr 7, 2022
1 parent bf03ef2 commit 1618f77
Show file tree
Hide file tree
Showing 39 changed files with 2,764 additions and 824 deletions.
1 change: 1 addition & 0 deletions .gitignore
Expand Up @@ -40,3 +40,4 @@ stack-local.yaml
# ghcid
**/.ghcid
**/ghcid.txt
tags
9 changes: 9 additions & 0 deletions cardano-crypto-class/cardano-crypto-class.cabal
Expand Up @@ -50,7 +50,9 @@ library
Cardano.Crypto.DSIGN
Cardano.Crypto.DSIGN.Class
Cardano.Crypto.DSIGN.Ed25519
Cardano.Crypto.DSIGN.Ed25519ML
Cardano.Crypto.DSIGN.Ed448
Cardano.Crypto.DSIGNM.Class
Cardano.Crypto.DSIGN.Mock
Cardano.Crypto.DSIGN.NeverUsed
Cardano.Crypto.Hash
Expand All @@ -65,6 +67,7 @@ library
Cardano.Crypto.KES.Class
Cardano.Crypto.KES.CompactSingle
Cardano.Crypto.KES.CompactSum
Cardano.Crypto.KES.ForgetMock
Cardano.Crypto.KES.Mock
Cardano.Crypto.KES.NeverUsed
Cardano.Crypto.KES.Simple
Expand All @@ -80,7 +83,9 @@ library
Cardano.Crypto.Libsodium.MLockedBytes
Cardano.Crypto.Libsodium.MLockedBytes.Internal
Cardano.Crypto.Libsodium.UnsafeC
Cardano.Crypto.MonadSodium
Cardano.Crypto.PinnedSizedBytes
Cardano.Crypto.SafePinned
Cardano.Crypto.Seed
Cardano.Crypto.Util
Cardano.Crypto.VRF
Expand All @@ -105,9 +110,13 @@ library
, ghc-prim
, integer-gmp
, memory
, mtl
, nothunks
, primitive
, random
, secp256k1-haskell
, serialise
, stm
, text
, transformers
, vector
Expand Down
2 changes: 2 additions & 0 deletions cardano-crypto-class/src/Cardano/Crypto/DSIGN.hs
Expand Up @@ -6,7 +6,9 @@ module Cardano.Crypto.DSIGN
where

import Cardano.Crypto.DSIGN.Class as X
import Cardano.Crypto.DSIGNM.Class as X
import Cardano.Crypto.DSIGN.Ed25519 as X
import Cardano.Crypto.DSIGN.Ed25519ML as X
import Cardano.Crypto.DSIGN.Ed448 as X
import Cardano.Crypto.DSIGN.Mock as X
import Cardano.Crypto.DSIGN.NeverUsed as X
Expand Down
6 changes: 3 additions & 3 deletions cardano-crypto-class/src/Cardano/Crypto/DSIGN/Class.hs
Expand Up @@ -38,7 +38,7 @@ module Cardano.Crypto.DSIGN.Class

-- * Encoded 'Size' expresssions
, encodedVerKeyDSIGNSizeExpr
, encodedSignKeyDESIGNSizeExpr
, encodedSignKeyDSIGNSizeExpr
, encodedSigDSIGNSizeExpr
)
where
Expand Down Expand Up @@ -290,8 +290,8 @@ encodedVerKeyDSIGNSizeExpr _proxy =
-- | 'Size' expression for 'SignKeyDSIGN' which is using 'sizeSignKeyDSIGN'
-- encoded as 'Size'.
--
encodedSignKeyDESIGNSizeExpr :: forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDESIGNSizeExpr _proxy =
encodedSignKeyDSIGNSizeExpr :: forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDSIGNSizeExpr _proxy =
-- 'encodeBytes' envelope
fromIntegral ((withWordSize :: Word -> Integer) (sizeSignKeyDSIGN (Proxy :: Proxy v)))
-- payload
Expand Down
70 changes: 35 additions & 35 deletions cardano-crypto-class/src/Cardano/Crypto/DSIGN/EcdsaSecp256k1.hs
Expand Up @@ -26,33 +26,33 @@ import Control.DeepSeq (NFData)
import qualified Crypto.Secp256k1 as ECDSA
import NoThunks.Class (NoThunks)
import Cardano.Crypto.DSIGN.Class (
DSIGNAlgorithm (VerKeyDSIGN,
SignKeyDSIGN,
DSIGNAlgorithm (VerKeyDSIGN,
SignKeyDSIGN,
SigDSIGN,
SeedSizeDSIGN,
SizeSigDSIGN,
SizeSignKeyDSIGN,
SizeVerKeyDSIGN,
SeedSizeDSIGN,
SizeSigDSIGN,
SizeSignKeyDSIGN,
SizeVerKeyDSIGN,
algorithmNameDSIGN,
deriveVerKeyDSIGN,
signDSIGN,
verifyDSIGN,
genKeyDSIGN,
deriveVerKeyDSIGN,
signDSIGN,
verifyDSIGN,
genKeyDSIGN,
rawSerialiseSigDSIGN,
Signable,
rawSerialiseVerKeyDSIGN,
rawSerialiseSignKeyDSIGN,
Signable,
rawSerialiseVerKeyDSIGN,
rawSerialiseSignKeyDSIGN,
rawDeserialiseVerKeyDSIGN,
rawDeserialiseSignKeyDSIGN,
rawDeserialiseSigDSIGN),
encodeVerKeyDSIGN,
encodedVerKeyDSIGNSizeExpr,
decodeVerKeyDSIGN,
encodeSignKeyDSIGN,
encodedSignKeyDESIGNSizeExpr,
decodeSignKeyDSIGN,
encodeSigDSIGN,
encodedSigDSIGNSizeExpr,
rawDeserialiseSignKeyDSIGN,
rawDeserialiseSigDSIGN),
encodeVerKeyDSIGN,
encodedVerKeyDSIGNSizeExpr,
decodeVerKeyDSIGN,
encodeSignKeyDSIGN,
encodedSignKeyDSIGNSizeExpr,
decodeSignKeyDSIGN,
encodeSigDSIGN,
encodedSigDSIGNSizeExpr,
decodeSigDSIGN
)

Expand All @@ -70,40 +70,40 @@ instance DSIGNAlgorithm EcdsaSecp256k1DSIGN where
type SizeSignKeyDSIGN EcdsaSecp256k1DSIGN = 32
type SizeVerKeyDSIGN EcdsaSecp256k1DSIGN = 64
type Signable EcdsaSecp256k1DSIGN = ((~) ECDSA.Msg)
newtype VerKeyDSIGN EcdsaSecp256k1DSIGN =
newtype VerKeyDSIGN EcdsaSecp256k1DSIGN =
VerKeyEcdsaSecp256k1 ECDSA.PubKey
deriving newtype (Eq, NFData)
deriving stock (Show, Generic)
newtype SignKeyDSIGN EcdsaSecp256k1DSIGN =
newtype SignKeyDSIGN EcdsaSecp256k1DSIGN =
SignKeyEcdsaSecp256k1 ECDSA.SecKey
deriving newtype (Eq, NFData)
deriving stock (Show, Generic)
newtype SigDSIGN EcdsaSecp256k1DSIGN =
newtype SigDSIGN EcdsaSecp256k1DSIGN =
SigEcdsaSecp256k1 ECDSA.Sig
deriving newtype (Eq, NFData)
deriving stock (Show, Generic)
algorithmNameDSIGN _ = "ecdsa-secp256k1"
deriveVerKeyDSIGN (SignKeyEcdsaSecp256k1 sk) =
deriveVerKeyDSIGN (SignKeyEcdsaSecp256k1 sk) =
VerKeyEcdsaSecp256k1 . ECDSA.derivePubKey $ sk
signDSIGN () msg (SignKeyEcdsaSecp256k1 k) =
signDSIGN () msg (SignKeyEcdsaSecp256k1 k) =
SigEcdsaSecp256k1 . ECDSA.signMsg k $ msg
verifyDSIGN () (VerKeyEcdsaSecp256k1 pk) msg (SigEcdsaSecp256k1 sig) =
verifyDSIGN () (VerKeyEcdsaSecp256k1 pk) msg (SigEcdsaSecp256k1 sig) =
if ECDSA.verifySig pk sig msg
then pure ()
else Left "ECDSA-SECP256k1 signature not verified"
genKeyDSIGN seed = runMonadRandomWithSeed seed $ do
bs <- getRandomBytes 32
case ECDSA.secKey bs of
case ECDSA.secKey bs of
Nothing -> error "Failed to construct a ECDSA-SECP256k1 secret key unexpectedly"
Just sk -> pure . SignKeyEcdsaSecp256k1 $ sk
rawSerialiseSigDSIGN (SigEcdsaSecp256k1 sig) = putting sig
rawSerialiseVerKeyDSIGN (VerKeyEcdsaSecp256k1 pk) = putting pk
rawSerialiseSignKeyDSIGN (SignKeyEcdsaSecp256k1 sk) = putting sk
rawDeserialiseVerKeyDSIGN bs =
rawDeserialiseVerKeyDSIGN bs =
VerKeyEcdsaSecp256k1 <$> (eitherToMaybe . getting $ bs)
rawDeserialiseSignKeyDSIGN bs =
rawDeserialiseSignKeyDSIGN bs =
SignKeyEcdsaSecp256k1 <$> (eitherToMaybe . getting $ bs)
rawDeserialiseSigDSIGN bs =
rawDeserialiseSigDSIGN bs =
SigEcdsaSecp256k1 <$> (eitherToMaybe . getting $ bs)

instance ToCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) where
Expand All @@ -115,7 +115,7 @@ instance FromCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) where

instance ToCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) where
toCBOR = encodeSignKeyDSIGN
encodedSizeExpr _ = encodedSignKeyDESIGNSizeExpr
encodedSizeExpr _ = encodedSignKeyDSIGNSizeExpr

instance FromCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) where
fromCBOR = decodeSignKeyDSIGN
Expand All @@ -137,7 +137,7 @@ instance NoThunks ECDSA.Sig

-- Helpers

eitherToMaybe :: forall (a :: Type) (b :: Type) .
eitherToMaybe :: forall (a :: Type) (b :: Type) .
Either b a -> Maybe a
eitherToMaybe = either (const Nothing) pure

Expand Down
3 changes: 2 additions & 1 deletion cardano-crypto-class/src/Cardano/Crypto/DSIGN/Ed25519.hs
Expand Up @@ -85,6 +85,7 @@ instance DSIGNAlgorithm Ed25519DSIGN where
-- (the libsodium \"seed\"). And because of this, we need to define the
-- sign key size to be SEEDBYTES (which is 32), not PRIVATEKEYBYTES (which
-- would be 64).
-- (the libsodium \"seed\").
type SizeSignKeyDSIGN Ed25519DSIGN = CRYPTO_SIGN_ED25519_SEEDBYTES
-- | Ed25519 signature size is 64 octets
type SizeSigDSIGN Ed25519DSIGN = CRYPTO_SIGN_ED25519_BYTES
Expand Down Expand Up @@ -195,7 +196,7 @@ instance FromCBOR (VerKeyDSIGN Ed25519DSIGN) where

instance ToCBOR (SignKeyDSIGN Ed25519DSIGN) where
toCBOR = encodeSignKeyDSIGN
encodedSizeExpr _ = encodedSignKeyDESIGNSizeExpr
encodedSizeExpr _ = encodedSignKeyDSIGNSizeExpr

instance FromCBOR (SignKeyDSIGN Ed25519DSIGN) where
fromCBOR = decodeSignKeyDSIGN
Expand Down

0 comments on commit 1618f77

Please sign in to comment.