vinyl-0.14.3: Extensible Records
Safe HaskellNone
LanguageHaskell2010

Data.Vinyl.FromTuple

Description

Concise vinyl record construction from tuples up to size 8. An example record construction using ElField for named fields: fieldRec (y =: b) :: FieldRec '[ '("x", Bool), '("y", Char) ]

Synopsis

Documentation

type family TupleToRecArgs f t = (r :: (u -> Type, [u])) | r -> t where ... Source #

Convert a tuple of types formed by the application of a common type constructor to a tuple of the common type constructor and a list of the types to which it is applied in the original tuple. E.g. TupleToRecArgs f (f a, f b) ~ (f, [a,b]).

Equations

TupleToRecArgs f (f a, f b, f c, f d, f e, f z, f g, f h) = '(f, [a, b, c, d, e, z, g, h]) 
TupleToRecArgs f (f a, f b, f c, f d, f e, f z, f g) = '(f, [a, b, c, d, e, z, g]) 
TupleToRecArgs f (f a, f b, f c, f d, f e, f z) = '(f, [a, b, c, d, e, z]) 
TupleToRecArgs f (f a, f b, f c, f d, f e) = '(f, [a, b, c, d, e]) 
TupleToRecArgs f (f a, f b, f c, f d) = '(f, [a, b, c, d]) 
TupleToRecArgs f (f a, f b, f c) = '(f, [a, b, c]) 
TupleToRecArgs f (f a, f b) = '(f, [a, b]) 
TupleToRecArgs f () = '(f, '[]) 

type family UncurriedRec (t :: (u -> Type, [u])) = r | r -> t where ... Source #

Apply the Rec type constructor to a type-level tuple of its arguments.

Equations

UncurriedRec '(f, ts) = Rec f ts 

type family UncurriedXRec (t :: (u -> Type, [u])) = r | r -> t where ... Source #

Apply the XRec type constructor to a type-level tuple of its arguments.

Equations

UncurriedXRec '(f, ts) = XRec f ts 

class TupleXRec f t where Source #

Convert between an XRec and an isomorphic tuple.

Methods

xrecTuple :: XRec f t -> ListToHKDTuple f t Source #

Convert an XRec to a tuple. Useful for pattern matching on an entire record.

xrecX :: ListToHKDTuple f t -> XRec f t Source #

Build an XRec from a tuple.

Instances

Instances details
TupleXRec (f :: u -> Type) ('[a, b, c, d, e, z, g, h] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

xrecTuple :: XRec f '[a, b, c, d, e, z, g, h] -> ListToHKDTuple f '[a, b, c, d, e, z, g, h] Source #

xrecX :: ListToHKDTuple f '[a, b, c, d, e, z, g, h] -> XRec f '[a, b, c, d, e, z, g, h] Source #

TupleXRec (f :: u -> Type) ('[a, b, c, d, e, z, g] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

xrecTuple :: XRec f '[a, b, c, d, e, z, g] -> ListToHKDTuple f '[a, b, c, d, e, z, g] Source #

xrecX :: ListToHKDTuple f '[a, b, c, d, e, z, g] -> XRec f '[a, b, c, d, e, z, g] Source #

TupleXRec (f :: u -> Type) ('[a, b, c, d, e, z] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

xrecTuple :: XRec f '[a, b, c, d, e, z] -> ListToHKDTuple f '[a, b, c, d, e, z] Source #

xrecX :: ListToHKDTuple f '[a, b, c, d, e, z] -> XRec f '[a, b, c, d, e, z] Source #

TupleXRec (f :: u -> Type) ('[a, b, c, d, e] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

xrecTuple :: XRec f '[a, b, c, d, e] -> ListToHKDTuple f '[a, b, c, d, e] Source #

xrecX :: ListToHKDTuple f '[a, b, c, d, e] -> XRec f '[a, b, c, d, e] Source #

TupleXRec (f :: u -> Type) ('[a, b, c, d] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

xrecTuple :: XRec f '[a, b, c, d] -> ListToHKDTuple f '[a, b, c, d] Source #

xrecX :: ListToHKDTuple f '[a, b, c, d] -> XRec f '[a, b, c, d] Source #

TupleXRec (f :: u -> Type) ('[a, b, c] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

xrecTuple :: XRec f '[a, b, c] -> ListToHKDTuple f '[a, b, c] Source #

xrecX :: ListToHKDTuple f '[a, b, c] -> XRec f '[a, b, c] Source #

TupleXRec (f :: u -> Type) ('[a, b] :: [u]) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

xrecTuple :: XRec f '[a, b] -> ListToHKDTuple f '[a, b] Source #

xrecX :: ListToHKDTuple f '[a, b] -> XRec f '[a, b] Source #

type family ListToHKDTuple (f :: u -> Type) (ts :: [u]) :: Type where ... Source #

Equations

ListToHKDTuple f '[] = HKD f () 
ListToHKDTuple f '[a, b] = (HKD f a, HKD f b) 
ListToHKDTuple f '[a, b, c] = (HKD f a, HKD f b, HKD f c) 
ListToHKDTuple f '[a, b, c, d] = (HKD f a, HKD f b, HKD f c, HKD f d) 
ListToHKDTuple f '[a, b, c, d, e] = (HKD f a, HKD f b, HKD f c, HKD f d, HKD f e) 
ListToHKDTuple f '[a, b, c, d, e, z] = (HKD f a, HKD f b, HKD f c, HKD f d, HKD f e, HKD f z) 
ListToHKDTuple f '[a, b, c, d, e, z, g] = (HKD f a, HKD f b, HKD f c, HKD f d, HKD f e, HKD f z, HKD f g) 
ListToHKDTuple f '[a, b, c, d, e, z, g, h] = (HKD f a, HKD f b, HKD f c, HKD f d, HKD f e, HKD f z, HKD f g, HKD f h) 
ListToHKDTuple f x = TypeError ('Text "Tuples are only supported up to size 8") 

ruple :: (IsoXRec f ts, TupleXRec f ts) => Rec f ts -> ListToHKDTuple f ts Source #

Convert a Rec to a tuple going through HKD to reduce syntactic noise. Useful for pattern matching on an entire Rec.

xrec :: (IsoXRec f t, TupleXRec f t) => ListToHKDTuple f t -> Rec f t Source #

Build a Rec from a tuple passing through XRec. This admits the most concise syntax for building a Rec. For example, xrec ("joe", 23) :: Rec Identity '[String, Int].

class TupleRec f t where Source #

Build a Rec from a tuple. An example would be building a value of type Rec f '[a,b] from a tuple of values with type '(f a, f b).

Instances

Instances details
TupleRec (f :: u -> Type) () Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

record :: () -> UncurriedRec (TupleToRecArgs f ()) Source #

TupleRec (f :: u -> Type) (f a, f b) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

record :: (f a, f b) -> UncurriedRec (TupleToRecArgs f (f a, f b)) Source #

TupleRec (f :: u -> Type) (f a, f b, f c) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

record :: (f a, f b, f c) -> UncurriedRec (TupleToRecArgs f (f a, f b, f c)) Source #

TupleRec (f :: u -> Type) (f a, f b, f c, f d) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

record :: (f a, f b, f c, f d) -> UncurriedRec (TupleToRecArgs f (f a, f b, f c, f d)) Source #

TupleRec (f :: u -> Type) (f a, f b, f c, f d, f e) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

record :: (f a, f b, f c, f d, f e) -> UncurriedRec (TupleToRecArgs f (f a, f b, f c, f d, f e)) Source #

TupleRec (f :: u -> Type) (f a, f b, f c, f d, f e, f z) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

record :: (f a, f b, f c, f d, f e, f z) -> UncurriedRec (TupleToRecArgs f (f a, f b, f c, f d, f e, f z)) Source #

TupleRec (f :: u -> Type) (f a, f b, f c, f d, f e, f z, f g) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

record :: (f a, f b, f c, f d, f e, f z, f g) -> UncurriedRec (TupleToRecArgs f (f a, f b, f c, f d, f e, f z, f g)) Source #

TupleRec (f :: u -> Type) (f a, f b, f c, f d, f e, f z, f g, f h) Source # 
Instance details

Defined in Data.Vinyl.FromTuple

Methods

record :: (f a, f b, f c, f d, f e, f z, f g, f h) -> UncurriedRec (TupleToRecArgs f (f a, f b, f c, f d, f e, f z, f g, f h)) Source #

fieldRec :: TupleRec ElField t => t -> UncurriedRec (TupleToRecArgs ElField t) Source #

Build a FieldRec from a tuple of ElField values.

namedArgs :: (TupleRec ElField t, ss ~ Snd (TupleToRecArgs ElField t), RecSubset Rec rs (Snd (TupleToRecArgs ElField t)) (RImage rs ss), UncurriedRec (TupleToRecArgs ElField t) ~ Rec ElField ss, RecSubsetFCtx Rec ElField) => t -> Rec ElField rs Source #

Build a FieldRec from a tuple and rcast it to another record type that is a subset of the constructed record. This is useful for re-ordering fields. For example, namedArgs (age =: 23) can supply arguments for a function expecting a record of arguments with its fields in the opposite order.

withDefaults :: (RMap rs, RApply rs, ss rs, RMap ss, RecApplicative rs) => Rec f rs -> Rec f ss -> Rec f rs Source #

Override a record with fields from a possibly narrower record. A typical use is to supply default values as the first argument, and overrides for those defaults as the second.