| Portability | portable |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | None |
Data.List.Lens
Contents
Description
Traversals for manipulating parts of a list.
- _head :: Simple Lens [a] a
- _tail :: Simple Lens [a] [a]
- _last :: Simple Lens [a] a
- _init :: Simple Lens [a] [a]
- interspersed :: a -> Getter [a] [a]
- intercalated :: [a] -> Getter [[a]] [a]
- traverseList :: IndexedTraversal Int [a] [b] a b
- traverseHead :: SimpleIndexedTraversal Int [a] a
- traverseTail :: SimpleIndexedTraversal Int [a] a
- traverseInit :: SimpleIndexedTraversal Int [a] a
- traverseLast :: SimpleIndexedTraversal Int [a] a
- (~:) :: c -> Setting a b [c] [c] -> a -> b
- (=:) :: MonadState a m => c -> SimpleSetting a [c] -> m ()
- (<~:) :: c -> LensLike ((,) [c]) a b [c] [c] -> a -> ([c], b)
- (<=:) :: MonadState a m => c -> SimpleLensLike ((,) [c]) a [c] -> m [c]
- (++~) :: Setting a b [c] [c] -> [c] -> a -> b
- (<++~) :: LensLike ((,) [c]) a b [c] [c] -> [c] -> a -> ([c], b)
- (++=) :: MonadState a m => SimpleSetting a [b] -> [b] -> m ()
- (<++=) :: MonadState a m => SimpleLensLike ((,) [b]) a [b] -> [b] -> m [b]
Documentation
_head :: Simple Lens [a] aSource
A lens reading and writing to the head of a non-empty list.
Attempting to read or write to the head of an empty list will result in an error.
>>>[1,2,3]^._head1
_tail :: Simple Lens [a] [a]Source
A lens reading and writing to the tail of a non-empty list
Attempting to read or write to the tail of an empty list will result in an error.
>>>_tail .~ [3,4,5] $ [1,2][1,3,4,5]
_last :: Simple Lens [a] aSource
A lens reading and writing to the last element of a non-empty list
Attempting to read or write to the last element of an empty list will result in an error.
>>>[1,2]^._last2
_init :: Simple Lens [a] [a]Source
A lens reading and replacing all but the a last element of a non-empty list
Attempting to read or write to all but the last element of an empty list will result in an error.
>>>[1,2,3,4]^._init[1,2,3]
interspersed :: a -> Getter [a] [a]Source
Obtain a version of the list with the supplied value interspersed.
>>>"abcde"^.interspersed ','"a,b,c,d,e"
xs^.interspersed a = intersperse a xs
intercalated :: [a] -> Getter [[a]] [a]Source
Obtain a version of the list with the supplied value intercalated.
Traversals
traverseList :: IndexedTraversal Int [a] [b] a bSource
Indexed traversal of a list. The position in the list is available as the index.
traverseHead :: SimpleIndexedTraversal Int [a] aSource
A traversal for reading and writing to the head of a list
The position of the head in the original list (0) is available as the index.
>>>traverseHead +~ 1 $ [1,2,3][2,2,3]
traverseHead::Applicativef => (a -> f a) -> [a] -> f [a]
traverseTail :: SimpleIndexedTraversal Int [a] aSource
A traversal for editing the tail of a list
The position of each element in the original list is available as the index.
>>>traverseTail +~ 1 $ [1,2,3][1,3,4]
traverseTail::Applicativef => (a -> f a) -> [a] -> f [a]
traverseInit :: SimpleIndexedTraversal Int [a] aSource
A traversal of all but the last element of a list
The position of each element is available as the index.
>>>traverseInit +~ 1 $ [1,2,3][2,3,3]
traverseInit::Applicativef => (a -> f a) -> [a] -> f [a]
traverseLast :: SimpleIndexedTraversal Int [a] aSource
A traversal the last element in a list
The position of the last element in the original list is available as the index.
>>>traverseLast +~ 1 $ [1,2,3][1,2,4]
traverseLast::Applicativef => (a -> f a) -> [a] -> f [a]
(=:) :: MonadState a m => c -> SimpleSetting a [c] -> m ()Source
Cons onto the list(s) referenced by a Setter in your monad state
(=:) ::MonadStatea m => c ->SimpleSettera [c] -> m () (=:) ::MonadStatea m => c ->SimpleTraversala [c] -> m () (=:) ::MonadStatea m => c ->SimpleLensa [c] -> m () (=:) ::MonadStatea m => c ->SimpleIsoa [c] -> m ()
(<~:) :: c -> LensLike ((,) [c]) a b [c] [c] -> a -> ([c], b)Source
Cons onto the list(s) referenced by a Lens (or Traversal), returning the result.
If you use this with a Traversal you will receive back the concatenation of all of
the resulting lists instead of an individual result.
>>>'h' <~: _1 $ ("ello","world")("hello",("hello","world"))
(<~:) :: b ->SimpleLensa [b] -> a -> ([b], a) (<~:) :: b ->SimpleIsoa [b] -> a -> ([b], a) (<~:) :: b ->SimpleTraversala [b] -> a -> ([b], a)
(<=:) :: MonadState a m => c -> SimpleLensLike ((,) [c]) a [c] -> m [c]Source
Cons onto the list(s) referenced by a Lens (or Traversal) into your monad state,
returning the result.
If you use this with a Traversal, you will receive back the concatenation of all
of the resulting lists instead of an individual result.
(<=:) ::MonadStatea m =>SimpleLensa [c] -> c -> m [c] (<=:) ::MonadStatea m =>SimpleIsoa [c] -> c -> m [c] (<=:) ::MonadStatea m =>SimpleTraversala [c] -> c -> m [c]
(++~) :: Setting a b [c] [c] -> [c] -> a -> bSource
Append to the target of a list-valued setter by appending to it with (++).
(<>~) generalizes this operation to an arbitrary Monoid.
>>>:m + Control.Lens>>>both ++~ "!!!" $ ("hello","world")("hello!!!","world!!!")
(++~) ::SimpleSettera [b] -> [b] -> a -> a (++~) ::SimpleIsoa [b] -> [b] -> a -> a (++~) ::SimpleLensa [b] -> [b] -> a -> a (++~) ::SimpleTraversala [b] -> [b] -> a -> a
(<++~) :: LensLike ((,) [c]) a b [c] [c] -> [c] -> a -> ([c], b)Source
Append onto the end of the list targeted by a Lens and return the result.
(<<>~) generalizes this operation to an arbitrary Monoid.
When using a Traversal, the result returned is actually the concatenation of all of the results.
When you do not need the result of the operation, (++~) is more flexible.
(++=) :: MonadState a m => SimpleSetting a [b] -> [b] -> m ()Source
Append to the target(s) of a Simple Lens, Iso, Setter or Traversal with (++) in the current state.
(<>=) generalizes this operation to an arbitrary Monoid.
(++=) ::MonadStatea m =>SimpleSettera [b] -> [b] -> m () (++=) ::MonadStatea m =>SimpleIsoa [b] -> [b] -> m () (++=) ::MonadStatea m =>SimpleLensa [b] -> [b] -> m () (++=) ::MonadStatea m =>SimpleTraversala [b] -> [b] -> m ()
(<++=) :: MonadState a m => SimpleLensLike ((,) [b]) a [b] -> [b] -> m [b]Source
Append onto the end of the list targeted by a Lens into the current monadic state, and return the result.
(<<>=) generalizes this operation to an arbitrary Monoid.
When using a Traversal, the result returned is actually the concatenation of all of the results.
When you do not need the result of the operation, (++=) is more flexible.