module Blockfrost.Types.Cardano.Epochs
( EpochInfo (..)
, PoolStakeDistribution (..)
, ProtocolParams (..)
, CostModels (..)
, StakeDistribution (..)
) where
import Blockfrost.Types.Shared
import Data.Aeson (object, FromJSON (..), ToJSON (..), withObject)
import Data.Map (Map)
import Data.Text (Text)
import Deriving.Aeson
import Servant.Docs (ToSample (..), singleSample)
import qualified Data.Aeson.Key
import qualified Data.Aeson.KeyMap
import qualified Data.Char
import qualified Data.Map
import Blockfrost.Types.Cardano.Scripts (ScriptType (..))
data EpochInfo = EpochInfo
{ EpochInfo -> Epoch
_epochInfoEpoch :: Epoch
, EpochInfo -> POSIXTime
_epochInfoStartTime :: POSIXTime
, EpochInfo -> POSIXTime
_epochInfoEndTime :: POSIXTime
, EpochInfo -> POSIXTime
_epochInfoFirstBlockTime :: POSIXTime
, EpochInfo -> POSIXTime
_epochInfoLastBlockTime :: POSIXTime
, EpochInfo -> Integer
_epochInfoBlockCount :: Integer
, EpochInfo -> Integer
_epochInfoTxCount :: Integer
, EpochInfo -> Lovelaces
_epochInfoOutput :: Lovelaces
, EpochInfo -> Lovelaces
_epochInfoFees :: Lovelaces
, EpochInfo -> Maybe Lovelaces
_epochInfoActiveStake :: Maybe Lovelaces
}
deriving stock (Int -> EpochInfo -> ShowS
[EpochInfo] -> ShowS
EpochInfo -> String
(Int -> EpochInfo -> ShowS)
-> (EpochInfo -> String)
-> ([EpochInfo] -> ShowS)
-> Show EpochInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EpochInfo -> ShowS
showsPrec :: Int -> EpochInfo -> ShowS
$cshow :: EpochInfo -> String
show :: EpochInfo -> String
$cshowList :: [EpochInfo] -> ShowS
showList :: [EpochInfo] -> ShowS
Show, EpochInfo -> EpochInfo -> Bool
(EpochInfo -> EpochInfo -> Bool)
-> (EpochInfo -> EpochInfo -> Bool) -> Eq EpochInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EpochInfo -> EpochInfo -> Bool
== :: EpochInfo -> EpochInfo -> Bool
$c/= :: EpochInfo -> EpochInfo -> Bool
/= :: EpochInfo -> EpochInfo -> Bool
Eq, (forall x. EpochInfo -> Rep EpochInfo x)
-> (forall x. Rep EpochInfo x -> EpochInfo) -> Generic EpochInfo
forall x. Rep EpochInfo x -> EpochInfo
forall x. EpochInfo -> Rep EpochInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EpochInfo -> Rep EpochInfo x
from :: forall x. EpochInfo -> Rep EpochInfo x
$cto :: forall x. Rep EpochInfo x -> EpochInfo
to :: forall x. Rep EpochInfo x -> EpochInfo
Generic)
deriving (Maybe EpochInfo
Value -> Parser [EpochInfo]
Value -> Parser EpochInfo
(Value -> Parser EpochInfo)
-> (Value -> Parser [EpochInfo])
-> Maybe EpochInfo
-> FromJSON EpochInfo
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser EpochInfo
parseJSON :: Value -> Parser EpochInfo
$cparseJSONList :: Value -> Parser [EpochInfo]
parseJSONList :: Value -> Parser [EpochInfo]
$comittedField :: Maybe EpochInfo
omittedField :: Maybe EpochInfo
FromJSON, [EpochInfo] -> Value
[EpochInfo] -> Encoding
EpochInfo -> Bool
EpochInfo -> Value
EpochInfo -> Encoding
(EpochInfo -> Value)
-> (EpochInfo -> Encoding)
-> ([EpochInfo] -> Value)
-> ([EpochInfo] -> Encoding)
-> (EpochInfo -> Bool)
-> ToJSON EpochInfo
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: EpochInfo -> Value
toJSON :: EpochInfo -> Value
$ctoEncoding :: EpochInfo -> Encoding
toEncoding :: EpochInfo -> Encoding
$ctoJSONList :: [EpochInfo] -> Value
toJSONList :: [EpochInfo] -> Value
$ctoEncodingList :: [EpochInfo] -> Encoding
toEncodingList :: [EpochInfo] -> Encoding
$comitField :: EpochInfo -> Bool
omitField :: EpochInfo -> Bool
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_epochInfo", CamelToSnake]] EpochInfo
instance ToSample EpochInfo where
toSamples :: Proxy EpochInfo -> [(Text, EpochInfo)]
toSamples = [(Text, EpochInfo)] -> Proxy EpochInfo -> [(Text, EpochInfo)]
forall a. a -> Proxy EpochInfo -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, EpochInfo)] -> Proxy EpochInfo -> [(Text, EpochInfo)])
-> [(Text, EpochInfo)] -> Proxy EpochInfo -> [(Text, EpochInfo)]
forall a b. (a -> b) -> a -> b
$ EpochInfo -> [(Text, EpochInfo)]
forall a. a -> [(Text, a)]
singleSample
EpochInfo
{ _epochInfoEpoch :: Epoch
_epochInfoEpoch = Epoch
225
, _epochInfoStartTime :: POSIXTime
_epochInfoStartTime = POSIXTime
1603403091
, _epochInfoEndTime :: POSIXTime
_epochInfoEndTime = POSIXTime
1603835086
, _epochInfoFirstBlockTime :: POSIXTime
_epochInfoFirstBlockTime = POSIXTime
1603403092
, _epochInfoLastBlockTime :: POSIXTime
_epochInfoLastBlockTime = POSIXTime
1603835084
, _epochInfoBlockCount :: Integer
_epochInfoBlockCount = Integer
21298
, _epochInfoTxCount :: Integer
_epochInfoTxCount = Integer
17856
, _epochInfoOutput :: Lovelaces
_epochInfoOutput = Discrete' "ADA" '(1000000, 1)
Lovelaces
7849943934049314
, _epochInfoFees :: Lovelaces
_epochInfoFees = Discrete' "ADA" '(1000000, 1)
Lovelaces
4203312194
, _epochInfoActiveStake :: Maybe Lovelaces
_epochInfoActiveStake = Discrete' "ADA" '(1000000, 1)
-> Maybe (Discrete' "ADA" '(1000000, 1))
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Discrete' "ADA" '(1000000, 1)
784953934049314
}
data ProtocolParams = ProtocolParams
{ ProtocolParams -> Epoch
_protocolParamsEpoch :: Epoch
, ProtocolParams -> Integer
_protocolParamsMinFeeA :: Integer
, ProtocolParams -> Integer
_protocolParamsMinFeeB :: Integer
, ProtocolParams -> Integer
_protocolParamsMaxBlockSize :: Integer
, ProtocolParams -> Integer
_protocolParamsMaxTxSize :: Integer
, :: Integer
, ProtocolParams -> Lovelaces
_protocolParamsKeyDeposit :: Lovelaces
, ProtocolParams -> Lovelaces
_protocolParamsPoolDeposit :: Lovelaces
, ProtocolParams -> Integer
_protocolParamsEMax :: Integer
, ProtocolParams -> Integer
_protocolParamsNOpt :: Integer
, ProtocolParams -> Rational
_protocolParamsA0 :: Rational
, ProtocolParams -> Rational
_protocolParamsRho :: Rational
, ProtocolParams -> Rational
_protocolParamsTau :: Rational
, ProtocolParams -> Rational
_protocolParamsDecentralisationParam :: Rational
, :: Maybe Text
, ProtocolParams -> Integer
_protocolParamsProtocolMajorVer :: Integer
, ProtocolParams -> Integer
_protocolParamsProtocolMinorVer :: Integer
, ProtocolParams -> Lovelaces
_protocolParamsMinUtxo :: Lovelaces
, ProtocolParams -> Lovelaces
_protocolParamsMinPoolCost :: Lovelaces
, ProtocolParams -> Text
_protocolParamsNonce :: Text
, ProtocolParams -> CostModels
_protocolParamsCostModels :: CostModels
, ProtocolParams -> Rational
_protocolParamsPriceMem :: Rational
, ProtocolParams -> Rational
_protocolParamsPriceStep :: Rational
, ProtocolParams -> Quantity
_protocolParamsMaxTxExMem :: Quantity
, ProtocolParams -> Quantity
_protocolParamsMaxTxExSteps :: Quantity
, ProtocolParams -> Quantity
_protocolParamsMaxBlockExMem :: Quantity
, ProtocolParams -> Quantity
_protocolParamsMaxBlockExSteps :: Quantity
, ProtocolParams -> Quantity
_protocolParamsMaxValSize :: Quantity
, ProtocolParams -> Integer
_protocolParamsCollateralPercent :: Integer
, ProtocolParams -> Integer
_protocolParamsMaxCollateralInputs :: Integer
, ProtocolParams -> Lovelaces
_protocolParamsCoinsPerUtxoSize :: Lovelaces
, ProtocolParams -> Lovelaces
_protocolParamsCoinsPerUtxoWord :: Lovelaces
}
deriving stock (Int -> ProtocolParams -> ShowS
[ProtocolParams] -> ShowS
ProtocolParams -> String
(Int -> ProtocolParams -> ShowS)
-> (ProtocolParams -> String)
-> ([ProtocolParams] -> ShowS)
-> Show ProtocolParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProtocolParams -> ShowS
showsPrec :: Int -> ProtocolParams -> ShowS
$cshow :: ProtocolParams -> String
show :: ProtocolParams -> String
$cshowList :: [ProtocolParams] -> ShowS
showList :: [ProtocolParams] -> ShowS
Show, ProtocolParams -> ProtocolParams -> Bool
(ProtocolParams -> ProtocolParams -> Bool)
-> (ProtocolParams -> ProtocolParams -> Bool) -> Eq ProtocolParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProtocolParams -> ProtocolParams -> Bool
== :: ProtocolParams -> ProtocolParams -> Bool
$c/= :: ProtocolParams -> ProtocolParams -> Bool
/= :: ProtocolParams -> ProtocolParams -> Bool
Eq, (forall x. ProtocolParams -> Rep ProtocolParams x)
-> (forall x. Rep ProtocolParams x -> ProtocolParams)
-> Generic ProtocolParams
forall x. Rep ProtocolParams x -> ProtocolParams
forall x. ProtocolParams -> Rep ProtocolParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProtocolParams -> Rep ProtocolParams x
from :: forall x. ProtocolParams -> Rep ProtocolParams x
$cto :: forall x. Rep ProtocolParams x -> ProtocolParams
to :: forall x. Rep ProtocolParams x -> ProtocolParams
Generic)
deriving (Maybe ProtocolParams
Value -> Parser [ProtocolParams]
Value -> Parser ProtocolParams
(Value -> Parser ProtocolParams)
-> (Value -> Parser [ProtocolParams])
-> Maybe ProtocolParams
-> FromJSON ProtocolParams
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ProtocolParams
parseJSON :: Value -> Parser ProtocolParams
$cparseJSONList :: Value -> Parser [ProtocolParams]
parseJSONList :: Value -> Parser [ProtocolParams]
$comittedField :: Maybe ProtocolParams
omittedField :: Maybe ProtocolParams
FromJSON, [ProtocolParams] -> Value
[ProtocolParams] -> Encoding
ProtocolParams -> Bool
ProtocolParams -> Value
ProtocolParams -> Encoding
(ProtocolParams -> Value)
-> (ProtocolParams -> Encoding)
-> ([ProtocolParams] -> Value)
-> ([ProtocolParams] -> Encoding)
-> (ProtocolParams -> Bool)
-> ToJSON ProtocolParams
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ProtocolParams -> Value
toJSON :: ProtocolParams -> Value
$ctoEncoding :: ProtocolParams -> Encoding
toEncoding :: ProtocolParams -> Encoding
$ctoJSONList :: [ProtocolParams] -> Value
toJSONList :: [ProtocolParams] -> Value
$ctoEncodingList :: [ProtocolParams] -> Encoding
toEncodingList :: [ProtocolParams] -> Encoding
$comitField :: ProtocolParams -> Bool
omitField :: ProtocolParams -> Bool
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_protocolParams", CamelToSnake]] ProtocolParams
instance ToSample ProtocolParams where
toSamples :: Proxy ProtocolParams -> [(Text, ProtocolParams)]
toSamples = [(Text, ProtocolParams)]
-> Proxy ProtocolParams -> [(Text, ProtocolParams)]
forall a. a -> Proxy ProtocolParams -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, ProtocolParams)]
-> Proxy ProtocolParams -> [(Text, ProtocolParams)])
-> [(Text, ProtocolParams)]
-> Proxy ProtocolParams
-> [(Text, ProtocolParams)]
forall a b. (a -> b) -> a -> b
$ ProtocolParams -> [(Text, ProtocolParams)]
forall a. a -> [(Text, a)]
singleSample
ProtocolParams
{ _protocolParamsEpoch :: Epoch
_protocolParamsEpoch = Epoch
225
, _protocolParamsMinFeeA :: Integer
_protocolParamsMinFeeA = Integer
44
, _protocolParamsMinFeeB :: Integer
_protocolParamsMinFeeB = Integer
155381
, _protocolParamsMaxBlockSize :: Integer
_protocolParamsMaxBlockSize = Integer
65536
, _protocolParamsMaxTxSize :: Integer
_protocolParamsMaxTxSize = Integer
16384
, _protocolParamsMaxBlockHeaderSize :: Integer
_protocolParamsMaxBlockHeaderSize = Integer
1100
, _protocolParamsKeyDeposit :: Lovelaces
_protocolParamsKeyDeposit = Discrete' "ADA" '(1000000, 1)
Lovelaces
2000000
, _protocolParamsPoolDeposit :: Lovelaces
_protocolParamsPoolDeposit = Discrete' "ADA" '(1000000, 1)
Lovelaces
500000000
, _protocolParamsEMax :: Integer
_protocolParamsEMax = Integer
18
, _protocolParamsNOpt :: Integer
_protocolParamsNOpt = Integer
150
, _protocolParamsA0 :: Rational
_protocolParamsA0 = Rational
0.3
, _protocolParamsRho :: Rational
_protocolParamsRho = Rational
0.003
, _protocolParamsTau :: Rational
_protocolParamsTau = Rational
0.2
, _protocolParamsDecentralisationParam :: Rational
_protocolParamsDecentralisationParam = Rational
0.5
, _protocolParamsExtraEntropy :: Maybe Text
_protocolParamsExtraEntropy = Maybe Text
forall a. Maybe a
Nothing
, _protocolParamsProtocolMajorVer :: Integer
_protocolParamsProtocolMajorVer = Integer
2
, _protocolParamsProtocolMinorVer :: Integer
_protocolParamsProtocolMinorVer = Integer
0
, _protocolParamsMinUtxo :: Lovelaces
_protocolParamsMinUtxo = Discrete' "ADA" '(1000000, 1)
Lovelaces
1000000
, _protocolParamsMinPoolCost :: Lovelaces
_protocolParamsMinPoolCost = Discrete' "ADA" '(1000000, 1)
Lovelaces
340000000
, _protocolParamsNonce :: Text
_protocolParamsNonce = Text
"1a3be38bcbb7911969283716ad7aa550250226b76a61fc51cc9a9a35d9276d81"
, _protocolParamsCostModels :: CostModels
_protocolParamsCostModels = CostModels
costModelsSample
, _protocolParamsPriceMem :: Rational
_protocolParamsPriceMem = Rational
0.0577
, _protocolParamsPriceStep :: Rational
_protocolParamsPriceStep = Rational
0.0000721
, _protocolParamsMaxTxExMem :: Quantity
_protocolParamsMaxTxExMem = Quantity
10000000
, _protocolParamsMaxTxExSteps :: Quantity
_protocolParamsMaxTxExSteps = Quantity
10000000000
, _protocolParamsMaxBlockExMem :: Quantity
_protocolParamsMaxBlockExMem = Quantity
50000000
, _protocolParamsMaxBlockExSteps :: Quantity
_protocolParamsMaxBlockExSteps = Quantity
40000000000
, _protocolParamsMaxValSize :: Quantity
_protocolParamsMaxValSize = Quantity
5000
, _protocolParamsCollateralPercent :: Integer
_protocolParamsCollateralPercent = Integer
150
, _protocolParamsMaxCollateralInputs :: Integer
_protocolParamsMaxCollateralInputs = Integer
3
, _protocolParamsCoinsPerUtxoSize :: Lovelaces
_protocolParamsCoinsPerUtxoSize = Discrete' "ADA" '(1000000, 1)
Lovelaces
34482
, _protocolParamsCoinsPerUtxoWord :: Lovelaces
_protocolParamsCoinsPerUtxoWord = Discrete' "ADA" '(1000000, 1)
Lovelaces
34482
}
newtype CostModels = CostModels { CostModels -> Map ScriptType (Map Text Integer)
unCostModels :: Map ScriptType (Map Text Integer) }
deriving (CostModels -> CostModels -> Bool
(CostModels -> CostModels -> Bool)
-> (CostModels -> CostModels -> Bool) -> Eq CostModels
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CostModels -> CostModels -> Bool
== :: CostModels -> CostModels -> Bool
$c/= :: CostModels -> CostModels -> Bool
/= :: CostModels -> CostModels -> Bool
Eq, Int -> CostModels -> ShowS
[CostModels] -> ShowS
CostModels -> String
(Int -> CostModels -> ShowS)
-> (CostModels -> String)
-> ([CostModels] -> ShowS)
-> Show CostModels
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CostModels -> ShowS
showsPrec :: Int -> CostModels -> ShowS
$cshow :: CostModels -> String
show :: CostModels -> String
$cshowList :: [CostModels] -> ShowS
showList :: [CostModels] -> ShowS
Show, (forall x. CostModels -> Rep CostModels x)
-> (forall x. Rep CostModels x -> CostModels) -> Generic CostModels
forall x. Rep CostModels x -> CostModels
forall x. CostModels -> Rep CostModels x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CostModels -> Rep CostModels x
from :: forall x. CostModels -> Rep CostModels x
$cto :: forall x. Rep CostModels x -> CostModels
to :: forall x. Rep CostModels x -> CostModels
Generic)
instance ToJSON CostModels where
toJSON :: CostModels -> Value
toJSON =
[Pair] -> Value
object
([Pair] -> Value) -> (CostModels -> [Pair]) -> CostModels -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ScriptType, Map Text Integer) -> Pair)
-> [(ScriptType, Map Text Integer)] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map (\(ScriptType
lang, Map Text Integer
params) ->
( String -> Key
Data.Aeson.Key.fromString (String -> Key) -> String -> Key
forall a b. (a -> b) -> a -> b
$ ScriptType -> String
forall a. Show a => a -> String
show ScriptType
lang
, [Pair] -> Value
object
([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ ((Text, Integer) -> Pair) -> [(Text, Integer)] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
key, Integer
param) ->
( Text -> Key
Data.Aeson.Key.fromText Text
key
, Integer -> Value
forall a. ToJSON a => a -> Value
toJSON Integer
param)
)
([(Text, Integer)] -> [Pair]) -> [(Text, Integer)] -> [Pair]
forall a b. (a -> b) -> a -> b
$ Map Text Integer -> [(Text, Integer)]
forall k a. Map k a -> [(k, a)]
Data.Map.toList Map Text Integer
params
))
([(ScriptType, Map Text Integer)] -> [Pair])
-> (CostModels -> [(ScriptType, Map Text Integer)])
-> CostModels
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map ScriptType (Map Text Integer)
-> [(ScriptType, Map Text Integer)]
forall k a. Map k a -> [(k, a)]
Data.Map.toList
(Map ScriptType (Map Text Integer)
-> [(ScriptType, Map Text Integer)])
-> (CostModels -> Map ScriptType (Map Text Integer))
-> CostModels
-> [(ScriptType, Map Text Integer)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CostModels -> Map ScriptType (Map Text Integer)
unCostModels
instance FromJSON CostModels where
parseJSON :: Value -> Parser CostModels
parseJSON = String
-> (Object -> Parser CostModels) -> Value -> Parser CostModels
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CostModel" ((Object -> Parser CostModels) -> Value -> Parser CostModels)
-> (Object -> Parser CostModels) -> Value -> Parser CostModels
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
let parseParams :: Value -> Parser [(Text, Integer)]
parseParams = String
-> (Object -> Parser [(Text, Integer)])
-> Value
-> Parser [(Text, Integer)]
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CostModelParams" ((Object -> Parser [(Text, Integer)])
-> Value -> Parser [(Text, Integer)])
-> (Object -> Parser [(Text, Integer)])
-> Value
-> Parser [(Text, Integer)]
forall a b. (a -> b) -> a -> b
$ \Object
po -> do
(Pair -> Parser (Text, Integer))
-> [Pair] -> Parser [(Text, Integer)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Value -> Parser (Text, Integer)
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser (Text, Integer))
-> (Pair -> Value) -> Pair -> Parser (Text, Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pair -> Value
forall a. ToJSON a => a -> Value
toJSON) ([Pair] -> Parser [(Text, Integer)])
-> [Pair] -> Parser [(Text, Integer)]
forall a b. (a -> b) -> a -> b
$ Object -> [Pair]
forall v. KeyMap v -> [(Key, v)]
Data.Aeson.KeyMap.toList Object
po
[(ScriptType, Map Text Integer)]
langs <- (Pair -> Parser (ScriptType, Map Text Integer))
-> [Pair] -> Parser [(ScriptType, Map Text Integer)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM
(\(Key
kLang, Value
vParams) -> do
ScriptType
l <- Value -> Parser ScriptType
forall a. FromJSON a => Value -> Parser a
parseJSON
(Value -> Parser ScriptType) -> Value -> Parser ScriptType
forall a b. (a -> b) -> a -> b
$ String -> Value
forall a. ToJSON a => a -> Value
toJSON
(String -> Value) -> String -> Value
forall a b. (a -> b) -> a -> b
$ (\String
lang -> case String
lang of
[] -> ShowS
forall a. String -> [a]
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Absurd empty language in CostModels"
(Char
x:String
xs) -> Char -> Char
Data.Char.toLower Char
xChar -> ShowS
forall a. a -> [a] -> [a]
:String
xs
)
ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Key -> String
Data.Aeson.Key.toString Key
kLang
[(Text, Integer)]
ps <- Value -> Parser [(Text, Integer)]
parseParams Value
vParams
(ScriptType, Map Text Integer)
-> Parser (ScriptType, Map Text Integer)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ScriptType
l, [(Text, Integer)] -> Map Text Integer
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList [(Text, Integer)]
ps)
)
([Pair] -> Parser [(ScriptType, Map Text Integer)])
-> [Pair] -> Parser [(ScriptType, Map Text Integer)]
forall a b. (a -> b) -> a -> b
$ Object -> [Pair]
forall v. KeyMap v -> [(Key, v)]
Data.Aeson.KeyMap.toList Object
o
CostModels -> Parser CostModels
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CostModels -> Parser CostModels)
-> CostModels -> Parser CostModels
forall a b. (a -> b) -> a -> b
$ Map ScriptType (Map Text Integer) -> CostModels
CostModels (Map ScriptType (Map Text Integer) -> CostModels)
-> Map ScriptType (Map Text Integer) -> CostModels
forall a b. (a -> b) -> a -> b
$ [(ScriptType, Map Text Integer)]
-> Map ScriptType (Map Text Integer)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList [(ScriptType, Map Text Integer)]
langs
costModelsSample :: CostModels
costModelsSample :: CostModels
costModelsSample = Map ScriptType (Map Text Integer) -> CostModels
CostModels
(Map ScriptType (Map Text Integer) -> CostModels)
-> Map ScriptType (Map Text Integer) -> CostModels
forall a b. (a -> b) -> a -> b
$ [(ScriptType, Map Text Integer)]
-> Map ScriptType (Map Text Integer)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[ ( ScriptType
PlutusV1
, [(Text, Integer)] -> Map Text Integer
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[ (Text
"addInteger-cpu-arguments-intercept", Integer
197209)
, (Text
"addInteger-cpu-arguments-slope", Integer
0)
]
)
, (ScriptType
PlutusV2
, [(Text, Integer)] -> Map Text Integer
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[ (Text
"addInteger-cpu-arguments-intercept", Integer
197209)
, (Text
"addInteger-cpu-arguments-slope", Integer
0)
]
)
]
instance ToSample CostModels where
toSamples :: Proxy CostModels -> [(Text, CostModels)]
toSamples = [(Text, CostModels)] -> Proxy CostModels -> [(Text, CostModels)]
forall a. a -> Proxy CostModels -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, CostModels)] -> Proxy CostModels -> [(Text, CostModels)])
-> [(Text, CostModels)] -> Proxy CostModels -> [(Text, CostModels)]
forall a b. (a -> b) -> a -> b
$ CostModels -> [(Text, CostModels)]
forall a. a -> [(Text, a)]
singleSample CostModels
costModelsSample
data StakeDistribution = StakeDistribution
{ StakeDistribution -> Address
_stakeDistributionStakeAddress :: Address
, StakeDistribution -> PoolId
_stakeDistributionPoolId :: PoolId
, StakeDistribution -> Lovelaces
_stakeDistributionAmount :: Lovelaces
}
deriving stock (Int -> StakeDistribution -> ShowS
[StakeDistribution] -> ShowS
StakeDistribution -> String
(Int -> StakeDistribution -> ShowS)
-> (StakeDistribution -> String)
-> ([StakeDistribution] -> ShowS)
-> Show StakeDistribution
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StakeDistribution -> ShowS
showsPrec :: Int -> StakeDistribution -> ShowS
$cshow :: StakeDistribution -> String
show :: StakeDistribution -> String
$cshowList :: [StakeDistribution] -> ShowS
showList :: [StakeDistribution] -> ShowS
Show, StakeDistribution -> StakeDistribution -> Bool
(StakeDistribution -> StakeDistribution -> Bool)
-> (StakeDistribution -> StakeDistribution -> Bool)
-> Eq StakeDistribution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StakeDistribution -> StakeDistribution -> Bool
== :: StakeDistribution -> StakeDistribution -> Bool
$c/= :: StakeDistribution -> StakeDistribution -> Bool
/= :: StakeDistribution -> StakeDistribution -> Bool
Eq, (forall x. StakeDistribution -> Rep StakeDistribution x)
-> (forall x. Rep StakeDistribution x -> StakeDistribution)
-> Generic StakeDistribution
forall x. Rep StakeDistribution x -> StakeDistribution
forall x. StakeDistribution -> Rep StakeDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StakeDistribution -> Rep StakeDistribution x
from :: forall x. StakeDistribution -> Rep StakeDistribution x
$cto :: forall x. Rep StakeDistribution x -> StakeDistribution
to :: forall x. Rep StakeDistribution x -> StakeDistribution
Generic)
deriving (Maybe StakeDistribution
Value -> Parser [StakeDistribution]
Value -> Parser StakeDistribution
(Value -> Parser StakeDistribution)
-> (Value -> Parser [StakeDistribution])
-> Maybe StakeDistribution
-> FromJSON StakeDistribution
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser StakeDistribution
parseJSON :: Value -> Parser StakeDistribution
$cparseJSONList :: Value -> Parser [StakeDistribution]
parseJSONList :: Value -> Parser [StakeDistribution]
$comittedField :: Maybe StakeDistribution
omittedField :: Maybe StakeDistribution
FromJSON, [StakeDistribution] -> Value
[StakeDistribution] -> Encoding
StakeDistribution -> Bool
StakeDistribution -> Value
StakeDistribution -> Encoding
(StakeDistribution -> Value)
-> (StakeDistribution -> Encoding)
-> ([StakeDistribution] -> Value)
-> ([StakeDistribution] -> Encoding)
-> (StakeDistribution -> Bool)
-> ToJSON StakeDistribution
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: StakeDistribution -> Value
toJSON :: StakeDistribution -> Value
$ctoEncoding :: StakeDistribution -> Encoding
toEncoding :: StakeDistribution -> Encoding
$ctoJSONList :: [StakeDistribution] -> Value
toJSONList :: [StakeDistribution] -> Value
$ctoEncodingList :: [StakeDistribution] -> Encoding
toEncodingList :: [StakeDistribution] -> Encoding
$comitField :: StakeDistribution -> Bool
omitField :: StakeDistribution -> Bool
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_stakeDistribution", CamelToSnake]] StakeDistribution
instance ToSample StakeDistribution where
toSamples :: Proxy StakeDistribution -> [(Text, StakeDistribution)]
toSamples = [(Text, StakeDistribution)]
-> Proxy StakeDistribution -> [(Text, StakeDistribution)]
forall a. a -> Proxy StakeDistribution -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, StakeDistribution)]
-> Proxy StakeDistribution -> [(Text, StakeDistribution)])
-> [(Text, StakeDistribution)]
-> Proxy StakeDistribution
-> [(Text, StakeDistribution)]
forall a b. (a -> b) -> a -> b
$ StakeDistribution -> [(Text, StakeDistribution)]
forall a. a -> [(Text, a)]
singleSample
StakeDistribution
{ _stakeDistributionStakeAddress :: Address
_stakeDistributionStakeAddress = Address
"stake1u9l5q5jwgelgagzyt6nuaasefgmn8pd25c8e9qpeprq0tdcp0e3uk"
, _stakeDistributionPoolId :: PoolId
_stakeDistributionPoolId = PoolId
"pool1pu5jlj4q9w9jlxeu370a3c9myx47md5j5m2str0naunn2q3lkdy"
, _stakeDistributionAmount :: Lovelaces
_stakeDistributionAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
4440295078
}
data PoolStakeDistribution = PoolStakeDistribution
{ PoolStakeDistribution -> Address
_poolStakeDistributionStakeAddress :: Address
, PoolStakeDistribution -> Lovelaces
_poolStakeDistributionAmount :: Lovelaces
}
deriving stock (Int -> PoolStakeDistribution -> ShowS
[PoolStakeDistribution] -> ShowS
PoolStakeDistribution -> String
(Int -> PoolStakeDistribution -> ShowS)
-> (PoolStakeDistribution -> String)
-> ([PoolStakeDistribution] -> ShowS)
-> Show PoolStakeDistribution
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PoolStakeDistribution -> ShowS
showsPrec :: Int -> PoolStakeDistribution -> ShowS
$cshow :: PoolStakeDistribution -> String
show :: PoolStakeDistribution -> String
$cshowList :: [PoolStakeDistribution] -> ShowS
showList :: [PoolStakeDistribution] -> ShowS
Show, PoolStakeDistribution -> PoolStakeDistribution -> Bool
(PoolStakeDistribution -> PoolStakeDistribution -> Bool)
-> (PoolStakeDistribution -> PoolStakeDistribution -> Bool)
-> Eq PoolStakeDistribution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PoolStakeDistribution -> PoolStakeDistribution -> Bool
== :: PoolStakeDistribution -> PoolStakeDistribution -> Bool
$c/= :: PoolStakeDistribution -> PoolStakeDistribution -> Bool
/= :: PoolStakeDistribution -> PoolStakeDistribution -> Bool
Eq, (forall x. PoolStakeDistribution -> Rep PoolStakeDistribution x)
-> (forall x. Rep PoolStakeDistribution x -> PoolStakeDistribution)
-> Generic PoolStakeDistribution
forall x. Rep PoolStakeDistribution x -> PoolStakeDistribution
forall x. PoolStakeDistribution -> Rep PoolStakeDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PoolStakeDistribution -> Rep PoolStakeDistribution x
from :: forall x. PoolStakeDistribution -> Rep PoolStakeDistribution x
$cto :: forall x. Rep PoolStakeDistribution x -> PoolStakeDistribution
to :: forall x. Rep PoolStakeDistribution x -> PoolStakeDistribution
Generic)
deriving (Maybe PoolStakeDistribution
Value -> Parser [PoolStakeDistribution]
Value -> Parser PoolStakeDistribution
(Value -> Parser PoolStakeDistribution)
-> (Value -> Parser [PoolStakeDistribution])
-> Maybe PoolStakeDistribution
-> FromJSON PoolStakeDistribution
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PoolStakeDistribution
parseJSON :: Value -> Parser PoolStakeDistribution
$cparseJSONList :: Value -> Parser [PoolStakeDistribution]
parseJSONList :: Value -> Parser [PoolStakeDistribution]
$comittedField :: Maybe PoolStakeDistribution
omittedField :: Maybe PoolStakeDistribution
FromJSON, [PoolStakeDistribution] -> Value
[PoolStakeDistribution] -> Encoding
PoolStakeDistribution -> Bool
PoolStakeDistribution -> Value
PoolStakeDistribution -> Encoding
(PoolStakeDistribution -> Value)
-> (PoolStakeDistribution -> Encoding)
-> ([PoolStakeDistribution] -> Value)
-> ([PoolStakeDistribution] -> Encoding)
-> (PoolStakeDistribution -> Bool)
-> ToJSON PoolStakeDistribution
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: PoolStakeDistribution -> Value
toJSON :: PoolStakeDistribution -> Value
$ctoEncoding :: PoolStakeDistribution -> Encoding
toEncoding :: PoolStakeDistribution -> Encoding
$ctoJSONList :: [PoolStakeDistribution] -> Value
toJSONList :: [PoolStakeDistribution] -> Value
$ctoEncodingList :: [PoolStakeDistribution] -> Encoding
toEncodingList :: [PoolStakeDistribution] -> Encoding
$comitField :: PoolStakeDistribution -> Bool
omitField :: PoolStakeDistribution -> Bool
ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_poolStakeDistribution", CamelToSnake]] PoolStakeDistribution
instance ToSample PoolStakeDistribution where
toSamples :: Proxy PoolStakeDistribution -> [(Text, PoolStakeDistribution)]
toSamples = [(Text, PoolStakeDistribution)]
-> Proxy PoolStakeDistribution -> [(Text, PoolStakeDistribution)]
forall a. a -> Proxy PoolStakeDistribution -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, PoolStakeDistribution)]
-> Proxy PoolStakeDistribution -> [(Text, PoolStakeDistribution)])
-> [(Text, PoolStakeDistribution)]
-> Proxy PoolStakeDistribution
-> [(Text, PoolStakeDistribution)]
forall a b. (a -> b) -> a -> b
$ PoolStakeDistribution -> [(Text, PoolStakeDistribution)]
forall a. a -> [(Text, a)]
singleSample
PoolStakeDistribution
{ _poolStakeDistributionStakeAddress :: Address
_poolStakeDistributionStakeAddress = Address
"stake1u9l5q5jwgelgagzyt6nuaasefgmn8pd25c8e9qpeprq0tdcp0e3uk"
, _poolStakeDistributionAmount :: Lovelaces
_poolStakeDistributionAmount = Discrete' "ADA" '(1000000, 1)
Lovelaces
4440295078
}