named-sop-0.2.0.0: Dependently-typed sums and products, tagged by field name

Safe HaskellNone
LanguageHaskell2010

Data.NamedSOP.Sum

Description

 
Synopsis

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

Constructors

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 # 
Instance details

Defined in Data.NamedSOP.Sum

Methods

(==) :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> Bool #

(/=) :: NSum ((k :-> v) ': xs) -> NSum ((k :-> v) ': xs) -> Bool #

Eq (NSum ([] :: [Mapping s Type])) Source # 
Instance details

Defined in Data.NamedSOP.Sum

Methods

(==) :: NSum [] -> NSum [] -> Bool #

(/=) :: NSum [] -> NSum [] -> Bool #

(Ord v, Ord (NSum xs)) => Ord (NSum ((k :-> v) ': xs)) Source # 
Instance details

Defined in Data.NamedSOP.Sum

Methods

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 # 
Instance details

Defined in Data.NamedSOP.Sum

Methods

compare :: NSum [] -> NSum [] -> Ordering #

(<) :: NSum [] -> NSum [] -> Bool #

(<=) :: NSum [] -> NSum [] -> Bool #

(>) :: NSum [] -> NSum [] -> Bool #

(>=) :: NSum [] -> NSum [] -> Bool #

max :: NSum [] -> NSum [] -> NSum [] #

min :: NSum [] -> NSum [] -> NSum [] #

(KnownSymbol k, Show v, Show (NSum xs)) => Show (NSum ((k :-> v) ': xs)) Source # 
Instance details

Defined in Data.NamedSOP.Sum

Methods

showsPrec :: Int -> NSum ((k :-> v) ': xs) -> ShowS #

show :: NSum ((k :-> v) ': xs) -> String #

showList :: [NSum ((k :-> v) ': xs)] -> ShowS #

Show (NSum ([] :: [Mapping s Type])) Source # 
Instance details

Defined in Data.NamedSOP.Sum

Methods

showsPrec :: Int -> NSum [] -> ShowS #

show :: NSum [] -> String #

showList :: [NSum []] -> ShowS #

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 NSums. 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.

NSums 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)