ixmonad-0.57: Embeds effect systems into Haskell using parameteric effect monads

Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Effect.Helpers.Set

Documentation

data Set n where Source

Constructors

Empty :: Set [] 
Ext :: e -> Set s -> Set (e : s) 

Instances

(Show e, Show' (Set s)) => Show (Set ((:) * e s)) 
Show (Set ([] *)) 

type Union s t = Nub (Sort (Append s t)) Source

type Unionable s t = (Sortable (Append s t), Nubable (Sort (Append s t))) Source

union :: Unionable s t => Set s -> Set t -> Set (Union s t) Source

bsort :: Bubbler s s => Set s -> Set (Sort s) Source

append :: Set s -> Set t -> Set (Append s t) Source

type Sort l = Bubble l l Source

type Sortable s = Bubbler s s Source

class OrdH e f where Source

Methods

minH :: e -> f -> Min e f Source

maxH :: e -> f -> Max e f Source

Instances

Chooser (CmpSymbol j k) => OrdH ((:->) j u) ((:->) k v) 

type family Min a b Source

Instances

type Min ((:->) j u) ((:->) k v) = (:->) (Select Symbol j k j k) (Select * j k u v) 

type family Max a b Source

Instances

type Max ((:->) j u) ((:->) k v) = (:->) (Select Symbol j k k j) (Select * j k v u) 

type family Append s t Source

Equations

Append [] t = t 
Append (x : xs) ys = x : Append xs ys 

class Split s t st where Source

Methods

split :: Set st -> (Set s, Set t) Source

Instances

Split s t st => Split s ((:) * x t) ((:) * x st) 
Split ([] *) ([] *) ([] *) 
Split s t st => Split ((:) * x s) t ((:) * x st) 
Split s t st => Split ((:) * x s) ((:) * x t) ((:) * x st) 

type family Nub t Source

Equations

Nub [] = [] 
Nub `[e]` = `[e]` 
Nub (e : (e : s)) = Nub (e : s) 
Nub (e : (f : s)) = e : Nub (f : s) 

class Nubable t where Source

Methods

nub :: Set t -> Set (Nub t) Source

Instances

Nubable ([] *) 
((~) [*] (Nub * ((:) * e ((:) * f s))) ((:) * e (Nub * ((:) * f s))), Nubable ((:) * f s)) => Nubable ((:) * e ((:) * f s)) 
Nubable ((:) * e ([] *)) 
(Monoid u, Nubable ((:) * ((:->) k u) s)) => Nubable ((:) * ((:->) k u) ((:) * ((:->) k u) s))

Define the operation for removing duplicates using mappend

type AsSet s = Nub (Sort s) Source

asSet :: (Sortable s, Nubable (Sort s)) => Set s -> Set (AsSet s) Source

type IsSet s = s ~ Nub (Sort s) Source

class Subset s t where Source

Methods

subset :: Set t -> Set s Source

Instances

Subset s t => Subset s ((:) * x t) 
Subset ([] *) t 
Subset s t => Subset ((:) * x s) ((:) * x t)