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

Morley.Michelson.Typed.AnnotatedValue

Contents

Synopsis

Documentation

data AnnotatedValue v Source #

Constructors

AnnotatedValue 

Fields

Optics

value :: IsoValue v => Lens' (AnnotatedValue v) v Source #

Extract the value out of an annotated value.

castTo :: forall v1 v2. (IsoValue v1, IsoValue v2) => Prism SomeAnnotatedValue SomeAnnotatedValue (AnnotatedValue v1) (AnnotatedValue v2) Source #

Attempts to cast to the given type.

variant :: FieldAnn -> Traversal' SomeAnnotatedValue SomeAnnotatedValue Source #

Matches on a (possibly nested) or, and focuses the value if its field annotation is a match.

Note that field annotations do not have to be unique. If two or branches have the same field annotation, variant will match on either branch.

>>> :{
val = SomeAnnotatedValue
  [notes|or (int %first) (or (nat %second) (int %third))|]
  (toVal (Right (Left 3) :: Either Integer (Either Natural Integer)))
:}
>>> val ^? variant [fieldAnnQ|second|] . to pretty
Just "3 :: nat"
>>> val ^? variant [fieldAnnQ|first|] . to pretty
Nothing

fields :: IndexedTraversal' FieldAnn SomeAnnotatedValue SomeAnnotatedValue Source #

Traverses all nodes in a tree of pairs that have a field annotation. The elements are indexed by their field annotations.

Note that sub-trees are not inspected. For example, for this type:

pair
  (int %storageField1)
  (pair %storageField2
    (int %nestedField1)
    (string %nestedField2)
  )

fields will:

  • ignore the top-level node, because it does not have a field annotation.
  • traverse the storageField1 and storageField2 fields.
  • ignore nestedField1 and nestedField2, because they're in a sub-tree of a traversed node.

Note that field annotations do not have to be unique. If two fields have the same field annotation, both will be indexed/traversed.

>>> :{
val = SomeAnnotatedValue
  [notes|pair (int %first) (nat %second) (int %third)|]
  (toVal ((1, 2, 3) :: (Integer, Natural, Integer)))
:}
>>> mapM_ print $ map (bimap pretty pretty) $ val ^@.. fields
("%first","1 :: int")
("%second","2 :: nat")
("%third","3 :: int")

field :: FieldAnn -> Traversal' SomeAnnotatedValue SomeAnnotatedValue Source #

Looks up a member of a tree of pairs by its field annotation. Note that sub-trees of nodes with field annotations are not inspected.

Note that field annotations do not have to be unique. If two fields have the same field annotation, both will be indexed/traversed.

>>> :{
val = SomeAnnotatedValue
  [notes|pair (int %first) (nat %second) (int %third)|]
  (toVal ((1, 2, 3) :: (Integer, Natural, Integer)))
:}
>>> val ^? field [fieldAnnQ|second|] . castTo @Natural . value
Just 2

nodes :: IndexedFold FieldAnn SomeAnnotatedValue SomeAnnotatedValue Source #

Lists all nodes in a tree of pairs. The elements are indexed by their field annotations.

Note that field annotations do not have to be unique. If two fields have the same field annotation, both will be indexed.

>>> :{
val = SomeAnnotatedValue
  [notes|pair (int %first) (nat %second) (int %third)|]
  (toVal ((1, 2, 3) :: (Integer, Natural, Integer)))
:}
>>> mapM_ print $ map (bimap pretty pretty) $ val ^@.. nodes
("%first","1 :: int")
("%","Pair 2 3 :: pair (nat %second) (int %third)")
("%second","2 :: nat")
("%third","3 :: int")

node :: FieldAnn -> Fold SomeAnnotatedValue SomeAnnotatedValue Source #

Looks up nodes in a tree of pairs with the given field annotation.

asList :: Fold SomeAnnotatedValue [SomeAnnotatedValue] Source #

Casts a SomeAnnotatedValue to a list.

>>> list = [ [mt|hello|], [mt|world|] ]
>>> val = SomeAnnotatedValue starNotes (toVal list)
>>> val ^? asList . ix 1 . castTo @MText . value . to pretty
Just "world"

asMap :: forall key. (IsoValue key, Ord key) => Fold SomeAnnotatedValue (Map key SomeAnnotatedValue) Source #

Casts a SomeAnnotatedValue to a map.

>>> map = Map.fromList @Integer @Bool [(10, False), (20, True)]
>>> val = SomeAnnotatedValue starNotes (toVal map)
>>> val ^? asMap @Integer . ix 20 . castTo @Bool . value
Just True