-- | Responses for Cardano accounts queries

module Blockfrost.Types.Cardano.Accounts
  ( AccountInfo (..)
  , RewardType (..)
  , AccountReward (..)
  , AccountHistory (..)
  , AccountDelegation (..)
  , AccountRegistration (..)
  , AccountRegistrationAction (..)
  , AccountWithdrawal (..)
  , AccountMir (..)
  , AddressAssociated (..)
  , AddressAssociatedTotal (..)
  ) where

import Blockfrost.Types.Shared
import Deriving.Aeson
import qualified Money
import Servant.Docs (ToSample (..), samples, singleSample)

-- | Information about an account, identified by its stake address
data AccountInfo = AccountInfo
  { AccountInfo -> Address
_accountInfoStakeAddress       :: Address -- ^ Bech32 stake address
  , AccountInfo -> Bool
_accountInfoActive             :: Bool -- ^ Registration state of an account
  , AccountInfo -> Maybe Integer
_accountInfoActiveEpoch        :: Maybe Integer -- ^ Epoch of the most recent action - registration or deregistration
  , AccountInfo -> Lovelaces
_accountInfoControlledAmount   :: Lovelaces  -- ^ Balance of the account in Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoRewardsSum         :: Lovelaces -- ^ Sum of all funds rewards for the account in the Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoWithdrawalsSum     :: Lovelaces -- ^ Sum of all the withdrawals for the account in the Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoReservesSum        :: Lovelaces -- ^ Sum of all funds from reserves for the account in the Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoTreasurySum        :: Lovelaces -- ^ Sum of all funds from treasury for the account in the Lovelaces
  , AccountInfo -> Lovelaces
_accountInfoWithdrawableAmount :: Lovelaces -- ^ Sum of available rewards that haven't been withdrawn yet for the account in the Lovelaces
  , AccountInfo -> Maybe PoolId
_accountInfoPoolId             :: Maybe PoolId -- ^ Bech32 pool ID that owns the account
  }
  deriving stock (Int -> AccountInfo -> ShowS
[AccountInfo] -> ShowS
AccountInfo -> String
(Int -> AccountInfo -> ShowS)
-> (AccountInfo -> String)
-> ([AccountInfo] -> ShowS)
-> Show AccountInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountInfo -> ShowS
showsPrec :: Int -> AccountInfo -> ShowS
$cshow :: AccountInfo -> String
show :: AccountInfo -> String
$cshowList :: [AccountInfo] -> ShowS
showList :: [AccountInfo] -> ShowS
Show, AccountInfo -> AccountInfo -> Bool
(AccountInfo -> AccountInfo -> Bool)
-> (AccountInfo -> AccountInfo -> Bool) -> Eq AccountInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountInfo -> AccountInfo -> Bool
== :: AccountInfo -> AccountInfo -> Bool
$c/= :: AccountInfo -> AccountInfo -> Bool
/= :: AccountInfo -> AccountInfo -> Bool
Eq, (forall x. AccountInfo -> Rep AccountInfo x)
-> (forall x. Rep AccountInfo x -> AccountInfo)
-> Generic AccountInfo
forall x. Rep AccountInfo x -> AccountInfo
forall x. AccountInfo -> Rep AccountInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccountInfo -> Rep AccountInfo x
from :: forall x. AccountInfo -> Rep AccountInfo x
$cto :: forall x. Rep AccountInfo x -> AccountInfo
to :: forall x. Rep AccountInfo x -> AccountInfo
Generic)
  deriving (Maybe AccountInfo
Value -> Parser [AccountInfo]
Value -> Parser AccountInfo
(Value -> Parser AccountInfo)
-> (Value -> Parser [AccountInfo])
-> Maybe AccountInfo
-> FromJSON AccountInfo
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccountInfo
parseJSON :: Value -> Parser AccountInfo
$cparseJSONList :: Value -> Parser [AccountInfo]
parseJSONList :: Value -> Parser [AccountInfo]
$comittedField :: Maybe AccountInfo
omittedField :: Maybe AccountInfo
FromJSON, [AccountInfo] -> Value
[AccountInfo] -> Encoding
AccountInfo -> Bool
AccountInfo -> Value
AccountInfo -> Encoding
(AccountInfo -> Value)
-> (AccountInfo -> Encoding)
-> ([AccountInfo] -> Value)
-> ([AccountInfo] -> Encoding)
-> (AccountInfo -> Bool)
-> ToJSON AccountInfo
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccountInfo -> Value
toJSON :: AccountInfo -> Value
$ctoEncoding :: AccountInfo -> Encoding
toEncoding :: AccountInfo -> Encoding
$ctoJSONList :: [AccountInfo] -> Value
toJSONList :: [AccountInfo] -> Value
$ctoEncodingList :: [AccountInfo] -> Encoding
toEncodingList :: [AccountInfo] -> Encoding
$comitField :: AccountInfo -> Bool
omitField :: AccountInfo -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountInfo", CamelToSnake]] AccountInfo

instance ToSample AccountInfo where
  toSamples :: Proxy AccountInfo -> [(Text, AccountInfo)]
toSamples = [(Text, AccountInfo)] -> Proxy AccountInfo -> [(Text, AccountInfo)]
forall a. a -> Proxy AccountInfo -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountInfo)]
 -> Proxy AccountInfo -> [(Text, AccountInfo)])
-> [(Text, AccountInfo)]
-> Proxy AccountInfo
-> [(Text, AccountInfo)]
forall a b. (a -> b) -> a -> b
$ AccountInfo -> [(Text, AccountInfo)]
forall a. a -> [(Text, a)]
singleSample (AccountInfo -> [(Text, AccountInfo)])
-> AccountInfo -> [(Text, AccountInfo)]
forall a b. (a -> b) -> a -> b
$ AccountInfo
    { _accountInfoStakeAddress :: Address
_accountInfoStakeAddress = Address
"stake1ux3g2c9dx2nhhehyrezyxpkstartcqmu9hk63qgfkccw5rqttygt7"
    , _accountInfoActive :: Bool
_accountInfoActive = Bool
True
    , _accountInfoActiveEpoch :: Maybe Integer
_accountInfoActiveEpoch = Integer -> Maybe Integer
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Integer
412
    , _accountInfoControlledAmount :: Lovelaces
_accountInfoControlledAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
619154618165
    , _accountInfoRewardsSum :: Lovelaces
_accountInfoRewardsSum = Discrete' "ADA" '(1000000, 1)
Lovelaces
319154618165
    , _accountInfoWithdrawalsSum :: Lovelaces
_accountInfoWithdrawalsSum = Discrete' "ADA" '(1000000, 1)
Lovelaces
12125369253
    , _accountInfoReservesSum :: Lovelaces
_accountInfoReservesSum = Discrete' "ADA" '(1000000, 1)
Lovelaces
319154618165
    , _accountInfoTreasurySum :: Lovelaces
_accountInfoTreasurySum = Discrete' "ADA" '(1000000, 1)
Lovelaces
12000000
    , _accountInfoWithdrawableAmount :: Lovelaces
_accountInfoWithdrawableAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
319154618165
    , _accountInfoPoolId :: Maybe PoolId
_accountInfoPoolId = PoolId -> Maybe PoolId
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
    }

-- | Reward type
data RewardType = Leader | Member | PoolDepositRefund
  deriving stock (Int -> RewardType -> ShowS
[RewardType] -> ShowS
RewardType -> String
(Int -> RewardType -> ShowS)
-> (RewardType -> String)
-> ([RewardType] -> ShowS)
-> Show RewardType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RewardType -> ShowS
showsPrec :: Int -> RewardType -> ShowS
$cshow :: RewardType -> String
show :: RewardType -> String
$cshowList :: [RewardType] -> ShowS
showList :: [RewardType] -> ShowS
Show, RewardType -> RewardType -> Bool
(RewardType -> RewardType -> Bool)
-> (RewardType -> RewardType -> Bool) -> Eq RewardType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RewardType -> RewardType -> Bool
== :: RewardType -> RewardType -> Bool
$c/= :: RewardType -> RewardType -> Bool
/= :: RewardType -> RewardType -> Bool
Eq, (forall x. RewardType -> Rep RewardType x)
-> (forall x. Rep RewardType x -> RewardType) -> Generic RewardType
forall x. Rep RewardType x -> RewardType
forall x. RewardType -> Rep RewardType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RewardType -> Rep RewardType x
from :: forall x. RewardType -> Rep RewardType x
$cto :: forall x. Rep RewardType x -> RewardType
to :: forall x. Rep RewardType x -> RewardType
Generic)
  deriving (Maybe RewardType
Value -> Parser [RewardType]
Value -> Parser RewardType
(Value -> Parser RewardType)
-> (Value -> Parser [RewardType])
-> Maybe RewardType
-> FromJSON RewardType
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser RewardType
parseJSON :: Value -> Parser RewardType
$cparseJSONList :: Value -> Parser [RewardType]
parseJSONList :: Value -> Parser [RewardType]
$comittedField :: Maybe RewardType
omittedField :: Maybe RewardType
FromJSON, [RewardType] -> Value
[RewardType] -> Encoding
RewardType -> Bool
RewardType -> Value
RewardType -> Encoding
(RewardType -> Value)
-> (RewardType -> Encoding)
-> ([RewardType] -> Value)
-> ([RewardType] -> Encoding)
-> (RewardType -> Bool)
-> ToJSON RewardType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: RewardType -> Value
toJSON :: RewardType -> Value
$ctoEncoding :: RewardType -> Encoding
toEncoding :: RewardType -> Encoding
$ctoJSONList :: [RewardType] -> Value
toJSONList :: [RewardType] -> Value
$ctoEncodingList :: [RewardType] -> Encoding
toEncodingList :: [RewardType] -> Encoding
$comitField :: RewardType -> Bool
omitField :: RewardType -> Bool
ToJSON)
  via CustomJSON '[ConstructorTagModifier '[CamelToKebab]] RewardType

instance ToSample RewardType where
  toSamples :: Proxy RewardType -> [(Text, RewardType)]
toSamples = [(Text, RewardType)] -> Proxy RewardType -> [(Text, RewardType)]
forall a. a -> Proxy RewardType -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, RewardType)] -> Proxy RewardType -> [(Text, RewardType)])
-> [(Text, RewardType)] -> Proxy RewardType -> [(Text, RewardType)]
forall a b. (a -> b) -> a -> b
$ [RewardType] -> [(Text, RewardType)]
forall a. [a] -> [(Text, a)]
samples [ RewardType
Leader, RewardType
Member, RewardType
PoolDepositRefund ]

-- | Reward received by an account
data AccountReward = AccountReward
  { AccountReward -> Epoch
_accountRewardEpoch  :: Epoch -- ^ Epoch of the associated reward
  , AccountReward -> Lovelaces
_accountRewardAmount :: Lovelaces -- ^ Rewards for given epoch in Lovelaces
  , AccountReward -> PoolId
_accountRewardPoolId :: PoolId -- ^ Bech32 pool ID being delegated to
  , AccountReward -> RewardType
_accountRewardType   :: RewardType -- ^ Reward type
  }
  deriving stock (Int -> AccountReward -> ShowS
[AccountReward] -> ShowS
AccountReward -> String
(Int -> AccountReward -> ShowS)
-> (AccountReward -> String)
-> ([AccountReward] -> ShowS)
-> Show AccountReward
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountReward -> ShowS
showsPrec :: Int -> AccountReward -> ShowS
$cshow :: AccountReward -> String
show :: AccountReward -> String
$cshowList :: [AccountReward] -> ShowS
showList :: [AccountReward] -> ShowS
Show, AccountReward -> AccountReward -> Bool
(AccountReward -> AccountReward -> Bool)
-> (AccountReward -> AccountReward -> Bool) -> Eq AccountReward
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountReward -> AccountReward -> Bool
== :: AccountReward -> AccountReward -> Bool
$c/= :: AccountReward -> AccountReward -> Bool
/= :: AccountReward -> AccountReward -> Bool
Eq, (forall x. AccountReward -> Rep AccountReward x)
-> (forall x. Rep AccountReward x -> AccountReward)
-> Generic AccountReward
forall x. Rep AccountReward x -> AccountReward
forall x. AccountReward -> Rep AccountReward x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccountReward -> Rep AccountReward x
from :: forall x. AccountReward -> Rep AccountReward x
$cto :: forall x. Rep AccountReward x -> AccountReward
to :: forall x. Rep AccountReward x -> AccountReward
Generic)
  deriving (Maybe AccountReward
Value -> Parser [AccountReward]
Value -> Parser AccountReward
(Value -> Parser AccountReward)
-> (Value -> Parser [AccountReward])
-> Maybe AccountReward
-> FromJSON AccountReward
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccountReward
parseJSON :: Value -> Parser AccountReward
$cparseJSONList :: Value -> Parser [AccountReward]
parseJSONList :: Value -> Parser [AccountReward]
$comittedField :: Maybe AccountReward
omittedField :: Maybe AccountReward
FromJSON, [AccountReward] -> Value
[AccountReward] -> Encoding
AccountReward -> Bool
AccountReward -> Value
AccountReward -> Encoding
(AccountReward -> Value)
-> (AccountReward -> Encoding)
-> ([AccountReward] -> Value)
-> ([AccountReward] -> Encoding)
-> (AccountReward -> Bool)
-> ToJSON AccountReward
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccountReward -> Value
toJSON :: AccountReward -> Value
$ctoEncoding :: AccountReward -> Encoding
toEncoding :: AccountReward -> Encoding
$ctoJSONList :: [AccountReward] -> Value
toJSONList :: [AccountReward] -> Value
$ctoEncodingList :: [AccountReward] -> Encoding
toEncodingList :: [AccountReward] -> Encoding
$comitField :: AccountReward -> Bool
omitField :: AccountReward -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountReward", CamelToSnake]] AccountReward

instance ToSample AccountReward where
  toSamples :: Proxy AccountReward -> [(Text, AccountReward)]
toSamples = [(Text, AccountReward)]
-> Proxy AccountReward -> [(Text, AccountReward)]
forall a. a -> Proxy AccountReward -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountReward)]
 -> Proxy AccountReward -> [(Text, AccountReward)])
-> [(Text, AccountReward)]
-> Proxy AccountReward
-> [(Text, AccountReward)]
forall a b. (a -> b) -> a -> b
$ [AccountReward] -> [(Text, AccountReward)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountReward
        { _accountRewardEpoch :: Epoch
_accountRewardEpoch = Epoch
214
        , _accountRewardAmount :: Lovelaces
_accountRewardAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
1395265
        , _accountRewardPoolId :: PoolId
_accountRewardPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        , _accountRewardType :: RewardType
_accountRewardType = RewardType
Member
        }
    , AccountReward
        { _accountRewardEpoch :: Epoch
_accountRewardEpoch = Epoch
215
        , _accountRewardAmount :: Lovelaces
_accountRewardAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
58632
        , _accountRewardPoolId :: PoolId
_accountRewardPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        , _accountRewardType :: RewardType
_accountRewardType = RewardType
Leader
        }
    , AccountReward
        { _accountRewardEpoch :: Epoch
_accountRewardEpoch = Epoch
216
        , _accountRewardAmount :: Lovelaces
_accountRewardAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
0
        , _accountRewardPoolId :: PoolId
_accountRewardPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        , _accountRewardType :: RewardType
_accountRewardType = RewardType
Leader
        }
    , AccountReward
        { _accountRewardEpoch :: Epoch
_accountRewardEpoch = Epoch
217
        , _accountRewardAmount :: Lovelaces
_accountRewardAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
1395265
        , _accountRewardPoolId :: PoolId
_accountRewardPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        , _accountRewardType :: RewardType
_accountRewardType = RewardType
PoolDepositRefund
        }
    ]

-- | History of accounts stake delegation
data AccountHistory = AccountHistory
  { AccountHistory -> Integer
_accountHistoryActiveEpoch :: Integer -- ^ Epoch in which the stake was active
  , AccountHistory -> Lovelaces
_accountHistoryAmount      :: Lovelaces -- ^ Stake amount in Lovelaces
  , AccountHistory -> PoolId
_accountHistoryPoolId      :: PoolId -- ^ Bech32 ID of pool being delegated to
  }
  deriving stock (Int -> AccountHistory -> ShowS
[AccountHistory] -> ShowS
AccountHistory -> String
(Int -> AccountHistory -> ShowS)
-> (AccountHistory -> String)
-> ([AccountHistory] -> ShowS)
-> Show AccountHistory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountHistory -> ShowS
showsPrec :: Int -> AccountHistory -> ShowS
$cshow :: AccountHistory -> String
show :: AccountHistory -> String
$cshowList :: [AccountHistory] -> ShowS
showList :: [AccountHistory] -> ShowS
Show, AccountHistory -> AccountHistory -> Bool
(AccountHistory -> AccountHistory -> Bool)
-> (AccountHistory -> AccountHistory -> Bool) -> Eq AccountHistory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountHistory -> AccountHistory -> Bool
== :: AccountHistory -> AccountHistory -> Bool
$c/= :: AccountHistory -> AccountHistory -> Bool
/= :: AccountHistory -> AccountHistory -> Bool
Eq, (forall x. AccountHistory -> Rep AccountHistory x)
-> (forall x. Rep AccountHistory x -> AccountHistory)
-> Generic AccountHistory
forall x. Rep AccountHistory x -> AccountHistory
forall x. AccountHistory -> Rep AccountHistory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccountHistory -> Rep AccountHistory x
from :: forall x. AccountHistory -> Rep AccountHistory x
$cto :: forall x. Rep AccountHistory x -> AccountHistory
to :: forall x. Rep AccountHistory x -> AccountHistory
Generic)
  deriving (Maybe AccountHistory
Value -> Parser [AccountHistory]
Value -> Parser AccountHistory
(Value -> Parser AccountHistory)
-> (Value -> Parser [AccountHistory])
-> Maybe AccountHistory
-> FromJSON AccountHistory
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccountHistory
parseJSON :: Value -> Parser AccountHistory
$cparseJSONList :: Value -> Parser [AccountHistory]
parseJSONList :: Value -> Parser [AccountHistory]
$comittedField :: Maybe AccountHistory
omittedField :: Maybe AccountHistory
FromJSON, [AccountHistory] -> Value
[AccountHistory] -> Encoding
AccountHistory -> Bool
AccountHistory -> Value
AccountHistory -> Encoding
(AccountHistory -> Value)
-> (AccountHistory -> Encoding)
-> ([AccountHistory] -> Value)
-> ([AccountHistory] -> Encoding)
-> (AccountHistory -> Bool)
-> ToJSON AccountHistory
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccountHistory -> Value
toJSON :: AccountHistory -> Value
$ctoEncoding :: AccountHistory -> Encoding
toEncoding :: AccountHistory -> Encoding
$ctoJSONList :: [AccountHistory] -> Value
toJSONList :: [AccountHistory] -> Value
$ctoEncodingList :: [AccountHistory] -> Encoding
toEncodingList :: [AccountHistory] -> Encoding
$comitField :: AccountHistory -> Bool
omitField :: AccountHistory -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountHistory", CamelToSnake]] AccountHistory

instance ToSample AccountHistory where
  toSamples :: Proxy AccountHistory -> [(Text, AccountHistory)]
toSamples  = [(Text, AccountHistory)]
-> Proxy AccountHistory -> [(Text, AccountHistory)]
forall a. a -> Proxy AccountHistory -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountHistory)]
 -> Proxy AccountHistory -> [(Text, AccountHistory)])
-> [(Text, AccountHistory)]
-> Proxy AccountHistory
-> [(Text, AccountHistory)]
forall a b. (a -> b) -> a -> b
$ [AccountHistory] -> [(Text, AccountHistory)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountHistory
        { _accountHistoryActiveEpoch :: Integer
_accountHistoryActiveEpoch = Integer
260
        , _accountHistoryAmount :: Lovelaces
_accountHistoryAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
1395265
        , _accountHistoryPoolId :: PoolId
_accountHistoryPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    , AccountHistory
        { _accountHistoryActiveEpoch :: Integer
_accountHistoryActiveEpoch = Integer
211
        , _accountHistoryAmount :: Lovelaces
_accountHistoryAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
22695385
        , _accountHistoryPoolId :: PoolId
_accountHistoryPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    ]

-- | Account delegations and associated transaction IDs
data AccountDelegation = AccountDelegation
  { AccountDelegation -> Epoch
_accountDelegationActiveEpoch :: Epoch -- ^ Epoch in which the delegation becomes active
  , AccountDelegation -> TxHash
_accountDelegationTxHash      :: TxHash -- ^ Hash of the transaction containing the delegation
  , AccountDelegation -> Lovelaces
_accountDelegationAmount      :: Lovelaces -- ^ Rewards for given epoch in Lovelaces
  , AccountDelegation -> PoolId
_accountDelegationPoolId      :: PoolId -- ^ Bech32 ID of pool being delegated to
  }
  deriving stock (Int -> AccountDelegation -> ShowS
[AccountDelegation] -> ShowS
AccountDelegation -> String
(Int -> AccountDelegation -> ShowS)
-> (AccountDelegation -> String)
-> ([AccountDelegation] -> ShowS)
-> Show AccountDelegation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountDelegation -> ShowS
showsPrec :: Int -> AccountDelegation -> ShowS
$cshow :: AccountDelegation -> String
show :: AccountDelegation -> String
$cshowList :: [AccountDelegation] -> ShowS
showList :: [AccountDelegation] -> ShowS
Show, AccountDelegation -> AccountDelegation -> Bool
(AccountDelegation -> AccountDelegation -> Bool)
-> (AccountDelegation -> AccountDelegation -> Bool)
-> Eq AccountDelegation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountDelegation -> AccountDelegation -> Bool
== :: AccountDelegation -> AccountDelegation -> Bool
$c/= :: AccountDelegation -> AccountDelegation -> Bool
/= :: AccountDelegation -> AccountDelegation -> Bool
Eq, (forall x. AccountDelegation -> Rep AccountDelegation x)
-> (forall x. Rep AccountDelegation x -> AccountDelegation)
-> Generic AccountDelegation
forall x. Rep AccountDelegation x -> AccountDelegation
forall x. AccountDelegation -> Rep AccountDelegation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccountDelegation -> Rep AccountDelegation x
from :: forall x. AccountDelegation -> Rep AccountDelegation x
$cto :: forall x. Rep AccountDelegation x -> AccountDelegation
to :: forall x. Rep AccountDelegation x -> AccountDelegation
Generic)
  deriving (Maybe AccountDelegation
Value -> Parser [AccountDelegation]
Value -> Parser AccountDelegation
(Value -> Parser AccountDelegation)
-> (Value -> Parser [AccountDelegation])
-> Maybe AccountDelegation
-> FromJSON AccountDelegation
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccountDelegation
parseJSON :: Value -> Parser AccountDelegation
$cparseJSONList :: Value -> Parser [AccountDelegation]
parseJSONList :: Value -> Parser [AccountDelegation]
$comittedField :: Maybe AccountDelegation
omittedField :: Maybe AccountDelegation
FromJSON, [AccountDelegation] -> Value
[AccountDelegation] -> Encoding
AccountDelegation -> Bool
AccountDelegation -> Value
AccountDelegation -> Encoding
(AccountDelegation -> Value)
-> (AccountDelegation -> Encoding)
-> ([AccountDelegation] -> Value)
-> ([AccountDelegation] -> Encoding)
-> (AccountDelegation -> Bool)
-> ToJSON AccountDelegation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccountDelegation -> Value
toJSON :: AccountDelegation -> Value
$ctoEncoding :: AccountDelegation -> Encoding
toEncoding :: AccountDelegation -> Encoding
$ctoJSONList :: [AccountDelegation] -> Value
toJSONList :: [AccountDelegation] -> Value
$ctoEncodingList :: [AccountDelegation] -> Encoding
toEncodingList :: [AccountDelegation] -> Encoding
$comitField :: AccountDelegation -> Bool
omitField :: AccountDelegation -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountDelegation", CamelToSnake]] AccountDelegation

instance ToSample AccountDelegation where
  toSamples :: Proxy AccountDelegation -> [(Text, AccountDelegation)]
toSamples = [(Text, AccountDelegation)]
-> Proxy AccountDelegation -> [(Text, AccountDelegation)]
forall a. a -> Proxy AccountDelegation -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountDelegation)]
 -> Proxy AccountDelegation -> [(Text, AccountDelegation)])
-> [(Text, AccountDelegation)]
-> Proxy AccountDelegation
-> [(Text, AccountDelegation)]
forall a b. (a -> b) -> a -> b
$ [AccountDelegation] -> [(Text, AccountDelegation)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountDelegation
        { _accountDelegationActiveEpoch :: Epoch
_accountDelegationActiveEpoch = Epoch
210
        , _accountDelegationTxHash :: TxHash
_accountDelegationTxHash = TxHash
"2dd15e0ef6e6a17841cb9541c27724072ce4d4b79b91e58432fbaa32d9572531"
        , _accountDelegationAmount :: Lovelaces
_accountDelegationAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
12695385
        , _accountDelegationPoolId :: PoolId
_accountDelegationPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
        }
    , AccountDelegation
        { _accountDelegationActiveEpoch :: Epoch
_accountDelegationActiveEpoch = Epoch
242
        , _accountDelegationTxHash :: TxHash
_accountDelegationTxHash = TxHash
"1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dde628516157f0"
        , _accountDelegationAmount :: Lovelaces
_accountDelegationAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
12691385
        , _accountDelegationPoolId :: PoolId
_accountDelegationPoolId = PoolId
"pool1kchver88u3kygsak8wgll7htr8uxn5v35lfrsyy842nkscrzyvj"
        }
    ]

-- | Registration action
data AccountRegistrationAction = Registered | Deregistered
  deriving stock (Int -> AccountRegistrationAction -> ShowS
[AccountRegistrationAction] -> ShowS
AccountRegistrationAction -> String
(Int -> AccountRegistrationAction -> ShowS)
-> (AccountRegistrationAction -> String)
-> ([AccountRegistrationAction] -> ShowS)
-> Show AccountRegistrationAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountRegistrationAction -> ShowS
showsPrec :: Int -> AccountRegistrationAction -> ShowS
$cshow :: AccountRegistrationAction -> String
show :: AccountRegistrationAction -> String
$cshowList :: [AccountRegistrationAction] -> ShowS
showList :: [AccountRegistrationAction] -> ShowS
Show, AccountRegistrationAction -> AccountRegistrationAction -> Bool
(AccountRegistrationAction -> AccountRegistrationAction -> Bool)
-> (AccountRegistrationAction -> AccountRegistrationAction -> Bool)
-> Eq AccountRegistrationAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountRegistrationAction -> AccountRegistrationAction -> Bool
== :: AccountRegistrationAction -> AccountRegistrationAction -> Bool
$c/= :: AccountRegistrationAction -> AccountRegistrationAction -> Bool
/= :: AccountRegistrationAction -> AccountRegistrationAction -> Bool
Eq, (forall x.
 AccountRegistrationAction -> Rep AccountRegistrationAction x)
-> (forall x.
    Rep AccountRegistrationAction x -> AccountRegistrationAction)
-> Generic AccountRegistrationAction
forall x.
Rep AccountRegistrationAction x -> AccountRegistrationAction
forall x.
AccountRegistrationAction -> Rep AccountRegistrationAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
AccountRegistrationAction -> Rep AccountRegistrationAction x
from :: forall x.
AccountRegistrationAction -> Rep AccountRegistrationAction x
$cto :: forall x.
Rep AccountRegistrationAction x -> AccountRegistrationAction
to :: forall x.
Rep AccountRegistrationAction x -> AccountRegistrationAction
Generic)
  deriving (Maybe AccountRegistrationAction
Value -> Parser [AccountRegistrationAction]
Value -> Parser AccountRegistrationAction
(Value -> Parser AccountRegistrationAction)
-> (Value -> Parser [AccountRegistrationAction])
-> Maybe AccountRegistrationAction
-> FromJSON AccountRegistrationAction
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccountRegistrationAction
parseJSON :: Value -> Parser AccountRegistrationAction
$cparseJSONList :: Value -> Parser [AccountRegistrationAction]
parseJSONList :: Value -> Parser [AccountRegistrationAction]
$comittedField :: Maybe AccountRegistrationAction
omittedField :: Maybe AccountRegistrationAction
FromJSON, [AccountRegistrationAction] -> Value
[AccountRegistrationAction] -> Encoding
AccountRegistrationAction -> Bool
AccountRegistrationAction -> Value
AccountRegistrationAction -> Encoding
(AccountRegistrationAction -> Value)
-> (AccountRegistrationAction -> Encoding)
-> ([AccountRegistrationAction] -> Value)
-> ([AccountRegistrationAction] -> Encoding)
-> (AccountRegistrationAction -> Bool)
-> ToJSON AccountRegistrationAction
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccountRegistrationAction -> Value
toJSON :: AccountRegistrationAction -> Value
$ctoEncoding :: AccountRegistrationAction -> Encoding
toEncoding :: AccountRegistrationAction -> Encoding
$ctoJSONList :: [AccountRegistrationAction] -> Value
toJSONList :: [AccountRegistrationAction] -> Value
$ctoEncodingList :: [AccountRegistrationAction] -> Encoding
toEncodingList :: [AccountRegistrationAction] -> Encoding
$comitField :: AccountRegistrationAction -> Bool
omitField :: AccountRegistrationAction -> Bool
ToJSON)
  via CustomJSON '[ConstructorTagModifier '[ToLower]] AccountRegistrationAction

instance ToSample AccountRegistrationAction where
  toSamples :: Proxy AccountRegistrationAction
-> [(Text, AccountRegistrationAction)]
toSamples = [(Text, AccountRegistrationAction)]
-> Proxy AccountRegistrationAction
-> [(Text, AccountRegistrationAction)]
forall a. a -> Proxy AccountRegistrationAction -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountRegistrationAction)]
 -> Proxy AccountRegistrationAction
 -> [(Text, AccountRegistrationAction)])
-> [(Text, AccountRegistrationAction)]
-> Proxy AccountRegistrationAction
-> [(Text, AccountRegistrationAction)]
forall a b. (a -> b) -> a -> b
$ [AccountRegistrationAction] -> [(Text, AccountRegistrationAction)]
forall a. [a] -> [(Text, a)]
samples [ AccountRegistrationAction
Registered, AccountRegistrationAction
Deregistered ]

-- | Account (de)registration
data AccountRegistration = AccountRegistration
  { AccountRegistration -> AccountRegistrationAction
_accountRegistrationAction :: AccountRegistrationAction -- ^ Action in the certificate
  , AccountRegistration -> TxHash
_accountRegistrationTxHash :: TxHash -- ^ Hash of the transaction containing the (de)registration certificate
  }
  deriving stock (Int -> AccountRegistration -> ShowS
[AccountRegistration] -> ShowS
AccountRegistration -> String
(Int -> AccountRegistration -> ShowS)
-> (AccountRegistration -> String)
-> ([AccountRegistration] -> ShowS)
-> Show AccountRegistration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountRegistration -> ShowS
showsPrec :: Int -> AccountRegistration -> ShowS
$cshow :: AccountRegistration -> String
show :: AccountRegistration -> String
$cshowList :: [AccountRegistration] -> ShowS
showList :: [AccountRegistration] -> ShowS
Show, AccountRegistration -> AccountRegistration -> Bool
(AccountRegistration -> AccountRegistration -> Bool)
-> (AccountRegistration -> AccountRegistration -> Bool)
-> Eq AccountRegistration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountRegistration -> AccountRegistration -> Bool
== :: AccountRegistration -> AccountRegistration -> Bool
$c/= :: AccountRegistration -> AccountRegistration -> Bool
/= :: AccountRegistration -> AccountRegistration -> Bool
Eq, (forall x. AccountRegistration -> Rep AccountRegistration x)
-> (forall x. Rep AccountRegistration x -> AccountRegistration)
-> Generic AccountRegistration
forall x. Rep AccountRegistration x -> AccountRegistration
forall x. AccountRegistration -> Rep AccountRegistration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccountRegistration -> Rep AccountRegistration x
from :: forall x. AccountRegistration -> Rep AccountRegistration x
$cto :: forall x. Rep AccountRegistration x -> AccountRegistration
to :: forall x. Rep AccountRegistration x -> AccountRegistration
Generic)
  deriving (Maybe AccountRegistration
Value -> Parser [AccountRegistration]
Value -> Parser AccountRegistration
(Value -> Parser AccountRegistration)
-> (Value -> Parser [AccountRegistration])
-> Maybe AccountRegistration
-> FromJSON AccountRegistration
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccountRegistration
parseJSON :: Value -> Parser AccountRegistration
$cparseJSONList :: Value -> Parser [AccountRegistration]
parseJSONList :: Value -> Parser [AccountRegistration]
$comittedField :: Maybe AccountRegistration
omittedField :: Maybe AccountRegistration
FromJSON, [AccountRegistration] -> Value
[AccountRegistration] -> Encoding
AccountRegistration -> Bool
AccountRegistration -> Value
AccountRegistration -> Encoding
(AccountRegistration -> Value)
-> (AccountRegistration -> Encoding)
-> ([AccountRegistration] -> Value)
-> ([AccountRegistration] -> Encoding)
-> (AccountRegistration -> Bool)
-> ToJSON AccountRegistration
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccountRegistration -> Value
toJSON :: AccountRegistration -> Value
$ctoEncoding :: AccountRegistration -> Encoding
toEncoding :: AccountRegistration -> Encoding
$ctoJSONList :: [AccountRegistration] -> Value
toJSONList :: [AccountRegistration] -> Value
$ctoEncodingList :: [AccountRegistration] -> Encoding
toEncodingList :: [AccountRegistration] -> Encoding
$comitField :: AccountRegistration -> Bool
omitField :: AccountRegistration -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountRegistration", CamelToSnake]] AccountRegistration

instance ToSample AccountRegistration where
  toSamples :: Proxy AccountRegistration -> [(Text, AccountRegistration)]
toSamples = [(Text, AccountRegistration)]
-> Proxy AccountRegistration -> [(Text, AccountRegistration)]
forall a. a -> Proxy AccountRegistration -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountRegistration)]
 -> Proxy AccountRegistration -> [(Text, AccountRegistration)])
-> [(Text, AccountRegistration)]
-> Proxy AccountRegistration
-> [(Text, AccountRegistration)]
forall a b. (a -> b) -> a -> b
$ [AccountRegistration] -> [(Text, AccountRegistration)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountRegistration
        { _accountRegistrationAction :: AccountRegistrationAction
_accountRegistrationAction = AccountRegistrationAction
Registered
        , _accountRegistrationTxHash :: TxHash
_accountRegistrationTxHash = TxHash
"2dd15e0ef6e6a17841cb9541c27724072ce4d4b79b91e58432fbaa32d9572531"
        }
    , AccountRegistration
        { _accountRegistrationAction :: AccountRegistrationAction
_accountRegistrationAction = AccountRegistrationAction
Deregistered
        , _accountRegistrationTxHash :: TxHash
_accountRegistrationTxHash = TxHash
"1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dde628516157f0"
        }
    ]

-- | Withdrawal from an account
data AccountWithdrawal = AccountWithdrawal
  { AccountWithdrawal -> Lovelaces
_accountWithdrawalAmount :: Lovelaces -- ^ Withdrawal amount in Lovelaces
  , AccountWithdrawal -> TxHash
_accountWithdrawalTxHash :: TxHash -- ^ Hash of the transaction containing the withdrawal
  }
  deriving stock (Int -> AccountWithdrawal -> ShowS
[AccountWithdrawal] -> ShowS
AccountWithdrawal -> String
(Int -> AccountWithdrawal -> ShowS)
-> (AccountWithdrawal -> String)
-> ([AccountWithdrawal] -> ShowS)
-> Show AccountWithdrawal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountWithdrawal -> ShowS
showsPrec :: Int -> AccountWithdrawal -> ShowS
$cshow :: AccountWithdrawal -> String
show :: AccountWithdrawal -> String
$cshowList :: [AccountWithdrawal] -> ShowS
showList :: [AccountWithdrawal] -> ShowS
Show, AccountWithdrawal -> AccountWithdrawal -> Bool
(AccountWithdrawal -> AccountWithdrawal -> Bool)
-> (AccountWithdrawal -> AccountWithdrawal -> Bool)
-> Eq AccountWithdrawal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountWithdrawal -> AccountWithdrawal -> Bool
== :: AccountWithdrawal -> AccountWithdrawal -> Bool
$c/= :: AccountWithdrawal -> AccountWithdrawal -> Bool
/= :: AccountWithdrawal -> AccountWithdrawal -> Bool
Eq, (forall x. AccountWithdrawal -> Rep AccountWithdrawal x)
-> (forall x. Rep AccountWithdrawal x -> AccountWithdrawal)
-> Generic AccountWithdrawal
forall x. Rep AccountWithdrawal x -> AccountWithdrawal
forall x. AccountWithdrawal -> Rep AccountWithdrawal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccountWithdrawal -> Rep AccountWithdrawal x
from :: forall x. AccountWithdrawal -> Rep AccountWithdrawal x
$cto :: forall x. Rep AccountWithdrawal x -> AccountWithdrawal
to :: forall x. Rep AccountWithdrawal x -> AccountWithdrawal
Generic)
  deriving (Maybe AccountWithdrawal
Value -> Parser [AccountWithdrawal]
Value -> Parser AccountWithdrawal
(Value -> Parser AccountWithdrawal)
-> (Value -> Parser [AccountWithdrawal])
-> Maybe AccountWithdrawal
-> FromJSON AccountWithdrawal
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccountWithdrawal
parseJSON :: Value -> Parser AccountWithdrawal
$cparseJSONList :: Value -> Parser [AccountWithdrawal]
parseJSONList :: Value -> Parser [AccountWithdrawal]
$comittedField :: Maybe AccountWithdrawal
omittedField :: Maybe AccountWithdrawal
FromJSON, [AccountWithdrawal] -> Value
[AccountWithdrawal] -> Encoding
AccountWithdrawal -> Bool
AccountWithdrawal -> Value
AccountWithdrawal -> Encoding
(AccountWithdrawal -> Value)
-> (AccountWithdrawal -> Encoding)
-> ([AccountWithdrawal] -> Value)
-> ([AccountWithdrawal] -> Encoding)
-> (AccountWithdrawal -> Bool)
-> ToJSON AccountWithdrawal
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccountWithdrawal -> Value
toJSON :: AccountWithdrawal -> Value
$ctoEncoding :: AccountWithdrawal -> Encoding
toEncoding :: AccountWithdrawal -> Encoding
$ctoJSONList :: [AccountWithdrawal] -> Value
toJSONList :: [AccountWithdrawal] -> Value
$ctoEncodingList :: [AccountWithdrawal] -> Encoding
toEncodingList :: [AccountWithdrawal] -> Encoding
$comitField :: AccountWithdrawal -> Bool
omitField :: AccountWithdrawal -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountWithdrawal", CamelToSnake]] AccountWithdrawal

instance ToSample AccountWithdrawal where
  toSamples :: Proxy AccountWithdrawal -> [(Text, AccountWithdrawal)]
toSamples = [(Text, AccountWithdrawal)]
-> Proxy AccountWithdrawal -> [(Text, AccountWithdrawal)]
forall a. a -> Proxy AccountWithdrawal -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountWithdrawal)]
 -> Proxy AccountWithdrawal -> [(Text, AccountWithdrawal)])
-> [(Text, AccountWithdrawal)]
-> Proxy AccountWithdrawal
-> [(Text, AccountWithdrawal)]
forall a b. (a -> b) -> a -> b
$ [AccountWithdrawal] -> [(Text, AccountWithdrawal)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountWithdrawal
        { _accountWithdrawalAmount :: Lovelaces
_accountWithdrawalAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
454541212442
        , _accountWithdrawalTxHash :: TxHash
_accountWithdrawalTxHash = TxHash
"48a9625c841eea0dd2bb6cf551eabe6523b7290c9ce34be74eedef2dd8f7ecc5"
        }
    , AccountWithdrawal
        { _accountWithdrawalAmount :: Lovelaces
_accountWithdrawalAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
97846969
        , _accountWithdrawalTxHash :: TxHash
_accountWithdrawalTxHash = TxHash
"4230b0cbccf6f449f0847d8ad1d634a7a49df60d8c142bb8cc2dbc8ca03d9e34"
        }
    ]

-- | Account MIR (Move Instantaneous Reward)
data AccountMir = AccountMir
  { AccountMir -> Lovelaces
_accountMirAmount :: Lovelaces -- ^ MIR amount in Lovelaces
  , AccountMir -> TxHash
_accountMirTxHash :: TxHash -- ^ Hash of the transaction containing the MIR
  }
  deriving stock (Int -> AccountMir -> ShowS
[AccountMir] -> ShowS
AccountMir -> String
(Int -> AccountMir -> ShowS)
-> (AccountMir -> String)
-> ([AccountMir] -> ShowS)
-> Show AccountMir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountMir -> ShowS
showsPrec :: Int -> AccountMir -> ShowS
$cshow :: AccountMir -> String
show :: AccountMir -> String
$cshowList :: [AccountMir] -> ShowS
showList :: [AccountMir] -> ShowS
Show, AccountMir -> AccountMir -> Bool
(AccountMir -> AccountMir -> Bool)
-> (AccountMir -> AccountMir -> Bool) -> Eq AccountMir
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountMir -> AccountMir -> Bool
== :: AccountMir -> AccountMir -> Bool
$c/= :: AccountMir -> AccountMir -> Bool
/= :: AccountMir -> AccountMir -> Bool
Eq, (forall x. AccountMir -> Rep AccountMir x)
-> (forall x. Rep AccountMir x -> AccountMir) -> Generic AccountMir
forall x. Rep AccountMir x -> AccountMir
forall x. AccountMir -> Rep AccountMir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccountMir -> Rep AccountMir x
from :: forall x. AccountMir -> Rep AccountMir x
$cto :: forall x. Rep AccountMir x -> AccountMir
to :: forall x. Rep AccountMir x -> AccountMir
Generic)
  deriving (Maybe AccountMir
Value -> Parser [AccountMir]
Value -> Parser AccountMir
(Value -> Parser AccountMir)
-> (Value -> Parser [AccountMir])
-> Maybe AccountMir
-> FromJSON AccountMir
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccountMir
parseJSON :: Value -> Parser AccountMir
$cparseJSONList :: Value -> Parser [AccountMir]
parseJSONList :: Value -> Parser [AccountMir]
$comittedField :: Maybe AccountMir
omittedField :: Maybe AccountMir
FromJSON, [AccountMir] -> Value
[AccountMir] -> Encoding
AccountMir -> Bool
AccountMir -> Value
AccountMir -> Encoding
(AccountMir -> Value)
-> (AccountMir -> Encoding)
-> ([AccountMir] -> Value)
-> ([AccountMir] -> Encoding)
-> (AccountMir -> Bool)
-> ToJSON AccountMir
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccountMir -> Value
toJSON :: AccountMir -> Value
$ctoEncoding :: AccountMir -> Encoding
toEncoding :: AccountMir -> Encoding
$ctoJSONList :: [AccountMir] -> Value
toJSONList :: [AccountMir] -> Value
$ctoEncodingList :: [AccountMir] -> Encoding
toEncodingList :: [AccountMir] -> Encoding
$comitField :: AccountMir -> Bool
omitField :: AccountMir -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_accountMir", CamelToSnake]] AccountMir

instance ToSample AccountMir where
  toSamples :: Proxy AccountMir -> [(Text, AccountMir)]
toSamples = [(Text, AccountMir)] -> Proxy AccountMir -> [(Text, AccountMir)]
forall a. a -> Proxy AccountMir -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AccountMir)] -> Proxy AccountMir -> [(Text, AccountMir)])
-> [(Text, AccountMir)] -> Proxy AccountMir -> [(Text, AccountMir)]
forall a b. (a -> b) -> a -> b
$ [AccountMir] -> [(Text, AccountMir)]
forall a. [a] -> [(Text, a)]
samples
    [ AccountMir
        { _accountMirAmount :: Lovelaces
_accountMirAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
6202170
        , _accountMirTxHash :: TxHash
_accountMirTxHash = TxHash
"2dd15e0ef6e6a17841cb9541c27724072ce4d4b79b91e58432fbaa32d9572531"
        }
    , AccountMir
        { _accountMirAmount :: Lovelaces
_accountMirAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
1202170
        , _accountMirTxHash :: TxHash
_accountMirTxHash = TxHash
"1dd15e0ef6e6a17841cb9541c27724072ce4d4b79b91e58432fbaa32d9572531"
        }
    ]

-- | Address associated with an account address
newtype AddressAssociated = AddressAssociated {AddressAssociated -> Address
_addressAssociatedAddress :: Address}
  deriving stock (AddressAssociated -> AddressAssociated -> Bool
(AddressAssociated -> AddressAssociated -> Bool)
-> (AddressAssociated -> AddressAssociated -> Bool)
-> Eq AddressAssociated
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AddressAssociated -> AddressAssociated -> Bool
== :: AddressAssociated -> AddressAssociated -> Bool
$c/= :: AddressAssociated -> AddressAssociated -> Bool
/= :: AddressAssociated -> AddressAssociated -> Bool
Eq, Int -> AddressAssociated -> ShowS
[AddressAssociated] -> ShowS
AddressAssociated -> String
(Int -> AddressAssociated -> ShowS)
-> (AddressAssociated -> String)
-> ([AddressAssociated] -> ShowS)
-> Show AddressAssociated
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AddressAssociated -> ShowS
showsPrec :: Int -> AddressAssociated -> ShowS
$cshow :: AddressAssociated -> String
show :: AddressAssociated -> String
$cshowList :: [AddressAssociated] -> ShowS
showList :: [AddressAssociated] -> ShowS
Show, (forall x. AddressAssociated -> Rep AddressAssociated x)
-> (forall x. Rep AddressAssociated x -> AddressAssociated)
-> Generic AddressAssociated
forall x. Rep AddressAssociated x -> AddressAssociated
forall x. AddressAssociated -> Rep AddressAssociated x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AddressAssociated -> Rep AddressAssociated x
from :: forall x. AddressAssociated -> Rep AddressAssociated x
$cto :: forall x. Rep AddressAssociated x -> AddressAssociated
to :: forall x. Rep AddressAssociated x -> AddressAssociated
Generic)
  deriving (Maybe AddressAssociated
Value -> Parser [AddressAssociated]
Value -> Parser AddressAssociated
(Value -> Parser AddressAssociated)
-> (Value -> Parser [AddressAssociated])
-> Maybe AddressAssociated
-> FromJSON AddressAssociated
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AddressAssociated
parseJSON :: Value -> Parser AddressAssociated
$cparseJSONList :: Value -> Parser [AddressAssociated]
parseJSONList :: Value -> Parser [AddressAssociated]
$comittedField :: Maybe AddressAssociated
omittedField :: Maybe AddressAssociated
FromJSON, [AddressAssociated] -> Value
[AddressAssociated] -> Encoding
AddressAssociated -> Bool
AddressAssociated -> Value
AddressAssociated -> Encoding
(AddressAssociated -> Value)
-> (AddressAssociated -> Encoding)
-> ([AddressAssociated] -> Value)
-> ([AddressAssociated] -> Encoding)
-> (AddressAssociated -> Bool)
-> ToJSON AddressAssociated
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AddressAssociated -> Value
toJSON :: AddressAssociated -> Value
$ctoEncoding :: AddressAssociated -> Encoding
toEncoding :: AddressAssociated -> Encoding
$ctoJSONList :: [AddressAssociated] -> Value
toJSONList :: [AddressAssociated] -> Value
$ctoEncodingList :: [AddressAssociated] -> Encoding
toEncodingList :: [AddressAssociated] -> Encoding
$comitField :: AddressAssociated -> Bool
omitField :: AddressAssociated -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_addressAssociated", CamelToSnake]] AddressAssociated

instance ToSample AddressAssociated where
  toSamples :: Proxy AddressAssociated -> [(Text, AddressAssociated)]
toSamples = [(Text, AddressAssociated)]
-> Proxy AddressAssociated -> [(Text, AddressAssociated)]
forall a. a -> Proxy AddressAssociated -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AddressAssociated)]
 -> Proxy AddressAssociated -> [(Text, AddressAssociated)])
-> [(Text, AddressAssociated)]
-> Proxy AddressAssociated
-> [(Text, AddressAssociated)]
forall a b. (a -> b) -> a -> b
$ [AddressAssociated] -> [(Text, AddressAssociated)]
forall a. [a] -> [(Text, a)]
samples
    [ Address -> AddressAssociated
AddressAssociated Address
"addr1qx2kd28nq8ac5prwg32hhvudlwggpgfp8utlyqxu6wqgz62f79qsdmm5dsknt9ecr5w468r9ey0fxwkdrwh08ly3tu9sy0f4qd"
    , Address -> AddressAssociated
AddressAssociated Address
"addr1q8j55h253zcvl326sk5qdt2n8z7eghzspe0ekxgncr796s2f79qsdmm5dsknt9ecr5w468r9ey0fxwkdrwh08ly3tu9sjmd35m"
    ]

-- | Detailed information about account associated addresses
data AddressAssociatedTotal = AddressAssociatedTotal {
    AddressAssociatedTotal -> Address
_addressAssociatedTotalStakeAddress :: Address -- ^ Bech32 encoded address
  , AddressAssociatedTotal -> [Amount]
_addressAssociatedTotalReceivedSum  :: [Amount]
  , AddressAssociatedTotal -> [Amount]
_addressAssociatedTotalSentSum      :: [Amount]
  , AddressAssociatedTotal -> Integer
_addressAssociatedTotalTxCount      :: Integer -- ^ Count of all transactions for all addresses associated with the account
  } deriving stock (Int -> AddressAssociatedTotal -> ShowS
[AddressAssociatedTotal] -> ShowS
AddressAssociatedTotal -> String
(Int -> AddressAssociatedTotal -> ShowS)
-> (AddressAssociatedTotal -> String)
-> ([AddressAssociatedTotal] -> ShowS)
-> Show AddressAssociatedTotal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AddressAssociatedTotal -> ShowS
showsPrec :: Int -> AddressAssociatedTotal -> ShowS
$cshow :: AddressAssociatedTotal -> String
show :: AddressAssociatedTotal -> String
$cshowList :: [AddressAssociatedTotal] -> ShowS
showList :: [AddressAssociatedTotal] -> ShowS
Show, AddressAssociatedTotal -> AddressAssociatedTotal -> Bool
(AddressAssociatedTotal -> AddressAssociatedTotal -> Bool)
-> (AddressAssociatedTotal -> AddressAssociatedTotal -> Bool)
-> Eq AddressAssociatedTotal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AddressAssociatedTotal -> AddressAssociatedTotal -> Bool
== :: AddressAssociatedTotal -> AddressAssociatedTotal -> Bool
$c/= :: AddressAssociatedTotal -> AddressAssociatedTotal -> Bool
/= :: AddressAssociatedTotal -> AddressAssociatedTotal -> Bool
Eq, (forall x. AddressAssociatedTotal -> Rep AddressAssociatedTotal x)
-> (forall x.
    Rep AddressAssociatedTotal x -> AddressAssociatedTotal)
-> Generic AddressAssociatedTotal
forall x. Rep AddressAssociatedTotal x -> AddressAssociatedTotal
forall x. AddressAssociatedTotal -> Rep AddressAssociatedTotal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AddressAssociatedTotal -> Rep AddressAssociatedTotal x
from :: forall x. AddressAssociatedTotal -> Rep AddressAssociatedTotal x
$cto :: forall x. Rep AddressAssociatedTotal x -> AddressAssociatedTotal
to :: forall x. Rep AddressAssociatedTotal x -> AddressAssociatedTotal
Generic)
  deriving (Maybe AddressAssociatedTotal
Value -> Parser [AddressAssociatedTotal]
Value -> Parser AddressAssociatedTotal
(Value -> Parser AddressAssociatedTotal)
-> (Value -> Parser [AddressAssociatedTotal])
-> Maybe AddressAssociatedTotal
-> FromJSON AddressAssociatedTotal
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AddressAssociatedTotal
parseJSON :: Value -> Parser AddressAssociatedTotal
$cparseJSONList :: Value -> Parser [AddressAssociatedTotal]
parseJSONList :: Value -> Parser [AddressAssociatedTotal]
$comittedField :: Maybe AddressAssociatedTotal
omittedField :: Maybe AddressAssociatedTotal
FromJSON, [AddressAssociatedTotal] -> Value
[AddressAssociatedTotal] -> Encoding
AddressAssociatedTotal -> Bool
AddressAssociatedTotal -> Value
AddressAssociatedTotal -> Encoding
(AddressAssociatedTotal -> Value)
-> (AddressAssociatedTotal -> Encoding)
-> ([AddressAssociatedTotal] -> Value)
-> ([AddressAssociatedTotal] -> Encoding)
-> (AddressAssociatedTotal -> Bool)
-> ToJSON AddressAssociatedTotal
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AddressAssociatedTotal -> Value
toJSON :: AddressAssociatedTotal -> Value
$ctoEncoding :: AddressAssociatedTotal -> Encoding
toEncoding :: AddressAssociatedTotal -> Encoding
$ctoJSONList :: [AddressAssociatedTotal] -> Value
toJSONList :: [AddressAssociatedTotal] -> Value
$ctoEncodingList :: [AddressAssociatedTotal] -> Encoding
toEncodingList :: [AddressAssociatedTotal] -> Encoding
$comitField :: AddressAssociatedTotal -> Bool
omitField :: AddressAssociatedTotal -> Bool
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_addressAssociatedTotal", CamelToSnake]] AddressAssociatedTotal

instance ToSample AddressAssociatedTotal where
  toSamples :: Proxy AddressAssociatedTotal -> [(Text, AddressAssociatedTotal)]
toSamples = [(Text, AddressAssociatedTotal)]
-> Proxy AddressAssociatedTotal -> [(Text, AddressAssociatedTotal)]
forall a. a -> Proxy AddressAssociatedTotal -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, AddressAssociatedTotal)]
 -> Proxy AddressAssociatedTotal
 -> [(Text, AddressAssociatedTotal)])
-> [(Text, AddressAssociatedTotal)]
-> Proxy AddressAssociatedTotal
-> [(Text, AddressAssociatedTotal)]
forall a b. (a -> b) -> a -> b
$ AddressAssociatedTotal -> [(Text, AddressAssociatedTotal)]
forall a. a -> [(Text, a)]
singleSample
    AddressAssociatedTotal
      { _addressAssociatedTotalStakeAddress :: Address
_addressAssociatedTotalStakeAddress = Address
"stake1u9l5q5jwgelgagzyt6nuaasefgmn8pd25c8e9qpeprq0tdcp0e3uk"
      , _addressAssociatedTotalReceivedSum :: [Amount]
_addressAssociatedTotalReceivedSum =
          [ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
Lovelaces
42000000
          , SomeDiscrete -> Amount
AssetAmount
              (SomeDiscrete -> Amount) -> SomeDiscrete -> Amount
forall a b. (a -> b) -> a -> b
$ Text -> Scale -> Integer -> SomeDiscrete
Money.mkSomeDiscrete
                  Text
"b0d07d45fe9514f80213f4020e5a61241458be626841cde717cb38a76e7574636f696e"
                   Scale
unitScale
                   Integer
12
          ]
      , _addressAssociatedTotalSentSum :: [Amount]
_addressAssociatedTotalSentSum =
          [ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
Lovelaces
123
          , SomeDiscrete -> Amount
AssetAmount
              (SomeDiscrete -> Amount) -> SomeDiscrete -> Amount
forall a b. (a -> b) -> a -> b
$ Text -> Scale -> Integer -> SomeDiscrete
Money.mkSomeDiscrete
                  Text
"b0d07d45fe9514f80213f4020e5a61241458be626841cde717cb38a76e7574636f696e"
                   Scale
unitScale
                   Integer
1
          ]
      , _addressAssociatedTotalTxCount :: Integer
_addressAssociatedTotalTxCount = Integer
2
      }