posable-1.0.0.0: A product-of-sums generics library
Safe HaskellNone
LanguageHaskell2010

Generics.POSable.Representation

Description

This module exports the Product and Sum type, and type- and valuelevel functions on these types.

Synopsis

Documentation

type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ... infixr 5 Source #

Concatenation of typelevel lists

Equations

'[] ++ ys = ys 
(x ': xs) ++ ys = x ': (xs ++ ys) 

data ProductType :: [[Type]] -> Type where Source #

Type witness for Product

Constructors

PTNil :: ProductType '[] 
PTCons :: SumType x -> ProductType xs -> ProductType (x ': xs) 

Instances

Instances details
All2 Show (Map2TypeRep xs) => Show (ProductType xs) Source # 
Instance details

Defined in Generics.POSable.Representation

concatPT :: ProductType x -> ProductType y -> ProductType (x ++ y) Source #

Concatenates ProductType values

data Product :: [[Type]] -> Type where Source #

Typelevel product of Sums with values

Constructors

Nil :: Product '[] 
Cons :: Sum x -> Product xs -> Product (x ': xs) 

Instances

Instances details
All2 Eq xs => Eq (Product xs) Source # 
Instance details

Defined in Generics.POSable.Representation

Methods

(==) :: Product xs -> Product xs -> Bool #

(/=) :: Product xs -> Product xs -> Bool #

All2 Show xs => Show (Product xs) Source # 
Instance details

Defined in Generics.POSable.Representation

Methods

showsPrec :: Int -> Product xs -> ShowS #

show :: Product xs -> String #

showList :: [Product xs] -> ShowS #

concatP :: Product x -> Product y -> Product (x ++ y) Source #

Concatenates Product values

data SumType :: [Type] -> Type where Source #

Type witness for Sum

Constructors

STSucc :: Ground x => x -> SumType xs -> SumType (x ': xs) 
STZero :: SumType '[] 

Instances

Instances details
All Show (MapTypeRep xs) => Show (SumType xs) Source # 
Instance details

Defined in Generics.POSable.Representation

Methods

showsPrec :: Int -> SumType xs -> ShowS #

show :: SumType xs -> String #

showList :: [SumType xs] -> ShowS #

data Sum :: [Type] -> Type where Source #

Typelevel sum, contains one value from the typelevel list of types, or undefined.

Constructors

Pick :: Ground x => x -> Sum (x ': xs) 
Skip :: Ground x => Sum xs -> Sum (x ': xs) 

Instances

Instances details
All Eq xs => Eq (Sum xs) Source # 
Instance details

Defined in Generics.POSable.Representation

Methods

(==) :: Sum xs -> Sum xs -> Bool #

(/=) :: Sum xs -> Sum xs -> Bool #

All Show x => Show (Sum x) Source # 
Instance details

Defined in Generics.POSable.Representation

Methods

showsPrec :: Int -> Sum x -> ShowS #

show :: Sum x -> String #

showList :: [Sum x] -> ShowS #

type family Merge (xs :: [[Type]]) (ys :: [[Type]]) :: [[Type]] where ... Source #

Zip two lists of lists with ++` as operator, while keeping the length of the longest outer list

Example:

>>> :kind! Merge '[ '[A, B, C], '[D, E]] '[ '[F, G]]
Merge '[ '[A, B, C], '[D, E]] '[ '[F, G]] :: [[Type]]
= '[ '[A, B, C, F, G], '[D, E]]

Equations

Merge '[] '[] = '[] 
Merge '[] (b ': bs) = (Undef ': b) ': Merge '[] bs 
Merge (a ': as) '[] = (a ++ '[Undef]) ': Merge as '[] 
Merge (a ': as) (b ': bs) = (a ++ b) ': Merge as bs 

type family FoldMerge (xss :: [[[Type]]]) :: [[Type]] where ... Source #

Fold Merge over a list (of lists, of lists)

Example:

>>> :kind! FoldMerge '[ '[ '[A, B, C], '[D, E]], '[ '[F, G]], '[ '[H]]]
FoldMerge '[ '[ '[A, B, C], '[D, E]], '[ '[F, G]], '[ '[H]]] :: [[Type]]
= '[ '[A, B, C, F, G, H], '[D, E]]

Equations

FoldMerge '[a] = a 
FoldMerge (a ': as) = Merge a (FoldMerge as) 
FoldMerge '[] = '[] 

type family MapConcat (xsss :: [[[x]]]) :: [[x]] where ... Source #

Map Concat over a list (of lists, of lists), typelevel equivalent of

map . concat :: [[[a]]] -> [[a]]

Example:

>>> :kind! MapConcat '[ '[ '[A, B], '[C, D]], '[[E, F], '[G, H]]]
MapConcat '[ '[ '[A, B], '[C, D]], '[[E, F], '[G, H]]] :: [[Type]]
= '[ '[A, B, C, D], '[E, F, G, H]]

Equations

MapConcat '[] = '[] 
MapConcat (xss ': xsss) = Concat xss ': MapConcat xsss 

type family Concat (xss :: [[x]]) :: [x] where ... Source #

Concatenate a list of lists, typelevel equivalent of

concat :: [[a]] -> [a]`

Example:

>>> :kind! Concat '[ '[A, B], '[C, D]]
Concat '[ '[A, B], '[C, D]] :: [Type]
= '[A, B, C, D]

Equations

Concat '[] = '[] 
Concat (xs ': xss) = xs ++ Concat xss 

class Typeable a => Ground a where Source #

The set of types that can exist in the sums. This set can be extended by the user by providing an instance of Ground for their types. The mkGround function gives a default value for the type. Ground depends on Typeable, as this makes it possible for library users to inspect the types of the contents of the sums.

Methods

mkGround :: a Source #

Instances

Instances details
Ground Double Source # 
Instance details

Defined in Examples

Ground Float Source # 
Instance details

Defined in Examples

Ground Undef Source # 
Instance details

Defined in Generics.POSable.Representation

splitLeft :: Product (Merge l r) -> ProductType l -> ProductType r -> Product l Source #

UnMerge a Product, using two ProductTypes as witnesses for the left and right argument of Merge. Produces a value of type Product left

splitRight :: Product (Merge l r) -> ProductType l -> ProductType r -> Product r Source #

UnMerge a Product, using two ProductTypes as witnesses for the left and right argument of Merge. Produces a value of type Product right

unConcatP :: Product (x ++ y) -> ProductType x -> (Product x, Product y) Source #

UnConcat a Product, using a ProductType as the witness for the first argument of ++. Produces a tuple with the first and second argument of ++

data Undef Source #

Constructors

Undef 

Instances

Instances details
Eq Undef Source # 
Instance details

Defined in Generics.POSable.Representation

Methods

(==) :: Undef -> Undef -> Bool #

(/=) :: Undef -> Undef -> Bool #

Show Undef Source # 
Instance details

Defined in Generics.POSable.Representation

Methods

showsPrec :: Int -> Undef -> ShowS #

show :: Undef -> String #

showList :: [Undef] -> ShowS #

Generic Undef Source # 
Instance details

Defined in Generics.POSable.Representation

Associated Types

type Rep Undef :: Type -> Type #

Methods

from :: Undef -> Rep Undef x #

to :: Rep Undef x -> Undef #

Generic Undef Source # 
Instance details

Defined in Generics.POSable.Representation

Associated Types

type Code Undef :: [[Type]] #

Methods

from :: Undef -> Rep Undef #

to :: Rep Undef -> Undef #

Ground Undef Source # 
Instance details

Defined in Generics.POSable.Representation

POSable Undef Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices Undef :: Nat Source #

type Fields Undef :: [[Type]] Source #

type Rep Undef Source # 
Instance details

Defined in Generics.POSable.Representation

type Rep Undef = D1 ('MetaData "Undef" "Generics.POSable.Representation" "posable-1.0.0.0-GalccFVB4tU3Vkh9X5MVgO" 'False) (C1 ('MetaCons "Undef" 'PrefixI 'False) (U1 :: Type -> Type))
type Code Undef Source # 
Instance details

Defined in Generics.POSable.Representation

type Choices Undef Source # 
Instance details

Defined in Generics.POSable.Instances

type Fields Undef Source # 
Instance details

Defined in Generics.POSable.Instances