lens-3.8.7.3: Lenses, Folds and Traversals

Portabilitynon-portable
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.At

Contents

Description

 

Synopsis

At

class At m whereSource

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

Methods

at :: Index m -> IndexedLens' (Index m) m (Maybe (IxValue m))Source

>>> Map.fromList [(1,"world")] ^.at 1
Just "world"
>>> at 1 ?~ "hello" $ Map.empty
fromList [(1,"hello")]

Note: Map-like containers form a reasonable instance, but not Array-like ones, where you cannot satisfy the Lens laws.

Instances

At (IntMap a) 
Ord k => At (Map k a) 
(Eq k, Hashable k) => At (HashMap k a) 

Ixed

type family IxValue m :: *Source

This provides a common notion of a value at an index that is shared by both Ixed and At.

class (Functor f, Contains (Accessor (IxValue m)) m) => 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 ! i ≡ arr ^. ix i
 arr // [(i,e)] ≡ ix i .~ e $ arr
(Applicative f, Ix i) => Ixed f (Array i e)
 arr ! i ≡ arr ^. ix i
 arr // [(i,e)] ≡ ix 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

A definition of ix for types with an At instance. This is the default if you don't specify a definition for ix.

ixEach :: (Applicative f, Eq (Index m), Each f m m (IxValue m) (IxValue m)) => Index m -> IndexedLensLike' (Index m) f m (IxValue m)Source

A definition of ix for types with an Each instance.

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

Gettable f => Contains f ByteString 
Gettable f => Contains f ByteString 
Gettable f => Contains f Text 
Gettable f => Contains f Text 
Functor f => Contains f IntSet 
(Gettable f, Unbox a) => Contains f (Vector a) 
(Gettable f, Storable a) => Contains f (Vector a) 
(Gettable f, Prim a) => Contains f (Vector a) 
Gettable f => Contains f (Vector a) 
Gettable k => Contains k (IntMap a) 
Gettable k => Contains k (Identity a) 
Gettable f => Contains f (Tree a) 
Gettable f => Contains f (Complex a) 
Gettable f => Contains f (Seq a) 
Gettable f => Contains f [a] 
(Functor f, Eq a, Hashable a) => Contains f (HashSet a) 
(Functor f, Ord a) => Contains f (Set a) 
(Gettable f, IArray UArray e, Ix i) => Contains f (UArray i e) 
(Gettable f, Ix i) => Contains f (Array i e) 
(Gettable f, Eq k, Hashable k) => Contains f (HashMap k a) 
(Gettable f, Ord k) => Contains f (Map k a) 
Gettable k => Contains k (a, b) 
Gettable f => Contains f (e -> a) 
Gettable k => Contains k (a, b, c) 
Gettable k => Contains k (a, b, c, d) 
Gettable k => Contains k (a, b, c, d, e) 
Gettable k => Contains k (a, b, c, d, e, f) 
Gettable k => Contains k (a, b, c, d, e, f, g) 
Gettable k => Contains k (a, b, c, d, e, f, g, h) 
Gettable k => Contains k (a, b, c, d, e, f, g, h, i) 

containsIx :: (Gettable f, Ixed (Accessor Any) m) => Index m -> IndexedLensLike' (Index m) f m BoolSource

A definition of contains for types with an Ix instance.

containsAt :: (Gettable f, At m) => Index m -> IndexedLensLike' (Index m) f m BoolSource

A definition of ix for types with an At instance. This is the default if you don't specify a definition for contains and you are on GHC >= 7.0.2

containsLength :: forall i s. (Ord i, Num i) => (s -> i) -> i -> IndexedGetter i s BoolSource

Construct a contains check based on some notion of length for the container.

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

Construct a contains check that uses an arbitrary lookup function.

Deprecated

_at :: Ixed f m => Index m -> IndexedLensLike' (Index m) f m (IxValue m)Source

Deprecated: use ix. This function will be removed in version 3.9

Deprecated aliases for ix.

resultAt :: Ixed f m => Index m -> IndexedLensLike' (Index m) f m (IxValue m)Source

Deprecated: use ix. This function will be removed in version 3.9

Deprecated aliases for ix.