~zinigor/cardano-node/trunk

« back to all changes in this revision

Viewing changes to cardano-api/src/Cardano/Api/Crypto/Ed25519Bip32.hs

  • Committer: Igor Zinovyev
  • Date: 2021-08-13 19:12:27 UTC
  • Revision ID: zinigor@gmail.com-20210813191227-stlnsj3mc5ypwn0c
Tags: upstream-1.27.0
ImportĀ upstreamĀ versionĀ 1.27.0

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# LANGUAGE DataKinds #-}
 
2
{-# LANGUAGE DeriveGeneric #-}
 
3
{-# LANGUAGE DerivingVia #-}
 
4
{-# LANGUAGE FlexibleInstances #-}
 
5
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
 
6
{-# LANGUAGE TypeFamilies #-}
 
7
 
 
8
-- | BIP32-Ed25519 digital signatures.
 
9
module Cardano.Api.Crypto.Ed25519Bip32
 
10
  ( Ed25519Bip32DSIGN
 
11
  , SigDSIGN (..)
 
12
  , SignKeyDSIGN (..)
 
13
  , VerKeyDSIGN (..)
 
14
 
 
15
    -- * Serialisation
 
16
  , xPrvToBytes
 
17
  , xPrvFromBytes
 
18
  )
 
19
where
 
20
 
 
21
import           Cardano.Prelude hiding (show)
 
22
import           Prelude (show)
 
23
 
 
24
import           Data.ByteArray as BA (ByteArrayAccess, ScrubbedBytes, convert)
 
25
import qualified Data.ByteString as BS
 
26
import           NoThunks.Class (InspectHeap (..), NoThunks)
 
27
 
 
28
import           Cardano.Binary (FromCBOR (..), ToCBOR (..))
 
29
import qualified Cardano.Crypto.Wallet as CC
 
30
 
 
31
import           Cardano.Crypto.DSIGN.Class
 
32
import           Cardano.Crypto.Seed
 
33
import           Cardano.Crypto.Util (SignableRepresentation (..))
 
34
 
 
35
import qualified Crypto.ECC.Edwards25519 as Ed25519
 
36
import           Crypto.Error (eitherCryptoError)
 
37
 
 
38
 
 
39
data Ed25519Bip32DSIGN
 
40
 
 
41
instance DSIGNAlgorithm Ed25519Bip32DSIGN where
 
42
 
 
43
    type SeedSizeDSIGN    Ed25519Bip32DSIGN = 32
 
44
 
 
45
    -- | BIP32-Ed25519 extended verification key size is 64 octets.
 
46
    type SizeVerKeyDSIGN  Ed25519Bip32DSIGN = 64
 
47
 
 
48
    -- | BIP32-Ed25519 extended signing key size is 96 octets.
 
49
    type SizeSignKeyDSIGN Ed25519Bip32DSIGN = 96
 
50
 
 
51
    -- | BIP32-Ed25519 extended signature size is 64 octets.
 
52
    type SizeSigDSIGN     Ed25519Bip32DSIGN = 64
 
53
 
 
54
    --
 
55
    -- Key and signature types
 
56
    --
 
57
 
 
58
    newtype VerKeyDSIGN Ed25519Bip32DSIGN = VerKeyEd25519Bip32DSIGN CC.XPub
 
59
        deriving (Show, Eq, Generic)
 
60
        deriving newtype NFData
 
61
        deriving NoThunks via InspectHeap CC.XPub
 
62
 
 
63
    newtype SignKeyDSIGN Ed25519Bip32DSIGN = SignKeyEd25519Bip32DSIGN CC.XPrv
 
64
        deriving (Generic, ByteArrayAccess)
 
65
        deriving newtype NFData
 
66
        deriving NoThunks via InspectHeap CC.XPrv
 
67
 
 
68
    newtype SigDSIGN Ed25519Bip32DSIGN = SigEd25519Bip32DSIGN CC.XSignature
 
69
        deriving (Show, Eq, Generic, ByteArrayAccess)
 
70
        deriving NoThunks via InspectHeap CC.XSignature
 
71
 
 
72
    --
 
73
    -- Metadata and basic key operations
 
74
    --
 
75
 
 
76
    algorithmNameDSIGN _ = "ed25519_bip32"
 
77
 
 
78
    deriveVerKeyDSIGN (SignKeyEd25519Bip32DSIGN sk) =
 
79
      VerKeyEd25519Bip32DSIGN $ CC.toXPub sk
 
80
 
 
81
    --
 
82
    -- Core algorithm operations
 
83
    --
 
84
 
 
85
    type Signable Ed25519Bip32DSIGN = SignableRepresentation
 
86
 
 
87
    signDSIGN () a (SignKeyEd25519Bip32DSIGN sk) =
 
88
      SigEd25519Bip32DSIGN $
 
89
        CC.sign (mempty :: ScrubbedBytes) sk (getSignableRepresentation a)
 
90
 
 
91
    verifyDSIGN () (VerKeyEd25519Bip32DSIGN vk) a (SigEd25519Bip32DSIGN sig) =
 
92
      if CC.verify vk (getSignableRepresentation a) sig
 
93
        then Right ()
 
94
        else Left "Verification failed"
 
95
 
 
96
    --
 
97
    -- Key generation
 
98
    --
 
99
 
 
100
    genKeyDSIGN seed =
 
101
      SignKeyEd25519Bip32DSIGN $
 
102
        CC.generateNew
 
103
          (getSeedBytes seed)
 
104
          (mempty :: ScrubbedBytes)
 
105
          (mempty :: ScrubbedBytes)
 
106
 
 
107
    --
 
108
    -- raw serialise/deserialise
 
109
    --
 
110
 
 
111
    rawSerialiseVerKeyDSIGN (VerKeyEd25519Bip32DSIGN vk) = CC.unXPub vk
 
112
    rawSerialiseSignKeyDSIGN (SignKeyEd25519Bip32DSIGN sk) = xPrvToBytes sk
 
113
    rawSerialiseSigDSIGN = BA.convert
 
114
 
 
115
    rawDeserialiseVerKeyDSIGN =
 
116
      either (const Nothing) (Just . VerKeyEd25519Bip32DSIGN) . CC.xpub
 
117
    rawDeserialiseSignKeyDSIGN =
 
118
      fmap SignKeyEd25519Bip32DSIGN . xPrvFromBytes
 
119
    rawDeserialiseSigDSIGN =
 
120
      either (const Nothing) (Just . SigEd25519Bip32DSIGN) . CC.xsignature
 
121
 
 
122
 
 
123
instance Show (SignKeyDSIGN Ed25519Bip32DSIGN) where
 
124
  show (SignKeyEd25519Bip32DSIGN sk) = show $ xPrvToBytes sk
 
125
 
 
126
instance ToCBOR (VerKeyDSIGN Ed25519Bip32DSIGN) where
 
127
  toCBOR = encodeVerKeyDSIGN
 
128
  encodedSizeExpr _ = encodedVerKeyDSIGNSizeExpr
 
129
 
 
130
instance FromCBOR (VerKeyDSIGN Ed25519Bip32DSIGN) where
 
131
  fromCBOR = decodeVerKeyDSIGN
 
132
 
 
133
instance ToCBOR (SignKeyDSIGN Ed25519Bip32DSIGN) where
 
134
  toCBOR = encodeSignKeyDSIGN
 
135
  encodedSizeExpr _ = encodedSignKeyDESIGNSizeExpr
 
136
 
 
137
instance FromCBOR (SignKeyDSIGN Ed25519Bip32DSIGN) where
 
138
  fromCBOR = decodeSignKeyDSIGN
 
139
 
 
140
instance ToCBOR (SigDSIGN Ed25519Bip32DSIGN) where
 
141
  toCBOR = encodeSigDSIGN
 
142
  encodedSizeExpr _ = encodedSigDSIGNSizeExpr
 
143
 
 
144
instance FromCBOR (SigDSIGN Ed25519Bip32DSIGN) where
 
145
  fromCBOR = decodeSigDSIGN
 
146
 
 
147
 
 
148
-- | Serialise an 'CC.XPrv' to a 'ByteString' (96 bytes).
 
149
--
 
150
-- In @cardano-crypto@, an 'CC.XPrv' was originally serialised using the
 
151
-- following 128-byte binary format:
 
152
--
 
153
-- +---------------------------------+-----------------------+-----------------------+
 
154
-- | Extended Private Key (64 bytes) | Public Key (32 bytes) | Chain Code (32 bytes) |
 
155
-- +---------------------------------+-----------------------+-----------------------+
 
156
--
 
157
-- However, this function serialises an 'CC.XPrv' using a more compact 96-byte
 
158
-- binary format:
 
159
--
 
160
-- +---------------------------------+-----------------------+
 
161
-- | Extended Private Key (64 bytes) | Chain Code (32 bytes) |
 
162
-- +---------------------------------+-----------------------+
 
163
--
 
164
xPrvToBytes :: CC.XPrv -> ByteString
 
165
xPrvToBytes xPrv = privateKeyBytes <> chainCodeBytes
 
166
  where
 
167
    privateKeyBytes :: ByteString
 
168
    privateKeyBytes = BS.take 64 (CC.unXPrv xPrv)
 
169
 
 
170
    chainCodeBytes :: ByteString
 
171
    chainCodeBytes = BS.drop 96 (CC.unXPrv xPrv)
 
172
 
 
173
-- | Deserialise an 'CC.XPrv' from a 'ByteString' (96 bytes).
 
174
--
 
175
-- In @cardano-crypto@, an 'CC.XPrv' was originally deserialised using the
 
176
-- following 128-byte binary format:
 
177
--
 
178
-- +---------------------------------+-----------------------+-----------------------+
 
179
-- | Extended Private Key (64 bytes) | Public Key (32 bytes) | Chain Code (32 bytes) |
 
180
-- +---------------------------------+-----------------------+-----------------------+
 
181
--
 
182
-- However, this function deserialises an 'CC.XPrv' using a more compact
 
183
-- 96-byte binary format:
 
184
--
 
185
-- +---------------------------------+-----------------------+
 
186
-- | Extended Private Key (64 bytes) | Chain Code (32 bytes) |
 
187
-- +---------------------------------+-----------------------+
 
188
--
 
189
xPrvFromBytes :: ByteString -> Maybe CC.XPrv
 
190
xPrvFromBytes bytes
 
191
    | BS.length bytes /= 96 = Nothing
 
192
    | otherwise = do
 
193
        let (prv, cc) = BS.splitAt 64 bytes
 
194
        pub <- ed25519ScalarMult (BS.take 32 prv)
 
195
        eitherToMaybe $ CC.xprv $ prv <> pub <> cc
 
196
  where
 
197
    eitherToMaybe :: Either a b -> Maybe b
 
198
    eitherToMaybe = either (const Nothing) Just
 
199
 
 
200
    ed25519ScalarMult :: ByteString -> Maybe ByteString
 
201
    ed25519ScalarMult bs = do
 
202
      scalar <- eitherToMaybe . eitherCryptoError $ Ed25519.scalarDecodeLong bs
 
203
      pure $ Ed25519.pointEncode $ Ed25519.toPoint scalar