| 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 |
Data.Generics.Product.HasFieldAt
Contents
Description
Derive product items lenses generically.
module Example where
import GHC.Generics
import Data.Generics.Product
data Human = Human String Int String
deriving (Generic, Show)
human :: Human
human = Human "Tunyasz" 50 "London"
- class HasFieldAt index a s | s index -> a where
- getFieldAt :: forall index a s. HasFieldAt index a s => s -> a
- setFieldAt :: forall index a s. HasFieldAt index a s => a -> s -> s
Documentation
class HasFieldAt index a s | s index -> a where Source #
Types that have a field at given position.
Minimal complete definition
Methods
Lens focusing on a field at a given index. Compatible with the lens package.
>>>human & itemAt @1 .~ "Tamas"Human "Tamas" 50 "London"
Getter and setter functions
getFieldAt :: forall index a s. HasFieldAt index a s => s -> a Source #
Get positional field
>>>getFieldAt @1 human"Tunyasz"
setFieldAt :: forall index a s. HasFieldAt index a s => a -> s -> s Source #
Set positional field
>>>setFieldAt @2 (setField @1 "Tamas" human) 30Human "Tamas" 30 "London"