generic-lens-1.1.0.0: Generically derive traversals, lenses and prisms.

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

Data.Generics.Product.Fields

Contents

Description

Derive record field 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.VL.Lens
>>> :m +Data.Function
>>> :{
data Human a
  = Human
    { name    :: String
    , age     :: Int
    , address :: String
    , other   :: a
    }
  | HumanNoAddress
    { name    :: String
    , age     :: Int
    , other   :: a
    }
  deriving (Generic, Show)
human :: Human Bool
human = Human { name = "Tunyasz", age = 50, address = "London", other = False }
:}

class HasField (field :: Symbol) s t a b | s field -> a, t field -> b, s field b -> t, t field a -> s where Source #

Records that have a field with a given name.

Methods

field :: Lens s t a b Source #

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

>>> human ^. field @"age"
50

Type changing

>>> :t human
human :: Human Bool
>>> :t human & field @"other" .~ (42 :: Int)
human & field @"other" .~ (42 :: Int) :: Human Int
>>> human & field @"other" .~ 42
Human {name = "Tunyasz", age = 50, address = "London", other = 42}

Type errors

>>> human & field @"weight" .~ 42
...
... The type Human Bool does not contain a field named 'weight'.
...
>>> human & field @"address" .~ ""
...
... Not all constructors of the type Human Bool
... contain a field named 'address'.
... The offending constructors are:
... HumanNoAddress
...
Instances
(Generic s, Generic t, ErrorUnless field s (CollectField field (Rep s)), HasTotalFieldP field (Rep s) ~~ Just a, HasTotalFieldP field (Rep t) ~~ Just b, HasTotalFieldP field (Rep (Indexed s)) ~~ Just a', HasTotalFieldP field (Rep (Indexed t)) ~~ Just b', t ~~ Infer s a' b, s ~~ Infer t b' a, GLens (HasTotalFieldPSym field) (Rep s) (Rep t) a b) => HasField field s t a b Source # 
Instance details

Defined in Data.Generics.Product.Fields

Methods

field :: Lens s t a b Source #

HasField f (Void1 a) (Void1 b) a b Source # 
Instance details

Defined in Data.Generics.Product.Fields

Methods

field :: Lens (Void1 a) (Void1 b) a b Source #

class HasField' (field :: Symbol) s a | s field -> a where Source #

Methods

field' :: Lens s s a a Source #

Instances
(Generic s, ErrorUnless field s (CollectField field (Rep s)), GLens' (HasTotalFieldPSym field) (Rep s) a) => HasField' field s a Source # 
Instance details

Defined in Data.Generics.Product.Fields

Methods

field' :: Lens s s a a Source #

class HasField_ (field :: Symbol) s t a b where Source #

Records that have a field with a given name.

This is meant to be more general than HasField, but that is not quite the case due to the lack of functional dependencies.

The types s and t must be applications of the same type constructor. In contrast, HasField also requires the parameters of that type constructor to have representational roles.

One use case of HasField_ over HasField is for records defined with data instance.

Methods

field_ :: Lens s t a b Source #

Instances
(Generic s, Generic t, ErrorUnless field s (CollectField field (Rep s)), HasTotalFieldP field (Rep s) ~~ Just a, HasTotalFieldP field (Rep t) ~~ Just b, UnifyHead s t, UnifyHead t s, GLens (HasTotalFieldPSym field) (Rep s) (Rep t) a b) => HasField_ field s t a b Source # 
Instance details

Defined in Data.Generics.Product.Fields

Methods

field_ :: Lens s t a b Source #

HasField_ f (Void1 a) (Void1 b) a b Source # 
Instance details

Defined in Data.Generics.Product.Fields

Methods

field_ :: Lens (Void1 a) (Void1 b) a b Source #

getField :: forall f a s. HasField' f s a => s -> a Source #

>>> getField @"age" human
50

setField :: forall f s a. HasField' f s a => a -> s -> s Source #

>>> setField @"age" 60 human
Human {name = "Tunyasz", age = 60, address = "London", other = False}