overeasy-0.2.0: A purely functional E-Graph library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Overeasy.EGraph

Description

See EGraph.

Synopsis

Documentation

newtype EClassId Source #

An opaque class id. Constructor exported for coercibility. Num instance for literals only.

Constructors

EClassId 

Fields

Instances

Instances details
Enum EClassId Source # 
Instance details

Defined in Overeasy.EGraph

Num EClassId Source # 
Instance details

Defined in Overeasy.EGraph

Show EClassId Source # 
Instance details

Defined in Overeasy.EGraph

NFData EClassId Source # 
Instance details

Defined in Overeasy.EGraph

Methods

rnf :: EClassId -> () #

Eq EClassId Source # 
Instance details

Defined in Overeasy.EGraph

Ord EClassId Source # 
Instance details

Defined in Overeasy.EGraph

Hashable EClassId Source # 
Instance details

Defined in Overeasy.EGraph

Methods

hashWithSalt :: Int -> EClassId -> Int #

hash :: EClassId -> Int #

newtype ENodeId Source #

An opaque node id Constructor exported for coercibility. Num instance for literals only.

Constructors

ENodeId 

Fields

Instances

Instances details
Enum ENodeId Source # 
Instance details

Defined in Overeasy.EGraph

Num ENodeId Source # 
Instance details

Defined in Overeasy.EGraph

Show ENodeId Source # 
Instance details

Defined in Overeasy.EGraph

NFData ENodeId Source # 
Instance details

Defined in Overeasy.EGraph

Methods

rnf :: ENodeId -> () #

Eq ENodeId Source # 
Instance details

Defined in Overeasy.EGraph

Methods

(==) :: ENodeId -> ENodeId -> Bool #

(/=) :: ENodeId -> ENodeId -> Bool #

Ord ENodeId Source # 
Instance details

Defined in Overeasy.EGraph

Hashable ENodeId Source # 
Instance details

Defined in Overeasy.EGraph

Methods

hashWithSalt :: Int -> ENodeId -> Int #

hash :: ENodeId -> Int #

type EAnalysis d f = f d -> d Source #

The definition of an EGraph analysis. d must be a join semilattice. This function must be monotonic.

noAnalysis :: EAnalysis () f Source #

A disabled analysis

data EClassInfo d f Source #

Info stored for every class: analysis data, class members (nodes), and parent nodes.

Constructors

EClassInfo 

Fields

Instances

Instances details
Generic (EClassInfo d f) Source # 
Instance details

Defined in Overeasy.EGraph

Associated Types

type Rep (EClassInfo d f) :: Type -> Type #

Methods

from :: EClassInfo d f -> Rep (EClassInfo d f) x #

to :: Rep (EClassInfo d f) x -> EClassInfo d f #

(Show d, Show (f ())) => Show (EClassInfo d f) Source # 
Instance details

Defined in Overeasy.EGraph

Methods

showsPrec :: Int -> EClassInfo d f -> ShowS #

show :: EClassInfo d f -> String #

showList :: [EClassInfo d f] -> ShowS #

(NFData d, NFData (f ())) => NFData (EClassInfo d f) Source # 
Instance details

Defined in Overeasy.EGraph

Methods

rnf :: EClassInfo d f -> () #

(Eq d, Eq (f ())) => Eq (EClassInfo d f) Source # 
Instance details

Defined in Overeasy.EGraph

Methods

(==) :: EClassInfo d f -> EClassInfo d f -> Bool #

(/=) :: EClassInfo d f -> EClassInfo d f -> Bool #

type Rep (EClassInfo d f) Source # 
Instance details

Defined in Overeasy.EGraph

type Rep (EClassInfo d f) = D1 ('MetaData "EClassInfo" "Overeasy.EGraph" "overeasy-0.2.0-7Shit7pE5Ru2Ny0HoLxUG4" 'False) (C1 ('MetaCons "EClassInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "eciData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 d) :*: (S1 ('MetaSel ('Just "eciNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Assoc ENodeId (f ()))) :*: S1 ('MetaSel ('Just "eciParents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IntLikeSet ENodeId)))))

data EGraph d f Source #

An E-Graph implementation

Instances

Instances details
Generic (EGraph d f) Source # 
Instance details

Defined in Overeasy.EGraph

Associated Types

type Rep (EGraph d f) :: Type -> Type #

Methods

from :: EGraph d f -> Rep (EGraph d f) x #

to :: Rep (EGraph d f) x -> EGraph d f #

(Show d, Show (f EClassId), Show (f ())) => Show (EGraph d f) Source # 
Instance details

Defined in Overeasy.EGraph

Methods

showsPrec :: Int -> EGraph d f -> ShowS #

show :: EGraph d f -> String #

showList :: [EGraph d f] -> ShowS #

(NFData d, NFData (f EClassId), NFData (f ())) => NFData (EGraph d f) Source # 
Instance details

Defined in Overeasy.EGraph

Methods

rnf :: EGraph d f -> () #

(Eq d, Eq (f EClassId), Eq (f ())) => Eq (EGraph d f) Source # 
Instance details

Defined in Overeasy.EGraph

Methods

(==) :: EGraph d f -> EGraph d f -> Bool #

(/=) :: EGraph d f -> EGraph d f -> Bool #

type Rep (EGraph d f) Source # 
Instance details

Defined in Overeasy.EGraph

type WorkItem = IntLikeSet EClassId Source #

A set of class ids to merge

type WorkList = Seq WorkItem Source #

A sequences of groups of class ids to mrege

type ClassReplacements = EquivFind EClassId Source #

An invertible multimap of new root class to the sets of old classes it subsumes Can be used to externally recanonicalize any structures that reference class ids after merges.

data MergeResult a Source #

Merging classes can result in a few outcomes:

Constructors

MergeResultUnchanged

All classes already merged, no change

MergeResultMissing !WorkItem

Some classes missing, returns first problematic worklist entry (note that not all classes in worklist item will be missing, only at least one from the set)

MergeResultChanged !a

Some classes merged, returns root map or merged class id

Instances

Instances details
Foldable MergeResult Source # 
Instance details

Defined in Overeasy.EGraph

Methods

fold :: Monoid m => MergeResult m -> m #

foldMap :: Monoid m => (a -> m) -> MergeResult a -> m #

foldMap' :: Monoid m => (a -> m) -> MergeResult a -> m #

foldr :: (a -> b -> b) -> b -> MergeResult a -> b #

foldr' :: (a -> b -> b) -> b -> MergeResult a -> b #

foldl :: (b -> a -> b) -> b -> MergeResult a -> b #

foldl' :: (b -> a -> b) -> b -> MergeResult a -> b #

foldr1 :: (a -> a -> a) -> MergeResult a -> a #

foldl1 :: (a -> a -> a) -> MergeResult a -> a #

toList :: MergeResult a -> [a] #

null :: MergeResult a -> Bool #

length :: MergeResult a -> Int #

elem :: Eq a => a -> MergeResult a -> Bool #

maximum :: Ord a => MergeResult a -> a #

minimum :: Ord a => MergeResult a -> a #

sum :: Num a => MergeResult a -> a #

product :: Num a => MergeResult a -> a #

Traversable MergeResult Source # 
Instance details

Defined in Overeasy.EGraph

Methods

traverse :: Applicative f => (a -> f b) -> MergeResult a -> f (MergeResult b) #

sequenceA :: Applicative f => MergeResult (f a) -> f (MergeResult a) #

mapM :: Monad m => (a -> m b) -> MergeResult a -> m (MergeResult b) #

sequence :: Monad m => MergeResult (m a) -> m (MergeResult a) #

Functor MergeResult Source # 
Instance details

Defined in Overeasy.EGraph

Methods

fmap :: (a -> b) -> MergeResult a -> MergeResult b #

(<$) :: a -> MergeResult b -> MergeResult a #

Show a => Show (MergeResult a) Source # 
Instance details

Defined in Overeasy.EGraph

Eq a => Eq (MergeResult a) Source # 
Instance details

Defined in Overeasy.EGraph

egClassSource :: EGraph d f -> Source EClassId Source #

Id source for classes

egNodeSource :: EGraph d f -> Source ENodeId Source #

Id source for nodes

egEquivFind :: EGraph d f -> EquivFind EClassId Source #

Class equivalences

egClassMap :: EGraph d f -> IntLikeMap EClassId (EClassInfo d f) Source #

Map of class to info Invariant: Only contains root classes.

egNodeAssoc :: EGraph d f -> Assoc ENodeId (f EClassId) Source #

Assoc of node id to node structure Invariant: only contains canonical structures (with root classes).

egHashCons :: EGraph d f -> IntLikeMap ENodeId EClassId Source #

Map of node to class Invariant: only contains root classes.

egClassSize :: EGraph d f -> Int Source #

Number of equivalent classes in the EGraph (see ufSize)

egNodeSize :: EGraph d f -> Int Source #

Number of nodes in the EGraph

egFindNode :: (Eq (f EClassId), Hashable (f EClassId)) => f EClassId -> EGraph d f -> Maybe EClassId Source #

Find the class of the given node, if it exists. Note that you may have to canonicalize first to find it!

egFindTerm :: (RecursiveWhole t f, Traversable f, Eq (f EClassId), Hashable (f EClassId)) => t -> EGraph d f -> Maybe EClassId Source #

Find the class of the given term, if it exists

egClassInfo :: EClassId -> EGraph d f -> Maybe (EClassInfo d f) Source #

Lookup info for the given EClass

egNew :: EGraph d f Source #

Creates a new EGraph

egClasses :: State (EGraph d f) (IntLikeSet EClassId) Source #

Yields all root classes

egCanonicalize :: Traversable f => f EClassId -> State (EGraph d f) (Either EClassId (f EClassId)) Source #

Find the canonical form of a node. If any classes are missing, the first missing is returned.

egCanonicalizePartial :: Traversable f => f EClassId -> State (EGraph d f) (f EClassId) Source #

Find the canonical form of a node. If any classes are missing, simply skip them.

egAddTerm :: (RecursiveWhole t f, Traversable f, Eq (f EClassId), Hashable (f EClassId), Hashable (f ())) => EAnalysis d f -> t -> State (EGraph d f) (Changed, EClassId) Source #

Adds a term (recursively) to the graph. If already in the graph, returns ChangedNo and existing class id. Otherwise returns ChangedYes and a new class id.

egMerge :: (Semigroup d, Traversable f, Eq (f EClassId), Hashable (f EClassId), Eq (f ()), Hashable (f ())) => EClassId -> EClassId -> State (EGraph d f) (MergeResult EClassId) Source #

Merges two classes: Returns Nothing if the classes are not found or if they're already equal. Otherwise returns the class remapping. Note that it's MUCH more efficient to accumulate a WorkList and use egMergeMany.

egMergeMany :: (Semigroup d, Traversable f, Eq (f EClassId), Hashable (f EClassId), Eq (f ()), Hashable (f ())) => WorkList -> State (EGraph d f) (MergeResult (ClassReplacements, IntLikeSet EClassId)) Source #

Merges many sets of classes. Returns Nothing if the classes are not found or if they're already equal. Otherwise returns the class remapping (equiv map of root to set of leaf classes). It is important to note that the leaf classes in the returned mapping have been REMOVED from the egraph, so they cannot be used to lookup classes in the future. Therefore, if you have any class ids stored externally, you'll want to (partially) canonicalize with the returned mapping. Also note that the analysis of a given class is going to be an UNDER-APPROXIMATION of the true analysis value, because per-node analyses are not recomputed.

egReanalyzeSubset :: (Eq d, Semigroup d, Functor f) => EAnalysis d f -> IntLikeSet EClassId -> State (EGraph d f) () Source #

Reanalyze a subset of classes - touched roots from merging is sufficient to ensure complete reanalysis. (Note this is implemented in a simplistic way, just taking the fixed point of rounds of analysis. The number of rounds can be no more than the size of the given set.) It may be necessary to call this because merging may leave class analyses in an under-approximating state. This method gives you the true analysis by fixed point.

egReanalyze :: (Eq d, Semigroup d, Functor f) => EAnalysis d f -> State (EGraph d f) () Source #

Reanalyze all classes in the graph.