-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Lenses, Folds and Traversals -- @package lens @version 4.13 -- | One of most commonly-asked questions about this package is whether it -- provides lenses for working with Map. It does, but their uses -- are perhaps obscured by their genericity. This module exists to -- provide documentation for them. -- -- Map is an instance of At, so we have a lenses on values -- at keys: -- --
-- >>> Map.fromList [(1, "world")] ^.at 1 -- Just "world" ---- --
-- >>> at 1 .~ Just "world" $ Map.empty -- fromList [(1,"world")] ---- --
-- >>> at 0 ?~ "hello" $ Map.empty -- fromList [(0,"hello")] ---- -- We can traverse, fold over, and map over key-value pairs in a -- Map, thanks to its TraversableWithIndex, -- FoldableWithIndex, and FunctorWithIndex instances. -- --
-- >>> imap const $ Map.fromList [(1, "Venus")] -- fromList [(1,1)] ---- --
-- >>> ifoldMap (\i _ -> Sum i) $ Map.fromList [(2, "Earth"), (3, "Mars")] -- Sum {getSum = 5} ---- --
-- >>> itraverse_ (curry print) $ Map.fromList [(4, "Jupiter")] -- (4,"Jupiter") ---- --
-- >>> itoList $ Map.fromList [(5, "Saturn")] -- [(5,"Saturn")] ---- -- A related class, Ixed, allows us to use ix to traverse a -- value at a particular key. -- --
-- >>> ix 2 %~ ("New " ++) $ Map.fromList [(2, "Earth")] -- fromList [(2,"New Earth")] ---- --
-- >>> preview (ix 8) $ Map.empty -- Nothing ---- -- Additionally, Map has TraverseMin and TraverseMax -- instances, which let us traverse over the value at the least and -- greatest keys, respectively. -- --
-- >>> preview traverseMin $ Map.fromList [(5, "Saturn"), (6, "Uranus")] -- Just "Saturn" ---- --
-- >>> preview traverseMax $ Map.fromList [(5, "Saturn"), (6, "Uranus")] -- Just "Uranus" --module Data.Map.Lens -- | This module provides utility functions on lists used by the library -- implementation. module Control.Lens.Internal.List -- | Return the the subset of given ordinals within a given bound and in -- order of the first occurrence seen. -- -- Bound: 0 <= x < l -- --
-- >>> ordinalNub 3 [-1,2,1,4,2,3] -- [2,1] --ordinalNub :: Int -> [Int] -> [Int] module Control.Lens.Internal.TH -- | Compatibility shim for recent changes to template haskell's -- tySynInstD tySynInstD' :: Name -> [TypeQ] -> TypeQ -> DecQ -- | Apply arguments to a type constructor appsT :: TypeQ -> [TypeQ] -> TypeQ -- | Apply arguments to a function appsE1 :: ExpQ -> [ExpQ] -> ExpQ -- | Construct a tuple type given a list of types. toTupleT :: [TypeQ] -> TypeQ -- | Construct a tuple value given a list of expressions. toTupleE :: [ExpQ] -> ExpQ -- | Construct a tuple pattern given a list of patterns. toTupleP :: [PatQ] -> PatQ -- | Apply arguments to a type constructor. conAppsT :: Name -> [Type] -> Type -- | Return Name contained in a TyVarBndr. bndrName :: TyVarBndr -> Name fromSet :: (k -> v) -> Set k -> Map k v lensPackageKey :: String mkLensName_tc :: String -> String -> Name mkLensName_v :: String -> String -> Name traversalTypeName :: Name traversal'TypeName :: Name lensTypeName :: Name lens'TypeName :: Name isoTypeName :: Name iso'TypeName :: Name getterTypeName :: Name foldTypeName :: Name prismTypeName :: Name prism'TypeName :: Name reviewTypeName :: Name wrappedTypeName :: Name unwrappedTypeName :: Name rewrappedTypeName :: Name _wrapped'ValName :: Name isoValName :: Name prismValName :: Name untoValName :: Name phantomValName :: Name phantom2 :: (Functor f, Contravariant f) => f a -> f b composeValName :: Name idValName :: Name fmapValName :: Name pureValName :: Name apValName :: Name rightDataName :: Name leftDataName :: Name -- | This module provides a shim around coerce that defaults to -- unsafeCoerce on GHC < 7.8 module Control.Lens.Internal.Coerce -- | The function coerce allows you to safely convert between -- values of types that have the same representation with no run-time -- overhead. In the simplest case you can use it instead of a newtype -- constructor, to go from the newtype's concrete type to the abstract -- type. But it also works in more complicated settings, e.g. converting -- a list of newtypes to a list of concrete types. coerce :: Coercible k a b => a -> b coerce' :: Coercible a b => b -> a -- | This module includes orphan instances for (,), Either -- and Const that should be supplied by base. These have moved -- to semigroupoids as of 4.2. module Control.Lens.Internal.Instances module Control.Lens.Internal.Zoom -- | This type family is used by Zoom to describe the common effect -- type. -- | Used by Zoom to zoom into StateT. newtype Focusing m s a Focusing :: m (s, a) -> Focusing m s a unfocusing :: Focusing m s a -> m (s, a) -- | Used by Zoom to zoom into RWST. newtype FocusingWith w m s a FocusingWith :: m (s, a, w) -> FocusingWith w m s a unfocusingWith :: FocusingWith w m s a -> m (s, a, w) -- | Used by Zoom to zoom into WriterT. newtype FocusingPlus w k s a FocusingPlus :: k (s, w) a -> FocusingPlus w k s a unfocusingPlus :: FocusingPlus w k s a -> k (s, w) a -- | Used by Zoom to zoom into MaybeT or ListT. newtype FocusingOn f k s a FocusingOn :: k (f s) a -> FocusingOn f k s a unfocusingOn :: FocusingOn f k s a -> k (f s) a -- | Used by Zoom to zoom into ErrorT. newtype FocusingMay k s a FocusingMay :: k (May s) a -> FocusingMay k s a unfocusingMay :: FocusingMay k s a -> k (May s) a -- | Make a Monoid out of Maybe for error handling. newtype May a May :: Maybe a -> May a getMay :: May a -> Maybe a -- | Used by Zoom to zoom into ErrorT. newtype FocusingErr e k s a FocusingErr :: k (Err e s) a -> FocusingErr e k s a unfocusingErr :: FocusingErr e k s a -> k (Err e s) a -- | Make a Monoid out of Either for error handling. newtype Err e a Err :: Either e a -> Err e a getErr :: Err e a -> Either e a -- | This type family is used by Magnify to describe the common -- effect type. -- | Wrap a monadic effect with a phantom type argument. newtype Effect m r a Effect :: m r -> Effect m r a getEffect :: Effect m r a -> m r -- | Wrap a monadic effect with a phantom type argument. Used when -- magnifying RWST. newtype EffectRWS w st m s a EffectRWS :: (st -> m (s, st, w)) -> EffectRWS w st m s a getEffectRWS :: EffectRWS w st m s a -> st -> m (s, st, w) instance [safe] Contravariant (EffectRWS w st m s) instance [safe] (Monoid s, Monoid w, Monad m) => Applicative (EffectRWS w st m s) instance [safe] (Semigroup s, Semigroup w, Bind m) => Apply (EffectRWS w st m s) instance [safe] Functor (EffectRWS w st m s) instance [safe] (Monad m, Monoid r) => Applicative (Effect m r) instance [safe] (Apply m, Semigroup r) => Apply (Effect m r) instance [safe] (Monad m, Monoid r) => Monoid (Effect m r a) instance [safe] (Apply m, Semigroup r) => Semigroup (Effect m r a) instance [safe] Contravariant (Effect m r) instance [safe] Functor (Effect m r) instance [safe] Applicative (k (Err e s)) => Applicative (FocusingErr e k s) instance [safe] Apply (k (Err e s)) => Apply (FocusingErr e k s) instance [safe] Functor (k (Err e s)) => Functor (FocusingErr e k s) instance [safe] Monoid a => Monoid (Err e a) instance [safe] Semigroup a => Semigroup (Err e a) instance [safe] Applicative (k (May s)) => Applicative (FocusingMay k s) instance [safe] Apply (k (May s)) => Apply (FocusingMay k s) instance [safe] Functor (k (May s)) => Functor (FocusingMay k s) instance [safe] Monoid a => Monoid (May a) instance [safe] Semigroup a => Semigroup (May a) instance [safe] Applicative (k (f s)) => Applicative (FocusingOn f k s) instance [safe] Apply (k (f s)) => Apply (FocusingOn f k s) instance [safe] Functor (k (f s)) => Functor (FocusingOn f k s) instance [safe] Applicative (k (s, w)) => Applicative (FocusingPlus w k s) instance [safe] Apply (k (s, w)) => Apply (FocusingPlus w k s) instance [safe] Functor (k (s, w)) => Functor (FocusingPlus w k s) instance [safe] (Monad m, Monoid s, Monoid w) => Applicative (FocusingWith w m s) instance [safe] (Monad m, Semigroup s, Semigroup w) => Apply (FocusingWith w m s) instance [safe] Monad m => Functor (FocusingWith w m s) instance [safe] (Monad m, Monoid s) => Applicative (Focusing m s) instance [safe] (Monad m, Semigroup s) => Apply (Focusing m s) instance [safe] Monad m => Functor (Focusing m s) module Control.Lens.Internal.Setter -- | Anything Settable must be isomorphic to the Identity -- Functor. class (Applicative f, Distributive f, Traversable f) => Settable f where untaintedDot g = g `seq` rmap untainted g taintedDot g = g `seq` rmap pure g untainted :: Settable f => f a -> a untaintedDot :: (Settable f, Profunctor p) => p a (f b) -> p a b taintedDot :: (Settable f, Profunctor p) => p a b -> p a (f b) instance (Settable f, Settable g) => Settable (Compose f g) instance Settable f => Settable (Backwards f) instance Settable Identity module Control.Lens.Internal.Review -- | This class is provided mostly for backwards compatibility with lens -- 3.8, but it can also shorten type signatures. class (Profunctor p, Bifunctor p) => Reviewable p -- | This is a profunctor used internally to implement Review -- -- It plays a role similar to that of Accessor or Const -- do for Control.Lens.Getter retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b instance (Profunctor p, Bifunctor p) => Reviewable p module Control.Lens.Internal.Prism -- | This type is used internally by the Prism code to provide -- efficient access to the two parts of a Prism. data Market a b s t Market :: (b -> t) -> (s -> Either t a) -> Market a b s t -- |
-- type Market' a s t = Market a a s t --type Market' a = Market a a instance Choice (Market a b) instance Profunctor (Market a b) instance Functor (Market a b s) module Control.Lens.Internal.Iso -- | This is used internally by the Iso code to provide efficient -- access to the two functions that make up an isomorphism. data Exchange a b s t Exchange :: (s -> a) -> (b -> t) -> Exchange a b s t -- | This class provides a generalized notion of list reversal extended to -- other containers. class Reversing t reversing :: Reversing t => t -> t instance Storable a => Reversing (Vector a) instance Unbox a => Reversing (Vector a) instance Prim a => Reversing (Vector a) instance Reversing (Seq a) instance Reversing (Vector a) instance Reversing Text instance Reversing Text instance Reversing ByteString instance Reversing ByteString instance Reversing [a] instance Profunctor (Exchange a b) instance Functor (Exchange a b s) -- | This module provides implementation details of the combinators in -- Control.Lens.Level, which provides for the breadth-first -- Traversal of an arbitrary Traversal. module Control.Lens.Internal.Level -- | This data type represents a path-compressed copy of one level of a -- source data structure. We can safely use path-compression because we -- know the depth of the tree. -- -- Path compression is performed by viewing a Level as a PATRICIA -- trie of the paths into the structure to leaves at a given depth, -- similar in many ways to a IntMap, but unlike a regular PATRICIA -- trie we do not need to store the mask bits merely the depth of the -- fork. -- -- One invariant of this structure is that underneath a Two node -- you will not find any Zero nodes, so Zero can only occur -- at the root. data Level i a Two :: {-# UNPACK #-} !Word -> !(Level i a) -> !(Level i a) -> Level i a One :: i -> a -> Level i a Zero :: Level i a -- | This is an illegal Monoid used to construct a single -- Level. newtype Deepening i a Deepening :: (forall r. Int -> (Level i a -> Bool -> r) -> r) -> Deepening i a runDeepening :: Deepening i a -> forall r. Int -> (Level i a -> Bool -> r) -> r -- | Generate the leaf of a given Deepening based on whether or not -- we're at the correct depth. deepening :: i -> a -> Deepening i a -- | This is an illegal Applicative used to replace the contents of -- a list of consecutive Level values representing each layer of a -- structure into the original shape that they were derived from. -- -- Attempting to Flow something back into a shape other than the -- one it was taken from will fail. newtype Flows i b a Flows :: ([Level i b] -> a) -> Flows i b a runFlows :: Flows i b a -> [Level i b] -> a instance (Eq i, Eq a) => Eq (Level i a) instance (Ord i, Ord a) => Ord (Level i a) instance (Show i, Show a) => Show (Level i a) instance (Read i, Read a) => Read (Level i a) instance Applicative (Flows i b) instance Apply (Flows i b) instance Functor (Flows i b) instance Monoid (Deepening i a) instance Semigroup (Deepening i a) instance Traversable (Level i) instance Foldable (Level i) instance Functor (Level i) -- | Internal implementation details for Indexed lens-likes module Control.Lens.Internal.Indexed -- | A function with access to a index. This constructor may be useful when -- you need to store an Indexable in a container to avoid -- ImpredicativeTypes. -- --
-- index :: Indexed i a b -> i -> a -> b --newtype Indexed i a b Indexed :: (i -> a -> b) -> Indexed i a b runIndexed :: Indexed i a b -> i -> a -> b -- | This is a Profunctor that is both Corepresentable by -- f and Representable by g such that f -- is left adjoint to g. From this you can derive a lot of -- structure due to the preservation of limits and colimits. class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p) => Conjoined p where distrib = tabulate . collect . sieve conjoined _ r = r distrib :: (Conjoined p, Functor f) => p a b -> p (f a) (f b) conjoined :: Conjoined p => (p ~ (->) => q (a -> b) r) -> q (p a b) r -> q (p a b) r -- | This class permits overloading of function application for things that -- also admit a notion of a key or index. class Conjoined p => Indexable i p indexed :: Indexable i p => p a b -> i -> a -> b -- | Applicative composition of State Int -- with a Functor, used by indexed. newtype Indexing f a Indexing :: (Int -> (Int, f a)) -> Indexing f a runIndexing :: Indexing f a -> Int -> (Int, f a) -- | Transform a Traversal into an IndexedTraversal or a -- Fold into an IndexedFold, etc. -- --
-- indexing :: Traversal s t a b -> IndexedTraversal Int s t a b -- indexing :: Prism s t a b -> IndexedTraversal Int s t a b -- indexing :: Lens s t a b -> IndexedLens Int s t a b -- indexing :: Iso s t a b -> IndexedLens Int s t a b -- indexing :: Fold s a -> IndexedFold Int s a -- indexing :: Getter s a -> IndexedGetter Int s a ---- --
-- indexing :: Indexable Int p => LensLike (Indexing f) s t a b -> Over p f s t a b --indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t -- | Applicative composition of State Int64 -- with a Functor, used by indexed64. newtype Indexing64 f a Indexing64 :: (Int64 -> (Int64, f a)) -> Indexing64 f a runIndexing64 :: Indexing64 f a -> Int64 -> (Int64, f a) -- | Transform a Traversal into an IndexedTraversal or a -- Fold into an IndexedFold, etc. -- -- This combinator is like indexing except that it handles large -- traversals and folds gracefully. -- --
-- indexing64 :: Traversal s t a b -> IndexedTraversal Int64 s t a b -- indexing64 :: Prism s t a b -> IndexedTraversal Int64 s t a b -- indexing64 :: Lens s t a b -> IndexedLens Int64 s t a b -- indexing64 :: Iso s t a b -> IndexedLens Int64 s t a b -- indexing64 :: Fold s a -> IndexedFold Int64 s a -- indexing64 :: Getter s a -> IndexedGetter Int64 s a ---- --
-- indexing64 :: Indexable Int64 p => LensLike (Indexing64 f) s t a b -> Over p f s t a b --indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f t -- | Fold a container with indices returning both the indices and the -- values. -- -- The result is only valid to compose in a Traversal, if you -- don't edit the index as edits to the index have no effect. withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t) -- | When composed with an IndexedFold or -- IndexedTraversal this yields an (Indexed) -- Fold of the indices. asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s) instance Contravariant f => Contravariant (Indexing64 f) instance Applicative f => Applicative (Indexing64 f) instance Apply f => Apply (Indexing64 f) instance Functor f => Functor (Indexing64 f) instance Contravariant f => Contravariant (Indexing f) instance Applicative f => Applicative (Indexing f) instance Apply f => Apply (Indexing f) instance Functor f => Functor (Indexing f) instance i ~ j => Indexable i (Indexed j) instance Conjoined (Indexed i) instance ArrowLoop (Indexed i) instance ArrowApply (Indexed i) instance ArrowChoice (Indexed i) instance Arrow (Indexed i) instance Category (Indexed i) instance Strong (Indexed i) instance Choice (Indexed i) instance Corepresentable (Indexed i) instance Cosieve (Indexed i) ((,) i) instance Representable (Indexed i) instance Sieve (Indexed i) ((->) i) instance Costrong (Indexed i) instance Profunctor (Indexed i) instance MonadFix (Indexed i a) instance Monad (Indexed i a) instance Bind (Indexed i a) instance Applicative (Indexed i a) instance Apply (Indexed i a) instance Functor (Indexed i a) instance Indexable i (->) instance Conjoined (->) module Control.Lens.Internal.Context -- | This is a Bob Atkey -style 2-argument indexed functor. -- -- It exists as a superclass for IndexedComonad and expresses the -- functoriality of an IndexedComonad in its third argument. class IndexedFunctor w ifmap :: IndexedFunctor w => (s -> t) -> w a b s -> w a b t -- | This is a Bob Atkey -style 2-argument indexed comonad. -- -- It exists as a superclass for IndexedComonad and expresses the -- functoriality of an IndexedComonad in its third argument. -- -- The notion of indexed monads is covered in more depth in Bob Atkey's -- "Parameterized Notions of Computation" -- http://bentnib.org/paramnotions-jfp.pdf and that construction -- is dualized here. class IndexedFunctor w => IndexedComonad w where iduplicate = iextend id iextend f = ifmap f . iduplicate iextract :: IndexedComonad w => w a a t -> t iduplicate :: IndexedComonad w => w a c t -> w a b (w b c t) iextend :: IndexedComonad w => (w b c t -> r) -> w a c t -> w a b r -- | This is an indexed analogue to ComonadStore for when you are -- working with an IndexedComonad. class IndexedComonad w => IndexedComonadStore w where ipeek c = iextract . iseek c ipeeks f = iextract . iseeks f iexperiment bfc wbct = (`ipeek` wbct) <$> bfc (ipos wbct) context wabt = Context (`ipeek` wabt) (ipos wabt) ipos :: IndexedComonadStore w => w a c t -> a ipeek :: IndexedComonadStore w => c -> w a c t -> t ipeeks :: IndexedComonadStore w => (a -> c) -> w a c t -> t iseek :: IndexedComonadStore w => b -> w a c t -> w b c t iseeks :: IndexedComonadStore w => (a -> b) -> w a c t -> w b c t iexperiment :: (IndexedComonadStore w, Functor f) => (b -> f c) -> w b c t -> f t context :: IndexedComonadStore w => w a b t -> Context a b t -- | This is used internally to construct a Bazaar, Context -- or Pretext from a singleton value. class Corepresentable p => Sellable p w | w -> p sell :: Sellable p w => p a (w a b b) -- | The indexed store can be used to characterize a Lens and is -- used by clone. -- -- Context a b t is isomorphic to newtype -- Context a b t = Context { runContext :: forall f. -- Functor f => (a -> f b) -> f t }, and to -- exists s. (s, Lens s t a b). -- -- A Context is like a Lens that has already been applied -- to a some structure. data Context a b t Context :: (b -> t) -> a -> Context a b t -- |
-- type Context' a s = Context a a s --type Context' a = Context a a -- | This is a generalized form of Context that can be repeatedly -- cloned with less impact on its performance, and which permits the use -- of an arbitrary Conjoined Profunctor newtype Pretext p a b t Pretext :: (forall f. Functor f => p a (f b) -> f t) -> Pretext p a b t runPretext :: Pretext p a b t -> forall f. Functor f => p a (f b) -> f t -- |
-- type Pretext' p a s = Pretext p a a s --type Pretext' p a = Pretext p a a -- | This is a generalized form of Context that can be repeatedly -- cloned with less impact on its performance, and which permits the use -- of an arbitrary Conjoined Profunctor. -- -- The extra phantom Functor is used to let us lie and claim -- Getter-compatibility under limited circumstances. This is used -- internally to permit a number of combinators to gracefully degrade -- when applied to a Fold or Getter. newtype PretextT p (g :: * -> *) a b t PretextT :: (forall f. Functor f => p a (f b) -> f t) -> PretextT p a b t runPretextT :: PretextT p a b t -> forall f. Functor f => p a (f b) -> f t -- |
-- type PretextT' p g a s = PretextT p g a a s --type PretextT' p g a = PretextT p g a a instance (Profunctor p, Contravariant g) => Contravariant (PretextT p g a b) instance Corepresentable p => Sellable p (PretextT p g) instance (a ~ b, Conjoined p) => ComonadStore a (PretextT p g a b) instance Conjoined p => IndexedComonadStore (PretextT p g) instance (a ~ b, Conjoined p) => Comonad (PretextT p g a b) instance Conjoined p => IndexedComonad (PretextT p g) instance Functor (PretextT p g a b) instance IndexedFunctor (PretextT p g) instance Corepresentable p => Sellable p (Pretext p) instance (a ~ b, Conjoined p) => ComonadStore a (Pretext p a b) instance Conjoined p => IndexedComonadStore (Pretext p) instance (a ~ b, Conjoined p) => Comonad (Pretext p a b) instance Conjoined p => IndexedComonad (Pretext p) instance Functor (Pretext p a b) instance IndexedFunctor (Pretext p) instance Sellable (->) Context instance a ~ b => ComonadStore a (Context a b) instance a ~ b => Comonad (Context a b) instance Functor (Context a b) instance IndexedComonadStore Context instance IndexedComonad Context instance IndexedFunctor Context module Control.Lens.Internal.Bazaar -- | This class is used to run the various Bazaar variants used in -- this library. class Profunctor p => Bizarre p w | w -> p bazaar :: (Bizarre p w, Applicative f) => p a (f b) -> w a b t -> f t -- | This is used to characterize a Traversal. -- -- a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, -- or an indexed FunList. -- -- http://twanvl.nl/blog/haskell/non-regular1 -- -- A Bazaar is like a Traversal that has already been -- applied to some structure. -- -- Where a Context a b t holds an a and a -- function from b to t, a Bazaar a b t -- holds N as and a function from N -- bs to t, (where N might be infinite). -- -- Mnemonically, a Bazaar holds many stores and you can easily add -- more. -- -- This is a final encoding of Bazaar. newtype Bazaar p a b t Bazaar :: (forall f. Applicative f => p a (f b) -> f t) -> Bazaar p a b t runBazaar :: Bazaar p a b t -> forall f. Applicative f => p a (f b) -> f t -- | This alias is helpful when it comes to reducing repetition in type -- signatures. -- --
-- type Bazaar' p a t = Bazaar p a a t --type Bazaar' p a = Bazaar p a a -- | BazaarT is like Bazaar, except that it provides a -- questionable Contravariant instance To protect this instance it -- relies on the soundness of another Contravariant type, and -- usage conventions. -- -- For example. This lets us write a suitably polymorphic and lazy -- taking, but there must be a better way! newtype BazaarT p (g :: * -> *) a b t BazaarT :: (forall f. Applicative f => p a (f b) -> f t) -> BazaarT p a b t runBazaarT :: BazaarT p a b t -> forall f. Applicative f => p a (f b) -> f t -- | This alias is helpful when it comes to reducing repetition in type -- signatures. -- --
-- type BazaarT' p g a t = BazaarT p g a a t --type BazaarT' p g a = BazaarT p g a a class Profunctor p => Bizarre1 p w | w -> p bazaar1 :: (Bizarre1 p w, Apply f) => p a (f b) -> w a b t -> f t -- | This is used to characterize a Traversal. -- -- a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, -- or an indexed FunList. -- -- http://twanvl.nl/blog/haskell/non-regular1 -- -- A Bazaar1 is like a Traversal that has already been -- applied to some structure. -- -- Where a Context a b t holds an a and a -- function from b to t, a Bazaar1 a b -- t holds N as and a function from N -- bs to t, (where N might be infinite). -- -- Mnemonically, a Bazaar1 holds many stores and you can easily -- add more. -- -- This is a final encoding of Bazaar1. newtype Bazaar1 p a b t Bazaar1 :: (forall f. Apply f => p a (f b) -> f t) -> Bazaar1 p a b t runBazaar1 :: Bazaar1 p a b t -> forall f. Apply f => p a (f b) -> f t -- | This alias is helpful when it comes to reducing repetition in type -- signatures. -- --
-- type Bazaar1' p a t = Bazaar1 p a a t --type Bazaar1' p a = Bazaar1 p a a -- | BazaarT1 is like Bazaar1, except that it provides a -- questionable Contravariant instance To protect this instance it -- relies on the soundness of another Contravariant type, and -- usage conventions. -- -- For example. This lets us write a suitably polymorphic and lazy -- taking, but there must be a better way! newtype BazaarT1 p (g :: * -> *) a b t BazaarT1 :: (forall f. Apply f => p a (f b) -> f t) -> BazaarT1 p a b t runBazaarT1 :: BazaarT1 p a b t -> forall f. Apply f => p a (f b) -> f t -- | This alias is helpful when it comes to reducing repetition in type -- signatures. -- --
-- type BazaarT1' p g a t = BazaarT1 p g a a t --type BazaarT1' p g a = BazaarT1 p g a a instance Contravariant g => Semigroup (BazaarT1 p g a b t) instance (Profunctor p, Contravariant g) => Contravariant (BazaarT1 p g a b) instance (a ~ b, Conjoined p) => ComonadApply (BazaarT1 p g a b) instance (a ~ b, Conjoined p) => Comonad (BazaarT1 p g a b) instance Apply (BazaarT1 p g a b) instance Functor (BazaarT1 p g a b) instance Profunctor p => Bizarre1 p (BazaarT1 p g) instance Corepresentable p => Sellable p (BazaarT1 p g) instance Conjoined p => IndexedComonad (BazaarT1 p g) instance IndexedFunctor (BazaarT1 p g) instance (a ~ b, Conjoined p) => ComonadApply (Bazaar1 p a b) instance (a ~ b, Conjoined p) => Comonad (Bazaar1 p a b) instance Apply (Bazaar1 p a b) instance Functor (Bazaar1 p a b) instance Profunctor p => Bizarre1 p (Bazaar1 p) instance Corepresentable p => Sellable p (Bazaar1 p) instance Conjoined p => IndexedComonad (Bazaar1 p) instance IndexedFunctor (Bazaar1 p) instance Contravariant g => Monoid (BazaarT p g a b t) instance Contravariant g => Semigroup (BazaarT p g a b t) instance (Profunctor p, Contravariant g) => Contravariant (BazaarT p g a b) instance (a ~ b, Conjoined p) => ComonadApply (BazaarT p g a b) instance (a ~ b, Conjoined p) => Comonad (BazaarT p g a b) instance Applicative (BazaarT p g a b) instance Apply (BazaarT p g a b) instance Functor (BazaarT p g a b) instance Profunctor p => Bizarre p (BazaarT p g) instance Corepresentable p => Sellable p (BazaarT p g) instance Conjoined p => IndexedComonad (BazaarT p g) instance IndexedFunctor (BazaarT p g) instance (a ~ b, Conjoined p) => ComonadApply (Bazaar p a b) instance (a ~ b, Conjoined p) => Comonad (Bazaar p a b) instance Applicative (Bazaar p a b) instance Apply (Bazaar p a b) instance Functor (Bazaar p a b) instance Profunctor p => Bizarre p (Bazaar p) instance Corepresentable p => Sellable p (Bazaar p) instance Conjoined p => IndexedComonad (Bazaar p) instance IndexedFunctor (Bazaar p) module Control.Lens.Internal.Magma -- | This provides a way to peek at the internal structure of a -- Traversal or IndexedTraversal data Magma i t b a MagmaAp :: Magma i (x -> y) b a -> Magma i x b a -> Magma i y b a MagmaPure :: x -> Magma i x b a MagmaFmap :: (x -> y) -> Magma i x b a -> Magma i y b a Magma :: i -> a -> Magma i b b a -- | Run a Magma where all the individual leaves have been converted -- to the expected type runMagma :: Magma i t a a -> t -- | This is a a non-reassociating initially encoded version of -- Bazaar. newtype Molten i a b t Molten :: Magma i t b a -> Molten i a b t runMolten :: Molten i a b t -> Magma i t b a -- | This is used to generate an indexed magma from an unindexed source -- -- By constructing it this way we avoid infinite reassociations in sums -- where possible. data Mafic a b t Mafic :: Int -> (Int -> Magma Int t b a) -> Mafic a b t -- | Generate a Magma using from a prefix sum. runMafic :: Mafic a b t -> Magma Int t b a -- | This is used to generate an indexed magma from an unindexed source -- -- By constructing it this way we avoid infinite reassociations where -- possible. -- -- In TakingWhile p g a b t, g has a -- nominal role to avoid exposing an illegal _|_ via -- Contravariant, while the remaining arguments are degraded to a -- nominal role by the invariants of Magma data TakingWhile p (g :: * -> *) a b t TakingWhile :: Bool -> t -> (Bool -> Magma () t b (Corep p a)) -> TakingWhile p a b t -- | Generate a Magma with leaves only while the predicate holds -- from left to right. runTakingWhile :: TakingWhile p f a b t -> Magma () t b (Corep p a) instance IndexedFunctor (TakingWhile p f) instance Contravariant f => Contravariant (TakingWhile p f a b) instance Corepresentable p => Bizarre p (TakingWhile p g) instance Applicative (TakingWhile p f a b) instance Apply (TakingWhile p f a b) instance Functor (TakingWhile p f a b) instance IndexedFunctor Mafic instance Bizarre (Indexed Int) Mafic instance Sellable (->) Mafic instance Applicative (Mafic a b) instance Apply (Mafic a b) instance Functor (Mafic a b) instance a ~ b => Comonad (Molten i a b) instance IndexedComonad (Molten i) instance IndexedFunctor (Molten i) instance Bizarre (Indexed i) (Molten i) instance Sellable (Indexed i) (Molten i) instance Applicative (Molten i a b) instance Apply (Molten i a b) instance Functor (Molten i a b) instance (Show i, Show a) => Show (Magma i t b a) instance Traversable (Magma i t b) instance Foldable (Magma i t b) instance Functor (Magma i t b) module Control.Lens.Internal.Getter -- | The mempty equivalent for a Contravariant -- Applicative Functor. noEffect :: (Contravariant f, Applicative f) => f a newtype AlongsideLeft f b a AlongsideLeft :: f (a, b) -> AlongsideLeft f b a getAlongsideLeft :: AlongsideLeft f b a -> f (a, b) newtype AlongsideRight f a b AlongsideRight :: f (a, b) -> AlongsideRight f a b getAlongsideRight :: AlongsideRight f a b -> f (a, b) instance Read (f (a, b)) => Read (AlongsideRight f a b) instance Show (f (a, b)) => Show (AlongsideRight f a b) instance Read (f (a, b)) => Read (AlongsideLeft f b a) instance Show (f (a, b)) => Show (AlongsideLeft f b a) instance Traversable f => Bitraversable (AlongsideRight f) instance Foldable f => Bifoldable (AlongsideRight f) instance Functor f => Bifunctor (AlongsideRight f) instance Traversable1 f => Traversable1 (AlongsideRight f a) instance Foldable1 f => Foldable1 (AlongsideRight f a) instance Traversable f => Traversable (AlongsideRight f a) instance Foldable f => Foldable (AlongsideRight f a) instance Contravariant f => Contravariant (AlongsideRight f a) instance Functor f => Functor (AlongsideRight f a) instance Traversable f => Bitraversable (AlongsideLeft f) instance Foldable f => Bifoldable (AlongsideLeft f) instance Functor f => Bifunctor (AlongsideLeft f) instance Traversable1 f => Traversable1 (AlongsideLeft f b) instance Foldable1 f => Foldable1 (AlongsideLeft f b) instance Traversable f => Traversable (AlongsideLeft f b) instance Foldable f => Foldable (AlongsideLeft f b) instance Contravariant f => Contravariant (AlongsideLeft f b) instance Functor f => Functor (AlongsideLeft f b) module Control.Lens.Internal.Fold -- | A Monoid for a Contravariant Applicative. newtype Folding f a Folding :: f a -> Folding f a getFolding :: Folding f a -> f a -- | Used internally by traverseOf_ and the like. -- -- The argument a of the result should not be used! newtype Traversed a f Traversed :: f a -> Traversed a f getTraversed :: Traversed a f -> f a -- | Used internally by mapM_ and the like. -- -- The argument a of the result should not be used! newtype Sequenced a m Sequenced :: m a -> Sequenced a m getSequenced :: Sequenced a m -> m a -- | Used for maximumOf. data Max a NoMax :: Max a Max :: a -> Max a -- | Obtain the maximum. getMax :: Max a -> Maybe a -- | Used for minimumOf. data Min a NoMin :: Min a Min :: a -> Min a -- | Obtain the minimum. getMin :: Min a -> Maybe a -- | Used for preview. data Leftmost a LPure :: Leftmost a LLeaf :: a -> Leftmost a LStep :: (Leftmost a) -> Leftmost a -- | Extract the Leftmost element. This will fairly eagerly -- determine that it can return Just the moment it sees any -- element at all. getLeftmost :: Leftmost a -> Maybe a -- | Used for lastOf. data Rightmost a RPure :: Rightmost a RLeaf :: a -> Rightmost a RStep :: (Rightmost a) -> Rightmost a -- | Extract the Rightmost element. This will fairly eagerly -- determine that it can return Just the moment it sees any -- element at all. getRightmost :: Rightmost a -> Maybe a data ReifiedMonoid a :: * -> * ReifiedMonoid :: (a -> a -> a) -> a -> ReifiedMonoid a reifiedMappend :: ReifiedMonoid a -> a -> a -> a reifiedMempty :: ReifiedMonoid a -> a instance Monoid (Rightmost a) instance Semigroup (Rightmost a) instance Monoid (Leftmost a) instance Semigroup (Leftmost a) instance Ord a => Monoid (Max a) instance Ord a => Semigroup (Max a) instance Ord a => Monoid (Min a) instance Ord a => Semigroup (Min a) instance Monad m => Monoid (Sequenced a m) instance Apply m => Semigroup (Sequenced a m) instance Applicative f => Monoid (Traversed a f) instance Apply f => Semigroup (Traversed a f) instance (Contravariant f, Applicative f) => Monoid (Folding f a) instance (Contravariant f, Apply f) => Semigroup (Folding f a) -- | This module exports the majority of the types that need to appear in -- user signatures or in documentation when talking about lenses. The -- remaining types for consuming lenses are distributed across various -- modules in the hierarchy. module Control.Lens.Type -- | A witness that (a ~ s, b ~ t). -- -- Note: Composition with an Equality is index-preserving. type Equality s t a b = forall p (f :: * -> *). p a (f b) -> p s (f t) -- | A Simple Equality. type Equality' s a = Equality s s a a -- | Composable asTypeOf. Useful for constraining excess -- polymorphism, foo . (id :: As Int) . bar. type As a = Equality' a a -- | Isomorphism families can be composed with another Lens using -- (.) and id. -- -- Note: Composition with an Iso is index- and measure- -- preserving. type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t) -- |
-- type Iso' = Simple Iso --type Iso' s a = Iso s s a a -- | A Prism l is a Traversal that can also be -- turned around with re to obtain a Getter in the opposite -- direction. -- -- There are two laws that a Prism should satisfy: -- -- First, if I re or review a value with a Prism and -- then preview or use (^?), I will get it back: -- --
-- preview l (review l b) ≡ Just b ---- -- Second, if you can extract a value a using a Prism -- l from a value s, then the value s is -- completely described by l and a: -- -- If preview l s ≡ Just a then -- review l a ≡ s -- -- These two laws imply that the Traversal laws hold for every -- Prism and that we traverse at most 1 element: -- --
-- lengthOf l x <= 1 ---- -- It may help to think of this as a Iso that can be partial in -- one direction. -- -- Every Prism is a valid Traversal. -- -- Every Iso is a valid Prism. -- -- For example, you might have a Prism' Integer -- Natural allows you to always go from a Natural to -- an Integer, and provide you with tools to check if an -- Integer is a Natural and/or to edit one if it is. -- --
-- nat :: Prism' Integer Natural -- nat = prism toInteger $ \ i -> -- if i < 0 -- then Left i -- else Right (fromInteger i) ---- -- Now we can ask if an Integer is a Natural. -- --
-- >>> 5^?nat -- Just 5 ---- --
-- >>> (-5)^?nat -- Nothing ---- -- We can update the ones that are: -- --
-- >>> (-3,4) & both.nat *~ 2 -- (-3,8) ---- -- And we can then convert from a Natural to an Integer. -- --
-- >>> 5 ^. re nat -- :: Natural -- 5 ---- -- Similarly we can use a Prism to traverse the -- Left half of an Either: -- --
-- >>> Left "hello" & _Left %~ length -- Left 5 ---- -- or to construct an Either: -- --
-- >>> 5^.re _Left -- Left 5 ---- -- such that if you query it with the Prism, you will get your -- original input back. -- --
-- >>> 5^.re _Left ^? _Left -- Just 5 ---- -- Another interesting way to think of a Prism is as the -- categorical dual of a Lens -- a co-Lens, so to speak. -- This is what permits the construction of outside. -- -- Note: Composition with a Prism is index-preserving. type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t) -- | A Simple Prism. type Prism' s a = Prism s s a a -- | This is a limited form of a Prism that can only be used for -- re operations. -- -- Like with a Getter, there are no laws to state for a -- Review. -- -- You can generate a Review by using unto. You can also -- use any Prism or Iso directly as a Review. type Review t b = forall p f. (Choice p, Bifunctor p, Settable f) => Optic' p f t b -- | If you see this in a signature for a function, the function is -- expecting a Review (in practice, this usually means a -- Prism). type AReview t b = Optic' Tagged Identity t b -- | A Lens is actually a lens family as described in -- http://comonad.com/reader/2012/mirrored-lenses/. -- -- With great power comes great responsibility and a Lens is -- subject to the three common sense Lens laws: -- -- 1) You get back what you put in: -- --
-- view l (set l v s) ≡ v ---- -- 2) Putting back what you got doesn't change anything: -- --
-- set l (view l s) s ≡ s ---- -- 3) Setting twice is the same as setting once: -- --
-- set l v' (set l v s) ≡ set l v' s ---- -- These laws are strong enough that the 4 type parameters of a -- Lens cannot vary fully independently. For more on how they -- interact, read the "Why is it a Lens Family?" section of -- http://comonad.com/reader/2012/mirrored-lenses/. -- -- There are some emergent properties of these laws: -- -- 1) set l s must be injective for every s This -- is a consequence of law #1 -- -- 2) set l must be surjective, because of law #2, which -- indicates that it is possible to obtain any v from some -- s such that set s v = s -- -- 3) Given just the first two laws you can prove a weaker form of law #3 -- where the values v that you are setting match: -- --
-- set l v (set l v s) ≡ set l v s ---- -- Every Lens can be used directly as a Setter or -- Traversal. -- -- You can also use a Lens for Getting as if it were a -- Fold or Getter. -- -- Since every Lens is a valid Traversal, the -- Traversal laws are required of any Lens you create: -- --
-- l pure ≡ pure -- fmap (l f) . l g ≡ getCompose . l (Compose . fmap f . g) ---- --
-- type Lens s t a b = forall f. Functor f => LensLike f s t a b --type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t -- |
-- type Lens' = Simple Lens --type Lens' s a = Lens s s a a -- | A Traversal can be used directly as a Setter or a -- Fold (but not as a Lens) and provides the ability to -- both read and update multiple fields, subject to some relatively weak -- Traversal laws. -- -- These have also been known as multilenses, but they have the signature -- and spirit of -- --
-- traverse :: Traversable f => Traversal (f a) (f b) a b ---- -- and the more evocative name suggests their application. -- -- Most of the time the Traversal you will want to use is just -- traverse, but you can also pass any Lens or Iso -- as a Traversal, and composition of a Traversal (or -- Lens or Iso) with a Traversal (or Lens or -- Iso) using (.) forms a valid Traversal. -- -- The laws for a Traversal t follow from the laws for -- Traversable as stated in "The Essence of the Iterator Pattern". -- --
-- t pure ≡ pure -- fmap (t f) . t g ≡ getCompose . t (Compose . fmap f . g) ---- -- One consequence of this requirement is that a Traversal needs -- to leave the same number of elements as a candidate for subsequent -- Traversal that it started with. Another testament to the -- strength of these laws is that the caveat expressed in section 5.5 of -- the "Essence of the Iterator Pattern" about exotic Traversable -- instances that traverse the same entry multiple times was -- actually already ruled out by the second law in that same paper! type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t -- |
-- type Traversal' = Simple Traversal --type Traversal' s a = Traversal s s a a type Traversal1 s t a b = forall f. Apply f => (a -> f b) -> s -> f t type Traversal1' s a = Traversal1 s s a a -- | The only LensLike law that can apply to a Setter -- l is that -- --
-- set l y (set l x a) ≡ set l y a ---- -- You can't view a Setter in general, so the other two -- laws are irrelevant. -- -- However, two Functor laws apply to a Setter: -- --
-- over l id ≡ id -- over l f . over l g ≡ over l (f . g) ---- -- These can be stated more directly: -- --
-- l pure ≡ pure -- l f . untainted . l g ≡ l (f . untainted . g) ---- -- You can compose a Setter with a Lens or a -- Traversal using (.) from the Prelude and the -- result is always only a Setter and nothing more. -- --
-- >>> over traverse f [a,b,c,d] -- [f a,f b,f c,f d] ---- --
-- >>> over _1 f (a,b) -- (f a,b) ---- --
-- >>> over (traverse._1) f [(a,b),(c,d)] -- [(f a,b),(f c,d)] ---- --
-- >>> over both f (a,b) -- (f a,f b) ---- --
-- >>> over (traverse.both) f [(a,b),(c,d)] -- [(f a,f b),(f c,f d)] --type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f t -- | A Setter' is just a Setter that doesn't change the -- types. -- -- These are particularly common when talking about monomorphic -- containers. e.g. -- --
-- sets Data.Text.map :: Setter' Text Char ---- --
-- type Setter' = Setter' --type Setter' s a = Setter s s a a -- | A Getter describes how to retrieve a single value in a way that -- can be composed with other LensLike constructions. -- -- Unlike a Lens a Getter is read-only. Since a -- Getter cannot be used to write back there are no Lens -- laws that can be applied to it. In fact, it is isomorphic to an -- arbitrary function from (s -> a). -- -- Moreover, a Getter can be used directly as a Fold, since -- it just ignores the Applicative. type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s -- | A Fold describes how to retrieve multiple values in a way that -- can be composed with other LensLike constructions. -- -- A Fold s a provides a structure with operations very -- similar to those of the Foldable typeclass, see -- foldMapOf and the other Fold combinators. -- -- By convention, if there exists a foo method that expects a -- Foldable (f a), then there should be a fooOf -- method that takes a Fold s a and a value of type -- s. -- -- A Getter is a legal Fold that just ignores the supplied -- Monoid. -- -- Unlike a Traversal a Fold is read-only. Since a -- Fold cannot be used to write back there are no Lens laws -- that apply. type Fold s a = forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s -- | A relevant Fold (aka Fold1) has one or more targets. type Fold1 s a = forall f. (Contravariant f, Apply f) => (a -> f a) -> s -> f s -- | Every IndexedLens is a valid Lens and a valid -- IndexedTraversal. type IndexedLens i s t a b = forall f p. (Indexable i p, Functor f) => p a (f b) -> s -> f t -- |
-- type IndexedLens' i = Simple (IndexedLens i) --type IndexedLens' i s a = IndexedLens i s s a a -- | Every IndexedTraversal is a valid Traversal or -- IndexedFold. -- -- The Indexed constraint is used to allow an -- IndexedTraversal to be used directly as a Traversal. -- -- The Traversal laws are still required to hold. -- -- In addition, the index i should satisfy the requirement that -- it stays unchanged even when modifying the value a, otherwise -- traversals like indices break the Traversal laws. type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f t -- |
-- type IndexedTraversal' i = Simple (IndexedTraversal i) --type IndexedTraversal' i s a = IndexedTraversal i s s a a type IndexedTraversal1 i s t a b = forall p f. (Indexable i p, Apply f) => p a (f b) -> s -> f t type IndexedTraversal1' i s a = IndexedTraversal1 i s s a a -- | Every IndexedSetter is a valid Setter. -- -- The Setter laws are still required to hold. type IndexedSetter i s t a b = forall f p. (Indexable i p, Settable f) => p a (f b) -> s -> f t -- |
-- type IndexedSetter' i = Simple (IndexedSetter i) --type IndexedSetter' i s a = IndexedSetter i s s a a -- | Every IndexedGetter is a valid IndexedFold and can be -- used for Getting like a Getter. type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s -- | Every IndexedFold is a valid Fold and can be used for -- Getting. type IndexedFold i s a = forall p f. (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s type IndexedFold1 i s a = forall p f. (Indexable i p, Contravariant f, Apply f) => p a (f a) -> s -> f s -- | An IndexPreservingLens leaves any index it is composed with -- alone. type IndexPreservingLens s t a b = forall p f. (Conjoined p, Functor f) => p a (f b) -> p s (f t) -- |
-- type IndexPreservingLens' = Simple IndexPreservingLens --type IndexPreservingLens' s a = IndexPreservingLens s s a a -- | An IndexPreservingLens leaves any index it is composed with -- alone. type IndexPreservingTraversal s t a b = forall p f. (Conjoined p, Applicative f) => p a (f b) -> p s (f t) -- |
-- type IndexPreservingTraversal' = Simple IndexPreservingTraversal --type IndexPreservingTraversal' s a = IndexPreservingTraversal s s a a type IndexPreservingTraversal1 s t a b = forall p f. (Conjoined p, Apply f) => p a (f b) -> p s (f t) type IndexPreservingTraversal1' s a = IndexPreservingTraversal1 s s a a -- | An IndexPreservingSetter can be composed with a -- IndexedSetter, IndexedTraversal or IndexedLens -- and leaves the index intact, yielding an IndexedSetter. type IndexPreservingSetter s t a b = forall p f. (Conjoined p, Settable f) => p a (f b) -> p s (f t) -- |
-- type IndexedPreservingSetter' i = Simple IndexedPreservingSetter --type IndexPreservingSetter' s a = IndexPreservingSetter s s a a -- | An IndexPreservingGetter can be used as a Getter, but -- when composed with an IndexedTraversal, IndexedFold, or -- IndexedLens yields an IndexedFold, IndexedFold or -- IndexedGetter respectively. type IndexPreservingGetter s a = forall p f. (Conjoined p, Contravariant f, Functor f) => p a (f a) -> p s (f s) -- | An IndexPreservingFold can be used as a Fold, but when -- composed with an IndexedTraversal, IndexedFold, or -- IndexedLens yields an IndexedFold respectively. type IndexPreservingFold s a = forall p f. (Conjoined p, Contravariant f, Applicative f) => p a (f a) -> p s (f s) type IndexPreservingFold1 s a = forall p f. (Conjoined p, Contravariant f, Apply f) => p a (f a) -> p s (f s) -- | A Simple Lens, Simple Traversal, ... can -- be used instead of a Lens,Traversal, ... whenever the -- type variables don't change upon setting a value. -- --
-- _imagPart :: Simple Lens (Complex a) a -- traversed :: Simple (IndexedTraversal Int) [a] a ---- -- Note: To use this alias in your own code with LensLike -- f or Setter, you may have to turn on -- LiberalTypeSynonyms. -- -- This is commonly abbreviated as a "prime" marker, e.g. -- Lens' = Simple Lens. type Simple f s a = f s s a a -- | Many combinators that accept a Lens can also accept a -- Traversal in limited situations. -- -- They do so by specializing the type of Functor that they -- require of the caller. -- -- If a function accepts a LensLike f s t a b for some -- Functor f, then they may be passed a Lens. -- -- Further, if f is an Applicative, they may also be -- passed a Traversal. type LensLike f s t a b = (a -> f b) -> s -> f t -- |
-- type LensLike' f = Simple (LensLike f) --type LensLike' f s a = LensLike f s s a a -- | This is a convenient alias for use when you need to consume either -- indexed or non-indexed lens-likes based on context. type Over p f s t a b = p a (f b) -> s -> f t -- | This is a convenient alias for use when you need to consume either -- indexed or non-indexed lens-likes based on context. -- --
-- type Over' p f = Simple (Over p f) --type Over' p f s a = Over p f s s a a -- | Convenient alias for constructing indexed lenses and their ilk. type IndexedLensLike i f s t a b = forall p. Indexable i p => p a (f b) -> s -> f t -- | Convenient alias for constructing simple indexed lenses and their ilk. type IndexedLensLike' i f s a = IndexedLensLike i f s s a a -- |
-- type LensLike f s t a b = Optical (->) (->) f s t a b ---- --
-- type Over p f s t a b = Optical p (->) f s t a b ---- --
-- type Optic p f s t a b = Optical p p f s t a b --type Optical p q f s t a b = p a (f b) -> q s (f t) -- |
-- type Optical' p q f s a = Simple (Optical p q f) s a --type Optical' p q f s a = Optical p q f s s a a -- | A valid Optic l should satisfy the laws: -- --
-- l pure ≡ pure -- l (Procompose f g) = Procompose (l f) (l g) ---- -- This gives rise to the laws for Equality, Iso, -- Prism, Lens, Traversal, Traversal1, -- Setter, Fold, Fold1, and Getter as well -- along with their index-preserving variants. -- --
-- type LensLike f s t a b = Optic (->) f s t a b --type Optic p f s t a b = p a (f b) -> p s (f t) -- |
-- type Optic' p f s a = Simple (Optic p f) s a --type Optic' p f s a = Optic p f s s a a -- | A Setter s t a b is a generalization of fmap -- from Functor. It allows you to map into a structure and change -- out the contents, but it isn't strong enough to allow you to enumerate -- those contents. Starting with fmap :: Functor f -- => (a -> b) -> f a -> f b we monomorphize the type to -- obtain (a -> b) -> s -> t and then decorate it with -- Identity to obtain: -- --
-- type Setter s t a b = (a -> Identity b) -> s -> Identity t ---- -- Every Traversal is a valid Setter, since Identity -- is Applicative. -- -- Everything you can do with a Functor, you can do with a -- Setter. There are combinators that generalize fmap and -- (<$). module Control.Lens.Setter -- | The only LensLike law that can apply to a Setter -- l is that -- --
-- set l y (set l x a) ≡ set l y a ---- -- You can't view a Setter in general, so the other two -- laws are irrelevant. -- -- However, two Functor laws apply to a Setter: -- --
-- over l id ≡ id -- over l f . over l g ≡ over l (f . g) ---- -- These can be stated more directly: -- --
-- l pure ≡ pure -- l f . untainted . l g ≡ l (f . untainted . g) ---- -- You can compose a Setter with a Lens or a -- Traversal using (.) from the Prelude and the -- result is always only a Setter and nothing more. -- --
-- >>> over traverse f [a,b,c,d] -- [f a,f b,f c,f d] ---- --
-- >>> over _1 f (a,b) -- (f a,b) ---- --
-- >>> over (traverse._1) f [(a,b),(c,d)] -- [(f a,b),(f c,d)] ---- --
-- >>> over both f (a,b) -- (f a,f b) ---- --
-- >>> over (traverse.both) f [(a,b),(c,d)] -- [(f a,f b),(f c,f d)] --type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f t -- | A Setter' is just a Setter that doesn't change the -- types. -- -- These are particularly common when talking about monomorphic -- containers. e.g. -- --
-- sets Data.Text.map :: Setter' Text Char ---- --
-- type Setter' = Setter' --type Setter' s a = Setter s s a a -- | Every IndexedSetter is a valid Setter. -- -- The Setter laws are still required to hold. type IndexedSetter i s t a b = forall f p. (Indexable i p, Settable f) => p a (f b) -> s -> f t -- |
-- type IndexedSetter' i = Simple (IndexedSetter i) --type IndexedSetter' i s a = IndexedSetter i s s a a -- | Running a Setter instantiates it to a concrete type. -- -- When consuming a setter directly to perform a mapping, you can use -- this type, but most user code will not need to use this type. type ASetter s t a b = (a -> Identity b) -> s -> Identity t -- | This is a useful alias for use when consuming a Setter'. -- -- Most user code will never have to use this type. -- --
-- type ASetter' = Simple ASetter --type ASetter' s a = ASetter s s a a -- | Running an IndexedSetter instantiates it to a concrete type. -- -- When consuming a setter directly to perform a mapping, you can use -- this type, but most user code will not need to use this type. type AnIndexedSetter i s t a b = Indexed i a (Identity b) -> s -> Identity t -- |
-- type AnIndexedSetter' i = Simple (AnIndexedSetter i) --type AnIndexedSetter' i s a = AnIndexedSetter i s s a a -- | This is a convenient alias when defining highly polymorphic code that -- takes both ASetter and AnIndexedSetter as appropriate. -- If a function takes this it is expecting one of those two things based -- on context. type Setting p s t a b = p a (Identity b) -> s -> Identity t -- | This is a convenient alias when defining highly polymorphic code that -- takes both ASetter' and AnIndexedSetter' as appropriate. -- If a function takes this it is expecting one of those two things based -- on context. type Setting' p s a = Setting p s s a a -- | Build a Setter, IndexedSetter or -- IndexPreservingSetter depending on your choice of -- Profunctor. -- --
-- sets :: ((a -> b) -> s -> t) -> Setter s t a b --sets :: (Profunctor p, Profunctor q, Settable f) => (p a b -> q s t) -> Optical p q f s t a b -- | Build an index-preserving Setter from a map-like function. -- -- Your supplied function f is required to satisfy: -- --
-- f id ≡ id -- f g . f h ≡ f (g . h) ---- -- Equational reasoning: -- --
-- setting . over ≡ id -- over . setting ≡ id ---- -- Another way to view sets is that it takes a "semantic editor -- combinator" and transforms it into a Setter. -- --
-- setting :: ((a -> b) -> s -> t) -> Setter s t a b --setting :: ((a -> b) -> s -> t) -> IndexPreservingSetter s t a b -- | Restore ASetter to a full Setter. cloneSetter :: ASetter s t a b -> Setter s t a b -- | Build an IndexPreservingSetter from any Setter. cloneIndexPreservingSetter :: ASetter s t a b -> IndexPreservingSetter s t a b -- | Clone an IndexedSetter. cloneIndexedSetter :: AnIndexedSetter i s t a b -> IndexedSetter i s t a b -- | This Setter can be used to map over all of the values in a -- Functor. -- --
-- fmap ≡ over mapped -- fmapDefault ≡ over traverse -- (<$) ≡ set mapped ---- --
-- >>> over mapped f [a,b,c] -- [f a,f b,f c] ---- --
-- >>> over mapped (+1) [1,2,3] -- [2,3,4] ---- --
-- >>> set mapped x [a,b,c] -- [x,x,x] ---- --
-- >>> [[a,b],[c]] & mapped.mapped +~ x -- [[a + x,b + x],[c + x]] ---- --
-- >>> over (mapped._2) length [("hello","world"),("leaders","!!!")] -- [("hello",5),("leaders",3)] ---- --
-- mapped :: Functor f => Setter (f a) (f b) a b ---- -- If you want an IndexPreservingSetter use setting -- fmap. mapped :: Functor f => Setter (f a) (f b) a b -- | This setter can be used to modify all of the values in a -- Monad. -- -- You sometimes have to use this rather than mapped -- due to -- temporary insanity Functor is not a superclass of Monad. -- --
-- liftM ≡ over lifted ---- --
-- >>> over lifted f [a,b,c] -- [f a,f b,f c] ---- --
-- >>> set lifted b (Just a) -- Just b ---- -- If you want an IndexPreservingSetter use setting -- liftM. lifted :: Monad m => Setter (m a) (m b) a b -- | This Setter can be used to map over all of the inputs to a -- Contravariant. -- --
-- contramap ≡ over contramapped ---- --
-- >>> getPredicate (over contramapped (*2) (Predicate even)) 5 -- True ---- --
-- >>> getOp (over contramapped (*5) (Op show)) 100 -- "500" ---- --
-- >>> Prelude.map ($ 1) $ over (mapped . _Unwrapping' Op . contramapped) (*12) [(*2),(+1),(^3)] -- [24,13,1728] --contramapped :: Contravariant f => Setter (f b) (f a) a b -- | This Setter can be used to map over the input of a -- Profunctor. -- -- The most common Profunctor to use this with is -- (->). -- --
-- >>> (argument %~ f) g x -- g (f x) ---- --
-- >>> (argument %~ show) length [1,2,3] -- 7 ---- --
-- >>> (argument %~ f) h x y -- h (f x) y ---- -- Map over the argument of the result of a function -- i.e., its second -- argument: -- --
-- >>> (mapped.argument %~ f) h x y -- h x (f y) ---- --
-- argument :: Setter (b -> r) (a -> r) a b --argument :: Profunctor p => Setter (p b r) (p a r) a b -- | Modify the target of a Lens or all the targets of a -- Setter or Traversal with a function. -- --
-- fmap ≡ over mapped -- fmapDefault ≡ over traverse -- sets . over ≡ id -- over . sets ≡ id ---- -- Given any valid Setter l, you can also rely on the -- law: -- --
-- over l f . over l g = over l (f . g) ---- -- e.g. -- --
-- >>> over mapped f (over mapped g [a,b,c]) == over mapped (f . g) [a,b,c] -- True ---- -- Another way to view over is to say that it transforms a -- Setter into a "semantic editor combinator". -- --
-- >>> over mapped f (Just a) -- Just (f a) ---- --
-- >>> over mapped (*10) [1,2,3] -- [10,20,30] ---- --
-- >>> over _1 f (a,b) -- (f a,b) ---- --
-- >>> over _1 show (10,20) -- ("10",20) ---- --
-- over :: Setter s t a b -> (a -> b) -> s -> t -- over :: ASetter s t a b -> (a -> b) -> s -> t --over :: ASetter s t a b -> (a -> b) -> s -> t -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal with a constant value. -- --
-- (<$) ≡ set mapped ---- --
-- >>> set _2 "hello" (1,()) -- (1,"hello") ---- --
-- >>> set mapped () [1,2,3,4] -- [(),(),(),()] ---- -- Note: Attempting to set a Fold or Getter will -- fail at compile time with an relatively nice error message. -- --
-- set :: Setter s t a b -> b -> s -> t -- set :: Iso s t a b -> b -> s -> t -- set :: Lens s t a b -> b -> s -> t -- set :: Traversal s t a b -> b -> s -> t --set :: ASetter s t a b -> b -> s -> t -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal with a constant value. -- -- This is an infix version of set, provided for consistency with -- (.=). -- --
-- f <$ a ≡ mapped .~ f $ a ---- --
-- >>> (a,b,c,d) & _4 .~ e -- (a,b,c,e) ---- --
-- >>> (42,"world") & _1 .~ "hello" -- ("hello","world") ---- --
-- >>> (a,b) & both .~ c -- (c,c) ---- --
-- (.~) :: Setter s t a b -> b -> s -> t -- (.~) :: Iso s t a b -> b -> s -> t -- (.~) :: Lens s t a b -> b -> s -> t -- (.~) :: Traversal s t a b -> b -> s -> t --(.~) :: ASetter s t a b -> b -> s -> t -- | Modifies the target of a Lens or all of the targets of a -- Setter or Traversal with a user supplied function. -- -- This is an infix version of over. -- --
-- fmap f ≡ mapped %~ f -- fmapDefault f ≡ traverse %~ f ---- --
-- >>> (a,b,c) & _3 %~ f -- (a,b,f c) ---- --
-- >>> (a,b) & both %~ f -- (f a,f b) ---- --
-- >>> _2 %~ length $ (1,"hello") -- (1,5) ---- --
-- >>> traverse %~ f $ [a,b,c] -- [f a,f b,f c] ---- --
-- >>> traverse %~ even $ [1,2,3] -- [False,True,False] ---- --
-- >>> traverse.traverse %~ length $ [["hello","world"],["!!!"]] -- [[5,5],[3]] ---- --
-- (%~) :: Setter s t a b -> (a -> b) -> s -> t -- (%~) :: Iso s t a b -> (a -> b) -> s -> t -- (%~) :: Lens s t a b -> (a -> b) -> s -> t -- (%~) :: Traversal s t a b -> (a -> b) -> s -> t --(%~) :: ASetter s t a b -> (a -> b) -> s -> t -- | Increment the target(s) of a numerically valued Lens, -- Setter 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 => Setter' s a -> a -> s -> s -- (+~) :: Num a => Iso' s a -> a -> s -> s -- (+~) :: Num a => Lens' s a -> a -> s -> s -- (+~) :: Num a => Traversal' s a -> a -> s -> s --(+~) :: Num a => ASetter s t a a -> a -> s -> t -- | Decrement the target(s) of a numerically valued Lens, -- Iso, Setter 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 => Setter' s a -> a -> s -> s -- (-~) :: Num a => Iso' s a -> a -> s -> s -- (-~) :: Num a => Lens' s a -> a -> s -> s -- (-~) :: Num a => Traversal' s a -> a -> s -> s --(-~) :: Num a => ASetter s t a a -> a -> s -> t -- | Multiply the target(s) of a numerically valued Lens, -- Iso, Setter or Traversal. -- --
-- >>> (a,b) & _1 *~ c -- (a * c,b) ---- --
-- >>> (a,b) & both *~ c -- (a * c,b * c) ---- --
-- >>> (1,2) & _2 *~ 4 -- (1,8) ---- --
-- >>> Just 24 & mapped *~ 2 -- Just 48 ---- --
-- (*~) :: Num a => Setter' s a -> a -> s -> s -- (*~) :: Num a => Iso' s a -> a -> s -> s -- (*~) :: Num a => Lens' s a -> a -> s -> s -- (*~) :: Num a => Traversal' s a -> a -> s -> s --(*~) :: Num a => ASetter s t a a -> a -> s -> t -- | Divide the target(s) of a numerically valued Lens, Iso, -- Setter or Traversal. -- --
-- >>> (a,b) & _1 //~ c -- (a / c,b) ---- --
-- >>> (a,b) & both //~ c -- (a / c,b / c) ---- --
-- >>> ("Hawaii",10) & _2 //~ 2 -- ("Hawaii",5.0) ---- --
-- (//~) :: Fractional a => Setter' s a -> a -> s -> s -- (//~) :: Fractional a => Iso' s a -> a -> s -> s -- (//~) :: Fractional a => Lens' s a -> a -> s -> s -- (//~) :: Fractional a => Traversal' s a -> a -> s -> s --(//~) :: Fractional a => ASetter s t a a -> a -> s -> t -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to a non-negative integral power. -- --
-- >>> (1,3) & _2 ^~ 2 -- (1,9) ---- --
-- (^~) :: (Num a, Integral e) => Setter' s a -> e -> s -> s -- (^~) :: (Num a, Integral e) => Iso' s a -> e -> s -> s -- (^~) :: (Num a, Integral e) => Lens' s a -> e -> s -> s -- (^~) :: (Num a, Integral e) => Traversal' s a -> e -> s -> s --(^~) :: (Num a, Integral e) => ASetter s t a a -> e -> s -> t -- | Raise the target(s) of a fractionally valued Lens, -- Setter or Traversal to an integral power. -- --
-- >>> (1,2) & _2 ^^~ (-1) -- (1,0.5) ---- --
-- (^^~) :: (Fractional a, Integral e) => Setter' s a -> e -> s -> s -- (^^~) :: (Fractional a, Integral e) => Iso' s a -> e -> s -> s -- (^^~) :: (Fractional a, Integral e) => Lens' s a -> e -> s -> s -- (^^~) :: (Fractional a, Integral e) => Traversal' s a -> e -> s -> s --(^^~) :: (Fractional a, Integral e) => ASetter s t a a -> e -> s -> t -- | Raise the target(s) of a floating-point valued Lens, -- Setter or Traversal to an arbitrary power. -- --
-- >>> (a,b) & _1 **~ c -- (a**c,b) ---- --
-- >>> (a,b) & both **~ c -- (a**c,b**c) ---- --
-- >>> _2 **~ 10 $ (3,2) -- (3,1024.0) ---- --
-- (**~) :: Floating a => Setter' s a -> a -> s -> s -- (**~) :: Floating a => Iso' s a -> a -> s -> s -- (**~) :: Floating a => Lens' s a -> a -> s -> s -- (**~) :: Floating a => Traversal' s a -> a -> s -> s --(**~) :: Floating a => ASetter s t a a -> a -> s -> t -- | Logically || the target(s) of a Bool-valued Lens -- or Setter. -- --
-- >>> both ||~ True $ (False,True) -- (True,True) ---- --
-- >>> both ||~ False $ (False,True) -- (False,True) ---- --
-- (||~) :: Setter' s Bool -> Bool -> s -> s -- (||~) :: Iso' s Bool -> Bool -> s -> s -- (||~) :: Lens' s Bool -> Bool -> s -> s -- (||~) :: Traversal' s Bool -> Bool -> s -> s --(||~) :: ASetter s t Bool Bool -> Bool -> s -> t -- | Modify the target of a monoidally valued by mappending another -- value. -- --
-- >>> (Sum a,b) & _1 <>~ Sum c -- (Sum {getSum = a + c},b) ---- --
-- >>> (Sum a,Sum b) & both <>~ Sum c -- (Sum {getSum = a + c},Sum {getSum = b + c}) ---- --
-- >>> both <>~ "!!!" $ ("hello","world") -- ("hello!!!","world!!!") ---- --
-- (<>~) :: Monoid a => Setter s t a a -> a -> s -> t -- (<>~) :: Monoid a => Iso s t a a -> a -> s -> t -- (<>~) :: Monoid a => Lens s t a a -> a -> s -> t -- (<>~) :: Monoid a => Traversal s t a a -> a -> s -> t --(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t -- | Logically && the target(s) of a Bool-valued -- Lens or Setter. -- --
-- >>> both &&~ True $ (False, True) -- (False,True) ---- --
-- >>> both &&~ False $ (False, True) -- (False,False) ---- --
-- (&&~) :: Setter' s Bool -> Bool -> s -> s -- (&&~) :: Iso' s Bool -> Bool -> s -> s -- (&&~) :: Lens' s Bool -> Bool -> s -> s -- (&&~) :: Traversal' s Bool -> Bool -> s -> s --(&&~) :: ASetter s t Bool Bool -> Bool -> s -> t -- | Set with pass-through. -- -- This is mostly present for consistency, but may be useful for chaining -- assignments. -- -- If you do not need a copy of the intermediate result, then using l -- .~ t directly is a good idea. -- --
-- >>> (a,b) & _1 <.~ c -- (c,(c,b)) ---- --
-- >>> ("good","morning","vietnam") & _3 <.~ "world" -- ("world",("good","morning","world")) ---- --
-- >>> (42,Map.fromList [("goodnight","gracie")]) & _2.at "hello" <.~ Just "world" -- (Just "world",(42,fromList [("goodnight","gracie"),("hello","world")])) ---- --
-- (<.~) :: Setter s t a b -> b -> s -> (b, t) -- (<.~) :: Iso s t a b -> b -> s -> (b, t) -- (<.~) :: Lens s t a b -> b -> s -> (b, t) -- (<.~) :: Traversal s t a b -> b -> s -> (b, t) --(<.~) :: ASetter s t a b -> b -> s -> (b, t) -- | Set the target of a Lens, Traversal or Setter to -- Just a value. -- --
-- l ?~ t ≡ set l (Just t) ---- --
-- >>> Nothing & id ?~ a -- Just a ---- --
-- >>> Map.empty & at 3 ?~ x -- fromList [(3,x)] ---- --
-- (?~) :: Setter s t a (Maybe b) -> b -> s -> t -- (?~) :: Iso s t a (Maybe b) -> b -> s -> t -- (?~) :: Lens s t a (Maybe b) -> b -> s -> t -- (?~) :: Traversal s t a (Maybe b) -> b -> s -> t --(?~) :: ASetter s t a (Maybe b) -> b -> s -> t -- | Set to Just a value with pass-through. -- -- This is mostly present for consistency, but may be useful for for -- chaining assignments. -- -- If you do not need a copy of the intermediate result, then using l -- ?~ d directly is a good idea. -- --
-- >>> import Data.Map as Map -- -- >>> _2.at "hello" <?~ "world" $ (42,Map.fromList [("goodnight","gracie")]) -- ("world",(42,fromList [("goodnight","gracie"),("hello","world")])) ---- --
-- (<?~) :: Setter s t a (Maybe b) -> b -> s -> (b, t) -- (<?~) :: Iso s t a (Maybe b) -> b -> s -> (b, t) -- (<?~) :: Lens s t a (Maybe b) -> b -> s -> (b, t) -- (<?~) :: Traversal s t a (Maybe b) -> b -> s -> (b, t) --(~) :: ASetter s t a (Maybe b) -> b -> s -> (b, t) -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state with a new -- value, irrespective of the old. -- -- This is an alias for (.=). -- --
-- >>> execState (do assign _1 c; assign _2 d) (a,b) -- (c,d) ---- --
-- >>> execState (both .= c) (a,b) -- (c,c) ---- --
-- assign :: MonadState s m => Iso' s a -> a -> m () -- assign :: MonadState s m => Lens' s a -> a -> m () -- assign :: MonadState s m => Traversal' s a -> a -> m () -- assign :: MonadState s m => Setter' s a -> a -> m () --assign :: MonadState s m => ASetter s s a b -> b -> m () -- | This is an alias for (%=). modifying :: MonadState s m => ASetter s s a b -> (a -> b) -> m () -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state with a new -- value, irrespective of the old. -- -- This is an infix version of assign. -- --
-- >>> execState (do _1 .= c; _2 .= d) (a,b) -- (c,d) ---- --
-- >>> execState (both .= c) (a,b) -- (c,c) ---- --
-- (.=) :: MonadState s m => Iso' s a -> a -> m () -- (.=) :: MonadState s m => Lens' s a -> a -> m () -- (.=) :: MonadState s m => Traversal' s a -> a -> m () -- (.=) :: MonadState s m => Setter' s a -> a -> m () ---- -- It puts the state in the monad or it gets the hose again. (.=) :: MonadState s m => ASetter s s a b -> b -> m () -- | Map over the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state. -- --
-- >>> execState (do _1 %= f;_2 %= g) (a,b) -- (f a,g b) ---- --
-- >>> execState (do both %= f) (a,b) -- (f a,f b) ---- --
-- (%=) :: MonadState s m => Iso' s a -> (a -> a) -> m () -- (%=) :: MonadState s m => Lens' s a -> (a -> a) -> m () -- (%=) :: MonadState s m => Traversal' s a -> (a -> a) -> m () -- (%=) :: MonadState s m => Setter' s a -> (a -> a) -> m () ---- --
-- (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () --(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by adding a value. -- -- Example: -- --
-- fresh :: MonadState Int m => m Int -- fresh = do -- id += 1 -- use id ---- --
-- >>> execState (do _1 += c; _2 += d) (a,b) -- (a + c,b + d) ---- --
-- >>> execState (do _1.at 1.non 0 += 10) (Map.fromList [(2,100)],"hello") -- (fromList [(1,10),(2,100)],"hello") ---- --
-- (+=) :: (MonadState s m, Num a) => Setter' s a -> a -> m () -- (+=) :: (MonadState s m, Num a) => Iso' s a -> a -> m () -- (+=) :: (MonadState s m, Num a) => Lens' s a -> a -> m () -- (+=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m () --(+=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by subtracting a value. -- --
-- >>> execState (do _1 -= c; _2 -= d) (a,b) -- (a - c,b - d) ---- --
-- (-=) :: (MonadState s m, Num a) => Setter' s a -> a -> m () -- (-=) :: (MonadState s m, Num a) => Iso' s a -> a -> m () -- (-=) :: (MonadState s m, Num a) => Lens' s a -> a -> m () -- (-=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m () --(-=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by multiplying by value. -- --
-- >>> execState (do _1 *= c; _2 *= d) (a,b) -- (a * c,b * d) ---- --
-- (*=) :: (MonadState s m, Num a) => Setter' s a -> a -> m () -- (*=) :: (MonadState s m, Num a) => Iso' s a -> a -> m () -- (*=) :: (MonadState s m, Num a) => Lens' s a -> a -> m () -- (*=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m () --(*=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by dividing by a value. -- --
-- >>> execState (do _1 //= c; _2 //= d) (a,b) -- (a / c,b / d) ---- --
-- (//=) :: (MonadState s m, Fractional a) => Setter' s a -> a -> m () -- (//=) :: (MonadState s m, Fractional a) => Iso' s a -> a -> m () -- (//=) :: (MonadState s m, Fractional a) => Lens' s a -> a -> m () -- (//=) :: (MonadState s m, Fractional a) => Traversal' s a -> a -> m () --(//=) :: (MonadState s m, Fractional a) => ASetter' s a -> a -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to a non-negative integral power. -- --
-- (^=) :: (MonadState s m, Num a, Integral e) => Setter' s a -> e -> m () -- (^=) :: (MonadState s m, Num a, Integral e) => Iso' s a -> e -> m () -- (^=) :: (MonadState s m, Num a, Integral e) => Lens' s a -> e -> m () -- (^=) :: (MonadState s m, Num a, Integral e) => Traversal' s a -> e -> m () --(^=) :: (MonadState s m, Num a, Integral e) => ASetter' s a -> e -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to an integral power. -- --
-- (^^=) :: (MonadState s m, Fractional a, Integral e) => Setter' s a -> e -> m () -- (^^=) :: (MonadState s m, Fractional a, Integral e) => Iso' s a -> e -> m () -- (^^=) :: (MonadState s m, Fractional a, Integral e) => Lens' s a -> e -> m () -- (^^=) :: (MonadState s m, Fractional a, Integral e) => Traversal' s a -> e -> m () --(^^=) :: (MonadState s m, Fractional a, Integral e) => ASetter' s a -> e -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to an arbitrary power -- --
-- >>> execState (do _1 **= c; _2 **= d) (a,b) -- (a**c,b**d) ---- --
-- (**=) :: (MonadState s m, Floating a) => Setter' s a -> a -> m () -- (**=) :: (MonadState s m, Floating a) => Iso' s a -> a -> m () -- (**=) :: (MonadState s m, Floating a) => Lens' s a -> a -> m () -- (**=) :: (MonadState s m, Floating a) => Traversal' s a -> a -> m () --(**=) :: (MonadState s m, Floating a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', 'Iso, Setter or -- Traversal by taking their logical || with a value. -- --
-- >>> execState (do _1 ||= True; _2 ||= False; _3 ||= True; _4 ||= False) (True,True,False,False) -- (True,True,True,False) ---- --
-- (||=) :: MonadState s m => Setter' s Bool -> Bool -> m () -- (||=) :: MonadState s m => Iso' s Bool -> Bool -> m () -- (||=) :: MonadState s m => Lens' s Bool -> Bool -> m () -- (||=) :: MonadState s m => Traversal' s Bool -> Bool -> m () --(||=) :: MonadState s m => ASetter' s Bool -> Bool -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by mappending a value. -- --
-- >>> execState (do _1 <>= Sum c; _2 <>= Product d) (Sum a,Product b) -- (Sum {getSum = a + c},Product {getProduct = b * d}) ---- --
-- >>> execState (both <>= "!!!") ("hello","world") -- ("hello!!!","world!!!") ---- --
-- (<>=) :: (MonadState s m, Monoid a) => Setter' s a -> a -> m () -- (<>=) :: (MonadState s m, Monoid a) => Iso' s a -> a -> m () -- (<>=) :: (MonadState s m, Monoid a) => Lens' s a -> a -> m () -- (<>=) :: (MonadState s m, Monoid a) => Traversal' s a -> a -> m () --(<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by taking their logical && with a -- value. -- --
-- >>> execState (do _1 &&= True; _2 &&= False; _3 &&= True; _4 &&= False) (True,True,False,False) -- (True,False,False,False) ---- --
-- (&&=) :: MonadState s m => Setter' s Bool -> Bool -> m () -- (&&=) :: MonadState s m => Iso' s Bool -> Bool -> m () -- (&&=) :: MonadState s m => Lens' s Bool -> Bool -> m () -- (&&=) :: MonadState s m => Traversal' s Bool -> Bool -> m () --(&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m () -- | Set with pass-through -- -- This is useful for chaining assignment without round-tripping through -- your Monad stack. -- --
-- do x <- _2 <.= ninety_nine_bottles_of_beer_on_the_wall ---- -- If you do not need a copy of the intermediate result, then using l -- .= d will avoid unused binding warnings. -- --
-- (<.=) :: MonadState s m => Setter s s a b -> b -> m b -- (<.=) :: MonadState s m => Iso s s a b -> b -> m b -- (<.=) :: MonadState s m => Lens s s a b -> b -> m b -- (<.=) :: MonadState s m => Traversal s s a b -> b -> m b --(<.=) :: MonadState s m => ASetter s s a b -> b -> m b -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state with -- Just a new value, irrespective of the old. -- --
-- >>> execState (do at 1 ?= a; at 2 ?= b) Map.empty -- fromList [(1,a),(2,b)] ---- --
-- >>> execState (do _1 ?= b; _2 ?= c) (Just a, Nothing) -- (Just b,Just c) ---- --
-- (?=) :: MonadState s m => Iso' s (Maybe a) -> a -> m () -- (?=) :: MonadState s m => Lens' s (Maybe a) -> a -> m () -- (?=) :: MonadState s m => Traversal' s (Maybe a) -> a -> m () -- (?=) :: MonadState s m => Setter' s (Maybe a) -> a -> m () --(?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m () -- | Set Just a value with pass-through -- -- This is useful for chaining assignment without round-tripping through -- your Monad stack. -- --
-- do x <- at "foo" <?= ninety_nine_bottles_of_beer_on_the_wall ---- -- If you do not need a copy of the intermediate result, then using l -- ?= d will avoid unused binding warnings. -- --
-- (<?=) :: MonadState s m => Setter s s a (Maybe b) -> b -> m b -- (<?=) :: MonadState s m => Iso s s a (Maybe b) -> b -> m b -- (<?=) :: MonadState s m => Lens s s a (Maybe b) -> b -> m b -- (<?=) :: MonadState s m => Traversal s s a (Maybe b) -> b -> m b --(=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m b -- | Run a monadic action, and set all of the targets of a Lens, -- Setter or Traversal to its result. -- --
-- (<~) :: MonadState s m => Iso s s a b -> m b -> m () -- (<~) :: MonadState s m => Lens s s a b -> m b -> m () -- (<~) :: MonadState s m => Traversal s s a b -> m b -> m () -- (<~) :: MonadState s m => Setter s s a b -> m b -> m () ---- -- As a reasonable mnemonic, this lets you store the result of a monadic -- action in a Lens rather than in a local variable. -- --
-- do foo <- bar -- ... ---- -- will store the result in a variable, while -- --
-- do foo <~ bar -- ... ---- -- will store the result in a Lens, Setter, or -- Traversal. (<~) :: MonadState s m => ASetter s s a b -> m b -> m () -- | Write to a fragment of a larger Writer format. scribe :: (MonadWriter t m, Monoid s) => ASetter s t a b -> b -> m () -- | This is a generalization of pass that alows you to modify just -- a portion of the resulting MonadWriter. passing :: MonadWriter w m => Setter w w u v -> m (a, u -> v) -> m a -- | This is a generalization of pass that alows you to modify just -- a portion of the resulting MonadWriter with access to the index -- of an IndexedSetter. ipassing :: MonadWriter w m => IndexedSetter i w w u v -> m (a, i -> u -> v) -> m a -- | This is a generalization of censor that alows you to -- censor just a portion of the resulting MonadWriter. censoring :: MonadWriter w m => Setter w w u v -> (u -> v) -> m a -> m a -- | This is a generalization of censor that alows you to -- censor just a portion of the resulting MonadWriter, with -- access to the index of an IndexedSetter. icensoring :: MonadWriter w m => IndexedSetter i w w u v -> (i -> u -> v) -> m a -> m a -- | Replace the target of a Lens or all of the targets of a -- Setter' or Traversal with a constant value, without -- changing its type. -- -- This is a type restricted version of set, which retains the -- type of the original. -- --
-- >>> set' mapped x [a,b,c,d] -- [x,x,x,x] ---- --
-- >>> set' _2 "hello" (1,"world") -- (1,"hello") ---- --
-- >>> set' mapped 0 [1,2,3,4] -- [0,0,0,0] ---- -- Note: Attempting to adjust set' a Fold or Getter -- will fail at compile time with an relatively nice error message. -- --
-- set' :: Setter' s a -> a -> s -> s -- set' :: Iso' s a -> a -> s -> s -- set' :: Lens' s a -> a -> s -> s -- set' :: Traversal' s a -> a -> s -> s --set' :: ASetter' s a -> a -> s -> s -- | Map with index. (Deprecated alias for iover). -- -- When you do not need access to the index, then mapOf is more -- liberal in what it can accept. -- --
-- mapOf l ≡ imapOf l . const ---- --
-- imapOf :: IndexedSetter i s t a b -> (i -> a -> b) -> s -> t -- imapOf :: IndexedLens i s t a b -> (i -> a -> b) -> s -> t -- imapOf :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t ---- | Deprecated: Use iover imapOf :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t -- | Map with index. This is an alias for imapOf. -- -- When you do not need access to the index, then over is more -- liberal in what it can accept. -- --
-- over l ≡ iover l . const -- iover l ≡ over l . Indexed ---- --
-- iover :: IndexedSetter i s t a b -> (i -> a -> b) -> s -> t -- iover :: IndexedLens i s t a b -> (i -> a -> b) -> s -> t -- iover :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t --iover :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t -- | Set with index. Equivalent to iover with the current value -- ignored. -- -- When you do not need access to the index, then set is more -- liberal in what it can accept. -- --
-- set l ≡ iset l . const ---- --
-- iset :: IndexedSetter i s t a b -> (i -> b) -> s -> t -- iset :: IndexedLens i s t a b -> (i -> b) -> s -> t -- iset :: IndexedTraversal i s t a b -> (i -> b) -> s -> t --iset :: AnIndexedSetter i s t a b -> (i -> b) -> s -> t -- | This is an alias for (%@=). imodifying :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m () -- | Build an IndexedSetter from an imap-like function. -- -- Your supplied function f is required to satisfy: -- --
-- f id ≡ id -- f g . f h ≡ f (g . h) ---- -- Equational reasoning: -- --
-- isets . iover ≡ id -- iover . isets ≡ id ---- -- Another way to view isets is that it takes a "semantic editor -- combinator" which has been modified to carry an index and transforms -- it into a IndexedSetter. isets :: ((i -> a -> b) -> s -> t) -> IndexedSetter i s t a b -- | Adjust every target of an IndexedSetter, IndexedLens or -- IndexedTraversal with access to the index. -- --
-- (%@~) ≡ iover ---- -- When you do not need access to the index then (%~) is more -- liberal in what it can accept. -- --
-- l %~ f ≡ l %@~ const f ---- --
-- (%@~) :: IndexedSetter i s t a b -> (i -> a -> b) -> s -> t -- (%@~) :: IndexedLens i s t a b -> (i -> a -> b) -> s -> t -- (%@~) :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t --(%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t -- | Replace every target of an IndexedSetter, IndexedLens or -- IndexedTraversal with access to the index. -- --
-- (.@~) ≡ iset ---- -- When you do not need access to the index then (.~) is more -- liberal in what it can accept. -- --
-- l .~ b ≡ l .@~ const b ---- --
-- (.@~) :: IndexedSetter i s t a b -> (i -> b) -> s -> t -- (.@~) :: IndexedLens i s t a b -> (i -> b) -> s -> t -- (.@~) :: IndexedTraversal i s t a b -> (i -> b) -> s -> t --(.@~) :: AnIndexedSetter i s t a b -> (i -> b) -> s -> t -- | Adjust every target in the current state of an IndexedSetter, -- IndexedLens or IndexedTraversal with access to the -- index. -- -- When you do not need access to the index then (%=) is more -- liberal in what it can accept. -- --
-- l %= f ≡ l %@= const f ---- --
-- (%@=) :: MonadState s m => IndexedSetter i s s a b -> (i -> a -> b) -> m () -- (%@=) :: MonadState s m => IndexedLens i s s a b -> (i -> a -> b) -> m () -- (%@=) :: MonadState s m => IndexedTraversal i s t a b -> (i -> a -> b) -> m () --(%@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m () -- | Replace every target in the current state of an IndexedSetter, -- IndexedLens or IndexedTraversal with access to the -- index. -- -- When you do not need access to the index then (.=) is more -- liberal in what it can accept. -- --
-- l .= b ≡ l .@= const b ---- --
-- (.@=) :: MonadState s m => IndexedSetter i s s a b -> (i -> b) -> m () -- (.@=) :: MonadState s m => IndexedLens i s s a b -> (i -> b) -> m () -- (.@=) :: MonadState s m => IndexedTraversal i s t a b -> (i -> b) -> m () --(.@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> b) -> m () -- | Run an arrow command and use the output to set all the targets of a -- Lens, Setter or Traversal to the result. -- -- assignA can be used very similarly to (<~), except -- that the type of the object being modified can change; for example: -- --
-- runKleisli action ((), (), ()) where -- action = assignA _1 (Kleisli (const getVal1)) -- >>> assignA _2 (Kleisli (const getVal2)) -- >>> assignA _3 (Kleisli (const getVal3)) -- getVal1 :: Either String Int -- getVal1 = ... -- getVal2 :: Either String Bool -- getVal2 = ... -- getVal3 :: Either String Char -- getVal3 = ... ---- -- has the type Either String (Int, Bool, -- Char) -- --
-- assignA :: Arrow p => Iso s t a b -> p s b -> p s t -- assignA :: Arrow p => Lens s t a b -> p s b -> p s t -- assignA :: Arrow p => Traversal s t a b -> p s b -> p s t -- assignA :: Arrow p => Setter s t a b -> p s b -> p s t --assignA :: Arrow p => ASetter s t a b -> p s b -> p s t -- | Anything Settable must be isomorphic to the Identity -- Functor. class (Applicative f, Distributive f, Traversable f) => Settable f where untaintedDot g = g `seq` rmap untainted g taintedDot g = g `seq` rmap pure g -- | Identity functor and monad. (a non-strict monad) newtype Identity a :: * -> * Identity :: a -> Identity a runIdentity :: Identity a -> a -- | mapOf is a deprecated alias for over. -- | Deprecated: Use over mapOf :: ASetter s t a b -> (a -> b) -> s -> t -- | A Lens s t a b is a purely functional reference. -- -- While a Traversal could be used for Getting like a valid -- Fold, it wasn't a valid Getter as a Getter can't -- require an Applicative constraint. -- -- Functor, however, is a constraint on both. -- --
-- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t ---- -- Every Lens is a valid Setter. -- -- Every Lens can be used for Getting like a Fold -- that doesn't use the Applicative or Contravariant. -- -- Every Lens is a valid Traversal that only uses the -- Functor part of the Applicative it is supplied. -- -- Every Lens can be used for Getting like a valid -- Getter. -- -- Since every Lens can be used for Getting like a valid -- Getter it follows that it must view exactly one element in the -- structure. -- -- The Lens laws follow from this property and the desire for it -- to act like a Traversable when used as a Traversal. -- -- In the examples below, getter and setter are -- supplied as example getters and setters, and are not actual functions -- supplied by this package. module Control.Lens.Lens -- | A Lens is actually a lens family as described in -- http://comonad.com/reader/2012/mirrored-lenses/. -- -- With great power comes great responsibility and a Lens is -- subject to the three common sense Lens laws: -- -- 1) You get back what you put in: -- --
-- view l (set l v s) ≡ v ---- -- 2) Putting back what you got doesn't change anything: -- --
-- set l (view l s) s ≡ s ---- -- 3) Setting twice is the same as setting once: -- --
-- set l v' (set l v s) ≡ set l v' s ---- -- These laws are strong enough that the 4 type parameters of a -- Lens cannot vary fully independently. For more on how they -- interact, read the "Why is it a Lens Family?" section of -- http://comonad.com/reader/2012/mirrored-lenses/. -- -- There are some emergent properties of these laws: -- -- 1) set l s must be injective for every s This -- is a consequence of law #1 -- -- 2) set l must be surjective, because of law #2, which -- indicates that it is possible to obtain any v from some -- s such that set s v = s -- -- 3) Given just the first two laws you can prove a weaker form of law #3 -- where the values v that you are setting match: -- --
-- set l v (set l v s) ≡ set l v s ---- -- Every Lens can be used directly as a Setter or -- Traversal. -- -- You can also use a Lens for Getting as if it were a -- Fold or Getter. -- -- Since every Lens is a valid Traversal, the -- Traversal laws are required of any Lens you create: -- --
-- l pure ≡ pure -- fmap (l f) . l g ≡ getCompose . l (Compose . fmap f . g) ---- --
-- type Lens s t a b = forall f. Functor f => LensLike f s t a b --type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t -- |
-- type Lens' = Simple Lens --type Lens' s a = Lens s s a a -- | Every IndexedLens is a valid Lens and a valid -- IndexedTraversal. type IndexedLens i s t a b = forall f p. (Indexable i p, Functor f) => p a (f b) -> s -> f t -- |
-- type IndexedLens' i = Simple (IndexedLens i) --type IndexedLens' i s a = IndexedLens i s s a a -- | When you see this as an argument to a function, it expects a -- Lens. -- -- This type can also be used when you need to store a Lens in a -- container, since it is rank-1. You can turn them back into a -- Lens with cloneLens, or use it directly with combinators -- like storing and (^#). type ALens s t a b = LensLike (Pretext (->) a b) s t a b -- |
-- type ALens' = Simple ALens --type ALens' s a = ALens s s a a -- | When you see this as an argument to a function, it expects an -- IndexedLens type AnIndexedLens i s t a b = Optical (Indexed i) (->) (Pretext (Indexed i) a b) s t a b -- |
-- type AnIndexedLens' = Simple (AnIndexedLens i) --type AnIndexedLens' i s a = AnIndexedLens i s s a a -- | Build a Lens from a getter and a setter. -- --
-- lens :: Functor f => (s -> a) -> (s -> b -> t) -> (a -> f b) -> s -> f t ---- --
-- >>> s ^. lens getter setter -- getter s ---- --
-- >>> s & lens getter setter .~ b -- setter s b ---- --
-- >>> s & lens getter setter %~ f -- setter s (f (getter s)) ---- --
-- lens :: (s -> a) -> (s -> a -> s) -> Lens' s a --lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b -- | Build an IndexedLens from a Getter and a Setter. ilens :: (s -> (i, a)) -> (s -> b -> t) -> IndexedLens i s t a b -- | Build an index-preserving Lens from a Getter and a -- Setter. iplens :: (s -> a) -> (s -> b -> t) -> IndexPreservingLens s t a b -- | (%%~) can be used in one of two scenarios: -- -- When applied to a Lens, it can edit the target of the -- Lens in a structure, extracting a functorial result. -- -- When applied to a Traversal, it can edit the targets of the -- traversals, extracting an applicative summary of its actions. -- --
-- >>> [66,97,116,109,97,110] & each %%~ \a -> ("na", chr a) -- ("nananananana","Batman") ---- -- For all that the definition of this combinator is just: -- --
-- (%%~) ≡ id ---- -- It may be beneficial to think about it as if it had these even more -- restricted types, however: -- --
-- (%%~) :: Functor f => Iso s t a b -> (a -> f b) -> s -> f t -- (%%~) :: Functor f => Lens s t a b -> (a -> f b) -> s -> f t -- (%%~) :: Applicative f => Traversal s t a b -> (a -> f b) -> s -> f t ---- -- When applied to a Traversal, it can edit the targets of the -- traversals, extracting a supplemental monoidal summary of its actions, -- by choosing f = ((,) m) -- --
-- (%%~) :: Iso s t a b -> (a -> (r, b)) -> s -> (r, t) -- (%%~) :: Lens s t a b -> (a -> (r, b)) -> s -> (r, t) -- (%%~) :: Monoid m => Traversal s t a b -> (a -> (m, b)) -> s -> (m, t) --(%%~) :: LensLike f s t a b -> (a -> f b) -> s -> f t -- | Modify the target of a Lens in the current state returning some -- extra information of type r or modify all targets of a -- Traversal in the current state, extracting extra information of -- type r and return a monoidal summary of the changes. -- --
-- >>> runState (_1 %%= \x -> (f x, g x)) (a,b) -- (f a,(g a,b)) ---- --
-- (%%=) ≡ (state .) ---- -- It may be useful to think of (%%=), instead, as having either -- of the following more restricted type signatures: -- --
-- (%%=) :: MonadState s m => Iso s s a b -> (a -> (r, b)) -> m r -- (%%=) :: MonadState s m => Lens s s a b -> (a -> (r, b)) -> m r -- (%%=) :: (MonadState s m, Monoid r) => Traversal s s a b -> (a -> (r, b)) -> m r --(%%=) :: MonadState s m => Over p ((,) r) s s a b -> p a (r, b) -> m r -- | Adjust the target of an IndexedLens returning a supplementary -- result, or adjust all of the targets of an IndexedTraversal and -- return a monoidal summary of the supplementary results and the answer. -- --
-- (%%@~) ≡ withIndex ---- --
-- (%%@~) :: Functor f => IndexedLens i s t a b -> (i -> a -> f b) -> s -> f t -- (%%@~) :: Applicative f => IndexedTraversal i s t a b -> (i -> a -> f b) -> s -> f t ---- -- In particular, it is often useful to think of this function as having -- one of these even more restricted type signatures: -- --
-- (%%@~) :: IndexedLens i s t a b -> (i -> a -> (r, b)) -> s -> (r, t) -- (%%@~) :: Monoid r => IndexedTraversal i s t a b -> (i -> a -> (r, b)) -> s -> (r, t) --(%%@~) :: IndexedLensLike i f s t a b -> (i -> a -> f b) -> s -> f t -- | Adjust the target of an IndexedLens returning a supplementary -- result, or adjust all of the targets of an IndexedTraversal -- within the current state, and return a monoidal summary of the -- supplementary results. -- --
-- l %%@= f ≡ state (l %%@~ f) ---- --
-- (%%@=) :: MonadState s m => IndexedLens i s s a b -> (i -> a -> (r, b)) -> s -> m r -- (%%@=) :: (MonadState s m, Monoid r) => IndexedTraversal i s s a b -> (i -> a -> (r, b)) -> s -> m r --(%%@=) :: MonadState s m => IndexedLensLike i ((,) r) s s a b -> (i -> a -> (r, b)) -> m r -- | Adjust the target of an IndexedLens returning the intermediate -- result, or adjust all of the targets of an IndexedTraversal and -- return a monoidal summary along with the answer. -- --
-- l <%~ f ≡ l <%@~ const f ---- -- When you do not need access to the index then (<%~) is more -- liberal in what it can accept. -- -- If you do not need the intermediate result, you can use (%@~) -- or even (%~). -- --
-- (<%@~) :: IndexedLens i s t a b -> (i -> a -> b) -> s -> (b, t) -- (<%@~) :: Monoid b => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> (b, t) --(<%@~) :: Over (Indexed i) ((,) b) s t a b -> (i -> a -> b) -> s -> (b, t) -- | Adjust the target of an IndexedLens returning the intermediate -- result, or adjust all of the targets of an IndexedTraversal -- within the current state, and return a monoidal summary of the -- intermediate results. -- --
-- (<%@=) :: MonadState s m => IndexedLens i s s a b -> (i -> a -> b) -> m b -- (<%@=) :: (MonadState s m, Monoid b) => IndexedTraversal i s s a b -> (i -> a -> b) -> m b --(<%@=) :: MonadState s m => IndexedLensLike i ((,) b) s s a b -> (i -> a -> b) -> m b -- | Adjust the target of an IndexedLens returning the old value, or -- adjust all of the targets of an IndexedTraversal and return a -- monoidal summary of the old values along with the answer. -- --
-- (<<%@~) :: IndexedLens i s t a b -> (i -> a -> b) -> s -> (a, t) -- (<<%@~) :: Monoid a => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> (a, t) --(<<%@~) :: Over (Indexed i) ((,) a) s t a b -> (i -> a -> b) -> s -> (a, t) -- | Adjust the target of an IndexedLens returning the old value, or -- adjust all of the targets of an IndexedTraversal within the -- current state, and return a monoidal summary of the old values. -- --
-- (<<%@=) :: MonadState s m => IndexedLens i s s a b -> (i -> a -> b) -> m a -- (<<%@=) :: (MonadState s m, Monoid b) => IndexedTraversal i s s a b -> (i -> a -> b) -> m a --(<<%@=) :: MonadState s m => IndexedLensLike i ((,) a) s s a b -> (i -> a -> b) -> m a -- | Passes the result of the left side to the function on the right side -- (forward pipe operator). -- -- This is the flipped version of ($), which is more common in -- languages like F# as (|>) where it is needed for -- inference. Here it is supplied for notational convenience and given a -- precedence that allows it to be nested inside uses of ($). -- --
-- >>> a & f -- f a ---- --
-- >>> "hello" & length & succ -- 6 ---- -- This combinator is commonly used when applying multiple Lens -- operations in sequence. -- --
-- >>> ("hello","world") & _1.element 0 .~ 'j' & _1.element 4 .~ 'y' -- ("jelly","world") ---- -- This reads somewhat similar to: -- --
-- >>> flip execState ("hello","world") $ do _1.element 0 .= 'j'; _1.element 4 .= 'y' -- ("jelly","world") --(&) :: a -> (a -> b) -> b -- | Infix flipped fmap. -- --
-- (<&>) = flip fmap --(<&>) :: Functor f => f a -> (a -> b) -> f b -- | This is convenient to flip argument order of composite -- functions defined as: -- --
-- fab ?? a = fmap ($ a) fab ---- -- For the Functor instance f = ((->) r) you can -- reason about this function as if the definition was (??) ≡ -- flip: -- --
-- >>> (h ?? x) a -- h a x ---- --
-- >>> execState ?? [] $ modify (1:) -- [1] ---- --
-- >>> over _2 ?? ("hello","world") $ length -- ("hello",5) ---- --
-- >>> over ?? length ?? ("hello","world") $ _2 -- ("hello",5) --(??) :: Functor f => f (a -> b) -> a -> f b -- | This can be used to chain lens operations using op= syntax -- rather than op~ syntax for simple non-type-changing cases. -- --
-- >>> (10,20) & _1 .~ 30 & _2 .~ 40 -- (30,40) ---- --
-- >>> (10,20) &~ do _1 .= 30; _2 .= 40 -- (30,40) ---- -- This does not support type-changing assignment, e.g. -- --
-- >>> (10,20) & _1 .~ "hello" -- ("hello",20) --(&~) :: s -> State s a -> s -- | Merge two lenses, getters, setters, folds or traversals. -- --
-- chosen ≡ choosing id id ---- --
-- choosing :: Getter s a -> Getter s' a -> Getter (Either s s') a -- choosing :: Fold s a -> Fold s' a -> Fold (Either s s') a -- choosing :: Lens' s a -> Lens' s' a -> Lens' (Either s s') a -- choosing :: Traversal' s a -> Traversal' s' a -> Traversal' (Either s s') a -- choosing :: Setter' s a -> Setter' s' a -> Setter' (Either s s') a --choosing :: Functor f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f (Either s s') (Either t t') a b -- | This is a Lens that updates either side of an Either, -- where both sides have the same type. -- --
-- chosen ≡ choosing id id ---- --
-- >>> Left a^.chosen -- a ---- --
-- >>> Right a^.chosen -- a ---- --
-- >>> Right "hello"^.chosen -- "hello" ---- --
-- >>> Right a & chosen *~ b -- Right (a * b) ---- --
-- chosen :: Lens (Either a a) (Either b b) a b -- chosen f (Left a) = Left <$> f a -- chosen f (Right a) = Right <$> f a --chosen :: IndexPreservingLens (Either a a) (Either b b) a b -- | alongside makes a Lens from two other lenses or a -- Getter from two other getters by executing them on their -- respective halves of a product. -- --
-- >>> (Left a, Right b)^.alongside chosen chosen -- (a,b) ---- --
-- >>> (Left a, Right b) & alongside chosen chosen .~ (c,d) -- (Left c,Right d) ---- --
-- alongside :: Lens s t a b -> Lens s' t' a' b' -> Lens (s,s') (t,t') (a,a') (b,b') -- alongside :: Getter s t a b -> Getter s' t' a' b' -> Getter (s,s') (t,t') (a,a') (b,b') --alongside :: LensLike (AlongsideLeft f b') s t a b -> LensLike (AlongsideRight f t) s' t' a' b' -> LensLike f (s, s') (t, t') (a, a') (b, b') -- | Lift a Lens so it can run under a function (or other -- corepresentable profunctor). -- --
-- inside :: Lens s t a b -> Lens (e -> s) (e -> t) (e -> a) (e -> b) ---- --
-- >>> (\x -> (x-1,x+1)) ^. inside _1 $ 5 -- 4 ---- --
-- >>> runState (modify (1:) >> modify (2:)) ^. (inside _2) $ [] -- [2,1] --inside :: Corepresentable p => ALens s t a b -> Lens (p e s) (p e t) (p e a) (p e b) -- | Modify the target of a Lens and return the result. -- -- When you do not need the result of the addition, (%~) is more -- flexible. -- --
-- (<%~) :: Lens s t a b -> (a -> b) -> s -> (b, t) -- (<%~) :: Iso s t a b -> (a -> b) -> s -> (b, t) -- (<%~) :: Monoid b => Traversal s t a b -> (a -> b) -> s -> (b, t) --(<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t) -- | Increment the target of a numerically valued Lens and return -- the result. -- -- When you do not need the result of the addition, (+~) is more -- flexible. -- --
-- (<+~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<+~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<+~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Decrement the target of a numerically valued Lens and return -- the result. -- -- When you do not need the result of the subtraction, (-~) is -- more flexible. -- --
-- (<-~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<-~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<-~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Multiply the target of a numerically valued Lens and return the -- result. -- -- When you do not need the result of the multiplication, (*~) is -- more flexible. -- --
-- (<*~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<*~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<*~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Divide the target of a fractionally valued Lens and return the -- result. -- -- When you do not need the result of the division, (//~) is more -- flexible. -- --
-- (<//~) :: Fractional a => Lens' s a -> a -> s -> (a, s) -- (<//~) :: Fractional a => Iso' s a -> a -> s -> (a, s) --(/~) :: Fractional a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Raise the target of a numerically valued Lens to a non-negative -- Integral power and return the result. -- -- When you do not need the result of the operation, (^~) is more -- flexible. -- --
-- (<^~) :: (Num a, Integral e) => Lens' s a -> e -> s -> (a, s) -- (<^~) :: (Num a, Integral e) => Iso' s a -> e -> s -> (a, s) --(<^~) :: (Num a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t) -- | Raise the target of a fractionally valued Lens to an -- Integral power and return the result. -- -- When you do not need the result of the operation, (^^~) is more -- flexible. -- --
-- (<^^~) :: (Fractional a, Integral e) => Lens' s a -> e -> s -> (a, s) -- (<^^~) :: (Fractional a, Integral e) => Iso' s a -> e -> s -> (a, s) --(<^^~) :: (Fractional a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t) -- | Raise the target of a floating-point valued Lens to an -- arbitrary power and return the result. -- -- When you do not need the result of the operation, (**~) is more -- flexible. -- --
-- (<**~) :: Floating a => Lens' s a -> a -> s -> (a, s) -- (<**~) :: Floating a => Iso' s a -> a -> s -> (a, s) --(<**~) :: Floating a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Logically || a Boolean valued Lens and return the -- result. -- -- When you do not need the result of the operation, (||~) is more -- flexible. -- --
-- (<||~) :: Lens' s Bool -> Bool -> s -> (Bool, s) -- (<||~) :: Iso' s Bool -> Bool -> s -> (Bool, s) --(<||~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t) -- | Logically && a Boolean valued Lens and return -- the result. -- -- When you do not need the result of the operation, (&&~) -- is more flexible. -- --
-- (<&&~) :: Lens' s Bool -> Bool -> s -> (Bool, s) -- (<&&~) :: Iso' s Bool -> Bool -> s -> (Bool, s) --(<&&~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t) -- | mappend a monoidal value onto the end of the target of a -- Lens and return the result. -- -- When you do not need the result of the operation, (<>~) -- is more flexible. (<<>~) :: Monoid m => LensLike ((,) m) s t m m -> m -> s -> (m, t) -- | Modify the target of a Lens, but return the old value. -- -- When you do not need the old value, (%~) is more flexible. -- --
-- (<<%~) :: Lens s t a b -> (a -> b) -> s -> (a, t) -- (<<%~) :: Iso 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) -- | Replace the target of a Lens, but return the old value. -- -- When you do not need the old value, (.~) is more flexible. -- --
-- (<<.~) :: Lens s t a b -> b -> s -> (a, t) -- (<<.~) :: Iso 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) -- | Increment the target of a numerically valued Lens and return -- the old value. -- -- When you do not need the old value, (+~) is more flexible. -- --
-- >>> (a,b) & _1 <<+~ c -- (a,(a + c,b)) ---- --
-- >>> (a,b) & _2 <<+~ c -- (b,(a,b + c)) ---- --
-- (<<+~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<<+~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<<+~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Decrement the target of a numerically valued Lens and return -- the old value. -- -- When you do not need the old value, (-~) is more flexible. -- --
-- >>> (a,b) & _1 <<-~ c -- (a,(a - c,b)) ---- --
-- >>> (a,b) & _2 <<-~ c -- (b,(a,b - c)) ---- --
-- (<<-~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<<-~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<<-~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Multiply the target of a numerically valued Lens and return the -- old value. -- -- When you do not need the old value, (-~) is more flexible. -- --
-- >>> (a,b) & _1 <<*~ c -- (a,(a * c,b)) ---- --
-- >>> (a,b) & _2 <<*~ c -- (b,(a,b * c)) ---- --
-- (<<*~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<<*~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<<*~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Divide the target of a numerically valued Lens and return the -- old value. -- -- When you do not need the old value, (//~) is more flexible. -- --
-- >>> (a,b) & _1 <<//~ c -- (a,(a / c,b)) ---- --
-- >>> ("Hawaii",10) & _2 <<//~ 2 -- (10.0,("Hawaii",5.0)) ---- --
-- (<<//~) :: Fractional a => Lens' s a -> a -> s -> (a, s) -- (<<//~) :: Fractional a => Iso' s a -> a -> s -> (a, s) --(</~) :: Fractional a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Raise the target of a numerically valued Lens to a non-negative -- power and return the old value. -- -- When you do not need the old value, (^~) is more flexible. -- --
-- (<<^~) :: (Num a, Integral e) => Lens' s a -> e -> s -> (a, s) -- (<<^~) :: (Num a, Integral e) => Iso' s a -> e -> s -> (a, s) --(<<^~) :: (Num a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s) -- | Raise the target of a fractionally valued Lens to an integral -- power and return the old value. -- -- When you do not need the old value, (^^~) is more flexible. -- --
-- (<<^^~) :: (Fractional a, Integral e) => Lens' s a -> e -> s -> (a, s) -- (<<^^~) :: (Fractional a, Integral e) => Iso' s a -> e -> S -> (a, s) --(<<^^~) :: (Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s) -- | Raise the target of a floating-point valued Lens to an -- arbitrary power and return the old value. -- -- When you do not need the old value, (**~) is more flexible. -- --
-- >>> (a,b) & _1 <<**~ c -- (a,(a**c,b)) ---- --
-- >>> (a,b) & _2 <<**~ c -- (b,(a,b**c)) ---- --
-- (<<**~) :: Floating a => Lens' s a -> a -> s -> (a, s) -- (<<**~) :: Floating a => Iso' s a -> a -> s -> (a, s) --(<<**~) :: Floating a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Logically || the target of a Bool-valued Lens and -- return the old value. -- -- When you do not need the old value, (||~) is more flexible. -- --
-- >>> (False,6) & _1 <<||~ True -- (False,(True,6)) ---- --
-- >>> ("hello",True) & _2 <<||~ False -- (True,("hello",True)) ---- --
-- (<<||~) :: Lens' s Bool -> Bool -> s -> (Bool, s) -- (<<||~) :: Iso' s Bool -> Bool -> s -> (Bool, s) --(<<||~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s) -- | Logically && the target of a Bool-valued -- Lens and return the old value. -- -- When you do not need the old value, (&&~) is more -- flexible. -- --
-- >>> (False,6) & _1 <<&&~ True -- (False,(False,6)) ---- --
-- >>> ("hello",True) & _2 <<&&~ False -- (True,("hello",False)) ---- --
-- (<<&&~) :: Lens' s Bool -> Bool -> s -> (Bool, s) -- (<<&&~) :: Iso' s Bool -> Bool -> s -> (Bool, s) --(<<&&~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s) -- | Modify the target of a monoidally valued Lens by -- mappending a new value and return the old value. -- -- When you do not need the old value, (<>~) is more -- flexible. -- --
-- >>> (Sum a,b) & _1 <<<>~ Sum c -- (Sum {getSum = a},(Sum {getSum = a + c},b)) ---- --
-- >>> _2 <<<>~ ", 007" $ ("James", "Bond") -- ("Bond",("James","Bond, 007")) ---- --
-- (<<<>~) :: Monoid r => Lens' s r -> r -> s -> (r, s) -- (<<<>~) :: Monoid r => Iso' s r -> r -> s -> (r, s) --(<<<>~) :: Monoid r => LensLike' ((,) r) s r -> r -> s -> (r, s) -- | Modify the target of a Lens into your Monad's state by -- a user supplied function and return the result. -- -- When applied to a Traversal, it this will return a monoidal -- summary of all of the intermediate results. -- -- When you do not need the result of the operation, (%=) is more -- flexible. -- --
-- (<%=) :: MonadState s m => Lens' s a -> (a -> a) -> m a -- (<%=) :: MonadState s m => Iso' s a -> (a -> a) -> m a -- (<%=) :: (MonadState s m, Monoid a) => Traversal' s a -> (a -> a) -> m a --(<%=) :: MonadState s m => LensLike ((,) b) s s a b -> (a -> b) -> m b -- | Add to the target of a numerically valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the addition, (+=) is more -- flexible. -- --
-- (<+=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<+=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Subtract from the target of a numerically valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the subtraction, (-=) is -- more flexible. -- --
-- (<-=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<-=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Multiply the target of a numerically valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the multiplication, (*=) is -- more flexible. -- --
-- (<*=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<*=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Divide the target of a fractionally valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the division, (//=) is more -- flexible. -- --
-- (<//=) :: (MonadState s m, Fractional a) => Lens' s a -> a -> m a -- (<//=) :: (MonadState s m, Fractional a) => Iso' s a -> a -> m a --(/=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a -- | Raise the target of a numerically valued Lens into your -- Monad's state to a non-negative Integral power and -- return the result. -- -- When you do not need the result of the operation, (^=) is more -- flexible. -- --
-- (<^=) :: (MonadState s m, Num a, Integral e) => Lens' s a -> e -> m a -- (<^=) :: (MonadState s m, Num a, Integral e) => Iso' s a -> e -> m a --(<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a -- | Raise the target of a fractionally valued Lens into your -- Monad's state to an Integral power and return the -- result. -- -- When you do not need the result of the operation, (^^=) is more -- flexible. -- --
-- (<^^=) :: (MonadState s m, Fractional b, Integral e) => Lens' s a -> e -> m a -- (<^^=) :: (MonadState s m, Fractional b, Integral e) => Iso' s a -> e -> m a --(<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a -- | Raise the target of a floating-point valued Lens into your -- Monad's state to an arbitrary power and return the result. -- -- When you do not need the result of the operation, (**=) is more -- flexible. -- --
-- (<**=) :: (MonadState s m, Floating a) => Lens' s a -> a -> m a -- (<**=) :: (MonadState s m, Floating a) => Iso' s a -> a -> m a --(<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a -- | Logically || a Boolean valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the operation, (||=) is more -- flexible. -- --
-- (<||=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool -- (<||=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool --(<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool -- | Logically && a Boolean valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the operation, (&&=) -- is more flexible. -- --
-- (<&&=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool -- (<&&=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool --(<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool -- | mappend a monoidal value onto the end of the target of a -- Lens into your Monad's state and return the result. -- -- When you do not need the result of the operation, (<>=) -- is more flexible. (<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r -- | Modify the target of a Lens into your Monad's state by -- a user supplied function and return the old value that was -- replaced. -- -- When applied to a Traversal, it this will return a monoidal -- summary of all of the old values present. -- -- When you do not need the result of the operation, (%=) is more -- flexible. -- --
-- (<<%=) :: MonadState s m => Lens' s a -> (a -> a) -> m a -- (<<%=) :: MonadState s m => Iso' s a -> (a -> a) -> m a -- (<<%=) :: (MonadState s m, Monoid a) => Traversal' s a -> (a -> a) -> m a ---- --
-- (<<%=) :: MonadState s m => LensLike ((,)a) s s a b -> (a -> b) -> m a --(<<%=) :: (Strong p, MonadState s m) => Over p ((,) a) s s a b -> p a b -> m a -- | Replace the target of a Lens into your Monad's state -- with a user supplied value and return the old value that was -- replaced. -- -- When applied to a Traversal, it this will return a monoidal -- summary of all of the old values present. -- -- When you do not need the result of the operation, (.=) is more -- flexible. -- --
-- (<<.=) :: MonadState s m => Lens' s a -> a -> m a -- (<<.=) :: MonadState s m => Iso' s a -> a -> m a -- (<<.=) :: (MonadState s m, Monoid t) => Traversal' s a -> a -> m a --(<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a -- | Modify the target of a Lens into your Monad's state by -- adding a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (+=) is more -- flexible. -- --
-- (<<+=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<<+=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monad's state by -- subtracting a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (-=) is more -- flexible. -- --
-- (<<-=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<<-=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monad's state by -- multipling a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (*=) is more -- flexible. -- --
-- (<<*=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<<*=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monads state by -- dividing by a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (//=) is more -- flexible. -- --
-- (<<//=) :: (MonadState s m, Fractional a) => Lens' s a -> a -> m a -- (<<//=) :: (MonadState s m, Fractional a) => Iso' s a -> a -> m a --(</=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monad's state by -- raising it by a non-negative power and return the old value -- that was replaced. -- -- When you do not need the result of the operation, (^=) is more -- flexible. -- --
-- (<<^=) :: (MonadState s m, Num a, Integral e) => Lens' s a -> e -> m a -- (<<^=) :: (MonadState s m, Num a, Integral e) => Iso' s a -> a -> m a --(<<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a -- | Modify the target of a Lens into your Monad's state by -- raising it by an integral power and return the old value that -- was replaced. -- -- When you do not need the result of the operation, (^^=) is more -- flexible. -- --
-- (<<^^=) :: (MonadState s m, Fractional a, Integral e) => Lens' s a -> e -> m a -- (<<^^=) :: (MonadState s m, Fractional a, Integral e) => Iso' s a -> e -> m a --(<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a -- | Modify the target of a Lens into your Monad's state by -- raising it by an arbitrary power and return the old value that -- was replaced. -- -- When you do not need the result of the operation, (**=) is more -- flexible. -- --
-- (<<**=) :: (MonadState s m, Floating a) => Lens' s a -> a -> m a -- (<<**=) :: (MonadState s m, Floating a) => Iso' s a -> a -> m a --(<<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monad's state by -- taking its logical || with a value and return the old -- value that was replaced. -- -- When you do not need the result of the operation, (||=) is more -- flexible. -- --
-- (<<||=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool -- (<<||=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool --(<<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool -- | Modify the target of a Lens into your Monad's state by -- taking its logical && with a value and return the -- old value that was replaced. -- -- When you do not need the result of the operation, (&&=) -- is more flexible. -- --
-- (<<&&=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool -- (<<&&=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool --(<<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool -- | Modify the target of a Lens into your Monad's state by -- mappending a value and return the old value that was -- replaced. -- -- When you do not need the result of the operation, (<>=) -- is more flexible. -- --
-- (<<<>=) :: (MonadState s m, Monoid r) => Lens' s r -> r -> m r -- (<<<>=) :: (MonadState s m, Monoid r) => Iso' s r -> r -> m r --(<<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r -- | Run a monadic action, and set the target of Lens to its result. -- --
-- (<<~) :: MonadState s m => Iso s s a b -> m b -> m b -- (<<~) :: MonadState s m => Lens s s a b -> m b -> m b ---- -- NB: This is limited to taking an actual Lens than admitting a -- Traversal because there are potential loss of state issues -- otherwise. (<<~) :: MonadState s m => ALens s s a b -> m b -> m b -- | Cloning a Lens is one way to make sure you aren't given -- something weaker, such as a Traversal and can be used as a way -- to pass around lenses that have to be monomorphic in f. -- -- Note: This only accepts a proper Lens. -- --
-- >>> let example l x = set (cloneLens l) (x^.cloneLens l + 1) x in example _2 ("hello",1,"you") -- ("hello",2,"you") --cloneLens :: ALens s t a b -> Lens s t a b -- | Clone a Lens as an IndexedPreservingLens that just -- passes through whatever index is on any IndexedLens, -- IndexedFold, IndexedGetter or IndexedTraversal it -- is composed with. cloneIndexPreservingLens :: ALens s t a b -> IndexPreservingLens s t a b -- | Clone an IndexedLens as an IndexedLens with the same -- index. cloneIndexedLens :: AnIndexedLens i s t a b -> IndexedLens i s t a b -- | over for Arrows. -- -- Unlike over, overA can't accept a simple Setter, -- but requires a full lens, or close enough. -- --
-- overA :: Arrow ar => Lens s t a b -> ar a b -> ar s t --overA :: Arrow ar => LensLike (Context a b) s t a b -> ar a b -> ar s t -- | A version of set that works on ALens. -- --
-- >>> storing _2 "world" ("hello","there") -- ("hello","world") --storing :: ALens s t a b -> b -> s -> t -- | A version of (^.) that works on ALens. -- --
-- >>> ("hello","world")^#_2 -- "world" --(^#) :: s -> ALens s t a b -> a -- | A version of (.~) that works on ALens. -- --
-- >>> ("hello","there") & _2 #~ "world" -- ("hello","world") --(#~) :: ALens s t a b -> b -> s -> t -- | A version of (%~) that works on ALens. -- --
-- >>> ("hello","world") & _2 #%~ length -- ("hello",5) --(#%~) :: ALens s t a b -> (a -> b) -> s -> t -- | A version of (%%~) that works on ALens. -- --
-- >>> ("hello","world") & _2 #%%~ \x -> (length x, x ++ "!") -- (5,("hello","world!")) --(#%%~) :: Functor f => ALens s t a b -> (a -> f b) -> s -> f t -- | A version of (<.~) that works on ALens. -- --
-- >>> ("hello","there") & _2 <#~ "world" -- ("world",("hello","world")) --(<#~) :: ALens s t a b -> b -> s -> (b, t) -- | A version of (<%~) that works on ALens. -- --
-- >>> ("hello","world") & _2 <#%~ length -- (5,("hello",5)) --(<#%~) :: ALens s t a b -> (a -> b) -> s -> (b, t) -- | A version of (.=) that works on ALens. (#=) :: MonadState s m => ALens s s a b -> b -> m () -- | A version of (%=) that works on ALens. (#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m () -- | A version of (%%=) that works on ALens. (#%%=) :: MonadState s m => ALens s s a b -> (a -> (r, b)) -> m r -- | A version of (<.=) that works on ALens. (<#=) :: MonadState s m => ALens s s a b -> b -> m b -- | A version of (<%=) that works on ALens. (<#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m b -- | There is a field for every type in the Void. Very zen. -- --
-- >>> [] & mapped.devoid +~ 1 -- [] ---- --
-- >>> Nothing & mapped.devoid %~ abs -- Nothing ---- --
-- devoid :: Lens' Void a --devoid :: Over p f Void Void a b -- | We can always retrieve a () from any type. -- --
-- >>> "hello"^.united -- () ---- --
-- >>> "hello" & united .~ () -- "hello" --united :: Lens' a () -- | The indexed store can be used to characterize a Lens and is -- used by clone. -- -- Context a b t is isomorphic to newtype -- Context a b t = Context { runContext :: forall f. -- Functor f => (a -> f b) -> f t }, and to -- exists s. (s, Lens s t a b). -- -- A Context is like a Lens that has already been applied -- to a some structure. data Context a b t Context :: (b -> t) -> a -> Context a b t -- |
-- type Context' a s = Context a a s --type Context' a = Context a a -- | This Lens lets you view the current pos of -- any indexed store comonad and seek to a new position. This -- reduces the API for working these instances to a single Lens. -- --
-- ipos w ≡ w ^. locus -- iseek s w ≡ w & locus .~ s -- iseeks f w ≡ w & locus %~ f ---- --
-- locus :: Lens' (Context' a s) a -- locus :: Conjoined p => Lens' (Pretext' p a s) a -- locus :: Conjoined p => Lens' (PretextT' p g a s) a --locus :: IndexedComonadStore p => Lens (p a c s) (p b c s) a b -- | Fuse a composition of lenses using Yoneda to provide -- fmap fusion. -- -- In general, given a pair of lenses foo and bar -- --
-- fusing (foo.bar) = foo.bar ---- -- however, foo and bar are either going to fmap -- internally or they are trivial. -- -- fusing exploits the Yoneda lemma to merge these separate -- uses into a single fmap. -- -- This is particularly effective when the choice of functor f -- is unknown at compile time or when the Lens foo.bar in -- the above description is recursive or complex enough to prevent -- inlining. -- --
-- fusing :: Lens s t a b -> Lens s t a b --fusing :: Functor f => LensLike (Yoneda f) s t a b -> LensLike f s t a b module Control.Lens.Tuple -- | Provides access to 1st field of a tuple. class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where _1 = ix proxyN0 _1 :: Field1 s t a b => Lens s t a b -- | Provides access to the 2nd field of a tuple. class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where _2 = ix proxyN1 _2 :: Field2 s t a b => Lens s t a b -- | Provides access to the 3rd field of a tuple. class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where _3 = ix proxyN2 _3 :: Field3 s t a b => Lens s t a b -- | Provide access to the 4th field of a tuple. class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where _4 = ix proxyN3 _4 :: Field4 s t a b => Lens s t a b -- | Provides access to the 5th field of a tuple. class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where _5 = ix proxyN4 _5 :: Field5 s t a b => Lens s t a b -- | Provides access to the 6th element of a tuple. class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where _6 = ix proxyN5 _6 :: Field6 s t a b => Lens s t a b -- | Provide access to the 7th field of a tuple. class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where _7 = ix proxyN6 _7 :: Field7 s t a b => Lens s t a b -- | Provide access to the 8th field of a tuple. class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where _8 = ix proxyN7 _8 :: Field8 s t a b => Lens s t a b -- | Provides access to the 9th field of a tuple. class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where _9 = ix proxyN8 _9 :: Field9 s t a b => Lens s t a b -- | Strict version of _1 _1' :: Field1 s t a b => Lens s t a b -- | Strict version of _2 _2' :: Field2 s t a b => Lens s t a b -- | Strict version of _3 _3' :: Field3 s t a b => Lens s t a b -- | Strict version of _4 _4' :: Field4 s t a b => Lens s t a b -- | Strict version of _5 _5' :: Field5 s t a b => Lens s t a b -- | Strict version of _6 _6' :: Field6 s t a b => Lens s t a b -- | Strict version of _7 _7' :: Field7 s t a b => Lens s t a b -- | Strict version of _8 _8' :: Field8 s t a b => Lens s t a b -- | Strict version of _9 _9' :: Field9 s t a b => Lens s t a b instance (GT (GSize s) n ~ F, n' ~ Subtract (GSize s) n, GIxed n' s' t' a b) => GIxed' F n s s' s t' a b instance (GT (GSize s) n ~ T, GT (GSize t) n ~ T, GIxed n s t a b) => GIxed' T n s s' t s' a b instance (p ~ GT (GSize s) n, p ~ GT (GSize t) n, GIxed' p n s s' t t' a b) => GIxed n (s :*: s') (t :*: t') a b instance GIxed n s t a b => GIxed n (M1 i c s) (M1 i c t) a b instance GIxed N0 (K1 i a) (K1 i b) a b instance Field9 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i') i i' instance Field8 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h', i) h h' instance Field8 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h') h h' instance Field7 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g', h, i) g g' instance Field7 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g', h) g g' instance Field7 (a, b, c, d, e, f, g) (a, b, c, d, e, f, g') g g' instance Field6 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f', g, h, i) f f' instance Field6 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f', g, h) f f' instance Field6 (a, b, c, d, e, f, g) (a, b, c, d, e, f', g) f f' instance Field6 (a, b, c, d, e, f) (a, b, c, d, e, f') f f' instance Field5 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e', f, g, h, i) e e' instance Field5 (a, b, c, d, e, f, g, h) (a, b, c, d, e', f, g, h) e e' instance Field5 (a, b, c, d, e, f, g) (a, b, c, d, e', f, g) e e' instance Field5 (a, b, c, d, e, f) (a, b, c, d, e', f) e e' instance Field5 (a, b, c, d, e) (a, b, c, d, e') e e' instance Field4 (a, b, c, d, e, f, g, h, i) (a, b, c, d', e, f, g, h, i) d d' instance Field4 (a, b, c, d, e, f, g, h) (a, b, c, d', e, f, g, h) d d' instance Field4 (a, b, c, d, e, f, g) (a, b, c, d', e, f, g) d d' instance Field4 (a, b, c, d, e, f) (a, b, c, d', e, f) d d' instance Field4 (a, b, c, d, e) (a, b, c, d', e) d d' instance Field4 (a, b, c, d) (a, b, c, d') d d' instance Field3 (a, b, c, d, e, f, g, h, i) (a, b, c', d, e, f, g, h, i) c c' instance Field3 (a, b, c, d, e, f, g, h) (a, b, c', d, e, f, g, h) c c' instance Field3 (a, b, c, d, e, f, g) (a, b, c', d, e, f, g) c c' instance Field3 (a, b, c, d, e, f) (a, b, c', d, e, f) c c' instance Field3 (a, b, c, d, e) (a, b, c', d, e) c c' instance Field3 (a, b, c, d) (a, b, c', d) c c' instance Field3 (a, b, c) (a, b, c') c c' instance Field2 (a, b, c, d, e, f, g, h, i) (a, b', c, d, e, f, g, h, i) b b' instance Field2 (a, b, c, d, e, f, g, h) (a, b', c, d, e, f, g, h) b b' instance Field2 (a, b, c, d, e, f, g) (a, b', c, d, e, f, g) b b' instance Field2 (a, b, c, d, e, f) (a, b', c, d, e, f) b b' instance Field2 (a, b, c, d, e) (a, b', c, d, e) b b' instance Field2 (a, b, c, d) (a, b', c, d) b b' instance Field2 (a, b, c) (a, b', c) b b' instance Field2 (a, b) (a, b') b b' instance Field2 ((:*:) f g p) ((:*:) f g' p) (g p) (g' p) instance Field2 (Product f g a) (Product f g' a) (g a) (g' a) instance Field1 (a, b, c, d, e, f, g, h, i) (a', b, c, d, e, f, g, h, i) a a' instance Field1 (a, b, c, d, e, f, g, h) (a', b, c, d, e, f, g, h) a a' instance Field1 (a, b, c, d, e, f, g) (a', b, c, d, e, f, g) a a' instance Field1 (a, b, c, d, e, f) (a', b, c, d, e, f) a a' instance Field1 (a, b, c, d, e) (a', b, c, d, e) a a' instance Field1 (a, b, c, d) (a', b, c, d) a a' instance Field1 (a, b, c) (a', b, c) a a' instance Field1 (a, b) (a', b) a a' instance Field1 ((:*:) f g p) ((:*:) f' g p) (f p) (f' p) instance Field1 (Product f g a) (Product f' g a) (f a) (f' a) instance Field1 (Identity a) (Identity b) a b -- | A Getter s a is just any function (s -> -- a), which we've flipped into continuation passing style, (a -- -> r) -> s -> r and decorated with Const to -- obtain: -- --
-- type Getting r s a = (a -> Const r a) -> s -> Const r s ---- -- If we restrict access to knowledge about the type r, we could -- get: -- --
-- type Getter s a = forall r. Getting r s a ---- -- However, for Getter (but not for Getting) we actually -- permit any functor f which is an instance of both -- Functor and Contravariant: -- --
-- type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s ---- -- Everything you can do with a function, you can do with a -- Getter, but note that because of the continuation passing style -- (.) composes them in the opposite order. -- -- Since it is only a function, every Getter obviously only -- retrieves a single value for a given input. module Control.Lens.Getter -- | A Getter describes how to retrieve a single value in a way that -- can be composed with other LensLike constructions. -- -- Unlike a Lens a Getter is read-only. Since a -- Getter cannot be used to write back there are no Lens -- laws that can be applied to it. In fact, it is isomorphic to an -- arbitrary function from (s -> a). -- -- Moreover, a Getter can be used directly as a Fold, since -- it just ignores the Applicative. type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s -- | Every IndexedGetter is a valid IndexedFold and can be -- used for Getting like a Getter. type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s -- | When you see this in a type signature it indicates that you can pass -- the function a Lens, Getter, Traversal, -- Fold, Prism, Iso, or one of the indexed variants, -- and it will just "do the right thing". -- -- Most Getter combinators are able to be used with both a -- Getter or a Fold in limited situations, to do so, they -- need to be monomorphic in what we are going to extract with -- Const. To be compatible with Lens, Traversal and -- Iso we also restricted choices of the irrelevant t and -- b parameters. -- -- If a function accepts a Getting r s a, then when -- r is a Monoid, then you can pass a Fold (or -- Traversal), otherwise you can only pass this a Getter or -- Lens. type Getting r s a = (a -> Const r a) -> s -> Const r s -- | Used to consume an IndexedFold. type IndexedGetting i m s a = Indexed i a (Const m a) -> s -> Const m s -- | This is a convenient alias used when consuming (indexed) getters and -- (indexed) folds in a highly general fashion. type Accessing p m s a = p a (Const m a) -> s -> Const m s -- | Build an (index-preserving) Getter from an arbitrary Haskell -- function. -- --
-- to f . to g ≡ to (g . f) ---- --
-- a ^. to f ≡ f a ---- --
-- >>> a ^.to f -- f a ---- --
-- >>> ("hello","world")^.to snd -- "world" ---- --
-- >>> 5^.to succ -- 6 ---- --
-- >>> (0, -5)^._2.to abs -- 5 ---- --
-- to :: (s -> a) -> IndexPreservingGetter s a --to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a -- |
-- ito :: (s -> (i, a)) -> IndexedGetter i s a --ito :: (Indexable i p, Contravariant f) => (s -> (i, a)) -> Over' p f s a -- | Build an constant-valued (index-preserving) Getter from an -- arbitrary Haskell value. -- --
-- like a . like b ≡ like b -- a ^. like b ≡ b -- a ^. like b ≡ a ^. to (const b) ---- -- This can be useful as a second case failing a Fold -- e.g. foo failing like 0 -- --
-- like :: a -> IndexPreservingGetter s a --like :: (Profunctor p, Contravariant f) => a -> Optic' p f s a -- |
-- ilike :: i -> a -> IndexedGetter i s a --ilike :: (Indexable i p, Contravariant f) => i -> a -> Over' p f s a -- | View the value pointed to by a Getter or Lens or the -- result of folding over all the results of a Fold or -- Traversal that points at a monoidal values. -- -- This is the same operation as view with the arguments flipped. -- -- The fixity and semantics are such that subsequent field accesses can -- be performed with (.). -- --
-- >>> (a,b)^._2 -- b ---- --
-- >>> ("hello","world")^._2 -- "world" ---- --
-- >>> import Data.Complex -- -- >>> ((0, 1 :+ 2), 3)^._1._2.to magnitude -- 2.23606797749979 ---- --
-- (^.) :: s -> Getter s a -> a -- (^.) :: Monoid m => s -> Fold s m -> m -- (^.) :: s -> Iso' s a -> a -- (^.) :: s -> Lens' s a -> a -- (^.) :: Monoid m => s -> Traversal' s m -> m --(^.) :: s -> Getting a s a -> a -- | View the value pointed to by a Getter, Iso or -- Lens or the result of folding over all the results of a -- Fold or Traversal that points at a monoidal value. -- --
-- view . to ≡ id ---- --
-- >>> view (to f) a -- f a ---- --
-- >>> view _2 (1,"hello") -- "hello" ---- --
-- >>> view (to succ) 5 -- 6 ---- --
-- >>> view (_2._1) ("hello",("world","!!!")) -- "world" ---- -- As view is commonly used to access the target of a -- Getter or obtain a monoidal summary of the targets of a -- Fold, It may be useful to think of it as having one of these -- more restricted signatures: -- --
-- view :: Getter s a -> s -> a -- view :: Monoid m => Fold s m -> s -> m -- view :: Iso' s a -> s -> a -- view :: Lens' s a -> s -> a -- view :: Monoid m => Traversal' s m -> s -> m ---- -- In a more general setting, such as when working with a Monad -- transformer stack you can use: -- --
-- view :: MonadReader s m => Getter s a -> m a -- view :: (MonadReader s m, Monoid a) => Fold s a -> m a -- view :: MonadReader s m => Iso' s a -> m a -- view :: MonadReader s m => Lens' s a -> m a -- view :: (MonadReader s m, Monoid a) => Traversal' s a -> m a --view :: MonadReader s m => Getting a s a -> m a -- | View a function of the value pointed to by a Getter or -- Lens or the result of folding over the result of mapping the -- targets of a Fold or Traversal. -- --
-- views l f ≡ view (l . to f) ---- --
-- >>> views (to f) g a -- g (f a) ---- --
-- >>> views _2 length (1,"hello") -- 5 ---- -- As views is commonly used to access the target of a -- Getter or obtain a monoidal summary of the targets of a -- Fold, It may be useful to think of it as having one of these -- more restricted signatures: -- --
-- views :: Getter s a -> (a -> r) -> s -> r -- views :: Monoid m => Fold s a -> (a -> m) -> s -> m -- views :: Iso' s a -> (a -> r) -> s -> r -- views :: Lens' s a -> (a -> r) -> s -> r -- views :: Monoid m => Traversal' s a -> (a -> m) -> s -> m ---- -- In a more general setting, such as when working with a Monad -- transformer stack you can use: -- --
-- views :: MonadReader s m => Getter s a -> (a -> r) -> m r -- views :: (MonadReader s m, Monoid r) => Fold s a -> (a -> r) -> m r -- views :: MonadReader s m => Iso' s a -> (a -> r) -> m r -- views :: MonadReader s m => Lens' s a -> (a -> r) -> m r -- views :: (MonadReader s m, Monoid r) => Traversal' s a -> (a -> r) -> m r ---- --
-- views :: MonadReader s m => Getting r s a -> (a -> r) -> m r --views :: MonadReader s m => LensLike' (Const r) s a -> (a -> r) -> m r -- | Use the target of a Lens, Iso, or Getter in the -- current state, or use a summary of a Fold or Traversal -- that points to a monoidal value. -- --
-- >>> evalState (use _1) (a,b) -- a ---- --
-- >>> evalState (use _1) ("hello","world") -- "hello" ---- --
-- use :: MonadState s m => Getter s a -> m a -- use :: (MonadState s m, Monoid r) => Fold s r -> m r -- use :: MonadState s m => Iso' s a -> m a -- use :: MonadState s m => Lens' s a -> m a -- use :: (MonadState s m, Monoid r) => Traversal' s r -> m r --use :: MonadState s m => Getting a s a -> m a -- | Use the target of a Lens, Iso or Getter in the -- current state, or use a summary of a Fold or Traversal -- that points to a monoidal value. -- --
-- >>> evalState (uses _1 length) ("hello","world") -- 5 ---- --
-- uses :: MonadState s m => Getter s a -> (a -> r) -> m r -- uses :: (MonadState s m, Monoid r) => Fold s a -> (a -> r) -> m r -- uses :: MonadState s m => Lens' s a -> (a -> r) -> m r -- uses :: MonadState s m => Iso' s a -> (a -> r) -> m r -- uses :: (MonadState s m, Monoid r) => Traversal' s a -> (a -> r) -> m r ---- --
-- uses :: MonadState s m => Getting r s t a b -> (a -> r) -> m r --uses :: MonadState s m => LensLike' (Const r) s a -> (a -> r) -> m r -- | This is a generalized form of listen that only extracts the -- portion of the log that is focused on by a Getter. If given a -- Fold or a Traversal then a monoidal summary of the parts -- of the log that are visited will be returned. -- --
-- listening :: MonadWriter w m => Getter w u -> m a -> m (a, u) -- listening :: MonadWriter w m => Lens' w u -> m a -> m (a, u) -- listening :: MonadWriter w m => Iso' w u -> m a -> m (a, u) -- listening :: (MonadWriter w m, Monoid u) => Fold w u -> m a -> m (a, u) -- listening :: (MonadWriter w m, Monoid u) => Traversal' w u -> m a -> m (a, u) -- listening :: (MonadWriter w m, Monoid u) => Prism' w u -> m a -> m (a, u) --listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u) -- | This is a generalized form of listen that only extracts the -- portion of the log that is focused on by a Getter. If given a -- Fold or a Traversal then a monoidal summary of the parts -- of the log that are visited will be returned. -- --
-- listenings :: MonadWriter w m => Getter w u -> (u -> v) -> m a -> m (a, v) -- listenings :: MonadWriter w m => Lens' w u -> (u -> v) -> m a -> m (a, v) -- listenings :: MonadWriter w m => Iso' w u -> (u -> v) -> m a -> m (a, v) -- listenings :: (MonadWriter w m, Monoid v) => Fold w u -> (u -> v) -> m a -> m (a, v) -- listenings :: (MonadWriter w m, Monoid v) => Traversal' w u -> (u -> v) -> m a -> m (a, v) -- listenings :: (MonadWriter w m, Monoid v) => Prism' w u -> (u -> v) -> m a -> m (a, v) --listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v) -- | View the index and value of an IndexedGetter or -- IndexedLens. -- -- This is the same operation as iview with the arguments flipped. -- -- The fixity and semantics are such that subsequent field accesses can -- be performed with (.). -- --
-- (^@.) :: s -> IndexedGetter i s a -> (i, a) -- (^@.) :: s -> IndexedLens' i s a -> (i, a) ---- -- The result probably doesn't have much meaning when applied to an -- IndexedFold. (^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a) -- | View the index and value of an IndexedGetter into the current -- environment as a pair. -- -- When applied to an IndexedFold the result will most likely be a -- nonsensical monoidal summary of the indices tupled with a monoidal -- summary of the values and probably not whatever it is you wanted. iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a) -- | View a function of the index and value of an IndexedGetter into -- the current environment. -- -- When applied to an IndexedFold the result will be a monoidal -- summary instead of a single answer. -- --
-- iviews ≡ ifoldMapOf --iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m r -- | Use the index and value of an IndexedGetter into the current -- state as a pair. -- -- When applied to an IndexedFold the result will most likely be a -- nonsensical monoidal summary of the indices tupled with a monoidal -- summary of the values and probably not whatever it is you wanted. iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a) -- | Use a function of the index and value of an IndexedGetter into -- the current state. -- -- When applied to an IndexedFold the result will be a monoidal -- summary instead of a single answer. iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m r -- | This is a generalized form of listen that only extracts the -- portion of the log that is focused on by a Getter. If given a -- Fold or a Traversal then a monoidal summary of the parts -- of the log that are visited will be returned. -- --
-- ilistening :: MonadWriter w m => IndexedGetter i w u -> m a -> m (a, (i, u)) -- ilistening :: MonadWriter w m => IndexedLens' i w u -> m a -> m (a, (i, u)) -- ilistening :: (MonadWriter w m, Monoid u) => IndexedFold i w u -> m a -> m (a, (i, u)) -- ilistening :: (MonadWriter w m, Monoid u) => IndexedTraversal' i w u -> m a -> m (a, (i, u)) --ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u)) -- | This is a generalized form of listen that only extracts the -- portion of the log that is focused on by a Getter. If given a -- Fold or a Traversal then a monoidal summary of the parts -- of the log that are visited will be returned. -- --
-- ilistenings :: MonadWriter w m => IndexedGetter w u -> (i -> u -> v) -> m a -> m (a, v) -- ilistenings :: MonadWriter w m => IndexedLens' w u -> (i -> u -> v) -> m a -> m (a, v) -- ilistenings :: (MonadWriter w m, Monoid v) => IndexedFold w u -> (i -> u -> v) -> m a -> m (a, v) -- ilistenings :: (MonadWriter w m, Monoid v) => IndexedTraversal' w u -> (i -> u -> v) -> m a -> m (a, v) --ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v) -- | Any instance should be subject to the following laws: -- --
-- contramap id = id -- contramap f . contramap g = contramap (g . f) ---- -- Note, that the second law follows from the free theorem of the type of -- contramap and the first law, so you need only check that the -- former condition holds. class Contravariant (f :: * -> *) contramap :: Contravariant f => (a -> b) -> f b -> f a (>$) :: Contravariant f => b -> f b -> f a -- | Coerce a Getter-compatible LensLike to a -- LensLike'. This is useful when using a Traversal that is -- not simple as a Getter or a Fold. getting :: (Functor f, Contravariant f) => LensLike f s t a b -> LensLike' f s a newtype Const a b :: * -> * -> * Const :: a -> Const a b getConst :: Const a b -> a -- | A Review is a type-restricted form of a Prism that can -- only be used for writing back via re, review, -- reuse. module Control.Lens.Review -- | This is a limited form of a Prism that can only be used for -- re operations. -- -- Like with a Getter, there are no laws to state for a -- Review. -- -- You can generate a Review by using unto. You can also -- use any Prism or Iso directly as a Review. type Review t b = forall p f. (Choice p, Bifunctor p, Settable f) => Optic' p f t b -- | If you see this in a signature for a function, the function is -- expecting a Review (in practice, this usually means a -- Prism). type AReview t b = Optic' Tagged Identity t b -- | An analogue of to for review. -- --
-- unto :: (b -> t) -> Review' t b ---- --
-- unto = un . to --unto :: (Profunctor p, Bifunctor p, Functor f) => (b -> t) -> Optic p f s t a b -- | Turn a Getter around to get a Review -- --
-- un = unto . view -- unto = un . to ---- --
-- >>> un (to length) # [1,2,3] -- 3 --un :: (Profunctor p, Bifunctor p, Functor f) => Getting a s a -> Optic' p f a s -- | Turn a Prism or Iso around to build a Getter. -- -- If you have an Iso, from is a more powerful version of -- this function that will return an Iso instead of a mere -- Getter. -- --
-- >>> 5 ^.re _Left -- Left 5 ---- --
-- >>> 6 ^.re (_Left.unto succ) -- Left 7 ---- --
-- review ≡ view . re -- reviews ≡ views . re -- reuse ≡ use . re -- reuses ≡ uses . re ---- --
-- re :: Prism s t a b -> Getter b t -- re :: Iso s t a b -> Getter b t --re :: Contravariant f => AReview t b -> LensLike' f b t -- | This can be used to turn an Iso or Prism around and -- view a value (or the current environment) through it the other -- way. -- --
-- review ≡ view . re -- review . unto ≡ id ---- --
-- >>> review _Left "mustard" -- Left "mustard" ---- --
-- >>> review (unto succ) 5 -- 6 ---- -- Usually review is used in the (->) Monad -- with a Prism or Iso, in which case it may be useful to -- think of it as having one of these more restricted type signatures: -- --
-- review :: Iso' s a -> a -> s -- review :: Prism' s a -> a -> s ---- -- However, when working with a Monad transformer stack, it is -- sometimes useful to be able to review the current environment, -- in which case it may be beneficial to think of it as having one of -- these slightly more liberal type signatures: -- --
-- review :: MonadReader a m => Iso' s a -> m s -- review :: MonadReader a m => Prism' s a -> m s --review :: MonadReader b m => AReview t b -> m t -- | This can be used to turn an Iso or Prism around and -- view a value (or the current environment) through it the other -- way, applying a function. -- --
-- reviews ≡ views . re -- reviews (unto f) g ≡ g . f ---- --
-- >>> reviews _Left isRight "mustard" -- False ---- --
-- >>> reviews (unto succ) (*2) 3 -- 8 ---- -- Usually this function is used in the (->) Monad -- with a Prism or Iso, in which case it may be useful to -- think of it as having one of these more restricted type signatures: -- --
-- reviews :: Iso' s a -> (s -> r) -> a -> r -- reviews :: Prism' s a -> (s -> r) -> a -> r ---- -- However, when working with a Monad transformer stack, it is -- sometimes useful to be able to review the current environment, -- in which case it may be beneficial to think of it as having one of -- these slightly more liberal type signatures: -- --
-- reviews :: MonadReader a m => Iso' s a -> (s -> r) -> m r -- reviews :: MonadReader a m => Prism' s a -> (s -> r) -> m r --reviews :: MonadReader b m => AReview t b -> (t -> r) -> m r -- | This can be used to turn an Iso or Prism around and -- use a value (or the current environment) through it the other -- way. -- --
-- reuse ≡ use . re -- reuse . unto ≡ gets ---- --
-- >>> evalState (reuse _Left) 5 -- Left 5 ---- --
-- >>> evalState (reuse (unto succ)) 5 -- 6 ---- --
-- reuse :: MonadState a m => Prism' s a -> m s -- reuse :: MonadState a m => Iso' s a -> m s --reuse :: MonadState b m => AReview t b -> m t -- | This can be used to turn an Iso or Prism around and -- use the current state through it the other way, applying a -- function. -- --
-- reuses ≡ uses . re -- reuses (unto f) g ≡ gets (g . f) ---- --
-- >>> evalState (reuses _Left isLeft) (5 :: Int) -- True ---- --
-- reuses :: MonadState a m => Prism' s a -> (s -> r) -> m r -- reuses :: MonadState a m => Iso' s a -> (s -> r) -> m r --reuses :: MonadState b m => AReview t b -> (t -> r) -> m r -- | An infix alias for review. -- --
-- unto f # x ≡ f x -- l # x ≡ x ^. re l ---- -- This is commonly used when using a Prism as a smart -- constructor. -- --
-- >>> _Left # 4 -- Left 4 ---- -- But it can be used for any Prism -- --
-- >>> base 16 # 123 -- "7b" ---- --
-- (#) :: Iso' s a -> a -> s -- (#) :: Prism' s a -> a -> s -- (#) :: Review s a -> a -> s -- (#) :: Equality' s a -> a -> s --(#) :: AReview t b -> b -> t -- | Minimal definition either bimap or first and -- second -- -- Formally, the class Bifunctor represents a bifunctor from -- Hask -> Hask. -- -- Intuitively it is a bifunctor where both the first and second -- arguments are covariant. -- -- You can define a Bifunctor by either defining bimap or -- by defining both first and second. -- -- If you supply bimap, you should ensure that: -- --
-- bimap id id ≡ id ---- -- If you supply first and second, ensure: -- --
-- first id ≡ id -- second id ≡ id ---- -- If you supply both, you should also ensure: -- --
-- bimap f g ≡ first f . second g ---- -- These ensure by parametricity: -- --
-- bimap (f . g) (h . i) ≡ bimap f h . bimap g i -- first (f . g) ≡ first f . first g -- second (f . g) ≡ second f . second g --class Bifunctor (p :: * -> * -> *) bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d -- | This is a profunctor used internally to implement Review -- -- It plays a role similar to that of Accessor or Const -- do for Control.Lens.Getter retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b -- | This class is provided mostly for backwards compatibility with lens -- 3.8, but it can also shorten type signatures. class (Profunctor p, Bifunctor p) => Reviewable p module Control.Lens.Prism -- | A Prism l is a Traversal that can also be -- turned around with re to obtain a Getter in the opposite -- direction. -- -- There are two laws that a Prism should satisfy: -- -- First, if I re or review a value with a Prism and -- then preview or use (^?), I will get it back: -- --
-- preview l (review l b) ≡ Just b ---- -- Second, if you can extract a value a using a Prism -- l from a value s, then the value s is -- completely described by l and a: -- -- If preview l s ≡ Just a then -- review l a ≡ s -- -- These two laws imply that the Traversal laws hold for every -- Prism and that we traverse at most 1 element: -- --
-- lengthOf l x <= 1 ---- -- It may help to think of this as a Iso that can be partial in -- one direction. -- -- Every Prism is a valid Traversal. -- -- Every Iso is a valid Prism. -- -- For example, you might have a Prism' Integer -- Natural allows you to always go from a Natural to -- an Integer, and provide you with tools to check if an -- Integer is a Natural and/or to edit one if it is. -- --
-- nat :: Prism' Integer Natural -- nat = prism toInteger $ \ i -> -- if i < 0 -- then Left i -- else Right (fromInteger i) ---- -- Now we can ask if an Integer is a Natural. -- --
-- >>> 5^?nat -- Just 5 ---- --
-- >>> (-5)^?nat -- Nothing ---- -- We can update the ones that are: -- --
-- >>> (-3,4) & both.nat *~ 2 -- (-3,8) ---- -- And we can then convert from a Natural to an Integer. -- --
-- >>> 5 ^. re nat -- :: Natural -- 5 ---- -- Similarly we can use a Prism to traverse the -- Left half of an Either: -- --
-- >>> Left "hello" & _Left %~ length -- Left 5 ---- -- or to construct an Either: -- --
-- >>> 5^.re _Left -- Left 5 ---- -- such that if you query it with the Prism, you will get your -- original input back. -- --
-- >>> 5^.re _Left ^? _Left -- Just 5 ---- -- Another interesting way to think of a Prism is as the -- categorical dual of a Lens -- a co-Lens, so to speak. -- This is what permits the construction of outside. -- -- Note: Composition with a Prism is index-preserving. type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t) -- | A Simple Prism. type Prism' s a = Prism s s a a -- | If you see this in a signature for a function, the function is -- expecting a Prism. type APrism s t a b = Market a b a (Identity b) -> Market a b s (Identity t) -- |
-- type APrism' = Simple APrism --type APrism' s a = APrism s s a a -- | Build a Prism. -- -- Either t a is used instead of Maybe a -- to permit the types of s and t to differ. prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b -- | This is usually used to build a Prism', when you have to use an -- operation like cast which already returns a Maybe. prism' :: (b -> s) -> (s -> Maybe a) -> Prism s s a b -- | Convert APrism to the pair of functions that characterize it. withPrism :: APrism s t a b -> ((b -> t) -> (s -> Either t a) -> r) -> r -- | Clone a Prism so that you can reuse the same monomorphically -- typed Prism for different purposes. -- -- See cloneLens and cloneTraversal for examples of why you -- might want to do this. clonePrism :: APrism s t a b -> Prism s t a b -- | Use a Prism as a kind of first-class pattern. -- --
-- outside :: Prism s t a b -> Lens (t -> r) (s -> r) (b -> r) (a -> r) --outside :: Representable p => APrism s t a b -> Lens (p t r) (p s r) (p b r) (p a r) -- | Use a Prism to work over part of a structure. aside :: APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b) -- | Given a pair of prisms, project sums. -- -- Viewing a Prism as a co-Lens, this combinator can be -- seen to be dual to alongside. without :: APrism s t a b -> APrism u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d) -- | lift a Prism through a Traversable functor, -- giving a Prism that matches only if all the elements of the container -- match the Prism. -- --
-- >>> [Left 1, Right "foo", Left 4, Right "woot"]^..below _Right -- [] ---- --
-- >>> [Right "hail hydra!", Right "foo", Right "blah", Right "woot"]^..below _Right -- [["hail hydra!","foo","blah","woot"]] --below :: Traversable f => APrism' s a -> Prism' (f s) (f a) -- | Check to see if this Prism doesn't match. -- --
-- >>> isn't _Left (Right 12) -- True ---- --
-- >>> isn't _Left (Left 12) -- False ---- --
-- >>> isn't _Empty [] -- False --isn't :: APrism s t a b -> s -> Bool -- | Retrieve the value targeted by a Prism or return the original -- value while allowing the type to change if it does not match. -- --
-- >>> matching _Just (Just 12) -- Right 12 ---- --
-- >>> matching _Just (Nothing :: Maybe Int) :: Either (Maybe Bool) Int -- Left Nothing --matching :: APrism s t a b -> s -> Either t a -- | This Prism provides a Traversal for tweaking the -- Left half of an Either: -- --
-- >>> over _Left (+1) (Left 2) -- Left 3 ---- --
-- >>> over _Left (+1) (Right 2) -- Right 2 ---- --
-- >>> Right 42 ^._Left :: String -- "" ---- --
-- >>> Left "hello" ^._Left -- "hello" ---- -- It also can be turned around to obtain the embedding into the -- Left half of an Either: -- --
-- >>> _Left # 5 -- Left 5 ---- --
-- >>> 5^.re _Left -- Left 5 --_Left :: Prism (Either a c) (Either b c) a b -- | This Prism provides a Traversal for tweaking the -- Right half of an Either: -- --
-- >>> over _Right (+1) (Left 2) -- Left 2 ---- --
-- >>> over _Right (+1) (Right 2) -- Right 3 ---- --
-- >>> Right "hello" ^._Right -- "hello" ---- --
-- >>> Left "hello" ^._Right :: [Double] -- [] ---- -- It also can be turned around to obtain the embedding into the -- Right half of an Either: -- --
-- >>> _Right # 5 -- Right 5 ---- --
-- >>> 5^.re _Right -- Right 5 --_Right :: Prism (Either c a) (Either c b) a b -- | This Prism provides a Traversal for tweaking the target -- of the value of Just in a Maybe. -- --
-- >>> over _Just (+1) (Just 2) -- Just 3 ---- -- Unlike traverse this is a Prism, and so you can use it -- to inject as well: -- --
-- >>> _Just # 5 -- Just 5 ---- --
-- >>> 5^.re _Just -- Just 5 ---- -- Interestingly, -- --
-- m ^? _Just ≡ m ---- --
-- >>> Just x ^? _Just -- Just x ---- --
-- >>> Nothing ^? _Just -- Nothing --_Just :: Prism (Maybe a) (Maybe b) a b -- | This Prism provides the Traversal of a Nothing in -- a Maybe. -- --
-- >>> Nothing ^? _Nothing -- Just () ---- --
-- >>> Just () ^? _Nothing -- Nothing ---- -- But you can turn it around and use it to construct Nothing as -- well: -- --
-- >>> _Nothing # () -- Nothing --_Nothing :: Prism' (Maybe a) () -- | Void is a logically uninhabited data type. -- -- This is a Prism that will always fail to match. _Void :: Prism s s a Void -- | This is an improper prism for text formatting based on Read and -- Show. -- -- This Prism is "improper" in the sense that it normalizes the -- text formatting, but round tripping is idempotent given sane -- 'Read'/'Show' instances. -- --
-- >>> _Show # 2 -- "2" ---- --
-- >>> "EQ" ^? _Show :: Maybe Ordering -- Just EQ ---- --
-- _Show ≡ prism' show readMaybe --_Show :: (Read a, Show a) => Prism' String a -- | This Prism compares for exact equality with a given value. -- --
-- >>> only 4 # () -- 4 ---- --
-- >>> 5 ^? only 4 -- Nothing --only :: Eq a => a -> Prism' a () -- | This Prism compares for approximate equality with a given value -- and a predicate for testing, an example where the value is the empty -- list and the predicate checks that a list is empty (same as -- _Empty with the AsEmpty list instance): -- --
-- >>> nearly [] null # () -- [] -- -- >>> [1,2,3,4] ^? nearly [] null -- Nothing ---- --
-- nearly [] null :: Prism' [a] () ---- -- To comply with the Prism laws the arguments you supply to -- nearly a p are somewhat constrained. -- -- We assume p x holds iff x ≡ a. Under that assumption -- then this is a valid Prism. -- -- This is useful when working with a type where you can test equality -- for only a subset of its values, and the prism selects such a value. nearly :: a -> (a -> Bool) -> Prism' a () -- | The generalization of Costar of Functor that is strong -- with respect to Either. -- -- Note: This is also a notion of strength, except with regards to -- another monoidal structure that we can choose to equip Hask with: the -- cocartesian coproduct. class Profunctor p => Choice (p :: * -> * -> *) left' :: Choice p => p a b -> p (Either a c) (Either b c) right' :: Choice p => p a b -> p (Either c a) (Either c b) module Control.Lens.Zoom -- | This class allows us to use magnify part of the environment, -- changing the environment supplied by many different Monad -- transformers. Unlike zoom this can change the environment of a -- deeply nested Monad transformer. -- -- Also, unlike zoom, this can be used with any valid -- Getter, but cannot be used with a Traversal or -- Fold. class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m magnify :: Magnify m n b a => LensLike' (Magnified m c) a b -> m c -> n c -- | This class allows us to use zoom in, changing the State -- supplied by many different Monad transformers, potentially -- quite deep in a Monad transformer stack. class (Zoomed m ~ Zoomed n, MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m zoom :: Zoom m n s t => LensLike' (Zoomed m c) t s -> m c -> n c instance Magnify m n b a => Magnify (IdentityT m) (IdentityT n) b a instance (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a instance (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a instance Magnify ((->) b) ((->) a) b a instance Monad m => Magnify (ReaderT b m) (ReaderT a m) b a instance Zoom m n s t => Zoom (ExceptT e m) (ExceptT e n) s t instance (Error e, Zoom m n s t) => Zoom (ErrorT e m) (ErrorT e n) s t instance Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t instance Zoom m n s t => Zoom (ListT m) (ListT n) s t instance (Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t instance (Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t instance (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t instance (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t instance Zoom m n s t => Zoom (IdentityT m) (IdentityT n) s t instance Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t instance Monad z => Zoom (StateT s z) (StateT t z) s t instance Monad z => Zoom (StateT s z) (StateT t z) s t module Data.Set.Lens -- | This Setter can be used to change the type of a Set by -- mapping the elements to new values. -- -- Sadly, you can't create a valid Traversal for a Set, but -- you can manipulate it by reading using folded and reindexing it -- via setmapped. -- --
-- >>> over setmapped (+1) (fromList [1,2,3,4]) -- fromList [2,3,4,5] --setmapped :: Ord j => IndexPreservingSetter (Set i) (Set j) i j -- | Construct a set from a Getter, Fold, Traversal, -- Lens or Iso. -- --
-- >>> setOf folded ["hello","world"] -- fromList ["hello","world"] ---- --
-- >>> setOf (folded._2) [("hello",1),("world",2),("!!!",3)] -- fromList [1,2,3] ---- --
-- setOf :: Getter s a -> s -> Set a -- setOf :: Ord a => Fold s a -> s -> Set a -- setOf :: Iso' s a -> s -> Set a -- setOf :: Lens' s a -> s -> Set a -- setOf :: Ord a => Traversal' s a -> s -> Set a --setOf :: Getting (Set a) s a -> s -> Set a module Data.HashSet.Lens -- | This Setter can be used to change the type of a HashSet -- by mapping the elements to new values. -- -- Sadly, you can't create a valid Traversal for a Set, -- but you can manipulate it by reading using folded and -- reindexing it via setmapped. setmapped :: (Eq j, Hashable j) => IndexPreservingSetter (HashSet i) (HashSet j) i j -- | Construct a set from a Getter, Fold, Traversal, -- Lens or Iso. -- --
-- setOf :: Hashable a => Getter s a -> s -> HashSet a -- setOf :: (Eq a, Hashable a) => Fold s a -> s -> HashSet a -- setOf :: Hashable a => Iso' s a -> s -> HashSet a -- setOf :: Hashable a => Lens' s a -> s -> HashSet a -- setOf :: (Eq a, Hashable a) => Traversal' s a -> s -> HashSet a --setOf :: Hashable a => Getting (HashSet a) s a -> s -> HashSet a -- | A Fold s a is a generalization of something -- Foldable. It allows you to extract multiple results from a -- container. A Foldable container can be characterized by the -- behavior of foldMap :: (Foldable t, Monoid m) -- => (a -> m) -> t a -> m. Since we want to be able to -- work with monomorphic containers, we could generalize this signature -- to forall m. Monoid m => (a -> m) -> s -> -- m, and then decorate it with Const to obtain -- --
-- type Fold s a = forall m. Monoid m => Getting m s a ---- -- Every Getter is a valid Fold that simply doesn't use the -- Monoid it is passed. -- -- In practice the type we use is slightly more complicated to allow for -- better error messages and for it to be transformed by certain -- Applicative transformers. -- -- Everything you can do with a Foldable container, you can with -- with a Fold and there are combinators that generalize the usual -- Foldable operations here. module Control.Lens.Fold -- | A Fold describes how to retrieve multiple values in a way that -- can be composed with other LensLike constructions. -- -- A Fold s a provides a structure with operations very -- similar to those of the Foldable typeclass, see -- foldMapOf and the other Fold combinators. -- -- By convention, if there exists a foo method that expects a -- Foldable (f a), then there should be a fooOf -- method that takes a Fold s a and a value of type -- s. -- -- A Getter is a legal Fold that just ignores the supplied -- Monoid. -- -- Unlike a Traversal a Fold is read-only. Since a -- Fold cannot be used to write back there are no Lens laws -- that apply. type Fold s a = forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s -- | Every IndexedFold is a valid Fold and can be used for -- Getting. type IndexedFold i s a = forall p f. (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s -- | A convenient infix (flipped) version of toListOf. -- --
-- >>> [[1,2],[3]]^..id -- [[[1,2],[3]]] -- -- >>> [[1,2],[3]]^..traverse -- [[1,2],[3]] -- -- >>> [[1,2],[3]]^..traverse.traverse -- [1,2,3] ---- --
-- >>> (1,2)^..both -- [1,2] ---- --
-- toList xs ≡ xs ^.. folded -- (^..) ≡ flip toListOf ---- --
-- (^..) :: s -> Getter s a -> [a] -- (^..) :: s -> Fold s a -> [a] -- (^..) :: s -> Lens' s a -> [a] -- (^..) :: s -> Iso' s a -> [a] -- (^..) :: s -> Traversal' s a -> [a] -- (^..) :: s -> Prism' s a -> [a] --(^..) :: s -> Getting (Endo [a]) s a -> [a] -- | Perform a safe head of a Fold or Traversal or -- retrieve Just the result from a Getter or Lens. -- -- When using a Traversal as a partial Lens, or a -- Fold as a partial Getter this can be a convenient way to -- extract the optional value. -- -- Note: if you get stack overflows due to this, you may want to use -- firstOf instead, which can deal more gracefully with heavily -- left-biased trees. -- --
-- >>> Left 4 ^?_Left -- Just 4 ---- --
-- >>> Right 4 ^?_Left -- Nothing ---- --
-- >>> "world" ^? ix 3 -- Just 'l' ---- --
-- >>> "world" ^? ix 20 -- Nothing ---- --
-- (^?) ≡ flip preview ---- --
-- (^?) :: s -> Getter s a -> Maybe a -- (^?) :: s -> Fold s a -> Maybe a -- (^?) :: s -> Lens' s a -> Maybe a -- (^?) :: s -> Iso' s a -> Maybe a -- (^?) :: s -> Traversal' s a -> Maybe a --(^?) :: s -> Getting (First a) s a -> Maybe a -- | Perform an *UNSAFE* head of a Fold or Traversal -- assuming that it is there. -- --
-- >>> Left 4 ^?! _Left -- 4 ---- --
-- >>> "world" ^?! ix 3 -- 'l' ---- --
-- (^?!) :: s -> Getter s a -> a -- (^?!) :: s -> Fold s a -> a -- (^?!) :: s -> Lens' s a -> a -- (^?!) :: s -> Iso' s a -> a -- (^?!) :: s -> Traversal' s a -> a --(^?!) :: s -> Getting (Endo a) s a -> a -- | This converts a Fold to a IndexPreservingGetter that -- returns the first element, if it exists, as a Maybe. -- --
-- pre :: Getter s a -> IndexPreservingGetter s (Maybe a) -- pre :: Fold s a -> IndexPreservingGetter s (Maybe a) -- pre :: Traversal' s a -> IndexPreservingGetter s (Maybe a) -- pre :: Lens' s a -> IndexPreservingGetter s (Maybe a) -- pre :: Iso' s a -> IndexPreservingGetter s (Maybe a) -- pre :: Prism' s a -> IndexPreservingGetter s (Maybe a) --pre :: Getting (First a) s a -> IndexPreservingGetter s (Maybe a) -- | This converts an IndexedFold to an IndexPreservingGetter -- that returns the first index and element, if they exist, as a -- Maybe. -- --
-- ipre :: IndexedGetter i s a -> IndexPreservingGetter s (Maybe (i, a)) -- ipre :: IndexedFold i s a -> IndexPreservingGetter s (Maybe (i, a)) -- ipre :: IndexedTraversal' i s a -> IndexPreservingGetter s (Maybe (i, a)) -- ipre :: IndexedLens' i s a -> IndexPreservingGetter s (Maybe (i, a)) --ipre :: IndexedGetting i (First (i, a)) s a -> IndexPreservingGetter s (Maybe (i, a)) -- | Retrieve the first value targeted by a Fold or Traversal -- (or Just the result from a Getter or Lens). See -- also (^?). -- --
-- listToMaybe . toList ≡ preview folded ---- -- This is usually applied in the Reader Monad (->) -- s. -- --
-- preview = view . pre ---- --
-- preview :: Getter s a -> s -> Maybe a -- preview :: Fold s a -> s -> Maybe a -- preview :: Lens' s a -> s -> Maybe a -- preview :: Iso' s a -> s -> Maybe a -- preview :: Traversal' s a -> s -> Maybe a ---- -- However, it may be useful to think of its full generality when working -- with a Monad transformer stack: -- --
-- preview :: MonadReader s m => Getter s a -> m (Maybe a) -- preview :: MonadReader s m => Fold s a -> m (Maybe a) -- preview :: MonadReader s m => Lens' s a -> m (Maybe a) -- preview :: MonadReader s m => Iso' s a -> m (Maybe a) -- preview :: MonadReader s m => Traversal' s a -> m (Maybe a) --preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a) -- | Retrieve a function of the first value targeted by a Fold or -- Traversal (or Just the result from a Getter or -- Lens). -- -- This is usually applied in the Reader Monad (->) -- s. previews :: MonadReader s m => Getting (First r) s a -> (a -> r) -> m (Maybe r) -- | Retrieve the first index and value targeted by a Fold or -- Traversal (or Just the result from a Getter or -- Lens). See also (^@?). -- --
-- ipreview = view . ipre ---- -- This is usually applied in the Reader Monad (->) -- s. -- --
-- ipreview :: IndexedGetter i s a -> s -> Maybe (i, a) -- ipreview :: IndexedFold i s a -> s -> Maybe (i, a) -- ipreview :: IndexedLens' i s a -> s -> Maybe (i, a) -- ipreview :: IndexedTraversal' i s a -> s -> Maybe (i, a) ---- -- However, it may be useful to think of its full generality when working -- with a Monad transformer stack: -- --
-- ipreview :: MonadReader s m => IndexedGetter s a -> m (Maybe (i, a)) -- ipreview :: MonadReader s m => IndexedFold s a -> m (Maybe (i, a)) -- ipreview :: MonadReader s m => IndexedLens' s a -> m (Maybe (i, a)) -- ipreview :: MonadReader s m => IndexedTraversal' s a -> m (Maybe (i, a)) --ipreview :: MonadReader s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a)) -- | Retrieve a function of the first index and value targeted by an -- IndexedFold or IndexedTraversal (or Just the -- result from an IndexedGetter or IndexedLens). See also -- (^@?). -- --
-- ipreviews = views . ipre ---- -- This is usually applied in the Reader Monad (->) -- s. -- --
-- ipreviews :: IndexedGetter i s a -> (i -> a -> r) -> s -> Maybe r -- ipreviews :: IndexedFold i s a -> (i -> a -> r) -> s -> Maybe r -- ipreviews :: IndexedLens' i s a -> (i -> a -> r) -> s -> Maybe r -- ipreviews :: IndexedTraversal' i s a -> (i -> a -> r) -> s -> Maybe r ---- -- However, it may be useful to think of its full generality when working -- with a Monad transformer stack: -- --
-- ipreviews :: MonadReader s m => IndexedGetter i s a -> (i -> a -> r) -> m (Maybe r) -- ipreviews :: MonadReader s m => IndexedFold i s a -> (i -> a -> r) -> m (Maybe r) -- ipreviews :: MonadReader s m => IndexedLens' i s a -> (i -> a -> r) -> m (Maybe r) -- ipreviews :: MonadReader s m => IndexedTraversal' i s a -> (i -> a -> r) -> m (Maybe r) --ipreviews :: MonadReader s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r) -- | Retrieve the first value targeted by a Fold or Traversal -- (or Just the result from a Getter or Lens) into -- the current state. -- --
-- preuse = use . pre ---- --
-- preuse :: MonadState s m => Getter s a -> m (Maybe a) -- preuse :: MonadState s m => Fold s a -> m (Maybe a) -- preuse :: MonadState s m => Lens' s a -> m (Maybe a) -- preuse :: MonadState s m => Iso' s a -> m (Maybe a) -- preuse :: MonadState s m => Traversal' s a -> m (Maybe a) --preuse :: MonadState s m => Getting (First a) s a -> m (Maybe a) -- | Retrieve a function of the first value targeted by a Fold or -- Traversal (or Just the result from a Getter or -- Lens) into the current state. -- --
-- preuses = uses . pre ---- --
-- preuses :: MonadState s m => Getter s a -> (a -> r) -> m (Maybe r) -- preuses :: MonadState s m => Fold s a -> (a -> r) -> m (Maybe r) -- preuses :: MonadState s m => Lens' s a -> (a -> r) -> m (Maybe r) -- preuses :: MonadState s m => Iso' s a -> (a -> r) -> m (Maybe r) -- preuses :: MonadState s m => Traversal' s a -> (a -> r) -> m (Maybe r) --preuses :: MonadState s m => Getting (First r) s a -> (a -> r) -> m (Maybe r) -- | Retrieve the first index and value targeted by an IndexedFold -- or IndexedTraversal (or Just the index and result from -- an IndexedGetter or IndexedLens) into the current state. -- --
-- ipreuse = use . ipre ---- --
-- ipreuse :: MonadState s m => IndexedGetter i s a -> m (Maybe (i, a)) -- ipreuse :: MonadState s m => IndexedFold i s a -> m (Maybe (i, a)) -- ipreuse :: MonadState s m => IndexedLens' i s a -> m (Maybe (i, a)) -- ipreuse :: MonadState s m => IndexedTraversal' i s a -> m (Maybe (i, a)) --ipreuse :: MonadState s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a)) -- | Retrieve a function of the first index and value targeted by an -- IndexedFold or IndexedTraversal (or a function of -- Just the index and result from an IndexedGetter or -- IndexedLens) into the current state. -- --
-- ipreuses = uses . ipre ---- --
-- ipreuses :: MonadState s m => IndexedGetter i s a -> (i -> a -> r) -> m (Maybe r) -- ipreuses :: MonadState s m => IndexedFold i s a -> (i -> a -> r) -> m (Maybe r) -- ipreuses :: MonadState s m => IndexedLens' i s a -> (i -> a -> r) -> m (Maybe r) -- ipreuses :: MonadState s m => IndexedTraversal' i s a -> (i -> a -> r) -> m (Maybe r) --ipreuses :: MonadState s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r) -- | Check to see if this Fold or Traversal matches 1 or more -- entries. -- --
-- >>> has (element 0) [] -- False ---- --
-- >>> has _Left (Left 12) -- True ---- --
-- >>> has _Right (Left 12) -- False ---- -- This will always return True for a Lens or -- Getter. -- --
-- >>> has _1 ("hello","world") -- True ---- --
-- has :: Getter s a -> s -> Bool -- has :: Fold s a -> s -> Bool -- has :: Iso' s a -> s -> Bool -- has :: Lens' s a -> s -> Bool -- has :: Traversal' s a -> s -> Bool --has :: Getting Any s a -> s -> Bool -- | Check to see if this Fold or Traversal has no matches. -- --
-- >>> hasn't _Left (Right 12) -- True ---- --
-- >>> hasn't _Left (Left 12) -- False --hasn't :: Getting All s a -> s -> Bool -- | Obtain a Fold by lifting an operation that returns a -- Foldable result. -- -- This can be useful to lift operations from Data.List and -- elsewhere into a Fold. -- --
-- >>> [1,2,3,4]^..folding tail -- [2,3,4] --folding :: Foldable f => (s -> f a) -> Fold s a ifolding :: (Foldable f, Indexable i p, Contravariant g, Applicative g) => (s -> f (i, a)) -> Over p g s t a b -- | Obtain a Fold by lifting foldr like function. -- --
-- >>> [1,2,3,4]^..foldring foldr -- [1,2,3,4] --foldring :: (Contravariant f, Applicative f) => ((a -> f a -> f a) -> f a -> s -> f a) -> LensLike f s t a b -- | Obtain FoldWithIndex by lifting ifoldr like function. ifoldring :: (Indexable i p, Contravariant f, Applicative f) => ((i -> a -> f a -> f a) -> f a -> s -> f a) -> Over p f s t a b -- | Obtain a Fold from any Foldable indexed by ordinal -- position. -- --
-- >>> Just 3^..folded -- [3] ---- --
-- >>> Nothing^..folded -- [] ---- --
-- >>> [(1,2),(3,4)]^..folded.both -- [1,2,3,4] --folded :: Foldable f => IndexedFold Int (f a) a -- | Obtain a Fold from any Foldable indexed by ordinal -- position. folded64 :: Foldable f => IndexedFold Int64 (f a) a -- | Build a Fold that unfolds its values from a seed. -- --
-- unfoldr ≡ toListOf . unfolded ---- --
-- >>> 10^..unfolded (\b -> if b == 0 then Nothing else Just (b, b-1)) -- [10,9,8,7,6,5,4,3,2,1] --unfolded :: (b -> Maybe (a, b)) -> Fold b a -- | x ^. iterated f returns an infinite -- Fold1 of repeated applications of f to x. -- --
-- toListOf (iterated f) a ≡ iterate f a ---- --
-- iterated :: (a -> a) -> Fold1 a a --iterated :: Apply f => (a -> a) -> LensLike' f a a -- | Obtain an Fold that can be composed with to filter another -- Lens, Iso, Getter, Fold (or -- Traversal). -- -- Note: This is not a legal Traversal, unless you are very -- careful not to invalidate the predicate on the target. -- -- Note: This is also not a legal Prism, unless you are -- very careful not to inject a value that matches the predicate. -- -- As a counter example, consider that given evens = filtered -- even the second Traversal law is violated: -- --
-- over evens succ . over evens succ /= over evens (succ . succ) ---- -- So, in order for this to qualify as a legal Traversal you can -- only use it for actions that preserve the result of the predicate! -- --
-- >>> [1..10]^..folded.filtered even -- [2,4,6,8,10] ---- -- This will preserve an index if it is present. filtered :: (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a -- | This allows you to traverse the elements of a pretty much any -- LensLike construction in the opposite order. -- -- This will preserve indexes on Indexed types and will give you -- the elements of a (finite) Fold or Traversal in the -- opposite order. -- -- This has no practical impact on a Getter, Setter, -- Lens or Iso. -- -- NB: To write back through an Iso, you want to use -- from. Similarly, to write back through an Prism, you -- want to use re. backwards :: (Profunctor p, Profunctor q) => Optical p q (Backwards f) s t a b -> Optical p q f s t a b -- | Form a Fold1 by repeating the input forever. -- --
-- repeat ≡ toListOf repeated ---- --
-- >>> timingOut $ 5^..taking 20 repeated -- [5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5] ---- --
-- repeated :: Fold1 a a --repeated :: Apply f => LensLike' f a a -- | A Fold that replicates its input n times. -- --
-- replicate n ≡ toListOf (replicated n) ---- --
-- >>> 5^..replicated 20 -- [5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5] --replicated :: Int -> Fold a a -- | Transform a non-empty Fold into a Fold1 that loops over -- its elements over and over. -- --
-- >>> timingOut $ [1,2,3]^..taking 7 (cycled traverse) -- [1,2,3,1,2,3,1] ---- --
-- cycled :: Fold1 s a -> Fold1 s a --cycled :: Apply f => LensLike f s t a b -> LensLike f s t a b -- | Obtain a Fold by taking elements from another Fold, -- Lens, Iso, Getter or Traversal while a -- predicate holds. -- --
-- takeWhile p ≡ toListOf (takingWhile p folded) ---- --
-- >>> timingOut $ toListOf (takingWhile (<=3) folded) [1..] -- [1,2,3] ---- --
-- takingWhile :: (a -> Bool) -> Fold s a -> Fold s a -- takingWhile :: (a -> Bool) -> Getter s a -> Fold s a -- takingWhile :: (a -> Bool) -> Traversal' s a -> Fold s a -- * See note below -- takingWhile :: (a -> Bool) -> Lens' s a -> Fold s a -- * See note below -- takingWhile :: (a -> Bool) -> Prism' s a -> Fold s a -- * See note below -- takingWhile :: (a -> Bool) -> Iso' s a -> Fold s a -- * See note below -- takingWhile :: (a -> Bool) -> IndexedTraversal' i s a -> IndexedFold i s a -- * See note below -- takingWhile :: (a -> Bool) -> IndexedLens' i s a -> IndexedFold i s a -- * See note below -- takingWhile :: (a -> Bool) -> IndexedFold i s a -> IndexedFold i s a -- takingWhile :: (a -> Bool) -> IndexedGetter i s a -> IndexedFold i s a ---- -- Note: When applied to a Traversal, takingWhile -- yields something that can be used as if it were a Traversal, -- but which is not a Traversal per the laws, unless you are -- careful to ensure that you do not invalidate the predicate when -- writing back through it. takingWhile :: (Conjoined p, Applicative f) => (a -> Bool) -> Over p (TakingWhile p f a a) s t a a -> Over p f s t a a -- | Obtain a Fold by dropping elements from another Fold, -- Lens, Iso, Getter or Traversal while a -- predicate holds. -- --
-- dropWhile p ≡ toListOf (droppingWhile p folded) ---- --
-- >>> toListOf (droppingWhile (<=3) folded) [1..6] -- [4,5,6] ---- --
-- >>> toListOf (droppingWhile (<=3) folded) [1,6,1] -- [6,1] ---- --
-- droppingWhile :: (a -> Bool) -> Fold s a -> Fold s a -- droppingWhile :: (a -> Bool) -> Getter s a -> Fold s a -- droppingWhile :: (a -> Bool) -> Traversal' s a -> Fold s a -- see notes -- droppingWhile :: (a -> Bool) -> Lens' s a -> Fold s a -- see notes -- droppingWhile :: (a -> Bool) -> Prism' s a -> Fold s a -- see notes -- droppingWhile :: (a -> Bool) -> Iso' s a -> Fold s a -- see notes ---- --
-- droppingWhile :: (a -> Bool) -> IndexPreservingTraversal' s a -> IndexPreservingFold s a -- see notes -- droppingWhile :: (a -> Bool) -> IndexPreservingLens' s a -> IndexPreservingFold s a -- see notes -- droppingWhile :: (a -> Bool) -> IndexPreservingGetter s a -> IndexPreservingFold s a -- droppingWhile :: (a -> Bool) -> IndexPreservingFold s a -> IndexPreservingFold s a ---- --
-- droppingWhile :: (a -> Bool) -> IndexedTraversal' i s a -> IndexedFold i s a -- see notes -- droppingWhile :: (a -> Bool) -> IndexedLens' i s a -> IndexedFold i s a -- see notes -- droppingWhile :: (a -> Bool) -> IndexedGetter i s a -> IndexedFold i s a -- droppingWhile :: (a -> Bool) -> IndexedFold i s a -> IndexedFold i s a ---- -- Note: Many uses of this combinator will yield something that meets the -- types, but not the laws of a valid Traversal or -- IndexedTraversal. The Traversal and -- IndexedTraversal laws are only satisfied if the new values you -- assign also pass the predicate! Otherwise subsequent traversals will -- visit fewer elements and Traversal fusion is not sound. droppingWhile :: (Conjoined p, Profunctor q, Applicative f) => (a -> Bool) -> Optical p q (Compose (State Bool) f) s t a a -> Optical p q f s t a a -- | A Fold over the individual words of a String. -- --
-- worded :: Fold String String -- worded :: Traversal' String String ---- --
-- worded :: IndexedFold Int String String -- worded :: IndexedTraversal' Int String String ---- -- Note: This function type-checks as a Traversal but it doesn't -- satisfy the laws. It's only valid to use it when you don't insert any -- whitespace characters while traversing, and if your original -- String contains only isolated space characters (and no other -- characters that count as space, such as non-breaking spaces). worded :: Applicative f => IndexedLensLike' Int f String String -- | A Fold over the individual lines of a String. -- --
-- lined :: Fold String String -- lined :: Traversal' String String ---- --
-- lined :: IndexedFold Int String String -- lined :: IndexedTraversal' Int String String ---- -- Note: This function type-checks as a Traversal but it doesn't -- satisfy the laws. It's only valid to use it when you don't insert any -- newline characters while traversing, and if your original -- String contains only isolated newline characters. lined :: Applicative f => IndexedLensLike' Int f String String -- | Map each part of a structure viewed through a Lens, -- Getter, Fold or Traversal to a monoid and combine -- the results. -- --
-- >>> foldMapOf (folded . both . _Just) Sum [(Just 21, Just 21)] -- Sum {getSum = 42} ---- --
-- foldMap = foldMapOf folded ---- --
-- foldMapOf ≡ views -- ifoldMapOf l = foldMapOf l . Indexed ---- --
-- foldMapOf :: Getter s a -> (a -> r) -> s -> r -- foldMapOf :: Monoid r => Fold s a -> (a -> r) -> s -> r -- foldMapOf :: Lens' s a -> (a -> r) -> s -> r -- foldMapOf :: Iso' s a -> (a -> r) -> s -> r -- foldMapOf :: Monoid r => Traversal' s a -> (a -> r) -> s -> r -- foldMapOf :: Monoid r => Prism' s a -> (a -> r) -> s -> r ---- --
-- foldMapOf :: Getting r s a -> (a -> r) -> s -> r --foldMapOf :: Getting r s a -> (a -> r) -> s -> r -- | Combine the elements of a structure viewed through a Lens, -- Getter, Fold or Traversal using a monoid. -- --
-- >>> foldOf (folded.folded) [[Sum 1,Sum 4],[Sum 8, Sum 8],[Sum 21]] -- Sum {getSum = 42} ---- --
-- fold = foldOf folded ---- --
-- foldOf ≡ view ---- --
-- foldOf :: Getter s m -> s -> m -- foldOf :: Monoid m => Fold s m -> s -> m -- foldOf :: Lens' s m -> s -> m -- foldOf :: Iso' s m -> s -> m -- foldOf :: Monoid m => Traversal' s m -> s -> m -- foldOf :: Monoid m => Prism' s m -> s -> m --foldOf :: Getting a s a -> s -> a -- | Right-associative fold of parts of a structure that are viewed through -- a Lens, Getter, Fold or Traversal. -- --
-- foldr ≡ foldrOf folded ---- --
-- foldrOf :: Getter s a -> (a -> r -> r) -> r -> s -> r -- foldrOf :: Fold s a -> (a -> r -> r) -> r -> s -> r -- foldrOf :: Lens' s a -> (a -> r -> r) -> r -> s -> r -- foldrOf :: Iso' s a -> (a -> r -> r) -> r -> s -> r -- foldrOf :: Traversal' s a -> (a -> r -> r) -> r -> s -> r -- foldrOf :: Prism' s a -> (a -> r -> r) -> r -> s -> r ---- --
-- ifoldrOf l ≡ foldrOf l . Indexed ---- --
-- foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r --foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r -- | Left-associative fold of the parts of a structure that are viewed -- through a Lens, Getter, Fold or Traversal. -- --
-- foldl ≡ foldlOf folded ---- --
-- foldlOf :: Getter s a -> (r -> a -> r) -> r -> s -> r -- foldlOf :: Fold s a -> (r -> a -> r) -> r -> s -> r -- foldlOf :: Lens' s a -> (r -> a -> r) -> r -> s -> r -- foldlOf :: Iso' s a -> (r -> a -> r) -> r -> s -> r -- foldlOf :: Traversal' s a -> (r -> a -> r) -> r -> s -> r -- foldlOf :: Prism' s a -> (r -> a -> r) -> r -> s -> r --foldlOf :: Getting (Dual (Endo r)) s a -> (r -> a -> r) -> r -> s -> r -- | Extract a list of the targets of a Fold. See also (^..). -- --
-- toList ≡ toListOf folded -- (^..) ≡ flip toListOf --toListOf :: Getting (Endo [a]) s a -> s -> [a] -- | Returns True if any target of a Fold satisfies a -- predicate. -- --
-- >>> anyOf both (=='x') ('x','y') -- True -- -- >>> import Data.Data.Lens -- -- >>> anyOf biplate (== "world") (((),2::Int),"hello",("world",11::Int)) -- True ---- --
-- any ≡ anyOf folded ---- --
-- ianyOf l ≡ allOf l . Indexed ---- --
-- anyOf :: Getter s a -> (a -> Bool) -> s -> Bool -- anyOf :: Fold s a -> (a -> Bool) -> s -> Bool -- anyOf :: Lens' s a -> (a -> Bool) -> s -> Bool -- anyOf :: Iso' s a -> (a -> Bool) -> s -> Bool -- anyOf :: Traversal' s a -> (a -> Bool) -> s -> Bool -- anyOf :: Prism' s a -> (a -> Bool) -> s -> Bool --anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool -- | Returns True if every target of a Fold satisfies a -- predicate. -- --
-- >>> allOf both (>=3) (4,5) -- True -- -- >>> allOf folded (>=2) [1..10] -- False ---- --
-- all ≡ allOf folded ---- --
-- iallOf l = allOf l . Indexed ---- --
-- allOf :: Getter s a -> (a -> Bool) -> s -> Bool -- allOf :: Fold s a -> (a -> Bool) -> s -> Bool -- allOf :: Lens' s a -> (a -> Bool) -> s -> Bool -- allOf :: Iso' s a -> (a -> Bool) -> s -> Bool -- allOf :: Traversal' s a -> (a -> Bool) -> s -> Bool -- allOf :: Prism' s a -> (a -> Bool) -> s -> Bool --allOf :: Getting All s a -> (a -> Bool) -> s -> Bool -- | Returns True only if no targets of a Fold satisfy a -- predicate. -- --
-- >>> noneOf each (is _Nothing) (Just 3, Just 4, Just 5) -- True -- -- >>> noneOf (folded.folded) (<10) [[13,99,20],[3,71,42]] -- False ---- --
-- inoneOf l = noneOf l . Indexed ---- --
-- noneOf :: Getter s a -> (a -> Bool) -> s -> Bool -- noneOf :: Fold s a -> (a -> Bool) -> s -> Bool -- noneOf :: Lens' s a -> (a -> Bool) -> s -> Bool -- noneOf :: Iso' s a -> (a -> Bool) -> s -> Bool -- noneOf :: Traversal' s a -> (a -> Bool) -> s -> Bool -- noneOf :: Prism' s a -> (a -> Bool) -> s -> Bool --noneOf :: Getting Any s a -> (a -> Bool) -> s -> Bool -- | Returns True if every target of a Fold is True. -- --
-- >>> andOf both (True,False) -- False -- -- >>> andOf both (True,True) -- True ---- --
-- and ≡ andOf folded ---- --
-- andOf :: Getter s Bool -> s -> Bool -- andOf :: Fold s Bool -> s -> Bool -- andOf :: Lens' s Bool -> s -> Bool -- andOf :: Iso' s Bool -> s -> Bool -- andOf :: Traversal' s Bool -> s -> Bool -- andOf :: Prism' s Bool -> s -> Bool --andOf :: Getting All s Bool -> s -> Bool -- | Returns True if any target of a Fold is True. -- --
-- >>> orOf both (True,False) -- True -- -- >>> orOf both (False,False) -- False ---- --
-- or ≡ orOf folded ---- --
-- orOf :: Getter s Bool -> s -> Bool -- orOf :: Fold s Bool -> s -> Bool -- orOf :: Lens' s Bool -> s -> Bool -- orOf :: Iso' s Bool -> s -> Bool -- orOf :: Traversal' s Bool -> s -> Bool -- orOf :: Prism' s Bool -> s -> Bool --orOf :: Getting Any s Bool -> s -> Bool -- | Calculate the Product of every number targeted by a -- Fold. -- --
-- >>> productOf both (4,5) -- 20 -- -- >>> productOf folded [1,2,3,4,5] -- 120 ---- --
-- product ≡ productOf folded ---- -- This operation may be more strict than you would expect. If you want a -- lazier version use ala Product . -- foldMapOf -- --
-- productOf :: Num a => Getter s a -> s -> a -- productOf :: Num a => Fold s a -> s -> a -- productOf :: Num a => Lens' s a -> s -> a -- productOf :: Num a => Iso' s a -> s -> a -- productOf :: Num a => Traversal' s a -> s -> a -- productOf :: Num a => Prism' s a -> s -> a --productOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a -- | Calculate the Sum of every number targeted by a Fold. -- --
-- >>> sumOf both (5,6) -- 11 -- -- >>> sumOf folded [1,2,3,4] -- 10 -- -- >>> sumOf (folded.both) [(1,2),(3,4)] -- 10 -- -- >>> import Data.Data.Lens -- -- >>> sumOf biplate [(1::Int,[]),(2,[(3::Int,4::Int)])] :: Int -- 10 ---- --
-- sum ≡ sumOf folded ---- -- This operation may be more strict than you would expect. If you want a -- lazier version use ala Sum . -- foldMapOf -- --
-- sumOf _1 :: Num a => (a, b) -> a -- sumOf (folded . _1) :: (Foldable f, Num a) => f (a, b) -> a ---- --
-- sumOf :: Num a => Getter s a -> s -> a -- sumOf :: Num a => Fold s a -> s -> a -- sumOf :: Num a => Lens' s a -> s -> a -- sumOf :: Num a => Iso' s a -> s -> a -- sumOf :: Num a => Traversal' s a -> s -> a -- sumOf :: Num a => Prism' s a -> s -> a --sumOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a -- | Traverse over all of the targets of a Fold (or Getter), -- computing an Applicative (or Functor)-based answer, but -- unlike traverseOf do not construct a new structure. -- traverseOf_ generalizes traverse_ to work over any -- Fold. -- -- When passed a Getter, traverseOf_ can work over any -- Functor, but when passed a Fold, traverseOf_ -- requires an Applicative. -- --
-- >>> traverseOf_ both putStrLn ("hello","world") -- hello -- world ---- --
-- traverse_ ≡ traverseOf_ folded ---- --
-- traverseOf_ _2 :: Functor f => (c -> f r) -> (d, c) -> f () -- traverseOf_ _Left :: Applicative f => (a -> f b) -> Either a c -> f () ---- --
-- itraverseOf_ l ≡ traverseOf_ l . Indexed ---- -- The rather specific signature of traverseOf_ allows it to be -- used as if the signature was any of: -- --
-- traverseOf_ :: Functor f => Getter s a -> (a -> f r) -> s -> f () -- traverseOf_ :: Applicative f => Fold s a -> (a -> f r) -> s -> f () -- traverseOf_ :: Functor f => Lens' s a -> (a -> f r) -> s -> f () -- traverseOf_ :: Functor f => Iso' s a -> (a -> f r) -> s -> f () -- traverseOf_ :: Applicative f => Traversal' s a -> (a -> f r) -> s -> f () -- traverseOf_ :: Applicative f => Prism' s a -> (a -> f r) -> s -> f () --traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f () -- | Traverse over all of the targets of a Fold (or Getter), -- computing an Applicative (or Functor)-based answer, but -- unlike forOf do not construct a new structure. forOf_ -- generalizes for_ to work over any Fold. -- -- When passed a Getter, forOf_ can work over any -- Functor, but when passed a Fold, forOf_ requires -- an Applicative. -- --
-- for_ ≡ forOf_ folded ---- --
-- >>> forOf_ both ("hello","world") putStrLn -- hello -- world ---- -- The rather specific signature of forOf_ allows it to be used as -- if the signature was any of: -- --
-- iforOf_ l s ≡ forOf_ l s . Indexed ---- --
-- forOf_ :: Functor f => Getter s a -> s -> (a -> f r) -> f () -- forOf_ :: Applicative f => Fold s a -> s -> (a -> f r) -> f () -- forOf_ :: Functor f => Lens' s a -> s -> (a -> f r) -> f () -- forOf_ :: Functor f => Iso' s a -> s -> (a -> f r) -> f () -- forOf_ :: Applicative f => Traversal' s a -> s -> (a -> f r) -> f () -- forOf_ :: Applicative f => Prism' s a -> s -> (a -> f r) -> f () --forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f () -- | Evaluate each action in observed by a Fold on a structure from -- left to right, ignoring the results. -- --
-- sequenceA_ ≡ sequenceAOf_ folded ---- --
-- >>> sequenceAOf_ both (putStrLn "hello",putStrLn "world") -- hello -- world ---- --
-- sequenceAOf_ :: Functor f => Getter s (f a) -> s -> f () -- sequenceAOf_ :: Applicative f => Fold s (f a) -> s -> f () -- sequenceAOf_ :: Functor f => Lens' s (f a) -> s -> f () -- sequenceAOf_ :: Functor f => Iso' s (f a) -> s -> f () -- sequenceAOf_ :: Applicative f => Traversal' s (f a) -> s -> f () -- sequenceAOf_ :: Applicative f => Prism' s (f a) -> s -> f () --sequenceAOf_ :: Functor f => Getting (Traversed a f) s (f a) -> s -> f () -- | Map each target of a Fold on a structure to a monadic action, -- evaluate these actions from left to right, and ignore the results. -- --
-- >>> mapMOf_ both putStrLn ("hello","world") -- hello -- world ---- --
-- mapM_ ≡ mapMOf_ folded ---- --
-- mapMOf_ :: Monad m => Getter s a -> (a -> m r) -> s -> m () -- mapMOf_ :: Monad m => Fold s a -> (a -> m r) -> s -> m () -- mapMOf_ :: Monad m => Lens' s a -> (a -> m r) -> s -> m () -- mapMOf_ :: Monad m => Iso' s a -> (a -> m r) -> s -> m () -- mapMOf_ :: Monad m => Traversal' s a -> (a -> m r) -> s -> m () -- mapMOf_ :: Monad m => Prism' s a -> (a -> m r) -> s -> m () --mapMOf_ :: Monad m => Getting (Sequenced r m) s a -> (a -> m r) -> s -> m () -- | forMOf_ is mapMOf_ with two of its arguments flipped. -- --
-- >>> forMOf_ both ("hello","world") putStrLn -- hello -- world ---- --
-- forM_ ≡ forMOf_ folded ---- --
-- forMOf_ :: Monad m => Getter s a -> s -> (a -> m r) -> m () -- forMOf_ :: Monad m => Fold s a -> s -> (a -> m r) -> m () -- forMOf_ :: Monad m => Lens' s a -> s -> (a -> m r) -> m () -- forMOf_ :: Monad m => Iso' s a -> s -> (a -> m r) -> m () -- forMOf_ :: Monad m => Traversal' s a -> s -> (a -> m r) -> m () -- forMOf_ :: Monad m => Prism' s a -> s -> (a -> m r) -> m () --forMOf_ :: Monad m => Getting (Sequenced r m) s a -> s -> (a -> m r) -> m () -- | Evaluate each monadic action referenced by a Fold on the -- structure from left to right, and ignore the results. -- --
-- >>> sequenceOf_ both (putStrLn "hello",putStrLn "world") -- hello -- world ---- --
-- sequence_ ≡ sequenceOf_ folded ---- --
-- sequenceOf_ :: Monad m => Getter s (m a) -> s -> m () -- sequenceOf_ :: Monad m => Fold s (m a) -> s -> m () -- sequenceOf_ :: Monad m => Lens' s (m a) -> s -> m () -- sequenceOf_ :: Monad m => Iso' s (m a) -> s -> m () -- sequenceOf_ :: Monad m => Traversal' s (m a) -> s -> m () -- sequenceOf_ :: Monad m => Prism' s (m a) -> s -> m () --sequenceOf_ :: Monad m => Getting (Sequenced a m) s (m a) -> s -> m () -- | The sum of a collection of actions, generalizing concatOf. -- --
-- >>> asumOf both ("hello","world") -- "helloworld" ---- --
-- >>> asumOf each (Nothing, Just "hello", Nothing) -- Just "hello" ---- --
-- asum ≡ asumOf folded ---- --
-- asumOf :: Alternative f => Getter s (f a) -> s -> f a -- asumOf :: Alternative f => Fold s (f a) -> s -> f a -- asumOf :: Alternative f => Lens' s (f a) -> s -> f a -- asumOf :: Alternative f => Iso' s (f a) -> s -> f a -- asumOf :: Alternative f => Traversal' s (f a) -> s -> f a -- asumOf :: Alternative f => Prism' s (f a) -> s -> f a --asumOf :: Alternative f => Getting (Endo (f a)) s (f a) -> s -> f a -- | The sum of a collection of actions, generalizing concatOf. -- --
-- >>> msumOf both ("hello","world") -- "helloworld" ---- --
-- >>> msumOf each (Nothing, Just "hello", Nothing) -- Just "hello" ---- --
-- msum ≡ msumOf folded ---- --
-- msumOf :: MonadPlus m => Getter s (m a) -> s -> m a -- msumOf :: MonadPlus m => Fold s (m a) -> s -> m a -- msumOf :: MonadPlus m => Lens' s (m a) -> s -> m a -- msumOf :: MonadPlus m => Iso' s (m a) -> s -> m a -- msumOf :: MonadPlus m => Traversal' s (m a) -> s -> m a -- msumOf :: MonadPlus m => Prism' s (m a) -> s -> m a --msumOf :: MonadPlus m => Getting (Endo (m a)) s (m a) -> s -> m a -- | Map a function over all the targets of a Fold of a container -- and concatenate the resulting lists. -- --
-- >>> concatMapOf both (\x -> [x, x + 1]) (1,3) -- [1,2,3,4] ---- --
-- concatMap ≡ concatMapOf folded ---- --
-- concatMapOf :: Getter s a -> (a -> [r]) -> s -> [r] -- concatMapOf :: Fold s a -> (a -> [r]) -> s -> [r] -- concatMapOf :: Lens' s a -> (a -> [r]) -> s -> [r] -- concatMapOf :: Iso' s a -> (a -> [r]) -> s -> [r] -- concatMapOf :: Traversal' s a -> (a -> [r]) -> s -> [r] --concatMapOf :: Getting [r] s a -> (a -> [r]) -> s -> [r] -- | Concatenate all of the lists targeted by a Fold into a longer -- list. -- --
-- >>> concatOf both ("pan","ama") -- "panama" ---- --
-- concat ≡ concatOf folded -- concatOf ≡ view ---- --
-- concatOf :: Getter s [r] -> s -> [r] -- concatOf :: Fold s [r] -> s -> [r] -- concatOf :: Iso' s [r] -> s -> [r] -- concatOf :: Lens' s [r] -> s -> [r] -- concatOf :: Traversal' s [r] -> s -> [r] --concatOf :: Getting [r] s [r] -> s -> [r] -- | Does the element occur anywhere within a given Fold of the -- structure? -- --
-- >>> elemOf both "hello" ("hello","world") -- True ---- --
-- elem ≡ elemOf folded ---- --
-- elemOf :: Eq a => Getter s a -> a -> s -> Bool -- elemOf :: Eq a => Fold s a -> a -> s -> Bool -- elemOf :: Eq a => Lens' s a -> a -> s -> Bool -- elemOf :: Eq a => Iso' s a -> a -> s -> Bool -- elemOf :: Eq a => Traversal' s a -> a -> s -> Bool -- elemOf :: Eq a => Prism' s a -> a -> s -> Bool --elemOf :: Eq a => Getting Any s a -> a -> s -> Bool -- | Does the element not occur anywhere within a given Fold of the -- structure? -- --
-- >>> notElemOf each 'd' ('a','b','c') -- True ---- --
-- >>> notElemOf each 'a' ('a','b','c') -- False ---- --
-- notElem ≡ notElemOf folded ---- --
-- notElemOf :: Eq a => Getter s a -> a -> s -> Bool -- notElemOf :: Eq a => Fold s a -> a -> s -> Bool -- notElemOf :: Eq a => Iso' s a -> a -> s -> Bool -- notElemOf :: Eq a => Lens' s a -> a -> s -> Bool -- notElemOf :: Eq a => Traversal' s a -> a -> s -> Bool -- notElemOf :: Eq a => Prism' s a -> a -> s -> Bool --notElemOf :: Eq a => Getting All s a -> a -> s -> Bool -- | Calculate the number of targets there are for a Fold in a given -- container. -- -- Note: This can be rather inefficient for large containers and -- just like length, this will not terminate for infinite folds. -- --
-- length ≡ lengthOf folded ---- --
-- >>> lengthOf _1 ("hello",()) -- 1 ---- --
-- >>> lengthOf traverse [1..10] -- 10 ---- --
-- >>> lengthOf (traverse.traverse) [[1,2],[3,4],[5,6]] -- 6 ---- --
-- lengthOf (folded . folded) :: (Foldable f, Foldable g) => f (g a) -> Int ---- --
-- lengthOf :: Getter s a -> s -> Int -- lengthOf :: Fold s a -> s -> Int -- lengthOf :: Lens' s a -> s -> Int -- lengthOf :: Iso' s a -> s -> Int -- lengthOf :: Traversal' s a -> s -> Int --lengthOf :: Getting (Endo (Endo Int)) s a -> s -> Int -- | Returns True if this Fold or Traversal has no -- targets in the given container. -- -- Note: nullOf on a valid Iso, Lens or -- Getter should always return False. -- --
-- null ≡ nullOf folded ---- -- This may be rather inefficient compared to the null check of -- many containers. -- --
-- >>> nullOf _1 (1,2) -- False ---- --
-- >>> nullOf ignored () -- True ---- --
-- >>> nullOf traverse [] -- True ---- --
-- >>> nullOf (element 20) [1..10] -- True ---- --
-- nullOf (folded . _1 . folded) :: (Foldable f, Foldable g) => f (g a, b) -> Bool ---- --
-- nullOf :: Getter s a -> s -> Bool -- nullOf :: Fold s a -> s -> Bool -- nullOf :: Iso' s a -> s -> Bool -- nullOf :: Lens' s a -> s -> Bool -- nullOf :: Traversal' s a -> s -> Bool --nullOf :: Getting All s a -> s -> Bool -- | Returns True if this Fold or Traversal has any -- targets in the given container. -- -- A more "conversational" alias for this combinator is has. -- -- Note: notNullOf on a valid Iso, Lens or -- Getter should always return True. -- --
-- null ≡ notNullOf folded ---- -- This may be rather inefficient compared to the not . -- null check of many containers. -- --
-- >>> notNullOf _1 (1,2) -- True ---- --
-- >>> notNullOf traverse [1..10] -- True ---- --
-- >>> notNullOf folded [] -- False ---- --
-- >>> notNullOf (element 20) [1..10] -- False ---- --
-- notNullOf (folded . _1 . folded) :: (Foldable f, Foldable g) => f (g a, b) -> Bool ---- --
-- notNullOf :: Getter s a -> s -> Bool -- notNullOf :: Fold s a -> s -> Bool -- notNullOf :: Iso' s a -> s -> Bool -- notNullOf :: Lens' s a -> s -> Bool -- notNullOf :: Traversal' s a -> s -> Bool --notNullOf :: Getting Any s a -> s -> Bool -- | Retrieve the First entry of a Fold or Traversal -- or retrieve Just the result from a Getter or -- Lens. -- -- The answer is computed in a manner that leaks space less than -- ala First . foldMapOf and gives -- you back access to the outermost Just constructor more quickly, -- but may have worse constant factors. -- --
-- >>> firstOf traverse [1..10] -- Just 1 ---- --
-- >>> firstOf both (1,2) -- Just 1 ---- --
-- >>> firstOf ignored () -- Nothing ---- --
-- firstOf :: Getter s a -> s -> Maybe a -- firstOf :: Fold s a -> s -> Maybe a -- firstOf :: Lens' s a -> s -> Maybe a -- firstOf :: Iso' s a -> s -> Maybe a -- firstOf :: Traversal' s a -> s -> Maybe a --firstOf :: Getting (Leftmost a) s a -> s -> Maybe a -- | Retrieve the Last entry of a Fold or Traversal or -- retrieve Just the result from a Getter or Lens. -- -- The answer is computed in a manner that leaks space less than -- ala Last . foldMapOf and gives -- you back access to the outermost Just constructor more quickly, -- but may have worse constant factors. -- --
-- >>> lastOf traverse [1..10] -- Just 10 ---- --
-- >>> lastOf both (1,2) -- Just 2 ---- --
-- >>> lastOf ignored () -- Nothing ---- --
-- lastOf :: Getter s a -> s -> Maybe a -- lastOf :: Fold s a -> s -> Maybe a -- lastOf :: Lens' s a -> s -> Maybe a -- lastOf :: Iso' s a -> s -> Maybe a -- lastOf :: Traversal' s a -> s -> Maybe a --lastOf :: Getting (Rightmost a) s a -> s -> Maybe a -- | Obtain the maximum element (if any) targeted by a Fold or -- Traversal safely. -- -- Note: maximumOf on a valid Iso, Lens or -- Getter will always return Just a value. -- --
-- >>> maximumOf traverse [1..10] -- Just 10 ---- --
-- >>> maximumOf traverse [] -- Nothing ---- --
-- >>> maximumOf (folded.filtered even) [1,4,3,6,7,9,2] -- Just 6 ---- --
-- maximum ≡ fromMaybe (error "empty") . maximumOf folded ---- -- In the interest of efficiency, This operation has semantics more -- strict than strictly necessary. rmap getMax -- (foldMapOf l Max) has lazier semantics but could -- leak memory. -- --
-- maximumOf :: Ord a => Getter s a -> s -> Maybe a -- maximumOf :: Ord a => Fold s a -> s -> Maybe a -- maximumOf :: Ord a => Iso' s a -> s -> Maybe a -- maximumOf :: Ord a => Lens' s a -> s -> Maybe a -- maximumOf :: Ord a => Traversal' s a -> s -> Maybe a --maximumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a -- | Obtain the minimum element (if any) targeted by a Fold or -- Traversal safely. -- -- Note: minimumOf on a valid Iso, Lens or -- Getter will always return Just a value. -- --
-- >>> minimumOf traverse [1..10] -- Just 1 ---- --
-- >>> minimumOf traverse [] -- Nothing ---- --
-- >>> minimumOf (folded.filtered even) [1,4,3,6,7,9,2] -- Just 2 ---- --
-- minimum ≡ fromMaybe (error "empty") . minimumOf folded ---- -- In the interest of efficiency, This operation has semantics more -- strict than strictly necessary. rmap getMin -- (foldMapOf l Min) has lazier semantics but could -- leak memory. -- --
-- minimumOf :: Ord a => Getter s a -> s -> Maybe a -- minimumOf :: Ord a => Fold s a -> s -> Maybe a -- minimumOf :: Ord a => Iso' s a -> s -> Maybe a -- minimumOf :: Ord a => Lens' s a -> s -> Maybe a -- minimumOf :: Ord a => Traversal' s a -> s -> Maybe a --minimumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a -- | Obtain the maximum element (if any) targeted by a Fold, -- Traversal, Lens, Iso, or Getter according -- to a user supplied Ordering. -- --
-- >>> maximumByOf traverse (compare `on` length) ["mustard","relish","ham"] -- Just "mustard" ---- -- In the interest of efficiency, This operation has semantics more -- strict than strictly necessary. -- --
-- maximumBy cmp ≡ fromMaybe (error "empty") . maximumByOf folded cmp ---- --
-- maximumByOf :: Getter s a -> (a -> a -> Ordering) -> s -> Maybe a -- maximumByOf :: Fold s a -> (a -> a -> Ordering) -> s -> Maybe a -- maximumByOf :: Iso' s a -> (a -> a -> Ordering) -> s -> Maybe a -- maximumByOf :: Lens' s a -> (a -> a -> Ordering) -> s -> Maybe a -- maximumByOf :: Traversal' s a -> (a -> a -> Ordering) -> s -> Maybe a --maximumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a -- | Obtain the minimum element (if any) targeted by a Fold, -- Traversal, Lens, Iso or Getter according -- to a user supplied Ordering. -- -- In the interest of efficiency, This operation has semantics more -- strict than strictly necessary. -- --
-- >>> minimumByOf traverse (compare `on` length) ["mustard","relish","ham"] -- Just "ham" ---- --
-- minimumBy cmp ≡ fromMaybe (error "empty") . minimumByOf folded cmp ---- --
-- minimumByOf :: Getter s a -> (a -> a -> Ordering) -> s -> Maybe a -- minimumByOf :: Fold s a -> (a -> a -> Ordering) -> s -> Maybe a -- minimumByOf :: Iso' s a -> (a -> a -> Ordering) -> s -> Maybe a -- minimumByOf :: Lens' s a -> (a -> a -> Ordering) -> s -> Maybe a -- minimumByOf :: Traversal' s a -> (a -> a -> Ordering) -> s -> Maybe a --minimumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a -- | The findOf function takes a Lens (or Getter, -- Iso, Fold, or Traversal), a predicate and a -- structure and returns the leftmost element of the structure matching -- the predicate, or Nothing if there is no such element. -- --
-- >>> findOf each even (1,3,4,6) -- Just 4 ---- --
-- >>> findOf folded even [1,3,5,7] -- Nothing ---- --
-- findOf :: Getter s a -> (a -> Bool) -> s -> Maybe a -- findOf :: Fold s a -> (a -> Bool) -> s -> Maybe a -- findOf :: Iso' s a -> (a -> Bool) -> s -> Maybe a -- findOf :: Lens' s a -> (a -> Bool) -> s -> Maybe a -- findOf :: Traversal' s a -> (a -> Bool) -> s -> Maybe a ---- --
-- find ≡ findOf folded -- ifindOf l ≡ findOf l . Indexed ---- -- A simpler version that didn't permit indexing, would be: -- --
-- findOf :: Getting (Endo (Maybe a)) s a -> (a -> Bool) -> s -> Maybe a -- findOf l p = foldrOf l (a y -> if p a then Just a else y) Nothing --findOf :: Getting (Endo (Maybe a)) s a -> (a -> Bool) -> s -> Maybe a -- | The findMOf function takes a Lens (or Getter, -- Iso, Fold, or Traversal), a monadic predicate and -- a structure and returns in the monad the leftmost element of the -- structure matching the predicate, or Nothing if there is no -- such element. -- --
-- >>> findMOf each ( \x -> print ("Checking " ++ show x) >> return (even x)) (1,3,4,6) -- "Checking 1" -- "Checking 3" -- "Checking 4" -- Just 4 ---- --
-- >>> findMOf each ( \x -> print ("Checking " ++ show x) >> return (even x)) (1,3,5,7) -- "Checking 1" -- "Checking 3" -- "Checking 5" -- "Checking 7" -- Nothing ---- --
-- findMOf :: (Monad m, Getter s a) -> (a -> m Bool) -> s -> m (Maybe a) -- findMOf :: (Monad m, Fold s a) -> (a -> m Bool) -> s -> m (Maybe a) -- findMOf :: (Monad m, Iso' s a) -> (a -> m Bool) -> s -> m (Maybe a) -- findMOf :: (Monad m, Lens' s a) -> (a -> m Bool) -> s -> m (Maybe a) -- findMOf :: (Monad m, Traversal' s a) -> (a -> m Bool) -> s -> m (Maybe a) ---- --
-- findMOf folded :: (Monad m, Foldable f) => (a -> m Bool) -> f a -> m (Maybe a) -- ifindMOf l ≡ findMOf l . Indexed ---- -- A simpler version that didn't permit indexing, would be: -- --
-- findMOf :: Monad m => Getting (Endo (m (Maybe a))) s a -> (a -> m Bool) -> s -> m (Maybe a) -- findMOf l p = foldrOf l (a y -> p a >>= x -> if x then return (Just a) else y) $ return Nothing --findMOf :: Monad m => Getting (Endo (m (Maybe a))) s a -> (a -> m Bool) -> s -> m (Maybe a) -- | Strictly fold right over the elements of a structure. -- --
-- foldr' ≡ foldrOf' folded ---- --
-- foldrOf' :: Getter s a -> (a -> r -> r) -> r -> s -> r -- foldrOf' :: Fold s a -> (a -> r -> r) -> r -> s -> r -- foldrOf' :: Iso' s a -> (a -> r -> r) -> r -> s -> r -- foldrOf' :: Lens' s a -> (a -> r -> r) -> r -> s -> r -- foldrOf' :: Traversal' s a -> (a -> r -> r) -> r -> s -> r --foldrOf' :: Getting (Dual (Endo (Endo r))) s a -> (a -> r -> r) -> r -> s -> r -- | Fold over the elements of a structure, associating to the left, but -- strictly. -- --
-- foldl' ≡ foldlOf' folded ---- --
-- foldlOf' :: Getter s a -> (r -> a -> r) -> r -> s -> r -- foldlOf' :: Fold s a -> (r -> a -> r) -> r -> s -> r -- foldlOf' :: Iso' s a -> (r -> a -> r) -> r -> s -> r -- foldlOf' :: Lens' s a -> (r -> a -> r) -> r -> s -> r -- foldlOf' :: Traversal' s a -> (r -> a -> r) -> r -> s -> r --foldlOf' :: Getting (Endo (Endo r)) s a -> (r -> a -> r) -> r -> s -> r -- | A variant of foldrOf that has no base case and thus may only be -- applied to lenses and structures such that the Lens views at -- least one element of the structure. -- --
-- >>> foldr1Of each (+) (1,2,3,4) -- 10 ---- --
-- foldr1Of l f ≡ foldr1 f . toListOf l -- foldr1 ≡ foldr1Of folded ---- --
-- foldr1Of :: Getter s a -> (a -> a -> a) -> s -> a -- foldr1Of :: Fold s a -> (a -> a -> a) -> s -> a -- foldr1Of :: Iso' s a -> (a -> a -> a) -> s -> a -- foldr1Of :: Lens' s a -> (a -> a -> a) -> s -> a -- foldr1Of :: Traversal' s a -> (a -> a -> a) -> s -> a --foldr1Of :: Getting (Endo (Maybe a)) s a -> (a -> a -> a) -> s -> a -- | A variant of foldlOf that has no base case and thus may only be -- applied to lenses and structures such that the Lens views at -- least one element of the structure. -- --
-- >>> foldl1Of each (+) (1,2,3,4) -- 10 ---- --
-- foldl1Of l f ≡ foldl1 f . toListOf l -- foldl1 ≡ foldl1Of folded ---- --
-- foldl1Of :: Getter s a -> (a -> a -> a) -> s -> a -- foldl1Of :: Fold s a -> (a -> a -> a) -> s -> a -- foldl1Of :: Iso' s a -> (a -> a -> a) -> s -> a -- foldl1Of :: Lens' s a -> (a -> a -> a) -> s -> a -- foldl1Of :: Traversal' s a -> (a -> a -> a) -> s -> a --foldl1Of :: Getting (Dual (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a -- | A variant of foldrOf' that has no base case and thus may only -- be applied to folds and structures such that the fold views at least -- one element of the structure. -- --
-- foldr1Of l f ≡ foldr1 f . toListOf l ---- --
-- foldr1Of' :: Getter s a -> (a -> a -> a) -> s -> a -- foldr1Of' :: Fold s a -> (a -> a -> a) -> s -> a -- foldr1Of' :: Iso' s a -> (a -> a -> a) -> s -> a -- foldr1Of' :: Lens' s a -> (a -> a -> a) -> s -> a -- foldr1Of' :: Traversal' s a -> (a -> a -> a) -> s -> a --foldr1Of' :: Getting (Dual (Endo (Endo (Maybe a)))) s a -> (a -> a -> a) -> s -> a -- | A variant of foldlOf' that has no base case and thus may only -- be applied to folds and structures such that the fold views at least -- one element of the structure. -- --
-- foldl1Of' l f ≡ foldl1' f . toListOf l ---- --
-- foldl1Of' :: Getter s a -> (a -> a -> a) -> s -> a -- foldl1Of' :: Fold s a -> (a -> a -> a) -> s -> a -- foldl1Of' :: Iso' s a -> (a -> a -> a) -> s -> a -- foldl1Of' :: Lens' s a -> (a -> a -> a) -> s -> a -- foldl1Of' :: Traversal' s a -> (a -> a -> a) -> s -> a --foldl1Of' :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a -- | Monadic fold over the elements of a structure, associating to the -- right, i.e. from right to left. -- --
-- foldrM ≡ foldrMOf folded ---- --
-- foldrMOf :: Monad m => Getter s a -> (a -> r -> m r) -> r -> s -> m r -- foldrMOf :: Monad m => Fold s a -> (a -> r -> m r) -> r -> s -> m r -- foldrMOf :: Monad m => Iso' s a -> (a -> r -> m r) -> r -> s -> m r -- foldrMOf :: Monad m => Lens' s a -> (a -> r -> m r) -> r -> s -> m r -- foldrMOf :: Monad m => Traversal' s a -> (a -> r -> m r) -> r -> s -> m r --foldrMOf :: Monad m => Getting (Dual (Endo (r -> m r))) s a -> (a -> r -> m r) -> r -> s -> m r -- | Monadic fold over the elements of a structure, associating to the -- left, i.e. from left to right. -- --
-- foldlM ≡ foldlMOf folded ---- --
-- foldlMOf :: Monad m => Getter s a -> (r -> a -> m r) -> r -> s -> m r -- foldlMOf :: Monad m => Fold s a -> (r -> a -> m r) -> r -> s -> m r -- foldlMOf :: Monad m => Iso' s a -> (r -> a -> m r) -> r -> s -> m r -- foldlMOf :: Monad m => Lens' s a -> (r -> a -> m r) -> r -> s -> m r -- foldlMOf :: Monad m => Traversal' s a -> (r -> a -> m r) -> r -> s -> m r --foldlMOf :: Monad m => Getting (Endo (r -> m r)) s a -> (r -> a -> m r) -> r -> s -> m r -- | An infix version of itoListOf. (^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)] -- | Perform a safe head (with index) of an IndexedFold or -- IndexedTraversal or retrieve Just the index and result -- from an IndexedGetter or IndexedLens. -- -- When using a IndexedTraversal as a partial IndexedLens, -- or an IndexedFold as a partial IndexedGetter this can be -- a convenient way to extract the optional value. -- --
-- (^@?) :: s -> IndexedGetter i s a -> Maybe (i, a) -- (^@?) :: s -> IndexedFold i s a -> Maybe (i, a) -- (^@?) :: s -> IndexedLens' i s a -> Maybe (i, a) -- (^@?) :: s -> IndexedTraversal' i s a -> Maybe (i, a) --(^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a) -- | Perform an *UNSAFE* head (with index) of an IndexedFold -- or IndexedTraversal assuming that it is there. -- --
-- (^@?!) :: s -> IndexedGetter i s a -> (i, a) -- (^@?!) :: s -> IndexedFold i s a -> (i, a) -- (^@?!) :: s -> IndexedLens' i s a -> (i, a) -- (^@?!) :: s -> IndexedTraversal' i s a -> (i, a) --(^@?!) :: s -> IndexedGetting i (Endo (i, a)) s a -> (i, a) -- | Fold an IndexedFold or IndexedTraversal by mapping -- indices and values to an arbitrary Monoid with access to the -- i. -- -- When you don't need access to the index then foldMapOf is more -- flexible in what it accepts. -- --
-- foldMapOf l ≡ ifoldMapOf l . const ---- --
-- ifoldMapOf :: IndexedGetter i s a -> (i -> a -> m) -> s -> m -- ifoldMapOf :: Monoid m => IndexedFold i s a -> (i -> a -> m) -> s -> m -- ifoldMapOf :: IndexedLens' i s a -> (i -> a -> m) -> s -> m -- ifoldMapOf :: Monoid m => IndexedTraversal' i s a -> (i -> a -> m) -> s -> m --ifoldMapOf :: IndexedGetting i m s a -> (i -> a -> m) -> s -> m -- | Right-associative fold of parts of a structure that are viewed through -- an IndexedFold or IndexedTraversal with access to the -- i. -- -- When you don't need access to the index then foldrOf is more -- flexible in what it accepts. -- --
-- foldrOf l ≡ ifoldrOf l . const ---- --
-- ifoldrOf :: IndexedGetter i s a -> (i -> a -> r -> r) -> r -> s -> r -- ifoldrOf :: IndexedFold i s a -> (i -> a -> r -> r) -> r -> s -> r -- ifoldrOf :: IndexedLens' i s a -> (i -> a -> r -> r) -> r -> s -> r -- ifoldrOf :: IndexedTraversal' i s a -> (i -> a -> r -> r) -> r -> s -> r --ifoldrOf :: IndexedGetting i (Endo r) s a -> (i -> a -> r -> r) -> r -> s -> r -- | Left-associative fold of the parts of a structure that are viewed -- through an IndexedFold or IndexedTraversal with access -- to the i. -- -- When you don't need access to the index then foldlOf is more -- flexible in what it accepts. -- --
-- foldlOf l ≡ ifoldlOf l . const ---- --
-- ifoldlOf :: IndexedGetter i s a -> (i -> r -> a -> r) -> r -> s -> r -- ifoldlOf :: IndexedFold i s a -> (i -> r -> a -> r) -> r -> s -> r -- ifoldlOf :: IndexedLens' i s a -> (i -> r -> a -> r) -> r -> s -> r -- ifoldlOf :: IndexedTraversal' i s a -> (i -> r -> a -> r) -> r -> s -> r --ifoldlOf :: IndexedGetting i (Dual (Endo r)) s a -> (i -> r -> a -> r) -> r -> s -> r -- | Return whether or not any element viewed through an IndexedFold -- or IndexedTraversal satisfy a predicate, with access to the -- i. -- -- When you don't need access to the index then anyOf is more -- flexible in what it accepts. -- --
-- anyOf l ≡ ianyOf l . const ---- --
-- ianyOf :: IndexedGetter i s a -> (i -> a -> Bool) -> s -> Bool -- ianyOf :: IndexedFold i s a -> (i -> a -> Bool) -> s -> Bool -- ianyOf :: IndexedLens' i s a -> (i -> a -> Bool) -> s -> Bool -- ianyOf :: IndexedTraversal' i s a -> (i -> a -> Bool) -> s -> Bool --ianyOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool -- | Return whether or not all elements viewed through an -- IndexedFold or IndexedTraversal satisfy a predicate, -- with access to the i. -- -- When you don't need access to the index then allOf is more -- flexible in what it accepts. -- --
-- allOf l ≡ iallOf l . const ---- --
-- iallOf :: IndexedGetter i s a -> (i -> a -> Bool) -> s -> Bool -- iallOf :: IndexedFold i s a -> (i -> a -> Bool) -> s -> Bool -- iallOf :: IndexedLens' i s a -> (i -> a -> Bool) -> s -> Bool -- iallOf :: IndexedTraversal' i s a -> (i -> a -> Bool) -> s -> Bool --iallOf :: IndexedGetting i All s a -> (i -> a -> Bool) -> s -> Bool -- | Return whether or not none of the elements viewed through an -- IndexedFold or IndexedTraversal satisfy a predicate, -- with access to the i. -- -- When you don't need access to the index then noneOf is more -- flexible in what it accepts. -- --
-- noneOf l ≡ inoneOf l . const ---- --
-- inoneOf :: IndexedGetter i s a -> (i -> a -> Bool) -> s -> Bool -- inoneOf :: IndexedFold i s a -> (i -> a -> Bool) -> s -> Bool -- inoneOf :: IndexedLens' i s a -> (i -> a -> Bool) -> s -> Bool -- inoneOf :: IndexedTraversal' i s a -> (i -> a -> Bool) -> s -> Bool --inoneOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool -- | Traverse the targets of an IndexedFold or -- IndexedTraversal with access to the i, discarding the -- results. -- -- When you don't need access to the index then traverseOf_ is -- more flexible in what it accepts. -- --
-- traverseOf_ l ≡ itraverseOf l . const ---- --
-- itraverseOf_ :: Functor f => IndexedGetter i s a -> (i -> a -> f r) -> s -> f () -- itraverseOf_ :: Applicative f => IndexedFold i s a -> (i -> a -> f r) -> s -> f () -- itraverseOf_ :: Functor f => IndexedLens' i s a -> (i -> a -> f r) -> s -> f () -- itraverseOf_ :: Applicative f => IndexedTraversal' i s a -> (i -> a -> f r) -> s -> f () --itraverseOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> (i -> a -> f r) -> s -> f () -- | Traverse the targets of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results (with the arguments flipped). -- --
-- iforOf_ ≡ flip . itraverseOf_ ---- -- When you don't need access to the index then forOf_ is more -- flexible in what it accepts. -- --
-- forOf_ l a ≡ iforOf_ l a . const ---- --
-- iforOf_ :: Functor f => IndexedGetter i s a -> s -> (i -> a -> f r) -> f () -- iforOf_ :: Applicative f => IndexedFold i s a -> s -> (i -> a -> f r) -> f () -- iforOf_ :: Functor f => IndexedLens' i s a -> s -> (i -> a -> f r) -> f () -- iforOf_ :: Applicative f => IndexedTraversal' i s a -> s -> (i -> a -> f r) -> f () --iforOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> s -> (i -> a -> f r) -> f () -- | Run monadic actions for each target of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results. -- -- When you don't need access to the index then mapMOf_ is more -- flexible in what it accepts. -- --
-- mapMOf_ l ≡ imapMOf l . const ---- --
-- imapMOf_ :: Monad m => IndexedGetter i s a -> (i -> a -> m r) -> s -> m () -- imapMOf_ :: Monad m => IndexedFold i s a -> (i -> a -> m r) -> s -> m () -- imapMOf_ :: Monad m => IndexedLens' i s a -> (i -> a -> m r) -> s -> m () -- imapMOf_ :: Monad m => IndexedTraversal' i s a -> (i -> a -> m r) -> s -> m () --imapMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> (i -> a -> m r) -> s -> m () -- | Run monadic actions for each target of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results (with the arguments flipped). -- --
-- iforMOf_ ≡ flip . imapMOf_ ---- -- When you don't need access to the index then forMOf_ is more -- flexible in what it accepts. -- --
-- forMOf_ l a ≡ iforMOf l a . const ---- --
-- iforMOf_ :: Monad m => IndexedGetter i s a -> s -> (i -> a -> m r) -> m () -- iforMOf_ :: Monad m => IndexedFold i s a -> s -> (i -> a -> m r) -> m () -- iforMOf_ :: Monad m => IndexedLens' i s a -> s -> (i -> a -> m r) -> m () -- iforMOf_ :: Monad m => IndexedTraversal' i s a -> s -> (i -> a -> m r) -> m () --iforMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> s -> (i -> a -> m r) -> m () -- | Concatenate the results of a function of the elements of an -- IndexedFold or IndexedTraversal with access to the -- index. -- -- When you don't need access to the index then concatMapOf is -- more flexible in what it accepts. -- --
-- concatMapOf l ≡ iconcatMapOf l . const -- iconcatMapOf ≡ ifoldMapOf ---- --
-- iconcatMapOf :: IndexedGetter i s a -> (i -> a -> [r]) -> s -> [r] -- iconcatMapOf :: IndexedFold i s a -> (i -> a -> [r]) -> s -> [r] -- iconcatMapOf :: IndexedLens' i s a -> (i -> a -> [r]) -> s -> [r] -- iconcatMapOf :: IndexedTraversal' i s a -> (i -> a -> [r]) -> s -> [r] --iconcatMapOf :: IndexedGetting i [r] s a -> (i -> a -> [r]) -> s -> [r] -- | The ifindOf function takes an IndexedFold or -- IndexedTraversal, a predicate that is also supplied the index, -- a structure and returns the left-most element of the structure -- matching the predicate, or Nothing if there is no such element. -- -- When you don't need access to the index then findOf is more -- flexible in what it accepts. -- --
-- findOf l ≡ ifindOf l . const ---- --
-- ifindOf :: IndexedGetter i s a -> (i -> a -> Bool) -> s -> Maybe a -- ifindOf :: IndexedFold i s a -> (i -> a -> Bool) -> s -> Maybe a -- ifindOf :: IndexedLens' i s a -> (i -> a -> Bool) -> s -> Maybe a -- ifindOf :: IndexedTraversal' i s a -> (i -> a -> Bool) -> s -> Maybe a --ifindOf :: IndexedGetting i (Endo (Maybe a)) s a -> (i -> a -> Bool) -> s -> Maybe a -- | The ifindMOf function takes an IndexedFold or -- IndexedTraversal, a monadic predicate that is also supplied the -- index, a structure and returns in the monad the left-most element of -- the structure matching the predicate, or Nothing if there is no -- such element. -- -- When you don't need access to the index then findMOf is more -- flexible in what it accepts. -- --
-- findMOf l ≡ ifindMOf l . const ---- --
-- ifindMOf :: Monad m => IndexedGetter i s a -> (i -> a -> m Bool) -> s -> m (Maybe a) -- ifindMOf :: Monad m => IndexedFold i s a -> (i -> a -> m Bool) -> s -> m (Maybe a) -- ifindMOf :: Monad m => IndexedLens' i s a -> (i -> a -> m Bool) -> s -> m (Maybe a) -- ifindMOf :: Monad m => IndexedTraversal' i s a -> (i -> a -> m Bool) -> s -> m (Maybe a) --ifindMOf :: Monad m => IndexedGetting i (Endo (m (Maybe a))) s a -> (i -> a -> m Bool) -> s -> m (Maybe a) -- | Strictly fold right over the elements of a structure with an -- index. -- -- When you don't need access to the index then foldrOf' is more -- flexible in what it accepts. -- --
-- foldrOf' l ≡ ifoldrOf' l . const ---- --
-- ifoldrOf' :: IndexedGetter i s a -> (i -> a -> r -> r) -> r -> s -> r -- ifoldrOf' :: IndexedFold i s a -> (i -> a -> r -> r) -> r -> s -> r -- ifoldrOf' :: IndexedLens' i s a -> (i -> a -> r -> r) -> r -> s -> r -- ifoldrOf' :: IndexedTraversal' i s a -> (i -> a -> r -> r) -> r -> s -> r --ifoldrOf' :: IndexedGetting i (Dual (Endo (r -> r))) s a -> (i -> a -> r -> r) -> r -> s -> r -- | Fold over the elements of a structure with an index, associating to -- the left, but strictly. -- -- When you don't need access to the index then foldlOf' is more -- flexible in what it accepts. -- --
-- foldlOf' l ≡ ifoldlOf' l . const ---- --
-- ifoldlOf' :: IndexedGetter i s a -> (i -> r -> a -> r) -> r -> s -> r -- ifoldlOf' :: IndexedFold i s a -> (i -> r -> a -> r) -> r -> s -> r -- ifoldlOf' :: IndexedLens' i s a -> (i -> r -> a -> r) -> r -> s -> r -- ifoldlOf' :: IndexedTraversal' i s a -> (i -> r -> a -> r) -> r -> s -> r --ifoldlOf' :: IndexedGetting i (Endo (r -> r)) s a -> (i -> r -> a -> r) -> r -> s -> r -- | Monadic fold right over the elements of a structure with an index. -- -- When you don't need access to the index then foldrMOf is more -- flexible in what it accepts. -- --
-- foldrMOf l ≡ ifoldrMOf l . const ---- --
-- ifoldrMOf :: Monad m => IndexedGetter i s a -> (i -> a -> r -> m r) -> r -> s -> m r -- ifoldrMOf :: Monad m => IndexedFold i s a -> (i -> a -> r -> m r) -> r -> s -> m r -- ifoldrMOf :: Monad m => IndexedLens' i s a -> (i -> a -> r -> m r) -> r -> s -> m r -- ifoldrMOf :: Monad m => IndexedTraversal' i s a -> (i -> a -> r -> m r) -> r -> s -> m r --ifoldrMOf :: Monad m => IndexedGetting i (Dual (Endo (r -> m r))) s a -> (i -> a -> r -> m r) -> r -> s -> m r -- | Monadic fold over the elements of a structure with an index, -- associating to the left. -- -- When you don't need access to the index then foldlMOf is more -- flexible in what it accepts. -- --
-- foldlMOf l ≡ ifoldlMOf l . const ---- --
-- ifoldlMOf :: Monad m => IndexedGetter i s a -> (i -> r -> a -> m r) -> r -> s -> m r -- ifoldlMOf :: Monad m => IndexedFold i s a -> (i -> r -> a -> m r) -> r -> s -> m r -- ifoldlMOf :: Monad m => IndexedLens' i s a -> (i -> r -> a -> m r) -> r -> s -> m r -- ifoldlMOf :: Monad m => IndexedTraversal' i s a -> (i -> r -> a -> m r) -> r -> s -> m r --ifoldlMOf :: Monad m => IndexedGetting i (Endo (r -> m r)) s a -> (i -> r -> a -> m r) -> r -> s -> m r -- | Extract the key-value pairs from a structure. -- -- When you don't need access to the indices in the result, then -- toListOf is more flexible in what it accepts. -- --
-- toListOf l ≡ map snd . itoListOf l ---- --
-- itoListOf :: IndexedGetter i s a -> s -> [(i,a)] -- itoListOf :: IndexedFold i s a -> s -> [(i,a)] -- itoListOf :: IndexedLens' i s a -> s -> [(i,a)] -- itoListOf :: IndexedTraversal' i s a -> s -> [(i,a)] --itoListOf :: IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)] -- | Retrieve the index of the first value targeted by a IndexedFold -- or IndexedTraversal which is equal to a given value. -- --
-- elemIndex ≡ elemIndexOf folded ---- --
-- elemIndexOf :: Eq a => IndexedFold i s a -> a -> s -> Maybe i -- elemIndexOf :: Eq a => IndexedTraversal' i s a -> a -> s -> Maybe i --elemIndexOf :: Eq a => IndexedGetting i (First i) s a -> a -> s -> Maybe i -- | Retrieve the indices of the values targeted by a IndexedFold or -- IndexedTraversal which are equal to a given value. -- --
-- elemIndices ≡ elemIndicesOf folded ---- --
-- elemIndicesOf :: Eq a => IndexedFold i s a -> a -> s -> [i] -- elemIndicesOf :: Eq a => IndexedTraversal' i s a -> a -> s -> [i] --elemIndicesOf :: Eq a => IndexedGetting i (Endo [i]) s a -> a -> s -> [i] -- | Retrieve the index of the first value targeted by a IndexedFold -- or IndexedTraversal which satisfies a predicate. -- --
-- findIndex ≡ findIndexOf folded ---- --
-- findIndexOf :: IndexedFold i s a -> (a -> Bool) -> s -> Maybe i -- findIndexOf :: IndexedTraversal' i s a -> (a -> Bool) -> s -> Maybe i --findIndexOf :: IndexedGetting i (First i) s a -> (a -> Bool) -> s -> Maybe i -- | Retrieve the indices of the values targeted by a IndexedFold or -- IndexedTraversal which satisfy a predicate. -- --
-- findIndices ≡ findIndicesOf folded ---- --
-- findIndicesOf :: IndexedFold i s a -> (a -> Bool) -> s -> [i] -- findIndicesOf :: IndexedTraversal' i s a -> (a -> Bool) -> s -> [i] --findIndicesOf :: IndexedGetting i (Endo [i]) s a -> (a -> Bool) -> s -> [i] -- | Filter an IndexedFold or IndexedGetter, obtaining an -- IndexedFold. -- --
-- >>> [0,0,0,5,5,5]^..traversed.ifiltered (\i a -> i <= a) -- [0,5,5,5] ---- -- Compose with filtered to filter another IndexedLens, -- IndexedIso, IndexedGetter, IndexedFold (or -- IndexedTraversal) with access to both the value and the index. -- -- Note: As with filtered, this is not a legal -- IndexedTraversal, unless you are very careful not to invalidate -- the predicate on the target! ifiltered :: (Indexable i p, Applicative f) => (i -> a -> Bool) -> Optical' p (Indexed i) f a a -- | Obtain an IndexedFold by taking elements from another -- IndexedFold, IndexedLens, IndexedGetter or -- IndexedTraversal while a predicate holds. -- --
-- itakingWhile :: (i -> a -> Bool) -> IndexedFold i s a -> IndexedFold i s a -- itakingWhile :: (i -> a -> Bool) -> IndexedTraversal' i s a -> IndexedFold i s a -- itakingWhile :: (i -> a -> Bool) -> IndexedLens' i s a -> IndexedFold i s a -- itakingWhile :: (i -> a -> Bool) -> IndexedGetter i s a -> IndexedFold i s a --itakingWhile :: (Indexable i p, Profunctor q, Contravariant f, Applicative f) => (i -> a -> Bool) -> Optical' (Indexed i) q (Const (Endo (f s))) s a -> Optical' p q f s a -- | Obtain an IndexedFold by dropping elements from another -- IndexedFold, IndexedLens, IndexedGetter or -- IndexedTraversal while a predicate holds. -- --
-- idroppingWhile :: (i -> a -> Bool) -> IndexedFold i s a -> IndexedFold i s a -- idroppingWhile :: (i -> a -> Bool) -> IndexedTraversal' i s a -> IndexedFold i s a -- see notes -- idroppingWhile :: (i -> a -> Bool) -> IndexedLens' i s a -> IndexedFold i s a -- see notes -- idroppingWhile :: (i -> a -> Bool) -> IndexedGetter i s a -> IndexedFold i s a ---- -- Applying idroppingWhile to an IndexedLens or -- IndexedTraversal will still allow you to use it as a -- pseudo-IndexedTraversal, but if you change the value of the -- targets to ones where the predicate returns True, then you will -- break the Traversal laws and Traversal fusion will no -- longer be sound. idroppingWhile :: (Indexable i p, Profunctor q, Applicative f) => (i -> a -> Bool) -> Optical (Indexed i) q (Compose (State Bool) f) s t a a -> Optical p q f s t a a -- | Used for preview. data Leftmost a -- | Used for lastOf. data Rightmost a -- | Used internally by traverseOf_ and the like. -- -- The argument a of the result should not be used! data Traversed a f -- | Used internally by mapM_ and the like. -- -- The argument a of the result should not be used! data Sequenced a m -- | Fold a value using its Foldable instance using explicitly -- provided Monoid operations. This is like fold where the -- Monoid instance can be manually specified. -- --
-- foldBy mappend mempty ≡ fold ---- --
-- >>> foldBy (++) [] ["hello","world"] -- "helloworld" --foldBy :: Foldable t => (a -> a -> a) -> a -> t a -> a -- | Fold a value using a specified Fold and Monoid -- operations. This is like foldBy where the Foldable -- instance can be manually specified. -- --
-- foldByOf folded ≡ foldBy ---- --
-- foldByOf :: Getter s a -> (a -> a -> a) -> a -> s -> a -- foldByOf :: Fold s a -> (a -> a -> a) -> a -> s -> a -- foldByOf :: Lens' s a -> (a -> a -> a) -> a -> s -> a -- foldByOf :: Traversal' s a -> (a -> a -> a) -> a -> s -> a -- foldByOf :: Iso' s a -> (a -> a -> a) -> a -> s -> a ---- --
-- >>> foldByOf both (++) [] ("hello","world") -- "helloworld" --foldByOf :: Fold s a -> (a -> a -> a) -> a -> s -> a -- | Fold a value using its Foldable instance using explicitly -- provided Monoid operations. This is like foldMap where -- the Monoid instance can be manually specified. -- --
-- foldMapBy mappend mempty ≡ foldMap ---- --
-- >>> foldMapBy (+) 0 length ["hello","world"] -- 10 --foldMapBy :: Foldable t => (r -> r -> r) -> r -> (a -> r) -> t a -> r -- | Fold a value using a specified Fold and Monoid -- operations. This is like foldMapBy where the Foldable -- instance can be manually specified. -- --
-- foldMapByOf folded ≡ foldMapBy ---- --
-- foldMapByOf :: Getter s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r -- foldMapByOf :: Fold s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r -- foldMapByOf :: Traversal' s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r -- foldMapByOf :: Lens' s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r -- foldMapByOf :: Iso' s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r ---- --
-- >>> foldMapByOf both (+) 0 length ("hello","world") -- 10 --foldMapByOf :: Fold s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r -- | A Traversal s t a b is a generalization of -- traverse from Traversable. It allows you to -- traverse over a structure and change out its contents with -- monadic or Applicative side-effects. Starting from -- --
-- traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) ---- -- we monomorphize the contents and result to obtain -- --
-- type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t ---- -- While a Traversal isn't quite a Fold, it _can_ be used -- for Getting like a Fold, because given a Monoid -- m, we have an Applicative for (Const -- m). Everything you know how to do with a Traversable -- container, you can with with a Traversal, and here we provide -- combinators that generalize the usual Traversable operations. module Control.Lens.Traversal -- | A Traversal can be used directly as a Setter or a -- Fold (but not as a Lens) and provides the ability to -- both read and update multiple fields, subject to some relatively weak -- Traversal laws. -- -- These have also been known as multilenses, but they have the signature -- and spirit of -- --
-- traverse :: Traversable f => Traversal (f a) (f b) a b ---- -- and the more evocative name suggests their application. -- -- Most of the time the Traversal you will want to use is just -- traverse, but you can also pass any Lens or Iso -- as a Traversal, and composition of a Traversal (or -- Lens or Iso) with a Traversal (or Lens or -- Iso) using (.) forms a valid Traversal. -- -- The laws for a Traversal t follow from the laws for -- Traversable as stated in "The Essence of the Iterator Pattern". -- --
-- t pure ≡ pure -- fmap (t f) . t g ≡ getCompose . t (Compose . fmap f . g) ---- -- One consequence of this requirement is that a Traversal needs -- to leave the same number of elements as a candidate for subsequent -- Traversal that it started with. Another testament to the -- strength of these laws is that the caveat expressed in section 5.5 of -- the "Essence of the Iterator Pattern" about exotic Traversable -- instances that traverse the same entry multiple times was -- actually already ruled out by the second law in that same paper! type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t -- |
-- type Traversal' = Simple Traversal --type Traversal' s a = Traversal s s a a type Traversal1 s t a b = forall f. Apply f => (a -> f b) -> s -> f t type Traversal1' s a = Traversal1 s s a a -- | Every IndexedTraversal is a valid Traversal or -- IndexedFold. -- -- The Indexed constraint is used to allow an -- IndexedTraversal to be used directly as a Traversal. -- -- The Traversal laws are still required to hold. -- -- In addition, the index i should satisfy the requirement that -- it stays unchanged even when modifying the value a, otherwise -- traversals like indices break the Traversal laws. type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f t -- |
-- type IndexedTraversal' i = Simple (IndexedTraversal i) --type IndexedTraversal' i s a = IndexedTraversal i s s a a type IndexedTraversal1 i s t a b = forall p f. (Indexable i p, Apply f) => p a (f b) -> s -> f t type IndexedTraversal1' i s a = IndexedTraversal1 i s s a a -- | When you see this as an argument to a function, it expects a -- Traversal. type ATraversal s t a b = LensLike (Bazaar (->) a b) s t a b -- |
-- type ATraversal' = Simple ATraversal --type ATraversal' s a = ATraversal s s a a -- | When you see this as an argument to a function, it expects a -- Traversal1. type ATraversal1 s t a b = LensLike (Bazaar1 (->) a b) s t a b -- |
-- type ATraversal1' = Simple ATraversal1 --type ATraversal1' s a = ATraversal1 s s a a -- | When you see this as an argument to a function, it expects an -- IndexedTraversal. type AnIndexedTraversal i s t a b = Over (Indexed i) (Bazaar (Indexed i) a b) s t a b -- |
-- type AnIndexedTraversal' = Simple (AnIndexedTraversal i) --type AnIndexedTraversal' i s a = AnIndexedTraversal i s s a a -- | When you see this as an argument to a function, it expects an -- IndexedTraversal1. type AnIndexedTraversal1 i s t a b = Over (Indexed i) (Bazaar1 (Indexed i) a b) s t a b -- |
-- type AnIndexedTraversal1' = Simple (AnIndexedTraversal1 i) --type AnIndexedTraversal1' i s a = AnIndexedTraversal1 i s s a a -- | When you see this as an argument to a function, it expects -- --
-- type Traversing' f = Simple (Traversing f) --type Traversing' p f s a = Traversing p f s s a a type Traversing1 p f s t a b = Over p (BazaarT1 p f a b) s t a b type Traversing1' p f s a = Traversing1 p f s s a a -- | Map each element of a structure targeted by a Lens or -- Traversal, evaluate these actions from left to right, and -- collect the results. -- -- This function is only provided for consistency, id is strictly -- more general. -- --
-- >>> traverseOf each print (1,2,3) -- 1 -- 2 -- 3 -- ((),(),()) ---- --
-- traverseOf ≡ id -- itraverseOf l ≡ traverseOf l . Indexed -- itraverseOf itraversed ≡ itraverse ---- -- This yields the obvious law: -- --
-- traverse ≡ traverseOf traverse ---- --
-- traverseOf :: Functor f => Iso s t a b -> (a -> f b) -> s -> f t -- traverseOf :: Functor f => Lens s t a b -> (a -> f b) -> s -> f t -- traverseOf :: Applicative f => Traversal s t a b -> (a -> f b) -> s -> f t --traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t -- | A version of traverseOf with the arguments flipped, such that: -- --
-- >>> forOf each (1,2,3) print -- 1 -- 2 -- 3 -- ((),(),()) ---- -- This function is only provided for consistency, flip is -- strictly more general. -- --
-- forOf ≡ flip -- forOf ≡ flip . traverseOf ---- --
-- for ≡ forOf traverse -- ifor l s ≡ for l s . Indexed ---- --
-- forOf :: Functor f => Iso s t a b -> s -> (a -> f b) -> f t -- forOf :: Functor f => Lens s t a b -> s -> (a -> f b) -> f t -- forOf :: Applicative f => Traversal s t a b -> s -> (a -> f b) -> f t --forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t -- | Evaluate each action in the structure from left to right, and collect -- the results. -- --
-- >>> sequenceAOf both ([1,2],[3,4]) -- [(1,3),(1,4),(2,3),(2,4)] ---- --
-- sequenceA ≡ sequenceAOf traverse ≡ traverse id -- sequenceAOf l ≡ traverseOf l id ≡ l id ---- --
-- sequenceAOf :: Functor f => Iso s t (f b) b -> s -> f t -- sequenceAOf :: Functor f => Lens s t (f b) b -> s -> f t -- sequenceAOf :: Applicative f => Traversal s t (f b) b -> s -> f t --sequenceAOf :: LensLike f s t (f b) b -> s -> f t -- | Map each element of a structure targeted by a Lens to a monadic -- action, evaluate these actions from left to right, and collect the -- results. -- --
-- >>> mapMOf both (\x -> [x, x + 1]) (1,3) -- [(1,3),(1,4),(2,3),(2,4)] ---- --
-- mapM ≡ mapMOf traverse -- imapMOf l ≡ forM l . Indexed ---- --
-- mapMOf :: Monad m => Iso s t a b -> (a -> m b) -> s -> m t -- mapMOf :: Monad m => Lens s t a b -> (a -> m b) -> s -> m t -- mapMOf :: Monad m => Traversal s t a b -> (a -> m b) -> s -> m t --mapMOf :: LensLike (WrappedMonad m) s t a b -> (a -> m b) -> s -> m t -- | forMOf is a flipped version of mapMOf, consistent with -- the definition of forM. -- --
-- >>> forMOf both (1,3) $ \x -> [x, x + 1] -- [(1,3),(1,4),(2,3),(2,4)] ---- --
-- forM ≡ forMOf traverse -- forMOf l ≡ flip (mapMOf l) -- iforMOf l s ≡ forM l s . Indexed ---- --
-- forMOf :: Monad m => Iso s t a b -> s -> (a -> m b) -> m t -- forMOf :: Monad m => Lens s t a b -> s -> (a -> m b) -> m t -- forMOf :: Monad m => Traversal s t a b -> s -> (a -> m b) -> m t --forMOf :: LensLike (WrappedMonad m) s t a b -> s -> (a -> m b) -> m t -- | Sequence the (monadic) effects targeted by a Lens in a -- container from left to right. -- --
-- >>> sequenceOf each ([1,2],[3,4],[5,6]) -- [(1,3,5),(1,3,6),(1,4,5),(1,4,6),(2,3,5),(2,3,6),(2,4,5),(2,4,6)] ---- --
-- sequence ≡ sequenceOf traverse -- sequenceOf l ≡ mapMOf l id -- sequenceOf l ≡ unwrapMonad . l WrapMonad ---- --
-- sequenceOf :: Monad m => Iso s t (m b) b -> s -> m t -- sequenceOf :: Monad m => Lens s t (m b) b -> s -> m t -- sequenceOf :: Monad m => Traversal s t (m b) b -> s -> m t --sequenceOf :: LensLike (WrappedMonad m) s t (m b) b -> s -> m t -- | This generalizes transpose to an arbitrary Traversal. -- -- Note: transpose handles ragged inputs more intelligently, but -- for non-ragged inputs: -- --
-- >>> transposeOf traverse [[1,2,3],[4,5,6]] -- [[1,4],[2,5],[3,6]] ---- --
-- transpose ≡ transposeOf traverse ---- -- Since every Lens is a Traversal, we can use this as a -- form of monadic strength as well: -- --
-- transposeOf _2 :: (b, [a]) -> [(b, a)] --transposeOf :: LensLike ZipList s t [a] a -> s -> [t] -- | This generalizes mapAccumL to an arbitrary Traversal. -- --
-- mapAccumL ≡ mapAccumLOf traverse ---- -- mapAccumLOf accumulates State from left to right. -- --
-- mapAccumLOf :: Iso s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- mapAccumLOf :: Lens s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- mapAccumLOf :: Traversal s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) ---- --
-- mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- mapAccumLOf l f acc0 s = swap (runState (l (a -> state (acc -> swap (f acc a))) s) acc0) --mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- | This generalizes mapAccumR to an arbitrary Traversal. -- --
-- mapAccumR ≡ mapAccumROf traverse ---- -- mapAccumROf accumulates State from right to left. -- --
-- mapAccumROf :: Iso s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- mapAccumROf :: Lens s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- mapAccumROf :: Traversal s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) ---- --
-- mapAccumROf :: LensLike (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) --mapAccumROf :: LensLike (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- | This permits the use of scanr1 over an arbitrary -- Traversal or Lens. -- --
-- scanr1 ≡ scanr1Of traverse ---- --
-- scanr1Of :: Iso s t a a -> (a -> a -> a) -> s -> t -- scanr1Of :: Lens s t a a -> (a -> a -> a) -> s -> t -- scanr1Of :: Traversal s t a a -> (a -> a -> a) -> s -> t --scanr1Of :: LensLike (Backwards (State (Maybe a))) s t a a -> (a -> a -> a) -> s -> t -- | This permits the use of scanl1 over an arbitrary -- Traversal or Lens. -- --
-- scanl1 ≡ scanl1Of traverse ---- --
-- scanl1Of :: Iso s t a a -> (a -> a -> a) -> s -> t -- scanl1Of :: Lens s t a a -> (a -> a -> a) -> s -> t -- scanl1Of :: Traversal s t a a -> (a -> a -> a) -> s -> t --scanl1Of :: LensLike (State (Maybe a)) s t a a -> (a -> a -> a) -> s -> t -- | Try to map a function over this Traversal, failing if the -- Traversal has no targets. -- --
-- >>> failover (element 3) (*2) [1,2] :: Maybe [Int] -- Nothing ---- --
-- >>> failover _Left (*2) (Right 4) :: Maybe (Either Int Int) -- Nothing ---- --
-- >>> failover _Right (*2) (Right 4) :: Maybe (Either Int Int) -- Just (Right 8) ---- --
-- failover :: Alternative m => Traversal s t a b -> (a -> b) -> s -> m t --failover :: Alternative m => LensLike ((,) Any) s t a b -> (a -> b) -> s -> m t -- | Try to map a function which uses the index over this -- IndexedTraversal, failing if the IndexedTraversal has no -- targets. -- --
-- ifailover :: Alternative m => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> m t --ifailover :: Alternative m => Over (Indexed i) ((,) Any) s t a b -> (i -> a -> b) -> s -> m t -- | A Traversal is completely characterized by its behavior on a -- Bazaar. -- -- Cloning a Traversal is one way to make sure you aren't given -- something weaker, such as a Fold and can be used as a way to -- pass around traversals that have to be monomorphic in f. -- -- Note: This only accepts a proper Traversal (or Lens). To -- clone a Lens as such, use cloneLens. -- -- Note: It is usually better to use ReifiedTraversal and -- runTraversal than to cloneTraversal. The former can -- execute at full speed, while the latter needs to round trip through -- the Bazaar. -- --
-- >>> let foo l a = (view (getting (cloneTraversal l)) a, set (cloneTraversal l) 10 a) -- -- >>> foo both ("hello","world") -- ("helloworld",(10,10)) ---- --
-- cloneTraversal :: LensLike (Bazaar (->) a b) s t a b -> Traversal s t a b --cloneTraversal :: ATraversal s t a b -> Traversal s t a b -- | Clone a Traversal yielding an IndexPreservingTraversal -- that passes through whatever index it is composed with. cloneIndexPreservingTraversal :: ATraversal s t a b -> IndexPreservingTraversal s t a b -- | Clone an IndexedTraversal yielding an IndexedTraversal -- with the same index. cloneIndexedTraversal :: AnIndexedTraversal i s t a b -> IndexedTraversal i s t a b -- | A Traversal1 is completely characterized by its behavior on a -- Bazaar1. cloneTraversal1 :: ATraversal1 s t a b -> Traversal1 s t a b -- | Clone a Traversal1 yielding an IndexPreservingTraversal1 -- that passes through whatever index it is composed with. cloneIndexPreservingTraversal1 :: ATraversal1 s t a b -> IndexPreservingTraversal1 s t a b -- | Clone an IndexedTraversal1 yielding an IndexedTraversal1 -- with the same index. cloneIndexedTraversal1 :: AnIndexedTraversal1 i s t a b -> IndexedTraversal1 i s t a b -- | partsOf turns a Traversal into a Lens that -- resembles an early version of the uniplate (or biplate) -- type. -- -- Note: You should really try to maintain the invariant of the -- number of children in the list. -- --
-- >>> (a,b,c) & partsOf each .~ [x,y,z] -- (x,y,z) ---- -- Any extras will be lost. If you do not supply enough, then the -- remainder will come from the original structure. -- --
-- >>> (a,b,c) & partsOf each .~ [w,x,y,z] -- (w,x,y) ---- --
-- >>> (a,b,c) & partsOf each .~ [x,y] -- (x,y,c) ---- --
-- >>> ('b', 'a', 'd', 'c') & partsOf each %~ sort -- ('a','b','c','d') ---- -- So technically, this is only a Lens if you do not change the -- number of results it returns. -- -- When applied to a Fold the result is merely a Getter. -- --
-- partsOf :: Iso' s a -> Lens' s [a] -- partsOf :: Lens' s a -> Lens' s [a] -- partsOf :: Traversal' s a -> Lens' s [a] -- partsOf :: Fold s a -> Getter s [a] -- partsOf :: Getter s a -> Getter s [a] --partsOf :: Functor f => Traversing (->) f s t a a -> LensLike f s t [a] [a] -- | A type-restricted version of partsOf that can only be used with -- a Traversal. partsOf' :: ATraversal s t a a -> Lens s t [a] [a] -- | unsafePartsOf turns a Traversal into a uniplate -- (or biplate) family. -- -- If you do not need the types of s and t to be -- different, it is recommended that you use partsOf. -- -- It is generally safer to traverse with the Bazaar rather than -- use this combinator. However, it is sometimes convenient. -- -- This is unsafe because if you don't supply at least as many -- b's as you were given a's, then the reconstruction -- of t will result in an error! -- -- When applied to a Fold the result is merely a Getter -- (and becomes safe). -- --
-- unsafePartsOf :: Iso s t a b -> Lens s t [a] [b] -- unsafePartsOf :: Lens s t a b -> Lens s t [a] [b] -- unsafePartsOf :: Traversal s t a b -> Lens s t [a] [b] -- unsafePartsOf :: Fold s a -> Getter s [a] -- unsafePartsOf :: Getter s a -> Getter s [a] --unsafePartsOf :: Functor f => Traversing (->) f s t a b -> LensLike f s t [a] [b] unsafePartsOf' :: ATraversal s t a b -> Lens s t [a] [b] -- | The one-level version of contextsOf. This extracts a list of -- the immediate children according to a given Traversal as -- editable contexts. -- -- Given a context you can use pos to see the values, peek -- at what the structure would be like with an edited result, or simply -- extract the original structure. -- --
-- propChildren l x = childrenOf l x == map pos (holesOf l x) -- propId l x = all (== x) [extract w | w <- holesOf l x] ---- --
-- holesOf :: Iso' s a -> s -> [Pretext' (->) a s] -- holesOf :: Lens' s a -> s -> [Pretext' (->) a s] -- holesOf :: Traversal' s a -> s -> [Pretext' (->) a s] -- holesOf :: IndexedLens' i s a -> s -> [Pretext' (Indexed i) a s] -- holesOf :: IndexedTraversal' i s a -> s -> [Pretext' (Indexed i) a s] --holesOf :: Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t] -- | This converts a Traversal that you "know" will target one or -- more elements to a Lens. It can also be used to transform a -- non-empty Fold into a Getter. -- -- The resulting Lens or Getter will be partial if the -- supplied Traversal returns no results. -- --
-- >>> [1,2,3] ^. singular _head -- 1 ---- --
-- >>> [] ^. singular _head -- *** Exception: singular: empty traversal ---- --
-- >>> Left 4 ^. singular _Left -- 4 ---- --
-- >>> [1..10] ^. singular (ix 7) -- 8 ---- --
-- >>> [] & singular traverse .~ 0 -- [] ---- --
-- singular :: Traversal s t a a -> Lens s t a a -- singular :: Fold s a -> Getter s a -- singular :: IndexedTraversal i s t a a -> IndexedLens i s t a a -- singular :: IndexedFold i s a -> IndexedGetter i s a --singular :: (Conjoined p, Functor f) => Traversing p f s t a a -> Over p f s t a a -- | This converts a Traversal that you "know" will target only one -- element to a Lens. It can also be used to transform a -- Fold into a Getter. -- -- The resulting Lens or Getter will be partial if the -- Traversal targets nothing or more than one element. -- --
-- >>> [] & unsafeSingular traverse .~ 0 -- *** Exception: unsafeSingular: empty traversal ---- --
-- unsafeSingular :: Traversal s t a b -> Lens s t a b -- unsafeSingular :: Fold s a -> Getter s a -- unsafeSingular :: IndexedTraversal i s t a b -> IndexedLens i s t a b -- unsafeSingular :: IndexedFold i s a -> IndexedGetter i s a --unsafeSingular :: (Conjoined p, Functor f) => Traversing p f s t a b -> Over p f s t a b -- | Functors representing data structures that can be traversed from left -- to right. -- -- Minimal complete definition: traverse or sequenceA. -- -- A definition of traverse must satisfy the following laws: -- --
-- t :: (Applicative f, Applicative g) => f a -> g a ---- -- preserving the Applicative operations, i.e. -- -- -- -- and the identity functor Identity and composition of functors -- Compose are defined as -- --
-- newtype Identity a = Identity a -- -- instance Functor Identity where -- fmap f (Identity x) = Identity (f x) -- -- instance Applicative Indentity where -- pure x = Identity x -- Identity f <*> Identity x = Identity (f x) -- -- newtype Compose f g a = Compose (f (g a)) -- -- instance (Functor f, Functor g) => Functor (Compose f g) where -- fmap f (Compose x) = Compose (fmap (fmap f) x) -- -- instance (Applicative f, Applicative g) => Applicative (Compose f g) where -- pure x = Compose (pure (pure x)) -- Compose f <*> Compose x = Compose ((<*>) <$> f <*> x) ---- -- (The naturality law is implied by parametricity.) -- -- Instances are similar to Functor, e.g. given a data type -- --
-- data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) ---- -- a suitable instance would be -- --
-- instance Traversable Tree where -- traverse f Empty = pure Empty -- traverse f (Leaf x) = Leaf <$> f x -- traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r ---- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- --
-- >>> (1,2) & both *~ 10 -- (10,20) ---- --
-- >>> over both length ("hello","world") -- (5,5) ---- --
-- >>> ("hello","world")^.both -- "helloworld" ---- --
-- both :: Traversal (a, a) (b, b) a b -- both :: Traversal (Either a a) (Either b b) a b --both :: Bitraversable r => Traversal (r a a) (r b b) a b -- | Apply a different Traversal or Fold to each side of a -- Bitraversable container. -- --
-- beside :: Traversal s t a b -> Traversal s' t' a b -> Traversal (r s s') (r t t') a b -- beside :: IndexedTraversal i s t a b -> IndexedTraversal i s' t' a b -> IndexedTraversal i (r s s') (r t t') a b -- beside :: IndexPreservingTraversal s t a b -> IndexPreservingTraversal s' t' a b -> IndexPreservingTraversal (r s s') (r t t') a b ---- --
-- beside :: Traversal s t a b -> Traversal s' t' a b -> Traversal (s,s') (t,t') a b -- beside :: Lens s t a b -> Lens s' t' a b -> Traversal (s,s') (t,t') a b -- beside :: Fold s a -> Fold s' a -> Fold (s,s') a -- beside :: Getter s a -> Getter s' a -> Fold (s,s') a ---- --
-- beside :: IndexedTraversal i s t a b -> IndexedTraversal i s' t' a b -> IndexedTraversal i (s,s') (t,t') a b -- beside :: IndexedLens i s t a b -> IndexedLens i s' t' a b -> IndexedTraversal i (s,s') (t,t') a b -- beside :: IndexedFold i s a -> IndexedFold i s' a -> IndexedFold i (s,s') a -- beside :: IndexedGetter i s a -> IndexedGetter i s' a -> IndexedFold i (s,s') a ---- --
-- beside :: IndexPreservingTraversal s t a b -> IndexPreservingTraversal s' t' a b -> IndexPreservingTraversal (s,s') (t,t') a b -- beside :: IndexPreservingLens s t a b -> IndexPreservingLens s' t' a b -> IndexPreservingTraversal (s,s') (t,t') a b -- beside :: IndexPreservingFold s a -> IndexPreservingFold s' a -> IndexPreservingFold (s,s') a -- beside :: IndexPreservingGetter s a -> IndexPreservingGetter s' a -> IndexPreservingFold (s,s') a ---- --
-- >>> ("hello",["world","!!!"])^..beside id traverse -- ["hello","world","!!!"] --beside :: (Representable q, Applicative (Rep q), Applicative f, Bitraversable r) => Optical p q f s t a b -> Optical p q f s' t' a b -> Optical p q f (r s s') (r t t') a b -- | Visit the first n targets of a Traversal, Fold, -- Getter or Lens. -- --
-- >>> [("hello","world"),("!!!","!!!")]^.. taking 2 (traverse.both) -- ["hello","world"] ---- --
-- >>> timingOut $ [1..] ^.. taking 3 traverse -- [1,2,3] ---- --
-- >>> over (taking 5 traverse) succ "hello world" -- "ifmmp world" ---- --
-- taking :: Int -> Traversal' s a -> Traversal' s a -- taking :: Int -> Lens' s a -> Traversal' s a -- taking :: Int -> Iso' s a -> Traversal' s a -- taking :: Int -> Prism' s a -> Traversal' s a -- taking :: Int -> Getter s a -> Fold s a -- taking :: Int -> Fold s a -> Fold s a -- taking :: Int -> IndexedTraversal' i s a -> IndexedTraversal' i s a -- taking :: Int -> IndexedLens' i s a -> IndexedTraversal' i s a -- taking :: Int -> IndexedGetter i s a -> IndexedFold i s a -- taking :: Int -> IndexedFold i s a -> IndexedFold i s a --taking :: (Conjoined p, Applicative f) => Int -> Traversing p f s t a a -> Over p f s t a a -- | Visit all but the first n targets of a Traversal, -- Fold, Getter or Lens. -- --
-- >>> ("hello","world") ^? dropping 1 both -- Just "world" ---- -- Dropping works on infinite traversals as well: -- --
-- >>> [1..] ^? dropping 1 folded -- Just 2 ---- --
-- dropping :: Int -> Traversal' s a -> Traversal' s a -- dropping :: Int -> Lens' s a -> Traversal' s a -- dropping :: Int -> Iso' s a -> Traversal' s a -- dropping :: Int -> Prism' s a -> Traversal' s a -- dropping :: Int -> Getter s a -> Fold s a -- dropping :: Int -> Fold s a -> Fold s a -- dropping :: Int -> IndexedTraversal' i s a -> IndexedTraversal' i s a -- dropping :: Int -> IndexedLens' i s a -> IndexedTraversal' i s a -- dropping :: Int -> IndexedGetter i s a -> IndexedFold i s a -- dropping :: Int -> IndexedFold i s a -> IndexedFold i s a --dropping :: (Conjoined p, Applicative f) => Int -> Over p (Indexing f) s t a a -> Over p f s t a a -- | Try the first Traversal (or Fold), falling back on the -- second Traversal (or Fold) if it returns no entries. -- -- This is only a valid Traversal if the second Traversal -- is disjoint from the result of the first or returns exactly the same -- results. These conditions are trivially met when given a Lens, -- Iso, Getter, Prism or "affine" Traversal -- one -- that has 0 or 1 target. -- -- Mutatis mutandis for Fold. -- --
-- >>> [0,1,2,3] ^? failing (ix 1) (ix 2) -- Just 1 ---- --
-- >>> [0,1,2,3] ^? failing (ix 42) (ix 2) -- Just 2 ---- --
-- failing :: Traversal s t a b -> Traversal s t a b -> Traversal s t a b -- failing :: Prism s t a b -> Prism s t a b -> Traversal s t a b -- failing :: Fold s a -> Fold s a -> Fold s a ---- -- These cases are also supported, trivially, but are boring, because the -- left hand side always succeeds. -- --
-- failing :: Lens s t a b -> Traversal s t a b -> Traversal s t a b -- failing :: Iso s t a b -> Traversal s t a b -> Traversal s t a b -- failing :: Equality s t a b -> Traversal s t a b -> Traversal s t a b -- failing :: Getter s a -> Fold s a -> Fold s a ---- -- If both of the inputs are indexed, the result is also indexed, so you -- can apply this to a pair of indexed traversals or indexed folds, -- obtaining an indexed traversal or indexed fold. -- --
-- failing :: IndexedTraversal i s t a b -> IndexedTraversal i s t a b -> IndexedTraversal i s t a b -- failing :: IndexedFold i s a -> IndexedFold i s a -> IndexedFold i s a ---- -- These cases are also supported, trivially, but are boring, because the -- left hand side always succeeds. -- --
-- failing :: IndexedLens i s t a b -> IndexedTraversal i s t a b -> IndexedTraversal i s t a b -- failing :: IndexedGetter i s a -> IndexedGetter i s a -> IndexedFold i s a --failing :: (Conjoined p, Applicative f) => Traversing p f s t a b -> Over p f s t a b -> Over p f s t a b -- | Try the second traversal. If it returns no entries, try again with all -- entries from the first traversal, recursively. -- --
-- deepOf :: Fold s s -> Fold s a -> Fold s a -- deepOf :: Traversal' s s -> Traversal' s a -> Traversal' s a -- deepOf :: Traversal s t s t -> Traversal s t a b -> Traversal s t a b -- deepOf :: Fold s s -> IndexedFold i s a -> IndexedFold i s a -- deepOf :: Traversal s t s t -> IndexedTraversal i s t a b -> IndexedTraversal i s t a b --deepOf :: (Conjoined p, Applicative f) => LensLike f s t s t -> Traversing p f s t a b -> Over p f s t a b -- | This is the trivial empty Traversal. -- --
-- ignored :: IndexedTraversal i s s a b ---- --
-- ignored ≡ const pure ---- --
-- >>> 6 & ignored %~ absurd -- 6 --ignored :: Applicative f => pafb -> s -> f s -- | Allows IndexedTraversal the value at the smallest index. class Ord k => TraverseMin k m | m -> k traverseMin :: TraverseMin k m => IndexedTraversal' k (m v) v -- | Allows IndexedTraversal of the value at the largest index. class Ord k => TraverseMax k m | m -> k traverseMax :: TraverseMax k m => IndexedTraversal' k (m v) v -- | Traverse any Traversable container. This is an -- IndexedTraversal that is indexed by ordinal position. traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b -- | Traverse any Traversable1 container. This is an -- IndexedTraversal1 that is indexed by ordinal position. traversed1 :: Traversable1 f => IndexedTraversal1 Int (f a) (f b) a b -- | Traverse any Traversable container. This is an -- IndexedTraversal that is indexed by ordinal position. traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a b -- | Traverse the nth elementOf a Traversal, -- Lens or Iso if it exists. -- --
-- >>> [[1],[3,4]] & elementOf (traverse.traverse) 1 .~ 5 -- [[1],[5,4]] ---- --
-- >>> [[1],[3,4]] ^? elementOf (folded.folded) 1 -- Just 3 ---- --
-- >>> timingOut $ ['a'..] ^?! elementOf folded 5 -- 'f' ---- --
-- >>> timingOut $ take 10 $ elementOf traverse 3 .~ 16 $ [0..] -- [0,1,2,16,4,5,6,7,8,9] ---- --
-- elementOf :: Traversal' s a -> Int -> IndexedTraversal' Int s a -- elementOf :: Fold s a -> Int -> IndexedFold Int s a --elementOf :: Applicative f => LensLike (Indexing f) s t a a -> Int -> IndexedLensLike Int f s t a a -- | Traverse the nth element of a Traversable container. -- --
-- element ≡ elementOf traverse --element :: Traversable t => Int -> IndexedTraversal' Int (t a) a -- | Traverse (or fold) selected elements of a Traversal (or -- Fold) where their ordinal positions match a predicate. -- --
-- elementsOf :: Traversal' s a -> (Int -> Bool) -> IndexedTraversal' Int s a -- elementsOf :: Fold s a -> (Int -> Bool) -> IndexedFold Int s a --elementsOf :: Applicative f => LensLike (Indexing f) s t a a -> (Int -> Bool) -> IndexedLensLike Int f s t a a -- | Traverse elements of a Traversable container where their -- ordinal positions match a predicate. -- --
-- elements ≡ elementsOf traverse --elements :: Traversable t => (Int -> Bool) -> IndexedTraversal' Int (t a) a -- | An indexed version of partsOf that receives the entire list of -- indices as its index. ipartsOf :: (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a a -> Over p f s t [a] [a] -- | A type-restricted version of ipartsOf that can only be used -- with an IndexedTraversal. ipartsOf' :: (Indexable [i] p, Functor f) => Over (Indexed i) (Bazaar' (Indexed i) a) s t a a -> Over p f s t [a] [a] -- | An indexed version of unsafePartsOf that receives the entire -- list of indices as its index. iunsafePartsOf :: (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a b -> Over p f s t [a] [b] iunsafePartsOf' :: Over (Indexed i) (Bazaar (Indexed i) a b) s t a b -> IndexedLens [i] s t [a] [b] -- | Traversal with an index. -- -- NB: When you don't need access to the index then you can just -- apply your IndexedTraversal directly as a function! -- --
-- itraverseOf ≡ withIndex -- traverseOf l = itraverseOf l . const = id ---- --
-- itraverseOf :: Functor f => IndexedLens i s t a b -> (i -> a -> f b) -> s -> f t -- itraverseOf :: Applicative f => IndexedTraversal i s t a b -> (i -> a -> f b) -> s -> f t -- itraverseOf :: Apply f => IndexedTraversal1 i s t a b -> (i -> a -> f b) -> s -> f t --itraverseOf :: (Indexed i a (f b) -> s -> f t) -> (i -> a -> f b) -> s -> f t -- | Traverse with an index (and the arguments flipped). -- --
-- forOf l a ≡ iforOf l a . const -- iforOf ≡ flip . itraverseOf ---- --
-- iforOf :: Functor f => IndexedLens i s t a b -> s -> (i -> a -> f b) -> f t -- iforOf :: Applicative f => IndexedTraversal i s t a b -> s -> (i -> a -> f b) -> f t -- iforOf :: Apply f => IndexedTraversal1 i s t a b -> s -> (i -> a -> f b) -> f t --iforOf :: (Indexed i a (f b) -> s -> f t) -> s -> (i -> a -> f b) -> f t -- | Map each element of a structure targeted by a Lens to a monadic -- action, evaluate these actions from left to right, and collect the -- results, with access its position. -- -- When you don't need access to the index mapMOf is more liberal -- in what it can accept. -- --
-- mapMOf l ≡ imapMOf l . const ---- --
-- imapMOf :: Monad m => IndexedLens i s t a b -> (i -> a -> m b) -> s -> m t -- imapMOf :: Monad m => IndexedTraversal i s t a b -> (i -> a -> m b) -> s -> m t -- imapMOf :: Bind m => IndexedTraversal1 i s t a b -> (i -> a -> m b) -> s -> m t --imapMOf :: Over (Indexed i) (WrappedMonad m) s t a b -> (i -> a -> m b) -> s -> m t -- | Map each element of a structure targeted by a Lens to a monadic -- action, evaluate these actions from left to right, and collect the -- results, with access its position (and the arguments flipped). -- --
-- forMOf l a ≡ iforMOf l a . const -- iforMOf ≡ flip . imapMOf ---- --
-- iforMOf :: Monad m => IndexedLens i s t a b -> s -> (i -> a -> m b) -> m t -- iforMOf :: Monad m => IndexedTraversal i s t a b -> s -> (i -> a -> m b) -> m t --iforMOf :: (Indexed i a (WrappedMonad m b) -> s -> WrappedMonad m t) -> s -> (i -> a -> m b) -> m t -- | Generalizes mapAccumR to an arbitrary IndexedTraversal -- with access to the index. -- -- imapAccumROf accumulates state from right to left. -- --
-- mapAccumROf l ≡ imapAccumROf l . const ---- --
-- imapAccumROf :: IndexedLens i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- imapAccumROf :: IndexedTraversal i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) --imapAccumROf :: Over (Indexed i) (Backwards (State acc)) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- | Generalizes mapAccumL to an arbitrary IndexedTraversal -- with access to the index. -- -- imapAccumLOf accumulates state from left to right. -- --
-- mapAccumLOf l ≡ imapAccumLOf l . const ---- --
-- imapAccumLOf :: IndexedLens i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- imapAccumLOf :: IndexedTraversal i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) --imapAccumLOf :: Over (Indexed i) (State acc) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) -- | Traverse a container using its Traversable instance using -- explicitly provided Applicative operations. This is like -- traverse where the Applicative instance can be manually -- specified. traverseBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> t a -> f (t b) -- | Traverse a container using a specified Applicative. -- -- This is like traverseBy where the Traversable instance -- can be specified by any Traversal -- --
-- traverseByOf traverse ≡ traverseBy --traverseByOf :: Traversal s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> s -> f t -- | Sequence a container using its Traversable instance using -- explicitly provided Applicative operations. This is like -- sequence where the Applicative instance can be manually -- specified. sequenceBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> t (f a) -> f (t a) -- | Sequence a container using a specified Applicative. -- -- This is like traverseBy where the Traversable instance -- can be specified by any Traversal -- --
-- sequenceByOf traverse ≡ sequenceBy --sequenceByOf :: Traversal s t (f b) b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> s -> f t -- | This is used to characterize a Traversal. -- -- a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, -- or an indexed FunList. -- -- http://twanvl.nl/blog/haskell/non-regular1 -- -- A Bazaar is like a Traversal that has already been -- applied to some structure. -- -- Where a Context a b t holds an a and a -- function from b to t, a Bazaar a b t -- holds N as and a function from N -- bs to t, (where N might be infinite). -- -- Mnemonically, a Bazaar holds many stores and you can easily add -- more. -- -- This is a final encoding of Bazaar. newtype Bazaar p a b t Bazaar :: (forall f. Applicative f => p a (f b) -> f t) -> Bazaar p a b t runBazaar :: Bazaar p a b t -> forall f. Applicative f => p a (f b) -> f t -- | This alias is helpful when it comes to reducing repetition in type -- signatures. -- --
-- type Bazaar' p a t = Bazaar p a a t --type Bazaar' p a = Bazaar p a a -- | This is used to characterize a Traversal. -- -- a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, -- or an indexed FunList. -- -- http://twanvl.nl/blog/haskell/non-regular1 -- -- A Bazaar1 is like a Traversal that has already been -- applied to some structure. -- -- Where a Context a b t holds an a and a -- function from b to t, a Bazaar1 a b -- t holds N as and a function from N -- bs to t, (where N might be infinite). -- -- Mnemonically, a Bazaar1 holds many stores and you can easily -- add more. -- -- This is a final encoding of Bazaar1. newtype Bazaar1 p a b t Bazaar1 :: (forall f. Apply f => p a (f b) -> f t) -> Bazaar1 p a b t runBazaar1 :: Bazaar1 p a b t -> forall f. Apply f => p a (f b) -> f t -- | This alias is helpful when it comes to reducing repetition in type -- signatures. -- --
-- type Bazaar1' p a t = Bazaar1 p a a t --type Bazaar1' p a = Bazaar1 p a a -- | This Traversal allows you to traverse the individual -- stores in a Bazaar. loci :: Traversal (Bazaar (->) a c s) (Bazaar (->) b c s) a b -- | This IndexedTraversal allows you to traverse the -- individual stores in a Bazaar with access to their indices. iloci :: IndexedTraversal i (Bazaar (Indexed i) a c s) (Bazaar (Indexed i) b c s) a b -- | Fuse a Traversal by reassociating all of the -- \<*\> operations to the left and fusing all of the -- fmap calls into one. This is particularly useful when -- constructing a Traversal using operations from GHC.Generics. -- -- Given a pair of Traversals foo and bar, -- --
-- confusing (foo.bar) = foo.bar ---- -- However, foo and bar are each going to use the -- Applicative they are given. -- -- confusing exploits the Yoneda lemma to merge their -- separate uses of fmap into a single fmap. and it further -- exploits an interesting property of the right Kan lift (or -- Rift) to left associate all of the uses of '(*)' to make -- it possible to fuse together more fmaps. -- -- This is particularly effective when the choice of functor f -- is unknown at compile time or when the Traversal -- foo.bar in the above description is recursive or complex -- enough to prevent inlining. -- -- fusing is a version of this combinator suitable for fusing -- lenses. -- --
-- confusing :: Traversal s t a b -> Traversal s t a b --confusing :: Applicative f => LensLike (Rift (Yoneda f) (Yoneda f)) s t a b -> LensLike f s t a b instance Ord k => TraverseMax k (Map k) instance TraverseMax Int IntMap instance Ord k => TraverseMin k (Map k) instance TraverseMin Int IntMap -- | (The classes in here need to be defined together for -- DefaultSignatures to work.) module Control.Lens.Indexed -- | This class permits overloading of function application for things that -- also admit a notion of a key or index. class Conjoined p => Indexable i p indexed :: Indexable i p => p a b -> i -> a -> b -- | This is a Profunctor that is both Corepresentable by -- f and Representable by g such that f -- is left adjoint to g. From this you can derive a lot of -- structure due to the preservation of limits and colimits. class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p) => Conjoined p where distrib = tabulate . collect . sieve conjoined _ r = r distrib :: (Conjoined p, Functor f) => p a b -> p (f a) (f b) conjoined :: Conjoined p => (p ~ (->) => q (a -> b) r) -> q (p a b) r -> q (p a b) r -- | A function with access to a index. This constructor may be useful when -- you need to store an Indexable in a container to avoid -- ImpredicativeTypes. -- --
-- index :: Indexed i a b -> i -> a -> b --newtype Indexed i a b Indexed :: (i -> a -> b) -> Indexed i a b runIndexed :: Indexed i a b -> i -> a -> b -- | Compose an Indexed function with a non-indexed function. -- -- Mnemonically, the < points to the indexing we want to -- preserve. -- --
-- >>> let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])] -- -- >>> nestedMap^..(itraversed<.itraversed).withIndex -- [(1,"one,ten"),(1,"one,twenty"),(2,"two,thirty"),(2,"two,forty")] --(<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r -- | Composition of Indexed functions. -- -- Mnemonically, the < and > points to the fact -- that we want to preserve the indices. -- --
-- >>> let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])] -- -- >>> nestedMap^..(itraversed<.>itraversed).withIndex -- [((1,10),"one,ten"),((1,20),"one,twenty"),((2,30),"two,thirty"),((2,40),"two,forty")] --(<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> r -- | Compose a non-indexed function with an Indexed function. -- -- Mnemonically, the > points to the indexing we want to -- preserve. -- -- This is the same as (.). -- -- f . g (and f .> g) gives you the -- index of g unless g is index-preserving, like a -- Prism, Iso or Equality, in which case it'll pass -- through the index of f. -- --
-- >>> let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])] -- -- >>> nestedMap^..(itraversed.>itraversed).withIndex -- [(10,"one,ten"),(20,"one,twenty"),(30,"two,thirty"),(40,"two,forty")] --(.>) :: (st -> r) -> (kab -> st) -> kab -> r -- | Use a value itself as its own index. This is essentially an indexed -- version of id. -- -- Note: When used to modify the value, this can break the index -- requirements assumed by indices and similar, so this is only -- properly an IndexedGetter, but it can be used as more. -- --
-- selfIndex :: IndexedGetter a a b --selfIndex :: Indexable a p => p a fb -> a -> fb -- | Remap the index. reindexed :: Indexable j p => (i -> j) -> (Indexed i a b -> r) -> p a b -> r -- | Composition of Indexed functions with a user supplied function -- for combining indices. icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> r -- | Transform a Traversal into an IndexedTraversal or a -- Fold into an IndexedFold, etc. -- --
-- indexing :: Traversal s t a b -> IndexedTraversal Int s t a b -- indexing :: Prism s t a b -> IndexedTraversal Int s t a b -- indexing :: Lens s t a b -> IndexedLens Int s t a b -- indexing :: Iso s t a b -> IndexedLens Int s t a b -- indexing :: Fold s a -> IndexedFold Int s a -- indexing :: Getter s a -> IndexedGetter Int s a ---- --
-- indexing :: Indexable Int p => LensLike (Indexing f) s t a b -> Over p f s t a b --indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t -- | Transform a Traversal into an IndexedTraversal or a -- Fold into an IndexedFold, etc. -- -- This combinator is like indexing except that it handles large -- traversals and folds gracefully. -- --
-- indexing64 :: Traversal s t a b -> IndexedTraversal Int64 s t a b -- indexing64 :: Prism s t a b -> IndexedTraversal Int64 s t a b -- indexing64 :: Lens s t a b -> IndexedLens Int64 s t a b -- indexing64 :: Iso s t a b -> IndexedLens Int64 s t a b -- indexing64 :: Fold s a -> IndexedFold Int64 s a -- indexing64 :: Getter s a -> IndexedGetter Int64 s a ---- --
-- indexing64 :: Indexable Int64 p => LensLike (Indexing64 f) s t a b -> Over p f s t a b --indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f t -- | A Functor with an additional index. -- -- Instances must satisfy a modified form of the Functor laws: -- --
-- imap f . imap g ≡ imap (\i -> f i . g i) -- imap (\_ a -> a) ≡ id --class Functor f => FunctorWithIndex i f | f -> i where imap = iover itraversed imapped = conjoined mapped (isets imap) imap :: FunctorWithIndex i f => (i -> a -> b) -> f a -> f b imapped :: FunctorWithIndex i f => IndexedSetter i (f a) (f b) a b -- | A container that supports folding with an additional index. class Foldable f => FoldableWithIndex i f | f -> i where ifoldMap = ifoldMapOf itraversed ifolded = conjoined folded $ \ f -> phantom . getFolding . ifoldMap (\ i -> Folding #. indexed f i) ifoldr f z t = appEndo (ifoldMap (\ i -> Endo #. f i) t) z ifoldl f z t = appEndo (getDual (ifoldMap (\ i -> Dual #. Endo #. flip (f i)) t)) z ifoldr' f z0 xs = ifoldl f' id xs z0 where f' i k x z = k $! f i x z ifoldl' f z0 xs = ifoldr f' id xs z0 where f' i x k z = k $! f i z x ifoldMap :: (FoldableWithIndex i f, Monoid m) => (i -> a -> m) -> f a -> m ifolded :: FoldableWithIndex i f => IndexedFold i (f a) a ifoldr :: FoldableWithIndex i f => (i -> a -> b -> b) -> b -> f a -> b ifoldl :: FoldableWithIndex i f => (i -> b -> a -> b) -> b -> f a -> b ifoldr' :: FoldableWithIndex i f => (i -> a -> b -> b) -> b -> f a -> b ifoldl' :: FoldableWithIndex i f => (i -> b -> a -> b) -> b -> f a -> b -- | Return whether or not any element in a container satisfies a -- predicate, with access to the index i. -- -- When you don't need access to the index then any is more -- flexible in what it accepts. -- --
-- any ≡ iany . const --iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool -- | Return whether or not all elements in a container satisfy a predicate, -- with access to the index i. -- -- When you don't need access to the index then all is more -- flexible in what it accepts. -- --
-- all ≡ iall . const --iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool -- | Return whether or not none of the elements in a container satisfy a -- predicate, with access to the index i. -- -- When you don't need access to the index then none is more -- flexible in what it accepts. -- --
-- none ≡ inone . const -- inone f ≡ not . iany f --inone :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool -- | Determines whether no elements of the structure satisfy the predicate. -- --
-- none f ≡ not . any f --none :: Foldable f => (a -> Bool) -> f a -> Bool -- | Traverse elements with access to the index i, discarding the -- results. -- -- When you don't need access to the index then traverse_ is more -- flexible in what it accepts. -- --
-- traverse_ l = itraverse . const --itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f () -- | Traverse elements with access to the index i, discarding the -- results (with the arguments flipped). -- --
-- ifor_ ≡ flip itraverse_ ---- -- When you don't need access to the index then for_ is more -- flexible in what it accepts. -- --
-- for_ a ≡ ifor_ a . const --ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f () -- | Run monadic actions for each target of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results. -- -- When you don't need access to the index then mapMOf_ is more -- flexible in what it accepts. -- --
-- mapM_ ≡ imapM . const --imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m () -- | Run monadic actions for each target of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results (with the arguments flipped). -- --
-- iforM_ ≡ flip imapM_ ---- -- When you don't need access to the index then forMOf_ is more -- flexible in what it accepts. -- --
-- forMOf_ l a ≡ iforMOf l a . const --iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m () -- | Concatenate the results of a function of the elements of an indexed -- container with access to the index. -- -- When you don't need access to the index then concatMap is more -- flexible in what it accepts. -- --
-- concatMap ≡ iconcatMap . const -- iconcatMap ≡ ifoldMap --iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b] -- | Searches a container with a predicate that is also supplied the index, -- returning the left-most element of the structure matching the -- predicate, or Nothing if there is no such element. -- -- When you don't need access to the index then find is more -- flexible in what it accepts. -- --
-- find ≡ ifind . const --ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a) -- | Monadic fold right over the elements of a structure with an index. -- -- When you don't need access to the index then foldrM is more -- flexible in what it accepts. -- --
-- foldrM ≡ ifoldrM . const --ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m b -- | Monadic fold over the elements of a structure with an index, -- associating to the left. -- -- When you don't need access to the index then foldlM is more -- flexible in what it accepts. -- --
-- foldlM ≡ ifoldlM . const --ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m b -- | Extract the key-value pairs from a structure. -- -- When you don't need access to the indices in the result, then -- toList is more flexible in what it accepts. -- --
-- toList ≡ map snd . itoList --itoList :: FoldableWithIndex i f => f a -> [(i, a)] -- | Fold a container with indices returning both the indices and the -- values. -- -- The result is only valid to compose in a Traversal, if you -- don't edit the index as edits to the index have no effect. withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t) -- | When composed with an IndexedFold or -- IndexedTraversal this yields an (Indexed) -- Fold of the indices. asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s) -- | This allows you to filter an IndexedFold, IndexedGetter, -- IndexedTraversal or IndexedLens based on a predicate on -- the indices. -- --
-- >>> ["hello","the","world","!!!"]^..traversed.indices even -- ["hello","world"] ---- --
-- >>> over (traversed.indices (>0)) Prelude.reverse $ ["He","was","stressed","o_O"] -- ["He","saw","desserts","O_o"] --indices :: (Indexable i p, Applicative f) => (i -> Bool) -> Optical' p (Indexed i) f a a -- | This allows you to filter an IndexedFold, IndexedGetter, -- IndexedTraversal or IndexedLens based on an index. -- --
-- >>> ["hello","the","world","!!!"]^?traversed.index 2 -- Just "world" --index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a a -- | A Traversable with an additional index. -- -- An instance must satisfy a (modified) form of the Traversable -- laws: -- --
-- itraverse (const Identity) ≡ Identity -- fmap (itraverse f) . itraverse g ≡ getCompose . itraverse (\i -> Compose . fmap (f i) . g i) --class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i t | t -> i where itraverse = traversed .# Indexed itraversed = conjoined traverse (itraverse . indexed) itraverse :: (TraversableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f (t b) itraversed :: TraversableWithIndex i t => IndexedTraversal i (t a) (t b) a b -- | Traverse with an index (and the arguments flipped). -- --
-- for a ≡ ifor a . const -- ifor ≡ flip itraverse --ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results, with access the -- index. -- -- When you don't need access to the index mapM is more liberal in -- what it can accept. -- --
-- mapM ≡ imapM . const --imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results, with access its -- position (and the arguments flipped). -- --
-- forM a ≡ iforM a . const -- iforM ≡ flip imapM --iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b) -- | Generalizes mapAccumR to add access to the index. -- -- imapAccumROf accumulates state from right to left. -- --
-- mapAccumR ≡ imapAccumR . const --imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b) -- | Generalizes mapAccumL to add access to the index. -- -- imapAccumLOf accumulates state from left to right. -- --
-- mapAccumLOf ≡ imapAccumL . const --imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b) ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> r ifoldMapByOf :: IndexedFold i t a -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> r itraverseBy :: TraversableWithIndex i t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> t a -> f (t b) itraverseByOf :: IndexedTraversal i s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> s -> f t instance TraversableWithIndex [Int] Tree instance FoldableWithIndex [Int] Tree instance FunctorWithIndex [Int] Tree instance FunctorWithIndex i w => FunctorWithIndex (s, i) (TracedT s w) instance FunctorWithIndex i m => FunctorWithIndex (e, i) (ReaderT e m) instance (TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Product f g) instance (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Product f g) instance (FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Product f g) instance TraversableWithIndex i m => TraversableWithIndex i (IdentityT m) instance FoldableWithIndex i m => FoldableWithIndex i (IdentityT m) instance FunctorWithIndex i m => FunctorWithIndex i (IdentityT m) instance (TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (i, j) (Compose f g) instance (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (Compose f g) instance (FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (Compose f g) instance TraversableWithIndex i f => TraversableWithIndex [i] (Cofree f) instance FoldableWithIndex i f => FoldableWithIndex [i] (Cofree f) instance FunctorWithIndex i f => FunctorWithIndex [i] (Cofree f) instance Ix i => TraversableWithIndex i (Array i) instance Ix i => FoldableWithIndex i (Array i) instance Ix i => FunctorWithIndex i (Array i) instance TraversableWithIndex i f => TraversableWithIndex [i] (Free f) instance FoldableWithIndex i f => FoldableWithIndex [i] (Free f) instance FunctorWithIndex i f => FunctorWithIndex [i] (Free f) instance TraversableWithIndex i (Magma i t b) instance FoldableWithIndex i (Magma i t b) instance FunctorWithIndex i (Magma i t b) instance TraversableWithIndex i (Level i) instance FoldableWithIndex i (Level i) instance FunctorWithIndex i (Level i) instance FunctorWithIndex r ((->) r) instance (Eq k, Hashable k) => TraversableWithIndex k (HashMap k) instance (Eq k, Hashable k) => FoldableWithIndex k (HashMap k) instance (Eq k, Hashable k) => FunctorWithIndex k (HashMap k) instance TraversableWithIndex k (Map k) instance FoldableWithIndex k (Map k) instance FunctorWithIndex k (Map k) instance TraversableWithIndex Int IntMap instance FoldableWithIndex Int IntMap instance FunctorWithIndex Int IntMap instance TraversableWithIndex Int Vector instance FoldableWithIndex Int Vector instance FunctorWithIndex Int Vector instance TraversableWithIndex Int Seq instance FoldableWithIndex Int Seq instance FunctorWithIndex Int Seq instance TraversableWithIndex () Maybe instance FoldableWithIndex () Maybe instance FunctorWithIndex () Maybe instance TraversableWithIndex Int NonEmpty instance FoldableWithIndex Int NonEmpty instance FunctorWithIndex Int NonEmpty instance TraversableWithIndex Int [] instance FoldableWithIndex Int [] instance FunctorWithIndex Int [] instance TraversableWithIndex k ((,) k) instance FoldableWithIndex k ((,) k) instance FunctorWithIndex k ((,) k) instance TraversableWithIndex () Identity instance FoldableWithIndex () Identity instance FunctorWithIndex () Identity instance TraversableWithIndex i f => TraversableWithIndex i (Reverse f) instance FoldableWithIndex i f => FoldableWithIndex i (Reverse f) instance FunctorWithIndex i f => FunctorWithIndex i (Reverse f) instance TraversableWithIndex i f => TraversableWithIndex i (Backwards f) instance FoldableWithIndex i f => FoldableWithIndex i (Backwards f) instance FunctorWithIndex i f => FunctorWithIndex i (Backwards f) -- | This module provides combinators for breadth-first searching within -- arbitrary traversals. module Control.Lens.Level -- | This data type represents a path-compressed copy of one level of a -- source data structure. We can safely use path-compression because we -- know the depth of the tree. -- -- Path compression is performed by viewing a Level as a PATRICIA -- trie of the paths into the structure to leaves at a given depth, -- similar in many ways to a IntMap, but unlike a regular PATRICIA -- trie we do not need to store the mask bits merely the depth of the -- fork. -- -- One invariant of this structure is that underneath a Two node -- you will not find any Zero nodes, so Zero can only occur -- at the root. data Level i a -- | This provides a breadth-first Traversal of the individual -- levels of any other Traversal via iterative deepening -- depth-first search. The levels are returned to you in a compressed -- format. -- -- This can permit us to extract the levels directly: -- --
-- >>> ["hello","world"]^..levels (traverse.traverse) -- [Zero,Zero,One () 'h',Two 0 (One () 'e') (One () 'w'),Two 0 (One () 'l') (One () 'o'),Two 0 (One () 'l') (One () 'r'),Two 0 (One () 'o') (One () 'l'),One () 'd'] ---- -- But we can also traverse them in turn: -- --
-- >>> ["hello","world"]^..levels (traverse.traverse).traverse -- "hewlolrold" ---- -- We can use this to traverse to a fixed depth in the tree of -- (<*>) used in the Traversal: -- --
-- >>> ["hello","world"] & taking 4 (levels (traverse.traverse)).traverse %~ toUpper -- ["HEllo","World"] ---- -- Or we can use it to traverse the first n elements in found in -- that Traversal regardless of the depth at which they were -- found. -- --
-- >>> ["hello","world"] & taking 4 (levels (traverse.traverse).traverse) %~ toUpper -- ["HELlo","World"] ---- -- The resulting Traversal of the levels which is indexed -- by the depth of each Level. -- --
-- >>> ["dog","cat"]^@..levels (traverse.traverse) <. traverse -- [(2,'d'),(3,'o'),(3,'c'),(4,'g'),(4,'a'),(5,'t')] ---- -- Note: Internally this is implemented by using an illegal -- Applicative, as it extracts information in an order that -- violates the Applicative laws. levels :: ATraversal s t a b -> IndexedTraversal Int s t (Level () a) (Level () b) -- | This provides a breadth-first Traversal of the individual -- levels of any other Traversal via iterative deepening -- depth-first search. The levels are returned to you in a compressed -- format. -- -- This is similar to levels, but retains the index of the -- original IndexedTraversal, so you can access it when traversing -- the levels later on. -- --
-- >>> ["dog","cat"]^@..ilevels (traversed<.>traversed).itraversed -- [((0,0),'d'),((0,1),'o'),((1,0),'c'),((0,2),'g'),((1,1),'a'),((1,2),'t')] ---- -- The resulting Traversal of the levels which is indexed by the -- depth of each Level. -- --
-- >>> ["dog","cat"]^@..ilevels (traversed<.>traversed)<.>itraversed -- [((2,(0,0)),'d'),((3,(0,1)),'o'),((3,(1,0)),'c'),((4,(0,2)),'g'),((4,(1,1)),'a'),((5,(1,2)),'t')] ---- -- Note: Internally this is implemented by using an illegal -- Applicative, as it extracts information in an order that -- violates the Applicative laws. ilevels :: AnIndexedTraversal i s t a b -> IndexedTraversal Int s t (Level i a) (Level j b) module Control.Lens.Reified -- | Reify a Lens so it can be stored safely in a container. newtype ReifiedLens s t a b Lens :: Lens s t a b -> ReifiedLens s t a b runLens :: ReifiedLens s t a b -> Lens s t a b -- |
-- type ReifiedLens' = Simple ReifiedLens --type ReifiedLens' s a = ReifiedLens s s a a -- | Reify an IndexedLens so it can be stored safely in a container. newtype ReifiedIndexedLens i s t a b IndexedLens :: IndexedLens i s t a b -> ReifiedIndexedLens i s t a b runIndexedLens :: ReifiedIndexedLens i s t a b -> IndexedLens i s t a b -- |
-- type ReifiedIndexedLens' i = Simple (ReifiedIndexedLens i) --type ReifiedIndexedLens' i s a = ReifiedIndexedLens i s s a a -- | Reify an IndexedTraversal so it can be stored safely in a -- container. newtype ReifiedIndexedTraversal i s t a b IndexedTraversal :: IndexedTraversal i s t a b -> ReifiedIndexedTraversal i s t a b runIndexedTraversal :: ReifiedIndexedTraversal i s t a b -> IndexedTraversal i s t a b -- |
-- type ReifiedIndexedTraversal' i = Simple (ReifiedIndexedTraversal i) --type ReifiedIndexedTraversal' i s a = ReifiedIndexedTraversal i s s a a -- | A form of Traversal that can be stored monomorphically in a -- container. newtype ReifiedTraversal s t a b Traversal :: Traversal s t a b -> ReifiedTraversal s t a b runTraversal :: ReifiedTraversal s t a b -> Traversal s t a b -- |
-- type ReifiedTraversal' = Simple ReifiedTraversal --type ReifiedTraversal' s a = ReifiedTraversal s s a a -- | Reify a Getter so it can be stored safely in a container. -- -- This can also be useful when combining getters in novel ways, as -- ReifiedGetter is isomorphic to '(->)' and provides similar -- instances. -- --
-- >>> ("hello","world","!!!")^.runGetter ((,) <$> Getter _2 <*> Getter (_1.to length)) -- ("world",5) --newtype ReifiedGetter s a Getter :: Getter s a -> ReifiedGetter s a runGetter :: ReifiedGetter s a -> Getter s a -- | Reify an IndexedGetter so it can be stored safely in a -- container. newtype ReifiedIndexedGetter i s a IndexedGetter :: IndexedGetter i s a -> ReifiedIndexedGetter i s a runIndexedGetter :: ReifiedIndexedGetter i s a -> IndexedGetter i s a -- | Reify a Fold so it can be stored safely in a container. -- -- This can also be useful for creatively combining folds as -- ReifiedFold s is isomorphic to ReaderT s [] -- and provides similar instances. -- --
-- >>> ("hello","world")^..runFold ((,) <$> Fold _2 <*> Fold both) -- [("world","hello"),("world","world")] --newtype ReifiedFold s a Fold :: Fold s a -> ReifiedFold s a runFold :: ReifiedFold s a -> Fold s a newtype ReifiedIndexedFold i s a IndexedFold :: IndexedFold i s a -> ReifiedIndexedFold i s a runIndexedFold :: ReifiedIndexedFold i s a -> IndexedFold i s a -- | Reify a Setter so it can be stored safely in a container. newtype ReifiedSetter s t a b Setter :: Setter s t a b -> ReifiedSetter s t a b runSetter :: ReifiedSetter s t a b -> Setter s t a b -- |
-- type ReifiedSetter' = Simple ReifiedSetter --type ReifiedSetter' s a = ReifiedSetter s s a a -- | Reify an IndexedSetter so it can be stored safely in a -- container. newtype ReifiedIndexedSetter i s t a b IndexedSetter :: IndexedSetter i s t a b -> ReifiedIndexedSetter i s t a b runIndexedSetter :: ReifiedIndexedSetter i s t a b -> IndexedSetter i s t a b -- |
-- type ReifiedIndexedSetter' i = Simple (ReifiedIndexedSetter i) --type ReifiedIndexedSetter' i s a = ReifiedIndexedSetter i s s a a -- | Reify an Iso so it can be stored safely in a container. newtype ReifiedIso s t a b Iso :: Iso s t a b -> ReifiedIso s t a b runIso :: ReifiedIso s t a b -> Iso s t a b -- |
-- type ReifiedIso' = Simple ReifiedIso --type ReifiedIso' s a = ReifiedIso s s a a -- | Reify a Prism so it can be stored safely in a container. newtype ReifiedPrism s t a b Prism :: Prism s t a b -> ReifiedPrism s t a b runPrism :: ReifiedPrism s t a b -> Prism s t a b -- |
-- type ReifiedPrism' = Simple ReifiedPrism --type ReifiedPrism' s a = ReifiedPrism s s a a instance Strong (ReifiedIndexedFold i) instance Representable (ReifiedIndexedFold i) instance Sieve (ReifiedIndexedFold i) (Compose [] ((,) i)) instance Profunctor (ReifiedIndexedFold i) instance Functor (ReifiedIndexedFold i s) instance Plus (ReifiedIndexedFold i s) instance Alt (ReifiedIndexedFold i s) instance Monoid (ReifiedIndexedFold i s a) instance Semigroup (ReifiedIndexedFold i s a) instance Plus (ReifiedFold s) instance Alt (ReifiedFold s) instance Monoid (ReifiedFold s a) instance Semigroup (ReifiedFold s a) instance MonadReader s (ReifiedFold s) instance MonadPlus (ReifiedFold s) instance Monad (ReifiedFold s) instance Bind (ReifiedFold s) instance Alternative (ReifiedFold s) instance Applicative (ReifiedFold s) instance Apply (ReifiedFold s) instance Functor (ReifiedFold s) instance ArrowApply ReifiedFold instance ArrowChoice ReifiedFold instance Arrow ReifiedFold instance Category ReifiedFold instance Choice ReifiedFold instance Strong ReifiedFold instance Representable ReifiedFold instance Sieve ReifiedFold [] instance Profunctor ReifiedFold instance Semigroup i => Apply (ReifiedIndexedGetter i s) instance Functor (ReifiedIndexedGetter i s) instance Strong (ReifiedIndexedGetter i) instance Representable (ReifiedIndexedGetter i) instance Sieve (ReifiedIndexedGetter i) ((,) i) instance Profunctor (ReifiedIndexedGetter i) instance ArrowLoop ReifiedGetter instance ArrowChoice ReifiedGetter instance ArrowApply ReifiedGetter instance Arrow ReifiedGetter instance Category ReifiedGetter instance Choice ReifiedGetter instance Strong ReifiedGetter instance Conjoined ReifiedGetter instance Costrong ReifiedGetter instance Representable ReifiedGetter instance Sieve ReifiedGetter Identity instance Corepresentable ReifiedGetter instance Cosieve ReifiedGetter Identity instance Profunctor ReifiedGetter instance MonadReader s (ReifiedGetter s) instance Monad (ReifiedGetter s) instance Bind (ReifiedGetter s) instance Applicative (ReifiedGetter s) instance Apply (ReifiedGetter s) instance Monoid s => ComonadApply (ReifiedGetter s) instance Monoid s => Comonad (ReifiedGetter s) instance Semigroup s => Extend (ReifiedGetter s) instance Functor (ReifiedGetter s) instance Distributive (ReifiedGetter s) -- | Smart and naïve generic traversals given Data instances. -- -- template, uniplate, and biplate each build up -- information about what types can be contained within another type to -- speed up Traversal. module Data.Data.Lens -- | Find every occurrence of a given type a recursively that -- doesn't require passing through something of type a using -- Data, while avoiding traversal of areas that cannot contain a -- value of type a. -- -- This is uniplate with a more liberal signature. template :: (Data s, Typeable a) => Traversal' s a -- | Naïve Traversal using Data. This does not attempt to -- optimize the traversal. -- -- This is primarily useful when the children are immediately obvious, -- and for benchmarking. tinplate :: (Data s, Typeable a) => Traversal' s a -- | Find descendants of type a non-transitively, while avoiding -- computation of areas that cannot contain values of type a -- using Data. -- -- uniplate is a useful default definition for plate uniplate :: Data a => Traversal' a a -- | biplate performs like template, except when s ~ -- a, it returns itself and nothing else. biplate :: (Data s, Typeable a) => Traversal' s a -- | This automatically constructs a Traversal' from an function. -- --
-- >>> (2,4) & upon fst *~ 5 -- (10,4) ---- -- There are however, caveats on how this function can be used! -- -- First, the user supplied function must access only one field of the -- specified type. That is to say the target must be a single element -- that would be visited by holesOnOf template -- uniplate -- -- Note: this even permits a number of functions to be used directly. -- --
-- >>> [1,2,3,4] & upon head .~ 0 -- [0,2,3,4] ---- --
-- >>> [1,2,3,4] & upon last .~ 5 -- [1,2,3,5] ---- --
-- >>> [1,2,3,4] ^? upon tail -- Just [2,3,4] ---- --
-- >>> "" ^? upon tail -- Nothing ---- -- Accessing parents on the way down to children is okay: -- --
-- >>> [1,2,3,4] & upon (tail.tail) .~ [10,20] -- [1,2,10,20] ---- -- Second, the structure must not contain strict or unboxed fields of the -- same type that will be visited by Data -- --
-- upon :: (Data s, Data a) => (s -> a) -> IndexedTraversal' [Int] s a --upon :: (Indexable [Int] p, Applicative f, Data s, Data a) => (s -> a) -> p a (f a) -> s -> f s -- | The design of onceUpon' doesn't allow it to search inside of -- values of type a for other values of type a. -- upon' provides this additional recursion. -- -- Like onceUpon', upon' trusts the user supplied function -- more than upon using it directly as the accessor. This enables -- reading from the resulting Lens to be considerably faster at -- the risk of generating an illegal lens. -- --
-- >>> upon' (tail.tail) .~ [10,20] $ [1,2,3,4] -- [1,2,10,20] --upon' :: (Data s, Data a) => (s -> a) -> IndexedLens' [Int] s a -- | This automatically constructs a Traversal' from a field -- accessor. -- -- The index of the Traversal can be used as an offset into -- elementOf (indexing template) or into -- the list returned by holesOf template. -- -- The design of onceUpon doesn't allow it to search inside of -- values of type a for other values of type a. -- upon provides this additional recursion, but at the expense of -- performance. -- --
-- >>> onceUpon (tail.tail) .~ [10,20] $ [1,2,3,4] -- BAD -- [1,10,20] ---- --
-- >>> upon (tail.tail) .~ [10,20] $ [1,2,3,4] -- GOOD -- [1,2,10,20] ---- -- When in doubt, use upon instead. onceUpon :: (Data s, Typeable a) => (s -> a) -> IndexedTraversal' Int s a -- | This more trusting version of upon uses your function directly -- as the getter for a Lens. -- -- This means that reading from upon' is considerably faster than -- upon. -- -- However, you pay for faster access in two ways: -- --
-- import Control.Applicative -- import Control.Lens -- import Control.Lens.Plated -- import Data.Data -- import Data.Data.Lens (uniplate) ---- --
-- data Expr -- = Val Int -- | Neg Expr -- | Add Expr Expr -- deriving (Eq,Ord,Show,Read,Data,Typeable) ---- --
-- instance Plated Expr where -- plate f (Neg e) = Neg <$> f e -- plate f (Add a b) = Add <$> f a <*> f b -- plate _ a = pure a ---- -- or -- --
-- instance Plated Expr where -- plate = uniplate ---- -- Example 2: -- --
-- import Control.Applicative -- import Control.Lens -- import Control.Lens.Plated -- import Data.Data -- import Data.Data.Lens (uniplate) ---- --
-- data Tree a -- = Bin (Tree a) (Tree a) -- | Tip a -- deriving (Eq,Ord,Show,Read,Data,Typeable) ---- --
-- instance Plated (Tree a) where -- plate f (Bin l r) = Bin <$> f l <*> f r -- plate _ t = pure t ---- -- or -- --
-- instance Data a => Plated (Tree a) where -- plate = uniplate ---- -- Note the big distinction between these two implementations. -- -- The former will only treat children directly in this tree as -- descendents, the latter will treat trees contained in the values under -- the tips also as descendants! -- -- When in doubt, pick a Traversal and just use the various -- ...Of combinators rather than pollute Plated with -- orphan instances! -- -- If you want to find something unplated and non-recursive with -- biplate use the ...OnOf variant with ignored, -- though those usecases are much better served in most cases by using -- the existing Lens combinators! e.g. -- --
-- toListOf biplate ≡ universeOnOf biplate ignored ---- -- This same ability to explicitly pass the Traversal in question -- is why there is no analogue to uniplate's Biplate. -- -- Moreover, since we can allow custom traversals, we implement -- reasonable defaults for polymorphic data types, that only -- traverse into themselves, and not their polymorphic -- arguments. class Plated a where plate = uniplate plate :: Plated a => Traversal' a a -- | Extract the immediate descendants of a Plated container. -- --
-- children ≡ toListOf plate --children :: Plated a => a -> [a] -- | Rewrite by applying a rule everywhere you can. Ensures that the rule -- cannot be applied anywhere in the result: -- --
-- propRewrite r x = all (isNothing . r) (universe (rewrite r x)) ---- -- Usually transform is more appropriate, but rewrite can -- give better compositionality. Given two single transformations -- f and g, you can construct a -> f a -- mplus g a which performs both rewrites until a fixed -- point. rewrite :: Plated a => (a -> Maybe a) -> a -> a -- | Rewrite by applying a rule everywhere you can. Ensures that the rule -- cannot be applied anywhere in the result: -- --
-- propRewriteOf l r x = all (isNothing . r) (universeOf l (rewriteOf l r x)) ---- -- Usually transformOf is more appropriate, but rewriteOf -- can give better compositionality. Given two single transformations -- f and g, you can construct a -> f a -- mplus g a which performs both rewrites until a fixed -- point. -- --
-- rewriteOf :: Iso' a a -> (a -> Maybe a) -> a -> a -- rewriteOf :: Lens' a a -> (a -> Maybe a) -> a -> a -- rewriteOf :: Traversal' a a -> (a -> Maybe a) -> a -> a -- rewriteOf :: Setter' a a -> (a -> Maybe a) -> a -> a --rewriteOf :: ASetter' a a -> (a -> Maybe a) -> a -> a -- | Rewrite recursively over part of a larger structure. -- --
-- rewriteOn :: Plated a => Iso' s a -> (a -> Maybe a) -> s -> s -- rewriteOn :: Plated a => Lens' s a -> (a -> Maybe a) -> s -> s -- rewriteOn :: Plated a => Traversal' s a -> (a -> Maybe a) -> s -> s -- rewriteOn :: Plated a => ASetter' s a -> (a -> Maybe a) -> s -> s --rewriteOn :: Plated a => ASetter s t a a -> (a -> Maybe a) -> s -> t -- | Rewrite recursively over part of a larger structure using a specified -- Setter. -- --
-- rewriteOnOf :: Iso' s a -> Iso' a a -> (a -> Maybe a) -> s -> s -- rewriteOnOf :: Lens' s a -> Lens' a a -> (a -> Maybe a) -> s -> s -- rewriteOnOf :: Traversal' s a -> Traversal' a a -> (a -> Maybe a) -> s -> s -- rewriteOnOf :: Setter' s a -> Setter' a a -> (a -> Maybe a) -> s -> s --rewriteOnOf :: ASetter s t a a -> ASetter' a a -> (a -> Maybe a) -> s -> t -- | Rewrite by applying a monadic rule everywhere you can. Ensures that -- the rule cannot be applied anywhere in the result. rewriteM :: (Monad m, Plated a) => (a -> m (Maybe a)) -> a -> m a -- | Rewrite by applying a monadic rule everywhere you recursing with a -- user-specified Traversal. Ensures that the rule cannot be -- applied anywhere in the result. rewriteMOf :: Monad m => LensLike' (WrappedMonad m) a a -> (a -> m (Maybe a)) -> a -> m a -- | Rewrite by applying a monadic rule everywhere inside of a structure -- located by a user-specified Traversal. Ensures that the rule -- cannot be applied anywhere in the result. rewriteMOn :: (Monad m, Plated a) => LensLike (WrappedMonad m) s t a a -> (a -> m (Maybe a)) -> s -> m t -- | Rewrite by applying a monadic rule everywhere inside of a structure -- located by a user-specified Traversal, using a user-specified -- Traversal for recursion. Ensures that the rule cannot be -- applied anywhere in the result. rewriteMOnOf :: Monad m => LensLike (WrappedMonad m) s t a a -> LensLike' (WrappedMonad m) a a -> (a -> m (Maybe a)) -> s -> m t -- | Retrieve all of the transitive descendants of a Plated -- container, including itself. universe :: Plated a => a -> [a] -- | Given a Fold that knows how to locate immediate children, -- retrieve all of the transitive descendants of a node, including -- itself. -- --
-- universeOf :: Fold a a -> a -> [a] --universeOf :: Getting [a] a a -> a -> [a] -- | Given a Fold that knows how to find Plated parts of a -- container retrieve them and all of their descendants, recursively. universeOn :: Plated a => Getting [a] s a -> s -> [a] -- | Given a Fold that knows how to locate immediate children, -- retrieve all of the transitive descendants of a node, including itself -- that lie in a region indicated by another Fold. -- --
-- toListOf l ≡ universeOnOf l ignored --universeOnOf :: Getting [a] s a -> Getting [a] a a -> s -> [a] -- | Fold over all transitive descendants of a Plated container, -- including itself. cosmos :: Plated a => Fold a a -- | Given a Fold that knows how to locate immediate children, fold -- all of the transitive descendants of a node, including itself. -- --
-- cosmosOf :: Fold a a -> Fold a a --cosmosOf :: (Applicative f, Contravariant f) => LensLike' f a a -> LensLike' f a a -- | Given a Fold that knows how to find Plated parts of a -- container fold them and all of their descendants, recursively. -- --
-- cosmosOn :: Plated a => Fold s a -> Fold s a --cosmosOn :: (Applicative f, Contravariant f, Plated a) => LensLike' f s a -> LensLike' f s a -- | Given a Fold that knows how to locate immediate children, fold -- all of the transitive descendants of a node, including itself that lie -- in a region indicated by another Fold. -- --
-- cosmosOnOf :: Fold s a -> Fold a a -> Fold s a --cosmosOnOf :: (Applicative f, Contravariant f) => LensLike' f s a -> LensLike' f a a -> LensLike' f s a -- | Transform every element in the tree, in a bottom-up manner. -- -- For example, replacing negative literals with literals: -- --
-- negLits = transform $ \x -> case x of -- Neg (Lit i) -> Lit (negate i) -- _ -> x --transform :: Plated a => (a -> a) -> a -> a -- | Transform every element by recursively applying a given Setter -- in a bottom-up manner. -- --
-- transformOf :: Traversal' a a -> (a -> a) -> a -> a -- transformOf :: Setter' a a -> (a -> a) -> a -> a --transformOf :: ASetter' a a -> (a -> a) -> a -> a -- | Transform every element in the tree in a bottom-up manner over a -- region indicated by a Setter. -- --
-- transformOn :: Plated a => Traversal' s a -> (a -> a) -> s -> s -- transformOn :: Plated a => Setter' s a -> (a -> a) -> s -> s --transformOn :: Plated a => ASetter s t a a -> (a -> a) -> s -> t -- | Transform every element in a region indicated by a Setter by -- recursively applying another Setter in a bottom-up manner. -- --
-- transformOnOf :: Setter' s a -> Traversal' a a -> (a -> a) -> s -> s -- transformOnOf :: Setter' s a -> Setter' a a -> (a -> a) -> s -> s --transformOnOf :: ASetter s t a a -> ASetter' a a -> (a -> a) -> s -> t -- | Transform every element in the tree, in a bottom-up manner, -- monadically. transformM :: (Monad m, Plated a) => (a -> m a) -> a -> m a -- | Transform every element in a tree using a user supplied -- Traversal in a bottom-up manner with a monadic effect. -- --
-- transformMOf :: Monad m => Traversal' a a -> (a -> m a) -> a -> m a --transformMOf :: Monad m => LensLike' (WrappedMonad m) a a -> (a -> m a) -> a -> m a -- | Transform every element in the tree in a region indicated by a -- supplied Traversal, in a bottom-up manner, monadically. -- --
-- transformMOn :: (Monad m, Plated a) => Traversal' s a -> (a -> m a) -> s -> m s --transformMOn :: (Monad m, Plated a) => LensLike (WrappedMonad m) s t a a -> (a -> m a) -> s -> m t -- | Transform every element in a tree that lies in a region indicated by a -- supplied Traversal, walking with a user supplied -- Traversal in a bottom-up manner with a monadic effect. -- --
-- transformMOnOf :: Monad m => Traversal' s a -> Traversal' a a -> (a -> m a) -> s -> m s --transformMOnOf :: Monad m => LensLike (WrappedMonad m) s t a a -> LensLike' (WrappedMonad m) a a -> (a -> m a) -> s -> m t -- | Return a list of all of the editable contexts for every location in -- the structure, recursively. -- --
-- propUniverse x = universe x == map pos (contexts x) -- propId x = all (== x) [extract w | w <- contexts x] ---- --
-- contexts ≡ contextsOf plate --contexts :: Plated a => a -> [Context a a a] -- | Return a list of all of the editable contexts for every location in -- the structure, recursively, using a user-specified Traversal to -- walk each layer. -- --
-- propUniverse l x = universeOf l x == map pos (contextsOf l x) -- propId l x = all (== x) [extract w | w <- contextsOf l x] ---- --
-- contextsOf :: Traversal' a a -> a -> [Context a a a] --contextsOf :: ATraversal' a a -> a -> [Context a a a] -- | Return a list of all of the editable contexts for every location in -- the structure in an areas indicated by a user supplied -- Traversal, recursively using plate. -- --
-- contextsOn b ≡ contextsOnOf b plate ---- --
-- contextsOn :: Plated a => Traversal' s a -> s -> [Context a a s] --contextsOn :: Plated a => ATraversal s t a a -> s -> [Context a a t] -- | Return a list of all of the editable contexts for every location in -- the structure in an areas indicated by a user supplied -- Traversal, recursively using another user-supplied -- Traversal to walk each layer. -- --
-- contextsOnOf :: Traversal' s a -> Traversal' a a -> s -> [Context a a s] --contextsOnOf :: ATraversal s t a a -> ATraversal' a a -> s -> [Context a a t] -- | The one-level version of context. This extracts a list of the -- immediate children as editable contexts. -- -- Given a context you can use pos to see the values, peek -- at what the structure would be like with an edited result, or simply -- extract the original structure. -- --
-- propChildren x = children l x == map pos (holes l x) -- propId x = all (== x) [extract w | w <- holes l x] ---- --
-- holes = holesOf plate --holes :: Plated a => a -> [Pretext (->) a a a] -- | An alias for holesOf, provided for consistency with the other -- combinators. -- --
-- holesOn ≡ holesOf ---- --
-- holesOn :: Iso' s a -> s -> [Pretext (->) a a s] -- holesOn :: Lens' s a -> s -> [Pretext (->) a a s] -- holesOn :: Traversal' s a -> s -> [Pretext (->) a a s] -- holesOn :: IndexedLens' i s a -> s -> [Pretext (Indexed i) a a s] -- holesOn :: IndexedTraversal' i s a -> s -> [Pretext (Indexed i) a a s] --holesOn :: Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t] -- | Extract one level of holes from a container in a region -- specified by one Traversal, using another. -- --
-- holesOnOf b l ≡ holesOf (b . l) ---- --
-- holesOnOf :: Iso' s a -> Iso' a a -> s -> [Pretext (->) a a s] -- holesOnOf :: Lens' s a -> Lens' a a -> s -> [Pretext (->) a a s] -- holesOnOf :: Traversal' s a -> Traversal' a a -> s -> [Pretext (->) a a s] -- holesOnOf :: Lens' s a -> IndexedLens' i a a -> s -> [Pretext (Indexed i) a a s] -- holesOnOf :: Traversal' s a -> IndexedTraversal' i a a -> s -> [Pretext (Indexed i) a a s] --holesOnOf :: Conjoined p => LensLike (Bazaar p r r) s t a b -> Over p (Bazaar p r r) a b r r -> s -> [Pretext p r r t] -- | Perform a fold-like computation on each value, technically a -- paramorphism. -- --
-- para ≡ paraOf plate --para :: Plated a => (a -> [r] -> r) -> a -> r -- | Perform a fold-like computation on each value, technically a -- paramorphism. -- --
-- paraOf :: Fold a a -> (a -> [r] -> r) -> a -> r --paraOf :: Getting (Endo [a]) a a -> (a -> [r] -> r) -> a -> r -- | Compose through a plate (...) :: (Applicative f, Plated c) => LensLike f s t c c -> Over p f c c a b -> Over p f s t a b -- | Try to apply a traversal to all transitive descendants of a -- Plated container, but do not recurse through matching -- descendants. -- --
-- deep :: Plated s => Fold s a -> Fold s a -- deep :: Plated s => IndexedFold s a -> IndexedFold s a -- deep :: Plated s => Traversal s s a b -> Traversal s s a b -- deep :: Plated s => IndexedTraversal s s a b -> IndexedTraversal s s a b --deep :: (Conjoined p, Applicative f, Plated s) => Traversing p f s s a b -> Over p f s s a b -- | Fold the immediate children of a Plated container. -- --
-- composOpFold z c f = foldrOf plate (c . f) z --composOpFold :: Plated a => b -> (b -> b -> b) -> (a -> b) -> a -> b -- | The original uniplate combinator, implemented in terms of -- Plated as a Lens. -- --
-- parts ≡ partsOf plate ---- -- The resulting Lens is safer to use as it ignores -- 'over-application' and deals gracefully with under-application, but it -- is only a proper Lens if you don't change the list -- length! parts :: Plated a => Lens' a [a] -- | Implement plate operation for a type using its Generic -- instance. gplate :: (Generic a, GPlated a (Rep a)) => Traversal' a a class GPlated a g instance [overlap ok] GPlated a V1 instance [overlap ok] GPlated a U1 instance [overlap ok] GPlated a (K1 i b) instance [overlap ok] GPlated a (K1 i a) instance [overlap ok] (GPlated a f, GPlated a g) => GPlated a (f :*: g) instance [overlap ok] (GPlated a f, GPlated a g) => GPlated a (f :+: g) instance [overlap ok] GPlated a f => GPlated a (M1 i c f) instance [overlap ok] Plated Pat instance [overlap ok] Plated Stmt instance [overlap ok] Plated Type instance [overlap ok] Plated Con instance [overlap ok] Plated Dec instance [overlap ok] Plated Exp instance [overlap ok] Plated (Tree a) instance [overlap ok] Traversable f => Plated (Cofree f a) instance [overlap ok] (Traversable f, Traversable w) => Plated (CofreeT f w a) instance [overlap ok] Traversable f => Plated (F f a) instance [overlap ok] (Traversable f, Traversable m) => Plated (FreeT f m a) instance [overlap ok] Traversable f => Plated (Free f a) instance [overlap ok] Plated [a] -- | This module spends a lot of time fiddling around with -- ByteString internals to work around -- http://hackage.haskell.org/trac/ghc/ticket/7556 on older -- Haskell Platforms and to improve constant and asymptotic factors in -- our performance. module Control.Lens.Internal.ByteString -- | Unpack a strict Bytestring unpackStrict :: ByteString -> [Word8] -- | Traverse a strict ByteString in a relatively balanced fashion, -- as a balanced tree with biased runs of elements at the leaves. traversedStrictTree :: IndexedTraversal' Int ByteString Word8 -- | Unpack a strict Bytestring, pretending the bytes are chars. unpackStrict8 :: ByteString -> String -- | Traverse a strict ByteString in a relatively balanced fashion, -- as a balanced tree with biased runs of elements at the leaves, -- pretending the bytes are chars. traversedStrictTree8 :: IndexedTraversal' Int ByteString Char -- | Unpack a lazy Bytestring unpackLazy :: ByteString -> [Word8] -- | An IndexedTraversal of the individual bytes in a lazy -- ByteString traversedLazy :: IndexedTraversal' Int64 ByteString Word8 -- | Unpack a lazy ByteString pretending the bytes are chars. unpackLazy8 :: ByteString -> String -- | An IndexedTraversal of the individual bytes in a lazy -- ByteString pretending the bytes are chars. traversedLazy8 :: IndexedTraversal' Int64 ByteString Char module Control.Lens.Equality -- | A witness that (a ~ s, b ~ t). -- -- Note: Composition with an Equality is index-preserving. type Equality s t a b = forall p (f :: * -> *). p a (f b) -> p s (f t) -- | A Simple Equality. type Equality' s a = Equality s s a a -- | When you see this as an argument to a function, it expects an -- Equality. type AnEquality s t a b = Identical a (Identity b) a (Identity b) -> Identical a (Identity b) s (Identity t) -- | A Simple AnEquality. type AnEquality' s a = AnEquality s s a a -- | Extract a witness of type Equality. runEq :: AnEquality s t a b -> Identical s t a b -- | Substituting types with Equality. substEq :: AnEquality s t a b -> ((s ~ a, t ~ b) => r) -> r -- | We can use Equality to do substitution into anything. mapEq :: AnEquality s t a b -> f s -> f a -- | Equality is symmetric. fromEq :: AnEquality s t a b -> Equality b a t s -- | This is an adverb that can be used to modify many other Lens -- combinators to make them require simple lenses, simple traversals, -- simple prisms or simple isos as input. simply :: (Optic' p f s a -> r) -> Optic' p f s a -> r -- | Composition with this isomorphism is occasionally useful when your -- Lens, Traversal or Iso has a constraint on an -- unused argument to force that argument to agree with the type of a -- used argument and avoid ScopedTypeVariables or other -- ugliness. simple :: Equality' a a -- | Provides witness that (s ~ a, b ~ t) holds. data Identical a b s t Identical :: Identical a b a b module Control.Lens.Iso -- | Isomorphism families can be composed with another Lens using -- (.) and id. -- -- Note: Composition with an Iso is index- and measure- -- preserving. type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t) -- |
-- type Iso' = Simple Iso --type Iso' s a = Iso s s a a -- | When you see this as an argument to a function, it expects an -- Iso. type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t) -- | A Simple AnIso. type AnIso' s a = AnIso s s a a -- | Build a simple isomorphism from a pair of inverse functions. -- --
-- view (iso f g) ≡ f -- view (from (iso f g)) ≡ g -- over (iso f g) h ≡ g . h . f -- over (from (iso f g)) h ≡ f . h . g --iso :: (s -> a) -> (b -> t) -> Iso s t a b -- | Invert an isomorphism. -- --
-- from (from l) ≡ l --from :: AnIso s t a b -> Iso b a t s -- | Convert from AnIso back to any Iso. -- -- This is useful when you need to store an isomorphism as a data type -- inside a container and later reconstitute it as an overloaded -- function. -- -- See cloneLens or cloneTraversal for more information on -- why you might want to do this. cloneIso :: AnIso s t a b -> Iso s t a b -- | Extract the two functions, one from s -> a and one from -- b -> t that characterize an Iso. withIso :: AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r -- | Based on ala from Conor McBride's work on Epigram. -- -- This version is generalized to accept any Iso, not just a -- newtype. -- --
-- >>> au (_Wrapping Sum) foldMap [1,2,3,4] -- 10 ---- -- You may want to think of this combinator as having the following, -- simpler type: -- --
-- au :: AnIso s t a b -> ((b -> t) -> e -> s) -> e -> a --au :: Functor f => AnIso s t a b -> ((b -> t) -> f s) -> f a -- | Based on ala' from Conor McBride's work on Epigram. -- -- This version is generalized to accept any Iso, not just a -- newtype. -- -- For a version you pass the name of the newtype constructor -- to, see alaf. -- --
-- >>> auf (_Unwrapping Sum) (foldMapOf both) Prelude.length ("hello","world") -- 10 ---- -- Mnemonically, the German auf plays a similar role to à -- la, and the combinator is au with an extra function -- argument: -- --
-- auf :: Iso s t a b -> ((r -> a) -> e -> b) -> (r -> s) -> e -> t ---- -- but the signature is general. auf :: (Functor f, Functor g) => Optic (Costar f) g s t a b -> (f a -> g b) -> f s -> g t -- | The opposite of working over a Setter is working -- under an isomorphism. -- --
-- under ≡ over . from ---- --
-- under :: Iso s t a b -> (t -> s) -> b -> a --under :: AnIso s t a b -> (t -> s) -> b -> a -- | This can be used to lift any Iso into an arbitrary -- Functor. mapping :: (Functor f, Functor g) => AnIso s t a b -> Iso (f s) (g t) (f a) (g b) -- | Composition with this isomorphism is occasionally useful when your -- Lens, Traversal or Iso has a constraint on an -- unused argument to force that argument to agree with the type of a -- used argument and avoid ScopedTypeVariables or other -- ugliness. simple :: Equality' a a -- | If v is an element of a type a, and a' is -- a sans the element v, then non v is -- an isomorphism from Maybe a' to a. -- --
-- non ≡ non' . only ---- -- Keep in mind this is only a real isomorphism if you treat the domain -- as being Maybe (a sans v). -- -- This is practically quite useful when you want to have a Map -- where all the entries should have non-zero values. -- --
-- >>> Map.fromList [("hello",1)] & at "hello" . non 0 +~ 2 -- fromList [("hello",3)] ---- --
-- >>> Map.fromList [("hello",1)] & at "hello" . non 0 -~ 1 -- fromList [] ---- --
-- >>> Map.fromList [("hello",1)] ^. at "hello" . non 0 -- 1 ---- --
-- >>> Map.fromList [] ^. at "hello" . non 0 -- 0 ---- -- This combinator is also particularly useful when working with nested -- maps. -- -- e.g. When you want to create the nested Map when it is -- missing: -- --
-- >>> Map.empty & at "hello" . non Map.empty . at "world" ?~ "!!!" -- fromList [("hello",fromList [("world","!!!")])] ---- -- and when have deleting the last entry from the nested Map mean -- that we should delete its entry from the surrounding one: -- --
-- >>> fromList [("hello",fromList [("world","!!!")])] & at "hello" . non Map.empty . at "world" .~ Nothing -- fromList [] ---- -- It can also be used in reverse to exclude a given value: -- --
-- >>> non 0 # rem 10 4 -- Just 2 ---- --
-- >>> non 0 # rem 10 5 -- Nothing --non :: Eq a => a -> Iso' (Maybe a) a -- | non' p generalizes non (p # ()) to -- take any unit Prism -- -- This function generates an isomorphism between Maybe (a | -- isn't p a) and a. -- --
-- >>> Map.singleton "hello" Map.empty & at "hello" . non' _Empty . at "world" ?~ "!!!" -- fromList [("hello",fromList [("world","!!!")])] ---- --
-- >>> fromList [("hello",fromList [("world","!!!")])] & at "hello" . non' _Empty . at "world" .~ Nothing -- fromList [] --non' :: APrism' a () -> Iso' (Maybe a) a -- | anon a p generalizes non a to take any -- value and a predicate. -- -- This function assumes that p a holds True and -- generates an isomorphism between Maybe (a | not (p -- a)) and a. -- --
-- >>> Map.empty & at "hello" . anon Map.empty Map.null . at "world" ?~ "!!!" -- fromList [("hello",fromList [("world","!!!")])] ---- --
-- >>> fromList [("hello",fromList [("world","!!!")])] & at "hello" . anon Map.empty Map.null . at "world" .~ Nothing -- fromList [] --anon :: a -> (a -> Bool) -> Iso' (Maybe a) a -- | This isomorphism can be used to convert to or from an instance of -- Enum. -- --
-- >>> LT^.from enum -- 0 ---- --
-- >>> 97^.enum :: Char -- 'a' ---- -- Note: this is only an isomorphism from the numeric range actually used -- and it is a bit of a pleasant fiction, since there are questionable -- Enum instances for Double, and Float that exist -- solely for [1.0 .. 4.0] sugar and the instances for those and -- Integer don't cover all values in their range. enum :: Enum a => Iso' Int a -- | The canonical isomorphism for currying and uncurrying a function. -- --
-- curried = iso curry uncurry ---- --
-- >>> (fst^.curried) 3 4 -- 3 ---- --
-- >>> view curried fst 3 4 -- 3 --curried :: Iso ((a, b) -> c) ((d, e) -> f) (a -> b -> c) (d -> e -> f) -- | The canonical isomorphism for uncurrying and currying a function. -- --
-- uncurried = iso uncurry curry ---- --
-- uncurried = from curried ---- --
-- >>> ((+)^.uncurried) (1,2) -- 3 --uncurried :: Iso (a -> b -> c) (d -> e -> f) ((a, b) -> c) ((d, e) -> f) -- | The isomorphism for flipping a function. -- --
-- >>> ((,)^.flipped) 1 2 -- (2,1) --flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c') -- | This class provides for symmetric bifunctors. class Bifunctor p => Swapped p swapped :: Swapped p => Iso (p a b) (p c d) (p b a) (p d c) -- | Ad hoc conversion between "strict" and "lazy" versions of a structure, -- such as Text or ByteString. class Strict lazy strict | lazy -> strict, strict -> lazy strict :: Strict lazy strict => Iso' lazy strict -- | An Iso between the strict variant of a structure and its lazy -- counterpart. -- --
-- lazy = from strict ---- -- See http://hackage.haskell.org/package/strict-base-types for an -- example use. lazy :: Strict lazy strict => Iso' strict lazy -- | This class provides a generalized notion of list reversal extended to -- other containers. class Reversing t reversing :: Reversing t => t -> t -- | An Iso between a list, ByteString, Text fragment, -- etc. and its reversal. -- --
-- >>> "live" ^. reversed -- "evil" ---- --
-- >>> "live" & reversed %~ ('d':) -- "lived" --reversed :: Reversing a => Iso' a a -- | Given a function that is its own inverse, this gives you an Iso -- using it in both directions. -- --
-- involuted ≡ join iso ---- --
-- >>> "live" ^. involuted reverse -- "evil" ---- --
-- >>> "live" & involuted reverse %~ ('d':) -- "lived" --involuted :: (a -> a) -> Iso' a a -- | This isomorphism can be used to inspect a Traversal to see how -- it associates the structure and it can also be used to bake the -- Traversal into a Magma so that you can traverse over it -- multiple times. magma :: LensLike (Mafic a b) s t a b -> Iso s u (Magma Int t b a) (Magma j u c c) -- | This isomorphism can be used to inspect an IndexedTraversal to -- see how it associates the structure and it can also be used to bake -- the IndexedTraversal into a Magma so that you can -- traverse over it multiple times with access to the original indices. imagma :: Over (Indexed i) (Molten i a b) s t a b -> Iso s t' (Magma i t b a) (Magma j t' c c) -- | This provides a way to peek at the internal structure of a -- Traversal or IndexedTraversal data Magma i t b a -- | Lift an Iso into a Contravariant functor. -- --
-- contramapping :: Contravariant f => Iso s t a b -> Iso (f a) (f b) (f s) (f t) -- contramapping :: Contravariant f => Iso' s a -> Iso' (f a) (f s) --contramapping :: Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t) -- | Formally, the class Profunctor represents a profunctor from -- Hask -> Hask. -- -- Intuitively it is a bifunctor where the first argument is -- contravariant and the second argument is covariant. -- -- You can define a Profunctor by either defining dimap or -- by defining both lmap and rmap. -- -- If you supply dimap, you should ensure that: -- --
-- dimap id id ≡ id ---- -- If you supply lmap and rmap, ensure: -- --
-- lmap id ≡ id -- rmap id ≡ id ---- -- If you supply both, you should also ensure: -- --
-- dimap f g ≡ lmap f . rmap g ---- -- These ensure by parametricity: -- --
-- dimap (f . g) (h . i) ≡ dimap g h . dimap f i -- lmap (f . g) ≡ lmap g . lmap f -- rmap (f . g) ≡ rmap f . rmap g --class Profunctor (p :: * -> * -> *) dimap :: Profunctor p => (a -> b) -> (c -> d) -> p b c -> p a d lmap :: Profunctor p => (a -> b) -> p b c -> p a c rmap :: Profunctor p => (b -> c) -> p a b -> p a c -- | Lift two Isos into both arguments of a Profunctor -- simultaneously. -- --
-- dimapping :: Profunctor p => Iso s t a b -> Iso s' t' a' b' -> Iso (p a s') (p b t') (p s a') (p t b') -- dimapping :: Profunctor p => Iso' s a -> Iso' s' a' -> Iso' (p a s') (p s a') --dimapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (p a s') (q b t') (p s a') (q t b') -- | Lift an Iso contravariantly into the left argument of a -- Profunctor. -- --
-- lmapping :: Profunctor p => Iso s t a b -> Iso (p a x) (p b y) (p s x) (p t y) -- lmapping :: Profunctor p => Iso' s a -> Iso' (p a x) (p s x) --lmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q t y) -- | Lift an Iso covariantly into the right argument of a -- Profunctor. -- --
-- rmapping :: Profunctor p => Iso s t a b -> Iso (p x s) (p y t) (p x a) (p y b) -- rmapping :: Profunctor p => Iso' s a -> Iso' (p x s) (p x a) --rmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q y b) -- | Lift two Isos into both arguments of a Bifunctor. -- --
-- bimapping :: Bifunctor p => Iso s t a b -> Iso s' t' a' b' -> Iso (p s s') (p t t') (p a a') (p b b') -- bimapping :: Bifunctor p => Iso' s a -> Iso' s' a' -> Iso' (p s s') (p a a') --bimapping :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (g t t') (f a a') (g b b') instance Strict (RWST r w s m a) (RWST r w s m a) instance Strict (WriterT w m a) (WriterT w m a) instance Strict (StateT s m a) (StateT s m a) instance Strict Text Text instance Strict ByteString ByteString instance Swapped Either instance Swapped (,) -- | The Wrapped class provides similar functionality as -- Control.Newtype, from the newtype package, but in a -- more convenient and efficient form. -- -- There are a few functions from newtype that are not provided -- here, because they can be done with the Iso directly: -- --
-- Control.Newtype.over Sum f ≡ _Unwrapping Sum %~ f -- Control.Newtype.under Sum f ≡ _Wrapping Sum %~ f -- Control.Newtype.overF Sum f ≡ mapping (_Unwrapping Sum) %~ f -- Control.Newtype.underF Sum f ≡ mapping (_Wrapping Sum) %~ f ---- -- under can also be used with _Unwrapping to provide the -- equivalent of Control.Newtype.under. Also, most use cases -- don't need full polymorphism, so only the single constructor -- _Wrapping functions would be needed. -- -- These equivalences aren't 100% honest, because newtype's -- operators need to rely on two Newtype constraints. This means -- that the wrapper used for the output is not necessarily the same as -- the input. module Control.Lens.Wrapped -- | Wrapped provides isomorphisms to wrap and unwrap newtypes or -- data types with one constructor. class Wrapped s where type family Unwrapped s :: * _Wrapped' :: Wrapped s => Iso' s (Unwrapped s) _Unwrapped' :: Wrapped s => Iso' (Unwrapped s) s -- | This is a convenient version of _Wrapped with an argument -- that's ignored. -- -- The user supplied function is ignored, merely its type is used. _Wrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' s (Unwrapped s) -- | This is a convenient version of _Wrapped with an argument -- that's ignored. -- -- The user supplied function is ignored, merely its type is used. _Unwrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' (Unwrapped s) s class Wrapped s => Rewrapped (s :: *) (t :: *) class (Rewrapped s t, Rewrapped t s) => Rewrapping s t -- | Work under a newtype wrapper. -- --
-- >>> Const "hello" & _Wrapped %~ Prelude.length & getConst -- 5 ---- --
-- _Wrapped ≡ from _Unwrapped -- _Unwrapped ≡ from _Wrapped --_Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) _Unwrapped :: Rewrapping s t => Iso (Unwrapped t) (Unwrapped s) t s -- | This is a convenient version of _Wrapped with an argument -- that's ignored. -- -- The user supplied function is ignored, merely its types are -- used. _Wrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso s t (Unwrapped s) (Unwrapped t) -- | This is a convenient version of _Unwrapped with an argument -- that's ignored. -- -- The user supplied function is ignored, merely its types are -- used. _Unwrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso (Unwrapped t) (Unwrapped s) t s -- | Given the constructor for a Wrapped type, return a -- deconstructor that is its inverse. -- -- Assuming the Wrapped instance is legal, these laws hold: -- --
-- op f . f ≡ id -- f . op f ≡ id ---- --
-- >>> op Identity (Identity 4) -- 4 ---- --
-- >>> op Const (Const "hello") -- "hello" --op :: Wrapped s => (Unwrapped s -> s) -> s -> Unwrapped s -- | This combinator is based on ala from Conor McBride's work on -- Epigram. -- -- As with _Wrapping, the user supplied function for the newtype -- is ignored. -- --
-- >>> ala Sum foldMap [1,2,3,4] -- 10 ---- --
-- >>> ala All foldMap [True,True] -- True ---- --
-- >>> ala All foldMap [True,False] -- False ---- --
-- >>> ala Any foldMap [False,False] -- False ---- --
-- >>> ala Any foldMap [True,False] -- True ---- --
-- >>> ala Sum foldMap [1,2,3,4] -- 10 ---- --
-- >>> ala Product foldMap [1,2,3,4] -- 24 ---- -- You may want to think of this combinator as having the following, -- simpler, type. -- --
-- ala :: Rewrapping s t => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> e -> s) -> e -> Unwrapped s --ala :: (Functor f, Rewrapping s t) => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> f s) -> f (Unwrapped s) -- | This combinator is based on ala' from Conor McBride's work on -- Epigram. -- -- As with _Wrapping, the user supplied function for the newtype -- is ignored. -- --
-- alaf :: Rewrapping s t => (Unwrapped s -> s) -> ((r -> t) -> e -> s) -> (r -> Unwrapped t) -> e -> Unwrapped s ---- --
-- >>> alaf Sum foldMap Prelude.length ["hello","world"] -- 10 --alaf :: (Functor f, Functor g, Rewrapping s t) => (Unwrapped s -> s) -> (f t -> g s) -> f (Unwrapped t) -> g (Unwrapped s) instance Wrapped ErrorCall instance t ~ ErrorCall => Rewrapped ErrorCall t instance Wrapped RecUpdError instance t ~ RecUpdError => Rewrapped RecUpdError t instance Wrapped RecSelError instance t ~ RecSelError => Rewrapped RecSelError t instance Wrapped RecConError instance t ~ RecConError => Rewrapped RecConError t instance Wrapped PatternMatchFail instance t ~ PatternMatchFail => Rewrapped PatternMatchFail t instance Wrapped NoMethodError instance t ~ NoMethodError => Rewrapped NoMethodError t instance Wrapped AssertionFailed instance t ~ AssertionFailed => Rewrapped AssertionFailed t instance Wrapped (Tagged s a) instance t ~ Tagged s' a' => Rewrapped (Tagged s a) t instance Wrapped (ComposeCF f g a) instance t ~ ComposeCF f' g' a' => Rewrapped (ComposeCF f g a) t instance Wrapped (ComposeFC f g a) instance t ~ ComposeFC f' g' a' => Rewrapped (ComposeFC f g a) t instance Wrapped (Compose f g a) instance t ~ Compose f' g' a' => Rewrapped (Compose f g a) t instance Wrapped (Op a b) instance t ~ Op a' b' => Rewrapped (Op a b) t instance Wrapped (Equivalence a) instance t ~ Equivalence b => Rewrapped (Equivalence a) t instance Wrapped (Comparison a) instance t ~ Comparison b => Rewrapped (Comparison a) t instance Wrapped (Predicate a) instance t ~ Predicate b => Rewrapped (Predicate a) t instance Wrapped (Option a) instance t ~ Option b => Rewrapped (Option a) t instance Wrapped (WrappedMonoid a) instance t ~ WrappedMonoid b => Rewrapped (WrappedMonoid a) t instance Wrapped (Last a) instance t ~ Last b => Rewrapped (Last a) t instance Wrapped (First a) instance t ~ First b => Rewrapped (First a) t instance Wrapped (Max a) instance t ~ Max b => Rewrapped (Max a) t instance Wrapped (Min a) instance t ~ Min b => Rewrapped (Min a) t instance Storable a => Wrapped (Vector a) instance (Storable a, t ~ Vector a') => Rewrapped (Vector a) t instance Unbox a => Wrapped (Vector a) instance (Unbox a, t ~ Vector a') => Rewrapped (Vector a) t instance Prim a => Wrapped (Vector a) instance (Prim a, t ~ Vector a') => Rewrapped (Vector a) t instance Wrapped (Vector a) instance t ~ Vector a' => Rewrapped (Vector a) t instance Wrapped (Seq a) instance t ~ Seq a' => Rewrapped (Seq a) t instance Ord a => Wrapped (Set a) instance (t ~ Set a', Ord a) => Rewrapped (Set a) t instance Ord k => Wrapped (Map k a) instance (t ~ Map k' a', Ord k) => Rewrapped (Map k a) t instance Wrapped IntSet instance t ~ IntSet => Rewrapped IntSet t instance Wrapped (IntMap a) instance t ~ IntMap a' => Rewrapped (IntMap a) t instance (Hashable a, Eq a) => Wrapped (HashSet a) instance (t ~ HashSet a', Hashable a, Eq a) => Rewrapped (HashSet a) t instance (Hashable k, Eq k) => Wrapped (HashMap k a) instance (t ~ HashMap k' a', Hashable k, Eq k) => Rewrapped (HashMap k a) t instance Wrapped (TracedT m w a) instance t ~ TracedT m' w' a' => Rewrapped (TracedT m w a) t instance Wrapped (Coproduct f g a) instance t ~ Coproduct f' g' a' => Rewrapped (Coproduct f g a) t instance Wrapped (WriterT w m a) instance t ~ WriterT w' m' a' => Rewrapped (WriterT w m a) t instance Wrapped (WriterT w m a) instance t ~ WriterT w' m' a' => Rewrapped (WriterT w m a) t instance Wrapped (StateT s m a) instance t ~ StateT s' m' a' => Rewrapped (StateT s m a) t instance Wrapped (StateT s m a) instance t ~ StateT s' m' a' => Rewrapped (StateT s m a) t instance Wrapped (RWST r w s m a) instance t ~ RWST r' w' s' m' a' => Rewrapped (RWST r w s m a) t instance Wrapped (RWST r w s m a) instance t ~ RWST r' w' s' m' a' => Rewrapped (RWST r w s m a) t instance Wrapped (Reverse f a) instance t ~ Reverse g b => Rewrapped (Reverse f a) t instance Wrapped (ReaderT r m a) instance t ~ ReaderT r n b => Rewrapped (ReaderT r m a) t instance Wrapped (MaybeT m a) instance t ~ MaybeT n b => Rewrapped (MaybeT m a) t instance Wrapped (ListT m a) instance t ~ ListT n b => Rewrapped (ListT m a) t instance Wrapped (IdentityT m a) instance t ~ IdentityT n b => Rewrapped (IdentityT m a) t instance Wrapped (Identity a) instance t ~ Identity b => Rewrapped (Identity a) t instance Wrapped (ErrorT e m a) instance t ~ ErrorT e' m' a' => Rewrapped (ErrorT e m a) t instance Wrapped (ContT r m a) instance t ~ ContT r' m' a' => Rewrapped (ContT r m a) t instance Wrapped (Constant a b) instance t ~ Constant a' b' => Rewrapped (Constant a b) t instance Wrapped (Compose f g a) instance t ~ Compose f' g' a' => Rewrapped (Compose f g a) t instance Wrapped (Backwards f a) instance t ~ Backwards g b => Rewrapped (Backwards f a) t instance Wrapped (Down a) instance t ~ Down a => Rewrapped (Down a) t instance Wrapped (ArrowMonad m a) instance (t ~ ArrowMonad m' a', ArrowApply m) => Rewrapped (ArrowMonad m a) t instance Wrapped (Last a) instance t ~ Last b => Rewrapped (Last a) t instance Wrapped (First a) instance t ~ First b => Rewrapped (First a) t instance Wrapped (Endo a) instance t ~ Endo b => Rewrapped (Endo b) t instance Wrapped (Dual a) instance t ~ Dual b => Rewrapped (Dual a) t instance Wrapped (Const a x) instance t ~ Const a' x' => Rewrapped (Const a x) t instance Wrapped (NonEmpty a) instance t ~ NonEmpty b => Rewrapped (NonEmpty a) t instance Wrapped (ZipList a) instance t ~ ZipList b => Rewrapped (ZipList a) t instance Wrapped (WrappedArrow a b c) instance t ~ WrappedArrow a' b' c' => Rewrapped (WrappedArrow a b c) t instance Wrapped (WrappedMonad m a) instance t ~ WrappedMonad m' a' => Rewrapped (WrappedMonad m a) t instance Wrapped (Kleisli m a b) instance t ~ Kleisli m' a' b' => Rewrapped (Kleisli m a b) t instance Wrapped (Product a) instance t ~ Product b => Rewrapped (Product a) t instance Wrapped (Sum a) instance t ~ Sum b => Rewrapped (Sum a) t instance Wrapped Any instance t ~ Any => Rewrapped Any t instance Wrapped All instance t ~ All => Rewrapped All t instance (Rewrapped s t, Rewrapped t s) => Rewrapping s t -- | This module provides lenses and traversals for working with generic -- vectors. module Data.Vector.Generic.Lens -- | Similar to toListOf, but returning a Vector. -- --
-- >>> (toVectorOf both (8,15) :: Vector.Vector Int) == Vector.fromList [8,15] -- True --toVectorOf :: Vector v a => Getting (Endo [a]) s a -> s -> v a -- | Convert a Vector to a version that doesn't retain any extra -- memory. forced :: Vector v a => Iso' (v a) (v a) -- | Convert a list to a Vector (or back.) -- --
-- >>> ([1,2,3] ^. vector :: Vector.Vector Int) == Vector.fromList [1,2,3] -- True ---- --
-- >>> Vector.fromList [0,8,15] ^. from vector -- [0,8,15] --vector :: (Vector v a, Vector v b) => Iso [a] [b] (v a) (v b) -- | Convert a Vector to a finite Bundle (or back.) asStream :: (Vector v a, Vector v b) => Iso (v a) (v b) (Bundle v a) (Bundle v b) -- | Convert a Vector to a finite Bundle from right to left -- (or back.) asStreamR :: (Vector v a, Vector v b) => Iso (v a) (v b) (Bundle v a) (Bundle v b) -- | Convert a Vector back and forth to an initializer that when run -- produces a copy of the Vector. cloned :: Vector v a => Iso' (v a) (New v a) -- | Different vector implementations are isomorphic to each other. converted :: (Vector v a, Vector w a, Vector v b, Vector w b) => Iso (v a) (v b) (w a) (w b) -- | sliced i n provides a Lens that edits the n -- elements starting at index i from a Lens. -- -- This is only a valid Lens if you do not change the length of -- the resulting Vector. -- -- Attempting to return a longer or shorter vector will result in -- violations of the Lens laws. -- --
-- >>> Vector.fromList [1..10] ^. sliced 2 5 == Vector.fromList [3,4,5,6,7] -- True ---- --
-- >>> (Vector.fromList [1..10] & sliced 2 5 . mapped .~ 0) == Vector.fromList [1,2,0,0,0,0,0,8,9,10] -- True --sliced :: Vector v a => Int -> Int -> Lens' (v a) (v a) -- | This Traversal will ignore any duplicates in the supplied list -- of indices. -- --
-- >>> toListOf (ordinals [1,3,2,5,9,10]) $ Vector.fromList [2,4..40] -- [4,8,6,12,20,22] --ordinals :: Vector v a => [Int] -> IndexedTraversal' Int (v a) a -- | Like ix but polymorphic in the vector type. vectorIx :: Vector v a => Int -> Traversal' (v a) a -- | Indexed vector traversal for a generic vector. vectorTraverse :: (Vector v a, Vector w b) => IndexedTraversal Int (v a) (w b) a b module Data.Text.Strict.Lens -- | This isomorphism can be used to pack (or unpack) strict -- Text. -- --
-- >>> "hello"^.packed -- :: Text -- "hello" ---- --
-- pack x ≡ x ^. packed -- unpack x ≡ x ^. from packed -- packed ≡ from unpacked -- packed ≡ iso pack unpack --packed :: Iso' String Text -- | This isomorphism can be used to unpack (or pack) lazy -- Text. -- --
-- >>> "hello"^.unpacked -- :: String -- "hello" ---- -- This Iso is provided for notational convenience rather than out -- of great need, since -- --
-- unpacked ≡ from packed ---- --
-- pack x ≡ x ^. from unpacked -- unpack x ≡ x ^. packed -- unpacked ≡ iso unpack pack --unpacked :: Iso' Text String -- | Convert between strict Text and Builder . -- --
-- fromText x ≡ x ^. builder -- toStrict (toLazyText x) ≡ x ^. from builder --builder :: Iso' Text Builder -- | Traverse the individual characters in strict Text. -- --
-- >>> anyOf text (=='o') "hello" -- True ---- -- When the type is unambiguous, you can also use the more general -- each. -- --
-- text ≡ unpacked . traversed -- text ≡ each ---- -- Note that when just using this as a Setter, setting -- map can be more efficient. text :: IndexedTraversal' Int Text Char -- | EncodeDecode a strict Text tofrom strict -- ByteString, via UTF-8. -- --
-- >>> utf8 # "☃" -- "\226\152\131" --utf8 :: Prism' ByteString Text -- | This is an alias for unpacked that makes it more obvious how to -- use it with '#' -- --
-- > _Text # "hello" -- :: Text ---- -- "hello" _Text :: Iso' Text String module Data.Text.Lazy.Lens -- | This isomorphism can be used to pack (or unpack) lazy -- Text. -- --
-- >>> "hello"^.packed -- :: Text -- "hello" ---- --
-- pack x ≡ x ^. packed -- unpack x ≡ x ^. from packed -- packed ≡ from unpacked --packed :: Iso' String Text -- | This isomorphism can be used to unpack (or pack) lazy -- Text. -- --
-- >>> "hello"^.unpacked -- :: String -- "hello" ---- --
-- pack x ≡ x ^. from unpacked -- unpack x ≡ x ^. packed ---- -- This Iso is provided for notational convenience rather than out -- of great need, since -- --
-- unpacked ≡ from packed --unpacked :: Iso' Text String -- | This is an alias for unpacked that makes it clearer how to use -- it with ('#'). -- --
-- _Text = from packed ---- --
-- >>> _Text # "hello" -- :: Text -- "hello" --_Text :: Iso' Text String -- | Traverse the individual characters in a Text. -- --
-- >>> anyOf text (=='c') "chello" -- True ---- --
-- text = unpacked . traversed ---- -- When the type is unambiguous, you can also use the more general -- each. -- --
-- text ≡ each ---- -- Note that when just using this as a Setter, setting -- map can be more efficient. text :: IndexedTraversal' Int Text Char -- | Convert between lazy Text and Builder . -- --
-- fromLazyText x ≡ x ^. builder -- toLazyText x ≡ x ^. from builder --builder :: Iso' Text Builder -- | EncodeDecode a lazy Text tofrom lazy ByteString, -- via UTF-8. -- -- Note: This function does not decode lazily, as it must consume the -- entire input before deciding whether or not it fails. -- --
-- >>> ByteString.unpack (utf8 # "☃") -- [226,152,131] --utf8 :: Prism' ByteString Text module Data.Text.Lens -- | Traversals for strict or lazy Text class IsText t where text = unpacked . traversed packed :: IsText t => Iso' String t builder :: IsText t => Iso' t Builder text :: IsText t => IndexedTraversal' Int t Char -- | This isomorphism can be used to unpack (or pack) both -- strict or lazy Text. -- --
-- unpack x ≡ x ^. unpacked -- pack x ≡ x ^. from unpacked ---- -- This Iso is provided for notational convenience rather than out -- of great need, since -- --
-- unpacked ≡ from packed --unpacked :: IsText t => Iso' t String -- | This is an alias for unpacked that makes it clearer how to use -- it with ('#'). -- --
-- _Text = from packed ---- --
-- >>> _Text # "hello" :: Strict.Text -- "hello" --_Text :: IsText t => Iso' t String instance IsText Text instance IsText Text instance IsText String module Control.Lens.Empty class AsEmpty a where _Empty = only mempty _Empty :: AsEmpty a => Prism' a () instance AsEmpty Text instance AsEmpty Text instance AsEmpty ByteString instance AsEmpty ByteString instance AsEmpty (Seq a) instance Storable a => AsEmpty (Vector a) instance Unbox a => AsEmpty (Vector a) instance AsEmpty (Vector a) instance AsEmpty IntSet instance AsEmpty (HashSet a) instance AsEmpty (Set a) instance AsEmpty (IntMap a) instance AsEmpty (HashMap k a) instance AsEmpty (Map k a) instance AsEmpty [a] instance (AsEmpty a, AsEmpty b, AsEmpty c) => AsEmpty (a, b, c) instance (AsEmpty a, AsEmpty b) => AsEmpty (a, b) instance AsEmpty a => AsEmpty (Dual a) instance AsEmpty (First a) instance AsEmpty (Last a) instance AsEmpty (Maybe a) instance (Eq a, Num a) => AsEmpty (Sum a) instance (Eq a, Num a) => AsEmpty (Product a) instance AsEmpty Event instance AsEmpty All instance AsEmpty Any instance AsEmpty () instance AsEmpty Ordering module Control.Lens.Each -- | Extract each element of a (potentially monomorphic) container. -- -- Notably, when applied to a tuple, this generalizes both to -- arbitrary homogeneous tuples. -- --
-- >>> (1,2,3) & each *~ 10 -- (10,20,30) ---- -- It can also be used on monomorphic containers like Text or -- ByteString. -- --
-- >>> over each Char.toUpper ("hello"^.Text.packed) -- "HELLO" ---- --
-- >>> ("hello","world") & each.each %~ Char.toUpper -- ("HELLO","WORLD") --class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where each = traverse each :: Each s t a b => Traversal s t a b instance (Ix i, IArray UArray a, IArray UArray b, i ~ j) => Each (UArray i a) (UArray j b) a b instance (Ix i, i ~ j) => Each (Array i a) (Array j b) a b instance (a ~ Word8, b ~ Word8) => Each ByteString ByteString a b instance (a ~ Word8, b ~ Word8) => Each ByteString ByteString a b instance (a ~ Char, b ~ Char) => Each Text Text a b instance (a ~ Char, b ~ Char) => Each Text Text a b instance (Unbox a, Unbox b) => Each (Vector a) (Vector b) a b instance (Storable a, Storable b) => Each (Vector a) (Vector b) a b instance (Prim a, Prim b) => Each (Vector a) (Vector b) a b instance Each (Vector a) (Vector b) a b instance Each (Tree a) (Tree b) a b instance Each (Seq a) (Seq b) a b instance Each (Maybe a) (Maybe b) a b instance Each (Identity a) (Identity b) a b instance Each (NonEmpty a) (NonEmpty b) a b instance Each [a] [b] a b instance c ~ d => Each (HashMap c a) (HashMap d b) a b instance Each (IntMap a) (IntMap b) a b instance c ~ d => Each (Map c a) (Map d b) a b instance Each (Complex a) (Complex b) a b instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8, a ~ a9, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7, b ~ b8, b ~ b9) => Each (a, a2, a3, a4, a5, a6, a7, a8, a9) (b, b2, b3, b4, b5, b6, b7, b8, b9) a b instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7, b ~ b8) => Each (a, a2, a3, a4, a5, a6, a7, a8) (b, b2, b3, b4, b5, b6, b7, b8) a b instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7) => Each (a, a2, a3, a4, a5, a6, a7) (b, b2, b3, b4, b5, b6, b7) a b instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6) => Each (a, a2, a3, a4, a5, a6) (b, b2, b3, b4, b5, b6) a b instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, b ~ b2, b ~ b3, b ~ b4, b ~ b5) => Each (a, a2, a3, a4, a5) (b, b2, b3, b4, b5) a b instance (a ~ a2, a ~ a3, a ~ a4, b ~ b2, b ~ b3, b ~ b4) => Each (a, a2, a3, a4) (b, b2, b3, b4) a b instance (a ~ a2, a ~ a3, b ~ b2, b ~ b3) => Each (a, a2, a3) (b, b2, b3) a b instance (a ~ a', b ~ b') => Each (a, a') (b, b') a b module Control.Lens.Cons -- | This class provides a way to attach or detach elements on the left -- side of a structure in a flexible manner. class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s _Cons :: Cons s t a b => Prism s t (a, s) (b, t) -- | cons an element onto a container. -- -- This is an infix alias for cons. -- --
-- >>> a <| [] -- [a] ---- --
-- >>> a <| [b, c] -- [a,b,c] ---- --
-- >>> a <| Seq.fromList [] -- fromList [a] ---- --
-- >>> a <| Seq.fromList [b, c] -- fromList [a,b,c] --(<|) :: Cons s s a a => a -> s -> s -- | cons an element onto a container. -- --
-- >>> cons a [] -- [a] ---- --
-- >>> cons a [b, c] -- [a,b,c] ---- --
-- >>> cons a (Seq.fromList []) -- fromList [a] ---- --
-- >>> cons a (Seq.fromList [b, c]) -- fromList [a,b,c] --cons :: Cons s s a a => a -> s -> s -- | Attempt to extract the left-most element from a container, and a -- version of the container without that element. -- --
-- >>> uncons [] -- Nothing ---- --
-- >>> uncons [a, b, c] -- Just (a,[b,c]) --uncons :: Cons s s a a => s -> Maybe (a, s) -- | A Traversal reading and writing to the head of a -- non-empty container. -- --
-- >>> [a,b,c]^? _head -- Just a ---- --
-- >>> [a,b,c] & _head .~ d -- [d,b,c] ---- --
-- >>> [a,b,c] & _head %~ f -- [f a,b,c] ---- --
-- >>> [] & _head %~ f -- [] ---- --
-- >>> [1,2,3]^?!_head -- 1 ---- --
-- >>> []^?_head -- Nothing ---- --
-- >>> [1,2]^?_head -- Just 1 ---- --
-- >>> [] & _head .~ 1 -- [] ---- --
-- >>> [0] & _head .~ 2 -- [2] ---- --
-- >>> [0,1] & _head .~ 2 -- [2,1] ---- -- This isn't limited to lists. -- -- For instance you can also traverse the head of a Seq: -- --
-- >>> Seq.fromList [a,b,c,d] & _head %~ f -- fromList [f a,b,c,d] ---- --
-- >>> Seq.fromList [] ^? _head -- Nothing ---- --
-- >>> Seq.fromList [a,b,c,d] ^? _head -- Just a ---- --
-- _head :: Traversal' [a] a -- _head :: Traversal' (Seq a) a -- _head :: Traversal' (Vector a) a --_head :: Cons s s a a => Traversal' s a -- | A Traversal reading and writing to the tail of a -- non-empty container. -- --
-- >>> [a,b] & _tail .~ [c,d,e] -- [a,c,d,e] ---- --
-- >>> [] & _tail .~ [a,b] -- [] ---- --
-- >>> [a,b,c,d,e] & _tail.traverse %~ f -- [a,f b,f c,f d,f e] ---- --
-- >>> [1,2] & _tail .~ [3,4,5] -- [1,3,4,5] ---- --
-- >>> [] & _tail .~ [1,2] -- [] ---- --
-- >>> [a,b,c]^?_tail -- Just [b,c] ---- --
-- >>> [1,2]^?!_tail -- [2] ---- --
-- >>> "hello"^._tail -- "ello" ---- --
-- >>> ""^._tail -- "" ---- -- This isn't limited to lists. For instance you can also traverse -- the tail of a Seq. -- --
-- >>> Seq.fromList [a,b] & _tail .~ Seq.fromList [c,d,e] -- fromList [a,c,d,e] ---- --
-- >>> Seq.fromList [a,b,c] ^? _tail -- Just (fromList [b,c]) ---- --
-- >>> Seq.fromList [] ^? _tail -- Nothing ---- --
-- _tail :: Traversal' [a] [a] -- _tail :: Traversal' (Seq a) (Seq a) -- _tail :: Traversal' (Vector a) (Vector a) --_tail :: Cons s s a a => Traversal' s s -- | This class provides a way to attach or detach elements on the right -- side of a structure in a flexible manner. class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s _Snoc :: Snoc s t a b => Prism s t (s, a) (t, b) -- | snoc an element onto the end of a container. -- -- This is an infix alias for snoc. -- --
-- >>> Seq.fromList [] |> a -- fromList [a] ---- --
-- >>> Seq.fromList [b, c] |> a -- fromList [b,c,a] ---- --
-- >>> LazyT.pack "hello" |> '!' -- "hello!" --(|>) :: Snoc s s a a => s -> a -> s -- | snoc an element onto the end of a container. -- --
-- >>> snoc (Seq.fromList []) a -- fromList [a] ---- --
-- >>> snoc (Seq.fromList [b, c]) a -- fromList [b,c,a] ---- --
-- >>> snoc (LazyT.pack "hello") '!' -- "hello!" --snoc :: Snoc s s a a => s -> a -> s -- | Attempt to extract the right-most element from a container, and a -- version of the container without that element. -- --
-- >>> unsnoc (LazyT.pack "hello!") -- Just ("hello",'!') ---- --
-- >>> unsnoc (LazyT.pack "") -- Nothing ---- --
-- >>> unsnoc (Seq.fromList [b,c,a]) -- Just (fromList [b,c],a) ---- --
-- >>> unsnoc (Seq.fromList []) -- Nothing --unsnoc :: Snoc s s a a => s -> Maybe (s, a) -- | A Traversal reading and replacing all but the a last element of -- a non-empty container. -- --
-- >>> [a,b,c,d]^?_init -- Just [a,b,c] ---- --
-- >>> []^?_init -- Nothing ---- --
-- >>> [a,b] & _init .~ [c,d,e] -- [c,d,e,b] ---- --
-- >>> [] & _init .~ [a,b] -- [] ---- --
-- >>> [a,b,c,d] & _init.traverse %~ f -- [f a,f b,f c,d] ---- --
-- >>> [1,2,3]^?_init -- Just [1,2] ---- --
-- >>> [1,2,3,4]^?!_init -- [1,2,3] ---- --
-- >>> "hello"^._init -- "hell" ---- --
-- >>> ""^._init -- "" ---- --
-- _init :: Traversal' [a] [a] -- _init :: Traversal' (Seq a) (Seq a) -- _init :: Traversal' (Vector a) (Vector a) --_init :: Snoc s s a a => Traversal' s s -- | A Traversal reading and writing to the last element of a -- non-empty container. -- --
-- >>> [a,b,c]^?!_last -- c ---- --
-- >>> []^?_last -- Nothing ---- --
-- >>> [a,b,c] & _last %~ f -- [a,b,f c] ---- --
-- >>> [1,2]^?_last -- Just 2 ---- --
-- >>> [] & _last .~ 1 -- [] ---- --
-- >>> [0] & _last .~ 2 -- [2] ---- --
-- >>> [0,1] & _last .~ 2 -- [0,2] ---- -- This Traversal is not limited to lists, however. We can also -- work with other containers, such as a Vector. -- --
-- >>> Vector.fromList "abcde" ^? _last -- Just 'e' ---- --
-- >>> Vector.empty ^? _last -- Nothing ---- --
-- >>> (Vector.fromList "abcde" & _last .~ 'Q') == Vector.fromList "abcdQ" -- True ---- --
-- _last :: Traversal' [a] a -- _last :: Traversal' (Seq a) a -- _last :: Traversal' (Vector a) a --_last :: Snoc s s a a => Traversal' s a instance Snoc Text Text Char Char instance Snoc Text Text Char Char instance Snoc ByteString ByteString Word8 Word8 instance Snoc ByteString ByteString Word8 Word8 instance (Unbox a, Unbox b) => Snoc (Vector a) (Vector b) a b instance (Storable a, Storable b) => Snoc (Vector a) (Vector b) a b instance (Prim a, Prim b) => Snoc (Vector a) (Vector b) a b instance Snoc (Vector a) (Vector b) a b instance Snoc (Seq a) (Seq b) a b instance a ~ b => Snoc (NonEmpty a) (NonEmpty b) a b instance Snoc [a] [b] a b instance (Unbox a, Unbox b) => Cons (Vector a) (Vector b) a b instance (Storable a, Storable b) => Cons (Vector a) (Vector b) a b instance (Prim a, Prim b) => Cons (Vector a) (Vector b) a b instance Cons (Vector a) (Vector b) a b instance Cons Text Text Char Char instance Cons Text Text Char Char instance Cons ByteString ByteString Word8 Word8 instance Cons ByteString ByteString Word8 Word8 instance Cons (Seq a) (Seq b) a b instance a ~ b => Cons (NonEmpty a) (NonEmpty b) a b instance Cons [a] [b] a b -- | This module is designed to be imported qualified. module Control.Lens.Internal.Deque -- | A Banker's deque based on Chris Okasaki's "Purely Functional Data -- Structures" data Deque a BD :: !Int -> [a] -> !Int -> [a] -> Deque a -- | O(1). Calculate the size of a Deque -- --
-- >>> size (fromList [1,4,6]) -- 3 --size :: Deque a -> Int -- | O(n) amortized. Construct a Deque from a list of values. -- --
-- >>> fromList [1,2] -- BD 1 [1] 1 [2] --fromList :: [a] -> Deque a -- | O(1). Determine if a Deque is empty. -- --
-- >>> null empty -- True ---- --
-- >>> null (singleton 1) -- False --null :: Deque a -> Bool -- | O(1). Generate a singleton Deque -- --
-- >>> singleton 1 -- BD 1 [1] 0 [] --singleton :: a -> Deque a instance Show a => Show (Deque a) instance Snoc (Deque a) (Deque b) a b instance Cons (Deque a) (Deque b) a b instance Monoid (Deque a) instance Semigroup (Deque a) instance TraversableWithIndex Int Deque instance Traversable Deque instance FoldableWithIndex Int Deque instance Foldable Deque instance MonadPlus Deque instance Monad Deque instance Bind Deque instance Reversing (Deque a) instance Alternative Deque instance Plus Deque instance Alt Deque instance Applicative Deque instance Apply Deque instance FunctorWithIndex Int Deque instance Functor Deque instance Ord a => Ord (Deque a) instance Eq a => Eq (Deque a) module Control.Lens.At -- | At provides a Lens that can be used to read, write or -- delete the value associated with a key in a Map-like container -- on an ad hoc basis. -- -- An instance of At should satisfy: -- --
-- ix k ≡ at k . traverse --class Ixed m => At m at :: At m => Index m -> Lens' m (Maybe (IxValue m)) -- | Delete the value associated with a key in a Map-like container -- --
-- sans k = at k .~ Nothing --sans :: At m => Index m -> m -> m -- | An indexed version of at. -- --
-- >>> Map.fromList [(1,"world")] ^@. iat 1 -- (1,Just "world") ---- --
-- >>> iat 1 %@~ (\i x -> if odd i then Just "hello" else Nothing) $ Map.empty -- fromList [(1,"hello")] ---- --
-- >>> iat 2 %@~ (\i x -> if odd i then Just "hello" else Nothing) $ Map.empty -- fromList [] --iat :: At m => Index m -> IndexedLens' (Index m) m (Maybe (IxValue m)) -- | This provides a common notion of a value at an index that is shared by -- both Ixed and At. -- | This simple Traversal lets you traverse the value at a -- given key in a Map or element at an ordinal position in a list -- or Seq. class Ixed m ix :: Ixed m => Index m -> Traversal' m (IxValue m) -- | A definition of ix for types with an At instance. This -- is the default if you don't specify a definition for ix. ixAt :: At m => Index m -> Traversal' m (IxValue m) -- | An indexed version of ix. -- --
-- >>> Seq.fromList [a,b,c,d] & iix 2 %@~ f' -- fromList [a,b,f' 2 c,d] ---- --
-- >>> Seq.fromList [a,b,c,d] & iix 2 .@~ h -- fromList [a,b,h 2,d] ---- --
-- >>> Seq.fromList [a,b,c,d] ^@? iix 2 -- Just (2,c) ---- --
-- >>> Seq.fromList [] ^@? iix 2 -- Nothing --iix :: Ixed m => Index m -> IndexedTraversal' (Index m) m (IxValue m) -- | This class provides a simple Lens that lets you view (and -- modify) information about whether or not a container contains a given -- Index. class Contains m contains :: Contains m => Index m -> Lens' m Bool -- | An indexed version of contains. -- --
-- >>> IntSet.fromList [1,2,3,4] ^@. icontains 3 -- (3,True) ---- --
-- >>> IntSet.fromList [1,2,3,4] ^@. icontains 5 -- (5,False) ---- --
-- >>> IntSet.fromList [1,2,3,4] & icontains 3 %@~ \i x -> if odd i then not x else x -- fromList [1,2,4] ---- --
-- >>> IntSet.fromList [1,2,3,4] & icontains 3 %@~ \i x -> if even i then not x else x -- fromList [1,2,3,4] --icontains :: Contains m => Index m -> IndexedLens' (Index m) m Bool instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8, a ~ a9) => Ixed (a, a2, a3, a4, a5, a6, a7, a8, a9) instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8) => Ixed (a, a2, a3, a4, a5, a6, a7, a8) instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7) => Ixed (a, a2, a3, a4, a5, a6, a7) instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6) => Ixed (a, a2, a3, a4, a5, a6) instance (a ~ a2, a ~ a3, a ~ a4, a ~ a5) => Ixed (a, a2, a3, a4, a5) instance (a ~ a2, a ~ a3, a ~ a4) => Ixed (a, a2, a3, a4) instance (a ~ a2, a ~ a3) => Ixed (a, a2, a3) instance a ~ a2 => Ixed (a, a2) instance (Eq k, Hashable k) => At (HashSet k) instance Ord k => At (Set k) instance At IntSet instance (Eq k, Hashable k) => At (HashMap k a) instance Ord k => At (Map k a) instance At (IntMap a) instance At (Maybe a) instance Ixed ByteString instance Ixed ByteString instance Ixed Text instance Ixed Text instance Unbox a => Ixed (Vector a) instance Storable a => Ixed (Vector a) instance Prim a => Ixed (Vector a) instance Ixed (Vector a) instance (IArray UArray e, Ix i) => Ixed (UArray i e) instance Ix i => Ixed (Array i e) instance (Eq k, Hashable k) => Ixed (HashSet k) instance Ixed IntSet instance Ord k => Ixed (Set k) instance (Eq k, Hashable k) => Ixed (HashMap k a) instance Ord k => Ixed (Map k a) instance Ixed (IntMap a) instance Ixed (Seq a) instance Ixed (Tree a) instance Ixed (Identity a) instance Ixed (NonEmpty a) instance Ixed [a] instance Ixed (Maybe a) instance Eq e => Ixed (e -> a) instance (Eq a, Hashable a) => Contains (HashSet a) instance Ord a => Contains (Set a) instance Contains IntSet -- | Lenses, Prisms, and Traversals for working with Template Haskell module Language.Haskell.TH.Lens -- | Has a Name class HasName t name :: HasName t => Lens' t Name -- | Contains some amount of Types inside class HasTypes t types :: HasTypes t => Traversal' t Type -- | Provides for the extraction of free type variables, and alpha -- renaming. class HasTypeVars t typeVarsEx :: HasTypeVars t => Set Name -> Traversal' t Name -- | Provides substitution for types class SubstType t substType :: SubstType t => Map Name Type -> t -> t -- | Traverse free type variables typeVars :: HasTypeVars t => Traversal' t Name -- | Substitute using a map of names in for free type variables substTypeVars :: HasTypeVars t => Map Name Name -> t -> t -- | Provides a Traversal of the types of each field of a -- constructor. conFields :: Traversal' Con StrictType -- | Traversal of the types of the named fields of a -- constructor. conNamedFields :: Traversal' Con VarStrictType locFileName :: Lens' Loc String locPackage :: Lens' Loc String locModule :: Lens' Loc String locStart :: Lens' Loc CharPos locEnd :: Lens' Loc CharPos funDepInputs :: Lens' FunDep [Name] funDepOutputs :: Lens' FunDep [Name] matchPattern :: Lens' Match Pat matchBody :: Lens' Match Body matchDeclarations :: Lens' Match [Dec] fixityPrecedence :: Lens' Fixity Int fixityDirection :: Lens' Fixity FixityDirection clausePattern :: Lens' Clause [Pat] clauseBody :: Lens' Clause Body clauseDecs :: Lens' Clause [Dec] fieldExpName :: Lens' FieldExp Name fieldExpExpression :: Lens' FieldExp Exp fieldPatName :: Lens' FieldPat Name fieldPatPattern :: Lens' FieldPat Pat tySynEqnPatterns :: Lens' TySynEqn [Type] tySynEqnResult :: Lens' TySynEqn Type _ClassI :: Prism' Info (Dec, [InstanceDec]) _ClassOpI :: Prism' Info (Name, Type, ParentName, Fixity) _TyConI :: Prism' Info Dec _FamilyI :: Prism' Info (Dec, [InstanceDec]) _PrimTyConI :: Prism' Info (Name, Arity, Unlifted) _DataConI :: Prism' Info (Name, Type, ParentName, Fixity) _VarI :: Prism' Info (Name, Type, Maybe Dec, Fixity) _TyVarI :: Prism' Info (Name, Type) _FunD :: Prism' Dec (Name, [Clause]) _ValD :: Prism' Dec (Pat, Body, [Dec]) _DataD :: Prism' Dec (Cxt, Name, [TyVarBndr], [Con], [Name]) _NewtypeD :: Prism' Dec (Cxt, Name, [TyVarBndr], Con, [Name]) _TySynD :: Prism' Dec (Name, [TyVarBndr], Type) _ClassD :: Prism' Dec (Cxt, Name, [TyVarBndr], [FunDep], [Dec]) _InstanceD :: Prism' Dec (Cxt, Type, [Dec]) _SigD :: Prism' Dec (Name, Type) _ForeignD :: Prism' Dec Foreign _InfixD :: Prism' Dec (Fixity, Name) _PragmaD :: Prism' Dec Pragma _FamilyD :: Prism' Dec (FamFlavour, Name, [TyVarBndr], Maybe Kind) _DataInstD :: Prism' Dec (Cxt, Name, [Type], [Con], [Name]) _NewtypeInstD :: Prism' Dec (Cxt, Name, [Type], Con, [Name]) _TySynInstD :: Prism' Dec (Name, TySynEqn) _ClosedTypeFamilyD :: Prism' Dec (Name, [TyVarBndr], Maybe Kind, [TySynEqn]) _RoleAnnotD :: Prism' Dec (Name, [Role]) _NormalC :: Prism' Con (Name, [StrictType]) _RecC :: Prism' Con (Name, [VarStrictType]) _InfixC :: Prism' Con (StrictType, Name, StrictType) _ForallC :: Prism' Con ([TyVarBndr], Cxt, Con) _IsStrict :: Prism' Strict () _NotStrict :: Prism' Strict () _Unpacked :: Prism' Strict () _ImportF :: Prism' Foreign (Callconv, Safety, String, Name, Type) _ExportF :: Prism' Foreign (Callconv, String, Name, Type) _CCall :: Prism' Callconv () _StdCall :: Prism' Callconv () _Unsafe :: Prism' Safety () _Safe :: Prism' Safety () _Interruptible :: Prism' Safety () _InlineP :: Prism' Pragma (Name, Inline, RuleMatch, Phases) _SpecialiseP :: Prism' Pragma (Name, Type, Maybe Inline, Phases) _SpecialiseInstP :: Prism' Pragma Type _RuleP :: Prism' Pragma (String, [RuleBndr], Exp, Exp, Phases) _AnnP :: Prism' Pragma (AnnTarget, Exp) _NoInline :: Prism' Inline () _Inline :: Prism' Inline () _Inlinable :: Prism' Inline () _ConLike :: Prism' RuleMatch () _FunLike :: Prism' RuleMatch () _AllPhases :: Prism' Phases () _FromPhase :: Prism' Phases Int _BeforePhase :: Prism' Phases Int _RuleVar :: Prism' RuleBndr Name _TypedRuleVar :: Prism' RuleBndr (Name, Type) _ModuleAnnotation :: Prism' AnnTarget () _TypeAnnotation :: Prism' AnnTarget Name _ValueAnnotation :: Prism' AnnTarget Name _FunDep :: Iso' FunDep ([Name], [Name]) _TypeFam :: Prism' FamFlavour () _DataFam :: Prism' FamFlavour () _InfixL :: Prism' FixityDirection () _InfixR :: Prism' FixityDirection () _InfixN :: Prism' FixityDirection () _VarE :: Prism' Exp Name _ConE :: Prism' Exp Name _LitE :: Prism' Exp Lit _AppE :: Prism' Exp (Exp, Exp) _InfixE :: Prism' Exp (Maybe Exp, Exp, Maybe Exp) _UInfixE :: Prism' Exp (Exp, Exp, Exp) _ParensE :: Prism' Exp Exp _LamE :: Prism' Exp ([Pat], Exp) _LamCaseE :: Prism' Exp [Match] _TupE :: Prism' Exp [Exp] _UnboxedTupE :: Prism' Exp [Exp] _CondE :: Prism' Exp (Exp, Exp, Exp) _MultiIfE :: Prism' Exp [(Guard, Exp)] _LetE :: Prism' Exp ([Dec], Exp) _CaseE :: Prism' Exp (Exp, [Match]) _DoE :: Prism' Exp [Stmt] _CompE :: Prism' Exp [Stmt] _ArithSeqE :: Prism' Exp Range _ListE :: Prism' Exp [Exp] _SigE :: Prism' Exp (Exp, Type) _RecConE :: Prism' Exp (Name, [FieldExp]) _RecUpdE :: Prism' Exp (Exp, [FieldExp]) _GuardedB :: Prism' Body [(Guard, Exp)] _NormalB :: Prism' Body Exp _NormalG :: Prism' Guard Exp _PatG :: Prism' Guard [Stmt] _BindS :: Prism' Stmt (Pat, Exp) _LetS :: Prism' Stmt [Dec] _NoBindS :: Prism' Stmt Exp _ParS :: Prism' Stmt [[Stmt]] _FromR :: Prism' Range Exp _FromThenR :: Prism' Range (Exp, Exp) _FromToR :: Prism' Range (Exp, Exp) _FromThenToR :: Prism' Range (Exp, Exp, Exp) _CharL :: Prism' Lit Char _StringL :: Prism' Lit String _IntegerL :: Prism' Lit Integer _RationalL :: Prism' Lit Rational _IntPrimL :: Prism' Lit Integer _WordPrimL :: Prism' Lit Integer _FloatPrimL :: Prism' Lit Rational _DoublePrimL :: Prism' Lit Rational _StringPrimL :: Prism' Lit [Word8] _LitP :: Prism' Pat Lit _VarP :: Prism' Pat Name _TupP :: Prism' Pat [Pat] _UnboxedTupP :: Prism' Pat [Pat] _ConP :: Prism' Pat (Name, [Pat]) _InfixP :: Prism' Pat (Pat, Name, Pat) _UInfixP :: Prism' Pat (Pat, Name, Pat) _ParensP :: Prism' Pat Pat _TildeP :: Prism' Pat Pat _BangP :: Prism' Pat Pat _AsP :: Prism' Pat (Name, Pat) _WildP :: Prism' Pat () _RecP :: Prism' Pat (Name, [FieldPat]) _ListP :: Prism' Pat [Pat] _SigP :: Prism' Pat (Pat, Type) _ViewP :: Prism' Pat (Exp, Pat) _ForallT :: Prism' Type ([TyVarBndr], Cxt, Type) _AppT :: Prism' Type (Type, Type) _SigT :: Prism' Type (Type, Kind) _VarT :: Prism' Type Name _ConT :: Prism' Type Name _PromotedT :: Prism' Type Name _TupleT :: Prism' Type Int _UnboxedTupleT :: Prism' Type Int _ArrowT :: Prism' Type () _ListT :: Prism' Type () _PromotedTupleT :: Prism' Type Int _PromotedNilT :: Prism' Type () _PromotedConsT :: Prism' Type () _StarT :: Prism' Type () _ConstraintT :: Prism' Type () _LitT :: Prism' Type TyLit _PlainTV :: Prism' TyVarBndr Name _KindedTV :: Prism' TyVarBndr (Name, Kind) _NumTyLit :: Prism' TyLit Integer _StrTyLit :: Prism' TyLit String _ClassP :: Prism' Pred (Name, [Type]) _EqualP :: Prism' Pred (Type, Type) _NominalR :: Prism' Role () _RepresentationalR :: Prism' Role () _PhantomR :: Prism' Role () _InferR :: Prism' Role () instance SubstType Pred instance SubstType t => SubstType [t] instance SubstType Type instance HasTypeVars t => HasTypeVars (Maybe t) instance HasTypeVars t => HasTypeVars [t] instance HasTypeVars Con instance HasTypeVars Pred instance HasTypeVars Type instance HasTypeVars Name instance HasTypeVars TyVarBndr instance HasTypes t => HasTypes [t] instance HasTypes Con instance HasTypes Type instance HasName Con instance HasName Name instance HasName TyVarBndr module Control.Lens.Internal.FieldTH data LensRules LensRules :: Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> (Name -> [Name] -> Name -> [DefName]) -> (Name -> Maybe (Name, Name)) -> LensRules _simpleLenses :: LensRules -> Bool _generateSigs :: LensRules -> Bool _generateClasses :: LensRules -> Bool _allowIsos :: LensRules -> Bool -- | Allow LensTraversal (otherwise GetterFold) _allowUpdates :: LensRules -> Bool _lazyPatterns :: LensRules -> Bool -- | Type Name -> Field Names -> Target Field Name -> Definition -- Names _fieldToDef :: LensRules -> Name -> [Name] -> Name -> [DefName] _classyLenses :: LensRules -> Name -> Maybe (Name, Name) -- | Name to give to generated field optics. data DefName -- | Simple top-level definiton name TopName :: Name -> DefName -- | makeFields-style class name and method name MethodName :: Name -> Name -> DefName -- | Compute the field optics for the type identified by the given type -- name. Lenses will be computed when possible, Traversals otherwise. makeFieldOptics :: LensRules -> Name -> DecsQ makeFieldOpticsForDec :: LensRules -> Dec -> DecsQ instance Show DefName instance Eq DefName instance Ord DefName module Control.Lens.Internal.PrismTH -- | Generate a Prism for each constructor of a data type. Isos -- generated when possible. Reviews are created for constructors with -- existentially quantified constructors and GADTs. -- -- e.g. -- --
-- data FooBarBaz a -- = Foo Int -- | Bar a -- | Baz Int Char -- makePrisms ''FooBarBaz ---- -- will create -- --
-- _Foo :: Prism' (FooBarBaz a) Int -- _Bar :: Prism (FooBarBaz a) (FooBarBaz b) a b -- _Baz :: Prism' (FooBarBaz a) (Int, Char) --makePrisms :: Name -> DecsQ -- | Generate a Prism for each constructor of a data type and -- combine them into a single class. No Isos are created. Reviews are -- created for constructors with existentially quantified constructors -- and GADTs. -- -- e.g. -- --
-- data FooBarBaz a -- = Foo Int -- | Bar a -- | Baz Int Char -- makeClassyPrisms ''FooBarBaz ---- -- will create -- --
-- class AsFooBarBaz s a | s -> a where -- _FooBarBaz :: Prism' s (FooBarBaz a) -- _Foo :: Prism' s Int -- _Bar :: Prism' s a -- _Baz :: Prism' s (Int,Char) -- -- _Foo = _FooBarBaz . _Foo -- _Bar = _FooBarBaz . _Bar -- _Baz = _FooBarBaz . _Baz -- -- instance AsFooBarBaz (FooBarBaz a) a ---- -- Generate an As class of prisms. Names are selected by prefixing -- the constructor name with an underscore. Constructors with multiple -- fields will construct Prisms to tuples of those fields. makeClassyPrisms :: Name -> DecsQ -- | Generate prisms for the given Dec makeDecPrisms :: Bool -> Dec -> DecsQ instance Eq NCon instance HasTypeVars NCon module Control.Lens.TH -- | Build lenses (and traversals) with a sensible default configuration. -- -- e.g. -- --
-- data FooBar -- = Foo { _x, _y :: Int } -- | Bar { _x :: Int } -- makeLenses ''FooBar ---- -- will create -- --
-- x :: Lens' FooBar Int -- x f (Foo a b) = (\a' -> Foo a' b) <$> f a -- x f (Bar a) = Bar <$> f a -- y :: Traversal' FooBar Int -- y f (Foo a b) = (\b' -> Foo a b') <$> f b -- y _ c@(Bar _) = pure c ---- --
-- makeLenses = makeLensesWith lensRules --makeLenses :: Name -> DecsQ -- | Derive lenses and traversals, specifying explicit pairings of -- (fieldName, lensName). -- -- If you map multiple names to the same label, and it is present in the -- same constructor then this will generate a Traversal. -- -- e.g. -- --
-- makeLensesFor [("_foo", "fooLens"), ("baz", "lbaz")] ''Foo -- makeLensesFor [("_barX", "bar"), ("_barY", "bar")] ''Bar --makeLensesFor :: [(String, String)] -> Name -> DecsQ -- | Make lenses and traversals for a type, and create a class when the -- type has no arguments. -- -- e.g. -- --
-- data Foo = Foo { _fooX, _fooY :: Int } -- makeClassy ''Foo ---- -- will create -- --
-- class HasFoo t where -- foo :: Lens' t Foo -- fooX :: Lens' t Int -- fooX = foo . go where go f (Foo x y) = (\x' -> Foo x' y) <$> f x -- fooY :: Lens' t Int -- fooY = foo . go where go f (Foo x y) = (\y' -> Foo x y') <$> f y -- instance HasFoo Foo where -- foo = id ---- --
-- makeClassy = makeLensesWith classyRules --makeClassy :: Name -> DecsQ -- | Derive lenses and traversals, using a named wrapper class, and -- specifying explicit pairings of (fieldName, traversalName). -- -- Example usage: -- --
-- makeClassyFor "HasFoo" "foo" [("_foo", "fooLens"), ("bar", "lbar")] ''Foo --makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ -- | Make lenses and traversals for a type, and create a class when the -- type has no arguments. Works the same as makeClassy except that -- (a) it expects that record field names do not begin with an -- underscore, (b) all record fields are made into lenses, and (c) the -- resulting lens is prefixed with an underscore. makeClassy_ :: Name -> DecsQ -- | Generate a Prism for each constructor of a data type. Isos -- generated when possible. Reviews are created for constructors with -- existentially quantified constructors and GADTs. -- -- e.g. -- --
-- data FooBarBaz a -- = Foo Int -- | Bar a -- | Baz Int Char -- makePrisms ''FooBarBaz ---- -- will create -- --
-- _Foo :: Prism' (FooBarBaz a) Int -- _Bar :: Prism (FooBarBaz a) (FooBarBaz b) a b -- _Baz :: Prism' (FooBarBaz a) (Int, Char) --makePrisms :: Name -> DecsQ -- | Generate a Prism for each constructor of a data type and -- combine them into a single class. No Isos are created. Reviews are -- created for constructors with existentially quantified constructors -- and GADTs. -- -- e.g. -- --
-- data FooBarBaz a -- = Foo Int -- | Bar a -- | Baz Int Char -- makeClassyPrisms ''FooBarBaz ---- -- will create -- --
-- class AsFooBarBaz s a | s -> a where -- _FooBarBaz :: Prism' s (FooBarBaz a) -- _Foo :: Prism' s Int -- _Bar :: Prism' s a -- _Baz :: Prism' s (Int,Char) -- -- _Foo = _FooBarBaz . _Foo -- _Bar = _FooBarBaz . _Bar -- _Baz = _FooBarBaz . _Baz -- -- instance AsFooBarBaz (FooBarBaz a) a ---- -- Generate an As class of prisms. Names are selected by prefixing -- the constructor name with an underscore. Constructors with multiple -- fields will construct Prisms to tuples of those fields. makeClassyPrisms :: Name -> DecsQ -- | Build Wrapped instance for a given newtype makeWrapped :: Name -> DecsQ -- | Generate overloaded field accessors. -- -- e.g -- --
-- data Foo a = Foo { _fooX :: Int, _fooY : a } -- newtype Bar = Bar { _barX :: Char } -- makeFields ''Foo -- makeFields ''Bar ---- -- will create -- --
-- _fooXLens :: Lens' (Foo a) Int -- _fooYLens :: Lens (Foo a) (Foo b) a b -- class HasX s a | s -> a where -- x :: Lens' s a -- instance HasX (Foo a) Int where -- x = _fooXLens -- class HasY s a | s -> a where -- y :: Lens' s a -- instance HasY (Foo a) a where -- y = _fooYLens -- _barXLens :: Iso' Bar Char -- instance HasX Bar Char where -- x = _barXLens ---- -- For details, see camelCaseFields. -- --
-- makeFields = makeLensesWith defaultFieldRules --makeFields :: Name -> DecsQ -- | Make lenses for all records in the given declaration quote. All record -- syntax in the input will be stripped off. -- -- e.g. -- --
-- declareLenses [d| -- data Foo = Foo { fooX, fooY :: Int } -- deriving Show -- |] ---- -- will create -- --
-- data Foo = Foo Int Int deriving Show -- fooX, fooY :: Lens' Foo Int --declareLenses :: DecsQ -> DecsQ -- | Similar to makeLensesFor, but takes a declaration quote. declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ -- | For each record in the declaration quote, make lenses and traversals -- for it, and create a class when the type has no arguments. All record -- syntax in the input will be stripped off. -- -- e.g. -- --
-- declareClassy [d| -- data Foo = Foo { fooX, fooY :: Int } -- deriving Show -- |] ---- -- will create -- --
-- data Foo = Foo Int Int deriving Show -- class HasFoo t where -- foo :: Lens' t Foo -- instance HasFoo Foo where foo = id -- fooX, fooY :: HasFoo t => Lens' t Int --declareClassy :: DecsQ -> DecsQ -- | Similar to makeClassyFor, but takes a declaration quote. declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ -- | Generate a Prism for each constructor of each data type. -- -- e.g. -- --
-- declarePrisms [d| -- data Exp = Lit Int | Var String | Lambda{ bound::String, body::Exp } -- |] ---- -- will create -- --
-- data Exp = Lit Int | Var String | Lambda { bound::String, body::Exp } -- _Lit :: Prism' Exp Int -- _Var :: Prism' Exp String -- _Lambda :: Prism' Exp (String, Exp) --declarePrisms :: DecsQ -> DecsQ -- | Build Wrapped instance for each newtype. declareWrapped :: DecsQ -> DecsQ -- |
-- declareFields = declareLensesWith defaultFieldRules --declareFields :: DecsQ -> DecsQ -- | Build lenses with a custom configuration. makeLensesWith :: LensRules -> Name -> DecsQ -- | Declare lenses for each records in the given declarations, using the -- specified LensRules. Any record syntax in the input will be -- stripped off. declareLensesWith :: LensRules -> DecsQ -> DecsQ defaultFieldRules :: LensRules -- | Field rules for fields in the form prefixFieldname or -- _prefixFieldname If you want all fields to be lensed, then there -- is no reason to use an _ before the prefix. If any of the -- record fields leads with an _ then it is assume a field -- without an _ should not have a lens created. -- -- Note: The prefix must be the same as the typename -- (with the first letter lowercased). This is a change from lens -- versions before lens 4.5. If you want the old behaviour, use -- makeLensesWith abbreviatedFields camelCaseFields :: LensRules -- | Field rules for fields in the form _prefix_fieldname underscoreFields :: LensRules -- | Field rules fields in the form prefixFieldname or -- _prefixFieldname If you want all fields to be lensed, then there -- is no reason to use an _ before the prefix. If any of the -- record fields leads with an _ then it is assume a field -- without an _ should not have a lens created. -- -- Note that prefix may be any string of characters that are not -- uppercase letters. (In particular, it may be arbitrary string of -- lowercase letters and numbers) This is the behavior that -- defaultFieldRules had in lens 4.4 and earlier. abbreviatedFields :: LensRules data LensRules -- | Name to give to generated field optics. data DefName -- | Simple top-level definiton name TopName :: Name -> DefName -- | makeFields-style class name and method name MethodName :: Name -> Name -> DefName -- | Rules for making fairly simple partial lenses, ignoring the special -- cases for isomorphisms and traversals, and not making any classes. lensRules :: LensRules -- | Construct a LensRules value for generating top-level -- definitions using the given map from field names to definition names. lensRulesFor :: [(String, String)] -> LensRules -- | Rules for making lenses and traversals that precompose another -- Lens. classyRules :: LensRules classyRules_ :: LensRules -- | Lens' to access the convention for naming fields in our -- LensRules. -- -- Defaults to stripping the _ off of the field name, lowercasing the -- name, and skipping the field if it doesn't start with an '_'. The -- field naming rule provides the names of all fields in the type as well -- as the current field. This extra generality enables field naming -- conventions that depend on the full set of names in a type. -- -- The field naming rule has access to the type name, the names of all -- the field of that type (including the field being named), and the name -- of the field being named. -- -- TypeName -> FieldNames -> FieldName -> DefinitionNames lensField :: Lens' LensRules (Name -> [Name] -> Name -> [DefName]) -- | Retrieve options such as the name of the class and method to put in it -- to build a class around monomorphic data types. Classy lenses -- are generated when this naming convention is provided. TypeName -> -- Maybe (ClassName, MainMethodName) lensClass :: Lens' LensRules (Name -> Maybe (Name, Name)) -- | Generate "simple" optics even when type-changing optics are possible. -- (e.g. Lens' instead of Lens) simpleLenses :: Lens' LensRules Bool -- | Create the class if the constructor is Simple and the -- lensClass rule matches. createClass :: Lens' LensRules Bool -- | Indicate whether or not to supply the signatures for the generated -- lenses. -- -- Disabling this can be useful if you want to provide a more restricted -- type signature or if you want to supply hand-written haddocks. generateSignatures :: Lens' LensRules Bool -- | Generate "updateable" optics when True. When False, -- Folds will be generated instead of Traversals and -- Getters will be generated instead of Lenses. This mode -- is intended to be used for types with invariants which must be -- maintained by "smart" constructors. generateUpdateableOptics :: Lens' LensRules Bool -- | Generate optics using lazy pattern matches. This can allow fields of -- an undefined value to be initialized with lenses: -- --
-- data Foo = Foo {_x :: Int, _y :: Bool} -- deriving Show -- -- makeLensesWith (lensRules & generateLazyPatterns .~ True) ''Foo ---- --
-- > undefined & x .~ 8 & y .~ True -- Foo {_x = 8, _y = True} ---- -- The downside of this flag is that it can lead to space-leaks and -- code-size/compile-time increases when generated for large records. By -- default this flag is turned off, and strict optics are generated. -- -- When using lazy optics the strict optic can be recovered by composing -- with $!: -- --
-- strictOptic = ($!) . lazyOptic --generateLazyPatterns :: Lens' LensRules Bool -- | This module uses dirty tricks to generate a Handler from an -- arbitrary Fold. module Control.Lens.Internal.Exception -- | Both exceptions and Control.Exception provide a -- Handler type. -- -- This lets us write combinators to build handlers that are agnostic -- about the choice of which of these they use. class Handleable e (m :: * -> *) (h :: * -> *) | h -> e m where handler_ l = handler l . const handler :: (Handleable e m h, Typeable a) => Getting (First a) e a -> (a -> m r) -> h r handler_ :: (Handleable e m h, Typeable a) => Getting (First a) e a -> m r -> h r -- | There was an Exception caused by abusing the internals of a -- Handler. data HandlingException HandlingException :: HandlingException instance Typeable HandlingException instance Typeable Handling instance Show HandlingException instance (Reifies s (SomeException -> Maybe a), Typeable (Handling a s m)) => Exception (Handling a s m) instance Show (Handling a s m) instance Exception HandlingException instance Typeable m => Handleable SomeException m (Handler m) instance Handleable SomeException IO Handler -- | These are some of the explicit Functor instances that leak into -- the type signatures of Control.Lens. You shouldn't need to -- import this module directly for most use-cases. module Control.Lens.Internal -- | Usage: -- -- You can derive lenses automatically for many data types: -- --
-- import Control.Lens -- -- data FooBar a -- = Foo { _x :: [Int], _y :: a } -- | Bar { _x :: [Int] } -- makeLenses ''FooBar ---- -- This defines the following lenses: -- --
-- x :: Lens' (FooBar a) [Int] -- y :: Traversal (FooBar a) (FooBar b) a b ---- -- You can then access the value of _x with (^.), the -- value of _y – with (^?) or (^?!) (since it can -- fail), set the values with (.~), modify them with (%~), -- and use almost any other combinator that is re-exported here on those -- fields. -- -- The combinators here have unusually specific type signatures, so for -- particularly tricky ones, the simpler type signatures you might want -- to pretend the combinators have are specified as well. -- -- More information on how to use lenses is available on the lens wiki: -- -- http://github.com/ekmett/lens/wiki -- module Control.Lens -- | This lets the subset of users who vociferously disagree about the full -- scope and set of operators that should be exported from lens to not -- have to look at any operator with which they disagree. -- --
-- import Control.Lens.Combinators --module Control.Lens.Combinators -- | A few extra names that didn't make it into Control.Lens. module Control.Lens.Extras -- | Check to see if this Prism matches. -- --
-- >>> is _Left (Right 12) -- False ---- --
-- >>> is hex "3f79" -- True --is :: APrism s t a b -> s -> Bool -- | This module exists for users who like to work with qualified imports -- but want access to the operators from Lens. -- --
-- import qualified Control.Lens as L -- import Control.Lens.Operators --module Control.Lens.Operators -- | cons an element onto a container. -- -- This is an infix alias for cons. -- --
-- >>> a <| [] -- [a] ---- --
-- >>> a <| [b, c] -- [a,b,c] ---- --
-- >>> a <| Seq.fromList [] -- fromList [a] ---- --
-- >>> a <| Seq.fromList [b, c] -- fromList [a,b,c] --(<|) :: Cons s s a a => a -> s -> s -- | snoc an element onto the end of a container. -- -- This is an infix alias for snoc. -- --
-- >>> Seq.fromList [] |> a -- fromList [a] ---- --
-- >>> Seq.fromList [b, c] |> a -- fromList [b,c,a] ---- --
-- >>> LazyT.pack "hello" |> '!' -- "hello!" --(|>) :: Snoc s s a a => s -> a -> s -- | A convenient infix (flipped) version of toListOf. -- --
-- >>> [[1,2],[3]]^..id -- [[[1,2],[3]]] -- -- >>> [[1,2],[3]]^..traverse -- [[1,2],[3]] -- -- >>> [[1,2],[3]]^..traverse.traverse -- [1,2,3] ---- --
-- >>> (1,2)^..both -- [1,2] ---- --
-- toList xs ≡ xs ^.. folded -- (^..) ≡ flip toListOf ---- --
-- (^..) :: s -> Getter s a -> [a] -- (^..) :: s -> Fold s a -> [a] -- (^..) :: s -> Lens' s a -> [a] -- (^..) :: s -> Iso' s a -> [a] -- (^..) :: s -> Traversal' s a -> [a] -- (^..) :: s -> Prism' s a -> [a] --(^..) :: s -> Getting (Endo [a]) s a -> [a] -- | Perform a safe head of a Fold or Traversal or -- retrieve Just the result from a Getter or Lens. -- -- When using a Traversal as a partial Lens, or a -- Fold as a partial Getter this can be a convenient way to -- extract the optional value. -- -- Note: if you get stack overflows due to this, you may want to use -- firstOf instead, which can deal more gracefully with heavily -- left-biased trees. -- --
-- >>> Left 4 ^?_Left -- Just 4 ---- --
-- >>> Right 4 ^?_Left -- Nothing ---- --
-- >>> "world" ^? ix 3 -- Just 'l' ---- --
-- >>> "world" ^? ix 20 -- Nothing ---- --
-- (^?) ≡ flip preview ---- --
-- (^?) :: s -> Getter s a -> Maybe a -- (^?) :: s -> Fold s a -> Maybe a -- (^?) :: s -> Lens' s a -> Maybe a -- (^?) :: s -> Iso' s a -> Maybe a -- (^?) :: s -> Traversal' s a -> Maybe a --(^?) :: s -> Getting (First a) s a -> Maybe a -- | Perform an *UNSAFE* head of a Fold or Traversal -- assuming that it is there. -- --
-- >>> Left 4 ^?! _Left -- 4 ---- --
-- >>> "world" ^?! ix 3 -- 'l' ---- --
-- (^?!) :: s -> Getter s a -> a -- (^?!) :: s -> Fold s a -> a -- (^?!) :: s -> Lens' s a -> a -- (^?!) :: s -> Iso' s a -> a -- (^?!) :: s -> Traversal' s a -> a --(^?!) :: s -> Getting (Endo a) s a -> a -- | An infix version of itoListOf. (^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)] -- | Perform a safe head (with index) of an IndexedFold or -- IndexedTraversal or retrieve Just the index and result -- from an IndexedGetter or IndexedLens. -- -- When using a IndexedTraversal as a partial IndexedLens, -- or an IndexedFold as a partial IndexedGetter this can be -- a convenient way to extract the optional value. -- --
-- (^@?) :: s -> IndexedGetter i s a -> Maybe (i, a) -- (^@?) :: s -> IndexedFold i s a -> Maybe (i, a) -- (^@?) :: s -> IndexedLens' i s a -> Maybe (i, a) -- (^@?) :: s -> IndexedTraversal' i s a -> Maybe (i, a) --(^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a) -- | Perform an *UNSAFE* head (with index) of an IndexedFold -- or IndexedTraversal assuming that it is there. -- --
-- (^@?!) :: s -> IndexedGetter i s a -> (i, a) -- (^@?!) :: s -> IndexedFold i s a -> (i, a) -- (^@?!) :: s -> IndexedLens' i s a -> (i, a) -- (^@?!) :: s -> IndexedTraversal' i s a -> (i, a) --(^@?!) :: s -> IndexedGetting i (Endo (i, a)) s a -> (i, a) -- | View the value pointed to by a Getter or Lens or the -- result of folding over all the results of a Fold or -- Traversal that points at a monoidal values. -- -- This is the same operation as view with the arguments flipped. -- -- The fixity and semantics are such that subsequent field accesses can -- be performed with (.). -- --
-- >>> (a,b)^._2 -- b ---- --
-- >>> ("hello","world")^._2 -- "world" ---- --
-- >>> import Data.Complex -- -- >>> ((0, 1 :+ 2), 3)^._1._2.to magnitude -- 2.23606797749979 ---- --
-- (^.) :: s -> Getter s a -> a -- (^.) :: Monoid m => s -> Fold s m -> m -- (^.) :: s -> Iso' s a -> a -- (^.) :: s -> Lens' s a -> a -- (^.) :: Monoid m => s -> Traversal' s m -> m --(^.) :: s -> Getting a s a -> a -- | View the index and value of an IndexedGetter or -- IndexedLens. -- -- This is the same operation as iview with the arguments flipped. -- -- The fixity and semantics are such that subsequent field accesses can -- be performed with (.). -- --
-- (^@.) :: s -> IndexedGetter i s a -> (i, a) -- (^@.) :: s -> IndexedLens' i s a -> (i, a) ---- -- The result probably doesn't have much meaning when applied to an -- IndexedFold. (^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a) -- | Compose an Indexed function with a non-indexed function. -- -- Mnemonically, the < points to the indexing we want to -- preserve. -- --
-- >>> let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])] -- -- >>> nestedMap^..(itraversed<.itraversed).withIndex -- [(1,"one,ten"),(1,"one,twenty"),(2,"two,thirty"),(2,"two,forty")] --(<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r -- | Compose a non-indexed function with an Indexed function. -- -- Mnemonically, the > points to the indexing we want to -- preserve. -- -- This is the same as (.). -- -- f . g (and f .> g) gives you the -- index of g unless g is index-preserving, like a -- Prism, Iso or Equality, in which case it'll pass -- through the index of f. -- --
-- >>> let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])] -- -- >>> nestedMap^..(itraversed.>itraversed).withIndex -- [(10,"one,ten"),(20,"one,twenty"),(30,"two,thirty"),(40,"two,forty")] --(.>) :: (st -> r) -> (kab -> st) -> kab -> r -- | Composition of Indexed functions. -- -- Mnemonically, the < and > points to the fact -- that we want to preserve the indices. -- --
-- >>> let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])] -- -- >>> nestedMap^..(itraversed<.>itraversed).withIndex -- [((1,10),"one,ten"),((1,20),"one,twenty"),((2,30),"two,thirty"),((2,40),"two,forty")] --(<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> r -- | (%%~) can be used in one of two scenarios: -- -- When applied to a Lens, it can edit the target of the -- Lens in a structure, extracting a functorial result. -- -- When applied to a Traversal, it can edit the targets of the -- traversals, extracting an applicative summary of its actions. -- --
-- >>> [66,97,116,109,97,110] & each %%~ \a -> ("na", chr a) -- ("nananananana","Batman") ---- -- For all that the definition of this combinator is just: -- --
-- (%%~) ≡ id ---- -- It may be beneficial to think about it as if it had these even more -- restricted types, however: -- --
-- (%%~) :: Functor f => Iso s t a b -> (a -> f b) -> s -> f t -- (%%~) :: Functor f => Lens s t a b -> (a -> f b) -> s -> f t -- (%%~) :: Applicative f => Traversal s t a b -> (a -> f b) -> s -> f t ---- -- When applied to a Traversal, it can edit the targets of the -- traversals, extracting a supplemental monoidal summary of its actions, -- by choosing f = ((,) m) -- --
-- (%%~) :: Iso s t a b -> (a -> (r, b)) -> s -> (r, t) -- (%%~) :: Lens s t a b -> (a -> (r, b)) -> s -> (r, t) -- (%%~) :: Monoid m => Traversal s t a b -> (a -> (m, b)) -> s -> (m, t) --(%%~) :: LensLike f s t a b -> (a -> f b) -> s -> f t -- | Modify the target of a Lens in the current state returning some -- extra information of type r or modify all targets of a -- Traversal in the current state, extracting extra information of -- type r and return a monoidal summary of the changes. -- --
-- >>> runState (_1 %%= \x -> (f x, g x)) (a,b) -- (f a,(g a,b)) ---- --
-- (%%=) ≡ (state .) ---- -- It may be useful to think of (%%=), instead, as having either -- of the following more restricted type signatures: -- --
-- (%%=) :: MonadState s m => Iso s s a b -> (a -> (r, b)) -> m r -- (%%=) :: MonadState s m => Lens s s a b -> (a -> (r, b)) -> m r -- (%%=) :: (MonadState s m, Monoid r) => Traversal s s a b -> (a -> (r, b)) -> m r --(%%=) :: MonadState s m => Over p ((,) r) s s a b -> p a (r, b) -> m r -- | Passes the result of the left side to the function on the right side -- (forward pipe operator). -- -- This is the flipped version of ($), which is more common in -- languages like F# as (|>) where it is needed for -- inference. Here it is supplied for notational convenience and given a -- precedence that allows it to be nested inside uses of ($). -- --
-- >>> a & f -- f a ---- --
-- >>> "hello" & length & succ -- 6 ---- -- This combinator is commonly used when applying multiple Lens -- operations in sequence. -- --
-- >>> ("hello","world") & _1.element 0 .~ 'j' & _1.element 4 .~ 'y' -- ("jelly","world") ---- -- This reads somewhat similar to: -- --
-- >>> flip execState ("hello","world") $ do _1.element 0 .= 'j'; _1.element 4 .= 'y' -- ("jelly","world") --(&) :: a -> (a -> b) -> b -- | This can be used to chain lens operations using op= syntax -- rather than op~ syntax for simple non-type-changing cases. -- --
-- >>> (10,20) & _1 .~ 30 & _2 .~ 40 -- (30,40) ---- --
-- >>> (10,20) &~ do _1 .= 30; _2 .= 40 -- (30,40) ---- -- This does not support type-changing assignment, e.g. -- --
-- >>> (10,20) & _1 .~ "hello" -- ("hello",20) --(&~) :: s -> State s a -> s -- | Infix flipped fmap. -- --
-- (<&>) = flip fmap --(<&>) :: Functor f => f a -> (a -> b) -> f b -- | This is convenient to flip argument order of composite -- functions defined as: -- --
-- fab ?? a = fmap ($ a) fab ---- -- For the Functor instance f = ((->) r) you can -- reason about this function as if the definition was (??) ≡ -- flip: -- --
-- >>> (h ?? x) a -- h a x ---- --
-- >>> execState ?? [] $ modify (1:) -- [1] ---- --
-- >>> over _2 ?? ("hello","world") $ length -- ("hello",5) ---- --
-- >>> over ?? length ?? ("hello","world") $ _2 -- ("hello",5) --(??) :: Functor f => f (a -> b) -> a -> f b -- | Modify the target of a Lens and return the result. -- -- When you do not need the result of the addition, (%~) is more -- flexible. -- --
-- (<%~) :: Lens s t a b -> (a -> b) -> s -> (b, t) -- (<%~) :: Iso s t a b -> (a -> b) -> s -> (b, t) -- (<%~) :: Monoid b => Traversal s t a b -> (a -> b) -> s -> (b, t) --(<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t) -- | Increment the target of a numerically valued Lens and return -- the result. -- -- When you do not need the result of the addition, (+~) is more -- flexible. -- --
-- (<+~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<+~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<+~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Decrement the target of a numerically valued Lens and return -- the result. -- -- When you do not need the result of the subtraction, (-~) is -- more flexible. -- --
-- (<-~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<-~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<-~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Multiply the target of a numerically valued Lens and return the -- result. -- -- When you do not need the result of the multiplication, (*~) is -- more flexible. -- --
-- (<*~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<*~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<*~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Divide the target of a fractionally valued Lens and return the -- result. -- -- When you do not need the result of the division, (//~) is more -- flexible. -- --
-- (<//~) :: Fractional a => Lens' s a -> a -> s -> (a, s) -- (<//~) :: Fractional a => Iso' s a -> a -> s -> (a, s) --(/~) :: Fractional a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Raise the target of a numerically valued Lens to a non-negative -- Integral power and return the result. -- -- When you do not need the result of the operation, (^~) is more -- flexible. -- --
-- (<^~) :: (Num a, Integral e) => Lens' s a -> e -> s -> (a, s) -- (<^~) :: (Num a, Integral e) => Iso' s a -> e -> s -> (a, s) --(<^~) :: (Num a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t) -- | Raise the target of a fractionally valued Lens to an -- Integral power and return the result. -- -- When you do not need the result of the operation, (^^~) is more -- flexible. -- --
-- (<^^~) :: (Fractional a, Integral e) => Lens' s a -> e -> s -> (a, s) -- (<^^~) :: (Fractional a, Integral e) => Iso' s a -> e -> s -> (a, s) --(<^^~) :: (Fractional a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t) -- | Raise the target of a floating-point valued Lens to an -- arbitrary power and return the result. -- -- When you do not need the result of the operation, (**~) is more -- flexible. -- --
-- (<**~) :: Floating a => Lens' s a -> a -> s -> (a, s) -- (<**~) :: Floating a => Iso' s a -> a -> s -> (a, s) --(<**~) :: Floating a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Logically || a Boolean valued Lens and return the -- result. -- -- When you do not need the result of the operation, (||~) is more -- flexible. -- --
-- (<||~) :: Lens' s Bool -> Bool -> s -> (Bool, s) -- (<||~) :: Iso' s Bool -> Bool -> s -> (Bool, s) --(<||~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t) -- | Logically && a Boolean valued Lens and return -- the result. -- -- When you do not need the result of the operation, (&&~) -- is more flexible. -- --
-- (<&&~) :: Lens' s Bool -> Bool -> s -> (Bool, s) -- (<&&~) :: Iso' s Bool -> Bool -> s -> (Bool, s) --(<&&~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t) -- | Modify the target of a Lens, but return the old value. -- -- When you do not need the old value, (%~) is more flexible. -- --
-- (<<%~) :: Lens s t a b -> (a -> b) -> s -> (a, t) -- (<<%~) :: Iso 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) -- | Replace the target of a Lens, but return the old value. -- -- When you do not need the old value, (.~) is more flexible. -- --
-- (<<.~) :: Lens s t a b -> b -> s -> (a, t) -- (<<.~) :: Iso 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) -- | Increment the target of a numerically valued Lens and return -- the old value. -- -- When you do not need the old value, (+~) is more flexible. -- --
-- >>> (a,b) & _1 <<+~ c -- (a,(a + c,b)) ---- --
-- >>> (a,b) & _2 <<+~ c -- (b,(a,b + c)) ---- --
-- (<<+~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<<+~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<<+~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Decrement the target of a numerically valued Lens and return -- the old value. -- -- When you do not need the old value, (-~) is more flexible. -- --
-- >>> (a,b) & _1 <<-~ c -- (a,(a - c,b)) ---- --
-- >>> (a,b) & _2 <<-~ c -- (b,(a,b - c)) ---- --
-- (<<-~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<<-~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<<-~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Multiply the target of a numerically valued Lens and return the -- old value. -- -- When you do not need the old value, (-~) is more flexible. -- --
-- >>> (a,b) & _1 <<*~ c -- (a,(a * c,b)) ---- --
-- >>> (a,b) & _2 <<*~ c -- (b,(a,b * c)) ---- --
-- (<<*~) :: Num a => Lens' s a -> a -> s -> (a, s) -- (<<*~) :: Num a => Iso' s a -> a -> s -> (a, s) --(<<*~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Divide the target of a numerically valued Lens and return the -- old value. -- -- When you do not need the old value, (//~) is more flexible. -- --
-- >>> (a,b) & _1 <<//~ c -- (a,(a / c,b)) ---- --
-- >>> ("Hawaii",10) & _2 <<//~ 2 -- (10.0,("Hawaii",5.0)) ---- --
-- (<<//~) :: Fractional a => Lens' s a -> a -> s -> (a, s) -- (<<//~) :: Fractional a => Iso' s a -> a -> s -> (a, s) --(</~) :: Fractional a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Raise the target of a numerically valued Lens to a non-negative -- power and return the old value. -- -- When you do not need the old value, (^~) is more flexible. -- --
-- (<<^~) :: (Num a, Integral e) => Lens' s a -> e -> s -> (a, s) -- (<<^~) :: (Num a, Integral e) => Iso' s a -> e -> s -> (a, s) --(<<^~) :: (Num a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s) -- | Raise the target of a fractionally valued Lens to an integral -- power and return the old value. -- -- When you do not need the old value, (^^~) is more flexible. -- --
-- (<<^^~) :: (Fractional a, Integral e) => Lens' s a -> e -> s -> (a, s) -- (<<^^~) :: (Fractional a, Integral e) => Iso' s a -> e -> S -> (a, s) --(<<^^~) :: (Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s) -- | Raise the target of a floating-point valued Lens to an -- arbitrary power and return the old value. -- -- When you do not need the old value, (**~) is more flexible. -- --
-- >>> (a,b) & _1 <<**~ c -- (a,(a**c,b)) ---- --
-- >>> (a,b) & _2 <<**~ c -- (b,(a,b**c)) ---- --
-- (<<**~) :: Floating a => Lens' s a -> a -> s -> (a, s) -- (<<**~) :: Floating a => Iso' s a -> a -> s -> (a, s) --(<<**~) :: Floating a => LensLike' ((,) a) s a -> a -> s -> (a, s) -- | Logically || the target of a Bool-valued Lens and -- return the old value. -- -- When you do not need the old value, (||~) is more flexible. -- --
-- >>> (False,6) & _1 <<||~ True -- (False,(True,6)) ---- --
-- >>> ("hello",True) & _2 <<||~ False -- (True,("hello",True)) ---- --
-- (<<||~) :: Lens' s Bool -> Bool -> s -> (Bool, s) -- (<<||~) :: Iso' s Bool -> Bool -> s -> (Bool, s) --(<<||~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s) -- | Logically && the target of a Bool-valued -- Lens and return the old value. -- -- When you do not need the old value, (&&~) is more -- flexible. -- --
-- >>> (False,6) & _1 <<&&~ True -- (False,(False,6)) ---- --
-- >>> ("hello",True) & _2 <<&&~ False -- (True,("hello",False)) ---- --
-- (<<&&~) :: Lens' s Bool -> Bool -> s -> (Bool, s) -- (<<&&~) :: Iso' s Bool -> Bool -> s -> (Bool, s) --(<<&&~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s) -- | Modify the target of a monoidally valued Lens by -- mappending a new value and return the old value. -- -- When you do not need the old value, (<>~) is more -- flexible. -- --
-- >>> (Sum a,b) & _1 <<<>~ Sum c -- (Sum {getSum = a},(Sum {getSum = a + c},b)) ---- --
-- >>> _2 <<<>~ ", 007" $ ("James", "Bond") -- ("Bond",("James","Bond, 007")) ---- --
-- (<<<>~) :: Monoid r => Lens' s r -> r -> s -> (r, s) -- (<<<>~) :: Monoid r => Iso' s r -> r -> s -> (r, s) --(<<<>~) :: Monoid r => LensLike' ((,) r) s r -> r -> s -> (r, s) -- | Modify the target of a Lens into your Monad's state by -- a user supplied function and return the result. -- -- When applied to a Traversal, it this will return a monoidal -- summary of all of the intermediate results. -- -- When you do not need the result of the operation, (%=) is more -- flexible. -- --
-- (<%=) :: MonadState s m => Lens' s a -> (a -> a) -> m a -- (<%=) :: MonadState s m => Iso' s a -> (a -> a) -> m a -- (<%=) :: (MonadState s m, Monoid a) => Traversal' s a -> (a -> a) -> m a --(<%=) :: MonadState s m => LensLike ((,) b) s s a b -> (a -> b) -> m b -- | Add to the target of a numerically valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the addition, (+=) is more -- flexible. -- --
-- (<+=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<+=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Subtract from the target of a numerically valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the subtraction, (-=) is -- more flexible. -- --
-- (<-=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<-=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Multiply the target of a numerically valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the multiplication, (*=) is -- more flexible. -- --
-- (<*=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<*=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Divide the target of a fractionally valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the division, (//=) is more -- flexible. -- --
-- (<//=) :: (MonadState s m, Fractional a) => Lens' s a -> a -> m a -- (<//=) :: (MonadState s m, Fractional a) => Iso' s a -> a -> m a --(/=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a -- | Raise the target of a numerically valued Lens into your -- Monad's state to a non-negative Integral power and -- return the result. -- -- When you do not need the result of the operation, (^=) is more -- flexible. -- --
-- (<^=) :: (MonadState s m, Num a, Integral e) => Lens' s a -> e -> m a -- (<^=) :: (MonadState s m, Num a, Integral e) => Iso' s a -> e -> m a --(<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a -- | Raise the target of a fractionally valued Lens into your -- Monad's state to an Integral power and return the -- result. -- -- When you do not need the result of the operation, (^^=) is more -- flexible. -- --
-- (<^^=) :: (MonadState s m, Fractional b, Integral e) => Lens' s a -> e -> m a -- (<^^=) :: (MonadState s m, Fractional b, Integral e) => Iso' s a -> e -> m a --(<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a -- | Raise the target of a floating-point valued Lens into your -- Monad's state to an arbitrary power and return the result. -- -- When you do not need the result of the operation, (**=) is more -- flexible. -- --
-- (<**=) :: (MonadState s m, Floating a) => Lens' s a -> a -> m a -- (<**=) :: (MonadState s m, Floating a) => Iso' s a -> a -> m a --(<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a -- | Logically || a Boolean valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the operation, (||=) is more -- flexible. -- --
-- (<||=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool -- (<||=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool --(<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool -- | Logically && a Boolean valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the operation, (&&=) -- is more flexible. -- --
-- (<&&=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool -- (<&&=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool --(<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool -- | Modify the target of a Lens into your Monad's state by -- a user supplied function and return the old value that was -- replaced. -- -- When applied to a Traversal, it this will return a monoidal -- summary of all of the old values present. -- -- When you do not need the result of the operation, (%=) is more -- flexible. -- --
-- (<<%=) :: MonadState s m => Lens' s a -> (a -> a) -> m a -- (<<%=) :: MonadState s m => Iso' s a -> (a -> a) -> m a -- (<<%=) :: (MonadState s m, Monoid a) => Traversal' s a -> (a -> a) -> m a ---- --
-- (<<%=) :: MonadState s m => LensLike ((,)a) s s a b -> (a -> b) -> m a --(<<%=) :: (Strong p, MonadState s m) => Over p ((,) a) s s a b -> p a b -> m a -- | Replace the target of a Lens into your Monad's state -- with a user supplied value and return the old value that was -- replaced. -- -- When applied to a Traversal, it this will return a monoidal -- summary of all of the old values present. -- -- When you do not need the result of the operation, (.=) is more -- flexible. -- --
-- (<<.=) :: MonadState s m => Lens' s a -> a -> m a -- (<<.=) :: MonadState s m => Iso' s a -> a -> m a -- (<<.=) :: (MonadState s m, Monoid t) => Traversal' s a -> a -> m a --(<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a -- | Modify the target of a Lens into your Monad's state by -- adding a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (+=) is more -- flexible. -- --
-- (<<+=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<<+=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monad's state by -- subtracting a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (-=) is more -- flexible. -- --
-- (<<-=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<<-=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monad's state by -- multipling a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (*=) is more -- flexible. -- --
-- (<<*=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a -- (<<*=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a --(<<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monads state by -- dividing by a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (//=) is more -- flexible. -- --
-- (<<//=) :: (MonadState s m, Fractional a) => Lens' s a -> a -> m a -- (<<//=) :: (MonadState s m, Fractional a) => Iso' s a -> a -> m a --(</=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monad's state by -- raising it by a non-negative power and return the old value -- that was replaced. -- -- When you do not need the result of the operation, (^=) is more -- flexible. -- --
-- (<<^=) :: (MonadState s m, Num a, Integral e) => Lens' s a -> e -> m a -- (<<^=) :: (MonadState s m, Num a, Integral e) => Iso' s a -> a -> m a --(<<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a -- | Modify the target of a Lens into your Monad's state by -- raising it by an integral power and return the old value that -- was replaced. -- -- When you do not need the result of the operation, (^^=) is more -- flexible. -- --
-- (<<^^=) :: (MonadState s m, Fractional a, Integral e) => Lens' s a -> e -> m a -- (<<^^=) :: (MonadState s m, Fractional a, Integral e) => Iso' s a -> e -> m a --(<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a -- | Modify the target of a Lens into your Monad's state by -- raising it by an arbitrary power and return the old value that -- was replaced. -- -- When you do not need the result of the operation, (**=) is more -- flexible. -- --
-- (<<**=) :: (MonadState s m, Floating a) => Lens' s a -> a -> m a -- (<<**=) :: (MonadState s m, Floating a) => Iso' s a -> a -> m a --(<<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target of a Lens into your Monad's state by -- taking its logical || with a value and return the old -- value that was replaced. -- -- When you do not need the result of the operation, (||=) is more -- flexible. -- --
-- (<<||=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool -- (<<||=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool --(<<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool -- | Modify the target of a Lens into your Monad's state by -- taking its logical && with a value and return the -- old value that was replaced. -- -- When you do not need the result of the operation, (&&=) -- is more flexible. -- --
-- (<<&&=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool -- (<<&&=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool --(<<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool -- | Modify the target of a Lens into your Monad's state by -- mappending a value and return the old value that was -- replaced. -- -- When you do not need the result of the operation, (<>=) -- is more flexible. -- --
-- (<<<>=) :: (MonadState s m, Monoid r) => Lens' s r -> r -> m r -- (<<<>=) :: (MonadState s m, Monoid r) => Iso' s r -> r -> m r --(<<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r -- | Run a monadic action, and set the target of Lens to its result. -- --
-- (<<~) :: MonadState s m => Iso s s a b -> m b -> m b -- (<<~) :: MonadState s m => Lens s s a b -> m b -> m b ---- -- NB: This is limited to taking an actual Lens than admitting a -- Traversal because there are potential loss of state issues -- otherwise. (<<~) :: MonadState s m => ALens s s a b -> m b -> m b -- | mappend a monoidal value onto the end of the target of a -- Lens and return the result. -- -- When you do not need the result of the operation, (<>~) -- is more flexible. (<<>~) :: Monoid m => LensLike ((,) m) s t m m -> m -> s -> (m, t) -- | mappend a monoidal value onto the end of the target of a -- Lens into your Monad's state and return the result. -- -- When you do not need the result of the operation, (<>=) -- is more flexible. (<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r -- | Adjust the target of an IndexedLens returning the intermediate -- result, or adjust all of the targets of an IndexedTraversal and -- return a monoidal summary along with the answer. -- --
-- l <%~ f ≡ l <%@~ const f ---- -- When you do not need access to the index then (<%~) is more -- liberal in what it can accept. -- -- If you do not need the intermediate result, you can use (%@~) -- or even (%~). -- --
-- (<%@~) :: IndexedLens i s t a b -> (i -> a -> b) -> s -> (b, t) -- (<%@~) :: Monoid b => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> (b, t) --(<%@~) :: Over (Indexed i) ((,) b) s t a b -> (i -> a -> b) -> s -> (b, t) -- | Adjust the target of an IndexedLens returning the old value, or -- adjust all of the targets of an IndexedTraversal and return a -- monoidal summary of the old values along with the answer. -- --
-- (<<%@~) :: IndexedLens i s t a b -> (i -> a -> b) -> s -> (a, t) -- (<<%@~) :: Monoid a => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> (a, t) --(<<%@~) :: Over (Indexed i) ((,) a) s t a b -> (i -> a -> b) -> s -> (a, t) -- | Adjust the target of an IndexedLens returning a supplementary -- result, or adjust all of the targets of an IndexedTraversal and -- return a monoidal summary of the supplementary results and the answer. -- --
-- (%%@~) ≡ withIndex ---- --
-- (%%@~) :: Functor f => IndexedLens i s t a b -> (i -> a -> f b) -> s -> f t -- (%%@~) :: Applicative f => IndexedTraversal i s t a b -> (i -> a -> f b) -> s -> f t ---- -- In particular, it is often useful to think of this function as having -- one of these even more restricted type signatures: -- --
-- (%%@~) :: IndexedLens i s t a b -> (i -> a -> (r, b)) -> s -> (r, t) -- (%%@~) :: Monoid r => IndexedTraversal i s t a b -> (i -> a -> (r, b)) -> s -> (r, t) --(%%@~) :: IndexedLensLike i f s t a b -> (i -> a -> f b) -> s -> f t -- | Adjust the target of an IndexedLens returning a supplementary -- result, or adjust all of the targets of an IndexedTraversal -- within the current state, and return a monoidal summary of the -- supplementary results. -- --
-- l %%@= f ≡ state (l %%@~ f) ---- --
-- (%%@=) :: MonadState s m => IndexedLens i s s a b -> (i -> a -> (r, b)) -> s -> m r -- (%%@=) :: (MonadState s m, Monoid r) => IndexedTraversal i s s a b -> (i -> a -> (r, b)) -> s -> m r --(%%@=) :: MonadState s m => IndexedLensLike i ((,) r) s s a b -> (i -> a -> (r, b)) -> m r -- | Adjust the target of an IndexedLens returning the intermediate -- result, or adjust all of the targets of an IndexedTraversal -- within the current state, and return a monoidal summary of the -- intermediate results. -- --
-- (<%@=) :: MonadState s m => IndexedLens i s s a b -> (i -> a -> b) -> m b -- (<%@=) :: (MonadState s m, Monoid b) => IndexedTraversal i s s a b -> (i -> a -> b) -> m b --(<%@=) :: MonadState s m => IndexedLensLike i ((,) b) s s a b -> (i -> a -> b) -> m b -- | Adjust the target of an IndexedLens returning the old value, or -- adjust all of the targets of an IndexedTraversal within the -- current state, and return a monoidal summary of the old values. -- --
-- (<<%@=) :: MonadState s m => IndexedLens i s s a b -> (i -> a -> b) -> m a -- (<<%@=) :: (MonadState s m, Monoid b) => IndexedTraversal i s s a b -> (i -> a -> b) -> m a --(<<%@=) :: MonadState s m => IndexedLensLike i ((,) a) s s a b -> (i -> a -> b) -> m a -- | A version of (^.) that works on ALens. -- --
-- >>> ("hello","world")^#_2 -- "world" --(^#) :: s -> ALens s t a b -> a -- | A version of (.~) that works on ALens. -- --
-- >>> ("hello","there") & _2 #~ "world" -- ("hello","world") --(#~) :: ALens s t a b -> b -> s -> t -- | A version of (%~) that works on ALens. -- --
-- >>> ("hello","world") & _2 #%~ length -- ("hello",5) --(#%~) :: ALens s t a b -> (a -> b) -> s -> t -- | A version of (%%~) that works on ALens. -- --
-- >>> ("hello","world") & _2 #%%~ \x -> (length x, x ++ "!") -- (5,("hello","world!")) --(#%%~) :: Functor f => ALens s t a b -> (a -> f b) -> s -> f t -- | A version of (.=) that works on ALens. (#=) :: MonadState s m => ALens s s a b -> b -> m () -- | A version of (%=) that works on ALens. (#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m () -- | A version of (<%~) that works on ALens. -- --
-- >>> ("hello","world") & _2 <#%~ length -- (5,("hello",5)) --(<#%~) :: ALens s t a b -> (a -> b) -> s -> (b, t) -- | A version of (<%=) that works on ALens. (<#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m b -- | A version of (%%=) that works on ALens. (#%%=) :: MonadState s m => ALens s s a b -> (a -> (r, b)) -> m r -- | A version of (<.~) that works on ALens. -- --
-- >>> ("hello","there") & _2 <#~ "world" -- ("world",("hello","world")) --(<#~) :: ALens s t a b -> b -> s -> (b, t) -- | A version of (<.=) that works on ALens. (<#=) :: MonadState s m => ALens s s a b -> b -> m b -- | Compose through a plate (...) :: (Applicative f, Plated c) => LensLike f s t c c -> Over p f c c a b -> Over p f s t a b -- | An infix alias for review. -- --
-- unto f # x ≡ f x -- l # x ≡ x ^. re l ---- -- This is commonly used when using a Prism as a smart -- constructor. -- --
-- >>> _Left # 4 -- Left 4 ---- -- But it can be used for any Prism -- --
-- >>> base 16 # 123 -- "7b" ---- --
-- (#) :: Iso' s a -> a -> s -- (#) :: Prism' s a -> a -> s -- (#) :: Review s a -> a -> s -- (#) :: Equality' s a -> a -> s --(#) :: AReview t b -> b -> t -- | Modifies the target of a Lens or all of the targets of a -- Setter or Traversal with a user supplied function. -- -- This is an infix version of over. -- --
-- fmap f ≡ mapped %~ f -- fmapDefault f ≡ traverse %~ f ---- --
-- >>> (a,b,c) & _3 %~ f -- (a,b,f c) ---- --
-- >>> (a,b) & both %~ f -- (f a,f b) ---- --
-- >>> _2 %~ length $ (1,"hello") -- (1,5) ---- --
-- >>> traverse %~ f $ [a,b,c] -- [f a,f b,f c] ---- --
-- >>> traverse %~ even $ [1,2,3] -- [False,True,False] ---- --
-- >>> traverse.traverse %~ length $ [["hello","world"],["!!!"]] -- [[5,5],[3]] ---- --
-- (%~) :: Setter s t a b -> (a -> b) -> s -> t -- (%~) :: Iso s t a b -> (a -> b) -> s -> t -- (%~) :: Lens s t a b -> (a -> b) -> s -> t -- (%~) :: Traversal s t a b -> (a -> b) -> s -> t --(%~) :: ASetter s t a b -> (a -> b) -> s -> t -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal with a constant value. -- -- This is an infix version of set, provided for consistency with -- (.=). -- --
-- f <$ a ≡ mapped .~ f $ a ---- --
-- >>> (a,b,c,d) & _4 .~ e -- (a,b,c,e) ---- --
-- >>> (42,"world") & _1 .~ "hello" -- ("hello","world") ---- --
-- >>> (a,b) & both .~ c -- (c,c) ---- --
-- (.~) :: Setter s t a b -> b -> s -> t -- (.~) :: Iso s t a b -> b -> s -> t -- (.~) :: Lens s t a b -> b -> s -> t -- (.~) :: Traversal s t a b -> b -> s -> t --(.~) :: ASetter s t a b -> b -> s -> t -- | Set the target of a Lens, Traversal or Setter to -- Just a value. -- --
-- l ?~ t ≡ set l (Just t) ---- --
-- >>> Nothing & id ?~ a -- Just a ---- --
-- >>> Map.empty & at 3 ?~ x -- fromList [(3,x)] ---- --
-- (?~) :: Setter s t a (Maybe b) -> b -> s -> t -- (?~) :: Iso s t a (Maybe b) -> b -> s -> t -- (?~) :: Lens s t a (Maybe b) -> b -> s -> t -- (?~) :: Traversal s t a (Maybe b) -> b -> s -> t --(?~) :: ASetter s t a (Maybe b) -> b -> s -> t -- | Set with pass-through. -- -- This is mostly present for consistency, but may be useful for chaining -- assignments. -- -- If you do not need a copy of the intermediate result, then using l -- .~ t directly is a good idea. -- --
-- >>> (a,b) & _1 <.~ c -- (c,(c,b)) ---- --
-- >>> ("good","morning","vietnam") & _3 <.~ "world" -- ("world",("good","morning","world")) ---- --
-- >>> (42,Map.fromList [("goodnight","gracie")]) & _2.at "hello" <.~ Just "world" -- (Just "world",(42,fromList [("goodnight","gracie"),("hello","world")])) ---- --
-- (<.~) :: Setter s t a b -> b -> s -> (b, t) -- (<.~) :: Iso s t a b -> b -> s -> (b, t) -- (<.~) :: Lens s t a b -> b -> s -> (b, t) -- (<.~) :: Traversal s t a b -> b -> s -> (b, t) --(<.~) :: ASetter s t a b -> b -> s -> (b, t) -- | Set to Just a value with pass-through. -- -- This is mostly present for consistency, but may be useful for for -- chaining assignments. -- -- If you do not need a copy of the intermediate result, then using l -- ?~ d directly is a good idea. -- --
-- >>> import Data.Map as Map -- -- >>> _2.at "hello" <?~ "world" $ (42,Map.fromList [("goodnight","gracie")]) -- ("world",(42,fromList [("goodnight","gracie"),("hello","world")])) ---- --
-- (<?~) :: Setter s t a (Maybe b) -> b -> s -> (b, t) -- (<?~) :: Iso s t a (Maybe b) -> b -> s -> (b, t) -- (<?~) :: Lens s t a (Maybe b) -> b -> s -> (b, t) -- (<?~) :: Traversal s t a (Maybe b) -> b -> s -> (b, t) --(~) :: ASetter s t a (Maybe b) -> b -> s -> (b, t) -- | Increment the target(s) of a numerically valued Lens, -- Setter 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 => Setter' s a -> a -> s -> s -- (+~) :: Num a => Iso' s a -> a -> s -> s -- (+~) :: Num a => Lens' s a -> a -> s -> s -- (+~) :: Num a => Traversal' s a -> a -> s -> s --(+~) :: Num a => ASetter s t a a -> a -> s -> t -- | Multiply the target(s) of a numerically valued Lens, -- Iso, Setter or Traversal. -- --
-- >>> (a,b) & _1 *~ c -- (a * c,b) ---- --
-- >>> (a,b) & both *~ c -- (a * c,b * c) ---- --
-- >>> (1,2) & _2 *~ 4 -- (1,8) ---- --
-- >>> Just 24 & mapped *~ 2 -- Just 48 ---- --
-- (*~) :: Num a => Setter' s a -> a -> s -> s -- (*~) :: Num a => Iso' s a -> a -> s -> s -- (*~) :: Num a => Lens' s a -> a -> s -> s -- (*~) :: Num a => Traversal' s a -> a -> s -> s --(*~) :: Num a => ASetter s t a a -> a -> s -> t -- | Decrement the target(s) of a numerically valued Lens, -- Iso, Setter 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 => Setter' s a -> a -> s -> s -- (-~) :: Num a => Iso' s a -> a -> s -> s -- (-~) :: Num a => Lens' s a -> a -> s -> s -- (-~) :: Num a => Traversal' s a -> a -> s -> s --(-~) :: Num a => ASetter s t a a -> a -> s -> t -- | Divide the target(s) of a numerically valued Lens, Iso, -- Setter or Traversal. -- --
-- >>> (a,b) & _1 //~ c -- (a / c,b) ---- --
-- >>> (a,b) & both //~ c -- (a / c,b / c) ---- --
-- >>> ("Hawaii",10) & _2 //~ 2 -- ("Hawaii",5.0) ---- --
-- (//~) :: Fractional a => Setter' s a -> a -> s -> s -- (//~) :: Fractional a => Iso' s a -> a -> s -> s -- (//~) :: Fractional a => Lens' s a -> a -> s -> s -- (//~) :: Fractional a => Traversal' s a -> a -> s -> s --(//~) :: Fractional a => ASetter s t a a -> a -> s -> t -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to a non-negative integral power. -- --
-- >>> (1,3) & _2 ^~ 2 -- (1,9) ---- --
-- (^~) :: (Num a, Integral e) => Setter' s a -> e -> s -> s -- (^~) :: (Num a, Integral e) => Iso' s a -> e -> s -> s -- (^~) :: (Num a, Integral e) => Lens' s a -> e -> s -> s -- (^~) :: (Num a, Integral e) => Traversal' s a -> e -> s -> s --(^~) :: (Num a, Integral e) => ASetter s t a a -> e -> s -> t -- | Raise the target(s) of a fractionally valued Lens, -- Setter or Traversal to an integral power. -- --
-- >>> (1,2) & _2 ^^~ (-1) -- (1,0.5) ---- --
-- (^^~) :: (Fractional a, Integral e) => Setter' s a -> e -> s -> s -- (^^~) :: (Fractional a, Integral e) => Iso' s a -> e -> s -> s -- (^^~) :: (Fractional a, Integral e) => Lens' s a -> e -> s -> s -- (^^~) :: (Fractional a, Integral e) => Traversal' s a -> e -> s -> s --(^^~) :: (Fractional a, Integral e) => ASetter s t a a -> e -> s -> t -- | Raise the target(s) of a floating-point valued Lens, -- Setter or Traversal to an arbitrary power. -- --
-- >>> (a,b) & _1 **~ c -- (a**c,b) ---- --
-- >>> (a,b) & both **~ c -- (a**c,b**c) ---- --
-- >>> _2 **~ 10 $ (3,2) -- (3,1024.0) ---- --
-- (**~) :: Floating a => Setter' s a -> a -> s -> s -- (**~) :: Floating a => Iso' s a -> a -> s -> s -- (**~) :: Floating a => Lens' s a -> a -> s -> s -- (**~) :: Floating a => Traversal' s a -> a -> s -> s --(**~) :: Floating a => ASetter s t a a -> a -> s -> t -- | Logically || the target(s) of a Bool-valued Lens -- or Setter. -- --
-- >>> both ||~ True $ (False,True) -- (True,True) ---- --
-- >>> both ||~ False $ (False,True) -- (False,True) ---- --
-- (||~) :: Setter' s Bool -> Bool -> s -> s -- (||~) :: Iso' s Bool -> Bool -> s -> s -- (||~) :: Lens' s Bool -> Bool -> s -> s -- (||~) :: Traversal' s Bool -> Bool -> s -> s --(||~) :: ASetter s t Bool Bool -> Bool -> s -> t -- | Logically && the target(s) of a Bool-valued -- Lens or Setter. -- --
-- >>> both &&~ True $ (False, True) -- (False,True) ---- --
-- >>> both &&~ False $ (False, True) -- (False,False) ---- --
-- (&&~) :: Setter' s Bool -> Bool -> s -> s -- (&&~) :: Iso' s Bool -> Bool -> s -> s -- (&&~) :: Lens' s Bool -> Bool -> s -> s -- (&&~) :: Traversal' s Bool -> Bool -> s -> s --(&&~) :: ASetter s t Bool Bool -> Bool -> s -> t -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state with a new -- value, irrespective of the old. -- -- This is an infix version of assign. -- --
-- >>> execState (do _1 .= c; _2 .= d) (a,b) -- (c,d) ---- --
-- >>> execState (both .= c) (a,b) -- (c,c) ---- --
-- (.=) :: MonadState s m => Iso' s a -> a -> m () -- (.=) :: MonadState s m => Lens' s a -> a -> m () -- (.=) :: MonadState s m => Traversal' s a -> a -> m () -- (.=) :: MonadState s m => Setter' s a -> a -> m () ---- -- It puts the state in the monad or it gets the hose again. (.=) :: MonadState s m => ASetter s s a b -> b -> m () -- | Map over the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state. -- --
-- >>> execState (do _1 %= f;_2 %= g) (a,b) -- (f a,g b) ---- --
-- >>> execState (do both %= f) (a,b) -- (f a,f b) ---- --
-- (%=) :: MonadState s m => Iso' s a -> (a -> a) -> m () -- (%=) :: MonadState s m => Lens' s a -> (a -> a) -> m () -- (%=) :: MonadState s m => Traversal' s a -> (a -> a) -> m () -- (%=) :: MonadState s m => Setter' s a -> (a -> a) -> m () ---- --
-- (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () --(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state with -- Just a new value, irrespective of the old. -- --
-- >>> execState (do at 1 ?= a; at 2 ?= b) Map.empty -- fromList [(1,a),(2,b)] ---- --
-- >>> execState (do _1 ?= b; _2 ?= c) (Just a, Nothing) -- (Just b,Just c) ---- --
-- (?=) :: MonadState s m => Iso' s (Maybe a) -> a -> m () -- (?=) :: MonadState s m => Lens' s (Maybe a) -> a -> m () -- (?=) :: MonadState s m => Traversal' s (Maybe a) -> a -> m () -- (?=) :: MonadState s m => Setter' s (Maybe a) -> a -> m () --(?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by adding a value. -- -- Example: -- --
-- fresh :: MonadState Int m => m Int -- fresh = do -- id += 1 -- use id ---- --
-- >>> execState (do _1 += c; _2 += d) (a,b) -- (a + c,b + d) ---- --
-- >>> execState (do _1.at 1.non 0 += 10) (Map.fromList [(2,100)],"hello") -- (fromList [(1,10),(2,100)],"hello") ---- --
-- (+=) :: (MonadState s m, Num a) => Setter' s a -> a -> m () -- (+=) :: (MonadState s m, Num a) => Iso' s a -> a -> m () -- (+=) :: (MonadState s m, Num a) => Lens' s a -> a -> m () -- (+=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m () --(+=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by subtracting a value. -- --
-- >>> execState (do _1 -= c; _2 -= d) (a,b) -- (a - c,b - d) ---- --
-- (-=) :: (MonadState s m, Num a) => Setter' s a -> a -> m () -- (-=) :: (MonadState s m, Num a) => Iso' s a -> a -> m () -- (-=) :: (MonadState s m, Num a) => Lens' s a -> a -> m () -- (-=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m () --(-=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by multiplying by value. -- --
-- >>> execState (do _1 *= c; _2 *= d) (a,b) -- (a * c,b * d) ---- --
-- (*=) :: (MonadState s m, Num a) => Setter' s a -> a -> m () -- (*=) :: (MonadState s m, Num a) => Iso' s a -> a -> m () -- (*=) :: (MonadState s m, Num a) => Lens' s a -> a -> m () -- (*=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m () --(*=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by dividing by a value. -- --
-- >>> execState (do _1 //= c; _2 //= d) (a,b) -- (a / c,b / d) ---- --
-- (//=) :: (MonadState s m, Fractional a) => Setter' s a -> a -> m () -- (//=) :: (MonadState s m, Fractional a) => Iso' s a -> a -> m () -- (//=) :: (MonadState s m, Fractional a) => Lens' s a -> a -> m () -- (//=) :: (MonadState s m, Fractional a) => Traversal' s a -> a -> m () --(//=) :: (MonadState s m, Fractional a) => ASetter' s a -> a -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to a non-negative integral power. -- --
-- (^=) :: (MonadState s m, Num a, Integral e) => Setter' s a -> e -> m () -- (^=) :: (MonadState s m, Num a, Integral e) => Iso' s a -> e -> m () -- (^=) :: (MonadState s m, Num a, Integral e) => Lens' s a -> e -> m () -- (^=) :: (MonadState s m, Num a, Integral e) => Traversal' s a -> e -> m () --(^=) :: (MonadState s m, Num a, Integral e) => ASetter' s a -> e -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to an integral power. -- --
-- (^^=) :: (MonadState s m, Fractional a, Integral e) => Setter' s a -> e -> m () -- (^^=) :: (MonadState s m, Fractional a, Integral e) => Iso' s a -> e -> m () -- (^^=) :: (MonadState s m, Fractional a, Integral e) => Lens' s a -> e -> m () -- (^^=) :: (MonadState s m, Fractional a, Integral e) => Traversal' s a -> e -> m () --(^^=) :: (MonadState s m, Fractional a, Integral e) => ASetter' s a -> e -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to an arbitrary power -- --
-- >>> execState (do _1 **= c; _2 **= d) (a,b) -- (a**c,b**d) ---- --
-- (**=) :: (MonadState s m, Floating a) => Setter' s a -> a -> m () -- (**=) :: (MonadState s m, Floating a) => Iso' s a -> a -> m () -- (**=) :: (MonadState s m, Floating a) => Lens' s a -> a -> m () -- (**=) :: (MonadState s m, Floating a) => Traversal' s a -> a -> m () --(**=) :: (MonadState s m, Floating a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by taking their logical && with a -- value. -- --
-- >>> execState (do _1 &&= True; _2 &&= False; _3 &&= True; _4 &&= False) (True,True,False,False) -- (True,False,False,False) ---- --
-- (&&=) :: MonadState s m => Setter' s Bool -> Bool -> m () -- (&&=) :: MonadState s m => Iso' s Bool -> Bool -> m () -- (&&=) :: MonadState s m => Lens' s Bool -> Bool -> m () -- (&&=) :: MonadState s m => Traversal' s Bool -> Bool -> m () --(&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m () -- | Modify the target(s) of a Lens', 'Iso, Setter or -- Traversal by taking their logical || with a value. -- --
-- >>> execState (do _1 ||= True; _2 ||= False; _3 ||= True; _4 ||= False) (True,True,False,False) -- (True,True,True,False) ---- --
-- (||=) :: MonadState s m => Setter' s Bool -> Bool -> m () -- (||=) :: MonadState s m => Iso' s Bool -> Bool -> m () -- (||=) :: MonadState s m => Lens' s Bool -> Bool -> m () -- (||=) :: MonadState s m => Traversal' s Bool -> Bool -> m () --(||=) :: MonadState s m => ASetter' s Bool -> Bool -> m () -- | Run a monadic action, and set all of the targets of a Lens, -- Setter or Traversal to its result. -- --
-- (<~) :: MonadState s m => Iso s s a b -> m b -> m () -- (<~) :: MonadState s m => Lens s s a b -> m b -> m () -- (<~) :: MonadState s m => Traversal s s a b -> m b -> m () -- (<~) :: MonadState s m => Setter s s a b -> m b -> m () ---- -- As a reasonable mnemonic, this lets you store the result of a monadic -- action in a Lens rather than in a local variable. -- --
-- do foo <- bar -- ... ---- -- will store the result in a variable, while -- --
-- do foo <~ bar -- ... ---- -- will store the result in a Lens, Setter, or -- Traversal. (<~) :: MonadState s m => ASetter s s a b -> m b -> m () -- | Set with pass-through -- -- This is useful for chaining assignment without round-tripping through -- your Monad stack. -- --
-- do x <- _2 <.= ninety_nine_bottles_of_beer_on_the_wall ---- -- If you do not need a copy of the intermediate result, then using l -- .= d will avoid unused binding warnings. -- --
-- (<.=) :: MonadState s m => Setter s s a b -> b -> m b -- (<.=) :: MonadState s m => Iso s s a b -> b -> m b -- (<.=) :: MonadState s m => Lens s s a b -> b -> m b -- (<.=) :: MonadState s m => Traversal s s a b -> b -> m b --(<.=) :: MonadState s m => ASetter s s a b -> b -> m b -- | Set Just a value with pass-through -- -- This is useful for chaining assignment without round-tripping through -- your Monad stack. -- --
-- do x <- at "foo" <?= ninety_nine_bottles_of_beer_on_the_wall ---- -- If you do not need a copy of the intermediate result, then using l -- ?= d will avoid unused binding warnings. -- --
-- (<?=) :: MonadState s m => Setter s s a (Maybe b) -> b -> m b -- (<?=) :: MonadState s m => Iso s s a (Maybe b) -> b -> m b -- (<?=) :: MonadState s m => Lens s s a (Maybe b) -> b -> m b -- (<?=) :: MonadState s m => Traversal s s a (Maybe b) -> b -> m b --(=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m b -- | Modify the target of a monoidally valued by mappending another -- value. -- --
-- >>> (Sum a,b) & _1 <>~ Sum c -- (Sum {getSum = a + c},b) ---- --
-- >>> (Sum a,Sum b) & both <>~ Sum c -- (Sum {getSum = a + c},Sum {getSum = b + c}) ---- --
-- >>> both <>~ "!!!" $ ("hello","world") -- ("hello!!!","world!!!") ---- --
-- (<>~) :: Monoid a => Setter s t a a -> a -> s -> t -- (<>~) :: Monoid a => Iso s t a a -> a -> s -> t -- (<>~) :: Monoid a => Lens s t a a -> a -> s -> t -- (<>~) :: Monoid a => Traversal s t a a -> a -> s -> t --(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by mappending a value. -- --
-- >>> execState (do _1 <>= Sum c; _2 <>= Product d) (Sum a,Product b) -- (Sum {getSum = a + c},Product {getProduct = b * d}) ---- --
-- >>> execState (both <>= "!!!") ("hello","world") -- ("hello!!!","world!!!") ---- --
-- (<>=) :: (MonadState s m, Monoid a) => Setter' s a -> a -> m () -- (<>=) :: (MonadState s m, Monoid a) => Iso' s a -> a -> m () -- (<>=) :: (MonadState s m, Monoid a) => Lens' s a -> a -> m () -- (<>=) :: (MonadState s m, Monoid a) => Traversal' s a -> a -> m () --(<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m () -- | Adjust every target of an IndexedSetter, IndexedLens or -- IndexedTraversal with access to the index. -- --
-- (%@~) ≡ iover ---- -- When you do not need access to the index then (%~) is more -- liberal in what it can accept. -- --
-- l %~ f ≡ l %@~ const f ---- --
-- (%@~) :: IndexedSetter i s t a b -> (i -> a -> b) -> s -> t -- (%@~) :: IndexedLens i s t a b -> (i -> a -> b) -> s -> t -- (%@~) :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t --(%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t -- | Adjust every target in the current state of an IndexedSetter, -- IndexedLens or IndexedTraversal with access to the -- index. -- -- When you do not need access to the index then (%=) is more -- liberal in what it can accept. -- --
-- l %= f ≡ l %@= const f ---- --
-- (%@=) :: MonadState s m => IndexedSetter i s s a b -> (i -> a -> b) -> m () -- (%@=) :: MonadState s m => IndexedLens i s s a b -> (i -> a -> b) -> m () -- (%@=) :: MonadState s m => IndexedTraversal i s t a b -> (i -> a -> b) -> m () --(%@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m () module Control.Monad.Error.Lens -- | Catch exceptions that match a given Prism (or any -- Getter, really). -- --
-- catching :: MonadError e m => Prism' e a -> m r -> (a -> m r) -> m r -- catching :: MonadError e m => Lens' e a -> m r -> (a -> m r) -> m r -- catching :: MonadError e m => Traversal' e a -> m r -> (a -> m r) -> m r -- catching :: MonadError e m => Iso' e a -> m r -> (a -> m r) -> m r -- catching :: MonadError e m => Getter e a -> m r -> (a -> m r) -> m r -- catching :: MonadError e m => Fold e a -> m r -> (a -> m r) -> m r --catching :: MonadError e m => Getting (First a) e a -> m r -> (a -> m r) -> m r -- | Catch exceptions that match a given Prism (or any -- Getter), discarding the information about the match. This is -- particuarly useful when you have a Prism' e () where -- the result of the Prism or Fold isn't particularly -- valuable, just the fact that it matches. -- --
-- catching_ :: MonadError e m => Prism' e a -> m r -> m r -> m r -- catching_ :: MonadError e m => Lens' e a -> m r -> m r -> m r -- catching_ :: MonadError e m => Traversal' e a -> m r -> m r -> m r -- catching_ :: MonadError e m => Iso' e a -> m r -> m r -> m r -- catching_ :: MonadError e m => Getter e a -> m r -> m r -> m r -- catching_ :: MonadError e m => Fold e a -> m r -> m r -> m r --catching_ :: MonadError e m => Getting (First a) e a -> m r -> m r -> m r -- | A version of catching with the arguments swapped around; useful -- in situations where the code for the handler is shorter. -- --
-- handling :: MonadError e m => Prism' e a -> (a -> m r) -> m r -> m r -- handling :: MonadError e m => Lens' e a -> (a -> m r) -> m r -> m r -- handling :: MonadError e m => Traversal' e a -> (a -> m r) -> m r -> m r -- handling :: MonadError e m => Iso' e a -> (a -> m r) -> m r -> m r -- handling :: MonadError e m => Fold e a -> (a -> m r) -> m r -> m r -- handling :: MonadError e m => Getter e a -> (a -> m r) -> m r -> m r --handling :: MonadError e m => Getting (First a) e a -> (a -> m r) -> m r -> m r -- | A version of catching_ with the arguments swapped around; -- useful in situations where the code for the handler is shorter. -- --
-- handling_ :: MonadError e m => Prism' e a -> m r -> m r -> m r -- handling_ :: MonadError e m => Lens' e a -> m r -> m r -> m r -- handling_ :: MonadError e m => Traversal' e a -> m r -> m r -> m r -- handling_ :: MonadError e m => Iso' e a -> m r -> m r -> m r -- handling_ :: MonadError e m => Getter e a -> m r -> m r -> m r -- handling_ :: MonadError e m => Fold e a -> m r -> m r -> m r --handling_ :: MonadError e m => Getting (First a) e a -> m r -> m r -> m r -- | trying takes a Prism (or any Getter) to select -- which exceptions are caught If the Exception does not match -- the predicate, it is re-thrown. -- --
-- trying :: MonadError e m => Prism' e a -> m r -> m (Either a r) -- trying :: MonadError e m => Lens' e a -> m r -> m (Either a r) -- trying :: MonadError e m => Traversal' e a -> m r -> m (Either a r) -- trying :: MonadError e m => Iso' e a -> m r -> m (Either a r) -- trying :: MonadError e m => Getter e a -> m r -> m (Either a r) -- trying :: MonadError e m => Fold e a -> m r -> m (Either a r) --trying :: MonadError e m => Getting (First a) e a -> m r -> m (Either a r) -- | This function exists to remedy a gap between the functionality of -- Control.Exception and Control.Monad.Error. -- Control.Exception supplies catches and a notion of -- Handler, which we duplicate here in a form suitable for working -- with any MonadError instance. -- -- Sometimes you want to catch two different sorts of error. You could do -- something like -- --
-- f = handling _Foo handleFoo (handling _Bar handleBar expr) ---- -- However, there are a couple of problems with this approach. The first -- is that having two exception handlers is inefficient. However, the -- more serious issue is that the second exception handler will catch -- exceptions in the first, e.g. in the example above, if -- handleFoo uses throwError then the second exception -- handler will catch it. -- -- Instead, we provide a function catches, which would be used -- thus: -- --
-- f = catches expr [ handler _Foo handleFoo -- , handler _Bar handleBar -- ] --catches :: MonadError e m => m a -> [Handler e m a] -> m a -- | You need this when using catches. data Handler e m r Handler :: (e -> Maybe a) -> (a -> m r) -> Handler e m r -- | Both exceptions and Control.Exception provide a -- Handler type. -- -- This lets us write combinators to build handlers that are agnostic -- about the choice of which of these they use. class Handleable e (m :: * -> *) (h :: * -> *) | h -> e m where handler_ l = handler l . const handler :: (Handleable e m h, Typeable a) => Getting (First a) e a -> (a -> m r) -> h r handler_ :: (Handleable e m h, Typeable a) => Getting (First a) e a -> m r -> h r -- | Throw an Exception described by a Prism. -- --
-- throwing l ≡ reviews l throwError ---- --
-- throwing :: MonadError e m => Prism' e t -> t -> a -- throwing :: MonadError e m => Iso' e t -> t -> a --throwing :: MonadError e m => AReview e t -> t -> m x instance Handleable e m (Handler e m) instance Monad m => Monoid (Handler e m a) instance Monad m => Plus (Handler e m) instance Monad m => Alt (Handler e m) instance Monad m => Semigroup (Handler e m a) instance Monad m => Functor (Handler e m) -- | A Lens or Traversal can be used to take the role of -- Traversable in Control.Parallel.Strategies, enabling -- those combinators to work with monomorphic containers. module Control.Parallel.Strategies.Lens -- | Evaluate the targets of a Lens or Traversal into a data -- structure according to the given Strategy. -- --
-- evalTraversable = evalOf traverse = traverse -- evalOf = id ---- --
-- evalOf :: Lens' s a -> Strategy a -> Strategy s -- evalOf :: Traversal' s a -> Strategy a -> Strategy s -- evalOf :: (a -> Eval a) -> s -> Eval s) -> Strategy a -> Strategy s --evalOf :: LensLike' Eval s a -> Strategy a -> Strategy s -- | Evaluate the targets of a Lens or Traversal according -- into a data structure according to a given Strategy in -- parallel. -- --
-- parTraversable = parOf traverse ---- --
-- parOf :: Lens' s a -> Strategy a -> Strategy s -- parOf :: Traversal' s a -> Strategy a -> Strategy s -- parOf :: ((a -> Eval a) -> s -> Eval s) -> Strategy a -> Strategy s --parOf :: LensLike' Eval s a -> Strategy a -> Strategy s -- | Transform a Lens, Fold, Getter, Setter or -- Traversal to first evaluates its argument according to a given -- Strategy before proceeding. -- --
-- after rdeepseq traverse :: Traversable t => Strategy a -> Strategy [a] --after :: Strategy s -> LensLike f s t a b -> LensLike f s t a b -- | Transform a Lens, Fold, Getter, Setter or -- Traversal to evaluate its argument according to a given -- Strategy in parallel with evaluating. -- --
-- throughout rdeepseq traverse :: Traversable t => Strategy a -> Strategy [a] --throughout :: Strategy s -> LensLike f s t a b -> LensLike f s t a b -- | A Fold can be used to take the role of Foldable in -- Control.Seq. module Control.Seq.Lens -- | Evaluate the elements targeted by a Lens, Traversal, -- Iso, Getter or Fold according to the given -- strategy. -- --
-- seqFoldable = seqOf folded --seqOf :: Getting (Endo [a]) s a -> Strategy a -> Strategy s module Data.Array.Lens -- | This setter can be used to derive a new IArray from an -- old IAarray by applying a function to each of the indices to -- look it up in the old IArray. -- -- This is a contravariant Setter. -- --
-- ixmap ≡ over . ixmapped -- ixmapped ≡ setting . ixmap -- over (ixmapped b) f arr ! i ≡ arr ! f i -- bounds (over (ixmapped b) f arr) ≡ b --ixmapped :: (IArray a e, Ix i, Ix j) => (i, i) -> IndexPreservingSetter (a j e) (a i e) i j module Data.Bits.Lens -- | Bitwise .|. the target(s) of a Lens or Setter. -- --
-- >>> _2 .|.~ 6 $ ("hello",3) -- ("hello",7) ---- --
-- (.|.~) :: Bits a => Setter s t a a -> a -> s -> t -- (.|.~) :: Bits a => Iso s t a a -> a -> s -> t -- (.|.~) :: Bits a => Lens s t a a -> a -> s -> t -- (.|.~) :: (Monoid a, Bits a) => Traversal s t a a -> a -> s -> t --(.|.~) :: Bits a => ASetter s t a a -> a -> s -> t -- | Bitwise .&. the target(s) of a Lens or -- Setter. -- --
-- >>> _2 .&.~ 7 $ ("hello",254) -- ("hello",6) ---- --
-- (.&.~) :: Bits a => Setter s t a a -> a -> s -> t -- (.&.~) :: Bits a => Iso s t a a -> a -> s -> t -- (.&.~) :: Bits a => Lens s t a a -> a -> s -> t -- (.&.~) :: (Monoid a, Bits a) => Traversal s t a a -> a -> s -> t --(.&.~) :: Bits a => ASetter s t a a -> a -> s -> t -- | Bitwise .|. the target(s) of a Lens (or -- Traversal), returning the result (or a monoidal summary of all -- of the results). -- --
-- >>> _2 <.|.~ 6 $ ("hello",3) -- (7,("hello",7)) ---- --
-- (<.|.~) :: Bits a => Iso s t a a -> a -> s -> (a, t) -- (<.|.~) :: Bits a => Lens s t a a -> a -> s -> (a, t) -- (<.|.~) :: (Bits a, Monoid a) => Traversal s t a a -> a -> s -> (a, t) --(<.|.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t) -- | Bitwise .&. the target(s) of a Lens or -- Traversal, returning the result (or a monoidal summary of all -- of the results). -- --
-- >>> _2 <.&.~ 7 $ ("hello",254) -- (6,("hello",6)) ---- --
-- (<.&.~) :: Bits a => Iso s t a a -> a -> s -> (a, t) -- (<.&.~) :: Bits a => Lens s t a a -> a -> s -> (a, t) -- (<.&.~) :: (Bits a, Monoid a) => Traversal s t a a -> a -> s -> (a, t) --(<.&.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t) (<<.|.~) :: Bits a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) (<<.&.~) :: Bits a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) -- | Modify the target(s) of a Lens', Setter or -- Traversal by computing its bitwise .|. with another -- value. -- --
-- >>> execState (do _1 .|.= 15; _2 .|.= 3) (7,7) -- (15,7) ---- --
-- (.|.=) :: (MonadState s m, Bits a) => Setter' s a -> a -> m () -- (.|.=) :: (MonadState s m, Bits a) => Iso' s a -> a -> m () -- (.|.=) :: (MonadState s m, Bits a) => Lens' s a -> a -> m () -- (.|.=) :: (MonadState s m, Bits a) => Traversal' s a -> a -> m () --(.|.=) :: (MonadState s m, Bits a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', Setter' or -- Traversal' by computing its bitwise .&. with another -- value. -- --
-- >>> execState (do _1 .&.= 15; _2 .&.= 3) (7,7) -- (7,3) ---- --
-- (.&.=) :: (MonadState s m, Bits a) => Setter' s a -> a -> m () -- (.&.=) :: (MonadState s m, Bits a) => Iso' s a -> a -> m () -- (.&.=) :: (MonadState s m, Bits a) => Lens' s a -> a -> m () -- (.&.=) :: (MonadState s m, Bits a) => Traversal' s a -> a -> m () --(.&.=) :: (MonadState s m, Bits a) => ASetter' s a -> a -> m () -- | Modify the target(s) of a Lens', (or Traversal) by -- computing its bitwise .|. with another value, returning the -- result (or a monoidal summary of all of the results traversed). -- --
-- >>> runState (_1 <.|.= 7) (28,0) -- (31,(31,0)) ---- --
-- (<.|.=) :: (MonadState s m, Bits a) => Lens' s a -> a -> m a -- (<.|.=) :: (MonadState s m, Bits a, Monoid a) => Traversal' s a -> a -> m a --(<.|.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a -- | Modify the target(s) of a Lens' (or Traversal') by -- computing its bitwise .&. with another value, returning the -- result (or a monoidal summary of all of the results traversed). -- --
-- >>> runState (_1 <.&.= 15) (31,0) -- (15,(15,0)) ---- --
-- (<.&.=) :: (MonadState s m, Bits a) => Lens' s a -> a -> m a -- (<.&.=) :: (MonadState s m, Bits a, Monoid a) => Traversal' s a -> a -> m a --(<.&.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a (<<.|.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a (<<.&.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a -- | This Lens can be used to access the value of the nth bit in a -- number. -- -- bitAt n is only a legal Lens into b if -- 0 <= n < bitSize (undefined :: -- b). -- --
-- >>> 16^.bitAt 4 -- True ---- --
-- >>> 15^.bitAt 4 -- False ---- --
-- >>> 15 & bitAt 4 .~ True -- 31 ---- --
-- >>> 16 & bitAt 4 .~ False -- 0 --bitAt :: Bits b => Int -> IndexedLens' Int b Bool -- | Traverse over all bits in a numeric type. -- -- The bit position is available as the index. -- --
-- >>> toListOf bits (5 :: Word8) -- [True,False,True,False,False,False,False,False] ---- -- If you supply this an Integer, the result will be an infinite -- Traversal, which can be productively consumed, but not -- reassembled. bits :: (Num b, Bits b) => IndexedTraversal' Int b Bool -- | Get the nth byte, counting from the low end. -- -- byteAt n is a legal Lens into b iff -- 0 <= n < div (bitSize -- (undefined :: b)) 8 -- --
-- >>> (0xff00 :: Word16)^.byteAt 0 -- 0 ---- --
-- >>> (0xff00 :: Word16)^.byteAt 1 -- 255 ---- --
-- >>> byteAt 1 .~ 0 $ 0xff00 :: Word16 -- 0 ---- --
-- >>> byteAt 0 .~ 0xff $ 0 :: Word16 -- 255 --byteAt :: (Integral b, Bits b) => Int -> IndexedLens' Int b Word8 -- | Traverse over all the bytes in an integral type, from the low end. -- -- The byte position is available as the index. -- --
-- >>> toListOf bytewise (1312301580 :: Word32) -- [12,34,56,78] ---- -- If you supply this an Integer, the result will be an infinite -- Traversal, which can be productively consumed, but not -- reassembled. -- -- Why is'nt this function called bytes to match bits? -- Alas, there is already a function by that name in -- Data.ByteString.Lens. bytewise :: (Integral b, Bits b) => IndexedTraversal' Int b Word8 module Data.ByteString.Strict.Lens -- | pack (or unpack) a list of bytes into a -- ByteString -- --
-- packedBytes ≡ from unpackedBytes -- pack x ≡ x ^. packedBytes -- unpack x ≡ x ^. from packedBytes ---- --
-- >>> [104,101,108,108,111]^.packedBytes -- "hello" --packedBytes :: Iso' [Word8] ByteString -- | unpack (or pack) a ByteString into a list of -- bytes -- --
-- unpackedBytes ≡ from packedBytes -- unpack x ≡ x ^. unpackedBytes -- pack x ≡ x ^. from unpackedBytes ---- --
-- >>> "hello"^.packedChars.unpackedBytes -- [104,101,108,108,111] --unpackedBytes :: Iso' ByteString [Word8] -- | Traverse each Word8 in a ByteString. -- -- This Traversal walks the ByteString in a tree-like -- fashion enable zippers to seek to locations in logarithmic time and -- accelerating many monoidal queries, but up to associativity (and -- constant factors) it is equivalent to the much slower: -- --
-- bytes ≡ unpackedBytes . traversed ---- --
-- >>> anyOf bytes (== 0x80) (Char8.pack "hello") -- False ---- -- Note that when just using this as a Setter, setting -- map can be more efficient. bytes :: IndexedTraversal' Int ByteString Word8 -- | pack (or unpack) a list of characters into a -- ByteString -- -- When writing back to the ByteString it is assumed that every -- Char lies between '\x00' and '\xff'. -- --
-- packedChars ≡ from unpackedChars -- pack x ≡ x ^. packedChars -- unpack x ≡ x ^. from packedChars ---- --
-- >>> "hello"^.packedChars.each.re (base 16 . enum).to (\x -> if Prelude.length x == 1 then '0':x else x) -- "68656c6c6f" --packedChars :: Iso' String ByteString -- | unpack (or pack) a list of characters into a -- ByteString -- -- When writing back to the ByteString it is assumed that every -- Char lies between '\x00' and '\xff'. -- --
-- unpackedChars ≡ from packedChars -- unpack x ≡ x ^. unpackedChars -- pack x ≡ x ^. from unpackedChars ---- --
-- >>> [104,101,108,108,111]^.packedBytes.unpackedChars -- "hello" --unpackedChars :: Iso' ByteString String -- | Traverse the individual bytes in a ByteString as characters. -- -- When writing back to the ByteString it is assumed that every -- Char lies between '\x00' and '\xff'. -- -- This Traversal walks the ByteString in a tree-like -- fashion enable zippers to seek to locations in logarithmic time and -- accelerating many monoidal queries, but up to associativity (and -- constant factors) it is equivalent to the much slower: -- --
-- chars = unpackedChars . traverse ---- --
-- >>> anyOf chars (== 'h') "hello" -- True --chars :: IndexedTraversal' Int ByteString Char -- | Lazy ByteString lenses. module Data.ByteString.Lazy.Lens -- | pack (or unpack) a list of bytes into a -- ByteString. -- --
-- packedBytes ≡ from unpackedBytes -- pack x ≡ x ^. packedBytes -- unpack x ≡ x ^. from packedBytes ---- --
-- >>> [104,101,108,108,111]^.packedBytes == Char8.pack "hello" -- True --packedBytes :: Iso' [Word8] ByteString -- | unpack (or pack) a ByteString into a list of -- bytes -- --
-- unpackedBytes ≡ from packedBytes -- unpack x ≡ x ^. unpackedBytes -- pack x ≡ x ^. from unpackedBytes ---- --
-- >>> "hello"^.packedChars.unpackedBytes -- [104,101,108,108,111] --unpackedBytes :: Iso' ByteString [Word8] -- | Traverse the individual bytes in a ByteString. -- -- This Traversal walks each strict ByteString chunk in a -- tree-like fashion enable zippers to seek to locations more quickly and -- accelerate many monoidal queries, but up to associativity (and -- constant factors) it is equivalent to the much slower: -- --
-- bytes ≡ unpackedBytes . traversed ---- --
-- >>> anyOf bytes (== 0x80) (Char8.pack "hello") -- False ---- -- Note that when just using this as a Setter, setting -- map can be more efficient. bytes :: IndexedTraversal' Int64 ByteString Word8 -- | pack (or unpack) a list of characters into a -- ByteString. -- -- When writing back to the ByteString it is assumed that every -- Char lies between '\x00' and '\xff'. -- --
-- packedChars ≡ from unpackedChars -- pack x ≡ x ^. packedChars -- unpack x ≡ x ^. from packedChars ---- --
-- >>> "hello"^.packedChars.each.re (base 16 . enum).to (\x -> if Prelude.length x == 1 then '0':x else x) -- "68656c6c6f" --packedChars :: Iso' String ByteString -- | unpack (or pack) a list of characters into a -- ByteString -- -- When writing back to the ByteString it is assumed that every -- Char lies between '\x00' and '\xff'. -- --
-- unpackedChars ≡ from packedChars -- unpack x ≡ x ^. unpackedChars -- pack x ≡ x ^. from unpackedChars ---- --
-- >>> [104,101,108,108,111]^.packedBytes.unpackedChars -- "hello" --unpackedChars :: Iso' ByteString String -- | Traverse the individual bytes in a ByteString as characters. -- -- When writing back to the ByteString it is assumed that every -- Char lies between '\x00' and '\xff'. -- -- This Traversal walks each strict ByteString chunk in a -- tree-like fashion enable zippers to seek to locations more quickly and -- accelerate many monoidal queries, but up to associativity (and -- constant factors) it is equivalent to: -- --
-- chars = unpackedChars . traversed ---- --
-- >>> anyOf chars (== 'h') "hello" -- True --chars :: IndexedTraversal' Int64 ByteString Char module Data.ByteString.Lens -- | Traversals for ByteStrings. class IsByteString t where bytes = from packedBytes . traversed chars = from packedChars . traversed packedBytes :: IsByteString t => Iso' [Word8] t packedChars :: IsByteString t => Iso' String t bytes :: IsByteString t => IndexedTraversal' Int t Word8 chars :: IsByteString t => IndexedTraversal' Int t Char -- | unpack (or pack) a ByteString into a list of -- bytes -- --
-- unpackedBytes ≡ from packedBytes -- unpack x ≡ x ^. unpackedBytes -- pack x ≡ x ^. from unpackedBytes ---- --
-- unpackedBytes :: Iso' ByteString [Word8] -- unpackedBytes :: Iso' ByteString [Word8] --unpackedBytes :: IsByteString t => Iso' t [Word8] -- | unpack (or pack) a list of characters into a strict (or -- lazy) ByteString -- -- When writing back to the ByteString it is assumed that every -- Char lies between '\x00' and '\xff'. -- --
-- unpackedChars ≡ from packedChars -- unpack x ≡ x ^. unpackedChars -- pack x ≡ x ^. from unpackedChars ---- --
-- unpackedChars :: Iso' ByteString String -- unpackedChars :: Iso' ByteString String --unpackedChars :: IsByteString t => Iso' t String instance IsByteString ByteString instance IsByteString ByteString -- | Lenses and traversals for complex numbers module Data.Complex.Lens -- | Access the realPart of a Complex number. -- --
-- >>> (a :+ b)^._realPart -- a ---- --
-- >>> a :+ b & _realPart *~ 2 -- a * 2 :+ b ---- --
-- _realPart :: Functor f => (a -> f a) -> Complex a -> f (Complex a) --_realPart :: Lens' (Complex a) a -- | Access the imagPart of a Complex number. -- --
-- >>> (a :+ b)^._imagPart -- b ---- --
-- >>> a :+ b & _imagPart *~ 2 -- a :+ b * 2 ---- --
-- _imagPart :: Functor f => (a -> f a) -> Complex a -> f (Complex a) --_imagPart :: Lens' (Complex a) a -- | This isn't quite a legal Lens. Notably the -- --
-- view l (set l b a) = b ---- -- law is violated when you set a polar value with 0 -- magnitude and non-zero phase as the phase -- information is lost, or with a negative magnitude which flips -- the phase and retains a positive magnitude. So don't do -- that! -- -- Otherwise, this is a perfectly cromulent Lens. _polar :: RealFloat a => Iso' (Complex a) (a, a) -- | Access the magnitude of a Complex number. -- --
-- >>> (10.0 :+ 20.0) & _magnitude *~ 2 -- 20.0 :+ 40.0 ---- -- This isn't quite a legal Lens. Notably the -- --
-- view l (set l b a) = b ---- -- law is violated when you set a negative magnitude. This flips -- the phase and retains a positive magnitude. So don't do -- that! -- -- Otherwise, this is a perfectly cromulent Lens. -- -- Setting the magnitude of a zero Complex number assumes -- the phase is 0. _magnitude :: RealFloat a => Lens' (Complex a) a -- | Access the phase of a Complex number. -- --
-- >>> (mkPolar 10 (2-pi) & _phase +~ pi & view _phase) ≈ 2 -- True ---- -- This isn't quite a legal Lens. Notably the -- --
-- view l (set l b a) = b ---- -- law is violated when you set a phase outside the range -- (-pi, pi]. The phase is always in that range -- when queried. So don't do that! -- -- Otherwise, this is a perfectly cromulent Lens. _phase :: RealFloat a => Lens' (Complex a) a -- | Access the conjugate of a Complex number. -- --
-- >>> (2.0 :+ 3.0) & _conjugate . _imagPart -~ 1 -- 2.0 :+ 4.0 ---- --
-- >>> (mkPolar 10.0 2.0 ^. _conjugate . _phase) ≈ (-2.0) -- True --_conjugate :: RealFloat a => Iso' (Complex a) (Complex a) module Data.IntSet.Lens -- | IntSet isn't Foldable, but this Fold can be used to access the -- members of an IntSet. -- --
-- >>> sumOf members $ setOf folded [1,2,3,4] -- 10 --members :: Fold IntSet Int -- | This Setter can be used to change the contents of an -- IntSet by mapping the elements to new values. -- -- Sadly, you can't create a valid Traversal for a Set, -- because the number of elements might change but you can manipulate it -- by reading using folded and reindexing it via setmapped. -- --
-- >>> over setmapped (+1) (fromList [1,2,3,4]) -- fromList [2,3,4,5] --setmapped :: IndexPreservingSetter' IntSet Int -- | Construct an IntSet from a Getter, Fold, -- Traversal, Lens or Iso. -- --
-- >>> setOf folded [1,2,3,4] -- fromList [1,2,3,4] ---- --
-- >>> setOf (folded._2) [("hello",1),("world",2),("!!!",3)] -- fromList [1,2,3] ---- --
-- setOf :: Getter s Int -> s -> IntSet -- setOf :: Fold s Int -> s -> IntSet -- setOf :: Iso' s Int -> s -> IntSet -- setOf :: Lens' s Int -> s -> IntSet -- setOf :: Traversal' s Int -> s -> IntSet --setOf :: Getting IntSet s Int -> s -> IntSet -- | Traversals for manipulating parts of a list. -- -- Additional optics for manipulating lists are present more generically -- in this package. -- -- The Ixed class allows traversing the element at a specific list -- index. -- --
-- >>> [0..10] ^? ix 4 -- Just 4 ---- --
-- >>> [0..5] & ix 4 .~ 2 -- [0,1,2,3,2,5] ---- --
-- >>> [0..10] ^? ix 14 -- Nothing ---- --
-- >>> [0..5] & ix 14 .~ 2 -- [0,1,2,3,4,5] ---- -- The Cons and AsEmpty classes provide Prisms for -- list constructors. -- --
-- >>> [1..10] ^? _Cons -- Just (1,[2,3,4,5,6,7,8,9,10]) ---- --
-- >>> [] ^? _Cons -- Nothing ---- --
-- >>> [] ^? _Empty -- Just () ---- --
-- >>> _Cons # (1, _Empty # ()) :: [Int] -- [1] ---- -- Additionally, Snoc provides a Prism for accessing the -- end of a list. Note that this Prism always will need to -- traverse the whole list. -- --
-- >>> [1..5] ^? _Snoc -- Just ([1,2,3,4],5) ---- --
-- >>> _Snoc # ([1,2],5) -- [1,2,5] ---- -- An instance of Plated allows for finding locations in the list -- where a traversal matches. -- --
-- >>> [Nothing, Just 7, Just 3, Nothing] & deep (ix 0 . _Just) +~ 10 -- [Nothing,Just 17,Just 3,Nothing] ---- -- An instance of Reversing provides an Iso between a list -- and its reverse. -- --
-- >>> "live" & reversed %~ ('d':) -- "lived" ---- -- Finally, it's possible to traverse, fold over, and map over -- index-value pairs thanks to instances of TraversableWithIndex, -- FoldableWithIndex, and FunctorWithIndex. -- --
-- >>> imap (,) "Hello" -- [(0,'H'),(1,'e'),(2,'l'),(3,'l'),(4,'o')] ---- --
-- >>> ifoldMap replicate "Hello" -- "ellllloooo" ---- --
-- >>> itraverse_ (curry print) "Hello" -- (0,'H') -- (1,'e') -- (2,'l') -- (3,'l') -- (4,'o') --module Data.List.Lens -- | A Prism stripping a prefix from a list when used as a -- Traversal, or prepending that prefix when run backwards: -- --
-- >>> "preview" ^? prefixed "pre" -- Just "view" ---- --
-- >>> "review" ^? prefixed "pre" -- Nothing ---- --
-- >>> prefixed "pre" # "amble" -- "preamble" --prefixed :: Eq a => [a] -> Prism' [a] [a] -- | A Prism stripping a suffix from a list when used as a -- Traversal, or appending that suffix when run backwards: -- --
-- >>> "review" ^? suffixed "view" -- Just "re" ---- --
-- >>> "review" ^? suffixed "tire" -- Nothing ---- --
-- >>> suffixed ".o" # "hello" -- "hello.o" --suffixed :: Eq a => [a] -> Prism' [a] [a] stripSuffix :: Eq a => [a] -> [a] -> Maybe [a] module Data.Sequence.Lens -- | A Seq is isomorphic to a ViewL -- --
-- viewl m ≡ m ^. viewL ---- --
-- >>> Seq.fromList [a,b,c] ^. viewL -- a :< fromList [b,c] ---- --
-- >>> Seq.empty ^. viewL -- EmptyL ---- --
-- >>> EmptyL ^. from viewL -- fromList [] ---- --
-- >>> review viewL $ a Seq.:< fromList [b,c] -- fromList [a,b,c] --viewL :: Iso (Seq a) (Seq b) (ViewL a) (ViewL b) -- | A Seq is isomorphic to a ViewR -- --
-- viewr m ≡ m ^. viewR ---- --
-- >>> Seq.fromList [a,b,c] ^. viewR -- fromList [a,b] :> c ---- --
-- >>> Seq.empty ^. viewR -- EmptyR ---- --
-- >>> EmptyR ^. from viewR -- fromList [] ---- --
-- >>> review viewR $ fromList [a,b] Seq.:> c -- fromList [a,b,c] --viewR :: Iso (Seq a) (Seq b) (ViewR a) (ViewR b) -- | Traverse all the elements numbered from i to j of a -- Seq -- --
-- >>> fromList [a,b,c,d,e] & sliced 1 3 %~ f -- fromList [a,f b,f c,d,e] --sliced :: Int -> Int -> IndexedTraversal' Int (Seq a) a -- | Traverse the first n elements of a Seq -- --
-- >>> fromList [a,b,c,d,e] ^.. slicedTo 2 -- [a,b] ---- --
-- >>> fromList [a,b,c,d,e] & slicedTo 2 %~ f -- fromList [f a,f b,c,d,e] ---- --
-- >>> fromList [a,b,c,d,e] & slicedTo 10 .~ x -- fromList [x,x,x,x,x] --slicedTo :: Int -> IndexedTraversal' Int (Seq a) a -- | Traverse all but the first n elements of a Seq -- --
-- >>> fromList [a,b,c,d,e] ^.. slicedFrom 2 -- [c,d,e] ---- --
-- >>> fromList [a,b,c,d,e] & slicedFrom 2 %~ f -- fromList [a,b,f c,f d,f e] ---- --
-- >>> fromList [a,b,c,d,e] & slicedFrom 10 .~ x -- fromList [a,b,c,d,e] --slicedFrom :: Int -> IndexedTraversal' Int (Seq a) a -- | Construct a Seq from a Getter, Fold, -- Traversal, Lens or Iso. -- --
-- >>> seqOf folded ["hello","world"] -- fromList ["hello","world"] ---- --
-- >>> seqOf (folded._2) [("hello",1),("world",2),("!!!",3)] -- fromList [1,2,3] ---- --
-- seqOf :: Getter s a -> s -> Seq a -- seqOf :: Fold s a -> s -> Seq a -- seqOf :: Iso' s a -> s -> Seq a -- seqOf :: Lens' s a -> s -> Seq a -- seqOf :: Traversal' s a -> s -> Seq a --seqOf :: Getting (Seq a) s a -> s -> Seq a module Data.Tree.Lens -- | A Lens that focuses on the root of a Tree. -- --
-- >>> view root $ Node 42 [] -- 42 --root :: Lens' (Tree a) a -- | A Lens returning the direct descendants of the root of a -- Tree -- --
-- view branches ≡ subForest --branches :: Lens' (Tree a) [Tree a] module Data.Typeable.Lens -- | A Traversal' for working with a cast of a -- Typeable value. _cast :: (Typeable s, Typeable a) => Traversal' s a -- | A Traversal' for working with a gcast of a -- Typeable value. _gcast :: (Typeable s, Typeable a) => Traversal' (c s) (c a) -- | This module provides lenses and traversals for working with generic -- vectors. module Data.Vector.Lens -- | Similar to toListOf, but returning a Vector. -- --
-- >>> toVectorOf both (8,15) == Vector.fromList [8,15] -- True --toVectorOf :: Getting (Endo [a]) s a -> s -> Vector a -- | Convert a list to a Vector (or back) -- --
-- >>> [1,2,3] ^. vector == Vector.fromList [1,2,3] -- True ---- --
-- >>> [1,2,3] ^. vector . from vector -- [1,2,3] ---- --
-- >>> Vector.fromList [0,8,15] ^. from vector . vector == Vector.fromList [0,8,15] -- True --vector :: Iso [a] [b] (Vector a) (Vector b) -- | Convert a Vector to a version that doesn't retain any extra -- memory. forced :: Iso (Vector a) (Vector b) (Vector a) (Vector b) -- | sliced i n provides a Lens that edits the n -- elements starting at index i from a Lens. -- -- This is only a valid Lens if you do not change the length of -- the resulting Vector. -- -- Attempting to return a longer or shorter vector will result in -- violations of the Lens laws. -- --
-- >>> Vector.fromList [1..10] ^. sliced 2 5 == Vector.fromList [3,4,5,6,7] -- True ---- --
-- >>> (Vector.fromList [1..10] & sliced 2 5 . mapped .~ 0) == Vector.fromList [1,2,0,0,0,0,0,8,9,10] -- True --sliced :: Int -> Int -> Lens' (Vector a) (Vector a) -- | This Traversal will ignore any duplicates in the supplied list -- of indices. -- --
-- >>> toListOf (ordinals [1,3,2,5,9,10]) $ Vector.fromList [2,4..40] -- [4,8,6,12,20,22] --ordinals :: [Int] -> IndexedTraversal' Int (Vector a) a -- | Note: Generics.Deriving exports a number of names that -- collide with Control.Lens. -- -- You can use hiding to mitigate this to an extent, and the following -- import represents a fair compromise for user code: -- --
-- import Generics.Deriving hiding (from, to) ---- -- You can use generic to replace from and to from -- Generics.Deriving. module Generics.Deriving.Lens -- | Convert from the data type to its representation (or back) -- --
-- >>> "hello"^.generic.from generic :: String -- "hello" --generic :: Generic a => Iso' a (Rep a b) -- | Convert from the data type to its representation (or back) generic1 :: Generic1 f => Iso' (f a) (Rep1 f a) -- | A Generic Traversal that visits every occurrence of -- something Typeable anywhere in a container. -- --
-- >>> allOf tinplate (=="Hello") (1::Int,2::Double,(),"Hello",["Hello"]) -- True ---- --
-- >>> mapMOf_ tinplate putStrLn ("hello",[(2 :: Int, "world!")]) -- hello -- world! --tinplate :: (Generic a, GTraversal (Rep a), Typeable b) => Traversal' a b -- | Used to traverse Generic data by uniplate. class GTraversal f instance GTraversal a => GTraversal (M1 i c a) instance (GTraversal f, GTraversal g) => GTraversal (f :+: g) instance (GTraversal f, GTraversal g) => GTraversal (f :*: g) instance GTraversal V1 instance GTraversal U1 instance (Generic a, GTraversal (Rep a), Typeable a) => GTraversal (K1 i a) -- | Note: GHC.Generics exports a number of names that collide -- with Control.Lens. -- -- You can use hiding or imports to mitigate this to an extent, and the -- following imports, represent a fair compromise for user code: -- --
-- import Control.Lens hiding (Rep) -- import GHC.Generics hiding (from, to) ---- -- You can use generic to replace from and to from -- GHC.Generics, and probably won't be explicitly referencing -- Rep from Control.Lens in code that uses generics. -- -- This module provides compatibility with older GHC versions by using -- the generic-deriving package. module GHC.Generics.Lens _V1 :: Over p f (V1 s) (V1 t) a b _U1 :: Iso (U1 p) (U1 q) () () _Par1 :: Iso (Par1 p) (Par1 q) p q _Rec1 :: Iso (Rec1 f p) (Rec1 g q) (f p) (g q) _K1 :: Iso (K1 i c p) (K1 j d q) c d _M1 :: Iso (M1 i c f p) (M1 j d g q) (f p) (g q) _L1 :: Prism' ((f :+: g) a) (f a) -- | You can access fields of `data (f :*: g) p` by using it's -- Field1 and Field2 instances _R1 :: Prism' ((f :+: g) a) (g a) module System.FilePath.Lens -- | Modify the path by adding another path. -- --
-- >>> both </>~ "bin" $ ("hello","world") -- ("hello/bin","world/bin") ---- --
-- (</>~) :: Setter s a FilePath FilePath -> FilePath -> s -> a -- (</>~) :: Iso s a FilePath FilePath -> FilePath -> s -> a -- (</>~) :: Lens s a FilePath FilePath -> FilePath -> s -> a -- (</>~) :: Traversal s a FilePath FilePath -> FilePath -> s -> a --(>~) :: ASetter s t FilePath FilePath -> FilePath -> s -> t -- | Add a path onto the end of the target of a Lens and return the -- result -- -- When you do not need the result of the operation, (</>~) -- is more flexible. (<>~) :: LensLike ((,) FilePath) s a FilePath FilePath -> FilePath -> s -> (FilePath, a) (<<>~) :: Optical' (->) q ((,) FilePath) s FilePath -> FilePath -> q s (FilePath, s) -- | Modify the path by adding an extension. -- --
-- >>> both <.>~ "txt" $ ("hello","world") -- ("hello.txt","world.txt") ---- --
-- (<.>~) :: Setter s a FilePath FilePath -> String -> s -> a -- (<.>~) :: Iso s a FilePath FilePath -> String -> s -> a -- (<.>~) :: Lens s a FilePath FilePath -> String -> s -> a -- (<.>~) :: Traversal s a FilePath FilePath -> String -> s -> a --(<.>~) :: ASetter s a FilePath FilePath -> String -> s -> a -- | Add an extension onto the end of the target of a Lens and -- return the result -- --
-- >>> _1 <<.>~ "txt" $ ("hello","world") -- ("hello.txt",("hello.txt","world")) ---- -- When you do not need the result of the operation, (<.>~) -- is more flexible. (<<.>~) :: LensLike ((,) FilePath) s a FilePath FilePath -> String -> s -> (FilePath, a) -- | Add an extension onto the end of the target of a Lens but -- return the old value -- --
-- >>> _1 <<<.>~ "txt" $ ("hello","world") -- ("hello",("hello.txt","world")) ---- -- When you do not need the old value, (<.>~) is more -- flexible. (<<<.>~) :: Optical' (->) q ((,) FilePath) s FilePath -> String -> q s (FilePath, s) -- | Modify the target(s) of a Lens', Iso', Setter' or -- Traversal' by adding a path. -- --
-- >>> execState (both </>= "bin") ("hello","world") -- ("hello/bin","world/bin") ---- --
-- (</>=) :: MonadState s m => Setter' s FilePath -> FilePath -> m () -- (</>=) :: MonadState s m => Iso' s FilePath -> FilePath -> m () -- (</>=) :: MonadState s m => Lens' s FilePath -> FilePath -> m () -- (</>=) :: MonadState s m => Traversal' s FilePath -> FilePath -> m () --(>=) :: MonadState s m => ASetter' s FilePath -> FilePath -> m () -- | Add a path onto the end of the target of a Lens into your -- monad's state and return the result. -- -- When you do not need the result of the operation, (</>=) -- is more flexible. (<>=) :: MonadState s m => LensLike' ((,) FilePath) s FilePath -> FilePath -> m FilePath (<<>=) :: MonadState s m => LensLike' ((,) FilePath) s FilePath -> FilePath -> m FilePath -- | Modify the target(s) of a Lens', Iso', Setter' or -- Traversal' by adding an extension. -- --
-- >>> execState (both <.>= "txt") ("hello","world") -- ("hello.txt","world.txt") ---- --
-- (<.>=) :: MonadState s m => Setter' s FilePath -> String -> m () -- (<.>=) :: MonadState s m => Iso' s FilePath -> String -> m () -- (<.>=) :: MonadState s m => Lens' s FilePath -> String -> m () -- (<.>=) :: MonadState s m => Traversal' s FilePath -> String -> m () --(<.>=) :: MonadState s m => ASetter' s FilePath -> String -> m () -- | Add an extension onto the end of the target of a Lens into your -- monad's state and return the result. -- --
-- >>> evalState (_1 <<.>= "txt") ("hello","world") -- "hello.txt" ---- -- When you do not need the result of the operation, (<.>=) -- is more flexible. (<<.>=) :: MonadState s m => LensLike' ((,) FilePath) s FilePath -> String -> m FilePath (<<<.>=) :: MonadState s m => LensLike' ((,) FilePath) s FilePath -> String -> m FilePath -- | A Lens for reading and writing to the basename -- -- Note: This is not a legal Lens unless the outer -- FilePath has both a directory and filename component and the -- generated basenames are not null and contain no directory separators. -- --
-- >>> basename .~ "filename" $ "path/name.png" -- "path/filename.png" --basename :: Lens' FilePath FilePath -- | A Lens for reading and writing to the directory -- -- Note: this is not a legal Lens unless the outer -- FilePath already has a directory component, and generated -- directories are not null. -- --
-- >>> "long/path/name.txt" ^. directory -- "long/path" --directory :: Lens' FilePath FilePath -- | A Lens for reading and writing to the extension -- -- Note: This is not a legal Lens, unless you are careful -- to ensure that generated extension FilePath components are -- either null or start with extSeparator and do not contain any -- internal extSeparators. -- --
-- >>> extension .~ ".png" $ "path/name.txt" -- "path/name.png" --extension :: Lens' FilePath FilePath -- | A Lens for reading and writing to the full filename -- -- Note: This is not a legal Lens, unless you are careful -- to ensure that generated filename FilePath components are not -- null and do not contain any elements of pathSeparatorss. -- --
-- >>> filename .~ "name.txt" $ "path/name.png" -- "path/name.txt" --filename :: Lens' FilePath FilePath module System.IO.Error.Lens -- | Where the error happened. location :: Lens' IOException String -- | Error type specific information. description :: Lens' IOException String -- | The handle used by the action flagging this error. handle :: Lens' IOException (Maybe Handle) -- | fileName the error is related to. fileName :: Lens' IOException (Maybe FilePath) -- | errno leading to this error, if any. errno :: Lens' IOException (Maybe CInt) -- | What type of error it is errorType :: Lens' IOException IOErrorType _AlreadyExists :: Prism' IOErrorType () _NoSuchThing :: Prism' IOErrorType () _ResourceBusy :: Prism' IOErrorType () _ResourceExhausted :: Prism' IOErrorType () _EOF :: Prism' IOErrorType () _IllegalOperation :: Prism' IOErrorType () _PermissionDenied :: Prism' IOErrorType () _UserError :: Prism' IOErrorType () _UnsatisfiedConstraints :: Prism' IOErrorType () _SystemError :: Prism' IOErrorType () _ProtocolError :: Prism' IOErrorType () _OtherError :: Prism' IOErrorType () _InvalidArgument :: Prism' IOErrorType () _InappropriateType :: Prism' IOErrorType () _HardwareFault :: Prism' IOErrorType () _UnsupportedOperation :: Prism' IOErrorType () _TimeExpired :: Prism' IOErrorType () _ResourceVanished :: Prism' IOErrorType () _Interrupted :: Prism' IOErrorType () module Numeric.Lens -- | A prism that shows and reads integers in base-2 through base-36 -- -- Note: This is an improper prism, since leading 0s are stripped when -- reading. -- --
-- >>> "100" ^? base 16 -- Just 256 ---- --
-- >>> 1767707668033969 ^. re (base 36) -- "helloworld" --base :: Integral a => Int -> Prism' String a -- | This Prism can be used to model the fact that every -- Integral type is a subset of Integer. -- -- Embedding through the Prism only succeeds if the Integer -- would pass through unmodified when re-extracted. integral :: (Integral a, Integral b) => Prism Integer Integer a b -- |
-- binary = base 2 --binary :: Integral a => Prism' String a -- |
-- octal = base 8 --octal :: Integral a => Prism' String a -- |
-- decimal = base 10 --decimal :: Integral a => Prism' String a -- |
-- hex = base 16 --hex :: Integral a => Prism' String a -- |
-- adding n = iso (+n) (subtract n) ---- --
-- >>> [1..3]^..traverse.adding 1000 -- [1001,1002,1003] --adding :: Num a => a -> Iso' a a -- |
-- subtracting n = iso (subtract n) ((+n) -- subtracting n = from (adding n) --subtracting :: Num a => a -> Iso' a a -- |
-- multiplying n = iso (*n) (/n) ---- -- Note: This errors for n = 0 -- --
-- >>> 5 & multiplying 1000 +~ 3 -- 5.003 ---- --
-- >>> let fahrenheit = multiplying (9/5).adding 32 in 230^.from fahrenheit -- 110.0 --multiplying :: (Fractional a, Eq a) => a -> Iso' a a -- |
-- dividing n = iso (/n) (*n) -- dividing n = from (multiplying n) ---- -- Note: This errors for n = 0 dividing :: (Fractional a, Eq a) => a -> Iso' a a -- |
-- exponentiating n = iso (**n) (**recip n) ---- -- Note: This errors for n = 0 -- --
-- >>> au (_Wrapping Sum . from (exponentiating 2)) (foldMapOf each) (3,4) == 5 -- True --exponentiating :: (Floating a, Eq a) => a -> Iso' a a -- |
-- negated = iso negate negate ---- --
-- >>> au (_Wrapping Sum . negated) (foldMapOf each) (3,4) == 7 -- True ---- --
-- >>> au (_Wrapping Sum) (foldMapOf (each.negated)) (3,4) == -7 -- True --negated :: Num a => Iso' a a -- | Control.Exception provides an example of a large open -- hierarchy that we can model with prisms and isomorphisms. -- -- Additional combinators for working with IOException results can -- be found in System.IO.Error.Lens. -- -- The combinators in this module have been generalized to work with -- MonadCatch instead of just IO. This enables them to be -- used more easily in Monad transformer stacks. module Control.Exception.Lens -- | Catch exceptions that match a given Prism (or any Fold, -- really). -- --
-- >>> catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught" -- "caught" ---- --
-- catching :: MonadCatch m => Prism' SomeException a -> m r -> (a -> m r) -> m r -- catching :: MonadCatch m => Lens' SomeException a -> m r -> (a -> m r) -> m r -- catching :: MonadCatch m => Traversal' SomeException a -> m r -> (a -> m r) -> m r -- catching :: MonadCatch m => Iso' SomeException a -> m r -> (a -> m r) -> m r -- catching :: MonadCatch m => Getter SomeException a -> m r -> (a -> m r) -> m r -- catching :: MonadCatch m => Fold SomeException a -> m r -> (a -> m r) -> m r --catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r -- | Catch exceptions that match a given Prism (or any -- Getter), discarding the information about the match. This is -- particuarly useful when you have a Prism' e () where -- the result of the Prism or Fold isn't particularly -- valuable, just the fact that it matches. -- --
-- >>> catching_ _AssertionFailed (assert False (return "uncaught")) $ return "caught" -- "caught" ---- --
-- catching_ :: MonadCatch m => Prism' SomeException a -> m r -> m r -> m r -- catching_ :: MonadCatch m => Lens' SomeException a -> m r -> m r -> m r -- catching_ :: MonadCatch m => Traversal' SomeException a -> m r -> m r -> m r -- catching_ :: MonadCatch m => Iso' SomeException a -> m r -> m r -> m r -- catching_ :: MonadCatch m => Getter SomeException a -> m r -> m r -> m r -- catching_ :: MonadCatch m => Fold SomeException a -> m r -> m r -> m r --catching_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m r -> m r -- | A version of catching with the arguments swapped around; useful -- in situations where the code for the handler is shorter. -- --
-- >>> handling _NonTermination (\_ -> return "caught") $ throwIO NonTermination -- "caught" ---- --
-- handling :: MonadCatch m => Prism' SomeException a -> (a -> m r) -> m r -> m r -- handling :: MonadCatch m => Lens' SomeException a -> (a -> m r) -> m r -> m r -- handling :: MonadCatch m => Traversal' SomeException a -> (a -> m r) -> m r -> m r -- handling :: MonadCatch m => Iso' SomeException a -> (a -> m r) -> m r -> m r -- handling :: MonadCatch m => Fold SomeException a -> (a -> m r) -> m r -> m r -- handling :: MonadCatch m => Getter SomeException a -> (a -> m r) -> m r -> m r --handling :: MonadCatch m => Getting (First a) SomeException a -> (a -> m r) -> m r -> m r -- | A version of catching_ with the arguments swapped around; -- useful in situations where the code for the handler is shorter. -- --
-- >>> handling_ _NonTermination (return "caught") $ throwIO NonTermination -- "caught" ---- --
-- handling_ :: MonadCatch m => Prism' SomeException a -> m r -> m r -> m r -- handling_ :: MonadCatch m => Lens' SomeException a -> m r -> m r -> m r -- handling_ :: MonadCatch m => Traversal' SomeException a -> m r -> m r -> m r -- handling_ :: MonadCatch m => Iso' SomeException a -> m r -> m r -> m r -- handling_ :: MonadCatch m => Getter SomeException a -> m r -> m r -> m r -- handling_ :: MonadCatch m => Fold SomeException a -> m r -> m r -> m r --handling_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m r -> m r -- | A variant of try that takes a Prism (or any Fold) -- to select which exceptions are caught (c.f. tryJust, -- catchJust). If the Exception does not match the -- predicate, it is re-thrown. -- --
-- trying :: MonadCatch m => Prism' SomeException a -> m r -> m (Either a r) -- trying :: MonadCatch m => Lens' SomeException a -> m r -> m (Either a r) -- trying :: MonadCatch m => Traversal' SomeException a -> m r -> m (Either a r) -- trying :: MonadCatch m => Iso' SomeException a -> m r -> m (Either a r) -- trying :: MonadCatch m => Getter SomeException a -> m r -> m (Either a r) -- trying :: MonadCatch m => Fold SomeException a -> m r -> m (Either a r) --trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r) -- | A version of trying that discards the specific exception -- thrown. -- --
-- trying_ :: MonadCatch m => Prism' SomeException a -> m r -> m (Maybe r) -- trying_ :: MonadCatch m => Lens' SomeException a -> m r -> m (Maybe r) -- trying_ :: MonadCatch m => Traversal' SomeException a -> m r -> m (Maybe r) -- trying_ :: MonadCatch m => Iso' SomeException a -> m r -> m (Maybe r) -- trying_ :: MonadCatch m => Getter SomeException a -> m r -> m (Maybe r) -- trying_ :: MonadCatch m => Fold SomeException a -> m r -> m (Maybe r) --trying_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Maybe r) -- | Throw an Exception described by a Prism. Exceptions may -- be thrown from purely functional code, but may only be caught within -- the IO Monad. -- --
-- throwing l ≡ reviews l throw ---- --
-- throwing :: Prism' SomeException t -> t -> r -- throwing :: Iso' SomeException t -> t -> r --throwing :: AReview SomeException b -> b -> r -- | A variant of throwing that can only be used within the -- IO Monad (or any other MonadCatch instance) to -- throw an Exception described by a Prism. -- -- Although throwingM has a type that is a specialization of the -- type of throwing, the two functions are subtly different: -- --
-- throwing l e `seq` x ≡ throwing e -- throwingM l e `seq` x ≡ x ---- -- The first example will cause the Exception e to be -- raised, whereas the second one won't. In fact, throwingM will -- only cause an Exception to be raised when it is used within the -- MonadCatch instance. The throwingM variant should be -- used in preference to throwing to raise an Exception -- within the Monad because it guarantees ordering with respect to -- other monadic operations, whereas throwing does not. -- --
-- throwingM l ≡ reviews l throw ---- --
-- throwingM :: MonadThrow m => Prism' SomeException t -> t -> m r -- throwingM :: MonadThrow m => Iso' SomeException t -> t -> m r --throwingM :: MonadThrow m => AReview SomeException b -> b -> m r -- | throwingTo raises an Exception specified by a -- Prism in the target thread. -- --
-- throwingTo thread l ≡ reviews l (throwTo thread) ---- --
-- throwingTo :: ThreadId -> Prism' SomeException t -> t -> m a -- throwingTo :: ThreadId -> Iso' SomeException t -> t -> m a --throwingTo :: MonadIO m => ThreadId -> AReview SomeException b -> b -> m () -- | This Setter can be used to purely map over the -- Exceptions an arbitrary expression might throw; it is a variant -- of mapException in the same way that mapped is a variant -- of fmap. -- --
-- 'mapException' ≡ 'over' 'mappedException' ---- -- This view that every Haskell expression can be regarded as carrying a -- bag of Exceptions is detailed in “A Semantics for Imprecise -- Exceptions” by Peyton Jones & al. at PLDI ’99. -- -- The following maps failed assertions to arithmetic overflow: -- --
-- >>> handling _Overflow (\_ -> return "caught") $ assert False (return "uncaught") & mappedException %~ \ (AssertionFailed _) -> Overflow -- "caught" --mappedException :: (Exception e, Exception e') => Setter s s e e' -- | This is a type restricted version of mappedException, which -- avoids the type ambiguity in the input Exception when using -- set. -- -- The following maps any exception to arithmetic overflow: -- --
-- >>> handling _Overflow (\_ -> return "caught") $ assert False (return "uncaught") & mappedException' .~ Overflow -- "caught" --mappedException' :: Exception e' => Setter s s SomeException e' -- | Traverse the strongly typed Exception contained in -- SomeException where the type of your function matches the -- desired Exception. -- --
-- exception :: (Applicative f, Exception a) -- => (a -> f a) -> SomeException -> f SomeException --exception :: Exception a => Prism' SomeException a -- | Both exceptions and Control.Exception provide a -- Handler type. -- -- This lets us write combinators to build handlers that are agnostic -- about the choice of which of these they use. class Handleable e (m :: * -> *) (h :: * -> *) | h -> e m where handler_ l = handler l . const handler :: (Handleable e m h, Typeable a) => Getting (First a) e a -> (a -> m r) -> h r handler_ :: (Handleable e m h, Typeable a) => Getting (First a) e a -> m r -> h r -- | Exceptions that occur in the IO Monad. An -- IOException records a more specific error type, a descriptive -- string and maybe the handle that was used when the error was flagged. -- -- Due to their richer structure relative to other exceptions, these have -- a more carefully overloaded signature. class AsIOException t _IOException :: AsIOException t => Prism' t IOException -- | Arithmetic exceptions. class AsArithException t _ArithException :: AsArithException t => Prism' t ArithException -- | Handle arithmetic _Overflow. -- --
-- _Overflow ≡ _ArithException . _Overflow ---- --
-- _Overflow :: Prism' ArithException ArithException -- _Overflow :: Prism' SomeException ArithException --_Overflow :: AsArithException t => Prism' t () -- | Handle arithmetic _Underflow. -- --
-- _Underflow ≡ _ArithException . _Underflow ---- --
-- _Underflow :: Prism' ArithException ArithException -- _Underflow :: Prism' SomeException ArithException --_Underflow :: AsArithException t => Prism' t () -- | Handle arithmetic loss of precision. -- --
-- _LossOfPrecision ≡ _ArithException . _LossOfPrecision ---- --
-- _LossOfPrecision :: Prism' ArithException ArithException -- _LossOfPrecision :: Prism' SomeException ArithException --_LossOfPrecision :: AsArithException t => Prism' t () -- | Handle division by zero. -- --
-- _DivideByZero ≡ _ArithException . _DivideByZero ---- --
-- _DivideByZero :: Prism' ArithException ArithException -- _DivideByZero :: Prism' SomeException ArithException --_DivideByZero :: AsArithException t => Prism' t () -- | Handle exceptional _Denormalized floating pure. -- --
-- _Denormal ≡ _ArithException . _Denormal ---- --
-- _Denormal :: Prism' ArithException ArithException -- _Denormal :: Prism' SomeException ArithException --_Denormal :: AsArithException t => Prism' t () -- | Added in base 4.6 in response to this libraries discussion: -- -- -- http://haskell.1045720.n5.nabble.com/Data-Ratio-and-exceptions-td5711246.html -- --
-- _RatioZeroDenominator ≡ _ArithException . _RatioZeroDenominator ---- --
-- _RatioZeroDenominator :: Prism' ArithException ArithException -- _RatioZeroDenominator :: Prism' SomeException ArithException --_RatioZeroDenominator :: AsArithException t => Prism' t () -- | Exceptions generated by array operations. class AsArrayException t _ArrayException :: AsArrayException t => Prism' t ArrayException -- | An attempt was made to index an array outside its declared bounds. -- --
-- _IndexOutOfBounds ≡ _ArrayException . _IndexOutOfBounds ---- --
-- _IndexOutOfBounds :: Prism' ArrayException String -- _IndexOutOfBounds :: Prism' SomeException String --_IndexOutOfBounds :: AsArrayException t => Prism' t String -- | An attempt was made to evaluate an element of an array that had not -- been initialized. -- --
-- _UndefinedElement ≡ _ArrayException . _UndefinedElement ---- --
-- _UndefinedElement :: Prism' ArrayException String -- _UndefinedElement :: Prism' SomeException String --_UndefinedElement :: AsArrayException t => Prism' t String -- | assert was applied to False. class AsAssertionFailed t _AssertionFailed :: AsAssertionFailed t => Prism' t String -- | Asynchronous exceptions. class AsAsyncException t _AsyncException :: AsAsyncException t => Prism' t AsyncException -- | The current thread's stack exceeded its limit. Since an -- Exception has been raised, the thread's stack will certainly be -- below its limit again, but the programmer should take remedial action -- immediately. -- --
-- _StackOverflow :: Prism' AsyncException () -- _StackOverflow :: Prism' SomeException () --_StackOverflow :: AsAsyncException t => Prism' t () -- | The program's heap is reaching its limit, and the program should take -- action to reduce the amount of live data it has. -- -- Notes: -- --
-- _HeapOverflow :: Prism' AsyncException () -- _HeapOverflow :: Prism' SomeException () --_HeapOverflow :: AsAsyncException t => Prism' t () -- | This Exception is raised by another thread calling -- killThread, or by the system if it needs to terminate the -- thread for some reason. -- --
-- _ThreadKilled :: Prism' AsyncException () -- _ThreadKilled :: Prism' SomeException () --_ThreadKilled :: AsAsyncException t => Prism' t () -- | This Exception is raised by default in the main thread of the -- program when the user requests to terminate the program via the usual -- mechanism(s) (e.g. Control-C in the console). -- --
-- _UserInterrupt :: Prism' AsyncException () -- _UserInterrupt :: Prism' SomeException () --_UserInterrupt :: AsAsyncException t => Prism' t () -- | Thrown when the runtime system detects that the computation is -- guaranteed not to terminate. Note that there is no guarantee that the -- runtime system will notice whether any given computation is guaranteed -- to terminate or not. class AsNonTermination t _NonTermination :: AsNonTermination t => Prism' t () -- | Thrown when the program attempts to call atomically, from the -- STM package, inside another call to atomically. class AsNestedAtomically t _NestedAtomically :: AsNestedAtomically t => Prism' t () -- | The thread is blocked on an MVar, but there are no other -- references to the MVar so it can't ever continue. class AsBlockedIndefinitelyOnMVar t _BlockedIndefinitelyOnMVar :: AsBlockedIndefinitelyOnMVar t => Prism' t () -- | The thread is waiting to retry an STM transaction, but there -- are no other references to any TVars involved, so it can't ever -- continue. class AsBlockedIndefinitelyOnSTM t _BlockedIndefinitelyOnSTM :: AsBlockedIndefinitelyOnSTM t => Prism' t () -- | There are no runnable threads, so the program is deadlocked. The -- Deadlock Exception is raised in the main thread only. class AsDeadlock t _Deadlock :: AsDeadlock t => Prism' t () -- | A class method without a definition (neither a default definition, nor -- a definition in the appropriate instance) was called. class AsNoMethodError t _NoMethodError :: AsNoMethodError t => Prism' t String -- | A pattern match failed. class AsPatternMatchFail t _PatternMatchFail :: AsPatternMatchFail t => Prism' t String -- | An uninitialised record field was used. class AsRecConError t _RecConError :: AsRecConError t => Prism' t String -- | A record selector was applied to a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. class AsRecSelError t _RecSelError :: AsRecSelError t => Prism' t String -- | A record update was performed on a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. class AsRecUpdError t _RecUpdError :: AsRecUpdError t => Prism' t String -- | This is thrown when the user calls error. class AsErrorCall t _ErrorCall :: AsErrorCall t => Prism' t String -- | This Exception is thrown by lens when the user somehow -- manages to rethrow an internal HandlingException. class AsHandlingException t _HandlingException :: AsHandlingException t => Prism' t () instance AsHandlingException SomeException instance AsHandlingException HandlingException instance AsErrorCall SomeException instance AsErrorCall ErrorCall instance AsRecUpdError SomeException instance AsRecUpdError RecUpdError instance AsRecSelError SomeException instance AsRecSelError RecSelError instance AsRecConError SomeException instance AsRecConError RecConError instance AsPatternMatchFail SomeException instance AsPatternMatchFail PatternMatchFail instance AsNoMethodError SomeException instance AsNoMethodError NoMethodError instance AsDeadlock SomeException instance AsDeadlock Deadlock instance AsBlockedIndefinitelyOnSTM SomeException instance AsBlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM instance AsBlockedIndefinitelyOnMVar SomeException instance AsBlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar instance AsNestedAtomically SomeException instance AsNestedAtomically NestedAtomically instance AsNonTermination SomeException instance AsNonTermination NonTermination instance AsAsyncException SomeException instance AsAsyncException AsyncException instance AsAssertionFailed SomeException instance AsAssertionFailed AssertionFailed instance AsArrayException SomeException instance AsArrayException ArrayException instance AsArithException SomeException instance AsArithException ArithException instance AsIOException SomeException instance AsIOException IOException module Data.Dynamic.Lens -- | Any Dynamic can be thrown as an Exception class AsDynamic t _Dynamic :: (AsDynamic t, Typeable a) => Prism' t a instance AsDynamic SomeException instance AsDynamic Dynamic -- | These prisms can be used with the combinators in -- Control.Exception.Lens. module System.Exit.Lens -- | Exit codes that a program can return with: class AsExitCode t _ExitCode :: AsExitCode t => Prism' t ExitCode -- | indicates program failure with an exit code. The exact interpretation -- of the code is operating-system dependent. In particular, some values -- may be prohibited (e.g. 0 on a POSIX-compliant system). -- --
-- _ExitFailure :: Prism' ExitCode Int -- _ExitFailure :: Prism' SomeException Int --_ExitFailure :: AsExitCode t => Prism' t Int -- | indicates successful termination; -- --
-- _ExitSuccess :: Prism' ExitCode () -- _ExitSuccess :: Prism' SomeException () --_ExitSuccess :: AsExitCode t => Prism' t () instance AsExitCode SomeException instance AsExitCode ExitCode