ajhc-0.8.0.8: Haskell compiler that produce binary through C language

Safe HaskellNone

Util.SetLike

Documentation

(\\) :: Unionize s => s -> s -> sSource

type family Elem es :: *Source

type family Key s :: *Source

type family Value m :: *Source

class Collection s => SetLike s whereSource

Methods

keys :: s -> [Key s]Source

member :: Key s -> s -> BoolSource

delete :: Key s -> s -> sSource

sfilter :: (Elem s -> Bool) -> s -> sSource

insert :: Elem s -> s -> sSource

spartition :: (Elem s -> Bool) -> s -> (s, s)Source

notMember :: SetLike s => Key s -> s -> BoolSource

class SetLike m => MapLike m whereSource

Methods

mlookup :: Key m -> m -> Maybe (Value m)Source

values :: m -> [Value m]Source

unionWith :: (Value m -> Value m -> Value m) -> m -> m -> mSource

Instances

minsert :: (MapLike m, Elem m ~ (k, v)) => k -> v -> m -> mSource

msingleton :: (MapLike m, Elem m ~ (k, v)) => k -> v -> mSource

intersects :: (IsEmpty a, Unionize a) => a -> a -> BoolSource

findWithDefault :: MapLike m => Value m -> Key m -> m -> Value mSource

newtype EnumSet a Source

Constructors

EnumSet IntSet 

Instances

newtype EnumMap k v Source

Constructors

EnumMap (IntMap v) 

Instances

Functor (EnumMap k) 
Foldable (EnumMap k) 
Traversable (EnumMap k) 
Eq v => Eq (EnumMap k v) 
Ord v => Ord (EnumMap k v) 
Monoid (EnumMap k v) 
HasSize (EnumMap k v) 
IsEmpty (EnumMap k v) 
Enum k => MapLike (EnumMap k v) 
Enum k => SetLike (EnumMap k v) 
Enum k => Collection (EnumMap k v) 
Unionize (EnumMap k v) 

newtype IntjectionSet a Source

Constructors

IntjectionSet IntSet 

Instances

Show IdSet 
Binary IdSet 
FreeVars TVr IdSet

determine free variables of a binding site

FreeVars E IdSet 
FreeVars ARules IdSet 
FreeVars Rule IdSet

we delete the free variables of the heads of a rule from the rule's free variables. the reason for doing this is that the rule cannot fire if all its heads are in scope, and if it were not done then many functions seem recursive when they arn't actually.

FreeVars Comb IdSet 
Eq (IntjectionSet a) 
Ord (IntjectionSet a) 
(Intjection a, Show a) => Show (IntjectionSet a) 
Monoid (IntjectionSet a) 
HasSize (IntjectionSet a) 
IsEmpty (IntjectionSet a) 
Intjection a => SetLike (IntjectionSet a) 
Intjection a => Collection (IntjectionSet a) 
Unionize (IntjectionSet a) 
FreeVars (Alt E) IdSet