Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ...
- data ProductType :: [[Type]] -> Type where
- PTNil :: ProductType '[]
- PTCons :: SumType x -> ProductType xs -> ProductType (x ': xs)
- concatPT :: ProductType x -> ProductType y -> ProductType (x ++ y)
- data Product :: [[Type]] -> Type where
- concatP :: Product x -> Product y -> Product (x ++ y)
- data SumType :: [Type] -> Type where
- data Sum :: [Type] -> Type where
- type family Merge (xs :: [[Type]]) (ys :: [[Type]]) :: [[Type]] where ...
- type family FoldMerge (xss :: [[[Type]]]) :: [[Type]] where ...
- type family MapConcat (xsss :: [[[x]]]) :: [[x]] where ...
- type family Concat (xss :: [[x]]) :: [x] where ...
- class Typeable a => Ground a where
- mkGround :: a
- mergeT :: ProductType l -> ProductType r -> ProductType (Merge l r)
- merge :: Either (Product l, ProductType r) (ProductType l, Product r) -> Product (Merge l r)
- splitLeft :: Product (Merge l r) -> ProductType l -> ProductType r -> Product l
- splitRight :: Product (Merge l r) -> ProductType l -> ProductType r -> Product r
- unConcatP :: Product (x ++ y) -> ProductType x -> (Product x, Product y)
- data Undef = Undef
Documentation
type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ... infixr 5 Source #
Concatenation of typelevel lists
data ProductType :: [[Type]] -> Type where Source #
Type witness for Product
PTNil :: ProductType '[] | |
PTCons :: SumType x -> ProductType xs -> ProductType (x ': xs) |
Instances
All2 Show (Map2TypeRep xs) => Show (ProductType xs) Source # | |
Defined in Generics.POSable.Representation showsPrec :: Int -> ProductType xs -> ShowS # show :: ProductType xs -> String # showList :: [ProductType xs] -> ShowS # |
concatPT :: ProductType x -> ProductType y -> ProductType (x ++ y) Source #
Concatenates ProductType
values
data Product :: [[Type]] -> Type where Source #
Typelevel product of Sum
s with values
data Sum :: [Type] -> Type where Source #
Typelevel sum, contains one value from the typelevel list of types, or undefined.
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]]
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]]
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]]
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]
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.
mergeT :: ProductType l -> ProductType r -> ProductType (Merge l r) Source #
Merge two ProductType
s
merge :: Either (Product l, ProductType r) (ProductType l, Product r) -> Product (Merge l r) Source #
Merge a ProductType
and a Product
splitLeft :: Product (Merge l r) -> ProductType l -> ProductType r -> Product l Source #
UnMerge a Product
, using two ProductType
s 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 ProductType
s 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 ++
Instances
Eq Undef Source # | |
Show Undef Source # | |
Generic Undef Source # | |
Generic Undef Source # | |
Ground Undef Source # | |
Defined in Generics.POSable.Representation | |
POSable Undef Source # | |
Defined in Generics.POSable.Instances | |
type Rep Undef Source # | |
type Code Undef Source # | |
Defined in Generics.POSable.Representation | |
type Choices Undef Source # | |
Defined in Generics.POSable.Instances | |
type Fields Undef Source # | |
Defined in Generics.POSable.Instances |