11{-# LANGUAGE TypeApplications #-}
22{-# LANGUAGE BangPatterns #-}
3+ {-# LANGUAGE MagicHash #-}
34-- {-# LANGUAGE ApplicativeDo #-}
45{-# LANGUAGE BlockArguments #-}
56{-# LANGUAGE FlexibleContexts #-}
@@ -24,14 +25,19 @@ module Data.Equality.Graph
2425 , find , canonicalize
2526
2627 -- * Functions on e-graphs
27- , emptyEGraph , newEClass
28+ , emptyEGraph
29+
30+ -- ** Low-level operations
31+ , newEClass , newPointerToClassId
2832
2933 -- * Re-exports
3034 , module Data.Equality.Graph.Classes
3135 , module Data.Equality.Graph.Nodes
3236 , module Data.Equality.Language
3337 ) where
3438
39+ import GHC.Exts (Int (.. ), (+#) , (<#) , isTrue #)
40+
3541-- ROMES:TODO: Is the E-Graph a Monad if the analysis data were the type arg? i.e. Monad (EGraph language)?
3642
3743-- import GHC.Conc
@@ -52,6 +58,7 @@ import Data.Equality.Utils.SizedList
5258
5359import Data.Equality.Graph.Internal
5460import Data.Equality.Graph.ReprUnionFind
61+ import qualified Data.Equality.Utils.IntToIntMap as IIM
5562import Data.Equality.Graph.Classes
5663import Data.Equality.Graph.Nodes
5764import Data.Equality.Analysis
@@ -334,7 +341,30 @@ newEClass adata egr =
334341 , classes = IM. insert new_eclass_id new_eclass (classes egr)
335342 }
336343 )
337- {-# INLINE newEClass #-}
344+ {-# INLINEABLE newEClass #-}
345+
346+ -- | Create a mapping from some class-id that does not exist in the e-graph to
347+ -- the given e-class id target. In practice, this basically creates an
348+ -- alias from the a given class-id to the e-class id of the target
349+ --
350+ -- If, instead, you want to create a mapping from an existing class-id to another one, use 'merge'.
351+ --
352+ -- Under the hood, this operation will bump the union find counter for next-ids
353+ -- to the given id+1 and add an entry to the union find from given id to the
354+ -- given target id.
355+ --
356+ -- INVARIANT: The given e-class pointer does not exist in the e-graph
357+ newPointerToClassId :: ClassId -- ^ Given Id (pointer) that will point to the target
358+ -> ClassId -- ^ The target id
359+ -> EGraph a l -> EGraph a l
360+ newPointerToClassId (I # pointer) (I # target) egr =
361+ egr { unionFind = case unionFind egr of
362+ RUF im _size ->
363+ if isTrue# (pointer <# _size)
364+ then error $ " newPointerToClassId: given pointer id (" ++ show (I # pointer) ++ " ) already exists in the e-graph"
365+ else RUF (IIM. insert pointer target im) (pointer +# 1 # )
366+ }
367+ {-# INLINEABLE newPointerToClassId #-}
338368
339369-- | Represent an expression (in fix-point form) and merge it with the e-class with the given id
340370representAndMerge :: (Analysis a l , Language l ) => ClassId -> Fix l -> EGraph a l -> EGraph a l
0 commit comments