Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides very basic lens functionality, without extra dependencies.
For the documentation of the combinators see lens package. This module uses the same vocabulary.
Synopsis
- 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
- type Traversal s t a b = forall f. Applicative f => LensLike f s t a b
- type Traversal' s a = Traversal s s a a
- type LensLike f s t a b = (a -> f b) -> s -> f t
- type LensLike' f s a = (a -> f a) -> s -> f s
- type Getting r s a = LensLike (Const r) s s a a
- type AGetter s a = LensLike (Const a) s s a a
- type ASetter s t a b = LensLike Identity s t a b
- type ALens s t a b = LensLike (Pretext a b) s t a b
- type ALens' s a = ALens s s a a
- view :: Getting a s a -> s -> a
- use :: MonadState s m => Getting a s a -> m a
- getting :: (s -> a) -> Getting r s a
- set :: ASetter s t a b -> b -> s -> t
- over :: ASetter s t a b -> (a -> b) -> s -> t
- toDListOf :: Getting (DList a) s a -> s -> DList a
- toListOf :: Getting (DList a) s a -> s -> [a]
- toSetOf :: Getting (Set a) s a -> s -> Set a
- cloneLens :: Functor f => ALens s t a b -> LensLike f s t a b
- aview :: ALens s t a b -> s -> a
- _1 :: Lens (a, c) (b, c) a b
- _2 :: Lens (c, a) (c, b) a b
- (&) :: a -> (a -> b) -> b
- (^.) :: s -> Getting a s a -> a
- (.~) :: ASetter s t a b -> b -> s -> t
- (?~) :: ASetter s t a (Maybe b) -> b -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- (.=) :: MonadState s m => ASetter s s a b -> b -> m ()
- (?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m ()
- (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- (^#) :: s -> ALens s t a b -> a
- (#~) :: ALens s t a b -> b -> s -> t
- (#%~) :: ALens s t a b -> (a -> b) -> s -> t
- data Pretext a b t = Pretext {
- runPretext :: forall f. Functor f => (a -> f b) -> f t
Types
type Traversal s t a b = forall f. Applicative f => LensLike f s t a b Source #
type Traversal' s a = Traversal s s a a Source #
LensLike
rank-1 types
Getter
use :: MonadState s m => Getting a s a -> m a Source #
getting :: (s -> a) -> Getting r s a Source #
>>>
(3 :: Int) ^. getting (+2) . getting show
"5"
Since: Cabal-2.4
Setter
Fold
Lens
Common lenses
Operators
(.=) :: MonadState s m => ASetter s s a b -> b -> m () infixr 4 Source #
(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () infixr 4 Source #
Internal Comonads
lens
variant is also parametrised by profunctor.
Pretext | |
|
Cabal developer info
We cannot depend on template-haskell
, because Cabal is a boot library.
This fact makes defining optics a manual task. Here is a small recipe to
make the process less tedious.
First start a repl
cabal new-repl Cabal:hackage-tests
Because --extra-package
isn't yet implemented, we use a test-suite
with generics-sop
dependency.
In the repl, we load a helper script:
:l ../generics-sop-lens.hs
Now we are set up to derive lenses!
:m +Distribution.Types.SourceRepo putStr $ genericLenses (Proxy :: Proxy SourceRepo)
repoKind :: Lens' SourceRepo RepoKind repoKind f s = fmap (\x -> s { T.repoKind = x }) (f (T.repoKind s)) {-# INLINE repoKind #-} ...
Note: You may need to adjust type-aliases, e.g. String
to FilePath
.