morley-1.17.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Micheline.Expression

Contents

Description

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

Synopsis

Documentation

data Exp x Source #

Type for Micheline Expression with extension points.

Following the Trees-that-Grow approach, this type provides the core set of constructors used by Tezos accompanied with additional data (XExp*). Plus additional constructors provided by XExp.

The type argument x will be called extension descriptor and it must have ExpExtensionDescriptor instance.

Bundled Patterns

pattern ExpPrim' :: XExpPrim x -> MichelinePrimitive -> [Exp x] -> [Annotation] -> Exp x 

Instances

Instances details
FromJSON Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

Buildable Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

build :: Expression -> Builder #

ToExpression Expression Source # 
Instance details

Defined in Morley.Micheline.Class

ExpAllExtrasConstrainted (Lift :: Type -> Constraint) x => Lift (Exp x :: Type) Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

lift :: Quote m => Exp x -> m Exp0 #

liftTyped :: forall (m :: Type -> Type). Quote m => Exp x -> Code m (Exp x) #

(ExpAllExtrasConstrainted Data x, Typeable x) => Data (Exp x) 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) -> Exp x -> c (Exp x) #

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

toConstr :: Exp x -> Constr #

dataTypeOf :: Exp x -> DataType #

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

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

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

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

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

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

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

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

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

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

ExpAllExtrasConstrainted Show x => Show (Exp x) Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> Exp x -> ShowS #

show :: Exp x -> String #

showList :: [Exp x] -> ShowS #

ExpAllExtrasConstrainted Eq x => Eq (Exp x) Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

(==) :: Exp x -> Exp x -> Bool #

(/=) :: Exp x -> Exp x -> Bool #

(Typeable x, ExpAllExtrasConstrainted Data x, ExpAllExtrasConstrainted (Typeable :: Type -> Constraint) x) => Plated (Exp x) Source #

Default instance that uses uniplate as implementation.

If it tries to find expressions for polymorphic types too agressively (requiring Data where you don't what that), feel free to define an overlapping manual instance.

Instance details

Defined in Morley.Micheline.Expression

Methods

plate :: Traversal' (Exp x) (Exp x) #

data RegularExp :: ExpExtensionDescriptorKind Source #

Extension descriptor for plain expressions without additional data.

Instances

Instances details
FromJSON Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

Exception FromExpressionError Source # 
Instance details

Defined in Morley.Micheline.Class

Buildable FromExpressionError Source # 
Instance details

Defined in Morley.Micheline.Class

Buildable Expression Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

build :: Expression -> Builder #

ToExpression Expression Source # 
Instance details

Defined in Morley.Micheline.Class

ExpExtensionDescriptor RegularExp Source # 
Instance details

Defined in Morley.Micheline.Expression

FromExp RegularExp ExpandedOp Source # 
Instance details

Defined in Morley.Micheline.Class

(SingI inp, SingI out) => FromExp RegularExp (Instr '[inp] '[out]) Source # 
Instance details

Defined in Morley.Micheline.Class

type XExp RegularExp Source # 
Instance details

Defined in Morley.Micheline.Expression

type XExpBytes RegularExp Source # 
Instance details

Defined in Morley.Micheline.Expression

type XExpInt RegularExp Source # 
Instance details

Defined in Morley.Micheline.Expression

type XExpPrim RegularExp Source # 
Instance details

Defined in Morley.Micheline.Expression

type XExpSeq RegularExp Source # 
Instance details

Defined in Morley.Micheline.Expression

type XExpString RegularExp Source # 
Instance details

Defined in Morley.Micheline.Expression

type Expression = Exp RegularExp Source #

Simple expression without any extras.

data MichelinePrimAp x Source #

Instances

Instances details
Lift (Exp x) => Lift (MichelinePrimAp x :: Type) Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

lift :: Quote m => MichelinePrimAp x -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => MichelinePrimAp x -> Code m (MichelinePrimAp x) #

FromJSON (Exp x) => FromJSON (MichelinePrimAp x) Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON (Exp x) => ToJSON (MichelinePrimAp x) Source # 
Instance details

Defined in Morley.Micheline.Expression

(Data (Exp x), Typeable x) => Data (MichelinePrimAp x) 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 x -> c (MichelinePrimAp x) #

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

toConstr :: MichelinePrimAp x -> Constr #

dataTypeOf :: MichelinePrimAp x -> DataType #

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

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

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

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

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

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

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

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

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

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

Show (Exp x) => Show (MichelinePrimAp x) Source # 
Instance details

Defined in Morley.Micheline.Expression

Eq (Exp x) => Eq (MichelinePrimAp x) Source # 
Instance details

Defined in Morley.Micheline.Expression

newtype MichelinePrimitive Source #

Constructors

MichelinePrimitive Text 

Instances

Instances details
FromJSON MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON 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 #

IsString MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

Show MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

Eq MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

Ord MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

Lift MichelinePrimitive Source # 
Instance details

Defined in Morley.Micheline.Expression

type ExpExtensionDescriptorKind = ExpExtensionTag -> Type Source #

Kind of extension descriptors.

We use a dedicated open type for this, not just Type, to notice earlier when type arguments are mis-placed.

class ExpExtensionDescriptor (x :: ExpExtensionDescriptorKind) Source #

Defines details of extension descriptor.

Associated Types

type XExpInt x :: Type Source #

Additional data in ExpInt constructor.

type XExpInt _ = ()

type XExpString x :: Type Source #

Additional data in ExpString constructor.

type XExpString _ = ()

type XExpBytes x :: Type Source #

Additional data in ExpBytes constructor.

type XExpBytes _ = ()

type XExpSeq x :: Type Source #

Additional data in ExpSeq constructor.

type XExpSeq _ = ()

type XExpPrim x :: Type Source #

Additional data in ExpPrim constructor.

type XExpPrim _ = ()

type XExp x :: Type Source #

Additional constructors.

type XExp _ = Void

type ExpExtrasConstrained c x = Each '[c] [XExpInt x, XExpString x, XExpBytes x, XExpSeq x, XExpPrim x] Source #

Constraint all the extra fields provided by this extension.

type ExpAllExtrasConstrainted c x = (ExpExtrasConstrained c x, c (XExp x)) Source #

Constraint all the extra fields and the constructor provided by this extension.

data ExpExtras f x Source #

A helper type that carries something for all extra fields.

Fields are carried in the given functor f so that one could provide a generator, parser or something else.

Extra constructor is not included here as it may need special treatment, you have to carry it separately.

Constructors

ExpExtras 

Fields

mkUniformExpExtras :: (extra ~ XExpInt x, extra ~ XExpString x, extra ~ XExpBytes x, extra ~ XExpSeq x, extra ~ XExpPrim x) => f extra -> ExpExtras f x Source #

Fill ExpExtras with the same data, assuming all types of extras are the same.

hoistExpExtras :: (forall extra. f1 extra -> f2 extra) -> ExpExtras f1 x -> ExpExtras f2 x Source #

Change the functor used in ExpExtras.

data Annotation Source #

Instances

Instances details
FromJSON Annotation Source # 
Instance details

Defined in Morley.Micheline.Expression

ToJSON 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

Eq Annotation Source # 
Instance details

Defined in Morley.Micheline.Expression

Lift Annotation Source # 
Instance details

Defined in Morley.Micheline.Expression

Methods

lift :: Quote m => Annotation -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Annotation -> Code m Annotation #

Prisms

_ExpSeq :: Prism' (Exp d) (XExpSeq d, [Exp d]) Source #

Lenses

mpaArgsL :: forall x x. Lens (MichelinePrimAp x) (MichelinePrimAp x) [Exp x] [Exp x] Source #