Copyright | (c) Fabricio Olivetti 2021 - 2024 |
---|---|
License | BSD3 |
Maintainer | fabricio.olivetti@gmail.com |
Stability | experimental |
Portability | |
Safe Haskell | None |
Language | Haskell2010 |
Equality Graph data structure Heavily based on hegg (https:/github.comalt-romes/hegg by alt-romes)
Synopsis
- type EClassId = Int
- type ClassIdMap = IntMap
- type ENode = SRTree EClassId
- type ENodeEnc = (Int, Int, Int, Double)
- type EGraphST (m :: Type -> Type) a = StateT EGraph m a
- type Cost = Int
- type CostFun = SRTree Cost -> Cost
- type RangeTree a = Seq (a, EClassId)
- encodeEnode :: ENode -> ENodeEnc
- decodeEnode :: ENodeEnc -> ENode
- insertRange :: (Ord a, Show a) => EClassId -> a -> RangeTree a -> RangeTree a
- removeRange :: (Ord a, Show a) => EClassId -> a -> RangeTree a -> RangeTree a
- getWithinRange :: Ord a => a -> a -> RangeTree a -> [EClassId]
- getSmallest :: Ord a => RangeTree a -> (a, EClassId)
- getGreatest :: Ord a => RangeTree a -> (a, EClassId)
- data EGraph = EGraph {}
- data EGraphDB = EDB {}
- data EClass = EClass {}
- data Consts
- data Property
- data EClassData = EData {}
- type DB = Map (SRTree ()) IntTrie
- data IntTrie = IntTrie {}
- canonicalMap :: Lens' EGraph (ClassIdMap EClassId)
- eClass :: Lens' EGraph (ClassIdMap EClass)
- eDB :: Lens' EGraph EGraphDB
- eNodeToEClass :: Lens' EGraph (Map ENode EClassId)
- eClassId :: Lens' EClass Int
- eNodes :: Lens' EClass (HashSet ENodeEnc)
- height :: Lens' EClass Int
- info :: Lens' EClass EClassData
- parents :: Lens' EClass (HashSet (EClassId, ENode))
- best :: Lens' EClassData ENode
- consts :: Lens' EClassData Consts
- cost :: Lens' EClassData Cost
- fitness :: Lens' EClassData (Maybe Double)
- size :: Lens' EClassData Int
- theta :: Lens' EClassData (Maybe PVector)
- analysis :: Lens' EGraphDB (HashSet (EClassId, ENode))
- fitRangeDB :: Lens' EGraphDB (RangeTree Double)
- nextId :: Lens' EGraphDB Int
- patDB :: Lens' EGraphDB DB
- sizeDB :: Lens' EGraphDB (IntMap IntSet)
- sizeFitDB :: Lens' EGraphDB (IntMap (RangeTree Double))
- unevaluated :: Lens' EGraphDB IntSet
- worklist :: Lens' EGraphDB (HashSet (EClassId, ENode))
- emptyGraph :: EGraph
- emptyDB :: EGraphDB
- createEClass :: EClassId -> ENode -> EClassData -> Int -> EClass
- canonical :: forall (m :: Type -> Type). Monad m => EClassId -> EGraphST m EClassId
- canonize :: forall (m :: Type -> Type). Monad m => ENode -> EGraphST m ENode
- getEClass :: forall (m :: Type -> Type). Monad m => EClassId -> EGraphST m EClass
- trie :: EClassId -> IntMap IntTrie -> IntTrie
- isConst :: forall (m :: Type -> Type). Monad m => EClassId -> EGraphST m Bool
Documentation
type ClassIdMap = IntMap Source #
encodeEnode :: ENode -> ENodeEnc Source #
this assumes up to 999 variables and params
decodeEnode :: ENodeEnc -> ENode Source #
data EClassData Source #
Instances
Show EClassData Source # | |
Defined in Algorithm.EqSat.Egraph showsPrec :: Int -> EClassData -> ShowS # show :: EClassData -> String # showList :: [EClassData] -> ShowS # | |
Eq EClassData Source # | |
Defined in Algorithm.EqSat.Egraph (==) :: EClassData -> EClassData -> Bool # (/=) :: EClassData -> EClassData -> Bool # |
E-Graph basic supporting functions
emptyGraph :: EGraph Source #
returns an empty e-graph
createEClass :: EClassId -> ENode -> EClassData -> Int -> EClass Source #
Creates a new e-class from an e-class id, a new e-node, and the info of this e-class
canonical :: forall (m :: Type -> Type). Monad m => EClassId -> EGraphST m EClassId Source #
gets the canonical id of an e-class
canonize :: forall (m :: Type -> Type). Monad m => ENode -> EGraphST m ENode Source #
canonize the e-node children
getEClass :: forall (m :: Type -> Type). Monad m => EClassId -> EGraphST m EClass Source #
gets an e-class with id c
isConst :: forall (m :: Type -> Type). Monad m => EClassId -> EGraphST m Bool Source #
Check whether an e-class is a constant value