vinyl-named-sugar-0.1.0.0: Syntax sugar for vinyl records using overloaded labels.

Safe HaskellNone
LanguageHaskell2010

Data.Vinyl.Sugar

Contents

Description

Provides "syntax sugar" for constructing vinyl records with named fields, using GHC's OverloadedLabels extension.

This lets you create records using the following syntax, clearly associating each field's name with its value:

john :: Rec ElField ['("name", String), '("age", Int)]
john = rec_
  #age 30
  #name "John Doe"

You can also extend an existing record using extend_:

john' :: Rec ElField ['("bornAt", String), '("name", String), '("age", Int)]
john' = extend_ john
  #bornAt "Zurich, Switzerland"
Synopsis

Record-construction sugar

rec_ :: RecSugarTy (Rec f '[]) o => o Source #

Create a record by adding fields to the empty record. This is the function you will use most of the time.

extend_ :: RecSugarTy (Rec f rs) o => Rec f rs -> o Source #

Create a record by extending an existing record.

Extending the syntax sugar

class NamedField (s :: Symbol) (r :: k) (f :: k -> Type) (a :: Type) | r -> s, r f -> a where Source #

Specifies how to convert a labeled value into an element of a vinyl record. The only default instance is for ElField, but you can define additional instances for your own interpretation functors.

Methods

toNamedField :: a -> f r Source #

Convert a value into a vinyl record element. You can imagine that this has the following type:

toNamedField :: KnownSymbol s => a -> ElField '(s, a)
Instances
(KnownSymbol s, s ~ s') => NamedField s' ((,) s a :: (Symbol, Type)) ElField a Source # 
Instance details

Defined in Data.Vinyl.Sugar

Methods

toNamedField :: a -> ElField (s, a) Source #

class RecSugarTy e o | o -> e where Source #

The workhorse class of this package. Implements a polyvariadic function that builds up a Rec and converts it into the desired output type.

You can enable rec_ syntax for your own types by writing additional RecSugarTy instances, adding a base case to rec'. Example:

data MyFunctor r -- elided

newtype MyRec rs = MyRec { unMyRec :: Rec MyFunctor rs }

instance RecSugarTy (Rec MyFunctor rs) (MyRec rs) where
  rec' = MyRec

Methods

rec' :: e -> o Source #

Instances
(NamedField s r f a, RecSugarTy (Rec f (r ': rs)) o, lbl ~ FieldLabel s) => RecSugarTy (Rec f rs) (lbl -> a -> o) Source # 
Instance details

Defined in Data.Vinyl.Sugar

Methods

rec' :: Rec f rs -> lbl -> a -> o Source #

Storable (Rec f rs) => RecSugarTy (Rec f rs) (SRec f rs) Source # 
Instance details

Defined in Data.Vinyl.Sugar

Methods

rec' :: Rec f rs -> SRec f rs Source #

NatToInt (RLength rs) => RecSugarTy (Rec f rs) (ARec f rs) Source # 
Instance details

Defined in Data.Vinyl.Sugar

Methods

rec' :: Rec f rs -> ARec f rs Source #

RecSugarTy (Rec f rs) (Rec f rs) Source # 
Instance details

Defined in Data.Vinyl.Sugar

Methods

rec' :: Rec f rs -> Rec f rs Source #

Auxiliary types

data FieldLabel (s :: Symbol) Source #

A simple proxy for type-level strings.

Constructors

FieldLabel 
Instances
s ~ s' => IsLabel s (FieldLabel s') Source # 
Instance details

Defined in Data.Vinyl.Sugar

Methods

fromLabel :: FieldLabel s' #

Enum (FieldLabel s) Source # 
Instance details

Defined in Data.Vinyl.Sugar

Eq (FieldLabel s) Source # 
Instance details

Defined in Data.Vinyl.Sugar

Methods

(==) :: FieldLabel s -> FieldLabel s -> Bool #

(/=) :: FieldLabel s -> FieldLabel s -> Bool #

Ord (FieldLabel s) Source # 
Instance details

Defined in Data.Vinyl.Sugar