Safe Haskell | None |
---|---|
Language | Haskell2010 |
Morley.Micheline.Expression
Description
Module that defines Expression type, its related types and its JSON instance.
Synopsis
- data Annotation
- data Expression
- data MichelinePrimAp = MichelinePrimAp {}
- newtype MichelinePrimitive = MichelinePrimitive Text
- michelsonPrimitive :: Seq Text
- annotToText :: Annotation -> Text
- annotFromText :: MonadFail m => Text -> m Annotation
Documentation
data Annotation Source #
Constructors
AnnotationType TypeAnn | |
AnnotationVariable VarAnn | |
AnnotationField FieldAnn |
Instances
Eq Annotation Source # | |
Defined in Morley.Micheline.Expression | |
Show Annotation Source # | |
Defined in Morley.Micheline.Expression Methods showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
ToJSON Annotation Source # | |
Defined in Morley.Micheline.Expression Methods toJSON :: Annotation -> Value # toEncoding :: Annotation -> Encoding # toJSONList :: [Annotation] -> Value # toEncodingList :: [Annotation] -> Encoding # | |
FromJSON Annotation Source # | |
Defined in Morley.Micheline.Expression |
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 (Seq Expression) | |
ExpressionPrim MichelinePrimAp |
Instances
Eq Expression Source # | |
Defined in Morley.Micheline.Expression | |
Show Expression Source # | |
Defined in Morley.Micheline.Expression Methods showsPrec :: Int -> Expression -> ShowS # show :: Expression -> String # showList :: [Expression] -> ShowS # | |
ToJSON Expression Source # | |
Defined in Morley.Micheline.Expression Methods toJSON :: Expression -> Value # toEncoding :: Expression -> Encoding # toJSONList :: [Expression] -> Value # toEncodingList :: [Expression] -> Encoding # | |
FromJSON Expression Source # | |
Defined in Morley.Micheline.Expression | |
Buildable Expression Source # | |
Defined in Morley.Micheline.Expression Methods build :: Expression -> Builder # |
data MichelinePrimAp Source #
Constructors
MichelinePrimAp | |
Fields |
Instances
Eq MichelinePrimAp Source # | |
Defined in Morley.Micheline.Expression Methods (==) :: MichelinePrimAp -> MichelinePrimAp -> Bool # (/=) :: MichelinePrimAp -> MichelinePrimAp -> Bool # | |
Show MichelinePrimAp Source # | |
Defined in Morley.Micheline.Expression Methods showsPrec :: Int -> MichelinePrimAp -> ShowS # show :: MichelinePrimAp -> String # showList :: [MichelinePrimAp] -> ShowS # | |
ToJSON MichelinePrimAp Source # | |
Defined in Morley.Micheline.Expression Methods toJSON :: MichelinePrimAp -> Value # toEncoding :: MichelinePrimAp -> Encoding # toJSONList :: [MichelinePrimAp] -> Value # toEncodingList :: [MichelinePrimAp] -> Encoding # | |
FromJSON MichelinePrimAp Source # | |
Defined in Morley.Micheline.Expression Methods parseJSON :: Value -> Parser MichelinePrimAp # parseJSONList :: Value -> Parser [MichelinePrimAp] # |
newtype MichelinePrimitive Source #
Constructors
MichelinePrimitive Text |
Instances
annotToText :: Annotation -> Text Source #
annotFromText :: MonadFail m => Text -> m Annotation Source #