| 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.HasField
Description
Derive record field getters and setters generically.
Lens
module Example where
import GHC.Generics
import Record.Generic
data Human = Human
{ name :: String
, age :: Int
, address :: String
} deriving (Generic, Show)
human :: Human
human = Human "Tunyasz" 50 "London"
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"}
Getter and setter functions
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) 30Human {name = "Tamas", age = 30, address = "London"}
Internals
class GHasField field s a | field s -> a where Source #
Like HasField, but on the generic representation
Minimal complete definition
Instances
| GHasField field (K1 R a) a Source # | |
| GHasField field (S1 (MetaSel (Just Symbol field) p f b) (Rec0 a)) a Source # | |
| GHasFieldProd Symbol field s s' a (Contains field s) => GHasField field ((:*:) s s') a Source # | |
| GHasField field s a => GHasField field (M1 C c s) a Source # | |
| GHasField field s a => GHasField field (M1 D c s) a Source # | |