| Copyright | (c) Fumiaki Kinoshita 2015 |
|---|---|
| License | BSD3 |
| Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Extensible.Inclusion
Description
- data Membership xs x
- runMembership :: Membership (y : xs) x -> ((x :~: y) -> r) -> (Membership xs x -> r) -> r
- type (∈) x xs = Member xs x
- class Member xs x where
- membership :: Membership xs x
- remember :: forall xs x r. Membership xs x -> (Member xs x => r) -> r
- data Expecting a
- data Missing a
- data Ambiguous a
- ord :: Int -> Q Exp
- data Assoc k v = k :> v
- class Associate k v xs | k xs -> v where
- association :: Membership xs (k :> v)
- type (⊆) xs ys = Include ys xs
- type Include ys = Forall (Member ys)
- inclusion :: forall xs ys. Include ys xs => Membership ys :* xs
- shrink :: xs ⊆ ys => (h :* ys) -> h :* xs
- spread :: xs ⊆ ys => (h :| xs) -> h :| ys
- type IncludeAssoc ys xs = Forall (Associated ys) xs
- class Associated xs t
- inclusionAssoc :: forall xs ys. IncludeAssoc ys xs => Membership ys :* xs
- shrinkAssoc :: IncludeAssoc ys xs => (h :* ys) -> h :* xs
- spreadAssoc :: IncludeAssoc ys xs => (h :| xs) -> h :| ys
- coinclusion :: (Include ys xs, Generate ys) => Nullable (Membership xs) :* ys
- wrench :: (Generate ys, xs ⊆ ys) => (h :* xs) -> Nullable h :* ys
- retrench :: (Generate ys, xs ⊆ ys) => (h :| ys) -> Nullable ((:|) h) xs
- data Nullable h x
- nullable :: r -> (h x -> r) -> Nullable h x -> r
- mapNullable :: (g x -> h y) -> Nullable g x -> Nullable h y
Membership
data Membership xs x Source
The position of x in the type level set xs.
Instances
| Typeable ([k] -> k -> *) (Membership k) | |
| Eq (Membership k xs x) | |
| Ord (Membership k xs x) | |
| Show (Membership k xs x) |
runMembership :: Membership (y : xs) x -> ((x :~: y) -> r) -> (Membership xs x -> r) -> r Source
Embodies a type equivalence to ensure that the Membership points the first element.
class Member xs x where Source
Methods
membership :: Membership xs x Source
remember :: forall xs x r. Membership xs x -> (Member xs x => r) -> r Source
Remember that Member xs x from Membership.
The kind of key-value pairs
Constructors
| k :> v |
Instances
| Associate k k1 k2 v xs => Associated (Assoc k k) xs ((:>) k k k v) |
class Associate k v xs | k xs -> v where Source
is essentially identical to Associate k v xs(k :> v) ∈ xs
, but the type v is inferred from k and xs.
Methods
association :: Membership xs (k :> v) Source
Inclusion
inclusion :: forall xs ys. Include ys xs => Membership ys :* xs Source
Reify the inclusion of type level sets.
Dictionary-like
type IncludeAssoc ys xs = Forall (Associated ys) xs Source
Similar to Include, but works nicely for key-value pairs.
class Associated xs t Source
Minimal complete definition
getAssociation
Instances
| Associate k k1 k2 v xs => Associated (Assoc k k) xs ((:>) k k k v) |
inclusionAssoc :: forall xs ys. IncludeAssoc ys xs => Membership ys :* xs Source
Reify the inclusion of type level sets.
shrinkAssoc :: IncludeAssoc ys xs => (h :* ys) -> h :* xs Source
O(m log n) Select some elements.
spreadAssoc :: IncludeAssoc ys xs => (h :| xs) -> h :| ys Source
O(log n) Embed to a larger union.
Inverse
coinclusion :: (Include ys xs, Generate ys) => Nullable (Membership xs) :* ys Source
The inverse of inclusion.
wrench :: (Generate ys, xs ⊆ ys) => (h :* xs) -> Nullable h :* ys Source
Extend a product and fill missing fields by Null.
retrench :: (Generate ys, xs ⊆ ys) => (h :| ys) -> Nullable ((:|) h) xs Source
Narrow the range of the sum, if possible.
Poly-kinded Maybe
mapNullable :: (g x -> h y) -> Nullable g x -> Nullable h y Source
Apply a function to its content.