hegg-0.5.0.0: Fast equality saturation in Haskell
Safe HaskellNone
LanguageHaskell2010

Data.Equality.Graph.Lens

Contents

Description

Hand-rolled lenses on e-graphs and e-classes which come in quite handy, are heavily used in Graph, and are the only exported way of editing the structure of the e-graph. If you want to write some complex Analysis you'll probably need these.

Synopsis

Documentation

type Lens' s a = forall (f :: Type -> Type). Functor f => (a -> f a) -> s -> f s Source #

A Lens' as defined in lens

type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t Source #

A Lens as defined in lens

type Traversal s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t Source #

A Traversal as defined in lens

_class :: forall a (l :: Type -> Type). ClassId -> Lens' (EGraph a l) (EClass a l) Source #

Lens for the e-class at the representative of the given id in an e-graph

Calls error when the e-class doesn't exist

_memo :: forall a (l :: Type -> Type) f. Functor f => (NodeMap l ClassId -> f (NodeMap l ClassId)) -> EGraph a l -> f (EGraph a l) Source #

Lens for the memo of e-nodes in an e-graph, that is, a mapping from e-nodes to the e-class they're represented in

_classes :: forall a (l :: Type -> Type) b f. Applicative f => (EClass a l -> f (EClass b l)) -> EGraph a l -> f (EGraph b l) Source #

Traversal for the existing classes in an e-graph

_iclasses :: forall a (l :: Type -> Type) b f. Applicative f => ((ClassId, EClass a l) -> f (EClass b l)) -> EGraph a l -> f (EGraph b l) Source #

Traversal for the existing classes in an e-graph

_data :: forall domain (l :: Type -> Type) domain' f. Functor f => (domain -> f domain') -> EClass domain l -> f (EClass domain' l) Source #

Lens for the Domain of an e-class

_parents :: forall a (l :: Type -> Type) f. Functor f => (SList (ClassId, ENode l) -> f (SList (ClassId, ENode l))) -> EClass a l -> f (EClass a l) Source #

Lens for the parent e-classes of an e-class

_nodes :: forall a (l :: Type -> Type) f. Functor f => (Set (ENode l) -> f (Set (ENode l))) -> EClass a l -> f (EClass a l) Source #

Lens for the e-nodes in an e-class

(^.) :: s -> Lens' s a -> a infixl 8 Source #

Like view but with the arguments flipped

(.~) :: Lens' s a -> a -> s -> s infixr 4 Source #

Synonym for set

(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 Source #

Synonym for over

view :: Lens' s a -> s -> a Source #

Applies a getter to a value

set :: Lens' s a -> a -> s -> s Source #

Applies a setter to a value

over :: ASetter s t a b -> (a -> b) -> s -> t Source #

Applies a function to the target

traverseOf :: Traversal s t a b -> forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t Source #

Basically traverse over a Traversal

allOf :: Traversal s t a b -> (a -> Bool) -> s -> Bool Source #

Returns True if every target of a Traversable satisfies a predicate.

Utilities

type ASetter s t a b = (a -> Identity b) -> s -> Identity t Source #

Used instead of Lens in over and %~ to ensure one can call those combinators on Lenss and Traversals. Essentially, it helps type inference in such function applications