Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Core vinyl definitions. The Rec
data type is defined here, but
also of interest are definitions commonly used functions like
rmap
, rapply
, and rtraverse
.
The definitions in this module are written in terms of type classes so that the definitions may be specialized to each record type at which they are used. This usually helps with runtime performance, but can slow down compilation time. If you are experiencing poor compile times, you may wish to try the semantically equivalent definitions in the Data.Vinyl.Recursive module: they should produce the same results given the same inputs as functions defined in this module, but they will not be specialized to your record type. Instead, they treat the record as a list of fields, so will have performance linear in the size of the record.
Synopsis
- data Rec :: (u -> *) -> [u] -> * where
- rappend :: Rec f as -> Rec f bs -> Rec f (as ++ bs)
- (<+>) :: Rec f as -> Rec f bs -> Rec f (as ++ bs)
- rcombine :: (RMap rs, RApply rs) => (forall a. m a -> m a -> m a) -> (forall a. f a -> m a) -> (forall a. m a -> g a) -> Rec f rs -> Rec f rs -> Rec g rs
- class RMap rs where
- (<<$>>) :: RMap rs => (forall x. f x -> g x) -> Rec f rs -> Rec g rs
- (<<&>>) :: RMap rs => Rec f rs -> (forall x. f x -> g x) -> Rec g rs
- class RApply rs where
- (<<*>>) :: RApply rs => Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs
- class RecApplicative rs where
- rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> Rec f rs -> h (Rec g rs)
- rtraverseIn :: forall h f g rs. (forall a. f a -> g (ApplyToField h a)) -> Rec f rs -> Rec g (MapTyCon h rs)
- rsequenceIn :: forall f g (rs :: [Type]). (Traversable f, Applicative g) => Rec (f :. g) rs -> Rec g (MapTyCon f rs)
- rzipWith :: (RMap xs, RApply xs) => (forall x. f x -> g x -> h x) -> Rec f xs -> Rec g xs -> Rec h xs
- class RFoldMap rs where
- rfoldMapAux :: Monoid m => (forall x. f x -> m) -> m -> Rec f rs -> m
- rfoldMap :: forall rs m f. (Monoid m, RFoldMap rs) => (forall x. f x -> m) -> Rec f rs -> m
- class RecordToList rs where
- recordToList :: Rec (Const a) rs -> [a]
- data Dict c a where
- class ReifyConstraint c f rs where
- reifyConstraint :: Rec f rs -> Rec (Dict c :. f) rs
- class RPureConstrained c ts where
- rpureConstrained :: (forall a. c a => f a) -> Rec f ts
- data DictOnly (c :: k -> Constraint) a where
- withPairedDict :: (c a => f a -> r) -> Product (DictOnly c) f a -> r
- class RPureConstraints cs ts where
- rpureConstraints :: (forall a. AllSatisfied cs a => f a) -> Rec f ts
- type family Head xs where ...
- type family Tail xs where ...
- type family AllRepsMatch_ (f :: j -> *) (xs :: [j]) (g :: k -> *) (ys :: [k]) :: Constraint where ...
- type AllRepsMatch f xs g ys = (AllRepsMatch_ f xs g ys, AllRepsMatch_ g ys f xs)
- repsMatchCoercion :: AllRepsMatch f xs g ys => Coercion (Rec f xs) (Rec g ys)
- consMatchCoercion :: (forall (x :: k). Coercible (f x) (g x)) => Coercion (Rec f xs) (Rec g xs)
Documentation
data Rec :: (u -> *) -> [u] -> * where Source #
A record is parameterized by a universe u
, an interpretation f
and a
list of rows rs
. The labels or indices of the record are given by
inhabitants of the kind u
; the type of values at any label r :: u
is
given by its interpretation f r :: *
.
Instances
RecSubset (Rec :: (k -> Type) -> [k] -> Type) ('[] :: [k]) (ss :: [k]) ('[] :: [Nat]) Source # | |
Defined in Data.Vinyl.Lens type RecSubsetFCtx Rec f Source # rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f '[] -> g (Rec f '[])) -> Rec f ss -> g (Rec f ss) Source # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f '[] Source # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f '[] -> Rec f ss -> Rec f ss Source # | |
(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) Source # | |
Defined in Data.Vinyl.Lens type RecSubsetFCtx Rec f Source # rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) Source # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) Source # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss Source # | |
RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) 'Z Source # | |
Defined in Data.Vinyl.Lens type RecElemFCtx Rec f Source # | |
(RIndex r (s ': rs) ~ 'S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) ('S i) Source # | |
Defined in Data.Vinyl.Lens type RecElemFCtx Rec f Source # | |
TestCoercion f => TestCoercion (Rec f :: [u] -> Type) Source # | |
Defined in Data.Vinyl.Core | |
TestEquality f => TestEquality (Rec f :: [u] -> Type) Source # | |
Defined in Data.Vinyl.Core | |
(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) Source # | |
Eq (Rec f ('[] :: [u])) Source # | |
(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) Source # | |
Defined in Data.Vinyl.Core compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering # (<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) # min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) # | |
Ord (Rec f ('[] :: [u])) Source # | |
Defined in Data.Vinyl.Core | |
(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs) Source # | Records may be shown insofar as their points may be shown.
|
Generic (Rec f rs) => Generic (Rec f (r ': rs)) Source # | |
Generic (Rec f ('[] :: [u])) Source # | |
(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) Source # | |
Semigroup (Rec f ('[] :: [u])) Source # | |
(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) Source # | |
Monoid (Rec f ('[] :: [u])) Source # | |
(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) Source # | |
Defined in Data.Vinyl.Core sizeOf :: Rec f (r ': rs) -> Int # alignment :: Rec f (r ': rs) -> Int # peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) # pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () # peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) # pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () # | |
Storable (Rec f ('[] :: [u])) Source # | |
Defined in Data.Vinyl.Core | |
ReifyConstraint NFData f xs => NFData (Rec f xs) Source # | |
Defined in Data.Vinyl.Core | |
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) Source # | |
Defined in Data.Vinyl.Lens | |
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) Source # | |
Defined in Data.Vinyl.Lens | |
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) Source # | |
Defined in Data.Vinyl.Lens | |
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) Source # | |
Defined in Data.Vinyl.Lens | |
type Rep (Rec f (r ': rs)) Source # | |
Defined in Data.Vinyl.Core type Rep (Rec f (r ': rs)) = C1 ('MetaCons ":&" ('InfixI 'RightAssociative 7) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f r)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rep (Rec f rs))) | |
type Rep (Rec f ('[] :: [u])) Source # | |
Defined in Data.Vinyl.Core |
rcombine :: (RMap rs, RApply rs) => (forall a. m a -> m a -> m a) -> (forall a. f a -> m a) -> (forall a. m a -> g a) -> Rec f rs -> Rec f rs -> Rec g rs Source #
Combine two records by combining their fields using the given
function. The first argument is a binary operation for combining
two values (e.g. (<>)
), the second argument takes a record field
into the type equipped with the desired operation, the third
argument takes the combined value back to a result type.
(<<$>>) :: RMap rs => (forall x. f x -> g x) -> Rec f rs -> Rec g rs infixl 8 Source #
A shorthand for rmap
.
(<<&>>) :: RMap rs => Rec f rs -> (forall x. f x -> g x) -> Rec g rs Source #
An inverted shorthand for rmap
.
class RApply rs where Source #
A record of components f r -> g r
may be applied to a record of f
to
get a record of g
.
(<<*>>) :: RApply rs => Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs infixl 8 Source #
A shorthand for rapply
.
class RecApplicative rs where Source #
Given a section of some functor, records in that functor of any size are inhabited.
Instances
RecApplicative ('[] :: [u]) Source # | |
Defined in Data.Vinyl.Core | |
RecApplicative rs => RecApplicative (r ': rs :: [u]) Source # | |
Defined in Data.Vinyl.Core |
rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> Rec f rs -> h (Rec g rs) Source #
A record may be traversed with respect to its interpretation functor. This can be used to yank (some or all) effects from the fields of the record to the outside of the record.
rtraverseIn :: forall h f g rs. (forall a. f a -> g (ApplyToField h a)) -> Rec f rs -> Rec g (MapTyCon h rs) Source #
While rtraverse
pulls the interpretation functor out of the
record, rtraverseIn
pushes the interpretation functor in to each
field type. This is particularly useful when you wish to discharge
that interpretation on a per-field basis. For instance, rather than
a Rec IO '[a,b]
, you may wish to have a Rec Identity '[IO a, IO
b]
so that you can evaluate a single field to obtain a value of
type Rec Identity '[a, IO b]
.
rsequenceIn :: forall f g (rs :: [Type]). (Traversable f, Applicative g) => Rec (f :. g) rs -> Rec g (MapTyCon f rs) Source #
Push an outer layer of interpretation functor into each field.
rzipWith :: (RMap xs, RApply xs) => (forall x. f x -> g x -> h x) -> Rec f xs -> Rec g xs -> Rec h xs Source #
class RFoldMap rs where Source #
Map each element of a record to a monoid and combine the results.
rfoldMapAux :: Monoid m => (forall x. f x -> m) -> m -> Rec f rs -> m Source #
Instances
RFoldMap ('[] :: [u]) Source # | |
Defined in Data.Vinyl.Core rfoldMapAux :: Monoid m => (forall (x :: u0). f x -> m) -> m -> Rec f '[] -> m Source # | |
RFoldMap xs => RFoldMap (x ': xs :: [u]) Source # | |
Defined in Data.Vinyl.Core rfoldMapAux :: Monoid m => (forall (x0 :: u0). f x0 -> m) -> m -> Rec f (x ': xs) -> m Source # |
rfoldMap :: forall rs m f. (Monoid m, RFoldMap rs) => (forall x. f x -> m) -> Rec f rs -> m Source #
class RecordToList rs where Source #
A record with uniform fields may be turned into a list.
recordToList :: Rec (Const a) rs -> [a] Source #
Instances
RecordToList ('[] :: [u]) Source # | |
Defined in Data.Vinyl.Core recordToList :: Rec (Const a) '[] -> [a] Source # | |
RecordToList xs => RecordToList (x ': xs :: [u]) Source # | |
Defined in Data.Vinyl.Core recordToList :: Rec (Const a) (x ': xs) -> [a] Source # |
Wrap up a value with a capability given by its type
class ReifyConstraint c f rs where Source #
Sometimes we may know something for all fields of a record, but when
you expect to be able to each of the fields, you are then out of luck.
Surely given ∀x:u.φ(x)
we should be able to recover x:u ⊢ φ(x)
! Sadly,
the constraint solver is not quite smart enough to realize this and we must
make it patently obvious by reifying the constraint pointwise with proof.
Instances
ReifyConstraint c (f :: u -> Type) ('[] :: [u]) Source # | |
Defined in Data.Vinyl.Core | |
(c (f x), ReifyConstraint c f xs) => ReifyConstraint c (f :: a -> Type) (x ': xs :: [a]) Source # | |
Defined in Data.Vinyl.Core |
class RPureConstrained c ts where Source #
Build a record whose elements are derived solely from a constraint satisfied by each.
rpureConstrained :: (forall a. c a => f a) -> Rec f ts Source #
Instances
RPureConstrained (c :: u -> Constraint) ('[] :: [u]) Source # | |
Defined in Data.Vinyl.Core rpureConstrained :: (forall (a :: u0). c a => f a) -> Rec f '[] Source # | |
(c x, RPureConstrained c xs) => RPureConstrained (c :: a -> Constraint) (x ': xs :: [a]) Source # | |
Defined in Data.Vinyl.Core rpureConstrained :: (forall (a0 :: u). c a0 => f a0) -> Rec f (x ': xs) Source # |
data DictOnly (c :: k -> Constraint) a where Source #
Capture a type class instance dictionary. See
getDict
for a way to obtain a DictOnly
value
from an RPureConstrained
constraint.
withPairedDict :: (c a => f a -> r) -> Product (DictOnly c) f a -> r Source #
A useful technique is to use 'rmap (Pair (DictOnly MyClass))' on
a
MyClass@. This helper can then be used to eliminate the original.Rec
to pair each field with a type class dictionary for
class RPureConstraints cs ts where Source #
Build a record whose elements are derived solely from a list of constraint constructors satisfied by each.
rpureConstraints :: (forall a. AllSatisfied cs a => f a) -> Rec f ts Source #
Instances
RPureConstraints (cs :: k) ('[] :: [u]) Source # | |
Defined in Data.Vinyl.Core rpureConstraints :: (forall (a :: u0). AllSatisfied cs a => f a) -> Rec f '[] Source # | |
(AllSatisfied cs t, RPureConstraints cs ts) => RPureConstraints (cs :: k) (t ': ts :: [u]) Source # | |
Defined in Data.Vinyl.Core rpureConstraints :: (forall (a :: u0). AllSatisfied cs a => f a) -> Rec f (t ': ts) Source # |
type family AllRepsMatch_ (f :: j -> *) (xs :: [j]) (g :: k -> *) (ys :: [k]) :: Constraint where ... Source #
AllRepsMatch_ f (x ': xs) g ys = (ys ~ (Head ys ': Tail ys), Coercible (f x) (g (Head ys)), AllRepsMatch_ f xs g (Tail ys)) | |
AllRepsMatch_ _ '[] _ ys = ys ~ '[] |
type AllRepsMatch f xs g ys = (AllRepsMatch_ f xs g ys, AllRepsMatch_ g ys f xs) Source #
AllRepsMatch f xs g ys
means that xs
and ys
have the
same lengths, and that mapping f
over xs
and g
over ys
produces lists whose corresponding elements are Coercible
with
each other. For example, the following hold:
AllRepsMatch Proxy '[1,2,3] Proxy '[4,5,6]
AllRepsMatch Sum '[Int,Word] Identity '[Min Int, Max Word]
repsMatchCoercion :: AllRepsMatch f xs g ys => Coercion (Rec f xs) (Rec g ys) Source #
Given that for each element x
in the list xs
,