Safe Haskell | None |
---|---|
Language | Haskell98 |
This module includes a set of common functions for Records and Variants. It includes:
- Common constructors, destructors, and querying functions
It specifically excludes:
- Functions that have the same name for Records and Variants (e.g.
focus
,update
,fromLabels
, etc.) - Common clashes with the standard Prelude or other modules (e.g.
map
,sequence
,zip
,Map
, etc.)
If these particular functions are needed, they should be brought in qualified from one of the Data.Row.*** modules directly.
- data Label (s :: Symbol) = Label
- class KnownSymbol (n :: Symbol)
- type family AllUniqueLabels (r :: Row *) :: Constraint where ...
- type WellBehaved ρ = (Forall ρ Unconstrained1, AllUniqueLabels ρ)
- data Var (r :: Row *)
- data Rec (r :: Row *)
- data Row a
- type Empty = R '[]
- type (≈) a b = a ~ b
- class (r .! l) ≈ a => HasType l a r
- class Lacks (l :: Symbol) (r :: Row *)
- type family (r :: Row *) .\ (l :: Symbol) :: Constraint where ...
- type family (l :: Row *) .+ (r :: Row *) :: Row * where ...
- class Forall (r :: Row *) (c :: * -> Constraint)
- class Switch (v :: Row *) (r :: Row *) x | v x -> r, r x -> v where
- empty :: Rec Empty
- type (.==) (l :: Symbol) (a :: *) = Extend l a Empty
- (.==) :: KnownSymbol l => Label l -> a -> Rec (l .== a)
- pattern (:==) :: forall l a. KnownSymbol l => Label l -> a -> Rec (l .== a)
- unSingleton :: forall l a. KnownSymbol l => Rec (l .== a) -> (Label l, a)
- type family (r :: Row *) .- (s :: Symbol) :: Row * where ...
- (.-) :: KnownSymbol l => Rec r -> Label l -> Rec (r .- l)
- restrict :: forall r r'. (Forall r Unconstrained1, Subset r r') => Rec r' -> Rec r
- type family (r :: Row *) .! (t :: Symbol) :: * where ...
- (.!) :: KnownSymbol l => Rec r -> Label l -> r .! l
- (.+) :: Rec l -> Rec r -> Rec (l .+ r)
- type Disjoint l r = (WellBehaved l, WellBehaved r, Subset l (l .+ r), Subset r (l .+ r), ((l .+ r) .\\ l) ≈ r, ((l .+ r) .\\ r) ≈ l)
- pattern (:+) :: forall l r. Disjoint l r => Rec l -> Rec r -> Rec (l .+ r)
- pattern IsJust :: forall l r. (AllUniqueLabels r, KnownSymbol l) => Label l -> (r .! l) -> Var r
- diversify :: forall r' r. AllUniqueLabels (r .+ r') => Var r -> Var (r .+ r')
- impossible :: Var Empty -> a
- trial :: KnownSymbol l => Var r -> Label l -> Either (r .! l) (Var (r .- l))
- trial' :: KnownSymbol l => Var r -> Label l -> Maybe (r .! l)
- multiTrial :: forall x y. (AllUniqueLabels x, Forall (y .\\ x) Unconstrained1) => Var y -> Either (Var x) (Var (y .\\ x))
- type family (l :: Row *) .\\ (r :: Row *) :: Row * where ...
- labels :: forall ρ c s. (IsString s, Forall ρ c) => [s]
Types and constraints
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
symbolSing
type family AllUniqueLabels (r :: Row *) :: Constraint where ... Source #
Are all of the labels in this Row unique?
AllUniqueLabels (R r) = AllUniqueLabelsR r |
type WellBehaved ρ = (Forall ρ Unconstrained1, AllUniqueLabels ρ) Source #
A convenient way to provide common, easy constraints
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.
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.
class Lacks (l :: Symbol) (r :: Row *) Source #
Alias for .\
. It is a class rather than an alias, so that
it can be partially applied.
type family (r :: Row *) .\ (l :: Symbol) :: Constraint where ... infixl 4 Source #
Does the row lack (i.e. it does not have) the specified label?
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.
class Switch (v :: Row *) (r :: Row *) x | v x -> r, r x -> v where Source #
Record Construction
type (.==) (l :: Symbol) (a :: *) = Extend l a Empty infix 7 Source #
A type level way to create a singleton Row.
pattern (:==) :: forall l a. KnownSymbol l => Label l -> a -> Rec (l .== a) infix 7 Source #
A pattern for the singleton record; can be used to both destruct a record when in a pattern position or construct one in an expression position.
unSingleton :: forall l a. KnownSymbol l => Rec (l .== a) -> (Label l, a) Source #
Turns a singleton record into a pair of the label and value.
Restriction
type family (r :: Row *) .- (s :: Symbol) :: Row * where ... infixl 6 Source #
Type level Row element removal
(.-) :: KnownSymbol l => Rec r -> Label l -> Rec (r .- l) infixl 6 Source #
Record restriction. Remove the label l from the record.
restrict :: forall r r'. (Forall r Unconstrained1, Subset r r') => Rec r' -> Rec r Source #
Arbitrary record restriction. Turn a record into a subset of itself.
Query
Disjoint union
type Disjoint l r = (WellBehaved l, WellBehaved r, Subset l (l .+ r), Subset r (l .+ r), ((l .+ r) .\\ l) ≈ r, ((l .+ r) .\\ r) ≈ l) Source #
A type synonym for disjointness.
pattern (:+) :: forall l r. Disjoint l r => Rec l -> Rec r -> Rec (l .+ r) infixl 6 Source #
A pattern version of record union, for use in pattern matching.
Variant construction
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.
Restriction
diversify :: forall r' r. AllUniqueLabels (r .+ r') => Var r -> Var (r .+ r') Source #
Make the variant arbitrarily more diverse.
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
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
.