Safe Haskell | None |
---|---|
Language | Haskell2010 |
Scope-related constraints used in Lorentz.
This contains constraints from Scope
modified for use
in Lorentz.
Synopsis
- type NiceComparable n = (KnownValue n, Comparable (ToT n))
- type NiceConstant a = (KnownValue a, ProperConstantBetterErrors (ToT a))
- type NiceFullPackedValue a = (NicePackedValue a, NiceUnpackedValue a)
- type NicePackedValue a = (KnownValue a, ProperPackedValBetterErrors (ToT a))
- type NiceParameter a = (KnownValue a, ProperParameterBetterErrors (ToT a))
- type NicePrintedValue a = (KnownValue a, ProperPrintedValBetterErrors (ToT a))
- type NiceStorage a = (HasAnnotation a, KnownValue a, ProperStorageBetterErrors (ToT a))
- type NiceUnpackedValue a = (KnownValue a, ProperUnpackedValBetterErrors (ToT a))
- niceParameterEvi :: forall a. NiceParameter a :- ParameterScope (ToT a)
- niceStorageEvi :: forall a. NiceStorage a :- StorageScope (ToT a)
- niceConstantEvi :: forall a. NiceConstant a :- ConstantScope (ToT a)
- nicePackedValueEvi :: forall a. NicePackedValue a :- PackedValScope (ToT a)
- niceUnpackedValueEvi :: forall a. NiceUnpackedValue a :- UnpackedValScope (ToT a)
- nicePrintedValueEvi :: forall a. NicePrintedValue a :- PrintedValScope (ToT a)
- class (IsoValue a, HasNoNestedBigMaps (ToT a)) => CanHaveBigMap a
- class (IsoValue a, Typeable a) => KnownValue a
- class (IsoValue a, ForbidOp (ToT a)) => NoOperation a
- class (IsoValue a, ForbidContract (ToT a)) => NoContractType a
- class (IsoValue a, ForbidBigMap (ToT a)) => NoBigMap a
- withDict :: HasDict c e => e -> (c => r) -> r
Grouped constraints
type NiceComparable n = (KnownValue n, Comparable (ToT n)) Source #
type NiceConstant a = (KnownValue a, ProperConstantBetterErrors (ToT a)) Source #
type NiceFullPackedValue a = (NicePackedValue a, NiceUnpackedValue a) Source #
type NicePackedValue a = (KnownValue a, ProperPackedValBetterErrors (ToT a)) Source #
type NiceParameter a = (KnownValue a, ProperParameterBetterErrors (ToT a)) Source #
Constraint applied to any part of parameter type.
Note that you don't usually apply this constraint to the whole parameter,
consider using NiceParameterFull
in such case.
Using this type is justified e.g. when calling another contract, there you usually supply an entrypoint argument, not the whole parameter.
type NicePrintedValue a = (KnownValue a, ProperPrintedValBetterErrors (ToT a)) Source #
type NiceStorage a = (HasAnnotation a, KnownValue a, ProperStorageBetterErrors (ToT a)) Source #
type NiceUnpackedValue a = (KnownValue a, ProperUnpackedValBetterErrors (ToT a)) Source #
niceParameterEvi :: forall a. NiceParameter a :- ParameterScope (ToT a) Source #
niceStorageEvi :: forall a. NiceStorage a :- StorageScope (ToT a) Source #
niceConstantEvi :: forall a. NiceConstant a :- ConstantScope (ToT a) Source #
nicePackedValueEvi :: forall a. NicePackedValue a :- PackedValScope (ToT a) Source #
niceUnpackedValueEvi :: forall a. NiceUnpackedValue a :- UnpackedValScope (ToT a) Source #
nicePrintedValueEvi :: forall a. NicePrintedValue a :- PrintedValScope (ToT a) Source #
Individual constraints (internals)
class (IsoValue a, HasNoNestedBigMaps (ToT a)) => CanHaveBigMap a Source #
Instances
(IsoValue a, HasNoNestedBigMaps (ToT a)) => CanHaveBigMap a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (IsoValue a, Typeable a) => KnownValue a Source #
Gathers constraints, commonly required for values.
Instances
(IsoValue a, Typeable a) => KnownValue a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (IsoValue a, ForbidOp (ToT a)) => NoOperation a Source #
Ensure given type does not contain "operation".
Instances
(IsoValue a, ForbidOp (ToT a)) => NoOperation a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (IsoValue a, ForbidContract (ToT a)) => NoContractType a Source #
Instances
(IsoValue a, ForbidContract (ToT a)) => NoContractType a Source # | |
Defined in Lorentz.Constraints.Scopes |
Re-exports
withDict :: HasDict c e => e -> (c => r) -> r #
From a Dict
, takes a value in an environment where the instance
witnessed by the Dict
is in scope, and evaluates it.
Essentially a deconstruction of a Dict
into its continuation-style
form.
Can also be used to deconstruct an entailment, a
, using a context :-
ba
.
withDict ::Dict
c -> (c => r) -> r withDict :: a => (a:-
c) -> (c => r) -> r