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 :: k) (c :: k) (a :: k). 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
- type Lens' s a = Lens s s a a
- class HasLens f s t (x :: Symbol) a b | x s -> a, x t -> b, x s b -> t, x t a -> s where
- data Proxy# :: forall k0. k0 -> TYPE (TupleRep ([] RuntimeRep))
- proxy# :: Proxy# k0 a
- class HasLens f s s x a a => HasLens' f s x a | x s -> a where
- 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 :: k) :: 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 :: Getting a s t a b -> s -> a
Lenses
A newtype for defining lenses. Can be composed using '(Control.Category..)', which is exported from this module.
(.) :: Category k cat => forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c infixr 9 #
morphism composition
HasLens
class HasLens f s t (x :: Symbol) 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 k0. k0 -> TYPE (TupleRep ([] RuntimeRep)) #
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.
class HasLens f s s x a a => HasLens' f s x a | x s -> a where Source #
A type class for lens fields of monomorphic types (i.e., where the lens doesn't change the outer type).
This class can be used to simplify instance declarations and type
errors, by "forwarding" HasLens
to simpler instances. For example:
instance (HasLens' f Foo x a, a ~ b) => HasLens f Foo Foo x a b where where lensOf = lensOf' instance Functor f => HasLens' f Foo "a" Int where ... instance Functor f => HasLens' f Foo "b" Double where ... instance Functor f => HasLens' f Foo "c" [Float] where ... ...
Setters
Getters
newtype Const k a (b :: k) :: forall k. * -> k -> * #
The Const
functor.
Generic1 k (Const k a) | |
Functor (Const * m) | Since: 2.1 |
Monoid m => Applicative (Const * m) | Since: 2.0.1 |
Foldable (Const * m) | Since: 4.7.0.0 |
Traversable (Const * m) | Since: 4.7.0.0 |
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
Since: 4.8.0.0 |
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
Since: 4.8.0.0 |
Ix a => Ix (Const k a b) | |
Generic (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 k (Const k a) | |
type Rep (Const k a b) | |