Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- type TypeCheckedInstr = InstrAbstract TypeCheckedOp
- data TypeCheckedOp where
- WellTypedOp :: (Typeable inp, Typeable out) => Instr inp out -> TypeCheckedOp
- IllTypedOp :: IllTypedInstr -> TypeCheckedOp
- data IllTypedInstr
- data TypeCheckedSeq inp
- = WellTypedSeq (SomeInstr inp)
- | MixedSeq (SomeInstr inp) TCError [IllTypedInstr]
- | IllTypedSeq TCError [IllTypedInstr]
- tcsEither :: ([TypeCheckedOp] -> TCError -> a) -> (SomeInstr inp -> a) -> TypeCheckedSeq inp -> a
- seqToOps :: TypeCheckedSeq inp -> [TypeCheckedOp]
- someInstrToOp :: SomeInstr inp -> TypeCheckedOp
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.
WellTypedOp :: (Typeable inp, Typeable 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. |
Instances
Eq TypeCheckedOp Source # | |
Defined in Michelson.TypeCheck.TypeCheckedOp (==) :: TypeCheckedOp -> TypeCheckedOp -> Bool # (/=) :: TypeCheckedOp -> TypeCheckedOp -> Bool # | |
NFData TypeCheckedOp Source # | |
Defined in Michelson.TypeCheck.TypeCheckedOp rnf :: TypeCheckedOp -> () # | |
RenderDoc TypeCheckedOp Source # | |
Defined in Michelson.TypeCheck.TypeCheckedOp renderDoc :: RenderContext -> TypeCheckedOp -> Doc Source # isRenderable :: TypeCheckedOp -> Bool Source # |
data IllTypedInstr Source #
Represents a non-well-typed operation
SemiTypedInstr TypeCheckedInstr | Constructs a partialy typed operation. |
NonTypedInstr ExpandedOp | Constructs a completely untyped operation. |
Instances
data TypeCheckedSeq inp Source #
Represents a partiall typed sequence of instructions.
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. |
:: ([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
.
seqToOps :: TypeCheckedSeq inp -> [TypeCheckedOp] Source #
someInstrToOp :: SomeInstr inp -> TypeCheckedOp Source #
Makes a well-typed node out of SomeInstr