morley-1.20.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.TypeCheck.TypeCheckedSeq

Description

This module provides a data type for representing a partially typed sequence of instructions.

It is needed to represent the fact that there can only be one well-typed node in a sequence and it is the first one. Also, it serves its role to remove TcError usage from TypeCheckedOp.

Synopsis

Documentation

type TypeCheckedInstr op = InstrAbstract [] (TypeCheckedOp op) Source #

Represents a root of a partially typed operation tree.

data TypeCheckedOp op where Source #

Represents nodes of a partially typed operation tree.

Constructors

WellTypedOp :: SomeSingInstr -> TypeCheckedOp op

Constructs well-typed node.

IllTypedOp :: [IllTypedInstr op] -> TypeCheckedOp op

Constructs ill-typed node which might in turn contain well-typed and non-typed operations.

MixedOp :: Nesting -> SomeSingInstr -> [IllTypedInstr op] -> TypeCheckedOp op

Partially typed sequence of operations. Used exclusively for error-reporting. Nesting argument exists because we can't mix typed and untyped instructions, so we need a way to represent brace nesting of { <typed seq>; seq }

Instances

Instances details
Functor TypeCheckedOp Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Methods

fmap :: (a -> b) -> TypeCheckedOp a -> TypeCheckedOp b #

(<$) :: a -> TypeCheckedOp b -> TypeCheckedOp a #

Show op => Show (TypeCheckedOp op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

NFData op => NFData (TypeCheckedOp op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Methods

rnf :: TypeCheckedOp op -> () #

Eq op => Eq (TypeCheckedOp op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

RenderDoc op => RenderDoc (TypeCheckedOp op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

data IllTypedInstr op Source #

Represents a non-well-typed operation

Constructors

SemiTypedInstr (TypeCheckedInstr op)

Constructs a partially typed operation.

NonTypedInstr op

Constructs a completely untyped operation.

IllTypedNest [IllTypedInstr op]

Nested sequence of ill-typed operations.

Instances

Instances details
Functor IllTypedInstr Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Methods

fmap :: (a -> b) -> IllTypedInstr a -> IllTypedInstr b #

(<$) :: a -> IllTypedInstr b -> IllTypedInstr a #

Generic (IllTypedInstr op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Associated Types

type Rep (IllTypedInstr op) :: Type -> Type #

Methods

from :: IllTypedInstr op -> Rep (IllTypedInstr op) x #

to :: Rep (IllTypedInstr op) x -> IllTypedInstr op #

Show op => Show (IllTypedInstr op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

(NFData (TypeCheckedOp op), NFData op) => NFData (IllTypedInstr op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Methods

rnf :: IllTypedInstr op -> () #

Eq op => Eq (IllTypedInstr op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

RenderDoc op => RenderDoc (IllTypedInstr op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

type Rep (IllTypedInstr op) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

type Rep (IllTypedInstr op) = D1 ('MetaData "IllTypedInstr" "Morley.Michelson.TypeCheck.TypeCheckedOp" "morley-1.20.0-inplace" 'False) (C1 ('MetaCons "SemiTypedInstr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (TypeCheckedInstr op))) :+: (C1 ('MetaCons "NonTypedInstr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 op)) :+: C1 ('MetaCons "IllTypedNest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [IllTypedInstr op]))))

data TypeCheckedSeq op inp Source #

Represents a partiall typed sequence of instructions.

Constructors

WellTypedSeq (SomeTcInstr inp)

A fully well-typed sequence.

MixedSeq Nesting (SomeTcInstr inp) (TcError' op) [IllTypedInstr op]

A well-typed prefix followed by some error and semi-typed instructions. Nesting argument exists because we can't mix typed and untyped instructions, so we need a way to represent brace nesting of { <typed seq>; seq }

IllTypedSeq (TcError' op) [IllTypedInstr op]

There is no well-typed prefix, only an error and semi-typed instructions.

data Nesting Source #

Instances

Instances details
Bounded Nesting Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Enum Nesting Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Num Nesting Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Show Nesting Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

NFData Nesting Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Methods

rnf :: Nesting -> () #

Eq Nesting Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Methods

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

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

Ord Nesting Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

tcsEither Source #

Arguments

:: ([TypeCheckedOp op] -> TcError' op -> a)

On error, with all already typechecked operations

-> (SomeTcInstr inp -> a)

On well-typed instruction

-> TypeCheckedSeq op inp

The sequence to dispatch on

-> a 

Case analysis for TypeCheckedSeq.

someInstrToOp :: SomeTcInstr inp -> TypeCheckedOp op Source #

Makes a well-typed node out of SomeTcInstr

someViewToOp :: SomeView st -> View' (TypeCheckedOp op) Source #

Makes takes a typed view and converts it into an untyped one with typechecked code.