| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Vinyl.XRec
Description
A variant of Rec whose values have eliminated common syntactic
 clutter due to Identity, Compose, and ElField type
 constructors.
A common pain point with using Rec is the mandatory context of
 each value. A basic record might look like this, Identity "joe" :&
 Identity 23 :& RNil :: Rec Identity '[String, Int]. The Identity
 constructors are a nuisance, so we offer a way of avoiding them:
 "joe" ::& 23 ::& XRNil :: XRec Identity '[String,Int]. Facilities
 are provided for converting between XRec and Rec so that the
 Rec API is available even if you choose to use XRec for
 construction or pattern matching.
Synopsis
- type XRec f = Rec (XData f)
- pattern (::&) :: HKD f r -> XRec f rs -> XRec f (r ': rs)
- pattern XRNil :: XRec f '[]
- rmapX :: forall f g rs. (XRMap f g rs, IsoXRec f rs, IsoXRec g rs) => (forall a. HKD f a -> HKD g a) -> Rec f rs -> Rec g rs
- rmapXEndo :: forall f rs. (XRMap f f rs, IsoXRec f rs) => (forall a. HKD f a -> HKD f a) -> Rec f rs -> Rec f rs
- xrmap :: forall f g rs. XRMap f g rs => (forall a. HKD f a -> HKD g a) -> XRec f rs -> XRec g rs
- newtype XData t a = XData {}
- class XRMap f g rs where
- class XRApply f g rs where
- class IsoXRec f ts where
- class IsoHKD f a where
- rgetX :: forall a record f rs. (RecElem record a a rs rs (RIndex a rs), RecElemFCtx record f, IsoHKD f a) => record f rs -> HKD f a
Documentation
rmapX :: forall f g rs. (XRMap f g rs, IsoXRec f rs, IsoXRec g rs) => (forall a. HKD f a -> HKD g a) -> Rec f rs -> Rec g rs Source #
rmapXEndo :: forall f rs. (XRMap f f rs, IsoXRec f rs) => (forall a. HKD f a -> HKD f a) -> Rec f rs -> Rec f rs Source #
This is rmapX specialized to a type at which it does not change
 interpretation functor. This can help with type inference.
xrmap :: forall f g rs. XRMap f g rs => (forall a. HKD f a -> HKD g a) -> XRec f rs -> XRec g rs Source #
This is rmap for XRec. We apply a natural transformation
 between interpretation functors to transport a record value between
 interpretations.
class XRMap f g rs where Source #
The implementation of xrmap is broken into a type class to
 permit unrolling of the recursion across a record. The function
 mapped across the vector hides the HKD type family under a newtype
 constructor to help the type checker.
class XRApply f g rs where Source #
Like rapply: record of components f r -> g r may be applied
 to a record of f to get a record of g.
class IsoXRec f ts where Source #
Conversion between XRec and Rec. It is convenient to build
 and consume XRec values to reduce syntactic noise, but Rec has
 a richer API that is difficult to build around the HKD type
 family.
class IsoHKD f a where Source #
Isomorphism between a syntactically noisy value and a concise
 one. For types like, Identity, we prefer to work with values of
 the underlying type without writing out the Identity
 constructor. For Compose f g a(f :. g) a, we prefer to
 work directly with values of type f (g a).
This involves the so-called higher-kinded data type family. See http://reasonablypolymorphic.com/blog/higher-kinded-data for more discussion.
Minimal complete definition
Nothing
Instances
| (IsoHKD f (HKD g a), IsoHKD g a, Functor f) => IsoHKD (Compose f g :: k -> Type) (a :: k) Source # | Work with values of type  | 
| (IsoHKD f a, IsoHKD g a) => IsoHKD (Lift ((->) :: Type -> Type -> Type) f g :: k -> Type) (a :: k) Source # | Work with values of type  | 
| IsoHKD Maybe (a :: Type) Source # | |
| IsoHKD IO (a :: Type) Source # | |
| IsoHKD First (a :: Type) Source # | |
| IsoHKD Last (a :: Type) Source # | |
| IsoHKD Sum (a :: Type) Source # | Work with values of type  | 
| IsoHKD Product (a :: Type) Source # | Work with values of type  | 
| IsoHKD Identity (a :: Type) Source # | Work with values of type  | 
| IsoHKD (Either a :: Type -> Type) (b :: Type) Source # | |
| IsoHKD ((,) a :: Type -> Type) (b :: Type) Source # | |
| KnownSymbol s => IsoHKD ElField ('(s, a) :: (Symbol, Type)) Source # | Work with values of type  | 
rgetX :: forall a record f rs. (RecElem record a a rs rs (RIndex a rs), RecElemFCtx record f, IsoHKD f a) => record f rs -> HKD f a Source #
Record field getter that pipes the field value through HKD to
 eliminate redundant newtype wrappings. Usage will typically involve
 a visible type application to the field type. The definition is
 similar to, getHKD = toHKD . rget.