-- | Address in Tezos.

module Tezos.Address
  ( ContractHash (..)
  , Address (..)
  , mkKeyAddress
  , detGenKeyAddress
  , mkContractAddressRaw
  , mkContractHashRaw

  -- * Formatting
  , ParseAddressError (..)
  , ParseContractAddressError
  , formatAddress
  , mformatAddress
  , parseAddress
  , unsafeParseAddress
  , unsafeParseContractHash
  ) where

import Data.Aeson (FromJSON(..), FromJSONKey, ToJSON(..), ToJSONKey)
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Encoding as Aeson
import qualified Data.Aeson.Types as AesonTypes
import qualified Data.ByteString as BS
import Fmt (fmt, hexF, pretty)
import qualified Formatting.Buildable as Buildable
import Test.QuickCheck (Arbitrary(..), oneof, vector)

import Michelson.Text
import Tezos.Crypto
import Util.CLI

-- TODO: we should probably have a `Hash` type.
-- | Hash of origination command for some contract.
newtype ContractHash = ContractHash ByteString
  deriving stock (Int -> ContractHash -> ShowS
[ContractHash] -> ShowS
ContractHash -> String
(Int -> ContractHash -> ShowS)
-> (ContractHash -> String)
-> ([ContractHash] -> ShowS)
-> Show ContractHash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContractHash] -> ShowS
$cshowList :: [ContractHash] -> ShowS
show :: ContractHash -> String
$cshow :: ContractHash -> String
showsPrec :: Int -> ContractHash -> ShowS
$cshowsPrec :: Int -> ContractHash -> ShowS
Show, ContractHash -> ContractHash -> Bool
(ContractHash -> ContractHash -> Bool)
-> (ContractHash -> ContractHash -> Bool) -> Eq ContractHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContractHash -> ContractHash -> Bool
$c/= :: ContractHash -> ContractHash -> Bool
== :: ContractHash -> ContractHash -> Bool
$c== :: ContractHash -> ContractHash -> Bool
Eq, Eq ContractHash
Eq ContractHash =>
(ContractHash -> ContractHash -> Ordering)
-> (ContractHash -> ContractHash -> Bool)
-> (ContractHash -> ContractHash -> Bool)
-> (ContractHash -> ContractHash -> Bool)
-> (ContractHash -> ContractHash -> Bool)
-> (ContractHash -> ContractHash -> ContractHash)
-> (ContractHash -> ContractHash -> ContractHash)
-> Ord ContractHash
ContractHash -> ContractHash -> Bool
ContractHash -> ContractHash -> Ordering
ContractHash -> ContractHash -> ContractHash
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ContractHash -> ContractHash -> ContractHash
$cmin :: ContractHash -> ContractHash -> ContractHash
max :: ContractHash -> ContractHash -> ContractHash
$cmax :: ContractHash -> ContractHash -> ContractHash
>= :: ContractHash -> ContractHash -> Bool
$c>= :: ContractHash -> ContractHash -> Bool
> :: ContractHash -> ContractHash -> Bool
$c> :: ContractHash -> ContractHash -> Bool
<= :: ContractHash -> ContractHash -> Bool
$c<= :: ContractHash -> ContractHash -> Bool
< :: ContractHash -> ContractHash -> Bool
$c< :: ContractHash -> ContractHash -> Bool
compare :: ContractHash -> ContractHash -> Ordering
$ccompare :: ContractHash -> ContractHash -> Ordering
$cp1Ord :: Eq ContractHash
Ord, (forall x. ContractHash -> Rep ContractHash x)
-> (forall x. Rep ContractHash x -> ContractHash)
-> Generic ContractHash
forall x. Rep ContractHash x -> ContractHash
forall x. ContractHash -> Rep ContractHash x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContractHash x -> ContractHash
$cfrom :: forall x. ContractHash -> Rep ContractHash x
Generic)

instance NFData ContractHash

-- | Data type corresponding to address structure in Tezos.
data Address
  = KeyAddress KeyHash
  -- ^ `tz` address which is a hash of a public key.
  | ContractAddress ContractHash
  -- ^ `KT` address which corresponds to a callable contract.
  deriving stock (Int -> Address -> ShowS
[Address] -> ShowS
Address -> String
(Int -> Address -> ShowS)
-> (Address -> String) -> ([Address] -> ShowS) -> Show Address
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Address] -> ShowS
$cshowList :: [Address] -> ShowS
show :: Address -> String
$cshow :: Address -> String
showsPrec :: Int -> Address -> ShowS
$cshowsPrec :: Int -> Address -> ShowS
Show, Address -> Address -> Bool
(Address -> Address -> Bool)
-> (Address -> Address -> Bool) -> Eq Address
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Address -> Address -> Bool
$c/= :: Address -> Address -> Bool
== :: Address -> Address -> Bool
$c== :: Address -> Address -> Bool
Eq, Eq Address
Eq Address =>
(Address -> Address -> Ordering)
-> (Address -> Address -> Bool)
-> (Address -> Address -> Bool)
-> (Address -> Address -> Bool)
-> (Address -> Address -> Bool)
-> (Address -> Address -> Address)
-> (Address -> Address -> Address)
-> Ord Address
Address -> Address -> Bool
Address -> Address -> Ordering
Address -> Address -> Address
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Address -> Address -> Address
$cmin :: Address -> Address -> Address
max :: Address -> Address -> Address
$cmax :: Address -> Address -> Address
>= :: Address -> Address -> Bool
$c>= :: Address -> Address -> Bool
> :: Address -> Address -> Bool
$c> :: Address -> Address -> Bool
<= :: Address -> Address -> Bool
$c<= :: Address -> Address -> Bool
< :: Address -> Address -> Bool
$c< :: Address -> Address -> Bool
compare :: Address -> Address -> Ordering
$ccompare :: Address -> Address -> Ordering
$cp1Ord :: Eq Address
Ord, (forall x. Address -> Rep Address x)
-> (forall x. Rep Address x -> Address) -> Generic Address
forall x. Rep Address x -> Address
forall x. Address -> Rep Address x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Address x -> Address
$cfrom :: forall x. Address -> Rep Address x
Generic)

instance NFData Address

-- | Smart constructor for 'KeyAddress'.
mkKeyAddress :: PublicKey -> Address
mkKeyAddress :: PublicKey -> Address
mkKeyAddress = KeyHash -> Address
KeyAddress (KeyHash -> Address)
-> (PublicKey -> KeyHash) -> PublicKey -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PublicKey -> KeyHash
hashKey

-- | Deterministically generate a random 'KeyAddress' and discard its
-- secret key.
detGenKeyAddress :: ByteString -> Address
detGenKeyAddress :: ByteString -> Address
detGenKeyAddress = PublicKey -> Address
mkKeyAddress (PublicKey -> Address)
-> (ByteString -> PublicKey) -> ByteString -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SecretKey -> PublicKey
toPublic (SecretKey -> PublicKey)
-> (ByteString -> SecretKey) -> ByteString -> PublicKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => ByteString -> SecretKey
ByteString -> SecretKey
detSecretKey

-- | Smart constructor for 'ContractAddress'. Its argument is
-- serialized origination operation.
--
-- Note: it's quite unsafe to pass 'ByteString', because we can pass
-- some garbage which is not a serialized origination operation, but
-- this operation includes contract itself and necessary types are
-- defined in 'Michelson.*'. So we have to serialize this data outside
-- this module and pass it here as a 'ByteString'. Alternatively we
-- could add some constraint, but it would be almost as unsafe as
-- passing a 'ByteString'. For this reason we add `Raw` suffix to this
-- function and provide a safer function in 'Michelson.Untyped.Instr'.
-- We may reconsider it later.
mkContractAddressRaw :: ByteString -> Address
mkContractAddressRaw :: ByteString -> Address
mkContractAddressRaw = ContractHash -> Address
ContractAddress (ContractHash -> Address)
-> (ByteString -> ContractHash) -> ByteString -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ContractHash
mkContractHashRaw

-- | Create a dummy 'ContractHash' value.
mkContractHashRaw :: ByteString -> ContractHash
mkContractHashRaw :: ByteString -> ContractHash
mkContractHashRaw = ByteString -> ContractHash
ContractHash (ByteString -> ContractHash)
-> (ByteString -> ByteString) -> ByteString -> ContractHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
blake2b160 (ByteString -> ByteString)
-> (ByteString -> ByteString) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
blake2b160

----------------------------------------------------------------------------
-- Formatting/parsing
----------------------------------------------------------------------------

formatContractHash :: ContractHash -> Text
formatContractHash :: ContractHash -> Text
formatContractHash (ContractHash bs :: ByteString
bs) =
  ByteString -> Text
encodeBase58Check (ByteString
contractAddressPrefix ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
bs)

formatAddress :: Address -> Text
formatAddress :: Address -> Text
formatAddress =
  \case
    KeyAddress h :: KeyHash
h -> KeyHash -> Text
formatKeyHash KeyHash
h
    ContractAddress h :: ContractHash
h -> ContractHash -> Text
formatContractHash ContractHash
h

mformatAddress :: Address -> MText
mformatAddress :: Address -> MText
mformatAddress = HasCallStack => Text -> MText
Text -> MText
mkMTextUnsafe (Text -> MText) -> (Address -> Text) -> Address -> MText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> Text
formatAddress

instance Buildable.Buildable Address where
  build :: Address -> Builder
build = Text -> Builder
forall p. Buildable p => p -> Builder
Buildable.build (Text -> Builder) -> (Address -> Text) -> Address -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> Text
formatAddress

-- | Errors that can happen during address parsing.
data ParseAddressError
  = ParseAddressWrongBase58Check
  -- ^ Address is not in Base58Check format.
  | ParseAddressBothFailed CryptoParseError ParseContractAddressError
  -- ^ Both address parsers failed with some error.
  deriving stock (Int -> ParseAddressError -> ShowS
[ParseAddressError] -> ShowS
ParseAddressError -> String
(Int -> ParseAddressError -> ShowS)
-> (ParseAddressError -> String)
-> ([ParseAddressError] -> ShowS)
-> Show ParseAddressError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParseAddressError] -> ShowS
$cshowList :: [ParseAddressError] -> ShowS
show :: ParseAddressError -> String
$cshow :: ParseAddressError -> String
showsPrec :: Int -> ParseAddressError -> ShowS
$cshowsPrec :: Int -> ParseAddressError -> ShowS
Show, ParseAddressError -> ParseAddressError -> Bool
(ParseAddressError -> ParseAddressError -> Bool)
-> (ParseAddressError -> ParseAddressError -> Bool)
-> Eq ParseAddressError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseAddressError -> ParseAddressError -> Bool
$c/= :: ParseAddressError -> ParseAddressError -> Bool
== :: ParseAddressError -> ParseAddressError -> Bool
$c== :: ParseAddressError -> ParseAddressError -> Bool
Eq, (forall x. ParseAddressError -> Rep ParseAddressError x)
-> (forall x. Rep ParseAddressError x -> ParseAddressError)
-> Generic ParseAddressError
forall x. Rep ParseAddressError x -> ParseAddressError
forall x. ParseAddressError -> Rep ParseAddressError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ParseAddressError x -> ParseAddressError
$cfrom :: forall x. ParseAddressError -> Rep ParseAddressError x
Generic)

instance NFData ParseAddressError

instance Buildable.Buildable ParseAddressError where
  build :: ParseAddressError -> Builder
build =
    \case
      ParseAddressWrongBase58Check -> "Wrong base58check format"
      ParseAddressBothFailed pkErr :: CryptoParseError
pkErr contractErr :: ParseContractAddressError
contractErr ->
        [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat
        [ "Address is neither `KeyAddress` ("
        , CryptoParseError -> Builder
forall p. Buildable p => p -> Builder
Buildable.build CryptoParseError
pkErr
        , "), nor `ContractAddress` ("
        , ParseContractAddressError -> Builder
forall p. Buildable p => p -> Builder
Buildable.build ParseContractAddressError
contractErr
        , ")"
        ]

-- | Parse an address from its human-readable textual representation
-- used by Tezos (e. g. "tz1faswCTDciRzE4oJ9jn2Vm2dvjeyA9fUzU"). Or
-- fail if it's invalid.
parseAddress :: Text -> Either ParseAddressError Address
parseAddress :: Text -> Either ParseAddressError Address
parseAddress addressText :: Text
addressText =
  case Text -> Either CryptoParseError KeyHash
parseKeyHash Text
addressText of
    Left CryptoParseWrongBase58Check -> ParseAddressError -> Either ParseAddressError Address
forall a b. a -> Either a b
Left ParseAddressError
ParseAddressWrongBase58Check
    Left keyAddrErr :: CryptoParseError
keyAddrErr -> (ParseContractAddressError -> ParseAddressError)
-> Either ParseContractAddressError Address
-> Either ParseAddressError Address
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (CryptoParseError -> ParseContractAddressError -> ParseAddressError
ParseAddressBothFailed CryptoParseError
keyAddrErr) (Either ParseContractAddressError Address
 -> Either ParseAddressError Address)
-> Either ParseContractAddressError Address
-> Either ParseAddressError Address
forall a b. (a -> b) -> a -> b
$
      ContractHash -> Address
ContractAddress (ContractHash -> Address)
-> Either ParseContractAddressError ContractHash
-> Either ParseContractAddressError Address
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either ParseContractAddressError ContractHash
parseContractHash Text
addressText
    Right keyHash :: KeyHash
keyHash -> Address -> Either ParseAddressError Address
forall a b. b -> Either a b
Right (KeyHash -> Address
KeyAddress KeyHash
keyHash)

-- | Partial version of 'parseAddress' which assumes that the address
-- is correct. Can be used in tests.
unsafeParseAddress :: HasCallStack => Text -> Address
unsafeParseAddress :: Text -> Address
unsafeParseAddress = (ParseAddressError -> Address)
-> (Address -> Address)
-> Either ParseAddressError Address
-> Address
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> Address
forall a. HasCallStack => Text -> a
error (Text -> Address)
-> (ParseAddressError -> Text) -> ParseAddressError -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseAddressError -> Text
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) Address -> Address
forall a. a -> a
id (Either ParseAddressError Address -> Address)
-> (Text -> Either ParseAddressError Address) -> Text -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either ParseAddressError Address
parseAddress

data ParseContractAddressError
  = ParseContractAddressWrongBase58Check
  | ParseContractAddressWrongTag ByteString
  | ParseContractAddressWrongSize Int
  deriving stock (Int -> ParseContractAddressError -> ShowS
[ParseContractAddressError] -> ShowS
ParseContractAddressError -> String
(Int -> ParseContractAddressError -> ShowS)
-> (ParseContractAddressError -> String)
-> ([ParseContractAddressError] -> ShowS)
-> Show ParseContractAddressError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParseContractAddressError] -> ShowS
$cshowList :: [ParseContractAddressError] -> ShowS
show :: ParseContractAddressError -> String
$cshow :: ParseContractAddressError -> String
showsPrec :: Int -> ParseContractAddressError -> ShowS
$cshowsPrec :: Int -> ParseContractAddressError -> ShowS
Show, ParseContractAddressError -> ParseContractAddressError -> Bool
(ParseContractAddressError -> ParseContractAddressError -> Bool)
-> (ParseContractAddressError -> ParseContractAddressError -> Bool)
-> Eq ParseContractAddressError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseContractAddressError -> ParseContractAddressError -> Bool
$c/= :: ParseContractAddressError -> ParseContractAddressError -> Bool
== :: ParseContractAddressError -> ParseContractAddressError -> Bool
$c== :: ParseContractAddressError -> ParseContractAddressError -> Bool
Eq, (forall x.
 ParseContractAddressError -> Rep ParseContractAddressError x)
-> (forall x.
    Rep ParseContractAddressError x -> ParseContractAddressError)
-> Generic ParseContractAddressError
forall x.
Rep ParseContractAddressError x -> ParseContractAddressError
forall x.
ParseContractAddressError -> Rep ParseContractAddressError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ParseContractAddressError x -> ParseContractAddressError
$cfrom :: forall x.
ParseContractAddressError -> Rep ParseContractAddressError x
Generic)

instance NFData ParseContractAddressError

instance Buildable.Buildable ParseContractAddressError where
  build :: ParseContractAddressError -> Builder
build =
    \case
      ParseContractAddressWrongBase58Check ->
        "Wrong base58check format"
      ParseContractAddressWrongTag tag :: ByteString
tag ->
        "Wrong tag for a contract address: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder -> Builder
forall b. FromBuilder b => Builder -> b
fmt (ByteString -> Builder
forall a. FormatAsHex a => a -> Builder
hexF ByteString
tag)
      ParseContractAddressWrongSize s :: Int
s ->
        "Wrong size for a contract address: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall p. Buildable p => p -> Builder
Buildable.build Int
s

parseContractHash :: Text -> Either ParseContractAddressError ContractHash
parseContractHash :: Text -> Either ParseContractAddressError ContractHash
parseContractHash text :: Text
text =
  case ByteString -> Text -> Either B58CheckWithPrefixError ByteString
decodeBase58CheckWithPrefix ByteString
contractAddressPrefix Text
text of
    Left (B58CheckWithPrefixWrongPrefix prefix :: ByteString
prefix) ->
      ParseContractAddressError
-> Either ParseContractAddressError ContractHash
forall a b. a -> Either a b
Left (ByteString -> ParseContractAddressError
ParseContractAddressWrongTag ByteString
prefix)
    Left B58CheckWithPrefixWrongEncoding ->
      ParseContractAddressError
-> Either ParseContractAddressError ContractHash
forall a b. a -> Either a b
Left ParseContractAddressError
ParseContractAddressWrongBase58Check
    -- We know that the length must be 20.
    -- Currently it's hardcoded here, later we'll probably have a `Hash` type.
    Right bs :: ByteString
bs | ByteString -> Int
forall t. Container t => t -> Int
length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 20 -> ContractHash -> Either ParseContractAddressError ContractHash
forall a b. b -> Either a b
Right (ByteString -> ContractHash
ContractHash ByteString
bs)
             | Bool
otherwise -> ParseContractAddressError
-> Either ParseContractAddressError ContractHash
forall a b. a -> Either a b
Left (ParseContractAddressError
 -> Either ParseContractAddressError ContractHash)
-> ParseContractAddressError
-> Either ParseContractAddressError ContractHash
forall a b. (a -> b) -> a -> b
$ Int -> ParseContractAddressError
ParseContractAddressWrongSize (ByteString -> Int
forall t. Container t => t -> Int
length ByteString
bs)

-- | Parse a `TK` contract address, fail if address does not match
-- the expected format.
unsafeParseContractHash :: HasCallStack => Text -> ContractHash
unsafeParseContractHash :: Text -> ContractHash
unsafeParseContractHash =
  (ParseContractAddressError -> ContractHash)
-> (ContractHash -> ContractHash)
-> Either ParseContractAddressError ContractHash
-> ContractHash
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> ContractHash
forall a. HasCallStack => Text -> a
error (Text -> ContractHash)
-> (ParseContractAddressError -> Text)
-> ParseContractAddressError
-> ContractHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseContractAddressError -> Text
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) ContractHash -> ContractHash
forall a. a -> a
id (Either ParseContractAddressError ContractHash -> ContractHash)
-> (Text -> Either ParseContractAddressError ContractHash)
-> Text
-> ContractHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either ParseContractAddressError ContractHash
parseContractHash

-- It's a magic constant used by Tezos to encode a contract address.
-- It was deduced empirically.
contractAddressPrefix :: ByteString
contractAddressPrefix :: ByteString
contractAddressPrefix = "\2\90\121"

instance HasCLReader Address where
  getReader :: ReadM Address
getReader = (String -> Either String Address) -> ReadM Address
forall a. (String -> Either String a) -> ReadM a
eitherReader String -> Either String Address
forall a a.
(Monoid a, IsString a, FromBuilder a, ToText a) =>
a -> Either a Address
parseAddrDo
    where
      parseAddrDo :: a -> Either a Address
parseAddrDo addr :: a
addr =
        (ParseAddressError -> Either a Address)
-> (Address -> Either a Address)
-> Either ParseAddressError Address
-> Either a Address
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (a -> Either a Address
forall a b. a -> Either a b
Left (a -> Either a Address)
-> (ParseAddressError -> a)
-> ParseAddressError
-> Either a Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> a
forall a. Monoid a => a -> a -> a
mappend "Failed to parse address: " (a -> a) -> (ParseAddressError -> a) -> ParseAddressError -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseAddressError -> a
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) Address -> Either a Address
forall a b. b -> Either a b
Right (Either ParseAddressError Address -> Either a Address)
-> Either ParseAddressError Address -> Either a Address
forall a b. (a -> b) -> a -> b
$
        Text -> Either ParseAddressError Address
parseAddress (Text -> Either ParseAddressError Address)
-> Text -> Either ParseAddressError Address
forall a b. (a -> b) -> a -> b
$ a -> Text
forall a. ToText a => a -> Text
toText a
addr
  getMetavar :: String
getMetavar = "ADDRESS"

----------------------------------------------------------------------------
-- Aeson instances
----------------------------------------------------------------------------

instance ToJSON ContractHash where
  toJSON :: ContractHash -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value) -> (ContractHash -> Text) -> ContractHash -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContractHash -> Text
formatContractHash
  toEncoding :: ContractHash -> Encoding
toEncoding = Text -> Encoding
forall a. Text -> Encoding' a
Aeson.text (Text -> Encoding)
-> (ContractHash -> Text) -> ContractHash -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContractHash -> Text
formatContractHash

instance ToJSONKey ContractHash where
  toJSONKey :: ToJSONKeyFunction ContractHash
toJSONKey = (ContractHash -> Text) -> ToJSONKeyFunction ContractHash
forall a. (a -> Text) -> ToJSONKeyFunction a
AesonTypes.toJSONKeyText ContractHash -> Text
formatContractHash

instance FromJSON ContractHash where
  parseJSON :: Value -> Parser ContractHash
parseJSON =
    String
-> (Text -> Parser ContractHash) -> Value -> Parser ContractHash
forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText "ContractHash" ((Text -> Parser ContractHash) -> Value -> Parser ContractHash)
-> (Text -> Parser ContractHash) -> Value -> Parser ContractHash
forall a b. (a -> b) -> a -> b
$
    (ParseContractAddressError -> Parser ContractHash)
-> (ContractHash -> Parser ContractHash)
-> Either ParseContractAddressError ContractHash
-> Parser ContractHash
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser ContractHash
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ContractHash)
-> (ParseContractAddressError -> String)
-> ParseContractAddressError
-> Parser ContractHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseContractAddressError -> String
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) ContractHash -> Parser ContractHash
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ParseContractAddressError ContractHash
 -> Parser ContractHash)
-> (Text -> Either ParseContractAddressError ContractHash)
-> Text
-> Parser ContractHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either ParseContractAddressError ContractHash
parseContractHash

instance FromJSONKey ContractHash where
  fromJSONKey :: FromJSONKeyFunction ContractHash
fromJSONKey =
    (Text -> Parser ContractHash) -> FromJSONKeyFunction ContractHash
forall a. (Text -> Parser a) -> FromJSONKeyFunction a
AesonTypes.FromJSONKeyTextParser
      ((ParseContractAddressError -> Parser ContractHash)
-> (ContractHash -> Parser ContractHash)
-> Either ParseContractAddressError ContractHash
-> Parser ContractHash
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser ContractHash
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ContractHash)
-> (ParseContractAddressError -> String)
-> ParseContractAddressError
-> Parser ContractHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseContractAddressError -> String
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) ContractHash -> Parser ContractHash
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ParseContractAddressError ContractHash
 -> Parser ContractHash)
-> (Text -> Either ParseContractAddressError ContractHash)
-> Text
-> Parser ContractHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either ParseContractAddressError ContractHash
parseContractHash)


instance ToJSON Address where
  toJSON :: Address -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value) -> (Address -> Text) -> Address -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> Text
formatAddress
  toEncoding :: Address -> Encoding
toEncoding = Text -> Encoding
forall a. Text -> Encoding' a
Aeson.text (Text -> Encoding) -> (Address -> Text) -> Address -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> Text
formatAddress

instance ToJSONKey Address where
  toJSONKey :: ToJSONKeyFunction Address
toJSONKey = (Address -> Text) -> ToJSONKeyFunction Address
forall a. (a -> Text) -> ToJSONKeyFunction a
AesonTypes.toJSONKeyText Address -> Text
formatAddress

instance FromJSON Address where
  parseJSON :: Value -> Parser Address
parseJSON =
    String -> (Text -> Parser Address) -> Value -> Parser Address
forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText "Address" ((Text -> Parser Address) -> Value -> Parser Address)
-> (Text -> Parser Address) -> Value -> Parser Address
forall a b. (a -> b) -> a -> b
$
    (ParseAddressError -> Parser Address)
-> (Address -> Parser Address)
-> Either ParseAddressError Address
-> Parser Address
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser Address
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Address)
-> (ParseAddressError -> String)
-> ParseAddressError
-> Parser Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseAddressError -> String
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) Address -> Parser Address
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ParseAddressError Address -> Parser Address)
-> (Text -> Either ParseAddressError Address)
-> Text
-> Parser Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either ParseAddressError Address
parseAddress

instance FromJSONKey Address where
  fromJSONKey :: FromJSONKeyFunction Address
fromJSONKey =
    (Text -> Parser Address) -> FromJSONKeyFunction Address
forall a. (Text -> Parser a) -> FromJSONKeyFunction a
AesonTypes.FromJSONKeyTextParser
      ((ParseAddressError -> Parser Address)
-> (Address -> Parser Address)
-> Either ParseAddressError Address
-> Parser Address
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser Address
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Address)
-> (ParseAddressError -> String)
-> ParseAddressError
-> Parser Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseAddressError -> String
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) Address -> Parser Address
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ParseAddressError Address -> Parser Address)
-> (Text -> Either ParseAddressError Address)
-> Text
-> Parser Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either ParseAddressError Address
parseAddress)

----------------------------------------------------------------------------
-- Arbitrary
----------------------------------------------------------------------------

instance Arbitrary Address where
  arbitrary :: Gen Address
arbitrary = [Gen Address] -> Gen Address
forall a. [Gen a] -> Gen a
oneof [Gen Address
genKeyAddress, Gen Address
genContractAddress]
    where
      genKeyAddress :: Gen Address
genKeyAddress = KeyHash -> Address
KeyAddress (KeyHash -> Address) -> Gen KeyHash -> Gen Address
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen KeyHash
forall a. Arbitrary a => Gen a
arbitrary
      genContractAddress :: Gen Address
genContractAddress = ContractHash -> Address
ContractAddress (ContractHash -> Address)
-> ([Word8] -> ContractHash) -> [Word8] -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ContractHash
ContractHash (ByteString -> ContractHash)
-> ([Word8] -> ByteString) -> [Word8] -> ContractHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
BS.pack ([Word8] -> Address) -> Gen [Word8] -> Gen Address
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Gen [Word8]
forall a. Arbitrary a => Int -> Gen [a]
vector 20