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 positional product type getters and setters generically.
Synopsis
- class HasPosition (i :: Nat) s t a b | s i -> a, t i -> b, s i b -> t, t i a -> s where
- class HasPosition' (i :: Nat) s a | s i -> a where
- class HasPosition_ (i :: Nat) s t a b where
- class HasPosition0 (i :: Nat) s t a b where
- getPosition :: forall i s a. HasPosition' i s a => s -> a
- setPosition :: forall i s a. HasPosition' i 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 = 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, t i -> b, s i b -> t, t i a -> s where Source #
Records that have a field at a given position.
position :: Lens s t a b Source #
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, Generic t, ErrorUnless i s ((0 <? i) && (i <=? Size (Rep s))), GLens (HasTotalPositionPSym i) (CRep s) (CRep t) a b, HasTotalPositionP i (CRep s) ~~ Just a, HasTotalPositionP i (CRep t) ~~ Just b, HasTotalPositionP i (CRep (Indexed s)) ~~ Just a', HasTotalPositionP i (CRep (Indexed t)) ~~ Just b', t ~~ Infer s a' b, s ~~ Infer t b' a, Coercible (CRep s) (Rep s), Coercible (CRep t) (Rep t)) => HasPosition i s t a b Source # | |
Defined in Data.Generics.Product.Positions | |
HasPosition f (Void1 a) (Void1 b) a b Source # | |
class HasPosition' (i :: Nat) s a | s i -> a where Source #
Records that have a field at a given position.
The difference between HasPosition
and HasPosition_
is similar to the
one between HasField
and
HasField_
.
See HasField_
.
class HasPosition_ (i :: Nat) s t a b where Source #
Instances
(Generic s, Generic t, ErrorUnless i s ((0 <? i) && (i <=? Size (Rep s))), GLens (HasTotalPositionPSym i) (CRep s) (CRep t) a b, UnifyHead s t, UnifyHead t s, Coercible (CRep s) (Rep s), Coercible (CRep t) (Rep t)) => HasPosition_ i s t a b Source # | |
Defined in Data.Generics.Product.Positions | |
HasPosition_ f (Void1 a) (Void1 b) a b Source # | |
class HasPosition0 (i :: Nat) s t a b where Source #
Records that have a field at a given position.
This class gives the minimal constraints needed to define this lens.
For common uses, see HasPosition
.
getPosition :: forall i s a. HasPosition' i s a => s -> a Source #
setPosition :: forall i s a. HasPosition' i s a => a -> s -> s Source #