-
Notifications
You must be signed in to change notification settings - Fork 720
/
Copy pathAddress.hs
720 lines (570 loc) · 24.6 KB
/
Address.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{- HLINT ignore "Avoid lambda using `infix`" -}
-- | Cardano addresses: payment and stake addresses.
--
module Cardano.Api.Address (
-- * Payment addresses
-- | Constructing and inspecting normal payment addresses
Address(..),
-- ** Byron addresses
ByronAddr,
makeByronAddress,
-- ** Shelley addresses
ShelleyAddr,
makeShelleyAddress,
PaymentCredential(..),
StakeAddressReference(..),
StakeAddressPointer(..),
-- ** Addresses in any era
AddressAny(..),
lexPlausibleAddressString,
parseAddressAny,
-- ** Addresses in specific eras
AddressInEra(..),
AddressTypeInEra(..),
byronAddressInEra,
shelleyAddressInEra,
anyAddressInShelleyBasedEra,
anyAddressInEra,
toAddressAny,
makeByronAddressInEra,
makeShelleyAddressInEra,
-- * Stake addresses
-- | Constructing and inspecting stake addresses
StakeAddress(..),
StakeCredential(..),
makeStakeAddress,
StakeKey,
StakeExtendedKey,
-- * Conversion functions
shelleyPayAddrToPlutusPubKHash,
-- * Internal conversion functions
toShelleyAddr,
toShelleyStakeAddr,
toShelleyStakeCredential,
fromShelleyAddr,
fromShelleyAddrIsSbe,
fromShelleyAddrToAny,
fromShelleyPaymentCredential,
fromShelleyStakeAddr,
fromShelleyStakeCredential,
fromShelleyStakeReference,
-- * Serialising addresses
SerialiseAddress(..),
-- * Data family instances
AsType(AsByronAddr, AsShelleyAddr, AsByronAddress, AsShelleyAddress,
AsAddress, AsAddressAny, AsAddressInEra, AsStakeAddress),
-- * Helpers
isKeyAddress
) where
import Prelude
import Control.Applicative ((<|>))
import Data.Aeson (FromJSON (..), ToJSON (..), withText, (.=))
import qualified Data.Aeson as Aeson
import qualified Data.ByteString.Base58 as Base58
import Data.Char (isAsciiLower, isAsciiUpper, isDigit)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.Typeable (Typeable)
import qualified Text.Parsec as Parsec
import qualified Text.Parsec.String as Parsec
import qualified Cardano.Chain.Common as Byron
import qualified Cardano.Ledger.Address as Shelley
import qualified Cardano.Ledger.Alonzo.TxInfo as Alonzo
import qualified Cardano.Ledger.BaseTypes as Shelley
import qualified Cardano.Ledger.Credential as Shelley
import Cardano.Ledger.Crypto (StandardCrypto)
import qualified Plutus.V1.Ledger.Api as Plutus
import Cardano.Api.EraCast
import Cardano.Api.Eras
import Cardano.Api.Hash
import Cardano.Api.HasTypeProxy
import Cardano.Api.Key
import Cardano.Api.KeysByron
import Cardano.Api.KeysShelley
import Cardano.Api.NetworkId
import Cardano.Api.Script
import Cardano.Api.SerialiseBech32
import Cardano.Api.SerialiseRaw
import Cardano.Api.Utils
import Control.DeepSeq (NFData (..), deepseq)
-- ----------------------------------------------------------------------------
-- Address Serialisation
--
-- | Address serialisation uses different serialisation formats for different
-- kinds of addresses, so it needs its own class.
--
-- In particular, Byron addresses are typically formatted in base 58, while
-- Shelley addresses (payment and stake) are formatted using Bech32.
--
class HasTypeProxy addr => SerialiseAddress addr where
serialiseAddress :: addr -> Text
deserialiseAddress :: AsType addr -> Text -> Maybe addr
-- TODO: consider adding data AddressDecodeError
-- ----------------------------------------------------------------------------
-- Payment address types
--
-- | A type used as a tag to distinguish Byron addresses.
data ByronAddr
-- | A type used as a tag to distinguish Shelley addresses.
data ShelleyAddr
instance HasTypeProxy ByronAddr where
data AsType ByronAddr = AsByronAddr
proxyToAsType _ = AsByronAddr
instance HasTypeProxy ShelleyAddr where
data AsType ShelleyAddr = AsShelleyAddr
proxyToAsType _ = AsShelleyAddr
-- ----------------------------------------------------------------------------
-- Payment addresses
--
-- | Addresses are used as locations where assets live. The address determines
-- the rights needed to spend assets at the address: in particular holding some
-- signing key or being able to satisfy the conditions of a script.
--
-- There are currently two types of address:
--
-- * Byron addresses, which use the type tag 'ByronAddr'; and
-- * Shelley addresses, which use the type tag 'ShelleyAddr'. Notably, Shelley
-- addresses support scripts and stake delegation.
--
-- The /address type/ is subtly from the /ledger era/ in which each
-- address type is valid: while Byron addresses are the only choice in the
-- Byron era, the Shelley era and all subsequent eras support both Byron and
-- Shelley addresses. The 'Address' type param only says the type of the address
-- (either Byron or Shelley). The 'AddressInEra' type connects the address type
-- with the era in which it is supported.
--
data Address addrtype where
-- | Byron addresses were the only supported address type in the original
-- Byron era.
--
ByronAddress
:: Byron.Address
-> Address ByronAddr
-- | Shelley addresses allow delegation. Shelley addresses were introduced
-- in Shelley era and are thus supported from the Shelley era onwards
--
ShelleyAddress
:: Shelley.Network
-> Shelley.PaymentCredential StandardCrypto
-> Shelley.StakeReference StandardCrypto
-> Address ShelleyAddr
-- Note that the two ledger credential types here are parametrised by
-- the era, but in fact this is a phantom type parameter and they are
-- the same for all eras. See 'toShelleyAddr' below.
deriving instance Eq (Address addrtype)
deriving instance Ord (Address addrtype)
deriving instance Show (Address addrtype)
instance NFData (Address addrtype) where
rnf = \case
ByronAddress address -> deepseq address ()
ShelleyAddress n pc sr -> deepseq (deepseq (deepseq n pc) sr) ()
instance HasTypeProxy addrtype => HasTypeProxy (Address addrtype) where
data AsType (Address addrtype) = AsAddress (AsType addrtype)
proxyToAsType _ = AsAddress (proxyToAsType (Proxy :: Proxy addrtype))
pattern AsByronAddress :: AsType (Address ByronAddr)
pattern AsByronAddress = AsAddress AsByronAddr
{-# COMPLETE AsByronAddress #-}
pattern AsShelleyAddress :: AsType (Address ShelleyAddr)
pattern AsShelleyAddress = AsAddress AsShelleyAddr
{-# COMPLETE AsShelleyAddress #-}
instance SerialiseAsRawBytes (Address ByronAddr) where
serialiseToRawBytes (ByronAddress addr) =
Shelley.serialiseAddr
. Shelley.AddrBootstrap
. Shelley.BootstrapAddress
$ addr
deserialiseFromRawBytes (AsAddress AsByronAddr) bs =
case Shelley.deserialiseAddr bs :: Maybe (Shelley.Addr StandardCrypto) of
Nothing -> Nothing
Just Shelley.Addr{} -> Nothing
Just (Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)) ->
Just (ByronAddress addr)
instance SerialiseAsRawBytes (Address ShelleyAddr) where
serialiseToRawBytes (ShelleyAddress nw pc scr) =
Shelley.serialiseAddr (Shelley.Addr nw pc scr)
deserialiseFromRawBytes (AsAddress AsShelleyAddr) bs =
case Shelley.deserialiseAddr bs of
Nothing -> Nothing
Just Shelley.AddrBootstrap{} -> Nothing
Just (Shelley.Addr nw pc scr) -> Just (ShelleyAddress nw pc scr)
instance SerialiseAsBech32 (Address ShelleyAddr) where
bech32PrefixFor (ShelleyAddress Shelley.Mainnet _ _) = "addr"
bech32PrefixFor (ShelleyAddress Shelley.Testnet _ _) = "addr_test"
bech32PrefixesPermitted (AsAddress AsShelleyAddr) = ["addr", "addr_test"]
instance SerialiseAddress (Address ByronAddr) where
serialiseAddress addr@ByronAddress{} =
Text.decodeLatin1
. Base58.encodeBase58 Base58.bitcoinAlphabet
. serialiseToRawBytes
$ addr
deserialiseAddress (AsAddress AsByronAddr) txt = do
bs <- Base58.decodeBase58 Base58.bitcoinAlphabet (Text.encodeUtf8 txt)
deserialiseFromRawBytes (AsAddress AsByronAddr) bs
instance SerialiseAddress (Address ShelleyAddr) where
serialiseAddress addr@ShelleyAddress{} =
serialiseToBech32 addr
deserialiseAddress (AsAddress AsShelleyAddr) t =
either (const Nothing) Just $
deserialiseFromBech32 (AsAddress AsShelleyAddr) t
instance ToJSON (Address ShelleyAddr) where
toJSON = Aeson.String . serialiseAddress
instance ToJSON (Address ByronAddr) where
toJSON = Aeson.String . serialiseAddress
instance FromJSON (Address ByronAddr) where
parseJSON = Aeson.withText "Address" $ \txt ->
maybe
(fail "Cardano.Api.Address.FromJSON: Invalid Byron address.")
pure
(deserialiseAddress AsByronAddress txt)
instance FromJSON (Address ShelleyAddr) where
parseJSON = Aeson.withText "Address" $ \txt ->
maybe
(fail "Cardano.Api.Address.FromJSON: Invalid Shelley address.")
pure
(deserialiseAddress AsShelleyAddress txt)
makeByronAddress :: NetworkId
-> VerificationKey ByronKey
-> Address ByronAddr
makeByronAddress nw (ByronVerificationKey vk) =
ByronAddress $
Byron.makeVerKeyAddress
(toByronNetworkMagic nw)
vk
makeShelleyAddress :: NetworkId
-> PaymentCredential
-> StakeAddressReference
-> Address ShelleyAddr
makeShelleyAddress nw pc scr =
ShelleyAddress
(toShelleyNetwork nw)
(toShelleyPaymentCredential pc)
(toShelleyStakeReference scr)
-- ----------------------------------------------------------------------------
-- Either type of address
--
-- | Either a Byron address or a Shelley address.
--
-- Sometimes we need to be able to work with either of the two types of
-- address (Byron or Shelley addresses), but without reference to an era in
-- which the address will be used. This type serves that purpose.
--
data AddressAny = AddressByron !(Address ByronAddr)
| AddressShelley !(Address ShelleyAddr)
deriving (Eq, Ord, Show)
instance HasTypeProxy AddressAny where
data AsType AddressAny = AsAddressAny
proxyToAsType _ = AsAddressAny
instance SerialiseAsRawBytes AddressAny where
serialiseToRawBytes (AddressByron addr) = serialiseToRawBytes addr
serialiseToRawBytes (AddressShelley addr) = serialiseToRawBytes addr
deserialiseFromRawBytes AsAddressAny bs =
case Shelley.deserialiseAddr bs of
Nothing -> Nothing
Just (Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)) ->
Just (AddressByron (ByronAddress addr))
Just (Shelley.Addr nw pc scr) ->
Just (AddressShelley (ShelleyAddress nw pc scr))
instance SerialiseAddress AddressAny where
serialiseAddress (AddressByron addr) = serialiseAddress addr
serialiseAddress (AddressShelley addr) = serialiseAddress addr
deserialiseAddress AsAddressAny t =
(AddressByron <$> deserialiseAddress (AsAddress AsByronAddr) t)
<|> (AddressShelley <$> deserialiseAddress (AsAddress AsShelleyAddr) t)
fromShelleyAddrToAny :: Shelley.Addr StandardCrypto -> AddressAny
fromShelleyAddrToAny (Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)) =
AddressByron $ ByronAddress addr
fromShelleyAddrToAny (Shelley.Addr nw pc scr) =
AddressShelley $ ShelleyAddress nw pc scr
-- ----------------------------------------------------------------------------
-- Addresses in the context of a ledger era
--
-- | An 'Address' that can be used in a particular ledger era.
--
-- All current ledger eras support Byron addresses. Shelley addresses are
-- supported in the 'ShelleyEra' and later eras.
--
data AddressInEra era where
AddressInEra :: AddressTypeInEra addrtype era
-> Address addrtype
-> AddressInEra era
instance NFData (AddressInEra era) where
rnf (AddressInEra t a) = deepseq (deepseq t a) ()
instance IsCardanoEra era => ToJSON (AddressInEra era) where
toJSON = Aeson.String . serialiseAddress
instance IsShelleyBasedEra era => FromJSON (AddressInEra era) where
parseJSON = withText "AddressInEra" $ \txt -> do
addressAny <- runParsecParser parseAddressAny txt
pure $ anyAddressInShelleyBasedEra addressAny
instance EraCast AddressInEra where
eraCast toEra' (AddressInEra addressTypeInEra address) = AddressInEra
<$> eraCast toEra' addressTypeInEra
<*> pure address
parseAddressAny :: Parsec.Parser AddressAny
parseAddressAny = do
str <- lexPlausibleAddressString
case deserialiseAddress AsAddressAny str of
Nothing -> fail $ "invalid address: " <> Text.unpack str
Just addr -> pure addr
lexPlausibleAddressString :: Parsec.Parser Text
lexPlausibleAddressString =
Text.pack <$> Parsec.many1 (Parsec.satisfy isPlausibleAddressChar)
where
-- Covers both base58 and bech32 (with constrained prefixes)
isPlausibleAddressChar c =
isAsciiLower c
|| isAsciiUpper c
|| isDigit c
|| c == '_'
instance Eq (AddressInEra era) where
(==) (AddressInEra ByronAddressInAnyEra addr1)
(AddressInEra ByronAddressInAnyEra addr2) = addr1 == addr2
(==) (AddressInEra ShelleyAddressInEra{} addr1)
(AddressInEra ShelleyAddressInEra{} addr2) = addr1 == addr2
(==) (AddressInEra ByronAddressInAnyEra _)
(AddressInEra ShelleyAddressInEra{} _) = False
(==) (AddressInEra ShelleyAddressInEra{} _)
(AddressInEra ByronAddressInAnyEra _) = False
instance Ord (AddressInEra era) where
compare (AddressInEra ByronAddressInAnyEra addr1)
(AddressInEra ByronAddressInAnyEra addr2) = compare addr1 addr2
compare (AddressInEra ShelleyAddressInEra{} addr1)
(AddressInEra ShelleyAddressInEra{} addr2) = compare addr1 addr2
compare (AddressInEra ByronAddressInAnyEra _)
(AddressInEra ShelleyAddressInEra{} _) = LT
compare (AddressInEra ShelleyAddressInEra{} _)
(AddressInEra ByronAddressInAnyEra _) = GT
deriving instance Show (AddressInEra era)
data AddressTypeInEra addrtype era where
ByronAddressInAnyEra :: AddressTypeInEra ByronAddr era
ShelleyAddressInEra :: ShelleyBasedEra era
-> AddressTypeInEra ShelleyAddr era
deriving instance Show (AddressTypeInEra addrtype era)
instance NFData (AddressTypeInEra addrtype era) where
rnf = \case
ByronAddressInAnyEra -> ()
ShelleyAddressInEra sbe -> deepseq sbe ()
instance HasTypeProxy era => HasTypeProxy (AddressInEra era) where
data AsType (AddressInEra era) = AsAddressInEra (AsType era)
proxyToAsType _ = AsAddressInEra (proxyToAsType (Proxy :: Proxy era))
instance (IsCardanoEra era, Typeable era) => SerialiseAsRawBytes (AddressInEra era) where
serialiseToRawBytes (AddressInEra ByronAddressInAnyEra addr) =
serialiseToRawBytes addr
serialiseToRawBytes (AddressInEra ShelleyAddressInEra{} addr) =
serialiseToRawBytes addr
deserialiseFromRawBytes _ bs =
anyAddressInEra cardanoEra =<< deserialiseFromRawBytes AsAddressAny bs
instance IsCardanoEra era => SerialiseAddress (AddressInEra era) where
serialiseAddress (AddressInEra ByronAddressInAnyEra addr) =
serialiseAddress addr
serialiseAddress (AddressInEra ShelleyAddressInEra{} addr) =
serialiseAddress addr
deserialiseAddress _ t =
anyAddressInEra cardanoEra =<< deserialiseAddress AsAddressAny t
instance EraCast (AddressTypeInEra addrtype) where
eraCast toEra' v = case v of
ByronAddressInAnyEra -> pure ByronAddressInAnyEra
ShelleyAddressInEra previousEra ->
case cardanoEraStyle toEra' of
LegacyByronEra -> Left $ EraCastError v (shelleyBasedToCardanoEra previousEra) toEra'
ShelleyBasedEra newSbe -> Right $ ShelleyAddressInEra newSbe
byronAddressInEra :: Address ByronAddr -> AddressInEra era
byronAddressInEra = AddressInEra ByronAddressInAnyEra
shelleyAddressInEra :: IsShelleyBasedEra era
=> Address ShelleyAddr -> AddressInEra era
shelleyAddressInEra = AddressInEra (ShelleyAddressInEra shelleyBasedEra)
anyAddressInShelleyBasedEra :: IsShelleyBasedEra era
=> AddressAny -> AddressInEra era
anyAddressInShelleyBasedEra (AddressByron addr) = byronAddressInEra addr
anyAddressInShelleyBasedEra (AddressShelley addr) = shelleyAddressInEra addr
anyAddressInEra :: CardanoEra era
-> AddressAny
-> Maybe (AddressInEra era)
anyAddressInEra _ (AddressByron addr) =
Just (AddressInEra ByronAddressInAnyEra addr)
anyAddressInEra era (AddressShelley addr) =
case cardanoEraStyle era of
LegacyByronEra -> Nothing
ShelleyBasedEra era' -> Just (AddressInEra (ShelleyAddressInEra era') addr)
toAddressAny :: Address addr -> AddressAny
toAddressAny a@ShelleyAddress{} = AddressShelley a
toAddressAny a@ByronAddress{} = AddressByron a
makeByronAddressInEra :: NetworkId
-> VerificationKey ByronKey
-> AddressInEra era
makeByronAddressInEra nw vk =
byronAddressInEra (makeByronAddress nw vk)
makeShelleyAddressInEra :: IsShelleyBasedEra era
=> NetworkId
-> PaymentCredential
-> StakeAddressReference
-> AddressInEra era
makeShelleyAddressInEra nw pc scr =
shelleyAddressInEra (makeShelleyAddress nw pc scr)
-- ----------------------------------------------------------------------------
-- Stake addresses
--
data StakeAddress where
StakeAddress
:: Shelley.Network
-> Shelley.StakeCredential StandardCrypto
-> StakeAddress
deriving (Eq, Ord, Show)
data PaymentCredential
= PaymentCredentialByKey (Hash PaymentKey)
| PaymentCredentialByScript ScriptHash
deriving (Eq, Ord, Show)
data StakeCredential
= StakeCredentialByKey (Hash StakeKey)
| StakeCredentialByScript ScriptHash
deriving (Eq, Ord, Show)
instance ToJSON StakeCredential where
toJSON =
Aeson.object
. \case
StakeCredentialByKey keyHash ->
["stakingKeyHash" .= serialiseToRawBytesHexText keyHash]
StakeCredentialByScript scriptHash ->
["stakingScriptHash" .= serialiseToRawBytesHexText scriptHash]
data StakeAddressReference
= StakeAddressByValue StakeCredential
| StakeAddressByPointer StakeAddressPointer
| NoStakeAddress
deriving (Eq, Show)
newtype StakeAddressPointer = StakeAddressPointer
{ unStakeAddressPointer :: Shelley.Ptr
}
deriving (Eq, Show)
instance HasTypeProxy StakeAddress where
data AsType StakeAddress = AsStakeAddress
proxyToAsType _ = AsStakeAddress
instance SerialiseAsRawBytes StakeAddress where
serialiseToRawBytes (StakeAddress nw sc) =
Shelley.serialiseRewardAcnt (Shelley.RewardAcnt nw sc)
deserialiseFromRawBytes AsStakeAddress bs =
case Shelley.deserialiseRewardAcnt bs of
Nothing -> Nothing
Just (Shelley.RewardAcnt nw sc) -> Just (StakeAddress nw sc)
instance SerialiseAsBech32 StakeAddress where
bech32PrefixFor (StakeAddress Shelley.Mainnet _) = "stake"
bech32PrefixFor (StakeAddress Shelley.Testnet _) = "stake_test"
bech32PrefixesPermitted AsStakeAddress = ["stake", "stake_test"]
instance SerialiseAddress StakeAddress where
serialiseAddress addr@StakeAddress{} =
serialiseToBech32 addr
deserialiseAddress AsStakeAddress t =
either (const Nothing) Just $
deserialiseFromBech32 AsStakeAddress t
instance ToJSON StakeAddress where
toJSON s = Aeson.String $ serialiseAddress s
instance FromJSON StakeAddress where
parseJSON = withText "StakeAddress" $ \str ->
case deserialiseAddress AsStakeAddress str of
Nothing ->
fail $ "Error while deserialising StakeAddress: " <> Text.unpack str
Just sAddr -> pure sAddr
makeStakeAddress :: NetworkId
-> StakeCredential
-> StakeAddress
makeStakeAddress nw sc =
StakeAddress
(toShelleyNetwork nw)
(toShelleyStakeCredential sc)
-- ----------------------------------------------------------------------------
-- Helpers
--
-- | Is the UTxO at the address only spendable via a key witness.
isKeyAddress :: AddressInEra era -> Bool
isKeyAddress (AddressInEra ByronAddressInAnyEra _) = True
isKeyAddress (AddressInEra (ShelleyAddressInEra _) (ShelleyAddress _ pCred _)) =
case fromShelleyPaymentCredential pCred of
PaymentCredentialByKey _ -> True
PaymentCredentialByScript _ -> False
-- | Converts a Shelley payment address to a Plutus public key hash.
shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe Plutus.PubKeyHash
shelleyPayAddrToPlutusPubKHash (ShelleyAddress _ payCred _) =
case payCred of
Shelley.ScriptHashObj _ -> Nothing
Shelley.KeyHashObj kHash -> Just $ Alonzo.transKeyHash kHash
-- ----------------------------------------------------------------------------
-- Internal conversion functions
--
toShelleyAddr :: AddressInEra era -> Shelley.Addr StandardCrypto
toShelleyAddr (AddressInEra ByronAddressInAnyEra (ByronAddress addr)) =
Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)
toShelleyAddr (AddressInEra (ShelleyAddressInEra _)
(ShelleyAddress nw pc scr)) =
Shelley.Addr nw pc scr
toShelleyStakeAddr :: StakeAddress -> Shelley.RewardAcnt StandardCrypto
toShelleyStakeAddr (StakeAddress nw sc) =
Shelley.RewardAcnt {
Shelley.getRwdNetwork = nw,
Shelley.getRwdCred = sc
}
toShelleyPaymentCredential :: PaymentCredential
-> Shelley.PaymentCredential StandardCrypto
toShelleyPaymentCredential (PaymentCredentialByKey (PaymentKeyHash kh)) =
Shelley.KeyHashObj kh
toShelleyPaymentCredential (PaymentCredentialByScript sh) =
Shelley.ScriptHashObj (toShelleyScriptHash sh)
toShelleyStakeCredential :: StakeCredential
-> Shelley.StakeCredential StandardCrypto
toShelleyStakeCredential (StakeCredentialByKey (StakeKeyHash kh)) =
Shelley.KeyHashObj kh
toShelleyStakeCredential (StakeCredentialByScript sh) =
Shelley.ScriptHashObj (toShelleyScriptHash sh)
toShelleyStakeReference :: StakeAddressReference
-> Shelley.StakeReference StandardCrypto
toShelleyStakeReference (StakeAddressByValue stakecred) =
Shelley.StakeRefBase (toShelleyStakeCredential stakecred)
toShelleyStakeReference (StakeAddressByPointer ptr) =
Shelley.StakeRefPtr (unStakeAddressPointer ptr)
toShelleyStakeReference NoStakeAddress =
Shelley.StakeRefNull
fromShelleyAddrIsSbe :: IsShelleyBasedEra era
=> Shelley.Addr StandardCrypto -> AddressInEra era
fromShelleyAddrIsSbe (Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)) =
AddressInEra ByronAddressInAnyEra (ByronAddress addr)
fromShelleyAddrIsSbe (Shelley.Addr nw pc scr) =
AddressInEra
(ShelleyAddressInEra shelleyBasedEra)
(ShelleyAddress nw pc scr)
fromShelleyAddr
:: ShelleyBasedEra era
-> Shelley.Addr StandardCrypto
-> AddressInEra era
fromShelleyAddr _ (Shelley.AddrBootstrap (Shelley.BootstrapAddress addr)) =
AddressInEra ByronAddressInAnyEra (ByronAddress addr)
fromShelleyAddr sBasedEra (Shelley.Addr nw pc scr) =
AddressInEra
(ShelleyAddressInEra sBasedEra)
(ShelleyAddress nw pc scr)
fromShelleyStakeAddr :: Shelley.RewardAcnt StandardCrypto -> StakeAddress
fromShelleyStakeAddr (Shelley.RewardAcnt nw sc) = StakeAddress nw sc
fromShelleyStakeCredential :: Shelley.StakeCredential StandardCrypto
-> StakeCredential
fromShelleyStakeCredential (Shelley.KeyHashObj kh) =
StakeCredentialByKey (StakeKeyHash kh)
fromShelleyStakeCredential (Shelley.ScriptHashObj sh) =
StakeCredentialByScript (fromShelleyScriptHash sh)
fromShelleyPaymentCredential :: Shelley.PaymentCredential StandardCrypto
-> PaymentCredential
fromShelleyPaymentCredential (Shelley.KeyHashObj kh) =
PaymentCredentialByKey (PaymentKeyHash kh)
fromShelleyPaymentCredential (Shelley.ScriptHashObj sh) =
PaymentCredentialByScript (ScriptHash sh)
fromShelleyStakeReference :: Shelley.StakeReference StandardCrypto
-> StakeAddressReference
fromShelleyStakeReference (Shelley.StakeRefBase stakecred) =
StakeAddressByValue (fromShelleyStakeCredential stakecred)
fromShelleyStakeReference (Shelley.StakeRefPtr ptr) =
StakeAddressByPointer (StakeAddressPointer ptr)
fromShelleyStakeReference Shelley.StakeRefNull =
NoStakeAddress