{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Playground.Types where
import Control.Lens (makeLenses)
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson qualified as JSON
import Data.Functor.Foldable (Fix)
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.OpenApi.Schema qualified as OpenApi
import Data.Text (Text)
import GHC.Generics (Generic)
import Language.Haskell.Interpreter (CompilationError, SourceCode)
import Language.Haskell.Interpreter qualified as HI
import Ledger (PaymentPubKeyHash, fromSymbol)
import Ledger.Ada qualified as Ada
import Ledger.CardanoWallet qualified as CW
import Ledger.Scripts (ValidatorHash)
import Ledger.Slot (Slot)
import Ledger.Value (TokenName)
import Ledger.Value qualified as V
import Schema (FormArgumentF, FormSchema, ToArgument, ToSchema)
import Wallet.Emulator.Types (EmulatorEvent, WalletNumber)
import Wallet.Rollup.Types (AnnotatedTx)
import Wallet.Types (EndpointDescription)
data KnownCurrency =
KnownCurrency
{ KnownCurrency -> ValidatorHash
hash :: ValidatorHash
, KnownCurrency -> String
friendlyName :: String
, KnownCurrency -> NonEmpty TokenName
knownTokens :: NonEmpty TokenName
}
deriving (KnownCurrency -> KnownCurrency -> Bool
(KnownCurrency -> KnownCurrency -> Bool)
-> (KnownCurrency -> KnownCurrency -> Bool) -> Eq KnownCurrency
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KnownCurrency -> KnownCurrency -> Bool
$c/= :: KnownCurrency -> KnownCurrency -> Bool
== :: KnownCurrency -> KnownCurrency -> Bool
$c== :: KnownCurrency -> KnownCurrency -> Bool
Eq, Int -> KnownCurrency -> ShowS
[KnownCurrency] -> ShowS
KnownCurrency -> String
(Int -> KnownCurrency -> ShowS)
-> (KnownCurrency -> String)
-> ([KnownCurrency] -> ShowS)
-> Show KnownCurrency
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KnownCurrency] -> ShowS
$cshowList :: [KnownCurrency] -> ShowS
show :: KnownCurrency -> String
$cshow :: KnownCurrency -> String
showsPrec :: Int -> KnownCurrency -> ShowS
$cshowsPrec :: Int -> KnownCurrency -> ShowS
Show, (forall x. KnownCurrency -> Rep KnownCurrency x)
-> (forall x. Rep KnownCurrency x -> KnownCurrency)
-> Generic KnownCurrency
forall x. Rep KnownCurrency x -> KnownCurrency
forall x. KnownCurrency -> Rep KnownCurrency x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KnownCurrency x -> KnownCurrency
$cfrom :: forall x. KnownCurrency -> Rep KnownCurrency x
Generic, [KnownCurrency] -> Encoding
[KnownCurrency] -> Value
KnownCurrency -> Encoding
KnownCurrency -> Value
(KnownCurrency -> Value)
-> (KnownCurrency -> Encoding)
-> ([KnownCurrency] -> Value)
-> ([KnownCurrency] -> Encoding)
-> ToJSON KnownCurrency
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [KnownCurrency] -> Encoding
$ctoEncodingList :: [KnownCurrency] -> Encoding
toJSONList :: [KnownCurrency] -> Value
$ctoJSONList :: [KnownCurrency] -> Value
toEncoding :: KnownCurrency -> Encoding
$ctoEncoding :: KnownCurrency -> Encoding
toJSON :: KnownCurrency -> Value
$ctoJSON :: KnownCurrency -> Value
ToJSON, Value -> Parser [KnownCurrency]
Value -> Parser KnownCurrency
(Value -> Parser KnownCurrency)
-> (Value -> Parser [KnownCurrency]) -> FromJSON KnownCurrency
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [KnownCurrency]
$cparseJSONList :: Value -> Parser [KnownCurrency]
parseJSON :: Value -> Parser KnownCurrency
$cparseJSON :: Value -> Parser KnownCurrency
FromJSON)
adaCurrency :: KnownCurrency
adaCurrency :: KnownCurrency
adaCurrency =
KnownCurrency :: ValidatorHash -> String -> NonEmpty TokenName -> KnownCurrency
KnownCurrency
{ hash :: ValidatorHash
hash = CurrencySymbol -> ValidatorHash
fromSymbol CurrencySymbol
Ada.adaSymbol
, friendlyName :: String
friendlyName = String
"Ada"
, knownTokens :: NonEmpty TokenName
knownTokens = TokenName
Ada.adaToken TokenName -> [TokenName] -> NonEmpty TokenName
forall a. a -> [a] -> NonEmpty a
:| []
}
data PayToWalletParams =
PayToWalletParams
{ PayToWalletParams -> WalletNumber
payTo :: WalletNumber
, PayToWalletParams -> Value
value :: V.Value
}
deriving (PayToWalletParams -> PayToWalletParams -> Bool
(PayToWalletParams -> PayToWalletParams -> Bool)
-> (PayToWalletParams -> PayToWalletParams -> Bool)
-> Eq PayToWalletParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PayToWalletParams -> PayToWalletParams -> Bool
$c/= :: PayToWalletParams -> PayToWalletParams -> Bool
== :: PayToWalletParams -> PayToWalletParams -> Bool
$c== :: PayToWalletParams -> PayToWalletParams -> Bool
Eq, Int -> PayToWalletParams -> ShowS
[PayToWalletParams] -> ShowS
PayToWalletParams -> String
(Int -> PayToWalletParams -> ShowS)
-> (PayToWalletParams -> String)
-> ([PayToWalletParams] -> ShowS)
-> Show PayToWalletParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PayToWalletParams] -> ShowS
$cshowList :: [PayToWalletParams] -> ShowS
show :: PayToWalletParams -> String
$cshow :: PayToWalletParams -> String
showsPrec :: Int -> PayToWalletParams -> ShowS
$cshowsPrec :: Int -> PayToWalletParams -> ShowS
Show, (forall x. PayToWalletParams -> Rep PayToWalletParams x)
-> (forall x. Rep PayToWalletParams x -> PayToWalletParams)
-> Generic PayToWalletParams
forall x. Rep PayToWalletParams x -> PayToWalletParams
forall x. PayToWalletParams -> Rep PayToWalletParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PayToWalletParams x -> PayToWalletParams
$cfrom :: forall x. PayToWalletParams -> Rep PayToWalletParams x
Generic)
deriving anyclass (Value -> Parser [PayToWalletParams]
Value -> Parser PayToWalletParams
(Value -> Parser PayToWalletParams)
-> (Value -> Parser [PayToWalletParams])
-> FromJSON PayToWalletParams
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PayToWalletParams]
$cparseJSONList :: Value -> Parser [PayToWalletParams]
parseJSON :: Value -> Parser PayToWalletParams
$cparseJSON :: Value -> Parser PayToWalletParams
FromJSON, [PayToWalletParams] -> Encoding
[PayToWalletParams] -> Value
PayToWalletParams -> Encoding
PayToWalletParams -> Value
(PayToWalletParams -> Value)
-> (PayToWalletParams -> Encoding)
-> ([PayToWalletParams] -> Value)
-> ([PayToWalletParams] -> Encoding)
-> ToJSON PayToWalletParams
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PayToWalletParams] -> Encoding
$ctoEncodingList :: [PayToWalletParams] -> Encoding
toJSONList :: [PayToWalletParams] -> Value
$ctoJSONList :: [PayToWalletParams] -> Value
toEncoding :: PayToWalletParams -> Encoding
$ctoEncoding :: PayToWalletParams -> Encoding
toJSON :: PayToWalletParams -> Value
$ctoJSON :: PayToWalletParams -> Value
ToJSON, FormSchema
FormSchema -> ToSchema PayToWalletParams
forall a. FormSchema -> ToSchema a
toSchema :: FormSchema
$ctoSchema :: FormSchema
ToSchema, ToSchema PayToWalletParams
ToSchema PayToWalletParams
-> (PayToWalletParams -> Fix FormArgumentF)
-> ToArgument PayToWalletParams
PayToWalletParams -> Fix FormArgumentF
forall a. ToSchema a -> (a -> Fix FormArgumentF) -> ToArgument a
toArgument :: PayToWalletParams -> Fix FormArgumentF
$ctoArgument :: PayToWalletParams -> Fix FormArgumentF
$cp1ToArgument :: ToSchema PayToWalletParams
ToArgument)
data SimulatorWallet =
SimulatorWallet
{ SimulatorWallet -> WalletNumber
simulatorWalletWallet :: WalletNumber
, SimulatorWallet -> Value
simulatorWalletBalance :: V.Value
}
deriving (Int -> SimulatorWallet -> ShowS
[SimulatorWallet] -> ShowS
SimulatorWallet -> String
(Int -> SimulatorWallet -> ShowS)
-> (SimulatorWallet -> String)
-> ([SimulatorWallet] -> ShowS)
-> Show SimulatorWallet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimulatorWallet] -> ShowS
$cshowList :: [SimulatorWallet] -> ShowS
show :: SimulatorWallet -> String
$cshow :: SimulatorWallet -> String
showsPrec :: Int -> SimulatorWallet -> ShowS
$cshowsPrec :: Int -> SimulatorWallet -> ShowS
Show, (forall x. SimulatorWallet -> Rep SimulatorWallet x)
-> (forall x. Rep SimulatorWallet x -> SimulatorWallet)
-> Generic SimulatorWallet
forall x. Rep SimulatorWallet x -> SimulatorWallet
forall x. SimulatorWallet -> Rep SimulatorWallet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SimulatorWallet x -> SimulatorWallet
$cfrom :: forall x. SimulatorWallet -> Rep SimulatorWallet x
Generic, SimulatorWallet -> SimulatorWallet -> Bool
(SimulatorWallet -> SimulatorWallet -> Bool)
-> (SimulatorWallet -> SimulatorWallet -> Bool)
-> Eq SimulatorWallet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimulatorWallet -> SimulatorWallet -> Bool
$c/= :: SimulatorWallet -> SimulatorWallet -> Bool
== :: SimulatorWallet -> SimulatorWallet -> Bool
$c== :: SimulatorWallet -> SimulatorWallet -> Bool
Eq)
deriving anyclass ([SimulatorWallet] -> Encoding
[SimulatorWallet] -> Value
SimulatorWallet -> Encoding
SimulatorWallet -> Value
(SimulatorWallet -> Value)
-> (SimulatorWallet -> Encoding)
-> ([SimulatorWallet] -> Value)
-> ([SimulatorWallet] -> Encoding)
-> ToJSON SimulatorWallet
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SimulatorWallet] -> Encoding
$ctoEncodingList :: [SimulatorWallet] -> Encoding
toJSONList :: [SimulatorWallet] -> Value
$ctoJSONList :: [SimulatorWallet] -> Value
toEncoding :: SimulatorWallet -> Encoding
$ctoEncoding :: SimulatorWallet -> Encoding
toJSON :: SimulatorWallet -> Value
$ctoJSON :: SimulatorWallet -> Value
ToJSON, Value -> Parser [SimulatorWallet]
Value -> Parser SimulatorWallet
(Value -> Parser SimulatorWallet)
-> (Value -> Parser [SimulatorWallet]) -> FromJSON SimulatorWallet
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SimulatorWallet]
$cparseJSONList :: Value -> Parser [SimulatorWallet]
parseJSON :: Value -> Parser SimulatorWallet
$cparseJSON :: Value -> Parser SimulatorWallet
FromJSON)
data ContractCall a
= CallEndpoint
{ ContractCall a -> WalletNumber
caller :: WalletNumber
, ContractCall a -> FunctionSchema a
argumentValues :: FunctionSchema a
}
| AddBlocks
{ ContractCall a -> Integer
blocks :: Integer
}
| AddBlocksUntil
{ ContractCall a -> Slot
slot :: Slot
}
| PayToWallet
{ ContractCall a -> WalletNumber
sender :: WalletNumber
, ContractCall a -> WalletNumber
recipient :: WalletNumber
, ContractCall a -> Value
amount :: V.Value
}
deriving ( Int -> ContractCall a -> ShowS
[ContractCall a] -> ShowS
ContractCall a -> String
(Int -> ContractCall a -> ShowS)
-> (ContractCall a -> String)
-> ([ContractCall a] -> ShowS)
-> Show (ContractCall a)
forall a. Show a => Int -> ContractCall a -> ShowS
forall a. Show a => [ContractCall a] -> ShowS
forall a. Show a => ContractCall a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContractCall a] -> ShowS
$cshowList :: forall a. Show a => [ContractCall a] -> ShowS
show :: ContractCall a -> String
$cshow :: forall a. Show a => ContractCall a -> String
showsPrec :: Int -> ContractCall a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ContractCall a -> ShowS
Show
, ContractCall a -> ContractCall a -> Bool
(ContractCall a -> ContractCall a -> Bool)
-> (ContractCall a -> ContractCall a -> Bool)
-> Eq (ContractCall a)
forall a. Eq a => ContractCall a -> ContractCall a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContractCall a -> ContractCall a -> Bool
$c/= :: forall a. Eq a => ContractCall a -> ContractCall a -> Bool
== :: ContractCall a -> ContractCall a -> Bool
$c== :: forall a. Eq a => ContractCall a -> ContractCall a -> Bool
Eq
, (forall x. ContractCall a -> Rep (ContractCall a) x)
-> (forall x. Rep (ContractCall a) x -> ContractCall a)
-> Generic (ContractCall a)
forall x. Rep (ContractCall a) x -> ContractCall a
forall x. ContractCall a -> Rep (ContractCall a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (ContractCall a) x -> ContractCall a
forall a x. ContractCall a -> Rep (ContractCall a) x
$cto :: forall a x. Rep (ContractCall a) x -> ContractCall a
$cfrom :: forall a x. ContractCall a -> Rep (ContractCall a) x
Generic
, a -> ContractCall b -> ContractCall a
(a -> b) -> ContractCall a -> ContractCall b
(forall a b. (a -> b) -> ContractCall a -> ContractCall b)
-> (forall a b. a -> ContractCall b -> ContractCall a)
-> Functor ContractCall
forall a b. a -> ContractCall b -> ContractCall a
forall a b. (a -> b) -> ContractCall a -> ContractCall b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ContractCall b -> ContractCall a
$c<$ :: forall a b. a -> ContractCall b -> ContractCall a
fmap :: (a -> b) -> ContractCall a -> ContractCall b
$cfmap :: forall a b. (a -> b) -> ContractCall a -> ContractCall b
Functor
, [ContractCall a] -> Encoding
[ContractCall a] -> Value
ContractCall a -> Encoding
ContractCall a -> Value
(ContractCall a -> Value)
-> (ContractCall a -> Encoding)
-> ([ContractCall a] -> Value)
-> ([ContractCall a] -> Encoding)
-> ToJSON (ContractCall a)
forall a. ToJSON a => [ContractCall a] -> Encoding
forall a. ToJSON a => [ContractCall a] -> Value
forall a. ToJSON a => ContractCall a -> Encoding
forall a. ToJSON a => ContractCall a -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ContractCall a] -> Encoding
$ctoEncodingList :: forall a. ToJSON a => [ContractCall a] -> Encoding
toJSONList :: [ContractCall a] -> Value
$ctoJSONList :: forall a. ToJSON a => [ContractCall a] -> Value
toEncoding :: ContractCall a -> Encoding
$ctoEncoding :: forall a. ToJSON a => ContractCall a -> Encoding
toJSON :: ContractCall a -> Value
$ctoJSON :: forall a. ToJSON a => ContractCall a -> Value
ToJSON
, Value -> Parser [ContractCall a]
Value -> Parser (ContractCall a)
(Value -> Parser (ContractCall a))
-> (Value -> Parser [ContractCall a]) -> FromJSON (ContractCall a)
forall a. FromJSON a => Value -> Parser [ContractCall a]
forall a. FromJSON a => Value -> Parser (ContractCall a)
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ContractCall a]
$cparseJSONList :: forall a. FromJSON a => Value -> Parser [ContractCall a]
parseJSON :: Value -> Parser (ContractCall a)
$cparseJSON :: forall a. FromJSON a => Value -> Parser (ContractCall a)
FromJSON
, ContractCall a -> Bool
(a -> m) -> ContractCall a -> m
(a -> b -> b) -> b -> ContractCall a -> b
(forall m. Monoid m => ContractCall m -> m)
-> (forall m a. Monoid m => (a -> m) -> ContractCall a -> m)
-> (forall m a. Monoid m => (a -> m) -> ContractCall a -> m)
-> (forall a b. (a -> b -> b) -> b -> ContractCall a -> b)
-> (forall a b. (a -> b -> b) -> b -> ContractCall a -> b)
-> (forall b a. (b -> a -> b) -> b -> ContractCall a -> b)
-> (forall b a. (b -> a -> b) -> b -> ContractCall a -> b)
-> (forall a. (a -> a -> a) -> ContractCall a -> a)
-> (forall a. (a -> a -> a) -> ContractCall a -> a)
-> (forall a. ContractCall a -> [a])
-> (forall a. ContractCall a -> Bool)
-> (forall a. ContractCall a -> Int)
-> (forall a. Eq a => a -> ContractCall a -> Bool)
-> (forall a. Ord a => ContractCall a -> a)
-> (forall a. Ord a => ContractCall a -> a)
-> (forall a. Num a => ContractCall a -> a)
-> (forall a. Num a => ContractCall a -> a)
-> Foldable ContractCall
forall a. Eq a => a -> ContractCall a -> Bool
forall a. Num a => ContractCall a -> a
forall a. Ord a => ContractCall a -> a
forall m. Monoid m => ContractCall m -> m
forall a. ContractCall a -> Bool
forall a. ContractCall a -> Int
forall a. ContractCall a -> [a]
forall a. (a -> a -> a) -> ContractCall a -> a
forall m a. Monoid m => (a -> m) -> ContractCall a -> m
forall b a. (b -> a -> b) -> b -> ContractCall a -> b
forall a b. (a -> b -> b) -> b -> ContractCall a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: ContractCall a -> a
$cproduct :: forall a. Num a => ContractCall a -> a
sum :: ContractCall a -> a
$csum :: forall a. Num a => ContractCall a -> a
minimum :: ContractCall a -> a
$cminimum :: forall a. Ord a => ContractCall a -> a
maximum :: ContractCall a -> a
$cmaximum :: forall a. Ord a => ContractCall a -> a
elem :: a -> ContractCall a -> Bool
$celem :: forall a. Eq a => a -> ContractCall a -> Bool
length :: ContractCall a -> Int
$clength :: forall a. ContractCall a -> Int
null :: ContractCall a -> Bool
$cnull :: forall a. ContractCall a -> Bool
toList :: ContractCall a -> [a]
$ctoList :: forall a. ContractCall a -> [a]
foldl1 :: (a -> a -> a) -> ContractCall a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> ContractCall a -> a
foldr1 :: (a -> a -> a) -> ContractCall a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> ContractCall a -> a
foldl' :: (b -> a -> b) -> b -> ContractCall a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> ContractCall a -> b
foldl :: (b -> a -> b) -> b -> ContractCall a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> ContractCall a -> b
foldr' :: (a -> b -> b) -> b -> ContractCall a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> ContractCall a -> b
foldr :: (a -> b -> b) -> b -> ContractCall a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> ContractCall a -> b
foldMap' :: (a -> m) -> ContractCall a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> ContractCall a -> m
foldMap :: (a -> m) -> ContractCall a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> ContractCall a -> m
fold :: ContractCall m -> m
$cfold :: forall m. Monoid m => ContractCall m -> m
Foldable
, Functor ContractCall
Foldable ContractCall
Functor ContractCall
-> Foldable ContractCall
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ContractCall a -> f (ContractCall b))
-> (forall (f :: * -> *) a.
Applicative f =>
ContractCall (f a) -> f (ContractCall a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ContractCall a -> m (ContractCall b))
-> (forall (m :: * -> *) a.
Monad m =>
ContractCall (m a) -> m (ContractCall a))
-> Traversable ContractCall
(a -> f b) -> ContractCall a -> f (ContractCall b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ContractCall (m a) -> m (ContractCall a)
forall (f :: * -> *) a.
Applicative f =>
ContractCall (f a) -> f (ContractCall a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ContractCall a -> m (ContractCall b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ContractCall a -> f (ContractCall b)
sequence :: ContractCall (m a) -> m (ContractCall a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
ContractCall (m a) -> m (ContractCall a)
mapM :: (a -> m b) -> ContractCall a -> m (ContractCall b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ContractCall a -> m (ContractCall b)
sequenceA :: ContractCall (f a) -> f (ContractCall a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
ContractCall (f a) -> f (ContractCall a)
traverse :: (a -> f b) -> ContractCall a -> f (ContractCall b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ContractCall a -> f (ContractCall b)
$cp2Traversable :: Foldable ContractCall
$cp1Traversable :: Functor ContractCall
Traversable
)
type SimulatorAction = ContractCall (Fix FormArgumentF)
type Expression = ContractCall JSON.Value
data Simulation =
Simulation
{ Simulation -> String
simulationName :: String
, Simulation -> Int
simulationId :: Int
, Simulation -> [SimulatorAction]
simulationActions :: [SimulatorAction]
, Simulation -> [SimulatorWallet]
simulationWallets :: [SimulatorWallet]
}
deriving (Int -> Simulation -> ShowS
[Simulation] -> ShowS
Simulation -> String
(Int -> Simulation -> ShowS)
-> (Simulation -> String)
-> ([Simulation] -> ShowS)
-> Show Simulation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Simulation] -> ShowS
$cshowList :: [Simulation] -> ShowS
show :: Simulation -> String
$cshow :: Simulation -> String
showsPrec :: Int -> Simulation -> ShowS
$cshowsPrec :: Int -> Simulation -> ShowS
Show, (forall x. Simulation -> Rep Simulation x)
-> (forall x. Rep Simulation x -> Simulation) -> Generic Simulation
forall x. Rep Simulation x -> Simulation
forall x. Simulation -> Rep Simulation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Simulation x -> Simulation
$cfrom :: forall x. Simulation -> Rep Simulation x
Generic, Simulation -> Simulation -> Bool
(Simulation -> Simulation -> Bool)
-> (Simulation -> Simulation -> Bool) -> Eq Simulation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Simulation -> Simulation -> Bool
$c/= :: Simulation -> Simulation -> Bool
== :: Simulation -> Simulation -> Bool
$c== :: Simulation -> Simulation -> Bool
Eq)
deriving anyclass ([Simulation] -> Encoding
[Simulation] -> Value
Simulation -> Encoding
Simulation -> Value
(Simulation -> Value)
-> (Simulation -> Encoding)
-> ([Simulation] -> Value)
-> ([Simulation] -> Encoding)
-> ToJSON Simulation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Simulation] -> Encoding
$ctoEncodingList :: [Simulation] -> Encoding
toJSONList :: [Simulation] -> Value
$ctoJSONList :: [Simulation] -> Value
toEncoding :: Simulation -> Encoding
$ctoEncoding :: Simulation -> Encoding
toJSON :: Simulation -> Value
$ctoJSON :: Simulation -> Value
ToJSON, Value -> Parser [Simulation]
Value -> Parser Simulation
(Value -> Parser Simulation)
-> (Value -> Parser [Simulation]) -> FromJSON Simulation
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Simulation]
$cparseJSONList :: Value -> Parser [Simulation]
parseJSON :: Value -> Parser Simulation
$cparseJSON :: Value -> Parser Simulation
FromJSON)
data Evaluation =
Evaluation
{ Evaluation -> [SimulatorWallet]
wallets :: [SimulatorWallet]
, Evaluation -> SourceCode
sourceCode :: SourceCode
, Evaluation -> Value
program :: JSON.Value
}
deriving ((forall x. Evaluation -> Rep Evaluation x)
-> (forall x. Rep Evaluation x -> Evaluation) -> Generic Evaluation
forall x. Rep Evaluation x -> Evaluation
forall x. Evaluation -> Rep Evaluation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Evaluation x -> Evaluation
$cfrom :: forall x. Evaluation -> Rep Evaluation x
Generic, [Evaluation] -> Encoding
[Evaluation] -> Value
Evaluation -> Encoding
Evaluation -> Value
(Evaluation -> Value)
-> (Evaluation -> Encoding)
-> ([Evaluation] -> Value)
-> ([Evaluation] -> Encoding)
-> ToJSON Evaluation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Evaluation] -> Encoding
$ctoEncodingList :: [Evaluation] -> Encoding
toJSONList :: [Evaluation] -> Value
$ctoJSONList :: [Evaluation] -> Value
toEncoding :: Evaluation -> Encoding
$ctoEncoding :: Evaluation -> Encoding
toJSON :: Evaluation -> Value
$ctoJSON :: Evaluation -> Value
ToJSON, Value -> Parser [Evaluation]
Value -> Parser Evaluation
(Value -> Parser Evaluation)
-> (Value -> Parser [Evaluation]) -> FromJSON Evaluation
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Evaluation]
$cparseJSONList :: Value -> Parser [Evaluation]
parseJSON :: Value -> Parser Evaluation
$cparseJSON :: Value -> Parser Evaluation
FromJSON)
pubKeys :: Evaluation -> [PaymentPubKeyHash]
pubKeys :: Evaluation -> [PaymentPubKeyHash]
pubKeys Evaluation {[SimulatorWallet]
wallets :: [SimulatorWallet]
wallets :: Evaluation -> [SimulatorWallet]
wallets} = MockWallet -> PaymentPubKeyHash
CW.paymentPubKeyHash (MockWallet -> PaymentPubKeyHash)
-> (SimulatorWallet -> MockWallet)
-> SimulatorWallet
-> PaymentPubKeyHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WalletNumber -> MockWallet
CW.fromWalletNumber (WalletNumber -> MockWallet)
-> (SimulatorWallet -> WalletNumber)
-> SimulatorWallet
-> MockWallet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimulatorWallet -> WalletNumber
simulatorWalletWallet (SimulatorWallet -> PaymentPubKeyHash)
-> [SimulatorWallet] -> [PaymentPubKeyHash]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SimulatorWallet]
wallets
data EvaluationResult =
EvaluationResult
{ EvaluationResult -> [[AnnotatedTx]]
resultRollup :: [[AnnotatedTx]]
, EvaluationResult -> [EmulatorEvent]
emulatorLog :: [EmulatorEvent]
, EvaluationResult -> Text
emulatorTrace :: Text
, EvaluationResult -> [SimulatorWallet]
fundsDistribution :: [SimulatorWallet]
, EvaluationResult -> [SimulatorWallet]
feesDistribution :: [SimulatorWallet]
, EvaluationResult -> [(PaymentPubKeyHash, WalletNumber)]
walletKeys :: [(PaymentPubKeyHash, WalletNumber)]
}
deriving (Int -> EvaluationResult -> ShowS
[EvaluationResult] -> ShowS
EvaluationResult -> String
(Int -> EvaluationResult -> ShowS)
-> (EvaluationResult -> String)
-> ([EvaluationResult] -> ShowS)
-> Show EvaluationResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EvaluationResult] -> ShowS
$cshowList :: [EvaluationResult] -> ShowS
show :: EvaluationResult -> String
$cshow :: EvaluationResult -> String
showsPrec :: Int -> EvaluationResult -> ShowS
$cshowsPrec :: Int -> EvaluationResult -> ShowS
Show, (forall x. EvaluationResult -> Rep EvaluationResult x)
-> (forall x. Rep EvaluationResult x -> EvaluationResult)
-> Generic EvaluationResult
forall x. Rep EvaluationResult x -> EvaluationResult
forall x. EvaluationResult -> Rep EvaluationResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EvaluationResult x -> EvaluationResult
$cfrom :: forall x. EvaluationResult -> Rep EvaluationResult x
Generic, [EvaluationResult] -> Encoding
[EvaluationResult] -> Value
EvaluationResult -> Encoding
EvaluationResult -> Value
(EvaluationResult -> Value)
-> (EvaluationResult -> Encoding)
-> ([EvaluationResult] -> Value)
-> ([EvaluationResult] -> Encoding)
-> ToJSON EvaluationResult
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [EvaluationResult] -> Encoding
$ctoEncodingList :: [EvaluationResult] -> Encoding
toJSONList :: [EvaluationResult] -> Value
$ctoJSONList :: [EvaluationResult] -> Value
toEncoding :: EvaluationResult -> Encoding
$ctoEncoding :: EvaluationResult -> Encoding
toJSON :: EvaluationResult -> Value
$ctoJSON :: EvaluationResult -> Value
ToJSON, Value -> Parser [EvaluationResult]
Value -> Parser EvaluationResult
(Value -> Parser EvaluationResult)
-> (Value -> Parser [EvaluationResult])
-> FromJSON EvaluationResult
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EvaluationResult]
$cparseJSONList :: Value -> Parser [EvaluationResult]
parseJSON :: Value -> Parser EvaluationResult
$cparseJSON :: Value -> Parser EvaluationResult
FromJSON)
data CompilationResult =
CompilationResult
{ CompilationResult -> [FunctionSchema FormSchema]
functionSchema :: [FunctionSchema FormSchema]
, CompilationResult -> [KnownCurrency]
knownCurrencies :: [KnownCurrency]
}
deriving (Int -> CompilationResult -> ShowS
[CompilationResult] -> ShowS
CompilationResult -> String
(Int -> CompilationResult -> ShowS)
-> (CompilationResult -> String)
-> ([CompilationResult] -> ShowS)
-> Show CompilationResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompilationResult] -> ShowS
$cshowList :: [CompilationResult] -> ShowS
show :: CompilationResult -> String
$cshow :: CompilationResult -> String
showsPrec :: Int -> CompilationResult -> ShowS
$cshowsPrec :: Int -> CompilationResult -> ShowS
Show, CompilationResult -> CompilationResult -> Bool
(CompilationResult -> CompilationResult -> Bool)
-> (CompilationResult -> CompilationResult -> Bool)
-> Eq CompilationResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompilationResult -> CompilationResult -> Bool
$c/= :: CompilationResult -> CompilationResult -> Bool
== :: CompilationResult -> CompilationResult -> Bool
$c== :: CompilationResult -> CompilationResult -> Bool
Eq, (forall x. CompilationResult -> Rep CompilationResult x)
-> (forall x. Rep CompilationResult x -> CompilationResult)
-> Generic CompilationResult
forall x. Rep CompilationResult x -> CompilationResult
forall x. CompilationResult -> Rep CompilationResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompilationResult x -> CompilationResult
$cfrom :: forall x. CompilationResult -> Rep CompilationResult x
Generic, [CompilationResult] -> Encoding
[CompilationResult] -> Value
CompilationResult -> Encoding
CompilationResult -> Value
(CompilationResult -> Value)
-> (CompilationResult -> Encoding)
-> ([CompilationResult] -> Value)
-> ([CompilationResult] -> Encoding)
-> ToJSON CompilationResult
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CompilationResult] -> Encoding
$ctoEncodingList :: [CompilationResult] -> Encoding
toJSONList :: [CompilationResult] -> Value
$ctoJSONList :: [CompilationResult] -> Value
toEncoding :: CompilationResult -> Encoding
$ctoEncoding :: CompilationResult -> Encoding
toJSON :: CompilationResult -> Value
$ctoJSON :: CompilationResult -> Value
ToJSON)
data ContractDemo =
ContractDemo
{ ContractDemo -> Text
contractDemoName :: Text
, ContractDemo -> SourceCode
contractDemoEditorContents :: SourceCode
, ContractDemo -> [Simulation]
contractDemoSimulations :: [Simulation]
, ContractDemo -> InterpreterResult CompilationResult
contractDemoContext :: HI.InterpreterResult CompilationResult
}
deriving (Int -> ContractDemo -> ShowS
[ContractDemo] -> ShowS
ContractDemo -> String
(Int -> ContractDemo -> ShowS)
-> (ContractDemo -> String)
-> ([ContractDemo] -> ShowS)
-> Show ContractDemo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContractDemo] -> ShowS
$cshowList :: [ContractDemo] -> ShowS
show :: ContractDemo -> String
$cshow :: ContractDemo -> String
showsPrec :: Int -> ContractDemo -> ShowS
$cshowsPrec :: Int -> ContractDemo -> ShowS
Show, ContractDemo -> ContractDemo -> Bool
(ContractDemo -> ContractDemo -> Bool)
-> (ContractDemo -> ContractDemo -> Bool) -> Eq ContractDemo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContractDemo -> ContractDemo -> Bool
$c/= :: ContractDemo -> ContractDemo -> Bool
== :: ContractDemo -> ContractDemo -> Bool
$c== :: ContractDemo -> ContractDemo -> Bool
Eq, (forall x. ContractDemo -> Rep ContractDemo x)
-> (forall x. Rep ContractDemo x -> ContractDemo)
-> Generic ContractDemo
forall x. Rep ContractDemo x -> ContractDemo
forall x. ContractDemo -> Rep ContractDemo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContractDemo x -> ContractDemo
$cfrom :: forall x. ContractDemo -> Rep ContractDemo x
Generic, [ContractDemo] -> Encoding
[ContractDemo] -> Value
ContractDemo -> Encoding
ContractDemo -> Value
(ContractDemo -> Value)
-> (ContractDemo -> Encoding)
-> ([ContractDemo] -> Value)
-> ([ContractDemo] -> Encoding)
-> ToJSON ContractDemo
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ContractDemo] -> Encoding
$ctoEncodingList :: [ContractDemo] -> Encoding
toJSONList :: [ContractDemo] -> Value
$ctoJSONList :: [ContractDemo] -> Value
toEncoding :: ContractDemo -> Encoding
$ctoEncoding :: ContractDemo -> Encoding
toJSON :: ContractDemo -> Value
$ctoJSON :: ContractDemo -> Value
ToJSON)
data FunctionSchema a =
FunctionSchema
{ FunctionSchema a -> EndpointDescription
endpointDescription :: EndpointDescription
, FunctionSchema a -> a
argument :: a
}
deriving ( FunctionSchema a -> FunctionSchema a -> Bool
(FunctionSchema a -> FunctionSchema a -> Bool)
-> (FunctionSchema a -> FunctionSchema a -> Bool)
-> Eq (FunctionSchema a)
forall a. Eq a => FunctionSchema a -> FunctionSchema a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FunctionSchema a -> FunctionSchema a -> Bool
$c/= :: forall a. Eq a => FunctionSchema a -> FunctionSchema a -> Bool
== :: FunctionSchema a -> FunctionSchema a -> Bool
$c== :: forall a. Eq a => FunctionSchema a -> FunctionSchema a -> Bool
Eq
, Int -> FunctionSchema a -> ShowS
[FunctionSchema a] -> ShowS
FunctionSchema a -> String
(Int -> FunctionSchema a -> ShowS)
-> (FunctionSchema a -> String)
-> ([FunctionSchema a] -> ShowS)
-> Show (FunctionSchema a)
forall a. Show a => Int -> FunctionSchema a -> ShowS
forall a. Show a => [FunctionSchema a] -> ShowS
forall a. Show a => FunctionSchema a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FunctionSchema a] -> ShowS
$cshowList :: forall a. Show a => [FunctionSchema a] -> ShowS
show :: FunctionSchema a -> String
$cshow :: forall a. Show a => FunctionSchema a -> String
showsPrec :: Int -> FunctionSchema a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> FunctionSchema a -> ShowS
Show
, (forall x. FunctionSchema a -> Rep (FunctionSchema a) x)
-> (forall x. Rep (FunctionSchema a) x -> FunctionSchema a)
-> Generic (FunctionSchema a)
forall x. Rep (FunctionSchema a) x -> FunctionSchema a
forall x. FunctionSchema a -> Rep (FunctionSchema a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (FunctionSchema a) x -> FunctionSchema a
forall a x. FunctionSchema a -> Rep (FunctionSchema a) x
$cto :: forall a x. Rep (FunctionSchema a) x -> FunctionSchema a
$cfrom :: forall a x. FunctionSchema a -> Rep (FunctionSchema a) x
Generic
, [FunctionSchema a] -> Encoding
[FunctionSchema a] -> Value
FunctionSchema a -> Encoding
FunctionSchema a -> Value
(FunctionSchema a -> Value)
-> (FunctionSchema a -> Encoding)
-> ([FunctionSchema a] -> Value)
-> ([FunctionSchema a] -> Encoding)
-> ToJSON (FunctionSchema a)
forall a. ToJSON a => [FunctionSchema a] -> Encoding
forall a. ToJSON a => [FunctionSchema a] -> Value
forall a. ToJSON a => FunctionSchema a -> Encoding
forall a. ToJSON a => FunctionSchema a -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FunctionSchema a] -> Encoding
$ctoEncodingList :: forall a. ToJSON a => [FunctionSchema a] -> Encoding
toJSONList :: [FunctionSchema a] -> Value
$ctoJSONList :: forall a. ToJSON a => [FunctionSchema a] -> Value
toEncoding :: FunctionSchema a -> Encoding
$ctoEncoding :: forall a. ToJSON a => FunctionSchema a -> Encoding
toJSON :: FunctionSchema a -> Value
$ctoJSON :: forall a. ToJSON a => FunctionSchema a -> Value
ToJSON
, Value -> Parser [FunctionSchema a]
Value -> Parser (FunctionSchema a)
(Value -> Parser (FunctionSchema a))
-> (Value -> Parser [FunctionSchema a])
-> FromJSON (FunctionSchema a)
forall a. FromJSON a => Value -> Parser [FunctionSchema a]
forall a. FromJSON a => Value -> Parser (FunctionSchema a)
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [FunctionSchema a]
$cparseJSONList :: forall a. FromJSON a => Value -> Parser [FunctionSchema a]
parseJSON :: Value -> Parser (FunctionSchema a)
$cparseJSON :: forall a. FromJSON a => Value -> Parser (FunctionSchema a)
FromJSON
, a -> FunctionSchema b -> FunctionSchema a
(a -> b) -> FunctionSchema a -> FunctionSchema b
(forall a b. (a -> b) -> FunctionSchema a -> FunctionSchema b)
-> (forall a b. a -> FunctionSchema b -> FunctionSchema a)
-> Functor FunctionSchema
forall a b. a -> FunctionSchema b -> FunctionSchema a
forall a b. (a -> b) -> FunctionSchema a -> FunctionSchema b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> FunctionSchema b -> FunctionSchema a
$c<$ :: forall a b. a -> FunctionSchema b -> FunctionSchema a
fmap :: (a -> b) -> FunctionSchema a -> FunctionSchema b
$cfmap :: forall a b. (a -> b) -> FunctionSchema a -> FunctionSchema b
Functor
, FunctionSchema a -> Bool
(a -> m) -> FunctionSchema a -> m
(a -> b -> b) -> b -> FunctionSchema a -> b
(forall m. Monoid m => FunctionSchema m -> m)
-> (forall m a. Monoid m => (a -> m) -> FunctionSchema a -> m)
-> (forall m a. Monoid m => (a -> m) -> FunctionSchema a -> m)
-> (forall a b. (a -> b -> b) -> b -> FunctionSchema a -> b)
-> (forall a b. (a -> b -> b) -> b -> FunctionSchema a -> b)
-> (forall b a. (b -> a -> b) -> b -> FunctionSchema a -> b)
-> (forall b a. (b -> a -> b) -> b -> FunctionSchema a -> b)
-> (forall a. (a -> a -> a) -> FunctionSchema a -> a)
-> (forall a. (a -> a -> a) -> FunctionSchema a -> a)
-> (forall a. FunctionSchema a -> [a])
-> (forall a. FunctionSchema a -> Bool)
-> (forall a. FunctionSchema a -> Int)
-> (forall a. Eq a => a -> FunctionSchema a -> Bool)
-> (forall a. Ord a => FunctionSchema a -> a)
-> (forall a. Ord a => FunctionSchema a -> a)
-> (forall a. Num a => FunctionSchema a -> a)
-> (forall a. Num a => FunctionSchema a -> a)
-> Foldable FunctionSchema
forall a. Eq a => a -> FunctionSchema a -> Bool
forall a. Num a => FunctionSchema a -> a
forall a. Ord a => FunctionSchema a -> a
forall m. Monoid m => FunctionSchema m -> m
forall a. FunctionSchema a -> Bool
forall a. FunctionSchema a -> Int
forall a. FunctionSchema a -> [a]
forall a. (a -> a -> a) -> FunctionSchema a -> a
forall m a. Monoid m => (a -> m) -> FunctionSchema a -> m
forall b a. (b -> a -> b) -> b -> FunctionSchema a -> b
forall a b. (a -> b -> b) -> b -> FunctionSchema a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: FunctionSchema a -> a
$cproduct :: forall a. Num a => FunctionSchema a -> a
sum :: FunctionSchema a -> a
$csum :: forall a. Num a => FunctionSchema a -> a
minimum :: FunctionSchema a -> a
$cminimum :: forall a. Ord a => FunctionSchema a -> a
maximum :: FunctionSchema a -> a
$cmaximum :: forall a. Ord a => FunctionSchema a -> a
elem :: a -> FunctionSchema a -> Bool
$celem :: forall a. Eq a => a -> FunctionSchema a -> Bool
length :: FunctionSchema a -> Int
$clength :: forall a. FunctionSchema a -> Int
null :: FunctionSchema a -> Bool
$cnull :: forall a. FunctionSchema a -> Bool
toList :: FunctionSchema a -> [a]
$ctoList :: forall a. FunctionSchema a -> [a]
foldl1 :: (a -> a -> a) -> FunctionSchema a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> FunctionSchema a -> a
foldr1 :: (a -> a -> a) -> FunctionSchema a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> FunctionSchema a -> a
foldl' :: (b -> a -> b) -> b -> FunctionSchema a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> FunctionSchema a -> b
foldl :: (b -> a -> b) -> b -> FunctionSchema a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> FunctionSchema a -> b
foldr' :: (a -> b -> b) -> b -> FunctionSchema a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> FunctionSchema a -> b
foldr :: (a -> b -> b) -> b -> FunctionSchema a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> FunctionSchema a -> b
foldMap' :: (a -> m) -> FunctionSchema a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> FunctionSchema a -> m
foldMap :: (a -> m) -> FunctionSchema a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> FunctionSchema a -> m
fold :: FunctionSchema m -> m
$cfold :: forall m. Monoid m => FunctionSchema m -> m
Foldable
, Functor FunctionSchema
Foldable FunctionSchema
Functor FunctionSchema
-> Foldable FunctionSchema
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FunctionSchema a -> f (FunctionSchema b))
-> (forall (f :: * -> *) a.
Applicative f =>
FunctionSchema (f a) -> f (FunctionSchema a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> FunctionSchema a -> m (FunctionSchema b))
-> (forall (m :: * -> *) a.
Monad m =>
FunctionSchema (m a) -> m (FunctionSchema a))
-> Traversable FunctionSchema
(a -> f b) -> FunctionSchema a -> f (FunctionSchema b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
FunctionSchema (m a) -> m (FunctionSchema a)
forall (f :: * -> *) a.
Applicative f =>
FunctionSchema (f a) -> f (FunctionSchema a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> FunctionSchema a -> m (FunctionSchema b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FunctionSchema a -> f (FunctionSchema b)
sequence :: FunctionSchema (m a) -> m (FunctionSchema a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
FunctionSchema (m a) -> m (FunctionSchema a)
mapM :: (a -> m b) -> FunctionSchema a -> m (FunctionSchema b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> FunctionSchema a -> m (FunctionSchema b)
sequenceA :: FunctionSchema (f a) -> f (FunctionSchema a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
FunctionSchema (f a) -> f (FunctionSchema a)
traverse :: (a -> f b) -> FunctionSchema a -> f (FunctionSchema b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FunctionSchema a -> f (FunctionSchema b)
$cp2Traversable :: Foldable FunctionSchema
$cp1Traversable :: Functor FunctionSchema
Traversable
)
deriving instance OpenApi.ToSchema a => OpenApi.ToSchema (FunctionSchema a)
data PlaygroundError
= CompilationErrors [CompilationError]
| InterpreterError HI.InterpreterError
| RollupError Text
| OtherError String
| JsonDecodingError
{ PlaygroundError -> String
expected :: String
, PlaygroundError -> String
decodingError :: String
, PlaygroundError -> String
input :: String
}
deriving (PlaygroundError -> PlaygroundError -> Bool
(PlaygroundError -> PlaygroundError -> Bool)
-> (PlaygroundError -> PlaygroundError -> Bool)
-> Eq PlaygroundError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlaygroundError -> PlaygroundError -> Bool
$c/= :: PlaygroundError -> PlaygroundError -> Bool
== :: PlaygroundError -> PlaygroundError -> Bool
$c== :: PlaygroundError -> PlaygroundError -> Bool
Eq, Int -> PlaygroundError -> ShowS
[PlaygroundError] -> ShowS
PlaygroundError -> String
(Int -> PlaygroundError -> ShowS)
-> (PlaygroundError -> String)
-> ([PlaygroundError] -> ShowS)
-> Show PlaygroundError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlaygroundError] -> ShowS
$cshowList :: [PlaygroundError] -> ShowS
show :: PlaygroundError -> String
$cshow :: PlaygroundError -> String
showsPrec :: Int -> PlaygroundError -> ShowS
$cshowsPrec :: Int -> PlaygroundError -> ShowS
Show, (forall x. PlaygroundError -> Rep PlaygroundError x)
-> (forall x. Rep PlaygroundError x -> PlaygroundError)
-> Generic PlaygroundError
forall x. Rep PlaygroundError x -> PlaygroundError
forall x. PlaygroundError -> Rep PlaygroundError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlaygroundError x -> PlaygroundError
$cfrom :: forall x. PlaygroundError -> Rep PlaygroundError x
Generic)
deriving anyclass ([PlaygroundError] -> Encoding
[PlaygroundError] -> Value
PlaygroundError -> Encoding
PlaygroundError -> Value
(PlaygroundError -> Value)
-> (PlaygroundError -> Encoding)
-> ([PlaygroundError] -> Value)
-> ([PlaygroundError] -> Encoding)
-> ToJSON PlaygroundError
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PlaygroundError] -> Encoding
$ctoEncodingList :: [PlaygroundError] -> Encoding
toJSONList :: [PlaygroundError] -> Value
$ctoJSONList :: [PlaygroundError] -> Value
toEncoding :: PlaygroundError -> Encoding
$ctoEncoding :: PlaygroundError -> Encoding
toJSON :: PlaygroundError -> Value
$ctoJSON :: PlaygroundError -> Value
ToJSON, Value -> Parser [PlaygroundError]
Value -> Parser PlaygroundError
(Value -> Parser PlaygroundError)
-> (Value -> Parser [PlaygroundError]) -> FromJSON PlaygroundError
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PlaygroundError]
$cparseJSONList :: Value -> Parser [PlaygroundError]
parseJSON :: Value -> Parser PlaygroundError
$cparseJSON :: Value -> Parser PlaygroundError
FromJSON)
makeLenses 'EvaluationResult