vinyl-0.8.1: Extensible Records

Safe HaskellNone
LanguageHaskell2010

Data.Vinyl.Lens

Description

Lenses into record fields.

Synopsis

Documentation

class i ~ RIndex r rs => RecElem record (r :: k) (rs :: [k]) (i :: Nat) where Source #

The presence of a field in a record is witnessed by a lens into its value. The third parameter to RElem, i, is there to help the constraint solver realize that this is a decidable predicate with respect to the judgemental equality in k.

Minimal complete definition

rlens, rget, rput

Methods

rlens :: Functor g => sing r -> (f r -> g (f r)) -> record f rs -> g (record f rs) Source #

We can get a lens for getting and setting the value of a field which is in a record. As a convenience, we take a proxy argument to fix the particular field being viewed. These lenses are compatible with the lens library. Morally:

rlens :: sing r => Lens' (Rec f rs) (f r)

rget :: sing r -> record f rs -> f r Source #

For Vinyl users who are not using the lens package, we provide a getter.

rput :: f r -> record f rs -> record f rs Source #

For Vinyl users who are not using the lens package, we also provide a setter. In general, it will be unambiguous what field is being written to, and so we do not take a proxy argument here.

Instances

((~) Nat i (RIndex k t ts), NatToInt (RIndex k t ts)) => RecElem k (ARec k) t ts i Source # 

Methods

rlens :: Functor g => sing ts -> (f ts -> g (f ts)) -> t f i -> g (t f i) Source #

rget :: sing ts -> t f i -> f ts Source #

rput :: f ts -> t f i -> t f i Source #

RecElem a (Rec a) r ((:) a r rs) Z Source # 

Methods

rlens :: Functor g => sing ((a ': r) rs) -> (f ((a ': r) rs) -> g (f ((a ': r) rs))) -> r f Z -> g (r f Z) Source #

rget :: sing ((a ': r) rs) -> r f Z -> f ((a ': r) rs) Source #

rput :: f ((a ': r) rs) -> r f Z -> r f Z Source #

((~) Nat (RIndex a r ((:) a s rs)) (S i), RElem a r rs i) => RecElem a (Rec a) r ((:) a s rs) (S i) Source # 

Methods

rlens :: Functor g => sing ((a ': s) rs) -> (f ((a ': s) rs) -> g (f ((a ': s) rs))) -> r f (S i) -> g (r f (S i)) Source #

rget :: sing ((a ': s) rs) -> r f (S i) -> f ((a ': s) rs) Source #

rput :: f ((a ': s) rs) -> r f (S i) -> r f (S i) Source #

type RElem = RecElem Rec Source #

RecElem for classic vinyl Rec types.

class is ~ RImage rs ss => RecSubset record (rs :: [k]) (ss :: [k]) is where Source #

If one field set is a subset another, then a lens of from the latter's record to the former's is evident. That is, we can either cast a larger record to a smaller one, or we may replace the values in a slice of a record.

Minimal complete definition

rsubset

Methods

rsubset :: Functor g => (record f rs -> g (record f rs)) -> record f ss -> g (record f ss) Source #

This is a lens into a slice of the larger record. Morally, we have:

rsubset :: Lens' (Rec f ss) (Rec f rs)

rcast :: record f ss -> record f rs Source #

The getter of the rsubset lens is rcast, which takes a larger record to a smaller one by forgetting fields.

rreplace :: record f rs -> record f ss -> record f ss Source #

The setter of the rsubset lens is rreplace, which allows a slice of a record to be replaced with different values.

Instances

((~) [Nat] is (RImage k rs ss), IndexWitnesses is, NatToInt (RLength k rs)) => RecSubset (k -> *) k (ARec k) rs ss is Source # 

Methods

rsubset :: Functor g => (ss f is -> g (ss f is)) -> ss f ss -> g (ss f ss) Source #

rcast :: ss f ss -> ss f is Source #

rreplace :: ss f is -> ss f ss -> ss f ss Source #

RecSubset (k -> *) k (Rec k) ([] k) ss ([] Nat) Source # 

Methods

rsubset :: Functor g => (ss f [Nat] -> g (ss f [Nat])) -> ss f ss -> g (ss f ss) Source #

rcast :: ss f ss -> ss f [Nat] Source #

rreplace :: ss f [Nat] -> ss f ss -> ss f ss Source #

(RElem k r ss i, RSubset k rs ss is) => RecSubset (k -> *) k (Rec k) ((:) k r rs) ss ((:) Nat i is) Source # 

Methods

rsubset :: Functor g => (ss f ((Nat ': i) is) -> g (ss f ((Nat ': i) is))) -> ss f ss -> g (ss f ss) Source #

rcast :: ss f ss -> ss f ((Nat ': i) is) Source #

rreplace :: ss f ((Nat ': i) is) -> ss f ss -> ss f ss Source #

type REquivalent rs ss is js = (RSubset rs ss is, RSubset ss rs js) Source #

Two record types are equivalent when they are subtypes of each other.

type (∈) r rs = RElem r rs (RIndex r rs) Source #

A shorthand for RElem which supplies its index.

type (⊆) rs ss = RSubset rs ss (RImage rs ss) Source #

A shorthand for RSubset which supplies its image.

type (≅) rs ss = REquivalent rs ss (RImage rs ss) (RImage ss rs) Source #

A shorthand for REquivalent which supplies its images.

type (<:) rs ss = rs ss Source #

A non-unicode equivalent of (⊆).

type (:~:) rs ss = rs ss Source #

A non-unicode equivalent of (≅).