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

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 = InstrAbstract TypeCheckedOp Source #

Represents a root of a partially typed operation tree.

data TypeCheckedOp where Source #

Represents nodes of a partially typed operation tree.

Constructors

WellTypedOp :: (SingI inp, SingI out) => Instr inp out -> TypeCheckedOp

Constructs well-typed node.

IllTypedOp :: IllTypedInstr -> TypeCheckedOp

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

data IllTypedInstr Source #

Represents a non-well-typed operation

Constructors

SemiTypedInstr TypeCheckedInstr

Constructs a partialy typed operation.

NonTypedInstr ExpandedOp

Constructs a completely untyped operation.

Instances

Instances details
Eq IllTypedInstr Source # 
Instance details

Defined in Michelson.TypeCheck.TypeCheckedOp

Generic IllTypedInstr Source # 
Instance details

Defined in Michelson.TypeCheck.TypeCheckedOp

Associated Types

type Rep IllTypedInstr :: Type -> Type #

NFData TypeCheckedOp => NFData IllTypedInstr Source # 
Instance details

Defined in Michelson.TypeCheck.TypeCheckedOp

Methods

rnf :: IllTypedInstr -> () #

type Rep IllTypedInstr Source # 
Instance details

Defined in Michelson.TypeCheck.TypeCheckedOp

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

data TypeCheckedSeq inp Source #

Represents a partiall typed sequence of instructions.

Constructors

WellTypedSeq (SomeInstr inp)

A fully well-typed sequence.

MixedSeq (SomeInstr inp) TCError [IllTypedInstr]

A well-typed prefix followed by some error and semi-typed instructions.

IllTypedSeq TCError [IllTypedInstr]

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

tcsEither Source #

Arguments

:: ([TypeCheckedOp] -> TCError -> a)

On error, with all already typechecked operations

-> (SomeInstr inp -> a)

On well-typed instruction

-> TypeCheckedSeq inp

The sequence to dispatch on

-> a 

Case analysis for TypeCheckedSeq.

someInstrToOp :: SomeInstr inp -> TypeCheckedOp Source #

Makes a well-typed node out of SomeInstr