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