named-records-0.4: Flexible records with named fields.

Safe HaskellNone

Data.NamedRecord

Contents

Description

Flexible records with named fields.

Named records allow you to define und use records with labeled fields. These records are first class objects. Record fields are labeled by names, which can basically be any type. However, the names package provides global name types and some syntactic sugar to use them.

Here is a complete walk-through, with Template Haskell syntactic sugar.

This is how a typical example preamble looks like:

 import Data.NamedRecord

In order to use names you need to declare them first (see the names package for further details):

 name "firstName"
 name "lastName"

These are two records Person and User:

 record "Person"
     `has` "firstName" := ''String
     `has` "lastName"  := ''String

 record "User"
     `has` "firstName" := ''String
     `has` "lastName"  := ''String
     `has` "loginName" := ''String

Note that these declarations create constructor functions newPerson and newUser, as well as type synonyms Person and User (use -ddump-splices to see what has been generated).

Here are two instances of these recors:

 julian = newPerson
    `set` firstName := "Julian"
    `set` lastName  := "Fleischer"

 alexander = newUser
    `set` firstName := "Alexander"
    `set` lastName  := "Carnicero"
    `set` loginName := "alexander.carnicero"

We can now create a displayName function like the following:

 displayName obj =
     (obj `get` firstName) ++ " " ++
     (obj `get` lastName)

Note that this function will accept any record that has a firstName and a lastName field of type String.

>>> displayName julian
Julian Fleischer
>>> displayName alexander
Alexander Carnicero

As mentioned above, records are first class citizens. That means you can create them anywhere:

>>> displayName (firstName := "John" :+ lastName := "Doe")
John Doe

It is also possible to declare default values:

 name "serverName"
 name "port"
 
 record "ServerConfig"
     `has` "serverName" := ''String := "localhost"
     `has` "port"       := ''Int := (4711 :: Int)
>>> newServerConfig
serverName := "localhost" :+ port := 4711
>>> newServerConfig `set` serverName := "example.org"
serverName := "example.org" :+ port := 4711
>>> newServerConfig `get` port
4711

Complex expressions and types need to be quoted using [e| expr |] and [t| type |] like so:

 record "Server"
     `has` "requestHandler" := [t| Request -> Response |]
                            := [e| \x -> answer x |]
     `has` "config" := ''Config := [e| newConfig |]

It is furthermore possible to extend existing records (but due to stage restrictions in GHCs implementation of Template Haskell, two records of which one extends the other can not be contained in the same module):

 module Sample2 where
 
 import Data.NamedRecord
 import Data.Word
 
 record "Account"
     `has` "id"        := ''Word64
 
     `has` "loginName" := ''String
     `has` "password"  := ''String
 
 record "Person"
     `has` "id"        := ''Word64
 
     `has` "firstName" := ''String
     `has` "lastName"  := ''String
 module Sample where
 
 import Data.NamedRecord
 import Data.Word
 
 import Sample2
 
 record "User"
     `extends` __Person
     `extends` __Account
 
     `has` "id"           := ''Word64
     `has` "emailAddress" := ''String

Synopsis

Documentation

class Property o n v | o n -> v whereSource

Methods

get :: o -> n -> vSource

set :: o -> (n := v) -> oSource

upd :: o -> (n := (v -> v)) -> oSource

Instances

Property b n v => Property (:+ a b) n v 
Property (:+ (:= n v) b) n v 
Property (:= n v) n v 

class New o whereSource

Methods

new :: oSource

Instances

(New a, New b) => New (:+ a b) 
New (:= a b) 

add :: b -> a -> a :+ bSource

data a := b Source

Constructors

a := b 

Instances

(Show a, Show b) => Show (:= a b) 
Binary v => Binary (:= n v) 
New (:= a b) 
Property (:+ (:= n v) b) n v 
Property (:= n v) n v 

data a :+ b Source

Constructors

a :+ b 

Instances

(Show a, Show b) => Show (:+ a b) 
(Binary v, Binary b) => Binary (:+ v b) 
(New a, New b) => New (:+ a b) 
Property b n v => Property (:+ a b) n v 
Property (:+ (:= n v) b) n v 

Template Haskell Syntactic Sugar

Declares a record (looks like a new keyword record). See the examples.

record :: String -> RecordSource

extends :: RecordExtends a => Record -> a -> RecordSource

Declares a field of a record. Use as infix operators. See the examples.

has :: RecordTemplate a b c => a -> b -> cSource

Names

name :: String -> Q [Dec]

names :: Names' a => a