Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class (i ~ RIndex r rs) => RElem r rs i where
- class (is ~ RImage rs ss) => RSubset rs ss is where
- type REquivalent rs ss is js = (RSubset rs ss is, RSubset ss rs js)
- type (∈) r rs = RElem r rs (RIndex r rs)
- type (⊆) rs ss = RSubset rs ss (RImage rs ss)
- type (≅) rs ss = REquivalent rs ss (RImage rs ss) (RImage ss rs)
- type (<:) rs ss = rs ⊆ ss
- type (:~:) rs ss = rs ≅ ss
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
.
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.
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.
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)
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 (⊆) 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.