yarl-0.1.1.0: Yet another records libraries
CopyrightGautier DI FOLCO
LicenseISC
MaintainerGautier DI FOLCO <gautier.difolco@gmail.com>
StabilityUnstable
Portabilitynot portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Records.Yarl.LinkedList

Description

Provide a simple record library working with HasField

Example:

import Data.Records.Yarl.LinkedList

type Person = Record '[Field "name" String, Field "age" Int]

marvin :: Person
marvin = Field "marvin" :> Field 42 :> RNil

desc :: Person -> String
desc p = "My name is " <> p.name <> " and I'm " <> show p.age
Synopsis

Documentation

data Record :: [Type] -> Type where Source #

Full extensible record

Constructors

RNil :: Record '[] 
(:>) :: HasNotField fieldName fields => Field fieldName a -> Record fields -> Record (Field fieldName a ': fields) infixr 5 

Instances

Instances details
HasField (fieldName :: Symbol) (Record (Field fieldName a ': otherFields)) a Source # 
Instance details

Defined in Data.Records.Yarl.LinkedList

Methods

getField :: Record (Field fieldName a ': otherFields) -> a #

HasField fieldName (Record otherFields) a => HasField (fieldName :: k) (Record (headField ': otherFields)) a Source # 
Instance details

Defined in Data.Records.Yarl.LinkedList

Methods

getField :: Record (headField ': otherFields) -> a #

newtype Field (name :: Symbol) a Source #

Field container

Constructors

Field 

Fields

Instances

Instances details
HasField (fieldName :: Symbol) (Record (Field fieldName a ': otherFields)) a Source # 
Instance details

Defined in Data.Records.Yarl.LinkedList

Methods

getField :: Record (Field fieldName a ': otherFields) -> a #

type family HasNotField (target :: Symbol) (names :: [Type]) :: Constraint where ... Source #

Watch for field name duplication

Equations

HasNotField x '[] = () 
HasNotField x (Field x v ': ys) = TypeError ('Text "Field already declared: " :<>: 'ShowType x) 
HasNotField x (Field y v ': ys) = HasNotField x ys 

class HasField (x :: k) r a | x r -> a where #

Constraint representing the fact that the field x belongs to the record type r and has field type a. This will be solved automatically, but manual instances may be provided as well.

Methods

getField :: r -> a #

Selector function to extract the field from the record.

Instances

Instances details
HasField (fieldName :: Symbol) (Record (Field fieldName a ': otherFields)) a Source # 
Instance details

Defined in Data.Records.Yarl.LinkedList

Methods

getField :: Record (Field fieldName a ': otherFields) -> a #

HasField fieldName (Record otherFields) a => HasField (fieldName :: k) (Record (headField ': otherFields)) a Source # 
Instance details

Defined in Data.Records.Yarl.LinkedList

Methods

getField :: Record (headField ': otherFields) -> a #