~zinigor/cardano-node/trunk

« back to all changes in this revision

Viewing changes to cardano-api/src/Cardano/Api/Address.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 FlexibleInstances #-}
 
2
{-# LANGUAGE GADTs #-}
 
3
{-# LANGUAGE PatternSynonyms #-}
 
4
{-# LANGUAGE ScopedTypeVariables #-}
 
5
{-# LANGUAGE StandaloneDeriving #-}
 
6
{-# LANGUAGE TypeFamilies #-}
 
7
 
 
8
-- | Cardano addresses: payment and stake addresses.
 
9
--
 
10
module Cardano.Api.Address (
 
11
    -- * Payment addresses
 
12
    -- | Constructing and inspecting normal payment addresses
 
13
    Address(..),
 
14
 
 
15
    -- ** Byron addresses
 
16
    ByronAddr,
 
17
    makeByronAddress,
 
18
 
 
19
    -- ** Shelley addresses
 
20
    ShelleyAddr,
 
21
    makeShelleyAddress,
 
22
    PaymentCredential(..),
 
23
    StakeAddressReference(..),
 
24
 
 
25
    -- ** Addresses in any era
 
26
    AddressAny(..),
 
27
 
 
28
    -- ** Addresses in specific eras
 
29
    AddressInEra(..),
 
30
    AddressTypeInEra(..),
 
31
    byronAddressInEra,
 
32
    shelleyAddressInEra,
 
33
    anyAddressInShelleyBasedEra,
 
34
    anyAddressInEra,
 
35
    toAddressAny,
 
36
    makeByronAddressInEra,
 
37
    makeShelleyAddressInEra,
 
38
 
 
39
    -- * Stake addresses
 
40
    -- | Constructing and inspecting stake addresses
 
41
    StakeAddress(..),
 
42
    StakeCredential(..),
 
43
    makeStakeAddress,
 
44
    StakeKey,
 
45
    StakeExtendedKey,
 
46
 
 
47
    -- * Internal conversion functions
 
48
    toShelleyAddr,
 
49
    toShelleyStakeAddr,
 
50
    toShelleyStakeCredential,
 
51
    fromShelleyAddr,
 
52
    fromShelleyPaymentCredential,
 
53
    fromShelleyStakeAddr,
 
54
    fromShelleyStakeCredential,
 
55
    fromShelleyStakeReference,
 
56
 
 
57
    -- * Serialising addresses
 
58
    SerialiseAddress(..),
 
59
 
 
60
    -- * Data family instances
 
61
    AsType(AsByronAddr, AsShelleyAddr, AsByronAddress, AsShelleyAddress,
 
62
           AsAddress, AsAddressAny, AsAddressInEra, AsStakeAddress)
 
63
  ) where
 
64
 
 
65
import           Prelude
 
66
 
 
67
import           Data.Aeson (ToJSON (..))
 
68
import qualified Data.Aeson as Aeson
 
69
import qualified Data.ByteString.Base58 as Base58
 
70
import           Data.Text (Text)
 
71
import qualified Data.Text.Encoding as Text
 
72
 
 
73
import           Control.Applicative
 
74
 
 
75
import qualified Cardano.Chain.Common as Byron
 
76
 
 
77
import           Ouroboros.Consensus.Shelley.Protocol.Crypto (StandardCrypto)
 
78
 
 
79
import qualified Shelley.Spec.Ledger.Address as Shelley
 
80
import qualified Shelley.Spec.Ledger.BaseTypes as Shelley
 
81
import qualified Shelley.Spec.Ledger.Credential as Shelley
 
82
 
 
83
import           Cardano.Api.Eras
 
84
import           Cardano.Api.Hash
 
85
import           Cardano.Api.HasTypeProxy
 
86
import           Cardano.Api.Key
 
87
import           Cardano.Api.KeysByron
 
88
import           Cardano.Api.KeysShelley
 
89
import           Cardano.Api.NetworkId
 
90
import           Cardano.Api.Script
 
91
import           Cardano.Api.SerialiseBech32
 
92
import           Cardano.Api.SerialiseRaw
 
93
 
 
94
 
 
95
-- ----------------------------------------------------------------------------
 
96
-- Address Serialisation
 
97
--
 
98
 
 
99
-- | Address serialisation uses different serialisation formats for different
 
100
-- kinds of addresses, so it needs its own class.
 
101
--
 
102
-- In particular, Byron addresses are typically formatted in base 58, while
 
103
-- Shelley addresses (payment and stake) are formatted using Bech32.
 
104
--
 
105
class HasTypeProxy addr => SerialiseAddress addr where
 
106
 
 
107
    serialiseAddress :: addr -> Text
 
108
 
 
109
    deserialiseAddress :: AsType addr -> Text -> Maybe addr
 
110
    -- TODO: consider adding data AddressDecodeError
 
111
 
 
112
 
 
113
-- ----------------------------------------------------------------------------
 
114
-- Payment address types
 
115
--
 
116
 
 
117
-- | A type used as a tag to distinguish Byron addresses.
 
118
data ByronAddr
 
119
 
 
120
-- | A type used as a tag to distinguish Shelley addresses.
 
121
data ShelleyAddr
 
122
 
 
123
instance HasTypeProxy ByronAddr where
 
124
    data AsType ByronAddr = AsByronAddr
 
125
    proxyToAsType _ = AsByronAddr
 
126
 
 
127
instance HasTypeProxy ShelleyAddr where
 
128
    data AsType ShelleyAddr = AsShelleyAddr
 
129
    proxyToAsType _ = AsShelleyAddr
 
130
 
 
131
 
 
132
-- ----------------------------------------------------------------------------
 
133
-- Payment addresses
 
134
--
 
135
 
 
136
-- | Addresses are used as locations where assets live. The address determines
 
137
-- the rights needed to spend assets at the address: in particular holding some
 
138
-- signing key or being able to satisfy the conditions of a script.
 
139
--
 
140
-- There are currently two types of address:
 
141
--
 
142
-- * Byron addresses, which use the type tag 'ByronAddr'; and
 
143
-- * Shelley addresses, which use the type tag 'ShelleyAddr'. Notably, Shelley
 
144
--   addresses support scripts and stake delegation.
 
145
--
 
146
-- The /address type/ is subtly from the /ledger era/ in which each
 
147
-- address type is valid: while Byron addresses are the only choice in the
 
148
-- Byron era, the Shelley era and all subsequent eras support both Byron and
 
149
-- Shelley addresses. The 'Address' type param only says the type of the address
 
150
-- (either Byron or Shelley). The 'AddressInEra' type connects the address type
 
151
-- with the era in which it is supported.
 
152
--
 
153
data Address addrtype where
 
154
 
 
155
     -- | Byron addresses were the only supported address type in the original
 
156
     -- Byron era.
 
157
     --
 
158
     ByronAddress
 
159
       :: Byron.Address
 
160
       -> Address ByronAddr
 
161
 
 
162
     -- | Shelley addresses allow delegation. Shelley addresses were introduced
 
163
     -- in Shelley era and are thus supported from the Shelley era onwards
 
164
     --
 
165
     ShelleyAddress
 
166
       :: Shelley.Network
 
167
       -> Shelley.PaymentCredential StandardCrypto
 
168
       -> Shelley.StakeReference    StandardCrypto
 
169
       -> Address ShelleyAddr
 
170
       -- Note that the two ledger credential types here are parametrised by
 
171
       -- the era, but in fact this is a phantom type parameter and they are
 
172
       -- the same for all eras. See 'toShelleyAddr' below.
 
173
 
 
174
deriving instance Eq   (Address addrtype)
 
175
deriving instance Ord  (Address addrtype)
 
176
deriving instance Show (Address addrtype)
 
177
 
 
178
 
 
179
instance HasTypeProxy addrtype => HasTypeProxy (Address addrtype) where
 
180
    data AsType (Address addrtype) = AsAddress (AsType addrtype)
 
181
    proxyToAsType _ = AsAddress (proxyToAsType (Proxy :: Proxy addrtype))
 
182
 
 
183
pattern AsByronAddress :: AsType (Address ByronAddr)
 
184
pattern AsByronAddress   = AsAddress AsByronAddr
 
185
{-# COMPLETE AsByronAddress #-}
 
186
 
 
187
pattern AsShelleyAddress :: AsType (Address ShelleyAddr)
 
188
pattern AsShelleyAddress = AsAddress AsShelleyAddr
 
189
{-# COMPLETE AsShelleyAddress #-}
 
190
 
 
191
instance SerialiseAsRawBytes (Address ByronAddr) where
 
192
    serialiseToRawBytes (ByronAddress addr) =
 
193
        Shelley.serialiseAddr
 
194
      . Shelley.AddrBootstrap
 
195
      . Shelley.BootstrapAddress
 
196
      $ addr
 
197
 
 
198
    deserialiseFromRawBytes (AsAddress AsByronAddr) bs =
 
199
        case Shelley.deserialiseAddr bs :: Maybe (Shelley.Addr StandardCrypto) of
 
200
          Nothing             -> Nothing
 
201
          Just Shelley.Addr{} -> Nothing
 
202
          Just (Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)) ->
 
203
            Just (ByronAddress addr)
 
204
 
 
205
instance SerialiseAsRawBytes (Address ShelleyAddr) where
 
206
    serialiseToRawBytes (ShelleyAddress nw pc scr) =
 
207
        Shelley.serialiseAddr (Shelley.Addr nw pc scr)
 
208
 
 
209
    deserialiseFromRawBytes (AsAddress AsShelleyAddr) bs =
 
210
        case Shelley.deserialiseAddr bs of
 
211
          Nothing                       -> Nothing
 
212
          Just Shelley.AddrBootstrap{}  -> Nothing
 
213
          Just (Shelley.Addr nw pc scr) -> Just (ShelleyAddress nw pc scr)
 
214
 
 
215
instance SerialiseAsBech32 (Address ShelleyAddr) where
 
216
    bech32PrefixFor (ShelleyAddress Shelley.Mainnet _ _) = "addr"
 
217
    bech32PrefixFor (ShelleyAddress Shelley.Testnet _ _) = "addr_test"
 
218
 
 
219
    bech32PrefixesPermitted (AsAddress AsShelleyAddr) = ["addr", "addr_test"]
 
220
 
 
221
 
 
222
instance SerialiseAddress (Address ByronAddr) where
 
223
    serialiseAddress addr@ByronAddress{} =
 
224
         Text.decodeLatin1
 
225
       . Base58.encodeBase58 Base58.bitcoinAlphabet
 
226
       . serialiseToRawBytes
 
227
       $ addr
 
228
 
 
229
    deserialiseAddress (AsAddress AsByronAddr) txt = do
 
230
      bs <- Base58.decodeBase58 Base58.bitcoinAlphabet (Text.encodeUtf8 txt)
 
231
      deserialiseFromRawBytes (AsAddress AsByronAddr) bs
 
232
 
 
233
instance SerialiseAddress (Address ShelleyAddr) where
 
234
    serialiseAddress addr@ShelleyAddress{} =
 
235
      serialiseToBech32 addr
 
236
 
 
237
    deserialiseAddress (AsAddress AsShelleyAddr) t =
 
238
      either (const Nothing) Just $
 
239
      deserialiseFromBech32 (AsAddress AsShelleyAddr) t
 
240
 
 
241
 
 
242
makeByronAddress :: NetworkId
 
243
                 -> VerificationKey ByronKey
 
244
                 -> Address ByronAddr
 
245
makeByronAddress nw (ByronVerificationKey vk) =
 
246
    ByronAddress $
 
247
      Byron.makeVerKeyAddress
 
248
        (toByronNetworkMagic nw)
 
249
        vk
 
250
 
 
251
 
 
252
makeShelleyAddress :: NetworkId
 
253
                   -> PaymentCredential
 
254
                   -> StakeAddressReference
 
255
                   -> Address ShelleyAddr
 
256
makeShelleyAddress nw pc scr =
 
257
    ShelleyAddress
 
258
      (toShelleyNetwork nw)
 
259
      (toShelleyPaymentCredential pc)
 
260
      (toShelleyStakeReference scr)
 
261
 
 
262
 
 
263
-- ----------------------------------------------------------------------------
 
264
-- Either type of address
 
265
--
 
266
 
 
267
-- | Either a Byron address or a Shelley address.
 
268
--
 
269
-- Sometimes we need to be able to work with either of the two types of
 
270
-- address (Byron or Shelley addresses), but without reference to an era in
 
271
-- which the address will be used. This type serves that purpose.
 
272
--
 
273
data AddressAny = AddressByron   !(Address ByronAddr)
 
274
                | AddressShelley !(Address ShelleyAddr)
 
275
  deriving (Eq, Ord, Show)
 
276
 
 
277
instance HasTypeProxy AddressAny where
 
278
    data AsType AddressAny = AsAddressAny
 
279
    proxyToAsType _ = AsAddressAny
 
280
 
 
281
instance SerialiseAsRawBytes AddressAny where
 
282
    serialiseToRawBytes (AddressByron   addr) = serialiseToRawBytes addr
 
283
    serialiseToRawBytes (AddressShelley addr) = serialiseToRawBytes addr
 
284
 
 
285
    deserialiseFromRawBytes AsAddressAny bs =
 
286
      case Shelley.deserialiseAddr bs of
 
287
        Nothing -> Nothing
 
288
        Just (Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)) ->
 
289
          Just (AddressByron (ByronAddress addr))
 
290
 
 
291
        Just (Shelley.Addr nw pc scr) ->
 
292
          Just (AddressShelley (ShelleyAddress nw pc scr))
 
293
 
 
294
instance SerialiseAddress AddressAny where
 
295
    serialiseAddress (AddressByron   addr) = serialiseAddress addr
 
296
    serialiseAddress (AddressShelley addr) = serialiseAddress addr
 
297
 
 
298
    deserialiseAddress AsAddressAny t =
 
299
          (AddressByron   <$> deserialiseAddress (AsAddress AsByronAddr)   t)
 
300
      <|> (AddressShelley <$> deserialiseAddress (AsAddress AsShelleyAddr) t)
 
301
 
 
302
 
 
303
-- ----------------------------------------------------------------------------
 
304
-- Addresses in the context of a ledger era
 
305
--
 
306
 
 
307
-- | An 'Address' that can be used in a particular ledger era.
 
308
--
 
309
-- All current ledger eras support Byron addresses. Shelley addresses are
 
310
-- supported in the 'ShelleyEra' and later eras.
 
311
--
 
312
data AddressInEra era where
 
313
     AddressInEra :: AddressTypeInEra addrtype era
 
314
                  -> Address addrtype
 
315
                  -> AddressInEra era
 
316
 
 
317
instance IsCardanoEra era => ToJSON (AddressInEra era) where
 
318
  toJSON = Aeson.String . serialiseAddress
 
319
 
 
320
instance Eq (AddressInEra era) where
 
321
  (==) (AddressInEra ByronAddressInAnyEra addr1)
 
322
       (AddressInEra ByronAddressInAnyEra addr2) = addr1 == addr2
 
323
 
 
324
  (==) (AddressInEra ShelleyAddressInEra{} addr1)
 
325
       (AddressInEra ShelleyAddressInEra{} addr2) = addr1 == addr2
 
326
 
 
327
  (==) (AddressInEra ByronAddressInAnyEra _)
 
328
       (AddressInEra ShelleyAddressInEra{} _) = False
 
329
 
 
330
  (==) (AddressInEra ShelleyAddressInEra{} _)
 
331
       (AddressInEra ByronAddressInAnyEra _) = False
 
332
 
 
333
deriving instance Show (AddressInEra era)
 
334
 
 
335
data AddressTypeInEra addrtype era where
 
336
 
 
337
     ByronAddressInAnyEra :: AddressTypeInEra ByronAddr era
 
338
 
 
339
     ShelleyAddressInEra  :: ShelleyBasedEra era
 
340
                          -> AddressTypeInEra ShelleyAddr era
 
341
 
 
342
deriving instance Show (AddressTypeInEra addrtype era)
 
343
 
 
344
 
 
345
instance HasTypeProxy era => HasTypeProxy (AddressInEra era) where
 
346
    data AsType (AddressInEra era) = AsAddressInEra (AsType era)
 
347
    proxyToAsType _ = AsAddressInEra (proxyToAsType (Proxy :: Proxy era))
 
348
 
 
349
instance IsCardanoEra era => SerialiseAsRawBytes (AddressInEra era) where
 
350
 
 
351
    serialiseToRawBytes (AddressInEra ByronAddressInAnyEra addr) =
 
352
      serialiseToRawBytes addr
 
353
 
 
354
    serialiseToRawBytes (AddressInEra ShelleyAddressInEra{} addr) =
 
355
      serialiseToRawBytes addr
 
356
 
 
357
    deserialiseFromRawBytes _ bs =
 
358
      anyAddressInEra cardanoEra =<< deserialiseFromRawBytes AsAddressAny bs
 
359
 
 
360
instance IsCardanoEra era => SerialiseAddress (AddressInEra era) where
 
361
    serialiseAddress (AddressInEra ByronAddressInAnyEra addr) =
 
362
      serialiseAddress addr
 
363
 
 
364
    serialiseAddress (AddressInEra ShelleyAddressInEra{} addr) =
 
365
      serialiseAddress addr
 
366
 
 
367
    deserialiseAddress _ t =
 
368
      anyAddressInEra cardanoEra =<< deserialiseAddress AsAddressAny t
 
369
 
 
370
 
 
371
byronAddressInEra :: Address ByronAddr -> AddressInEra era
 
372
byronAddressInEra = AddressInEra ByronAddressInAnyEra
 
373
 
 
374
 
 
375
shelleyAddressInEra :: IsShelleyBasedEra era
 
376
                    => Address ShelleyAddr -> AddressInEra era
 
377
shelleyAddressInEra = AddressInEra (ShelleyAddressInEra shelleyBasedEra)
 
378
 
 
379
 
 
380
anyAddressInShelleyBasedEra :: IsShelleyBasedEra era
 
381
                            => AddressAny -> AddressInEra era
 
382
anyAddressInShelleyBasedEra (AddressByron   addr) = byronAddressInEra addr
 
383
anyAddressInShelleyBasedEra (AddressShelley addr) = shelleyAddressInEra addr
 
384
 
 
385
 
 
386
anyAddressInEra :: CardanoEra era
 
387
                -> AddressAny
 
388
                -> Maybe (AddressInEra era)
 
389
anyAddressInEra _ (AddressByron addr) =
 
390
    Just (AddressInEra ByronAddressInAnyEra addr)
 
391
 
 
392
anyAddressInEra era (AddressShelley addr) =
 
393
    case cardanoEraStyle era of
 
394
      LegacyByronEra       -> Nothing
 
395
      ShelleyBasedEra era' -> Just (AddressInEra (ShelleyAddressInEra era') addr)
 
396
 
 
397
toAddressAny :: Address addr -> AddressAny
 
398
toAddressAny a@ShelleyAddress{} = AddressShelley a
 
399
toAddressAny a@ByronAddress{}   = AddressByron a
 
400
 
 
401
makeByronAddressInEra :: NetworkId
 
402
                      -> VerificationKey ByronKey
 
403
                      -> AddressInEra era
 
404
makeByronAddressInEra nw vk =
 
405
    byronAddressInEra (makeByronAddress nw vk)
 
406
 
 
407
 
 
408
makeShelleyAddressInEra :: IsShelleyBasedEra era
 
409
                        => NetworkId
 
410
                        -> PaymentCredential
 
411
                        -> StakeAddressReference
 
412
                        -> AddressInEra era
 
413
makeShelleyAddressInEra nw pc scr =
 
414
    shelleyAddressInEra (makeShelleyAddress nw pc scr)
 
415
 
 
416
 
 
417
-- ----------------------------------------------------------------------------
 
418
-- Stake addresses
 
419
--
 
420
 
 
421
data StakeAddress where
 
422
 
 
423
     StakeAddress
 
424
       :: Shelley.Network
 
425
       -> Shelley.StakeCredential StandardCrypto
 
426
       -> StakeAddress
 
427
  deriving (Eq, Ord, Show)
 
428
 
 
429
data PaymentCredential
 
430
       = PaymentCredentialByKey    (Hash PaymentKey)
 
431
       | PaymentCredentialByScript  ScriptHash
 
432
  deriving (Eq, Ord, Show)
 
433
 
 
434
data StakeCredential
 
435
       = StakeCredentialByKey    (Hash StakeKey)
 
436
       | StakeCredentialByScript  ScriptHash
 
437
  deriving (Eq, Ord, Show)
 
438
 
 
439
data StakeAddressReference
 
440
       = StakeAddressByValue   StakeCredential
 
441
       | StakeAddressByPointer StakeAddressPointer
 
442
       | NoStakeAddress
 
443
  deriving (Eq, Show)
 
444
 
 
445
--TODO: wrap this type properly and export it
 
446
type StakeAddressPointer = Shelley.Ptr
 
447
 
 
448
 
 
449
instance HasTypeProxy StakeAddress where
 
450
    data AsType StakeAddress = AsStakeAddress
 
451
    proxyToAsType _ = AsStakeAddress
 
452
 
 
453
 
 
454
instance SerialiseAsRawBytes StakeAddress where
 
455
    serialiseToRawBytes (StakeAddress nw sc) =
 
456
        Shelley.serialiseRewardAcnt (Shelley.RewardAcnt nw sc)
 
457
 
 
458
    deserialiseFromRawBytes AsStakeAddress bs =
 
459
        case Shelley.deserialiseRewardAcnt bs of
 
460
          Nothing -> Nothing
 
461
          Just (Shelley.RewardAcnt nw sc) -> Just (StakeAddress nw sc)
 
462
 
 
463
 
 
464
instance SerialiseAsBech32 StakeAddress where
 
465
    bech32PrefixFor (StakeAddress Shelley.Mainnet _) = "stake"
 
466
    bech32PrefixFor (StakeAddress Shelley.Testnet _) = "stake_test"
 
467
 
 
468
    bech32PrefixesPermitted AsStakeAddress = ["stake", "stake_test"]
 
469
 
 
470
 
 
471
instance SerialiseAddress StakeAddress where
 
472
    serialiseAddress addr@StakeAddress{} =
 
473
      serialiseToBech32 addr
 
474
 
 
475
    deserialiseAddress AsStakeAddress t =
 
476
      either (const Nothing) Just $
 
477
      deserialiseFromBech32 AsStakeAddress t
 
478
 
 
479
 
 
480
makeStakeAddress :: NetworkId
 
481
                 -> StakeCredential
 
482
                 -> StakeAddress
 
483
makeStakeAddress nw sc =
 
484
    StakeAddress
 
485
      (toShelleyNetwork nw)
 
486
      (toShelleyStakeCredential sc)
 
487
 
 
488
 
 
489
-- ----------------------------------------------------------------------------
 
490
-- Internal conversion functions
 
491
--
 
492
 
 
493
toShelleyAddr :: AddressInEra era -> Shelley.Addr StandardCrypto
 
494
toShelleyAddr (AddressInEra ByronAddressInAnyEra (ByronAddress addr)) =
 
495
    Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)
 
496
toShelleyAddr (AddressInEra (ShelleyAddressInEra _)
 
497
                            (ShelleyAddress nw pc scr)) =
 
498
    Shelley.Addr nw pc scr
 
499
 
 
500
toShelleyStakeAddr :: StakeAddress -> Shelley.RewardAcnt StandardCrypto
 
501
toShelleyStakeAddr (StakeAddress nw sc) =
 
502
    Shelley.RewardAcnt {
 
503
      Shelley.getRwdNetwork = nw,
 
504
      Shelley.getRwdCred    = sc
 
505
    }
 
506
 
 
507
toShelleyPaymentCredential :: PaymentCredential
 
508
                           -> Shelley.PaymentCredential StandardCrypto
 
509
toShelleyPaymentCredential (PaymentCredentialByKey (PaymentKeyHash kh)) =
 
510
    Shelley.KeyHashObj kh
 
511
toShelleyPaymentCredential (PaymentCredentialByScript sh) =
 
512
    Shelley.ScriptHashObj (toShelleyScriptHash sh)
 
513
 
 
514
toShelleyStakeCredential :: StakeCredential
 
515
                         -> Shelley.StakeCredential StandardCrypto
 
516
toShelleyStakeCredential (StakeCredentialByKey (StakeKeyHash kh)) =
 
517
    Shelley.KeyHashObj kh
 
518
toShelleyStakeCredential (StakeCredentialByScript sh) =
 
519
    Shelley.ScriptHashObj (toShelleyScriptHash sh)
 
520
 
 
521
toShelleyStakeReference :: StakeAddressReference
 
522
                        -> Shelley.StakeReference StandardCrypto
 
523
toShelleyStakeReference (StakeAddressByValue stakecred) =
 
524
    Shelley.StakeRefBase (toShelleyStakeCredential stakecred)
 
525
toShelleyStakeReference (StakeAddressByPointer ptr) =
 
526
    Shelley.StakeRefPtr ptr
 
527
toShelleyStakeReference  NoStakeAddress =
 
528
    Shelley.StakeRefNull
 
529
 
 
530
 
 
531
fromShelleyAddr :: IsShelleyBasedEra era
 
532
                => Shelley.Addr StandardCrypto -> AddressInEra era
 
533
fromShelleyAddr (Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)) =
 
534
    AddressInEra ByronAddressInAnyEra (ByronAddress addr)
 
535
 
 
536
fromShelleyAddr (Shelley.Addr nw pc scr) =
 
537
    AddressInEra
 
538
      (ShelleyAddressInEra shelleyBasedEra)
 
539
      (ShelleyAddress nw pc scr)
 
540
 
 
541
fromShelleyStakeAddr :: Shelley.RewardAcnt StandardCrypto -> StakeAddress
 
542
fromShelleyStakeAddr (Shelley.RewardAcnt nw sc) = StakeAddress nw sc
 
543
 
 
544
fromShelleyStakeCredential :: Shelley.StakeCredential StandardCrypto
 
545
                           -> StakeCredential
 
546
fromShelleyStakeCredential (Shelley.KeyHashObj kh) =
 
547
    StakeCredentialByKey (StakeKeyHash kh)
 
548
fromShelleyStakeCredential (Shelley.ScriptHashObj sh) =
 
549
    StakeCredentialByScript (fromShelleyScriptHash sh)
 
550
 
 
551
fromShelleyPaymentCredential :: Shelley.PaymentCredential StandardCrypto
 
552
                             -> PaymentCredential
 
553
fromShelleyPaymentCredential (Shelley.KeyHashObj kh) =
 
554
  PaymentCredentialByKey (PaymentKeyHash kh)
 
555
fromShelleyPaymentCredential (Shelley.ScriptHashObj sh) =
 
556
  PaymentCredentialByScript (ScriptHash sh)
 
557
 
 
558
fromShelleyStakeReference :: Shelley.StakeReference StandardCrypto
 
559
                          -> StakeAddressReference
 
560
fromShelleyStakeReference (Shelley.StakeRefBase stakecred) =
 
561
  StakeAddressByValue (fromShelleyStakeCredential stakecred)
 
562
fromShelleyStakeReference (Shelley.StakeRefPtr ptr) =
 
563
  StakeAddressByPointer ptr
 
564
fromShelleyStakeReference Shelley.StakeRefNull =
 
565
  NoStakeAddress