generic-records-0.2.0.0: Magic record operations using generics

Copyright(C) 2017 Csongor Kiss
LicenseBSD3
MaintainerCsongor Kiss <kiss.csongor.kiss@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Records.Generic

Contents

Description

Magic record operations using Generics

These classes need not be instantiated manually, as GHC can automatically prove valid instances via Generics. Only the Generic class needs to be derived (see examples).

Synopsis

Subtype relationship

class Subtype sub sup where Source #

Structural subtype relationship

  module Test where

  import GHC.Generics
  import Record.Generic

  data Human = Human
    { name    :: String
    , age     :: Int
    , address :: String
    } deriving (Generic, Show)

  data Animal = Animal
    { name    :: String
    , age     :: Int
    } deriving (Generic, Show)

   human :: Human
   human = Human "Tunyasz" 50 "London"

>>> human
Human {name = "Tunyasz", age = 50, address = "London"}
>>> upcast human :: Animal
Animal {name = "Tunyasz", age = 50}

Minimal complete definition

upcast

Methods

upcast :: sub -> sup Source #

Cast the more specific subtype to the more general supertype

Instances

(Convert (Rep a) (Rep b), Generic a, Generic b) => Subtype a b Source #

Instances are created by the compiler

Methods

upcast :: a -> b Source #

Magic lens

class HasField field a s | s field -> a where Source #

Records that have a field with a given name.

Minimal complete definition

label

Methods

label :: Lens' s a Source #

Lens focusing on a field with a given name. Compatible with the lens package.

 type Lens' s a
   = forall f. Functor f => (a -> f a) -> s -> f s
>>> human & label @"name" .~ "Tamas"
Human {name = "Tamas", age = 50, address = "London"}

Instances

(Generic s, (~) (Maybe Type) (Contains field (Rep s)) (Just Type a), GHasField field (Rep s) a) => HasField field a s Source #

Instances are generated on the fly for all records that have the required field.

Methods

label :: Lens' s a Source #

Getter and setter

getField :: forall field a s. HasField field a s => s -> a Source #

Get field

>>> getField @"name" human
"Tunyasz"

setField :: forall field a s. HasField field a s => a -> s -> s Source #

Set field

>>> setField @"age" (setField @"name" "Tamas" human) 30
Human {name = "Tamas", age = 30, address = "London"}