| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Vinyl.Recursive
Description
Recursive definitions of various core vinyl functions. These are simple definitions that put less strain on the compiler. They are expected to have slower run times, but faster compile times than the definitions in Data.Vinyl.Core.
Synopsis
- rappend :: Rec f as -> Rec f bs -> Rec f (as ++ bs)
- (<+>) :: Rec f as -> Rec f bs -> Rec f (as ++ bs)
- rmap :: (forall x. f x -> g x) -> Rec f rs -> Rec g rs
- (<<$>>) :: (forall x. f x -> g x) -> Rec f rs -> Rec g rs
- (<<&>>) :: Rec f rs -> (forall x. f x -> g x) -> Rec g rs
- rapply :: Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs
- (<<*>>) :: Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs
- rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> Rec f rs -> h (Rec g rs)
- rzipWith :: (forall x. f x -> g x -> h x) -> forall xs. Rec f xs -> Rec g xs -> Rec h xs
- rfoldMap :: forall f m rs. Monoid m => (forall x. f x -> m) -> Rec f rs -> m
- recordToList :: Rec (Const a) rs -> [a]
- reifyConstraint :: RecAll f rs c => proxy c -> Rec f rs -> Rec (Dict c :. f) rs
- rpureConstrained :: forall u c (f :: u -> *) proxy ts. (AllConstrained c ts, RecApplicative ts) => proxy c -> (forall a. c a => f a) -> Rec f ts
- rpureConstraints :: forall cs (f :: * -> *) proxy ts. (AllAllSat cs ts, RecApplicative ts) => proxy cs -> (forall a. AllSatisfied cs a => f a) -> Rec f ts
Documentation
rapply :: Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs Source #
A record of components f r -> g r may be applied to a record of f to
 get a record of g.
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.
rfoldMap :: forall f m rs. Monoid m => (forall x. f x -> m) -> Rec f rs -> m Source #
Map each element of a record to a monoid and combine the results.
recordToList :: Rec (Const a) rs -> [a] Source #
A record with uniform fields may be turned into a list.
reifyConstraint :: RecAll f rs c => proxy c -> Rec f rs -> Rec (Dict c :. f) rs 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.
rpureConstrained :: forall u c (f :: u -> *) proxy ts. (AllConstrained c ts, RecApplicative ts) => proxy c -> (forall a. c a => f a) -> Rec f ts Source #
Build a record whose elements are derived solely from a constraint satisfied by each.
rpureConstraints :: forall cs (f :: * -> *) proxy ts. (AllAllSat cs ts, RecApplicative ts) => proxy cs -> (forall a. AllSatisfied cs a => f a) -> Rec f ts Source #
Build a record whose elements are derived solely from a list of constraint constructors satisfied by each.