Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type family PLamArgs (p :: S -> Type) :: [Type] where ...
- data PA (s :: S)
- data PB (s :: S)
- data PC (s :: S)
- punlam' :: forall (fin :: S -> Type) (p :: S -> Type). PUnLam fin p => (forall s. Term s p) -> PUnLamHask fin p
- punlam :: forall (fin :: S -> Type) (p :: S -> Type). PUnLam fin p => (forall s. Term s p) -> PUnLamHask fin p
- fromPFun :: forall (p :: S -> Type). FromPFun PBool p => ClosedTerm p -> PLamWrapped (PUnLamHask PBool p)
- fromPPartial :: forall (p :: S -> Type). FromPFun POpaque p => ClosedTerm p -> PLamWrapped (PUnLamHask POpaque p)
- fromFailingPPartial :: forall (p :: S -> Type). (PUnLam POpaque p, PWrapLam (PUnLamHask POpaque p), PExpectFailure (PLamWrapped (PUnLamHask POpaque p))) => ClosedTerm p -> PExpectingFail (PLamWrapped (PUnLamHask POpaque p))
- pexpectFailure :: forall (a :: Type). PExpectFailure a => a -> PExpectingFail a
- haskEquiv' :: forall (e :: Equality) (par :: Partiality) (h :: Type) (p :: S -> Type) (args :: [Type]). (HaskEquiv e par h p args, All Arbitrary args) => h -> (forall s. Term s p) -> Property
- haskEquiv :: HaskEquiv e par h p args => h -> TestableTerm p -> NP Gen args -> Property
- shrinkPLift :: forall (a :: S -> Type). (PLift a, Arbitrary (PLifted a)) => TestableTerm a -> [TestableTerm a]
- arbitraryPLift :: forall (a :: S -> Type). (PLift a, Arbitrary (PLifted a)) => Gen (TestableTerm a)
- data PFun (a :: S -> Type) (b :: S -> Type) where
- pattern PFn :: forall {a :: S -> Type} {b :: S -> Type}. (PUnsafeLiftDecl a, PUnsafeLiftDecl b) => (forall (s :: S). Term s (a :--> b)) -> PFun a b
- data TestableTerm (a :: S -> Type) = TestableTerm (forall (s :: S). Term s a)
- class PArbitrary (a :: S -> Type) where
- parbitrary :: Gen (TestableTerm a)
- pshrink :: TestableTerm a -> [TestableTerm a]
- pconstantT :: forall {p :: S -> Type} {h :: Type}. (PLift p, PLifted p ~ h) => h -> TestableTerm p
- pliftT :: forall {p :: S -> Type} {h :: Type}. (PLift p, PLifted p ~ h) => TestableTerm p -> h
- uplcEq :: forall (a :: S -> Type) (b :: S -> Type). TestableTerm a -> TestableTerm b -> Property
- data Equality
- data Partiality
- type PWrapLam (h :: Type) = (PWrapLam' h (IsLam h) (IsLast h), OnlyTestableTerm h)
- type family PUnLamHask (fin :: S -> Type) (p :: S -> Type) :: Type where ...
- type family PLamWrapped (h :: Type) :: Type where ...
- type FromPFun (end :: S -> Type) (a :: S -> Type) = (PUnLam end a, PWrapLam (PUnLamHask end a))
- type NotPLam (p :: S -> Type) = IsLam (TestableTerm p) ~ 'False
- shouldCrash :: Script -> Property
- shouldRun :: Script -> Property
Documentation
type family PLamArgs (p :: S -> Type) :: [Type] where ... Source #
Extracts all TestableTerm
s from give Plutarch function.
Since: 2.0.0
PLamArgs (a :--> b) = TestableTerm a ': PLamArgs b | |
PLamArgs _ = '[] |
Placeholder for a polymorphic type. Plutarch equivalence of QuickCheck's
A
.
Since: 2.0.0
Instances
Same as PA
.
Since: 2.0.0
Instances
Same as PA
.
Since: 2.0.0
Instances
punlam' :: forall (fin :: S -> Type) (p :: S -> Type). PUnLam fin p => (forall s. Term s p) -> PUnLamHask fin p Source #
Bring Plutarch function into the Haskell level with each Plutarch
types wrapped in the TestableTerm
.
Since: 2.1.0
punlam :: forall (fin :: S -> Type) (p :: S -> Type). PUnLam fin p => (forall s. Term s p) -> PUnLamHask fin p Source #
Same as punlam'
but evaluates the given Plutarch function before
the conversion. It will throw an error if evaluation fails.
Since: 2.1.0
fromPFun :: forall (p :: S -> Type). FromPFun PBool p => ClosedTerm p -> PLamWrapped (PUnLamHask PBool p) Source #
"Converts a Plutarch function into a Haskell function on
TestableTerm
s, then wraps functions into PFun
as
necessary. The result will be 'Quickcheck-compatible' if all
Plutarch types used have PArbitrary
instances."
Since: 2.0.0
fromPPartial :: forall (p :: S -> Type). FromPFun POpaque p => ClosedTerm p -> PLamWrapped (PUnLamHask POpaque p) Source #
fromFailingPPartial :: forall (p :: S -> Type). (PUnLam POpaque p, PWrapLam (PUnLamHask POpaque p), PExpectFailure (PLamWrapped (PUnLamHask POpaque p))) => ClosedTerm p -> PExpectingFail (PLamWrapped (PUnLamHask POpaque p)) Source #
Same as fromPPartial
but it test for failure instead of successes.
Since: 2.1.6
pexpectFailure :: forall (a :: Type). PExpectFailure a => a -> PExpectingFail a Source #
Mark testable function to expect failing case. Unlike expectFailure
from
QC, this will *not* abort after encountering one failing. Instead, it will
run for all cases and make sure all cases fail. This can accept any
Plutarch types.
Since: 2.1.6
haskEquiv' :: forall (e :: Equality) (par :: Partiality) (h :: Type) (p :: S -> Type) (args :: [Type]). (HaskEquiv e par h p args, All Arbitrary args) => h -> (forall s. Term s p) -> Property Source #
Simplified version of haskEquiv
. It will use arbitrary instead of
asking custom generators.
Since: 2.0.0
shrinkPLift :: forall (a :: S -> Type). (PLift a, Arbitrary (PLifted a)) => TestableTerm a -> [TestableTerm a] Source #
This shinker simplifies
the underlying Plutarch representation. When
shrinking a list, this shinker is always preferable.
Since: 2.0.0
arbitraryPLift :: forall (a :: S -> Type). (PLift a, Arbitrary (PLifted a)) => Gen (TestableTerm a) Source #
This generator uses the Arbitrary
instance of a Haskell representation to
make a value and lift it into Plutarch.
Since: 2.0.0
data PFun (a :: S -> Type) (b :: S -> Type) where Source #
PFun :: (PLift a, PLift b) => [(PLifted a, PLifted b)] -> PLifted b -> TestableTerm (a :--> b) -> PFun a b |
pattern PFn :: forall {a :: S -> Type} {b :: S -> Type}. (PUnsafeLiftDecl a, PUnsafeLiftDecl b) => (forall (s :: S). Term s (a :--> b)) -> PFun a b Source #
data TestableTerm (a :: S -> Type) Source #
TestableTerm is a wrapper for closed Plutarch terms. This abstraction allows Plutarch values to be generated via QuickCheck generators.
Note
The typechecker is picky about how TestableTerm
s are constructed.
Meaning, TestableTerm can throw an error when it's composed.
Since: 2.0.0
TestableTerm (forall (s :: S). Term s a) |
Instances
class PArbitrary (a :: S -> Type) where Source #
PArbitrary is the Plutarch equivalent of the Arbitrary
typeclass from
QuickCheck. It generates pseudo-random closed term, which can be used
to test properties over Plutarch code without having to compile and
evaluate.
Default implmentations are given for any Plutarch type that
implements PLift a
and Arbitrary (PLifted a)
. This generates
a Haskell value and converts it into a Plutarch term using pconstant
.
Note
The default implementation for pshrink
does no shrinking. If at all
possible, please define a shrinker, as this will make your test results
much more useful.
Since: 2.0.0
Nothing
parbitrary :: Gen (TestableTerm a) Source #
default parbitrary :: (PLift a, Arbitrary (PLifted a)) => Gen (TestableTerm a) Source #
pshrink :: TestableTerm a -> [TestableTerm a] Source #
Instances
pconstantT :: forall {p :: S -> Type} {h :: Type}. (PLift p, PLifted p ~ h) => h -> TestableTerm p Source #
pliftT :: forall {p :: S -> Type} {h :: Type}. (PLift p, PLifted p ~ h) => TestableTerm p -> h Source #
uplcEq :: forall (a :: S -> Type) (b :: S -> Type). TestableTerm a -> TestableTerm b -> Property Source #
Compares evaluated UPLC
Since: 2.0.1
Ways an Plutarch terms can be compared.
OnPEq
uses Plutarch PEq
instance to compare give terms. This
means two terms with different UPLC representations can be
considered equal when PEq
instance defines so.
OnUPLC
uses compiled and evaluated raw UPLC to compare two
terms. It is useful comparing Terms that forgot their types--
POpqaue
.
Since: 2.1.0
data Partiality Source #
Partiality of the comparison. ByPartial
will have some
performance disadventages.
Since: 2.1.0
type PWrapLam (h :: Type) = (PWrapLam' h (IsLam h) (IsLast h), OnlyTestableTerm h) Source #
Constraint for PWrapLam
` that will give a better type error message.
Since: 2.1.0
type family PUnLamHask (fin :: S -> Type) (p :: S -> Type) :: Type where ... Source #
PUnLamHask a a = TestableTerm a | |
PUnLamHask fin ((a :--> b) :--> c) = TestableTerm (a :--> b) -> PUnLamHask fin c | |
PUnLamHask fin (a :--> b) = TestableTerm a -> PUnLamHask fin b |
type family PLamWrapped (h :: Type) :: Type where ... Source #
PLamWrapped (TestableTerm (a :--> b) -> c) = PFun a b -> PLamWrapped c | |
PLamWrapped (a -> b) = a -> PLamWrapped b | |
PLamWrapped a = a |
type FromPFun (end :: S -> Type) (a :: S -> Type) = (PUnLam end a, PWrapLam (PUnLamHask end a)) Source #
Constraint for fromPFun
.
Since: 2.2.0
type NotPLam (p :: S -> Type) = IsLam (TestableTerm p) ~ 'False Source #
Ensure given PType
('S -> Type') ir not an arrow. This is very useful
when using ambiguous type variable.
Since: 2.2.0
shouldCrash :: Script -> Property Source #
Helper for writing property tests at the Haskell level. Given a Script
,
run it with the largest limits possible: if it crashes, pass; otherwise,
fail and report any logs.
Note
Depending on the logging settings the Script
was compiled with, you may not
get any logs. While we print a warning when this happens, there might have
just not been any logs to give you in the first place: there's no way to tell
for sure.
Since: 2.1.5
shouldRun :: Script -> Property Source #
Helper for writing property tests at the Haskell level. Given a Script
,
run it with the largest limits possible: if it runs, pass; otherwise, fail
and report the error, as well as any logs.
Note
Depending on the logging settings the Script
was compiled with, you may not
get any logs. While we print a warning when this happens, there might have
just not been any logs to give you in the first place: there's no way to tell
for sure.
Since: 2.1.5
Orphan instances
PConstantDecl A Source # | |
type PConstantRepr A Source # type PConstanted A :: PType Source # pconstantToRepr :: A -> PConstantRepr A Source # pconstantFromRepr :: PConstantRepr A -> Maybe A Source # | |
PConstantDecl B Source # | |
type PConstantRepr B Source # type PConstanted B :: PType Source # pconstantToRepr :: B -> PConstantRepr B Source # pconstantFromRepr :: PConstantRepr B -> Maybe B Source # | |
PConstantDecl C Source # | |
type PConstantRepr C Source # type PConstanted C :: PType Source # pconstantToRepr :: C -> PConstantRepr C Source # pconstantFromRepr :: PConstantRepr C -> Maybe C Source # |