| Copyright | (C) 2017 Csongor Kiss |
|---|---|
| License | BSD3 |
| Maintainer | Csongor Kiss <kiss.csongor.kiss@gmail.com> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Records.Generic
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).
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"
>>>humanHuman {name = "Tunyasz", age = 50, address = "London"}
>>>upcast human :: AnimalAnimal {name = "Tunyasz", age = 50}
Minimal complete definition
Magic lens
class HasField field a s | s field -> a where Source #
Records that have a field with a given name.
Minimal complete definition
Methods
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"}