Copyright | (c) Fumiaki Kinoshita 2018 |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data (h :: k -> *) :| (s :: [k]) where
- EmbedAt :: !(Membership xs x) -> h x -> h :| xs
- hoist :: (forall x. g x -> h x) -> (g :| xs) -> h :| xs
- embed :: x ∈ xs => h x -> h :| xs
- strike :: forall h x xs. x ∈ xs => (h :| xs) -> Maybe (h x)
- strikeAt :: forall h x xs. Membership xs x -> (h :| xs) -> Maybe (h x)
- (<:|) :: (h x -> r) -> ((h :| xs) -> r) -> (h :| (x ': xs)) -> r
- exhaust :: (h :| '[]) -> r
- embedAssoc :: Associate k a xs => h (k :> a) -> h :| xs
Documentation
data (h :: k -> *) :| (s :: [k]) where Source #
The extensible sum type
(:|) :: (k -> *) -> [k] -> *
EmbedAt :: !(Membership xs x) -> h x -> h :| xs |
Instances
strike :: forall h x xs. x ∈ xs => (h :| xs) -> Maybe (h x) Source #
Try to extract something you want.
strikeAt :: forall h x xs. Membership xs x -> (h :| xs) -> Maybe (h x) Source #
Try to extract something you want.