records-0.1.1.2: A flexible record system

Data.Record.Combinators

Contents

Description

Record combinators built on top of the record core that Data.Record provides.

Synopsis

Record styles

withStyle :: Record (Domain style) rec => rec style -> style -> rec styleSource

Fixes the style of a record. When a record is constructed using X, (:&), and (:=), the style of this record is not fixed. For example, the most general type of the record

    X :& Surname := "Jeltsch" :& Age := 33 :& Room := "HG/2.39"

is

    (App style sortSurname ~ String, Num (App style sortAge), App style sortRoom ~ String) =>
    (X :& Surname ::: sortSurname :& Age ::: sortAge :& Room ::: sortRoom) style

We can fix the style of that record using the expression

    X :& Surname := "Jeltsch" :& Age := 33 :& Room := "HG/2.39" `withStyle` Id KindStar

which has the most general type

    (Num age) =>
    (X :& Surname ::: String :& Age ::: age :& Room ::: String) (Id KindStar)

The withStyle combinator is similar to asTypeOf.

Field operations

(!!!) :: Separation rec remain sepName sepSort => rec style -> sepName -> App style sepSortSource

Looks up the value of a record field.

(\\\) :: Separation rec remain sepName sepSort => rec style -> sepName -> remain styleSource

Removes a record field.

Catenation

type family Cat rec1 rec2 :: * -> *Source

Catenation of two record schemes.

catSource

Arguments

:: (TypeFun style, Record (Domain style) rec1, Record (Domain style) rec2) 
=> rec1 style 
-> rec2 style 
-> Cat rec1 rec2 style 

Catenation of two records.

Applicative functor operations

repeatSource

Arguments

:: (TypeFun style, Record (Domain style) rec) 
=> Universal style 
-> rec style 

Generates a record whose fields all contain the same value. In contrast to the repeat function from the Prelude, this function generates a finite data structure. Thereby, the size of the generated record is determined by its type. repeat is almost a proper implementation of pure from the Applicative class.

(<<*>>)Source

Arguments

:: (TypeFun style, TypeFun style', Domain style ~ Domain style', Record (Domain (style :-> style')) rec) 
=> rec (style :-> style') 
-> rec style 
-> rec style' 

Merges a record of functions and a record of arguments by applying the functions to the corresponding arguments. The (<<*>>) function is almost a proper implementation of (<*>) from the Applicative class.

mapSource

Arguments

:: (TypeFun style, TypeFun style', Domain style ~ Domain style', Record (Domain (style :-> style')) rec) 
=> Universal (style :-> style') 
-> rec style 
-> rec style' 

Transforms a record by applying a function to all its field values.

zipWithSource

Arguments

:: (TypeFun style1, TypeFun style2, TypeFun style', Domain style1 ~ Domain style2, Domain style2 ~ Domain style', Record (Domain (style1 :-> (style2 :-> style'))) rec) 
=> Universal (style1 :-> (style2 :-> style')) 
-> rec style1 
-> rec style2 
-> rec style' 

Merges two records by applying a function to each pair of corresponding field values.

Modification of fields

modifySource

Arguments

:: (TypeFun style, Record (Domain style) rec, Record (Domain style) modRec, Convertible rec modRec) 
=> modRec (style :-> style) 
-> rec style 
-> rec style 

Modifies a record by changing some of its field values. The first argument of modify is called the modification record, and the second argument is called the data record. The result is formed by applying each field value of the modification record to the corresponding field value of the data record and replacing the latter by the result of the application. Data record fields that have no corresponding field in the modification record are left unchanged.

(///)Source

Arguments

:: (TypeFun style, Record (Domain style) rec, Record (Domain style) replRec, Convertible rec replRec) 
=> rec style 
-> replRec style 
-> rec style 

Overwrites the values of multiple record fields. The first argument is the source record, and the second argument lists the names of the fields to be modified together with their new values.

Conversion

toList :: (Kind kind, Record kind rec) => rec (Const kind val) -> [val]Source

Converts a record whose style is a constant function into the list of its field values.