summer-0.1.0.0: An implementation of extensible products and sums

Copyright(c) Samuel Schlesinger 2020
LicenseMIT
Maintainersgschlesinger@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Prodder

Contents

Description

Description: Extensible products

Synopsis

The extensible product type

data Prod (xs :: [*]) Source #

An extensible product type

Instances
(Eq x, Eq (Prod xs)) => Eq (Prod (x ': xs)) Source # 
Instance details

Defined in Data.Prodder

Methods

(==) :: Prod (x ': xs) -> Prod (x ': xs) -> Bool #

(/=) :: Prod (x ': xs) -> Prod (x ': xs) -> Bool #

Eq (Prod ([] :: [Type])) Source # 
Instance details

Defined in Data.Prodder

Methods

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

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

Type families

type family IndexIn (x :: k) (xs :: [k]) where ... Source #

A type family for computing the index of a type in a list of types.

Equations

IndexIn x (x ': xs) = 0 
IndexIn x (y ': xs) = 1 + IndexIn x xs 

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

Defined in Data.Prodder

type family Consumer xs r where ... Source #

This is a reified pattern match on an extensible product

Equations

Consumer '[] r = r 
Consumer (x ': xs) r = x -> Consumer xs r 

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

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.

Methods

consume :: forall r. Prod xs -> Consumer xs r -> r Source #

produce :: (forall r. Consumer xs r -> r) -> Prod xs Source #

extend1 :: x -> Consumer xs (Prod (x ': xs)) Source #

cmap :: (r -> r') -> Consumer xs r -> Consumer xs r' Source #

Instances
Consume ([] :: [Type]) Source # 
Instance details

Defined in Data.Prodder

Methods

consume :: Prod [] -> Consumer [] r -> r Source #

produce :: (forall r. Consumer [] r -> r) -> Prod [] Source #

extend1 :: x -> Consumer [] (Prod (x ': [])) Source #

cmap :: (r -> r') -> Consumer [] r -> Consumer [] r' Source #

Consume xs => Consume (x ': xs) Source # 
Instance details

Defined in Data.Prodder

Methods

consume :: Prod (x ': xs) -> Consumer (x ': xs) r -> r Source #

produce :: (forall r. Consumer (x ': xs) r -> r) -> Prod (x ': xs) Source #

extend1 :: x0 -> Consumer (x ': xs) (Prod (x0 ': (x ': xs))) Source #

cmap :: (r -> r') -> Consumer (x ': xs) r -> Consumer (x ': xs) r' Source #

Rearranging and removing elements

class Strengthen xs ys where Source #

A typeclass to rearrange and possibly remove things from a product.

Methods

strengthen :: Prod xs -> Prod ys Source #

Instances
Strengthen xs ([] :: [Type]) Source # 
Instance details

Defined in Data.Prodder

Methods

strengthen :: Prod xs -> Prod [] Source #

(Strengthen xs ys, HasIndexIn y xs) => Strengthen xs (y ': ys) Source # 
Instance details

Defined in Data.Prodder

Methods

strengthen :: Prod xs -> Prod (y ': 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