row-types-0.2.0.0: Open Records and Variants

Safe HaskellNone
LanguageHaskell98

Data.Row.Variants

Contents

Description

This module implements extensible variants using closed type families.

Synopsis

Types and constraints

data Label (s :: Symbol) Source #

A label

Constructors

Label 

Instances

(≈) Symbol x y => IsLabel x (Label y) Source # 

Methods

fromLabel :: Label y #

KnownSymbol s => Show (Label s) Source # 

Methods

showsPrec :: Int -> Label s -> ShowS #

show :: Label s -> String #

showList :: [Label s] -> ShowS #

class KnownSymbol (n :: Symbol) #

This class gives the string associated with a type-level symbol. There are instances of the class for every concrete literal: "hello", etc.

Since: 4.7.0.0

Minimal complete definition

symbolSing

type family AllUniqueLabels (r :: Row *) :: Constraint where ... Source #

Are all of the labels in this Row unique?

Equations

AllUniqueLabels (R r) = AllUniqueLabelsR r 

type WellBehaved ρ = (Forall ρ Unconstrained1, AllUniqueLabels ρ) Source #

A convenient way to provide common, easy constraints

data Var (r :: Row *) Source #

The variant type.

Instances

Forall r Eq => Eq (Var r) Source # 

Methods

(==) :: Var r -> Var r -> Bool #

(/=) :: Var r -> Var r -> Bool #

(Forall r Eq, Forall r Ord) => Ord (Var r) Source # 

Methods

compare :: Var r -> Var r -> Ordering #

(<) :: Var r -> Var r -> Bool #

(<=) :: Var r -> Var r -> Bool #

(>) :: Var r -> Var r -> Bool #

(>=) :: Var r -> Var r -> Bool #

max :: Var r -> Var r -> Var r #

min :: Var r -> Var r -> Var r #

Forall r Show => Show (Var r) Source # 

Methods

showsPrec :: Int -> Var r -> ShowS #

show :: Var r -> String #

showList :: [Var r] -> ShowS #

Forall r NFData => NFData (Var r) Source # 

Methods

rnf :: Var r -> () #

data Row a Source #

The kind of rows. This type is only used as a datakind. A row is a typelevel entity telling us which symbols are associated with which types.

type Empty = R '[] Source #

Type level version of empty

type (≈) a b = a ~ b infix 4 Source #

A lower fixity operator for type equality

Construction

class (r .! l) a => HasType l a r Source #

Alias for (r .! l) ≈ a. It is a class rather than an alias, so that it can be partially applied.

Instances

(≈) * ((.!) r l) a => HasType l a r Source # 

pattern IsJust :: forall l r. (AllUniqueLabels r, KnownSymbol l) => Label l -> (r .! l) -> Var r Source #

A pattern for variants; can be used to both destruct a variant when in a pattern position or construct one in an expression position.

singleton :: KnownSymbol l => Label l -> a -> Var (l .== a) Source #

A quick constructor to create a singleton variant.

fromLabels :: forall c ρ f. (Alternative f, Forall ρ c, AllUniqueLabels ρ) => (forall l a. (KnownSymbol l, c a) => Label l -> f a) -> f (Var ρ) Source #

Initialize a variant from a producer function that accepts labels. If this function returns more than one possibility, then one is chosen arbitrarily to be the value in the variant.

Extension

type family (r :: Row *) .\ (l :: Symbol) :: Constraint where ... infixl 4 Source #

Does the row lack (i.e. it does not have) the specified label?

Equations

(R r) .\ l = LacksR l r r 

class Lacks (l :: Symbol) (r :: Row *) Source #

Alias for .\. It is a class rather than an alias, so that it can be partially applied.

Instances

(.\) r l => Lacks l r Source # 

diversify :: forall r' r. AllUniqueLabels (r .+ r') => Var r -> Var (r .+ r') Source #

Make the variant arbitrarily more diverse.

type family (l :: Row *) .+ (r :: Row *) :: Row * where ... infixl 6 Source #

Type level Row append

Equations

(R l) .+ (R r) = R (Merge l r) 

Modification

update :: KnownSymbol l => Label l -> a -> Var r -> Var r Source #

If the variant exists at the given label, update it to the given value. Otherwise, do nothing.

focus :: (Applicative f, KnownSymbol l) => Label l -> ((r .! l) -> f a) -> Var r -> f (Var (Modify l a r)) Source #

If the variant exists at the given label, focus on the value associated with it. Otherwise, do nothing.

type family Modify (l :: Symbol) (a :: *) (r :: Row *) :: Row * where ... Source #

Type level Row modification

Equations

Modify l a (R ρ) = R (ModifyR l a ρ) 

rename :: (KnownSymbol l, KnownSymbol l') => Label l -> Label l' -> Var r -> Var (Rename l l' r) Source #

Rename the given label.

type family Rename (l :: Symbol) (l' :: Symbol) (r :: Row *) :: Row * where ... Source #

Type level row renaming

Equations

Rename l l' r = Extend l' (r .! l) (r .- l) 

Destruction

impossible :: Var Empty -> a Source #

A Variant with no options is uninhabited.

trial :: KnownSymbol l => Var r -> Label l -> Either (r .! l) (Var (r .- l)) Source #

Convert a variant into either the value at the given label or a variant without that label. This is the basic variant destructor.

trial' :: KnownSymbol l => Var r -> Label l -> Maybe (r .! l) Source #

A version of trial that ignores the leftover variant.

multiTrial :: forall x y. (AllUniqueLabels x, Forall (y .\\ x) Unconstrained1) => Var y -> Either (Var x) (Var (y .\\ x)) Source #

A trial over multiple types

view :: KnownSymbol l => Label l -> Var r -> Maybe (r .! l) Source #

A convenient function for using view patterns when dispatching variants. For example:

 myShow :: Var ("y" '::= String :| "x" '::= Int :| Empty) -> String
 myShow (view x -> Just n) = "Int of "++show n
 myShow (view y -> Just s) = "String of "++s

Types for destruction

type family (r :: Row *) .! (t :: Symbol) :: * where ... infixl 5 Source #

Type level label fetching

Equations

(R r) .! l = Get l r 

type family (r :: Row *) .- (s :: Symbol) :: Row * where ... infixl 6 Source #

Type level Row element removal

Equations

(R r) .- l = R (Remove l r) 

type family (l :: Row *) .\\ (r :: Row *) :: Row * where ... infixl 6 Source #

Type level Row difference. That is, l .\\ r is the row remaining after removing any matching elements of r from l.

Equations

(R l) .\\ (R r) = R (Diff l r) 

type (.==) (l :: Symbol) (a :: *) = Extend l a Empty infix 7 Source #

A type level way to create a singleton Row.

Row operations

Map

type family Map (f :: a -> b) (r :: Row a) :: Row b where ... Source #

Map a type level function over a Row.

Equations

Map f (R r) = R (MapR f r) 

map :: forall c f r. Forall r c => (forall a. c a => a -> f a) -> Var r -> Var (Map f r) Source #

A function to map over a variant given a constraint.

map' :: forall f r. Forall r Unconstrained1 => (forall a. a -> f a) -> Var r -> Var (Map f r) Source #

A function to map over a variant given no constraint.

transform :: forall r c f g. Forall r c => (forall a. c a => f a -> g a) -> Var (Map f r) -> Var (Map g r) Source #

Lifts a natrual transformation over a variant. In other words, it acts as a variant transformer to convert a variant of f a values to a variant of g a values. If no constraint is needed, instantiate the first type argument with Unconstrained1.

transform' :: forall r f g. Forall r Unconstrained1 => (forall a. f a -> g a) -> Var (Map f r) -> Var (Map g r) Source #

A form of transformC that doesn't have a constraint on a

Fold

class Forall (r :: Row *) (c :: * -> Constraint) Source #

Any structure over a row in which every element is similarly constrained can be metamorphized into another structure over the same row.

Minimal complete definition

metamorph, metamorph'

Instances

(KnownSymbol ℓ, c τ, FoldStep ℓ τ ρ, Forall (R * ρ) c) => Forall (R * ((:) (LT *) ((:->) * ℓ τ) ρ)) c Source # 

Methods

metamorph :: Proxy (* -> *) h -> (f (Empty *) -> g (Empty *)) -> (forall (a :: Symbol) b (d :: [LT *]). (KnownSymbol a, c b) => Label a -> f (R * ((LT * ': (* :-> a) b) d)) -> (h b, f (R * d))) -> (forall (a :: Symbol) b (d :: [LT *]). (KnownSymbol a, c b, FoldStep a b d) => Label a -> h b -> g (R * d) -> g (R * ((LT * ': (* :-> a) b) d))) -> f (R * ((LT * ': (* :-> ℓ) τ) ρ)) -> g (R * ((LT * ': (* :-> ℓ) τ) ρ)) Source #

metamorph' :: Proxy (* -> *) h -> (f (Empty *) -> g (Empty *)) -> (forall (a :: Symbol) b (d :: [LT *]). (KnownSymbol a, c b) => Label a -> f (R * ((LT * ': (* :-> a) b) d)) -> Either (h b) (f (R * d))) -> (forall (a :: Symbol) b (d :: [LT *]). (KnownSymbol a, c b, FoldStep a b d) => Label a -> Either (h b) (g (R * d)) -> g (R * ((LT * ': (* :-> a) b) d))) -> f (R * ((LT * ': (* :-> ℓ) τ) ρ)) -> g (R * ((LT * ': (* :-> ℓ) τ) ρ)) Source #

Forall (R * ([] (LT *))) c Source # 

Methods

metamorph :: Proxy (* -> *) h -> (f (Empty *) -> g (Empty *)) -> (forall (ℓ :: Symbol) τ (ρ :: [LT *]). (KnownSymbol ℓ, c τ) => Label ℓ -> f (R * ((LT * ': (* :-> ℓ) τ) ρ)) -> (h τ, f (R * ρ))) -> (forall (ℓ :: Symbol) τ (ρ :: [LT *]). (KnownSymbol ℓ, c τ, FoldStep ℓ τ ρ) => Label ℓ -> h τ -> g (R * ρ) -> g (R * ((LT * ': (* :-> ℓ) τ) ρ))) -> f (R * [LT *]) -> g (R * [LT *]) Source #

metamorph' :: Proxy (* -> *) h -> (f (Empty *) -> g (Empty *)) -> (forall (ℓ :: Symbol) τ (ρ :: [LT *]). (KnownSymbol ℓ, c τ) => Label ℓ -> f (R * ((LT * ': (* :-> ℓ) τ) ρ)) -> Either (h τ) (f (R * ρ))) -> (forall (ℓ :: Symbol) τ (ρ :: [LT *]). (KnownSymbol ℓ, c τ, FoldStep ℓ τ ρ) => Label ℓ -> Either (h τ) (g (R * ρ)) -> g (R * ((LT * ': (* :-> ℓ) τ) ρ))) -> f (R * [LT *]) -> g (R * [LT *]) Source #

erase :: forall c ρ b. Forall ρ c => (forall a. c a => a -> b) -> Var ρ -> b Source #

A standard fold

eraseWithLabels :: forall c ρ s b. (Forall ρ c, IsString s) => (forall a. c a => a -> b) -> Var ρ -> (s, b) Source #

A fold with labels

eraseZip :: forall c ρ b. Forall ρ c => (forall a. c a => a -> a -> b) -> Var ρ -> Var ρ -> Maybe b Source #

A fold over two row type structures at once

Sequence

sequence :: forall f r. (Forall r Unconstrained1, Applicative f) => Var (Map f r) -> f (Var r) Source #

Applicative sequencing over a variant

Compose

We can easily convert between mapping two functors over the types of a row and mapping the composition of the two functors. The following two functions perform this composition with the gaurantee that:

>>> compose . uncompose = id
>>> uncompose . compose = id

compose :: forall (f :: * -> *) g r. Forall r Unconstrained1 => Var (Map f (Map g r)) -> Var (Map (Compose f g) r) Source #

Convert from a variant where two functors have been mapped over the types to one where the composition of the two functors is mapped over the types.

uncompose :: forall (f :: * -> *) g r. Forall r Unconstrained1 => Var (Map (Compose f g) r) -> Var (Map f (Map g r)) Source #

Convert from a variant where the composition of two functors have been mapped over the types to one where the two functors are mapped individually one at a time over the types.

labels

labels :: forall ρ c s. (IsString s, Forall ρ c) => [s] Source #

Return a list of the labels in a row type.

UNSAFE operations

unsafeMakeVar :: forall r l. KnownSymbol l => Label l -> (r .! l) -> Var r Source #

An unsafe way to make a Variant. This function does not guarantee that the labels are all unique.

unsafeInjectFront :: forall l a r. KnownSymbol l => Var (R r) -> Var (R ((l :-> a) ': r)) Source #

A helper function for unsafely adding an element to the front of a variant. This can cause the type of the resulting variant to be malformed, for instance, if the variant already contains labels that are lexicographically before the given label. Realistically, this function should only be used when writing calls to metamorph.