vinyl-0.5.3: Extensible Records

Safe HaskellNone
LanguageHaskell2010

Data.Vinyl.Lens

Synopsis

Documentation

class i ~ RIndex r rs => RElem r rs i 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

Methods

rlens :: Functor g => sing r -> (f r -> g (f r)) -> Rec f rs -> g (Rec 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 -> Rec f rs -> f r Source #

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

rput :: f r -> Rec f rs -> Rec 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

RElem a r ((:) a r rs) Z Source # 

Methods

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

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

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

((~) Nat (RIndex a r ((:) a s rs)) (S i), RElem a r rs i) => RElem 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))) -> Rec r f (S i) -> g (Rec r f (S i)) Source #

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

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

class is ~ RImage rs ss => RSubset rs ss 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 => (Rec f rs -> g (Rec f rs)) -> Rec f ss -> g (Rec 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 :: Rec f ss -> Rec f rs Source #

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

rreplace :: Rec f rs -> Rec f ss -> Rec 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

RSubset k ([] k) ss ([] Nat) Source # 

Methods

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

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

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

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

Methods

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

rcast :: Rec ((k ': r) rs) f ((Nat ': i) is) -> Rec ((k ': r) rs) f ss Source #

rreplace :: Rec ((k ': r) rs) f ss -> Rec ((k ': r) rs) f ((Nat ': i) is) -> Rec ((k ': r) rs) f ((Nat ': i) is) 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 (≅).