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

Morley.Micheline.Expression.WithMeta

Description

Expression that carries the same extra data for all Exp constructors.

Synopsis

General case

expAllExtraL :: forall x2 x1 meta2 meta1. (ExpExtrasConstrained (IsEq meta1) x1, ExpExtrasConstrained (IsEq meta2) x2) => Traversal (XExp x1) (XExp x2) meta1 meta2 -> Traversal (Exp x1) (Exp x2) meta1 meta2 Source #

Traversal that visits all the extra fields (XExpInt and others) in DFS order assuming they are the same for every constructor.

It is generic enough to work not only with ExpressionWithMeta, but with any Exp that has all the extra fields of the same type; hence, this traversal is applicable to Expression too.

This also supports additional constructors. Use devoid if you have none.

Moreover, when used as setter, it can change the type of meta.

Custom extra field, no extra constructors

data WithMeta (meta :: Type) :: ExpExtensionDescriptorKind Source #

Expression that has the same type of metadata attached to each of its constructors.

Instances

Instances details
ExpExtensionDescriptor (WithMeta m) Source # 
Instance details

Defined in Morley.Micheline.Expression.WithMeta

type XExp (WithMeta m) Source # 
Instance details

Defined in Morley.Micheline.Expression.WithMeta

type XExp (WithMeta m) = Void
type XExpBytes (WithMeta m) Source # 
Instance details

Defined in Morley.Micheline.Expression.WithMeta

type XExpBytes (WithMeta m) = m
type XExpInt (WithMeta m) Source # 
Instance details

Defined in Morley.Micheline.Expression.WithMeta

type XExpInt (WithMeta m) = m
type XExpPrim (WithMeta m) Source # 
Instance details

Defined in Morley.Micheline.Expression.WithMeta

type XExpPrim (WithMeta m) = m
type XExpSeq (WithMeta m) Source # 
Instance details

Defined in Morley.Micheline.Expression.WithMeta

type XExpSeq (WithMeta m) = m
type XExpString (WithMeta m) Source # 
Instance details

Defined in Morley.Micheline.Expression.WithMeta

type XExpString (WithMeta m) = m

type ExpressionWithMeta meta = Exp (WithMeta meta) Source #

Alias for expression with given meta.

expMetaL :: Lens' (Exp (WithMeta meta)) meta Source #

Lens for getting immediate meta of the node.

expAllMetaL :: forall x2 x1 meta2 meta1. (ExpExtrasConstrained (IsEq meta1) x1, ExpExtrasConstrained (IsEq meta2) x2) => Traversal (ExpressionWithMeta meta1) (ExpressionWithMeta meta2) meta1 meta2 Source #

Traversal that visits all the metas in DFS order. This is a specialization of expAllExtraL.

This is pretty similar to expMetaL, but picks meta of all the transitive children.

When used as setter, it can change the type of meta.

Utilities

class a ~ b => IsEq a b Source #

Equality constraint in form of a typeclass.

Instances

Instances details
a ~ b => IsEq (a :: k) (b :: k) Source # 
Instance details

Defined in Morley.Util.Type