Safe Haskell | None |
---|---|
Language | Haskell2010 |
Morley.Micheline.Expression
Description
Module that defines Expression type, its related types and its JSON instance.
Synopsis
- data Expression where
- data MichelinePrimAp = MichelinePrimAp {
- mpaPrim :: MichelinePrimitive
- mpaArgs :: [Expression]
- mpaAnnots :: [Annotation]
- newtype MichelinePrimitive = MichelinePrimitive Text
- michelsonPrimitive :: Seq Text
- data Annotation
- annotToText :: Annotation -> Text
- annotFromText :: forall m. MonadFail m => Text -> m Annotation
- isAnnotationField :: Annotation -> Bool
- isAnnotationType :: Annotation -> Bool
- isAnnotationVariable :: Annotation -> Bool
- isNoAnn :: Annotation -> Bool
- mkAnns :: [TypeAnn] -> [FieldAnn] -> [VarAnn] -> [Annotation]
- toAnnSet :: [Annotation] -> AnnotationSet
- _ExpressionInt :: Prism' Expression Integer
- _ExpressionString :: Prism' Expression Text
- _ExpressionBytes :: Prism' Expression ByteString
- _ExpressionSeq :: Prism' Expression [Expression]
- _ExpressionPrim :: Prism' Expression MichelinePrimAp
- _AnnotationField :: Prism' Annotation FieldAnn
- _AnnotationVariable :: Prism' Annotation VarAnn
- _AnnotationType :: Prism' Annotation TypeAnn
- mpaPrimL :: Lens' MichelinePrimAp MichelinePrimitive
- mpaArgsL :: Lens' MichelinePrimAp [Expression]
- mpaAnnotsL :: Lens' MichelinePrimAp [Annotation]
Documentation
data Expression Source #
Type for Micheline Expression
Constructors
ExpressionInt Integer | Micheline represents both nats and ints using the same decimal format. The Haskell Integer type spans all possible values that the final (Michelson) type could end up being, and then some, so we use (StringEncode Integer) to represent all integral values here for easy JSON encoding compatibility. |
ExpressionString Text | |
ExpressionBytes ByteString | |
ExpressionSeq [Expression] | |
ExpressionPrim MichelinePrimAp |
Bundled Patterns
pattern PrimExpr :: Text -> [Expression] -> [Annotation] -> Expression |
Instances
data MichelinePrimAp Source #
Constructors
MichelinePrimAp | |
Fields
|
Instances
newtype MichelinePrimitive Source #
Constructors
MichelinePrimitive Text |
Instances
data Annotation Source #
Constructors
AnnotationType TypeAnn | |
AnnotationVariable VarAnn | |
AnnotationField FieldAnn |
Instances
annotToText :: Annotation -> Text Source #
annotFromText :: forall m. MonadFail m => Text -> m Annotation Source #
isAnnotationField :: Annotation -> Bool Source #
isAnnotationType :: Annotation -> Bool Source #
isNoAnn :: Annotation -> Bool Source #
toAnnSet :: [Annotation] -> AnnotationSet Source #