Copyright | (C) 2018 Csongor Kiss |
---|---|
License | BSD3 |
Maintainer | Csongor Kiss <kiss.csongor.kiss@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Derive record field getters and setters generically.
Synopsis
- class HasField (field :: Symbol) s t a b | s field -> a, t field -> b, s field b -> t, t field a -> s where
- class HasField' (field :: Symbol) s a | s field -> a where
- class HasField_ (field :: Symbol) s t a b where
- getField :: forall f a s. HasField' f s a => s -> a
- setField :: forall f s a. HasField' f s a => a -> s -> s
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.
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 # | |
Defined in Data.Generics.Product.Fields | |
HasField f (Void1 a) (Void1 b) a b 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
.
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 # | |
Defined in Data.Generics.Product.Fields | |
HasField_ f (Void1 a) (Void1 b) a b Source # | |