{-# OPTIONS_GHC -Wno-orphans #-}
module PlutusLedgerApi.V1.Orphans.Scripts () where
import Data.Coerce (coerce)
import PlutusLedgerApi.Orphans.Common (
Blake2b244Hash (Blake2b244Hash),
Blake2b256Hash (Blake2b256Hash),
)
import PlutusLedgerApi.V1 qualified as PLA
import PlutusTx.Prelude qualified as PlutusTx
import Test.QuickCheck (
Arbitrary,
CoArbitrary,
Function (function),
functionMap,
)
deriving via PlutusTx.BuiltinData instance Arbitrary PLA.Redeemer
deriving via PlutusTx.BuiltinData instance CoArbitrary PLA.Redeemer
instance Function PLA.Redeemer where
{-# INLINEABLE function #-}
function :: forall b. (Redeemer -> b) -> Redeemer :-> b
function = (Redeemer -> BuiltinData)
-> (BuiltinData -> Redeemer) -> (Redeemer -> b) -> Redeemer :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Redeemer -> BuiltinData
forall a b. Coercible a b => a -> b
coerce BuiltinData -> Redeemer
PLA.Redeemer
deriving via PlutusTx.BuiltinData instance Arbitrary PLA.Datum
deriving via PlutusTx.BuiltinData instance CoArbitrary PLA.Datum
instance Function PLA.Datum where
{-# INLINEABLE function #-}
function :: forall b. (Datum -> b) -> Datum :-> b
function = (Datum -> BuiltinData)
-> (BuiltinData -> Datum) -> (Datum -> b) -> Datum :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Datum -> BuiltinData
forall a b. Coercible a b => a -> b
coerce BuiltinData -> Datum
PLA.Datum
deriving via Blake2b256Hash instance Arbitrary PLA.DatumHash
deriving via Blake2b256Hash instance CoArbitrary PLA.DatumHash
instance Function PLA.DatumHash where
{-# INLINEABLE function #-}
function :: forall b. (DatumHash -> b) -> DatumHash :-> b
function = (DatumHash -> BuiltinByteString)
-> (BuiltinByteString -> DatumHash)
-> (DatumHash -> b)
-> DatumHash :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap DatumHash -> BuiltinByteString
forall a b. Coercible a b => a -> b
coerce BuiltinByteString -> DatumHash
PLA.DatumHash
deriving via PLA.DatumHash instance Arbitrary PLA.RedeemerHash
deriving via PLA.DatumHash instance CoArbitrary PLA.RedeemerHash
instance Function PLA.RedeemerHash where
{-# INLINEABLE function #-}
function :: forall b. (RedeemerHash -> b) -> RedeemerHash :-> b
function = (RedeemerHash -> BuiltinByteString)
-> (BuiltinByteString -> RedeemerHash)
-> (RedeemerHash -> b)
-> RedeemerHash :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap RedeemerHash -> BuiltinByteString
forall a b. Coercible a b => a -> b
coerce BuiltinByteString -> RedeemerHash
PLA.RedeemerHash
deriving via Blake2b244Hash instance Arbitrary PLA.ScriptHash
deriving via Blake2b244Hash instance CoArbitrary PLA.ScriptHash
instance Function PLA.ScriptHash where
{-# INLINEABLE function #-}
function :: forall b. (ScriptHash -> b) -> ScriptHash :-> b
function = (ScriptHash -> BuiltinByteString)
-> (BuiltinByteString -> ScriptHash)
-> (ScriptHash -> b)
-> ScriptHash :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ScriptHash -> BuiltinByteString
forall a b. Coercible a b => a -> b
coerce BuiltinByteString -> ScriptHash
PLA.ScriptHash