Safe Haskell | None |
---|---|
Language | Haskell2010 |
A lens library that integrates with OverloadedLabels.
Unlike the lens
package (and others), lenses are defined as a newtype
instead of a type synonym, to avoid overlapping with other IsLabel
instances. However, the LensFn
and runLens
functions allow converting
between the two types; for example:
LensFn :: Control.Lens.LensLike f s t a b -> Lens.Labels.LensLike f s t a b runLens :: Lens.Labels.LensLike f s t a b -> Control.Lens.LensLike f s t a b
TODO: support more general optic types (e.g., prisms).
- newtype LensFn a b = LensFn {
- runLens :: a -> b
- type LensLike f s t a b = LensFn (a -> f b) (s -> f t)
- type LensLike' f s a = LensLike f s s a a
- (&) :: a -> (a -> b) -> b
- (.) :: Category k cat => forall b c a. cat b c -> cat a b -> cat a c
- type Lens s t a b = forall f. Functor f => LensLike f s t a b
- class HasLens x f s t a b | x s -> a, x t -> b, x s b -> t, x t a -> s where
- data Proxy# :: forall k. k -> TYPE VoidRep
- proxy# :: Proxy# k a
- type ASetter s t a b = LensLike Identity s t a b
- (.~) :: ASetter s t a b -> b -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- over :: ASetter s t a b -> (a -> b) -> s -> t
- newtype Const k a b :: forall k. * -> k -> * = Const {
- getConst :: a
- type Getting r s t a b = LensLike (Const r) s t a b
- (^.) :: s -> Getting a s t a b -> a
- view :: s -> Getting a s t a b -> a
Lenses
A newtype for defining lenses. Can be composed using `(Control.Category..)` (also exported from this module).
HasLens
class HasLens x f s t a b | x s -> a, x t -> b, x s b -> t, x t a -> s where Source #
A type class for lens fields.
data Proxy# :: forall k. k -> TYPE VoidRep #
The type constructor Proxy#
is used to bear witness to some
type variable. It's used when you want to pass around proxy values
for doing things like modelling type applications. A Proxy#
is not only unboxed, it also has a polymorphic kind, and has no
runtime representation, being totally free.
Setters
Getters
newtype Const k a b :: forall k. * -> k -> * #
The Const
functor.
Functor (Const * m) | |
Monoid m => Applicative (Const * m) | |
Foldable (Const * m) | |
Generic1 (Const * a) | |
Bounded a => Bounded (Const k a b) | |
Enum a => Enum (Const k a b) | |
Eq a => Eq (Const k a b) | |
Floating a => Floating (Const k a b) | |
Fractional a => Fractional (Const k a b) | |
Integral a => Integral (Const k a b) | |
Num a => Num (Const k a b) | |
Ord a => Ord (Const k a b) | |
Read a => Read (Const k a b) | This instance would be equivalent to the derived instances of the
|
Real a => Real (Const k a b) | |
RealFloat a => RealFloat (Const k a b) | |
RealFrac a => RealFrac (Const k a b) | |
Show a => Show (Const k a b) | This instance would be equivalent to the derived instances of the
|
Ix a => Ix (Const k a b) | |
Generic (Const k a b) | |
Semigroup a => Semigroup (Const k a b) | |
Monoid a => Monoid (Const k a b) | |
Storable a => Storable (Const k a b) | |
Bits a => Bits (Const k a b) | |
FiniteBits a => FiniteBits (Const k a b) | |
type Rep1 (Const * a) | |
type Rep (Const k a b) | |