Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Scope-related constraints used in Lorentz.
This contains constraints from Morley.Michelson.Typed.Scope modified for use in Lorentz.
Synopsis
- class (ComparabilityScopeC (NiceComparable n) (ToT n), KnownValue n) => NiceComparable n
- class (ConstantScopeC (NiceConstant a) (ToT a), KnownValue a) => NiceConstant a
- class (DupableScopeC (Dupable a) (ToT a), KnownValue a) => Dupable a
- type NiceFullPackedValue a = (NicePackedValue a, NiceUnpackedValue a)
- class (PackedValScopeC (NicePackedValue a) (ToT a), KnownValue a) => NicePackedValue a
- class (ParameterScopeC (NiceParameter a) (ToT a), KnownValue a) => NiceParameter a
- class (UntypedValScopeC (NiceUntypedValue a) (ToT a), KnownValue a) => NiceUntypedValue a
- class (StorageScopeC (NiceStorage a) (ToT a), KnownValue a) => NiceStorage a
- type NiceStorageFull a = (NiceStorage a, HasAnnotation a)
- class (UnpackedValScopeC (NiceUnpackedValue a) (ToT a), KnownValue a) => NiceUnpackedValue a
- class (ViewableScopeC (NiceViewable a) (ToT a), KnownValue a) => NiceViewable a
- class (KnownValue n, ForbidManyT (NiceNoBigMap n) '['PSBigMap] (ToT n)) => NiceNoBigMap n
- class (ForbidNestedBigMaps (ToT a), IsoValue a) => CanHaveBigMap a
- class (IsoValue a, Typeable a) => KnownValue a
- class (ForbidOp (ToT a), IsoValue a) => NoOperation a
- class (ForbidContract (ToT a), IsoValue a) => NoContractType a
- class (ForbidBigMap (ToT a), IsoValue a) => NoBigMap a
- withDict :: HasDict c e => e -> (c => r) -> r
Grouped constraints
class (ComparabilityScopeC (NiceComparable n) (ToT n), KnownValue n) => NiceComparable n Source #
Constraint applied to any type, to check if Michelson representation (if exists) of this type is Comparable. In case it is not prints human-readable error message
>>>
emptySet @[Integer]
... ... Non-comparable type ... 'TList 'TInt ... is not allowed in this scope ...
>>>
emptySet
... ... Can't check if type ... ToT e0 ... contains non-comparable types. Perhaps you need to add ... NiceComparable e0 ... constraint? You can also try adding a type annotation. ...
Instances
(ComparabilityScopeC (NiceComparable n) (ToT n), KnownValue n) => NiceComparable n Source # | |
Defined in Lorentz.Constraints.Scopes |
class (ConstantScopeC (NiceConstant a) (ToT a), KnownValue a) => NiceConstant a Source #
Constraint applied to constants.
Shows human-readable errors on ambiguity:
>>>
push undefined
... ... Can't check if type ... ToT t0 ... contains `operation`, `big_map`, `contract`, `ticket` or `sapling_state`. Perhaps you need to add ... NiceConstant t0 ... constraint? You can also try adding a type annotation. ...
>>>
pretty $ push (1 :: Integer)
[PUSH int 1]
Instances
(ConstantScopeC (NiceConstant a) (ToT a), KnownValue a) => NiceConstant a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (DupableScopeC (Dupable a) (ToT a), KnownValue a) => Dupable a Source #
Constraint applied to constants.
Shows human-readable errors:
>>>
ticket # dup
... ... Type `ticket` found in ... 'TOption ('TTicket (ToT a)) ... is not allowed in this scope ...
Also on ambiguity:
>>>
dup
... ... Can't check if type ... ToT a0 ... contains `ticket`. Perhaps you need to add ... Dupable a0 ... constraint? You can also try adding a type annotation. ...
>>>
pretty $ dup @Integer
[DUP]
Instances
(DupableScopeC (Dupable a) (ToT a), KnownValue a) => Dupable a Source # | |
Defined in Lorentz.Constraints.Scopes |
type NiceFullPackedValue a = (NicePackedValue a, NiceUnpackedValue a) Source #
class (PackedValScopeC (NicePackedValue a) (ToT a), KnownValue a) => NicePackedValue a Source #
Constraint applied to a value being packed.
Shows human-readable errors:
>>>
pack @Operation
... ... Type `operation` found in ... 'TOperation ... is not allowed in this scope ...
Also on ambiguity:
>>>
pack
... ... Can't check if type ... ToT a0 ... contains `operation`, `big_map`, `ticket` or `sapling_state`. Perhaps you need to add ... NicePackedValue a0 ... constraint? You can also try adding a type annotation. ...
Instances
(PackedValScopeC (NicePackedValue a) (ToT a), KnownValue a) => NicePackedValue a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (ParameterScopeC (NiceParameter a) (ToT a), KnownValue a) => NiceParameter a Source #
Constraint applied to any part of a parameter type.
Use NiceParameterFull
instead
when you need to know the contract's entrypoints at compile-time.
Shows human-readable errors:
>>>
epAddressToContract @Operation
... ... Type `operation` found in ... 'TOperation ... is not allowed in this scope ...
Also on ambiguity:
>>>
epAddressToContract
... ... Can't check if type ... ToT p0 ... contains `operation` or nested `big_map`s. Perhaps you need to add ... NiceParameter p0 ... constraint? You can also try adding a type annotation. ...
Instances
(ParameterScopeC (NiceParameter a) (ToT a), KnownValue a) => NiceParameter a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (UntypedValScopeC (NiceUntypedValue a) (ToT a), KnownValue a) => NiceUntypedValue a Source #
Instances
(UntypedValScopeC (NiceUntypedValue a) (ToT a), KnownValue a) => NiceUntypedValue a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (StorageScopeC (NiceStorage a) (ToT a), KnownValue a) => NiceStorage a Source #
Instances
(StorageScopeC (NiceStorage a) (ToT a), KnownValue a) => NiceStorage a Source # | |
Defined in Lorentz.Constraints.Scopes |
type NiceStorageFull a = (NiceStorage a, HasAnnotation a) Source #
class (UnpackedValScopeC (NiceUnpackedValue a) (ToT a), KnownValue a) => NiceUnpackedValue a Source #
Constraint applied to a value being unpacked.
Shows human-readable errors:
>>>
unpack @Operation
... ... Type `operation` found in ... 'TOperation ... is not allowed in this scope ...
Also on ambiguity:
>>>
unpack
... ... Can't check if type ... ToT a0 ... contains `operation`, `big_map`, `contract`, `ticket` or `sapling_state`. Perhaps you need to add ... NiceUnpackedValue a0 ... constraint? You can also try adding a type annotation. ...
Instances
(UnpackedValScopeC (NiceUnpackedValue a) (ToT a), KnownValue a) => NiceUnpackedValue a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (ViewableScopeC (NiceViewable a) (ToT a), KnownValue a) => NiceViewable a Source #
Constraint applied to a value returned from a view.
Shows human-readable errors:
>>>
view' @"SomeView" @Operation
... ... Type `operation` found in ... 'TOperation ... is not allowed in this scope ...
Also on ambiguity:
>>>
view' @"SomeView"
... ... Can't check if type ... ToT ret0 ... contains `operation`, `big_map` or `ticket`. Perhaps you need to add ... NiceViewable ret0 ... constraint? You can also try adding a type annotation. ...
Instances
(ViewableScopeC (NiceViewable a) (ToT a), KnownValue a) => NiceViewable a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (KnownValue n, ForbidManyT (NiceNoBigMap n) '['PSBigMap] (ToT n)) => NiceNoBigMap n Source #
Constraint applied to a big_map
value type.
Shows human-readable errors:
>>>
emptyBigMap @Integer @(BigMap Integer Integer)
... ... Type `big_map` found in ... 'TBigMap 'TInt 'TInt ... is not allowed in this scope ...
Also on ambiguity:
>>>
emptyBigMap @Integer
... ... Can't check if type ... ToT v0 ... contains `big_map`. Perhaps you need to add ... NiceNoBigMap v0 ... constraint? You can also try adding a type annotation. ...
Instances
(KnownValue n, ForbidManyT (NiceNoBigMap n) '['PSBigMap] (ToT n)) => NiceNoBigMap n Source # | |
Defined in Lorentz.Constraints.Scopes |
Individual constraints (internals)
class (ForbidNestedBigMaps (ToT a), IsoValue a) => CanHaveBigMap a Source #
Instances
(ForbidNestedBigMaps (ToT a), IsoValue 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 (ForbidOp (ToT a), IsoValue a) => NoOperation a Source #
Ensure given type does not contain "operation".
Instances
(ForbidOp (ToT a), IsoValue a) => NoOperation a Source # | |
Defined in Lorentz.Constraints.Scopes |
class (ForbidContract (ToT a), IsoValue a) => NoContractType a Source #
Instances
(ForbidContract (ToT a), IsoValue 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