module Blockfrost.Types.Cardano.Addresses
  ( AddressInfo (..)
  , AddressType (..)
  , AddressDetails (..)
  , AddressUtxo (..)
  , AddressTransaction (..)
  ) where
import Deriving.Aeson
import qualified Money
import Servant.Docs (ToSample (..), samples, singleSample)
import Blockfrost.Types.Cardano.Scripts (InlineDatum (..))
import Blockfrost.Types.Shared
data AddressInfo = AddressInfo
  { AddressInfo -> Address
_addressInfoAddress      :: Address 
  , AddressInfo -> [Amount]
_addressInfoAmount       :: [Amount] 
  , AddressInfo -> Maybe Address
_addressInfoStakeAddress :: Maybe Address 
  , AddressInfo -> AddressType
_addressInfoType         :: AddressType 
  , AddressInfo -> Bool
_addressInfoScript       :: Bool 
  } deriving stock (Int -> AddressInfo -> ShowS
[AddressInfo] -> ShowS
AddressInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressInfo] -> ShowS
$cshowList :: [AddressInfo] -> ShowS
show :: AddressInfo -> String
$cshow :: AddressInfo -> String
showsPrec :: Int -> AddressInfo -> ShowS
$cshowsPrec :: Int -> AddressInfo -> ShowS
Show, AddressInfo -> AddressInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressInfo -> AddressInfo -> Bool
$c/= :: AddressInfo -> AddressInfo -> Bool
== :: AddressInfo -> AddressInfo -> Bool
$c== :: AddressInfo -> AddressInfo -> Bool
Eq, forall x. Rep AddressInfo x -> AddressInfo
forall x. AddressInfo -> Rep AddressInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddressInfo x -> AddressInfo
$cfrom :: forall x. AddressInfo -> Rep AddressInfo x
Generic)
  deriving (Value -> Parser [AddressInfo]
Value -> Parser AddressInfo
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AddressInfo]
$cparseJSONList :: Value -> Parser [AddressInfo]
parseJSON :: Value -> Parser AddressInfo
$cparseJSON :: Value -> Parser AddressInfo
FromJSON, [AddressInfo] -> Encoding
[AddressInfo] -> Value
AddressInfo -> Encoding
AddressInfo -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AddressInfo] -> Encoding
$ctoEncodingList :: [AddressInfo] -> Encoding
toJSONList :: [AddressInfo] -> Value
$ctoJSONList :: [AddressInfo] -> Value
toEncoding :: AddressInfo -> Encoding
$ctoEncoding :: AddressInfo -> Encoding
toJSON :: AddressInfo -> Value
$ctoJSON :: AddressInfo -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_addressInfo", CamelToSnake]] AddressInfo
instance ToSample AddressInfo where
  toSamples :: Proxy AddressInfo -> [(Text, AddressInfo)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
    AddressInfo
      { _addressInfoAddress :: Address
_addressInfoAddress = Address
"addr1qxqs59lphg8g6qndelq8xwqn60ag3aeyfcp33c2kdp46a09re5df3pzwwmyq946axfcejy5n4x0y99wqpgtp2gd0k09qsgy6pz"
      , _addressInfoAmount :: [Amount]
_addressInfoAmount =
        [ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
42000000
        , SomeDiscrete -> Amount
AssetAmount
            forall a b. (a -> b) -> a -> b
$ Text -> Scale -> Integer -> SomeDiscrete
Money.mkSomeDiscrete
                Text
"b0d07d45fe9514f80213f4020e5a61241458be626841cde717cb38a76e7574636f696e"
                Scale
unitScale
                Integer
12
        ]
      , _addressInfoStakeAddress :: Maybe Address
_addressInfoStakeAddress = forall (f :: * -> *) a. Applicative f => a -> f a
pure Address
"stake1ux3g2c9dx2nhhehyrezyxpkstartcqmu9hk63qgfkccw5rqttygt7"
      , _addressInfoType :: AddressType
_addressInfoType = AddressType
Shelley
      , _addressInfoScript :: Bool
_addressInfoScript = Bool
False
      }
data AddressType = Byron | Shelley
  deriving stock (Int -> AddressType -> ShowS
[AddressType] -> ShowS
AddressType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressType] -> ShowS
$cshowList :: [AddressType] -> ShowS
show :: AddressType -> String
$cshow :: AddressType -> String
showsPrec :: Int -> AddressType -> ShowS
$cshowsPrec :: Int -> AddressType -> ShowS
Show, AddressType -> AddressType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressType -> AddressType -> Bool
$c/= :: AddressType -> AddressType -> Bool
== :: AddressType -> AddressType -> Bool
$c== :: AddressType -> AddressType -> Bool
Eq, forall x. Rep AddressType x -> AddressType
forall x. AddressType -> Rep AddressType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddressType x -> AddressType
$cfrom :: forall x. AddressType -> Rep AddressType x
Generic)
  deriving (Value -> Parser [AddressType]
Value -> Parser AddressType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AddressType]
$cparseJSONList :: Value -> Parser [AddressType]
parseJSON :: Value -> Parser AddressType
$cparseJSON :: Value -> Parser AddressType
FromJSON, [AddressType] -> Encoding
[AddressType] -> Value
AddressType -> Encoding
AddressType -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AddressType] -> Encoding
$ctoEncodingList :: [AddressType] -> Encoding
toJSONList :: [AddressType] -> Value
$ctoJSONList :: [AddressType] -> Value
toEncoding :: AddressType -> Encoding
$ctoEncoding :: AddressType -> Encoding
toJSON :: AddressType -> Value
$ctoJSON :: AddressType -> Value
ToJSON)
  via CustomJSON '[ConstructorTagModifier '[ToLower]] AddressType
instance ToSample AddressType where
  toSamples :: Proxy AddressType -> [(Text, AddressType)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [(Text, a)]
samples [ AddressType
Byron, AddressType
Shelley ]
data AddressDetails = AddressDetails
  { AddressDetails -> Address
_addressDetailsAddress     :: Address 
  , AddressDetails -> [Amount]
_addressDetailsReceivedSum :: [Amount] 
  , AddressDetails -> [Amount]
_addressDetailsSentSum     :: [Amount] 
  , AddressDetails -> Integer
_addressDetailsTxCount     :: Integer 
  } deriving stock (Int -> AddressDetails -> ShowS
[AddressDetails] -> ShowS
AddressDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressDetails] -> ShowS
$cshowList :: [AddressDetails] -> ShowS
show :: AddressDetails -> String
$cshow :: AddressDetails -> String
showsPrec :: Int -> AddressDetails -> ShowS
$cshowsPrec :: Int -> AddressDetails -> ShowS
Show, AddressDetails -> AddressDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressDetails -> AddressDetails -> Bool
$c/= :: AddressDetails -> AddressDetails -> Bool
== :: AddressDetails -> AddressDetails -> Bool
$c== :: AddressDetails -> AddressDetails -> Bool
Eq, forall x. Rep AddressDetails x -> AddressDetails
forall x. AddressDetails -> Rep AddressDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddressDetails x -> AddressDetails
$cfrom :: forall x. AddressDetails -> Rep AddressDetails x
Generic)
  deriving (Value -> Parser [AddressDetails]
Value -> Parser AddressDetails
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AddressDetails]
$cparseJSONList :: Value -> Parser [AddressDetails]
parseJSON :: Value -> Parser AddressDetails
$cparseJSON :: Value -> Parser AddressDetails
FromJSON, [AddressDetails] -> Encoding
[AddressDetails] -> Value
AddressDetails -> Encoding
AddressDetails -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AddressDetails] -> Encoding
$ctoEncodingList :: [AddressDetails] -> Encoding
toJSONList :: [AddressDetails] -> Value
$ctoJSONList :: [AddressDetails] -> Value
toEncoding :: AddressDetails -> Encoding
$ctoEncoding :: AddressDetails -> Encoding
toJSON :: AddressDetails -> Value
$ctoJSON :: AddressDetails -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_addressDetails", CamelToSnake]] AddressDetails
instance ToSample AddressDetails where
  toSamples :: Proxy AddressDetails -> [(Text, AddressDetails)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample
    AddressDetails
      { _addressDetailsAddress :: Address
_addressDetailsAddress = Address
"addr1qxqs59lphg8g6qndelq8xwqn60ag3aeyfcp33c2kdp46a09re5df3pzwwmyq946axfcejy5n4x0y99wqpgtp2gd0k09qsgy6pz"
      , _addressDetailsReceivedSum :: [Amount]
_addressDetailsReceivedSum = [Amount]
amounts
      , _addressDetailsSentSum :: [Amount]
_addressDetailsSentSum = [Amount]
amounts
      , _addressDetailsTxCount :: Integer
_addressDetailsTxCount = Integer
12
      }
    where amounts :: [Amount]
amounts =
            [ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
42000000
            , SomeDiscrete -> Amount
AssetAmount
                forall a b. (a -> b) -> a -> b
$ Text -> Scale -> Integer -> SomeDiscrete
Money.mkSomeDiscrete
                        Text
"b0d07d45fe9514f80213f4020e5a61241458be626841cde717cb38a76e7574636f696e"
                        Scale
unitScale
                        Integer
12
            ]
data AddressUtxo = AddressUtxo
  { AddressUtxo -> TxHash
_addressUtxoTxHash      :: TxHash 
  , AddressUtxo -> Integer
_addressUtxoOutputIndex :: Integer 
  , AddressUtxo -> [Amount]
_addressUtxoAmount      :: [Amount] 
  , AddressUtxo -> BlockHash
_addressUtxoBlock       :: BlockHash 
  , AddressUtxo -> Maybe DatumHash
_addressUtxoDataHash    :: Maybe DatumHash 
  , AddressUtxo -> Maybe InlineDatum
_addressUtxoInlineDatum :: Maybe InlineDatum 
  , AddressUtxo -> Maybe ScriptHash
_addressUtxoReferenceScriptHash :: Maybe ScriptHash 
  } deriving stock (Int -> AddressUtxo -> ShowS
[AddressUtxo] -> ShowS
AddressUtxo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressUtxo] -> ShowS
$cshowList :: [AddressUtxo] -> ShowS
show :: AddressUtxo -> String
$cshow :: AddressUtxo -> String
showsPrec :: Int -> AddressUtxo -> ShowS
$cshowsPrec :: Int -> AddressUtxo -> ShowS
Show, AddressUtxo -> AddressUtxo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressUtxo -> AddressUtxo -> Bool
$c/= :: AddressUtxo -> AddressUtxo -> Bool
== :: AddressUtxo -> AddressUtxo -> Bool
$c== :: AddressUtxo -> AddressUtxo -> Bool
Eq, forall x. Rep AddressUtxo x -> AddressUtxo
forall x. AddressUtxo -> Rep AddressUtxo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddressUtxo x -> AddressUtxo
$cfrom :: forall x. AddressUtxo -> Rep AddressUtxo x
Generic)
  deriving (Value -> Parser [AddressUtxo]
Value -> Parser AddressUtxo
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AddressUtxo]
$cparseJSONList :: Value -> Parser [AddressUtxo]
parseJSON :: Value -> Parser AddressUtxo
$cparseJSON :: Value -> Parser AddressUtxo
FromJSON, [AddressUtxo] -> Encoding
[AddressUtxo] -> Value
AddressUtxo -> Encoding
AddressUtxo -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AddressUtxo] -> Encoding
$ctoEncodingList :: [AddressUtxo] -> Encoding
toJSONList :: [AddressUtxo] -> Value
$ctoJSONList :: [AddressUtxo] -> Value
toEncoding :: AddressUtxo -> Encoding
$ctoEncoding :: AddressUtxo -> Encoding
toJSON :: AddressUtxo -> Value
$ctoJSON :: AddressUtxo -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_addressUtxo", CamelToSnake]] AddressUtxo
instance ToSample AddressUtxo where
  toSamples :: Proxy AddressUtxo -> [(Text, AddressUtxo)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [(Text, a)]
samples
    [ AddressUtxo
      { _addressUtxoTxHash :: TxHash
_addressUtxoTxHash = TxHash
"39a7a284c2a0948189dc45dec670211cd4d72f7b66c5726c08d9b3df11e44d58"
      , _addressUtxoOutputIndex :: Integer
_addressUtxoOutputIndex = Integer
0
      , _addressUtxoAmount :: [Amount]
_addressUtxoAmount = [ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
42000000 ]
      , _addressUtxoBlock :: BlockHash
_addressUtxoBlock = BlockHash
"7eb8e27d18686c7db9a18f8bbcfe34e3fed6e047afaa2d969904d15e934847e6"
      , _addressUtxoDataHash :: Maybe DatumHash
_addressUtxoDataHash = forall a. a -> Maybe a
Just DatumHash
"9e478573ab81ea7a8e31891ce0648b81229f408d596a3483e6f4f9b92d3cf710"
      , _addressUtxoInlineDatum :: Maybe InlineDatum
_addressUtxoInlineDatum = forall a. Maybe a
Nothing
      , _addressUtxoReferenceScriptHash :: Maybe ScriptHash
_addressUtxoReferenceScriptHash = forall a. Maybe a
Nothing
      }
    , AddressUtxo
      { _addressUtxoTxHash :: TxHash
_addressUtxoTxHash = TxHash
"4c4e67bafa15e742c13c592b65c8f74c769cd7d9af04c848099672d1ba391b49"
      , _addressUtxoOutputIndex :: Integer
_addressUtxoOutputIndex = Integer
0
      , _addressUtxoAmount :: [Amount]
_addressUtxoAmount = [ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
729235000 ]
      , _addressUtxoBlock :: BlockHash
_addressUtxoBlock = BlockHash
"953f1b80eb7c11a7ffcd67cbd4fde66e824a451aca5a4065725e5174b81685b7"
      , _addressUtxoDataHash :: Maybe DatumHash
_addressUtxoDataHash = forall a. Maybe a
Nothing
      , _addressUtxoInlineDatum :: Maybe InlineDatum
_addressUtxoInlineDatum = forall a. Maybe a
Nothing
      , _addressUtxoReferenceScriptHash :: Maybe ScriptHash
_addressUtxoReferenceScriptHash = forall a. Maybe a
Nothing
      }
    , AddressUtxo
      { _addressUtxoTxHash :: TxHash
_addressUtxoTxHash = TxHash
"768c63e27a1c816a83dc7b07e78af673b2400de8849ea7e7b734ae1333d100d2"
      , _addressUtxoOutputIndex :: Integer
_addressUtxoOutputIndex = Integer
1
      , _addressUtxoAmount :: [Amount]
_addressUtxoAmount =
          [ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
42000000
          , SomeDiscrete -> Amount
AssetAmount
              forall a b. (a -> b) -> a -> b
$ Text -> Scale -> Integer -> SomeDiscrete
Money.mkSomeDiscrete
                  Text
"b0d07d45fe9514f80213f4020e5a61241458be626841cde717cb38a76e7574636f696e"
                   Scale
unitScale
                   Integer
12
          ]
      , _addressUtxoBlock :: BlockHash
_addressUtxoBlock = BlockHash
"5c571f83fe6c784d3fbc223792627ccf0eea96773100f9aedecf8b1eda4544d7"
      , _addressUtxoDataHash :: Maybe DatumHash
_addressUtxoDataHash = forall a. Maybe a
Nothing
      , _addressUtxoInlineDatum :: Maybe InlineDatum
_addressUtxoInlineDatum = forall a. Maybe a
Nothing
      , _addressUtxoReferenceScriptHash :: Maybe ScriptHash
_addressUtxoReferenceScriptHash = forall a. Maybe a
Nothing
      }
    ]
data AddressTransaction = AddressTransaction {
    AddressTransaction -> TxHash
_addressTransactionTxHash      :: TxHash 
  , AddressTransaction -> Integer
_addressTransactionTxIndex     :: Integer 
  , AddressTransaction -> Integer
_addressTransactionBlockHeight :: Integer 
  , AddressTransaction -> POSIXTime
_addressTransactionBlockTime   :: POSIXTime 
  } deriving stock (Int -> AddressTransaction -> ShowS
[AddressTransaction] -> ShowS
AddressTransaction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressTransaction] -> ShowS
$cshowList :: [AddressTransaction] -> ShowS
show :: AddressTransaction -> String
$cshow :: AddressTransaction -> String
showsPrec :: Int -> AddressTransaction -> ShowS
$cshowsPrec :: Int -> AddressTransaction -> ShowS
Show, AddressTransaction -> AddressTransaction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressTransaction -> AddressTransaction -> Bool
$c/= :: AddressTransaction -> AddressTransaction -> Bool
== :: AddressTransaction -> AddressTransaction -> Bool
$c== :: AddressTransaction -> AddressTransaction -> Bool
Eq, forall x. Rep AddressTransaction x -> AddressTransaction
forall x. AddressTransaction -> Rep AddressTransaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddressTransaction x -> AddressTransaction
$cfrom :: forall x. AddressTransaction -> Rep AddressTransaction x
Generic)
  deriving (Value -> Parser [AddressTransaction]
Value -> Parser AddressTransaction
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AddressTransaction]
$cparseJSONList :: Value -> Parser [AddressTransaction]
parseJSON :: Value -> Parser AddressTransaction
$cparseJSON :: Value -> Parser AddressTransaction
FromJSON, [AddressTransaction] -> Encoding
[AddressTransaction] -> Value
AddressTransaction -> Encoding
AddressTransaction -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AddressTransaction] -> Encoding
$ctoEncodingList :: [AddressTransaction] -> Encoding
toJSONList :: [AddressTransaction] -> Value
$ctoJSONList :: [AddressTransaction] -> Value
toEncoding :: AddressTransaction -> Encoding
$ctoEncoding :: AddressTransaction -> Encoding
toJSON :: AddressTransaction -> Value
$ctoJSON :: AddressTransaction -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_addressTransaction", CamelToSnake]] AddressTransaction
instance ToSample AddressTransaction where
  toSamples :: Proxy AddressTransaction -> [(Text, AddressTransaction)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [(Text, a)]
samples
    [ AddressTransaction
      { _addressTransactionTxHash :: TxHash
_addressTransactionTxHash = TxHash
"8788591983aa73981fc92d6cddbbe643959f5a784e84b8bee0db15823f575a5b"
      , _addressTransactionTxIndex :: Integer
_addressTransactionTxIndex = Integer
6
      , _addressTransactionBlockHeight :: Integer
_addressTransactionBlockHeight = Integer
69
      , _addressTransactionBlockTime :: POSIXTime
_addressTransactionBlockTime = POSIXTime
1635505891
      }
    , AddressTransaction
      { _addressTransactionTxHash :: TxHash
_addressTransactionTxHash = TxHash
"52e748c4dec58b687b90b0b40d383b9fe1f24c1a833b7395cdf07dd67859f46f"
      , _addressTransactionTxIndex :: Integer
_addressTransactionTxIndex = Integer
9
      , _addressTransactionBlockHeight :: Integer
_addressTransactionBlockHeight = Integer
4547
      , _addressTransactionBlockTime :: POSIXTime
_addressTransactionBlockTime = POSIXTime
1635505987
      }
    , AddressTransaction
      { _addressTransactionTxHash :: TxHash
_addressTransactionTxHash = TxHash
"e8073fd5318ff43eca18a852527166aa8008bee9ee9e891f585612b7e4ba700b"
      , _addressTransactionTxIndex :: Integer
_addressTransactionTxIndex = Integer
0
      , _addressTransactionBlockHeight :: Integer
_addressTransactionBlockHeight = Integer
564654
      , _addressTransactionBlockTime :: POSIXTime
_addressTransactionBlockTime = POSIXTime
1834505492
      }
    ]