generic-lens-0.5.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.Positions

Contents

Description

Derive positional product type getters and setters generically.

Synopsis

Lenses

Running example:

>>> :set -XTypeApplications
>>> :set -XDataKinds
>>> :set -XDeriveGeneric
>>> :set -XGADTs
>>> :set -XFlexibleContexts
>>> import GHC.Generics
>>> :m +Data.Generics.Internal.Lens
>>> :m +Data.Function
>>> :{
data Human = Human
  { name    :: String
  , age     :: Int
  , address :: String
  }
  deriving (Generic, Show)
human :: Human
human = Human "Tunyasz" 50 "London"
:}

class HasPosition (i :: Nat) s t a b | s i -> a, s i b -> t where #

Records that have a field at a given position.

Minimal complete definition

position

Methods

position :: Lens s t a b #

A lens that focuses on a field at a given position. Compatible with the lens package's Lens type.

>>> human ^. position @1
"Tunyasz"
>>> human & position @3 .~ "Berlin"
Human {name = "Tunyasz", age = 50, address = "Berlin"}

Type errors

>>> human & position @4 .~ "Berlin"
...
... The type Human does not contain a field at position 4
...

Instances

(Generic s, ErrorUnless i s ((&&) ((<?) 0 i) ((<=?) i (Size * (Rep s)))), Generic t, (~) * s' (Proxied * s), GHasPosition' i (Rep s) a, GHasPosition' i (Rep s') a', GHasPosition 1 i (Rep s) (Rep t) a b, (~) (*, *) ((,) * * t b) (Infer s' a' a (PickTv * a' b))) => HasPosition i s t a b # 

Methods

position :: Lens s t a b #

type HasPosition' i s a = HasPosition i s s a a #

getPosition :: forall i s a. HasPosition' i s a => s -> a #

setPosition :: forall i s a. HasPosition' i s a => a -> s -> s #