-- | Cardano Scripts responses

module Blockfrost.Types.Cardano.Scripts
  ( Script (..)
  , ScriptType (..)
  , ScriptRedeemer (..)
  , ScriptDatum (..)
  , ScriptJSON (..)
  , ScriptCBOR (..)
  ) where

import Data.Aeson (Value)
import Data.Text (Text)
import Deriving.Aeson
import Servant.Docs (ToSample (..), samples, singleSample)

import Blockfrost.Types.Shared
import Blockfrost.Types.Cardano.Transactions (ValidationPurpose(Spend))

-- | Script type
data ScriptType = Plutus | Timelock
  deriving stock (Int -> ScriptType -> ShowS
[ScriptType] -> ShowS
ScriptType -> String
(Int -> ScriptType -> ShowS)
-> (ScriptType -> String)
-> ([ScriptType] -> ShowS)
-> Show ScriptType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptType] -> ShowS
$cshowList :: [ScriptType] -> ShowS
show :: ScriptType -> String
$cshow :: ScriptType -> String
showsPrec :: Int -> ScriptType -> ShowS
$cshowsPrec :: Int -> ScriptType -> ShowS
Show, ScriptType -> ScriptType -> Bool
(ScriptType -> ScriptType -> Bool)
-> (ScriptType -> ScriptType -> Bool) -> Eq ScriptType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptType -> ScriptType -> Bool
$c/= :: ScriptType -> ScriptType -> Bool
== :: ScriptType -> ScriptType -> Bool
$c== :: ScriptType -> ScriptType -> Bool
Eq, (forall x. ScriptType -> Rep ScriptType x)
-> (forall x. Rep ScriptType x -> ScriptType) -> Generic ScriptType
forall x. Rep ScriptType x -> ScriptType
forall x. ScriptType -> Rep ScriptType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScriptType x -> ScriptType
$cfrom :: forall x. ScriptType -> Rep ScriptType x
Generic)
  deriving (Value -> Parser [ScriptType]
Value -> Parser ScriptType
(Value -> Parser ScriptType)
-> (Value -> Parser [ScriptType]) -> FromJSON ScriptType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ScriptType]
$cparseJSONList :: Value -> Parser [ScriptType]
parseJSON :: Value -> Parser ScriptType
$cparseJSON :: Value -> Parser ScriptType
FromJSON, [ScriptType] -> Encoding
[ScriptType] -> Value
ScriptType -> Encoding
ScriptType -> Value
(ScriptType -> Value)
-> (ScriptType -> Encoding)
-> ([ScriptType] -> Value)
-> ([ScriptType] -> Encoding)
-> ToJSON ScriptType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ScriptType] -> Encoding
$ctoEncodingList :: [ScriptType] -> Encoding
toJSONList :: [ScriptType] -> Value
$ctoJSONList :: [ScriptType] -> Value
toEncoding :: ScriptType -> Encoding
$ctoEncoding :: ScriptType -> Encoding
toJSON :: ScriptType -> Value
$ctoJSON :: ScriptType -> Value
ToJSON)
  via CustomJSON '[ConstructorTagModifier '[ToLower]] ScriptType

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

-- | Script info
data Script = Script
  { Script -> ScriptHash
_scriptScriptHash     :: ScriptHash -- ^ Hash of the script
  , Script -> ScriptType
_scriptType           :: ScriptType -- ^ Type of the script language
  , Script -> Maybe Integer
_scriptSerialisedSize :: Maybe Integer -- ^ The size of the CBOR serialised script, if a Plutus script
  }
  deriving stock (Int -> Script -> ShowS
[Script] -> ShowS
Script -> String
(Int -> Script -> ShowS)
-> (Script -> String) -> ([Script] -> ShowS) -> Show Script
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Script] -> ShowS
$cshowList :: [Script] -> ShowS
show :: Script -> String
$cshow :: Script -> String
showsPrec :: Int -> Script -> ShowS
$cshowsPrec :: Int -> Script -> ShowS
Show, Script -> Script -> Bool
(Script -> Script -> Bool)
-> (Script -> Script -> Bool) -> Eq Script
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Script -> Script -> Bool
$c/= :: Script -> Script -> Bool
== :: Script -> Script -> Bool
$c== :: Script -> Script -> Bool
Eq, (forall x. Script -> Rep Script x)
-> (forall x. Rep Script x -> Script) -> Generic Script
forall x. Rep Script x -> Script
forall x. Script -> Rep Script x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Script x -> Script
$cfrom :: forall x. Script -> Rep Script x
Generic)
  deriving (Value -> Parser [Script]
Value -> Parser Script
(Value -> Parser Script)
-> (Value -> Parser [Script]) -> FromJSON Script
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Script]
$cparseJSONList :: Value -> Parser [Script]
parseJSON :: Value -> Parser Script
$cparseJSON :: Value -> Parser Script
FromJSON, [Script] -> Encoding
[Script] -> Value
Script -> Encoding
Script -> Value
(Script -> Value)
-> (Script -> Encoding)
-> ([Script] -> Value)
-> ([Script] -> Encoding)
-> ToJSON Script
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Script] -> Encoding
$ctoEncodingList :: [Script] -> Encoding
toJSONList :: [Script] -> Value
$ctoJSONList :: [Script] -> Value
toEncoding :: Script -> Encoding
$ctoEncoding :: Script -> Encoding
toJSON :: Script -> Value
$ctoJSON :: Script -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_script", CamelToSnake]] Script

instance ToSample Script where
  toSamples :: Proxy Script -> [(Text, Script)]
toSamples = [(Text, Script)] -> Proxy Script -> [(Text, Script)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, Script)] -> Proxy Script -> [(Text, Script)])
-> [(Text, Script)] -> Proxy Script -> [(Text, Script)]
forall a b. (a -> b) -> a -> b
$ Script -> [(Text, Script)]
forall a. a -> [(Text, a)]
singleSample
    Script :: ScriptHash -> ScriptType -> Maybe Integer -> Script
Script
      { _scriptScriptHash :: ScriptHash
_scriptScriptHash = ScriptHash
"67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656"
      , _scriptType :: ScriptType
_scriptType = ScriptType
Plutus
      , _scriptSerialisedSize :: Maybe Integer
_scriptSerialisedSize = Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
3119
      }

-- | Script redeemer
data ScriptRedeemer = ScriptRedeemer
  { ScriptRedeemer -> TxHash
_scriptRedeemerTxHash    :: TxHash -- ^ Hash of the transaction
  , ScriptRedeemer -> Integer
_scriptRedeemerTxIndex   :: Integer -- ^ Index of the redeemer within a transaction
  , ScriptRedeemer -> ValidationPurpose
_scriptRedeemerPurpose   :: ValidationPurpose -- ^ Validation purpose
  , ScriptRedeemer -> Text
_scriptRedeemerDatumHash :: Text -- ^ Datum hash
  , ScriptRedeemer -> Quantity
_scriptRedeemerUnitMem   :: Quantity -- ^ The budget in Memory to run a script
  , ScriptRedeemer -> Quantity
_scriptRedeemerUnitSteps :: Quantity -- ^ The budget in Steps to run a script
  , ScriptRedeemer -> Lovelaces
_scriptRedeemerFee       :: Lovelaces -- ^ The fee consumed to run the script
  }
  deriving stock (Int -> ScriptRedeemer -> ShowS
[ScriptRedeemer] -> ShowS
ScriptRedeemer -> String
(Int -> ScriptRedeemer -> ShowS)
-> (ScriptRedeemer -> String)
-> ([ScriptRedeemer] -> ShowS)
-> Show ScriptRedeemer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptRedeemer] -> ShowS
$cshowList :: [ScriptRedeemer] -> ShowS
show :: ScriptRedeemer -> String
$cshow :: ScriptRedeemer -> String
showsPrec :: Int -> ScriptRedeemer -> ShowS
$cshowsPrec :: Int -> ScriptRedeemer -> ShowS
Show, ScriptRedeemer -> ScriptRedeemer -> Bool
(ScriptRedeemer -> ScriptRedeemer -> Bool)
-> (ScriptRedeemer -> ScriptRedeemer -> Bool) -> Eq ScriptRedeemer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptRedeemer -> ScriptRedeemer -> Bool
$c/= :: ScriptRedeemer -> ScriptRedeemer -> Bool
== :: ScriptRedeemer -> ScriptRedeemer -> Bool
$c== :: ScriptRedeemer -> ScriptRedeemer -> Bool
Eq, (forall x. ScriptRedeemer -> Rep ScriptRedeemer x)
-> (forall x. Rep ScriptRedeemer x -> ScriptRedeemer)
-> Generic ScriptRedeemer
forall x. Rep ScriptRedeemer x -> ScriptRedeemer
forall x. ScriptRedeemer -> Rep ScriptRedeemer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScriptRedeemer x -> ScriptRedeemer
$cfrom :: forall x. ScriptRedeemer -> Rep ScriptRedeemer x
Generic)
  deriving (Value -> Parser [ScriptRedeemer]
Value -> Parser ScriptRedeemer
(Value -> Parser ScriptRedeemer)
-> (Value -> Parser [ScriptRedeemer]) -> FromJSON ScriptRedeemer
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ScriptRedeemer]
$cparseJSONList :: Value -> Parser [ScriptRedeemer]
parseJSON :: Value -> Parser ScriptRedeemer
$cparseJSON :: Value -> Parser ScriptRedeemer
FromJSON, [ScriptRedeemer] -> Encoding
[ScriptRedeemer] -> Value
ScriptRedeemer -> Encoding
ScriptRedeemer -> Value
(ScriptRedeemer -> Value)
-> (ScriptRedeemer -> Encoding)
-> ([ScriptRedeemer] -> Value)
-> ([ScriptRedeemer] -> Encoding)
-> ToJSON ScriptRedeemer
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ScriptRedeemer] -> Encoding
$ctoEncodingList :: [ScriptRedeemer] -> Encoding
toJSONList :: [ScriptRedeemer] -> Value
$ctoJSONList :: [ScriptRedeemer] -> Value
toEncoding :: ScriptRedeemer -> Encoding
$ctoEncoding :: ScriptRedeemer -> Encoding
toJSON :: ScriptRedeemer -> Value
$ctoJSON :: ScriptRedeemer -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_scriptRedeemer", CamelToSnake]] ScriptRedeemer

instance ToSample ScriptRedeemer where
  toSamples :: Proxy ScriptRedeemer -> [(Text, ScriptRedeemer)]
toSamples = [(Text, ScriptRedeemer)]
-> Proxy ScriptRedeemer -> [(Text, ScriptRedeemer)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, ScriptRedeemer)]
 -> Proxy ScriptRedeemer -> [(Text, ScriptRedeemer)])
-> [(Text, ScriptRedeemer)]
-> Proxy ScriptRedeemer
-> [(Text, ScriptRedeemer)]
forall a b. (a -> b) -> a -> b
$ ScriptRedeemer -> [(Text, ScriptRedeemer)]
forall a. a -> [(Text, a)]
singleSample
    ScriptRedeemer :: TxHash
-> Integer
-> ValidationPurpose
-> Text
-> Quantity
-> Quantity
-> Lovelaces
-> ScriptRedeemer
ScriptRedeemer
      { _scriptRedeemerTxHash :: TxHash
_scriptRedeemerTxHash = TxHash
"1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dce628516157f0"
      , _scriptRedeemerTxIndex :: Integer
_scriptRedeemerTxIndex = Integer
0
      , _scriptRedeemerPurpose :: ValidationPurpose
_scriptRedeemerPurpose = ValidationPurpose
Spend
      , _scriptRedeemerDatumHash :: Text
_scriptRedeemerDatumHash = Text
"923918e403bf43c34b4ef6b48eb2ee04babed17320d8d1b9ff9ad086e86f44ec"
      , _scriptRedeemerUnitMem :: Quantity
_scriptRedeemerUnitMem = Quantity
1700
      , _scriptRedeemerUnitSteps :: Quantity
_scriptRedeemerUnitSteps = Quantity
476468
      , _scriptRedeemerFee :: Lovelaces
_scriptRedeemerFee = Lovelaces
172033
      }

newtype ScriptDatum = ScriptDatum { ScriptDatum -> Value
_scriptDatumJsonValue :: Value }
  deriving stock (Int -> ScriptDatum -> ShowS
[ScriptDatum] -> ShowS
ScriptDatum -> String
(Int -> ScriptDatum -> ShowS)
-> (ScriptDatum -> String)
-> ([ScriptDatum] -> ShowS)
-> Show ScriptDatum
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptDatum] -> ShowS
$cshowList :: [ScriptDatum] -> ShowS
show :: ScriptDatum -> String
$cshow :: ScriptDatum -> String
showsPrec :: Int -> ScriptDatum -> ShowS
$cshowsPrec :: Int -> ScriptDatum -> ShowS
Show, ScriptDatum -> ScriptDatum -> Bool
(ScriptDatum -> ScriptDatum -> Bool)
-> (ScriptDatum -> ScriptDatum -> Bool) -> Eq ScriptDatum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptDatum -> ScriptDatum -> Bool
$c/= :: ScriptDatum -> ScriptDatum -> Bool
== :: ScriptDatum -> ScriptDatum -> Bool
$c== :: ScriptDatum -> ScriptDatum -> Bool
Eq, (forall x. ScriptDatum -> Rep ScriptDatum x)
-> (forall x. Rep ScriptDatum x -> ScriptDatum)
-> Generic ScriptDatum
forall x. Rep ScriptDatum x -> ScriptDatum
forall x. ScriptDatum -> Rep ScriptDatum x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScriptDatum x -> ScriptDatum
$cfrom :: forall x. ScriptDatum -> Rep ScriptDatum x
Generic)
  deriving (Value -> Parser [ScriptDatum]
Value -> Parser ScriptDatum
(Value -> Parser ScriptDatum)
-> (Value -> Parser [ScriptDatum]) -> FromJSON ScriptDatum
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ScriptDatum]
$cparseJSONList :: Value -> Parser [ScriptDatum]
parseJSON :: Value -> Parser ScriptDatum
$cparseJSON :: Value -> Parser ScriptDatum
FromJSON, [ScriptDatum] -> Encoding
[ScriptDatum] -> Value
ScriptDatum -> Encoding
ScriptDatum -> Value
(ScriptDatum -> Value)
-> (ScriptDatum -> Encoding)
-> ([ScriptDatum] -> Value)
-> ([ScriptDatum] -> Encoding)
-> ToJSON ScriptDatum
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ScriptDatum] -> Encoding
$ctoEncodingList :: [ScriptDatum] -> Encoding
toJSONList :: [ScriptDatum] -> Value
$ctoJSONList :: [ScriptDatum] -> Value
toEncoding :: ScriptDatum -> Encoding
$ctoEncoding :: ScriptDatum -> Encoding
toJSON :: ScriptDatum -> Value
$ctoJSON :: ScriptDatum -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_scriptDatum", CamelToSnake]] ScriptDatum

newtype ScriptJSON = ScriptJSON { ScriptJSON -> Maybe Value
_scriptJsonJson :: Maybe Value }
  deriving stock (Int -> ScriptJSON -> ShowS
[ScriptJSON] -> ShowS
ScriptJSON -> String
(Int -> ScriptJSON -> ShowS)
-> (ScriptJSON -> String)
-> ([ScriptJSON] -> ShowS)
-> Show ScriptJSON
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptJSON] -> ShowS
$cshowList :: [ScriptJSON] -> ShowS
show :: ScriptJSON -> String
$cshow :: ScriptJSON -> String
showsPrec :: Int -> ScriptJSON -> ShowS
$cshowsPrec :: Int -> ScriptJSON -> ShowS
Show, ScriptJSON -> ScriptJSON -> Bool
(ScriptJSON -> ScriptJSON -> Bool)
-> (ScriptJSON -> ScriptJSON -> Bool) -> Eq ScriptJSON
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptJSON -> ScriptJSON -> Bool
$c/= :: ScriptJSON -> ScriptJSON -> Bool
== :: ScriptJSON -> ScriptJSON -> Bool
$c== :: ScriptJSON -> ScriptJSON -> Bool
Eq, (forall x. ScriptJSON -> Rep ScriptJSON x)
-> (forall x. Rep ScriptJSON x -> ScriptJSON) -> Generic ScriptJSON
forall x. Rep ScriptJSON x -> ScriptJSON
forall x. ScriptJSON -> Rep ScriptJSON x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScriptJSON x -> ScriptJSON
$cfrom :: forall x. ScriptJSON -> Rep ScriptJSON x
Generic)
  deriving (Value -> Parser [ScriptJSON]
Value -> Parser ScriptJSON
(Value -> Parser ScriptJSON)
-> (Value -> Parser [ScriptJSON]) -> FromJSON ScriptJSON
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ScriptJSON]
$cparseJSONList :: Value -> Parser [ScriptJSON]
parseJSON :: Value -> Parser ScriptJSON
$cparseJSON :: Value -> Parser ScriptJSON
FromJSON, [ScriptJSON] -> Encoding
[ScriptJSON] -> Value
ScriptJSON -> Encoding
ScriptJSON -> Value
(ScriptJSON -> Value)
-> (ScriptJSON -> Encoding)
-> ([ScriptJSON] -> Value)
-> ([ScriptJSON] -> Encoding)
-> ToJSON ScriptJSON
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ScriptJSON] -> Encoding
$ctoEncodingList :: [ScriptJSON] -> Encoding
toJSONList :: [ScriptJSON] -> Value
$ctoJSONList :: [ScriptJSON] -> Value
toEncoding :: ScriptJSON -> Encoding
$ctoEncoding :: ScriptJSON -> Encoding
toJSON :: ScriptJSON -> Value
$ctoJSON :: ScriptJSON -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_scriptJson", CamelToSnake]] ScriptJSON

newtype ScriptCBOR = ScriptCBOR { ScriptCBOR -> Maybe Text
_scriptCborCbor :: Maybe Text }
  deriving stock (Int -> ScriptCBOR -> ShowS
[ScriptCBOR] -> ShowS
ScriptCBOR -> String
(Int -> ScriptCBOR -> ShowS)
-> (ScriptCBOR -> String)
-> ([ScriptCBOR] -> ShowS)
-> Show ScriptCBOR
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptCBOR] -> ShowS
$cshowList :: [ScriptCBOR] -> ShowS
show :: ScriptCBOR -> String
$cshow :: ScriptCBOR -> String
showsPrec :: Int -> ScriptCBOR -> ShowS
$cshowsPrec :: Int -> ScriptCBOR -> ShowS
Show, ScriptCBOR -> ScriptCBOR -> Bool
(ScriptCBOR -> ScriptCBOR -> Bool)
-> (ScriptCBOR -> ScriptCBOR -> Bool) -> Eq ScriptCBOR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptCBOR -> ScriptCBOR -> Bool
$c/= :: ScriptCBOR -> ScriptCBOR -> Bool
== :: ScriptCBOR -> ScriptCBOR -> Bool
$c== :: ScriptCBOR -> ScriptCBOR -> Bool
Eq, (forall x. ScriptCBOR -> Rep ScriptCBOR x)
-> (forall x. Rep ScriptCBOR x -> ScriptCBOR) -> Generic ScriptCBOR
forall x. Rep ScriptCBOR x -> ScriptCBOR
forall x. ScriptCBOR -> Rep ScriptCBOR x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScriptCBOR x -> ScriptCBOR
$cfrom :: forall x. ScriptCBOR -> Rep ScriptCBOR x
Generic)
  deriving (Value -> Parser [ScriptCBOR]
Value -> Parser ScriptCBOR
(Value -> Parser ScriptCBOR)
-> (Value -> Parser [ScriptCBOR]) -> FromJSON ScriptCBOR
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ScriptCBOR]
$cparseJSONList :: Value -> Parser [ScriptCBOR]
parseJSON :: Value -> Parser ScriptCBOR
$cparseJSON :: Value -> Parser ScriptCBOR
FromJSON, [ScriptCBOR] -> Encoding
[ScriptCBOR] -> Value
ScriptCBOR -> Encoding
ScriptCBOR -> Value
(ScriptCBOR -> Value)
-> (ScriptCBOR -> Encoding)
-> ([ScriptCBOR] -> Value)
-> ([ScriptCBOR] -> Encoding)
-> ToJSON ScriptCBOR
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ScriptCBOR] -> Encoding
$ctoEncodingList :: [ScriptCBOR] -> Encoding
toJSONList :: [ScriptCBOR] -> Value
$ctoJSONList :: [ScriptCBOR] -> Value
toEncoding :: ScriptCBOR -> Encoding
$ctoEncoding :: ScriptCBOR -> Encoding
toJSON :: ScriptCBOR -> Value
$ctoJSON :: ScriptCBOR -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_scriptCbor", CamelToSnake]] ScriptCBOR