Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
Control.Lens.At
Contents
Description
- class At m where
- sans :: At m => Index m -> m -> m
- type family IxValue m :: *
- class Functor f => Ixed f m where
- ix :: Index m -> IndexedLensLike' (Index m) f m (IxValue m)
- ixAt :: (Applicative f, At m) => Index m -> IndexedLensLike' (Index m) f m (IxValue m)
- ixEach :: (Applicative f, Eq (Index m), Each f m m (IxValue m) (IxValue m)) => Index m -> IndexedLensLike' (Index m) f m (IxValue m)
- class Functor f => Contains f m where
- contains :: Index m -> IndexedLensLike' (Index m) f m Bool
- containsIx :: (Contravariant f, Functor f, Ixed (Accessor Any) m) => Index m -> IndexedLensLike' (Index m) f m Bool
- containsAt :: (Contravariant f, Functor f, At m) => Index m -> IndexedLensLike' (Index m) f m Bool
- containsLength :: forall i s. (Ord i, Num i) => (s -> i) -> i -> IndexedGetter i s Bool
- containsN :: Int -> Int -> IndexedGetter Int s Bool
- containsTest :: forall i s. (i -> s -> Bool) -> i -> IndexedGetter i s Bool
- containsLookup :: forall i s a. (i -> s -> Maybe a) -> i -> IndexedGetter i s Bool
- _at :: Ixed f m => Index m -> IndexedLensLike' (Index m) f m (IxValue m)
- resultAt :: Ixed f m => Index m -> IndexedLensLike' (Index m) f m (IxValue m)
At
At
provides a Lens
that can be used to read,
write or delete the value associated with a key in a Map
-like
container on an ad hoc basis.
An instance of At
should satisfy:
ix
k ≡at
k<.
traverse
Ixed
class Functor f => Ixed f m whereSource
This simple IndexedTraversal
lets you traverse
the value at a given
key in a Map
or element at an ordinal position in a list or Seq
.
Methods
ix :: Index m -> IndexedLensLike' (Index m) f m (IxValue m)Source
This simple IndexedTraversal
lets you traverse
the value at a given
key in a Map
or element at an ordinal position in a list or Seq
.
NB: Setting the value of this Traversal
will only set the value in the
Lens
if it is already present.
If you want to be able to insert missing values, you want at
.
>>>
Seq.fromList [a,b,c,d] & ix 2 %~ f
fromList [a,b,f c,d]
>>>
Seq.fromList [a,b,c,d] & ix 2 .~ e
fromList [a,b,e,d]
>>>
Seq.fromList [a,b,c,d] ^? ix 2
Just c
>>>
Seq.fromList [] ^? ix 2
Nothing
Instances
Applicative f => Ixed f ByteString | |
Applicative f => Ixed f ByteString | |
Applicative f => Ixed f Text | |
Applicative f => Ixed f Text | |
Applicative f => Ixed f (Complex a) | |
(Applicative f, Unbox a) => Ixed f (Vector a) | |
(Applicative f, Storable a) => Ixed f (Vector a) | |
(Applicative f, Prim a) => Ixed f (Vector a) | |
Applicative f => Ixed f (Vector a) | |
Applicative f => Ixed f (IntMap a) | |
Applicative f => Ixed f (Seq a) | |
Applicative f => Ixed f (Tree a) | |
Functor f => Ixed f (Identity a) | |
Applicative f => Ixed f [a] | |
(Applicative f, ~ * a b) => Ixed f (a, b) | |
(Functor f, Eq k) => Ixed f (k -> a) | |
(Applicative f, IArray UArray e, Ix i) => Ixed f (UArray i e) | arr |
(Applicative f, Ix i) => Ixed f (Array i e) | arr |
(Applicative f, Eq k, Hashable k) => Ixed f (HashMap k a) | |
(Applicative f, Ord k) => Ixed f (Map k a) | |
(Applicative f, ~ * a b, ~ * b c) => Ixed f (a, b, c) | |
(Applicative f, ~ * a b, ~ * b c, ~ * c d) => Ixed f (a, b, c, d) | |
(Applicative f, ~ * a b, ~ * b c, ~ * c d, ~ * d e) => Ixed f (a, b, c, d, e) | |
(Applicative f, ~ * a b, ~ * b c, ~ * c d, ~ * d e, ~ * e f') => Ixed f (a, b, c, d, e, f') | |
(Applicative f, ~ * a b, ~ * b c, ~ * c d, ~ * d e, ~ * e f', ~ * f' g) => Ixed f (a, b, c, d, e, f', g) | |
(Applicative f, ~ * a b, ~ * b c, ~ * c d, ~ * d e, ~ * e f', ~ * f' g, ~ * g h) => Ixed f (a, b, c, d, e, f', g, h) | |
(Applicative f, ~ * a b, ~ * b c, ~ * c d, ~ * d e, ~ * e f', ~ * f' g, ~ * g h, ~ * h i) => Ixed f (a, b, c, d, e, f', g, h, i) |
ixAt :: (Applicative f, At m) => Index m -> IndexedLensLike' (Index m) f m (IxValue m)Source
ixEach :: (Applicative f, Eq (Index m), Each f m m (IxValue m) (IxValue m)) => Index m -> IndexedLensLike' (Index m) f m (IxValue m)Source
Contains
class Functor f => Contains f m whereSource
This class provides a simple IndexedFold
(or IndexedTraversal
) that lets you view (and modify)
information about whether or not a container contains a given Index
.
Methods
contains :: Index m -> IndexedLensLike' (Index m) f m BoolSource
>>>
IntSet.fromList [1,2,3,4] ^. contains 3
True
>>>
IntSet.fromList [1,2,3,4] ^. contains 5
False
>>>
IntSet.fromList [1,2,3,4] & contains 3 .~ False
fromList [1,2,4]
Instances
containsIx :: (Contravariant f, Functor f, Ixed (Accessor Any) m) => Index m -> IndexedLensLike' (Index m) f m BoolSource
containsAt :: (Contravariant f, Functor f, At m) => Index m -> IndexedLensLike' (Index m) f m BoolSource
containsLength :: forall i s. (Ord i, Num i) => (s -> i) -> i -> IndexedGetter i s BoolSource
containsN :: Int -> Int -> IndexedGetter Int s BoolSource
Construct a contains
check for a fixed number of elements.
containsTest :: forall i s. (i -> s -> Bool) -> i -> IndexedGetter i s BoolSource
Construct a contains
check that uses an arbitrary test.
containsLookup :: forall i s a. (i -> s -> Maybe a) -> i -> IndexedGetter i s BoolSource