| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Morley.Michelson.TypeCheck.Error
Description
Errors that can occur when some code is being typechecked.
Synopsis
- data TypeContext
- data TopLevelType
- data TCTypeError
- = AnnError AnnConvergeError
- | TypeEqError (MismatchError T)
- | StackEqError (MismatchError [T])
- | UnsupportedTypeForScope T BadTypeForScope
- | NotNumericTypes T T
- | UnexpectedType (NonEmpty (NonEmpty Text))
- | UnexpectedTopLevelType TopLevelType (MismatchError T)
- | InvalidInstruction ExpandedInstr Text
- | InvalidValueType T
- | NotEnoughItemsOnStack
- | IllegalEntrypoint EpNameFromRefAnnError
- | UnknownContract Address
- | EntrypointNotFound EpName
- | IllegalParamDecl ParamEpError
- | NegativeNat
- | MutezOverflow
- | InvalidAddress ParseEpAddressError
- | InvalidKeyHash CryptoParseError
- | InvalidBls12381Object DeserializationError
- | InvalidTimestamp
- | CodeAlwaysFails
- | EmptyCode
- | AnyError
- data TCError
- = TCFailedOnInstr ExpandedInstr SomeHST InstrCallStack (Maybe TypeContext) (Maybe TCTypeError)
- | TCFailedOnValue Value T Text InstrCallStack (Maybe TCTypeError)
- | TCContractError Text (Maybe TCTypeError)
- | TCViewError Text ViewName (Maybe TCTypeError)
- | TCUnreachableCode InstrCallStack (NonEmpty ExpandedOp)
- | TCExtError SomeHST InstrCallStack ExtError
- | TCIncompletelyTyped TCError (Contract' TypeCheckedOp)
- | TCIncompletelyTypedView TCError (View' TypeCheckedOp)
- data ExtError
- newtype StackSize = StackSize Natural
- pairWithNodeIndex :: Word -> Text
- pairWithElems :: Word -> Text
Documentation
data TypeContext Source #
Contexts where type error can occur.
Constructors
Instances
data TopLevelType Source #
Constructors
| TltParameterType | |
| TltStorageType |
Instances
| Eq TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error | |
| Show TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error Methods showsPrec :: Int -> TopLevelType -> ShowS # show :: TopLevelType -> String # showList :: [TopLevelType] -> ShowS # | |
| Generic TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error Associated Types type Rep TopLevelType :: Type -> Type # | |
| NFData TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error Methods rnf :: TopLevelType -> () # | |
| Buildable TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error Methods build :: TopLevelType -> Builder # | |
| RenderDoc TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error Methods renderDoc :: RenderContext -> TopLevelType -> Doc Source # isRenderable :: TopLevelType -> Bool Source # | |
| type Rep TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error | |
data TCTypeError Source #
Data type that represents various errors
which are related to type system.
These errors are used to specify info about type check errors
in TCError data type.
Constructors
| AnnError AnnConvergeError | Annotation unify error |
| TypeEqError (MismatchError T) | Type equality error |
| StackEqError (MismatchError [T]) | Stacks equality error |
| UnsupportedTypeForScope T BadTypeForScope | Error that happens when type cannot be used in the corresponding scope.
Argument of this constructor carries type which violates
the restriction, e.g. |
| NotNumericTypes T T | Arithmetic operation is applied to types, at least one of which is not numeric
(e.g. |
| UnexpectedType (NonEmpty (NonEmpty Text)) | Error that happens when actual types are different from the type that instruction expects. The param is an non-empty list of all expected stack types that the instruction would accept. Each expected stack types is represented as non-empty list as well. |
| UnexpectedTopLevelType TopLevelType (MismatchError T) | Error that happens when the caller expected one top-level type, but the contract has another type specified. |
| InvalidInstruction ExpandedInstr Text | Some instruction is invalid or used in an invalid way.
For example, |
| InvalidValueType T | Error that happens when a |
| NotEnoughItemsOnStack | There are not enough items on stack to perform a certain instruction. |
| IllegalEntrypoint EpNameFromRefAnnError | Invalid entrypoint name provided |
| UnknownContract Address | Contract with given address is not originated. |
| EntrypointNotFound EpName | Given entrypoint is not present. |
| IllegalParamDecl ParamEpError | Incorrect parameter declaration (with respect to entrypoints feature). |
| NegativeNat | Natural numbers cannot be negative |
| MutezOverflow | Exceeds the maximal mutez value |
| InvalidAddress ParseEpAddressError | Address couldn't be parsed from its textual representation |
| InvalidKeyHash CryptoParseError | KeyHash couldn't be parsed from its textual representation |
| InvalidBls12381Object DeserializationError | BLS12-381 primitive couldn't be parsed |
| InvalidTimestamp | Timestamp is not RFC339 compliant |
| CodeAlwaysFails | Code always fails, but shouldn't, like in ITER body.
This is actually more general, any instruction that allows no continuation
(like |
| EmptyCode | Empty block of code, like ITER body. |
| AnyError | Generic error when instruction does not match something sensible. |
Instances
Type check error
Constructors
Instances
Various type errors possible when checking Morley extension commands
Constructors
Instances
pairWithNodeIndex :: Word -> Text Source #
Given a node index ix, creates a string representing the
smallest possible right-combed pair with at least ix+1 nodes.
Since the node index 0 is valid even for non-pair values
(e.g. we can run GET 0 on a string or an int),
we simply return a type variable 'a in this case.
>>>pairWithNodeIndex 0"'a"
>>>pairWithNodeIndex 4"pair 'a1 'a2 'a3"
>>>pairWithNodeIndex 5"pair 'a1 'a2 'a3 'a4"
pairWithElems :: Word -> Text Source #
Given a number n, creates a string representing a
right-combed pair of arity n.
pairType 3 == "pair 'a1 'a2 'a3"