vinyl-0.9.3: Extensible Records

Safe HaskellNone
LanguageHaskell2010

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

Documentation

type XRec f = Rec (XData f) Source #

pattern (::&) :: HKD f r -> XRec f rs -> XRec f (r ': rs) infixr 7 Source #

pattern XRNil :: XRec f '[] Source #

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 #

Like rmap, but the supplied function is written against the HKD-simplified types. This is xrmap sandwiched in between fromXRec and toXRec.

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.

newtype XData t a Source #

A wrapper for an HKD-simplified value. That is, noisy value constructors like Identity and Compose are ellided. This is used in the xrmapAux type class method, but may be ignored by users whose needs are met by xrmap and rmapX.

Constructors

XData 

Fields

class XRMap (f :: u -> *) (g :: u -> *) (rs :: [u]) 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.

Minimal complete definition

xrmapAux

Methods

xrmapAux :: (forall (a :: u). XData f a -> XData g a) -> XRec f rs -> XRec g rs Source #

Instances
XRMap (f :: u -> *) (g :: u -> *) ([] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.XRec

Methods

xrmapAux :: (forall (a :: u0). XData f a -> XData g a) -> XRec f [] -> XRec g [] Source #

(XRMap f g rs, IsoHKD f r, IsoHKD g r) => XRMap (f :: a -> *) (g :: a -> *) (r ': rs :: [a]) Source # 
Instance details

Defined in Data.Vinyl.XRec

Methods

xrmapAux :: (forall (a0 :: u). XData f a0 -> XData g a0) -> XRec f (r ': rs) -> XRec g (r ': rs) Source #

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.

Minimal complete definition

xrapply

Methods

xrapply :: XRec (Lift (->) f g) rs -> XRec f rs -> XRec g rs Source #

Instances
XRApply (f :: u -> *) (g :: u -> *) ([] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.XRec

Methods

xrapply :: XRec (Lift (->) f g) [] -> XRec f [] -> XRec g [] Source #

XRApply f g rs => XRApply (f :: a -> *) (g :: a -> *) (r ': rs :: [a]) Source # 
Instance details

Defined in Data.Vinyl.XRec

Methods

xrapply :: XRec (Lift (->) f g) (r ': rs) -> XRec f (r ': rs) -> XRec g (r ': rs) Source #

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.

Minimal complete definition

fromXRec, toXRec

Methods

fromXRec :: XRec f ts -> Rec f ts Source #

toXRec :: Rec f ts -> XRec f ts Source #

Instances
IsoXRec (f :: u -> *) ([] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.XRec

Methods

fromXRec :: XRec f [] -> Rec f [] Source #

toXRec :: Rec f [] -> XRec f [] Source #

(IsoXRec f ts, IsoHKD f t) => IsoXRec (f :: a -> *) (t ': ts :: [a]) Source # 
Instance details

Defined in Data.Vinyl.XRec

Methods

fromXRec :: XRec f (t ': ts) -> Rec f (t ': ts) Source #

toXRec :: Rec f (t ': ts) -> XRec f (t ': ts) Source #

class IsoHKD (f :: u -> *) (a :: u) 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, aka (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.

Associated Types

type HKD f a Source #

Methods

unHKD :: HKD f a -> f a Source #

unHKD :: HKD f a ~ f a => HKD f a -> f a Source #

toHKD :: f a -> HKD f a Source #

toHKD :: HKD f a ~ f a => f a -> HKD f a Source #

Instances
(IsoHKD f (HKD g a), IsoHKD g a, Functor f) => IsoHKD (Compose f g :: u -> *) (a :: u) Source #

Work with values of type Compose f g a as if they were of type f (g a).

Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD (Compose f g) a :: * Source #

Methods

unHKD :: HKD (Compose f g) a -> Compose f g a Source #

toHKD :: Compose f g a -> HKD (Compose f g) a Source #

(IsoHKD f a, IsoHKD g a) => IsoHKD (Lift ((->) :: * -> * -> *) f g :: u -> *) (a :: u) Source #

Work with values of type Lift (->) f g a as if they were of type f a -> g a.

Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD (Lift (->) f g) a :: * Source #

Methods

unHKD :: HKD (Lift (->) f g) a -> Lift (->) f g a Source #

toHKD :: Lift (->) f g a -> HKD (Lift (->) f g) a Source #

IsoHKD Maybe (a :: *) Source # 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Maybe a :: * Source #

Methods

unHKD :: HKD Maybe a -> Maybe a Source #

toHKD :: Maybe a -> HKD Maybe a Source #

IsoHKD IO (a :: *) Source # 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD IO a :: * Source #

Methods

unHKD :: HKD IO a -> IO a Source #

toHKD :: IO a -> HKD IO a Source #

IsoHKD First (a :: *) Source # 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD First a :: * Source #

Methods

unHKD :: HKD First a -> First a Source #

toHKD :: First a -> HKD First a Source #

IsoHKD Last (a :: *) Source # 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Last a :: * Source #

Methods

unHKD :: HKD Last a -> Last a Source #

toHKD :: Last a -> HKD Last a Source #

IsoHKD Sum (a :: *) Source #

Work with values of type Sum a as if they were of type a.

Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Sum a :: * Source #

Methods

unHKD :: HKD Sum a -> Sum a Source #

toHKD :: Sum a -> HKD Sum a Source #

IsoHKD Product (a :: *) Source #

Work with values of type Product a as if they were of type a.

Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Product a :: * Source #

IsoHKD Identity (a :: *) Source #

Work with values of type Identity a as if they were simple of type a.

Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Identity a :: * Source #

IsoHKD (Either a :: * -> *) (b :: *) Source # 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD (Either a) b :: * Source #

Methods

unHKD :: HKD (Either a) b -> Either a b Source #

toHKD :: Either a b -> HKD (Either a) b Source #

KnownSymbol s => IsoHKD ElField ((,) s a :: (Symbol, Type)) Source #

Work with values of type ElField '(s,a) as if they were of type a.

Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD ElField (s, a) :: * Source #

Methods

unHKD :: HKD ElField (s, a) -> ElField (s, a) Source #

toHKD :: ElField (s, a) -> HKD ElField (s, a) Source #