| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
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
- type TypeCheckedInstr op = InstrAbstract [] (TypeCheckedOp op)
- data TypeCheckedOp op where
- WellTypedOp :: SomeSingInstr -> TypeCheckedOp op
- IllTypedOp :: [IllTypedInstr op] -> TypeCheckedOp op
- MixedOp :: Nesting -> SomeSingInstr -> [IllTypedInstr op] -> TypeCheckedOp op
- data IllTypedInstr op
- = SemiTypedInstr (TypeCheckedInstr op)
- | NonTypedInstr op
- | IllTypedNest [IllTypedInstr op]
- data TypeCheckedSeq op inp
- = WellTypedSeq (SomeTcInstr inp)
- | MixedSeq Nesting (SomeTcInstr inp) (TcError' op) [IllTypedInstr op]
- | IllTypedSeq (TcError' op) [IllTypedInstr op]
- data Nesting
- tcsEither :: ([TypeCheckedOp op] -> TcError' op -> a) -> (SomeTcInstr inp -> a) -> TypeCheckedSeq op inp -> a
- seqToOps :: TypeCheckedSeq op inp -> [TypeCheckedOp op]
- someInstrToOp :: SomeTcInstr inp -> TypeCheckedOp op
- someViewToOp :: SomeView st -> View' (TypeCheckedOp op)
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.
|
Instances
| Functor TypeCheckedOp Source # | |
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 # | |
Defined in Morley.Michelson.TypeCheck.TypeCheckedOp Methods showsPrec :: Int -> TypeCheckedOp op -> ShowS # show :: TypeCheckedOp op -> String # showList :: [TypeCheckedOp op] -> ShowS # | |
| NFData op => NFData (TypeCheckedOp op) Source # | |
Defined in Morley.Michelson.TypeCheck.TypeCheckedOp Methods rnf :: TypeCheckedOp op -> () # | |
| Eq op => Eq (TypeCheckedOp op) Source # | |
Defined in Morley.Michelson.TypeCheck.TypeCheckedOp Methods (==) :: TypeCheckedOp op -> TypeCheckedOp op -> Bool # (/=) :: TypeCheckedOp op -> TypeCheckedOp op -> Bool # | |
| RenderDoc op => RenderDoc (TypeCheckedOp op) Source # | |
Defined in Morley.Michelson.TypeCheck.TypeCheckedOp Methods renderDoc :: RenderContext -> TypeCheckedOp op -> Doc Source # isRenderable :: TypeCheckedOp op -> Bool Source # | |
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
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.
|
| IllTypedSeq (TcError' op) [IllTypedInstr op] | There is no well-typed prefix, only an error and semi-typed instructions. |
Instances
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.
seqToOps :: TypeCheckedSeq op inp -> [TypeCheckedOp op] Source #
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.