Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Morley.Michelson.TypeCheck.Error
Description
Errors that can occur when some code is being typechecked.
Synopsis
- data TypeContext
- = LambdaArgument
- | LambdaCodeCtx
- | DipCode
- | ConsArgument
- | ComparisonArguments
- | ContractParameter
- | ContractStorage
- | ArithmeticOperation
- | Iteration
- | Cast
- | UnpairArgument
- | CarArgument
- | CdrArgument
- | If
- | ConcatArgument
- | ContainerKeyType
- | ContainerValueType
- | FailwithArgument
- | TicketsJoin
- | ViewBlock
- | EmitArgument
- data TopLevelType
- data TcTypeError
- = TypeEqError (MismatchError T)
- | StackEqError (MismatchError [T])
- | UnsupportedTypeForScope T BadTypeForScope
- | NotNumericTypes T T
- | UnexpectedType (NonEmpty (NonEmpty Text))
- | UnexpectedTopLevelType TopLevelType (MismatchError T)
- | InvalidInstruction (InstrAbstract [] ()) Text
- | InvalidValueType T
- | NotEnoughItemsOnStack
- | IllegalEntrypoint EpNameFromRefAnnError
- | UnknownContract ContractAddress
- | EntrypointNotFound EpName
- | IllegalParamDecl ParamEpError
- | NegativeNat
- | MutezOverflow
- | InvalidAddress ParseEpAddressError
- | InvalidKeyHash CryptoParseError
- | InvalidBls12381Object DeserializationError
- | InvalidTimestamp
- | CodeAlwaysFails
- | EmptyCode
- | AnyError
- | InvalidBigMapId Integer
- | UnexpectedBigMapType Integer (MismatchError T)
- type TcError = TcError' ExpandedOp
- data TcError' op
- = TcFailedOnInstr (InstrAbstract [] op) SomeHST ErrorSrcPos (Maybe TypeContext) (Maybe TcTypeError)
- | TcFailedOnValue (Value' [] op) T Text ErrorSrcPos (Maybe TcTypeError)
- | TcContractError Text (Maybe TcTypeError)
- | TcViewError Text ViewName (Maybe TcTypeError)
- | TcUnreachableCode ErrorSrcPos (NonEmpty op)
- | TcExtError SomeHST ErrorSrcPos ExtError
- | TcIncompletelyTyped (TcError' op) (Contract' (TCOpSeq op))
- | TcIncompletelyTypedView (TcError' op) (View' (TCOpSeq op))
- | TcDeprecatedType Text T
- data ExtError
- newtype StackSize = StackSize Natural
- newtype TCOpSeq op = TCOpSeq [TypeCheckedOp op]
- 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
Generic TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error Associated Types type Rep TopLevelType :: Type -> Type # | |
Show TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error Methods showsPrec :: Int -> TopLevelType -> ShowS # show :: TopLevelType -> String # showList :: [TopLevelType] -> ShowS # | |
NFData TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error Methods rnf :: TopLevelType -> () # | |
Eq TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error | |
Buildable TopLevelType Source # | |
Defined in Morley.Michelson.TypeCheck.Error | |
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
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 (InstrAbstract [] ()) Text | Some instruction is invalid or used in an invalid way.
For example, The Since this makes sense only for primitive instructions, we keep
|
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 ContractAddress | 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. |
InvalidBigMapId Integer | A big_map with the given ID was not found. |
UnexpectedBigMapType | We found a big_map with the given big_map ID, but its key and/or value types are not the same as the requested types. |
Fields
|
Instances
type TcError = TcError' ExpandedOp Source #
Type check error
Constructors
TcFailedOnInstr (InstrAbstract [] op) SomeHST ErrorSrcPos (Maybe TypeContext) (Maybe TcTypeError) | |
TcFailedOnValue (Value' [] op) T Text ErrorSrcPos (Maybe TcTypeError) | |
TcContractError Text (Maybe TcTypeError) | |
TcViewError Text ViewName (Maybe TcTypeError) | |
TcUnreachableCode ErrorSrcPos (NonEmpty op) | |
TcExtError SomeHST ErrorSrcPos ExtError | |
TcIncompletelyTyped (TcError' op) (Contract' (TCOpSeq op)) | |
TcIncompletelyTypedView (TcError' op) (View' (TCOpSeq op)) | |
TcDeprecatedType Text T |
Instances
Various type errors possible when checking Morley extension commands
Constructors
Instances
Used to smooth out the impedance mismatch between instruction arguments, which must be sequences, and contract/view code which can be a singular instruction. Only used for error reporting, as in general this isn't valid.
Constructors
TCOpSeq [TypeCheckedOp op] |
Instances
Functor TCOpSeq Source # | |
Generic (TCOpSeq op) Source # | |
Show op => Show (TCOpSeq op) Source # | |
NFData op => NFData (TCOpSeq op) Source # | |
Defined in Morley.Michelson.TypeCheck.Error | |
Eq op => Eq (TCOpSeq op) Source # | |
RenderDoc op => RenderDoc (TCOpSeq op) Source # | |
Defined in Morley.Michelson.TypeCheck.Error Methods renderDoc :: RenderContext -> TCOpSeq op -> Doc Source # isRenderable :: TCOpSeq op -> Bool Source # | |
type Rep (TCOpSeq op) Source # | |
Defined in Morley.Michelson.TypeCheck.Error type Rep (TCOpSeq op) = D1 ('MetaData "TCOpSeq" "Morley.Michelson.TypeCheck.Error" "morley-1.20.0-inplace" 'True) (C1 ('MetaCons "TCOpSeq" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeCheckedOp op]))) |
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"