-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Lenses, Folds and Traversals -- -- This package comes "Batteries Included" with many useful lenses for -- the types commonly used from the Haskell Platform, and with tools for -- automatically generating lenses and isomorphisms for user-supplied -- data types. -- -- The combinators in Control.Lens provide a highly generic -- toolbox for composing families of getters, folds, isomorphisms, -- traversals, setters and lenses and their indexed variants. -- -- More information on the care and feeding of lenses, including a -- tutorial and motivation for their types can be found on the lens wiki. -- -- https://github.com/ekmett/lens/wiki -- -- A small game that manages its state using lenses can be found in the -- example folder. -- -- https://github.com/ekmett/lens/blob/master/examples/Pong.hs -- -- Lenses, Folds and Traversals -- -- The core of this hierarchy looks like: -- -- -- You can compose any two elements of the hierarchy above using (.) from -- the Prelude, and you can use any element of the hierarchy as any type -- it links to above it. -- -- The result is their lowest upper bound in the hierarchy (or an error -- if that bound doesn't exist). -- -- For instance: -- -- -- -- Minimizing Dependencies -- -- If you want to provide lenses and traversals for your own types in -- your own libraries, then you can do so without incurring a dependency -- on this (or any other) lens package at all. -- -- e.g. for a data type: -- --
--   data Foo a = Foo Int Int a
--   
-- -- You can define lenses such as -- --
--   -- bar :: Simple Lens (Foo a) Int
--   bar :: Functor f => (Int -> f Int) -> Foo a -> f Foo a
--   bar f (Foo a b c) = fmap (\a' -> Foo a' b c) (f a)
--   
-- --
--   -- baz :: Lens (Foo a) (Foo b) a b
--   quux :: Functor f => (a -> f b) -> Foo a -> f (Foo b)
--   quux f (Foo a b c) = fmap (Foo a b) (f c)
--   
-- -- without the need to use any type that isn't already defined in the -- Prelude. -- -- And you can define a traversal of multiple fields with -- Control.Applicative.Applicative: -- --
--   -- traverseBarAndBaz :: Simple Traversal (Foo a) Int
--   traverseBarAndBaz :: Applicative f => (Int -> f Int) -> Foo a -> f (Foo a)
--   traverseBarAndBaz f (Foo a b c) = Foo <$> f a <*> f b <*> pure c
--   
-- -- What is provided in this library is a number of stock lenses and -- traversals for common haskell types, a wide array of combinators for -- working them, and more exotic functionality, (e.g. getters, setters, -- indexed folds, isomorphisms). @package lens @version 2.4 module Control.Lens.Isomorphic -- | Used to provide overloading of isomorphism application -- -- This is a Category with a canonical mapping to it from the -- category of isomorphisms over Haskell types. class Category k => Isomorphic k isomorphic :: Isomorphic k => (a -> b) -> (b -> a) -> k a b isomap :: Isomorphic k => ((a -> b) -> c -> d) -> ((b -> a) -> d -> c) -> k a b -> k c d -- | A concrete data type for isomorphisms. -- -- This lets you place an isomorphism inside a container without using -- ImpredicativeTypes. data Isomorphism a b Isomorphism :: (a -> b) -> (b -> a) -> Isomorphism a b -- | Invert an isomorphism. -- -- Note to compose an isomorphism and receive an isomorphism in turn -- you'll need to use Category -- --
--   from (from l) = l
--   
-- -- If you imported . from Control.Category, then: -- --
--   from l . from r = from (r . l)
--   
from :: Isomorphic k => Isomorphism a b -> k b a -- | Convert from an Isomorphism back to any Isomorphic -- value. -- -- This is useful when you need to store an isomoprhism as a data type -- inside a container and later reconstitute it as an overloaded -- function. via :: Isomorphic k => Isomorphism a b -> k a b instance Typeable2 Isomorphism instance Isomorphic Isomorphism instance Category Isomorphism instance Isomorphic (->) -- | 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, unless you are coming up with a whole new kind of -- "Family" and need to add instances. module Control.Lens.Internal -- | The indexed store can be used to characterize a Lens and is -- used by clone data IndexedStore c d a IndexedStore :: (d -> a) -> c -> IndexedStore c d a -- | Used by Zoom to zoom into StateT newtype Focusing m c a Focusing :: m (c, a) -> Focusing m c a unfocusing :: Focusing m c a -> m (c, a) -- | Used by Zoom to zoom into RWST newtype FocusingWith w m c a FocusingWith :: m (c, a, w) -> FocusingWith w m c a unfocusingWith :: FocusingWith w m c a -> m (c, a, w) -- | Used by Zoom to zoom into WriterT. newtype FocusingPlus w k c a FocusingPlus :: k (c, w) a -> FocusingPlus w k c a unfocusingPlus :: FocusingPlus w k c a -> k (c, w) a -- | Used by Zoom to zoom into MaybeT or ListT newtype FocusingOn f k c a FocusingOn :: k (f c) a -> FocusingOn f k c a unfocusingOn :: FocusingOn f k c a -> k (f c) a -- | Used by Zoom to zoom into ErrorT newtype FocusingErr e k c a FocusingErr :: k (Err e c) a -> FocusingErr e k c a unfocusingErr :: FocusingErr e k c a -> k (Err e c) 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 -- | Used by Zoom to zoom into ErrorT newtype FocusingMay k c a FocusingMay :: k (May c) a -> FocusingMay k c a unfocusingMay :: FocusingMay k c a -> k (May c) a -- | Make a monoid out of Maybe for error handling newtype May a May :: Maybe a -> May a getMay :: May a -> Maybe a -- | Used internally by traverseOf_ and the like. newtype Traversed f Traversed :: f () -> Traversed f getTraversed :: Traversed f -> f () -- | Used internally by mapM_ and the like. newtype Sequenced m Sequenced :: m () -> Sequenced m getSequenced :: Sequenced m -> m () -- | Applicative composition of State Int with a -- Functor, used by elementOf, elementsOf, -- traverseElement, traverseElementsOf newtype AppliedState f a AppliedState :: (Int -> (f a, Int)) -> AppliedState f a runAppliedState :: AppliedState f a -> Int -> (f a, Int) -- | Used for minimumOf data Min a NoMin :: Min a Min :: a -> Min a -- | Obtain the minimum. getMin :: Min a -> Maybe a -- | Used for maximumOf data Max a NoMax :: Max a Max :: a -> Max a -- | Obtain the maximum getMax :: Max a -> Maybe a -- | Used to find the nth element of a Traversal. newtype ElementOf f a ElementOf :: (Int -> ElementOfResult f a) -> ElementOf f a getElementOf :: ElementOf f a -> Int -> ElementOfResult f a -- | The result of trying to find the nth element of a -- Traversal. data ElementOfResult f a Searching :: {-# UNPACK #-} !Int -> a -> ElementOfResult f a Found :: {-# UNPACK #-} !Int -> (f a) -> ElementOfResult f a NotFound :: String -> ElementOfResult f a -- | The Indexed Kleene Store comonad, aka the 'indexed cartesian -- store comonad' or an indexed FunList. -- -- This is used to characterize a Traversal. -- -- http://twanvl.nl/blog/haskell/non-regular1 data Kleene c d a Done :: a -> Kleene c d a More :: (Kleene c d (d -> a)) -> c -> Kleene c d a -- | Given an action to run for each matched pair, traverse a store. kleene :: Applicative f => (c -> f d) -> Kleene c d b -> f b -- | 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 s m c a EffectRWS :: (s -> m (c, s, w)) -> EffectRWS w s m c a getEffectRWS :: EffectRWS w s m c a -> s -> m (c, s, w) -- | Generalizing Const so we can apply simple Applicative -- transformations to it and so we can get nicer error messages -- -- A Gettable Functor ignores its argument, which it -- carries solely as a phantom type parameter. -- -- To ensure this, an instance of Gettable is required to satisfy: -- --
--   id = fmap f = coerce
--   
class Functor f => Gettable f coerce :: Gettable f => f a -> f b -- | Used instead of Const to report -- --
--   No instance of (Settable Accessor)
--   
-- -- when the user attempts to misuse a Setter as a Getter, -- rather than a monolithic unification error. newtype Accessor r a Accessor :: r -> Accessor r a runAccessor :: Accessor r a -> r -- | An Effective Functor ignores its argument and is -- isomorphic to a monad wrapped around a value. -- -- That said, the monad is possibly rather unrelated to any -- Applicative structure. class (Monad m, Gettable f) => Effective m r f | f -> m r effective :: (Effective m r f, Isomorphic k) => k (m r) (f a) -- | A convenient antonym that is used internally. ineffective :: Effective m r f => Isomorphic k => k (f a) (m r) -- | Anything Settable must be isomorphic to the Identity -- Functor. class Applicative f => Settable f untainted :: Settable f => f a -> a -- | Mutator is just a renamed Identity functor to give -- better error messages when someone attempts to use a getter as a -- setter. -- -- Most user code will never need to see this type. newtype Mutator a Mutator :: a -> Mutator a runMutator :: Mutator a -> a instance Applicative Mutator instance Functor Mutator instance Settable Mutator instance (Settable f, Settable g) => Settable (Compose f g) instance Settable f => Settable (Backwards f) instance Settable Identity instance Monad m => Effective m r (Effect m r) instance Effective m r f => Effective m (Dual r) (Backwards f) instance Effective Identity r (Accessor r) instance Monoid r => Applicative (Accessor r) instance Functor (Accessor r) instance Gettable (Accessor r) instance Gettable f => Gettable (ElementOf f) instance Gettable (EffectRWS w s m c) instance Gettable (Effect m r) instance (Functor f, Gettable g) => Gettable (Compose f g) instance Gettable f => Gettable (Backwards f) instance Gettable (Const r) instance (Monoid c, Monoid w, Monad m) => Applicative (EffectRWS w s m c) instance Functor (EffectRWS w s m c) instance (Monad m, Monoid r) => Applicative (Effect m r) instance (Monad m, Monoid r) => Monoid (Effect m r a) instance Functor (Effect m r) instance Applicative (Kleene c d) instance Functor (Kleene c d) instance Functor f => Applicative (ElementOf f) instance Functor f => Functor (ElementOf f) instance Functor f => Functor (ElementOfResult f) instance Ord a => Monoid (Max a) instance Ord a => Monoid (Min a) instance Monad m => Monoid (Sequenced m) instance Applicative f => Monoid (Traversed f) instance Applicative f => Applicative (AppliedState f) instance Functor f => Functor (AppliedState f) instance Functor (IndexedStore c d) instance Applicative (k (Err e c)) => Applicative (FocusingErr e k c) instance Functor (k (Err e c)) => Functor (FocusingErr e k c) instance Monoid a => Monoid (Err e a) instance Applicative (k (May c)) => Applicative (FocusingMay k c) instance Functor (k (May c)) => Functor (FocusingMay k c) instance Monoid a => Monoid (May a) instance Applicative (k (f c)) => Applicative (FocusingOn f k c) instance Functor (k (f c)) => Functor (FocusingOn f k c) instance (Monoid w, Applicative (k (c, w))) => Applicative (FocusingPlus w k c) instance Functor (k (c, w)) => Functor (FocusingPlus w k c) instance (Monad m, Monoid c, Monoid w) => Applicative (FocusingWith w m c) instance Monad m => Functor (FocusingWith w m c) instance (Monad m, Monoid c) => Applicative (Focusing m c) instance Monad m => Functor (Focusing m c) -- | Combinators for working with Indexed functions. module Control.Lens.Indexed -- | Permit overloading of function application for things that also admit -- a notion of a key or index. -- -- Provides overloading for Indexed functions. class Indexed i k index :: Indexed i k => ((i -> a) -> b) -> k a b -- | Type alias for passing around polymorphic Indexed functions -- that can be called withIndex or directly as a function type Indexable i a b = forall k. Indexed i k => k a b -- | A function with access to a index. This constructor may be useful when -- you need to store a Indexable in a container to avoid -- ImpredicativeTypes. newtype Index i a b Index :: ((i -> a) -> b) -> Index i a b withIndex :: Index i a b -> (i -> a) -> b -- | Composition of Indexed functions -- -- Mnemonically, the @ and @ points to the fact that we -- want to preserve the indices. (<.>) :: Indexed (i, j) k => Index i b c -> Index j a b -> k a c -- | Compose an Indexed function with a non-indexed function. -- -- Mnemonically, the < points to the index we want to -- preserve. (<.) :: Indexed i k => Index i b c -> (a -> b) -> k a c -- | Compose a non-indexed function with an Indexed function. -- -- Mnemonically, the > points to the index we want to -- preserve. (.>) :: Indexed i k => (b -> c) -> Index i a b -> k a c -- | Composition of Indexed functions with a user supplied function -- for combining indexs icompose :: Indexed k r => (i -> j -> k) -> Index i b c -> Index j a b -> r a c -- | Remap the index. reindex :: Indexed j k => (i -> j) -> Index i a b -> k a b instance i ~ j => Indexed i (Index j) instance Indexed i (->) module Control.Lens.IndexedGetter -- | Every IndexedGetter is a valid IndexedFold and -- Getter. type IndexedGetter i a c = forall k f. (Indexed i k, Gettable f) => k (c -> f c) (a -> f a) -- | Used to consume an IndexedFold. type IndexedGetting i m a c = Index i (c -> Accessor m c) (a -> Accessor m a) module Control.Lens.IndexedFold -- | Every IndexedFold is a valid Fold. type IndexedFold i a c = forall k f. (Indexed i k, Applicative f, Gettable f) => k (c -> f c) (a -> f a) -- | Fold an IndexedFold or IndexedTraversal by mapping -- indices and values to an arbitrary Monoid with access to the -- index 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 a c          -> (i -> c -> m) -> a -> m
--   ifoldMapOf :: Monoid m => IndexedFold i a c            -> (i -> c -> m) -> a -> m
--   ifoldMapOf ::             SimpleIndexedLens i a c      -> (i -> c -> m) -> a -> m
--   ifoldMapOf :: Monoid m => SimpleIndexedTraversal i a c -> (i -> c -> m) -> a -> m
--   
ifoldMapOf :: IndexedGetting i m a c -> (i -> c -> m) -> a -> m -- | Right-associative fold of parts of a structure that are viewed through -- an IndexedFold or IndexedTraversal with access to the -- index 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 a c          -> (i -> c -> e -> e) -> e -> a -> e
--   ifoldrOf :: IndexedFold i a c            -> (i -> c -> e -> e) -> e -> a -> e
--   ifoldrOf :: SimpleIndexedLens i a c      -> (i -> c -> e -> e) -> e -> a -> e
--   ifoldrOf :: SimpleIndexedTraversal i a c -> (i -> c -> e -> e) -> e -> a -> e
--   
ifoldrOf :: IndexedGetting i (Endo e) a c -> (i -> c -> e -> e) -> e -> a -> e -- | Left-associative fold of the parts of a structure that are viewed -- through an IndexedFold or IndexedTraversal with access -- to the index 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 a c          -> (i -> e -> c -> e) -> e -> a -> e
--   ifoldlOf :: IndexedFold i a c            -> (i -> e -> c -> e) -> e -> a -> e
--   ifoldlOf :: SimpleIndexedLens i a c      -> (i -> e -> c -> e) -> e -> a -> e
--   ifoldlOf :: SimpleIndexedTraversal i a c -> (i -> e -> c -> e) -> e -> a -> e
--   
ifoldlOf :: IndexedGetting i (Dual (Endo e)) a c -> (i -> e -> c -> e) -> e -> a -> e -- | Return whether or not any element viewed through an IndexedFold -- or IndexedTraversal satisfy a predicate, with access to the -- index 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 a c          -> (i -> c -> Bool) -> a -> Bool
--   ianyOf :: IndexedFold i a c            -> (i -> c -> Bool) -> a -> Bool
--   ianyOf :: SimpleIndexedLens i a c      -> (i -> c -> Bool) -> a -> Bool
--   ianyOf :: SimpleIndexedTraversal i a c -> (i -> c -> Bool) -> a -> Bool
--   
ianyOf :: IndexedGetting i Any a c -> (i -> c -> Bool) -> a -> Bool -- | Return whether or not all elements viewed through an -- IndexedFold or IndexedTraversal satisfy a predicate, -- with access to the index 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 a c          -> (i -> c -> Bool) -> a -> Bool
--   iallOf :: IndexedFold i a c            -> (i -> c -> Bool) -> a -> Bool
--   iallOf :: SimpleIndexedLens i a c      -> (i -> c -> Bool) -> a -> Bool
--   iallOf :: SimpleIndexedTraversal i a c -> (i -> c -> Bool) -> a -> Bool
--   
iallOf :: IndexedGetting i All a c -> (i -> c -> Bool) -> a -> Bool -- | Traverse the targets of an IndexedFold or -- IndexedTraversal with access to the index 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 a c          -> (i -> c -> f e) -> a -> f ()
--   itraverseOf_ :: Applicative f => IndexedFold i a c            -> (i -> c -> f e) -> a -> f ()
--   itraverseOf_ :: Functor f     => SimpleIndexedLens i a c      -> (i -> c -> f e) -> a -> f ()
--   itraverseOf_ :: Applicative f => SimpleIndexedTraversal i a c -> (i -> c -> f e) -> a -> f ()
--   
itraverseOf_ :: Functor f => IndexedGetting i (Traversed f) a c -> (i -> c -> f e) -> a -> 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 a c          -> a -> (i -> c -> f e) -> f ()
--   iforOf_ :: Applicative f => IndexedFold i a c            -> a -> (i -> c -> f e) -> f ()
--   iforOf_ :: Functor f     => SimpleIndexedLens i a c      -> a -> (i -> c -> f e) -> f ()
--   iforOf_ :: Applicative f => SimpleIndexedTraversal i a c -> a -> (i -> c -> f e) -> f ()
--   
iforOf_ :: Functor f => IndexedGetting i (Traversed f) a c -> a -> (i -> c -> f e) -> 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 a c          -> (i -> c -> m e) -> a -> m ()
--   imapMOf_ :: Monad m => IndexedFold i a c            -> (i -> c -> m e) -> a -> m ()
--   imapMOf_ :: Monad m => SimpleIndexedLens i a c      -> (i -> c -> m e) -> a -> m ()
--   imapMOf_ :: Monad m => SimpleIndexedTraversal i a c -> (i -> c -> m e) -> a -> m ()
--   
imapMOf_ :: Monad m => IndexedGetting i (Sequenced m) a c -> (i -> c -> m e) -> 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). -- --
--   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 a c          -> a -> (i -> c -> m e) -> m ()
--   iforMOf_ :: Monad m => IndexedFold i a c            -> a -> (i -> c -> m e) -> m ()
--   iforMOf_ :: Monad m => SimpleIndexedLens i a c      -> a -> (i -> c -> m e) -> m ()
--   iforMOf_ :: Monad m => SimpleIndexedTraversal i a c -> a -> (i -> c -> m e) -> m ()
--   
iforMOf_ :: Monad m => IndexedGetting i (Sequenced m) a c -> a -> (i -> c -> m e) -> 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 = iconcatMapMOf l . const
--   
-- --
--   iconcatMapOf :: IndexedGetter i a c          -> (i -> c -> [e]) -> a -> [e]
--   iconcatMapOf :: IndexedFold i a c            -> (i -> c -> [e]) -> a -> [e]
--   iconcatMapOf :: SimpleIndexedLens i a c      -> (i -> c -> [e]) -> a -> [e]
--   iconcatMapOf :: SimpleIndexedTraversal i a c -> (i -> c -> [e]) -> a -> [e]
--   
iconcatMapOf :: IndexedGetting i [e] a c -> (i -> c -> [e]) -> a -> [e] -- | The findOf 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 = ifoldOf l . const
--   
-- --
--   ifindOf :: IndexedGetter a c          -> (i -> c -> Bool) -> a -> Maybe (i, c)
--   ifindOf :: IndexedFold a c            -> (i -> c -> Bool) -> a -> Maybe (i, c)
--   ifindOf :: SimpleIndexedLens a c      -> (i -> c -> Bool) -> a -> Maybe (i, c)
--   ifindOf :: SimpleIndexedTraversal a c -> (i -> c -> Bool) -> a -> Maybe (i, c)
--   
ifindOf :: IndexedGetting i (First (i, c)) a c -> (i -> c -> Bool) -> a -> Maybe (i, c) -- | 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 a c          -> (i -> c -> e -> e) -> e -> a -> e
--   ifoldrOf' :: IndexedFold i a c            -> (i -> c -> e -> e) -> e -> a -> e
--   ifoldrOf' :: SimpleIndexedLens i a c      -> (i -> c -> e -> e) -> e -> a -> e
--   ifoldrOf' :: SimpleIndexedTraversal i a c -> (i -> c -> e -> e) -> e -> a -> e
--   
ifoldrOf' :: IndexedGetting i (Dual (Endo (e -> e))) a c -> (i -> c -> e -> e) -> e -> a -> e -- | 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 a c            -> (i -> e -> c -> e) -> e -> a -> e
--   ifoldlOf' :: IndexedFold i a c              -> (i -> e -> c -> e) -> e -> a -> e
--   ifoldlOf' :: SimpleIndexedLens i a c        -> (i -> e -> c -> e) -> e -> a -> e
--   ifoldlOf' :: SimpleIndexedTraversal i a c   -> (i -> e -> c -> e) -> e -> a -> e
--   
ifoldlOf' :: IndexedGetting i (Endo (e -> e)) a c -> (i -> e -> c -> e) -> e -> a -> e -- | 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 a c          -> (i -> c -> e -> m e) -> e -> a -> e
--   ifoldrMOf :: Monad m => IndexedFold i a c            -> (i -> c -> e -> m e) -> e -> a -> e
--   ifoldrMOf :: Monad m => SimpleIndexedLens i a c      -> (i -> c -> e -> m e) -> e -> a -> e
--   ifoldrMOf :: Monad m => SimpleIndexedTraversal i a c -> (i -> c -> e -> m e) -> e -> a -> e
--   
ifoldrMOf :: Monad m => IndexedGetting i (Dual (Endo (e -> m e))) a c -> (i -> c -> e -> m e) -> e -> a -> m e -- | 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
--   
-- --
--   ifoldlOf' :: Monad m => IndexedGetter i a c            -> (i -> e -> c -> m e) -> e -> a -> e
--   ifoldlOf' :: Monad m => IndexedFold i a c              -> (i -> e -> c -> m e) -> e -> a -> e
--   ifoldlOf' :: Monad m => SimpleIndexedLens i a c        -> (i -> e -> c -> m e) -> e -> a -> e
--   ifoldlOf' :: Monad m => SimpleIndexedTraversal i a c   -> (i -> e -> c -> m e) -> e -> a -> e
--   
ifoldlMOf :: Monad m => IndexedGetting i (Endo (e -> m e)) a c -> (i -> e -> c -> m e) -> e -> a -> m e -- | 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 fst . itoListOf l
--   
-- --
--   itoListOf :: IndexedGetter i a c          -> a -> [(i,c)]
--   itoListOf :: IndexedFold i a c            -> a -> [(i,c)]
--   itoListOf :: SimpleIndexedLens i a c      -> a -> [(i,c)]
--   itoListOf :: SimpleIndexedTraversal i a c -> a -> [(i,c)]
--   
itoListOf :: IndexedGetting i [(i, c)] a c -> a -> [(i, c)] -- | Obtain an IndexedFold by filtering a IndexedLens, -- IndexedGetter, IndexedFold or IndexedTraversal. ifiltered :: (Gettable f, Applicative f, Indexed i k) => (i -> c -> Bool) -> Index i (c -> f c) (a -> f a) -> k (c -> f c) (a -> f a) -- | Obtain an IndexedFold by taking elements from another -- IndexedFold, IndexedLens, IndexedGetter or -- IndexedTraversal while a predicate holds. itakingWhile :: (Gettable f, Applicative f, Indexed i k) => (i -> c -> Bool) -> IndexedGetting i (Endo (f a)) a c -> k (c -> f c) (a -> f a) -- | Obtain an IndexedFold by dropping elements from another -- IndexedFold, IndexedLens, IndexedGetter or -- IndexedTraversal while a predicate holds. idroppingWhile :: (Gettable f, Applicative f, Indexed i k) => (i -> c -> Bool) -> IndexedGetting i (Endo (f a)) a c -> k (c -> f c) (a -> f a) module Control.Lens.Action -- | An Action is a Getter enriched with access to a -- Monad for side-effects. -- -- Every Getter can be used as an Action -- -- You can compose an Action with another Action using -- (.) from the Prelude. type Action m a c = forall f r. Effective m r f => (c -> f c) -> a -> f a -- | Construct an Action from a monadic side-effect act :: Monad m => (a -> m c) -> Action m a c -- | A self-running Action, analogous to join. -- --
--   acts = act id
--   
-- --
--   >>> import Control.Lens
--   
-- --
--   >>> (1,"hello")^!_2.acts.to succ
--   "ifmmp"
--   
acts :: Action m (m a) a -- | Perform an Action. -- --
--   perform = flip (^!)
--   
perform :: Monad m => Acting m c a c -> a -> m c -- | Apply a Monad transformer to an Action. liftAct :: (MonadTrans t, Monad m) => Acting m c a c -> Action (t m) a c -- | Perform an Action -- --
--   >>> import Control.Lens
--   
-- --
--   >>> ["hello","world"]^!folded.act putStrLn
--   hello
--   world
--   
(^!) :: Monad m => a -> Acting m c a c -> m c -- | A MonadicFold is a Fold enriched with access to a -- Monad for side-effects. -- -- Every Fold can be used as a MonadicFold, that simply -- ignores the access to the Monad. -- -- You can compose a MonadicFold with another MonadicFold -- using (.) from the Prelude. type MonadicFold m a c = forall f r. (Effective m r f, Applicative f) => (c -> f c) -> a -> f a -- | Used to evaluate an Action. type Acting m r a c = (c -> Effect m r c) -> a -> Effect m r a -- | A Setter a b c d 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 => (c -- -> d) -> f c -> f d we monomorphize the type to obtain -- (c -> d) -> a -> b and then decorate it with -- Identity to obtain -- --
--   type Setter a b c d = (c -> Identity d) -> a -> Identity b
--   
-- -- 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 Lens-like law that can apply to a Setter -- l is that -- --
--   set l c (set l b a) = set l c 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 an 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. type Setter a b c d = forall f. Settable f => (c -> f d) -> a -> f b -- | Build a 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: -- --
--   sets . over = id
--   over . sets = id
--   
-- -- Another way to view sets is that it takes a "semantic editor -- combinator" and transforms it into a Setter. sets :: ((c -> d) -> a -> b) -> Setter a b c d -- | This setter can be used to map over all of the values in a -- Functor. -- --
--   fmap = over mapped
--   fmapDefault = over traverse
--   (<$) = set mapped
--   
mapped :: Functor f => Setter (f a) (f b) 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
--   
-- -- Another way to view over is to say that it transformers a -- Setter into a "semantic editor combinator". -- --
--   over :: Setter a b c d -> (c -> d) -> a -> b
--   
over :: Setting a b c d -> (c -> d) -> a -> b -- | Modify the target of a Lens or all the targets of a -- Setter or Traversal with a function. This is an alias -- for over that is provided for consistency. -- --
--   mapOf = over
--   fmap = mapOf mapped
--   fmapDefault = mapOf traverse
--   sets . mapOf = id
--   mapOf . sets = id
--   
-- --
--   mapOf :: Setter a b c d      -> (c -> d) -> a -> b
--   mapOf :: Iso a b c d         -> (c -> d) -> a -> b
--   mapOf :: Lens a b c d        -> (c -> d) -> a -> b
--   mapOf :: Traversal a b c d   -> (c -> d) -> a -> b
--   
mapOf :: Setting a b c d -> (c -> d) -> a -> b -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal with a constant value. -- --
--   (<$) = set mapped
--   
-- --
--   >>> import Control.Lens
--   
--   >>> 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 a b c d    -> d -> a -> b
--   set :: Iso a b c d       -> d -> a -> b
--   set :: Lens a b c d      -> d -> a -> b
--   set :: Traversal a b c d -> d -> a -> b
--   
set :: Setting a b c d -> d -> a -> b -- | 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
--   
-- --
--   >>> import Control.Lens
--   
--   >>> _1 .~ "hello" $ (42,"world")
--   ("hello","world")
--   
-- --
--   (.~) :: Setter a b c d    -> d -> a -> b
--   (.~) :: Iso a b c d       -> d -> a -> b
--   (.~) :: Lens a b c d      -> d -> a -> b
--   (.~) :: Traversal a b c d -> d -> a -> b
--   
(.~) :: Setting a b c d -> d -> a -> b -- | 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
--   
-- --
--   >>> import Control.Lens
--   
--   >>> _2 %~ length $ (1,"hello")
--   (1,5)
--   
-- --
--   (%~) :: Setter a b c d    -> (c -> d) -> a -> b
--   (%~) :: Iso a b c d       -> (c -> d) -> a -> b
--   (%~) :: Lens a b c d      -> (c -> d) -> a -> b
--   (%~) :: Traversal a b c d -> (c -> d) -> a -> b
--   
(%~) :: Setting a b c d -> (c -> d) -> a -> b -- | Increment the target(s) of a numerically valued Lens, -- Setter or Traversal -- --
--   >>> import Control.Lens
--   
--   >>> _1 +~ 1 $ (1,2)
--   (2,2)
--   
-- --
--   (+~) :: Num c => Setter a b c c -> c -> a -> b
--   (+~) :: Num c => Iso a b c c -> c -> a -> b
--   (+~) :: Num c => Lens a b c c -> c -> a -> b
--   (+~) :: Num c => Traversal a b c c -> c -> a -> b
--   
(+~) :: Num c => Setting a b c c -> c -> a -> b -- | Decrement the target(s) of a numerically valued Lens, -- Iso, Setter or Traversal -- --
--   >>> import Control.Lens
--   
--   >>> _1 -~ 2 $ (1,2)
--   (-1,2)
--   
-- --
--   (-~) :: Num c => Setter a b c c -> c -> a -> b
--   (-~) :: Num c => Iso a b c c -> c -> a -> b
--   (-~) :: Num c => Lens a b c c -> c -> a -> b
--   (-~) :: Num c => Traversal a b c c -> c -> a -> b
--   
(-~) :: Num c => Setting a b c c -> c -> a -> b -- | Multiply the target(s) of a numerically valued Lens, -- Iso, Setter or Traversal -- --
--   >>> import Control.Lens
--   
--   >>> _2 *~ 4 $ (1,2)
--   (1,8)
--   
-- --
--   (*~) :: Num c => Setter a b c c -> c -> a -> b
--   (*~) :: Num c => Iso a b c c -> c -> a -> b
--   (*~) :: Num c => Lens a b c c -> c -> a -> b
--   (*~) :: Num c => Traversal a b c c -> c -> a -> b
--   
(*~) :: Num c => Setting a b c c -> c -> a -> b -- | Divide the target(s) of a numerically valued Lens, Iso, -- Setter or Traversal -- --
--   (~) :: Fractional c => Setter a b c c -> c -> a -> b
--   (~) :: Fractional c => Iso a b c c -> c -> a -> b
--   (~) :: Fractional c => Lens a b c c -> c -> a -> b
--   (~) :: Fractional c => Traversal a b c c -> c -> a -> b
--   
(//~) :: Fractional c => Setting a b c c -> c -> a -> b -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to a non-negative integral power -- --
--   >>> import Control.Lens
--   
--   >>> _2 ^~ 2 $ (1,3)
--   (1,9)
--   
(^~) :: (Num c, Integral e) => Setting a b c c -> e -> a -> b -- | Raise the target(s) of a fractionally valued Lens, -- Setter or Traversal to an integral power -- --
--   >>> import Control.Lens
--   
--   >>> _2 ^^~ (-1) $ (1,2)
--   (1,0.5)
--   
-- --
--   (^^~) :: (Fractional c, Integral e) => Setter a b c c -> e -> a -> b
--   (^^~) :: (Fractional c, Integral e) => Iso a b c c -> e -> a -> b
--   (^^~) :: (Fractional c, Integral e) => Lens a b c c -> e -> a -> b
--   (^^~) :: (Fractional c, Integral e) => Traversal a b c c -> e -> a -> b
--   
(^^~) :: (Fractional c, Integral e) => Setting a b c c -> e -> a -> b -- | Raise the target(s) of a floating-point valued Lens, -- Setter or Traversal to an arbitrary power. -- --
--   >>> import Control.Lens
--   
--   >>> _2 **~ pi $ (1,3)
--   (1,31.54428070019754)
--   
-- --
--   (**~) :: Floating c => Setter a b c c -> c -> a -> b
--   (**~) :: Floating c => Iso a b c c -> c -> a -> b
--   (**~) :: Floating c => Lens a b c c -> c -> a -> b
--   (**~) :: Floating c => Traversal a b c c -> c -> a -> b
--   
(**~) :: Floating c => Setting a b c c -> c -> a -> b -- | Logically || the target(s) of a Bool-valued Lens -- or Setter -- --
--   >>> :m + Control.Lens Data.Pair.Lens
--   
-- --
--   >>> both ||~ True $ (False,True)
--   (True,True)
--   
-- --
--   >>> both ||~ False $ (False,True)
--   (False,True)
--   
-- --
--   (||~):: Setter a b Bool Bool -> Bool -> a -> b
--   (||~):: Iso a b Bool Bool -> Bool -> a -> b
--   (||~):: Lens a b Bool Bool -> Bool -> a -> b
--   (||~):: Traversal a b Bool Bool -> Bool -> a -> b
--   
(||~) :: Setting a b Bool Bool -> Bool -> a -> b -- | Logically && the target(s) of a Bool-valued -- Lens or Setter -- --
--   >>> :m + Control.Lens Data.Pair.Lens
--   
-- --
--   >>> both &&~ True $ (False, True)
--   (False,True)
--   
-- --
--   >>> both &&~ False $ (False, True)
--   (False,False)
--   
-- --
--   (&&~):: Setter a b Bool Bool -> Bool -> a -> b
--   (&&~):: Iso a b Bool Bool -> Bool -> a -> b
--   (&&~):: Lens a b Bool Bool -> Bool -> a -> b
--   (&&~):: Traversal a b Bool Bool -> Bool -> a -> b
--   
(&&~) :: Setting a b Bool Bool -> Bool -> a -> b -- | Set 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. -- --
--   (<.~) :: Setter a b c d    -> d -> a -> (d, b)
--   (<.~) :: Iso a b c d       -> d -> a -> (d, b)
--   (<.~) :: Lens a b c d      -> d -> a -> (d, b)
--   (<.~) :: Traversal a b c d -> d -> a -> (d, b)
--   
(<.~) :: Setting a b c d -> d -> a -> (d, b) -- | 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. -- --
--   (.=) :: MonadState a m => Iso a a c d             -> d -> m ()
--   (.=) :: MonadState a m => Lens a a c d            -> d -> m ()
--   (.=) :: MonadState a m => Traversal a a c d       -> d -> m ()
--   (.=) :: MonadState a m => Setter a a c d          -> d -> m ()
--   
-- -- It puts the state in the monad or it gets the hose again. (.=) :: MonadState a m => Setting a a c d -> d -> m () -- | Map over the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state. -- --
--   (%=) :: MonadState a m => Iso a a c d             -> (c -> d) -> m ()
--   (%=) :: MonadState a m => Lens a a c d            -> (c -> d) -> m ()
--   (%=) :: MonadState a m => Traversal a a c d       -> (c -> d) -> m ()
--   (%=) :: MonadState a m => Setter a a c d          -> (c -> d) -> m ()
--   
(%=) :: MonadState a m => Setting a a c d -> (c -> d) -> m () -- | Modify the target(s) of a Simple Lens, Iso, -- Setter or Traversal by adding a value -- -- Example: -- --
--   fresh :: MonadState Int m => m Int
--   fresh = do
--     id += 1
--     use id
--   
-- --
--   (+=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()
--   (+=) :: (MonadState a m, Num b) => Simple Iso a b -> b -> m ()
--   (+=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m ()
--   (+=) :: (MonadState a m, Num b) => Simple Traversal a b -> b -> m ()
--   
(+=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m () -- | Modify the target(s) of a Simple Lens, Iso, -- Setter or Traversal by subtracting a value -- --
--   (-=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()
--   (-=) :: (MonadState a m, Num b) => Simple Iso a b -> b -> m ()
--   (-=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m ()
--   (-=) :: (MonadState a m, Num b) => Simple Traversal a b -> b -> m ()
--   
(-=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m () -- | Modify the target(s) of a Simple Lens, Iso, -- Setter or Traversal by multiplying by value. -- --
--   ballSpeed . both *= speedMultiplier
--   
-- --
--   (*=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()
--   (*=) :: (MonadState a m, Num b) => Simple Iso a b -> b -> m ()
--   (*=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m ()
--   (*=) :: (MonadState a m, Num b) => Simple Traversal a b -> b -> m ()
--   
(*=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m () -- | Modify the target(s) of a Simple Lens, Iso, -- Setter or Traversal by dividing by a value. -- --
--   (=) :: (MonadState a m, Fractional b) => Simple Setter a b -> b -> m ()
--   (=) :: (MonadState a m, Fractional b) => Simple Iso a b -> b -> m ()
--   (=) :: (MonadState a m, Fractional b) => Simple Lens a b -> b -> m ()
--   (=) :: (MonadState a m, Fractional b) => Simple Traversal a b -> b -> m ()
--   
(//=) :: (MonadState a m, Fractional b) => SimpleSetting a b -> b -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to a non-negative integral power. -- --
--   (^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Setter a b -> c -> m ()
--   (^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Iso a b -> c -> m ()
--   (^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Lens a b -> c -> m ()
--   (^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Traversal a b -> c -> m ()
--   
(^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to an integral power. -- --
--   (^^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Setter a b -> c -> m ()
--   (^^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Iso a b -> c -> m ()
--   (^^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Lens a b -> c -> m ()
--   (^^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Traversal a b -> c -> m ()
--   
(^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m () -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to an arbitrary power -- --
--   (**=) ::  (MonadState a m, Floating b) => Simple Setter a b -> b -> m ()
--   (**=) ::  (MonadState a m, Floating b) => Simple Iso a b -> b -> m ()
--   (**=) ::  (MonadState a m, Floating b) => Simple Lens a b -> b -> m ()
--   (**=) ::  (MonadState a m, Floating b) => Simple Traversal a b -> b -> m ()
--   
(**=) :: (MonadState a m, Floating b) => SimpleSetting a b -> b -> m () -- | Modify the target(s) of a Simple Lens, 'Iso, -- Setter or Traversal by taking their logical || -- with a value -- --
--   (||=):: MonadState a m => Simple Setter a Bool -> Bool -> m ()
--   (||=):: MonadState a m => Simple Iso a Bool -> Bool -> m ()
--   (||=):: MonadState a m => Simple Lens a Bool -> Bool -> m ()
--   (||=):: MonadState a m => Simple Traversal a Bool -> Bool -> m ()
--   
(||=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m () -- | Modify the target(s) of a Simple Lens, Iso, -- Setter or Traversal by taking their logical -- && with a value -- --
--   (&&=):: MonadState a m => Simple Setter a Bool -> Bool -> m ()
--   (&&=):: MonadState a m => Simple Iso a Bool -> Bool -> m ()
--   (&&=):: MonadState a m => Simple Lens a Bool -> Bool -> m ()
--   (&&=):: MonadState a m => Simple Traversal a Bool -> Bool -> m ()
--   
(&&=) :: MonadState a m => SimpleSetting a 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 a m => Setter a a c d -> d -> m d
--   (<.=) :: MonadState a m => Iso a a c d -> d -> m d
--   (<.=) :: MonadState a m => Lens a a c d -> d -> m d
--   (<.=) :: MonadState a m => Traversal a a c d -> d -> m d
--   
(<.=) :: MonadState a m => Setting a a c d -> d -> m d -- | Run a monadic action, and set all of the targets of a Lens, -- Setter or Traversal to its result. -- --
--   (<~) :: MonadState a m => Iso a a c d       -> m d -> m ()
--   (<~) :: MonadState a m => Lens a a c d      -> m d -> m ()
--   (<~) :: MonadState a m => Traversal a a c d -> m d -> m ()
--   (<~) :: MonadState a m => Setter a a c d    -> m d -> 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 a m => Setting a a c d -> m d -> m () -- | 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. -- -- By choosing Mutator rather than Identity, we get nicer -- error messages. type Setting a b c d = (c -> Mutator d) -> a -> Mutator b -- | This is a useful alias for use when consuming a SimpleSetter. -- -- Most user code will never have to use this type. -- --
--   type SimpleSetting m = Simple Setting
--   
type SimpleSetting a b = Setting a a b b -- | A Simple 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 :: SimpleSetter Text Char
--   
-- --
--   type SimpleSetter = Simple Setter
--   
type SimpleSetter a b = Setter a a b b -- | A Getter a c is just any function (a -> -- c), which we've flipped into continuation passing style, (c -- -> r) -> a -> r and decorated with Accessor to -- obtain: -- --
--   type Getting r a c = (c -> Accessor r c) -> a -> Accessor r a
--   
-- -- If we restrict access to knowledge about the type r and can -- work for any d and b, we could get: -- --
--   type Getter a c = forall r. Getting r a c
--   
-- -- But we actually hide the use of Accessor behind a class -- Gettable to error messages from type class resolution rather -- than at unification time, where they are much uglier. -- --
--   type Getter a c = forall f. Gettable f => (c -> f c) -> a -> f a
--   
-- -- 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 lens-like 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 (a -> c). -- -- Moreover, a Getter can be used directly as a Fold, since -- it just ignores the Applicative. type Getter a c = forall f. Gettable f => (c -> f c) -> a -> f a -- | 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 b -- and d parameters. -- -- If a function accepts a Getting r a c, 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 a c = (c -> Accessor r c) -> a -> Accessor r a -- | Build a Getter from an arbitrary Haskell function. -- --
--   to f . to g = to (g . f)
--   
-- --
--   a ^. to f = f a
--   
-- --
--   >>> import Control.Lens
--   
--   >>> (0, -5)^._2.to abs
--   5
--   
to :: (a -> c) -> Getter a c -- | 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 (.) -- --
--   >>> :m + Data.Complex Control.Lens
--   
--   >>> ((0, 1 :+ 2), 3)^._1._2.to magnitude
--   2.23606797749979
--   
-- --
--   (^.) ::             a -> Getter a c             -> c
--   (^.) :: Monoid m => a -> Fold a m               -> m
--   (^.) ::             a -> Simple Iso a c         -> c
--   (^.) ::             a -> Simple Lens a c        -> c
--   (^.) :: Monoid m => a -> Simple Traversal a m   -> m
--   
(^.) :: a -> Getting c a c -> c -- | 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 values. -- -- This is the same operation as view, only infix. -- --
--   >>> import Control.Lens
--   
--   >>> _2 ^$ (1, "hello")
--   "hello"
--   
-- --
--   (^$) ::             Getter a c             -> a -> c
--   (^$) :: Monoid m => Fold a m               -> a -> m
--   (^$) ::             Simple Iso a c         -> a -> c
--   (^$) ::             Simple Lens a c        -> a -> c
--   (^$) :: Monoid m => Simple Traversal a m   -> a -> m
--   
(^$) :: Getting c a c -> a -> c -- | 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 values. -- --
--   view . to = id
--   
-- --
--   >>> import Control.Lens
--   
--   >>> view _2 (1,"hello")
--   "hello"
--   
-- -- It may be useful to think of view as having these more -- restrictive signatures: -- --
--   view ::             Getter a c             -> a -> c
--   view :: Monoid m => Fold a m               -> a -> m
--   view ::             Simple Iso a c         -> a -> c
--   view ::             Simple Lens a c        -> a -> c
--   view :: Monoid m => Simple Traversal a m   -> a -> m
--   
view :: Getting c a c -> a -> c -- | View the value of a Getter, Iso, Lens or the -- result of folding over the result of mapping the targets of a -- Fold or Traversal. -- -- It may be useful to think of views as having these more -- restrictive signatures: -- --
--   >>> import Control.Lens
--   
--   >>> views _2 length (1,"hello")
--   5
--   
-- --
--   views ::             Getter a c             -> (c -> d) -> a -> d
--   views :: Monoid m => Fold a c               -> (c -> m) -> a -> m
--   views ::             Simple Iso a c         -> (c -> d) -> a -> d
--   views ::             Simple Lens a c        -> (c -> d) -> a -> d
--   views :: Monoid m => Simple Traversal a c   -> (c -> m) -> a -> m
--   
views :: Getting m a c -> (c -> m) -> a -> m -- | 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. -- --
--   use :: MonadState a m             => Getter a c             -> m c
--   use :: (MonadState a m, Monoid r) => Fold a r               -> m r
--   use :: MonadState a m             => Simple Iso a c         -> m c
--   use :: MonadState a m             => Simple Lens a c        -> m c
--   use :: (MonadState a m, Monoid r) => Simple Traversal a r   -> m r
--   
use :: MonadState a m => Getting c a c -> m c -- | 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. -- --
--   uses :: MonadState a m             => Getter a c           -> (c -> e) -> m e
--   uses :: (MonadState a m, Monoid r) => Fold a c             -> (c -> r) -> m r
--   uses :: MonadState a m             => Simple Lens a c      -> (c -> e) -> m e
--   uses :: MonadState a m             => Simple Iso a c       -> (c -> e) -> m e
--   uses :: (MonadState a m, Monoid r) => Simple Traversal a c -> (c -> r) -> m r
--   
uses :: MonadState a m => Getting e a c -> (c -> e) -> m e -- | Query 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. -- --
--   query :: MonadReader a m             => Getter a c           -> m c
--   query :: (MonadReader a m, Monoid c) => Fold a c             -> m c
--   query :: MonadReader a m             => Simple Iso a c       -> m c
--   query :: MonadReader a m             => Simple Lens a c      -> m c
--   query :: (MonadReader a m, Monoid c) => Simple Traversal a c -> m c
--   
query :: MonadReader a m => Getting c a c -> m c -- | 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. -- --
--   queries :: MonadReader a m             => Getter a c           -> (c -> e) -> m e
--   queries :: (MonadReader a m, Monoid c) => Fold a c             -> (c -> e) -> m e
--   queries :: MonadReader a m             => Simple Iso a c       -> (c -> e) -> m e
--   queries :: MonadReader a m             => Simple Lens a c      -> (c -> e) -> m e
--   queries :: (MonadReader a m, Monoid c) => Simple Traversal a c -> (c -> e) -> m e
--   
queries :: MonadReader a m => Getting e a c -> (c -> e) -> m e -- | A Lens a b c d is a purely functional reference. -- -- While a Traversal could be used for Getting like a valid -- Fold, it wasn't a valid Getter as Applicative -- wasn't a superclass of Gettable. -- -- Functor, however is the superclass of both. -- --
--   type Lens a b c d = forall f. Functor f => (c -> f d) -> a -> f b
--   
-- -- Every Lens is a valid Setter, choosing f = -- Mutator. -- -- Every Lens can be used for Getting like a Fold -- that doesn't use the Applicative or Gettable. -- -- 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 Functor is a superclass of Gettable -- -- 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. module Control.Lens.Type -- | 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 Lensis -- subject to the three common sense lens laws: -- -- 1) You get back what you put in: -- --
--   view l (set l b a)  = b
--   
-- -- 2) Putting back what you got doesn't change anything: -- --
--   set l (view l a) a  = a
--   
-- -- 3) Setting twice is the same as setting once: -- --
--   set l c (set l b a) = set l c a
--   
-- -- 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/. -- -- 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 -- should also apply to any lenses you create. -- --
--   l pure = pure
--   fmap (l f) . l g = getCompose . l (Compose . fmap f . g)
--   
-- --
--   type Lens a b c d = forall f. Functor f => LensLike f a b c d
--   
type Lens a b c d = forall f. Functor f => (c -> f d) -> a -> f b -- | A Simple Lens, Simple Traversal, ... can -- be used instead of a Lens,Traversal, ... whenever the -- type variables don't change upon setting a value. -- --
--   imaginary :: Simple Lens (Complex a) a
--   traverseHead :: Simple Traversal [a] a
--   
-- -- Note: To use this alias in your own code with LensLike -- f or Setter, you may have to turn on -- LiberalTypeSynonyms. type Simple f a b = f a a b b -- | Build a Lens from a getter and a setter. -- --
--   lens :: Functor f => (a -> c) -> (a -> d -> b) -> (c -> f d) -> a -> f b
--   
lens :: (a -> c) -> (a -> d -> b) -> Lens a b c d -- | (%%~) 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. -- -- For all that the definition of this combinator is just: -- --
--   (%%~) = id
--   
-- --
--   (%%~) :: Functor f =>     Iso a b c d       -> (c -> f d) -> a -> f b
--   (%%~) :: Functor f =>     Lens a b c d      -> (c -> f d) -> a -> f b
--   (%%~) :: Applicative f => Traversal a b c d -> (c -> f d) -> a -> f b
--   
-- -- It may be beneficial to think about it as if it had these even more -- restrictive types, however: -- -- 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 a b c d       -> (c -> (e, d)) -> a -> (e, b)
--   (%%~) ::             Lens a b c d      -> (c -> (e, d)) -> a -> (e, b)
--   (%%~) :: Monoid m => Traversal a b c d -> (c -> (m, d)) -> a -> (m, b)
--   
(%%~) :: LensLike f a b c d -> (c -> f d) -> a -> f b -- | Modify the target of a Lens in the current state returning some -- extra information of c or modify all targets of a -- Traversal in the current state, extracting extra information of -- type c and return a monoidal summary of the changes. -- --
--   (%%=) = (state .)
--   
-- -- It may be useful to think of (%%=), instead, as having either -- of the following more restricted type signatures: -- --
--   (%%=) :: MonadState a m             => Iso a a c d       -> (c -> (e, d) -> m e
--   (%%=) :: MonadState a m             => Lens a a c d      -> (c -> (e, d) -> m e
--   (%%=) :: (MonadState a m, Monoid e) => Traversal a a c d -> (c -> (e, d) -> m e
--   
(%%=) :: MonadState a m => LensLike ((,) e) a a c d -> (c -> (e, d)) -> m e -- | This lens can be used to change the result of a function but only -- where the arguments match the key given. resultAt :: Eq e => e -> Simple Lens (e -> a) a -- | Merge two lenses, getters, setters, folds or traversals. merged :: Functor f => LensLike f a b c c -> LensLike f a' b' c c -> LensLike f (Either a a') (Either b b') c c -- | alongside makes a Lens from two other lenses (or -- isomorphisms) alongside :: Lens a b c d -> Lens a' b' c' d' -> Lens (a, a') (b, b') (c, c') (d, d') -- | Modify the target of a Lens and return the result -- -- When you do not need the result of the addition, (+~) is more -- flexible. (<%~) :: LensLike ((,) d) a b c d -> (c -> d) -> a -> (d, b) -- | 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 c => LensLike ((,) c) a b c c -> c -> a -> (c, b) -- | 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 c => LensLike ((,) c) a b c c -> c -> a -> (c, b) -- | 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 c => LensLike ((,) c) a b c c -> c -> a -> (c, b) -- | 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. ( LensLike ((,) c) a b c c -> c -> a -> (c, b) -- | 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 division, (^~) is more -- flexible. (<^~) :: (Num c, Integral d) => LensLike ((,) c) a b c c -> d -> a -> (c, b) -- | 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 division, (^^~) is more -- flexible. (<^^~) :: (Fractional c, Integral d) => LensLike ((,) c) a b c c -> d -> a -> (c, b) -- | 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 division, (**~) is more -- flexible. (<**~) :: Floating c => LensLike ((,) c) a b c c -> c -> a -> (c, b) -- | Logically || a Boolean valued Lens and return the result -- -- When you do not need the result of the operation, (||~) is more -- flexible. (<||~) :: LensLike ((,) Bool) a b Bool Bool -> Bool -> a -> (Bool, b) -- | Logically && a Boolean valued Lens and return -- the result -- -- When you do not need the result of the operation, (&&~) -- is more flexible. (<&&~) :: LensLike ((,) Bool) a b Bool Bool -> Bool -> a -> (Bool, b) -- | Modify the target of a Lens into your monad's state by a user -- supplied function and return the result. -- -- When you do not need the result of the operation, (%=) is more -- flexible. (<%=) :: MonadState a m => LensLike ((,) d) a a c d -> (c -> d) -> m d -- | 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 multiplication, (+=) is -- more flexible. (<+=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m b -- | 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 multiplication, (-=) is -- more flexible. (<-=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m b -- | 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 a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m b -- | 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. ( SimpleLensLike ((,) b) a b -> b -> m b -- | 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 a m, Num b, Integral c) => SimpleLensLike ((,) b) a b -> c -> m b -- | 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 a m, Fractional b, Integral c) => SimpleLensLike ((,) b) a b -> c -> m b -- | 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 a m, Floating b) => SimpleLensLike ((,) b) a b -> b -> m b -- | 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 a m => SimpleLensLike ((,) Bool) a 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 a m => SimpleLensLike ((,) Bool) a Bool -> Bool -> m Bool -- | Cloning a Lens is one way to make sure you arent 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. -- -- "Costate Comonad Coalgebra is equivalent of Java's member variable -- update technology for Haskell" -- @PLT_Borat on Twitter cloneLens :: Functor f => LensLike (IndexedStore c d) a b c d -> (c -> f d) -> a -> f b -- | 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 a b c d 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 a b c d = (c -> f d) -> a -> f b -- |
--   type LensLike f a b c d = Overloaded (->) f a b c d
--   
type Overloaded k f a b c d = k (c -> f d) (a -> f b) -- |
--   type SimpleLens = Simple Lens
--   
type SimpleLens a b = Lens a a b b -- |
--   type SimpleLensLike f = Simple (LensLike f)
--   
type SimpleLensLike f a b = LensLike f a a b b -- |
--   type SimpleOverloaded k f a b = Simple (Overloaded k f) a b
--   
type SimpleOverloaded k f a b = Overloaded k f a a b b -- | A Fold a c 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) => -- (c -> m) -> t c -> m. Since we want to be able to work -- with monomorphic containers, we could generalize this signature to -- forall m. Monoid m => (c -> m) -> a -> m, -- and then decorate it with Accessor to obtain -- --
--   type Fold a c = forall m. Monoid m => Getting m a c
--   
-- -- 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 lens-like constructions. -- -- A Fold a c 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 c), then there should be a fooOf -- method that takes a Fold a c and a value of type -- a. -- -- 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 a c = forall f. (Gettable f, Applicative f) => (c -> f c) -> a -> f a -- | 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. folding :: (Foldable f, Applicative g, Gettable g) => (a -> f c) -> LensLike g a b c d -- | Obtain a Fold from any Foldable. folded :: Foldable f => Fold (f c) c -- | Build a fold that unfolds its values from a seed. -- --
--   unfoldr = toListOf . unfolded
--   
unfolded :: (b -> Maybe (a, b)) -> Fold b a -- | x ^. iterated f Return an infinite fold of repeated -- applications of f to x. -- --
--   toListOf (iterated f) a = iterate f a
--   
iterated :: (a -> a) -> Fold a a -- | Obtain a Fold by filtering a Lens, Iso, -- Getter, Fold or Traversal. filtered :: (Gettable f, Applicative f) => (c -> Bool) -> SimpleLensLike f a c -> SimpleLensLike f a c -- | This allows you to traverse the elements of a Traversal or -- Fold in the opposite order. -- -- Note: backwards should have no impact on a Getter -- Setter, Lens or Iso. -- -- To change the direction of an Iso, use from. backwards :: LensLike (Backwards f) a b c d -> LensLike f a b c d -- | Fold by repeating the input forever. -- --
--   repeat = toListOf repeated
--   
repeated :: Fold a a -- | A fold that replicates its input n times. -- --
--   replicate n = toListOf (replicated n)
--   
replicated :: Int -> Fold a a -- | Transform a fold into a fold that loops over its elements over and -- over. -- --
--   >>> import Control.Lens
--   
--   >>> take 6 $ toListOf (cycled traverse) [1,2,3]
--   [1,2,3,1,2,3]
--   
cycled :: (Applicative f, Gettable f) => SimpleLensLike f a c -> SimpleLensLike f a c -- | Obtain a Fold by taking elements from another Fold, -- Lens, Iso, Getter or Traversal while a -- predicate holds. -- --
--   takeWhile p = toListOf (takingWhile p folded)
--   
-- --
--   >>> toListOf (takingWhile (<=3) folded) [1..]
--   [1,2,3]
--   
takingWhile :: (Gettable f, Applicative f) => (c -> Bool) -> Getting (Endo (f a)) a c -> SimpleLensLike f a c -- | 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]
--   
droppingWhile :: (Gettable f, Applicative f) => (c -> Bool) -> Getting (Endo (f a)) a c -> SimpleLensLike f a c -- |
--   foldMap = foldMapOf folded
--   
-- --
--   foldMapOf = views
--   
-- --
--   foldMapOf ::             Getter a c           -> (c -> r) -> a -> r
--   foldMapOf :: Monoid r => Fold a c             -> (c -> r) -> a -> r
--   foldMapOf ::             Simple Lens a c      -> (c -> r) -> a -> r
--   foldMapOf ::             Simple Iso a c       -> (c -> r) -> a -> r
--   foldMapOf :: Monoid r => Simple Traversal a c -> (c -> r) -> a -> r
--   
foldMapOf :: Getting r a c -> (c -> r) -> a -> r -- |
--   fold = foldOf folded
--   
-- --
--   foldOf = view
--   
-- --
--   foldOf ::             Getter a m           -> a -> m
--   foldOf :: Monoid m => Fold a m             -> a -> m
--   foldOf ::             Simple Lens a m      -> a -> m
--   foldOf ::             Simple Iso a m       -> a -> m
--   foldOf :: Monoid m => Simple Traversal a m -> a -> m
--   
foldOf :: Getting c a c -> a -> c -- | Right-associative fold of parts of a structure that are viewed through -- a Lens, Getter, Fold or Traversal. -- --
--   foldr = foldrOf folded
--   
-- --
--   foldrOf :: Getter a c           -> (c -> e -> e) -> e -> a -> e
--   foldrOf :: Fold a c             -> (c -> e -> e) -> e -> a -> e
--   foldrOf :: Simple Lens a c      -> (c -> e -> e) -> e -> a -> e
--   foldrOf :: Simple Iso a c       -> (c -> e -> e) -> e -> a -> e
--   foldrOf :: Simple Traversal a c -> (c -> e -> e) -> e -> a -> e
--   
foldrOf :: Getting (Endo e) a c -> (c -> e -> e) -> e -> a -> e -- | Left-associative fold of the parts of a structure that are viewed -- through a Lens, Getter, Fold or Traversal. -- --
--   foldl = foldlOf folded
--   
-- --
--   foldlOf :: Getter a c           -> (e -> c -> e) -> e -> a -> e
--   foldlOf :: Fold a c             -> (e -> c -> e) -> e -> a -> e
--   foldlOf :: Simple Lens a c      -> (e -> c -> e) -> e -> a -> e
--   foldlOf :: Simple Iso a c       -> (e -> c -> e) -> e -> a -> e
--   foldlOf :: Simple Traversal a c -> (e -> c -> e) -> e -> a -> e
--   
foldlOf :: Getting (Dual (Endo e)) a c -> (e -> c -> e) -> e -> a -> e -- |
--   toList = toListOf folded
--   
-- --
--   toListOf :: Getter a c           -> a -> [c]
--   toListOf :: Fold a c             -> a -> [c]
--   toListOf :: Simple Lens a c      -> a -> [c]
--   toListOf :: Simple Iso a c       -> a -> [c]
--   toListOf :: Simple Traversal a c -> a -> [c]
--   
toListOf :: Getting [c] a c -> a -> [c] -- |
--   any = anyOf folded
--   
-- --
--   anyOf :: Getter a c               -> (c -> Bool) -> a -> Bool
--   anyOf :: Fold a c                 -> (c -> Bool) -> a -> Bool
--   anyOf :: Simple Lens a b c d      -> (c -> Bool) -> a -> Bool
--   anyOf :: Simple Iso a b c d       -> (c -> Bool) -> a -> Bool
--   anyOf :: Simple Traversal a b c d -> (c -> Bool) -> a -> Bool
--   
anyOf :: Getting Any a c -> (c -> Bool) -> a -> Bool -- |
--   all = allOf folded
--   
-- --
--   allOf :: Getter a c           -> (c -> Bool) -> a -> Bool
--   allOf :: Fold a c             -> (c -> Bool) -> a -> Bool
--   allOf :: Simple Lens a c      -> (c -> Bool) -> a -> Bool
--   allOf :: Simple Iso a c       -> (c -> Bool) -> a -> Bool
--   allOf :: Simple Traversal a c -> (c -> Bool) -> a -> Bool
--   
allOf :: Getting All a c -> (c -> Bool) -> a -> Bool -- |
--   and = andOf folded
--   
-- --
--   andOf :: Getter a Bool           -> a -> Bool
--   andOf :: Fold a Bool             -> a -> Bool
--   andOf :: Simple Lens a Bool      -> a -> Bool
--   andOf :: Simple Iso a Bool       -> a -> Bool
--   andOf :: Simple Traversal a Bool -> a -> Bool
--   
andOf :: Getting All a Bool -> a -> Bool -- |
--   or = orOf folded
--   
-- --
--   orOf :: Getter a Bool           -> a -> Bool
--   orOf :: Fold a Bool             -> a -> Bool
--   orOf :: Simple Lens a Bool      -> a -> Bool
--   orOf :: Simple Iso a Bool       -> a -> Bool
--   orOf :: Simple Traversal a Bool -> a -> Bool
--   
orOf :: Getting Any a Bool -> a -> Bool -- |
--   product = productOf folded
--   
-- --
--   productOf ::          Getter a c           -> a -> c
--   productOf :: Num c => Fold a c             -> a -> c
--   productOf ::          Simple Lens a c      -> a -> c
--   productOf ::          Simple Iso a c       -> a -> c
--   productOf :: Num c => Simple Traversal a c -> a -> c
--   
productOf :: Getting (Product c) a c -> a -> c -- |
--   sum = sumOf folded
--   
-- --
--   sumOf _1 :: (a, b) -> a
--   
-- --
--   sumOf (folded . _1) :: (Foldable f, Num a) => f (a, b) -> a
--   
-- --
--   sumOf ::          Getter a c           -> a -> c
--   sumOf :: Num c => Fold a c             -> a -> c
--   sumOf ::          Simple Lens a c      -> a -> c
--   sumOf ::          Simple Iso a c       -> a -> c
--   sumOf :: Num c => Simple Traversal a c -> a -> c
--   
sumOf :: Getting (Sum c) a c -> a -> c -- | When passed a Getter, traverseOf_ can work over a -- Functor. -- -- When passed a Fold, traverseOf_ requires an -- Applicative. -- --
--   traverse_ = traverseOf_ folded
--   
-- --
--   traverseOf_ _2 :: Functor f => (c -> f e) -> (c1, c) -> f ()
--   
-- --
--   traverseOf_ traverseLeft :: Applicative f => (a -> f b) -> Either a c -> f ()
--   
-- -- The rather specific signature of traverseOf_ allows it to be used as -- if the signature was either: -- --
--   traverseOf_ :: Functor f     => Getter a c           -> (c -> f e) -> a -> f ()
--   traverseOf_ :: Applicative f => Fold a c             -> (c -> f e) -> a -> f ()
--   traverseOf_ :: Functor f     => Simple Lens a c      -> (c -> f e) -> a -> f ()
--   traverseOf_ :: Functor f     => Simple Iso a c       -> (c -> f e) -> a -> f ()
--   traverseOf_ :: Applicative f => Simple Traversal a c -> (c -> f e) -> a -> f ()
--   
traverseOf_ :: Functor f => Getting (Traversed f) a c -> (c -> f e) -> a -> f () -- |
--   for_ = forOf_ folded
--   
-- --
--   forOf_ :: Functor f     => Getter a c           -> a -> (c -> f e) -> f ()
--   forOf_ :: Applicative f => Fold a c             -> a -> (c -> f e) -> f ()
--   forOf_ :: Functor f     => Simple Lens a c      -> a -> (c -> f e) -> f ()
--   forOf_ :: Functor f     => Simple Iso a c       -> a -> (c -> f e) -> f ()
--   forOf_ :: Applicative f => Simple Traversal a c -> a -> (c -> f e) -> f ()
--   
forOf_ :: Functor f => Getting (Traversed f) a c -> a -> (c -> f e) -> f () -- |
--   sequenceA_ = sequenceAOf_ folded
--   
-- --
--   sequenceAOf_ :: Functor f     => Getter a (f ())           -> a -> f ()
--   sequenceAOf_ :: Applicative f => Fold a (f ())             -> a -> f ()
--   sequenceAOf_ :: Functor f     => Simple Lens a (f ())      -> a -> f ()
--   sequenceAOf_ :: Functor f     => Simple Iso a (f ())       -> a -> f ()
--   sequenceAOf_ :: Applicative f => Simple Traversal a (f ()) -> a -> f ()
--   
sequenceAOf_ :: Functor f => Getting (Traversed f) a (f ()) -> a -> f () -- |
--   mapM_ = mapMOf_ folded
--   
-- --
--   mapMOf_ :: Monad m => Getter a c           -> (c -> m e) -> a -> m ()
--   mapMOf_ :: Monad m => Fold a c             -> (c -> m e) -> a -> m ()
--   mapMOf_ :: Monad m => Simple Lens a c      -> (c -> m e) -> a -> m ()
--   mapMOf_ :: Monad m => Simple Iso a c       -> (c -> m e) -> a -> m ()
--   mapMOf_ :: Monad m => Simple Traversal a c -> (c -> m e) -> a -> m ()
--   
mapMOf_ :: Monad m => Getting (Sequenced m) a c -> (c -> m e) -> a -> m () -- |
--   forM_ = forMOf_ folded
--   
-- --
--   forMOf_ :: Monad m => Getter a c           -> a -> (c -> m e) -> m ()
--   forMOf_ :: Monad m => Fold a c             -> a -> (c -> m e) -> m ()
--   forMOf_ :: Monad m => Simple Lens a c      -> a -> (c -> m e) -> m ()
--   forMOf_ :: Monad m => Simple Iso a c       -> a -> (c -> m e) -> m ()
--   forMOf_ :: Monad m => Simple Traversal a c -> a -> (c -> m e) -> m ()
--   
forMOf_ :: Monad m => Getting (Sequenced m) a c -> a -> (c -> m e) -> m () -- |
--   sequence_ = sequenceOf_ folded
--   
-- --
--   sequenceOf_ :: Monad m => Getter a (m b)           -> a -> m ()
--   sequenceOf_ :: Monad m => Fold a (m b)             -> a -> m ()
--   sequenceOf_ :: Monad m => Simple Lens a (m b)      -> a -> m ()
--   sequenceOf_ :: Monad m => Simple Iso a (m b)       -> a -> m ()
--   sequenceOf_ :: Monad m => Simple Traversal a (m b) -> a -> m ()
--   
sequenceOf_ :: Monad m => Getting (Sequenced m) a (m c) -> a -> m () -- | The sum of a collection of actions, generalizing concatOf. -- --
--   asum = asumOf folded
--   
-- --
--   asumOf :: Alternative f => Getter a c           -> a -> f c
--   asumOf :: Alternative f => Fold a c             -> a -> f c
--   asumOf :: Alternative f => Simple Lens a c      -> a -> f c
--   asumOf :: Alternative f => Simple Iso a c       -> a -> f c
--   asumOf :: Alternative f => Simple Traversal a c -> a -> f c
--   
asumOf :: Alternative f => Getting (Endo (f c)) a (f c) -> a -> f c -- | The sum of a collection of actions, generalizing concatOf. -- --
--   msum = msumOf folded
--   
-- --
--   msumOf :: MonadPlus m => Getter a c           -> a -> m c
--   msumOf :: MonadPlus m => Fold a c             -> a -> m c
--   msumOf :: MonadPlus m => Simple Lens a c      -> a -> m c
--   msumOf :: MonadPlus m => Simple Iso a c       -> a -> m c
--   msumOf :: MonadPlus m => Simple Traversal a c -> a -> m c
--   
msumOf :: MonadPlus m => Getting (Endo (m c)) a (m c) -> a -> m c -- |
--   concatMap = concatMapOf folded
--   
-- --
--   concatMapOf :: Getter a c           -> (c -> [e]) -> a -> [e]
--   concatMapOf :: Fold a c             -> (c -> [e]) -> a -> [e]
--   concatMapOf :: Simple Lens a c      -> (c -> [e]) -> a -> [e]
--   concatMapOf :: Simple Iso a c       -> (c -> [e]) -> a -> [e]
--   concatMapOf :: Simple Traversal a c -> (c -> [e]) -> a -> [e]
--   
concatMapOf :: Getting [e] a c -> (c -> [e]) -> a -> [e] -- |
--   concat = concatOf folded
--   concatOf = view
--   
-- --
--   concatOf :: Getter a [e]           -> a -> [e]
--   concatOf :: Fold a [e]             -> a -> [e]
--   concatOf :: Simple Iso a [e]       -> a -> [e]
--   concatOf :: Simple Lens a [e]      -> a -> [e]
--   concatOf :: Simple Traversal a [e] -> a -> [e]
--   
concatOf :: Getting [e] a [e] -> a -> [e] -- |
--   elem = elemOf folded
--   
-- --
--   elemOf :: Eq c => Getter a c           -> c -> a -> Bool
--   elemOf :: Eq c => Fold a c             -> c -> a -> Bool
--   elemOf :: Eq c => Simple Lens a c      -> c -> a -> Bool
--   elemOf :: Eq c => Simple Iso a c       -> c -> a -> Bool
--   elemOf :: Eq c => Simple Traversal a c -> c -> a -> Bool
--   
elemOf :: Eq c => Getting Any a c -> c -> a -> Bool -- |
--   notElem = notElemOf folded
--   
-- --
--   notElemOf :: Eq c => Getter a c           -> c -> a -> Bool
--   notElemOf :: Eq c => Fold a c             -> c -> a -> Bool
--   notElemOf :: Eq c => Simple Iso a c       -> c -> a -> Bool
--   notElemOf :: Eq c => Simple Lens a c      -> c -> a -> Bool
--   notElemOf :: Eq c => Simple Traversal a c -> c -> a -> Bool
--   
notElemOf :: Eq c => Getting All a c -> c -> a -> Bool -- | Note: this can be rather inefficient for large containers. -- --
--   length = lengthOf folded
--   
-- --
--   >>> import Control.Lens
--   
--   >>> lengthOf _1 ("hello",())
--   1
--   
-- --
--   lengthOf (folded . folded) :: Foldable f => f (g a) -> Int
--   
-- --
--   lengthOf :: Getter a c           -> a -> Int
--   lengthOf :: Fold a c             -> a -> Int
--   lengthOf :: Simple Lens a c      -> a -> Int
--   lengthOf :: Simple Iso a c       -> a -> Int
--   lengthOf :: Simple Traversal a c -> a -> Int
--   
lengthOf :: Getting (Sum Int) a c -> a -> 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. -- --
--   >>> import Control.Lens
--   
--   >>> nullOf _1 (1,2)
--   False
--   
-- --
--   nullOf (folded . _1 . folded) :: Foldable f => f (g a, b) -> Bool
--   
-- --
--   nullOf :: Getter a c           -> a -> Bool
--   nullOf :: Fold a c             -> a -> Bool
--   nullOf :: Simple Iso a c       -> a -> Bool
--   nullOf :: Simple Lens a c      -> a -> Bool
--   nullOf :: Simple Traversal a c -> a -> Bool
--   
nullOf :: Getting All a c -> a -> Bool -- | Perform a safe head of a Fold or Traversal or -- retrieve Just the result from a Getter or Lens. -- --
--   listToMaybe . toList = headOf folded
--   
-- --
--   headOf :: Getter a c           -> a -> Maybe c
--   headOf :: Fold a c             -> a -> Maybe c
--   headOf :: Simple Lens a c      -> a -> Maybe c
--   headOf :: Simple Iso a c       -> a -> Maybe c
--   headOf :: Simple Traversal a c -> a -> Maybe c
--   
headOf :: Getting (First c) a c -> a -> Maybe c -- | Perform a safe last of a Fold or Traversal or -- retrieve Just the result from a Getter or Lens. -- --
--   lastOf :: Getter a c           -> a -> Maybe c
--   lastOf :: Fold a c             -> a -> Maybe c
--   lastOf :: Simple Lens a c      -> a -> Maybe c
--   lastOf :: Simple Iso a c       -> a -> Maybe c
--   lastOf :: Simple Traversal a c -> a -> Maybe c
--   
lastOf :: Getting (Last c) a c -> a -> Maybe c -- | Obtain the maximum element (if any) targeted by a Fold or -- Traversal -- -- Note: maximumOf on a valid Iso, Lens or Getter -- will always return Just a value. -- --
--   maximum = fromMaybe (error empty) . maximumOf folded
--   
-- --
--   maximumOf ::          Getter a c           -> a -> Maybe c
--   maximumOf :: Ord c => Fold a c             -> a -> Maybe c
--   maximumOf ::          Simple Iso a c       -> a -> Maybe c
--   maximumOf ::          Simple Lens a c      -> a -> Maybe c
--   maximumOf :: Ord c => Simple Traversal a c -> a -> Maybe c
--   
maximumOf :: Getting (Max c) a c -> a -> Maybe c -- | Obtain the minimum element (if any) targeted by a Fold or -- Traversal -- -- Note: minimumOf on a valid Iso, Lens or Getter -- will always return Just a value. -- --
--   minimum = fromMaybe (error empty) . minimumOf folded
--   
-- --
--   minimumOf ::          Getter a c           -> a -> Maybe c
--   minimumOf :: Ord c => Fold a c             -> a -> Maybe c
--   minimumOf ::          Simple Iso a c       -> a -> Maybe c
--   minimumOf ::          Simple Lens a c      -> a -> Maybe c
--   minimumOf :: Ord c => Simple Traversal a c -> a -> Maybe c
--   
minimumOf :: Getting (Min c) a c -> a -> Maybe c -- | Obtain the maximum element (if any) targeted by a Fold, -- Traversal, Lens, Iso, or Getter according -- to a user supplied ordering. -- --
--   maximumBy cmp = fromMaybe (error empty) . maximumByOf folded cmp
--   
-- --
--   maximumByOf :: Getter a c           -> (c -> c -> Ordering) -> a -> Maybe c
--   maximumByOf :: Fold a c             -> (c -> c -> Ordering) -> a -> Maybe c
--   maximumByOf :: Simple Iso a c       -> (c -> c -> Ordering) -> a -> Maybe c
--   maximumByOf :: Simple Lens a c      -> (c -> c -> Ordering) -> a -> Maybe c
--   maximumByOf :: Simple Traversal a c -> (c -> c -> Ordering) -> a -> Maybe c
--   
maximumByOf :: Getting (Endo (Maybe c)) a c -> (c -> c -> Ordering) -> a -> Maybe c -- | Obtain the minimum element (if any) targeted by a Fold, -- Traversal, Lens, Iso or Getter according -- to a user supplied ordering. -- --
--   minimumBy cmp = fromMaybe (error "empty") . minimumByOf folded cmp
--   
-- --
--   minimumByOf :: Getter a c           -> (c -> c -> Ordering) -> a -> Maybe c
--   minimumByOf :: Fold a c             -> (c -> c -> Ordering) -> a -> Maybe c
--   minimumByOf :: Simple Iso a c       -> (c -> c -> Ordering) -> a -> Maybe c
--   minimumByOf :: Simple Lens a c      -> (c -> c -> Ordering) -> a -> Maybe c
--   minimumByOf :: Simple Traversal a c -> (c -> c -> Ordering) -> a -> Maybe c
--   
minimumByOf :: Getting (Endo (Maybe c)) a c -> (c -> c -> Ordering) -> a -> Maybe c -- | 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 :: Getter a c           -> (c -> Bool) -> a -> Maybe c
--   findOf :: Fold a c             -> (c -> Bool) -> a -> Maybe c
--   findOf :: Simple Iso a c       -> (c -> Bool) -> a -> Maybe c
--   findOf :: Simple Lens a c      -> (c -> Bool) -> a -> Maybe c
--   findOf :: Simple Traversal a c -> (c -> Bool) -> a -> Maybe c
--   
findOf :: Getting (First c) a c -> (c -> Bool) -> a -> Maybe c -- | Strictly fold right over the elements of a structure. -- --
--   foldr' = foldrOf' folded
--   
-- --
--   foldrOf' :: Getter a c           -> (c -> e -> e) -> e -> a -> e
--   foldrOf' :: Fold a c             -> (c -> e -> e) -> e -> a -> e
--   foldrOf' :: Simple Iso a c       -> (c -> e -> e) -> e -> a -> e
--   foldrOf' :: Simple Lens a c      -> (c -> e -> e) -> e -> a -> e
--   foldrOf' :: Simple Traversal a c -> (c -> e -> e) -> e -> a -> e
--   
foldrOf' :: Getting (Dual (Endo (e -> e))) a c -> (c -> e -> e) -> e -> a -> e -- | Fold over the elements of a structure, associating to the left, but -- strictly. -- --
--   foldl' = foldlOf' folded
--   
-- --
--   foldlOf' :: Getter a c           -> (e -> c -> e) -> e -> a -> e
--   foldlOf' :: Fold a c             -> (e -> c -> e) -> e -> a -> e
--   foldlOf' :: Simple Iso a c       -> (e -> c -> e) -> e -> a -> e
--   foldlOf' :: Simple Lens a c      -> (e -> c -> e) -> e -> a -> e
--   foldlOf' :: Simple Traversal a c -> (e -> c -> e) -> e -> a -> e
--   
foldlOf' :: Getting (Endo (e -> e)) a c -> (e -> c -> e) -> e -> a -> e -- | 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 l f = foldr1 f . toListOf l
--   
-- --
--   foldr1 = foldr1Of folded
--   
-- --
--   foldr1Of :: Getter a c           -> (c -> c -> c) -> a -> c
--   foldr1Of :: Fold a c             -> (c -> c -> c) -> a -> c
--   foldr1Of :: Simple Iso a c       -> (c -> c -> c) -> a -> c
--   foldr1Of :: Simple Lens a c      -> (c -> c -> c) -> a -> c
--   foldr1Of :: Simple Traversal a c -> (c -> c -> c) -> a -> c
--   
foldr1Of :: Getting (Endo (Maybe c)) a c -> (c -> c -> c) -> a -> c -- | A variant of foldlOf that has no base case and thus may only be -- applied to lenses and strutures such that the lens views at least one -- element of the structure. -- --
--   foldl1Of l f = foldl1Of l f . toList
--   
-- --
--   foldl1 = foldl1Of folded
--   
-- --
--   foldl1Of :: Getter a c           -> (c -> c -> c) -> a -> c
--   foldl1Of :: Fold a c             -> (c -> c -> c) -> a -> c
--   foldl1Of :: Simple Iso a c       -> (c -> c -> c) -> a -> c
--   foldl1Of :: Simple Lens a c      -> (c -> c -> c) -> a -> c
--   foldl1Of :: Simple Traversal a c -> (c -> c -> c) -> a -> c
--   
foldl1Of :: Getting (Dual (Endo (Maybe c))) a c -> (c -> c -> c) -> a -> c -- | 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 a c           -> (c -> e -> m e) -> e -> a -> m e
--   foldrMOf :: Monad m => Fold a c             -> (c -> e -> m e) -> e -> a -> m e
--   foldrMOf :: Monad m => Simple Iso a c       -> (c -> e -> m e) -> e -> a -> m e
--   foldrMOf :: Monad m => Simple Lens a c      -> (c -> e -> m e) -> e -> a -> m e
--   foldrMOf :: Monad m => Simple Traversal a c -> (c -> e -> m e) -> e -> a -> m e
--   
foldrMOf :: Monad m => Getting (Dual (Endo (e -> m e))) a c -> (c -> e -> m e) -> e -> a -> m e -- | 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 a c           -> (e -> c -> m e) -> e -> a -> m e
--   foldlMOf :: Monad m => Fold a c             -> (e -> c -> m e) -> e -> a -> m e
--   foldlMOf :: Monad m => Simple Iso a c       -> (e -> c -> m e) -> e -> a -> m e
--   foldlMOf :: Monad m => Simple Lens a c      -> (e -> c -> m e) -> e -> a -> m e
--   foldlMOf :: Monad m => Simple Traversal a c -> (e -> c -> m e) -> e -> a -> m e
--   
foldlMOf :: Monad m => Getting (Endo (e -> m e)) a c -> (e -> c -> m e) -> e -> a -> m e instance (Gettable f, Applicative f) => Monoid (GA f a) -- | A Traversal a b c d 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) -- => (c -> f d) -> t c -> f (t d), -- -- we monomorphize the contents and result to obtain -- --
--   type Traversal a b c d = forall f. Applicative f => (c -> f d) -> a -> f b
--   
-- -- 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 a b c d = forall f. Applicative f => (c -> f d) -> a -> f b -- | Access the nth element of a Traversable container. -- -- Attempts to access beyond the range of the Traversal will cause -- an error. -- --
--   element = elementOf traverse
--   
element :: Traversable t => Int -> Simple Lens (t a) a -- | A Lens to 'Control.Lens.Getter.view'/'Control.Lens.Setter.set' -- the nth element elementOf a Traversal, Lens or -- Iso. -- -- Attempts to access beyond the range of the Traversal will cause -- an error. -- --
--   >>> import Control.Lens
--   
--   >>> [[1],[3,4]]^.elementOf (traverse.traverse) 1
--   3
--   
elementOf :: Functor f => LensLike (ElementOf f) a b c c -> Int -> LensLike f a b c c -- | Map each element of a structure targeted by a Lens or Traversal, -- evaluate these actions from left to right, and collect the results. -- --
--   traverseOf = id
--   
-- --
--   traverse = traverseOf traverse
--   
-- --
--   traverseOf :: Iso a b c d       -> (c -> f d) -> a -> f b
--   traverseOf :: Lens a b c d      -> (c -> f d) -> a -> f b
--   traverseOf :: Traversal a b c d -> (c -> f d) -> a -> f b
--   
traverseOf :: LensLike f a b c d -> (c -> f d) -> a -> f b -- |
--   forOf l = flip (traverseOf l)
--   
-- --
--   for = forOf traverse
--   forOf = flip
--   
-- --
--   forOf :: Iso a b c d -> a -> (c -> f d) -> f b
--   forOf :: Lens a b c d -> a -> (c -> f d) -> f b
--   forOf :: Traversal a b c d -> a -> (c -> f d) -> f b
--   
forOf :: LensLike f a b c d -> a -> (c -> f d) -> f b -- | Evaluate each action in the structure from left to right, and collect -- the results. -- --
--   sequenceA = sequenceAOf traverse = traverse id
--   sequenceAOf l = traverseOf l id
--   sequenceAOf l = l id
--   
-- --
--   sequenceAOf ::                  Iso a b (f c) c       -> a -> f b
--   sequenceAOf ::                  Lens a b (f c) c      -> a -> f b
--   sequenceAOf :: Applicative f => Traversal a b (f c) c -> a -> f b
--   
sequenceAOf :: LensLike f a b (f c) c -> a -> f b -- | 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. -- --
--   mapM = mapMOf traverse
--   
-- --
--   'mapMOf ::            Iso a b c d       -> (c -> m d) -> a -> m b
--   'mapMOf ::            Lens a b c d      -> (c -> m d) -> a -> m b
--   'mapMOf :: Monad m => Traversal a b c d -> (c -> m d) -> a -> m b
--   
mapMOf :: LensLike (WrappedMonad m) a b c d -> (c -> m d) -> a -> m b -- |
--   forM = forMOf traverse
--   forMOf l = flip (mapMOf l)
--   
-- --
--   forMOf ::            Iso a b c d       -> a -> (c -> m d) -> m b
--   forMOf ::            Lens a b c d      -> a -> (c -> m d) -> m b
--   forMOf :: Monad m => Traversal a b c d -> a -> (c -> m d) -> m b
--   
forMOf :: LensLike (WrappedMonad m) a b c d -> a -> (c -> m d) -> m b -- |
--   sequence = sequenceOf traverse
--   sequenceOf l = mapMOf l id
--   sequenceOf l = unwrapMonad . l WrapMonad
--   
-- --
--   sequenceOf ::            Iso a b (m c) c       -> a -> m b
--   sequenceOf ::            Lens a b (m c) c      -> a -> m b
--   sequenceOf :: Monad m => Traversal a b (m c) c -> a -> m b
--   
sequenceOf :: LensLike (WrappedMonad m) a b (m c) c -> a -> m b -- | This generalizes transpose to an arbitrary Traversal. -- -- Note: transpose handles ragged inputs more intelligently, but -- for non-ragged inputs: -- --
--   transpose = transposeOf traverse
--   
-- --
--   >>> transposeOf traverse [[1,2,3],[4,5,6]]
--   [[1,4],[2,5],[3,6]]
--   
-- -- 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 a b [c] c -> a -> [b] -- | Generalized mapAccumL to an arbitrary Traversal. -- --
--   mapAccumL = mapAccumLOf traverse
--   
-- -- mapAccumLOf accumulates state from left to right. -- --
--   mapAccumLOf :: Iso a b c d       -> (s -> c -> (s, d)) -> s -> a -> (s, b)
--   mapAccumLOf :: Lens a b c d      -> (s -> c -> (s, d)) -> s -> a -> (s, b)
--   mapAccumLOf :: Traversal a b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b)
--   
mapAccumLOf :: LensLike (Backwards (State s)) a b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b) -- | Generalizes mapAccumR to an arbitrary Traversal. -- --
--   mapAccumR = mapAccumROf traverse
--   
-- -- mapAccumROf accumulates state from right to left. -- --
--   mapAccumROf :: Iso a b c d       -> (s -> c -> (s, d)) -> s -> a -> (s, b)
--   mapAccumROf :: Lens a b c d      -> (s -> c -> (s, d)) -> s -> a -> (s, b)
--   mapAccumROf :: Traversal a b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b)
--   
mapAccumROf :: LensLike (State s) a b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b) -- | Permit the use of scanr1 over an arbitrary Traversal or -- Lens. -- --
--   scanr1 = scanr1Of traverse
--   
-- --
--   scanr1Of :: Iso a b c c       -> (c -> c -> c) -> a -> b
--   scanr1Of :: Lens a b c c      -> (c -> c -> c) -> a -> b
--   scanr1Of :: Traversal a b c c -> (c -> c -> c) -> a -> b
--   
scanr1Of :: LensLike (State (Maybe c)) a b c c -> (c -> c -> c) -> a -> b -- | Permit the use of scanl1 over an arbitrary Traversal or -- Lens. -- --
--   scanl1 = scanl1Of traverse
--   
-- --
--   scanr1Of :: Iso a b c c       -> (c -> c -> c) -> a -> b
--   scanr1Of :: Lens a b c c      -> (c -> c -> c) -> a -> b
--   scanr1Of :: Traversal a b c c -> (c -> c -> c) -> a -> b
--   
scanl1Of :: LensLike (Backwards (State (Maybe c))) a b c c -> (c -> c -> c) -> a -> b -- | Functors representing data structures that can be traversed from left -- to right. -- -- Minimal complete definition: traverse or sequenceA. -- -- 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: -- -- class (Functor t, Foldable t) => Traversable (t :: * -> *) traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) -- | This is the traversal that just doesn't return anything -- --
--   traverseNothing :: Applicative f => (c -> f d) -> a -> f a
--   
traverseNothing :: Traversal a a c d -- | A traversal is completely characterized by its behavior on the indexed -- Kleene store comonad. -- -- Cloning a Traversal is one way to make sure you arent 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 cloneTraversal :: Applicative f => ((c -> Kleene c d d) -> a -> Kleene c d b) -> (c -> f d) -> a -> f b -- |
--   type SimpleTraversal = Simple Traversal
--   
type SimpleTraversal a b = Traversal a a b b module Control.Lens.Iso -- | Isomorphim families can be composed with other lenses using either -- (.) and id from the Prelude or from Control.Category. -- However, if you compose them with each other using (.) from the -- Prelude, they will be dumbed down to a mere Lens. -- --
--   import Control.Category
--   import Prelude hiding ((.),id)
--   
-- --
--   type Iso a b c d = forall k f. (Isomorphic k, Functor f) => Overloaded k f a b c d
--   
type Iso a b c d = forall k f. (Isomorphic k, Functor f) => k (c -> f d) (a -> f b) -- | Build a simple isomorphism from a pair of inverse functions -- --
--   view (iso f g) = f
--   view (from (iso f g)) = g
--   set (isos f g) h = g . h . f
--   set (from (iso f g')) h = f . h . g
--   
-- --
--   iso :: (a -> b) -> (b -> a) -> Simple Iso a b
--   
iso :: (Isomorphic k, Functor f) => (a -> b) -> (b -> a) -> k (b -> f b) (a -> f a) -- | Build an isomorphism family from two pairs of inverse functions -- --
--   view (isos ac ca bd db) = ac
--   view (from (isos ac ca bd db)) = ca
--   set (isos ac ca bd db) cd = db . cd . ac
--   set (from (isos ac ca bd db')) ab = bd . ab . ca
--   
-- --
--   isos :: (a -> c) -> (c -> a) -> (b -> d) -> (d -> b) -> Iso a b c d
--   
isos :: (Isomorphic k, Functor f) => (a -> c) -> (c -> a) -> (b -> d) -> (d -> b) -> k (c -> f d) (a -> f b) -- | Based on ala from Conor McBride's work on Epigram. -- -- Mnemonically, au is a French contraction of à le. -- --
--   >>> :m + Control.Lens Data.Monoid.Lens Data.Foldable
--   
--   >>> au _sum foldMap [1,2,3,4]
--   10
--   
au :: Simple Iso a b -> ((a -> b) -> c -> b) -> c -> a -- | Based on ala' from Conor McBride's work on Epigram. -- -- Mnemonically, the German auf plays a similar role to à -- la, and the combinator is au with an extra function -- argument. auf :: Simple Iso a b -> ((d -> b) -> c -> b) -> (d -> a) -> c -> a -- | The opposite of working over a Setter is working under -- an Isomorphism. -- --
--   under = over . from
--   
-- --
--   under :: Iso a b c d -> (a -> b) -> (c -> d)
--   
under :: Isomorphism (c -> Mutator d) (a -> Mutator b) -> (a -> b) -> c -> d -- | Invert an isomorphism. -- -- Note to compose an isomorphism and receive an isomorphism in turn -- you'll need to use Category -- --
--   from (from l) = l
--   
-- -- If you imported . from Control.Category, then: -- --
--   from l . from r = from (r . l)
--   
from :: Isomorphic k => Isomorphism a b -> k b a -- | Convert from an Isomorphism back to any Isomorphic -- value. -- -- This is useful when you need to store an isomoprhism as a data type -- inside a container and later reconstitute it as an overloaded -- function. via :: Isomorphic k => Isomorphism a b -> k a b -- | A concrete data type for isomorphisms. -- -- This lets you place an isomorphism inside a container without using -- ImpredicativeTypes. data Isomorphism a b Isomorphism :: (a -> b) -> (b -> a) -> Isomorphism a b -- | Used to provide overloading of isomorphism application -- -- This is a Category with a canonical mapping to it from the -- category of isomorphisms over Haskell types. class Category k => Isomorphic k isomorphic :: Isomorphic k => (a -> b) -> (b -> a) -> k a b isomap :: Isomorphic k => ((a -> b) -> c -> d) -> ((b -> a) -> d -> c) -> k a b -> k c d -- | This isomorphism can be used to wrap or unwrap a value in Const -- --
--   x ^. _const = Const x
--   Const x ^. from _const = x
--   
_const :: Iso a b (Const a c) (Const b d) -- | This isomorphism can be used to wrap or unwrap a value in -- Identity. -- --
--   x^.identity = Identity x
--   Identity x ^. from identity = x
--   
identity :: Iso a b (Identity a) (Identity b) -- |
--   type SimpleIso = Simple Iso
--   
type SimpleIso a b = Iso a a b b module Control.Lens.IndexedLens -- | Every IndexedLens is a valid Lens and a valid -- IndexedTraversal. type IndexedLens i a b c d = forall f k. (Indexed i k, Functor f) => k (c -> f d) (a -> f b) -- | 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 a b c d      -> (i -> c -> f d) -> a -> f b
--   (%%@~) :: Functor f => IndexedTraversal i a b c d -> (i -> c -> f d) -> a -> f b
--   
-- -- In particular, it is often useful to think of this function as having -- one of these even more restrictive type signatures -- --
--   (%%@~) ::             IndexedLens i a b c d      -> (i -> c -> (e, d)) -> a -> (e, b)
--   (%%@~) :: Monoid e => IndexedTraversal i a b c d -> (i -> c -> (e, d)) -> a -> (e, b)
--   
(%%@~) :: Overloaded (Index i) f a b c d -> (i -> c -> f d) -> a -> f b -- | 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 a b c d -> (i -> c -> d) -> a -> (d, b)
--   (<%@~) :: Monoid d => IndexedTraversal i a b c d -> (i -> c -> d) -> a -> (d, b)
--   
(<%@~) :: Overloaded (Index i) ((,) d) a b c d -> (i -> c -> d) -> a -> (d, b) -- | 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 a m                IndexedLens i a a c d      -> (i -> c -> (e, d)) -> a -> m e
--   (%%@=) :: (MonadState a m, Monoid e) => IndexedTraversal i a a c d -> (i -> c -> (e, d)) -> a -> m e
--   
(%%@=) :: MonadState a m => Overloaded (Index i) ((,) e) a a c d -> (i -> c -> (e, d)) -> m e -- | 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 a m                IndexedLens i a a c d      -> (i -> c -> d) -> a -> m d
--   (<%@=) :: (MonadState a m, Monoid e) => IndexedTraversal i a a c d -> (i -> c -> d) -> a -> m d
--   
(<%@=) :: MonadState a m => Overloaded (Index i) ((,) d) a a c d -> (i -> c -> d) -> m d -- |
--   type SimpleIndexedLens i = Simple (IndexedLens i)
--   
type SimpleIndexedLens i a b = IndexedLens i a a b b module Control.Lens.IndexedTraversal -- | Every indexed traversal 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. type IndexedTraversal i a b c d = forall f k. (Indexed i k, Applicative f) => k (c -> f d) (a -> f 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 = itraverseOf . const = id
--   
-- --
--   itraverseOf :: IndexedLens i a b c d      -> (i -> c -> f d) -> a -> f b
--   itraverseOf :: IndexedTraversal i a b c d -> (i -> c -> f d) -> a -> f b
--   
itraverseOf :: Overloaded (Index i) f a b c d -> (i -> c -> f d) -> a -> f b -- | Traverse with an index (and the arguments flipped) -- --
--   forOf l a = iforOf l a . const
--   
-- --
--   iforOf = flip . itraverseOf
--   
-- --
--   iforOf :: IndexedLens i a b c d      -> a -> (i -> c -> f d) -> f b
--   iforOf :: IndexedTraversal i a b c d -> a -> (i -> c -> f d) -> f b
--   
iforOf :: Overloaded (Index i) f a b c d -> a -> (i -> c -> f d) -> f b -- | 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 = imapMOf . const
--   
-- --
--   imapMOf :: Monad m => IndexedLens      i a b c d -> (i -> c -> m d) -> a -> m b
--   imapMOf :: Monad m => IndexedTraversal i a b c d -> (i -> c -> m d) -> a -> m b
--   
imapMOf :: Overloaded (Index i) (WrappedMonad m) a b c d -> (i -> c -> m d) -> a -> m b -- | 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 a b c d      -> a -> (i -> c -> m d) -> m b
--   iforMOf :: Monad m => IndexedTraversal i a b c d -> a -> (i -> c -> m d) -> m b
--   
iforMOf :: Overloaded (Index i) (WrappedMonad m) a b c d -> a -> (i -> c -> m d) -> m b -- | 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 a b c d      -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)
--   imapAccumROf :: IndexedTraversal i a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)
--   
imapAccumROf :: Overloaded (Index i) (State s) a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b) -- | 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 a b c d      -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)
--   imapAccumLOf :: IndexedTraversal i a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)
--   
imapAccumLOf :: Overloaded (Index i) (Backwards (State s)) a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b) -- |
--   type SimpleIndexedTraversal i = Simple (IndexedTraversal i)
--   
type SimpleIndexedTraversal i a b = IndexedTraversal i a a b b module Data.Map.Lens -- | This Lens can be used to read, write or delete the value -- associated with a key in a Map. -- --
--   >>> :m + Control.Lens Data.Map.Lens
--   
-- --
--   >>> Map.fromList [("hello",12)] ^.at "hello"
--   Just 12
--   
-- --
--   >>> at 10 .~ Just "hello" $ Map.empty
--   fromList [(10,"hello")]
--   
-- --
--   at :: Ord k => k -> (Maybe v -> f (Maybe v)) -> Map k v -> f (Map k v)
--   
at :: Ord k => k -> SimpleIndexedLens k (Map k v) (Maybe v) -- | Traversal of a Map indexed by the key. traverseMap :: IndexedTraversal k (Map k v) (Map k v') v v' -- | Traverse the value at a given key in a Map -- --
--   traverseAt :: (Applicative f, Ord k) => k -> (v -> f v) -> Map k v -> f (Map k v)
--   traverseAt k = valueAt k . traverse
--   
traverseAt :: Ord k => k -> SimpleIndexedTraversal k (Map k v) v -- | Traverse the value at the minimum key in a Map. -- -- The key of the minimum element is available as the index of the -- traversal. traverseAtMin :: SimpleIndexedTraversal k (Map k v) v -- | Traverse the value at the maximum key in a Map. -- -- The key of the maximum element is available as the index of the -- traversal. traverseAtMax :: SimpleIndexedTraversal k (Map k v) v module Control.Lens.IndexedSetter -- | Every IndexedSetter is a valid Setter -- -- The Setter laws are still required to hold. type IndexedSetter i a b c d = forall f k. (Indexed i k, Settable f) => k (c -> f d) (a -> f b) -- | Map with index. -- -- 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 a b c d    -> (i -> c -> d) -> a -> b
--   imapOf :: IndexedLens i a b c d      -> (i -> c -> d) -> a -> b
--   imapOf :: IndexedTraversal i a b c d -> (i -> c -> d) -> a -> b
--   
imapOf :: Overloaded (Index i) Mutator a b c d -> (i -> c -> d) -> a -> b -- | Adjust every target of an IndexedSetter, IndexedLens or -- IndexedTraversal with access to the index. -- --
--   (%@~) = imapOf
--   
-- -- 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 a b c d    -> (i -> c -> d) -> a -> b
--   (%@~) :: IndexedLens i a b c d      -> (i -> c -> d) -> a -> b
--   (%@~) :: IndexedTraversal i a b c d -> (i -> c -> d) -> a -> b
--   
(%@~) :: Overloaded (Index i) Mutator a b c d -> (i -> c -> d) -> a -> b -- | 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 a m => IndexedSetter i a a c d    -> (i -> c -> d) -> m ()
--   (%@=) :: MonadState a m => IndexedLens i a a c d      -> (i -> c -> d) -> m ()
--   (%@=) :: MonadState a m => IndexedTraversal i a b c d -> (i -> c -> d) -> m ()
--   
(%@=) :: MonadState a m => Overloaded (Index i) Mutator a a c d -> (i -> c -> d) -> m () -- |
--   type SimpleIndexedSetter i = Simple (IndexedSetter i)
--   
type SimpleIndexedSetter i a b = IndexedSetter i a a b b -- | Corepresentable endofunctors represented by their polymorphic lenses -- -- The polymorphic lenses of the form (forall x. Lens (f x) -- x) each represent a distinct path into a functor f. If -- the functor is entirely characterized by assigning values to these -- paths, then the functor is representable. -- -- Consider the following example. -- --
--   import Control.Lens
--   import Data.Distributive
--   
-- --
--   data Pair a = Pair { _x :: a, _y :: a }
--   
-- --
--   makeLenses ''Pair
--   
-- --
--   instance Representable Pair where
--     rep f = Pair (f x) (f y)
--   
-- -- From there, you can get definitions for a number of instances for -- free. -- --
--   instance Applicative Pair where
--     pure  = pureRep
--     (<*>) = apRep
--   
-- --
--   instance Monad Pair where
--     return = pureRep
--     (>>=) = bindRep
--   
-- --
--   instance Distributive Pair where
--     distribute = distributeRep
--   
module Control.Lens.Representable -- | Representable Functors. -- -- A Functor f is Representable if it is -- isomorphic to (x -> a) for some x. Nearly all such -- functors can be represented by choosing x to be the set of -- lenses that are polymorphic in the contents of the Functor, -- that is to say x = Rep f is a valid choice of -- x for (nearly) every Representable Functor. -- -- Note: Some sources refer to covariant representable functors as -- corepresentable functors, and leave the "representable" name to -- contravariant functors (those are isomorphic to (a -> x) -- for some x). -- -- As the covariant case is vastly more common, and both are often -- referred to as representable functors, we choose to call these -- functors Representable here. class Functor f => Representable f rep :: Representable f => (Rep f -> a) -> f a -- | The representation of a Representable Functor as Lenses type Rep f = forall a. Simple Lens (f a) a -- | fmapRep is a valid default definition for fmap for a -- Representable functor. -- --
--   fmapRep f m = rep $ i -> f (m ^. i)
--   
-- -- Usage for a Representable Foo: -- --
--   instance Functor Foo where
--     fmap = fmapRep
--   
fmapRep :: Representable f => (a -> b) -> f a -> f b -- | pureRep is a valid default definition for pure and -- return for a Representable functor. -- --
--   pureRep = rep . const
--   
-- -- Usage for a Representable Foo: -- --
--   instance Applicative Foo where
--     pure = pureRep
--     ...
--   
-- --
--   instance Monad Foo where
--     return = pureRep
--     ...
--   
pureRep :: Representable f => a -> f a -- | apRep is a valid default definition for (<*>) for -- a Representable functor. -- --
--   apRep mf ma = rep $ i -> mf ^. i $ ma ^. i
--   
-- -- Usage for a Representable Foo: -- --
--   instance Applicative Foo where
--     pure = pureRep
--     (<*>) = apRep
--   
apRep :: Representable f => f (a -> b) -> f a -> f b -- | bindRep is a valid default default definition for '(>>=)' -- for a representable functor. -- --
--   bindRep m f = rep $ i -> f (m ^. i) ^. i
--   
-- -- Usage for a Representable Foo: -- --
--   instance Monad Foo where
--     return = pureRep
--     (>>=) = bindRep
--   
bindRep :: Representable f => f a -> (a -> f b) -> f b -- | A default definition for distribute for a Representable -- Functor -- --
--   distributeRep wf = rep $ i -> fmap (^. i) wf
--   
-- -- Usage for a Representable Foo: -- --
--   instance Distributive Foo where
--     distribute = distributeRep
--   
distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a) -- | Sometimes you need to store a path lens into a container, but at least -- at this time, ImpredicativePolymorphism in GHC is somewhat -- lacking. -- -- This type provides a way to, say, store a [] of polymorphic -- lenses. newtype Path f Path :: Rep f -> Path f walk :: Path f -> Rep f -- | A Representable Functor has a fixed shape. This fills -- each position in it with a Path paths :: Representable f => f (Path f) -- | A version of rep that is an isomorphism. Predicativity requires -- that we wrap the Rep as a Key, however. tabulated :: (Isomorphic k, Representable f) => k (Path f -> a) (f a) -- | Map over a Representable functor with access to the Lens -- for the current position -- --
--   mapWithRep f m = rep $ i -> f i (m ^. i)
--   
mapWithRep :: Representable f => (Rep f -> a -> b) -> f a -> f b -- | Fold over a Representable functor with access to the current -- path as a Lens, yielding a Monoid foldMapWithRep :: (Representable f, Foldable f, Monoid m) => (Rep f -> a -> m) -> f a -> m -- | Fold over a Representable functor with access to the current -- path as a Lens. foldrWithRep :: (Representable f, Foldable f) => (Rep f -> a -> b -> b) -> b -> f a -> b -- | Traverse a Representable functor with access to the current -- path traverseWithRep :: (Representable f, Traversable f, Applicative g) => (Rep f -> a -> g b) -> f a -> g (f b) -- | Traverse a Representable functor with access to the current -- path as a Lens, discarding the result traverseWithRep_ :: (Representable f, Foldable f, Applicative g) => (Rep f -> a -> g b) -> f a -> g () -- | Traverse a Representable functor with access to the current -- path and a Lens (and the arguments flipped) forWithRep :: (Representable f, Traversable f, Applicative g) => f a -> (Rep f -> a -> g b) -> g (f b) -- | mapM over a Representable functor with access to the -- current path as a Lens mapMWithRep :: (Representable f, Traversable f, Monad m) => (Rep f -> a -> m b) -> f a -> m (f b) -- | mapM over a Representable functor with access to the -- current path as a Lens, discarding the result mapMWithRep_ :: (Representable f, Foldable f, Monad m) => (Rep f -> a -> m b) -> f a -> m () -- | mapM over a Representable functor with access to the -- current path as a Lens (with the arguments flipped) forMWithRep :: (Representable f, Traversable f, Monad m) => f a -> (Rep f -> a -> m b) -> m (f b) instance Eq e => Representable ((->) e) instance Representable Identity module Control.Lens.Tuple -- | Provides access to 1st field of a tuple. class Field1 a b c d | a -> c, b -> d, a d -> b, b c -> a _1 :: Field1 a b c d => Lens a b c d -- | Provides access to the 2nd field of a tuple class Field2 a b c d | a -> c, b -> d, a d -> b, b c -> a _2 :: Field2 a b c d => Lens a b c d -- | Provides access to the 3rd field of a tuple class Field3 a b c d | a -> c, b -> d, a d -> b, b c -> a _3 :: Field3 a b c d => Lens a b c d -- | Provide access to the 4th field of a tuple class Field4 a b c d | a -> c, b -> d, a d -> b, b c -> a _4 :: Field4 a b c d => Lens a b c d -- | Provides access to the 5th field of a tuple class Field5 a b c d | a -> c, b -> d, a d -> b, b c -> a _5 :: Field5 a b c d => Lens a b c d -- | Provides access to the 6th element of a tuple class Field6 a b c d | a -> c, b -> d, a d -> b, b c -> a _6 :: Field6 a b c d => Lens a b c d -- | Provide access to the 7th field of a tuple class Field7 a b c d | a -> c, b -> d, a d -> b, b c -> a _7 :: Field7 a b c d => Lens a b c d -- | Provide access to the 8th field of a tuple class Field8 a b c d | a -> c, b -> d, a d -> b, b c -> a _8 :: Field8 a b c d => Lens a b c d -- | Provides access to the 9th field of a tuple class Field9 a b c d | a -> c, b -> d, a d -> b, b c -> a _9 :: Field9 a b c d => Lens a b c d 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 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' 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 focus this can change the environment of -- a deeply nested monad transformer. -- -- Also, unlike focus, this can be used with any valid -- Getter, but cannot be used with a Traversal or -- Fold. class (MonadReader b m, MonadReader a n) => Magnify m n k b a | m -> b, n -> a, m a -> n, n b -> m magnify :: Magnify m n k b a => ((b -> k c b) -> a -> k c a) -> 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 (MonadState s m, MonadState t n) => Zoom m n k s t | m -> s k, n -> t k, m t -> n, n s -> m zoom :: (Zoom m n k s t, Monad m) => SimpleLensLike (k c) t s -> m c -> n c instance Magnify m n k b a => Magnify (IdentityT m) (IdentityT n) k b a instance (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) (EffectRWS w s m) b a instance (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) (EffectRWS w s m) b a instance Magnify ((->) b) ((->) a) Accessor b a instance Monad m => Magnify (ReaderT b m) (ReaderT a m) (Effect m) b a instance (Error e, Zoom m n k s t) => Zoom (ErrorT e m) (ErrorT e n) (FocusingErr e k) s t instance Zoom m n k s t => Zoom (MaybeT m) (MaybeT n) (FocusingMay k) s t instance Zoom m n k s t => Zoom (ListT m) (ListT n) (FocusingOn [] k) s t instance (Monoid w, Zoom m n k s t) => Zoom (WriterT w m) (WriterT w n) (FocusingPlus w k) s t instance (Monoid w, Zoom m n k s t) => Zoom (WriterT w m) (WriterT w n) (FocusingPlus w k) s t instance (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) (FocusingWith w z) s t instance (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) (FocusingWith w z) s t instance Zoom m n k s t => Zoom (IdentityT m) (IdentityT n) k s t instance Zoom m n k s t => Zoom (ReaderT e m) (ReaderT e n) k s t instance Monad z => Zoom (StateT s z) (StateT t z) (Focusing z) s t instance Monad z => Zoom (StateT s z) (StateT t z) (Focusing z) s t module Data.Set.Lens -- | This Lens can be used to read, write or delete a member of a -- Set -- --
--   >>> :m + Data.Set.Lens Control.Lens
--   
--   >>> contains 3 .~ False $ Set.fromList [1,2,3,4]
--   fromList [1,2,4]
--   
-- --
--   contains :: Ord k => k -> (Bool -> f Bool) -> Set k -> f (Set k)
--   
contains :: Ord k => k -> Simple Lens (Set k) Bool -- | 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 setmap. -- --
--   >>> :m + Data.Set.Lens Control.Lens
--   
--   >>> over setmapped (+1) (fromList [1,2,3,4])
--   fromList [2,3,4,5]
--   
setmapped :: (Ord i, Ord j) => Setter (Set i) (Set j) i j -- | Construct a set from a Getter, Fold, -- Traversal, Lens or Iso. -- --
--   >>> :m + Data.Set.Lens Control.Lens
--   
--   >>> setOf (folded._2) [("hello",1),("world",2),("!!!",3)]
--   fromList [1,2,3]
--   
-- --
--   setOf ::          Getter a c           -> a -> Set c
--   setOf :: Ord c => Fold a c             -> a -> Set c
--   setOf ::          Simple Iso a c       -> a -> Set c
--   setOf ::          Simple Lens a c      -> a -> Set c
--   setOf :: Ord c => Simple Traversal a c -> a -> Set c
--   
setOf :: Getting (Set c) a c -> a -> Set c -- | Lenses and Traversals for working with Template Haskell module Language.Haskell.TH.Lens -- | Has a Name class HasName t name :: HasName t => Simple Lens t Name -- | Provides for the extraction of free type variables, and alpha -- renaming. class HasTypeVars t typeVarsEx :: HasTypeVars t => Set Name -> Simple 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 => Simple 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 :: Simple Traversal Con StrictType instance SubstType Pred instance SubstType t => SubstType [t] instance SubstType Type instance HasTypeVars t => HasTypeVars [t] instance HasTypeVars Pred instance HasTypeVars Type instance HasTypeVars Name instance HasTypeVars TyVarBndr instance HasName Con instance HasName Name instance HasName TyVarBndr module Control.Lens.TH -- | This configuration describes the options we'll be using to make -- isomorphisms or lenses data LensRules LensRules :: (String -> Maybe String) -> (String -> Maybe String) -> (String -> Maybe (String, String)) -> Set LensFlag -> LensRules -- | Lens to access the convention for naming top level isomorphisms in our -- lens rules -- -- Defaults to lowercasing the first letter of the constructor. lensIso :: Simple Lens LensRules (String -> Maybe String) -- | Lens to access the convention for naming fields in our lens rules -- -- Defaults to stripping the _ off of the field name and lowercasing the -- name and rejecting the field if it doesn't start with an '_'. lensField :: Simple Lens LensRules (String -> Maybe String) -- | Retrieve options such as the name of the class and method to put in it -- to build a class around monomorphic data types. lensClass :: Simple Lens LensRules (String -> Maybe (String, String)) -- | Retrieve options such as the name of the class and method to put in it -- to build a class around monomorphic data types. lensFlags :: Simple Lens LensRules (Set LensFlag) -- | Flags for lens construction data LensFlag SimpleLenses :: LensFlag SingletonAndField :: LensFlag SingletonIso :: LensFlag HandleSingletons :: LensFlag SingletonRequired :: LensFlag CreateClass :: LensFlag CreateInstance :: LensFlag ClassRequired :: LensFlag -- | Only Generate valid Simple Lens lenses simpleLenses :: Simple Lens LensRules Bool -- | Handle singleton constructors specially handleSingletons :: Simple Lens LensRules Bool -- | Use Iso for singleton constructors singletonIso :: Simple Lens LensRules Bool -- | Expect a single constructor, single field newtype or data type. singletonRequired :: Simple Lens LensRules Bool -- | Create the class if the constructor is simple and the lensClass -- rule matches createClass :: Simple Lens LensRules Bool -- | Create the instance if the constructor is simple and the -- lensClass rule matches createInstance :: Simple Lens LensRules Bool -- | Die if the lensClass fails to match classRequired :: Simple Lens LensRules Bool -- | Make 'classy lenses' for a type -- --
--   makeClassy = makeLensesWith classyRules
--   
makeClassy :: Name -> Q [Dec] -- | Derive lenses, specifying explicit pairings of (fieldName, -- lensName) using a wrapper class. -- -- Example usage: -- --
--   makeClassyFor "HasFoo" "foo" [("_foo", "fooLens"), ("bar", "lbar")] ''Foo
--   
makeClassyFor :: String -> String -> [(String, String)] -> Name -> Q [Dec] -- | Make a top level isomorphism injecting _into_ the type -- -- The supplied name is required to be for a type with a single -- constructor that has a single argument -- --
--   makeIso = makeLensesWith isoRules
--   
makeIso :: Name -> Q [Dec] -- | Build lenses with a sensible default configuration -- --
--   makeLenses = makeLensesWith lensRules
--   
makeLenses :: Name -> Q [Dec] -- | Derive lenses, specifying explicit pairings of (fieldName, -- lensName). -- -- Example usage: -- --
--   makeLensesFor [("_foo", "fooLens"), ("bar", "lbar")] ''Foo
--   
makeLensesFor :: [(String, String)] -> Name -> Q [Dec] -- | Build lenses with a custom configuration makeLensesWith :: LensRules -> Name -> Q [Dec] -- | Rules for making fairly simple lenses, ignoring the special cases for -- isomorphisms, and not making any classes. lensRules :: LensRules -- | Rules for making lenses that precompose another lens. classyRules :: LensRules -- | Rules for making an isomorphism from a data type isoRules :: LensRules -- | Default lens rules defaultRules :: LensRules instance Eq LensFlag instance Ord LensFlag instance Show LensFlag instance Read LensFlag -- | Usage: -- -- You can derive lenses automatically for many data types: -- --
--   import Control.Lens
--   data Foo a = Foo { _fooArgs :: [String], _fooValue :: a }
--   makeLenses ''Foo
--   
-- -- This defines the following lenses: -- --
--   fooArgs :: Simple Lens (Foo a) [String]
--   fooValue :: Lens (Foo a) (Foo b) a b
--   
-- -- You can then access the value with (^.) and set the value of -- the field with (.~) and can 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 module Control.Exception.Lens -- | Traverse the strongly typed Exception contained in -- SomeException where the type of your function matches the -- desired Exception. -- --
--   traverseException :: (Applicative f, Exception a, Exception b)
--                     => (a -> f b) -> SomeException -> f SomeException
--   
traverseException :: (Exception a, Exception b) => Traversal SomeException SomeException a b module Data.Bits.Lens -- | Bitwise .|. the target(s) of a Lens or Setter -- --
--   >>> _2 |~ 6 $ ("hello",3)
--   ("hello",7)
--   
-- --
--   (|~) :: Bits c => Setter a b c c -> c -> a -> b
--   (|~) :: Bits c => Iso a b c c -> c -> a -> b
--   (|~) :: Bits c => Lens a b c c -> c -> a -> b
--   (|~) :: ('Monoid c', Bits c) => Traversal a b c c -> c -> a -> b
--   
(|~) :: Bits c => Setting a b c c -> c -> a -> b -- | Bitwise .&. the target(s) of a Lens or Setter -- --
--   >>> _2 &~ 7 $ ("hello",254)
--   ("hello",6)
--   
-- --
--   (&~) :: Bits c => Setter a b c c -> c -> a -> b
--   (&~) :: Bits c => Iso a b c c -> c -> a -> b
--   (&~) :: Bits c => Lens a b c c -> c -> a -> b
--   (&~) :: ('Monoid c', Bits c) => Traversal a b c c -> c -> a -> b
--   
(&~) :: Bits c => Setting a b c c -> c -> a -> b -- | 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 c => Iso a b c c -> c -> a -> (c, b)
--   (<|~) :: Bits c => Lens a b c c -> c -> a -> (c, b)
--   (<|~) :: (Bits c, 'Monoid c) => Traversal a b c c -> c -> a -> (c, b)
--   
(<|~) :: Bits c => LensLike ((,) c) a b c c -> c -> a -> (c, b) -- | 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 c => Iso a b c c -> c -> a -> (c, b)
--   (<&~) :: Bits c => Lens a b c c -> c -> a -> (c, b)
--   (<&~) :: (Bits c, 'Monoid c) => Traversal a b c c -> c -> a -> (c, b)
--   
(<&~) :: Bits c => LensLike ((,) c) a b c c -> c -> a -> (c, b) -- | Modify the target(s) of a Simple Lens, Setter or -- Traversal by computing its bitwise .|. with another -- value. -- --
--   (|=):: (MonadState a m, Bits b) => Simple Setter a b -> b -> m ()
--   (|=):: (MonadState a m, Bits b) => Simple Iso a b -> b -> m ()
--   (|=):: (MonadState a m, Bits b) => Simple Lens a b -> b -> m ()
--   (|=):: (MonadState a m, Bits b) => Simple Traversal a b -> b -> m ()
--   
(|=) :: (MonadState a m, Bits b) => Simple Setting a b -> b -> m () -- | Modify the target(s) of a Simple Lens, Setter or -- Traversal by computing its bitwise .&. with another -- value. -- --
--   (&=):: (MonadState a m, Bits b) => Simple Setter a b -> b -> m ()
--   (&=):: (MonadState a m, Bits b) => Simple Iso a b -> b -> m ()
--   (&=):: (MonadState a m, Bits b) => Simple Lens a b -> b -> m ()
--   (&=):: (MonadState a m, Bits b) => Simple Traversal a b -> b -> m ()
--   
(&=) :: (MonadState a m, Bits b) => Simple Setting a b -> b -> m () -- | Modify the target(s) of a Simple Lens, (or -- Traversal) by computing its bitwise .|. with another -- value, returning the result (or a monoidal summary of all of the -- results traversed) -- --
--   (<|=) :: (MonadState a m, Bits b) => Simple Lens a b -> b -> m b
--   (<|=) :: (MonadState a m, Bits b, Monoid b) => Simple Traversal a b -> b -> m b
--   
(<|=) :: (MonadState a m, Bits b) => SimpleLensLike ((,) b) a b -> b -> m b -- | Modify the target(s) of a Simple Lens (or -- Traversal) by computing its bitwise .&. with another -- value, returning the result (or a monoidal summary of all of the -- results traversed) -- --
--   (<&=) :: (MonadState a m, Bits b) => Simple Lens a b -> b -> m b
--   (<&=) :: (MonadState a m, Bits b, Monoid b) => Simple Traversal a b -> b -> m b
--   
(<&=) :: (MonadState a m, Bits b) => SimpleLensLike ((,) b) a b -> b -> m b -- | 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
--   
bitAt :: Bits b => Int -> SimpleIndexedLens Int b Bool -- | Traverse over all bits in a numeric type. -- -- The bit position is available as the index. -- --
--   >>> import Data.Word
--   
--   >>> toListOf traverseBits (5 :: Word8)
--   [True,False,True,False,False,False,False,False]
--   
-- -- If you supply this an Integer, the result will be an infinite -- Traversal that can be productively consumed. traverseBits :: Bits b => SimpleIndexedTraversal Int b Bool module Data.Complex.Lens -- | Access the realPart of a Complex number -- --
--   real :: Functor f => (a -> f a) -> Complex a -> f (Complex a)
--   
real :: Simple Lens (Complex a) a -- | Access the imaginaryPart of a Complex number -- --
--   imaginary :: Functor f => (a -> f a) -> Complex a -> f (Complex a)
--   
imaginary :: Simple 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. So don't do that! -- -- Otherwise, this is a perfectly cromulent Lens. polarize :: (RealFloat a, RealFloat b) => Iso (Complex a) (Complex b) (a, a) (b, b) -- | Traverse both the real and imaginary parts of a Complex number. -- --
--   traverseComplex :: Applicative f => (a -> f b) -> Complex a -> f (Complex b)
--   
traverseComplex :: Traversal (Complex a) (Complex b) a b module Data.Dynamic.Lens -- | Traverse the typed value contained in a Dynamic where the type -- required by your function matches that of the contents of the -- Dynamic. -- --
--   traverseDynamic :: (Applicative f, Typeable a, Typeable b) => (a -> f b) -> Dynamic -> f Dynamic
--   
traverseDynamic :: (Typeable a, Typeable b) => Traversal Dynamic Dynamic a b -- | Lenses for working with sums module Data.Either.Lens -- | A traversal for tweaking the left-hand value of an Either: -- --
--   traverseLeft :: Applicative f => (a -> f b) -> Either a c -> f (Either b c)
--   
traverseLeft :: Traversal (Either a c) (Either b c) a b -- | traverse the right-hand value of an Either: -- --
--   traverseRight = traverse
--   
-- -- Unfortunately the instance for Traversable (Either -- c) is still missing from base, so this can't just be -- traverse -- --
--   traverseRight :: Applicative f => (a -> f b) -> Either c a -> f (Either c a)
--   
traverseRight :: Traversal (Either c a) (Either c b) a b -- | Traversals for manipulating parts of a list. module Data.List.Lens -- | A lens reading and writing to the head of a non-empty list -- --
--   >>> [1,2,3]^._head
--   1
--   
_head :: Simple Lens [a] a -- | A lens reading and writing to the tail of a non-empty list -- --
--   >>> _tail .~ [3,4,5] $ [1,2]
--   [1,3,4,5]
--   
_tail :: Simple Lens [a] [a] -- | A lens reading and writing to the last element of a non-empty -- list -- --
--   >>> [1,2]^._last
--   2
--   
_last :: Simple Lens [a] a -- | A lens reading and replacing all but the a last element of a -- non-empty list -- --
--   >>> [1,2,3,4]^._init
--   [1,2,3]
--   
_init :: Simple Lens [a] [a] -- | Obtain a version of the list with the supplied value interspersed. -- --
--   >>> "abcde"^.interspersed ','
--   "a,b,c,d,e"
--   
-- --
--   xs^.interspersed a = intersperse a xs
--   
interspersed :: a -> Getter [a] [a] -- | Obtain a version of the list with the supplied value intercalated intercalated :: [a] -> Getter [[a]] [a] -- | Indexed traversal of a list. The position in the list is available as -- the index. traverseList :: IndexedTraversal Int [a] [b] a b -- | The traversal for reading and writing to the head of a list -- -- The position of the head in the original list (0) is available as the -- index. -- --
--   >>> traverseHead +~ 1 $ [1,2,3]
--   [2,2,3]
--   
-- --
--   traverseHead :: Applicative f => (a -> f a) -> [a] -> f [a]
--   
traverseHead :: SimpleIndexedTraversal Int [a] a -- | Traversal for editing the tail of a list. -- -- The position of each element in the original list is available -- as the index. -- --
--   >>> traverseTail +~ 1 $ [1,2,3]
--   [1,3,4]
--   
-- --
--   traverseTail :: Applicative f => (a -> f a) -> [a] -> f [a]
--   
traverseTail :: SimpleIndexedTraversal Int [a] a -- | Traverse all but the last element of a list -- -- The position of each element is available as the index. -- --
--   >>> traverseInit +~ 1 $ [1,2,3]
--   [2,3,3]
--   
-- --
--   traverseInit :: Applicative f => (a -> f a) -> [a] -> f [a]
--   
traverseInit :: SimpleIndexedTraversal Int [a] a -- | Traverse the last element in a list. -- -- The position of the last element in the original list is available as -- the index. -- --
--   >>> traverseLast +~ 1 $ [1,2,3]
--   [1,2,4]
--   
-- --
--   traverseLast :: Applicative f => (a -> f a) -> [a] -> f [a]
--   
traverseLast :: SimpleIndexedTraversal Int [a] a -- | Lenses for working with products. -- -- Due to their ubiquity, _1 and _2 are defined in -- Control.Lens. module Data.Pair.Lens -- | Traverse both parts of a tuple with matching types. both :: Traversal (a, a) (b, b) a b -- | This provides a Traversal that checks a predicate on a key -- before allowing you to traverse into a value. value :: (k -> Bool) -> SimpleIndexedTraversal k (k, v) v module Data.IntMap.Lens -- | This Lens can be used to read, write or delete the value -- associated with a key in an IntMap. -- --
--   >>> fromList [(1,"hello")] ^.at 1
--   Just "hello"
--   
-- --
--   >>> at 1 .~ Just "hello" $ IntMap.empty
--   fromList [(1,"hello")]
--   
-- --
--   at :: Int -> (Maybe v -> f (Maybe v)) -> IntMap v -> f (IntMap v)
--   
at :: Int -> SimpleIndexedLens Int (IntMap v) (Maybe v) -- | Traversal of an IntMap indexed by the key. traverseIntMap :: IndexedTraversal Int (IntMap v) (IntMap v') v v' -- | Traverse the value at a given key in an IntMap -- --
--   traverseAt :: Applicative f => Int -> (v -> f v) -> IntMap v -> f (IntMap v)
--   traverseAt k = at k . traverse
--   
traverseAt :: Int -> SimpleIndexedTraversal Int (IntMap v) v -- | Traverse the value at the minimum key in a Map -- -- The key of the minimum element is available as the index. traverseAtMin :: SimpleIndexedTraversal Int (IntMap v) v -- | Traverse the value at the maximum key in a Map traverseAtMax :: SimpleIndexedTraversal Int (IntMap v) v module Data.IntSet.Lens -- | This Lens can be used to read, write or delete a member of an -- IntSet -- --
--   ghci> contains 3 +~ False $ fromList [1,2,3,4]
--   fromList [1,2,4]
--   
-- --
--   contains :: Functor f => Int -> (Bool -> f Bool) -> IntSet -> f IntSet
--   
contains :: Int -> Simple Lens IntSet Bool -- | 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 setmap. -- --
--   >>> over setmapped (+1) (fromList [1,2,3,4])
--   fromList [2,3,4,5]
--   
setmapped :: Simple Setter IntSet Int -- | Construct an IntSet from a Getter, Fold, -- Traversal, Lens or Iso. -- --
--   >>> :m + Data.IntSet.Lens Control.Lens
--   
--   >>> setOf (folded._2) [("hello",1),("world",2),("!!!",3)]
--   fromList [1,2,3]
--   
-- --
--   setOf :: Getter a Int           -> a -> IntSet
--   setOf :: Fold a Int             -> a -> IntSet
--   setOf :: Simple Iso a Int       -> a -> IntSet
--   setOf :: Simple Lens a Int      -> a -> IntSet
--   setOf :: Simple Traversal a Int -> a -> IntSet
--   
setOf :: Getting IntSet a Int -> a -> IntSet module Data.Monoid.Lens -- | Modify the target of a monoidally valued by mappending another -- value. -- --
--   >>> :m + Control.Lens Data.Pair.Lens
--   
--   >>> both <>~ "!!!" $ ("hello","world")
--   ("hello!!!","world!!!")
--   
-- --
--   (~) :: Monoid c => Setter a b c c -> c -> a -> b
--   (~) :: Monoid c => Iso a b c c -> c -> a -> b
--   (~) :: Monoid c => Lens a b c c -> c -> a -> b
--   (~) :: Monoid c => Traversal a b c c -> c -> a -> b
--   
(<>~) :: Monoid c => Setting a b c c -> c -> a -> 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) a b m m -> m -> a -> (m, b) -- | Modify the target(s) of a Simple Lens, Iso, -- Setter or Traversal by mappending a value. -- --
--   (=) :: (MonadState a m, Monoid b) => Simple Setter a b -> b -> m ()
--   (=) :: (MonadState a m, Monoid b) => Simple Iso a b -> b -> m ()
--   (=) :: (MonadState a m, Monoid b) => Simple Lens a b -> b -> m ()
--   (=) :: (MonadState a m, Monoid b) => Simple Traversal a b -> b -> m ()
--   
(<>=) :: (MonadState a m, Monoid b) => SimpleSetting a b -> b -> m () -- | 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 a m, Monoid r) => SimpleLensLike ((,) r) a r -> r -> m r -- | Isomorphism for Dual _dual :: Iso a b (Dual a) (Dual b) -- | Isomorphism for Endo _endo :: Iso (a -> a) (b -> b) (Endo a) (Endo b) -- | Isomorphism for All -- --
--   >>> :m + Control.Lens Data.Monoid.Lens Data.Foldable
--   
--   >>> au _all foldMap [True,True]
--   True
--   
-- --
--   >>> :m + Control.Lens Data.Monoid.Lens Data.Foldable
--   
--   >>> au _all foldMap [True,False]
--   False
--   
_all :: Simple Iso Bool All -- | Isomorphism for Any -- --
--   >>> :m + Control.Lens Data.Monoid.Lens Data.Foldable
--   
--   >>> au _any foldMap [False,False]
--   False
--   
-- --
--   >>> :m + Control.Lens Data.Monoid.Lens Data.Foldable
--   
--   >>> au _any foldMap [True,False]
--   True
--   
_any :: Simple Iso Bool Any -- | Isomorphism for Sum -- --
--   >>> :m + Control.Lens Data.Monoid.Lens Data.Foldable
--   
--   >>> au _sum foldMap [1,2,3,4]
--   10
--   
_sum :: Iso a b (Sum a) (Sum b) -- | Isomorphism for Product -- --
--   >>> :m + Control.Lens Data.Monoid.Lens Data.Foldable
--   
--   >>> au _product foldMap [1,2,3,4]
--   24
--   
_product :: Iso a b (Product a) (Product b) -- | Isomorphism for First _first :: Iso (Maybe a) (Maybe b) (First a) (First b) -- | Isomorphism for Last _last :: Iso (Maybe a) (Maybe b) (Last a) (Last b) module Data.Sequence.Lens -- | A Lens that can access the nth element of a -- Seq. -- -- Note: This is only a legal lens if there is such an element! at :: Int -> SimpleIndexedLens Int (Seq a) a -- | A Seq is isomorphic to a ViewL -- --
--   viewl m = m^.viewL
--   
viewL :: Iso (Seq a) (Seq b) (ViewL a) (ViewL b) -- | A Seq is isomorphic to a ViewR -- --
--   viewr m = m^.viewR
--   
viewR :: Iso (Seq a) (Seq b) (ViewR a) (ViewR b) -- | Traverse the head of a Seq traverseHead :: SimpleIndexedTraversal Int (Seq a) a -- | Traverse the tail of a Seq traverseTail :: SimpleIndexedTraversal Int (Seq a) a -- | Traverse the last element of a Seq traverseLast :: SimpleIndexedTraversal Int (Seq a) a -- | Traverse all but the last element of a Seq traverseInit :: SimpleIndexedTraversal Int (Seq a) a -- | Traverse the first n elements of a Seq traverseTo :: Int -> SimpleIndexedTraversal Int (Seq a) a -- | Traverse all but the first n elements of a Seq traverseFrom :: Int -> SimpleIndexedTraversal Int (Seq a) a -- | Travere all the elements numbered from i to j of a -- Seq traverseSlice :: Int -> Int -> SimpleIndexedTraversal Int (Seq a) a module Data.Tree.Lens -- | A Lens that focuses on the root of a Tree. root :: Simple Lens (Tree a) a -- | A Traversal of the direct descendants of the root of a -- Tree indexed by its position in the list of children children :: SimpleIndexedTraversal Int (Tree a) (Tree a) module Data.Array.Lens -- | Access an element of an array. -- -- Note: The indexed element is assumed to exist in the target -- IArray. -- --
--   arr ! i = arr ^. ix i
--   
-- --
--   arr // [(i,e)] = ix i .~ e $ arr
--   
-- --
--   >>> ix 2 .~ 9 $ (listArray (1,5) [4,5,6,7,8] :: Array Int Int)
--   array (1,5) [(1,4),(2,9),(3,6),(4,7),(5,8)]
--   
ix :: (IArray a e, Ix i) => i -> Simple Lens (a i e) e -- | This setter can be used to derive a new IArray from an old -- array 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 = sets . 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) -> Setter (a j e) (a i e) i j -- | An IndexedTraversal of the elements of an IArray, using -- the index into the array as the index of the traversal. -- --
--   amap = over traverseArray
--   
traverseArray :: (IArray a c, IArray a d, Ix i) => IndexedTraversal i (a i c) (a i d) c d module System.FilePath.Lens -- | Modify the path by adding another path. -- --
--   >>> :m + Control.Lens Data.Pair.Lens
--   
--   >>> both </>~ "!!!" $ ("hello","world")
--   ("hello/!!!","world/!!!")
--   
-- --
--   (/~) :: Setter a b FilePath FilePath -> FilePath -> a -> b
--   (/~) :: Iso a b FilePath FilePath -> FilePath -> a -> b
--   (/~) :: Lens a b FilePath FilePath -> FilePath -> a -> b
--   (/~) :: Traversal a b FilePath FilePath -> FilePath -> a -> b
--   
(~) :: Setting a b FilePath FilePath -> FilePath -> a -> b -- | 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) a b FilePath FilePath -> FilePath -> a -> (FilePath, b) -- | Modify the path by adding extension. -- --
--   >>> :m + Control.Lens Data.Pair.Lens
--   
--   >>> both <.>~ "!!!" $ ("hello","world")
--   ("hello.!!!","world.!!!")
--   
-- --
--   (/~) :: Setter a b FilePath FilePath -> String -> a -> b
--   (/~) :: Iso a b FilePath FilePath -> String -> a -> b
--   (/~) :: Lens a b FilePath FilePath -> String -> a -> b
--   (/~) :: Traversal a b FilePath FilePath -> String -> a -> b
--   
(<.>~) :: Setting a b FilePath FilePath -> String -> a -> b -- | Add an extension 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) a b FilePath FilePath -> String -> a -> (FilePath, b) -- | Modify the target(s) of a Simple Lens, Iso, -- Setter or Traversal by adding a path. -- --
--   (/=) :: MonadState a m => Simple Setter a FilePath -> FilePath -> m ()
--   (/=) :: MonadState a m => Simple Iso a FilePath -> FilePath -> m ()
--   (/=) :: MonadState a m => Simple Lens a FilePath -> FilePath -> m ()
--   (/=) :: MonadState a m => Simple Traversal a FilePath -> FilePath -> m ()
--   
(=) :: MonadState a m => SimpleSetting a 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 a m => SimpleLensLike ((,) FilePath) a FilePath -> FilePath -> m FilePath -- | Modify the target(s) of a Simple Lens, Iso, -- Setter or Traversal by adding an extension. -- --
--   (.=) :: MonadState a m => Simple Setter a FilePath -> String -> m ()
--   (.=) :: MonadState a m => Simple Iso a FilePath -> String -> m ()
--   (.=) :: MonadState a m => Simple Lens a FilePath -> String -> m ()
--   (.=) :: MonadState a m => Simple Traversal a FilePath -> String -> m ()
--   
(<.>=) :: MonadState a m => SimpleSetting a FilePath -> String -> m () -- | Add an extension 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 a m => SimpleLensLike ((,) FilePath) a FilePath -> String -> m FilePath -- | A lens reading and writing to the basename. -- --
--   >>> _basename .~ "filename" $ "path/name.png"
--   "path/filename.png"
--   
_basename :: Simple Lens FilePath FilePath -- | A lens reading and writing to the directory. -- --
--   >>> "long/path/name.txt" ^. _directory
--   "long/path"
--   
_directory :: Simple Lens FilePath FilePath -- | A lens reading and writing to the extension. -- --
--   >>> _extension .~ ".png" $ "path/name.txt"
--   "path/name.png"
--   
_extension :: Simple Lens FilePath FilePath -- | A lens reading and writing to the full filename. -- --
--   >>> _filename .~ "name.txt" $ "path/name.png"
--   "path/name.txt"
--   
_filename :: Simple Lens FilePath FilePath module Data.ByteString.Lens -- | pack (or unpack) a list of bytes into a -- ByteString -- --
--   pack x = x ^. packedBytes
--   
-- --
--   unpack x = x ^. from packedBytes
--   
packedBytes :: Simple Iso [Word8] ByteString -- | Traverse each Word8 in a ByteString -- --
--   bytes = from packedBytes .> traverseList
--   
-- --
--   anyOf bytes (== 0x80) :: ByteString -> Bool
--   
bytes :: SimpleIndexedTraversal 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'. -- --
--   pack x = x ^. packedChars
--   
-- --
--   unpack x = x ^. from packedChars
--   
packedChars :: Simple Iso String ByteString -- | 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'. -- --
--   chars = from packed . traverse
--   
-- --
--   anyOf chars (== 'c') :: ByteString -> Bool
--   
chars :: SimpleIndexedTraversal Int ByteString Char -- | Lenses for lazy bytestrings module Data.ByteString.Lazy.Lens -- | pack (or unpack) a list of bytes into a -- ByteString -- --
--   pack x = x ^. packedBytes
--   
-- --
--   unpack x = x ^. from packedBytes
--   
packedBytes :: Simple Iso [Word8] ByteString -- | Traverse the individual bytes in a ByteString -- --
--   bytes = from packedBytes . traverseList
--   
-- --
--   anyOf bytes (== 0x80) :: ByteString -> Bool
--   
bytes :: SimpleIndexedTraversal 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'. -- --
--   pack x = x ^. packedChars
--   
-- --
--   unpack x = x ^. from packedChars
--   
packedChars :: Simple Iso String ByteString -- | 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'. -- --
--   chars = from packedChars .> traverseList
--   
-- --
--   anyOf chars (== 'c') :: ByteString -> Bool
--   
chars :: SimpleIndexedTraversal Int ByteString Char module Data.Text.Lens -- | Pack (or unpack) Text. -- --
--   pack x = x^.packed
--   unpack x = x^.from packed
--   
packed :: Simple Iso String Text -- | Traverse the individual characters in a either strict or lazy -- Text. -- --
--   anyOf text (=='c') :: Text -> Bool
--   
text :: SimpleIndexedTraversal Int Text Char module Data.Text.Lazy.Lens -- | Pack (or unpack) Text. -- --
--   pack x = x^.packed
--   unpack x = x^.from packed
--   
packed :: Simple Iso String Text -- | Traverse the individual characters in a Text. -- --
--   anyOf text (=='c') :: Text -> Bool
--   
text :: Simple Traversal Text Char -- | 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 :: Simple Lens a b -> Strategy b -> Strategy a
--   evalOf :: Simple Traversal a b -> Strategy b -> Strategy a
--   evalOf :: (b -> Eval b) -> a -> Eval a) -> Strategy b -> Strategy a
--   
evalOf :: SimpleLensLike Eval a b -> Strategy b -> Strategy a -- | Evaluate the targets of a Lens or Traversal according -- into a data structure according to a given Strategy in -- parallel. -- --
--   parTraversable = parOf traverse
--   
-- --
--   parOf :: Simple Lens a b -> Strategy b -> Strategy a
--   parOf :: Simple Traversal a b -> Strategy b -> Strategy a
--   parOf :: ((b -> Eval b) -> a -> Eval a) -> Strategy b -> Strategy a
--   
parOf :: SimpleLensLike Eval a b -> Strategy b -> Strategy a -- | 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 a -> LensLike f a b c d -> LensLike f a b c d -- | 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 a -> LensLike f a b c d -> LensLike f a b c d -- | 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 [c] a c -> Strategy c -> Strategy 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. module GHC.Generics.Lens -- | Convert from the data type to its representation (or back) -- --
--   >>> "hello"^.generic.from generic :: String
--   "hello"
--   
generic :: Generic a => Simple Iso a (Rep a b) -- | Convert from the data type to its representation (or back) generic1 :: Generic1 f => Simple Iso (f a) (Rep1 f a) -- | A Generic Traversal that visits every occurence of -- something Typeable anywhere in a container. -- --
--   >>> allOf every (=="Hello") (1::Int,2::Double,(),"Hello",["Hello"])
--   True
--   
-- --
--   >>> mapMOf_ every putStrLn ("hello",[(2 :: Int, "world!")])
--   hello
--   world!
--   
every :: (Generic a, GTraversal (Rep a), Typeable b) => Simple Traversal a b -- | Used to traverse Generic data by every. class GTraversal f instance (Traversable f, GTraversal g) => GTraversal (f :.: g) 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 U1 instance (Generic a, GTraversal (Rep a), Typeable a) => GTraversal (K1 i a)