morley-1.7.0: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Michelson.TypeCheck.Error

Description

Errors that can occur when some code is being typechecked.

Synopsis

Documentation

data ExpectType Source #

Description of the type to be expected by certain instruction.

Instances

Instances details
Eq ExpectType Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Show ExpectType Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Generic ExpectType Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Associated Types

type Rep ExpectType :: Type -> Type #

NFData ExpectType Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

rnf :: ExpectType -> () #

Buildable ExpectType Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

build :: ExpectType -> Builder #

type Rep ExpectType Source # 
Instance details

Defined in Michelson.TypeCheck.Error

type Rep ExpectType = D1 ('MetaData "ExpectType" "Michelson.TypeCheck.Error" "morley-1.7.0-inplace" 'False) ((((C1 ('MetaCons "ExpectTypeVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExpectStackVar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExpectBool" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ExpectInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExpectNat" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ExpectByte" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExpectString" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExpectAddress" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ExpectKey" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExpectKeyHash" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ExpectSignature" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExpectContract" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExpectMutez" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ExpectList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType))) :+: C1 ('MetaCons "ExpectSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType)))))) :+: ((C1 ('MetaCons "ExpectMap" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ExpectBigMap" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExpectOption" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType))))) :+: (C1 ('MetaCons "ExpectPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType))) :+: (C1 ('MetaCons "ExpectOr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType))) :+: C1 ('MetaCons "ExpectLambda" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ExpectType))))))))

data TypeContext Source #

Contexts where type error can occur.

Instances

Instances details
Eq TypeContext Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Show TypeContext Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Generic TypeContext Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Associated Types

type Rep TypeContext :: Type -> Type #

NFData TypeContext Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

rnf :: TypeContext -> () #

Buildable TypeContext Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

build :: TypeContext -> Builder #

type Rep TypeContext Source # 
Instance details

Defined in Michelson.TypeCheck.Error

type Rep TypeContext = D1 ('MetaData "TypeContext" "Michelson.TypeCheck.Error" "morley-1.7.0-inplace" 'False) ((((C1 ('MetaCons "LambdaArgument" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LambdaCode" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DipCode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsArgument" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ComparisonArguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContractParameter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ContractStorage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArithmeticOperation" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Iteration" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cast" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CarArgument" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CdrArgument" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "If" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConcatArgument" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ContainerKeyType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContainerValueType" 'PrefixI 'False) (U1 :: Type -> Type)))))

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 T T

Type equality error

StackEqError [T] [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. big_map in UNPACK, and a concrete reason why the type is unsuported.

NotNumericTypes T T

Arithmetic operation is applied to types, at least one of which is not numeric (e.g. timestamp and timestamp passed to MUL instruction).

UnexpectedType (NonEmpty (NonEmpty ExpectType))

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.

InvalidInstruction ExpandedInstr

Some instruction can not be used in a specific context, like SELF in LAMBDA.

InvalidValueType T

Error that happens when a Value is never a valid source for this type (e.g. timestamp cannot be obtained from a ValueTrue)

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

InvalidTimestamp

Timestamp is not RFC339 compliant

CodeAlwaysFails

Code always fails, but shouldn't, like ITER body.

EmptyCode

Empty block of code, like ITER body.

AnyError

Generic error when instruction does not match something sensible.

Instances

Instances details
Eq TCTypeError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Show TCTypeError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Generic TCTypeError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Associated Types

type Rep TCTypeError :: Type -> Type #

NFData TCTypeError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

rnf :: TCTypeError -> () #

Buildable TCTypeError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

build :: TCTypeError -> Builder #

type Rep TCTypeError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

type Rep TCTypeError = D1 ('MetaData "TCTypeError" "Michelson.TypeCheck.Error" "morley-1.7.0-inplace" 'False) ((((C1 ('MetaCons "AnnError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AnnConvergeError)) :+: C1 ('MetaCons "TypeEqError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T))) :+: (C1 ('MetaCons "StackEqError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [T]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [T])) :+: (C1 ('MetaCons "UnsupportedTypeForScope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BadTypeForScope)) :+: C1 ('MetaCons "NotNumericTypes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T))))) :+: ((C1 ('MetaCons "UnexpectedType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty (NonEmpty ExpectType)))) :+: C1 ('MetaCons "InvalidInstruction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExpandedInstr))) :+: (C1 ('MetaCons "InvalidValueType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T)) :+: (C1 ('MetaCons "NotEnoughItemsOnStack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IllegalEntrypoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 EpNameFromRefAnnError)))))) :+: (((C1 ('MetaCons "UnknownContract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Address)) :+: C1 ('MetaCons "EntrypointNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 EpName))) :+: (C1 ('MetaCons "IllegalParamDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParamEpError)) :+: (C1 ('MetaCons "NegativeNat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MutezOverflow" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "InvalidAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParseEpAddressError)) :+: (C1 ('MetaCons "InvalidKeyHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CryptoParseError)) :+: C1 ('MetaCons "InvalidTimestamp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CodeAlwaysFails" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EmptyCode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AnyError" 'PrefixI 'False) (U1 :: Type -> Type))))))

data TCError Source #

Type check error

Instances

Instances details
Eq TCError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

(==) :: TCError -> TCError -> Bool #

(/=) :: TCError -> TCError -> Bool #

Buildable ExpandedInstr => Show TCError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Generic TCError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Associated Types

type Rep TCError :: Type -> Type #

Methods

from :: TCError -> Rep TCError x #

to :: Rep TCError x -> TCError #

Buildable ExpandedInstr => Exception TCError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

NFData TCError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

rnf :: TCError -> () #

Buildable TCError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

build :: TCError -> Builder #

type Rep TCError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

type Rep TCError = D1 ('MetaData "TCError" "Michelson.TypeCheck.Error" "morley-1.7.0-inplace" 'False) ((C1 ('MetaCons "TCFailedOnInstr" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExpandedInstr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SomeHST)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InstrCallStack) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TypeContext)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TCTypeError))))) :+: C1 ('MetaCons "TCFailedOnValue" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InstrCallStack) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TCTypeError)))))) :+: (C1 ('MetaCons "TCContractError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TCTypeError))) :+: (C1 ('MetaCons "TCUnreachableCode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InstrCallStack) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty ExpandedOp))) :+: C1 ('MetaCons "TCExtError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SomeHST) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InstrCallStack) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExtError))))))

data ExtError Source #

Various type errors possible when checking Morley extension commands

Instances

Instances details
Eq ExtError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Generic ExtError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Associated Types

type Rep ExtError :: Type -> Type #

Methods

from :: ExtError -> Rep ExtError x #

to :: Rep ExtError x -> ExtError #

NFData ExtError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

rnf :: ExtError -> () #

Buildable ExtError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

build :: ExtError -> Builder #

type Rep ExtError Source # 
Instance details

Defined in Michelson.TypeCheck.Error

type Rep ExtError = D1 ('MetaData "ExtError" "Michelson.TypeCheck.Error" "morley-1.7.0-inplace" 'False) ((C1 ('MetaCons "LengthMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackTypePattern)) :+: (C1 ('MetaCons "VarError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackFn)) :+: C1 ('MetaCons "TypeMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackTypePattern) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TCTypeError))))) :+: ((C1 ('MetaCons "TyVarMismatch" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Var) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackTypePattern) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TCTypeError)))) :+: C1 ('MetaCons "StkRestMismatch" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackTypePattern) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SomeHST)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SomeHST) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TCTypeError)))) :+: (C1 ('MetaCons "TestAssertError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "InvalidStackReference" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackSize)))))

newtype StackSize Source #

Constructors

StackSize Natural 

Instances

Instances details
Eq StackSize Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Show StackSize Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Generic StackSize Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Associated Types

type Rep StackSize :: Type -> Type #

NFData StackSize Source # 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

rnf :: StackSize -> () #

type Rep StackSize Source # 
Instance details

Defined in Michelson.TypeCheck.Error

type Rep StackSize = D1 ('MetaData "StackSize" "Michelson.TypeCheck.Error" "morley-1.7.0-inplace" 'True) (C1 ('MetaCons "StackSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))