Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data NSum :: [Mapping s Type] -> Type where
- unionSum :: forall s (xs :: [Mapping s *]) (ys :: [Mapping s *]). (SingI xs, SingI ys, SOrd s) => Either (NSum xs) (NSum ys) -> NSum (Union xs ys)
- ununionSum :: forall s (xs :: [Mapping s *]) (ys :: [Mapping s *]). (SingI xs, SingI ys, SOrd s) => NSum (Union xs ys) -> Either (NSum xs) (NSum ys)
- module Data.NamedSOP.Type
Documentation
data NSum :: [Mapping s Type] -> Type where Source #
A dependently-typed sum. The following are roughly equilvalent:
type A = NSum '[ "B" ':-> Int, "C" ':-> Bool ] data A = B Int | C Bool
NSumThis :: forall k v xs. v -> NSum ((k :-> v) ': xs) | |
NSumThat :: forall x xs. NSum xs -> NSum (x ': xs) |
Instances
(Eq v, Eq (NSum xs)) => Eq (NSum ((k :-> v) ': xs)) Source # | |
Eq (NSum ([] :: [Mapping s Type])) Source # | |
(Ord v, Ord (NSum xs)) => Ord (NSum ((k :-> v) ': xs)) Source # | |
Defined in Data.NamedSOP.Sum compare :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> Ordering # (<) :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> Bool # (<=) :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> Bool # (>) :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> Bool # (>=) :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> Bool # max :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) # min :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) # | |
Ord (NSum ([] :: [Mapping s Type])) Source # | |
(KnownSymbol k, Show v, Show (NSum xs)) => Show (NSum ((k :-> v) ': xs)) Source # | |
Show (NSum ([] :: [Mapping s Type])) Source # | |
unionSum :: forall s (xs :: [Mapping s *]) (ys :: [Mapping s *]). (SingI xs, SingI ys, SOrd s) => Either (NSum xs) (NSum ys) -> NSum (Union xs ys) Source #
Combine two NSum
s. This is dual to
unionMap
, which accepts a product of products
and returns a product; unionSum
accepts a sum of sums and returns
a sum. The order of fields does not matter, because they will be
sorted.
NSum
s form a commutative monoid under unionSum
, with NSum '[]
as the identity.
Together with NMap
,
NMapEmpty
, and unionMap
, it
is a semiring.
ununionSum :: forall s (xs :: [Mapping s *]) (ys :: [Mapping s *]). (SingI xs, SingI ys, SOrd s) => NSum (Union xs ys) -> Either (NSum xs) (NSum ys) Source #
Split a sorted NSum
into either of two (potentially unsorted)
subsums. Select the subsums with -XTypeApplications
.
>>>
s :: NSum '[ "A" ':-> Int, "B" ':-> Bool, "C" ':-> String ]
>>>
s = NSumThat (NSumThis True) -- Select the "B" field.
>>>
ununionSum @_ @'[ "B" ':-> Bool, "A" ':-> Int ] @'[ "C" ':-> String ] s
Left (B :-> True)
module Data.NamedSOP.Type