Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Synopsis
- data Set (n :: [k]) where
- type Union s t = Nub (Sort (s :++ t))
- type Unionable s t = (Sortable (s :++ t), Nubable (Sort (s :++ t)))
- union :: Unionable s t => Set s -> Set t -> Set (Union s t)
- quicksort :: Sortable xs => Set xs -> Set (Sort xs)
- append :: Set s -> Set t -> Set (s :++ t)
- type family Sort (xs :: [k]) :: [k] where ...
- class Sortable xs
- type family (x :: [k]) :++ (y :: [k]) :: [k] where ...
- class Split s t st where
- type family Cmp (a :: k) (b :: k) :: Ordering
- type family Filter (f :: Flag) (p :: k) (xs :: [k]) :: [k] where ...
- data Flag
- type family Nub t where ...
- class Nubable t where
- type AsSet s = Nub (Sort s)
- asSet :: (Sortable s, Nubable (Sort s)) => Set s -> Set (AsSet s)
- type IsSet s = s ~ Nub (Sort s)
- class Subset s t where
- type family Delete elem set where ...
- data Proxy (p :: k) = Proxy
- remove :: Remove s t => Set s -> Proxy t -> Set (s :\ t)
- class Remove s t
- type family (m :: [k]) :\ (x :: k) :: [k] where ...
- class Member a s where
- type NonMember a s = MemberP a s ~ False
- type family MemberP a s :: Bool where ...
Documentation
type family Sort (xs :: [k]) :: [k] where ... Source #
Type-level quick sort for normalising the representation of sets
Value-level quick sort that respects the type-level ordering
type family (x :: [k]) :++ (y :: [k]) :: [k] where ... Source #
List append (essentially set disjoint union)
class Split s t st where Source #
Splitting a union a set, given the sets we want to split it into
type family Cmp (a :: k) (b :: k) :: Ordering Source #
Open-family for the ordering operation in the sort
class Nubable t where Source #
Value-level counterpart to the type-level Nub
Note: the value-level case for equal types is not define here,
but should be given per-application, e.g., custom merging
behaviour may be required
asSet :: (Sortable s, Nubable (Sort s)) => Set s -> Set (AsSet s) Source #
At the value level, noramlise the list form to the set form
class Subset s t where Source #
Construct a subsetset s
from a superset t