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

Morley.Micheline.Expression

Description

Module that defines Expression type, its related types and its JSON instance.

Synopsis

Documentation

data Annotation Source #

Instances

Instances details
Eq Annotation Source # 
Instance details

Defined in Morley.Micheline.Expression

Data Annotation Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation -> c Annotation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotation #

toConstr :: Annotation -> Constr #

dataTypeOf :: Annotation -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotation) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation) #

gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation #

Show Annotation Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON Annotation Source # 
Instance details

Defined in Morley.Micheline.Expression

FromJSON Annotation Source # 
Instance details

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

Instances details
Eq Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

Data Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expression -> c Expression #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Expression #

toConstr :: Expression -> Constr #

dataTypeOf :: Expression -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Expression) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Expression) #

gmapT :: (forall b. Data b => b -> b) -> Expression -> Expression #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expression -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expression -> r #

gmapQ :: (forall d. Data d => d -> u) -> Expression -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expression -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expression -> m Expression #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expression -> m Expression #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expression -> m Expression #

Show Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

FromJSON Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

Buildable Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

build :: Expression -> Builder #

Plated Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

data MichelinePrimAp Source #

Instances

Instances details
Eq MichelinePrimAp Source # 
Instance details

Defined in Morley.Micheline.Expression

Data MichelinePrimAp Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MichelinePrimAp -> c MichelinePrimAp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MichelinePrimAp #

toConstr :: MichelinePrimAp -> Constr #

dataTypeOf :: MichelinePrimAp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MichelinePrimAp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MichelinePrimAp) #

gmapT :: (forall b. Data b => b -> b) -> MichelinePrimAp -> MichelinePrimAp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MichelinePrimAp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MichelinePrimAp -> r #

gmapQ :: (forall d. Data d => d -> u) -> MichelinePrimAp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MichelinePrimAp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MichelinePrimAp -> m MichelinePrimAp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MichelinePrimAp -> m MichelinePrimAp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MichelinePrimAp -> m MichelinePrimAp #

Show MichelinePrimAp Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON MichelinePrimAp Source # 
Instance details

Defined in Morley.Micheline.Expression

FromJSON MichelinePrimAp Source # 
Instance details

Defined in Morley.Micheline.Expression

newtype MichelinePrimitive Source #

Constructors

MichelinePrimitive Text 

Instances

Instances details
Eq MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

Data MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MichelinePrimitive -> c MichelinePrimitive #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MichelinePrimitive #

toConstr :: MichelinePrimitive -> Constr #

dataTypeOf :: MichelinePrimitive -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MichelinePrimitive) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MichelinePrimitive) #

gmapT :: (forall b. Data b => b -> b) -> MichelinePrimitive -> MichelinePrimitive #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MichelinePrimitive -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MichelinePrimitive -> r #

gmapQ :: (forall d. Data d => d -> u) -> MichelinePrimitive -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MichelinePrimitive -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MichelinePrimitive -> m MichelinePrimitive #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MichelinePrimitive -> m MichelinePrimitive #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MichelinePrimitive -> m MichelinePrimitive #

Ord MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

Show MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

FromJSON MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression