generic-lens-0.1.0.0: Generic data-structure operations exposed as lenses.

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

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"

Synopsis

Documentation

class HasFieldAt index a s | s index -> a where Source #

Types that have a field at given position.

Minimal complete definition

itemAt

Methods

itemAt :: Lens' s a Source #

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

>>> human & itemAt @1 .~ "Tamas"
Human "Tamas" 50 "London"

Instances

(Generic s, (~) Bool (ContainsAt BaseIndex index (Rep s)) True, GHasFieldAt BaseIndex index (Rep s) a) => HasFieldAt index a s Source #

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

Methods

itemAt :: Lens' s a Source #

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) 30
Human "Tamas" 30 "London"