Copyright | (c) Samuel Schlesinger 2020 |
---|---|
License | MIT |
Maintainer | sgschlesinger@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data Prod (xs :: [*])
- extract :: forall x xs. x `HasIndexIn` xs => Prod xs -> x
- index :: forall x xs. x `HasIndexIn` xs => Word
- tailN :: forall n xs. (KnownNat n, n <= Length xs) => Prod xs -> Prod (Tail n xs)
- initN :: forall n xs. (KnownNat n, n <= Length xs) => Prod xs -> Prod (Init n xs)
- dropFirst :: forall x xs. Prod (x ': xs) -> Prod xs
- class Consume xs where
- produce :: (KnownNat (Length xs), Consume xs) => (forall r. Consumer xs r -> r) -> Prod xs
- empty :: Prod '[]
- class ForAll c xs => FoldProd c xs where
- toList :: forall c xs a. FoldProd c xs => (forall x. c x => x -> a) -> Prod xs -> [a]
- type family ForAll c xs :: Constraint where ...
- atType :: forall a b xs f. (a `HasIndexIn` xs, Functor f) => (a -> f b) -> Prod xs -> f (Prod (Replace a b xs))
- buildProd :: forall xs. KnownNat (Length xs) => ProdBuilder xs -> Prod xs
- data ProdBuilder (xs :: [*])
- consB :: x -> ProdBuilder xs -> ProdBuilder (x ': xs)
- emptyB :: ProdBuilder '[]
- appendB :: ProdBuilder xs -> ProdBuilder ys -> ProdBuilder (xs <> ys)
- type family Index (n :: Nat) (xs :: [k]) where ...
- type family IndexIn (x :: k) (xs :: [k]) where ...
- class KnownNat (x `IndexIn` xs) => HasIndexIn x xs
- type family Consumer xs r where ...
- type family (xs :: [k]) <> (ys :: [k]) :: [k] where ...
- type family Length (xs :: [k]) where ...
- type family Tail n xs where ...
- type family Init n xs where ...
- type family Replace x y xs where ...
- class Strengthen xs ys where
- strengthenP :: Prod xs -> ProdBuilder ys
- strengthen :: (KnownNat (Length ys), Strengthen xs ys) => Prod xs -> Prod ys
- remap :: forall x y xs. x `HasIndexIn` xs => (x -> y) -> Prod xs -> Prod (Replace x y xs)
- class Selection def selector a where
- type family FieldsFromSelector def selector where ...
- type family Selector def fields a where ...
The extensible product type
data Prod (xs :: [*]) Source #
An extensible product type
Construction and deconstruction
extract :: forall x xs. x `HasIndexIn` xs => Prod xs -> x Source #
Extract a value at a particular index
index :: forall x xs. x `HasIndexIn` xs => Word Source #
Computes the index of the given type in the given type level list.
tailN :: forall n xs. (KnownNat n, n <= Length xs) => Prod xs -> Prod (Tail n xs) Source #
Takes the tail of a product after the nth element.
initN :: forall n xs. (KnownNat n, n <= Length xs) => Prod xs -> Prod (Init n xs) Source #
Takes the initial length n segment of a product.
dropFirst :: forall x xs. Prod (x ': xs) -> Prod xs Source #
Drop the first element of a product. Sometimes needed for better type inference and less piping around of constraints.
class Consume xs where Source #
A typeclass that is useful to define the scott encoding/decoding for extensible products.
consume :: forall r. Prod xs -> Consumer xs r -> r Source #
produceB :: (forall r. Consumer xs r -> r) -> ProdBuilder xs Source #
extend1 :: x -> Consumer xs (ProdBuilder (x ': xs)) Source #
cmap :: (r -> r') -> Consumer xs r -> Consumer xs r' Source #
class ForAll c xs => FoldProd c xs where Source #
A class for folding over a Prod
using a function which only requires that
every element of the product satisfy a certain constraint.
Instances
type family ForAll c xs :: Constraint where ... Source #
atType :: forall a b xs f. (a `HasIndexIn` xs, Functor f) => (a -> f b) -> Prod xs -> f (Prod (Replace a b xs)) Source #
Lens to modify one element of a product.
Efficient Iterative Construction
buildProd :: forall xs. KnownNat (Length xs) => ProdBuilder xs -> Prod xs Source #
Execute a ProdBuilder
, pulling out a Prod
.
data ProdBuilder (xs :: [*]) Source #
A type for constructing products with linear memory use.
consB :: x -> ProdBuilder xs -> ProdBuilder (x ': xs) Source #
Cons an element onto the head of a ProdBuilder
.
emptyB :: ProdBuilder '[] Source #
Empty ProdBuilder
.
appendB :: ProdBuilder xs -> ProdBuilder ys -> ProdBuilder (xs <> ys) Source #
Appends two ProdBuilder
s.
Type families
type family Index (n :: Nat) (xs :: [k]) where ... Source #
A type family for indexing into lists of types.
type family IndexIn (x :: k) (xs :: [k]) where ... Source #
A type family for computing the index of a type in a list of types.
class KnownNat (x `IndexIn` xs) => HasIndexIn x xs Source #
A class that is used for convenience in order to make certain type signatures read more clearly.
Instances
KnownNat (IndexIn x xs) => HasIndexIn (x :: k) (xs :: [k]) Source # | |
Defined in Data.Prodder |
type family Consumer xs r where ... Source #
This is a reified pattern match on an extensible product
type family Length (xs :: [k]) where ... Source #
A type family for computing the length of a type level list
type family Init n xs where ... Source #
A type family for computing the initial segment of a type level list
type family Replace x y xs where ... Source #
Type family for replacing one type in a type level list with another
Rearranging and removing elements
class Strengthen xs ys where Source #
A typeclass to rearrange and possibly remove things from a product.
strengthenP :: Prod xs -> ProdBuilder ys Source #
Instances
Strengthen xs ('[] :: [Type]) Source # | |
Defined in Data.Prodder strengthenP :: Prod xs -> ProdBuilder '[] Source # | |
(Strengthen xs ys, HasIndexIn y xs) => Strengthen xs (y ': ys) Source # | |
Defined in Data.Prodder strengthenP :: Prod xs -> ProdBuilder (y ': ys) Source # |
strengthen :: (KnownNat (Length ys), Strengthen xs ys) => Prod xs -> Prod ys Source #
Transforming extensible products
remap :: forall x y xs. x `HasIndexIn` xs => (x -> y) -> Prod xs -> Prod (Replace x y xs) Source #
Replaces one type with another via a function
Picking out individual components of a product
class Selection def selector a where Source #
A class for constructing the select function inductively.
type family FieldsFromSelector def selector where ... Source #
Extracts the fields intended from the given selector type.
FieldsFromSelector def (a -> b) = IndexIn a def ': FieldsFromSelector def b | |
FieldsFromSelector def (Identity a) = '[] |