module Tezos.Address
( ContractHash (..)
, Address (..)
, mkKeyAddress
, detGenKeyAddress
, mkContractAddressRaw
, mkContractHashRaw
, 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
newtype ContractHash = ContractHash ByteString
deriving stock (Show, Eq, Ord)
data Address
= KeyAddress KeyHash
| ContractAddress ContractHash
deriving stock (Show, Eq, Ord)
mkKeyAddress :: PublicKey -> Address
mkKeyAddress = KeyAddress . hashKey
detGenKeyAddress :: ByteString -> Address
detGenKeyAddress = mkKeyAddress . toPublic . detSecretKey
mkContractAddressRaw :: ByteString -> Address
mkContractAddressRaw = ContractAddress . mkContractHashRaw
mkContractHashRaw :: ByteString -> ContractHash
mkContractHashRaw = ContractHash . blake2b160 . blake2b160
formatContractHash :: ContractHash -> Text
formatContractHash (ContractHash bs) =
encodeBase58Check (contractAddressPrefix <> bs)
formatAddress :: Address -> Text
formatAddress =
\case
KeyAddress h -> formatKeyHash h
ContractAddress h -> formatContractHash h
mformatAddress :: Address -> MText
mformatAddress = mkMTextUnsafe . formatAddress
instance Buildable.Buildable Address where
build = Buildable.build . formatAddress
data ParseAddressError
= ParseAddressWrongBase58Check
| ParseAddressBothFailed CryptoParseError ParseContractAddressError
deriving stock (Show, Eq)
instance Buildable.Buildable ParseAddressError where
build =
\case
ParseAddressWrongBase58Check -> "Wrong base58check format"
ParseAddressBothFailed pkErr contractErr ->
mconcat
[ "Address is neither `KeyAddress` ("
, Buildable.build pkErr
, "), nor `ContractAddress` ("
, Buildable.build contractErr
, ")"
]
parseAddress :: Text -> Either ParseAddressError Address
parseAddress addressText =
case parseKeyHash addressText of
Left CryptoParseWrongBase58Check -> Left ParseAddressWrongBase58Check
Left keyAddrErr -> first (ParseAddressBothFailed keyAddrErr) $
ContractAddress <$> parseContractHash addressText
Right keyHash -> Right (KeyAddress keyHash)
unsafeParseAddress :: HasCallStack => Text -> Address
unsafeParseAddress = either (error . pretty) id . parseAddress
data ParseContractAddressError
= ParseContractAddressWrongBase58Check
| ParseContractAddressWrongTag ByteString
| ParseContractAddressWrongSize Int
deriving stock (Show, Eq)
instance Buildable.Buildable ParseContractAddressError where
build =
\case
ParseContractAddressWrongBase58Check ->
"Wrong base58check format"
ParseContractAddressWrongTag tag ->
"Wrong tag for a contract address: " <> fmt (hexF tag)
ParseContractAddressWrongSize s ->
"Wrong size for a contract address: " <> Buildable.build s
parseContractHash :: Text -> Either ParseContractAddressError ContractHash
parseContractHash text =
case decodeBase58CheckWithPrefix contractAddressPrefix text of
Left (B58CheckWithPrefixWrongPrefix prefix) ->
Left (ParseContractAddressWrongTag prefix)
Left B58CheckWithPrefixWrongEncoding ->
Left ParseContractAddressWrongBase58Check
Right bs | length bs == 20 -> Right (ContractHash bs)
| otherwise -> Left $ ParseContractAddressWrongSize (length bs)
unsafeParseContractHash :: HasCallStack => Text -> ContractHash
unsafeParseContractHash =
either (error . pretty) id . parseContractHash
contractAddressPrefix :: ByteString
contractAddressPrefix = "\2\90\121"
instance ToJSON ContractHash where
toJSON = Aeson.String . formatContractHash
toEncoding = Aeson.text . formatContractHash
instance ToJSONKey ContractHash where
toJSONKey = AesonTypes.toJSONKeyText formatContractHash
instance FromJSON ContractHash where
parseJSON =
Aeson.withText "ContractHash" $
either (fail . pretty) pure . parseContractHash
instance FromJSONKey ContractHash where
fromJSONKey =
AesonTypes.FromJSONKeyTextParser
(either (fail . pretty) pure . parseContractHash)
instance ToJSON Address where
toJSON = Aeson.String . formatAddress
toEncoding = Aeson.text . formatAddress
instance ToJSONKey Address where
toJSONKey = AesonTypes.toJSONKeyText formatAddress
instance FromJSON Address where
parseJSON =
Aeson.withText "Address" $
either (fail . pretty) pure . parseAddress
instance FromJSONKey Address where
fromJSONKey =
AesonTypes.FromJSONKeyTextParser
(either (fail . pretty) pure . parseAddress)
instance Arbitrary Address where
arbitrary = oneof [genKeyAddress, genContractAddress]
where
genKeyAddress = KeyAddress <$> arbitrary
genContractAddress = ContractAddress . ContractHash . BS.pack <$> vector 20