Copyright | (c) Samuel Schlesinger 2020 |
---|---|
License | MIT |
Maintainer | sgschlesinger@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data Sum (xs :: [*])
- pattern Inj :: forall x xs. x `HasTagIn` xs => x -> Sum xs
- tag :: forall x xs. x `HasTagIn` xs => Word
- inject :: forall x xs. x `HasTagIn` xs => x -> Sum xs
- inspect :: forall x xs. x `HasTagIn` xs => Sum xs -> Maybe x
- consider :: forall x xs. x `HasTagIn` xs => Sum xs -> Either (Sum (Delete x xs)) x
- considerFirst :: forall x xs. Sum (x ': xs) -> Either (Sum xs) x
- variant :: forall a b xs p f. (a `HasTagIn` xs, Applicative f, Choice p) => p a (f b) -> p (Sum xs) (f (Sum (Replace a b xs)))
- class UnorderedMatch xs matcher where
- unorderedMatch :: Sum xs -> matcher
- class Match xs where
- class Unmatch xs ys
- type family TagIn (x :: k) (xs :: [k]) where ...
- class KnownNat (x `TagIn` xs) => HasTagIn x xs
- type family Delete (x :: k) (xs :: [k]) :: [k] where ...
- class HaveSameTagsIn xs ys
- type family Matcher xs r :: Type where ...
- class Weaken xs ys where
- noOpWeaken :: forall xs ys. xs `HaveSameTagsIn` ys => Sum xs -> Sum ys
- inmap :: forall x y xs. (x `HasTagIn` xs, y `HasTagIn` xs) => (x -> y) -> Sum xs -> Sum xs
- smap :: forall x y xs ys. (Weaken (Delete x xs) ys, x `HasTagIn` xs, y `HasTagIn` ys) => (x -> y) -> Sum xs -> Sum ys
- class ForAll c xs => ApplyFunction c xs where
- type family ForAll c xs :: Constraint where ...
The extensible sum type and its associated pattern for convenience
The extensible sum type, allowing inhabitants to be of any of the types in the given type list.
Instances
ApplyFunction ShowTypeable xs => Show (Sum xs) Source # | Showing extensible sums. |
Generic (Sum xs) => Generic (Sum (x ': xs)) Source # | |
Generic (Sum ('[] :: [Type])) Source # | |
(Eq (Sum xs), Eq x) => Eq (Sum (x ': xs)) Source # | Testing extensible sums for equality. |
Eq (Sum ('[] :: [Type])) Source # | |
type Code (Sum (x ': xs)) Source # | |
Defined in Data.Summer | |
type Code (Sum ('[] :: [Type])) Source # | |
Defined in Data.Summer |
pattern Inj :: forall x xs. x `HasTagIn` xs => x -> Sum xs Source #
A pattern to match on for convenience. Without this, the user facing interface is rather baroque.
tag :: forall x xs. x `HasTagIn` xs => Word Source #
Computes the tag of the given type in the given type level list.
Construction and Deconstruction
inject :: forall x xs. x `HasTagIn` xs => x -> Sum xs Source #
Injects a type into the extensible sum.
inspect :: forall x xs. x `HasTagIn` xs => Sum xs -> Maybe x Source #
Inspects an extensible sum for a particular type.
consider :: forall x xs. x `HasTagIn` xs => Sum xs -> Either (Sum (Delete x xs)) x Source #
Consider a certain type, discarding it as an option if it is not the correct one.
considerFirst :: forall x xs. Sum (x ': xs) -> Either (Sum xs) x Source #
Consider the first type in the list of possibilities, a useful specialization for type inference.
variant :: forall a b xs p f. (a `HasTagIn` xs, Applicative f, Choice p) => p a (f b) -> p (Sum xs) (f (Sum (Replace a b xs))) Source #
A prism which operates on a chosen variant of a Sum
class UnorderedMatch xs matcher where Source #
unorderedMatch :: Sum xs -> matcher Source #
Instances
(Result matcher ~ r, Match (Unmatcher matcher r), Matcher (Unmatcher matcher r) r ~ matcher, HasTagIn y xs, UnorderedMatch (Delete y xs) matcher) => UnorderedMatch xs ((y -> r) -> matcher) Source # | |
Defined in Data.Summer unorderedMatch :: Sum xs -> (y -> r) -> matcher Source # | |
UnorderedMatch ('[] :: [Type]) r Source # | |
Defined in Data.Summer unorderedMatch :: Sum '[] -> r Source # |
A typeclass for scott encoding extensible sums
match :: forall r. Sum xs -> Matcher xs r Source #
unmatch :: (forall r. Matcher xs r) -> Sum xs Source #
override :: forall r. r -> Matcher xs r -> Matcher xs r Source #
A utility typeclass which makes the implementation of Match
cleaner.
unmatchGo
Type families
type family TagIn (x :: k) (xs :: [k]) where ... Source #
A type family for computing the tag of a given type in an extensible sum. In practice, this means computing the first index of the given type in the list.
class KnownNat (x `TagIn` xs) => HasTagIn x xs Source #
A class that is used for convenience in order to make certain type signatures read more clearly.
type family Delete (x :: k) (xs :: [k]) :: [k] where ... Source #
A type family for deleting the given type from a list
class HaveSameTagsIn xs ys Source #
A class which checks that every type has the same tag in the first list as the second. In other words, checks if the first list is a prefix of the other.
Instances
HaveSameTagsIn ('[] :: [k2]) (ys :: k1) Source # | |
Defined in Data.Summer | |
HaveSameTagsIn xs ys => HaveSameTagsIn (x ': xs :: [a]) (x ': ys :: [a]) Source # | |
Defined in Data.Summer |
Weakening extensible sums
class Weaken xs ys where Source #
Transforming one sum into a sum which contains all of the same types
noOpWeaken :: forall xs ys. xs `HaveSameTagsIn` ys => Sum xs -> Sum ys Source #
A free version of weakening, where all you're doing is adding more possibilities at exclusively higher tags.
Transforming extensible sums
inmap :: forall x y xs. (x `HasTagIn` xs, y `HasTagIn` xs) => (x -> y) -> Sum xs -> Sum xs Source #
Transforms one type in the sum into another.
smap :: forall x y xs ys. (Weaken (Delete x xs) ys, x `HasTagIn` xs, y `HasTagIn` ys) => (x -> y) -> Sum xs -> Sum ys Source #
Transform one type in one sum into another type in another sum.
Applying Polymorphic Functions
class ForAll c xs => ApplyFunction c xs where Source #
Using functions which only require constraints which are satisfied by all members of the sum.
Instances
ApplyFunction c ('[] :: [Type]) Source # | |
Defined in Data.Summer | |
(c x, ApplyFunction c xs) => ApplyFunction c (x ': xs) Source # | |
Defined in Data.Summer |