Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class UnpackedValScopeC (UnpackedValScope t) t => UnpackedValScope t
- class ConstantScopeC (ConstantScope t) t => ConstantScope t
- class PackedValScopeC (PackedValScope t) t => PackedValScope t
- class ParameterScopeC (ParameterScope t) t => ParameterScope t
- class StorageScopeC (StorageScope t) t => StorageScope t
- class DupableScopeC (DupableScope t) t => DupableScope t
- class UntypedValScopeC (UntypedValScope t) t => UntypedValScope t
- class ViewableScopeC (ViewableScope t) t => ViewableScope t
- class ComparabilityScopeC (ComparabilityScope t) t => ComparabilityScope t
- type family IsDupableScope (t :: T) :: Bool where ...
- type CommonScopeC c ps t = (SingI t, ForbidManyT c ps t, WellTyped t)
- type ParameterScopeC c t = CommonScopeC c ['PSOp, 'PSNestedBigMaps] t
- type StorageScopeC c t = CommonScopeC c ['PSOp, 'PSNestedBigMaps, 'PSContract] t
- type ConstantScopeC c t = CommonScopeC c ['PSOp, 'PSBigMap, 'PSContract, 'PSTicket, 'PSSaplingState] t
- type DupableScopeC c t = (SingI t, ForbidManyT c '['PSTicket] t)
- type PackedValScopeC c t = CommonScopeC c ['PSOp, 'PSBigMap, 'PSTicket, 'PSSaplingState] t
- type UnpackedValScopeC c t = ConstantScopeC c t
- type ViewableScopeC c t = (SingI t, ForbidManyT c ['PSOp, 'PSBigMap, 'PSTicket] t)
- type UntypedValScopeC c t = (SingI t, ForbidManyT c '['PSOp] t)
- type ComparabilityScopeC c t = (SingI t, ForbidManyT c '['PSNonComparable] t, Comparable t)
Documentation
class UnpackedValScopeC (UnpackedValScope t) t => UnpackedValScope t Source #
Set of constraints that Michelson applies to unpacked values.
Same as ConstantScope
.
Not just a type alias in order to show better errors on ambiguity or missing constraint.
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: UnpackedValScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains `operation`, `big_map`, `contract`, `ticket` or `sapling_state`. Perhaps you need to add ... UnpackedValScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
UnpackedValScopeC (UnpackedValScope t) t => UnpackedValScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes | |
SingI t => CheckScope (UnpackedValScope t) Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope checkScope :: Either BadTypeForScope (Dict (UnpackedValScope t)) Source # |
class ConstantScopeC (ConstantScope t) t => ConstantScope t Source #
Set of constraints that Michelson applies to pushed constants.
Not just a type alias in order to be able to partially apply it
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: ConstantScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains `operation`, `big_map`, `contract`, `ticket` or `sapling_state`. Perhaps you need to add ... ConstantScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
ConstantScopeC (ConstantScope t) t => ConstantScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes | |
(WithDeMorganScope ForbidOp t a b, WithDeMorganScope ForbidBigMap t a b, WithDeMorganScope ForbidContract t a b, WithDeMorganScope ForbidTicket t a b, WithDeMorganScope ForbidSaplingState t a b, WellTyped a, WellTyped b) => WithDeMorganScope ConstantScope t a b Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope withDeMorganScope :: ConstantScope (t a b) => ((ConstantScope a, ConstantScope b) => ret) -> ret Source # | |
SingI t => CheckScope (ConstantScope t) Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope checkScope :: Either BadTypeForScope (Dict (ConstantScope t)) Source # |
class PackedValScopeC (PackedValScope t) t => PackedValScope t Source #
Set of constraints that Michelson applies to packed values.
Not just a type alias in order to be able to partially apply it.
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: PackedValScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains `operation`, `big_map`, `ticket` or `sapling_state`. Perhaps you need to add ... PackedValScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
PackedValScopeC (PackedValScope t) t => PackedValScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes | |
(WithDeMorganScope ForbidOp t a b, WithDeMorganScope ForbidBigMap t a b, WithDeMorganScope ForbidTicket t a b, WithDeMorganScope ForbidSaplingState t a b, WellTyped a, WellTyped b) => WithDeMorganScope PackedValScope t a b Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope withDeMorganScope :: PackedValScope (t a b) => ((PackedValScope a, PackedValScope b) => ret) -> ret Source # | |
SingI t => CheckScope (PackedValScope t) Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope checkScope :: Either BadTypeForScope (Dict (PackedValScope t)) Source # |
class ParameterScopeC (ParameterScope t) t => ParameterScope t Source #
Set of constraints that Michelson applies to parameters.
Not just a type alias in order to be able to partially apply it
Produces human-readable error messages:
>>>
() :: ParameterScope (TBigMap TUnit (TBigMap TUnit TOperation)) => ()
... ... Type `operation` found in ... 'TBigMap 'TUnit ('TBigMap 'TUnit 'TOperation) ... is not allowed in this scope ... ... Nested `big_map`s found in ... 'TBigMap 'TUnit ('TBigMap 'TUnit 'TOperation) ... are not allowed ...>>>
() :: ParameterScope (TBigMap TInt TNat) => ()
()
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: ParameterScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains `operation` or nested `big_map`s. Perhaps you need to add ... ParameterScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
ParameterScopeC (ParameterScope t) t => ParameterScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes | |
(WithDeMorganScope ForbidOp t a b, WithDeMorganScope ForbidNestedBigMaps t a b, WellTyped a, WellTyped b) => WithDeMorganScope ParameterScope t a b Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope withDeMorganScope :: ParameterScope (t a b) => ((ParameterScope a, ParameterScope b) => ret) -> ret Source # | |
SingI t => CheckScope (ParameterScope t) Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope checkScope :: Either BadTypeForScope (Dict (ParameterScope t)) Source # |
class StorageScopeC (StorageScope t) t => StorageScope t Source #
Set of constraints that Michelson applies to contract storage.
Not just a type alias in order to be able to partially apply it
Produces human-readable error messages:
>>>
() :: StorageScope (TContract TOperation) => ()
... ... Type `operation` found in ... 'TOperation ... is not allowed in this scope ... ... Type `contract` found in ... 'TContract 'TOperation ... is not allowed in this scope ...>>>
() :: StorageScope TUnit => ()
()
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: StorageScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains `operation`, nested `big_map`s or `contract`. Perhaps you need to add ... StorageScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
StorageScopeC (StorageScope t) t => StorageScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes | |
(WithDeMorganScope ForbidOp t a b, WithDeMorganScope ForbidNestedBigMaps t a b, WithDeMorganScope ForbidContract t a b, WellTyped a, WellTyped b) => WithDeMorganScope StorageScope t a b Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope withDeMorganScope :: StorageScope (t a b) => ((StorageScope a, StorageScope b) => ret) -> ret Source # | |
SingI t => CheckScope (StorageScope t) Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope checkScope :: Either BadTypeForScope (Dict (StorageScope t)) Source # |
class DupableScopeC (DupableScope t) t => DupableScope t Source #
Alias for constraints which Michelson requires in DUP
instruction.
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: DupableScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains `ticket`. Perhaps you need to add ... DupableScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
DupableScopeC (DupableScope t) t => DupableScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes | |
SingI t => CheckScope (DupableScope t) Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope checkScope :: Either BadTypeForScope (Dict (DupableScope t)) Source # |
class UntypedValScopeC (UntypedValScope t) t => UntypedValScope t Source #
Alias for constraints which are required for untyped representation.
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: UntypedValScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains `operation`. Perhaps you need to add ... UntypedValScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
UntypedValScopeC (UntypedValScope t) t => UntypedValScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes |
class ViewableScopeC (ViewableScope t) t => ViewableScope t Source #
Set of constraints that Michelson applies to argument type and return type of views. All info related to views can be found in TZIP.
Not just a type alias in order to be able to partially apply it.
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: ViewableScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains `operation`, `big_map` or `ticket`. Perhaps you need to add ... ViewableScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
ViewableScopeC (ViewableScope t) t => ViewableScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes | |
SingI t => CheckScope (ViewableScope t) Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope checkScope :: Either BadTypeForScope (Dict (ViewableScope t)) Source # |
class ComparabilityScopeC (ComparabilityScope t) t => ComparabilityScope t Source #
Alias for comparable types.
On ambiguous or polymorphic types, suggests adding the constraint:
>>>
(const () :: ComparabilityScope t => f t -> ()) undefined
... ... Can't check if type ... t0 ... contains non-comparable types. Perhaps you need to add ... ComparabilityScope t0 ... constraint? You can also try adding a type annotation. ...
Instances
ComparabilityScopeC (ComparabilityScope t) t => ComparabilityScope t Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.Scopes | |
SingI t => CheckScope (ComparabilityScope t) Source # | |
Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope checkScope :: Either BadTypeForScope (Dict (ComparabilityScope t)) Source # |
type family IsDupableScope (t :: T) :: Bool where ... Source #
Returns whether the type is dupable.
IsDupableScope t = Not (ContainsT 'PSTicket t) |
type CommonScopeC c ps t = (SingI t, ForbidManyT c ps t, WellTyped t) Source #
Common constraints used for scopes defined below.
type ParameterScopeC c t = CommonScopeC c ['PSOp, 'PSNestedBigMaps] t Source #
type StorageScopeC c t = CommonScopeC c ['PSOp, 'PSNestedBigMaps, 'PSContract] t Source #
type ConstantScopeC c t = CommonScopeC c ['PSOp, 'PSBigMap, 'PSContract, 'PSTicket, 'PSSaplingState] t Source #
type DupableScopeC c t = (SingI t, ForbidManyT c '['PSTicket] t) Source #
type PackedValScopeC c t = CommonScopeC c ['PSOp, 'PSBigMap, 'PSTicket, 'PSSaplingState] t Source #
type UnpackedValScopeC c t = ConstantScopeC c t Source #
type ViewableScopeC c t = (SingI t, ForbidManyT c ['PSOp, 'PSBigMap, 'PSTicket] t) Source #
type UntypedValScopeC c t = (SingI t, ForbidManyT c '['PSOp] t) Source #
type ComparabilityScopeC c t = (SingI t, ForbidManyT c '['PSNonComparable] t, Comparable t) Source #