1{-# LANGUAGE CPP #-}
2{-# LANGUAGE FlexibleInstances #-}
3{-# LANGUAGE FlexibleContexts #-}
4{-# LANGUAGE UndecidableInstances #-}
5{-# LANGUAGE RankNTypes #-}
6{-# LANGUAGE ScopedTypeVariables #-}
7{-# LANGUAGE MonoLocalBinds #-}
8{-# LANGUAGE ConstraintKinds #-}
9{-# LANGUAGE Trustworthy #-}
10
11
12{- |
13Module      :  Lens.Micro
14Copyright   :  (C) 2013-2016 Edward Kmett, 2015-2016 Artyom Kazak, 2018 Monadfix
15License     :  BSD-style (see the file LICENSE)
16
17This module provides the essential functionality. There are other packages in the microlens family – mix and match them at will. If you're writing an app, you want <http://hackage.haskell.org/package/microlens-platform microlens-platform> – it provides the most functionality.
18
19* <http://hackage.haskell.org/package/microlens-mtl microlens-mtl> – (@+=@) and friends, @use@, @zoom@\/@magnify@
20* <http://hackage.haskell.org/package/microlens-th microlens-th> – @makeLenses@ and @makeFields@
21* <http://hackage.haskell.org/package/microlens-ghc microlens-ghc> – everything in microlens + instances to make @each@\/@at@\/@ix@ usable with arrays, @ByteString@, and containers
22* <http://hackage.haskell.org/package/microlens-platform microlens-platform> – microlens-ghc + microlens-mtl + microlens-th + instances for @Text@, @Vector@, and @HashMap@
23* <http://hackage.haskell.org/package/microlens-contra microlens-contra> – @Fold@ and @Getter@ that are exact copies of types in lens
24
25Unofficial:
26
27* <http://hackage.haskell.org/package/microlens-aeson microlens-aeson> – a port of <http://hackage.haskell.org/package/lens-aeson lens-aeson>
28* <http://hackage.haskell.org/package/microlens-process microlens-process> - a port of <http://hackage.haskell.org/package/lens-process lens-process>
29
30-}
31module Lens.Micro
32(
33  (&),
34  -- $ampersand-note
35  (<&>),
36  -- $reverse-fmap-note
37
38  -- * Setter: modifies something in a structure
39  -- $setters-note
40  ASetter, ASetter',
41  sets,
42  (%~), over, (+~), (-~),
43  (<>~),
44  (.~), set,
45  (?~),
46  (<%~), (<<%~), (<<.~),
47  mapped,
48  rewriteOf,
49  transformOf,
50
51  -- * Getter: extracts a value from a structure
52  -- $getters-note
53  SimpleGetter,
54  Getting,
55  (^.),
56  to,
57
58  -- * Fold: extracts multiple elements
59  -- $folds-note
60  SimpleFold,
61  (^..), toListOf,
62  (^?),
63  (^?!),
64  traverseOf_,
65  forOf_,
66  has,
67  folded,
68  folding,
69
70  -- * Lens: a combined getter-and-setter
71  -- $lenses-note
72  Lens, Lens',
73  lens,
74  at,
75  _1, _2, _3, _4, _5,
76
77  -- * Iso: a lens that only changes the representation
78  -- $isos-note
79  strict, lazy,
80  non,
81
82  -- * Traversal: a lens iterating over several elements
83  -- $traversals-note
84  Traversal, Traversal',
85  traverseOf,
86  forOf,
87  singular,
88  failing,
89  filtered,
90  both,
91  traversed,
92  each,
93  ix,
94  _head, _tail, _init, _last,
95  mapAccumLOf,
96
97  -- * Prism: a traversal iterating over at most 1 element
98  -- $prisms-note
99  _Left, _Right,
100  _Just, _Nothing,
101
102  -- * Other types
103  LensLike, LensLike',
104)
105where
106
107
108import Lens.Micro.Type
109import Lens.Micro.Internal
110
111import Control.Applicative
112import Control.Monad
113import Data.Functor.Identity
114import Data.Monoid
115import Data.Maybe
116import Data.Tuple
117import qualified Data.Foldable as F
118
119#if MIN_VERSION_base(4,8,0)
120import Data.Function ((&))
121#endif
122
123#if MIN_VERSION_base(4,11,0)
124import Data.Functor ((<&>))
125#endif
126
127-- This is for the reimplementation of State
128#if MIN_VERSION_base(4,9,0)
129import qualified Control.Monad.Fail as Fail
130#endif
131
132{- $setup
133-- >>> import Data.Char (toUpper)
134-- >>> import Control.Arrow (first, second, left, right)
135-}
136
137
138#if !(MIN_VERSION_base(4,8,0))
139{- |
140'&' is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator '$', which allows '&' to be nested in '$'.
141-}
142(&) :: a -> (a -> b) -> b
143a & f = f a
144{-# INLINE (&) #-}
145infixl 1 &
146#endif
147
148{- $ampersand-note
149
150This operator is useful when you want to modify something several times. For instance, if you want to change 1st and 3rd elements of a tuple, you can write this:
151
152@
153(1,2,3) '&' '_1' '.~' 0
154        '&' '_3' '%~' 'negate'
155@
156
157instead of e.g. this:
158
159@
160('_1' '.~' 0) '.' ('_3' '%~' 'negate') '$' (1,2,3)
161@
162
163or this:
164
165@
166'set' '_1' 0 '.'
167'over' '_3' 'negate'
168  '$' (1,2,3)
169@
170-}
171
172#if !(MIN_VERSION_base(4,11,0))
173{- |
174Flipped version of '<$>'.
175-}
176(<&>) :: Functor f => f a -> (a -> b) -> f b
177(<&>) x f = f <$> x
178{-# INLINE (<&>) #-}
179
180infixl 1 <&>
181#endif
182
183{- $reverse-fmap-note
184
185('<&>') is flipped ('<$>'):
186
187@
188x '<&>' f = f '<$>' x
189@
190
191It's often useful when writing lenses. For instance, let's say you're writing 'ix' for @Map@; if the key is found in the map, you have to apply a function to it and then change the map based on the new value – which requires a lambda, like this:
192
193@
194'ix' key f map = case Map.lookup key map of
195     Just val -> (\\val' -> Map.insert key val' map) '<$>' f val
196     Nothing  -> 'pure' map
197@
198
199With ('<&>') you can get rid of parentheses and move the long lambda expression to the right of the value (like when you use '>>='):
200
201@
202'ix' key f map = case Map.lookup key map of
203     Just val -> f val '<&>' \\val' -> Map.insert key val' map
204     Nothing  -> 'pure' map
205@
206-}
207
208-- Setting -----------------------------------------------------------------
209
210{- $setters-note
211
212A setter is, broadly speaking, something that lets you modify a part of some value. Most likely you already know some setters:
213
214  * @'Control.Arrow.first' :: (a -> b) -> (a, x) -> (b, x)@
215
216      (modifies 1st element of a pair; corresponds to 'Lens.Micro._1')
217
218  * @'Control.Arrow.left' :: (a -> b) -> 'Either' a x -> 'Either' b x@
219
220      (modifies left branch of 'Either'; corresponds to 'Lens.Micro._Left')
221
222  * @'map' :: (a -> b) -> [a] -> [b]@
223
224      (modifies every element in a list; corresponds to 'Lens.Micro.mapped')
225
226As you see, a setter takes a function, a value, and applies the function to some part (or several parts) of the value. Moreover, setters can be pretty specific – for instance, a function that modifies the 3rd element of a list is a setter too:
227
228@
229-- Modify 3rd element in a list, if present.
230modify3rd :: (a -> a) -> [a] -> [a]
231modify3rd f (a:b:c:xs) = a : b : f c : xs
232modify3rd _ xs         = xs
233@
234
235A nice thing about setters is that they compose easily – you can write @'map' '.' 'Control.Arrow.left'@ and it would be a function that takes a list of 'Either's and modifies all of them that are 'Left's.
236
237This library provides its own type for setters – 'ASetter'; it's needed so that some functions in this library (like '_1') would be usable both as setters and as getters. You can turn an ordinary function like 'map' to a “lensy” setter with 'sets'.
238
239To apply a setter to a value, use ('%~') or 'over':
240
241>>> [1,2,3] & mapped %~ succ
242[2,3,4]
243>>> over _head toUpper "jane"
244"Jane"
245
246To modify a value deeper inside the structure, use ('.'):
247
248>>> ["abc","def","ghi"] & ix 1 . ix 2 %~ toUpper
249["abc","deF","ghi"]
250
251To set a value instead of modifying it, use 'set' or ('.~'):
252
253>>> "abc" & mapped .~ 'x'
254"xxx"
255>>> set _2 'X' ('a','b','c')
256('a','X','c')
257
258It's also possible to get both the old and the new value back – see ('<%~') and ('<<%~').
259-}
260
261{- |
262('%~') applies a function to the target; an alternative explanation is that it is an inverse of 'sets', which turns a setter into an ordinary function. @'mapped' '%~' 'reverse'@ is the same thing as @'fmap' 'reverse'@.
263
264See 'over' if you want a non-operator synonym.
265
266Negating the 1st element of a pair:
267
268>>> (1,2) & _1 %~ negate
269(-1,2)
270
271Turning all @Left@s in a list to upper case:
272
273>>> (mapped._Left.mapped %~ toUpper) [Left "foo", Right "bar"]
274[Left "FOO",Right "bar"]
275-}
276(%~) :: ASetter s t a b -> (a -> b) -> s -> t
277(%~) = over
278{-# INLINE (%~) #-}
279
280infixr 4 %~
281
282{- |
283'over' is a synonym for ('%~').
284
285Getting 'fmap' in a roundabout way:
286
287@
288'over' 'mapped' :: 'Functor' f => (a -> b) -> f a -> f b
289'over' 'mapped' = 'fmap'
290@
291
292Applying a function to both components of a pair:
293
294@
295'over' 'both' :: (a -> b) -> (a, a) -> (b, b)
296'over' 'both' = \\f t -> (f (fst t), f (snd t))
297@
298
299Using @'over' '_2'@ as a replacement for 'Control.Arrow.second':
300
301>>> over _2 show (10,20)
302(10,"20")
303-}
304over :: ASetter s t a b -> (a -> b) -> s -> t
305over l f = runIdentity #. l (Identity #. f)
306{-# INLINE over #-}
307
308
309{- |
310Increment the target(s) of a numerically valued 'Lens' or 'Traversal'.
311
312>>> (a,b) & _1 +~ c
313(a + c,b)
314
315>>> (a,b) & both +~ c
316(a + c,b + c)
317
318>>> (1,2) & _2 +~ 1
319(1,3)
320
321>>> [(a,b),(c,d)] & traverse.both +~ e
322[(a + e,b + e),(c + e,d + e)]
323
324@
325('+~') :: 'Num' a => 'Lens'' s a      -> a -> s -> s
326('+~') :: 'Num' a => 'Traversal'' s a -> a -> s -> s
327@
328
329@since 0.4.10
330-}
331(+~) :: Num a => ASetter s t a a -> a -> s -> t
332l +~ n = over l (+ n)
333{-# INLINE (+~) #-}
334
335infixr 4 +~
336
337{- |
338Decrement the target(s) of a numerically valued 'Lens', or 'Traversal'.
339
340>>> (a,b) & _1 -~ c
341(a - c,b)
342
343>>> (a,b) & both -~ c
344(a - c,b - c)
345
346>>> _1 -~ 2 $ (1,2)
347(-1,2)
348
349>>> mapped.mapped -~ 1 $ [[4,5],[6,7]]
350[[3,4],[5,6]]
351
352@
353('-~') :: 'Num' a => 'Lens'' s a      -> a -> s -> s
354('-~') :: 'Num' a => 'Traversal'' s a -> a -> s -> s
355@
356
357@since 0.4.10
358-}
359(-~) :: Num a => ASetter s t a a -> a -> s -> t
360l -~ n = over l (subtract n)
361{-# INLINE (-~) #-}
362
363infixr 4 -~
364
365{- |
366('<>~') appends a value monoidally to the target.
367
368>>> ("hello", "goodbye") & both <>~ " world!"
369("hello world!", "goodbye world!")
370
371@since 0.4.9
372-}
373(<>~) :: (Monoid a) => ASetter s t a a -> a -> s -> t
374(<>~) l a = over l (`mappend` a)
375{-# INLINE (<>~) #-}
376
377infixr 4 <>~
378
379{- |
380('.~') assigns a value to the target. It's the same thing as using ('%~') with 'const':
381
382@
383l '.~' x = l '%~' 'const' x
384@
385
386See 'set' if you want a non-operator synonym.
387
388Here it is used to change 2 fields of a 3-tuple:
389
390>>> (0,0,0) & _1 .~ 1 & _3 .~ 3
391(1,0,3)
392-}
393(.~) :: ASetter s t a b -> b -> s -> t
394(.~) = set
395{-# INLINE (.~) #-}
396
397infixr 4 .~
398
399{- |
400'set' is a synonym for ('.~').
401
402Setting the 1st component of a pair:
403
404@
405'set' '_1' :: x -> (a, b) -> (x, b)
406'set' '_1' = \\x t -> (x, snd t)
407@
408
409Using it to rewrite ('Data.Functor.<$'):
410
411@
412'set' 'mapped' :: 'Functor' f => a -> f b -> f a
413'set' 'mapped' = ('Data.Functor.<$')
414@
415-}
416set :: ASetter s t a b -> b -> s -> t
417set l b = runIdentity #. l (\_ -> Identity b)
418{-# INLINE set #-}
419
420{- |
421('?~') is a version of ('.~') that wraps the value into 'Just' before setting.
422
423@
424l ?~ b = l .~ Just b
425@
426
427It can be useful in combination with 'at':
428
429>>> Map.empty & at 3 ?~ x
430fromList [(3,x)]
431-}
432(?~) :: ASetter s t a (Maybe b) -> b -> s -> t
433l ?~ b = set l (Just b)
434{-# INLINE (?~) #-}
435
436infixr 4 ?~
437
438{- |
439'mapped' is a setter for everything contained in a functor. You can use it to map over lists, @Maybe@, or even @IO@ (which is something you can't do with 'traversed' or 'each').
440
441Here 'mapped' is used to turn a value to all non-'Nothing' values in a list:
442
443>>> [Just 3,Nothing,Just 5] & mapped.mapped .~ 0
444[Just 0,Nothing,Just 0]
445
446Keep in mind that while 'mapped' is a more powerful setter than 'each', it can't be used as a getter! This won't work (and will fail with a type error):
447
448@
449[(1,2),(3,4),(5,6)] '^..' 'mapped' . 'both'
450@
451-}
452mapped :: Functor f => ASetter (f a) (f b) a b
453mapped = sets fmap
454{-# INLINE mapped #-}
455
456{- |
457This is a version of ('%~') which modifies the structure and returns it along with the new value:
458
459>>> (1, 2) & _1 <%~ negate
460(-1, (-1, 2))
461
462Simpler type signatures:
463
464@
465('<%~') ::             'Lens' s t a b      -> (a -> b) -> s -> (b, t)
466('<%~') :: 'Monoid' b => 'Traversal' s t a b -> (a -> b) -> s -> (b, t)
467@
468
469Since it does getting in addition to setting, you can't use it with 'ASetter' (but you can use it with lens and traversals).
470-}
471(<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t)
472(<%~) l f = l (join (,) . f)
473{-# INLINE (<%~) #-}
474
475infixr 4 <%~
476
477{- |
478This is a version of ('%~') which modifies the structure and returns it along with the old value:
479
480>>> (1, 2) & _1 <<%~ negate
481(1, (-1, 2))
482
483Simpler type signatures:
484
485@
486('<<%~') ::             'Lens' s t a b      -> (a -> b) -> s -> (a, t)
487('<<%~') :: 'Monoid' a => 'Traversal' s t a b -> (a -> b) -> s -> (a, t)
488@
489-}
490(<<%~) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t)
491(<<%~) l f = l (\a -> (a, f a))
492{-# INLINE (<<%~) #-}
493
494infixr 4 <<%~
495
496{- |
497This is a version of ('.~') which modifies the structure and returns it along with the old value:
498
499>>> (1, 2) & _1 <<.~ 0
500(1, (0, 2))
501
502Simpler type signatures:
503
504@
505('<<.~') ::             'Lens' s t a b      -> b -> s -> (a, t)
506('<<.~') :: 'Monoid' a => 'Traversal' s t a b -> b -> s -> (a, t)
507@
508-}
509(<<.~) :: LensLike ((,) a) s t a b -> b -> s -> (a, t)
510(<<.~) l x = l (\a -> (a, x))
511{-# INLINE (<<.~) #-}
512
513infixr 4 <<.~
514
515{- |
516→ See <https://github.com/monadfix/microlens/pull/119#issuecomment-496004851 an example> on GitHub.
517
518Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result.
519
520Usually 'transformOf' is more appropriate, but 'rewriteOf' can give better compositionality. Given two single transformations @f@ and @g@, you can construct @\\a -> f a '<|>' g a@ which performs both rewrites until a fixed point.
521
522@since 0.4.11
523-}
524rewriteOf :: ASetter a b a b -> (b -> Maybe a) -> a -> b
525rewriteOf l f = go where
526  go = transformOf l (\x -> maybe x go (f x))
527{-# INLINE rewriteOf #-}
528
529{- |
530Transform every element by recursively applying a given 'ASetter' in a bottom-up manner.
531
532@since 0.4.11
533-}
534transformOf :: ASetter a b a b -> (b -> b) -> a -> b
535transformOf l f = go where
536  go = f . over l go
537{-# INLINE transformOf #-}
538
539-- Getting -----------------------------------------------------------------
540
541{- $getters-note
542
543A getter extracts something from a value; in fact, any function is a getter. However, same as with setters, this library uses a special type for getters so that functions like '_1' would be usable both as a setter and a getter. An ordinary function can be turned into a getter with 'to'.
544
545Using a getter is done with ('^.') or 'Lens.Micro.Extras.view' from "Lens.Micro.Extras":
546
547>>> ('x','y') ^. _1
548'x'
549>>> view (ix 2) [0..5]
5502
551
552Getters can be composed with ('.'):
553
554>>> [(1,2),(3,4),(5,6)] ^. ix 1 . _2
5554
556
557A getter always returns exactly 1 element (getters that can return more than one element are called folds and are present in this library as well).
558-}
559
560{- |
561('^.') applies a getter to a value; in other words, it gets a value out of a structure using a getter (which can be a lens, traversal, fold, etc.).
562
563Getting 1st field of a tuple:
564
565@
566('^.' '_1') :: (a, b) -> a
567('^.' '_1') = 'fst'
568@
569
570When ('^.') is used with a traversal, it combines all results using the 'Monoid' instance for the resulting type. For instance, for lists it would be simple concatenation:
571
572>>> ("str","ing") ^. each
573"string"
574
575The reason for this is that traversals use 'Applicative', and the 'Applicative' instance for 'Const' uses monoid concatenation to combine “effects” of 'Const'.
576
577A non-operator version of ('^.') is called @view@, and it's a bit more general than ('^.') (it works in @MonadReader@). If you need the general version, you can get it from <http://hackage.haskell.org/package/microlens-mtl microlens-mtl>; otherwise there's 'Lens.Micro.Extras.view' available in "Lens.Micro.Extras".
578-}
579(^.) :: s -> Getting a s a -> a
580s ^. l = getConst (l Const s)
581{-# INLINE (^.) #-}
582
583infixl 8 ^.
584
585{- |
586'to' creates a getter from any function:
587
588@
589a '^.' 'to' f = f a
590@
591
592It's most useful in chains, because it lets you mix lenses and ordinary functions. Suppose you have a record which comes from some third-party library and doesn't have any lens accessors. You want to do something like this:
593
594@
595value ^. _1 . field . at 2
596@
597
598However, @field@ isn't a getter, and you have to do this instead:
599
600@
601field (value ^. _1) ^. at 2
602@
603
604but now @value@ is in the middle and it's hard to read the resulting code. A variant with 'to' is prettier and more readable:
605
606@
607value ^. _1 . to field . at 2
608@
609-}
610to :: (s -> a) -> SimpleGetter s a
611to k f = phantom . f . k
612{-# INLINE to #-}
613
614-- Folds -------------------------------------------------------------------
615
616{- $folds-note
617
618Folds are getters that can return more than one element (or no elements at all). <http://comonad.com/reader/2015/free-monoids-in-haskell/ Except for some rare cases>, a fold is the same thing as @(s -> [a])@; you can use 'folding' to turn any function of type @(s -> f a)@ (where @f@ is 'F.Foldable') into a fold.
619
620Folds can be applied to values by using operators like ('^..'), ('^?'), etc:
621
622>>> (1,2) ^.. both
623[1,2]
624
625A nice thing about folds is that you can combine them with ('Data.Monoid.<>') to concatenate their outputs:
626
627>>> (1,2,3) ^.. (_2 <> _1)
628[2,1]
629
630When you need to get all elements of the same type in a complicated structure, ('Data.Monoid.<>') can be more helpful than 'each':
631
632>>> ([1,2], 3, [Nothing, Just 4]) ^.. (_1.each <> _2 <> _3.each._Just)
633[1,2,3,4]
634
635(Just like setters and getters before, folds can be composed with ('.').)
636
637The ('Data.Monoid.<>') trick works nicely with ('^?'), too. For instance, if you want to get the 9th element of the list, but would be fine with 5th too if the list is too short, you could combine @ix 9@ and @ix 5@:
638
639>>> [0..9] ^? (ix 9 <> ix 5)
640Just 9
641>>> [0..8] ^? (ix 9 <> ix 5)
642Just 5
643>>> [0..3] ^? (ix 9 <> ix 5)
644Nothing
645
646(Unfortunately, this trick won't help you with setting or modifying.)
647-}
648
649{- |
650@s ^.. t@ returns the list of all values that @t@ gets from @s@.
651
652A 'Maybe' contains either 0 or 1 values:
653
654>>> Just 3 ^.. _Just
655[3]
656
657Gathering all values in a list of tuples:
658
659>>> [(1,2),(3,4)] ^.. each.each
660[1,2,3,4]
661-}
662(^..) :: s -> Getting (Endo [a]) s a -> [a]
663s ^.. l = toListOf l s
664{-# INLINE (^..) #-}
665
666infixl 8 ^..
667
668{- |
669'toListOf' is a synonym for ('^..').
670-}
671toListOf :: Getting (Endo [a]) s a -> s -> [a]
672toListOf l = foldrOf l (:) []
673{-# INLINE toListOf #-}
674
675{- |
676@s ^? t@ returns the 1st element @t@ returns, or 'Nothing' if @t@ doesn't return anything. It's trivially implemented by passing the 'First' monoid to the getter.
677
678Safe 'head':
679
680>>> [] ^? each
681Nothing
682
683>>> [1..3] ^? each
684Just 1
685
686Converting 'Either' to 'Maybe':
687
688>>> Left 1 ^? _Right
689Nothing
690
691>>> Right 1 ^? _Right
692Just 1
693
694A non-operator version of ('^?') is called @preview@, and – like @view@ – it's a bit more general than ('^?') (it works in @MonadReader@). If you need the general version, you can get it from <http://hackage.haskell.org/package/microlens-mtl microlens-mtl>; otherwise there's 'Lens.Micro.Extras.preview' available in "Lens.Micro.Extras".
695-}
696(^?) :: s -> Getting (First a) s a -> Maybe a
697s ^? l = getFirst (foldMapOf l (First #. Just) s)
698{-# INLINE (^?) #-}
699
700infixl 8 ^?
701
702{- |
703('^?!') is an unsafe variant of ('^?') – instead of using 'Nothing' to indicate that there were no elements returned, it throws an exception.
704-}
705(^?!) :: HasCallStack => s -> Getting (Endo a) s a -> a
706s ^?! l = foldrOf l const (error "(^?!): empty Fold") s
707{-# INLINE (^?!) #-}
708
709infixl 8 ^?!
710
711{- |
712Apply an action to all targets and discard the result (like 'Control.Monad.mapM_' or 'Data.Foldable.traverse_'):
713
714>>> traverseOf_ both putStrLn ("hello", "world")
715hello
716world
717
718Works with anything that allows getting, including lenses and getters (so, anything except for 'ASetter'). Should be faster than 'traverseOf' when you don't need the result.
719-}
720traverseOf_
721  :: Functor f
722  => Getting (Traversed r f) s a -> (a -> f r) -> s -> f ()
723traverseOf_ l f = void . getTraversed #. foldMapOf l (Traversed #. f)
724{-# INLINE traverseOf_ #-}
725
726{- |
727'traverseOf_' with flipped arguments. Useful if the “loop body” is a lambda
728or a @do@ block, or in some other cases – for instance, you can avoid
729accidentally using 'Data.Foldable.for_' on a tuple or 'Either' by switching
730to @'forOf_' 'each'@. Or you can write custom loops like these:
731
732@
733'forOf_' 'both' (a, b) $ \\x -\>
734  ...
735'forOf_' 'each' [1..10] $ \\x -\>
736  ...
737'forOf_' ('each' . '_Right') $ \\x -\>
738  ...
739@
740-}
741forOf_
742  :: Functor f
743  => Getting (Traversed r f) s a -> s -> (a -> f r) -> f ()
744forOf_ = flip . traverseOf_
745{-# INLINE forOf_ #-}
746
747{- |
748'has' checks whether a getter (any getter, including lenses, traversals, and folds) returns at least 1 value.
749
750Checking whether a list is non-empty:
751
752>>> has each []
753False
754
755You can also use it with e.g. '_Left' (and other 0-or-1 traversals) as a replacement for 'Data.Maybe.isNothing', 'Data.Maybe.isJust' and other @isConstructorName@ functions:
756
757>>> has _Left (Left 1)
758True
759-}
760has :: Getting Any s a -> s -> Bool
761has l = getAny #. foldMapOf l (\_ -> Any True)
762{-# INLINE has #-}
763
764{- |
765'folding' creates a fold out of any function that returns a 'F.Foldable' container (for instance, a list):
766
767>>> [1..5] ^.. folding tail
768[2,3,4,5]
769-}
770folding :: F.Foldable f => (s -> f a) -> SimpleFold s a
771folding sfa agb = phantom . F.traverse_ agb . sfa
772{-# INLINE folding #-}
773
774-- Lenses ------------------------------------------------------------------
775
776{- $lenses-note
777
778Lenses are composable “pointers” at values inside some bigger structure (e.g. '_1' points at the first element of a tuple). You can use ('^.') to get, ('.~') to set, and ('%~') to modify:
779
780>>> (1,2) ^. _1
7811
782>>> (1,2) & _1 .~ 3
783(3,2)
784>>> (1,2) & _1 %~ negate
785(-1,2)
786
787To apply a monadic action (or an 'Applicative' action, or even a 'Functor' action) to the pointed value, just apply the lens directly or use 'traverseOf' (or 'traverseOf_' if you don't need the result):
788
789>>> traverseOf_ _1 print (1,2)
7901
791
792>>> _1 id (Just 1, 2)
793Just (1, 2)
794>>> _1 id (Nothing, 2)
795Nothing
796
797A 'Lens' can only point at a single value inside a structure (unlike a 'Traversal').
798
799('.') composes lenses (i.e. if a @B@ is a part of @A@, and a @C@ is a part of @B@, then @b.c@ lets you operate on @C@ inside @A@). You can create lenses with 'lens', or you can write them by hand.
800
801There are several ways to get lenses for some datatype:
802
803* They can already be provided by the package, by @microlens@, or by some other package like <http://hackage.haskell.org/package/microlens-platform microlens-platform>.
804
805* They can be provided by some unofficial package (like <http://hackage.haskell.org/package/microlens-aeson microlens-aeson>).
806
807* You can get them by combining already existing lenses.
808
809* You can derive them with Template Haskell (with <http://hackage.haskell.org/package/microlens-th microlens-th>).
810
811* You can write them with 'lens' if you have a setter and a getter. It's a simple and good way.
812
813* You can write them manually (sometimes it looks a bit better than the variant with 'lens', sometimes worse). The generic template is as follows:
814
815@
816somelens :: Lens s t a b
817
818-- “f” is the “a -> f b” function, “s” is the structure.
819somelens f s =
820  let
821    a = ...                 -- Extract the value from “s”.
822    rebuildWith b = ...     -- Write a function which would
823                            -- combine “s” and modified value
824                            -- to produce new structure.
825  in
826    rebuildWith '<$>' f a     -- Apply the structure-producing
827                            -- function to the modified value.
828@
829
830Here's the '_1' lens, for instance:
831
832@
833'_1' :: 'Lens' (a, x) (b, x) a b
834'_1' f (a, x) = (\\b -> (b, x)) '<$>' f a
835@
836
837Here's a more complicated lens, which extracts /several/ values from a structure (in a tuple):
838
839@
840type Age     = Int
841type City    = String
842type Country = String
843
844data Person = Person Age City Country
845
846-- This lens lets you access all location-related information about a person.
847location :: 'Lens'' Person (City, Country)
848location f (Person age city country) =
849  (\\(city', country') -> Person age city' country') '<$>' f (city, country)
850@
851
852You even can choose to use a lens to present /all/ information contained in the structure (in a different way). Such lenses are called @<http://hackage.haskell.org/package/lens/docs/Control-Lens-Iso.html#t:Iso Iso>@ in lens's terminology. For instance (assuming you don't mind functions that can error out), here's a lens which lets you act on the string representation of a value:
853
854@
855string :: (Read a, Show a) => 'Lens'' a String
856string f s = read '<$>' f (show s)
857@
858
859Using it to reverse a number:
860
861@
862>>> 123 '&' string '%~' reverse
863321
864@
865-}
866
867{- |
868'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.
869
870A (partial) lens for list indexing:
871
872@
873ix :: Int -> 'Lens'' [a] a
874ix i = 'lens' ('!!' i)                                   -- getter
875            (\\s b -> take i s ++ b : drop (i+1) s)   -- setter
876@
877
878Usage:
879
880@
881>>> [1..9] '^.' ix 3
8824
883
884>>> [1..9] & ix 3 '%~' negate
885[1,2,3,-4,5,6,7,8,9]
886@
887
888When 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:
889
890>>> [1,2,3] & lens undefined (\s b -> b : tail s) .~ 10
891[10,2,3]
892-}
893lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
894lens sa sbt afb s = sbt s <$> afb (sa s)
895{-# INLINE lens #-}
896
897-- Isos --------------------------------------------------------------------
898
899{- $isos-note
900
901Isos (or isomorphisms) are lenses that convert a value instead of targeting a part of it; in other words, inside of every list lives a reversed list, inside of every strict @Text@ lives a lazy @Text@, and inside of every @(a, b)@ lives a @(b, a)@. Since an isomorphism doesn't lose any information, it's possible to /reverse/ it and use it in the opposite direction by using @from@ from the lens library:
902
903@
904from :: Iso' s a -> Iso' a s
905@
906
907However, it's not possible for microlens to export isomorphisms, because their type depends on @<http://hackage.haskell.org/package/profunctors/docs/Data-Profunctor.html#t:Profunctor Profunctor>@, which resides in the <http://hackage.haskell.org/package/profunctors profunctors> library, which is a somewhat huge dependency. So, all isomorphisms included here are lenses instead (and thus you can't use them in the opposite direction).
908-}
909
910{- |
911'non' lets you “relabel” a 'Maybe' by equating 'Nothing' to an arbitrary value (which you can choose):
912
913>>> Just 1 ^. non 0
9141
915
916>>> Nothing ^. non 0
9170
918
919The 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':
920
921>>> Just 1 & non 0 .~ 0
922Nothing
923
924Setting anything else works just fine:
925
926>>> Just 1 & non 0 .~ 5
927Just 5
928
929Same happens if you try to modify a value:
930
931>>> Just 1 & non 0 %~ subtract 1
932Nothing
933
934>>> Just 1 & non 0 %~ (+ 1)
935Just 2
936
937'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.
938
939Decrease playcount of a song to 0, and it'll be gone:
940
941>>> fromList [("Soon",1),("Yesterday",3)] & at "Soon" . non 0 %~ subtract 1
942fromList [("Yesterday",3)]
943
944Try to add a song with 0 plays, and it won't be added:
945
946>>> fromList [("Yesterday",3)] & at "Soon" . non 0 .~ 0
947fromList [("Yesterday",3)]
948
949But it will be added if you set any other number:
950
951>>> fromList [("Yesterday",3)] & at "Soon" . non 0 .~ 1
952fromList [("Soon",1),("Yesterday",3)]
953
954'non' is also useful when working with nested maps. Here a nested map is created when it's missing:
955
956>>> Map.empty & at "Dez Mona" . non Map.empty . at "Soon" .~ Just 1
957fromList [("Dez Mona",fromList [("Soon",1)])]
958
959and here it is deleted when its last entry is deleted (notice that 'non' is used twice here):
960
961>>> fromList [("Dez Mona",fromList [("Soon",1)])] & at "Dez Mona" . non Map.empty . at "Soon" . non 0 %~ subtract 1
962fromList []
963
964To understand the last example better, observe the flow of values in it:
965
966* the map goes into @at \"Dez Mona\"@
967* the nested map (wrapped into @Just@) goes into @non Map.empty@
968* @Just@ is unwrapped and the nested map goes into @at \"Soon\"@
969* @Just 1@ is unwrapped by @non 0@
970
971Then the final value – i.e. 1 – is modified by @subtract 1@ and the result (which is 0) starts flowing backwards:
972
973* @non 0@ sees the 0 and produces a @Nothing@
974* @at \"Soon\"@ sees @Nothing@ and deletes the corresponding value from the map
975* the resulting empty map is passed to @non Map.empty@, which sees that it's empty and thus produces @Nothing@
976* @at \"Dez Mona\"@ sees @Nothing@ and removes the key from the map
977-}
978non :: Eq a => a -> Lens' (Maybe a) a
979non x afb s = f <$> afb (fromMaybe x s)
980  where f y = if x == y then Nothing else Just y
981{-# INLINE non #-}
982
983-- Traversals --------------------------------------------------------------
984
985{- $traversals-note
986
987Traversals are like lenses but they can point at multiple values. Use ('^..') to get all values, ('^?') to get the 1st value, ('.~') to set values, ('%~') to modify them. ('.') composes traversals just as it composes lenses. ('^.') can be used with traversals as well, but don't confuse it with ('^..') – ('^..') gets all traversed values, ('^.') combines traversed values using the ('Data.Monoid.<>') operation (if the values are instances of 'Monoid'; if they aren't, it won't compile). 'traverseOf' and 'traverseOf_' apply an action to all pointed values of a traversal.
988
989Traversals don't differ from lenses when it comes to setting – you can use usual ('%~') and ('.~') to modify and set values. Getting is a bit different, because you have to decide what to do in the case of multiple values. In particular, you can use these combinators (as well as everything else in the “Folds” section):
990
991  * ('^..') gets a list of values
992  * ('^?') gets the 1st value (or 'Nothing' if there are no values)
993  * ('^?!') gets the 1st value and throws an exception if there are no values
994
995If you are sure that the traversal will traverse at least one value, you can convert it to a lens with 'singular'.
996
997'traversed' is a universal traversal for anything that belongs to the 'Traversable' typeclass. However, in many cases 'each' works as well and is shorter and nicer-looking.
998-}
999
1000{- |
1001Apply an action to all targets (like 'Control.Monad.mapM' or 'Data.Traversable.traverse'):
1002
1003>>> traverseOf both readFile ("file1", "file2")
1004(<contents of file1>, <contents of file2>)
1005
1006>>> traverseOf _1 id (Just 1, 2)
1007Just (1, 2)
1008>>> traverseOf _1 id (Nothing, 2)
1009Nothing
1010
1011You can also just apply the lens\/traversal directly (but 'traverseOf' might be more readable):
1012
1013>>> both readFile ("file1", "file2")
1014(<contents of file1>, <contents of file2>)
1015
1016If you don't need the result, use 'traverseOf_'.
1017-}
1018traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t
1019traverseOf = id
1020{-# INLINE traverseOf #-}
1021
1022{- |
1023'traverseOf' with flipped arguments. Useful if the “loop body” is a lambda or
1024a @do@ block.
1025-}
1026forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t
1027forOf = flip
1028{-# INLINE forOf #-}
1029
1030{- |
1031'singular' turns a traversal into a lens that behaves like a single-element traversal:
1032
1033>>> [1,2,3] ^. singular each
10341
1035
1036>>> [1,2,3] & singular each %~ negate
1037[-1,2,3]
1038
1039If there is nothing to return, it'll throw an error:
1040
1041>>> [] ^. singular each
1042*** Exception: Lens.Micro.singular: empty traversal
1043
1044However, it won't fail if you are merely setting the value:
1045
1046>>> [] & singular each %~ negate
1047-}
1048singular :: HasCallStack => Traversal s t a a -> Lens s t a a
1049singular l afb s = case ins b of
1050  (w:ws) -> unsafeOuts b . (:ws) <$> afb w
1051  []     -> unsafeOuts b . return <$>
1052              afb (error "Lens.Micro.singular: empty traversal")
1053  where
1054    Bazaar b = l sell s
1055    sell w = Bazaar ($ w)
1056    ins f = (coerce :: [Identity a] -> [a])
1057              (getConst (f (\ra -> Const [Identity ra])))
1058    unsafeOuts f = evalState (f (\_ -> state (unconsWithDefault fakeVal)))
1059      where fakeVal = error "unsafeOuts: not enough elements were supplied"
1060    unconsWithDefault d []     = (d,[])
1061    unconsWithDefault _ (x:xs) = (x,xs)
1062{-# INLINE singular #-}
1063
1064{- |
1065'failing' lets you chain traversals together; if the 1st traversal fails, the 2nd traversal will be used.
1066
1067>>> ([1,2],[3]) & failing (_1.each) (_2.each) .~ 0
1068([0,0],[3])
1069
1070>>> ([],[3]) & failing (_1.each) (_2.each) .~ 0
1071([],[0])
1072
1073Note 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 <http://stackoverflow.com/questions/27138856/why-does-failing-from-lens-produce-invalid-traversals this Stackoverflow question>.
1074-}
1075failing :: Traversal s t a b -> Traversal s t a b -> Traversal s t a b
1076failing left right afb s = case pins b of
1077  [] -> right afb s
1078  _  -> b afb
1079  where
1080    Bazaar b = left sell s
1081    sell w = Bazaar ($ w)
1082    pins f = getConst (f (\ra -> Const [Identity ra]))
1083
1084infixl 5 `failing`
1085
1086{- |
1087'filtered' is a traversal that filters elements “passing” through it:
1088
1089>>> (1,2,3,4) ^.. each
1090[1,2,3,4]
1091
1092>>> (1,2,3,4) ^.. each . filtered even
1093[2,4]
1094
1095It also can be used to modify elements selectively:
1096
1097>>> (1,2,3,4) & each . filtered even %~ (*100)
1098(1,200,3,400)
1099
1100The implementation of 'filtered' is very simple. Consider this traversal, which always “traverses” just the value it's given:
1101
1102@
1103id :: 'Traversal'' a a
1104id f s = f s
1105@
1106
1107And this traversal, which traverses nothing (in other words, /doesn't/ traverse the value it's given):
1108
1109@
1110ignored :: 'Traversal'' a a
1111ignored f s = 'pure' s
1112@
1113
1114And now combine them into a traversal that conditionally traverses the value it's given, and you get 'filtered':
1115
1116@
1117filtered :: (a -> Bool) -> 'Traversal'' a a
1118filtered p f s = if p s then f s else 'pure' s
1119@
1120
1121By 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.)
1122
1123Let's use @evens@ as an example:
1124
1125@
1126evens = 'filtered' 'even'
1127@
1128
1129If @evens@ was a legal traversal, you'd be able to fuse several applications of @evens@ like this:
1130
1131@
1132'over' evens f '.' 'over' evens g = 'over' evens (f '.' g)
1133@
1134
1135Unfortunately, in case of @evens@ this isn't a correct optimisation:
1136
1137  * 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)
1138
1139  * the right-side variant applies @f@ and @g@ to all even numbers
1140
1141Of 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.
1142
1143If 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:
1144
1145@
1146pairedWithEvens :: 'Traversal' [(Int, a)] [(Int, b)] a b
1147pairedWithEvens = 'each' '.' 'filtered' ('even' '.' 'fst') '.' '_2'
1148@
1149
1150Since you can't do anything with the 1st components through this traversal, the following holds for any @f@ and @g@:
1151
1152@
1153'over' pairedWithEvens f '.' 'over' pairedWithEvens g = 'over' pairedWithEvens (f '.' g)
1154@
1155-}
1156filtered :: (a -> Bool) -> Traversal' a a
1157filtered p f s = if p s then f s else pure s
1158{-# INLINE filtered #-}
1159
1160{- |
1161'both' traverses both fields of a tuple. Unlike @<http://hackage.haskell.org/package/lens/docs/Control-Lens-Traversal.html#v:both both>@ from lens, it only works for pairs – not for triples or 'Either'.
1162
1163>>> ("str","ing") ^. both
1164"string"
1165
1166>>> ("str","ing") & both %~ reverse
1167("rts","gni")
1168-}
1169both :: Traversal (a, a) (b, b) a b
1170both f = \ ~(a, b) -> liftA2 (,) (f a) (f b)
1171{-# INLINE both #-}
1172
1173{- |
1174'_head' traverses the 1st element of something (usually a list, but can also be a @Seq@, etc):
1175
1176>>> [1..5] ^? _head
1177Just 1
1178
1179It can be used to modify too, as in this example where the 1st letter of a sentence is capitalised:
1180
1181>>> "mary had a little lamb." & _head %~ toTitle
1182"Mary had a little lamb."
1183
1184The reason it's a traversal and not a lens is that there's nothing to traverse when the list is empty:
1185
1186>>> [] ^? _head
1187Nothing
1188
1189This package only lets you use '_head' on lists, but if you use <http://hackage.haskell.org/package/microlens-ghc microlens-ghc> you get instances for @ByteString@ and @Seq@, and if you use <http://hackage.haskell.org/package/microlens-platform microlens-platform> you additionally get instances for @Text@ and @Vector@.
1190-}
1191_head :: Cons s s a a => Traversal' s a
1192_head = _Cons._1
1193{-# INLINE _head #-}
1194
1195{- |
1196'_tail' gives you access to the tail of a list (or @Seq@, etc):
1197
1198>>> [1..5] ^? _tail
1199Just [2,3,4,5]
1200
1201You can modify the tail as well:
1202
1203>>> [4,1,2,3] & _tail %~ reverse
1204[4,3,2,1]
1205
1206Since lists are monoids, you can use '_tail' with plain ('^.') (and then it'll return an empty list if you give it an empty list):
1207
1208>>> [1..5] ^. _tail
1209[2,3,4,5]
1210
1211>>> [] ^. _tail
1212[]
1213
1214If you want to traverse each /element/ of the tail, use '_tail' with 'each':
1215
1216>>> "I HATE CAPS." & _tail.each %~ toLower
1217"I hate caps."
1218
1219This package only lets you use '_tail' on lists, but if you use <http://hackage.haskell.org/package/microlens-ghc microlens-ghc> you get instances for @ByteString@ and @Seq@, and if you use <http://hackage.haskell.org/package/microlens-platform microlens-platform> you additionally get instances for @Text@ and @Vector@.
1220-}
1221_tail :: Cons s s a a => Traversal' s s
1222_tail = _Cons._2
1223{-# INLINE _tail #-}
1224
1225{- |
1226'_init' gives you access to all-but-the-last elements of the list:
1227
1228>>> "Hello." ^. _init
1229"Hello"
1230
1231See documentation for '_tail', as '_init' and '_tail' are pretty similar.
1232-}
1233_init :: Snoc s s a a => Traversal' s s
1234_init = _Snoc._1
1235{-# INLINE _init #-}
1236
1237{- |
1238'_last' gives you access to the last element of the list:
1239
1240>>> "Hello." ^? _last
1241'.'
1242
1243See documentation for '_head', as '_last' and '_head' are pretty similar.
1244-}
1245_last :: Snoc s s a a => Traversal' s a
1246_last = _Snoc._2
1247{-# INLINE _last #-}
1248
1249
1250{- |
1251This generalizes 'Data.Traversable.mapAccumL' to an arbitrary 'Traversal'. (Note that it doesn't work on folds, only traversals.)
1252
1253@
1254'mapAccumL' ≡ 'mapAccumLOf' 'traverse'
1255@
1256-}
1257mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
1258mapAccumLOf l f acc0 s = swap (runState (l g s) acc0)
1259  where
1260    g a = state $ \acc -> swap (f acc a)
1261{-# INLINE mapAccumLOf #-}
1262
1263-- Prisms ------------------------------------------------------------------
1264
1265{- $prisms-note
1266
1267Prisms are traversals that always target 0 or 1 values. Moreover, it's possible to /reverse/ a prism, using it to construct a structure instead of peeking into it. Here's an example from the lens library:
1268
1269@
1270>>> over _Left (+1) (Left 2)
1271Left 3
1272
1273>>> _Left # 5
1274Left 5
1275@
1276
1277However, it's not possible for microlens to export prisms, because their type depends on @<http://hackage.haskell.org/package/profunctors/docs/Data-Profunctor.html#t:Choice Choice>@ from <http://hackage.haskell.org/package/profunctors profunctors>. So, all prisms included here are traversals instead (and you can't reverse them).
1278-}
1279
1280{- |
1281'_Left' targets the value contained in an 'Either', provided it's a 'Left'.
1282
1283Gathering all @Left@s in a structure (like the 'Data.Either.lefts' function, but not necessarily just for lists):
1284
1285>>> [Left 1, Right 'c', Left 3] ^.. each._Left
1286[1,3]
1287
1288Checking whether an 'Either' is a 'Left' (like 'Data.Either.isLeft'):
1289
1290>>> has _Left (Left 1)
1291True
1292
1293>>> has _Left (Right 1)
1294False
1295
1296Extracting a value (if you're sure it's a 'Left'):
1297
1298>>> Left 1 ^?! _Left
12991
1300
1301Mapping over all 'Left's:
1302
1303>>> (each._Left %~ map toUpper) [Left "foo", Right "bar"]
1304[Left "FOO",Right "bar"]
1305
1306Implementation:
1307
1308@
1309'_Left' f (Left a)  = 'Left' '<$>' f a
1310'_Left' _ (Right b) = 'pure' ('Right' b)
1311@
1312-}
1313_Left :: Traversal (Either a b) (Either a' b) a a'
1314_Left f (Left a) = Left <$> f a
1315_Left _ (Right b) = pure (Right b)
1316{-# INLINE _Left #-}
1317
1318{- |
1319'_Right' targets the value contained in an 'Either', provided it's a 'Right'.
1320
1321See documentation for '_Left'.
1322-}
1323_Right :: Traversal (Either a b) (Either a b') b b'
1324_Right f (Right b) = Right <$> f b
1325_Right _ (Left a) = pure (Left a)
1326{-# INLINE _Right #-}
1327
1328{- |
1329'_Just' targets the value contained in a 'Maybe', provided it's a 'Just'.
1330
1331See documentation for '_Left' (as these 2 are pretty similar). In particular, it can be used to write these:
1332
1333  * Unsafely extracting a value from a 'Just':
1334
1335    @
1336    'Data.Maybe.fromJust' = ('^?!' '_Just')
1337    @
1338
1339  * Checking whether a value is a 'Just':
1340
1341    @
1342    'Data.Maybe.isJust' = 'has' '_Just'
1343    @
1344
1345  * Converting a 'Maybe' to a list (empty or consisting of a single element):
1346
1347    @
1348    'Data.Maybe.maybeToList' = ('^..' '_Just')
1349    @
1350
1351  * Gathering all 'Just's in a list:
1352
1353    @
1354    'Data.Maybe.catMaybes' = ('^..' 'each' '.' '_Just')
1355    @
1356-}
1357_Just :: Traversal (Maybe a) (Maybe a') a a'
1358_Just f (Just a) = Just <$> f a
1359_Just _ Nothing = pure Nothing
1360{-# INLINE _Just #-}
1361
1362{- |
1363'_Nothing' targets a @()@ if the 'Maybe' is a 'Nothing', and doesn't target anything otherwise:
1364
1365>>> Just 1 ^.. _Nothing
1366[]
1367
1368>>> Nothing ^.. _Nothing
1369[()]
1370
1371It's not particularly useful (unless you want to use @'has' '_Nothing'@ as a replacement for 'Data.Maybe.isNothing'), and provided mainly for consistency.
1372
1373Implementation:
1374
1375@
1376'_Nothing' f Nothing = 'const' 'Nothing' '<$>' f ()
1377'_Nothing' _ j       = 'pure' j
1378@
1379-}
1380_Nothing :: Traversal' (Maybe a) ()
1381_Nothing f Nothing = const Nothing <$> f ()
1382_Nothing _ j = pure j
1383{-# INLINE _Nothing #-}
1384
1385-- Some of the guts of lens
1386
1387newtype Traversed a f = Traversed { getTraversed :: f a }
1388
1389instance Applicative f => Monoid (Traversed a f) where
1390  mempty = Traversed (pure (error "Lens.Micro.Traversed: value used"))
1391  {-# INLINE mempty #-}
1392#if !MIN_VERSION_base(4,11,0)
1393  Traversed ma `mappend` Traversed mb = Traversed (ma *> mb)
1394  {-# INLINE mappend #-}
1395#else
1396instance Applicative f => Semigroup (Traversed a f) where
1397  Traversed ma <> Traversed mb = Traversed (ma *> mb)
1398  {-# INLINE (<>) #-}
1399#endif
1400
1401newtype Bazaar a b t = Bazaar (forall f. Applicative f => (a -> f b) -> f t)
1402
1403instance Functor (Bazaar a b) where
1404  fmap f (Bazaar k) = Bazaar (fmap f . k)
1405  {-# INLINE fmap #-}
1406
1407instance Applicative (Bazaar a b) where
1408  pure a = Bazaar $ \_ -> pure a
1409  {-# INLINE pure #-}
1410  Bazaar mf <*> Bazaar ma = Bazaar $ \afb -> mf afb <*> ma afb
1411  {-# INLINE (<*>) #-}
1412
1413-- A reimplementation of State
1414
1415newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
1416
1417type State s = StateT s Identity
1418
1419state :: Monad m => (s -> (a, s)) -> StateT s m a
1420state f = StateT (return . f)
1421{-# INLINE state #-}
1422
1423evalState :: State s a -> s -> a
1424evalState m s = fst (runState m s)
1425{-# INLINE evalState #-}
1426
1427runState :: State s a -> s -> (a, s)
1428runState m = runIdentity . runStateT m
1429{-# INLINE runState #-}
1430
1431instance (Functor m) => Functor (StateT s m) where
1432    fmap f m = StateT $ \ s ->
1433        fmap (\ ~(a, s') -> (f a, s')) $ runStateT m s
1434    {-# INLINE fmap #-}
1435
1436instance (Functor m, Monad m) => Applicative (StateT s m) where
1437    pure a = StateT $ \ s -> return (a, s)
1438    {-# INLINE pure #-}
1439    StateT mf <*> StateT mx = StateT $ \ s -> do
1440        ~(f, s') <- mf s
1441        ~(x, s'') <- mx s'
1442        return (f x, s'')
1443    {-# INLINE (<*>) #-}
1444
1445instance (Monad m) => Monad (StateT s m) where
1446#if !(MIN_VERSION_base(4,8,0))
1447    return a = StateT $ \ s -> return (a, s)
1448    {-# INLINE return #-}
1449#endif
1450    m >>= k  = StateT $ \ s -> do
1451        ~(a, s') <- runStateT m s
1452        runStateT (k a) s'
1453    {-# INLINE (>>=) #-}
1454#if !MIN_VERSION_base(4,13,0)
1455    fail str = StateT $ \ _ -> fail str
1456    {-# INLINE fail #-}
1457#endif
1458
1459#if MIN_VERSION_base(4,9,0)
1460instance (Fail.MonadFail m) => Fail.MonadFail (StateT s m) where
1461    fail str = StateT $ \ _ -> Fail.fail str
1462#endif
1463