rio-0.1.18.0: A standard library for Haskell

LicenseMIT
MaintainerColin Woodbury <colin@fosskers.ca>
Safe HaskellSafe
LanguageHaskell2010

RIO.Lens

Contents

Description

Extra utilities from microlens.

@since: 0.1.16.0

Synopsis

Fold

type SimpleFold s a = forall r. Monoid r => Getting r s a #

A SimpleFold s a extracts several as from s; so, it's pretty much the same thing as (s -> [a]), but you can use it with lens operators.

The actual Fold from lens is more general:

type Fold s a =
  forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s

There are several functions in lens that accept lens's Fold but won't accept SimpleFold; I'm aware of takingWhile, droppingWhile, backwards, foldByOf, foldMapByOf. For this reason, try not to export SimpleFolds if at all possible. microlens-contra provides a fully lens-compatible Fold.

Lens users: you can convert a SimpleFold to Fold by applying folded . toListOf to it.

toListOf :: Getting (Endo [a]) s a -> s -> [a] #

toListOf is a synonym for (^..).

has :: Getting Any s a -> s -> Bool #

has checks whether a getter (any getter, including lenses, traversals, and folds) returns at least 1 value.

Checking whether a list is non-empty:

>>> has each []
False

You can also use it with e.g. _Left (and other 0-or-1 traversals) as a replacement for isNothing, isJust and other isConstructorName functions:

>>> has _Left (Left 1)
True

Lens

_1 :: Field1 s t a b => Lens s t a b #

Gives access to the 1st field of a tuple (up to 5-tuples).

Getting the 1st component:

>>> (1,2,3,4,5) ^. _1
1

Setting the 1st component:

>>> (1,2,3) & _1 .~ 10
(10,2,3)

Note that this lens is lazy, and can set fields even of undefined:

>>> set _1 10 undefined :: (Int, Int)
(10,*** Exception: Prelude.undefined

This is done to avoid violating a lens law stating that you can get back what you put:

>>> view _1 . set _1 10 $ (undefined :: (Int, Int))
10

The implementation (for 2-tuples) is:

_1 f t = (,) <$> f    (fst t)
             <*> pure (snd t)

or, alternatively,

_1 f ~(a,b) = (\a' -> (a',b)) <$> f a

(where ~ means a lazy pattern).

_2, _3, _4, and _5 are also available (see below).

_2 :: Field2 s t a b => Lens s t a b #

_3 :: Field3 s t a b => Lens s t a b #

_4 :: Field4 s t a b => Lens s t a b #

_5 :: Field5 s t a b => Lens s t a b #

at :: At m => Index m -> Lens' m (Maybe (IxValue m)) #

This lens lets you read, write, or delete elements in Map-like structures. It returns Nothing when the value isn't found, just like lookup:

Data.Map.lookup k m = m ^. at k

However, it also lets you insert and delete values by setting the value to Just value or Nothing:

Data.Map.insert k a m = m & at k .~ Just a

Data.Map.delete k m = m & at k .~ Nothing

Or you could use (?~) instead of (.~):

Data.Map.insert k a m = m & at k ?~ a

Note that at doesn't work for arrays or lists. You can't delete an arbitrary element from an array (what would be left in its place?), and you can't set an arbitrary element in a list because if the index is out of list's bounds, you'd have to somehow fill the stretch between the last element and the element you just inserted (i.e. [1,2,3] & at 10 .~ 5 is undefined). If you want to modify an already existing value in an array or list, you should use ix instead.

at is often used with non. See the documentation of non for examples.

Note that at isn't strict for Map, even if you're using Data.Map.Strict:

>>> Data.Map.Strict.size (Data.Map.Strict.empty & at 1 .~ Just undefined)
1

The reason for such behavior is that there's actually no “strict Map” type; Data.Map.Strict just provides some strict functions for ordinary Maps.

This package doesn't actually provide any instances for at, but there are instances for Map and IntMap in microlens-ghc and an instance for HashMap in microlens-platform.

lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b #

lens creates a Lens from a getter and a setter. The resulting lens isn't the most effective one (because of having to traverse the structure twice when modifying), but it shouldn't matter much.

A (partial) lens for list indexing:

ix :: Int -> Lens' [a] a
ix i = lens (!! i)                                   -- getter
            (\s b -> take i s ++ b : drop (i+1) s)   -- setter

Usage:

>>> [1..9] ^. ix 3
4

>>> [1..9] & ix 3 %~ negate
[1,2,3,-4,5,6,7,8,9]

When getting, the setter is completely unused; when setting, the getter is unused. Both are used only when the value is being modified. For instance, here we define a lens for the 1st element of a list, but instead of a legitimate getter we use undefined. Then we use the resulting lens for setting and it works, which proves that the getter wasn't used:

>>> [1,2,3] & lens undefined (\s b -> b : tail s) .~ 10
[10,2,3]

Iso

non :: Eq a => a -> Lens' (Maybe a) a #

non lets you “relabel” a Maybe by equating Nothing to an arbitrary value (which you can choose):

>>> Just 1 ^. non 0
1
>>> Nothing ^. non 0
0

The most useful thing about non is that relabeling also works in other direction. If you try to set the “forbidden” value, it'll be turned to Nothing:

>>> Just 1 & non 0 .~ 0
Nothing

Setting anything else works just fine:

>>> Just 1 & non 0 .~ 5
Just 5

Same happens if you try to modify a value:

>>> Just 1 & non 0 %~ subtract 1
Nothing
>>> Just 1 & non 0 %~ (+ 1)
Just 2

non is often useful when combined with at. For instance, if you have a map of songs and their playcounts, it makes sense not to store songs with 0 plays in the map; non can act as a filter that wouldn't pass such entries.

Decrease playcount of a song to 0, and it'll be gone:

>>> fromList [("Soon",1),("Yesterday",3)] & at "Soon" . non 0 %~ subtract 1
fromList [("Yesterday",3)]

Try to add a song with 0 plays, and it won't be added:

>>> fromList [("Yesterday",3)] & at "Soon" . non 0 .~ 0
fromList [("Yesterday",3)]

But it will be added if you set any other number:

>>> fromList [("Yesterday",3)] & at "Soon" . non 0 .~ 1
fromList [("Soon",1),("Yesterday",3)]

non is also useful when working with nested maps. Here a nested map is created when it's missing:

>>> Map.empty & at "Dez Mona" . non Map.empty . at "Soon" .~ Just 1
fromList [("Dez Mona",fromList [("Soon",1)])]

and here it is deleted when its last entry is deleted (notice that non is used twice here):

>>> fromList [("Dez Mona",fromList [("Soon",1)])] & at "Dez Mona" . non Map.empty . at "Soon" . non 0 %~ subtract 1
fromList []

To understand the last example better, observe the flow of values in it:

  • the map goes into at "Dez Mona"
  • the nested map (wrapped into Just) goes into non Map.empty
  • Just is unwrapped and the nested map goes into at "Soon"
  • Just 1 is unwrapped by non 0

Then the final value – i.e. 1 – is modified by subtract 1 and the result (which is 0) starts flowing backwards:

  • non 0 sees the 0 and produces a Nothing
  • at "Soon" sees Nothing and deletes the corresponding value from the map
  • the resulting empty map is passed to non Map.empty, which sees that it's empty and thus produces Nothing
  • at "Dez Mona" sees Nothing and removes the key from the map

Traversal

singular :: HasCallStack => Traversal s t a a -> Lens s t a a #

singular turns a traversal into a lens that behaves like a single-element traversal:

>>> [1,2,3] ^. singular each
1
>>> [1,2,3] & singular each %~ negate
[-1,2,3]

If there is nothing to return, it'll throw an error:

>>> [] ^. singular each
*** Exception: Lens.Micro.singular: empty traversal

However, it won't fail if you are merely setting the value:

>>> [] & singular each %~ negate

failing :: Traversal s t a b -> Traversal s t a b -> Traversal s t a b infixl 5 #

failing lets you chain traversals together; if the 1st traversal fails, the 2nd traversal will be used.

>>> ([1,2],[3]) & failing (_1.each) (_2.each) .~ 0
([0,0],[3])
>>> ([],[3]) & failing (_1.each) (_2.each) .~ 0
([],[0])

Note that the resulting traversal won't be valid unless either both traversals don't touch each others' elements, or both traversals return exactly the same results. To see an example of how failing can generate invalid traversals, see this Stackoverflow question.

filtered :: (a -> Bool) -> Traversal' a a #

filtered is a traversal that filters elements “passing” through it:

>>> (1,2,3,4) ^.. each
[1,2,3,4]
>>> (1,2,3,4) ^.. each . filtered even
[2,4]

It also can be used to modify elements selectively:

>>> (1,2,3,4) & each . filtered even %~ (*100)
(1,200,3,400)

The implementation of filtered is very simple. Consider this traversal, which always “traverses” just the value it's given:

id :: Traversal' a a
id f s = f s

And this traversal, which traverses nothing (in other words, doesn't traverse the value it's given):

ignored :: Traversal' a a
ignored f s = pure s

And now combine them into a traversal that conditionally traverses the value it's given, and you get filtered:

filtered :: (a -> Bool) -> Traversal' a a
filtered p f s = if p s then f s else pure s

By the way, note that filtered can generate illegal traversals – sometimes this can bite you. In particular, an optimisation that should be safe becomes unsafe. (To the best of my knowledge, this optimisation never happens automatically. If you just use filtered to modify/view something, you're safe. If you don't define any traversals that use filtered, you're safe too.)

Let's use evens as an example:

evens = filtered even

If evens was a legal traversal, you'd be able to fuse several applications of evens like this:

over evens f . over evens g = over evens (f . g)

Unfortunately, in case of evens this isn't a correct optimisation:

  • the left-side variant applies g to all even numbers, and then applies f to all even numbers that are left after f (because f might've turned some even numbers into odd ones)
  • the right-side variant applies f and g to all even numbers

Of course, when you are careful and know what you're doing, you won't try to make such an optimisation. However, if you export an illegal traversal created with filtered and someone tries to use it, they might mistakenly assume that it's legal, do the optimisation, and silently get an incorrect result.

If you are using filtered with some another traversal that doesn't overlap with -whatever the predicate checks-, the resulting traversal will be legal. For instance, here the predicate looks at the 1st element of a tuple, but the resulting traversal only gives you access to the 2nd:

pairedWithEvens :: Traversal [(Int, a)] [(Int, b)] a b
pairedWithEvens = each . filtered (even . fst) . _2

Since you can't do anything with the 1st components through this traversal, the following holds for any f and g:

over pairedWithEvens f . over pairedWithEvens g = over pairedWithEvens (f . g)

both :: Traversal (a, a) (b, b) a b #

both traverses both fields of a tuple. Unlike both from lens, it only works for pairs – not for triples or Either.

>>> ("str","ing") ^. both
"string"
>>> ("str","ing") & both %~ reverse
("rts","gni")

traversed :: Traversable f => Traversal (f a) (f b) a b #

traversed traverses any Traversable container (list, vector, Map, Maybe, you name it):

>>> Just 1 ^.. traversed
[1]

traversed is the same as traverse, but can be faster thanks to magic rewrite rules.

each :: Each s t a b => Traversal s t a b #

each tries to be a universal Traversal – it behaves like traversed in most situations, but also adds support for e.g. tuples with same-typed values:

>>> (1,2) & each %~ succ
(2,3)
>>> ["x", "y", "z"] ^. each
"xyz"

However, note that each doesn't work on every instance of Traversable. If you have a Traversable which isn't supported by each, you can use traversed instead. Personally, I like using each instead of traversed whenever possible – it's shorter and more descriptive.

You can use each with these things:

each :: Traversal [a] [b] a b

each :: Traversal (Maybe a) (Maybe b) a b
each :: Traversal (Either a a) (Either b b) a b  -- since 0.4.11

each :: Traversal (a,a) (b,b) a b
each :: Traversal (a,a,a) (b,b,b) a b
each :: Traversal (a,a,a,a) (b,b,b,b) a b
each :: Traversal (a,a,a,a,a) (b,b,b,b,b) a b

each :: (RealFloat a, RealFloat b) => Traversal (Complex a) (Complex b) a b

You can also use each with types from array, bytestring, and containers by using microlens-ghc, or additionally with types from vector, text, and unordered-containers by using microlens-platform.

ix :: Ixed m => Index m -> Traversal' m (IxValue m) #

This traversal lets you access (and update) an arbitrary element in a list, array, Map, etc. (If you want to insert or delete elements as well, look at at.)

An example for lists:

>>> [0..5] & ix 3 .~ 10
[0,1,2,10,4,5]

You can use it for getting, too:

>>> [0..5] ^? ix 3
Just 3

Of course, the element may not be present (which means that you can use ix as a safe variant of (!!)):

>>> [0..5] ^? ix 10
Nothing

Another useful instance is the one for functions – it lets you modify their outputs for specific inputs. For instance, here's maximum that returns 0 when the list is empty (instead of throwing an exception):

maximum0 = maximum & ix [] .~ 0

The following instances are provided in this package:

ix :: Int -> Traversal' [a] a

ix :: (Eq e) => e -> Traversal' (e -> a) a

You can also use ix with types from array, bytestring, and containers by using microlens-ghc, or additionally with types from vector, text, and unordered-containers by using microlens-platform.

_head :: Cons s s a a => Traversal' s a #

_head traverses the 1st element of something (usually a list, but can also be a Seq, etc):

>>> [1..5] ^? _head
Just 1

It can be used to modify too, as in this example where the 1st letter of a sentence is capitalised:

>>> "mary had a little lamb." & _head %~ toTitle
"Mary had a little lamb."

The reason it's a traversal and not a lens is that there's nothing to traverse when the list is empty:

>>> [] ^? _head
Nothing

This package only lets you use _head on lists, but if you use microlens-ghc you get instances for ByteString and Seq, and if you use microlens-platform you additionally get instances for Text and Vector.

_tail :: Cons s s a a => Traversal' s s #

_tail gives you access to the tail of a list (or Seq, etc):

>>> [1..5] ^? _tail
Just [2,3,4,5]

You can modify the tail as well:

>>> [4,1,2,3] & _tail %~ reverse
[4,3,2,1]

Since lists are monoids, you can use _tail with plain (^.) (and then it'll return an empty list if you give it an empty list):

>>> [1..5] ^. _tail
[2,3,4,5]
>>> [] ^. _tail
[]

If you want to traverse each element of the tail, use _tail with each:

>>> "I HATE CAPS." & _tail.each %~ toLower
"I hate caps."

This package only lets you use _tail on lists, but if you use microlens-ghc you get instances for ByteString and Seq, and if you use microlens-platform you additionally get instances for Text and Vector.

_init :: Snoc s s a a => Traversal' s s #

_init gives you access to all-but-the-last elements of the list:

>>> "Hello." ^. _init
"Hello"

See documentation for _tail, as _init and _tail are pretty similar.

_last :: Snoc s s a a => Traversal' s a #

_last gives you access to the last element of the list:

>>> "Hello." ^? _last
'.'

See documentation for _head, as _last and _head are pretty similar.

Prism

_Left :: Traversal (Either a b) (Either a' b) a a' #

_Left targets the value contained in an Either, provided it's a Left.

Gathering all Lefts in a structure (like the lefts function, but not necessarily just for lists):

>>> [Left 1, Right 'c', Left 3] ^.. each._Left
[1,3]

Checking whether an Either is a Left (like isLeft):

>>> has _Left (Left 1)
True
>>> has _Left (Right 1)
False

Extracting a value (if you're sure it's a Left):

>>> Left 1 ^?! _Left
1

Mapping over all Lefts:

>>> (each._Left %~ map toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]

Implementation:

_Left f (Left a)  = Left <$> f a
_Left _ (Right b) = pure (Right b)

_Right :: Traversal (Either a b) (Either a b') b b' #

_Right targets the value contained in an Either, provided it's a Right.

See documentation for _Left.

_Just :: Traversal (Maybe a) (Maybe a') a a' #

_Just targets the value contained in a Maybe, provided it's a Just.

See documentation for _Left (as these 2 are pretty similar). In particular, it can be used to write these:

  • Unsafely extracting a value from a Just:
   fromJust = (^?! _Just)
   
  • Checking whether a value is a Just:
   isJust = has _Just
   
  • Converting a Maybe to a list (empty or consisting of a single element):
   maybeToList = (^.. _Just)
   
  • Gathering all Justs in a list:
   catMaybes = (^.. each . _Just)
   

_Nothing :: Traversal' (Maybe a) () #

_Nothing targets a () if the Maybe is a Nothing, and doesn't target anything otherwise:

>>> Just 1 ^.. _Nothing
[]
>>> Nothing ^.. _Nothing
[()]

It's not particularly useful (unless you want to use has _Nothing as a replacement for isNothing), and provided mainly for consistency.

Implementation:

_Nothing f Nothing = const Nothing <$> f ()
_Nothing _ j       = pure j