Copyright | (C) 2012-16 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
Synopsis
- class Ixed m => At m where
- sans :: At m => Index m -> m -> m
- iat :: At m => Index m -> IndexedLens' (Index m) m (Maybe (IxValue m))
- type family Index (s :: *) :: *
- type family IxValue (m :: *) :: *
- class Ixed m where
- ixAt :: At m => Index m -> Traversal' m (IxValue m)
- iix :: Ixed m => Index m -> IndexedTraversal' (Index m) m (IxValue m)
- class Contains m where
- icontains :: Contains m => Index m -> IndexedLens' (Index m) m Bool
At
class Ixed m => At m where Source #
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
iat :: At m => Index m -> IndexedLens' (Index m) m (Maybe (IxValue m)) Source #
An indexed version of at
.
>>>
Map.fromList [(1,"world")] ^@. iat 1
(1,Just "world")
>>>
iat 1 %@~ (\i x -> if odd i then Just "hello" else Nothing) $ Map.empty
fromList [(1,"hello")]
>>>
iat 2 %@~ (\i x -> if odd i then Just "hello" else Nothing) $ Map.empty
fromList []
Ixed
type family Index (s :: *) :: * Source #
Instances
type Index ByteString Source # | |
type Index ByteString Source # | |
type Index IntSet Source # | |
type Index Text Source # | |
type Index Text Source # | |
type Index [a] Source # | |
type Index (Maybe a) Source # | |
type Index (Complex a) Source # | |
type Index (NonEmpty a) Source # | |
type Index (Identity a) Source # | |
type Index (IntMap a) Source # | |
type Index (Tree a) Source # | |
type Index (Seq a) Source # | |
type Index (Set a) Source # | |
type Index (HashSet a) Source # | |
type Index (Vector a) Source # | |
type Index (Vector a) Source # | |
type Index (Vector a) Source # | |
type Index (Vector a) Source # | |
type Index (e -> a) Source # | |
type Index (e -> a) = e | |
type Index (a, b) Source # | |
type Index (UArray i e) Source # | |
type Index (Array i e) Source # | |
type Index (Map k a) Source # | |
type Index (HashMap k a) Source # | |
type Index (a, b, c) Source # | |
type Index (a, b, c, d) Source # | |
type Index (a, b, c, d, e) Source # | |
type Index (a, b, c, d, e, f) Source # | |
type Index (a, b, c, d, e, f, g) Source # | |
type Index (a, b, c, d, e, f, g, h) Source # | |
type Index (a, b, c, d, e, f, g, h, i) Source # | |
type family IxValue (m :: *) :: * Source #
Instances
type IxValue ByteString Source # | |
type IxValue ByteString Source # | |
type IxValue IntSet Source # | |
type IxValue Text Source # | |
type IxValue Text Source # | |
type IxValue [a] Source # | |
type IxValue [a] = a | |
type IxValue (Maybe a) Source # | |
type IxValue (NonEmpty a) Source # | |
type IxValue (Identity a) Source # | |
type IxValue (IntMap a) Source # | |
type IxValue (Tree a) Source # | |
type IxValue (Seq a) Source # | |
type IxValue (Set k) Source # | |
type IxValue (HashSet k) Source # | |
type IxValue (Vector a) Source # | |
type IxValue (Vector a) Source # | |
type IxValue (Vector a) Source # | |
type IxValue (Vector a) Source # | |
type IxValue (e -> a) Source # | |
type IxValue (e -> a) = a | |
type IxValue (a, a2) Source # | |
type IxValue (a, a2) = a | |
type IxValue (UArray i e) Source # | |
type IxValue (Array i e) Source # | |
type IxValue (Map k a) Source # | |
type IxValue (HashMap k a) Source # | |
type IxValue (a, a2, a3) Source # | |
type IxValue (a, a2, a3) = a | |
type IxValue (a, a2, a3, a4) Source # | |
type IxValue (a, a2, a3, a4) = a | |
type IxValue (a, a2, a3, a4, a5) Source # | |
type IxValue (a, a2, a3, a4, a5) = a | |
type IxValue (a, a2, a3, a4, a5, a6) Source # | |
type IxValue (a, a2, a3, a4, a5, a6) = a | |
type IxValue (a, a2, a3, a4, a5, a6, a7) Source # | |
type IxValue (a, a2, a3, a4, a5, a6, a7) = a | |
type IxValue (a, a2, a3, a4, a5, a6, a7, a8) Source # | |
type IxValue (a, a2, a3, a4, a5, a6, a7, a8) = a | |
type IxValue (a, a2, a3, a4, a5, a6, a7, a8, a9) Source # | |
type IxValue (a, a2, a3, a4, a5, a6, a7, a8, a9) = a |
Provides a simple Traversal
lets you traverse
the value at a given
key in a Map
or element at an ordinal position in a list or Seq
.
ix :: Index m -> Traversal' m (IxValue m) Source #
NB: Setting the value of this Traversal
will only set the value in
at
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
ix :: (Applicative f, At m) => Index m -> LensLike' f m (IxValue m) Source #
NB: Setting the value of this Traversal
will only set the value in
at
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
Ixed ByteString Source # | |
ix :: Index ByteString -> Traversal' ByteString (IxValue ByteString) Source # | |
Ixed ByteString Source # | |
ix :: Index ByteString -> Traversal' ByteString (IxValue ByteString) Source # | |
Ixed IntSet Source # | |
Ixed Text Source # | |
Ixed Text Source # | |
Ixed [a] Source # | |
Ixed (Maybe a) Source # | |
Ixed (NonEmpty a) Source # | |
Ixed (Identity a) Source # | |
Ixed (IntMap a) Source # | |
Ixed (Tree a) Source # | |
Ixed (Seq a) Source # | |
Ord k => Ixed (Set k) Source # | |
(Eq k, Hashable k) => Ixed (HashSet k) Source # | |
Unbox a => Ixed (Vector a) Source # | |
Storable a => Ixed (Vector a) Source # | |
Prim a => Ixed (Vector a) Source # | |
Ixed (Vector a) Source # | |
Eq e => Ixed (e -> a) Source # | |
(~) * a a2 => Ixed (a, a2) Source # | |
(IArray UArray e, Ix i) => Ixed (UArray i e) Source # | arr |
Ix i => Ixed (Array i e) Source # | arr |
Ord k => Ixed (Map k a) Source # | |
(Eq k, Hashable k) => Ixed (HashMap k a) Source # | |
((~) * a a2, (~) * a a3) => Ixed (a, a2, a3) Source # | |
((~) * a a2, (~) * a a3, (~) * a a4) => Ixed (a, a2, a3, a4) Source # | |
((~) * a a2, (~) * a a3, (~) * a a4, (~) * a a5) => Ixed (a, a2, a3, a4, a5) Source # | |
((~) * a a2, (~) * a a3, (~) * a a4, (~) * a a5, (~) * a a6) => Ixed (a, a2, a3, a4, a5, a6) Source # | |
((~) * a a2, (~) * a a3, (~) * a a4, (~) * a a5, (~) * a a6, (~) * a a7) => Ixed (a, a2, a3, a4, a5, a6, a7) Source # | |
((~) * a a2, (~) * a a3, (~) * a a4, (~) * a a5, (~) * a a6, (~) * a a7, (~) * a a8) => Ixed (a, a2, a3, a4, a5, a6, a7, a8) Source # | |
((~) * a a2, (~) * a a3, (~) * a a4, (~) * a a5, (~) * a a6, (~) * a a7, (~) * a a8, (~) * a a9) => Ixed (a, a2, a3, a4, a5, a6, a7, a8, a9) Source # | |
iix :: Ixed m => Index m -> IndexedTraversal' (Index m) m (IxValue m) Source #
An indexed version of ix
.
>>>
Seq.fromList [a,b,c,d] & iix 2 %@~ f'
fromList [a,b,f' 2 c,d]
>>>
Seq.fromList [a,b,c,d] & iix 2 .@~ h
fromList [a,b,h 2,d]
>>>
Seq.fromList [a,b,c,d] ^@? iix 2
Just (2,c)
>>>
Seq.fromList [] ^@? iix 2
Nothing
Contains
class Contains m where Source #
This class provides a simple Lens
that lets you view (and modify)
information about whether or not a container contains a given Index
.
icontains :: Contains m => Index m -> IndexedLens' (Index m) m Bool Source #
An indexed version of contains
.
>>>
IntSet.fromList [1,2,3,4] ^@. icontains 3
(3,True)
>>>
IntSet.fromList [1,2,3,4] ^@. icontains 5
(5,False)
>>>
IntSet.fromList [1,2,3,4] & icontains 3 %@~ \i x -> if odd i then not x else x
fromList [1,2,4]
>>>
IntSet.fromList [1,2,3,4] & icontains 3 %@~ \i x -> if even i then not x else x
fromList [1,2,3,4]