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

Overeasy.EquivFind

Description

Synopsis

Documentation

data EquivFind x Source #

A "Union-Find" implementation using explicit equivalence classes. Sure, the asympotics aren't as good, but we eventually have to construct these classes, so we might as well just do it as we go!

Instances

Instances details
Generic (EquivFind x) Source # 
Instance details

Defined in Overeasy.EquivFind

Associated Types

type Rep (EquivFind x) :: Type -> Type #

Methods

from :: EquivFind x -> Rep (EquivFind x) x0 #

to :: Rep (EquivFind x) x0 -> EquivFind x #

Show x => Show (EquivFind x) Source # 
Instance details

Defined in Overeasy.EquivFind

NFData x => NFData (EquivFind x) Source # 
Instance details

Defined in Overeasy.EquivFind

Methods

rnf :: EquivFind x -> () #

Eq x => Eq (EquivFind x) Source # 
Instance details

Defined in Overeasy.EquivFind

Methods

(==) :: EquivFind x -> EquivFind x -> Bool #

(/=) :: EquivFind x -> EquivFind x -> Bool #

type Rep (EquivFind x) Source # 
Instance details

Defined in Overeasy.EquivFind

type Rep (EquivFind x) = D1 ('MetaData "EquivFind" "Overeasy.EquivFind" "overeasy-0.2.0-7Shit7pE5Ru2Ny0HoLxUG4" 'False) (C1 ('MetaCons "EquivFind" 'PrefixI 'True) (S1 ('MetaSel ('Just "efFwd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IntLikeMap x (IntLikeSet x))) :*: S1 ('MetaSel ('Just "efBwd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IntLikeMap x x))))

efFwd :: EquivFind x -> IntLikeMap x (IntLikeSet x) Source #

Map of root to equivalent leaves Invariant: Map keys are only roots Invariant: Sets only contain leaf keys (and not the root itself)

efBwd :: EquivFind x -> IntLikeMap x x Source #

Map of leaf to root Invariant: Map keys are only leaves, values are only roots

efRootsSize :: EquivFind x -> Int Source #

Number of roots in the equiv.

efLeavesSize :: EquivFind x -> Int Source #

Number of leaves in the equiv.

efTotalSize :: EquivFind x -> Int Source #

Total number of keys in the equiv.

efCanonicalize :: (Traversable f, Coercible x Int) => f x -> EquivFind x -> Either x (f x) Source #

Canonicalize the given expression functor by replacing leaves with roots. If any elements are missing, the first is returned.

efCanonicalizePartial :: (Functor f, Coercible x Int) => f x -> EquivFind x -> f x Source #

Canonicalize the given expression functor by replacing leaves with roots. If any elements are missing, they are simply skipped.

efNew :: EquivFind x Source #

Creates an empty equiv

efSingleton :: Coercible x Int => x -> EquivFind x Source #

Creates a singleton equiv

efMember :: Coercible x Int => x -> EquivFind x -> Bool Source #

Is the key in the equiv?

efRoots :: Coercible x Int => EquivFind x -> [x] Source #

List all roots in the equiv.

efLeaves :: Coercible x Int => EquivFind x -> [x] Source #

List all leaves in the equiv.

efMembers :: Coercible x Int => EquivFind x -> [x] Source #

List all members (roots and leaves) in the equiv.

data EquivAddRes x Source #

Result of adding something to the equiv, if you're interested.

Instances

Instances details
Generic (EquivAddRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

Associated Types

type Rep (EquivAddRes x) :: Type -> Type #

Methods

from :: EquivAddRes x -> Rep (EquivAddRes x) x0 #

to :: Rep (EquivAddRes x) x0 -> EquivAddRes x #

Show x => Show (EquivAddRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

NFData x => NFData (EquivAddRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

Methods

rnf :: EquivAddRes x -> () #

Eq x => Eq (EquivAddRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

type Rep (EquivAddRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

type Rep (EquivAddRes x) = D1 ('MetaData "EquivAddRes" "Overeasy.EquivFind" "overeasy-0.2.0-7Shit7pE5Ru2Ny0HoLxUG4" 'False) (C1 ('MetaCons "EquivAddResAlreadyRoot" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EquivAddResAlreadyLeafOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 x)) :+: C1 ('MetaCons "EquivAddResNewRoot" 'PrefixI 'False) (U1 :: Type -> Type)))

efAddInc :: Coercible x Int => x -> EquivFind x -> (EquivAddRes x, EquivFind x) Source #

Add the given key to the equiv (raw version).

efAdd :: Coercible x Int => x -> State (EquivFind x) (EquivAddRes x) Source #

Add the given key to the equiv (raw version).

efEquivs :: Coercible x Int => x -> EquivFind x -> IntLikeSet x Source #

All keys equivalent to the given key in the equiv. Always returns a set with the given key, even if it's not present.

efClosure :: Coercible x Int => [x] -> EquivFind x -> IntLikeSet x Source #

Set of all keys equivalent to the given keys in the equiv.

efFindRoot :: Coercible x Int => x -> EquivFind x -> Maybe x Source #

Find the root equivalent to the given key (if it exists).

efFindLeaves :: Coercible x Int => x -> EquivFind x -> Maybe (IntLikeSet x) Source #

Find the leaves equivalent to the given key (if they exist).

efSubset :: Coercible x Int => [x] -> EquivFind x -> EquivFind x Source #

Returns an EquivFind subset representing the given list of keys.

efLookupRoot :: Coercible x Int => x -> EquivFind x -> x Source #

Like efFindRoot but returns same key if not found - does not guarantee presence in map.

efLookupLeaves :: Coercible x Int => x -> EquivFind x -> IntLikeSet x Source #

Like efFindLeaves but returns empty set if not found - does not guarantee presence in map.

efFindAll :: Coercible x Int => [x] -> EquivFind x -> Either x (IntLikeSet x) Source #

Returns the set of roots for the given set of keys, or an error with the first key not found in the equiv.

data EquivMergeRes x Source #

The result of trying to merge two keys, if you care.

Instances

Instances details
Generic (EquivMergeRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

Associated Types

type Rep (EquivMergeRes x) :: Type -> Type #

Methods

from :: EquivMergeRes x -> Rep (EquivMergeRes x) x0 #

to :: Rep (EquivMergeRes x) x0 -> EquivMergeRes x #

Show x => Show (EquivMergeRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

NFData x => NFData (EquivMergeRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

Methods

rnf :: EquivMergeRes x -> () #

Eq x => Eq (EquivMergeRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

type Rep (EquivMergeRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

type Rep (EquivMergeRes x) = D1 ('MetaData "EquivMergeRes" "Overeasy.EquivFind" "overeasy-0.2.0-7Shit7pE5Ru2Ny0HoLxUG4" 'False) (C1 ('MetaCons "EquivMergeResMissing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 x)) :+: (C1 ('MetaCons "EquivMergeResUnchanged" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 x)) :+: C1 ('MetaCons "EquivMergeResChanged" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 x) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IntLikeSet x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EquivFind x))))))

efUnsafeMerge :: (Coercible x Int, Ord x) => x -> x -> EquivFind x -> (x, IntLikeSet x, EquivFind x) Source #

Don't even think about it, it's got unsafe in the name.

efMergeInc :: (Coercible x Int, Ord x) => x -> x -> EquivFind x -> EquivMergeRes x Source #

Merge two keys (raw version).

efMerge :: (Coercible x Int, Ord x) => x -> x -> State (EquivFind x) (Maybe (x, IntLikeSet x)) Source #

Merge two keys (state version).

data EquivMergeSetsRes x Source #

The result of trying to merge multiple sets of keys, if you care.

Instances

Instances details
Generic (EquivMergeSetsRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

Associated Types

type Rep (EquivMergeSetsRes x) :: Type -> Type #

Show x => Show (EquivMergeSetsRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

NFData x => NFData (EquivMergeSetsRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

Methods

rnf :: EquivMergeSetsRes x -> () #

Eq x => Eq (EquivMergeSetsRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

type Rep (EquivMergeSetsRes x) Source # 
Instance details

Defined in Overeasy.EquivFind

type Rep (EquivMergeSetsRes x) = D1 ('MetaData "EquivMergeSetsRes" "Overeasy.EquivFind" "overeasy-0.2.0-7Shit7pE5Ru2Ny0HoLxUG4" 'False) ((C1 ('MetaCons "EquivMergeSetsResEmptySet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EquivMergeSetsResMissing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 x))) :+: (C1 ('MetaCons "EquivMergeSetsResUnchanged" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IntLikeSet x))) :+: C1 ('MetaCons "EquivMergeSetsResChanged" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IntLikeSet x)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IntLikeSet x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EquivFind x))))))

efMergeSetsInc :: Coercible x Int => [IntLikeSet x] -> EquivFind x -> EquivMergeSetsRes x Source #

Merge sets of keys (raw version).

efMergeSets :: Coercible x Int => [IntLikeSet x] -> State (EquivFind x) (Maybe (IntLikeSet x, IntLikeSet x)) Source #

Merge sets of keys (state version).

efCanCompact :: EquivFind x -> Bool Source #

Are they compactible keys?

efCompactInc :: Coercible x Int => EquivFind x -> (IntLikeMap x (IntLikeSet x), EquivFind x) Source #

See efCompact (this is the raw version).

efCompact :: Coercible x Int => State (EquivFind x) (IntLikeMap x (IntLikeSet x)) Source #

Removes leaves and returns map of root to deleted leaf.

efRemoveAllInc :: Coercible x Int => [x] -> EquivFind x -> (IntLikeMap x x, EquivFind x) Source #

See efRemoveAll (this is the raw version).

efRemoveAll :: Coercible x Int => [x] -> State (EquivFind x) (IntLikeMap x x) Source #

Removes the given keys from the equiv map. If a key is a leaf or singleton root, simply remove it. If it is a root of a larger class, select the min leaf and make it root. Returns a map of old roots to new roots (only those changed in the process - possibly empty). If a key is not found, it is simply ignored.

efUnsafeAddLeafInc :: Coercible x Int => x -> x -> EquivFind x -> EquivFind x Source #

Given root, add leaf. Requires that root be present in the map and that leaf would be picked as a leaf. (Therefore, unsafe.) Exposed for efficient merging.