microlens-0.4.13.1/0000755000000000000000000000000007346545000012122 5ustar0000000000000000microlens-0.4.13.1/CHANGELOG.md0000644000000000000000000000772007346545000013741 0ustar0000000000000000# 0.4.13.0 * Added `_Show`, `worded`, and `lined`. # 0.4.12.0 * Added instance `Ixed (NonEmpty a)` for GHC >= 8. # 0.4.11.3 * Exported a `coerce` compatibility shim from `Lens.Micro.Internal`. # 0.4.11.2 * Fixed compilation on GHC 8.8 (thanks to @vmchale). # 0.4.11.1 * Reverted marking `Lens.Micro.Internal` as `Trustworthy`, see [#122](https://github.com/monadfix/microlens/issues/122). # 0.4.11 * Added fixity declarations for `+~` and `-~` (thanks to Francesco Ariis). * Added `rewriteOf` and `transformOf` (thanks to @quasicomputational). * Added an instance `Each (Either a a) (Either b b) a b`, following `lens`'s suit. * Marked `Lens.Micro.Internal` as `Trustworthy` starting from GHC 7.8. # 0.4.10 * Added `+~` and `-~`. * Marked `#.` and `.#` with `INLINE`. # 0.4.9.1 * Reexported `<&>` from `Data.Functor` (on recent versions of `base`). # 0.4.9 * Added `<>~`. * Added fixities for `<%~`, `<<%~`, `<<.~`. # 0.4.8.3 * Fixed compilation on GHC 8.4. # 0.4.8.2 Skipped (the tarball got corrupted). # 0.4.8.1 * Added `HasCallStack` for some partial functions. # 0.4.8.0 * Added `forOf_` and `forOf`. * Added an instance for `Each (NonEmpty a)` (available starting from GHC 8). # 0.4.7.0 * Fixed the [Haddock crash on GHC 8](https://github.com/monadfix/microlens/issues/72) by removing default method implementations (`each = traverse` and `ix = ixAt`). If you had custom instances of `Ixed` or `Each` which relied on default methods, they'd stop working. # 0.4.6.0 * Added `traverseOf` and `traverseOf_`. * Changed fixities of `#.` and `.#` to the ones in the profunctors package. Those operators are only available from `Lens.Micro.Internal`, so this shouldn't affect most users. # 0.4.5.0 * Added `<&>` (which makes lens creation easier). # 0.4.4.3 * Fixed markup in the .cabal file. * Added descriptions of other packages to `Lens.Micro`. # 0.4.4.2 * More changes to make microlens-platform more prominent. # 0.4.4.1 * Pointed to microlens-platform in the synopsis. # 0.4.4.0 * Added `mapAccumLOf`. # 0.4.3.0 * Added `?~`. # 0.4.2.1 * Added forgotten copyright/authorship information. # 0.4.2.0 * Added `singular`. # 0.4.1.0 * Added `strict` and `lazy`. # 0.4.0.1 * Fixed a bug that wasn't letting the package compile with GHC 8.0 (see issue #63). # 0.4.0.0 * Added `folding`. * Renamed `Getter` and `Fold` to `SimpleGetter` and `SimpleFold` and put them into `Lens.Micro`. Genuine `Getter` and `Fold` are available in microlens-contra. * Replaced `Applicative (Const r)` constraints with `Monoid r` because it's the same thing but easier to understand. # 0.3.5.1 * Backported the fix for the bug that wasn't letting the package compile with GHC 8.0 (see issue #63). # 0.3.5.0 * Added `Lens.Micro.Extras` with `view`, `preview`, `Getter`, and `Fold`. Now you no longer need microlens-mtl if the only thing you need from it is `view`. # 0.3.4.1 * Changed the description of the package from “A tiny part of the lens library which you can depend upon” to “A tiny part of the lens library with no dependencies” because the previous one was ambiguous (I admit I kinda liked that ambiguity, though). # 0.3.4.0 * Added `non`. # 0.3.3.0 * Added `filtered`. * Added Safe Haskell pragmas. # 0.3.2.0 * Added `toListOf` back. * Added `to`. # 0.3.1.0 * Added `LensLike` and `LensLike'`. * Added `failing`. # 0.3.0.0 * Moved `Lens.Micro.Classes` into `Lens.Micro.Internal`. * Added `<%~`, `<<%~`, `<<.~`. * Added `_head`, `_tail`, `_init`, `_last`. # 0.2.0.0 * Removed `toListOf`. * Removed `+~`, `-~`, `*~`, `//~` and the `Lens.Micro.Extras` module. # 0.1.5.0 * Added `ix` and `at`. * Added `traversed`. * Moved some things into `Lens.Micro.Internal`. * Bumped base version. # 0.1.3.0 * Moved some things into `Lens.Micro.Type` and `Lens.Micro.Classes`. * `Each` and `Field*` aren't exported by `Lens.Micro` now. # 0.1.2.0 * Added `each`. # 0.1.1.0 * Added `ASetter'`, which is useful because we can't provide real `Setter` and `Setter'`. # 0.1.0.0 First release. microlens-0.4.13.1/LICENSE0000644000000000000000000000306507346545000013133 0ustar0000000000000000Copyright (c) 2013-2016 Edward Kmett, 2015-2016 Artyom Kazak, 2018 Monadfix All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of Monadfix nor the names of other contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. microlens-0.4.13.1/Setup.hs0000644000000000000000000000005607346545000013557 0ustar0000000000000000import Distribution.Simple main = defaultMain microlens-0.4.13.1/microlens.cabal0000644000000000000000000001104207346545000015077 0ustar0000000000000000name: microlens version: 0.4.13.1 synopsis: A tiny lens library with no dependencies description: NOTE: If you're writing an app, you probably want – it has the most features. is intended more for library writers who want a tiny lens library (after all, lenses are pretty useful for everything, not just for updating records!). . This library is an extract from (with no dependencies). It's not a toy lenses library, unsuitable for “real world”, but merely a small one. It is compatible with lens, and should have same performance. It also has better documentation. . There's a longer readme . It has a migration guide for lens users, a description of other packages in the family, a discussion of other lens libraries you could use instead, and so on. . Here are some usecases for this library: . * You want to define lenses or traversals in your own library, but don't want to depend on lens. Having lenses available often make working with a library more pleasant. . * You just want to be able to use lenses to transform data (or even just use @over _1@ to change the first element of a tuple). . * You are new to lenses and want a small library to play with. . However, don't use this library if: . * You need @Iso@s, @Prism@s, indexed traversals, or actually anything else which isn't defined here (though some indexed functions are available elsewhere – containers and vector provide them for their types, and provides indexed functions for lists). . * You want a library with a clean, understandable implementation (in which case you're looking for ). . As already mentioned, if you're writing an application which uses lenses more extensively, look at – it combines features of most other microlens packages (, , ). . If you want to export getters or folds and don't mind the dependency, please consider using . . If you haven't ever used lenses before, read . (It's for lens, but it applies to microlens just as well.) . Note that microlens has no dependencies starting from GHC 7.10 (base-4.8). Prior to that, it depends on transformers-0.2 or above. license: BSD3 license-file: LICENSE author: Edward Kmett, Artyom Kazak maintainer: Steven Fontanella homepage: http://github.com/monadfix/microlens bug-reports: http://github.com/monadfix/microlens/issues -- copyright: category: Data, Lenses build-type: Simple extra-source-files: CHANGELOG.md cabal-version: >=1.10 tested-with: GHC==7.6.3 GHC==7.8.4 GHC==7.10.3 GHC==8.0.2 GHC==8.2.2 GHC==8.4.4 GHC==8.6.5 GHC==8.8.4 GHC==8.10.7 GHC==9.0.2 GHC==9.2.5 GHC==9.4.3 source-repository head type: git location: git://github.com/monadfix/microlens.git library exposed-modules: Lens.Micro Lens.Micro.Extras Lens.Micro.Internal Lens.Micro.Type -- other-modules: -- other-extensions: -- Since base-4.8 we get the Identity functor in base, so we can avoid a -- transformers dependency. if impl(ghc>=7.9) build-depends: base >=4.8 && <5 if !impl(ghc>=7.9) build-depends: base >=4.5 && <5 , transformers >=0.2 ghc-options: -Wall -fwarn-tabs -O2 -fdicts-cheap -funbox-strict-fields -fmax-simplifier-iterations=10 hs-source-dirs: src default-language: Haskell2010 default-extensions: TypeOperators microlens-0.4.13.1/src/Lens/0000755000000000000000000000000007346545000013612 5ustar0000000000000000microlens-0.4.13.1/src/Lens/Micro.hs0000644000000000000000000013125707346545000015230 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE Trustworthy #-} {- | Module : Lens.Micro Copyright : (C) 2013-2016 Edward Kmett, 2015-2016 Artyom Kazak, 2018 Monadfix License : BSD-style (see the file LICENSE) This 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 – it provides the most functionality. * – (@+=@) and friends, @use@, @zoom@\/@magnify@ * – @makeLenses@ and @makeFields@ * – everything in microlens + instances to make @each@\/@at@\/@ix@ usable with arrays, @ByteString@, and containers * – microlens-ghc + microlens-mtl + microlens-th + instances for @Text@, @Vector@, and @HashMap@ * – @Fold@ and @Getter@ that are exact copies of types in lens Unofficial: * – a port of * - a port of -} module Lens.Micro ( (&), -- $ampersand-note (<&>), -- $reverse-fmap-note -- * Setter: modifies something in a structure -- $setters-note ASetter, ASetter', sets, (%~), over, (+~), (-~), (<>~), (.~), set, (?~), (<%~), (<<%~), (<<.~), mapped, rewriteOf, transformOf, -- * Getter: extracts a value from a structure -- $getters-note SimpleGetter, Getting, (^.), to, -- * Fold: extracts multiple elements -- $folds-note SimpleFold, (^..), toListOf, (^?), (^?!), traverseOf_, forOf_, has, folded, folding, -- * Lens: a combined getter-and-setter -- $lenses-note Lens, Lens', lens, at, _1, _2, _3, _4, _5, -- * Iso: a lens that only changes the representation -- $isos-note strict, lazy, non, -- * Traversal: a lens iterating over several elements -- $traversals-note Traversal, Traversal', traverseOf, forOf, singular, failing, filtered, both, traversed, each, ix, _head, _tail, _init, _last, mapAccumLOf, worded, lined, -- * Prism: a traversal iterating over at most 1 element -- $prisms-note _Left, _Right, _Just, _Nothing, _Show, -- * Other types LensLike, LensLike', ) where import Lens.Micro.Type import Lens.Micro.Internal import Control.Applicative import Control.Monad import Data.Functor.Identity import Data.List (intercalate) import Data.Monoid import Data.Maybe import Data.Tuple import qualified Data.Foldable as F #if MIN_VERSION_base(4,8,0) import Data.Function ((&)) #else import Data.Traversable (traverse) #endif #if MIN_VERSION_base(4,11,0) import Data.Functor ((<&>)) #endif -- This is for the reimplementation of State #if MIN_VERSION_base(4,9,0) import qualified Control.Monad.Fail as Fail #endif {- $setup -- >>> import Data.Char (toUpper) -- >>> import Control.Arrow (first, second, left, right) -} #if !(MIN_VERSION_base(4,8,0)) {- | '&' 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 '$'. -} (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-} infixl 1 & #endif {- $ampersand-note This 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: @ (1,2,3) '&' '_1' '.~' 0 '&' '_3' '%~' 'negate' @ instead of e.g. this: @ ('_1' '.~' 0) '.' ('_3' '%~' 'negate') '$' (1,2,3) @ or this: @ 'set' '_1' 0 '.' 'over' '_3' 'negate' '$' (1,2,3) @ -} #if !(MIN_VERSION_base(4,11,0)) {- | Flipped version of '<$>'. -} (<&>) :: Functor f => f a -> (a -> b) -> f b (<&>) x f = f <$> x {-# INLINE (<&>) #-} infixl 1 <&> #endif {- $reverse-fmap-note ('<&>') is flipped ('<$>'): @ x '<&>' f = f '<$>' x @ It'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: @ 'ix' key f map = case Map.lookup key map of Just val -> (\\val' -> Map.insert key val' map) '<$>' f val Nothing -> 'pure' map @ With ('<&>') you can get rid of parentheses and move the long lambda expression to the right of the value (like when you use '>>='): @ 'ix' key f map = case Map.lookup key map of Just val -> f val '<&>' \\val' -> Map.insert key val' map Nothing -> 'pure' map @ -} -- Setting ----------------------------------------------------------------- {- $setters-note A setter is, broadly speaking, something that lets you modify a part of some value. Most likely you already know some setters: * @'Control.Arrow.first' :: (a -> b) -> (a, x) -> (b, x)@ (modifies 1st element of a pair; corresponds to 'Lens.Micro._1') * @'Control.Arrow.left' :: (a -> b) -> 'Either' a x -> 'Either' b x@ (modifies left branch of 'Either'; corresponds to 'Lens.Micro._Left') * @'map' :: (a -> b) -> [a] -> [b]@ (modifies every element in a list; corresponds to 'Lens.Micro.mapped') As 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: @ -- Modify 3rd element in a list, if present. modify3rd :: (a -> a) -> [a] -> [a] modify3rd f (a:b:c:xs) = a : b : f c : xs modify3rd _ xs = xs @ A 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. This 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'. To apply a setter to a value, use ('%~') or 'over': >>> [1,2,3] & mapped %~ succ [2,3,4] >>> over _head toUpper "jane" "Jane" To modify a value deeper inside the structure, use ('.'): >>> ["abc","def","ghi"] & ix 1 . ix 2 %~ toUpper ["abc","deF","ghi"] To set a value instead of modifying it, use 'set' or ('.~'): >>> "abc" & mapped .~ 'x' "xxx" >>> set _2 'X' ('a','b','c') ('a','X','c') It's also possible to get both the old and the new value back – see ('<%~') and ('<<%~'). -} {- | ('%~') 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'@. See 'over' if you want a non-operator synonym. Negating the 1st element of a pair: >>> (1,2) & _1 %~ negate (-1,2) Turning all @Left@s in a list to upper case: >>> (mapped._Left.mapped %~ toUpper) [Left "foo", Right "bar"] [Left "FOO",Right "bar"] -} (%~) :: ASetter s t a b -> (a -> b) -> s -> t (%~) = over {-# INLINE (%~) #-} infixr 4 %~ {- | 'over' is a synonym for ('%~'). Getting 'fmap' in a roundabout way: @ 'over' 'mapped' :: 'Functor' f => (a -> b) -> f a -> f b 'over' 'mapped' = 'fmap' @ Applying a function to both components of a pair: @ 'over' 'both' :: (a -> b) -> (a, a) -> (b, b) 'over' 'both' = \\f t -> (f (fst t), f (snd t)) @ Using @'over' '_2'@ as a replacement for 'Control.Arrow.second': >>> over _2 show (10,20) (10,"20") -} over :: ASetter s t a b -> (a -> b) -> s -> t over l f = runIdentity #. l (Identity #. f) {-# INLINE over #-} {- | Increment the target(s) of a numerically valued 'Lens' or 'Traversal'. >>> (a,b) & _1 +~ c (a + c,b) >>> (a,b) & both +~ c (a + c,b + c) >>> (1,2) & _2 +~ 1 (1,3) >>> [(a,b),(c,d)] & traverse.both +~ e [(a + e,b + e),(c + e,d + e)] @ ('+~') :: 'Num' a => 'Lens'' s a -> a -> s -> s ('+~') :: 'Num' a => 'Traversal'' s a -> a -> s -> s @ @since 0.4.10 -} (+~) :: Num a => ASetter s t a a -> a -> s -> t l +~ n = over l (+ n) {-# INLINE (+~) #-} infixr 4 +~ {- | Decrement the target(s) of a numerically valued 'Lens', or 'Traversal'. >>> (a,b) & _1 -~ c (a - c,b) >>> (a,b) & both -~ c (a - c,b - c) >>> _1 -~ 2 $ (1,2) (-1,2) >>> mapped.mapped -~ 1 $ [[4,5],[6,7]] [[3,4],[5,6]] @ ('-~') :: 'Num' a => 'Lens'' s a -> a -> s -> s ('-~') :: 'Num' a => 'Traversal'' s a -> a -> s -> s @ @since 0.4.10 -} (-~) :: Num a => ASetter s t a a -> a -> s -> t l -~ n = over l (subtract n) {-# INLINE (-~) #-} infixr 4 -~ {- | ('<>~') appends a value monoidally to the target. >>> ("hello", "goodbye") & both <>~ " world!" ("hello world!", "goodbye world!") @since 0.4.9 -} (<>~) :: (Monoid a) => ASetter s t a a -> a -> s -> t (<>~) l a = over l (`mappend` a) {-# INLINE (<>~) #-} infixr 4 <>~ {- | ('.~') assigns a value to the target. It's the same thing as using ('%~') with 'const': @ l '.~' x = l '%~' 'const' x @ See 'set' if you want a non-operator synonym. Here it is used to change 2 fields of a 3-tuple: >>> (0,0,0) & _1 .~ 1 & _3 .~ 3 (1,0,3) -} (.~) :: ASetter s t a b -> b -> s -> t (.~) = set {-# INLINE (.~) #-} infixr 4 .~ {- | 'set' is a synonym for ('.~'). Setting the 1st component of a pair: @ 'set' '_1' :: x -> (a, b) -> (x, b) 'set' '_1' = \\x t -> (x, snd t) @ Using it to rewrite ('Data.Functor.<$'): @ 'set' 'mapped' :: 'Functor' f => a -> f b -> f a 'set' 'mapped' = ('Data.Functor.<$') @ -} set :: ASetter s t a b -> b -> s -> t set l b = runIdentity #. l (\_ -> Identity b) {-# INLINE set #-} {- | ('?~') is a version of ('.~') that wraps the value into 'Just' before setting. @ l ?~ b = l .~ Just b @ It can be useful in combination with 'at': >>> Map.empty & at 3 ?~ x fromList [(3,x)] -} (?~) :: ASetter s t a (Maybe b) -> b -> s -> t l ?~ b = set l (Just b) {-# INLINE (?~) #-} infixr 4 ?~ {- | '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'). Here 'mapped' is used to turn a value to all non-'Nothing' values in a list: >>> [Just 3,Nothing,Just 5] & mapped.mapped .~ 0 [Just 0,Nothing,Just 0] Keep 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): @ [(1,2),(3,4),(5,6)] '^..' 'mapped' . 'both' @ -} mapped :: Functor f => ASetter (f a) (f b) a b mapped = sets fmap {-# INLINE mapped #-} {- | This is a version of ('%~') which modifies the structure and returns it along with the new value: >>> (1, 2) & _1 <%~ negate (-1, (-1, 2)) Simpler type signatures: @ ('<%~') :: 'Lens' s t a b -> (a -> b) -> s -> (b, t) ('<%~') :: 'Monoid' b => 'Traversal' s t a b -> (a -> b) -> s -> (b, t) @ Since it does getting in addition to setting, you can't use it with 'ASetter' (but you can use it with lens and traversals). -} (<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t) (<%~) l f = l (join (,) . f) {-# INLINE (<%~) #-} infixr 4 <%~ {- | This is a version of ('%~') which modifies the structure and returns it along with the old value: >>> (1, 2) & _1 <<%~ negate (1, (-1, 2)) Simpler type signatures: @ ('<<%~') :: 'Lens' s t a b -> (a -> b) -> s -> (a, t) ('<<%~') :: 'Monoid' a => 'Traversal' s t a b -> (a -> b) -> s -> (a, t) @ -} (<<%~) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t) (<<%~) l f = l (\a -> (a, f a)) {-# INLINE (<<%~) #-} infixr 4 <<%~ {- | This is a version of ('.~') which modifies the structure and returns it along with the old value: >>> (1, 2) & _1 <<.~ 0 (1, (0, 2)) Simpler type signatures: @ ('<<.~') :: 'Lens' s t a b -> b -> s -> (a, t) ('<<.~') :: 'Monoid' a => 'Traversal' s t a b -> b -> s -> (a, t) @ -} (<<.~) :: LensLike ((,) a) s t a b -> b -> s -> (a, t) (<<.~) l x = l (\a -> (a, x)) {-# INLINE (<<.~) #-} infixr 4 <<.~ {- | → See on GitHub. Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result. Usually '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. @since 0.4.11 -} rewriteOf :: ASetter a b a b -> (b -> Maybe a) -> a -> b rewriteOf l f = go where go = transformOf l (\x -> maybe x go (f x)) {-# INLINE rewriteOf #-} {- | Transform every element by recursively applying a given 'ASetter' in a bottom-up manner. @since 0.4.11 -} transformOf :: ASetter a b a b -> (b -> b) -> a -> b transformOf l f = go where go = f . over l go {-# INLINE transformOf #-} -- Getting ----------------------------------------------------------------- {- $getters-note A 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'. Using a getter is done with ('^.') or 'Lens.Micro.Extras.view' from "Lens.Micro.Extras": >>> ('x','y') ^. _1 'x' >>> view (ix 2) [0..5] 2 Getters can be composed with ('.'): >>> [(1,2),(3,4),(5,6)] ^. ix 1 . _2 4 A 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). -} {- | ('^.') 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.). Getting 1st field of a tuple: @ ('^.' '_1') :: (a, b) -> a ('^.' '_1') = 'fst' @ When ('^.') 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: >>> ("str","ing") ^. each "string" The reason for this is that traversals use 'Applicative', and the 'Applicative' instance for 'Const' uses monoid concatenation to combine “effects” of 'Const'. A 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 ; otherwise there's 'Lens.Micro.Extras.view' available in "Lens.Micro.Extras". -} (^.) :: s -> Getting a s a -> a s ^. l = getConst (l Const s) {-# INLINE (^.) #-} infixl 8 ^. {- | 'to' creates a getter from any function: @ a '^.' 'to' f = f a @ It'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: @ value ^. _1 . field . at 2 @ However, @field@ isn't a getter, and you have to do this instead: @ field (value ^. _1) ^. at 2 @ but now @value@ is in the middle and it's hard to read the resulting code. A variant with 'to' is prettier and more readable: @ value ^. _1 . to field . at 2 @ -} to :: (s -> a) -> SimpleGetter s a to k f = phantom . f . k {-# INLINE to #-} -- Folds ------------------------------------------------------------------- {- $folds-note Folds are getters that can return more than one element (or no elements at all). , 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. Folds can be applied to values by using operators like ('^..'), ('^?'), etc: >>> (1,2) ^.. both [1,2] A nice thing about folds is that you can combine them with ('Data.Monoid.<>') to concatenate their outputs: >>> (1,2,3) ^.. (_2 <> _1) [2,1] When you need to get all elements of the same type in a complicated structure, ('Data.Monoid.<>') can be more helpful than 'each': >>> ([1,2], 3, [Nothing, Just 4]) ^.. (_1.each <> _2 <> _3.each._Just) [1,2,3,4] (Just like setters and getters before, folds can be composed with ('.').) The ('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@: >>> [0..9] ^? (ix 9 <> ix 5) Just 9 >>> [0..8] ^? (ix 9 <> ix 5) Just 5 >>> [0..3] ^? (ix 9 <> ix 5) Nothing (Unfortunately, this trick won't help you with setting or modifying.) -} {- | @s ^.. t@ returns the list of all values that @t@ gets from @s@. A 'Maybe' contains either 0 or 1 values: >>> Just 3 ^.. _Just [3] Gathering all values in a list of tuples: >>> [(1,2),(3,4)] ^.. each.each [1,2,3,4] -} (^..) :: s -> Getting (Endo [a]) s a -> [a] s ^.. l = toListOf l s {-# INLINE (^..) #-} infixl 8 ^.. {- | 'toListOf' is a synonym for ('^..'). -} toListOf :: Getting (Endo [a]) s a -> s -> [a] toListOf l = foldrOf l (:) [] {-# INLINE toListOf #-} {- | @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. Safe 'head': >>> [] ^? each Nothing >>> [1..3] ^? each Just 1 Converting 'Either' to 'Maybe': >>> Left 1 ^? _Right Nothing >>> Right 1 ^? _Right Just 1 A 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 ; otherwise there's 'Lens.Micro.Extras.preview' available in "Lens.Micro.Extras". -} (^?) :: s -> Getting (First a) s a -> Maybe a s ^? l = getFirst (foldMapOf l (First #. Just) s) {-# INLINE (^?) #-} infixl 8 ^? {- | ('^?!') is an unsafe variant of ('^?') – instead of using 'Nothing' to indicate that there were no elements returned, it throws an exception. -} (^?!) :: HasCallStack => s -> Getting (Endo a) s a -> a s ^?! l = foldrOf l const (error "(^?!): empty Fold") s {-# INLINE (^?!) #-} infixl 8 ^?! {- | Apply an action to all targets and discard the result (like 'Control.Monad.mapM_' or 'Data.Foldable.traverse_'): >>> traverseOf_ both putStrLn ("hello", "world") hello world Works 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. -} traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f () traverseOf_ l f = void . getTraversed #. foldMapOf l (Traversed #. f) {-# INLINE traverseOf_ #-} {- | 'traverseOf_' with flipped arguments. Useful if the “loop body” is a lambda or a @do@ block, or in some other cases – for instance, you can avoid accidentally using 'Data.Foldable.for_' on a tuple or 'Either' by switching to @'forOf_' 'each'@. Or you can write custom loops like these: @ 'forOf_' 'both' (a, b) $ \\x -\> ... 'forOf_' 'each' [1..10] $ \\x -\> ... 'forOf_' ('each' . '_Right') $ \\x -\> ... @ -} forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f () forOf_ = flip . traverseOf_ {-# INLINE forOf_ #-} {- | 'has' checks whether a getter (any getter, including lenses, traversals, and folds) returns at least 1 value. Checking whether a list is non-empty: >>> has each [] False You can also use it with e.g. '_Left' (and other 0-or-1 traversals) as a replacement for 'Data.Maybe.isNothing', 'Data.Maybe.isJust' and other @isConstructorName@ functions: >>> has _Left (Left 1) True -} has :: Getting Any s a -> s -> Bool has l = getAny #. foldMapOf l (\_ -> Any True) {-# INLINE has #-} {- | 'folding' creates a fold out of any function that returns a 'F.Foldable' container (for instance, a list): >>> [1..5] ^.. folding tail [2,3,4,5] -} folding :: F.Foldable f => (s -> f a) -> SimpleFold s a folding sfa agb = phantom . F.traverse_ agb . sfa {-# INLINE folding #-} -- Lenses ------------------------------------------------------------------ {- $lenses-note Lenses 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: >>> (1,2) ^. _1 1 >>> (1,2) & _1 .~ 3 (3,2) >>> (1,2) & _1 %~ negate (-1,2) To 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): >>> traverseOf_ _1 print (1,2) 1 >>> _1 id (Just 1, 2) Just (1, 2) >>> _1 id (Nothing, 2) Nothing A 'Lens' can only point at a single value inside a structure (unlike a 'Traversal'). ('.') 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. There are several ways to get lenses for some datatype: * They can already be provided by the package, by @microlens@, or by some other package like . * They can be provided by some unofficial package (like ). * You can get them by combining already existing lenses. * You can derive them with Template Haskell (with ). * You can write them with 'lens' if you have a setter and a getter. It's a simple and good way. * You can write them manually (sometimes it looks a bit better than the variant with 'lens', sometimes worse). The generic template is as follows: @ somelens :: Lens s t a b -- “f” is the “a -> f b” function, “s” is the structure. somelens f s = let a = ... -- Extract the value from “s”. rebuildWith b = ... -- Write a function which would -- combine “s” and modified value -- to produce new structure. in rebuildWith '<$>' f a -- Apply the structure-producing -- function to the modified value. @ Here's the '_1' lens, for instance: @ '_1' :: 'Lens' (a, x) (b, x) a b '_1' f (a, x) = (\\b -> (b, x)) '<$>' f a @ Here's a more complicated lens, which extracts /several/ values from a structure (in a tuple): @ type Age = Int type City = String type Country = String data Person = Person Age City Country -- This lens lets you access all location-related information about a person. location :: 'Lens'' Person (City, Country) location f (Person age city country) = (\\(city', country') -> Person age city' country') '<$>' f (city, country) @ You even can choose to use a lens to present /all/ information contained in the structure (in a different way). Such lenses are called @@ 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: @ string :: (Read a, Show a) => 'Lens'' a String string f s = read '<$>' f (show s) @ Using it to reverse a number: @ >>> 123 '&' string '%~' reverse 321 @ -} {- | 'lens' creates a 'Lens' from a getter and a setter. The resulting lens isn't the most effective one (because of having to traverse the structure twice when modifying), but it shouldn't matter much. A (partial) lens for list indexing: @ ix :: Int -> 'Lens'' [a] a ix i = 'lens' ('!!' i) -- getter (\\s b -> take i s ++ b : drop (i+1) s) -- setter @ Usage: @ >>> [1..9] '^.' ix 3 4 >>> [1..9] & ix 3 '%~' negate [1,2,3,-4,5,6,7,8,9] @ When getting, the setter is completely unused; when setting, the getter is unused. Both are used only when the value is being modified. For instance, here we define a lens for the 1st element of a list, but instead of a legitimate getter we use 'undefined'. Then we use the resulting lens for /setting/ and it works, which proves that the getter wasn't used: >>> [1,2,3] & lens undefined (\s b -> b : tail s) .~ 10 [10,2,3] -} lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b lens sa sbt afb s = sbt s <$> afb (sa s) {-# INLINE lens #-} -- Isos -------------------------------------------------------------------- {- $isos-note Isos (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: @ from :: Iso' s a -> Iso' a s @ However, it's not possible for microlens to export isomorphisms, because their type depends on @@, which resides in the 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). -} {- | 'non' lets you “relabel” a 'Maybe' by equating 'Nothing' to an arbitrary value (which you can choose): >>> Just 1 ^. non 0 1 >>> Nothing ^. non 0 0 The most useful thing about 'non' is that relabeling also works in other direction. If you try to 'set' the “forbidden” value, it'll be turned to 'Nothing': >>> Just 1 & non 0 .~ 0 Nothing Setting anything else works just fine: >>> Just 1 & non 0 .~ 5 Just 5 Same happens if you try to modify a value: >>> Just 1 & non 0 %~ subtract 1 Nothing >>> Just 1 & non 0 %~ (+ 1) Just 2 'non' is often useful when combined with 'at'. For instance, if you have a map of songs and their playcounts, it makes sense not to store songs with 0 plays in the map; 'non' can act as a filter that wouldn't pass such entries. Decrease playcount of a song to 0, and it'll be gone: >>> fromList [("Soon",1),("Yesterday",3)] & at "Soon" . non 0 %~ subtract 1 fromList [("Yesterday",3)] Try to add a song with 0 plays, and it won't be added: >>> fromList [("Yesterday",3)] & at "Soon" . non 0 .~ 0 fromList [("Yesterday",3)] But it will be added if you set any other number: >>> fromList [("Yesterday",3)] & at "Soon" . non 0 .~ 1 fromList [("Soon",1),("Yesterday",3)] 'non' is also useful when working with nested maps. Here a nested map is created when it's missing: >>> Map.empty & at "Dez Mona" . non Map.empty . at "Soon" .~ Just 1 fromList [("Dez Mona",fromList [("Soon",1)])] and here it is deleted when its last entry is deleted (notice that 'non' is used twice here): >>> fromList [("Dez Mona",fromList [("Soon",1)])] & at "Dez Mona" . non Map.empty . at "Soon" . non 0 %~ subtract 1 fromList [] To understand the last example better, observe the flow of values in it: * the map goes into @at \"Dez Mona\"@ * the nested map (wrapped into @Just@) goes into @non Map.empty@ * @Just@ is unwrapped and the nested map goes into @at \"Soon\"@ * @Just 1@ is unwrapped by @non 0@ Then the final value – i.e. 1 – is modified by @subtract 1@ and the result (which is 0) starts flowing backwards: * @non 0@ sees the 0 and produces a @Nothing@ * @at \"Soon\"@ sees @Nothing@ and deletes the corresponding value from the map * the resulting empty map is passed to @non Map.empty@, which sees that it's empty and thus produces @Nothing@ * @at \"Dez Mona\"@ sees @Nothing@ and removes the key from the map -} non :: Eq a => a -> Lens' (Maybe a) a non x afb s = f <$> afb (fromMaybe x s) where f y = if x == y then Nothing else Just y {-# INLINE non #-} -- Traversals -------------------------------------------------------------- {- $traversals-note Traversals 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. Traversals 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): * ('^..') gets a list of values * ('^?') gets the 1st value (or 'Nothing' if there are no values) * ('^?!') gets the 1st value and throws an exception if there are no values If you are sure that the traversal will traverse at least one value, you can convert it to a lens with 'singular'. '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. -} {- | Apply an action to all targets (like 'Control.Monad.mapM' or 'Data.Traversable.traverse'): >>> traverseOf both readFile ("file1", "file2") (, ) >>> traverseOf _1 id (Just 1, 2) Just (1, 2) >>> traverseOf _1 id (Nothing, 2) Nothing You can also just apply the lens\/traversal directly (but 'traverseOf' might be more readable): >>> both readFile ("file1", "file2") (, ) If you don't need the result, use 'traverseOf_'. -} traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t traverseOf = id {-# INLINE traverseOf #-} {- | 'traverseOf' with flipped arguments. Useful if the “loop body” is a lambda or a @do@ block. -} forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t forOf = flip {-# INLINE forOf #-} {- | 'singular' turns a traversal into a lens that behaves like a single-element traversal: >>> [1,2,3] ^. singular each 1 >>> [1,2,3] & singular each %~ negate [-1,2,3] If there is nothing to return, it'll throw an error: >>> [] ^. singular each *** Exception: Lens.Micro.singular: empty traversal However, it won't fail if you are merely setting the value: >>> [] & singular each %~ negate -} singular :: HasCallStack => Traversal s t a a -> Lens s t a a singular l afb s = case ins b of (w:ws) -> unsafeOuts b . (:ws) <$> afb w [] -> unsafeOuts b . return <$> afb (error "Lens.Micro.singular: empty traversal") where Bazaar b = l sell s sell w = Bazaar ($ w) ins f = (coerce :: [Identity a] -> [a]) (getConst (f (\ra -> Const [Identity ra]))) unsafeOuts f = evalState (f (\_ -> state (unconsWithDefault fakeVal))) where fakeVal = error "unsafeOuts: not enough elements were supplied" unconsWithDefault d [] = (d,[]) unconsWithDefault _ (x:xs) = (x,xs) {-# INLINE singular #-} {- | 'failing' lets you chain traversals together; if the 1st traversal fails, the 2nd traversal will be used. >>> ([1,2],[3]) & failing (_1.each) (_2.each) .~ 0 ([0,0],[3]) >>> ([],[3]) & failing (_1.each) (_2.each) .~ 0 ([],[0]) Note that the resulting traversal won't be valid unless either both traversals don't touch each others' elements, or both traversals return exactly the same results. To see an example of how 'failing' can generate invalid traversals, see . -} failing :: Traversal s t a b -> Traversal s t a b -> Traversal s t a b failing left right afb s = case pins b of [] -> right afb s _ -> b afb where Bazaar b = left sell s sell w = Bazaar ($ w) pins f = getConst (f (\ra -> Const [Identity ra])) infixl 5 `failing` {- | 'filtered' is a traversal that filters elements “passing” through it: >>> (1,2,3,4) ^.. each [1,2,3,4] >>> (1,2,3,4) ^.. each . filtered even [2,4] It also can be used to modify elements selectively: >>> (1,2,3,4) & each . filtered even %~ (*100) (1,200,3,400) The implementation of 'filtered' is very simple. Consider this traversal, which always “traverses” just the value it's given: @ id :: 'Traversal'' a a id f s = f s @ And this traversal, which traverses nothing (in other words, /doesn't/ traverse the value it's given): @ ignored :: 'Traversal'' a a ignored f s = 'pure' s @ And now combine them into a traversal that conditionally traverses the value it's given, and you get 'filtered': @ filtered :: (a -> Bool) -> 'Traversal'' a a filtered p f s = if p s then f s else 'pure' s @ By the way, note that 'filtered' can generate illegal traversals – sometimes this can bite you. In particular, an optimisation that should be safe becomes unsafe. (To the best of my knowledge, this optimisation never happens automatically. If you just use 'filtered' to modify/view something, you're safe. If you don't define any traversals that use 'filtered', you're safe too.) Let's use @evens@ as an example: @ evens = 'filtered' 'even' @ If @evens@ was a legal traversal, you'd be able to fuse several applications of @evens@ like this: @ 'over' evens f '.' 'over' evens g = 'over' evens (f '.' g) @ Unfortunately, in case of @evens@ this isn't a correct optimisation: * the left-side variant applies @g@ to all even numbers, and then applies @f@ to all even numbers that are left after @f@ (because @f@ might've turned some even numbers into odd ones) * the right-side variant applies @f@ and @g@ to all even numbers Of course, when you are careful and know what you're doing, you won't try to make such an optimisation. However, if you export an illegal traversal created with 'filtered' and someone tries to use it, they might mistakenly assume that it's legal, do the optimisation, and silently get an incorrect result. If you are using 'filtered' with some another traversal that doesn't overlap with -whatever the predicate checks-, the resulting traversal will be legal. For instance, here the predicate looks at the 1st element of a tuple, but the resulting traversal only gives you access to the 2nd: @ pairedWithEvens :: 'Traversal' [(Int, a)] [(Int, b)] a b pairedWithEvens = 'each' '.' 'filtered' ('even' '.' 'fst') '.' '_2' @ Since you can't do anything with the 1st components through this traversal, the following holds for any @f@ and @g@: @ 'over' pairedWithEvens f '.' 'over' pairedWithEvens g = 'over' pairedWithEvens (f '.' g) @ -} filtered :: (a -> Bool) -> Traversal' a a filtered p f s = if p s then f s else pure s {-# INLINE filtered #-} {- | 'both' traverses both fields of a tuple. Unlike @@ from lens, it only works for pairs – not for triples or 'Either'. >>> ("str","ing") ^. both "string" >>> ("str","ing") & both %~ reverse ("rts","gni") -} both :: Traversal (a, a) (b, b) a b both f = \ ~(a, b) -> liftA2 (,) (f a) (f b) {-# INLINE both #-} {- | '_head' traverses the 1st element of something (usually a list, but can also be a @Seq@, etc): >>> [1..5] ^? _head Just 1 It can be used to modify too, as in this example where the 1st letter of a sentence is capitalised: >>> "mary had a little lamb." & _head %~ toTitle "Mary had a little lamb." The reason it's a traversal and not a lens is that there's nothing to traverse when the list is empty: >>> [] ^? _head Nothing This package only lets you use '_head' on lists, but if you use you get instances for @ByteString@ and @Seq@, and if you use you additionally get instances for @Text@ and @Vector@. -} _head :: Cons s s a a => Traversal' s a _head = _Cons._1 {-# INLINE _head #-} {- | '_tail' gives you access to the tail of a list (or @Seq@, etc): >>> [1..5] ^? _tail Just [2,3,4,5] You can modify the tail as well: >>> [4,1,2,3] & _tail %~ reverse [4,3,2,1] Since lists are monoids, you can use '_tail' with plain ('^.') (and then it'll return an empty list if you give it an empty list): >>> [1..5] ^. _tail [2,3,4,5] >>> [] ^. _tail [] If you want to traverse each /element/ of the tail, use '_tail' with 'each': >>> "I HATE CAPS." & _tail.each %~ toLower "I hate caps." This package only lets you use '_tail' on lists, but if you use you get instances for @ByteString@ and @Seq@, and if you use you additionally get instances for @Text@ and @Vector@. -} _tail :: Cons s s a a => Traversal' s s _tail = _Cons._2 {-# INLINE _tail #-} {- | '_init' gives you access to all-but-the-last elements of the list: >>> "Hello." ^. _init "Hello" See documentation for '_tail', as '_init' and '_tail' are pretty similar. -} _init :: Snoc s s a a => Traversal' s s _init = _Snoc._1 {-# INLINE _init #-} {- | '_last' gives you access to the last element of the list: >>> "Hello." ^? _last '.' See documentation for '_head', as '_last' and '_head' are pretty similar. -} _last :: Snoc s s a a => Traversal' s a _last = _Snoc._2 {-# INLINE _last #-} {- | This generalizes 'Data.Traversable.mapAccumL' to an arbitrary 'Traversal'. (Note that it doesn't work on folds, only traversals.) @ 'mapAccumL' ≡ 'mapAccumLOf' 'traverse' @ -} mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) mapAccumLOf l f acc0 s = swap (runState (l g s) acc0) where g a = state $ \acc -> swap (f acc a) {-# INLINE mapAccumLOf #-} {- | Focus on the 'words' of a string. >>> "avoid success at all costs" & worded . _head %~ toUpper "Avoid Success At All Costs" This violates the traversal laws when whitespace is set or when the source has space at the ends or more than one contiguous space anywhere. -} worded :: Traversal' String String worded f = fmap unwords . traverse f . words {-# INLINE worded #-} {- | Focus on the 'lines' of a string. @ countAndMarkEmptyLines :: String -> State Int String countAndMarkEmptyLines s = runState (f s) 0 where f = 'traverseOf' (lined . 'filtered' null) $ \\_ -> do modify' (+ 1) return "# Empty line" @ This violates the traversal laws when newlines are set or when the source has more than one contiguous newline anywhere. -} lined :: Traversal' String String lined f = fmap (intercalate "\n") . traverse f . lines {-# INLINE lined #-} -- Prisms ------------------------------------------------------------------ {- $prisms-note Prisms 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: @ >>> over _Left (+1) (Left 2) Left 3 >>> _Left # 5 Left 5 @ However, it's not possible for microlens to export prisms, because their type depends on @@ from . So, all prisms included here are traversals instead (and you can't reverse them). -} {- | '_Left' targets the value contained in an 'Either', provided it's a 'Left'. Gathering all @Left@s in a structure (like the 'Data.Either.lefts' function, but not necessarily just for lists): >>> [Left 1, Right 'c', Left 3] ^.. each._Left [1,3] Checking whether an 'Either' is a 'Left' (like 'Data.Either.isLeft'): >>> has _Left (Left 1) True >>> has _Left (Right 1) False Extracting a value (if you're sure it's a 'Left'): >>> Left 1 ^?! _Left 1 Mapping over all 'Left's: >>> (each._Left %~ map toUpper) [Left "foo", Right "bar"] [Left "FOO",Right "bar"] Implementation: @ '_Left' f (Left a) = 'Left' '<$>' f a '_Left' _ (Right b) = 'pure' ('Right' b) @ -} _Left :: Traversal (Either a b) (Either a' b) a a' _Left f (Left a) = Left <$> f a _Left _ (Right b) = pure (Right b) {-# INLINE _Left #-} {- | '_Right' targets the value contained in an 'Either', provided it's a 'Right'. See documentation for '_Left'. -} _Right :: Traversal (Either a b) (Either a b') b b' _Right f (Right b) = Right <$> f b _Right _ (Left a) = pure (Left a) {-# INLINE _Right #-} {- | '_Just' targets the value contained in a 'Maybe', provided it's a 'Just'. See documentation for '_Left' (as these 2 are pretty similar). In particular, it can be used to write these: * Unsafely extracting a value from a 'Just': @ 'Data.Maybe.fromJust' = ('^?!' '_Just') @ * Checking whether a value is a 'Just': @ 'Data.Maybe.isJust' = 'has' '_Just' @ * Converting a 'Maybe' to a list (empty or consisting of a single element): @ 'Data.Maybe.maybeToList' = ('^..' '_Just') @ * Gathering all 'Just's in a list: @ 'Data.Maybe.catMaybes' = ('^..' 'each' '.' '_Just') @ -} _Just :: Traversal (Maybe a) (Maybe a') a a' _Just f (Just a) = Just <$> f a _Just _ Nothing = pure Nothing {-# INLINE _Just #-} {- | '_Nothing' targets a @()@ if the 'Maybe' is a 'Nothing', and doesn't target anything otherwise: >>> Just 1 ^.. _Nothing [] >>> Nothing ^.. _Nothing [()] It's not particularly useful (unless you want to use @'has' '_Nothing'@ as a replacement for 'Data.Maybe.isNothing'), and provided mainly for consistency. Implementation: @ '_Nothing' f Nothing = 'const' 'Nothing' '<$>' f () '_Nothing' _ j = 'pure' j @ -} _Nothing :: Traversal' (Maybe a) () _Nothing f Nothing = const Nothing <$> f () _Nothing _ j = pure j {-# INLINE _Nothing #-} {- | '_Show' targets the Haskell value in a @String@ using 'Read', or nothing if parsing fails. Likewise, setting a Haskell value through this prism renders a @String@ using 'Show'. >>> ["abc","8","def","9"] & mapped . _Show %~ \x -> x + 1 :: Int ["abc","9","def","10"] Note that this prism is improper for types that don\'t satisfy @read . show = id@: >>> "25.9999999" & _Show %~ \x -> x :: Float "26.0" These functions from @base@ can be expressed in terms of '_Show': * Unsafely parsing a value from a 'String': @ 'read' = ('^?!' '_Show') @ * Safely parsing a value from a 'String': @ 'Text.Read.readMaybe' = ('^?' '_Show') @ -} _Show :: (Show a, Read a) => Traversal' String a _Show f s = case reads s of [(a,"")] -> show <$> f a _ -> pure s {-# INLINE _Show #-} -- Some of the guts of lens newtype Traversed a f = Traversed { getTraversed :: f a } instance Applicative f => Monoid (Traversed a f) where mempty = Traversed (pure (error "Lens.Micro.Traversed: value used")) {-# INLINE mempty #-} #if !MIN_VERSION_base(4,11,0) Traversed ma `mappend` Traversed mb = Traversed (ma *> mb) {-# INLINE mappend #-} #else instance Applicative f => Semigroup (Traversed a f) where Traversed ma <> Traversed mb = Traversed (ma *> mb) {-# INLINE (<>) #-} #endif newtype Bazaar a b t = Bazaar (forall f. Applicative f => (a -> f b) -> f t) instance Functor (Bazaar a b) where fmap f (Bazaar k) = Bazaar (fmap f . k) {-# INLINE fmap #-} instance Applicative (Bazaar a b) where pure a = Bazaar $ \_ -> pure a {-# INLINE pure #-} Bazaar mf <*> Bazaar ma = Bazaar $ \afb -> mf afb <*> ma afb {-# INLINE (<*>) #-} -- A reimplementation of State newtype StateT s m a = StateT { runStateT :: s -> m (a, s) } type State s = StateT s Identity state :: Monad m => (s -> (a, s)) -> StateT s m a state f = StateT (return . f) {-# INLINE state #-} evalState :: State s a -> s -> a evalState m s = fst (runState m s) {-# INLINE evalState #-} runState :: State s a -> s -> (a, s) runState m = runIdentity . runStateT m {-# INLINE runState #-} instance (Functor m) => Functor (StateT s m) where fmap f m = StateT $ \ s -> fmap (\ ~(a, s') -> (f a, s')) $ runStateT m s {-# INLINE fmap #-} instance (Functor m, Monad m) => Applicative (StateT s m) where pure a = StateT $ \ s -> return (a, s) {-# INLINE pure #-} StateT mf <*> StateT mx = StateT $ \ s -> do ~(f, s') <- mf s ~(x, s'') <- mx s' return (f x, s'') {-# INLINE (<*>) #-} instance (Monad m) => Monad (StateT s m) where #if !(MIN_VERSION_base(4,8,0)) return a = StateT $ \ s -> return (a, s) {-# INLINE return #-} #endif m >>= k = StateT $ \ s -> do ~(a, s') <- runStateT m s runStateT (k a) s' {-# INLINE (>>=) #-} #if !MIN_VERSION_base(4,13,0) fail str = StateT $ \ _ -> fail str {-# INLINE fail #-} #endif #if MIN_VERSION_base(4,9,0) instance (Fail.MonadFail m) => Fail.MonadFail (StateT s m) where fail str = StateT $ \ _ -> Fail.fail str #endif microlens-0.4.13.1/src/Lens/Micro/0000755000000000000000000000000007346545000014663 5ustar0000000000000000microlens-0.4.13.1/src/Lens/Micro/Extras.hs0000644000000000000000000000266407346545000016475 0ustar0000000000000000{-# LANGUAGE Trustworthy #-} {- | Module : Lens.Micro.Extras Copyright : (C) 2013-2016 Edward Kmett, 2015-2016 Artyom Kazak, 2018 Monadfix License : BSD-style (see the file LICENSE) -} module Lens.Micro.Extras ( view, preview, ) where import Lens.Micro import Lens.Micro.Internal import Control.Applicative import Data.Monoid {- | 'view' is a synonym for ('^.'): >>> view _1 (1, 2) 1 The reason it's not in "Lens.Micro" is that @view@ in lens has a more general signature: @ view :: MonadReader s m => Getting a s a -> m a @ So, you would be able to use this 'view' with functions, but not in various reader monads. For most people this shouldn't be an issue; if it is for you, use @view@ from . -} view :: Getting a s a -> s -> a view l = getConst #. l Const {-# INLINE view #-} {- | 'preview' is a synonym for ('^?'): >>> preview _head [1,2,3] Just 1 The reason it's not in "Lens.Micro" is that @preview@ in lens has a more general signature: @ preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a) @ Just like with 'view', you would be able to use this 'preview' with functions, but not in reader monads; if this is an issue for you, use @preview@ from . -} preview :: Getting (First a) s a -> s -> Maybe a preview l = getFirst #. foldMapOf l (First #. Just) {-# INLINE preview #-} microlens-0.4.13.1/src/Lens/Micro/Internal.hs0000644000000000000000000005115307346545000017000 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ImplicitParams #-} -- Note: this module is marked 'Unsafe' because it exports 'coerce', and Data.Coerce is marked 'Unsafe' in base. As per , this is an issue for 'lens' as well but they have opted for 'Trustworthy' instead. {-# LANGUAGE Unsafe #-} {- | Module : Lens.Micro.Internal Copyright : (C) 2013-2016 Edward Kmett, 2015-2016 Artyom Kazak, 2018 Monadfix License : BSD-style (see the file LICENSE) This module is needed to give other packages from the microlens family (like ) access to functions and classes that don't need to be exported from "Lens.Micro" (because they just clutter the namespace). Also: * 'traversed' is here because otherwise there'd be a dependency cycle * 'sets' is here because it's used in RULEs Classes like 'Each', 'Ixed', etc are provided for convenience – you're not supposed to export functions that work on all members of 'Ixed', for instance. Only microlens can do that. You mustn't declare instances of those classes for other types, either; these classes are incompatible with lens's classes, and by doing so you would divide the ecosystem. If you absolutely need to define an instance (e.g. for internal use), only do it for your own types, because otherwise I might add an instance to one of the microlens packages later and if our instances are different it might lead to subtle bugs. -} module Lens.Micro.Internal ( traversed, folded, foldring, foldrOf, foldMapOf, sets, phantom, Each(..), Index, IxValue, Ixed(..), At(..), ixAt, Field1(..), Field2(..), Field3(..), Field4(..), Field5(..), Cons(..), Snoc(..), Strict(..), -- * CallStack HasCallStack, -- * Coerce compatibility shim coerce, -- * Coerce-like composition ( #. ), ( .# ), ) where import Lens.Micro.Type import Control.Applicative import Data.Monoid import Data.Foldable as F import Data.Functor.Identity import Data.Complex #if __GLASGOW_HASKELL__ >= 800 import Data.List.NonEmpty (NonEmpty(..)) #endif #if __GLASGOW_HASKELL__ < 710 import Data.Traversable #endif #if __GLASGOW_HASKELL__ >= 708 import Data.Coerce #else import Unsafe.Coerce #endif -- We don't depend on the call-stack package because building an extra -- package is likely slower than adding several lines of code here. #if MIN_VERSION_base(4,9,0) import Data.Kind (Type) import GHC.Stack (HasCallStack) #elif MIN_VERSION_base(4,8,1) import qualified GHC.Stack as GHC type HasCallStack = (?callStack :: GHC.CallStack) #else import GHC.Exts (Constraint) type HasCallStack = (() :: Constraint) #endif {- | 'traversed' traverses any 'Traversable' container (list, vector, @Map@, 'Maybe', you name it): >>> Just 1 ^.. traversed [1] 'traversed' is the same as 'traverse', but can be faster thanks to magic rewrite rules. -} traversed :: Traversable f => Traversal (f a) (f b) a b traversed = traverse {-# INLINE [0] traversed #-} {-# RULES "traversed -> mapped" traversed = sets fmap :: Functor f => ASetter (f a) (f b) a b; "traversed -> folded" traversed = folded :: Foldable f => Getting (Endo r) (f a) a; #-} {- | 'folded' is a fold for anything 'Foldable'. In a way, it's an opposite of 'mapped' – the most powerful getter, but can't be used as a setter. -} folded :: Foldable f => SimpleFold (f a) a folded = foldring F.foldr {-# INLINE folded #-} foldring :: Monoid r => ((a -> Const r a -> Const r a) -> Const r a -> s -> Const r a) -> (a -> Const r b) -> s -> Const r t foldring fr f = phantom . fr (\a fa -> f a *> fa) noEffect {-# INLINE foldring #-} foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r foldrOf l f z = flip appEndo z . foldMapOf l (Endo #. f) {-# INLINE foldrOf #-} foldMapOf :: Getting r s a -> (a -> r) -> s -> r foldMapOf l f = getConst #. l (Const #. f) {-# INLINE foldMapOf #-} {- | 'sets' creates an 'ASetter' from an ordinary function. (The only thing it does is wrapping and unwrapping 'Identity'.) -} sets :: ((a -> b) -> s -> t) -> ASetter s t a b sets f g = Identity #. f (runIdentity #. g) {-# INLINE sets #-} ------------------------------------------------------------------------------ -- Control.Lens.Internal.Getter ------------------------------------------------------------------------------ -- was renamed from “coerce” phantom :: Const r a -> Const r b phantom = Const #. getConst {-# INLINE phantom #-} noEffect :: Monoid r => Const r a noEffect = phantom (pure ()) {-# INLINE noEffect #-} ------------------------------------------------------------------------------ -- classes ------------------------------------------------------------------------------ class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where {- | 'each' tries to be a universal 'Traversal' – it behaves like 'traversed' in most situations, but also adds support for e.g. tuples with same-typed values: >>> (1,2) & each %~ succ (2,3) >>> ["x", "y", "z"] ^. each "xyz" However, note that 'each' doesn't work on /every/ instance of 'Traversable'. If you have a 'Traversable' which isn't supported by 'each', you can use 'traversed' instead. Personally, I like using 'each' instead of 'traversed' whenever possible – it's shorter and more descriptive. You can use 'each' with these things: @ 'each' :: 'Traversal' [a] [b] a b 'each' :: 'Traversal' ('Maybe' a) ('Maybe' b) a b 'each' :: 'Traversal' ('Either' a a) ('Either' b b) a b -- since 0.4.11 'each' :: 'Traversal' (a,a) (b,b) a b 'each' :: 'Traversal' (a,a,a) (b,b,b) a b 'each' :: 'Traversal' (a,a,a,a) (b,b,b,b) a b 'each' :: 'Traversal' (a,a,a,a,a) (b,b,b,b,b) a b 'each' :: ('RealFloat' a, 'RealFloat' b) => 'Traversal' ('Complex' a) ('Complex' b) a b @ You can also use 'each' with types from , , and by using , or additionally with types from , , and by using . -} each :: Traversal s t a b instance (a~b, q~r) => Each (a,b) (q,r) a q where each f ~(a,b) = (,) <$> f a <*> f b {-# INLINE each #-} instance (a~b, a~c, q~r, q~s) => Each (a,b,c) (q,r,s) a q where each f ~(a,b,c) = (,,) <$> f a <*> f b <*> f c {-# INLINE each #-} instance (a~b, a~c, a~d, q~r, q~s, q~t) => Each (a,b,c,d) (q,r,s,t) a q where each f ~(a,b,c,d) = (,,,) <$> f a <*> f b <*> f c <*> f d {-# INLINE each #-} instance (a~b, a~c, a~d, a~e, q~r, q~s, q~t, q~u) => Each (a,b,c,d,e) (q,r,s,t,u) a q where each f ~(a,b,c,d,e) = (,,,,) <$> f a <*> f b <*> f c <*> f d <*> f e {-# INLINE each #-} instance Each (Complex a) (Complex b) a b where each f (a :+ b) = (:+) <$> f a <*> f b {-# INLINE each #-} instance Each [a] [b] a b where each = traversed {-# INLINE each #-} instance Each (Maybe a) (Maybe b) a b where each = traverse {-# INLINE each #-} {- | @since 0.4.11 -} instance (a~a', b~b') => Each (Either a a') (Either b b') a b where each f (Left a) = Left <$> f a each f (Right a ) = Right <$> f a {-# INLINE each #-} #if __GLASGOW_HASKELL__ >= 800 instance Each (NonEmpty a) (NonEmpty b) a b where each = traversed {-# INLINE each #-} #endif -- NOTE: when adding new instances of 'Each', update the docs for 'each'. #if MIN_VERSION_base(4,9,0) type family Index (s :: Type) :: Type type family IxValue (m :: Type) :: Type #else type family Index (s :: *) :: * type family IxValue (m :: *) :: * #endif type instance Index (e -> a) = e type instance IxValue (e -> a) = a type instance Index [a] = Int type instance IxValue [a] = a #if __GLASGOW_HASKELL__ >= 800 type instance Index (NonEmpty a) = Int type instance IxValue (NonEmpty a) = a #endif class Ixed m where {- | This traversal lets you access (and update) an arbitrary element in a list, array, @Map@, etc. (If you want to insert or delete elements as well, look at 'at'.) An example for lists: >>> [0..5] & ix 3 .~ 10 [0,1,2,10,4,5] You can use it for getting, too: >>> [0..5] ^? ix 3 Just 3 Of course, the element may not be present (which means that you can use 'ix' as a safe variant of ('!!')): >>> [0..5] ^? ix 10 Nothing Another useful instance is the one for functions – it lets you modify their outputs for specific inputs. For instance, here's 'maximum' that returns 0 when the list is empty (instead of throwing an exception): @ maximum0 = 'maximum' 'Lens.Micro.&' 'ix' [] 'Lens.Micro..~' 0 @ The following instances are provided in this package: #if __GLASGOW_HASKELL__ >= 800 @ 'ix' :: 'Int' -> 'Traversal'' [a] a 'ix' :: 'Int' -> 'Traversal'' (NonEmpty a) a 'ix' :: ('Eq' e) => e -> 'Traversal'' (e -> a) a @ #else @ 'ix' :: 'Int' -> 'Traversal'' [a] a 'ix' :: ('Eq' e) => e -> 'Traversal'' (e -> a) a @ #endif You can also use 'ix' with types from , , and by using , or additionally with types from , , and by using . -} ix :: Index m -> Traversal' m (IxValue m) class Ixed m => At m where {- | This lens lets you read, write, or delete elements in @Map@-like structures. It returns 'Nothing' when the value isn't found, just like @lookup@: @ Data.Map.lookup k m = m 'Lens.Micro.^.' at k @ However, it also lets you insert and delete values by setting the value to @'Just' value@ or 'Nothing': @ Data.Map.insert k a m = m 'Lens.Micro.&' at k 'Lens.Micro..~' Just a Data.Map.delete k m = m 'Lens.Micro.&' at k 'Lens.Micro..~' Nothing @ Or you could use ('Lens.Micro.?~') instead of ('Lens.Micro..~'): @ Data.Map.insert k a m = m 'Lens.Micro.&' at k 'Lens.Micro.?~' a @ Note that 'at' doesn't work for arrays or lists. You can't delete an arbitrary element from an array (what would be left in its place?), and you can't set an arbitrary element in a list because if the index is out of list's bounds, you'd have to somehow fill the stretch between the last element and the element you just inserted (i.e. @[1,2,3] & at 10 .~ 5@ is undefined). If you want to modify an already existing value in an array or list, you should use 'ix' instead. 'at' is often used with 'Lens.Micro.non'. See the documentation of 'Lens.Micro.non' for examples. Note that 'at' isn't strict for @Map@, even if you're using @Data.Map.Strict@: >>> Data.Map.Strict.size (Data.Map.Strict.empty & at 1 .~ Just undefined) 1 The reason for such behavior is that there's actually no “strict @Map@” type; @Data.Map.Strict@ just provides some strict functions for ordinary @Map@s. This package doesn't actually provide any instances for 'at', but there are instances for @Map@ and @IntMap@ in and an instance for @HashMap@ in . -} at :: Index m -> Lens' m (Maybe (IxValue m)) ixAt :: At m => Index m -> Traversal' m (IxValue m) ixAt i = at i . traverse {-# INLINE ixAt #-} instance Eq e => Ixed (e -> a) where ix e p f = (\a e' -> if e == e' then a else f e') <$> p (f e) {-# INLINE ix #-} instance Ixed [a] where ix k f xs0 | k < 0 = pure xs0 | otherwise = go xs0 k where go [] _ = pure [] go (a:as) 0 = (:as) <$> f a go (a:as) i = (a:) <$> (go as $! i - 1) {-# INLINE ix #-} #if __GLASGOW_HASKELL__ >= 800 instance Ixed (NonEmpty a) where ix k f xs0 | k < 0 = pure xs0 | otherwise = go xs0 k where go (a:|as) 0 = (:|as) <$> f a go (a:|as) i = (a:|) <$> ix (i - 1) f as {-# INLINE ix #-} #endif class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where {- | Gives access to the 1st field of a tuple (up to 5-tuples). Getting the 1st component: >>> (1,2,3,4,5) ^. _1 1 Setting the 1st component: >>> (1,2,3) & _1 .~ 10 (10,2,3) Note that this lens is lazy, and can set fields even of 'undefined': >>> set _1 10 undefined :: (Int, Int) (10,*** Exception: Prelude.undefined This is done to avoid violating a lens law stating that you can get back what you put: >>> view _1 . set _1 10 $ (undefined :: (Int, Int)) 10 The implementation (for 2-tuples) is: @ '_1' f t = (,) '<$>' f ('fst' t) '<*>' 'pure' ('snd' t) @ or, alternatively, @ '_1' f ~(a,b) = (\\a' -> (a',b)) '<$>' f a @ (where @~@ means a ). '_2', '_3', '_4', and '_5' are also available (see below). -} _1 :: Lens s t a b instance Field1 (a,b) (a',b) a a' where _1 k ~(a,b) = (\a' -> (a',b)) <$> k a {-# INLINE _1 #-} instance Field1 (a,b,c) (a',b,c) a a' where _1 k ~(a,b,c) = (\a' -> (a',b,c)) <$> k a {-# INLINE _1 #-} instance Field1 (a,b,c,d) (a',b,c,d) a a' where _1 k ~(a,b,c,d) = (\a' -> (a',b,c,d)) <$> k a {-# INLINE _1 #-} instance Field1 (a,b,c,d,e) (a',b,c,d,e) a a' where _1 k ~(a,b,c,d,e) = (\a' -> (a',b,c,d,e)) <$> k a {-# INLINE _1 #-} {- instance Field1 (a,b,c,d,e,f) (a',b,c,d,e,f) a a' where _1 k ~(a,b,c,d,e,f) = (\a' -> (a',b,c,d,e,f)) <$> k a {-# INLINE _1 #-} instance Field1 (a,b,c,d,e,f,g) (a',b,c,d,e,f,g) a a' where _1 k ~(a,b,c,d,e,f,g) = (\a' -> (a',b,c,d,e,f,g)) <$> k a {-# INLINE _1 #-} instance Field1 (a,b,c,d,e,f,g,h) (a',b,c,d,e,f,g,h) a a' where _1 k ~(a,b,c,d,e,f,g,h) = (\a' -> (a',b,c,d,e,f,g,h)) <$> k a {-# INLINE _1 #-} instance Field1 (a,b,c,d,e,f,g,h,i) (a',b,c,d,e,f,g,h,i) a a' where _1 k ~(a,b,c,d,e,f,g,h,i) = (\a' -> (a',b,c,d,e,f,g,h,i)) <$> k a {-# INLINE _1 #-} -} class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where _2 :: Lens s t a b instance Field2 (a,b) (a,b') b b' where _2 k ~(a,b) = (\b' -> (a,b')) <$> k b {-# INLINE _2 #-} instance Field2 (a,b,c) (a,b',c) b b' where _2 k ~(a,b,c) = (\b' -> (a,b',c)) <$> k b {-# INLINE _2 #-} instance Field2 (a,b,c,d) (a,b',c,d) b b' where _2 k ~(a,b,c,d) = (\b' -> (a,b',c,d)) <$> k b {-# INLINE _2 #-} instance Field2 (a,b,c,d,e) (a,b',c,d,e) b b' where _2 k ~(a,b,c,d,e) = (\b' -> (a,b',c,d,e)) <$> k b {-# INLINE _2 #-} {- instance Field2 (a,b,c,d,e,f) (a,b',c,d,e,f) b b' where _2 k ~(a,b,c,d,e,f) = (\b' -> (a,b',c,d,e,f)) <$> k b {-# INLINE _2 #-} instance Field2 (a,b,c,d,e,f,g) (a,b',c,d,e,f,g) b b' where _2 k ~(a,b,c,d,e,f,g) = (\b' -> (a,b',c,d,e,f,g)) <$> k b {-# INLINE _2 #-} instance Field2 (a,b,c,d,e,f,g,h) (a,b',c,d,e,f,g,h) b b' where _2 k ~(a,b,c,d,e,f,g,h) = (\b' -> (a,b',c,d,e,f,g,h)) <$> k b {-# INLINE _2 #-} instance Field2 (a,b,c,d,e,f,g,h,i) (a,b',c,d,e,f,g,h,i) b b' where _2 k ~(a,b,c,d,e,f,g,h,i) = (\b' -> (a,b',c,d,e,f,g,h,i)) <$> k b {-# INLINE _2 #-} -} class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where _3 :: Lens s t a b instance Field3 (a,b,c) (a,b,c') c c' where _3 k ~(a,b,c) = (\c' -> (a,b,c')) <$> k c {-# INLINE _3 #-} instance Field3 (a,b,c,d) (a,b,c',d) c c' where _3 k ~(a,b,c,d) = (\c' -> (a,b,c',d)) <$> k c {-# INLINE _3 #-} instance Field3 (a,b,c,d,e) (a,b,c',d,e) c c' where _3 k ~(a,b,c,d,e) = (\c' -> (a,b,c',d,e)) <$> k c {-# INLINE _3 #-} {- instance Field3 (a,b,c,d,e,f) (a,b,c',d,e,f) c c' where _3 k ~(a,b,c,d,e,f) = (\c' -> (a,b,c',d,e,f)) <$> k c {-# INLINE _3 #-} instance Field3 (a,b,c,d,e,f,g) (a,b,c',d,e,f,g) c c' where _3 k ~(a,b,c,d,e,f,g) = (\c' -> (a,b,c',d,e,f,g)) <$> k c {-# INLINE _3 #-} instance Field3 (a,b,c,d,e,f,g,h) (a,b,c',d,e,f,g,h) c c' where _3 k ~(a,b,c,d,e,f,g,h) = (\c' -> (a,b,c',d,e,f,g,h)) <$> k c {-# INLINE _3 #-} instance Field3 (a,b,c,d,e,f,g,h,i) (a,b,c',d,e,f,g,h,i) c c' where _3 k ~(a,b,c,d,e,f,g,h,i) = (\c' -> (a,b,c',d,e,f,g,h,i)) <$> k c {-# INLINE _3 #-} -} class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where _4 :: Lens s t a b instance Field4 (a,b,c,d) (a,b,c,d') d d' where _4 k ~(a,b,c,d) = (\d' -> (a,b,c,d')) <$> k d {-# INLINE _4 #-} instance Field4 (a,b,c,d,e) (a,b,c,d',e) d d' where _4 k ~(a,b,c,d,e) = (\d' -> (a,b,c,d',e)) <$> k d {-# INLINE _4 #-} {- instance Field4 (a,b,c,d,e,f) (a,b,c,d',e,f) d d' where _4 k ~(a,b,c,d,e,f) = (\d' -> (a,b,c,d',e,f)) <$> k d {-# INLINE _4 #-} instance Field4 (a,b,c,d,e,f,g) (a,b,c,d',e,f,g) d d' where _4 k ~(a,b,c,d,e,f,g) = (\d' -> (a,b,c,d',e,f,g)) <$> k d {-# INLINE _4 #-} instance Field4 (a,b,c,d,e,f,g,h) (a,b,c,d',e,f,g,h) d d' where _4 k ~(a,b,c,d,e,f,g,h) = (\d' -> (a,b,c,d',e,f,g,h)) <$> k d {-# INLINE _4 #-} instance Field4 (a,b,c,d,e,f,g,h,i) (a,b,c,d',e,f,g,h,i) d d' where _4 k ~(a,b,c,d,e,f,g,h,i) = (\d' -> (a,b,c,d',e,f,g,h,i)) <$> k d {-# INLINE _4 #-} -} class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where _5 :: Lens s t a b instance Field5 (a,b,c,d,e) (a,b,c,d,e') e e' where _5 k ~(a,b,c,d,e) = (\e' -> (a,b,c,d,e')) <$> k e {-# INLINE _5 #-} {- instance Field5 (a,b,c,d,e,f) (a,b,c,d,e',f) e e' where _5 k ~(a,b,c,d,e,f) = (\e' -> (a,b,c,d,e',f)) <$> k e {-# INLINE _5 #-} instance Field5 (a,b,c,d,e,f,g) (a,b,c,d,e',f,g) e e' where _5 k ~(a,b,c,d,e,f,g) = (\e' -> (a,b,c,d,e',f,g)) <$> k e {-# INLINE _5 #-} instance Field5 (a,b,c,d,e,f,g,h) (a,b,c,d,e',f,g,h) e e' where _5 k ~(a,b,c,d,e,f,g,h) = (\e' -> (a,b,c,d,e',f,g,h)) <$> k e {-# INLINE _5 #-} instance Field5 (a,b,c,d,e,f,g,h,i) (a,b,c,d,e',f,g,h,i) e e' where _5 k ~(a,b,c,d,e,f,g,h,i) = (\e' -> (a,b,c,d,e',f,g,h,i)) <$> k e {-# INLINE _5 #-} -} class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where _Cons :: Traversal s t (a,s) (b,t) instance Cons [a] [b] a b where _Cons f (a:as) = uncurry (:) <$> f (a, as) _Cons _ [] = pure [] {-# INLINE _Cons #-} class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where _Snoc :: Traversal s t (s,a) (t,b) instance Snoc [a] [b] a b where _Snoc _ [] = pure [] _Snoc f xs = (\(as,a) -> as ++ [a]) <$> f (init xs, last xs) {-# INLINE _Snoc #-} class Strict lazy strict | lazy -> strict, strict -> lazy where {- | 'strict' lets you convert between strict and lazy versions of a datatype: >>> let someText = "hello" :: Lazy.Text >>> someText ^. strict "hello" :: Strict.Text It can also be useful if you have a function that works on a strict type but your type is lazy: @ stripDiacritics :: Strict.Text -> Strict.Text stripDiacritics = ... @ >>> let someText = "Paul Erdős" :: Lazy.Text >>> someText & strict %~ stripDiacritics "Paul Erdos" :: Lazy.Text 'strict' works on @ByteString@ and @StateT@\/@WriterT@\/@RWST@ if you use , and additionally on @Text@ if you use . -} strict :: Lens' lazy strict {- | 'lazy' is like 'strict' but works in opposite direction: >>> let someText = "hello" :: Strict.Text >>> someText ^. lazy "hello" :: Lazy.Text -} lazy :: Lens' strict lazy ---------------------------------------------------------------------------- -- Coerce compatibility shim ---------------------------------------------------------------------------- #if __GLASGOW_HASKELL__ < 708 coerce :: a -> b coerce = unsafeCoerce {-# INLINE coerce #-} #endif ---------------------------------------------------------------------------- -- Coerce-like composition ---------------------------------------------------------------------------- -- Note: 'lens' defines a type-restricted version of (#.) to work around a -- bug, but our version is restricted enough that we don't need it. See -- #if __GLASGOW_HASKELL__ >= 708 ( #. ) :: Coercible c b => (b -> c) -> (a -> b) -> (a -> c) ( #. ) _ = coerce (\x -> x :: b) :: forall a b. Coercible b a => a -> b ( .# ) :: Coercible b a => (b -> c) -> (a -> b) -> (a -> c) ( .# ) pbc _ = coerce pbc #else ( #. ) :: (b -> c) -> (a -> b) -> (a -> c) ( #. ) _ = unsafeCoerce ( .# ) :: (b -> c) -> (a -> b) -> (a -> c) ( .# ) pbc _ = unsafeCoerce pbc #endif {-# INLINE ( #. ) #-} {-# INLINE ( .# ) #-} infixr 9 #. infixl 8 .# microlens-0.4.13.1/src/Lens/Micro/Type.hs0000644000000000000000000001767107346545000016154 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE Safe #-} {- | Module : Lens.Micro.Type Copyright : (C) 2013-2016 Edward Kmett, 2015-2016 Artyom Kazak, 2018 Monadfix License : BSD-style (see the file LICENSE) This module provides just the types ('Lens', 'Traversal', etc). It's needed to break the dependency cycle – "Lens.Micro" depends on "Lens.Micro.Internal", but "Lens.Micro.Internal" needs types like 'Lens', so 'Lens' can't be defined in "Lens.Micro". -} module Lens.Micro.Type ( ASetter, ASetter', SimpleGetter, Getting, SimpleFold, Lens, Lens', Traversal, Traversal', LensLike, LensLike', ) where import Control.Applicative import Data.Functor.Identity #if __GLASGOW_HASKELL__ < 710 import Data.Monoid #endif {- | @ASetter s t a b@ is something that turns a function modifying a value into a function modifying a /structure/. If you ignore 'Identity' (as @Identity a@ is the same thing as @a@), the type is: @ type ASetter s t a b = (a -> b) -> s -> t @ The reason 'Identity' is used here is for 'ASetter' to be composable with other types, such as 'Lens'. Technically, if you're writing a library, you shouldn't use this type for setters you are exporting from your library; the right type to use is @@, but it is not provided by this package (because then it'd have to depend on ). It's completely alright, however, to export functions which take an 'ASetter' as an argument. -} type ASetter s t a b = (a -> Identity b) -> s -> Identity t {- | This is a type alias for monomorphic setters which don't change the type of the container (or of the value inside). It's useful more often than the same type in lens, because we can't provide real setters and so it does the job of both @@ and @@. -} type ASetter' s a = ASetter s s a a {- | A @SimpleGetter s a@ extracts @a@ from @s@; so, it's the same thing as @(s -> a)@, but you can use it in lens chains because its type looks like this: @ type SimpleGetter s a = forall r. (a -> Const r a) -> s -> Const r s @ Since @Const r@ is a functor, 'SimpleGetter' has the same shape as other lens types and can be composed with them. To get @(s -> a)@ out of a 'SimpleGetter', choose @r ~ a@ and feed @Const :: a -> Const a a@ to the getter: @ -- the actual signature is more permissive: -- 'Lens.Micro.Extras.view' :: 'Getting' a s a -> s -> a 'Lens.Micro.Extras.view' :: 'SimpleGetter' s a -> s -> a 'Lens.Micro.Extras.view' getter = 'getConst' . getter 'Const' @ The actual @@ from lens is more general: @ type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s @ I'm not currently aware of any functions that take lens's @Getter@ but won't accept 'SimpleGetter', but you should try to avoid exporting 'SimpleGetter's anyway to minimise confusion. Alternatively, look at , which provides a fully lens-compatible @Getter@. Lens users: you can convert a 'SimpleGetter' to @Getter@ by applying @to . view@ to it. -} type SimpleGetter s a = forall r. Getting r s a {- | Functions that operate on getters and folds – such as ('Lens.Micro.^.'), ('Lens.Micro.^..'), ('Lens.Micro.^?') – use @Getter r s a@ (with different values of @r@) to describe what kind of result they need. For instance, ('Lens.Micro.^.') needs the getter to be able to return a single value, and so it accepts a getter of type @Getting a s a@. ('Lens.Micro.^..') wants the getter to gather values together, so it uses @Getting (Endo [a]) s a@ (it could've used @Getting [a] s a@ instead, but it's faster with 'Data.Monoid.Endo'). The choice of @r@ depends on what you want to do with elements you're extracting from @s@. -} type Getting r s a = (a -> Const r a) -> s -> Const r s {- | A @SimpleFold s a@ extracts several @a@s from @s@; so, it's pretty much the same thing as @(s -> [a])@, but you can use it with lens operators. The actual @Fold@ from lens is more general: @ type Fold s a = forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s @ There are several functions in lens that accept lens's @Fold@ but won't accept 'SimpleFold'; I'm aware of @@, @@, @@, @@, @@. For this reason, try not to export 'SimpleFold's if at all possible. provides a fully lens-compatible @Fold@. Lens users: you can convert a 'SimpleFold' to @Fold@ by applying @folded . toListOf@ to it. -} type SimpleFold s a = forall r. Monoid r => Getting r s a {- | @Lens s t a b@ is the lowest common denominator of a setter and a getter, something that has the power of both; it has a 'Functor' constraint, and since both 'Const' and 'Identity' are functors, it can be used whenever a getter or a setter is needed. * @a@ is the type of the value inside of structure * @b@ is the type of the replaced value * @s@ is the type of the whole structure * @t@ is the type of the structure after replacing @a@ in it with @b@ -} type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t {- | This is a type alias for monomorphic lenses which don't change the type of the container (or of the value inside). -} type Lens' s a = Lens s s a a {- | @Traversal s t a b@ is a generalisation of 'Lens' which allows many targets (possibly 0). It's achieved by changing the constraint to 'Applicative' instead of 'Functor' – indeed, the point of 'Applicative' is that you can combine effects, which is just what we need to have many targets. Ultimately, traversals should follow 2 laws: @ t pure ≡ pure fmap (t f) . t g ≡ getCompose . t (Compose . fmap f . g) @ The 1st law states that you can't change the shape of the structure or do anything funny with elements (traverse elements which aren't in the structure, create new elements out of thin air, etc.). The 2nd law states that you should be able to fuse 2 identical traversals into one. For a more detailed explanation of the laws, see (if you prefer rambling blog posts), or (if you prefer papers). Traversing any value twice is a violation of traversal laws. You can, however, traverse values in any order. -} type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t {- | This is a type alias for monomorphic traversals which don't change the type of the container (or of the values inside). -} type Traversal' s a = Traversal s s a a {- | 'LensLike' is a type that is often used to make combinators as general as possible. For instance, take ('Lens.Micro.<<%~'), which only requires the passed lens to be able to work with the @(,) a@ functor (lenses and traversals can do that). The fully expanded type is as follows: @ ('Lens.Micro.<<%~') :: ((a -> (a, b)) -> s -> (a, t)) -> (a -> b) -> s -> (a, t) @ With 'LensLike', the intent to use the @(,) a@ functor can be made a bit clearer: @ ('Lens.Micro.<<%~') :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t) @ -} type LensLike f s t a b = (a -> f b) -> s -> f t {- | A type alias for monomorphic 'LensLike's. -} type LensLike' f s a = LensLike f s s a a