-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Yet another prelude. -- -- A prelude built on basic-prelude. @package preamble @version 0.0.62 -- | Public Module module Preamble -- | See examples in Control.Monad.Reader. Note, the partially -- applied function type (->) r is a simple reader monad. See -- the instance declaration below. class Monad m => MonadReader r (m :: * -> *) | m -> r -- | A Monad which allows for safe resource allocation. In theory, -- any monad transformer stack which includes a ResourceT can be -- an instance of MonadResource. -- -- Note: runResourceT has a requirement for a MonadUnliftIO -- m monad, which allows control operations to be lifted. A -- MonadResource does not have this requirement. This means that -- transformers such as ContT can be an instance of -- MonadResource. However, the ContT wrapper will need -- to be unwrapped before calling runResourceT. -- -- Since 0.3.0 class MonadIO m => MonadResource (m :: * -> *) -- | Unwrap a ResourceT transformer, and call all registered release -- actions. -- -- Note that there is some reference counting involved due to -- resourceForkIO. If multiple threads are sharing the same -- collection of resources, only the last call to runResourceT -- will deallocate the resources. -- -- NOTE Since version 1.2.0, this function will throw a -- ResourceCleanupException if any of the cleanup functions throw -- an exception. runResourceT :: MonadUnliftIO m => ResourceT m a -> m a -- |

Writing instances

-- -- The usual way to write a MonadBaseControl instance for -- a transformer stack over a base monad B is to write an -- instance MonadBaseControl B B for the base monad, and -- MonadTransControl T instances for every transformer -- T. Instances for MonadBaseControl are then -- simply implemented using ComposeSt, -- defaultLiftBaseWith, defaultRestoreM. class MonadBase b m => MonadBaseControl (b :: * -> *) (m :: * -> *) | m -> b -- | Stat type Stat = ByteString -> IO () -- | Logger type Logger = Loc -> LogSource -> LogLevel -> LogStr -> IO () -- | Tags type Tags = [(Text, Text)] -- | Pairs type Pairs = [(Text, Value)] -- | Ctx -- -- Base context, supports tracing. data Ctx Ctx :: Pairs -> Logger -> Ctx -- | Object to encode on every trace line. [_cPreamble] :: Ctx -> Pairs -- | Configurable tracing function. [_cLogger] :: Ctx -> Logger -- | StatsCtx -- -- Stats context. data StatsCtx StatsCtx :: Ctx -> Tags -> Stat -> Text -> StatsCtx -- | Parent environment. [_scCtx] :: StatsCtx -> Ctx -- | Tags to append to every stat. [_scLabels] :: StatsCtx -> Tags -- | Configurable stat function. [_scStat] :: StatsCtx -> Stat -- | Stats prefix. [_scPrefix] :: StatsCtx -> Text type MonadCtx c m = (MonadIO m, MonadReader c m, MonadLogger m, MonadMask m, MonadCatch m, MonadThrow m, HasCtx c) class HasCtx c_aq6s ctx :: HasCtx c_aq6s => Lens' c_aq6s Ctx cLogger :: HasCtx c_aq6s => Lens' c_aq6s Logger cPreamble :: HasCtx c_aq6s => Lens' c_aq6s Pairs type MonadStatsCtx c m = (MonadCtx c m, HasStatsCtx c) class HasCtx c_ar0X => HasStatsCtx c_ar0X statsCtx :: HasStatsCtx c_ar0X => Lens' c_ar0X StatsCtx scCtx :: HasStatsCtx c_ar0X => Lens' c_ar0X Ctx scLabels :: HasStatsCtx c_ar0X => Lens' c_ar0X Tags scPrefix :: HasStatsCtx c_ar0X => Lens' c_ar0X Text scStat :: HasStatsCtx c_ar0X => Lens' c_ar0X Stat -- | Monad transformer for reading and logging. newtype TransT c m a TransT :: LoggingT (ReaderT c m) a -> TransT c m a -- | LoggingT and ReaderT transformer. [unTransT] :: TransT c m a -> LoggingT (ReaderT c m) a -- | New logger to stderr. newStderrLogger :: MonadIO m => LogLevel -> m Logger -- | New logger to stdout. newStdoutLogger :: MonadIO m => LogLevel -> m Logger -- | Logger to nowhere. nullLogger :: Logger -- | Debug tracing. traceDebug :: MonadCtx c m => Text -> Pairs -> m () -- | Info tracing. traceInfo :: MonadCtx c m => Text -> Pairs -> m () -- | Warn tracing. traceWarn :: MonadCtx c m => Text -> Pairs -> m () -- | Error tracing. traceError :: MonadCtx c m => Text -> Pairs -> m () (.=) :: (KeyValue kv, ToJSON v) => Text -> v -> kv infixr 8 .= statsCount :: (MonadStatsCtx c m, Show a) => Text -> a -> Tags -> m () statsGauge :: (MonadStatsCtx c m, Show a) => Text -> a -> Tags -> m () statsHistogram :: (MonadStatsCtx c m, Show a) => Text -> a -> Tags -> m () statsTimer :: (MonadStatsCtx c m, Show a) => Text -> a -> Tags -> m () statsSet :: (MonadStatsCtx c m, Show a) => Text -> a -> Tags -> m () statsIncrement :: MonadStatsCtx c m => Text -> Tags -> m () statsDecrement :: MonadStatsCtx c m => Text -> Tags -> m () -- | The value of seq a b is bottom if a is bottom, and -- otherwise equal to b. In other words, it evaluates the first -- argument a to weak head normal form (WHNF). seq is -- usually introduced to improve performance by avoiding unneeded -- laziness. -- -- A note on evaluation order: the expression seq a b does -- not guarantee that a will be evaluated before -- b. The only guarantee given by seq is that the both -- a and b will be evaluated before seq -- returns a value. In particular, this means that b may be -- evaluated before a. If you need to guarantee a specific order -- of evaluation, you must use the function pseq from the -- "parallel" package. seq :: () => a -> b -> b -- | filter, applied to a predicate and a list, returns the list of -- those elements that satisfy the predicate; i.e., -- --
--   filter p xs = [ x | x <- xs, p x]
--   
filter :: () => a -> Bool -> [a] -> [a] -- | zip takes two lists and returns a list of corresponding pairs. -- If one input list is short, excess elements of the longer list are -- discarded. -- -- zip is right-lazy: -- --
--   zip [] _|_ = []
--   
zip :: () => [a] -> [b] -> [(a, b)] -- | Extract the first component of a pair. fst :: () => (a, b) -> a -- | Extract the second component of a pair. snd :: () => (a, b) -> b -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
--   f x | x < 0     = ...
--       | otherwise = ...
--   
otherwise :: Bool -- | If the first argument evaluates to True, then the result is the -- second argument. Otherwise an AssertionFailed exception is -- raised, containing a String with the source file and line -- number of the call to assert. -- -- Assertions can normally be turned on or off with a compiler flag (for -- GHC, assertions are normally on unless optimisation is turned on with -- -O or the -fignore-asserts option is given). When -- assertions are turned off, the first argument to assert is -- ignored, and the second argument is returned as the result. assert :: () => Bool -> a -> a -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
--   f $ g $ h x  =  f (g (h x))
--   
-- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. ($) :: () => a -> b -> a -> b infixr 0 $ -- | general coercion from integral types fromIntegral :: (Integral a, Num b) => a -> b -- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b -- | Conditional failure of Alternative computations. Defined by -- --
--   guard True  = pure ()
--   guard False = empty
--   
-- --

Examples

-- -- Common uses of guard include conditionally signaling an error -- in an error monad and conditionally rejecting the current choice in an -- Alternative-based parser. -- -- As an example of signaling an error in the error monad Maybe, -- consider a safe division function safeDiv x y that returns -- Nothing when the denominator y is zero and -- Just (x `div` y) otherwise. For example: -- --
--   >>> safeDiv 4 0
--   Nothing
--   >>> safeDiv 4 2
--   Just 2
--   
-- -- A definition of safeDiv using guards, but not guard: -- --
--   safeDiv :: Int -> Int -> Maybe Int
--   safeDiv x y | y /= 0    = Just (x `div` y)
--               | otherwise = Nothing
--   
-- -- A definition of safeDiv using guard and Monad -- do-notation: -- --
--   safeDiv :: Int -> Int -> Maybe Int
--   safeDiv x y = do
--     guard (y /= 0)
--     return (x `div` y)
--   
guard :: Alternative f => Bool -> f () -- | The join function is the conventional monad join operator. It -- is used to remove one level of monadic structure, projecting its bound -- argument into the outer level. join :: Monad m => m m a -> m a -- | The Bounded class is used to name the upper and lower limits of -- a type. Ord is not a superclass of Bounded since types -- that are not totally ordered may also have upper and lower bounds. -- -- The Bounded class may be derived for any enumeration type; -- minBound is the first constructor listed in the data -- declaration and maxBound is the last. Bounded may also -- be derived for single-constructor datatypes whose constituent types -- are in Bounded. class Bounded a minBound :: Bounded a => a maxBound :: Bounded a => a -- | Class Enum defines operations on sequentially ordered types. -- -- The enumFrom... methods are used in Haskell's translation of -- arithmetic sequences. -- -- Instances of Enum may be derived for any enumeration type -- (types whose constructors have no fields). The nullary constructors -- are assumed to be numbered left-to-right by fromEnum from -- 0 through n-1. See Chapter 10 of the Haskell -- Report for more details. -- -- For any type that is an instance of class Bounded as well as -- Enum, the following should hold: -- -- -- --
--   enumFrom     x   = enumFromTo     x maxBound
--   enumFromThen x y = enumFromThenTo x y bound
--     where
--       bound | fromEnum y >= fromEnum x = maxBound
--             | otherwise                = minBound
--   
class Enum a -- | the successor of a value. For numeric types, succ adds 1. succ :: Enum a => a -> a -- | the predecessor of a value. For numeric types, pred subtracts -- 1. pred :: Enum a => a -> a -- | Convert from an Int. toEnum :: Enum a => Int -> a -- | Convert to an Int. It is implementation-dependent what -- fromEnum returns when applied to a value that is too large to -- fit in an Int. fromEnum :: Enum a => a -> Int -- | Used in Haskell's translation of [n..]. enumFrom :: Enum a => a -> [a] -- | Used in Haskell's translation of [n,n'..]. enumFromThen :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n..m]. enumFromTo :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n,n'..m]. enumFromThenTo :: Enum a => a -> a -> a -> [a] -- | The Eq class defines equality (==) and inequality -- (/=). All the basic datatypes exported by the Prelude -- are instances of Eq, and Eq may be derived for any -- datatype whose constituents are also instances of Eq. -- -- Minimal complete definition: either == or /=. class Eq a (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => a -> a -> Bool -- | Trigonometric and hyperbolic functions and related functions. class Fractional a => Floating a pi :: Floating a => a exp :: Floating a => a -> a log :: Floating a => a -> a sqrt :: Floating a => a -> a (**) :: Floating a => a -> a -> a logBase :: Floating a => a -> a -> a sin :: Floating a => a -> a cos :: Floating a => a -> a tan :: Floating a => a -> a asin :: Floating a => a -> a acos :: Floating a => a -> a atan :: Floating a => a -> a sinh :: Floating a => a -> a cosh :: Floating a => a -> a tanh :: Floating a => a -> a asinh :: Floating a => a -> a acosh :: Floating a => a -> a atanh :: Floating a => a -> a -- | Fractional numbers, supporting real division. class Num a => Fractional a -- | fractional division (/) :: Fractional a => a -> a -> a -- | reciprocal fraction recip :: Fractional a => a -> a -- | Conversion from a Rational (that is Ratio -- Integer). A floating literal stands for an application of -- fromRational to a value of type Rational, so such -- literals have type (Fractional a) => a. fromRational :: Fractional a => Rational -> a -- | Integral numbers, supporting integer division. class (Real a, Enum a) => Integral a -- | integer division truncated toward zero quot :: Integral a => a -> a -> a -- | integer remainder, satisfying -- --
--   (x `quot` y)*y + (x `rem` y) == x
--   
rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
--   (x `div` y)*y + (x `mod` y) == x
--   
mod :: Integral a => a -> a -> a -- | simultaneous quot and rem quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer -- | The Monad class defines the basic operations over a -- monad, a concept from a branch of mathematics known as -- category theory. From the perspective of a Haskell programmer, -- however, it is best to think of a monad as an abstract datatype -- of actions. Haskell's do expressions provide a convenient -- syntax for writing monadic expressions. -- -- Instances of Monad should satisfy the following laws: -- -- -- -- Furthermore, the Monad and Applicative operations should -- relate as follows: -- -- -- -- The above laws imply: -- -- -- -- and that pure and (<*>) satisfy the applicative -- functor laws. -- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Applicative m => Monad (m :: * -> *) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. (>>=) :: Monad m => m a -> a -> m b -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. (>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a -- | Fail with a message. This operation is not part of the mathematical -- definition of a monad, but is invoked on pattern-match failure in a -- do expression. -- -- As part of the MonadFail proposal (MFP), this function is moved to its -- own class MonadFail (see Control.Monad.Fail for more -- details). The definition here will be removed in a future release. fail :: Monad m => String -> m a -- | The Functor class is used for types that can be mapped over. -- Instances of Functor should satisfy the following laws: -- --
--   fmap id  ==  id
--   fmap (f . g)  ==  fmap f . fmap g
--   
-- -- The instances of Functor for lists, Maybe and IO -- satisfy these laws. class Functor (f :: * -> *) fmap :: Functor f => a -> b -> f a -> f b -- | Replace all locations in the input with the same value. The default -- definition is fmap . const, but this may be -- overridden with a more efficient version. (<$) :: Functor f => a -> f b -> f a -- | Basic numeric class. class Num a (+) :: Num a => a -> a -> a (-) :: Num a => a -> a -> a (*) :: Num a => a -> a -> a -- | Unary negation. negate :: Num a => a -> a -- | Absolute value. abs :: Num a => a -> a -- | Sign of a number. The functions abs and signum should -- satisfy the law: -- --
--   abs x * signum x == x
--   
-- -- For real numbers, the signum is either -1 (negative), -- 0 (zero) or 1 (positive). signum :: Num a => a -> a -- | Conversion from an Integer. An integer literal represents the -- application of the function fromInteger to the appropriate -- value of type Integer, so such literals have type -- (Num a) => a. fromInteger :: Num a => Integer -> a -- | The Ord class is used for totally ordered datatypes. -- -- Instances of Ord can be derived for any user-defined datatype -- whose constituent types are in Ord. The declared order of the -- constructors in the data declaration determines the ordering in -- derived Ord instances. The Ordering datatype allows a -- single comparison to determine the precise ordering of two objects. -- -- Minimal complete definition: either compare or <=. -- Using compare can be more efficient for complex types. class Eq a => Ord a compare :: Ord a => a -> a -> Ordering (<) :: Ord a => a -> a -> Bool (<=) :: Ord a => a -> a -> Bool (>) :: Ord a => a -> a -> Bool (>=) :: Ord a => a -> a -> Bool max :: Ord a => a -> a -> a min :: Ord a => a -> a -> a -- | Parsing of Strings, producing values. -- -- Derived instances of Read make the following assumptions, which -- derived instances of Show obey: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Read in Haskell 2010 is equivalent to -- --
--   instance (Read a) => Read (Tree a) where
--   
--           readsPrec d r =  readParen (d > app_prec)
--                            (\r -> [(Leaf m,t) |
--                                    ("Leaf",s) <- lex r,
--                                    (m,t) <- readsPrec (app_prec+1) s]) r
--   
--                         ++ readParen (d > up_prec)
--                            (\r -> [(u:^:v,w) |
--                                    (u,s) <- readsPrec (up_prec+1) r,
--                                    (":^:",t) <- lex s,
--                                    (v,w) <- readsPrec (up_prec+1) t]) r
--   
--             where app_prec = 10
--                   up_prec = 5
--   
-- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
--   instance (Read a) => Read (Tree a) where
--   
--           readPrec = parens $ (prec app_prec $ do
--                                    Ident "Leaf" <- lexP
--                                    m <- step readPrec
--                                    return (Leaf m))
--   
--                        +++ (prec up_prec $ do
--                                    u <- step readPrec
--                                    Symbol ":^:" <- lexP
--                                    v <- step readPrec
--                                    return (u :^: v))
--   
--             where app_prec = 10
--                   up_prec = 5
--   
--           readListPrec = readListPrecDefault
--   
-- -- Why do both readsPrec and readPrec exist, and why does -- GHC opt to implement readPrec in derived Read instances -- instead of readsPrec? The reason is that readsPrec is -- based on the ReadS type, and although ReadS is mentioned -- in the Haskell 2010 Report, it is not a very efficient parser data -- structure. -- -- readPrec, on the other hand, is based on a much more efficient -- ReadPrec datatype (a.k.a "new-style parsers"), but its -- definition relies on the use of the RankNTypes language -- extension. Therefore, readPrec (and its cousin, -- readListPrec) are marked as GHC-only. Nevertheless, it is -- recommended to use readPrec instead of readsPrec -- whenever possible for the efficiency improvements it brings. -- -- As mentioned above, derived Read instances in GHC will -- implement readPrec instead of readsPrec. The default -- implementations of readsPrec (and its cousin, readList) -- will simply use readPrec under the hood. If you are writing a -- Read instance by hand, it is recommended to write it like so: -- --
--   instance Read T where
--     readPrec     = ...
--     readListPrec = readListPrecDefault
--   
class Read a -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. readList :: Read a => ReadS [a] class (Num a, Ord a) => Real a -- | the rational equivalent of its real argument with full precision toRational :: Real a => a -> Rational -- | Efficient, machine-independent access to the components of a -- floating-point number. class (RealFrac a, Floating a) => RealFloat a -- | a constant function, returning the radix of the representation (often -- 2) floatRadix :: RealFloat a => a -> Integer -- | a constant function, returning the number of digits of -- floatRadix in the significand floatDigits :: RealFloat a => a -> Int -- | a constant function, returning the lowest and highest values the -- exponent may assume floatRange :: RealFloat a => a -> (Int, Int) -- | The function decodeFloat applied to a real floating-point -- number returns the significand expressed as an Integer and an -- appropriately scaled exponent (an Int). If -- decodeFloat x yields (m,n), then x -- is equal in value to m*b^^n, where b is the -- floating-point radix, and furthermore, either m and -- n are both zero or else b^(d-1) <= abs m < -- b^d, where d is the value of floatDigits -- x. In particular, decodeFloat 0 = (0,0). If the -- type contains a negative zero, also decodeFloat (-0.0) = -- (0,0). The result of decodeFloat x is -- unspecified if either of isNaN x or -- isInfinite x is True. decodeFloat :: RealFloat a => a -> (Integer, Int) -- | encodeFloat performs the inverse of decodeFloat in the -- sense that for finite x with the exception of -0.0, -- uncurry encodeFloat (decodeFloat x) = -- x. encodeFloat m n is one of the two closest -- representable floating-point numbers to m*b^^n (or -- ±Infinity if overflow occurs); usually the closer, but if -- m contains too many bits, the result may be rounded in the -- wrong direction. encodeFloat :: RealFloat a => Integer -> Int -> a -- | exponent corresponds to the second component of -- decodeFloat. exponent 0 = 0 and for finite -- nonzero x, exponent x = snd (decodeFloat x) -- + floatDigits x. If x is a finite floating-point -- number, it is equal in value to significand x * b ^^ -- exponent x, where b is the floating-point radix. -- The behaviour is unspecified on infinite or NaN values. exponent :: RealFloat a => a -> Int -- | The first component of decodeFloat, scaled to lie in the open -- interval (-1,1), either 0.0 or of absolute -- value >= 1/b, where b is the floating-point -- radix. The behaviour is unspecified on infinite or NaN -- values. significand :: RealFloat a => a -> a -- | multiplies a floating-point number by an integer power of the radix scaleFloat :: RealFloat a => Int -> a -> a -- | True if the argument is an IEEE "not-a-number" (NaN) value isNaN :: RealFloat a => a -> Bool -- | True if the argument is an IEEE infinity or negative infinity isInfinite :: RealFloat a => a -> Bool -- | True if the argument is too small to be represented in -- normalized format isDenormalized :: RealFloat a => a -> Bool -- | True if the argument is an IEEE negative zero isNegativeZero :: RealFloat a => a -> Bool -- | True if the argument is an IEEE floating point number isIEEE :: RealFloat a => a -> Bool -- | a version of arctangent taking two real floating-point arguments. For -- real floating x and y, atan2 y x -- computes the angle (from the positive x-axis) of the vector from the -- origin to the point (x,y). atan2 y x returns -- a value in the range [-pi, pi]. It follows the -- Common Lisp semantics for the origin when signed zeroes are supported. -- atan2 y 1, with y in a type that is -- RealFloat, should return the same value as atan -- y. A default definition of atan2 is provided, but -- implementors can provide a more accurate implementation. atan2 :: RealFloat a => a -> a -> a -- | Extracting components of fractions. class (Real a, Fractional a) => RealFrac a -- | The function properFraction takes a real fractional number -- x and returns a pair (n,f) such that x = -- n+f, and: -- -- -- -- The default definitions of the ceiling, floor, -- truncate and round functions are in terms of -- properFraction. properFraction :: (RealFrac a, Integral b) => a -> (b, a) -- | truncate x returns the integer nearest x -- between zero and x truncate :: (RealFrac a, Integral b) => a -> b -- | round x returns the nearest integer to x; the -- even integer if x is equidistant between two integers round :: (RealFrac a, Integral b) => a -> b -- | ceiling x returns the least integer not less than -- x ceiling :: (RealFrac a, Integral b) => a -> b -- | floor x returns the greatest integer not greater than -- x floor :: (RealFrac a, Integral b) => a -> b -- | Conversion of values to readable Strings. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Show is equivalent to -- --
--   instance (Show a) => Show (Tree a) where
--   
--          showsPrec d (Leaf m) = showParen (d > app_prec) $
--               showString "Leaf " . showsPrec (app_prec+1) m
--            where app_prec = 10
--   
--          showsPrec d (u :^: v) = showParen (d > up_prec) $
--               showsPrec (up_prec+1) u .
--               showString " :^: "      .
--               showsPrec (up_prec+1) v
--            where up_prec = 5
--   
-- -- Note that right-associativity of :^: is ignored. For example, -- -- class Show a -- | Convert a value to a readable String. -- -- showsPrec should satisfy the law -- --
--   showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)
--   
-- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Show a => Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: Show a => a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: Show a => [a] -> ShowS -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable (a :: k) -- | Class for string-like datastructures; used by the overloaded string -- extension (-XOverloadedStrings in GHC). class IsString a fromString :: IsString a => String -> a -- | A functor with application, providing operations to -- -- -- -- A minimal complete definition must include implementations of -- pure and of either <*> or liftA2. If it -- defines both, then they must behave the same as their default -- definitions: -- --
--   (<*>) = liftA2 id
--   
-- --
--   liftA2 f x y = f <$> x <*> y
--   
-- -- Further, any definition must satisfy the following: -- -- -- -- The other methods have the following default definitions, which may be -- overridden with equivalent specialized implementations: -- -- -- -- As a consequence of these laws, the Functor instance for -- f will satisfy -- -- -- -- It may be useful to note that supposing -- --
--   forall x y. p (q x y) = f x . g y
--   
-- -- it follows from the above that -- --
--   liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v
--   
-- -- If f is also a Monad, it should satisfy -- -- -- -- (which implies that pure and <*> satisfy the -- applicative functor laws). class Functor f => Applicative (f :: * -> *) -- | Lift a value. pure :: Applicative f => a -> f a -- | Sequential application. -- -- A few functors support an implementation of <*> that is -- more efficient than the default one. (<*>) :: Applicative f => f a -> b -> f a -> f b -- | Lift a binary function to actions. -- -- Some functors support an implementation of liftA2 that is more -- efficient than the default one. In particular, if fmap is an -- expensive operation, it is likely better to use liftA2 than to -- fmap over the structure and then use <*>. liftA2 :: Applicative f => a -> b -> c -> f a -> f b -> f c -- | Sequence actions, discarding the value of the first argument. (*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. (<*) :: Applicative f => f a -> f b -> f a -- | Data structures that can be folded. -- -- For example, given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Foldable Tree where
--      foldMap f Empty = mempty
--      foldMap f (Leaf x) = f x
--      foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
--   
-- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
--   instance Foldable Tree where
--      foldr f z Empty = z
--      foldr f z (Leaf x) = f x z
--      foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
--   
-- -- Foldable instances are expected to satisfy the following -- laws: -- --
--   foldr f z t = appEndo (foldMap (Endo . f) t ) z
--   
-- --
--   foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
--   
-- --
--   fold = foldMap id
--   
-- --
--   length = getSum . foldMap (Sum . const  1)
--   
-- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
--   sum = getSum . foldMap Sum
--   
-- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
--   foldMap f = fold . fmap f
--   
-- -- which implies that -- --
--   foldMap f . fmap g = foldMap (f . g)
--   
class Foldable (t :: * -> *) -- | Map each element of the structure to a monoid, and combine the -- results. foldMap :: (Foldable t, Monoid m) => a -> m -> t a -> m -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when applied to a binary operator, -- a starting value (typically the right-identity of the operator), and a -- list, reduces the list using the binary operator, from right to left: -- --
--   foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
--   
-- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldr f z = foldr f z . toList
--   
foldr :: Foldable t => a -> b -> b -> b -> t a -> b -- | Right-associative fold of a structure, but with strict application of -- the operator. foldr' :: Foldable t => a -> b -> b -> b -> t a -> b -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when applied to a binary operator, -- a starting value (typically the left-identity of the operator), and a -- list, reduces the list using the binary operator, from left to right: -- --
--   foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
--   
-- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z f -- x1 in the above example) before applying them to the operator -- (e.g. to (f x2)). This results in a thunk chain -- O(n) elements long, which then must be evaluated from the -- outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl f z . toList
--   
foldl :: Foldable t => b -> a -> b -> b -> t a -> b -- | Left-associative fold of a structure but with strict application of -- the operator. -- -- This ensures that each step of the fold is forced to weak head normal -- form before being applied, avoiding the collection of thunks that -- would otherwise occur. This is often what you want to strictly reduce -- a finite list to a single, monolithic result (e.g. length). -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl' f z . toList
--   
foldl' :: Foldable t => b -> a -> b -> b -> t a -> b -- | A variant of foldr that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldr1 f = foldr1 f . toList
--   
foldr1 :: Foldable t => a -> a -> a -> t a -> a -- | A variant of foldl that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldl1 f = foldl1 f . toList
--   
foldl1 :: Foldable t => a -> a -> a -> t a -> a -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. length :: Foldable t => t a -> Int -- | Does the element occur in the structure? elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The largest element of a non-empty structure. maximum :: (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. minimum :: (Foldable t, Ord a) => t a -> a -- | Functors representing data structures that can be traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- -- -- -- A definition of sequenceA must satisfy the following laws: -- -- -- -- where an applicative transformation is a function -- --
--   t :: (Applicative f, Applicative g) => f a -> g a
--   
-- -- preserving the Applicative operations, i.e. -- -- -- -- and the identity functor Identity and composition of functors -- Compose are defined as -- --
--   newtype Identity a = Identity a
--   
--   instance Functor Identity where
--     fmap f (Identity x) = Identity (f x)
--   
--   instance Applicative Identity where
--     pure x = Identity x
--     Identity f <*> Identity x = Identity (f x)
--   
--   newtype Compose f g a = Compose (f (g a))
--   
--   instance (Functor f, Functor g) => Functor (Compose f g) where
--     fmap f (Compose x) = Compose (fmap (fmap f) x)
--   
--   instance (Applicative f, Applicative g) => Applicative (Compose f g) where
--     pure x = Compose (pure (pure x))
--     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
--   
-- -- (The naturality law is implied by parametricity.) -- -- Instances are similar to Functor, e.g. given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Traversable Tree where
--      traverse f Empty = pure Empty
--      traverse f (Leaf x) = Leaf <$> f x
--      traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
--   
-- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- -- class (Functor t, Foldable t) => Traversable (t :: * -> *) -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and collect the results. For a version that -- ignores the results see traverse_. traverse :: (Traversable t, Applicative f) => a -> f b -> t a -> f t b -- | Evaluate each action in the structure from left to right, and and -- collect the results. For a version that ignores the results see -- sequenceA_. sequenceA :: (Traversable t, Applicative f) => t f a -> f t a -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results. For a version -- that ignores the results see mapM_. mapM :: (Traversable t, Monad m) => a -> m b -> t a -> m t b -- | Evaluate each monadic action in the structure from left to right, and -- collect the results. For a version that ignores the results see -- sequence_. sequence :: (Traversable t, Monad m) => t m a -> m t a -- | An associative operation. (<>) :: Semigroup a => a -> a -> a infixr 6 <> -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following laws: -- -- -- -- The method names refer to the monoid of lists under concatenation, but -- there are many other instances. -- -- Some types can be viewed as a monoid in more than one way, e.g. both -- addition and multiplication on numbers. In such cases we often define -- newtypes and make those instances of Monoid, e.g. -- Sum and Product. -- -- NOTE: Semigroup is a superclass of Monoid since -- base-4.11.0.0. class Semigroup a => Monoid a -- | Identity of mappend mempty :: Monoid a => a -- | An associative operation -- -- NOTE: This method is redundant and has the default -- implementation mappend = '(<>)' since -- base-4.11.0.0. mappend :: Monoid a => a -> a -> a -- | Fold a list using the monoid. -- -- For most types, the default definition for mconcat will be -- used, but the function is included in the class definition so that an -- optimized version can be provided for specific types. mconcat :: Monoid a => [a] -> a data Bool False :: Bool True :: Bool -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. -- characters, see http://www.unicode.org/ for details). This set -- extends the ISO 8859-1 (Latin-1) character set (the first 256 -- characters), which is itself an extension of the ASCII character set -- (the first 128 characters). A character literal in Haskell has type -- Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char -- | Double-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- double-precision type. data Double -- | Single-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- single-precision type. data Float -- | A fixed-precision integer type with at least the range [-2^29 .. -- 2^29-1]. The exact range for a given implementation can be -- determined by using minBound and maxBound from the -- Bounded class. data Int -- | 32-bit signed integer type data Int32 -- | 64-bit signed integer type data Int64 -- | Invariant: Jn# and Jp# are used iff value doesn't fit in -- S# -- -- Useful properties resulting from the invariants: -- -- data Integer -- | The Maybe type encapsulates an optional value. A value of type -- Maybe a either contains a value of type a -- (represented as Just a), or it is empty (represented -- as Nothing). Using Maybe is a good way to deal with -- errors or exceptional cases without resorting to drastic measures such -- as error. -- -- The Maybe type is also a monad. It is a simple kind of error -- monad, where all errors are represented by Nothing. A richer -- error monad can be built using the Either type. data Maybe a Nothing :: Maybe a Just :: a -> Maybe a data Ordering LT :: Ordering EQ :: Ordering GT :: Ordering -- | Arbitrary-precision rational numbers, represented as a ratio of two -- Integer values. A rational number may be constructed using the -- % operator. type Rational = Ratio Integer -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- There is really only one way to "perform" an I/O action: bind it to -- Main.main in your program. When your program is run, the I/O -- will be performed. It isn't possible to perform I/O from an arbitrary -- function, unless that function is itself in the IO monad and -- called at some point, directly or indirectly, from Main.main. -- -- IO is a monad, so IO actions can be combined using -- either the do-notation or the >> and >>= -- operations from the Monad class. data IO a -- | A Word is an unsigned integral type, with the same size as -- Int. data Word -- | 8-bit unsigned integer type data Word8 -- | 32-bit unsigned integer type data Word32 -- | 64-bit unsigned integer type data Word64 -- | The Either type represents values with two possibilities: a -- value of type Either a b is either Left -- a or Right b. -- -- The Either type is sometimes used to represent a value which is -- either correct or an error; by convention, the Left constructor -- is used to hold an error value and the Right constructor is -- used to hold a correct value (mnemonic: "right" also means "correct"). -- --

Examples

-- -- The type Either String Int is the type -- of values which can be either a String or an Int. The -- Left constructor can be used only on Strings, and the -- Right constructor can be used only on Ints: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> s
--   Left "foo"
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> n
--   Right 3
--   
--   >>> :type s
--   s :: Either String Int
--   
--   >>> :type n
--   n :: Either String Int
--   
-- -- The fmap from our Functor instance will ignore -- Left values, but will apply the supplied function to values -- contained in a Right: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> fmap (*2) s
--   Left "foo"
--   
--   >>> fmap (*2) n
--   Right 6
--   
-- -- The Monad instance for Either allows us to chain -- together multiple actions which may fail, and fail overall if any of -- the individual steps failed. First we'll write a function that can -- either parse an Int from a Char, or fail. -- --
--   >>> import Data.Char ( digitToInt, isDigit )
--   
--   >>> :{
--       let parseEither :: Char -> Either String Int
--           parseEither c
--             | isDigit c = Right (digitToInt c)
--             | otherwise = Left "parse error"
--   
--   >>> :}
--   
-- -- The following should work, since both '1' and '2' -- can be parsed as Ints. -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither '1'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Right 3
--   
-- -- But the following should fail overall, since the first operation where -- we attempt to parse 'm' as an Int will fail: -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither 'm'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Left "parse error"
--   
data Either a b Left :: a -> Either a b Right :: b -> Either a b -- | Lift a computation from the argument monad to the constructed monad. lift :: (MonadTrans t, Monad m) => m a -> t m a -- | Monads that also support choice and failure. class (Alternative m, Monad m) => MonadPlus (m :: * -> *) -- | The identity of mplus. It should also satisfy the equations -- --
--   mzero >>= f  =  mzero
--   v >> mzero   =  mzero
--   
-- -- The default definition is -- --
--   mzero = empty
--   
mzero :: MonadPlus m => m a -- | An associative operation. The default definition is -- --
--   mplus = (<|>)
--   
mplus :: MonadPlus m => m a -> m a -> m a -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => a -> m b -> m a -> m b infixr 1 =<< -- | Conditional execution of Applicative expressions. For example, -- --
--   when debug (putStrLn "Debugging")
--   
-- -- will output the string Debugging if the Boolean value -- debug is True, and otherwise do nothing. when :: Applicative f => Bool -> f () -> f () -- | Promote a function to a monad. liftM :: Monad m => a1 -> r -> m a1 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right. For example, -- --
--   liftM2 (+) [0,1] [0,2] = [0,2,1,3]
--   liftM2 (+) (Just 1) Nothing = Nothing
--   
liftM2 :: Monad m => a1 -> a2 -> r -> m a1 -> m a2 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM3 :: Monad m => a1 -> a2 -> a3 -> r -> m a1 -> m a2 -> m a3 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM4 :: Monad m => a1 -> a2 -> a3 -> a4 -> r -> m a1 -> m a2 -> m a3 -> m a4 -> m r -- | Promote a function to a monad, scanning the monadic arguments from -- left to right (cf. liftM2). liftM5 :: Monad m => a1 -> a2 -> a3 -> a4 -> a5 -> r -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r -- | In many situations, the liftM operations can be replaced by -- uses of ap, which promotes function application. -- --
--   return f `ap` x1 `ap` ... `ap` xn
--   
-- -- is equivalent to -- --
--   liftMn f x1 x2 ... xn
--   
ap :: Monad m => m a -> b -> m a -> m b -- | void value discards or ignores the result of -- evaluation, such as the return value of an IO action. -- --

Examples

-- -- Replace the contents of a Maybe Int with -- unit: -- --
--   >>> void Nothing
--   Nothing
--   
--   >>> void (Just 3)
--   Just ()
--   
-- -- Replace the contents of an Either Int -- Int with unit, resulting in an Either -- Int '()': -- --
--   >>> void (Left 8675309)
--   Left 8675309
--   
--   >>> void (Right 8675309)
--   Right ()
--   
-- -- Replace every element of a list with unit: -- --
--   >>> void [1,2,3]
--   [(),(),()]
--   
-- -- Replace the second element of a pair with unit: -- --
--   >>> void (1,2)
--   (1,())
--   
-- -- Discard the result of an IO action: -- --
--   >>> mapM print [1,2]
--   1
--   2
--   [(),()]
--   
--   >>> void $ mapM print [1,2]
--   1
--   2
--   
void :: Functor f => f a -> f () -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and ignore the results. For a version that -- doesn't ignore the results see mapM. -- -- As of base 4.8.0.0, mapM_ is just traverse_, specialized -- to Monad. mapM_ :: (Foldable t, Monad m) => a -> m b -> t a -> m () -- | forM_ is mapM_ with its arguments flipped. For a version -- that doesn't ignore the results see forM. -- -- As of base 4.8.0.0, forM_ is just for_, specialized to -- Monad. forM_ :: (Foldable t, Monad m) => t a -> a -> m b -> m () -- | Evaluate each monadic action in the structure from left to right, and -- ignore the results. For a version that doesn't ignore the results see -- sequence. -- -- As of base 4.8.0.0, sequence_ is just sequenceA_, -- specialized to Monad. sequence_ :: (Foldable t, Monad m) => t m a -> m () -- | The sum of a collection of actions, generalizing concat. As of -- base 4.8.0.0, msum is just asum, specialized to -- MonadPlus. msum :: (Foldable t, MonadPlus m) => t m a -> m a -- | forM is mapM with its arguments flipped. For a version -- that ignores the results see forM_. forM :: (Traversable t, Monad m) => t a -> a -> m b -> m t b -- | This generalizes the list-based filter function. filterM :: Applicative m => a -> m Bool -> [a] -> m [a] -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => a -> m b -> b -> m c -> a -> m c infixr 1 >=> -- | Right-to-left Kleisli composition of monads. -- (>=>), with the arguments flipped. -- -- Note how this operator resembles function composition -- (.): -- --
--   (.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
--   (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
--   
(<=<) :: Monad m => b -> m c -> a -> m b -> a -> m c infixr 1 <=< -- | forever act repeats the action infinitely. forever :: Applicative f => f a -> f b -- | The mapAndUnzipM function maps its first argument over a list, -- returning the result as a pair of lists. This function is mainly used -- with complicated data structures or a state-transforming monad. mapAndUnzipM :: Applicative m => a -> m (b, c) -> [a] -> m ([b], [c]) -- | The zipWithM function generalizes zipWith to arbitrary -- applicative functors. zipWithM :: Applicative m => a -> b -> m c -> [a] -> [b] -> m [c] -- | zipWithM_ is the extension of zipWithM which ignores the -- final result. zipWithM_ :: Applicative m => a -> b -> m c -> [a] -> [b] -> m () -- | The foldM function is analogous to foldl, except that -- its result is encapsulated in a monad. Note that foldM works -- from left-to-right over the list arguments. This could be an issue -- where (>>) and the `folded function' are not -- commutative. -- --
--   foldM f a1 [x1, x2, ..., xm]
--   
--   ==
--   
--   do
--     a2 <- f a1 x1
--     a3 <- f a2 x2
--     ...
--     f am xm
--   
-- -- If right-to-left evaluation is required, the input list should be -- reversed. -- -- Note: foldM is the same as foldlM foldM :: (Foldable t, Monad m) => b -> a -> m b -> b -> t a -> m b -- | Like foldM, but discards the result. foldM_ :: (Foldable t, Monad m) => b -> a -> m b -> b -> t a -> m () -- | replicateM n act performs the action n times, -- gathering the results. replicateM :: Applicative m => Int -> m a -> m [a] -- | Like replicateM, but discards the result. replicateM_ :: Applicative m => Int -> m a -> m () -- | The reverse of when. unless :: Applicative f => Bool -> f () -> f () -- | Strict version of <$>. (<$!>) :: Monad m => a -> b -> m a -> m b infixl 4 <$!> -- | Direct MonadPlus equivalent of filter -- filter = (mfilter:: (a -> Bool) -> [a] -- -> [a] applicable to any MonadPlus, for example -- mfilter odd (Just 1) == Just 1 mfilter odd (Just 2) == -- Nothing mfilter :: MonadPlus m => a -> Bool -> m a -> m a -- | Monads in which IO computations may be embedded. Any monad -- built by applying a sequence of monad transformers to the IO -- monad will be an instance of this class. -- -- Instances should satisfy the following laws, which state that -- liftIO is a transformer of monads: -- -- class Monad m => MonadIO (m :: * -> *) -- | Lift a computation from the IO monad. liftIO :: MonadIO m => IO a -> m a -- | Case analysis for the Either type. If the value is -- Left a, apply the first function to a; if it -- is Right b, apply the second function to b. -- --

Examples

-- -- We create two values of type Either String -- Int, one using the Left constructor and another -- using the Right constructor. Then we apply "either" the -- length function (if we have a String) or the -- "times-two" function (if we have an Int): -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> either length (*2) s
--   3
--   
--   >>> either length (*2) n
--   6
--   
either :: () => a -> c -> b -> c -> Either a b -> c -- | The class of contravariant functors. -- -- Whereas in Haskell, one can think of a Functor as containing or -- producing values, a contravariant functor is a functor that can be -- thought of as consuming values. -- -- As an example, consider the type of predicate functions a -> -- Bool. One such predicate might be negative x = x < 0, -- which classifies integers as to whether they are negative. However, -- given this predicate, we can re-use it in other situations, providing -- we have a way to map values to integers. For instance, we can -- use the negative predicate on a person's bank balance to work -- out if they are currently overdrawn: -- --
--   newtype Predicate a = Predicate { getPredicate :: a -> Bool }
--   
--   instance Contravariant Predicate where
--     contramap f (Predicate p) = Predicate (p . f)
--                                            |   `- First, map the input...
--                                            `----- then apply the predicate.
--   
--   overdrawn :: Predicate Person
--   overdrawn = contramap personBankBalance negative
--   
-- -- Any instance should be subject to the following laws: -- --
--   contramap id = id
--   contramap f . contramap g = contramap (g . f)
--   
-- -- Note, that the second law follows from the free theorem of the type of -- contramap and the first law, so you need only check that the -- former condition holds. class Contravariant (f :: * -> *) contramap :: Contravariant f => a -> b -> f b -> f a -- | Replace all locations in the output with the same value. The default -- definition is contramap . const, but this may -- be overridden with a more efficient version. (>$) :: Contravariant f => b -> f b -> f a -- | A space-efficient representation of a Word8 vector, supporting -- many efficient operations. -- -- A ByteString contains 8-bit bytes, or by using the operations -- from Data.ByteString.Char8 it can be interpreted as containing -- 8-bit characters. data ByteString -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
--    ($)  ::              (a -> b) ->   a ->   b
--   (<$>) :: Functor f => (a -> b) -> f a -> f b
--   
-- -- Whereas $ is function application, <$> is -- function application lifted over a Functor. -- --

Examples

-- -- Convert from a Maybe Int to a -- Maybe String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
--   >>> show <$> Left 17
--   Left 17
--   
--   >>> show <$> Right 17
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> (*2) <$> [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> even <$> (2,2)
--   (2,True)
--   
(<$>) :: Functor f => a -> b -> f a -> f b infixl 4 <$> -- | A String is a list of characters. String constants in Haskell -- are values of type String. type String = [Char] -- | The class of types that can be converted to a hash value. -- -- Minimal implementation: hashWithSalt. class Hashable a -- | Return a hash value for the argument, using the given salt. -- -- The general contract of hashWithSalt is: -- -- hashWithSalt :: Hashable a => Int -> a -> Int -- | Like hashWithSalt, but no salt is used. The default -- implementation uses hashWithSalt with some default salt. -- Instances might want to implement this method to provide a more -- efficient implementation than the default implementation. hash :: Hashable a => a -> Int -- | A space efficient, packed, unboxed Unicode text type. data Text -- | A map from keys to values. A map cannot contain duplicate keys; each -- key can map to at most one value. data HashMap k v -- | A Map from keys k to values a. data Map k a -- | An associative binary operation (<|>) :: Alternative f => f a -> f a -> f a infixl 3 <|> -- | A bifunctor is a type constructor that takes two type arguments and is -- a functor in both arguments. That is, unlike with -- Functor, a type constructor such as Either does not need -- to be partially applied for a Bifunctor instance, and the -- methods in this class permit mapping functions over the Left -- value or the Right value, or both at the same time. -- -- Formally, the class Bifunctor represents a bifunctor from -- Hask -> Hask. -- -- Intuitively it is a bifunctor where both the first and second -- arguments are covariant. -- -- You can define a Bifunctor by either defining bimap or -- by defining both first and second. -- -- If you supply bimap, you should ensure that: -- --
--   bimap id idid
--   
-- -- If you supply first and second, ensure: -- --
--   first idid
--   second idid
--   
-- -- If you supply both, you should also ensure: -- --
--   bimap f g ≡ first f . second g
--   
-- -- These ensure by parametricity: -- --
--   bimap  (f . g) (h . i) ≡ bimap f h . bimap g i
--   first  (f . g) ≡ first  f . first  g
--   second (f . g) ≡ second f . second g
--   
class Bifunctor (p :: * -> * -> *) -- | Map over both arguments at the same time. -- --
--   bimap f g ≡ first f . second g
--   
-- --

Examples

-- --
--   >>> bimap toUpper (+1) ('j', 3)
--   ('J',4)
--   
-- --
--   >>> bimap toUpper (+1) (Left 'j')
--   Left 'J'
--   
-- --
--   >>> bimap toUpper (+1) (Right 3)
--   Right 4
--   
bimap :: Bifunctor p => a -> b -> c -> d -> p a c -> p b d -- | The isSubsequenceOf function takes two lists and returns -- True if all the elements of the first list occur, in order, in -- the second. The elements do not have to occur consecutively. -- -- isSubsequenceOf x y is equivalent to elem x -- (subsequences y). -- --

Examples

-- --
--   >>> isSubsequenceOf "GHC" "The Glorious Haskell Compiler"
--   True
--   
--   >>> isSubsequenceOf ['a','d'..'z'] ['a'..'z']
--   True
--   
--   >>> isSubsequenceOf [1..10] [10,9..0]
--   False
--   
isSubsequenceOf :: Eq a => [a] -> [a] -> Bool -- | The mapAccumR function behaves like a combination of -- fmap and foldr; it applies a function to each element -- of a structure, passing an accumulating parameter from right to left, -- and returning a final value of this accumulator together with the new -- structure. mapAccumR :: Traversable t => a -> b -> (a, c) -> a -> t b -> (a, t c) -- | The mapAccumL function behaves like a combination of -- fmap and foldl; it applies a function to each element -- of a structure, passing an accumulating parameter from left to right, -- and returning a final value of this accumulator together with the new -- structure. mapAccumL :: Traversable t => a -> b -> (a, c) -> a -> t b -> (a, t c) -- | for is traverse with its arguments flipped. For a -- version that ignores the results see for_. for :: (Traversable t, Applicative f) => t a -> a -> f b -> f t b -- | Send the first component of the input through the argument arrow, and -- copy the rest unchanged to the output. first :: Arrow a => a b c -> a (b, d) (c, d) -- | A mirror image of first. -- -- The default definition may be overridden with a more efficient version -- if desired. second :: Arrow a => a b c -> a (d, b) (d, c) -- | Split the input between the two argument arrows and combine their -- output. Note that this is in general not a functor. -- -- The default definition may be overridden with a more efficient version -- if desired. (***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c') infixr 3 *** -- | Fanout: send the input to both argument arrows and combine their -- output. -- -- The default definition may be overridden with a more efficient version -- if desired. (&&&) :: Arrow a => a b c -> a b c' -> a b (c, c') infixr 3 &&& -- | Identity functor and monad. (a non-strict monad) newtype Identity a Identity :: a -> Identity a [runIdentity] :: Identity a -> a -- | The catchIOError function establishes a handler that receives -- any IOError raised in the action protected by -- catchIOError. An IOError is caught by the most recent -- handler established by one of the exception handling functions. These -- handlers are not selective: all IOErrors are caught. Exception -- propagation must be explicitly provided in a handler by re-raising any -- unwanted exceptions. For example, in -- --
--   f = catchIOError g (\e -> if IO.isEOFError e then return [] else ioError e)
--   
-- -- the function f returns [] when an end-of-file -- exception (cf. isEOFError) occurs in g; otherwise, the -- exception is propagated to the next outer handler. -- -- When an exception propagates outside the main program, the Haskell -- system prints the associated IOError value and exits the -- program. -- -- Non-I/O exceptions are not caught by this variant; to catch all -- exceptions, use catch from Control.Exception. catchIOError :: () => IO a -> IOError -> IO a -> IO a -- | Adds a location description and maybe a file path and file handle to -- an IOError. If any of the file handle or file path is not given -- the corresponding value in the IOError remains unaltered. annotateIOError :: IOError -> String -> Maybe Handle -> Maybe FilePath -> IOError -- | Catch any IOError that occurs in the computation and throw a -- modified version. modifyIOError :: () => IOError -> IOError -> IO a -> IO a ioeSetFileName :: IOError -> FilePath -> IOError ioeSetHandle :: IOError -> Handle -> IOError ioeSetLocation :: IOError -> String -> IOError ioeSetErrorString :: IOError -> String -> IOError ioeSetErrorType :: IOError -> IOErrorType -> IOError ioeGetFileName :: IOError -> Maybe FilePath ioeGetHandle :: IOError -> Maybe Handle ioeGetLocation :: IOError -> String ioeGetErrorString :: IOError -> String ioeGetErrorType :: IOError -> IOErrorType -- | I/O error that is programmer-defined. isUserErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because the user does not have -- sufficient operating system privilege to perform that operation. isPermissionErrorType :: IOErrorType -> Bool -- | I/O error where the operation is not possible. isIllegalOperationErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because the end of file has been -- reached. isEOFErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because the device is full. isFullErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because one of its arguments is a -- single-use resource, which is already being used. isAlreadyInUseErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because one of its arguments does -- not exist. isDoesNotExistErrorType :: IOErrorType -> Bool -- | I/O error where the operation failed because one of its arguments -- already exists. isAlreadyExistsErrorType :: IOErrorType -> Bool -- | I/O error that is programmer-defined. userErrorType :: IOErrorType -- | I/O error where the operation failed because the user does not have -- sufficient operating system privilege to perform that operation. permissionErrorType :: IOErrorType -- | I/O error where the operation is not possible. illegalOperationErrorType :: IOErrorType -- | I/O error where the operation failed because the end of file has been -- reached. eofErrorType :: IOErrorType -- | I/O error where the operation failed because the device is full. fullErrorType :: IOErrorType -- | I/O error where the operation failed because one of its arguments is a -- single-use resource, which is already being used. alreadyInUseErrorType :: IOErrorType -- | I/O error where the operation failed because one of its arguments does -- not exist. doesNotExistErrorType :: IOErrorType -- | I/O error where the operation failed because one of its arguments -- already exists. alreadyExistsErrorType :: IOErrorType -- | A programmer-defined error value constructed using userError. isUserError :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- user does not have sufficient operating system privilege to perform -- that operation. isPermissionError :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- operation was not possible. Any computation which returns an IO -- result may fail with isIllegalOperation. In some cases, an -- implementation will not be able to distinguish between the possible -- error causes. In this case it should fail with -- isIllegalOperation. isIllegalOperation :: IOError -> Bool -- | An error indicating that an IO operation failed because the end -- of file has been reached. isEOFError :: IOError -> Bool -- | An error indicating that an IO operation failed because the -- device is full. isFullError :: IOError -> Bool -- | An error indicating that an IO operation failed because one of -- its arguments is a single-use resource, which is already being used -- (for example, opening the same file twice for writing might give this -- error). isAlreadyInUseError :: IOError -> Bool -- | An error indicating that an IO operation failed because one of -- its arguments does not exist. isDoesNotExistError :: IOError -> Bool -- | An error indicating that an IO operation failed because one of -- its arguments already exists. isAlreadyExistsError :: IOError -> Bool -- | Construct an IOError of the given type where the second -- argument describes the error location and the third and fourth -- argument contain the file handle and file path of the file involved in -- the error if applicable. mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe FilePath -> IOError -- | The construct tryIOError comp exposes IO errors which -- occur within a computation, and which are not fully handled. -- -- Non-I/O exceptions are not caught by this variant; to catch all -- exceptions, use try from Control.Exception. tryIOError :: () => IO a -> IO Either IOError a -- | This function maps one exception into another as proposed in the paper -- "A semantics for imprecise exceptions". mapException :: (Exception e1, Exception e2) => e1 -> e2 -> a -> a -- | A pattern match failed. The String gives information about -- the source location of the pattern. newtype PatternMatchFail PatternMatchFail :: String -> PatternMatchFail -- | A record selector was applied to a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. The String gives information about the source -- location of the record selector. newtype RecSelError RecSelError :: String -> RecSelError -- | An uninitialised record field was used. The String gives -- information about the source location where the record was -- constructed. newtype RecConError RecConError :: String -> RecConError -- | A record update was performed on a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. The String gives information about the source -- location of the record update. newtype RecUpdError RecUpdError :: String -> RecUpdError -- | A class method without a definition (neither a default definition, nor -- a definition in the appropriate instance) was called. The -- String gives information about which method it was. newtype NoMethodError NoMethodError :: String -> NoMethodError -- | An expression that didn't typecheck during compile time was called. -- This is only possible with -fdefer-type-errors. The String -- gives details about the failed type check. newtype TypeError TypeError :: String -> TypeError -- | Thrown when the runtime system detects that the computation is -- guaranteed not to terminate. Note that there is no guarantee that the -- runtime system will notice whether any given computation is guaranteed -- to terminate or not. data NonTermination NonTermination :: NonTermination -- | Thrown when the program attempts to call atomically, from the -- stm package, inside another call to atomically. data NestedAtomically NestedAtomically :: NestedAtomically -- | Raise an IOError in the IO monad. ioError :: () => IOError -> IO a asyncExceptionFromException :: Exception e => SomeException -> Maybe e asyncExceptionToException :: Exception e => e -> SomeException -- | The thread is blocked on an MVar, but there are no other -- references to the MVar so it can't ever continue. data BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar :: BlockedIndefinitelyOnMVar -- | The thread is waiting to retry an STM transaction, but there are no -- other references to any TVars involved, so it can't ever -- continue. data BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM :: BlockedIndefinitelyOnSTM -- | There are no runnable threads, so the program is deadlocked. The -- Deadlock exception is raised in the main thread only. data Deadlock Deadlock :: Deadlock -- | This thread has exceeded its allocation limit. See -- setAllocationCounter and enableAllocationLimit. data AllocationLimitExceeded AllocationLimitExceeded :: AllocationLimitExceeded -- | Compaction found an object that cannot be compacted. Functions cannot -- be compacted, nor can mutable objects or pinned objects. See -- compact. newtype CompactionFailed CompactionFailed :: String -> CompactionFailed -- | assert was applied to False. newtype AssertionFailed AssertionFailed :: String -> AssertionFailed -- | Superclass for asynchronous exceptions. data SomeAsyncException [SomeAsyncException] :: SomeAsyncException -- | Asynchronous exceptions. data AsyncException -- | The current thread's stack exceeded its limit. Since an exception has -- been raised, the thread's stack will certainly be below its limit -- again, but the programmer should take remedial action immediately. StackOverflow :: AsyncException -- | The program's heap is reaching its limit, and the program should take -- action to reduce the amount of live data it has. Notes: -- -- HeapOverflow :: AsyncException -- | This exception is raised by another thread calling killThread, -- or by the system if it needs to terminate the thread for some reason. ThreadKilled :: AsyncException -- | This exception is raised by default in the main thread of the program -- when the user requests to terminate the program via the usual -- mechanism(s) (e.g. Control-C in the console). UserInterrupt :: AsyncException -- | Exceptions generated by array operations data ArrayException -- | An attempt was made to index an array outside its declared bounds. IndexOutOfBounds :: String -> ArrayException -- | An attempt was made to evaluate an element of an array that had not -- been initialized. UndefinedElement :: String -> ArrayException -- | An abstract type that contains a value for each variant of -- IOError. data IOErrorType -- | Allow asynchronous exceptions to be raised even inside mask, -- making the operation interruptible (see the discussion of -- "Interruptible operations" in Exception). -- -- When called outside mask, or inside uninterruptibleMask, -- this function has no effect. interruptible :: () => IO a -> IO a -- | File and directory names are values of type String, whose -- precise meaning is operating system dependent. Files can be opened, -- yielding a handle which can then be used to operate on the contents of -- that file. type FilePath = String -- | Describes the behaviour of a thread when an asynchronous exception is -- received. data MaskingState -- | asynchronous exceptions are unmasked (the normal state) Unmasked :: MaskingState -- | the state during mask: asynchronous exceptions are masked, but -- blocking operations may still be interrupted MaskedInterruptible :: MaskingState -- | the state during uninterruptibleMask: asynchronous exceptions -- are masked, and blocking operations may not be interrupted MaskedUninterruptible :: MaskingState -- | Construct an IOError value with a string describing the error. -- The fail method of the IO instance of the Monad -- class raises a userError, thus: -- --
--   instance Monad IO where
--     ...
--     fail s = ioError (userError s)
--   
userError :: String -> IOError -- | Exceptions that occur in the IO monad. An -- IOException records a more specific error type, a descriptive -- string and maybe the handle that was used when the error was flagged. data IOException -- | The Haskell 2010 type for exceptions in the IO monad. Any I/O -- operation may raise an IOError instead of returning a result. -- For a more general type of exception, including also those that arise -- in pure code, see Exception. -- -- In Haskell 2010, this is an opaque type. type IOError = IOException -- | Throw an exception. Exceptions may be thrown from purely functional -- code, but may only be caught within the IO monad. throw :: Exception e => e -> a -- | Any type that you wish to throw or catch as an exception must be an -- instance of the Exception class. The simplest case is a new -- exception type directly below the root: -- --
--   data MyException = ThisException | ThatException
--       deriving Show
--   
--   instance Exception MyException
--   
-- -- The default method definitions in the Exception class do what -- we need in this case. You can now throw and catch -- ThisException and ThatException as exceptions: -- --
--   *Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
--   Caught ThisException
--   
-- -- In more complicated examples, you may wish to define a whole hierarchy -- of exceptions: -- --
--   ---------------------------------------------------------------------
--   -- Make the root exception type for all the exceptions in a compiler
--   
--   data SomeCompilerException = forall e . Exception e => SomeCompilerException e
--   
--   instance Show SomeCompilerException where
--       show (SomeCompilerException e) = show e
--   
--   instance Exception SomeCompilerException
--   
--   compilerExceptionToException :: Exception e => e -> SomeException
--   compilerExceptionToException = toException . SomeCompilerException
--   
--   compilerExceptionFromException :: Exception e => SomeException -> Maybe e
--   compilerExceptionFromException x = do
--       SomeCompilerException a <- fromException x
--       cast a
--   
--   ---------------------------------------------------------------------
--   -- Make a subhierarchy for exceptions in the frontend of the compiler
--   
--   data SomeFrontendException = forall e . Exception e => SomeFrontendException e
--   
--   instance Show SomeFrontendException where
--       show (SomeFrontendException e) = show e
--   
--   instance Exception SomeFrontendException where
--       toException = compilerExceptionToException
--       fromException = compilerExceptionFromException
--   
--   frontendExceptionToException :: Exception e => e -> SomeException
--   frontendExceptionToException = toException . SomeFrontendException
--   
--   frontendExceptionFromException :: Exception e => SomeException -> Maybe e
--   frontendExceptionFromException x = do
--       SomeFrontendException a <- fromException x
--       cast a
--   
--   ---------------------------------------------------------------------
--   -- Make an exception type for a particular frontend compiler exception
--   
--   data MismatchedParentheses = MismatchedParentheses
--       deriving Show
--   
--   instance Exception MismatchedParentheses where
--       toException   = frontendExceptionToException
--       fromException = frontendExceptionFromException
--   
-- -- We can now catch a MismatchedParentheses exception as -- MismatchedParentheses, SomeFrontendException or -- SomeCompilerException, but not other types, e.g. -- IOException: -- --
--   *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException))
--   *** Exception: MismatchedParentheses
--   
class (Typeable e, Show e) => Exception e toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Render this exception value in a human-friendly manner. -- -- Default implementation: show. displayException :: Exception e => e -> String -- | This is thrown when the user calls error. The first -- String is the argument given to error, second -- String is the location. data ErrorCall ErrorCallWithLocation :: String -> String -> ErrorCall -- | Arithmetic exceptions. data ArithException Overflow :: ArithException Underflow :: ArithException LossOfPrecision :: ArithException DivideByZero :: ArithException Denormal :: ArithException RatioZeroDenominator :: ArithException -- | The Const functor. newtype Const a (b :: k) :: forall k. () => * -> k -> * Const :: a -> Const a [getConst] :: Const a -> a -- | The find function takes a predicate and a structure and returns -- the leftmost element of the structure matching the predicate, or -- Nothing if there is no such element. find :: Foldable t => a -> Bool -> t a -> Maybe a -- | notElem is the negation of elem. notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 `notElem` -- | The least element of a non-empty structure with respect to the given -- comparison function. minimumBy :: Foldable t => a -> a -> Ordering -> t a -> a -- | The largest element of a non-empty structure with respect to the given -- comparison function. maximumBy :: Foldable t => a -> a -> Ordering -> t a -> a -- | Determines whether all elements of the structure satisfy the -- predicate. all :: Foldable t => a -> Bool -> t a -> Bool -- | Determines whether any element of the structure satisfies the -- predicate. any :: Foldable t => a -> Bool -> t a -> Bool -- | or returns the disjunction of a container of Bools. For the -- result to be False, the container must be finite; True, -- however, results from a True value finitely far from the left -- end. or :: Foldable t => t Bool -> Bool -- | and returns the conjunction of a container of Bools. For the -- result to be True, the container must be finite; False, -- however, results from a False value finitely far from the left -- end. and :: Foldable t => t Bool -> Bool -- | Map a function over all the elements of a container and concatenate -- the resulting lists. concatMap :: Foldable t => a -> [b] -> t a -> [b] -- | The sum of a collection of actions, generalizing concat. -- -- asum [Just Hello, Nothing, Just World] Just Hello asum :: (Foldable t, Alternative f) => t f a -> f a -- | Evaluate each action in the structure from left to right, and ignore -- the results. For a version that doesn't ignore the results see -- sequenceA. sequenceA_ :: (Foldable t, Applicative f) => t f a -> f () -- | for_ is traverse_ with its arguments flipped. For a -- version that doesn't ignore the results see for. -- --
--   >>> for_ [1..4] print
--   1
--   2
--   3
--   4
--   
for_ :: (Foldable t, Applicative f) => t a -> a -> f b -> f () -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and ignore the results. For a version that doesn't -- ignore the results see traverse. traverse_ :: (Foldable t, Applicative f) => a -> f b -> t a -> f () -- | The unfoldr function is a `dual' to foldr: while -- foldr reduces a list to a summary value, unfoldr builds -- a list from a seed value. The function takes the element and returns -- Nothing if it is done producing the list or returns Just -- (a,b), in which case, a is a prepended to the list -- and b is used as the next element in a recursive call. For -- example, -- --
--   iterate f == unfoldr (\x -> Just (x, f x))
--   
-- -- In some cases, unfoldr can undo a foldr operation: -- --
--   unfoldr f' (foldr f z xs) == xs
--   
-- -- if the following holds: -- --
--   f' (f x y) = Just (x,y)
--   f' z       = Nothing
--   
-- -- A simple use of unfoldr: -- --
--   >>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
--   [10,9,8,7,6,5,4,3,2,1]
--   
unfoldr :: () => b -> Maybe (a, b) -> b -> [a] -- | Sort a list by comparing the results of a key function applied to each -- element. sortOn f is equivalent to sortBy (comparing -- f), but has the performance advantage of only evaluating -- f once for each element in the input list. This is called the -- decorate-sort-undecorate paradigm, or Schwartzian transform. -- -- Elements are arranged from from lowest to highest, keeping duplicates -- in the order they appeared in the input. -- --
--   >>> sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
--   [(1,"Hello"),(2,"world"),(4,"!")]
--   
sortOn :: Ord b => a -> b -> [a] -> [a] -- | The sortBy function is the non-overloaded version of -- sort. -- --
--   >>> sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]
--   [(1,"Hello"),(2,"world"),(4,"!")]
--   
sortBy :: () => a -> a -> Ordering -> [a] -> [a] -- | The sort function implements a stable sorting algorithm. It is -- a special case of sortBy, which allows the programmer to supply -- their own comparison function. -- -- Elements are arranged from from lowest to highest, keeping duplicates -- in the order they appeared in the input. -- --
--   >>> sort [1,6,4,3,2,5]
--   [1,2,3,4,5,6]
--   
sort :: Ord a => [a] -> [a] -- | The permutations function returns the list of all permutations -- of the argument. -- --
--   >>> permutations "abc"
--   ["abc","bac","cba","bca","cab","acb"]
--   
permutations :: () => [a] -> [[a]] -- | The subsequences function returns the list of all subsequences -- of the argument. -- --
--   >>> subsequences "abc"
--   ["","a","b","ab","c","ac","bc","abc"]
--   
subsequences :: () => [a] -> [[a]] -- | The tails function returns all final segments of the argument, -- longest first. For example, -- --
--   >>> tails "abc"
--   ["abc","bc","c",""]
--   
-- -- Note that tails has the following strictness property: -- tails _|_ = _|_ : _|_ tails :: () => [a] -> [[a]] -- | The inits function returns all initial segments of the -- argument, shortest first. For example, -- --
--   >>> inits "abc"
--   ["","a","ab","abc"]
--   
-- -- Note that inits has the following strictness property: -- inits (xs ++ _|_) = inits xs ++ _|_ -- -- In particular, inits _|_ = [] : _|_ inits :: () => [a] -> [[a]] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: () => a -> a -> Bool -> [a] -> [[a]] -- | The group function takes a list and returns a list of lists -- such that the concatenation of the result is equal to the argument. -- Moreover, each sublist in the result contains only equal elements. For -- example, -- --
--   >>> group "Mississippi"
--   ["M","i","ss","i","ss","i","pp","i"]
--   
-- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. group :: Eq a => [a] -> [[a]] -- | The deleteFirstsBy function takes a predicate and two lists and -- returns the first list with the first occurrence of each element of -- the second list removed. deleteFirstsBy :: () => a -> a -> Bool -> [a] -> [a] -> [a] -- | The unzip7 function takes a list of seven-tuples and returns -- seven lists, analogous to unzip. unzip7 :: () => [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) -- | The unzip6 function takes a list of six-tuples and returns six -- lists, analogous to unzip. unzip6 :: () => [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) -- | The unzip5 function takes a list of five-tuples and returns -- five lists, analogous to unzip. unzip5 :: () => [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e]) -- | The unzip4 function takes a list of quadruples and returns four -- lists, analogous to unzip. unzip4 :: () => [(a, b, c, d)] -> ([a], [b], [c], [d]) -- | The zipWith7 function takes a function which combines seven -- elements, as well as seven lists and returns a list of their -- point-wise combination, analogous to zipWith. zipWith7 :: () => a -> b -> c -> d -> e -> f -> g -> h -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] -- | The zipWith6 function takes a function which combines six -- elements, as well as six lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith6 :: () => a -> b -> c -> d -> e -> f -> g -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -- | The zipWith5 function takes a function which combines five -- elements, as well as five lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith5 :: () => a -> b -> c -> d -> e -> f -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -- | The zipWith4 function takes a function which combines four -- elements, as well as four lists and returns a list of their point-wise -- combination, analogous to zipWith. zipWith4 :: () => a -> b -> c -> d -> e -> [a] -> [b] -> [c] -> [d] -> [e] -- | The zip7 function takes seven lists and returns a list of -- seven-tuples, analogous to zip. zip7 :: () => [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)] -- | The zip6 function takes six lists and returns a list of -- six-tuples, analogous to zip. zip6 :: () => [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)] -- | The zip5 function takes five lists and returns a list of -- five-tuples, analogous to zip. zip5 :: () => [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)] -- | The zip4 function takes four lists and returns a list of -- quadruples, analogous to zip. zip4 :: () => [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)] -- | The genericReplicate function is an overloaded version of -- replicate, which accepts any Integral value as the -- number of repetitions to make. genericReplicate :: Integral i => i -> a -> [a] -- | The genericIndex function is an overloaded version of -- !!, which accepts any Integral value as the index. genericIndex :: Integral i => [a] -> i -> a -- | The genericSplitAt function is an overloaded version of -- splitAt, which accepts any Integral value as the -- position at which to split. genericSplitAt :: Integral i => i -> [a] -> ([a], [a]) -- | The genericDrop function is an overloaded version of -- drop, which accepts any Integral value as the number of -- elements to drop. genericDrop :: Integral i => i -> [a] -> [a] -- | The genericTake function is an overloaded version of -- take, which accepts any Integral value as the number of -- elements to take. genericTake :: Integral i => i -> [a] -> [a] -- | The genericLength function is an overloaded version of -- length. In particular, instead of returning an Int, it -- returns any type which is an instance of Num. It is, however, -- less efficient than length. genericLength :: Num i => [a] -> i -- | The non-overloaded version of insert. insertBy :: () => a -> a -> Ordering -> a -> [a] -> [a] -- | The insert function takes an element and a list and inserts the -- element into the list at the first position where it is less than or -- equal to the next element. In particular, if the list is sorted before -- the call, the result will also be sorted. It is a special case of -- insertBy, which allows the programmer to supply their own -- comparison function. -- --
--   >>> insert 4 [1,2,3,5,6,7]
--   [1,2,3,4,5,6,7]
--   
insert :: Ord a => a -> [a] -> [a] -- | The partition function takes a predicate a list and returns the -- pair of lists of elements which do and do not satisfy the predicate, -- respectively; i.e., -- --
--   partition p xs == (filter p xs, filter (not . p) xs)
--   
-- --
--   >>> partition (`elem` "aeiou") "Hello World!"
--   ("eoo","Hll Wrld!")
--   
partition :: () => a -> Bool -> [a] -> ([a], [a]) -- | The transpose function transposes the rows and columns of its -- argument. For example, -- --
--   >>> transpose [[1,2,3],[4,5,6]]
--   [[1,4],[2,5],[3,6]]
--   
-- -- If some of the rows are shorter than the following rows, their -- elements are skipped: -- --
--   >>> transpose [[10,11],[20],[],[30,31,32]]
--   [[10,20,30],[11,31],[32]]
--   
transpose :: () => [[a]] -> [[a]] -- | The intersperse function takes an element and a list and -- `intersperses' that element between the elements of the list. For -- example, -- --
--   >>> intersperse ',' "abcde"
--   "a,b,c,d,e"
--   
intersperse :: () => a -> [a] -> [a] -- | The intersectBy function is the non-overloaded version of -- intersect. intersectBy :: () => a -> a -> Bool -> [a] -> [a] -> [a] -- | The intersect function takes the list intersection of two -- lists. For example, -- --
--   >>> [1,2,3,4] `intersect` [2,4,6,8]
--   [2,4]
--   
-- -- If the first list contains duplicates, so will the result. -- --
--   >>> [1,2,2,3,4] `intersect` [6,4,4,2]
--   [2,2,4]
--   
-- -- It is a special case of intersectBy, which allows the -- programmer to supply their own equality test. If the element is found -- in both the first and the second list, the element from the first list -- will be used. intersect :: Eq a => [a] -> [a] -> [a] -- | The unionBy function is the non-overloaded version of -- union. unionBy :: () => a -> a -> Bool -> [a] -> [a] -> [a] -- | The union function returns the list union of the two lists. For -- example, -- --
--   >>> "dog" `union` "cow"
--   "dogcw"
--   
-- -- Duplicates, and elements of the first list, are removed from the the -- second list, but if the first list contains duplicates, so will the -- result. It is a special case of unionBy, which allows the -- programmer to supply their own equality test. union :: Eq a => [a] -> [a] -> [a] -- | The \\ function is list difference (non-associative). In the -- result of xs \\ ys, the first occurrence of -- each element of ys in turn (if any) has been removed from -- xs. Thus -- --
--   (xs ++ ys) \\ xs == ys.
--   
-- --
--   >>> "Hello World!" \\ "ell W"
--   "Hoorld!"
--   
-- -- It is a special case of deleteFirstsBy, which allows the -- programmer to supply their own equality test. (\\) :: Eq a => [a] -> [a] -> [a] infix 5 \\ -- | The deleteBy function behaves like delete, but takes a -- user-supplied equality predicate. -- --
--   >>> deleteBy (<=) 4 [1..10]
--   [1,2,3,5,6,7,8,9,10]
--   
deleteBy :: () => a -> a -> Bool -> a -> [a] -> [a] -- | delete x removes the first occurrence of x -- from its list argument. For example, -- --
--   >>> delete 'a' "banana"
--   "bnana"
--   
-- -- It is a special case of deleteBy, which allows the programmer -- to supply their own equality test. delete :: Eq a => a -> [a] -> [a] -- | The nubBy function behaves just like nub, except it uses -- a user-supplied equality predicate instead of the overloaded == -- function. -- --
--   >>> nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6]
--   [1,2,6]
--   
nubBy :: () => a -> a -> Bool -> [a] -> [a] -- | O(n^2). The nub function removes duplicate elements from -- a list. In particular, it keeps only the first occurrence of each -- element. (The name nub means `essence'.) It is a special case -- of nubBy, which allows the programmer to supply their own -- equality test. -- --
--   >>> nub [1,2,3,4,3,2,1,2,4,3,5]
--   [1,2,3,4,5]
--   
nub :: Eq a => [a] -> [a] -- | The isInfixOf function takes two lists and returns True -- iff the first list is contained, wholly and intact, anywhere within -- the second. -- --
--   >>> isInfixOf "Haskell" "I really like Haskell."
--   True
--   
-- --
--   >>> isInfixOf "Ial" "I really like Haskell."
--   False
--   
isInfixOf :: Eq a => [a] -> [a] -> Bool -- | The isSuffixOf function takes two lists and returns True -- iff the first list is a suffix of the second. The second list must be -- finite. -- --
--   >>> "ld!" `isSuffixOf` "Hello World!"
--   True
--   
-- --
--   >>> "World" `isSuffixOf` "Hello World!"
--   False
--   
isSuffixOf :: Eq a => [a] -> [a] -> Bool -- | The isPrefixOf function takes two lists and returns True -- iff the first list is a prefix of the second. -- --
--   >>> "Hello" `isPrefixOf` "Hello World!"
--   True
--   
-- --
--   >>> "Hello" `isPrefixOf` "Wello Horld!"
--   False
--   
isPrefixOf :: Eq a => [a] -> [a] -> Bool -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. -- --
--   >>> findIndices (`elem` "aeiou") "Hello World!"
--   [1,4,7]
--   
findIndices :: () => a -> Bool -> [a] -> [Int] -- | The findIndex function takes a predicate and a list and returns -- the index of the first element in the list satisfying the predicate, -- or Nothing if there is no such element. -- --
--   >>> findIndex isSpace "Hello World!"
--   Just 5
--   
findIndex :: () => a -> Bool -> [a] -> Maybe Int -- | The elemIndices function extends elemIndex, by returning -- the indices of all elements equal to the query element, in ascending -- order. -- --
--   >>> elemIndices 'o' "Hello World"
--   [4,7]
--   
elemIndices :: Eq a => a -> [a] -> [Int] -- | The elemIndex function returns the index of the first element -- in the given list which is equal (by ==) to the query element, -- or Nothing if there is no such element. -- --
--   >>> elemIndex 4 [0..]
--   Just 4
--   
elemIndex :: Eq a => a -> [a] -> Maybe Int -- | The stripPrefix function drops the given prefix from a list. It -- returns Nothing if the list did not start with the prefix -- given, or Just the list after the prefix, if it does. -- --
--   >>> stripPrefix "foo" "foobar"
--   Just "bar"
--   
-- --
--   >>> stripPrefix "foo" "foo"
--   Just ""
--   
-- --
--   >>> stripPrefix "foo" "barfoo"
--   Nothing
--   
-- --
--   >>> stripPrefix "foo" "barfoobaz"
--   Nothing
--   
stripPrefix :: Eq a => [a] -> [a] -> Maybe [a] -- | The dropWhileEnd function drops the largest suffix of a list in -- which the given predicate holds for all elements. For example: -- --
--   >>> dropWhileEnd isSpace "foo\n"
--   "foo"
--   
-- --
--   >>> dropWhileEnd isSpace "foo bar"
--   "foo bar"
--   
-- --
--   dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined
--   
dropWhileEnd :: () => a -> Bool -> [a] -> [a] -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | Partitions a list of Either into two lists. All the Left -- elements are extracted, in order, to the first component of the -- output. Similarly the Right elements are extracted to the -- second component of the output. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> partitionEithers list
--   (["foo","bar","baz"],[3,7])
--   
-- -- The pair returned by partitionEithers x should be the -- same pair as (lefts x, rights x): -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> partitionEithers list == (lefts list, rights list)
--   True
--   
partitionEithers :: () => [Either a b] -> ([a], [b]) -- | Extracts from a list of Either all the Right elements. -- All the Right elements are extracted in order. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> rights list
--   [3,7]
--   
rights :: () => [Either a b] -> [b] -- | Extracts from a list of Either all the Left elements. -- All the Left elements are extracted in order. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> lefts list
--   ["foo","bar","baz"]
--   
lefts :: () => [Either a b] -> [a] -- |
--   comparing p x y = compare (p x) (p y)
--   
-- -- Useful combinator for use in conjunction with the xxxBy -- family of functions from Data.List, for example: -- --
--   ... sortBy (comparing fst) ...
--   
comparing :: Ord a => b -> a -> b -> b -> Ordering -- | The Down type allows you to reverse sort order conveniently. A -- value of type Down a contains a value of type -- a (represented as Down a). If a has -- an Ord instance associated with it then comparing two -- values thus wrapped will give you the opposite of their normal sort -- order. This is particularly useful when sorting in generalised list -- comprehensions, as in: then sortWith by Down x newtype Down a Down :: a -> Down a -- | the identity morphism id :: Category cat => cat a a -- | morphism composition (.) :: Category cat => cat b c -> cat a b -> cat a c infixr 9 . -- | The member functions of this class facilitate writing values of -- primitive types to raw memory (which may have been allocated with the -- above mentioned routines) and reading values from blocks of raw -- memory. The class, furthermore, includes support for computing the -- storage requirements and alignment restrictions of storable types. -- -- Memory addresses are represented as values of type Ptr -- a, for some a which is an instance of class -- Storable. The type argument to Ptr helps provide some -- valuable type safety in FFI code (you can't mix pointers of different -- types without an explicit cast), while helping the Haskell type system -- figure out which marshalling method is needed for a given pointer. -- -- All marshalling between Haskell and a foreign language ultimately -- boils down to translating Haskell data structures into the binary -- representation of a corresponding data structure of the foreign -- language and vice versa. To code this marshalling in Haskell, it is -- necessary to manipulate primitive data types stored in unstructured -- memory blocks. The class Storable facilitates this manipulation -- on all types for which it is instantiated, which are the standard -- basic types of Haskell, the fixed size Int types -- (Int8, Int16, Int32, Int64), the fixed -- size Word types (Word8, Word16, Word32, -- Word64), StablePtr, all types from -- Foreign.C.Types, as well as Ptr. class Storable a -- | The lex function reads a single lexeme from the input, -- discarding initial white space, and returning the characters that -- constitute the lexeme. If the input string contains only white space, -- lex returns a single successful `lexeme' consisting of the -- empty string. (Thus lex "" = [("","")].) If there is -- no legal lexeme at the beginning of the input string, lex fails -- (i.e. returns []). -- -- This lexer is not completely faithful to the Haskell lexical syntax in -- the following respects: -- -- lex :: ReadS String -- | readParen True p parses what p parses, -- but surrounded with parentheses. -- -- readParen False p parses what p -- parses, but optionally surrounded with parentheses. readParen :: () => Bool -> ReadS a -> ReadS a -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | Case analysis for the Bool type. bool x y p -- evaluates to x when p is False, and evaluates -- to y when p is True. -- -- This is equivalent to if p then y else x; that is, one can -- think of it as an if-then-else construct with its arguments reordered. -- --

Examples

-- -- Basic usage: -- --
--   >>> bool "foo" "bar" True
--   "bar"
--   
--   >>> bool "foo" "bar" False
--   "foo"
--   
-- -- Confirm that bool x y p and if p then y else -- x are equivalent: -- --
--   >>> let p = True; x = "bar"; y = "foo"
--   
--   >>> bool x y p == if p then y else x
--   True
--   
--   >>> let p = False
--   
--   >>> bool x y p == if p then y else x
--   True
--   
bool :: () => a -> a -> Bool -> a -- | & is a reverse application operator. This provides -- notational convenience. Its precedence is one higher than that of the -- forward application operator $, which allows & to be -- nested in $. -- --
--   >>> 5 & (+1) & show
--   "6"
--   
(&) :: () => a -> a -> b -> b infixl 1 & on :: () => b -> b -> c -> a -> b -> a -> a -> c infixl 0 `on` -- | Flipped version of <$>. -- --
--   (<&>) = flip fmap
--   
-- --

Examples

-- -- Apply (+1) to a list, a Just and a Right: -- --
--   >>> Just 2 <&> (+1)
--   Just 3
--   
-- --
--   >>> [1,2,3] <&> (+1)
--   [2,3,4]
--   
-- --
--   >>> Right 3 <&> (+1)
--   Right 4
--   
(<&>) :: Functor f => f a -> a -> b -> f b infixl 1 <&> -- | lcm x y is the smallest positive integer that both -- x and y divide. lcm :: Integral a => a -> a -> a -- | gcd x y is the non-negative factor of both x -- and y of which every common factor of x and -- y is also a factor; for example gcd 4 2 = 2, -- gcd (-4) 6 = 2, gcd 0 4 = 4. -- gcd 0 0 = 0. (That is, the common divisor -- that is "greatest" in the divisibility preordering.) -- -- Note: Since for signed fixed-width integer types, abs -- minBound < 0, the result may be negative if one of the -- arguments is minBound (and necessarily is if the other -- is 0 or minBound) for such types. gcd :: Integral a => a -> a -> a -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 ^^ -- | raise a number to a non-negative integral power (^) :: (Num a, Integral b) => a -> b -> a infixr 8 ^ odd :: Integral a => a -> Bool even :: Integral a => a -> Bool -- | utility function that surrounds the inner show function with -- parentheses when the Bool parameter is True. showParen :: Bool -> ShowS -> ShowS -- | utility function converting a String to a show function that -- simply prepends the string unchanged. showString :: String -> ShowS -- | utility function converting a Char to a show function that -- simply prepends the character unchanged. showChar :: Char -> ShowS -- | equivalent to showsPrec with a precedence of 0. shows :: Show a => a -> ShowS -- | The shows functions return a function that prepends the -- output String to an existing String. This allows -- constant-time concatenation of results using function composition. type ShowS = String -> String -- | The unzip3 function takes a list of triples and returns three -- lists, analogous to unzip. unzip3 :: () => [(a, b, c)] -> ([a], [b], [c]) -- | unzip transforms a list of pairs into a list of first -- components and a list of second components. unzip :: () => [(a, b)] -> ([a], [b]) -- | The zipWith3 function takes a function which combines three -- elements, as well as three lists and returns a list of their -- point-wise combination, analogous to zipWith. zipWith3 :: () => a -> b -> c -> d -> [a] -> [b] -> [c] -> [d] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two lists to -- produce the list of corresponding sums. -- -- zipWith is right-lazy: -- --
--   zipWith f [] _|_ = []
--   
zipWith :: () => a -> b -> c -> [a] -> [b] -> [c] -- | zip3 takes three lists and returns a list of triples, analogous -- to zip. zip3 :: () => [a] -> [b] -> [c] -> [(a, b, c)] -- | List index (subscript) operator, starting from 0. It is an instance of -- the more general genericIndex, which takes an index of any -- integral type. (!!) :: () => [a] -> Int -> a infixl 9 !! -- | lookup key assocs looks up a key in an association -- list. lookup :: Eq a => a -> [(a, b)] -> Maybe b -- | reverse xs returns the elements of xs in -- reverse order. xs must be finite. reverse :: () => [a] -> [a] -- | break, applied to a predicate p and a list -- xs, returns a tuple where first element is longest prefix -- (possibly empty) of xs of elements that do not satisfy -- p and second element is the remainder of the list: -- --
--   break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4])
--   break (< 9) [1,2,3] == ([],[1,2,3])
--   break (> 9) [1,2,3] == ([1,2,3],[])
--   
-- -- break p is equivalent to span (not . -- p). break :: () => a -> Bool -> [a] -> ([a], [a]) -- | span, applied to a predicate p and a list xs, -- returns a tuple where first element is longest prefix (possibly empty) -- of xs of elements that satisfy p and second element -- is the remainder of the list: -- --
--   span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4])
--   span (< 9) [1,2,3] == ([1,2,3],[])
--   span (< 0) [1,2,3] == ([],[1,2,3])
--   
-- -- span p xs is equivalent to (takeWhile p xs, -- dropWhile p xs) span :: () => a -> Bool -> [a] -> ([a], [a]) -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
--   splitAt 6 "Hello World!" == ("Hello ","World!")
--   splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5])
--   splitAt 1 [1,2,3] == ([1],[2,3])
--   splitAt 3 [1,2,3] == ([1,2,3],[])
--   splitAt 4 [1,2,3] == ([1,2,3],[])
--   splitAt 0 [1,2,3] == ([],[1,2,3])
--   splitAt (-1) [1,2,3] == ([],[1,2,3])
--   
-- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: () => Int -> [a] -> ([a], [a]) -- | drop n xs returns the suffix of xs after the -- first n elements, or [] if n > length -- xs: -- --
--   drop 6 "Hello World!" == "World!"
--   drop 3 [1,2,3,4,5] == [4,5]
--   drop 3 [1,2] == []
--   drop 3 [] == []
--   drop (-1) [1,2] == [1,2]
--   drop 0 [1,2] == [1,2]
--   
-- -- It is an instance of the more general genericDrop, in which -- n may be of any integral type. drop :: () => Int -> [a] -> [a] -- | take n, applied to a list xs, returns the -- prefix of xs of length n, or xs itself if -- n > length xs: -- --
--   take 5 "Hello World!" == "Hello"
--   take 3 [1,2,3,4,5] == [1,2,3]
--   take 3 [1,2] == [1,2]
--   take 3 [] == []
--   take (-1) [1,2] == []
--   take 0 [1,2] == []
--   
-- -- It is an instance of the more general genericTake, in which -- n may be of any integral type. take :: () => Int -> [a] -> [a] -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs: -- --
--   dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3]
--   dropWhile (< 9) [1,2,3] == []
--   dropWhile (< 0) [1,2,3] == [1,2,3]
--   
dropWhile :: () => a -> Bool -> [a] -> [a] -- | takeWhile, applied to a predicate p and a list -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p: -- --
--   takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2]
--   takeWhile (< 9) [1,2,3] == [1,2,3]
--   takeWhile (< 0) [1,2,3] == []
--   
takeWhile :: () => a -> Bool -> [a] -> [a] -- | cycle ties a finite list into a circular one, or equivalently, -- the infinite repetition of the original list. It is the identity on -- infinite lists. cycle :: () => [a] -> [a] -- | replicate n x is a list of length n with -- x the value of every element. It is an instance of the more -- general genericReplicate, in which n may be of any -- integral type. replicate :: () => Int -> a -> [a] -- | repeat x is an infinite list, with x the -- value of every element. repeat :: () => a -> [a] -- | 'iterate\'' is the strict version of iterate. -- -- It ensures that the result of each application of force to weak head -- normal form before proceeding. iterate' :: () => a -> a -> a -> [a] -- | iterate f x returns an infinite list of repeated -- applications of f to x: -- --
--   iterate f x == [x, f x, f (f x), ...]
--   
-- -- Note that iterate is lazy, potentially leading to thunk -- build-up if the consumer doesn't force each iterate. See 'iterate\'' -- for a strict variant of this function. iterate :: () => a -> a -> a -> [a] -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: () => a -> a -> a -> [a] -> [a] -- | scanr is the right-to-left dual of scanl. Note that -- --
--   head (scanr f z xs) == foldr f z xs.
--   
scanr :: () => a -> b -> b -> b -> [a] -> [b] -- | A strictly accumulating version of scanl scanl' :: () => b -> a -> b -> b -> [a] -> [b] -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
scanl1 :: () => a -> a -> a -> [a] -> [a] -- | scanl is similar to foldl, but returns a list of -- successive reduced values from the left: -- --
--   scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--   
-- -- Note that -- --
--   last (scanl f z xs) == foldl f z xs.
--   
scanl :: () => b -> a -> b -> b -> [a] -> [b] -- | A strict version of foldl1 foldl1' :: () => a -> a -> a -> [a] -> a -- | Return all the elements of a list except the last one. The list must -- be non-empty. init :: () => [a] -> [a] -- | Extract the last element of a list, which must be finite and -- non-empty. last :: () => [a] -> a -- | Extract the elements after the head of a list, which must be -- non-empty. tail :: () => [a] -> [a] -- | Decompose a list into its head and tail. If the list is empty, returns -- Nothing. If the list is non-empty, returns Just (x, -- xs), where x is the head of the list and xs its -- tail. uncons :: () => [a] -> Maybe (a, [a]) -- | Extract the first element of a list, which must be non-empty. head :: () => [a] -> a -- | The mapMaybe function is a version of map which can -- throw out elements. In particular, the functional argument returns -- something of type Maybe b. If this is Nothing, -- no element is added on to the result list. If it is Just -- b, then b is included in the result list. -- --

Examples

-- -- Using mapMaybe f x is a shortcut for -- catMaybes $ map f x in most cases: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> let readMaybeInt = readMaybe :: String -> Maybe Int
--   
--   >>> mapMaybe readMaybeInt ["1", "Foo", "3"]
--   [1,3]
--   
--   >>> catMaybes $ map readMaybeInt ["1", "Foo", "3"]
--   [1,3]
--   
-- -- If we map the Just constructor, the entire list should be -- returned: -- --
--   >>> mapMaybe Just [1,2,3]
--   [1,2,3]
--   
mapMaybe :: () => a -> Maybe b -> [a] -> [b] -- | The catMaybes function takes a list of Maybes and -- returns a list of all the Just values. -- --

Examples

-- -- Basic usage: -- --
--   >>> catMaybes [Just 1, Nothing, Just 3]
--   [1,3]
--   
-- -- When constructing a list of Maybe values, catMaybes can -- be used to return all of the "success" results (if the list is the -- result of a map, then mapMaybe would be more -- appropriate): -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
--   [Just 1,Nothing,Just 3]
--   
--   >>> catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
--   [1,3]
--   
catMaybes :: () => [Maybe a] -> [a] -- | The listToMaybe function returns Nothing on an empty -- list or Just a where a is the first element -- of the list. -- --

Examples

-- -- Basic usage: -- --
--   >>> listToMaybe []
--   Nothing
--   
-- --
--   >>> listToMaybe [9]
--   Just 9
--   
-- --
--   >>> listToMaybe [1,2,3]
--   Just 1
--   
-- -- Composing maybeToList with listToMaybe should be the -- identity on singleton/empty lists: -- --
--   >>> maybeToList $ listToMaybe [5]
--   [5]
--   
--   >>> maybeToList $ listToMaybe []
--   []
--   
-- -- But not on lists with more than one element: -- --
--   >>> maybeToList $ listToMaybe [1,2,3]
--   [1]
--   
listToMaybe :: () => [a] -> Maybe a -- | The maybeToList function returns an empty list when given -- Nothing or a singleton list when not given Nothing. -- --

Examples

-- -- Basic usage: -- --
--   >>> maybeToList (Just 7)
--   [7]
--   
-- --
--   >>> maybeToList Nothing
--   []
--   
-- -- One can use maybeToList to avoid pattern matching when combined -- with a function that (safely) works on lists: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> sum $ maybeToList (readMaybe "3")
--   3
--   
--   >>> sum $ maybeToList (readMaybe "")
--   0
--   
maybeToList :: () => Maybe a -> [a] -- | The fromMaybe function takes a default value and and -- Maybe value. If the Maybe is Nothing, it returns -- the default values; otherwise, it returns the value contained in the -- Maybe. -- --

Examples

-- -- Basic usage: -- --
--   >>> fromMaybe "" (Just "Hello, World!")
--   "Hello, World!"
--   
-- --
--   >>> fromMaybe "" Nothing
--   ""
--   
-- -- Read an integer from a string using readMaybe. If we fail to -- parse an integer, we want to return 0 by default: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> fromMaybe 0 (readMaybe "5")
--   5
--   
--   >>> fromMaybe 0 (readMaybe "")
--   0
--   
fromMaybe :: () => a -> Maybe a -> a -- | The isNothing function returns True iff its argument is -- Nothing. -- --

Examples

-- -- Basic usage: -- --
--   >>> isNothing (Just 3)
--   False
--   
-- --
--   >>> isNothing (Just ())
--   False
--   
-- --
--   >>> isNothing Nothing
--   True
--   
-- -- Only the outer constructor is taken into consideration: -- --
--   >>> isNothing (Just Nothing)
--   False
--   
isNothing :: () => Maybe a -> Bool -- | The isJust function returns True iff its argument is of -- the form Just _. -- --

Examples

-- -- Basic usage: -- --
--   >>> isJust (Just 3)
--   True
--   
-- --
--   >>> isJust (Just ())
--   True
--   
-- --
--   >>> isJust Nothing
--   False
--   
-- -- Only the outer constructor is taken into consideration: -- --
--   >>> isJust (Just Nothing)
--   True
--   
isJust :: () => Maybe a -> Bool -- | The maybe function takes a default value, a function, and a -- Maybe value. If the Maybe value is Nothing, the -- function returns the default value. Otherwise, it applies the function -- to the value inside the Just and returns the result. -- --

Examples

-- -- Basic usage: -- --
--   >>> maybe False odd (Just 3)
--   True
--   
-- --
--   >>> maybe False odd Nothing
--   False
--   
-- -- Read an integer from a string using readMaybe. If we succeed, -- return twice the integer; that is, apply (*2) to it. If -- instead we fail to parse an integer, return 0 by default: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> maybe 0 (*2) (readMaybe "5")
--   10
--   
--   >>> maybe 0 (*2) (readMaybe "")
--   0
--   
-- -- Apply show to a Maybe Int. If we have Just -- n, we want to show the underlying Int n. But if -- we have Nothing, we return the empty string instead of (for -- example) "Nothing": -- --
--   >>> maybe "" show (Just 5)
--   "5"
--   
--   >>> maybe "" show Nothing
--   ""
--   
maybe :: () => b -> a -> b -> Maybe a -> b -- | Swap the components of a pair. swap :: () => (a, b) -> (b, a) -- | uncurry converts a curried function to a function on pairs. -- --

Examples

-- --
--   >>> uncurry (+) (1,2)
--   3
--   
-- --
--   >>> uncurry ($) (show, 1)
--   "1"
--   
-- --
--   >>> map (uncurry max) [(1,2), (3,4), (6,8)]
--   [2,4,8]
--   
uncurry :: () => a -> b -> c -> (a, b) -> c -- | curry converts an uncurried function to a curried function. -- --

Examples

-- --
--   >>> curry fst 1 2
--   1
--   
curry :: () => (a, b) -> c -> a -> b -> c -- | the same as flip (-). -- -- Because - is treated specially in the Haskell grammar, -- (- e) is not a section, but an application of -- prefix negation. However, (subtract -- exp) is equivalent to the disallowed section. subtract :: Num a => a -> a -> a -- | asTypeOf is a type-restricted version of const. It is -- usually used as an infix operator, and its typing forces its first -- argument (which is usually overloaded) to have the same type as the -- second. asTypeOf :: () => a -> a -> a -- | until p f yields the result of applying f -- until p holds. until :: () => a -> Bool -> a -> a -> a -> a -- | Strict (call-by-value) application operator. It takes a function and -- an argument, evaluates the argument to weak head normal form (WHNF), -- then calls the function with that value. ($!) :: () => a -> b -> a -> b infixr 0 $! -- | flip f takes its (first) two arguments in the reverse -- order of f. -- --
--   >>> flip (++) "hello" "world"
--   "worldhello"
--   
flip :: () => a -> b -> c -> b -> a -> c -- | const x is a unary function which evaluates to x for -- all inputs. -- --
--   >>> const 42 "hello"
--   42
--   
-- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: () => a -> b -> a -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: HasCallStack => a -- | error stops execution and displays an error message. error :: HasCallStack => [Char] -> a -- | The SomeException type is the root of the exception type -- hierarchy. When an exception of type e is thrown, behind the -- scenes it is encapsulated in a SomeException. data SomeException [SomeException] :: SomeException -- | Boolean "and" (&&) :: Bool -> Bool -> Bool infixr 3 && -- | Boolean "or" (||) :: Bool -> Bool -> Bool infixr 2 || -- | Boolean "not" not :: Bool -> Bool -- | The readLn function combines getLine and readIO. readLn :: (MonadIO m, Read a) => m a putChar :: MonadIO m => Char -> m () getChar :: MonadIO m => m Char readMay :: Read a => Text -> Maybe a interact :: MonadIO m => LText -> LText -> m () getContents :: MonadIO m => m LText getLine :: MonadIO m => m Text -- | Note that this is not the standard -- Data.Text.Encoding.decodeUtf8. That function will throw -- impure exceptions on any decoding errors. This function instead uses -- decodeLenient. decodeUtf8 :: ByteString -> Text -- | Since 0.3.13 fpToString :: FilePath -> String -- | Since 0.3.13 fpFromText :: Text -> FilePath -- | This function assumes file paths are encoded in UTF8. If it cannot -- decode the FilePath, the result is just an approximation. -- -- Since 0.3.13 fpToText :: FilePath -> Text ltextToString :: LText -> String textToString :: Text -> String -- | Write Text to the end of a file. appendFile :: MonadIO m => FilePath -> Text -> m () -- | Write Text to a file. The file is truncated to zero length before -- writing begins. writeFile :: MonadIO m => FilePath -> Text -> m () -- | Read a file and return the contents of the file as Text. The entire -- file is read strictly. readFile :: MonadIO m => FilePath -> m Text -- | The readIO function is similar to read except that it signals parse -- failure to the IO monad instead of terminating the program. readIO :: (MonadIO m, Read a) => Text -> m a -- | Parse Text to a value read :: Read a => Text -> a -- | Convert a value to readable IsString -- -- Since 0.3.12 fromShow :: (Show a, IsString b) => a -> b -- | Convert a value to readable Text tshow :: Show a => a -> Text -- | Compute the product of a finite list of numbers. product :: (Foldable f, Num a) => f a -> a -- | Compute the sum of a finite list of numbers. sum :: (Foldable f, Num a) => f a -> a -- |
--   intercalate = mconcat .: intersperse
--   
intercalate :: Monoid w => w -> [w] -> w -- |
--   concat = mconcat
--   
concat :: Monoid w => [w] -> w -- |
--   (++) = mappend
--   
(++) :: Monoid w => w -> w -> w infixr 5 ++ -- |
--   empty = mempty
--   
empty :: Monoid w => w -- |
--   map = fmap
--   
map :: Functor f => a -> b -> f a -> f b -- | error applied to Text -- -- Since 0.4.1 terror :: HasCallStack => Text -> a print :: (MonadIO m, Show a) => a -> m () putStrLn :: MonadIO m => Text -> m () putStr :: MonadIO m => Text -> m () getArgs :: MonadIO m => m [Text] equating :: Eq a => b -> a -> b -> b -> Bool type LText = Text type LByteString = ByteString type UVector = Vector type SVector = Vector -- | Boxed vectors, supporting efficient slicing. data Vector a class (Vector Vector a, MVector MVector a) => Unbox a -- | A set of values. A set cannot contain duplicate values. data HashSet a -- | Encode text using UTF-8 encoding. encodeUtf8 :: Text -> ByteString -- | O(n) Breaks a Text up into a list of words, delimited by -- Chars representing white space. words :: Text -> [Text] -- | O(n) Breaks a Text up into a list of Texts at -- newline Chars. The resulting strings do not contain newlines. lines :: Text -> [Text] -- | O(n) Joins lines, after appending a terminating newline to -- each. unlines :: [Text] -> Text -- | O(n) Joins words using single space characters. unwords :: [Text] -> Text -- | Add an extension, even if there is already one there, equivalent to -- addExtension. -- --
--   "/directory/path" <.> "ext" == "/directory/path.ext"
--   "/directory/path" <.> ".ext" == "/directory/path.ext"
--   
(<.>) :: FilePath -> String -> FilePath infixr 7 <.> -- | Combine two paths with a path separator. If the second path starts -- with a path separator or a drive letter, then it returns the second. -- The intention is that readFile (dir </> file) -- will access the same file as setCurrentDirectory dir; readFile -- file. -- --
--   Posix:   "/directory" </> "file.ext" == "/directory/file.ext"
--   Windows: "/directory" </> "file.ext" == "/directory\\file.ext"
--            "directory" </> "/file.ext" == "/file.ext"
--   Valid x => (takeDirectory x </> takeFileName x) `equalFilePath` x
--   
-- -- Combined: -- --
--   Posix:   "/" </> "test" == "/test"
--   Posix:   "home" </> "bob" == "home/bob"
--   Posix:   "x:" </> "foo" == "x:/foo"
--   Windows: "C:\\foo" </> "bar" == "C:\\foo\\bar"
--   Windows: "home" </> "bob" == "home\\bob"
--   
-- -- Not combined: -- --
--   Posix:   "home" </> "/bob" == "/bob"
--   Windows: "home" </> "C:\\bob" == "C:\\bob"
--   
-- -- Not combined (tricky): -- -- On Windows, if a filepath starts with a single slash, it is relative -- to the root of the current drive. In [1], this is (confusingly) -- referred to as an absolute path. The current behavior of -- </> is to never combine these forms. -- --
--   Windows: "home" </> "/bob" == "/bob"
--   Windows: "home" </> "\\bob" == "\\bob"
--   Windows: "C:\\home" </> "\\bob" == "\\bob"
--   
-- -- On Windows, from [1]: "If a file name begins with only a disk -- designator but not the backslash after the colon, it is interpreted as -- a relative path to the current directory on the drive with the -- specified letter." The current behavior of </> is to -- never combine these forms. -- --
--   Windows: "D:\\foo" </> "C:bar" == "C:bar"
--   Windows: "C:\\foo" </> "C:bar" == "C:bar"
--   
() :: FilePath -> FilePath -> FilePath infixr 5 -- | A set of values a. data Set a -- | General-purpose finite sequences. data Seq a -- | A set of integers. data IntSet -- | A map of integers to values a. data IntMap a -- | Formally, the class Profunctor represents a profunctor from -- Hask -> Hask. -- -- Intuitively it is a bifunctor where the first argument is -- contravariant and the second argument is covariant. -- -- You can define a Profunctor by either defining dimap or -- by defining both lmap and rmap. -- -- If you supply dimap, you should ensure that: -- --
--   dimap id idid
--   
-- -- If you supply lmap and rmap, ensure: -- --
--   lmap idid
--   rmap idid
--   
-- -- If you supply both, you should also ensure: -- --
--   dimap f g ≡ lmap f . rmap g
--   
-- -- These ensure by parametricity: -- --
--   dimap (f . g) (h . i) ≡ dimap g h . dimap f i
--   lmap (f . g) ≡ lmap g . lmap f
--   rmap (f . g) ≡ rmap f . rmap g
--   
class Profunctor (p :: * -> * -> *) -- | Map over both arguments at the same time. -- --
--   dimap f g ≡ lmap f . rmap g
--   
dimap :: Profunctor p => a -> b -> c -> d -> p b c -> p a d -- | Map the first argument contravariantly. -- --
--   lmap f ≡ dimap f id
--   
lmap :: Profunctor p => a -> b -> p b c -> p a c -- | Map the second argument covariantly. -- --
--   rmapdimap id
--   
rmap :: Profunctor p => b -> c -> p a b -> p a c defaultFieldRules :: LensRules -- | Generate overloaded field accessors based on field names which are -- only prefixed with an underscore (e.g. _name), not -- additionally with the type name (e.g. _fooName). -- -- This might be the desired behaviour in case the -- DuplicateRecordFields language extension is used in order to -- get rid of the necessity to prefix each field name with the type name. -- -- As an example: -- --
--   data Foo a  = Foo { _x :: Int, _y :: a }
--   newtype Bar = Bar { _x :: Char }
--   makeFieldsNoPrefix ''Foo
--   makeFieldsNoPrefix ''Bar
--   
-- -- will create classes -- --
--   class HasX s a | s -> a where
--     x :: Lens' s a
--   class HasY s a | s -> a where
--     y :: Lens' s a
--   
-- -- together with instances -- --
--   instance HasX (Foo a) Int
--   instance HasY (Foo a) a where
--   instance HasX Bar Char where
--   
-- -- For details, see classUnderscoreNoPrefixFields. -- --
--   makeFieldsNoPrefix = makeLensesWith classUnderscoreNoPrefixFields
--   
makeFieldsNoPrefix :: Name -> DecsQ -- | Generate overloaded field accessors. -- -- e.g -- --
--   data Foo a = Foo { _fooX :: Int, _fooY :: a }
--   newtype Bar = Bar { _barX :: Char }
--   makeFields ''Foo
--   makeFields ''Bar
--   
-- -- will create -- --
--   _fooXLens :: Lens' (Foo a) Int
--   _fooYLens :: Lens (Foo a) (Foo b) a b
--   class HasX s a | s -> a where
--     x :: Lens' s a
--   instance HasX (Foo a) Int where
--     x = _fooXLens
--   class HasY s a | s -> a where
--     y :: Lens' s a
--   instance HasY (Foo a) a where
--     y = _fooYLens
--   _barXLens :: Iso' Bar Char
--   instance HasX Bar Char where
--     x = _barXLens
--   
-- -- For details, see camelCaseFields. -- --
--   makeFields = makeLensesWith defaultFieldRules
--   
makeFields :: Name -> DecsQ -- | A FieldNamer for abbreviatedFields. abbreviatedNamer :: FieldNamer -- | Field rules fields in the form prefixFieldname or -- _prefixFieldname If you want all fields to be lensed, then there -- is no reason to use an _ before the prefix. If any of the -- record fields leads with an _ then it is assume a field -- without an _ should not have a lens created. -- -- Note that prefix may be any string of characters that are not -- uppercase letters. (In particular, it may be arbitrary string of -- lowercase letters and numbers) This is the behavior that -- defaultFieldRules had in lens 4.4 and earlier. abbreviatedFields :: LensRules -- | A FieldNamer for classUnderscoreNoPrefixFields. classUnderscoreNoPrefixNamer :: FieldNamer -- | Field rules for fields in the form _fieldname (the leading -- underscore is mandatory). -- -- Note: The primary difference to camelCaseFields is that -- for classUnderscoreNoPrefixFields the field names are not -- expected to be prefixed with the type name. This might be the desired -- behaviour when the DuplicateRecordFields extension is -- enabled. classUnderscoreNoPrefixFields :: LensRules -- | A FieldNamer for camelCaseFields. camelCaseNamer :: FieldNamer -- | Field rules for fields in the form prefixFieldname or -- _prefixFieldname If you want all fields to be lensed, then there -- is no reason to use an _ before the prefix. If any of the -- record fields leads with an _ then it is assume a field -- without an _ should not have a lens created. -- -- Note: The prefix must be the same as the typename -- (with the first letter lowercased). This is a change from lens -- versions before lens 4.5. If you want the old behaviour, use -- makeLensesWith abbreviatedFields camelCaseFields :: LensRules -- | A FieldNamer for underscoreFields. underscoreNamer :: FieldNamer -- | Field rules for fields in the form _prefix_fieldname underscoreFields :: LensRules -- | Build Wrapped instance for a given newtype makeWrapped :: Name -> DecsQ -- | Declare lenses for each records in the given declarations, using the -- specified LensRules. Any record syntax in the input will be -- stripped off. declareLensesWith :: LensRules -> DecsQ -> DecsQ -- |
--   declareFields = declareLensesWith defaultFieldRules
--   
declareFields :: DecsQ -> DecsQ -- | Build Wrapped instance for each newtype. declareWrapped :: DecsQ -> DecsQ -- | Generate a Prism for each constructor of each data type. -- -- e.g. -- --
--   declarePrisms [d|
--     data Exp = Lit Int | Var String | Lambda{ bound::String, body::Exp }
--     |]
--   
-- -- will create -- --
--   data Exp = Lit Int | Var String | Lambda { bound::String, body::Exp }
--   _Lit :: Prism' Exp Int
--   _Var :: Prism' Exp String
--   _Lambda :: Prism' Exp (String, Exp)
--   
declarePrisms :: DecsQ -> DecsQ -- | Similar to makeClassyFor, but takes a declaration quote. declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ -- | For each record in the declaration quote, make lenses and traversals -- for it, and create a class when the type has no arguments. All record -- syntax in the input will be stripped off. -- -- e.g. -- --
--   declareClassy [d|
--     data Foo = Foo { fooX, fooY :: Int }
--       deriving Show
--     |]
--   
-- -- will create -- --
--   data Foo = Foo Int Int deriving Show
--   class HasFoo t where
--     foo :: Lens' t Foo
--   instance HasFoo Foo where foo = id
--   fooX, fooY :: HasFoo t => Lens' t Int
--   
declareClassy :: DecsQ -> DecsQ -- | Similar to makeLensesFor, but takes a declaration quote. declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ -- | Make lenses for all records in the given declaration quote. All record -- syntax in the input will be stripped off. -- -- e.g. -- --
--   declareLenses [d|
--     data Foo = Foo { fooX, fooY :: Int }
--       deriving Show
--     |]
--   
-- -- will create -- --
--   data Foo = Foo Int Int deriving Show
--   fooX, fooY :: Lens' Foo Int
--   
declareLenses :: DecsQ -> DecsQ -- | Build lenses with a custom configuration. makeLensesWith :: LensRules -> Name -> DecsQ -- | Derive lenses and traversals, using a named wrapper class, and -- specifying explicit pairings of (fieldName, traversalName). -- -- Example usage: -- --
--   makeClassyFor "HasFoo" "foo" [("_foo", "fooLens"), ("bar", "lbar")] ''Foo
--   
makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ -- | Derive lenses and traversals, specifying explicit pairings of -- (fieldName, lensName). -- -- If you map multiple names to the same label, and it is present in the -- same constructor then this will generate a Traversal. -- -- e.g. -- --
--   makeLensesFor [("_foo", "fooLens"), ("baz", "lbaz")] ''Foo
--   makeLensesFor [("_barX", "bar"), ("_barY", "bar")] ''Bar
--   
makeLensesFor :: [(String, String)] -> Name -> DecsQ -- | Make lenses and traversals for a type, and create a class when the -- type has no arguments. Works the same as makeClassy except that -- (a) it expects that record field names do not begin with an -- underscore, (b) all record fields are made into lenses, and (c) the -- resulting lens is prefixed with an underscore. makeClassy_ :: Name -> DecsQ -- | Make lenses and traversals for a type, and create a class when the -- type has no arguments. -- -- e.g. -- --
--   data Foo = Foo { _fooX, _fooY :: Int }
--   makeClassy ''Foo
--   
-- -- will create -- --
--   class HasFoo t where
--     foo :: Lens' t Foo
--     fooX :: Lens' t Int
--     fooX = foo . go where go f (Foo x y) = (\x' -> Foo x' y) <$> f x
--     fooY :: Lens' t Int
--     fooY = foo . go where go f (Foo x y) = (\y' -> Foo x y') <$> f y
--   instance HasFoo Foo where
--     foo = id
--   
-- --
--   makeClassy = makeLensesWith classyRules
--   
makeClassy :: Name -> DecsQ -- | Build lenses (and traversals) with a sensible default configuration. -- -- e.g. -- --
--   data FooBar
--     = Foo { _x, _y :: Int }
--     | Bar { _x :: Int }
--   makeLenses ''FooBar
--   
-- -- will create -- --
--   x :: Lens' FooBar Int
--   x f (Foo a b) = (\a' -> Foo a' b) <$> f a
--   x f (Bar a)   = Bar <$> f a
--   y :: Traversal' FooBar Int
--   y f (Foo a b) = (\b' -> Foo a  b') <$> f b
--   y _ c@(Bar _) = pure c
--   
-- --
--   makeLenses = makeLensesWith lensRules
--   
makeLenses :: Name -> DecsQ -- | A LensRules used by makeClassy_. classyRules_ :: LensRules -- | Rules for making lenses and traversals that precompose another -- Lens. classyRules :: LensRules -- | Create a FieldNamer from a mapping function. If the function -- returns [], it creates no lens for the field. mappingNamer :: String -> [String] -> FieldNamer -- | Create a FieldNamer from explicit pairings of (fieldName, -- lensName). lookingupNamer :: [(String, String)] -> FieldNamer -- | Construct a LensRules value for generating top-level -- definitions using the given map from field names to definition names. lensRulesFor :: [(String, String)] -> LensRules -- | A FieldNamer that strips the _ off of the field name, -- lowercases the name, and skips the field if it doesn't start with an -- '_'. underscoreNoPrefixNamer :: FieldNamer -- | Rules for making fairly simple partial lenses, ignoring the special -- cases for isomorphisms and traversals, and not making any classes. It -- uses underscoreNoPrefixNamer. lensRules :: LensRules -- | Lens' to access the option for naming "classy" lenses. lensClass :: Lens' LensRules ClassyNamer -- | Lens' to access the convention for naming fields in our -- LensRules. lensField :: Lens' LensRules FieldNamer -- | Create the class if the constructor is Simple and the -- lensClass rule matches. createClass :: Lens' LensRules Bool -- | Generate optics using lazy pattern matches. This can allow fields of -- an undefined value to be initialized with lenses: -- --
--   data Foo = Foo {_x :: Int, _y :: Bool}
--     deriving Show
--   
--   makeLensesWith (lensRules & generateLazyPatterns .~ True) ''Foo
--   
-- --
--   > undefined & x .~ 8 & y .~ True
--   Foo {_x = 8, _y = True}
--   
-- -- The downside of this flag is that it can lead to space-leaks and -- code-size/compile-time increases when generated for large records. By -- default this flag is turned off, and strict optics are generated. -- -- When using lazy optics the strict optic can be recovered by composing -- with $!: -- --
--   strictOptic = ($!) . lazyOptic
--   
generateLazyPatterns :: Lens' LensRules Bool -- | Generate "updateable" optics when True. When False, -- Folds will be generated instead of Traversals and -- Getters will be generated instead of Lenses. This mode -- is intended to be used for types with invariants which must be -- maintained by "smart" constructors. generateUpdateableOptics :: Lens' LensRules Bool -- | Indicate whether or not to supply the signatures for the generated -- lenses. -- -- Disabling this can be useful if you want to provide a more restricted -- type signature or if you want to supply hand-written haddocks. generateSignatures :: Lens' LensRules Bool -- | Generate "simple" optics even when type-changing optics are possible. -- (e.g. Lens' instead of Lens) simpleLenses :: Lens' LensRules Bool -- | Rules to construct lenses for data fields. data LensRules -- | The rule to create function names of lenses for data fields. -- -- Although it's sometimes useful, you won't need the first two arguments -- most of the time. type FieldNamer = Name -> [Name] -> Name -> [DefName] -- | Name to give to generated field optics. data DefName -- | Simple top-level definiton name TopName :: Name -> DefName -- | makeFields-style class name and method name MethodName :: Name -> Name -> DefName -- | The optional rule to create a class and method around a monomorphic -- data type. If this naming convention is provided, it generates a -- "classy" lens. type ClassyNamer = Name -> Maybe (Name, Name) -- | Generate a Prism for each constructor of a data type and -- combine them into a single class. No Isos are created. Reviews are -- created for constructors with existentially quantified constructors -- and GADTs. -- -- e.g. -- --
--   data FooBarBaz a
--     = Foo Int
--     | Bar a
--     | Baz Int Char
--   makeClassyPrisms ''FooBarBaz
--   
-- -- will create -- --
--   class AsFooBarBaz s a | s -> a where
--     _FooBarBaz :: Prism' s (FooBarBaz a)
--     _Foo :: Prism' s Int
--     _Bar :: Prism' s a
--     _Baz :: Prism' s (Int,Char)
--   
--     _Foo = _FooBarBaz . _Foo
--     _Bar = _FooBarBaz . _Bar
--     _Baz = _FooBarBaz . _Baz
--   
--   instance AsFooBarBaz (FooBarBaz a) a
--   
-- -- Generate an As class of prisms. Names are selected by prefixing -- the constructor name with an underscore. Constructors with multiple -- fields will construct Prisms to tuples of those fields. makeClassyPrisms :: Name -> DecsQ -- | Generate a Prism for each constructor of a data type. Isos -- generated when possible. Reviews are created for constructors with -- existentially quantified constructors and GADTs. -- -- e.g. -- --
--   data FooBarBaz a
--     = Foo Int
--     | Bar a
--     | Baz Int Char
--   makePrisms ''FooBarBaz
--   
-- -- will create -- --
--   _Foo :: Prism' (FooBarBaz a) Int
--   _Bar :: Prism (FooBarBaz a) (FooBarBaz b) a b
--   _Baz :: Prism' (FooBarBaz a) (Int, Char)
--   
makePrisms :: Name -> DecsQ -- | An indexed version of at. -- --
--   >>> Map.fromList [(1,"world")] ^@. iat 1
--   (1,Just "world")
--   
-- --
--   >>> iat 1 %@~ (\i x -> if odd i then Just "hello" else Nothing) $ Map.empty
--   fromList [(1,"hello")]
--   
-- --
--   >>> iat 2 %@~ (\i x -> if odd i then Just "hello" else Nothing) $ Map.empty
--   fromList []
--   
iat :: At m => Index m -> IndexedLens' Index m m Maybe IxValue m -- | Delete the value associated with a key in a Map-like container -- --
--   sans k = at k .~ Nothing
--   
sans :: At m => Index m -> m -> m -- | A definition of ix for types with an At instance. This -- is the default if you don't specify a definition for ix. ixAt :: At m => Index m -> Traversal' m IxValue m -- | An indexed version of ix. -- --
--   >>> Seq.fromList [a,b,c,d] & iix 2 %@~ f'
--   fromList [a,b,f' 2 c,d]
--   
-- --
--   >>> Seq.fromList [a,b,c,d] & iix 2 .@~ h
--   fromList [a,b,h 2,d]
--   
-- --
--   >>> Seq.fromList [a,b,c,d] ^@? iix 2
--   Just (2,c)
--   
-- --
--   >>> Seq.fromList [] ^@? iix 2
--   Nothing
--   
iix :: Ixed m => Index m -> IndexedTraversal' Index m m IxValue m -- | An indexed version of contains. -- --
--   >>> IntSet.fromList [1,2,3,4] ^@. icontains 3
--   (3,True)
--   
-- --
--   >>> IntSet.fromList [1,2,3,4] ^@. icontains 5
--   (5,False)
--   
-- --
--   >>> IntSet.fromList [1,2,3,4] & icontains 3 %@~ \i x -> if odd i then not x else x
--   fromList [1,2,4]
--   
-- --
--   >>> IntSet.fromList [1,2,3,4] & icontains 3 %@~ \i x -> if even i then not x else x
--   fromList [1,2,3,4]
--   
icontains :: Contains m => Index m -> IndexedLens' Index m m Bool -- | This class provides a simple Lens that lets you view (and -- modify) information about whether or not a container contains a given -- Index. class Contains m -- |
--   >>> IntSet.fromList [1,2,3,4] ^. contains 3
--   True
--   
-- --
--   >>> IntSet.fromList [1,2,3,4] ^. contains 5
--   False
--   
-- --
--   >>> IntSet.fromList [1,2,3,4] & contains 3 .~ False
--   fromList [1,2,4]
--   
contains :: Contains m => Index m -> Lens' m Bool -- | This provides a common notion of a value at an index that is shared by -- both Ixed and At. -- | Provides a simple Traversal lets you traverse the value -- at a given key in a Map or element at an ordinal position in a -- list or Seq. class Ixed m -- | NB: Setting the value of this Traversal will only set -- the value in at if it is already present. -- -- If you want to be able to insert missing values, you want -- at. -- --
--   >>> Seq.fromList [a,b,c,d] & ix 2 %~ f
--   fromList [a,b,f c,d]
--   
-- --
--   >>> Seq.fromList [a,b,c,d] & ix 2 .~ e
--   fromList [a,b,e,d]
--   
-- --
--   >>> Seq.fromList [a,b,c,d] ^? ix 2
--   Just c
--   
-- --
--   >>> Seq.fromList [] ^? ix 2
--   Nothing
--   
ix :: Ixed m => Index m -> Traversal' m IxValue m -- | At provides a Lens that can be used to read, write or -- delete the value associated with a key in a Map-like container -- on an ad hoc basis. -- -- An instance of At should satisfy: -- --
--   ix k ≡ at k . traverse
--   
class Ixed m => At m -- |
--   >>> Map.fromList [(1,"world")] ^.at 1
--   Just "world"
--   
-- --
--   >>> at 1 ?~ "hello" $ Map.empty
--   fromList [(1,"hello")]
--   
-- -- Note: Map-like containers form a reasonable instance, -- but not Array-like ones, where you cannot satisfy the -- Lens laws. at :: At m => Index m -> Lens' m Maybe IxValue m -- | Extract each element of a (potentially monomorphic) container. -- -- Notably, when applied to a tuple, this generalizes both to -- arbitrary homogeneous tuples. -- --
--   >>> (1,2,3) & each *~ 10
--   (10,20,30)
--   
-- -- It can also be used on monomorphic containers like Text or -- ByteString. -- --
--   >>> over each Char.toUpper ("hello"^.Text.packed)
--   "HELLO"
--   
-- --
--   >>> ("hello","world") & each.each %~ Char.toUpper
--   ("HELLO","WORLD")
--   
class Each s t a b | s -> a, t -> b, s b -> t, t a -> s each :: Each s t a b => Traversal s t a b -- | Implement plate operation for a type using its Generic -- instance. gplate :: (Generic a, GPlated a Rep a) => Traversal' a a -- | The original uniplate combinator, implemented in terms of -- Plated as a Lens. -- --
--   partspartsOf plate
--   
-- -- The resulting Lens is safer to use as it ignores -- 'over-application' and deals gracefully with under-application, but it -- is only a proper Lens if you don't change the list -- length! parts :: Plated a => Lens' a [a] -- | Fold the immediate children of a Plated container. -- --
--   composOpFold z c f = foldrOf plate (c . f) z
--   
composOpFold :: Plated a => b -> b -> b -> b -> a -> b -> a -> b -- | Perform a fold-like computation on each value, technically a -- paramorphism. -- --
--   paraparaOf plate
--   
para :: Plated a => a -> [r] -> r -> a -> r -- | Perform a fold-like computation on each value, technically a -- paramorphism. -- --
--   paraOf :: Fold a a -> (a -> [r] -> r) -> a -> r
--   
paraOf :: () => Getting Endo [a] a a -> a -> [r] -> r -> a -> r -- | Extract one level of holes from a container in a region -- specified by one Traversal, using another. -- --
--   holesOnOf b l ≡ holesOf (b . l)
--   
-- --
--   holesOnOf :: Iso' s a       -> Iso' a a                -> s -> [Pretext (->) a a s]
--   holesOnOf :: Lens' s a      -> Lens' a a               -> s -> [Pretext (->) a a s]
--   holesOnOf :: Traversal' s a -> Traversal' a a          -> s -> [Pretext (->) a a s]
--   holesOnOf :: Lens' s a      -> IndexedLens' i a a      -> s -> [Pretext (Indexed i) a a s]
--   holesOnOf :: Traversal' s a -> IndexedTraversal' i a a -> s -> [Pretext (Indexed i) a a s]
--   
holesOnOf :: Conjoined p => LensLike Bazaar p r r s t a b -> Over p Bazaar p r r a b r r -> s -> [Pretext p r r t] -- | An alias for holesOf, provided for consistency with the other -- combinators. -- --
--   holesOnholesOf
--   
-- --
--   holesOn :: Iso' s a                -> s -> [Pretext (->) a a s]
--   holesOn :: Lens' s a               -> s -> [Pretext (->) a a s]
--   holesOn :: Traversal' s a          -> s -> [Pretext (->) a a s]
--   holesOn :: IndexedLens' i s a      -> s -> [Pretext (Indexed i) a a s]
--   holesOn :: IndexedTraversal' i s a -> s -> [Pretext (Indexed i) a a s]
--   
holesOn :: Conjoined p => Over p Bazaar p a a s t a a -> s -> [Pretext p a a t] -- | The one-level version of context. This extracts a list of the -- immediate children as editable contexts. -- -- Given a context you can use pos to see the values, peek -- at what the structure would be like with an edited result, or simply -- extract the original structure. -- --
--   propChildren x = children l x == map pos (holes l x)
--   propId x = all (== x) [extract w | w <- holes l x]
--   
-- --
--   holes = holesOf plate
--   
holes :: Plated a => a -> [Pretext ((->) :: * -> * -> *) a a a] -- | Return a list of all of the editable contexts for every location in -- the structure in an areas indicated by a user supplied -- Traversal, recursively using another user-supplied -- Traversal to walk each layer. -- --
--   contextsOnOf :: Traversal' s a -> Traversal' a a -> s -> [Context a a s]
--   
contextsOnOf :: () => ATraversal s t a a -> ATraversal' a a -> s -> [Context a a t] -- | Return a list of all of the editable contexts for every location in -- the structure in an areas indicated by a user supplied -- Traversal, recursively using plate. -- --
--   contextsOn b ≡ contextsOnOf b plate
--   
-- --
--   contextsOn :: Plated a => Traversal' s a -> s -> [Context a a s]
--   
contextsOn :: Plated a => ATraversal s t a a -> s -> [Context a a t] -- | Return a list of all of the editable contexts for every location in -- the structure, recursively, using a user-specified Traversal to -- walk each layer. -- --
--   propUniverse l x = universeOf l x == map pos (contextsOf l x)
--   propId l x = all (== x) [extract w | w <- contextsOf l x]
--   
-- --
--   contextsOf :: Traversal' a a -> a -> [Context a a a]
--   
contextsOf :: () => ATraversal' a a -> a -> [Context a a a] -- | Return a list of all of the editable contexts for every location in -- the structure, recursively. -- --
--   propUniverse x = universe x == map pos (contexts x)
--   propId x = all (== x) [extract w | w <- contexts x]
--   
-- --
--   contextscontextsOf plate
--   
contexts :: Plated a => a -> [Context a a a] -- | Transform every element in a tree that lies in a region indicated by a -- supplied Traversal, walking with a user supplied -- Traversal in a bottom-up manner with a monadic effect. -- --
--   transformMOnOf :: Monad m => Traversal' s a -> Traversal' a a -> (a -> m a) -> s -> m s
--   
transformMOnOf :: Monad m => LensLike WrappedMonad m s t a b -> LensLike WrappedMonad m a b a b -> b -> m b -> s -> m t -- | Transform every element in a tree using a user supplied -- Traversal in a bottom-up manner with a monadic effect. -- --
--   transformMOf :: Monad m => Traversal' a a -> (a -> m a) -> a -> m a
--   
transformMOf :: Monad m => LensLike WrappedMonad m a b a b -> b -> m b -> a -> m b -- | Transform every element in the tree in a region indicated by a -- supplied Traversal, in a bottom-up manner, monadically. -- --
--   transformMOn :: (Monad m, Plated a) => Traversal' s a -> (a -> m a) -> s -> m s
--   
transformMOn :: (Monad m, Plated a) => LensLike WrappedMonad m s t a a -> a -> m a -> s -> m t -- | Transform every element in the tree, in a bottom-up manner, -- monadically. transformM :: (Monad m, Plated a) => a -> m a -> a -> m a -- | Transform every element in a region indicated by a Setter by -- recursively applying another Setter in a bottom-up manner. -- --
--   transformOnOf :: Setter' s a -> Traversal' a a -> (a -> a) -> s -> s
--   transformOnOf :: Setter' s a -> Setter' a a    -> (a -> a) -> s -> s
--   
transformOnOf :: () => ASetter s t a b -> ASetter a b a b -> b -> b -> s -> t -- | Transform every element by recursively applying a given Setter -- in a bottom-up manner. -- --
--   transformOf :: Traversal' a a -> (a -> a) -> a -> a
--   transformOf :: Setter' a a    -> (a -> a) -> a -> a
--   
transformOf :: () => ASetter a b a b -> b -> b -> a -> b -- | Transform every element in the tree in a bottom-up manner over a -- region indicated by a Setter. -- --
--   transformOn :: Plated a => Traversal' s a -> (a -> a) -> s -> s
--   transformOn :: Plated a => Setter' s a    -> (a -> a) -> s -> s
--   
transformOn :: Plated a => ASetter s t a a -> a -> a -> s -> t -- | Transform every element in the tree, in a bottom-up manner. -- -- For example, replacing negative literals with literals: -- --
--   negLits = transform $ \x -> case x of
--     Neg (Lit i) -> Lit (negate i)
--     _           -> x
--   
transform :: Plated a => a -> a -> a -> a -- | Given a Fold that knows how to locate immediate children, fold -- all of the transitive descendants of a node, including itself that lie -- in a region indicated by another Fold. -- --
--   cosmosOnOf :: Fold s a -> Fold a a -> Fold s a
--   
cosmosOnOf :: (Applicative f, Contravariant f) => LensLike' f s a -> LensLike' f a a -> LensLike' f s a -- | Given a Fold that knows how to find Plated parts of a -- container fold them and all of their descendants, recursively. -- --
--   cosmosOn :: Plated a => Fold s a -> Fold s a
--   
cosmosOn :: (Applicative f, Contravariant f, Plated a) => LensLike' f s a -> LensLike' f s a -- | Given a Fold that knows how to locate immediate children, fold -- all of the transitive descendants of a node, including itself. -- --
--   cosmosOf :: Fold a a -> Fold a a
--   
cosmosOf :: (Applicative f, Contravariant f) => LensLike' f a a -> LensLike' f a a -- | Fold over all transitive descendants of a Plated container, -- including itself. cosmos :: Plated a => Fold a a -- | Given a Fold that knows how to locate immediate children, -- retrieve all of the transitive descendants of a node, including itself -- that lie in a region indicated by another Fold. -- --
--   toListOf l ≡ universeOnOf l ignored
--   
universeOnOf :: () => Getting [a] s a -> Getting [a] a a -> s -> [a] -- | Given a Fold that knows how to find Plated parts of a -- container retrieve them and all of their descendants, recursively. universeOn :: Plated a => Getting [a] s a -> s -> [a] -- | Given a Fold that knows how to locate immediate children, -- retrieve all of the transitive descendants of a node, including -- itself. -- --
--   universeOf :: Fold a a -> a -> [a]
--   
universeOf :: () => Getting [a] a a -> a -> [a] -- | Retrieve all of the transitive descendants of a Plated -- container, including itself. universe :: Plated a => a -> [a] -- | Rewrite by applying a monadic rule everywhere inside of a structure -- located by a user-specified Traversal, using a user-specified -- Traversal for recursion. Ensures that the rule cannot be -- applied anywhere in the result. rewriteMOnOf :: Monad m => LensLike WrappedMonad m s t a b -> LensLike WrappedMonad m a b a b -> b -> m Maybe a -> s -> m t -- | Rewrite by applying a monadic rule everywhere inside of a structure -- located by a user-specified Traversal. Ensures that the rule -- cannot be applied anywhere in the result. rewriteMOn :: (Monad m, Plated a) => LensLike WrappedMonad m s t a a -> a -> m Maybe a -> s -> m t -- | Rewrite by applying a monadic rule everywhere you recursing with a -- user-specified Traversal. Ensures that the rule cannot be -- applied anywhere in the result. rewriteMOf :: Monad m => LensLike WrappedMonad m a b a b -> b -> m Maybe a -> a -> m b -- | Rewrite by applying a monadic rule everywhere you can. Ensures that -- the rule cannot be applied anywhere in the result. rewriteM :: (Monad m, Plated a) => a -> m Maybe a -> a -> m a -- | Rewrite recursively over part of a larger structure using a specified -- Setter. -- --
--   rewriteOnOf :: Iso' s a       -> Iso' a a       -> (a -> Maybe a) -> s -> s
--   rewriteOnOf :: Lens' s a      -> Lens' a a      -> (a -> Maybe a) -> s -> s
--   rewriteOnOf :: Traversal' s a -> Traversal' a a -> (a -> Maybe a) -> s -> s
--   rewriteOnOf :: Setter' s a    -> Setter' a a    -> (a -> Maybe a) -> s -> s
--   
rewriteOnOf :: () => ASetter s t a b -> ASetter a b a b -> b -> Maybe a -> s -> t -- | Rewrite recursively over part of a larger structure. -- --
--   rewriteOn :: Plated a => Iso' s a       -> (a -> Maybe a) -> s -> s
--   rewriteOn :: Plated a => Lens' s a      -> (a -> Maybe a) -> s -> s
--   rewriteOn :: Plated a => Traversal' s a -> (a -> Maybe a) -> s -> s
--   rewriteOn :: Plated a => ASetter' s a   -> (a -> Maybe a) -> s -> s
--   
rewriteOn :: Plated a => ASetter s t a a -> a -> Maybe a -> s -> t -- | Rewrite by applying a rule everywhere you can. Ensures that the rule -- cannot be applied anywhere in the result: -- --
--   propRewriteOf l r x = all (isNothing . r) (universeOf l (rewriteOf l r x))
--   
-- -- Usually transformOf is more appropriate, but rewriteOf -- can give better compositionality. Given two single transformations -- f and g, you can construct a -> f a -- mplus g a which performs both rewrites until a fixed -- point. -- --
--   rewriteOf :: Iso' a a       -> (a -> Maybe a) -> a -> a
--   rewriteOf :: Lens' a a      -> (a -> Maybe a) -> a -> a
--   rewriteOf :: Traversal' a a -> (a -> Maybe a) -> a -> a
--   rewriteOf :: Setter' a a    -> (a -> Maybe a) -> a -> a
--   
rewriteOf :: () => ASetter a b a b -> b -> Maybe a -> a -> b -- | Rewrite by applying a rule everywhere you can. Ensures that the rule -- cannot be applied anywhere in the result: -- --
--   propRewrite r x = all (isNothing . r) (universe (rewrite r x))
--   
-- -- Usually transform is more appropriate, but rewrite can -- give better compositionality. Given two single transformations -- f and g, you can construct a -> f a -- mplus g a which performs both rewrites until a fixed -- point. rewrite :: Plated a => a -> Maybe a -> a -> a -- | Extract the immediate descendants of a Plated container. -- --
--   childrentoListOf plate
--   
children :: Plated a => a -> [a] -- | Try to apply a traversal to all transitive descendants of a -- Plated container, but do not recurse through matching -- descendants. -- --
--   deep :: Plated s => Fold s a                 -> Fold s a
--   deep :: Plated s => IndexedFold s a          -> IndexedFold s a
--   deep :: Plated s => Traversal s s a b        -> Traversal s s a b
--   deep :: Plated s => IndexedTraversal s s a b -> IndexedTraversal s s a b
--   
deep :: (Conjoined p, Applicative f, Plated s) => Traversing p f s s a b -> Over p f s s a b -- | Compose through a plate (...) :: (Applicative f, Plated c) => LensLike f s t c c -> Over p f c c a b -> Over p f s t a b infixr 9 ... -- | A Plated type is one where we know how to extract its immediate -- self-similar children. -- -- Example 1: -- --
--   import Control.Applicative
--   import Control.Lens
--   import Control.Lens.Plated
--   import Data.Data
--   import Data.Data.Lens (uniplate)
--   
-- --
--   data Expr
--     = Val Int
--     | Neg Expr
--     | Add Expr Expr
--     deriving (Eq,Ord,Show,Read,Data,Typeable)
--   
-- --
--   instance Plated Expr where
--     plate f (Neg e) = Neg <$> f e
--     plate f (Add a b) = Add <$> f a <*> f b
--     plate _ a = pure a
--   
-- -- or -- --
--   instance Plated Expr where
--     plate = uniplate
--   
-- -- Example 2: -- --
--   import Control.Applicative
--   import Control.Lens
--   import Control.Lens.Plated
--   import Data.Data
--   import Data.Data.Lens (uniplate)
--   
-- --
--   data Tree a
--     = Bin (Tree a) (Tree a)
--     | Tip a
--     deriving (Eq,Ord,Show,Read,Data,Typeable)
--   
-- --
--   instance Plated (Tree a) where
--     plate f (Bin l r) = Bin <$> f l <*> f r
--     plate _ t = pure t
--   
-- -- or -- --
--   instance Data a => Plated (Tree a) where
--     plate = uniplate
--   
-- -- Note the big distinction between these two implementations. -- -- The former will only treat children directly in this tree as -- descendents, the latter will treat trees contained in the values under -- the tips also as descendants! -- -- When in doubt, pick a Traversal and just use the various -- ...Of combinators rather than pollute Plated with -- orphan instances! -- -- If you want to find something unplated and non-recursive with -- biplate use the ...OnOf variant with ignored, -- though those usecases are much better served in most cases by using -- the existing Lens combinators! e.g. -- --
--   toListOf biplateuniverseOnOf biplate ignored
--   
-- -- This same ability to explicitly pass the Traversal in question -- is why there is no analogue to uniplate's Biplate. -- -- Moreover, since we can allow custom traversals, we implement -- reasonable defaults for polymorphic data types, that only -- traverse into themselves, and not their polymorphic -- arguments. class Plated a -- | Traversal of the immediate children of this structure. -- -- If you're using GHC 7.2 or newer and your type has a Data -- instance, plate will default to uniplate and you can -- choose to not override it with your own definition. plate :: Plated a => Traversal' a a class GPlated a (g :: * -> *) -- | This type family is used by Zoom to describe the common effect -- type. -- | This type family is used by Magnify to describe the common -- effect type. -- | 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 :: * -> *) s t | m -> s, n -> t, m t -> n, n s -> m -- | Run a monadic action in a larger State than it was defined in, -- using a Lens' or Traversal'. -- -- This is commonly used to lift actions in a simpler State -- Monad into a State Monad with a larger -- State type. -- -- When applied to a Traversal' over multiple values, the actions -- for each target are executed sequentially and the results are -- aggregated. -- -- This can be used to edit pretty much any Monad transformer -- stack with a State in it! -- --
--   >>> flip State.evalState (a,b) $ zoom _1 $ use id
--   a
--   
-- --
--   >>> flip State.execState (a,b) $ zoom _1 $ id .= c
--   (c,b)
--   
-- --
--   >>> flip State.execState [(a,b),(c,d)] $ zoom traverse $ _2 %= f
--   [(a,f b),(c,f d)]
--   
-- --
--   >>> flip State.runState [(a,b),(c,d)] $ zoom traverse $ _2 <%= f
--   (f b <> f d <> mempty,[(a,f b),(c,f d)])
--   
-- --
--   >>> flip State.evalState (a,b) $ zoom both (use id)
--   a <> b
--   
-- --
--   zoom :: Monad m             => Lens' s t      -> StateT t m a -> StateT s m a
--   zoom :: (Monad m, Monoid c) => Traversal' s t -> StateT t m c -> StateT s m c
--   zoom :: (Monad m, Monoid w)             => Lens' s t      -> RWST r w t m c -> RWST r w s m c
--   zoom :: (Monad m, Monoid w, Monoid c) => Traversal' s t -> RWST r w t m c -> RWST r w s m c
--   zoom :: (Monad m, Monoid w, Error e)  => Lens' s t      -> ErrorT e (RWST r w t m) c -> ErrorT e (RWST r w s m) c
--   zoom :: (Monad m, Monoid w, Monoid c, Error e) => Traversal' s t -> ErrorT e (RWST r w t m) c -> ErrorT e (RWST r w s m) c
--   ...
--   
zoom :: Zoom m n s t => LensLike' Zoomed m c t s -> m c -> n c -- | This class allows us to use magnify part of the environment, -- changing the environment supplied by many different Monad -- transformers. Unlike zoom this can change the environment of a -- deeply nested Monad transformer. -- -- Also, unlike zoom, this can be used with any valid -- Getter, but cannot be used with a Traversal or -- Fold. class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify (m :: * -> *) (n :: * -> *) b a | m -> b, n -> a, m a -> n, n b -> m -- | Run a monadic action in a larger environment than it was defined in, -- using a Getter. -- -- This acts like local, but can in many cases change the type of -- the environment as well. -- -- This is commonly used to lift actions in a simpler Reader -- Monad into a Monad with a larger environment type. -- -- This can be used to edit pretty much any Monad transformer -- stack with an environment in it: -- --
--   >>> (1,2) & magnify _2 (+1)
--   3
--   
-- --
--   >>> flip Reader.runReader (1,2) $ magnify _1 Reader.ask
--   1
--   
-- --
--   >>> flip Reader.runReader (1,2,[10..20]) $ magnify (_3._tail) Reader.ask
--   [11,12,13,14,15,16,17,18,19,20]
--   
-- --
--   magnify :: Getter s a -> (a -> r) -> s -> r
--   magnify :: Monoid r => Fold s a   -> (a -> r) -> s -> r
--   
-- --
--   magnify :: Monoid w                 => Getter s t -> RWS t w st c -> RWS s w st c
--   magnify :: (Monoid w, Monoid c) => Fold s a   -> RWS a w st c -> RWS s w st c
--   ...
--   
magnify :: Magnify m n b a => LensLike' Magnified m c a b -> m c -> n c -- | This combinator is based on ala' from Conor McBride's work on -- Epigram. -- -- As with _Wrapping, the user supplied function for the newtype -- is ignored. -- --
--   alaf :: Rewrapping s t => (Unwrapped s -> s) -> ((r ->  t) -> e -> s) -> (r -> Unwrapped t) -> e -> Unwrapped s
--   
-- --
--   >>> alaf Sum foldMap Prelude.length ["hello","world"]
--   10
--   
alaf :: (Functor f, Functor g, Rewrapping s t) => Unwrapped s -> s -> f t -> g s -> f Unwrapped t -> g Unwrapped s -- | This combinator is based on ala from Conor McBride's work on -- Epigram. -- -- As with _Wrapping, the user supplied function for the newtype -- is ignored. -- --
--   >>> ala Sum foldMap [1,2,3,4]
--   10
--   
-- --
--   >>> ala All foldMap [True,True]
--   True
--   
-- --
--   >>> ala All foldMap [True,False]
--   False
--   
-- --
--   >>> ala Any foldMap [False,False]
--   False
--   
-- --
--   >>> ala Any foldMap [True,False]
--   True
--   
-- --
--   >>> ala Product foldMap [1,2,3,4]
--   24
--   
-- -- You may want to think of this combinator as having the following, -- simpler, type. -- --
--   ala :: Rewrapping s t => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> e -> s) -> e -> Unwrapped s
--   
ala :: (Functor f, Rewrapping s t) => Unwrapped s -> s -> Unwrapped t -> t -> f s -> f Unwrapped s -- | This is a convenient version of _Unwrapped with an argument -- that's ignored. -- -- The user supplied function is ignored, merely its types are -- used. _Unwrapping :: Rewrapping s t => Unwrapped s -> s -> Iso Unwrapped t Unwrapped s t s -- | This is a convenient version of _Wrapped with an argument -- that's ignored. -- -- The user supplied function is ignored, merely its types are -- used. _Wrapping :: Rewrapping s t => Unwrapped s -> s -> Iso s t Unwrapped s Unwrapped t -- | This is a convenient version of _Wrapped with an argument -- that's ignored. -- -- The user supplied function is ignored, merely its type is used. _Unwrapping' :: Wrapped s => Unwrapped s -> s -> Iso' Unwrapped s s -- | This is a convenient version of _Wrapped with an argument -- that's ignored. -- -- The user supplied function is ignored, merely its type is used. _Wrapping' :: Wrapped s => Unwrapped s -> s -> Iso' s Unwrapped s -- | Given the constructor for a Wrapped type, return a -- deconstructor that is its inverse. -- -- Assuming the Wrapped instance is legal, these laws hold: -- --
--   op f . f ≡ id
--   f . op f ≡ id
--   
-- --
--   >>> op Identity (Identity 4)
--   4
--   
-- --
--   >>> op Const (Const "hello")
--   "hello"
--   
op :: Wrapped s => Unwrapped s -> s -> s -> Unwrapped s _Unwrapped :: Rewrapping s t => Iso Unwrapped t Unwrapped s t s -- | Work under a newtype wrapper. -- --
--   >>> Const "hello" & _Wrapped %~ Prelude.length & getConst
--   5
--   
-- --
--   _Wrappedfrom _Unwrapped
--   _Unwrappedfrom _Wrapped
--   
_Wrapped :: Rewrapping s t => Iso s t Unwrapped s Unwrapped t _Unwrapped' :: Wrapped s => Iso' Unwrapped s s -- | Implement the _Wrapped operation for a type using its -- Generic instance. _GWrapped' :: (Generic s, D1 d C1 c S1 s' Rec0 a ~ Rep s, Unwrapped s ~ GUnwrapped Rep s) => Iso' s Unwrapped s -- | Wrapped provides isomorphisms to wrap and unwrap newtypes or -- data types with one constructor. class Wrapped s where { type family Unwrapped s :: *; } -- | An isomorphism between s and a. -- -- If your type has a Generic instance, _Wrapped' will -- default to _GWrapped', and you can choose to not override it -- with your own definition. _Wrapped' :: Wrapped s => Iso' s Unwrapped s class Wrapped s => Rewrapped s t class (Rewrapped s t, Rewrapped t s) => Rewrapping s t -- | Attempt to extract the right-most element from a container, and a -- version of the container without that element. -- --
--   >>> unsnoc (LazyT.pack "hello!")
--   Just ("hello",'!')
--   
-- --
--   >>> unsnoc (LazyT.pack "")
--   Nothing
--   
-- --
--   >>> unsnoc (Seq.fromList [b,c,a])
--   Just (fromList [b,c],a)
--   
-- --
--   >>> unsnoc (Seq.fromList [])
--   Nothing
--   
unsnoc :: Snoc s s a a => s -> Maybe (s, a) -- | snoc an element onto the end of a container. -- --
--   >>> snoc (Seq.fromList []) a
--   fromList [a]
--   
-- --
--   >>> snoc (Seq.fromList [b, c]) a
--   fromList [b,c,a]
--   
-- --
--   >>> snoc (LazyT.pack "hello") '!'
--   "hello!"
--   
snoc :: Snoc s s a a => s -> a -> s infixl 5 `snoc` -- | snoc an element onto the end of a container. -- -- This is an infix alias for snoc. -- --
--   >>> Seq.fromList [] |> a
--   fromList [a]
--   
-- --
--   >>> Seq.fromList [b, c] |> a
--   fromList [b,c,a]
--   
-- --
--   >>> LazyT.pack "hello" |> '!'
--   "hello!"
--   
(|>) :: Snoc s s a a => s -> a -> s infixl 5 |> -- | A Traversal reading and writing to the last element of a -- non-empty container. -- --
--   >>> [a,b,c]^?!_last
--   c
--   
-- --
--   >>> []^?_last
--   Nothing
--   
-- --
--   >>> [a,b,c] & _last %~ f
--   [a,b,f c]
--   
-- --
--   >>> [1,2]^?_last
--   Just 2
--   
-- --
--   >>> [] & _last .~ 1
--   []
--   
-- --
--   >>> [0] & _last .~ 2
--   [2]
--   
-- --
--   >>> [0,1] & _last .~ 2
--   [0,2]
--   
-- -- This Traversal is not limited to lists, however. We can also -- work with other containers, such as a Vector. -- --
--   >>> Vector.fromList "abcde" ^? _last
--   Just 'e'
--   
-- --
--   >>> Vector.empty ^? _last
--   Nothing
--   
-- --
--   >>> (Vector.fromList "abcde" & _last .~ 'Q') == Vector.fromList "abcdQ"
--   True
--   
-- --
--   _last :: Traversal' [a] a
--   _last :: Traversal' (Seq a) a
--   _last :: Traversal' (Vector a) a
--   
_last :: Snoc s s a a => Traversal' s a -- | A Traversal reading and replacing all but the a last element of -- a non-empty container. -- --
--   >>> [a,b,c,d]^?_init
--   Just [a,b,c]
--   
-- --
--   >>> []^?_init
--   Nothing
--   
-- --
--   >>> [a,b] & _init .~ [c,d,e]
--   [c,d,e,b]
--   
-- --
--   >>> [] & _init .~ [a,b]
--   []
--   
-- --
--   >>> [a,b,c,d] & _init.traverse %~ f
--   [f a,f b,f c,d]
--   
-- --
--   >>> [1,2,3]^?_init
--   Just [1,2]
--   
-- --
--   >>> [1,2,3,4]^?!_init
--   [1,2,3]
--   
-- --
--   >>> "hello"^._init
--   "hell"
--   
-- --
--   >>> ""^._init
--   ""
--   
-- --
--   _init :: Traversal' [a] [a]
--   _init :: Traversal' (Seq a) (Seq a)
--   _init :: Traversal' (Vector a) (Vector a)
--   
_init :: Snoc s s a a => Traversal' s s -- | A Traversal reading and writing to the tail of a -- non-empty container. -- --
--   >>> [a,b] & _tail .~ [c,d,e]
--   [a,c,d,e]
--   
-- --
--   >>> [] & _tail .~ [a,b]
--   []
--   
-- --
--   >>> [a,b,c,d,e] & _tail.traverse %~ f
--   [a,f b,f c,f d,f e]
--   
-- --
--   >>> [1,2] & _tail .~ [3,4,5]
--   [1,3,4,5]
--   
-- --
--   >>> [] & _tail .~ [1,2]
--   []
--   
-- --
--   >>> [a,b,c]^?_tail
--   Just [b,c]
--   
-- --
--   >>> [1,2]^?!_tail
--   [2]
--   
-- --
--   >>> "hello"^._tail
--   "ello"
--   
-- --
--   >>> ""^._tail
--   ""
--   
-- -- This isn't limited to lists. For instance you can also traverse -- the tail of a Seq. -- --
--   >>> Seq.fromList [a,b] & _tail .~ Seq.fromList [c,d,e]
--   fromList [a,c,d,e]
--   
-- --
--   >>> Seq.fromList [a,b,c] ^? _tail
--   Just (fromList [b,c])
--   
-- --
--   >>> Seq.fromList [] ^? _tail
--   Nothing
--   
-- --
--   _tail :: Traversal' [a] [a]
--   _tail :: Traversal' (Seq a) (Seq a)
--   _tail :: Traversal' (Vector a) (Vector a)
--   
_tail :: Cons s s a a => Traversal' s s -- | A Traversal reading and writing to the head of a -- non-empty container. -- --
--   >>> [a,b,c]^? _head
--   Just a
--   
-- --
--   >>> [a,b,c] & _head .~ d
--   [d,b,c]
--   
-- --
--   >>> [a,b,c] & _head %~ f
--   [f a,b,c]
--   
-- --
--   >>> [] & _head %~ f
--   []
--   
-- --
--   >>> [1,2,3]^?!_head
--   1
--   
-- --
--   >>> []^?_head
--   Nothing
--   
-- --
--   >>> [1,2]^?_head
--   Just 1
--   
-- --
--   >>> [] & _head .~ 1
--   []
--   
-- --
--   >>> [0] & _head .~ 2
--   [2]
--   
-- --
--   >>> [0,1] & _head .~ 2
--   [2,1]
--   
-- -- This isn't limited to lists. -- -- For instance you can also traverse the head of a Seq: -- --
--   >>> Seq.fromList [a,b,c,d] & _head %~ f
--   fromList [f a,b,c,d]
--   
-- --
--   >>> Seq.fromList [] ^? _head
--   Nothing
--   
-- --
--   >>> Seq.fromList [a,b,c,d] ^? _head
--   Just a
--   
-- --
--   _head :: Traversal' [a] a
--   _head :: Traversal' (Seq a) a
--   _head :: Traversal' (Vector a) a
--   
_head :: Cons s s a a => Traversal' s a -- | cons an element onto a container. -- --
--   >>> cons a []
--   [a]
--   
-- --
--   >>> cons a [b, c]
--   [a,b,c]
--   
-- --
--   >>> cons a (Seq.fromList [])
--   fromList [a]
--   
-- --
--   >>> cons a (Seq.fromList [b, c])
--   fromList [a,b,c]
--   
cons :: Cons s s a a => a -> s -> s infixr 5 `cons` -- | cons an element onto a container. -- -- This is an infix alias for cons. -- --
--   >>> a <| []
--   [a]
--   
-- --
--   >>> a <| [b, c]
--   [a,b,c]
--   
-- --
--   >>> a <| Seq.fromList []
--   fromList [a]
--   
-- --
--   >>> a <| Seq.fromList [b, c]
--   fromList [a,b,c]
--   
(<|) :: Cons s s a a => a -> s -> s infixr 5 <| infixr 5 :< infixl 5 :> -- | This class provides a way to attach or detach elements on the left -- side of a structure in a flexible manner. class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s -- |
--   _Cons :: Prism [a] [b] (a, [a]) (b, [b])
--   _Cons :: Prism (Seq a) (Seq b) (a, Seq a) (b, Seq b)
--   _Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
--   _Cons :: Prism' String (Char, String)
--   _Cons :: Prism' Text (Char, Text)
--   _Cons :: Prism' ByteString (Word8, ByteString)
--   
_Cons :: Cons s t a b => Prism s t (a, s) (b, t) -- | This class provides a way to attach or detach elements on the right -- side of a structure in a flexible manner. class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s -- |
--   _Snoc :: Prism [a] [b] ([a], a) ([b], b)
--   _Snoc :: Prism (Seq a) (Seq b) (Seq a, a) (Seq b, b)
--   _Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
--   _Snoc :: Prism' String (String, Char)
--   _Snoc :: Prism' Text (Text, Char)
--   _Snoc :: Prism' ByteString (ByteString, Word8)
--   
_Snoc :: Snoc s t a b => Prism s t (s, a) (t, b) class AsEmpty a -- |
--   >>> isn't _Empty [1,2,3]
--   True
--   
_Empty :: AsEmpty a => Prism' a () -- | Data types that are representationally equal are isomorphic. -- -- This is only available on GHC 7.8+ coerced :: (Coercible s a, Coercible t b) => Iso s t a b -- | Lift an Iso into the second argument of a Bifunctor. -- This is essentially the same as mapping, but it takes a -- 'Bifunctor p' constraint instead of a 'Functor (p a)' one. -- --
--   seconding :: Bifunctor p => Iso s t a b -> Iso (p x s) (p y t) (p x a) (p y b)
--   seconding :: Bifunctor p => Iso' s a -> Iso' (p x s) (p x a)
--   
seconding :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso f x s g y t f x a g y b -- | Lift an Iso into the first argument of a Bifunctor. -- --
--   firsting :: Bifunctor p => Iso s t a b -> Iso (p s x) (p t y) (p a x) (p b y)
--   firsting :: Bifunctor p => Iso' s a -> Iso' (p s x) (p a x)
--   
firsting :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso f s x g t y f a x g b y -- | Lift two Isos into both arguments of a Bifunctor. -- --
--   bimapping :: Bifunctor p => Iso s t a b -> Iso s' t' a' b' -> Iso (p s s') (p t t') (p a a') (p b b')
--   bimapping :: Bifunctor p => Iso' s a -> Iso' s' a' -> Iso' (p s s') (p a a')
--   
bimapping :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso f s s' g t t' f a a' g b b' -- | Lift an Iso covariantly into the right argument of a -- Profunctor. -- --
--   rmapping :: Profunctor p => Iso s t a b -> Iso (p x s) (p y t) (p x a) (p y b)
--   rmapping :: Profunctor p => Iso' s a -> Iso' (p x s) (p x a)
--   
rmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso p x s q y t p x a q y b -- | Lift an Iso contravariantly into the left argument of a -- Profunctor. -- --
--   lmapping :: Profunctor p => Iso s t a b -> Iso (p a x) (p b y) (p s x) (p t y)
--   lmapping :: Profunctor p => Iso' s a -> Iso' (p a x) (p s x)
--   
lmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso p a x q b y p s x q t y -- | Lift two Isos into both arguments of a Profunctor -- simultaneously. -- --
--   dimapping :: Profunctor p => Iso s t a b -> Iso s' t' a' b' -> Iso (p a s') (p b t') (p s a') (p t b')
--   dimapping :: Profunctor p => Iso' s a -> Iso' s' a' -> Iso' (p a s') (p s a')
--   
dimapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> AnIso s' t' a' b' -> Iso p a s' q b t' p s a' q t b' -- | Lift an Iso into a Contravariant functor. -- --
--   contramapping :: Contravariant f => Iso s t a b -> Iso (f a) (f b) (f s) (f t)
--   contramapping :: Contravariant f => Iso' s a -> Iso' (f a) (f s)
--   
contramapping :: Contravariant f => AnIso s t a b -> Iso f a f b f s f t -- | This isomorphism can be used to inspect an IndexedTraversal to -- see how it associates the structure and it can also be used to bake -- the IndexedTraversal into a Magma so that you can -- traverse over it multiple times with access to the original indices. imagma :: () => Over Indexed i Molten i a b s t a b -> Iso s t' Magma i t b a Magma j t' c c -- | This isomorphism can be used to inspect a Traversal to see how -- it associates the structure and it can also be used to bake the -- Traversal into a Magma so that you can traverse over it -- multiple times. magma :: () => LensLike Mafic a b s t a b -> Iso s u Magma Int t b a Magma j u c c -- | Given a function that is its own inverse, this gives you an Iso -- using it in both directions. -- --
--   involutedjoin iso
--   
-- --
--   >>> "live" ^. involuted reverse
--   "evil"
--   
-- --
--   >>> "live" & involuted reverse %~ ('d':)
--   "lived"
--   
involuted :: () => a -> a -> Iso' a a -- | An Iso between a list, ByteString, Text fragment, -- etc. and its reversal. -- --
--   >>> "live" ^. reversed
--   "evil"
--   
-- --
--   >>> "live" & reversed %~ ('d':)
--   "lived"
--   
reversed :: Reversing a => Iso' a a -- | An Iso between the strict variant of a structure and its lazy -- counterpart. -- --
--   lazy = from strict
--   
-- -- See http://hackage.haskell.org/package/strict-base-types for an -- example use. lazy :: Strict lazy strict => Iso' strict lazy -- | The isomorphism for flipping a function. -- --
--   >>> ((,)^.flipped) 1 2
--   (2,1)
--   
flipped :: (Profunctor p, Functor f) => p b -> a -> c f b' -> a' -> c' -> p a -> b -> c f a' -> b' -> c' -- | The canonical isomorphism for uncurrying and currying a function. -- --
--   uncurried = iso uncurry curry
--   
-- --
--   uncurried = from curried
--   
-- --
--   >>> ((+)^.uncurried) (1,2)
--   3
--   
uncurried :: (Profunctor p, Functor f) => p (a, b) -> c f (d, e) -> f -> p a -> b -> c f d -> e -> f -- | The canonical isomorphism for currying and uncurrying a function. -- --
--   curried = iso curry uncurry
--   
-- --
--   >>> (fst^.curried) 3 4
--   3
--   
-- --
--   >>> view curried fst 3 4
--   3
--   
curried :: (Profunctor p, Functor f) => p a -> b -> c f d -> e -> f -> p (a, b) -> c f (d, e) -> f -- | anon a p generalizes non a to take any -- value and a predicate. -- -- This function assumes that p a holds True and -- generates an isomorphism between Maybe (a | not (p -- a)) and a. -- --
--   >>> Map.empty & at "hello" . anon Map.empty Map.null . at "world" ?~ "!!!"
--   fromList [("hello",fromList [("world","!!!")])]
--   
-- --
--   >>> fromList [("hello",fromList [("world","!!!")])] & at "hello" . anon Map.empty Map.null . at "world" .~ Nothing
--   fromList []
--   
anon :: () => a -> a -> Bool -> Iso' Maybe a a -- | non' p generalizes non (p # ()) to -- take any unit Prism -- -- This function generates an isomorphism between Maybe (a | -- isn't p a) and a. -- --
--   >>> Map.singleton "hello" Map.empty & at "hello" . non' _Empty . at "world" ?~ "!!!"
--   fromList [("hello",fromList [("world","!!!")])]
--   
-- --
--   >>> fromList [("hello",fromList [("world","!!!")])] & at "hello" . non' _Empty . at "world" .~ Nothing
--   fromList []
--   
non' :: () => APrism' a () -> Iso' Maybe a a -- | If v is an element of a type a, and a' is -- a sans the element v, then non v is -- an isomorphism from Maybe a' to a. -- --
--   nonnon' . only
--   
-- -- Keep in mind this is only a real isomorphism if you treat the domain -- as being Maybe (a sans v). -- -- This is practically quite useful when you want to have a Map -- where all the entries should have non-zero values. -- --
--   >>> Map.fromList [("hello",1)] & at "hello" . non 0 +~ 2
--   fromList [("hello",3)]
--   
-- --
--   >>> Map.fromList [("hello",1)] & at "hello" . non 0 -~ 1
--   fromList []
--   
-- --
--   >>> Map.fromList [("hello",1)] ^. at "hello" . non 0
--   1
--   
-- --
--   >>> Map.fromList [] ^. at "hello" . non 0
--   0
--   
-- -- This combinator is also particularly useful when working with nested -- maps. -- -- e.g. When you want to create the nested Map when it is -- missing: -- --
--   >>> Map.empty & at "hello" . non Map.empty . at "world" ?~ "!!!"
--   fromList [("hello",fromList [("world","!!!")])]
--   
-- -- and when have deleting the last entry from the nested Map mean -- that we should delete its entry from the surrounding one: -- --
--   >>> fromList [("hello",fromList [("world","!!!")])] & at "hello" . non Map.empty . at "world" .~ Nothing
--   fromList []
--   
-- -- It can also be used in reverse to exclude a given value: -- --
--   >>> non 0 # rem 10 4
--   Just 2
--   
-- --
--   >>> non 0 # rem 10 5
--   Nothing
--   
non :: Eq a => a -> Iso' Maybe a a -- | This can be used to lift any Iso into an arbitrary -- Functor. mapping :: (Functor f, Functor g) => AnIso s t a b -> Iso f s g t f a g b -- | This isomorphism can be used to convert to or from an instance of -- Enum. -- --
--   >>> LT^.from enum
--   0
--   
-- --
--   >>> 97^.enum :: Char
--   'a'
--   
-- -- Note: this is only an isomorphism from the numeric range actually used -- and it is a bit of a pleasant fiction, since there are questionable -- Enum instances for Double, and Float that exist -- solely for [1.0 .. 4.0] sugar and the instances for those and -- Integer don't cover all values in their range. enum :: Enum a => Iso' Int a -- | The opposite of working over a Setter is working -- under an isomorphism. -- --
--   underover . from
--   
-- --
--   under :: Iso s t a b -> (t -> s) -> b -> a
--   
under :: () => AnIso s t a b -> t -> s -> b -> a -- | Based on ala' from Conor McBride's work on Epigram. -- -- This version is generalized to accept any Iso, not just a -- newtype. -- -- For a version you pass the name of the newtype constructor -- to, see alaf. -- --
--   >>> auf (_Unwrapping Sum) (foldMapOf both) Prelude.length ("hello","world")
--   10
--   
-- -- Mnemonically, the German auf plays a similar role to à -- la, and the combinator is au with an extra function -- argument: -- --
--   auf :: Iso s t a b -> ((r ->  a) -> e -> b) -> (r -> s) -> e -> t
--   
-- -- but the signature is general. auf :: () => Optic Costar f g s t a b -> f a -> g b -> f s -> g t -- | Based on ala from Conor McBride's work on Epigram. -- -- This version is generalized to accept any Iso, not just a -- newtype. -- --
--   >>> au (_Wrapping Sum) foldMap [1,2,3,4]
--   10
--   
-- -- You may want to think of this combinator as having the following, -- simpler type: -- --
--   au :: AnIso s t a b -> ((b -> t) -> e -> s) -> e -> a
--   
au :: Functor f => AnIso s t a b -> b -> t -> f s -> f a -- | Convert from AnIso back to any Iso. -- -- This is useful when you need to store an isomorphism as a data type -- inside a container and later reconstitute it as an overloaded -- function. -- -- See cloneLens or cloneTraversal for more information on -- why you might want to do this. cloneIso :: () => AnIso s t a b -> Iso s t a b -- | Extract the two functions, one from s -> a and one from -- b -> t that characterize an Iso. withIso :: () => AnIso s t a b -> s -> a -> b -> t -> r -> r -- | Invert an isomorphism. -- --
--   from (from l) ≡ l
--   
from :: () => AnIso s t a b -> Iso b a t s -- | Build a simple isomorphism from a pair of inverse functions. -- --
--   view (iso f g) ≡ f
--   view (from (iso f g)) ≡ g
--   over (iso f g) h ≡ g . h . f
--   over (from (iso f g)) h ≡ f . h . g
--   
iso :: () => s -> a -> b -> t -> Iso s t a b -- | When you see this as an argument to a function, it expects an -- Iso. type AnIso s t a b = Exchange a b a Identity b -> Exchange a b s Identity t -- | A Simple AnIso. type AnIso' s a = AnIso s s a a -- | This class provides for symmetric bifunctors. class Bifunctor p => Swapped (p :: * -> * -> *) -- |
--   swapped . swappedid
--   first f . swapped = swapped . second f
--   second g . swapped = swapped . first g
--   bimap f g . swapped = swapped . bimap g f
--   
-- --
--   >>> (1,2)^.swapped
--   (2,1)
--   
swapped :: (Swapped p, Profunctor p, Functor f) => p p b a f p d c -> p p a b f p c d -- | Ad hoc conversion between "strict" and "lazy" versions of a structure, -- such as Text or ByteString. class Strict lazy strict | lazy -> strict, strict -> lazy strict :: Strict lazy strict => Iso' lazy strict -- | Composition with this isomorphism is occasionally useful when your -- Lens, Traversal or Iso has a constraint on an -- unused argument to force that argument to agree with the type of a -- used argument and avoid ScopedTypeVariables or other -- ugliness. simple :: () => p a f a -> p a f a -- | This is an adverb that can be used to modify many other Lens -- combinators to make them require simple lenses, simple traversals, -- simple prisms or simple isos as input. simply :: () => Optic' p f s a -> r -> Optic' p f s a -> r -- | Equality is symmetric. fromEq :: () => AnEquality s t a b -> Equality b a t s -- | We can use Equality to do substitution into anything. mapEq :: () => AnEquality s t a b -> f s -> f a -- | Substituting types with Equality. substEq :: () => AnEquality s t a b -> s ~ a -> t ~ b -> r -> r -- | Extract a witness of type Equality. runEq :: () => AnEquality s t a b -> Identical s t a b -- | Provides witness that (s ~ a, b ~ t) holds. data Identical (a :: k) (b :: k1) (s :: k) (t :: k1) :: forall k k1. () => k -> k1 -> k -> k1 -> * [Identical] :: Identical a b a b -- | When you see this as an argument to a function, it expects an -- Equality. type AnEquality (s :: k1) (t :: k2) (a :: k1) (b :: k2) = Identical a Proxy b a Proxy b -> Identical a Proxy b s Proxy t -- | A Simple AnEquality. type AnEquality' (s :: k2) (a :: k2) = AnEquality s s a a itraverseByOf :: () => IndexedTraversal i s t a b -> forall x. () => x -> f x -> forall x y. () => f x -> y -> f x -> f y -> i -> a -> f b -> s -> f t itraverseBy :: TraversableWithIndex i t => forall x. () => x -> f x -> forall x y. () => f x -> y -> f x -> f y -> i -> a -> f b -> t a -> f t b ifoldMapByOf :: () => IndexedFold i t a -> r -> r -> r -> r -> i -> a -> r -> t -> r ifoldMapBy :: FoldableWithIndex i t => r -> r -> r -> r -> i -> a -> r -> t a -> r -- | Generalizes mapAccumL to add access to the index. -- -- imapAccumLOf accumulates state from left to right. -- --
--   mapAccumLOfimapAccumL . const
--   
imapAccumL :: TraversableWithIndex i t => i -> s -> a -> (s, b) -> s -> t a -> (s, t b) -- | Generalizes mapAccumR to add access to the index. -- -- imapAccumROf accumulates state from right to left. -- --
--   mapAccumRimapAccumR . const
--   
imapAccumR :: TraversableWithIndex i t => i -> s -> a -> (s, b) -> s -> t a -> (s, t b) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results, with access its -- position (and the arguments flipped). -- --
--   forM a ≡ iforM a . const
--   iforMflip imapM
--   
iforM :: (TraversableWithIndex i t, Monad m) => t a -> i -> a -> m b -> m t b -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results, with access the -- index. -- -- When you don't need access to the index mapM is more liberal in -- what it can accept. -- --
--   mapMimapM . const
--   
imapM :: (TraversableWithIndex i t, Monad m) => i -> a -> m b -> t a -> m t b -- | Traverse with an index (and the arguments flipped). -- --
--   for a ≡ ifor a . const
--   iforflip itraverse
--   
ifor :: (TraversableWithIndex i t, Applicative f) => t a -> i -> a -> f b -> f t b -- | Extract the key-value pairs from a structure. -- -- When you don't need access to the indices in the result, then -- toList is more flexible in what it accepts. -- --
--   toListmap snd . itoList
--   
itoList :: FoldableWithIndex i f => f a -> [(i, a)] -- | Monadic fold over the elements of a structure with an index, -- associating to the left. -- -- When you don't need access to the index then foldlM is more -- flexible in what it accepts. -- --
--   foldlMifoldlM . const
--   
ifoldlM :: (FoldableWithIndex i f, Monad m) => i -> b -> a -> m b -> b -> f a -> m b -- | Monadic fold right over the elements of a structure with an index. -- -- When you don't need access to the index then foldrM is more -- flexible in what it accepts. -- --
--   foldrMifoldrM . const
--   
ifoldrM :: (FoldableWithIndex i f, Monad m) => i -> a -> b -> m b -> b -> f a -> m b -- | Searches a container with a predicate that is also supplied the index, -- returning the left-most element of the structure matching the -- predicate, or Nothing if there is no such element. -- -- When you don't need access to the index then find is more -- flexible in what it accepts. -- --
--   findifind . const
--   
ifind :: FoldableWithIndex i f => i -> a -> Bool -> f a -> Maybe (i, a) -- | Concatenate the results of a function of the elements of an indexed -- container with access to the index. -- -- When you don't need access to the index then concatMap is more -- flexible in what it accepts. -- --
--   concatMapiconcatMap . const
--   iconcatMapifoldMap
--   
iconcatMap :: FoldableWithIndex i f => i -> a -> [b] -> f a -> [b] -- | Run monadic actions for each target of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results (with the arguments flipped). -- --
--   iforM_flip imapM_
--   
-- -- When you don't need access to the index then forMOf_ is more -- flexible in what it accepts. -- --
--   forMOf_ l a ≡ iforMOf l a . const
--   
iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> i -> a -> m b -> m () -- | Run monadic actions for each target of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results. -- -- When you don't need access to the index then mapMOf_ is more -- flexible in what it accepts. -- --
--   mapM_imapM . const
--   
imapM_ :: (FoldableWithIndex i t, Monad m) => i -> a -> m b -> t a -> m () -- | Traverse elements with access to the index i, discarding the -- results (with the arguments flipped). -- --
--   ifor_flip itraverse_
--   
-- -- When you don't need access to the index then for_ is more -- flexible in what it accepts. -- --
--   for_ a ≡ ifor_ a . const
--   
ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> i -> a -> f b -> f () -- | Traverse elements with access to the index i, discarding the -- results. -- -- When you don't need access to the index then traverse_ is more -- flexible in what it accepts. -- --
--   traverse_ l = itraverse . const
--   
itraverse_ :: (FoldableWithIndex i t, Applicative f) => i -> a -> f b -> t a -> f () -- | Determines whether no elements of the structure satisfy the predicate. -- --
--   none f ≡ not . any f
--   
none :: Foldable f => a -> Bool -> f a -> Bool -- | Return whether or not none of the elements in a container satisfy a -- predicate, with access to the index i. -- -- When you don't need access to the index then none is more -- flexible in what it accepts. -- --
--   noneinone . const
--   inone f ≡ not . iany f
--   
inone :: FoldableWithIndex i f => i -> a -> Bool -> f a -> Bool -- | Return whether or not all elements in a container satisfy a predicate, -- with access to the index i. -- -- When you don't need access to the index then all is more -- flexible in what it accepts. -- --
--   alliall . const
--   
iall :: FoldableWithIndex i f => i -> a -> Bool -> f a -> Bool -- | Return whether or not any element in a container satisfies a -- predicate, with access to the index i. -- -- When you don't need access to the index then any is more -- flexible in what it accepts. -- --
--   anyiany . const
--   
iany :: FoldableWithIndex i f => i -> a -> Bool -> f a -> Bool -- | This allows you to filter an IndexedFold, IndexedGetter, -- IndexedTraversal or IndexedLens based on an index. -- --
--   >>> ["hello","the","world","!!!"]^?traversed.index 2
--   Just "world"
--   
index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p Indexed i f a a -- | This allows you to filter an IndexedFold, IndexedGetter, -- IndexedTraversal or IndexedLens based on a predicate on -- the indices. -- --
--   >>> ["hello","the","world","!!!"]^..traversed.indices even
--   ["hello","world"]
--   
-- --
--   >>> over (traversed.indices (>0)) Prelude.reverse $ ["He","was","stressed","o_O"]
--   ["He","saw","desserts","O_o"]
--   
indices :: (Indexable i p, Applicative f) => i -> Bool -> Optical' p Indexed i f a a -- | Composition of Indexed functions with a user supplied function -- for combining indices. icompose :: Indexable p c => i -> j -> p -> Indexed i s t -> r -> Indexed j a b -> s -> t -> c a b -> r -- | Remap the index. reindexed :: Indexable j p => i -> j -> Indexed i a b -> r -> p a b -> r -- | Use a value itself as its own index. This is essentially an indexed -- version of id. -- -- Note: When used to modify the value, this can break the index -- requirements assumed by indices and similar, so this is only -- properly an IndexedGetter, but it can be used as more. -- --
--   selfIndex :: IndexedGetter a a b
--   
selfIndex :: Indexable a p => p a fb -> a -> fb -- | Compose a non-indexed function with an Indexed function. -- -- Mnemonically, the > points to the indexing we want to -- preserve. -- -- This is the same as (.). -- -- f . g (and f .> g) gives you the -- index of g unless g is index-preserving, like a -- Prism, Iso or Equality, in which case it'll pass -- through the index of f. -- --
--   >>> let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]
--   
--   >>> nestedMap^..(itraversed.>itraversed).withIndex
--   [(10,"one,ten"),(20,"one,twenty"),(30,"two,thirty"),(40,"two,forty")]
--   
(.>) :: () => st -> r -> kab -> st -> kab -> r infixr 9 .> -- | Compose an Indexed function with a non-indexed function. -- -- Mnemonically, the < points to the indexing we want to -- preserve. -- --
--   >>> let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]
--   
--   >>> nestedMap^..(itraversed<.itraversed).withIndex
--   [(1,"one,ten"),(1,"one,twenty"),(2,"two,thirty"),(2,"two,forty")]
--   
(<.) :: Indexable i p => Indexed i s t -> r -> a -> b -> s -> t -> p a b -> r infixr 9 <. -- | A Functor with an additional index. -- -- Instances must satisfy a modified form of the Functor laws: -- --
--   imap f . imap g ≡ imap (\i -> f i . g i)
--   imap (\_ a -> a) ≡ id
--   
class Functor f => FunctorWithIndex i (f :: * -> *) | f -> i -- | Map with access to the index. imap :: FunctorWithIndex i f => i -> a -> b -> f a -> f b -- | The IndexedSetter for a FunctorWithIndex. -- -- If you don't need access to the index, then mapped is more -- flexible in what it accepts. imapped :: (FunctorWithIndex i f, Indexable i p, Settable f) => p a f b -> f a -> f f b -- | A container that supports folding with an additional index. class Foldable f => FoldableWithIndex i (f :: * -> *) | f -> i -- | Fold a container by mapping value to an arbitrary Monoid with -- access to the index i. -- -- When you don't need access to the index then foldMap is more -- flexible in what it accepts. -- --
--   foldMapifoldMap . const
--   
ifoldMap :: (FoldableWithIndex i f, Monoid m) => i -> a -> m -> f a -> m -- | The IndexedFold of a FoldableWithIndex container. -- -- ifolded . asIndex is a fold over the -- keys of a FoldableWithIndex. -- --
--   >>> Data.Map.fromList [(2, "hello"), (1, "world")]^..ifolded.asIndex
--   [1,2]
--   
ifolded :: (FoldableWithIndex i f, Indexable i p, Contravariant f, Applicative f) => p a f a -> f a -> f f a -- | Right-associative fold of an indexed container with access to the -- index i. -- -- When you don't need access to the index then foldr is more -- flexible in what it accepts. -- --
--   foldrifoldr . const
--   
ifoldr :: FoldableWithIndex i f => i -> a -> b -> b -> b -> f a -> b -- | Left-associative fold of an indexed container with access to the index -- i. -- -- When you don't need access to the index then foldl is more -- flexible in what it accepts. -- --
--   foldlifoldl . const
--   
ifoldl :: FoldableWithIndex i f => i -> b -> a -> b -> b -> f a -> b -- | Strictly fold right over the elements of a structure with -- access to the index i. -- -- When you don't need access to the index then foldr' is more -- flexible in what it accepts. -- --
--   foldr'ifoldr' . const
--   
ifoldr' :: FoldableWithIndex i f => i -> a -> b -> b -> b -> f a -> b -- | 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
--   
ifoldl' :: FoldableWithIndex i f => i -> b -> a -> b -> b -> f a -> b -- | A Traversable with an additional index. -- -- An instance must satisfy a (modified) form of the Traversable -- laws: -- --
--   itraverse (const Identity) ≡ Identity
--   fmap (itraverse f) . itraverse g ≡ getCompose . itraverse (\i -> Compose . fmap (f i) . g i)
--   
class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: * -> *) | t -> i -- | Traverse an indexed container. -- --
--   itraverseitraverseOf itraversed
--   
itraverse :: (TraversableWithIndex i t, Applicative f) => i -> a -> f b -> t a -> f t b -- | The IndexedTraversal of a TraversableWithIndex -- container. itraversed :: (TraversableWithIndex i t, Indexable i p, Applicative f) => p a f b -> t a -> f t b -- | Reify a Lens so it can be stored safely in a container. newtype ReifiedLens s t a b Lens :: Lens s t a b -> ReifiedLens s t a b [runLens] :: ReifiedLens s t a b -> Lens s t a b -- |
--   type ReifiedLens' = Simple ReifiedLens
--   
type ReifiedLens' s a = ReifiedLens s s a a -- | Reify an IndexedLens so it can be stored safely in a container. newtype ReifiedIndexedLens i s t a b IndexedLens :: IndexedLens i s t a b -> ReifiedIndexedLens i s t a b [runIndexedLens] :: ReifiedIndexedLens i s t a b -> IndexedLens i s t a b -- |
--   type ReifiedIndexedLens' i = Simple (ReifiedIndexedLens i)
--   
type ReifiedIndexedLens' i s a = ReifiedIndexedLens i s s a a -- | Reify an IndexedTraversal so it can be stored safely in a -- container. newtype ReifiedIndexedTraversal i s t a b IndexedTraversal :: IndexedTraversal i s t a b -> ReifiedIndexedTraversal i s t a b [runIndexedTraversal] :: ReifiedIndexedTraversal i s t a b -> IndexedTraversal i s t a b -- |
--   type ReifiedIndexedTraversal' i = Simple (ReifiedIndexedTraversal i)
--   
type ReifiedIndexedTraversal' i s a = ReifiedIndexedTraversal i s s a a -- | A form of Traversal that can be stored monomorphically in a -- container. newtype ReifiedTraversal s t a b Traversal :: Traversal s t a b -> ReifiedTraversal s t a b [runTraversal] :: ReifiedTraversal s t a b -> Traversal s t a b -- |
--   type ReifiedTraversal' = Simple ReifiedTraversal
--   
type ReifiedTraversal' s a = ReifiedTraversal s s a a -- | Reify a Getter so it can be stored safely in a container. -- -- This can also be useful when combining getters in novel ways, as -- ReifiedGetter is isomorphic to '(->)' and provides similar -- instances. -- --
--   >>> ("hello","world","!!!")^.runGetter ((,) <$> Getter _2 <*> Getter (_1.to length))
--   ("world",5)
--   
newtype ReifiedGetter s a Getter :: Getter s a -> ReifiedGetter s a [runGetter] :: ReifiedGetter s a -> Getter s a -- | Reify an IndexedGetter so it can be stored safely in a -- container. newtype ReifiedIndexedGetter i s a IndexedGetter :: IndexedGetter i s a -> ReifiedIndexedGetter i s a [runIndexedGetter] :: ReifiedIndexedGetter i s a -> IndexedGetter i s a -- | Reify a Fold so it can be stored safely in a container. -- -- This can also be useful for creatively combining folds as -- ReifiedFold s is isomorphic to ReaderT s [] -- and provides similar instances. -- --
--   >>> ("hello","world")^..runFold ((,) <$> Fold _2 <*> Fold both)
--   [("world","hello"),("world","world")]
--   
newtype ReifiedFold s a Fold :: Fold s a -> ReifiedFold s a [runFold] :: ReifiedFold s a -> Fold s a newtype ReifiedIndexedFold i s a IndexedFold :: IndexedFold i s a -> ReifiedIndexedFold i s a [runIndexedFold] :: ReifiedIndexedFold i s a -> IndexedFold i s a -- | Reify a Setter so it can be stored safely in a container. newtype ReifiedSetter s t a b Setter :: Setter s t a b -> ReifiedSetter s t a b [runSetter] :: ReifiedSetter s t a b -> Setter s t a b -- |
--   type ReifiedSetter' = Simple ReifiedSetter
--   
type ReifiedSetter' s a = ReifiedSetter s s a a -- | Reify an IndexedSetter so it can be stored safely in a -- container. newtype ReifiedIndexedSetter i s t a b IndexedSetter :: IndexedSetter i s t a b -> ReifiedIndexedSetter i s t a b [runIndexedSetter] :: ReifiedIndexedSetter i s t a b -> IndexedSetter i s t a b -- |
--   type ReifiedIndexedSetter' i = Simple (ReifiedIndexedSetter i)
--   
type ReifiedIndexedSetter' i s a = ReifiedIndexedSetter i s s a a -- | Reify an Iso so it can be stored safely in a container. newtype ReifiedIso s t a b Iso :: Iso s t a b -> ReifiedIso s t a b [runIso] :: ReifiedIso s t a b -> Iso s t a b -- |
--   type ReifiedIso' = Simple ReifiedIso
--   
type ReifiedIso' s a = ReifiedIso s s a a -- | Reify a Prism so it can be stored safely in a container. newtype ReifiedPrism s t a b Prism :: Prism s t a b -> ReifiedPrism s t a b [runPrism] :: ReifiedPrism s t a b -> Prism s t a b -- |
--   type ReifiedPrism' = Simple ReifiedPrism
--   
type ReifiedPrism' s a = ReifiedPrism s s a a -- | This provides a breadth-first Traversal or Fold of the -- individual levels of any other Traversal or Fold via -- iterative deepening depth-first search. The levels are returned to you -- in a compressed format. -- -- This is similar to levels, but retains the index of the -- original IndexedTraversal, so you can access it when traversing -- the levels later on. -- --
--   >>> ["dog","cat"]^@..ilevels (traversed<.>traversed).itraversed
--   [((0,0),'d'),((0,1),'o'),((1,0),'c'),((0,2),'g'),((1,1),'a'),((1,2),'t')]
--   
-- -- The resulting Traversal of the levels which is indexed by the -- depth of each Level. -- --
--   >>> ["dog","cat"]^@..ilevels (traversed<.>traversed)<.>itraversed
--   [((2,(0,0)),'d'),((3,(0,1)),'o'),((3,(1,0)),'c'),((4,(0,2)),'g'),((4,(1,1)),'a'),((5,(1,2)),'t')]
--   
-- --
--   ilevels :: IndexedTraversal i s t a b      -> IndexedTraversal Int s t (Level i a) (Level i b)
--   ilevels :: IndexedFold i s a               -> IndexedFold Int s (Level i a)
--   
-- -- Note: Internally this is implemented by using an illegal -- Applicative, as it extracts information in an order that -- violates the Applicative laws. ilevels :: Applicative f => Traversing Indexed i f s t a b -> IndexedLensLike Int f s t Level i a Level j b -- | This provides a breadth-first Traversal or Fold of the -- individual levels of any other Traversal or Fold -- via iterative deepening depth-first search. The levels are returned to -- you in a compressed format. -- -- This can permit us to extract the levels directly: -- --
--   >>> ["hello","world"]^..levels (traverse.traverse)
--   [Zero,Zero,One () 'h',Two 0 (One () 'e') (One () 'w'),Two 0 (One () 'l') (One () 'o'),Two 0 (One () 'l') (One () 'r'),Two 0 (One () 'o') (One () 'l'),One () 'd']
--   
-- -- But we can also traverse them in turn: -- --
--   >>> ["hello","world"]^..levels (traverse.traverse).traverse
--   "hewlolrold"
--   
-- -- We can use this to traverse to a fixed depth in the tree of -- (<*>) used in the Traversal: -- --
--   >>> ["hello","world"] & taking 4 (levels (traverse.traverse)).traverse %~ toUpper
--   ["HEllo","World"]
--   
-- -- Or we can use it to traverse the first n elements in found in -- that Traversal regardless of the depth at which they were -- found. -- --
--   >>> ["hello","world"] & taking 4 (levels (traverse.traverse).traverse) %~ toUpper
--   ["HELlo","World"]
--   
-- -- The resulting Traversal of the levels which is indexed -- by the depth of each Level. -- --
--   >>> ["dog","cat"]^@..levels (traverse.traverse) <. traverse
--   [(2,'d'),(3,'o'),(3,'c'),(4,'g'),(4,'a'),(5,'t')]
--   
-- --
--   levels :: Traversal s t a b      -> IndexedTraversal Int s t (Level () a) (Level () b)
--   levels :: Fold s a               -> IndexedFold Int s (Level () a)
--   
-- -- Note: Internally this is implemented by using an illegal -- Applicative, as it extracts information in an order that -- violates the Applicative laws. levels :: Applicative f => Traversing ((->) :: * -> * -> *) f s t a b -> IndexedLensLike Int f s t Level () a Level () b -- | Sequence a container using a specified Applicative. -- -- This is like traverseBy where the Traversable instance -- can be specified by any Traversal -- --
--   sequenceByOf traversesequenceBy
--   
sequenceByOf :: () => Traversal s t f b b -> forall x. () => x -> f x -> forall x y. () => f x -> y -> f x -> f y -> s -> f t -- | Traverse a container using a specified Applicative. -- -- This is like traverseBy where the Traversable instance -- can be specified by any Traversal -- --
--   traverseByOf traversetraverseBy
--   
traverseByOf :: () => Traversal s t a b -> forall x. () => x -> f x -> forall x y. () => f x -> y -> f x -> f y -> a -> f b -> s -> f t -- | Fuse a Traversal by reassociating all of the -- (<*>) operations to the left and fusing all of -- the fmap calls into one. This is particularly useful when -- constructing a Traversal using operations from -- GHC.Generics. -- -- Given a pair of Traversals foo and bar, -- --
--   confusing (foo.bar) = foo.bar
--   
-- -- However, foo and bar are each going to use the -- Applicative they are given. -- -- confusing exploits the Yoneda lemma to merge their -- separate uses of fmap into a single fmap. and it further -- exploits an interesting property of the right Kan lift (or -- Curried) to left associate all of the uses of -- (<*>) to make it possible to fuse together more -- fmaps. -- -- This is particularly effective when the choice of functor f -- is unknown at compile time or when the Traversal -- foo.bar in the above description is recursive or complex -- enough to prevent inlining. -- -- fusing is a version of this combinator suitable for fusing -- lenses. -- --
--   confusing :: Traversal s t a b -> Traversal s t a b
--   
confusing :: Applicative f => LensLike Curried Yoneda f Yoneda f s t a b -> LensLike f s t a b -- | Try the second traversal. If it returns no entries, try again with all -- entries from the first traversal, recursively. -- --
--   deepOf :: Fold s s          -> Fold s a                   -> Fold s a
--   deepOf :: Traversal' s s    -> Traversal' s a             -> Traversal' s a
--   deepOf :: Traversal s t s t -> Traversal s t a b          -> Traversal s t a b
--   deepOf :: Fold s s          -> IndexedFold i s a          -> IndexedFold i s a
--   deepOf :: Traversal s t s t -> IndexedTraversal i s t a b -> IndexedTraversal i s t a b
--   
deepOf :: (Conjoined p, Applicative f) => LensLike f s t s t -> Traversing p f s t a b -> Over p f s t a b -- | Try the first Traversal (or Fold), falling back on the -- second Traversal (or Fold) if it returns no entries. -- -- This is only a valid Traversal if the second Traversal -- is disjoint from the result of the first or returns exactly the same -- results. These conditions are trivially met when given a Lens, -- Iso, Getter, Prism or "affine" Traversal -- one -- that has 0 or 1 target. -- -- Mutatis mutandis for Fold. -- --
--   >>> [0,1,2,3] ^? failing (ix 1) (ix 2)
--   Just 1
--   
-- --
--   >>> [0,1,2,3] ^? failing (ix 42) (ix 2)
--   Just 2
--   
-- --
--   failing :: Traversal s t a b -> Traversal s t a b -> Traversal s t a b
--   failing :: Prism s t a b     -> Prism s t a b     -> Traversal s t a b
--   failing :: Fold s a          -> Fold s a          -> Fold s a
--   
-- -- These cases are also supported, trivially, but are boring, because the -- left hand side always succeeds. -- --
--   failing :: Lens s t a b      -> Traversal s t a b -> Traversal s t a b
--   failing :: Iso s t a b       -> Traversal s t a b -> Traversal s t a b
--   failing :: Equality s t a b  -> Traversal s t a b -> Traversal s t a b
--   failing :: Getter s a        -> Fold s a          -> Fold s a
--   
-- -- If both of the inputs are indexed, the result is also indexed, so you -- can apply this to a pair of indexed traversals or indexed folds, -- obtaining an indexed traversal or indexed fold. -- --
--   failing :: IndexedTraversal i s t a b -> IndexedTraversal i s t a b -> IndexedTraversal i s t a b
--   failing :: IndexedFold i s a          -> IndexedFold i s a          -> IndexedFold i s a
--   
-- -- These cases are also supported, trivially, but are boring, because the -- left hand side always succeeds. -- --
--   failing :: IndexedLens i s t a b      -> IndexedTraversal i s t a b -> IndexedTraversal i s t a b
--   failing :: IndexedGetter i s a        -> IndexedGetter i s a        -> IndexedFold i s a
--   
failing :: (Conjoined p, Applicative f) => Traversing p f s t a b -> Over p f s t a b -> Over p f s t a b infixl 5 `failing` -- | Try to map a function which uses the index over this -- IndexedTraversal, failing if the IndexedTraversal has no -- targets. -- --
--   ifailover :: Alternative m => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> m t
--   
ifailover :: Alternative m => Over Indexed i (,) Any s t a b -> i -> a -> b -> s -> m t -- | Try to map a function over this Traversal, failing if the -- Traversal has no targets. -- --
--   >>> failover (element 3) (*2) [1,2] :: Maybe [Int]
--   Nothing
--   
-- --
--   >>> failover _Left (*2) (Right 4) :: Maybe (Either Int Int)
--   Nothing
--   
-- --
--   >>> failover _Right (*2) (Right 4) :: Maybe (Either Int Int)
--   Just (Right 8)
--   
-- --
--   failover :: Alternative m => Traversal s t a b -> (a -> b) -> s -> m t
--   
failover :: Alternative m => LensLike (,) Any s t a b -> a -> b -> s -> m t -- | Traverse elements of a Traversable container where their -- ordinal positions match a predicate. -- --
--   elementselementsOf traverse
--   
elements :: Traversable t => Int -> Bool -> IndexedTraversal' Int t a a -- | Traverse (or fold) selected elements of a Traversal (or -- Fold) where their ordinal positions match a predicate. -- --
--   elementsOf :: Traversal' s a -> (Int -> Bool) -> IndexedTraversal' Int s a
--   elementsOf :: Fold s a       -> (Int -> Bool) -> IndexedFold Int s a
--   
elementsOf :: Applicative f => LensLike Indexing f s t a a -> Int -> Bool -> IndexedLensLike Int f s t a a -- | Traverse the nth element of a Traversable container. -- --
--   elementelementOf traverse
--   
element :: Traversable t => Int -> IndexedTraversal' Int t a a -- | Traverse the nth elementOf a Traversal, -- Lens or Iso if it exists. -- --
--   >>> [[1],[3,4]] & elementOf (traverse.traverse) 1 .~ 5
--   [[1],[5,4]]
--   
-- --
--   >>> [[1],[3,4]] ^? elementOf (folded.folded) 1
--   Just 3
--   
-- --
--   >>> timingOut $ ['a'..] ^?! elementOf folded 5
--   'f'
--   
-- --
--   >>> timingOut $ take 10 $ elementOf traverse 3 .~ 16 $ [0..]
--   [0,1,2,16,4,5,6,7,8,9]
--   
-- --
--   elementOf :: Traversal' s a -> Int -> IndexedTraversal' Int s a
--   elementOf :: Fold s a       -> Int -> IndexedFold Int s a
--   
elementOf :: Applicative f => LensLike Indexing f s t a a -> Int -> IndexedLensLike Int f s t a a -- | This is the trivial empty Traversal. -- --
--   ignored :: IndexedTraversal i s s a b
--   
-- --
--   ignoredconst pure
--   
-- --
--   >>> 6 & ignored %~ absurd
--   6
--   
ignored :: Applicative f => pafb -> s -> f s -- | Traverse any Traversable container. This is an -- IndexedTraversal that is indexed by ordinal position. traversed64 :: Traversable f => IndexedTraversal Int64 f a f b a b -- | Traverse any Traversable1 container. This is an -- IndexedTraversal1 that is indexed by ordinal position. traversed1 :: Traversable1 f => IndexedTraversal1 Int f a f b a b -- | Traverse any Traversable container. This is an -- IndexedTraversal that is indexed by ordinal position. traversed :: Traversable f => IndexedTraversal Int f a f b a 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 s t a b      -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   imapAccumLOf :: IndexedTraversal i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   
imapAccumLOf :: () => Over Indexed i State acc s t a b -> i -> acc -> a -> (acc, b) -> acc -> s -> (acc, t) -- | Generalizes mapAccumR to an arbitrary IndexedTraversal -- with access to the index. -- -- imapAccumROf accumulates state from right to left. -- --
--   mapAccumROf l ≡ imapAccumROf l . const
--   
-- --
--   imapAccumROf :: IndexedLens i s t a b      -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   imapAccumROf :: IndexedTraversal i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   
imapAccumROf :: () => Over Indexed i Backwards State acc s t a b -> i -> acc -> a -> (acc, b) -> acc -> s -> (acc, t) -- | 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
--   iforMOfflip . imapMOf
--   
-- --
--   iforMOf :: Monad m => IndexedLens i s t a b      -> s -> (i -> a -> m b) -> m t
--   iforMOf :: Monad m => IndexedTraversal i s t a b -> s -> (i -> a -> m b) -> m t
--   
iforMOf :: () => Indexed i a WrappedMonad m b -> s -> WrappedMonad m t -> s -> i -> a -> m b -> m t -- | Map each element of a structure targeted by a Lens to a monadic -- action, evaluate these actions from left to right, and collect the -- results, with access its position. -- -- When you don't need access to the index mapMOf is more liberal -- in what it can accept. -- --
--   mapMOf l ≡ imapMOf l . const
--   
-- --
--   imapMOf :: Monad m => IndexedLens       i s t a b -> (i -> a -> m b) -> s -> m t
--   imapMOf :: Monad m => IndexedTraversal  i s t a b -> (i -> a -> m b) -> s -> m t
--   imapMOf :: Bind  m => IndexedTraversal1 i s t a b -> (i -> a -> m b) -> s -> m t
--   
imapMOf :: () => Over Indexed i WrappedMonad m s t a b -> i -> a -> m b -> s -> m t -- | Traverse with an index (and the arguments flipped). -- --
--   forOf l a ≡ iforOf l a . const
--   iforOfflip . itraverseOf
--   
-- --
--   iforOf :: Functor f     => IndexedLens i s t a b       -> s -> (i -> a -> f b) -> f t
--   iforOf :: Applicative f => IndexedTraversal i s t a b  -> s -> (i -> a -> f b) -> f t
--   iforOf :: Apply f       => IndexedTraversal1 i s t a b -> s -> (i -> a -> f b) -> f t
--   
iforOf :: () => Indexed i a f b -> s -> f t -> s -> i -> a -> f b -> f t -- | 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! -- --
--   itraverseOfwithIndex
--   traverseOf l = itraverseOf l . const = id
--   
-- --
--   itraverseOf :: Functor f     => IndexedLens i s t a b       -> (i -> a -> f b) -> s -> f t
--   itraverseOf :: Applicative f => IndexedTraversal i s t a b  -> (i -> a -> f b) -> s -> f t
--   itraverseOf :: Apply f       => IndexedTraversal1 i s t a b -> (i -> a -> f b) -> s -> f t
--   
itraverseOf :: () => Indexed i a f b -> s -> f t -> i -> a -> f b -> s -> f t -- | Clone an IndexedTraversal1 yielding an IndexedTraversal1 -- with the same index. cloneIndexedTraversal1 :: () => AnIndexedTraversal1 i s t a b -> IndexedTraversal1 i s t a b -- | Clone a Traversal1 yielding an IndexPreservingTraversal1 -- that passes through whatever index it is composed with. cloneIndexPreservingTraversal1 :: () => ATraversal1 s t a b -> IndexPreservingTraversal1 s t a b -- | A Traversal1 is completely characterized by its behavior on a -- Bazaar1. cloneTraversal1 :: () => ATraversal1 s t a b -> Traversal1 s t a b -- | Clone an IndexedTraversal yielding an IndexedTraversal -- with the same index. cloneIndexedTraversal :: () => AnIndexedTraversal i s t a b -> IndexedTraversal i s t a b -- | Clone a Traversal yielding an IndexPreservingTraversal -- that passes through whatever index it is composed with. cloneIndexPreservingTraversal :: () => ATraversal s t a b -> IndexPreservingTraversal s t a b -- | A Traversal is completely characterized by its behavior on a -- Bazaar. -- -- Cloning a Traversal is one way to make sure you aren't given -- something weaker, such as a Fold and can be used as a way to -- pass around traversals that have to be monomorphic in f. -- -- Note: This only accepts a proper Traversal (or Lens). To -- clone a Lens as such, use cloneLens. -- -- Note: It is usually better to use ReifiedTraversal and -- runTraversal than to cloneTraversal. The former can -- execute at full speed, while the latter needs to round trip through -- the Bazaar. -- --
--   >>> let foo l a = (view (getting (cloneTraversal l)) a, set (cloneTraversal l) 10 a)
--   
--   >>> foo both ("hello","world")
--   ("helloworld",(10,10))
--   
-- --
--   cloneTraversal :: LensLike (Bazaar (->) a b) s t a b -> Traversal s t a b
--   
cloneTraversal :: () => ATraversal s t a b -> Traversal s t a b -- | Visit all but the first n targets of a Traversal, -- Fold, Getter or Lens. -- --
--   >>> ("hello","world") ^? dropping 1 both
--   Just "world"
--   
-- -- Dropping works on infinite traversals as well: -- --
--   >>> [1..] ^? dropping 1 folded
--   Just 2
--   
-- --
--   dropping :: Int -> Traversal' s a                   -> Traversal' s a
--   dropping :: Int -> Lens' s a                        -> Traversal' s a
--   dropping :: Int -> Iso' s a                         -> Traversal' s a
--   dropping :: Int -> Prism' s a                       -> Traversal' s a
--   dropping :: Int -> Getter s a                       -> Fold s a
--   dropping :: Int -> Fold s a                         -> Fold s a
--   dropping :: Int -> IndexedTraversal' i s a          -> IndexedTraversal' i s a
--   dropping :: Int -> IndexedLens' i s a               -> IndexedTraversal' i s a
--   dropping :: Int -> IndexedGetter i s a              -> IndexedFold i s a
--   dropping :: Int -> IndexedFold i s a                -> IndexedFold i s a
--   
dropping :: (Conjoined p, Applicative f) => Int -> Over p Indexing f s t a a -> Over p f s t a a -- | Visit the first n targets of a Traversal, Fold, -- Getter or Lens. -- --
--   >>> [("hello","world"),("!!!","!!!")]^.. taking 2 (traverse.both)
--   ["hello","world"]
--   
-- --
--   >>> timingOut $ [1..] ^.. taking 3 traverse
--   [1,2,3]
--   
-- --
--   >>> over (taking 5 traverse) succ "hello world"
--   "ifmmp world"
--   
-- --
--   taking :: Int -> Traversal' s a                   -> Traversal' s a
--   taking :: Int -> Lens' s a                        -> Traversal' s a
--   taking :: Int -> Iso' s a                         -> Traversal' s a
--   taking :: Int -> Prism' s a                       -> Traversal' s a
--   taking :: Int -> Getter s a                       -> Fold s a
--   taking :: Int -> Fold s a                         -> Fold s a
--   taking :: Int -> IndexedTraversal' i s a          -> IndexedTraversal' i s a
--   taking :: Int -> IndexedLens' i s a               -> IndexedTraversal' i s a
--   taking :: Int -> IndexedGetter i s a              -> IndexedFold i s a
--   taking :: Int -> IndexedFold i s a                -> IndexedFold i s a
--   
taking :: (Conjoined p, Applicative f) => Int -> Traversing p f s t a a -> Over p f s t a a -- | Apply a different Traversal or Fold to each side of a -- Bitraversable container. -- --
--   beside :: Traversal s t a b                -> Traversal s' t' a b                -> Traversal (r s s') (r t t') a b
--   beside :: IndexedTraversal i s t a b       -> IndexedTraversal i s' t' a b       -> IndexedTraversal i (r s s') (r t t') a b
--   beside :: IndexPreservingTraversal s t a b -> IndexPreservingTraversal s' t' a b -> IndexPreservingTraversal (r s s') (r t t') a b
--   
-- --
--   beside :: Traversal s t a b                -> Traversal s' t' a b                -> Traversal (s,s') (t,t') a b
--   beside :: Lens s t a b                     -> Lens s' t' a b                     -> Traversal (s,s') (t,t') a b
--   beside :: Fold s a                         -> Fold s' a                          -> Fold (s,s') a
--   beside :: Getter s a                       -> Getter s' a                        -> Fold (s,s') a
--   
-- --
--   beside :: IndexedTraversal i s t a b       -> IndexedTraversal i s' t' a b       -> IndexedTraversal i (s,s') (t,t') a b
--   beside :: IndexedLens i s t a b            -> IndexedLens i s' t' a b            -> IndexedTraversal i (s,s') (t,t') a b
--   beside :: IndexedFold i s a                -> IndexedFold i s' a                 -> IndexedFold i (s,s') a
--   beside :: IndexedGetter i s a              -> IndexedGetter i s' a               -> IndexedFold i (s,s') a
--   
-- --
--   beside :: IndexPreservingTraversal s t a b -> IndexPreservingTraversal s' t' a b -> IndexPreservingTraversal (s,s') (t,t') a b
--   beside :: IndexPreservingLens s t a b      -> IndexPreservingLens s' t' a b      -> IndexPreservingTraversal (s,s') (t,t') a b
--   beside :: IndexPreservingFold s a          -> IndexPreservingFold s' a           -> IndexPreservingFold (s,s') a
--   beside :: IndexPreservingGetter s a        -> IndexPreservingGetter s' a         -> IndexPreservingFold (s,s') a
--   
-- --
--   >>> ("hello",["world","!!!"])^..beside id traverse
--   ["hello","world","!!!"]
--   
beside :: (Representable q, Applicative Rep q, Applicative f, Bitraversable r) => Optical p q f s t a b -> Optical p q f s' t' a b -> Optical p q f r s s' r t t' a b -- | Traverse both parts of a Bitraversable1 container with matching -- types. -- -- Usually that type will be a pair. -- --
--   both1 :: Traversal1 (a, a)       (b, b)       a b
--   both1 :: Traversal1 (Either a a) (Either b b) a b
--   
both1 :: Bitraversable1 r => Traversal1 r a a r b b a b -- | Traverse both parts of a Bitraversable container with matching -- types. -- -- Usually that type will be a pair. -- --
--   >>> (1,2) & both *~ 10
--   (10,20)
--   
-- --
--   >>> over both length ("hello","world")
--   (5,5)
--   
-- --
--   >>> ("hello","world")^.both
--   "helloworld"
--   
-- --
--   both :: Traversal (a, a)       (b, b)       a b
--   both :: Traversal (Either a a) (Either b b) a b
--   
both :: Bitraversable r => Traversal r a a r b b a b -- | The one-level version of contextsOf. This extracts a list of -- the immediate children according to a given Traversal as -- editable contexts. -- -- Given a context you can use pos to see the values, peek -- at what the structure would be like with an edited result, or simply -- extract the original structure. -- --
--   propChildren l x = toListOf l x == map pos (holesOf l x)
--   propId l x = all (== x) [extract w | w <- holesOf l x]
--   
-- --
--   holesOf :: Iso' s a                -> s -> [Pretext' (->) a s]
--   holesOf :: Lens' s a               -> s -> [Pretext' (->) a s]
--   holesOf :: Traversal' s a          -> s -> [Pretext' (->) a s]
--   holesOf :: IndexedLens' i s a      -> s -> [Pretext' (Indexed i) a s]
--   holesOf :: IndexedTraversal' i s a -> s -> [Pretext' (Indexed i) a s]
--   
holesOf :: Conjoined p => Over p Bazaar p a a s t a a -> s -> [Pretext p a a t] -- | This converts a Traversal that you "know" will target only one -- element to a Lens. It can also be used to transform a -- Fold into a Getter. -- -- The resulting Lens or Getter will be partial if the -- Traversal targets nothing or more than one element. -- --
--   >>> Left (ErrorCall "unsafeSingular: empty traversal") <- try (evaluate ([] & unsafeSingular traverse .~ 0)) :: IO (Either ErrorCall [Integer])
--   
-- --
--   unsafeSingular :: Traversal s t a b          -> Lens s t a b
--   unsafeSingular :: Fold s a                   -> Getter s a
--   unsafeSingular :: IndexedTraversal i s t a b -> IndexedLens i s t a b
--   unsafeSingular :: IndexedFold i s a          -> IndexedGetter i s a
--   
unsafeSingular :: (HasCallStack, Conjoined p, Functor f) => Traversing p f s t a b -> Over p f s t a b -- | This converts a Traversal that you "know" will target one or -- more elements to a Lens. It can also be used to transform a -- non-empty Fold into a Getter. -- -- The resulting Lens or Getter will be partial if the -- supplied Traversal returns no results. -- --
--   >>> [1,2,3] ^. singular _head
--   1
--   
-- --
--   >>> Left (ErrorCall "singular: empty traversal") <- try (evaluate ([] ^. singular _head)) :: IO (Either ErrorCall ())
--   
-- --
--   >>> Left 4 ^. singular _Left
--   4
--   
-- --
--   >>> [1..10] ^. singular (ix 7)
--   8
--   
-- --
--   >>> [] & singular traverse .~ 0
--   []
--   
-- --
--   singular :: Traversal s t a a          -> Lens s t a a
--   singular :: Fold s a                   -> Getter s a
--   singular :: IndexedTraversal i s t a a -> IndexedLens i s t a a
--   singular :: IndexedFold i s a          -> IndexedGetter i s a
--   
singular :: (HasCallStack, Conjoined p, Functor f) => Traversing p f s t a a -> Over p f s t a a iunsafePartsOf' :: () => Over Indexed i Bazaar Indexed i a b s t a b -> IndexedLens [i] s t [a] [b] unsafePartsOf' :: () => ATraversal s t a b -> Lens s t [a] [b] -- | An indexed version of unsafePartsOf that receives the entire -- list of indices as its index. iunsafePartsOf :: (Indexable [i] p, Functor f) => Traversing Indexed i f s t a b -> Over p f s t [a] [b] -- | unsafePartsOf turns a Traversal into a uniplate -- (or biplate) family. -- -- If you do not need the types of s and t to be -- different, it is recommended that you use partsOf. -- -- It is generally safer to traverse with the Bazaar rather than -- use this combinator. However, it is sometimes convenient. -- -- This is unsafe because if you don't supply at least as many -- b's as you were given a's, then the reconstruction -- of t will result in an error! -- -- When applied to a Fold the result is merely a Getter -- (and becomes safe). -- --
--   unsafePartsOf :: Iso s t a b       -> Lens s t [a] [b]
--   unsafePartsOf :: Lens s t a b      -> Lens s t [a] [b]
--   unsafePartsOf :: Traversal s t a b -> Lens s t [a] [b]
--   unsafePartsOf :: Fold s a          -> Getter s [a]
--   unsafePartsOf :: Getter s a        -> Getter s [a]
--   
unsafePartsOf :: Functor f => Traversing ((->) :: * -> * -> *) f s t a b -> LensLike f s t [a] [b] -- | A type-restricted version of ipartsOf that can only be used -- with an IndexedTraversal. ipartsOf' :: (Indexable [i] p, Functor f) => Over Indexed i Bazaar' Indexed i a s t a a -> Over p f s t [a] [a] -- | A type-restricted version of partsOf that can only be used with -- a Traversal. partsOf' :: () => ATraversal s t a a -> Lens s t [a] [a] -- | An indexed version of partsOf that receives the entire list of -- indices as its index. ipartsOf :: (Indexable [i] p, Functor f) => Traversing Indexed i f s t a a -> Over p f s t [a] [a] -- | partsOf turns a Traversal into a Lens that -- resembles an early version of the uniplate (or biplate) -- type. -- -- Note: You should really try to maintain the invariant of the -- number of children in the list. -- --
--   >>> (a,b,c) & partsOf each .~ [x,y,z]
--   (x,y,z)
--   
-- -- Any extras will be lost. If you do not supply enough, then the -- remainder will come from the original structure. -- --
--   >>> (a,b,c) & partsOf each .~ [w,x,y,z]
--   (w,x,y)
--   
-- --
--   >>> (a,b,c) & partsOf each .~ [x,y]
--   (x,y,c)
--   
-- --
--   >>> ('b', 'a', 'd', 'c') & partsOf each %~ sort
--   ('a','b','c','d')
--   
-- -- So technically, this is only a Lens if you do not change the -- number of results it returns. -- -- When applied to a Fold the result is merely a Getter. -- --
--   partsOf :: Iso' s a       -> Lens' s [a]
--   partsOf :: Lens' s a      -> Lens' s [a]
--   partsOf :: Traversal' s a -> Lens' s [a]
--   partsOf :: Fold s a       -> Getter s [a]
--   partsOf :: Getter s a     -> Getter s [a]
--   
partsOf :: Functor f => Traversing ((->) :: * -> * -> *) f s t a a -> LensLike f s t [a] [a] -- | This IndexedTraversal allows you to traverse the -- individual stores in a Bazaar with access to their indices. iloci :: (Indexable i p, Applicative f) => p a f b -> Bazaar Indexed i a c s -> f Bazaar Indexed i b c s -- | This Traversal allows you to traverse the individual -- stores in a Bazaar. loci :: Applicative f => a -> f b -> Bazaar ((->) :: * -> * -> *) a c s -> f Bazaar ((->) :: * -> * -> *) b c s -- | This permits the use of scanl1 over an arbitrary -- Traversal or Lens. -- --
--   scanl1scanl1Of traverse
--   
-- --
--   scanl1Of :: Iso s t a a       -> (a -> a -> a) -> s -> t
--   scanl1Of :: Lens s t a a      -> (a -> a -> a) -> s -> t
--   scanl1Of :: Traversal s t a a -> (a -> a -> a) -> s -> t
--   
scanl1Of :: () => LensLike State Maybe a s t a a -> a -> a -> a -> s -> t -- | This permits the use of scanr1 over an arbitrary -- Traversal or Lens. -- --
--   scanr1scanr1Of traverse
--   
-- --
--   scanr1Of :: Iso s t a a       -> (a -> a -> a) -> s -> t
--   scanr1Of :: Lens s t a a      -> (a -> a -> a) -> s -> t
--   scanr1Of :: Traversal s t a a -> (a -> a -> a) -> s -> t
--   
scanr1Of :: () => LensLike Backwards State Maybe a s t a a -> a -> a -> a -> s -> t -- | This generalizes mapAccumL to an arbitrary Traversal. -- --
--   mapAccumLmapAccumLOf traverse
--   
-- -- mapAccumLOf accumulates State from left to right. -- --
--   mapAccumLOf :: Iso s t a b       -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   mapAccumLOf :: Lens s t a b      -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   mapAccumLOf :: Traversal s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   
-- --
--   mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   mapAccumLOf l f acc0 s = swap (runState (l (a -> state (acc -> swap (f acc a))) s) acc0)
--   
mapAccumLOf :: () => LensLike State acc s t a b -> acc -> a -> (acc, b) -> acc -> s -> (acc, t) -- | This generalizes mapAccumR to an arbitrary Traversal. -- --
--   mapAccumRmapAccumROf traverse
--   
-- -- mapAccumROf accumulates State from right to left. -- --
--   mapAccumROf :: Iso s t a b       -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   mapAccumROf :: Lens s t a b      -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   mapAccumROf :: Traversal s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   
-- --
--   mapAccumROf :: LensLike (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
--   
mapAccumROf :: () => LensLike Backwards State acc s t a b -> acc -> a -> (acc, b) -> acc -> s -> (acc, t) -- | This generalizes transpose to an arbitrary Traversal. -- -- Note: transpose handles ragged inputs more intelligently, but -- for non-ragged inputs: -- --
--   >>> transposeOf traverse [[1,2,3],[4,5,6]]
--   [[1,4],[2,5],[3,6]]
--   
-- --
--   transposetransposeOf traverse
--   
-- -- Since every Lens is a Traversal, we can use this as a -- form of monadic strength as well: -- --
--   transposeOf _2 :: (b, [a]) -> [(b, a)]
--   
transposeOf :: () => LensLike ZipList s t [a] a -> s -> [t] -- | Sequence the (monadic) effects targeted by a Lens in a -- container from left to right. -- --
--   >>> sequenceOf each ([1,2],[3,4],[5,6])
--   [(1,3,5),(1,3,6),(1,4,5),(1,4,6),(2,3,5),(2,3,6),(2,4,5),(2,4,6)]
--   
-- --
--   sequencesequenceOf traverse
--   sequenceOf l ≡ mapMOf l id
--   sequenceOf l ≡ unwrapMonad . l WrapMonad
--   
-- --
--   sequenceOf :: Monad m => Iso s t (m b) b       -> s -> m t
--   sequenceOf :: Monad m => Lens s t (m b) b      -> s -> m t
--   sequenceOf :: Monad m => Traversal s t (m b) b -> s -> m t
--   
sequenceOf :: () => LensLike WrappedMonad m s t m b b -> s -> m t -- | forMOf is a flipped version of mapMOf, consistent with -- the definition of forM. -- --
--   >>> forMOf both (1,3) $ \x -> [x, x + 1]
--   [(1,3),(1,4),(2,3),(2,4)]
--   
-- --
--   forMforMOf traverse
--   forMOf l ≡ flip (mapMOf l)
--   iforMOf l s ≡ forM l s . Indexed
--   
-- --
--   forMOf :: Monad m => Iso s t a b       -> s -> (a -> m b) -> m t
--   forMOf :: Monad m => Lens s t a b      -> s -> (a -> m b) -> m t
--   forMOf :: Monad m => Traversal s t a b -> s -> (a -> m b) -> m t
--   
forMOf :: () => LensLike WrappedMonad m s t a b -> s -> a -> m b -> m t -- | Map each element of a structure targeted by a Lens to a monadic -- action, evaluate these actions from left to right, and collect the -- results. -- --
--   >>> mapMOf both (\x -> [x, x + 1]) (1,3)
--   [(1,3),(1,4),(2,3),(2,4)]
--   
-- --
--   mapMmapMOf traverse
--   imapMOf l ≡ forM l . Indexed
--   
-- --
--   mapMOf :: Monad m => Iso s t a b       -> (a -> m b) -> s -> m t
--   mapMOf :: Monad m => Lens s t a b      -> (a -> m b) -> s -> m t
--   mapMOf :: Monad m => Traversal s t a b -> (a -> m b) -> s -> m t
--   
mapMOf :: () => LensLike WrappedMonad m s t a b -> a -> m b -> s -> m t -- | Evaluate each action in the structure from left to right, and collect -- the results. -- --
--   >>> sequenceAOf both ([1,2],[3,4])
--   [(1,3),(1,4),(2,3),(2,4)]
--   
-- --
--   sequenceAsequenceAOf traversetraverse id
--   sequenceAOf l ≡ traverseOf l id ≡ l id
--   
-- --
--   sequenceAOf :: Functor f => Iso s t (f b) b       -> s -> f t
--   sequenceAOf :: Functor f => Lens s t (f b) b      -> s -> f t
--   sequenceAOf :: Applicative f => Traversal s t (f b) b -> s -> f t
--   
sequenceAOf :: () => LensLike f s t f b b -> s -> f t -- | A version of traverseOf with the arguments flipped, such that: -- --
--   >>> forOf each (1,2,3) print
--   1
--   2
--   3
--   ((),(),())
--   
-- -- This function is only provided for consistency, flip is -- strictly more general. -- --
--   forOfflip
--   forOfflip . traverseOf
--   
-- --
--   forforOf traverse
--   ifor l s ≡ for l s . Indexed
--   
-- --
--   forOf :: Functor f => Iso s t a b -> s -> (a -> f b) -> f t
--   forOf :: Functor f => Lens s t a b -> s -> (a -> f b) -> f t
--   forOf :: Applicative f => Traversal s t a b -> s -> (a -> f b) -> f t
--   
forOf :: () => LensLike f s t a b -> s -> a -> f b -> f t -- | Map each element of a structure targeted by a Lens or -- Traversal, evaluate these actions from left to right, and -- collect the results. -- -- This function is only provided for consistency, id is strictly -- more general. -- --
--   >>> traverseOf each print (1,2,3)
--   1
--   2
--   3
--   ((),(),())
--   
-- --
--   traverseOfid
--   itraverseOf l ≡ traverseOf l . Indexed
--   itraverseOf itraverseditraverse
--   
-- -- This yields the obvious law: -- --
--   traversetraverseOf traverse
--   
-- --
--   traverseOf :: Functor f     => Iso s t a b        -> (a -> f b) -> s -> f t
--   traverseOf :: Functor f     => Lens s t a b       -> (a -> f b) -> s -> f t
--   traverseOf :: Apply f       => Traversal1 s t a b -> (a -> f b) -> s -> f t
--   traverseOf :: Applicative f => Traversal s t a b  -> (a -> f b) -> s -> f t
--   
traverseOf :: () => LensLike f s t a b -> a -> f b -> s -> f t -- | When you see this as an argument to a function, it expects a -- Traversal. type ATraversal s t a b = LensLike Bazaar ((->) :: * -> * -> *) a b s t a b -- |
--   type ATraversal' = Simple ATraversal
--   
type ATraversal' s a = ATraversal s s a a -- | When you see this as an argument to a function, it expects a -- Traversal1. type ATraversal1 s t a b = LensLike Bazaar1 ((->) :: * -> * -> *) a b s t a b -- |
--   type ATraversal1' = Simple ATraversal1
--   
type ATraversal1' s a = ATraversal1 s s a a -- | When you see this as an argument to a function, it expects an -- IndexedTraversal. type AnIndexedTraversal i s t a b = Over Indexed i Bazaar Indexed i a b s t a b -- | When you see this as an argument to a function, it expects an -- IndexedTraversal1. type AnIndexedTraversal1 i s t a b = Over Indexed i Bazaar1 Indexed i a b s t a b -- |
--   type AnIndexedTraversal' = Simple (AnIndexedTraversal i)
--   
type AnIndexedTraversal' i s a = AnIndexedTraversal i s s a a -- |
--   type AnIndexedTraversal1' = Simple (AnIndexedTraversal1 i)
--   
type AnIndexedTraversal1' i s a = AnIndexedTraversal1 i s s a a -- | When you see this as an argument to a function, it expects -- -- type Traversing (p :: * -> * -> *) (f :: * -> *) s t a b = Over p BazaarT p f a b s t a b type Traversing1 (p :: * -> * -> *) (f :: * -> *) s t a b = Over p BazaarT1 p f a b s t a b -- |
--   type Traversing' f = Simple (Traversing f)
--   
type Traversing' (p :: * -> * -> *) (f :: * -> *) s a = Traversing p f s s a a type Traversing1' (p :: * -> * -> *) (f :: * -> *) s a = Traversing1 p f s s a a -- | Allows IndexedTraversal the value at the smallest index. class Ord k => TraverseMin k (m :: * -> *) | m -> k -- | IndexedTraversal of the element with the smallest index. traverseMin :: (TraverseMin k m, Indexable k p, Applicative f) => p v f v -> m v -> f m v -- | Allows IndexedTraversal of the value at the largest index. class Ord k => TraverseMax k (m :: * -> *) | m -> k -- | IndexedTraversal of the element at the largest index. traverseMax :: (TraverseMax k m, Indexable k p, Applicative f) => p v f v -> m v -> f m v -- | Fold a value using a specified Fold and Monoid -- operations. This is like foldMapBy where the Foldable -- instance can be manually specified. -- --
--   foldMapByOf foldedfoldMapBy
--   
-- --
--   foldMapByOf :: Getter s a     -> (r -> r -> r) -> r -> (a -> r) -> s -> r
--   foldMapByOf :: Fold s a       -> (r -> r -> r) -> r -> (a -> r) -> s -> r
--   foldMapByOf :: Traversal' s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r
--   foldMapByOf :: Lens' s a      -> (r -> r -> r) -> r -> (a -> r) -> s -> r
--   foldMapByOf :: Iso' s a       -> (r -> r -> r) -> r -> (a -> r) -> s -> r
--   
-- --
--   >>> foldMapByOf both (+) 0 length ("hello","world")
--   10
--   
foldMapByOf :: () => Fold s a -> r -> r -> r -> r -> a -> r -> s -> r -- | Fold a value using a specified Fold and Monoid -- operations. This is like foldBy where the Foldable -- instance can be manually specified. -- --
--   foldByOf foldedfoldBy
--   
-- --
--   foldByOf :: Getter s a     -> (a -> a -> a) -> a -> s -> a
--   foldByOf :: Fold s a       -> (a -> a -> a) -> a -> s -> a
--   foldByOf :: Lens' s a      -> (a -> a -> a) -> a -> s -> a
--   foldByOf :: Traversal' s a -> (a -> a -> a) -> a -> s -> a
--   foldByOf :: Iso' s a       -> (a -> a -> a) -> a -> s -> a
--   
-- --
--   >>> foldByOf both (++) [] ("hello","world")
--   "helloworld"
--   
foldByOf :: () => Fold s a -> a -> a -> a -> a -> s -> a -- | Obtain an IndexedFold by dropping elements from another -- IndexedFold, IndexedLens, IndexedGetter or -- IndexedTraversal while a predicate holds. -- --
--   idroppingWhile :: (i -> a -> Bool) -> IndexedFold i s a          -> IndexedFold i s a
--   idroppingWhile :: (i -> a -> Bool) -> IndexedTraversal' i s a    -> IndexedFold i s a -- see notes
--   idroppingWhile :: (i -> a -> Bool) -> IndexedLens' i s a         -> IndexedFold i s a -- see notes
--   idroppingWhile :: (i -> a -> Bool) -> IndexedGetter i s a        -> IndexedFold i s a
--   
-- -- Note: As with droppingWhile applying idroppingWhile to -- an IndexedLens or IndexedTraversal will still allow you -- to use it as a pseudo-IndexedTraversal, but if you change the -- value of the first target to one where the predicate returns -- True, then you will break the Traversal laws and -- Traversal fusion will no longer be sound. idroppingWhile :: (Indexable i p, Profunctor q, Applicative f) => i -> a -> Bool -> Optical Indexed i q Compose State Bool f s t a a -> Optical p q f s t a a -- | Obtain an IndexedFold by taking elements from another -- IndexedFold, IndexedLens, IndexedGetter or -- IndexedTraversal while a predicate holds. -- --
--   itakingWhile :: (i -> a -> Bool) -> IndexedFold i s a          -> IndexedFold i s a
--   itakingWhile :: (i -> a -> Bool) -> IndexedTraversal' i s a    -> IndexedFold i s a
--   itakingWhile :: (i -> a -> Bool) -> IndexedLens' i s a         -> IndexedFold i s a
--   itakingWhile :: (i -> a -> Bool) -> IndexedGetter i s a        -> IndexedFold i s a
--   
-- -- Note: Applying itakingWhile to an IndexedLens or -- IndexedTraversal will still allow you to use it as a -- pseudo-IndexedTraversal, but if you change the value of any -- target to one where the predicate returns False, then you will -- break the Traversal laws and Traversal fusion will no -- longer be sound. itakingWhile :: (Indexable i p, Profunctor q, Contravariant f, Applicative f) => i -> a -> Bool -> Optical' Indexed i q (Const Endo f s :: * -> *) s a -> Optical' p q f s a -- | Filter an IndexedFold or IndexedGetter, obtaining an -- IndexedFold. -- --
--   >>> [0,0,0,5,5,5]^..traversed.ifiltered (\i a -> i <= a)
--   [0,5,5,5]
--   
-- -- Compose with ifiltered to filter another IndexedLens, -- IndexedIso, IndexedGetter, IndexedFold (or -- IndexedTraversal) with access to both the value and the index. -- -- Note: As with filtered, this is not a legal -- IndexedTraversal, unless you are very careful not to invalidate -- the predicate on the target! ifiltered :: (Indexable i p, Applicative f) => i -> a -> Bool -> Optical' p Indexed i f a a -- | Retrieve the indices of the values targeted by a IndexedFold or -- IndexedTraversal which satisfy a predicate. -- --
--   findIndicesfindIndicesOf folded
--   
-- --
--   findIndicesOf :: IndexedFold i s a       -> (a -> Bool) -> s -> [i]
--   findIndicesOf :: IndexedTraversal' i s a -> (a -> Bool) -> s -> [i]
--   
findIndicesOf :: () => IndexedGetting i Endo [i] s a -> a -> Bool -> s -> [i] -- | Retrieve the index of the first value targeted by a IndexedFold -- or IndexedTraversal which satisfies a predicate. -- --
--   findIndexfindIndexOf folded
--   
-- --
--   findIndexOf :: IndexedFold i s a       -> (a -> Bool) -> s -> Maybe i
--   findIndexOf :: IndexedTraversal' i s a -> (a -> Bool) -> s -> Maybe i
--   
findIndexOf :: () => IndexedGetting i First i s a -> a -> Bool -> s -> Maybe i -- | Retrieve the indices of the values targeted by a IndexedFold or -- IndexedTraversal which are equal to a given value. -- --
--   elemIndiceselemIndicesOf folded
--   
-- --
--   elemIndicesOf :: Eq a => IndexedFold i s a       -> a -> s -> [i]
--   elemIndicesOf :: Eq a => IndexedTraversal' i s a -> a -> s -> [i]
--   
elemIndicesOf :: Eq a => IndexedGetting i Endo [i] s a -> a -> s -> [i] -- | Retrieve the index of the first value targeted by a IndexedFold -- or IndexedTraversal which is equal to a given value. -- --
--   elemIndexelemIndexOf folded
--   
-- --
--   elemIndexOf :: Eq a => IndexedFold i s a       -> a -> s -> Maybe i
--   elemIndexOf :: Eq a => IndexedTraversal' i s a -> a -> s -> Maybe i
--   
elemIndexOf :: Eq a => IndexedGetting i First i s a -> a -> s -> Maybe i -- | Perform an *UNSAFE* head (with index) of an IndexedFold -- or IndexedTraversal assuming that it is there. -- --
--   (^@?!) :: s -> IndexedGetter i s a     -> (i, a)
--   (^@?!) :: s -> IndexedFold i s a       -> (i, a)
--   (^@?!) :: s -> IndexedLens' i s a      -> (i, a)
--   (^@?!) :: s -> IndexedTraversal' i s a -> (i, a)
--   
(^@?!) :: HasCallStack => s -> IndexedGetting i Endo (i, a) s a -> (i, a) infixl 8 ^@?! -- | Perform a safe head (with index) of an IndexedFold or -- IndexedTraversal or retrieve Just the index and result -- from an IndexedGetter or IndexedLens. -- -- When using a IndexedTraversal as a partial IndexedLens, -- or an IndexedFold as a partial IndexedGetter this can be -- a convenient way to extract the optional value. -- --
--   (^@?) :: s -> IndexedGetter i s a     -> Maybe (i, a)
--   (^@?) :: s -> IndexedFold i s a       -> Maybe (i, a)
--   (^@?) :: s -> IndexedLens' i s a      -> Maybe (i, a)
--   (^@?) :: s -> IndexedTraversal' i s a -> Maybe (i, a)
--   
(^@?) :: () => s -> IndexedGetting i Endo Maybe (i, a) s a -> Maybe (i, a) infixl 8 ^@? -- | An infix version of itoListOf. (^@..) :: () => s -> IndexedGetting i Endo [(i, a)] s a -> [(i, a)] infixl 8 ^@.. -- | Extract the key-value pairs from a structure. -- -- When you don't need access to the indices in the result, then -- toListOf is more flexible in what it accepts. -- --
--   toListOf l ≡ map snd . itoListOf l
--   
-- --
--   itoListOf :: IndexedGetter i s a     -> s -> [(i,a)]
--   itoListOf :: IndexedFold i s a       -> s -> [(i,a)]
--   itoListOf :: IndexedLens' i s a      -> s -> [(i,a)]
--   itoListOf :: IndexedTraversal' i s a -> s -> [(i,a)]
--   
itoListOf :: () => IndexedGetting i Endo [(i, a)] s a -> s -> [(i, a)] -- | Monadic fold over the elements of a structure with an index, -- associating to the left. -- -- When you don't need access to the index then foldlMOf is more -- flexible in what it accepts. -- --
--   foldlMOf l ≡ ifoldlMOf l . const
--   
-- --
--   ifoldlMOf :: Monad m => IndexedGetter i s a     -> (i -> r -> a -> m r) -> r -> s -> m r
--   ifoldlMOf :: Monad m => IndexedFold i s a       -> (i -> r -> a -> m r) -> r -> s -> m r
--   ifoldlMOf :: Monad m => IndexedLens' i s a      -> (i -> r -> a -> m r) -> r -> s -> m r
--   ifoldlMOf :: Monad m => IndexedTraversal' i s a -> (i -> r -> a -> m r) -> r -> s -> m r
--   
ifoldlMOf :: Monad m => IndexedGetting i Endo r -> m r s a -> i -> r -> a -> m r -> r -> s -> m r -- | Monadic fold right over the elements of a structure with an index. -- -- When you don't need access to the index then foldrMOf is more -- flexible in what it accepts. -- --
--   foldrMOf l ≡ ifoldrMOf l . const
--   
-- --
--   ifoldrMOf :: Monad m => IndexedGetter i s a     -> (i -> a -> r -> m r) -> r -> s -> m r
--   ifoldrMOf :: Monad m => IndexedFold i s a       -> (i -> a -> r -> m r) -> r -> s -> m r
--   ifoldrMOf :: Monad m => IndexedLens' i s a      -> (i -> a -> r -> m r) -> r -> s -> m r
--   ifoldrMOf :: Monad m => IndexedTraversal' i s a -> (i -> a -> r -> m r) -> r -> s -> m r
--   
ifoldrMOf :: Monad m => IndexedGetting i Dual Endo r -> m r s a -> i -> a -> r -> m r -> r -> s -> m r -- | Fold over the elements of a structure with an index, associating to -- the left, but strictly. -- -- When you don't need access to the index then foldlOf' is more -- flexible in what it accepts. -- --
--   foldlOf' l ≡ ifoldlOf' l . const
--   
-- --
--   ifoldlOf' :: IndexedGetter i s a       -> (i -> r -> a -> r) -> r -> s -> r
--   ifoldlOf' :: IndexedFold i s a         -> (i -> r -> a -> r) -> r -> s -> r
--   ifoldlOf' :: IndexedLens' i s a        -> (i -> r -> a -> r) -> r -> s -> r
--   ifoldlOf' :: IndexedTraversal' i s a   -> (i -> r -> a -> r) -> r -> s -> r
--   
ifoldlOf' :: () => IndexedGetting i Endo r -> r s a -> i -> r -> a -> r -> r -> s -> r -- | Strictly fold right over the elements of a structure with an -- index. -- -- When you don't need access to the index then foldrOf' is more -- flexible in what it accepts. -- --
--   foldrOf' l ≡ ifoldrOf' l . const
--   
-- --
--   ifoldrOf' :: IndexedGetter i s a     -> (i -> a -> r -> r) -> r -> s -> r
--   ifoldrOf' :: IndexedFold i s a       -> (i -> a -> r -> r) -> r -> s -> r
--   ifoldrOf' :: IndexedLens' i s a      -> (i -> a -> r -> r) -> r -> s -> r
--   ifoldrOf' :: IndexedTraversal' i s a -> (i -> a -> r -> r) -> r -> s -> r
--   
ifoldrOf' :: () => IndexedGetting i Dual Endo r -> r s a -> i -> a -> r -> r -> r -> s -> r -- | The ifindMOf function takes an IndexedFold or -- IndexedTraversal, a monadic predicate that is also supplied the -- index, a structure and returns in the monad the left-most element of -- the structure matching the predicate, or Nothing if there is no -- such element. -- -- When you don't need access to the index then findMOf is more -- flexible in what it accepts. -- --
--   findMOf l ≡ ifindMOf l . const
--   
-- --
--   ifindMOf :: Monad m => IndexedGetter i s a     -> (i -> a -> m Bool) -> s -> m (Maybe a)
--   ifindMOf :: Monad m => IndexedFold i s a       -> (i -> a -> m Bool) -> s -> m (Maybe a)
--   ifindMOf :: Monad m => IndexedLens' i s a      -> (i -> a -> m Bool) -> s -> m (Maybe a)
--   ifindMOf :: Monad m => IndexedTraversal' i s a -> (i -> a -> m Bool) -> s -> m (Maybe a)
--   
ifindMOf :: Monad m => IndexedGetting i Endo m Maybe a s a -> i -> a -> m Bool -> s -> m Maybe a -- | The ifindOf function takes an IndexedFold or -- IndexedTraversal, a predicate that is also supplied the index, -- a structure and returns the left-most element of the structure -- matching the predicate, or Nothing if there is no such element. -- -- When you don't need access to the index then findOf is more -- flexible in what it accepts. -- --
--   findOf l ≡ ifindOf l . const
--   
-- --
--   ifindOf :: IndexedGetter i s a     -> (i -> a -> Bool) -> s -> Maybe a
--   ifindOf :: IndexedFold i s a       -> (i -> a -> Bool) -> s -> Maybe a
--   ifindOf :: IndexedLens' i s a      -> (i -> a -> Bool) -> s -> Maybe a
--   ifindOf :: IndexedTraversal' i s a -> (i -> a -> Bool) -> s -> Maybe a
--   
ifindOf :: () => IndexedGetting i Endo Maybe a s a -> i -> a -> Bool -> s -> Maybe a -- | Concatenate the results of a function of the elements of an -- IndexedFold or IndexedTraversal with access to the -- index. -- -- When you don't need access to the index then concatMapOf is -- more flexible in what it accepts. -- --
--   concatMapOf l ≡ iconcatMapOf l . const
--   iconcatMapOfifoldMapOf
--   
-- --
--   iconcatMapOf :: IndexedGetter i s a     -> (i -> a -> [r]) -> s -> [r]
--   iconcatMapOf :: IndexedFold i s a       -> (i -> a -> [r]) -> s -> [r]
--   iconcatMapOf :: IndexedLens' i s a      -> (i -> a -> [r]) -> s -> [r]
--   iconcatMapOf :: IndexedTraversal' i s a -> (i -> a -> [r]) -> s -> [r]
--   
iconcatMapOf :: () => IndexedGetting i [r] s a -> i -> a -> [r] -> s -> [r] -- | Run monadic actions for each target of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results (with the arguments flipped). -- --
--   iforMOf_flip . imapMOf_
--   
-- -- When you don't need access to the index then forMOf_ is more -- flexible in what it accepts. -- --
--   forMOf_ l a ≡ iforMOf l a . const
--   
-- --
--   iforMOf_ :: Monad m => IndexedGetter i s a     -> s -> (i -> a -> m r) -> m ()
--   iforMOf_ :: Monad m => IndexedFold i s a       -> s -> (i -> a -> m r) -> m ()
--   iforMOf_ :: Monad m => IndexedLens' i s a      -> s -> (i -> a -> m r) -> m ()
--   iforMOf_ :: Monad m => IndexedTraversal' i s a -> s -> (i -> a -> m r) -> m ()
--   
iforMOf_ :: Monad m => IndexedGetting i Sequenced r m s a -> s -> i -> a -> m r -> m () -- | Run monadic actions for each target of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results. -- -- When you don't need access to the index then mapMOf_ is more -- flexible in what it accepts. -- --
--   mapMOf_ l ≡ imapMOf l . const
--   
-- --
--   imapMOf_ :: Monad m => IndexedGetter i s a     -> (i -> a -> m r) -> s -> m ()
--   imapMOf_ :: Monad m => IndexedFold i s a       -> (i -> a -> m r) -> s -> m ()
--   imapMOf_ :: Monad m => IndexedLens' i s a      -> (i -> a -> m r) -> s -> m ()
--   imapMOf_ :: Monad m => IndexedTraversal' i s a -> (i -> a -> m r) -> s -> m ()
--   
imapMOf_ :: Monad m => IndexedGetting i Sequenced r m s a -> i -> a -> m r -> s -> m () -- | Traverse the targets of an IndexedFold or -- IndexedTraversal with access to the index, discarding the -- results (with the arguments flipped). -- --
--   iforOf_flip . itraverseOf_
--   
-- -- When you don't need access to the index then forOf_ is more -- flexible in what it accepts. -- --
--   forOf_ l a ≡ iforOf_ l a . const
--   
-- --
--   iforOf_ :: Functor f     => IndexedGetter i s a     -> s -> (i -> a -> f r) -> f ()
--   iforOf_ :: Applicative f => IndexedFold i s a       -> s -> (i -> a -> f r) -> f ()
--   iforOf_ :: Functor f     => IndexedLens' i s a      -> s -> (i -> a -> f r) -> f ()
--   iforOf_ :: Applicative f => IndexedTraversal' i s a -> s -> (i -> a -> f r) -> f ()
--   
iforOf_ :: Functor f => IndexedGetting i Traversed r f s a -> s -> i -> a -> f r -> f () -- | Traverse the targets of an IndexedFold or -- IndexedTraversal with access to the i, discarding the -- results. -- -- When you don't need access to the index then traverseOf_ is -- more flexible in what it accepts. -- --
--   traverseOf_ l ≡ itraverseOf l . const
--   
-- --
--   itraverseOf_ :: Functor f     => IndexedGetter i s a     -> (i -> a -> f r) -> s -> f ()
--   itraverseOf_ :: Applicative f => IndexedFold i s a       -> (i -> a -> f r) -> s -> f ()
--   itraverseOf_ :: Functor f     => IndexedLens' i s a      -> (i -> a -> f r) -> s -> f ()
--   itraverseOf_ :: Applicative f => IndexedTraversal' i s a -> (i -> a -> f r) -> s -> f ()
--   
itraverseOf_ :: Functor f => IndexedGetting i Traversed r f s a -> i -> a -> f r -> s -> f () -- | Return whether or not none of the elements viewed through an -- IndexedFold or IndexedTraversal satisfy a predicate, -- with access to the i. -- -- When you don't need access to the index then noneOf is more -- flexible in what it accepts. -- --
--   noneOf l ≡ inoneOf l . const
--   
-- --
--   inoneOf :: IndexedGetter i s a     -> (i -> a -> Bool) -> s -> Bool
--   inoneOf :: IndexedFold i s a       -> (i -> a -> Bool) -> s -> Bool
--   inoneOf :: IndexedLens' i s a      -> (i -> a -> Bool) -> s -> Bool
--   inoneOf :: IndexedTraversal' i s a -> (i -> a -> Bool) -> s -> Bool
--   
inoneOf :: () => IndexedGetting i Any s a -> i -> a -> Bool -> s -> Bool -- | Return whether or not all elements viewed through an -- IndexedFold or IndexedTraversal satisfy a predicate, -- with access to the i. -- -- When you don't need access to the index then allOf is more -- flexible in what it accepts. -- --
--   allOf l ≡ iallOf l . const
--   
-- --
--   iallOf :: IndexedGetter i s a     -> (i -> a -> Bool) -> s -> Bool
--   iallOf :: IndexedFold i s a       -> (i -> a -> Bool) -> s -> Bool
--   iallOf :: IndexedLens' i s a      -> (i -> a -> Bool) -> s -> Bool
--   iallOf :: IndexedTraversal' i s a -> (i -> a -> Bool) -> s -> Bool
--   
iallOf :: () => IndexedGetting i All s a -> i -> a -> Bool -> s -> Bool -- | Return whether or not any element viewed through an IndexedFold -- or IndexedTraversal satisfy a predicate, with access to the -- i. -- -- When you don't need access to the index then anyOf is more -- flexible in what it accepts. -- --
--   anyOf l ≡ ianyOf l . const
--   
-- --
--   ianyOf :: IndexedGetter i s a     -> (i -> a -> Bool) -> s -> Bool
--   ianyOf :: IndexedFold i s a       -> (i -> a -> Bool) -> s -> Bool
--   ianyOf :: IndexedLens' i s a      -> (i -> a -> Bool) -> s -> Bool
--   ianyOf :: IndexedTraversal' i s a -> (i -> a -> Bool) -> s -> Bool
--   
ianyOf :: () => IndexedGetting i Any s a -> i -> a -> Bool -> s -> Bool -- | Left-associative fold of the parts of a structure that are viewed -- through an IndexedFold or IndexedTraversal with access -- to the i. -- -- When you don't need access to the index then foldlOf is more -- flexible in what it accepts. -- --
--   foldlOf l ≡ ifoldlOf l . const
--   
-- --
--   ifoldlOf :: IndexedGetter i s a     -> (i -> r -> a -> r) -> r -> s -> r
--   ifoldlOf :: IndexedFold i s a       -> (i -> r -> a -> r) -> r -> s -> r
--   ifoldlOf :: IndexedLens' i s a      -> (i -> r -> a -> r) -> r -> s -> r
--   ifoldlOf :: IndexedTraversal' i s a -> (i -> r -> a -> r) -> r -> s -> r
--   
ifoldlOf :: () => IndexedGetting i Dual Endo r s a -> i -> r -> a -> r -> r -> s -> r -- | Right-associative fold of parts of a structure that are viewed through -- an IndexedFold or IndexedTraversal with access to the -- i. -- -- When you don't need access to the index then foldrOf is more -- flexible in what it accepts. -- --
--   foldrOf l ≡ ifoldrOf l . const
--   
-- --
--   ifoldrOf :: IndexedGetter i s a     -> (i -> a -> r -> r) -> r -> s -> r
--   ifoldrOf :: IndexedFold i s a       -> (i -> a -> r -> r) -> r -> s -> r
--   ifoldrOf :: IndexedLens' i s a      -> (i -> a -> r -> r) -> r -> s -> r
--   ifoldrOf :: IndexedTraversal' i s a -> (i -> a -> r -> r) -> r -> s -> r
--   
ifoldrOf :: () => IndexedGetting i Endo r s a -> i -> a -> r -> r -> r -> s -> r -- | Fold an IndexedFold or IndexedTraversal by mapping -- indices and values to an arbitrary Monoid with access to the -- i. -- -- When you don't need access to the index then foldMapOf is more -- flexible in what it accepts. -- --
--   foldMapOf l ≡ ifoldMapOf l . const
--   
-- --
--   ifoldMapOf ::             IndexedGetter i s a     -> (i -> a -> m) -> s -> m
--   ifoldMapOf :: Monoid m => IndexedFold i s a       -> (i -> a -> m) -> s -> m
--   ifoldMapOf ::             IndexedLens' i s a      -> (i -> a -> m) -> s -> m
--   ifoldMapOf :: Monoid m => IndexedTraversal' i s a -> (i -> a -> m) -> s -> m
--   
ifoldMapOf :: () => IndexedGetting i m s a -> i -> a -> m -> s -> m -- | This allows you to traverse the elements of a pretty much any -- LensLike construction in the opposite order. -- -- This will preserve indexes on Indexed types and will give you -- the elements of a (finite) Fold or Traversal in the -- opposite order. -- -- This has no practical impact on a Getter, Setter, -- Lens or Iso. -- -- NB: To write back through an Iso, you want to use -- from. Similarly, to write back through an Prism, you -- want to use re. backwards :: (Profunctor p, Profunctor q) => Optical p q Backwards f s t a b -> Optical p q f s t a b -- | Retrieve a function of the first index and value targeted by an -- IndexedFold or IndexedTraversal (or a function of -- Just the index and result from an IndexedGetter or -- IndexedLens) into the current state. -- --
--   ipreuses = uses . ipre
--   
-- --
--   ipreuses :: MonadState s m => IndexedGetter i s a     -> (i -> a -> r) -> m (Maybe r)
--   ipreuses :: MonadState s m => IndexedFold i s a       -> (i -> a -> r) -> m (Maybe r)
--   ipreuses :: MonadState s m => IndexedLens' i s a      -> (i -> a -> r) -> m (Maybe r)
--   ipreuses :: MonadState s m => IndexedTraversal' i s a -> (i -> a -> r) -> m (Maybe r)
--   
ipreuses :: MonadState s m => IndexedGetting i First r s a -> i -> a -> r -> m Maybe r -- | Retrieve a function of the first value targeted by a Fold or -- Traversal (or Just the result from a Getter or -- Lens) into the current state. -- --
--   preuses = uses . pre
--   
-- --
--   preuses :: MonadState s m => Getter s a     -> (a -> r) -> m (Maybe r)
--   preuses :: MonadState s m => Fold s a       -> (a -> r) -> m (Maybe r)
--   preuses :: MonadState s m => Lens' s a      -> (a -> r) -> m (Maybe r)
--   preuses :: MonadState s m => Iso' s a       -> (a -> r) -> m (Maybe r)
--   preuses :: MonadState s m => Traversal' s a -> (a -> r) -> m (Maybe r)
--   
preuses :: MonadState s m => Getting First r s a -> a -> r -> m Maybe r -- | Retrieve the first index and value targeted by an IndexedFold -- or IndexedTraversal (or Just the index and result from -- an IndexedGetter or IndexedLens) into the current state. -- --
--   ipreuse = use . ipre
--   
-- --
--   ipreuse :: MonadState s m => IndexedGetter i s a     -> m (Maybe (i, a))
--   ipreuse :: MonadState s m => IndexedFold i s a       -> m (Maybe (i, a))
--   ipreuse :: MonadState s m => IndexedLens' i s a      -> m (Maybe (i, a))
--   ipreuse :: MonadState s m => IndexedTraversal' i s a -> m (Maybe (i, a))
--   
ipreuse :: MonadState s m => IndexedGetting i First (i, a) s a -> m Maybe (i, a) -- | Retrieve the first value targeted by a Fold or Traversal -- (or Just the result from a Getter or Lens) into -- the current state. -- --
--   preuse = use . pre
--   
-- --
--   preuse :: MonadState s m => Getter s a     -> m (Maybe a)
--   preuse :: MonadState s m => Fold s a       -> m (Maybe a)
--   preuse :: MonadState s m => Lens' s a      -> m (Maybe a)
--   preuse :: MonadState s m => Iso' s a       -> m (Maybe a)
--   preuse :: MonadState s m => Traversal' s a -> m (Maybe a)
--   
preuse :: MonadState s m => Getting First a s a -> m Maybe a -- | Retrieve a function of the first index and value targeted by an -- IndexedFold or IndexedTraversal (or Just the -- result from an IndexedGetter or IndexedLens). See also -- (^@?). -- --
--   ipreviews = views . ipre
--   
-- -- This is usually applied in the Reader Monad (->) -- s. -- --
--   ipreviews :: IndexedGetter i s a     -> (i -> a -> r) -> s -> Maybe r
--   ipreviews :: IndexedFold i s a       -> (i -> a -> r) -> s -> Maybe r
--   ipreviews :: IndexedLens' i s a      -> (i -> a -> r) -> s -> Maybe r
--   ipreviews :: IndexedTraversal' i s a -> (i -> a -> r) -> s -> Maybe r
--   
-- -- However, it may be useful to think of its full generality when working -- with a Monad transformer stack: -- --
--   ipreviews :: MonadReader s m => IndexedGetter i s a     -> (i -> a -> r) -> m (Maybe r)
--   ipreviews :: MonadReader s m => IndexedFold i s a       -> (i -> a -> r) -> m (Maybe r)
--   ipreviews :: MonadReader s m => IndexedLens' i s a      -> (i -> a -> r) -> m (Maybe r)
--   ipreviews :: MonadReader s m => IndexedTraversal' i s a -> (i -> a -> r) -> m (Maybe r)
--   
ipreviews :: MonadReader s m => IndexedGetting i First r s a -> i -> a -> r -> m Maybe r -- | Retrieve a function of the first value targeted by a Fold or -- Traversal (or Just the result from a Getter or -- Lens). -- -- This is usually applied in the Reader Monad (->) -- s. previews :: MonadReader s m => Getting First r s a -> a -> r -> m Maybe r -- | Retrieve the first index and value targeted by a Fold or -- Traversal (or Just the result from a Getter or -- Lens). See also (^@?). -- --
--   ipreview = view . ipre
--   
-- -- This is usually applied in the Reader Monad (->) -- s. -- --
--   ipreview :: IndexedGetter i s a     -> s -> Maybe (i, a)
--   ipreview :: IndexedFold i s a       -> s -> Maybe (i, a)
--   ipreview :: IndexedLens' i s a      -> s -> Maybe (i, a)
--   ipreview :: IndexedTraversal' i s a -> s -> Maybe (i, a)
--   
-- -- However, it may be useful to think of its full generality when working -- with a Monad transformer stack: -- --
--   ipreview :: MonadReader s m => IndexedGetter s a     -> m (Maybe (i, a))
--   ipreview :: MonadReader s m => IndexedFold s a       -> m (Maybe (i, a))
--   ipreview :: MonadReader s m => IndexedLens' s a      -> m (Maybe (i, a))
--   ipreview :: MonadReader s m => IndexedTraversal' s a -> m (Maybe (i, a))
--   
ipreview :: MonadReader s m => IndexedGetting i First (i, a) s a -> m Maybe (i, a) -- | Retrieve the first value targeted by a Fold or Traversal -- (or Just the result from a Getter or Lens). See -- also (^?). -- --
--   listToMaybe . toListpreview folded
--   
-- -- This is usually applied in the Reader Monad (->) -- s. -- --
--   preview = view . pre
--   
-- --
--   preview :: Getter s a     -> s -> Maybe a
--   preview :: Fold s a       -> s -> Maybe a
--   preview :: Lens' s a      -> s -> Maybe a
--   preview :: Iso' s a       -> s -> Maybe a
--   preview :: Traversal' s a -> s -> Maybe a
--   
-- -- However, it may be useful to think of its full generality when working -- with a Monad transformer stack: -- --
--   preview :: MonadReader s m => Getter s a     -> m (Maybe a)
--   preview :: MonadReader s m => Fold s a       -> m (Maybe a)
--   preview :: MonadReader s m => Lens' s a      -> m (Maybe a)
--   preview :: MonadReader s m => Iso' s a       -> m (Maybe a)
--   preview :: MonadReader s m => Traversal' s a -> m (Maybe a)
--   
preview :: MonadReader s m => Getting First a s a -> m Maybe a -- | This converts an IndexedFold to an IndexPreservingGetter -- that returns the first index and element, if they exist, as a -- Maybe. -- --
--   ipre :: IndexedGetter i s a     -> IndexPreservingGetter s (Maybe (i, a))
--   ipre :: IndexedFold i s a       -> IndexPreservingGetter s (Maybe (i, a))
--   ipre :: IndexedTraversal' i s a -> IndexPreservingGetter s (Maybe (i, a))
--   ipre :: IndexedLens' i s a      -> IndexPreservingGetter s (Maybe (i, a))
--   
ipre :: () => IndexedGetting i First (i, a) s a -> IndexPreservingGetter s Maybe (i, a) -- | This converts a Fold to a IndexPreservingGetter that -- returns the first element, if it exists, as a Maybe. -- --
--   pre :: Getter s a     -> IndexPreservingGetter s (Maybe a)
--   pre :: Fold s a       -> IndexPreservingGetter s (Maybe a)
--   pre :: Traversal' s a -> IndexPreservingGetter s (Maybe a)
--   pre :: Lens' s a      -> IndexPreservingGetter s (Maybe a)
--   pre :: Iso' s a       -> IndexPreservingGetter s (Maybe a)
--   pre :: Prism' s a     -> IndexPreservingGetter s (Maybe a)
--   
pre :: () => Getting First a s a -> IndexPreservingGetter s Maybe a -- | Check to see if this Fold or Traversal has no matches. -- --
--   >>> hasn't _Left (Right 12)
--   True
--   
-- --
--   >>> hasn't _Left (Left 12)
--   False
--   
hasn't :: () => Getting All s a -> s -> Bool -- | Check to see if this Fold or Traversal matches 1 or more -- entries. -- --
--   >>> has (element 0) []
--   False
--   
-- --
--   >>> has _Left (Left 12)
--   True
--   
-- --
--   >>> has _Right (Left 12)
--   False
--   
-- -- This will always return True for a Lens or -- Getter. -- --
--   >>> has _1 ("hello","world")
--   True
--   
-- --
--   has :: Getter s a     -> s -> Bool
--   has :: Fold s a       -> s -> Bool
--   has :: Iso' s a       -> s -> Bool
--   has :: Lens' s a      -> s -> Bool
--   has :: Traversal' s a -> s -> Bool
--   
has :: () => Getting Any s a -> s -> Bool -- | Monadic fold over the elements of a structure, associating to the -- left, i.e. from left to right. -- --
--   foldlMfoldlMOf folded
--   
-- --
--   foldlMOf :: Monad m => Getter s a     -> (r -> a -> m r) -> r -> s -> m r
--   foldlMOf :: Monad m => Fold s a       -> (r -> a -> m r) -> r -> s -> m r
--   foldlMOf :: Monad m => Iso' s a       -> (r -> a -> m r) -> r -> s -> m r
--   foldlMOf :: Monad m => Lens' s a      -> (r -> a -> m r) -> r -> s -> m r
--   foldlMOf :: Monad m => Traversal' s a -> (r -> a -> m r) -> r -> s -> m r
--   
foldlMOf :: Monad m => Getting Endo r -> m r s a -> r -> a -> m r -> r -> s -> m r -- | Monadic fold over the elements of a structure, associating to the -- right, i.e. from right to left. -- --
--   foldrMfoldrMOf folded
--   
-- --
--   foldrMOf :: Monad m => Getter s a     -> (a -> r -> m r) -> r -> s -> m r
--   foldrMOf :: Monad m => Fold s a       -> (a -> r -> m r) -> r -> s -> m r
--   foldrMOf :: Monad m => Iso' s a       -> (a -> r -> m r) -> r -> s -> m r
--   foldrMOf :: Monad m => Lens' s a      -> (a -> r -> m r) -> r -> s -> m r
--   foldrMOf :: Monad m => Traversal' s a -> (a -> r -> m r) -> r -> s -> m r
--   
foldrMOf :: Monad m => Getting Dual Endo r -> m r s a -> a -> r -> m r -> r -> s -> m r -- | A variant of foldlOf' that has no base case and thus may only -- be applied to folds and structures such that the fold views at least -- one element of the structure. -- --
--   foldl1Of' l f ≡ foldl1' f . toListOf l
--   
-- --
--   foldl1Of' :: Getter s a     -> (a -> a -> a) -> s -> a
--   foldl1Of' :: Fold s a       -> (a -> a -> a) -> s -> a
--   foldl1Of' :: Iso' s a       -> (a -> a -> a) -> s -> a
--   foldl1Of' :: Lens' s a      -> (a -> a -> a) -> s -> a
--   foldl1Of' :: Traversal' s a -> (a -> a -> a) -> s -> a
--   
foldl1Of' :: HasCallStack => Getting Endo Endo Maybe a s a -> a -> a -> a -> s -> a -- | A variant of foldrOf' that has no base case and thus may only -- be applied to folds and structures such that the fold views at least -- one element of the structure. -- --
--   foldr1Of l f ≡ foldr1 f . toListOf l
--   
-- --
--   foldr1Of' :: Getter s a     -> (a -> a -> a) -> s -> a
--   foldr1Of' :: Fold s a       -> (a -> a -> a) -> s -> a
--   foldr1Of' :: Iso' s a       -> (a -> a -> a) -> s -> a
--   foldr1Of' :: Lens' s a      -> (a -> a -> a) -> s -> a
--   foldr1Of' :: Traversal' s a -> (a -> a -> a) -> s -> a
--   
foldr1Of' :: HasCallStack => Getting Dual Endo Endo Maybe a s a -> a -> a -> a -> s -> a -- | Fold over the elements of a structure, associating to the left, but -- strictly. -- --
--   foldl'foldlOf' folded
--   
-- --
--   foldlOf' :: Getter s a     -> (r -> a -> r) -> r -> s -> r
--   foldlOf' :: Fold s a       -> (r -> a -> r) -> r -> s -> r
--   foldlOf' :: Iso' s a       -> (r -> a -> r) -> r -> s -> r
--   foldlOf' :: Lens' s a      -> (r -> a -> r) -> r -> s -> r
--   foldlOf' :: Traversal' s a -> (r -> a -> r) -> r -> s -> r
--   
foldlOf' :: () => Getting Endo Endo r s a -> r -> a -> r -> r -> s -> r -- | Strictly fold right over the elements of a structure. -- --
--   foldr'foldrOf' folded
--   
-- --
--   foldrOf' :: Getter s a     -> (a -> r -> r) -> r -> s -> r
--   foldrOf' :: Fold s a       -> (a -> r -> r) -> r -> s -> r
--   foldrOf' :: Iso' s a       -> (a -> r -> r) -> r -> s -> r
--   foldrOf' :: Lens' s a      -> (a -> r -> r) -> r -> s -> r
--   foldrOf' :: Traversal' s a -> (a -> r -> r) -> r -> s -> r
--   
foldrOf' :: () => Getting Dual Endo Endo r s a -> a -> r -> r -> r -> s -> r -- | A variant of foldlOf that has no base case and thus may only be -- applied to lenses and structures such that the Lens views at -- least one element of the structure. -- --
--   >>> foldl1Of each (+) (1,2,3,4)
--   10
--   
-- --
--   foldl1Of l f ≡ foldl1 f . toListOf l
--   foldl1foldl1Of folded
--   
-- --
--   foldl1Of :: Getter s a     -> (a -> a -> a) -> s -> a
--   foldl1Of :: Fold s a       -> (a -> a -> a) -> s -> a
--   foldl1Of :: Iso' s a       -> (a -> a -> a) -> s -> a
--   foldl1Of :: Lens' s a      -> (a -> a -> a) -> s -> a
--   foldl1Of :: Traversal' s a -> (a -> a -> a) -> s -> a
--   
foldl1Of :: HasCallStack => Getting Dual Endo Maybe a s a -> a -> a -> a -> s -> a -- | A variant of foldrOf that has no base case and thus may only be -- applied to lenses and structures such that the Lens views at -- least one element of the structure. -- --
--   >>> foldr1Of each (+) (1,2,3,4)
--   10
--   
-- --
--   foldr1Of l f ≡ foldr1 f . toListOf l
--   foldr1foldr1Of folded
--   
-- --
--   foldr1Of :: Getter s a     -> (a -> a -> a) -> s -> a
--   foldr1Of :: Fold s a       -> (a -> a -> a) -> s -> a
--   foldr1Of :: Iso' s a       -> (a -> a -> a) -> s -> a
--   foldr1Of :: Lens' s a      -> (a -> a -> a) -> s -> a
--   foldr1Of :: Traversal' s a -> (a -> a -> a) -> s -> a
--   
foldr1Of :: HasCallStack => Getting Endo Maybe a s a -> a -> a -> a -> s -> a -- | The lookupOf function takes a Fold (or Getter, -- Traversal, Lens, Iso, etc.), a key, and a -- structure containing key/value pairs. It returns the first value -- corresponding to the given key. This function generalizes -- lookup to work on an arbitrary Fold instead of lists. -- --
--   >>> lookupOf folded 4 [(2, 'a'), (4, 'b'), (4, 'c')]
--   Just 'b'
--   
-- --
--   >>> lookupOf each 2 [(2, 'a'), (4, 'b'), (4, 'c')]
--   Just 'a'
--   
-- --
--   lookupOf :: Eq k => Fold s (k,v) -> k -> s -> Maybe v
--   
lookupOf :: Eq k => Getting Endo Maybe v s (k, v) -> k -> s -> Maybe v -- | The findMOf function takes a Lens (or Getter, -- Iso, Fold, or Traversal), a monadic predicate and -- a structure and returns in the monad the leftmost element of the -- structure matching the predicate, or Nothing if there is no -- such element. -- --
--   >>> findMOf each ( \x -> print ("Checking " ++ show x) >> return (even x)) (1,3,4,6)
--   "Checking 1"
--   "Checking 3"
--   "Checking 4"
--   Just 4
--   
-- --
--   >>> findMOf each ( \x -> print ("Checking " ++ show x) >> return (even x)) (1,3,5,7)
--   "Checking 1"
--   "Checking 3"
--   "Checking 5"
--   "Checking 7"
--   Nothing
--   
-- --
--   findMOf :: (Monad m, Getter s a)     -> (a -> m Bool) -> s -> m (Maybe a)
--   findMOf :: (Monad m, Fold s a)       -> (a -> m Bool) -> s -> m (Maybe a)
--   findMOf :: (Monad m, Iso' s a)       -> (a -> m Bool) -> s -> m (Maybe a)
--   findMOf :: (Monad m, Lens' s a)      -> (a -> m Bool) -> s -> m (Maybe a)
--   findMOf :: (Monad m, Traversal' s a) -> (a -> m Bool) -> s -> m (Maybe a)
--   
-- --
--   findMOf folded :: (Monad m, Foldable f) => (a -> m Bool) -> f a -> m (Maybe a)
--   ifindMOf l ≡ findMOf l . Indexed
--   
-- -- A simpler version that didn't permit indexing, would be: -- --
--   findMOf :: Monad m => Getting (Endo (m (Maybe a))) s a -> (a -> m Bool) -> s -> m (Maybe a)
--   findMOf l p = foldrOf l (a y -> p a >>= x -> if x then return (Just a) else y) $ return Nothing
--   
findMOf :: Monad m => Getting Endo m Maybe a s a -> a -> m Bool -> s -> m Maybe a -- | The findOf function takes a Lens (or Getter, -- Iso, Fold, or Traversal), a predicate and a -- structure and returns the leftmost element of the structure matching -- the predicate, or Nothing if there is no such element. -- --
--   >>> findOf each even (1,3,4,6)
--   Just 4
--   
-- --
--   >>> findOf folded even [1,3,5,7]
--   Nothing
--   
-- --
--   findOf :: Getter s a     -> (a -> Bool) -> s -> Maybe a
--   findOf :: Fold s a       -> (a -> Bool) -> s -> Maybe a
--   findOf :: Iso' s a       -> (a -> Bool) -> s -> Maybe a
--   findOf :: Lens' s a      -> (a -> Bool) -> s -> Maybe a
--   findOf :: Traversal' s a -> (a -> Bool) -> s -> Maybe a
--   
-- --
--   findfindOf folded
--   ifindOf l ≡ findOf l . Indexed
--   
-- -- A simpler version that didn't permit indexing, would be: -- --
--   findOf :: Getting (Endo (Maybe a)) s a -> (a -> Bool) -> s -> Maybe a
--   findOf l p = foldrOf l (a y -> if p a then Just a else y) Nothing
--   
findOf :: () => Getting Endo Maybe a s a -> a -> Bool -> s -> Maybe a -- | Obtain the minimum element (if any) targeted by a Fold, -- Traversal, Lens, Iso or Getter according -- to a user supplied Ordering. -- -- In the interest of efficiency, This operation has semantics more -- strict than strictly necessary. -- --
--   >>> minimumByOf traverse (compare `on` length) ["mustard","relish","ham"]
--   Just "ham"
--   
-- --
--   minimumBy cmp ≡ fromMaybe (error "empty") . minimumByOf folded cmp
--   
-- --
--   minimumByOf :: Getter s a     -> (a -> a -> Ordering) -> s -> Maybe a
--   minimumByOf :: Fold s a       -> (a -> a -> Ordering) -> s -> Maybe a
--   minimumByOf :: Iso' s a       -> (a -> a -> Ordering) -> s -> Maybe a
--   minimumByOf :: Lens' s a      -> (a -> a -> Ordering) -> s -> Maybe a
--   minimumByOf :: Traversal' s a -> (a -> a -> Ordering) -> s -> Maybe a
--   
minimumByOf :: () => Getting Endo Endo Maybe a s a -> a -> a -> Ordering -> s -> Maybe a -- | Obtain the maximum element (if any) targeted by a Fold, -- Traversal, Lens, Iso, or Getter according -- to a user supplied Ordering. -- --
--   >>> maximumByOf traverse (compare `on` length) ["mustard","relish","ham"]
--   Just "mustard"
--   
-- -- In the interest of efficiency, This operation has semantics more -- strict than strictly necessary. -- --
--   maximumBy cmp ≡ fromMaybe (error "empty") . maximumByOf folded cmp
--   
-- --
--   maximumByOf :: Getter s a     -> (a -> a -> Ordering) -> s -> Maybe a
--   maximumByOf :: Fold s a       -> (a -> a -> Ordering) -> s -> Maybe a
--   maximumByOf :: Iso' s a       -> (a -> a -> Ordering) -> s -> Maybe a
--   maximumByOf :: Lens' s a      -> (a -> a -> Ordering) -> s -> Maybe a
--   maximumByOf :: Traversal' s a -> (a -> a -> Ordering) -> s -> Maybe a
--   
maximumByOf :: () => Getting Endo Endo Maybe a s a -> a -> a -> Ordering -> s -> Maybe a -- | Obtain the minimum element targeted by a Fold1 or -- Traversal1. -- --
--   >>> minimum1Of traverse1 (1 :| [2..10])
--   1
--   
-- --
--   minimum1Of :: Ord a => Getter s a      -> s -> a
--   minimum1Of :: Ord a => Fold1 s a       -> s -> a
--   minimum1Of :: Ord a => Iso' s a        -> s -> a
--   minimum1Of :: Ord a => Lens' s a       -> s -> a
--   minimum1Of :: Ord a => Traversal1' s a -> s -> a
--   
minimum1Of :: Ord a => Getting Min a s a -> s -> a -- | Obtain the minimum element (if any) targeted by a Fold or -- Traversal safely. -- -- Note: minimumOf on a valid Iso, Lens or -- Getter will always return Just a value. -- --
--   >>> minimumOf traverse [1..10]
--   Just 1
--   
-- --
--   >>> minimumOf traverse []
--   Nothing
--   
-- --
--   >>> minimumOf (folded.filtered even) [1,4,3,6,7,9,2]
--   Just 2
--   
-- --
--   minimumfromMaybe (error "empty") . minimumOf folded
--   
-- -- In the interest of efficiency, This operation has semantics more -- strict than strictly necessary. rmap getMin -- (foldMapOf l Min) has lazier semantics but could -- leak memory. -- --
--   minimumOf :: Ord a => Getter s a     -> s -> Maybe a
--   minimumOf :: Ord a => Fold s a       -> s -> Maybe a
--   minimumOf :: Ord a => Iso' s a       -> s -> Maybe a
--   minimumOf :: Ord a => Lens' s a      -> s -> Maybe a
--   minimumOf :: Ord a => Traversal' s a -> s -> Maybe a
--   
minimumOf :: Ord a => Getting Endo Endo Maybe a s a -> s -> Maybe a -- | Obtain the maximum element targeted by a Fold1 or -- Traversal1. -- --
--   >>> maximum1Of traverse1 (1 :| [2..10])
--   10
--   
-- --
--   maximum1Of :: Ord a => Getter s a      -> s -> a
--   maximum1Of :: Ord a => Fold1 s a       -> s -> a
--   maximum1Of :: Ord a => Iso' s a        -> s -> a
--   maximum1Of :: Ord a => Lens' s a       -> s -> a
--   maximum1Of :: Ord a => Traversal1' s a -> s -> a
--   
maximum1Of :: Ord a => Getting Max a s a -> s -> a -- | Obtain the maximum element (if any) targeted by a Fold or -- Traversal safely. -- -- Note: maximumOf on a valid Iso, Lens or -- Getter will always return Just a value. -- --
--   >>> maximumOf traverse [1..10]
--   Just 10
--   
-- --
--   >>> maximumOf traverse []
--   Nothing
--   
-- --
--   >>> maximumOf (folded.filtered even) [1,4,3,6,7,9,2]
--   Just 6
--   
-- --
--   maximumfromMaybe (error "empty") . maximumOf folded
--   
-- -- In the interest of efficiency, This operation has semantics more -- strict than strictly necessary. rmap getMax -- (foldMapOf l Max) has lazier semantics but could -- leak memory. -- --
--   maximumOf :: Ord a => Getter s a     -> s -> Maybe a
--   maximumOf :: Ord a => Fold s a       -> s -> Maybe a
--   maximumOf :: Ord a => Iso' s a       -> s -> Maybe a
--   maximumOf :: Ord a => Lens' s a      -> s -> Maybe a
--   maximumOf :: Ord a => Traversal' s a -> s -> Maybe a
--   
maximumOf :: Ord a => Getting Endo Endo Maybe a s a -> s -> Maybe a -- | Returns True if this Fold or Traversal has any -- targets in the given container. -- -- A more "conversational" alias for this combinator is has. -- -- Note: notNullOf on a valid Iso, Lens or -- Getter should always return True. -- --
--   not . nullnotNullOf folded
--   
-- -- This may be rather inefficient compared to the not . -- null check of many containers. -- --
--   >>> notNullOf _1 (1,2)
--   True
--   
-- --
--   >>> notNullOf traverse [1..10]
--   True
--   
-- --
--   >>> notNullOf folded []
--   False
--   
-- --
--   >>> notNullOf (element 20) [1..10]
--   False
--   
-- --
--   notNullOf (folded . _1 . folded) :: (Foldable f, Foldable g) => f (g a, b) -> Bool
--   
-- --
--   notNullOf :: Getter s a     -> s -> Bool
--   notNullOf :: Fold s a       -> s -> Bool
--   notNullOf :: Iso' s a       -> s -> Bool
--   notNullOf :: Lens' s a      -> s -> Bool
--   notNullOf :: Traversal' s a -> s -> Bool
--   
notNullOf :: () => Getting Any s a -> s -> Bool -- | 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. -- --
--   nullnullOf folded
--   
-- -- This may be rather inefficient compared to the null check of -- many containers. -- --
--   >>> nullOf _1 (1,2)
--   False
--   
-- --
--   >>> nullOf ignored ()
--   True
--   
-- --
--   >>> nullOf traverse []
--   True
--   
-- --
--   >>> nullOf (element 20) [1..10]
--   True
--   
-- --
--   nullOf (folded . _1 . folded) :: (Foldable f, Foldable g) => f (g a, b) -> Bool
--   
-- --
--   nullOf :: Getter s a     -> s -> Bool
--   nullOf :: Fold s a       -> s -> Bool
--   nullOf :: Iso' s a       -> s -> Bool
--   nullOf :: Lens' s a      -> s -> Bool
--   nullOf :: Traversal' s a -> s -> Bool
--   
nullOf :: () => Getting All s a -> s -> Bool -- | Retrieve the Last entry of a Fold1 or Traversal1 -- or retrieve the result from a Getter or Lens.o -- --
--   >>> last1Of traverse1 (1 :| [2..10])
--   10
--   
-- --
--   >>> last1Of both1 (1,2)
--   2
--   
-- --
--   last1Of :: Getter s a      -> s -> Maybe a
--   last1Of :: Fold1 s a       -> s -> Maybe a
--   last1Of :: Lens' s a       -> s -> Maybe a
--   last1Of :: Iso' s a        -> s -> Maybe a
--   last1Of :: Traversal1' s a -> s -> Maybe a
--   
last1Of :: () => Getting Last a s a -> s -> a -- | Retrieve the Last entry of a Fold or Traversal or -- retrieve Just the result from a Getter or Lens. -- -- The answer is computed in a manner that leaks space less than -- ala Last . foldMapOf and gives -- you back access to the outermost Just constructor more quickly, -- but may have worse constant factors. -- --
--   >>> lastOf traverse [1..10]
--   Just 10
--   
-- --
--   >>> lastOf both (1,2)
--   Just 2
--   
-- --
--   >>> lastOf ignored ()
--   Nothing
--   
-- --
--   lastOf :: Getter s a     -> s -> Maybe a
--   lastOf :: Fold s a       -> s -> Maybe a
--   lastOf :: Lens' s a      -> s -> Maybe a
--   lastOf :: Iso' s a       -> s -> Maybe a
--   lastOf :: Traversal' s a -> s -> Maybe a
--   
lastOf :: () => Getting Rightmost a s a -> s -> Maybe a -- | Retrieve the First entry of a Fold1 or Traversal1 -- or the result from a Getter or Lens. -- --
--   >>> first1Of traverse1 (1 :| [2..10])
--   1
--   
-- --
--   >>> first1Of both1 (1,2)
--   1
--   
-- -- Note: this is different from ^.. -- --
--   >>> first1Of traverse1 ([1,2] :| [[3,4],[5,6]])
--   [1,2]
--   
-- --
--   >>> ([1,2] :| [[3,4],[5,6]]) ^. traverse1
--   [1,2,3,4,5,6]
--   
-- --
--   first1Of :: Getter s a      -> s -> a
--   first1Of :: Fold1 s a       -> s -> a
--   first1Of :: Lens' s a       -> s -> a
--   first1Of :: Iso' s a        -> s -> a
--   first1Of :: Traversal1' s a -> s -> a
--   
first1Of :: () => Getting First a s a -> s -> a -- | Retrieve the First entry of a Fold or Traversal -- or retrieve Just the result from a Getter or -- Lens. -- -- The answer is computed in a manner that leaks space less than -- ala First . foldMapOf and gives -- you back access to the outermost Just constructor more quickly, -- but may have worse constant factors. -- -- Note: this could been named headOf. -- --
--   >>> firstOf traverse [1..10]
--   Just 1
--   
-- --
--   >>> firstOf both (1,2)
--   Just 1
--   
-- --
--   >>> firstOf ignored ()
--   Nothing
--   
-- --
--   firstOf :: Getter s a     -> s -> Maybe a
--   firstOf :: Fold s a       -> s -> Maybe a
--   firstOf :: Lens' s a      -> s -> Maybe a
--   firstOf :: Iso' s a       -> s -> Maybe a
--   firstOf :: Traversal' s a -> s -> Maybe a
--   
firstOf :: () => Getting Leftmost a s a -> s -> Maybe a -- | Perform an *UNSAFE* head of a Fold or Traversal -- assuming that it is there. -- --
--   >>> Left 4 ^?! _Left
--   4
--   
-- --
--   >>> "world" ^?! ix 3
--   'l'
--   
-- --
--   (^?!) :: s -> Getter s a     -> a
--   (^?!) :: s -> Fold s a       -> a
--   (^?!) :: s -> Lens' s a      -> a
--   (^?!) :: s -> Iso' s a       -> a
--   (^?!) :: s -> Traversal' s a -> a
--   
(^?!) :: HasCallStack => s -> Getting Endo a s a -> a infixl 8 ^?! -- | Perform a safe head of a Fold or Traversal or -- retrieve Just the result from a Getter or Lens. -- -- When using a Traversal as a partial Lens, or a -- Fold as a partial Getter this can be a convenient way to -- extract the optional value. -- -- Note: if you get stack overflows due to this, you may want to use -- firstOf instead, which can deal more gracefully with heavily -- left-biased trees. -- --
--   >>> Left 4 ^?_Left
--   Just 4
--   
-- --
--   >>> Right 4 ^?_Left
--   Nothing
--   
-- --
--   >>> "world" ^? ix 3
--   Just 'l'
--   
-- --
--   >>> "world" ^? ix 20
--   Nothing
--   
-- --
--   (^?) ≡ flip preview
--   
-- --
--   (^?) :: s -> Getter s a     -> Maybe a
--   (^?) :: s -> Fold s a       -> Maybe a
--   (^?) :: s -> Lens' s a      -> Maybe a
--   (^?) :: s -> Iso' s a       -> Maybe a
--   (^?) :: s -> Traversal' s a -> Maybe a
--   
(^?) :: () => s -> Getting First a s a -> Maybe a infixl 8 ^? -- | Calculate the number of targets there are for a Fold in a given -- container. -- -- Note: This can be rather inefficient for large containers and -- just like length, this will not terminate for infinite folds. -- --
--   lengthlengthOf folded
--   
-- --
--   >>> lengthOf _1 ("hello",())
--   1
--   
-- --
--   >>> lengthOf traverse [1..10]
--   10
--   
-- --
--   >>> lengthOf (traverse.traverse) [[1,2],[3,4],[5,6]]
--   6
--   
-- --
--   lengthOf (folded . folded) :: (Foldable f, Foldable g) => f (g a) -> Int
--   
-- --
--   lengthOf :: Getter s a     -> s -> Int
--   lengthOf :: Fold s a       -> s -> Int
--   lengthOf :: Lens' s a      -> s -> Int
--   lengthOf :: Iso' s a       -> s -> Int
--   lengthOf :: Traversal' s a -> s -> Int
--   
lengthOf :: () => Getting Endo Endo Int s a -> s -> Int -- | Concatenate all of the lists targeted by a Fold into a longer -- list. -- --
--   >>> concatOf both ("pan","ama")
--   "panama"
--   
-- --
--   concatconcatOf folded
--   concatOfview
--   
-- --
--   concatOf :: Getter s [r]     -> s -> [r]
--   concatOf :: Fold s [r]       -> s -> [r]
--   concatOf :: Iso' s [r]       -> s -> [r]
--   concatOf :: Lens' s [r]      -> s -> [r]
--   concatOf :: Traversal' s [r] -> s -> [r]
--   
concatOf :: () => Getting [r] s [r] -> s -> [r] -- | Map a function over all the targets of a Fold of a container -- and concatenate the resulting lists. -- --
--   >>> concatMapOf both (\x -> [x, x + 1]) (1,3)
--   [1,2,3,4]
--   
-- --
--   concatMapconcatMapOf folded
--   
-- --
--   concatMapOf :: Getter s a     -> (a -> [r]) -> s -> [r]
--   concatMapOf :: Fold s a       -> (a -> [r]) -> s -> [r]
--   concatMapOf :: Lens' s a      -> (a -> [r]) -> s -> [r]
--   concatMapOf :: Iso' s a       -> (a -> [r]) -> s -> [r]
--   concatMapOf :: Traversal' s a -> (a -> [r]) -> s -> [r]
--   
concatMapOf :: () => Getting [r] s a -> a -> [r] -> s -> [r] -- | Does the element not occur anywhere within a given Fold of the -- structure? -- --
--   >>> notElemOf each 'd' ('a','b','c')
--   True
--   
-- --
--   >>> notElemOf each 'a' ('a','b','c')
--   False
--   
-- --
--   notElemnotElemOf folded
--   
-- --
--   notElemOf :: Eq a => Getter s a     -> a -> s -> Bool
--   notElemOf :: Eq a => Fold s a       -> a -> s -> Bool
--   notElemOf :: Eq a => Iso' s a       -> a -> s -> Bool
--   notElemOf :: Eq a => Lens' s a      -> a -> s -> Bool
--   notElemOf :: Eq a => Traversal' s a -> a -> s -> Bool
--   notElemOf :: Eq a => Prism' s a     -> a -> s -> Bool
--   
notElemOf :: Eq a => Getting All s a -> a -> s -> Bool -- | Does the element occur anywhere within a given Fold of the -- structure? -- --
--   >>> elemOf both "hello" ("hello","world")
--   True
--   
-- --
--   elemelemOf folded
--   
-- --
--   elemOf :: Eq a => Getter s a     -> a -> s -> Bool
--   elemOf :: Eq a => Fold s a       -> a -> s -> Bool
--   elemOf :: Eq a => Lens' s a      -> a -> s -> Bool
--   elemOf :: Eq a => Iso' s a       -> a -> s -> Bool
--   elemOf :: Eq a => Traversal' s a -> a -> s -> Bool
--   elemOf :: Eq a => Prism' s a     -> a -> s -> Bool
--   
elemOf :: Eq a => Getting Any s a -> a -> s -> Bool -- | The sum of a collection of actions, generalizing concatOf. -- --
--   >>> msumOf both ("hello","world")
--   "helloworld"
--   
-- --
--   >>> msumOf each (Nothing, Just "hello", Nothing)
--   Just "hello"
--   
-- --
--   msummsumOf folded
--   
-- --
--   msumOf :: MonadPlus m => Getter s (m a)     -> s -> m a
--   msumOf :: MonadPlus m => Fold s (m a)       -> s -> m a
--   msumOf :: MonadPlus m => Lens' s (m a)      -> s -> m a
--   msumOf :: MonadPlus m => Iso' s (m a)       -> s -> m a
--   msumOf :: MonadPlus m => Traversal' s (m a) -> s -> m a
--   msumOf :: MonadPlus m => Prism' s (m a)     -> s -> m a
--   
msumOf :: MonadPlus m => Getting Endo m a s m a -> s -> m a -- | The sum of a collection of actions, generalizing concatOf. -- --
--   >>> asumOf both ("hello","world")
--   "helloworld"
--   
-- --
--   >>> asumOf each (Nothing, Just "hello", Nothing)
--   Just "hello"
--   
-- --
--   asumasumOf folded
--   
-- --
--   asumOf :: Alternative f => Getter s (f a)     -> s -> f a
--   asumOf :: Alternative f => Fold s (f a)       -> s -> f a
--   asumOf :: Alternative f => Lens' s (f a)      -> s -> f a
--   asumOf :: Alternative f => Iso' s (f a)       -> s -> f a
--   asumOf :: Alternative f => Traversal' s (f a) -> s -> f a
--   asumOf :: Alternative f => Prism' s (f a)     -> s -> f a
--   
asumOf :: Alternative f => Getting Endo f a s f a -> s -> f a -- | Evaluate each monadic action referenced by a Fold on the -- structure from left to right, and ignore the results. -- --
--   >>> sequenceOf_ both (putStrLn "hello",putStrLn "world")
--   hello
--   world
--   
-- --
--   sequence_sequenceOf_ folded
--   
-- --
--   sequenceOf_ :: Monad m => Getter s (m a)     -> s -> m ()
--   sequenceOf_ :: Monad m => Fold s (m a)       -> s -> m ()
--   sequenceOf_ :: Monad m => Lens' s (m a)      -> s -> m ()
--   sequenceOf_ :: Monad m => Iso' s (m a)       -> s -> m ()
--   sequenceOf_ :: Monad m => Traversal' s (m a) -> s -> m ()
--   sequenceOf_ :: Monad m => Prism' s (m a)     -> s -> m ()
--   
sequenceOf_ :: Monad m => Getting Sequenced a m s m a -> s -> m () -- | forMOf_ is mapMOf_ with two of its arguments flipped. -- --
--   >>> forMOf_ both ("hello","world") putStrLn
--   hello
--   world
--   
-- --
--   forM_forMOf_ folded
--   
-- --
--   forMOf_ :: Monad m => Getter s a     -> s -> (a -> m r) -> m ()
--   forMOf_ :: Monad m => Fold s a       -> s -> (a -> m r) -> m ()
--   forMOf_ :: Monad m => Lens' s a      -> s -> (a -> m r) -> m ()
--   forMOf_ :: Monad m => Iso' s a       -> s -> (a -> m r) -> m ()
--   forMOf_ :: Monad m => Traversal' s a -> s -> (a -> m r) -> m ()
--   forMOf_ :: Monad m => Prism' s a     -> s -> (a -> m r) -> m ()
--   
forMOf_ :: Monad m => Getting Sequenced r m s a -> s -> a -> m r -> m () -- | Map each target of a Fold on a structure to a monadic action, -- evaluate these actions from left to right, and ignore the results. -- --
--   >>> mapMOf_ both putStrLn ("hello","world")
--   hello
--   world
--   
-- --
--   mapM_mapMOf_ folded
--   
-- --
--   mapMOf_ :: Monad m => Getter s a     -> (a -> m r) -> s -> m ()
--   mapMOf_ :: Monad m => Fold s a       -> (a -> m r) -> s -> m ()
--   mapMOf_ :: Monad m => Lens' s a      -> (a -> m r) -> s -> m ()
--   mapMOf_ :: Monad m => Iso' s a       -> (a -> m r) -> s -> m ()
--   mapMOf_ :: Monad m => Traversal' s a -> (a -> m r) -> s -> m ()
--   mapMOf_ :: Monad m => Prism' s a     -> (a -> m r) -> s -> m ()
--   
mapMOf_ :: Monad m => Getting Sequenced r m s a -> a -> m r -> s -> m () -- | See sequenceAOf_ and traverse1Of_. -- --
--   sequence1Of_ :: Apply f => Fold1 s (f a) -> s -> f ()
--   
sequence1Of_ :: Functor f => Getting TraversedF a f s f a -> s -> f () -- | See forOf_ and traverse1Of_. -- --
--   >>> for1Of_ both1 ("abc", "bcd") (\ks -> Map.fromList [ (k, ()) | k <- ks ])
--   fromList [('b',()),('c',())]
--   
-- --
--   for1Of_ :: Apply f => Fold1 s a -> s -> (a -> f r) -> f ()
--   
for1Of_ :: Functor f => Getting TraversedF r f s a -> s -> a -> f r -> f () -- | Traverse over all of the targets of a Fold1, computing an -- Apply based answer. -- -- As long as you have Applicative or Functor effect you -- are better using traverseOf_. The traverse1Of_ is useful -- only when you have genuine Apply effect. -- --
--   >>> traverse1Of_ both1 (\ks -> Map.fromList [ (k, ()) | k <- ks ]) ("abc", "bcd")
--   fromList [('b',()),('c',())]
--   
-- --
--   traverse1Of_ :: Apply f => Fold1 s a -> (a -> f r) -> s -> f ()
--   
traverse1Of_ :: Functor f => Getting TraversedF r f s a -> a -> f r -> s -> f () -- | Evaluate each action in observed by a Fold on a structure from -- left to right, ignoring the results. -- --
--   sequenceA_sequenceAOf_ folded
--   
-- --
--   >>> sequenceAOf_ both (putStrLn "hello",putStrLn "world")
--   hello
--   world
--   
-- --
--   sequenceAOf_ :: Functor f     => Getter s (f a)     -> s -> f ()
--   sequenceAOf_ :: Applicative f => Fold s (f a)       -> s -> f ()
--   sequenceAOf_ :: Functor f     => Lens' s (f a)      -> s -> f ()
--   sequenceAOf_ :: Functor f     => Iso' s (f a)       -> s -> f ()
--   sequenceAOf_ :: Applicative f => Traversal' s (f a) -> s -> f ()
--   sequenceAOf_ :: Applicative f => Prism' s (f a)     -> s -> f ()
--   
sequenceAOf_ :: Functor f => Getting Traversed a f s f a -> s -> f () -- | Traverse over all of the targets of a Fold (or Getter), -- computing an Applicative (or Functor)-based answer, but -- unlike forOf do not construct a new structure. forOf_ -- generalizes for_ to work over any Fold. -- -- When passed a Getter, forOf_ can work over any -- Functor, but when passed a Fold, forOf_ requires -- an Applicative. -- --
--   for_forOf_ folded
--   
-- --
--   >>> forOf_ both ("hello","world") putStrLn
--   hello
--   world
--   
-- -- The rather specific signature of forOf_ allows it to be used as -- if the signature was any of: -- --
--   iforOf_ l s ≡ forOf_ l s . Indexed
--   
-- --
--   forOf_ :: Functor f     => Getter s a     -> s -> (a -> f r) -> f ()
--   forOf_ :: Applicative f => Fold s a       -> s -> (a -> f r) -> f ()
--   forOf_ :: Functor f     => Lens' s a      -> s -> (a -> f r) -> f ()
--   forOf_ :: Functor f     => Iso' s a       -> s -> (a -> f r) -> f ()
--   forOf_ :: Applicative f => Traversal' s a -> s -> (a -> f r) -> f ()
--   forOf_ :: Applicative f => Prism' s a     -> s -> (a -> f r) -> f ()
--   
forOf_ :: Functor f => Getting Traversed r f s a -> s -> a -> f r -> f () -- | Traverse over all of the targets of a Fold (or Getter), -- computing an Applicative (or Functor)-based answer, but -- unlike traverseOf do not construct a new structure. -- traverseOf_ generalizes traverse_ to work over any -- Fold. -- -- When passed a Getter, traverseOf_ can work over any -- Functor, but when passed a Fold, traverseOf_ -- requires an Applicative. -- --
--   >>> traverseOf_ both putStrLn ("hello","world")
--   hello
--   world
--   
-- --
--   traverse_traverseOf_ folded
--   
-- --
--   traverseOf_ _2 :: Functor f => (c -> f r) -> (d, c) -> f ()
--   traverseOf_ _Left :: Applicative f => (a -> f b) -> Either a c -> f ()
--   
-- --
--   itraverseOf_ l ≡ traverseOf_ l . Indexed
--   
-- -- The rather specific signature of traverseOf_ allows it to be -- used as if the signature was any of: -- --
--   traverseOf_ :: Functor f     => Getter s a     -> (a -> f r) -> s -> f ()
--   traverseOf_ :: Applicative f => Fold s a       -> (a -> f r) -> s -> f ()
--   traverseOf_ :: Functor f     => Lens' s a      -> (a -> f r) -> s -> f ()
--   traverseOf_ :: Functor f     => Iso' s a       -> (a -> f r) -> s -> f ()
--   traverseOf_ :: Applicative f => Traversal' s a -> (a -> f r) -> s -> f ()
--   traverseOf_ :: Applicative f => Prism' s a     -> (a -> f r) -> s -> f ()
--   
traverseOf_ :: Functor f => Getting Traversed r f s a -> a -> f r -> s -> f () -- | Calculate the Sum of every number targeted by a Fold. -- --
--   >>> sumOf both (5,6)
--   11
--   
--   >>> sumOf folded [1,2,3,4]
--   10
--   
--   >>> sumOf (folded.both) [(1,2),(3,4)]
--   10
--   
--   >>> import Data.Data.Lens
--   
--   >>> sumOf biplate [(1::Int,[]),(2,[(3::Int,4::Int)])] :: Int
--   10
--   
-- --
--   sumsumOf folded
--   
-- -- This operation may be more strict than you would expect. If you want a -- lazier version use ala Sum . -- foldMapOf -- --
--   sumOf _1 :: Num a => (a, b) -> a
--   sumOf (folded . _1) :: (Foldable f, Num a) => f (a, b) -> a
--   
-- --
--   sumOf :: Num a => Getter s a     -> s -> a
--   sumOf :: Num a => Fold s a       -> s -> a
--   sumOf :: Num a => Lens' s a      -> s -> a
--   sumOf :: Num a => Iso' s a       -> s -> a
--   sumOf :: Num a => Traversal' s a -> s -> a
--   sumOf :: Num a => Prism' s a     -> s -> a
--   
sumOf :: Num a => Getting Endo Endo a s a -> s -> a -- | Calculate the Product of every number targeted by a -- Fold. -- --
--   >>> productOf both (4,5)
--   20
--   
--   >>> productOf folded [1,2,3,4,5]
--   120
--   
-- --
--   productproductOf folded
--   
-- -- This operation may be more strict than you would expect. If you want a -- lazier version use ala Product . -- foldMapOf -- --
--   productOf :: Num a => Getter s a     -> s -> a
--   productOf :: Num a => Fold s a       -> s -> a
--   productOf :: Num a => Lens' s a      -> s -> a
--   productOf :: Num a => Iso' s a       -> s -> a
--   productOf :: Num a => Traversal' s a -> s -> a
--   productOf :: Num a => Prism' s a     -> s -> a
--   
productOf :: Num a => Getting Endo Endo a s a -> s -> a -- | Returns True only if no targets of a Fold satisfy a -- predicate. -- --
--   >>> noneOf each (is _Nothing) (Just 3, Just 4, Just 5)
--   True
--   
--   >>> noneOf (folded.folded) (<10) [[13,99,20],[3,71,42]]
--   False
--   
-- --
--   inoneOf l = noneOf l . Indexed
--   
-- --
--   noneOf :: Getter s a     -> (a -> Bool) -> s -> Bool
--   noneOf :: Fold s a       -> (a -> Bool) -> s -> Bool
--   noneOf :: Lens' s a      -> (a -> Bool) -> s -> Bool
--   noneOf :: Iso' s a       -> (a -> Bool) -> s -> Bool
--   noneOf :: Traversal' s a -> (a -> Bool) -> s -> Bool
--   noneOf :: Prism' s a     -> (a -> Bool) -> s -> Bool
--   
noneOf :: () => Getting Any s a -> a -> Bool -> s -> Bool -- | Returns True if every target of a Fold satisfies a -- predicate. -- --
--   >>> allOf both (>=3) (4,5)
--   True
--   
--   >>> allOf folded (>=2) [1..10]
--   False
--   
-- --
--   allallOf folded
--   
-- --
--   iallOf l = allOf l . Indexed
--   
-- --
--   allOf :: Getter s a     -> (a -> Bool) -> s -> Bool
--   allOf :: Fold s a       -> (a -> Bool) -> s -> Bool
--   allOf :: Lens' s a      -> (a -> Bool) -> s -> Bool
--   allOf :: Iso' s a       -> (a -> Bool) -> s -> Bool
--   allOf :: Traversal' s a -> (a -> Bool) -> s -> Bool
--   allOf :: Prism' s a     -> (a -> Bool) -> s -> Bool
--   
allOf :: () => Getting All s a -> a -> Bool -> s -> Bool -- | Returns True if any target of a Fold satisfies a -- predicate. -- --
--   >>> anyOf both (=='x') ('x','y')
--   True
--   
--   >>> import Data.Data.Lens
--   
--   >>> anyOf biplate (== "world") (((),2::Int),"hello",("world",11::Int))
--   True
--   
-- --
--   anyanyOf folded
--   
-- --
--   ianyOf l ≡ anyOf l . Indexed
--   
-- --
--   anyOf :: Getter s a     -> (a -> Bool) -> s -> Bool
--   anyOf :: Fold s a       -> (a -> Bool) -> s -> Bool
--   anyOf :: Lens' s a      -> (a -> Bool) -> s -> Bool
--   anyOf :: Iso' s a       -> (a -> Bool) -> s -> Bool
--   anyOf :: Traversal' s a -> (a -> Bool) -> s -> Bool
--   anyOf :: Prism' s a     -> (a -> Bool) -> s -> Bool
--   
anyOf :: () => Getting Any s a -> a -> Bool -> s -> Bool -- | Returns True if any target of a Fold is True. -- --
--   >>> orOf both (True,False)
--   True
--   
--   >>> orOf both (False,False)
--   False
--   
-- --
--   ororOf folded
--   
-- --
--   orOf :: Getter s Bool     -> s -> Bool
--   orOf :: Fold s Bool       -> s -> Bool
--   orOf :: Lens' s Bool      -> s -> Bool
--   orOf :: Iso' s Bool       -> s -> Bool
--   orOf :: Traversal' s Bool -> s -> Bool
--   orOf :: Prism' s Bool     -> s -> Bool
--   
orOf :: () => Getting Any s Bool -> s -> Bool -- | Returns True if every target of a Fold is True. -- --
--   >>> andOf both (True,False)
--   False
--   
--   >>> andOf both (True,True)
--   True
--   
-- --
--   andandOf folded
--   
-- --
--   andOf :: Getter s Bool     -> s -> Bool
--   andOf :: Fold s Bool       -> s -> Bool
--   andOf :: Lens' s Bool      -> s -> Bool
--   andOf :: Iso' s Bool       -> s -> Bool
--   andOf :: Traversal' s Bool -> s -> Bool
--   andOf :: Prism' s Bool     -> s -> Bool
--   
andOf :: () => Getting All s Bool -> s -> Bool -- | A convenient infix (flipped) version of toListOf. -- --
--   >>> [[1,2],[3]]^..id
--   [[[1,2],[3]]]
--   
--   >>> [[1,2],[3]]^..traverse
--   [[1,2],[3]]
--   
--   >>> [[1,2],[3]]^..traverse.traverse
--   [1,2,3]
--   
-- --
--   >>> (1,2)^..both
--   [1,2]
--   
-- --
--   toList xs ≡ xs ^.. folded
--   (^..) ≡ flip toListOf
--   
-- --
--   (^..) :: s -> Getter s a     -> a :: s -> Fold s a       -> a :: s -> Lens' s a      -> a :: s -> Iso' s a       -> a :: s -> Traversal' s a -> a :: s -> Prism' s a     -> [a]
--   
(^..) :: () => s -> Getting Endo [a] s a -> [a] infixl 8 ^.. -- | Extract a NonEmpty of the targets of Fold1. -- --
--   >>> toNonEmptyOf both1 ("hello", "world")
--   "hello" :| ["world"]
--   
-- --
--   toNonEmptyOf :: Getter s a      -> s -> NonEmpty a
--   toNonEmptyOf :: Fold1 s a       -> s -> NonEmpty a
--   toNonEmptyOf :: Lens' s a       -> s -> NonEmpty a
--   toNonEmptyOf :: Iso' s a        -> s -> NonEmpty a
--   toNonEmptyOf :: Traversal1' s a -> s -> NonEmpty a
--   toNonEmptyOf :: Prism' s a      -> s -> NonEmpty a
--   
toNonEmptyOf :: () => Getting NonEmptyDList a s a -> s -> NonEmpty a -- | Extract a list of the targets of a Fold. See also (^..). -- --
--   toListtoListOf folded
--   (^..) ≡ flip toListOf
--   
toListOf :: () => Getting Endo [a] s a -> s -> [a] -- | Left-associative fold of the parts of a structure that are viewed -- through a Lens, Getter, Fold or Traversal. -- --
--   foldlfoldlOf folded
--   
-- --
--   foldlOf :: Getter s a     -> (r -> a -> r) -> r -> s -> r
--   foldlOf :: Fold s a       -> (r -> a -> r) -> r -> s -> r
--   foldlOf :: Lens' s a      -> (r -> a -> r) -> r -> s -> r
--   foldlOf :: Iso' s a       -> (r -> a -> r) -> r -> s -> r
--   foldlOf :: Traversal' s a -> (r -> a -> r) -> r -> s -> r
--   foldlOf :: Prism' s a     -> (r -> a -> r) -> r -> s -> r
--   
foldlOf :: () => Getting Dual Endo r s a -> r -> a -> r -> r -> s -> r -- | Right-associative fold of parts of a structure that are viewed through -- a Lens, Getter, Fold or Traversal. -- --
--   foldrfoldrOf folded
--   
-- --
--   foldrOf :: Getter s a     -> (a -> r -> r) -> r -> s -> r
--   foldrOf :: Fold s a       -> (a -> r -> r) -> r -> s -> r
--   foldrOf :: Lens' s a      -> (a -> r -> r) -> r -> s -> r
--   foldrOf :: Iso' s a       -> (a -> r -> r) -> r -> s -> r
--   foldrOf :: Traversal' s a -> (a -> r -> r) -> r -> s -> r
--   foldrOf :: Prism' s a     -> (a -> r -> r) -> r -> s -> r
--   
-- --
--   ifoldrOf l ≡ foldrOf l . Indexed
--   
-- --
--   foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r
--   
foldrOf :: () => Getting Endo r s a -> a -> r -> r -> r -> s -> r -- | Combine the elements of a structure viewed through a Lens, -- Getter, Fold or Traversal using a monoid. -- --
--   >>> foldOf (folded.folded) [[Sum 1,Sum 4],[Sum 8, Sum 8],[Sum 21]]
--   Sum {getSum = 42}
--   
-- --
--   fold = foldOf folded
--   
-- --
--   foldOfview
--   
-- --
--   foldOf ::             Getter s m     -> s -> m
--   foldOf :: Monoid m => Fold s m       -> s -> m
--   foldOf ::             Lens' s m      -> s -> m
--   foldOf ::             Iso' s m       -> s -> m
--   foldOf :: Monoid m => Traversal' s m -> s -> m
--   foldOf :: Monoid m => Prism' s m     -> s -> m
--   
foldOf :: () => Getting a s a -> s -> a -- | Map each part of a structure viewed through a Lens, -- Getter, Fold or Traversal to a monoid and combine -- the results. -- --
--   >>> foldMapOf (folded . both . _Just) Sum [(Just 21, Just 21)]
--   Sum {getSum = 42}
--   
-- --
--   foldMap = foldMapOf folded
--   
-- --
--   foldMapOfviews
--   ifoldMapOf l = foldMapOf l . Indexed
--   
-- --
--   foldMapOf ::                Getter s a      -> (a -> r) -> s -> r
--   foldMapOf :: Monoid r    => Fold s a        -> (a -> r) -> s -> r
--   foldMapOf :: Semigroup r => Fold1 s a       -> (a -> r) -> s -> r
--   foldMapOf ::                Lens' s a       -> (a -> r) -> s -> r
--   foldMapOf ::                Iso' s a        -> (a -> r) -> s -> r
--   foldMapOf :: Monoid r    => Traversal' s a  -> (a -> r) -> s -> r
--   foldMapOf :: Semigroup r => Traversal1' s a -> (a -> r) -> s -> r
--   foldMapOf :: Monoid r    => Prism' s a      -> (a -> r) -> s -> r
--   
-- --
--   foldMapOf :: Getting r s a -> (a -> r) -> s -> r
--   
foldMapOf :: () => Getting r s a -> a -> r -> s -> r -- | A Fold over the individual lines of a String. -- --
--   lined :: Fold String String
--   lined :: Traversal' String String
--   
-- --
--   lined :: IndexedFold Int String String
--   lined :: IndexedTraversal' Int String String
--   
-- -- Note: This function type-checks as a Traversal but it doesn't -- satisfy the laws. It's only valid to use it when you don't insert any -- newline characters while traversing, and if your original -- String contains only isolated newline characters. lined :: Applicative f => IndexedLensLike' Int f String String -- | A Fold over the individual words of a String. -- --
--   worded :: Fold String String
--   worded :: Traversal' String String
--   
-- --
--   worded :: IndexedFold Int String String
--   worded :: IndexedTraversal' Int String String
--   
-- -- Note: This function type-checks as a Traversal but it doesn't -- satisfy the laws. It's only valid to use it when you don't insert any -- whitespace characters while traversing, and if your original -- String contains only isolated space characters (and no other -- characters that count as space, such as non-breaking spaces). worded :: Applicative f => IndexedLensLike' Int f String String -- | Obtain a Fold by dropping elements from another Fold, -- Lens, Iso, Getter or Traversal while a -- predicate holds. -- --
--   dropWhile p ≡ toListOf (droppingWhile p folded)
--   
-- --
--   >>> toListOf (droppingWhile (<=3) folded) [1..6]
--   [4,5,6]
--   
-- --
--   >>> toListOf (droppingWhile (<=3) folded) [1,6,1]
--   [6,1]
--   
-- --
--   droppingWhile :: (a -> Bool) -> Fold s a                         -> Fold s a
--   droppingWhile :: (a -> Bool) -> Getter s a                       -> Fold s a
--   droppingWhile :: (a -> Bool) -> Traversal' s a                   -> Fold s a                -- see notes
--   droppingWhile :: (a -> Bool) -> Lens' s a                        -> Fold s a                -- see notes
--   droppingWhile :: (a -> Bool) -> Prism' s a                       -> Fold s a                -- see notes
--   droppingWhile :: (a -> Bool) -> Iso' s a                         -> Fold s a                -- see notes
--   
-- --
--   droppingWhile :: (a -> Bool) -> IndexPreservingTraversal' s a    -> IndexPreservingFold s a -- see notes
--   droppingWhile :: (a -> Bool) -> IndexPreservingLens' s a         -> IndexPreservingFold s a -- see notes
--   droppingWhile :: (a -> Bool) -> IndexPreservingGetter s a        -> IndexPreservingFold s a
--   droppingWhile :: (a -> Bool) -> IndexPreservingFold s a          -> IndexPreservingFold s a
--   
-- --
--   droppingWhile :: (a -> Bool) -> IndexedTraversal' i s a          -> IndexedFold i s a       -- see notes
--   droppingWhile :: (a -> Bool) -> IndexedLens' i s a               -> IndexedFold i s a       -- see notes
--   droppingWhile :: (a -> Bool) -> IndexedGetter i s a              -> IndexedFold i s a
--   droppingWhile :: (a -> Bool) -> IndexedFold i s a                -> IndexedFold i s a
--   
-- -- Note: Many uses of this combinator will yield something that meets the -- types, but not the laws of a valid Traversal or -- IndexedTraversal. The Traversal and -- IndexedTraversal laws are only satisfied if the new values you -- assign to the first target also does not pass the predicate! Otherwise -- subsequent traversals will visit fewer elements and Traversal -- fusion is not sound. -- -- So for any traversal t and predicate p, -- droppingWhile p t may not be lawful, but -- (dropping 1 . droppingWhile p) t is. For -- example: -- --
--   >>> let l  :: Traversal' [Int] Int; l  = droppingWhile (<= 1) traverse
--   
--   >>> let l' :: Traversal' [Int] Int; l' = dropping 1 l
--   
-- -- l is not a lawful setter because over l f . -- over l g ≢ over l (f . g): -- --
--   >>> [1,2,3] & l .~ 0 & l .~ 4
--   [1,0,0]
--   
--   >>> [1,2,3] & l .~ 4
--   [1,4,4]
--   
-- -- l' on the other hand behaves lawfully: -- --
--   >>> [1,2,3] & l' .~ 0 & l' .~ 4
--   [1,2,4]
--   
--   >>> [1,2,3] & l' .~ 4
--   [1,2,4]
--   
droppingWhile :: (Conjoined p, Profunctor q, Applicative f) => a -> Bool -> Optical p q Compose State Bool f s t a a -> Optical p q f s t a a -- | Obtain a Fold by taking elements from another Fold, -- Lens, Iso, Getter or Traversal while a -- predicate holds. -- --
--   takeWhile p ≡ toListOf (takingWhile p folded)
--   
-- --
--   >>> timingOut $ toListOf (takingWhile (<=3) folded) [1..]
--   [1,2,3]
--   
-- --
--   takingWhile :: (a -> Bool) -> Fold s a                         -> Fold s a
--   takingWhile :: (a -> Bool) -> Getter s a                       -> Fold s a
--   takingWhile :: (a -> Bool) -> Traversal' s a                   -> Fold s a -- * See note below
--   takingWhile :: (a -> Bool) -> Lens' s a                        -> Fold s a -- * See note below
--   takingWhile :: (a -> Bool) -> Prism' s a                       -> Fold s a -- * See note below
--   takingWhile :: (a -> Bool) -> Iso' s a                         -> Fold s a -- * See note below
--   takingWhile :: (a -> Bool) -> IndexedTraversal' i s a          -> IndexedFold i s a -- * See note below
--   takingWhile :: (a -> Bool) -> IndexedLens' i s a               -> IndexedFold i s a -- * See note below
--   takingWhile :: (a -> Bool) -> IndexedFold i s a                -> IndexedFold i s a
--   takingWhile :: (a -> Bool) -> IndexedGetter i s a              -> IndexedFold i s a
--   
-- -- Note: When applied to a Traversal, takingWhile -- yields something that can be used as if it were a Traversal, -- but which is not a Traversal per the laws, unless you are -- careful to ensure that you do not invalidate the predicate when -- writing back through it. takingWhile :: (Conjoined p, Applicative f) => a -> Bool -> Over p TakingWhile p f a a s t a a -> Over p f s t a a -- | Obtain an Fold that can be composed with to filter another -- Lens, Iso, Getter, Fold (or -- Traversal). -- -- Note: This is not a legal Traversal, unless you are very -- careful not to invalidate the predicate on the target. -- -- Note: This is also not a legal Prism, unless you are -- very careful not to inject a value that matches the predicate. -- -- As a counter example, consider that given evens = filtered -- even the second Traversal law is violated: -- --
--   over evens succ . over evens succ /= over evens (succ . succ)
--   
-- -- So, in order for this to qualify as a legal Traversal you can -- only use it for actions that preserve the result of the predicate! -- --
--   >>> [1..10]^..folded.filtered even
--   [2,4,6,8,10]
--   
-- -- This will preserve an index if it is present. filtered :: (Choice p, Applicative f) => a -> Bool -> Optic' p f a a -- | x ^. iterated f returns an infinite -- Fold1 of repeated applications of f to x. -- --
--   toListOf (iterated f) a ≡ iterate f a
--   
-- --
--   iterated :: (a -> a) -> Fold1 a a
--   
iterated :: Apply f => a -> a -> LensLike' f a a -- | Build a Fold that unfolds its values from a seed. -- --
--   unfoldrtoListOf . unfolded
--   
-- --
--   >>> 10^..unfolded (\b -> if b == 0 then Nothing else Just (b, b-1))
--   [10,9,8,7,6,5,4,3,2,1]
--   
unfolded :: () => b -> Maybe (a, b) -> Fold b a -- | Transform a non-empty Fold into a Fold1 that loops over -- its elements over and over. -- --
--   >>> timingOut $ [1,2,3]^..taking 7 (cycled traverse)
--   [1,2,3,1,2,3,1]
--   
-- --
--   cycled :: Fold1 s a -> Fold1 s a
--   
cycled :: Apply f => LensLike f s t a b -> LensLike f s t a b -- | A Fold that replicates its input n times. -- --
--   replicate n ≡ toListOf (replicated n)
--   
-- --
--   >>> 5^..replicated 20
--   [5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5]
--   
replicated :: () => Int -> Fold a a -- | Form a Fold1 by repeating the input forever. -- --
--   repeattoListOf repeated
--   
-- --
--   >>> timingOut $ 5^..taking 20 repeated
--   [5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5]
--   
-- --
--   repeated :: Fold1 a a
--   
repeated :: Apply f => LensLike' f a a -- | Obtain a Fold from any Foldable indexed by ordinal -- position. folded64 :: Foldable f => IndexedFold Int64 f a a -- | Obtain a Fold from any Foldable indexed by ordinal -- position. -- --
--   >>> Just 3^..folded
--   [3]
--   
-- --
--   >>> Nothing^..folded
--   []
--   
-- --
--   >>> [(1,2),(3,4)]^..folded.both
--   [1,2,3,4]
--   
folded :: Foldable f => IndexedFold Int f a a -- | Obtain FoldWithIndex by lifting ifoldr like function. ifoldring :: (Indexable i p, Contravariant f, Applicative f) => i -> a -> f a -> f a -> f a -> s -> f a -> Over p f s t a b -- | Obtain a Fold by lifting foldr like function. -- --
--   >>> [1,2,3,4]^..foldring foldr
--   [1,2,3,4]
--   
foldring :: (Contravariant f, Applicative f) => a -> f a -> f a -> f a -> s -> f a -> LensLike f s t a b ifolding :: (Foldable f, Indexable i p, Contravariant g, Applicative g) => s -> f (i, a) -> Over p g s t a b -- | Obtain a Fold by lifting an operation that returns a -- Foldable result. -- -- This can be useful to lift operations from Data.List and -- elsewhere into a Fold. -- --
--   >>> [1,2,3,4]^..folding tail
--   [2,3,4]
--   
folding :: Foldable f => s -> f a -> Fold s a -- | This is an improper prism for text formatting based on Read and -- Show. -- -- This Prism is "improper" in the sense that it normalizes the -- text formatting, but round tripping is idempotent given sane -- 'Read'/'Show' instances. -- --
--   >>> _Show # 2
--   "2"
--   
-- --
--   >>> "EQ" ^? _Show :: Maybe Ordering
--   Just EQ
--   
-- --
--   _Showprism' show readMaybe
--   
_Show :: (Read a, Show a) => Prism' String a -- | This Prism compares for approximate equality with a given value -- and a predicate for testing, an example where the value is the empty -- list and the predicate checks that a list is empty (same as -- _Empty with the AsEmpty list instance): -- --
--   >>> nearly [] null # ()
--   []
--   
--   >>> [1,2,3,4] ^? nearly [] null
--   Nothing
--   
-- --
--   nearly [] null :: Prism' [a] ()
--   
-- -- To comply with the Prism laws the arguments you supply to -- nearly a p are somewhat constrained. -- -- We assume p x holds iff x ≡ a. Under that assumption -- then this is a valid Prism. -- -- This is useful when working with a type where you can test equality -- for only a subset of its values, and the prism selects such a value. nearly :: () => a -> a -> Bool -> Prism' a () -- | This Prism compares for exact equality with a given value. -- --
--   >>> only 4 # ()
--   4
--   
-- --
--   >>> 5 ^? only 4
--   Nothing
--   
only :: Eq a => a -> Prism' a () -- | Void is a logically uninhabited data type. -- -- This is a Prism that will always fail to match. _Void :: (Choice p, Applicative f) => p a f Void -> p s f s -- | This Prism provides the Traversal of a Nothing in -- a Maybe. -- --
--   >>> Nothing ^? _Nothing
--   Just ()
--   
-- --
--   >>> Just () ^? _Nothing
--   Nothing
--   
-- -- But you can turn it around and use it to construct Nothing as -- well: -- --
--   >>> _Nothing # ()
--   Nothing
--   
_Nothing :: (Choice p, Applicative f) => p () f () -> p Maybe a f Maybe a -- | This Prism provides a Traversal for tweaking the target -- of the value of Just in a Maybe. -- --
--   >>> over _Just (+1) (Just 2)
--   Just 3
--   
-- -- Unlike traverse this is a Prism, and so you can use it -- to inject as well: -- --
--   >>> _Just # 5
--   Just 5
--   
-- --
--   >>> 5^.re _Just
--   Just 5
--   
-- -- Interestingly, -- --
--   m ^? _Just ≡ m
--   
-- --
--   >>> Just x ^? _Just
--   Just x
--   
-- --
--   >>> Nothing ^? _Just
--   Nothing
--   
_Just :: (Choice p, Applicative f) => p a f b -> p Maybe a f Maybe b -- | This Prism provides a Traversal for tweaking the -- Right half of an Either: -- --
--   >>> over _Right (+1) (Left 2)
--   Left 2
--   
-- --
--   >>> over _Right (+1) (Right 2)
--   Right 3
--   
-- --
--   >>> Right "hello" ^._Right
--   "hello"
--   
-- --
--   >>> Left "hello" ^._Right :: [Double]
--   []
--   
-- -- It also can be turned around to obtain the embedding into the -- Right half of an Either: -- --
--   >>> _Right # 5
--   Right 5
--   
-- --
--   >>> 5^.re _Right
--   Right 5
--   
_Right :: (Choice p, Applicative f) => p a f b -> p Either c a f Either c b -- | This Prism provides a Traversal for tweaking the -- Left half of an Either: -- --
--   >>> over _Left (+1) (Left 2)
--   Left 3
--   
-- --
--   >>> over _Left (+1) (Right 2)
--   Right 2
--   
-- --
--   >>> Right 42 ^._Left :: String
--   ""
--   
-- --
--   >>> Left "hello" ^._Left
--   "hello"
--   
-- -- It also can be turned around to obtain the embedding into the -- Left half of an Either: -- --
--   >>> _Left # 5
--   Left 5
--   
-- --
--   >>> 5^.re _Left
--   Left 5
--   
_Left :: (Choice p, Applicative f) => p a f b -> p Either a c f Either b c -- | Retrieve the value targeted by a Prism or return the original -- value while allowing the type to change if it does not match. -- --
--   >>> matching _Just (Just 12)
--   Right 12
--   
-- --
--   >>> matching _Just (Nothing :: Maybe Int) :: Either (Maybe Bool) Int
--   Left Nothing
--   
matching :: () => APrism s t a b -> s -> Either t a -- | Check to see if this Prism doesn't match. -- --
--   >>> isn't _Left (Right 12)
--   True
--   
-- --
--   >>> isn't _Left (Left 12)
--   False
--   
-- --
--   >>> isn't _Empty []
--   False
--   
isn't :: () => APrism s t a b -> s -> Bool -- | lift a Prism through a Traversable functor, -- giving a Prism that matches only if all the elements of the container -- match the Prism. -- --
--   >>> [Left 1, Right "foo", Left 4, Right "woot"]^..below _Right
--   []
--   
-- --
--   >>> [Right "hail hydra!", Right "foo", Right "blah", Right "woot"]^..below _Right
--   [["hail hydra!","foo","blah","woot"]]
--   
below :: Traversable f => APrism' s a -> Prism' f s f a -- | Use a Prism to work over part of a structure. aside :: () => APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b) -- | Given a pair of prisms, project sums. -- -- Viewing a Prism as a co-Lens, this combinator can be -- seen to be dual to alongside. without :: () => APrism s t a b -> APrism u v c d -> Prism Either s u Either t v Either a c Either b d -- | Use a Prism as a kind of first-class pattern. -- --
--   outside :: Prism s t a b -> Lens (t -> r) (s -> r) (b -> r) (a -> r)
--   
outside :: Representable p => APrism s t a b -> Lens p t r p s r p b r p a r -- | This is usually used to build a Prism', when you have to use an -- operation like cast which already returns a Maybe. prism' :: () => b -> s -> s -> Maybe a -> Prism s s a b -- | Build a Prism. -- -- Either t a is used instead of Maybe a -- to permit the types of s and t to differ. prism :: () => b -> t -> s -> Either t a -> Prism s t a b -- | Clone a Prism so that you can reuse the same monomorphically -- typed Prism for different purposes. -- -- See cloneLens and cloneTraversal for examples of why you -- might want to do this. clonePrism :: () => APrism s t a b -> Prism s t a b -- | Convert APrism to the pair of functions that characterize it. withPrism :: () => APrism s t a b -> b -> t -> s -> Either t a -> r -> r -- | If you see this in a signature for a function, the function is -- expecting a Prism. type APrism s t a b = Market a b a Identity b -> Market a b s Identity t -- |
--   type APrism' = Simple APrism
--   
type APrism' s a = APrism s s a a -- | This can be used to turn an Iso or Prism around and -- use the current state through it the other way, applying a -- function. -- --
--   reusesuses . re
--   reuses (unto f) g ≡ gets (g . f)
--   
-- --
--   >>> evalState (reuses _Left isLeft) (5 :: Int)
--   True
--   
-- --
--   reuses :: MonadState a m => Prism' s a -> (s -> r) -> m r
--   reuses :: MonadState a m => Iso' s a   -> (s -> r) -> m r
--   
reuses :: MonadState b m => AReview t b -> t -> r -> m r -- | This can be used to turn an Iso or Prism around and -- use a value (or the current environment) through it the other -- way. -- --
--   reuseuse . re
--   reuse . untogets
--   
-- --
--   >>> evalState (reuse _Left) 5
--   Left 5
--   
-- --
--   >>> evalState (reuse (unto succ)) 5
--   6
--   
-- --
--   reuse :: MonadState a m => Prism' s a -> m s
--   reuse :: MonadState a m => Iso' s a   -> m s
--   
reuse :: MonadState b m => AReview t b -> m t -- | This can be used to turn an Iso or Prism around and -- view a value (or the current environment) through it the other -- way, applying a function. -- --
--   reviewsviews . re
--   reviews (unto f) g ≡ g . f
--   
-- --
--   >>> reviews _Left isRight "mustard"
--   False
--   
-- --
--   >>> reviews (unto succ) (*2) 3
--   8
--   
-- -- Usually this function is used in the (->) Monad -- with a Prism or Iso, in which case it may be useful to -- think of it as having one of these more restricted type signatures: -- --
--   reviews :: Iso' s a   -> (s -> r) -> a -> r
--   reviews :: Prism' s a -> (s -> r) -> a -> r
--   
-- -- However, when working with a Monad transformer stack, it is -- sometimes useful to be able to review the current environment, -- in which case it may be beneficial to think of it as having one of -- these slightly more liberal type signatures: -- --
--   reviews :: MonadReader a m => Iso' s a   -> (s -> r) -> m r
--   reviews :: MonadReader a m => Prism' s a -> (s -> r) -> m r
--   
reviews :: MonadReader b m => AReview t b -> t -> r -> m r -- | An infix alias for review. -- --
--   unto f # x ≡ f x
--   l # x ≡ x ^. re l
--   
-- -- This is commonly used when using a Prism as a smart -- constructor. -- --
--   >>> _Left # 4
--   Left 4
--   
-- -- But it can be used for any Prism -- --
--   >>> base 16 # 123
--   "7b"
--   
-- --
--   (#) :: Iso'      s a -> a -> s
--   (#) :: Prism'    s a -> a -> s
--   (#) :: Review    s a -> a -> s
--   (#) :: Equality' s a -> a -> s
--   
(#) :: () => AReview t b -> b -> t infixr 8 # -- | This can be used to turn an Iso or Prism around and -- view a value (or the current environment) through it the other -- way. -- --
--   reviewview . re
--   review . untoid
--   
-- --
--   >>> review _Left "mustard"
--   Left "mustard"
--   
-- --
--   >>> review (unto succ) 5
--   6
--   
-- -- Usually review is used in the (->) Monad -- with a Prism or Iso, in which case it may be useful to -- think of it as having one of these more restricted type signatures: -- --
--   review :: Iso' s a   -> a -> s
--   review :: Prism' s a -> a -> s
--   
-- -- However, when working with a Monad transformer stack, it is -- sometimes useful to be able to review the current environment, -- in which case it may be beneficial to think of it as having one of -- these slightly more liberal type signatures: -- --
--   review :: MonadReader a m => Iso' s a   -> m s
--   review :: MonadReader a m => Prism' s a -> m s
--   
review :: MonadReader b m => AReview t b -> m t -- | Turn a Prism or Iso around to build a Getter. -- -- If you have an Iso, from is a more powerful version of -- this function that will return an Iso instead of a mere -- Getter. -- --
--   >>> 5 ^.re _Left
--   Left 5
--   
-- --
--   >>> 6 ^.re (_Left.unto succ)
--   Left 7
--   
-- --
--   reviewview  . re
--   reviewsviews . re
--   reuseuse   . re
--   reusesuses  . re
--   
-- --
--   re :: Prism s t a b -> Getter b t
--   re :: Iso s t a b   -> Getter b t
--   
re :: () => AReview t b -> Getter b t -- | Turn a Getter around to get a Review -- --
--   un = unto . view
--   unto = un . to
--   
-- --
--   >>> un (to length) # [1,2,3]
--   3
--   
un :: (Profunctor p, Bifunctor p, Functor f) => Getting a s a -> Optic' p f a s -- | An analogue of to for review. -- --
--   unto :: (b -> t) -> Review' t b
--   
-- --
--   unto = un . to
--   
unto :: (Profunctor p, Bifunctor p, Functor f) => b -> t -> Optic p f s t a b -- | Coerce a Getter-compatible Optical to an -- Optical'. This is useful when using a Traversal that is -- not simple as a Getter or a Fold. -- --
--   getting :: Traversal s t a b          -> Fold s a
--   getting :: Lens s t a b               -> Getter s a
--   getting :: IndexedTraversal i s t a b -> IndexedFold i s a
--   getting :: IndexedLens i s t a b      -> IndexedGetter i s a
--   
getting :: (Profunctor p, Profunctor q, Functor f, Contravariant f) => Optical p q f s t a b -> Optical' p q f s a -- | View the index and value of an IndexedGetter or -- IndexedLens. -- -- This is the same operation as iview with the arguments flipped. -- -- The fixity and semantics are such that subsequent field accesses can -- be performed with (.). -- --
--   (^@.) :: s -> IndexedGetter i s a -> (i, a)
--   (^@.) :: s -> IndexedLens' i s a  -> (i, a)
--   
-- -- The result probably doesn't have much meaning when applied to an -- IndexedFold. (^@.) :: () => s -> IndexedGetting i (i, a) s a -> (i, a) infixl 8 ^@. -- | Use a function of the index and value of an IndexedGetter into -- the current state. -- -- When applied to an IndexedFold the result will be a monoidal -- summary instead of a single answer. iuses :: MonadState s m => IndexedGetting i r s a -> i -> a -> r -> m r -- | Use the index and value of an IndexedGetter into the current -- state as a pair. -- -- When applied to an IndexedFold the result will most likely be a -- nonsensical monoidal summary of the indices tupled with a monoidal -- summary of the values and probably not whatever it is you wanted. iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a) -- | View a function of the index and value of an IndexedGetter into -- the current environment. -- -- When applied to an IndexedFold the result will be a monoidal -- summary instead of a single answer. -- --
--   iviewsifoldMapOf
--   
iviews :: MonadReader s m => IndexedGetting i r s a -> i -> a -> r -> m r -- | View the index and value of an IndexedGetter into the current -- environment as a pair. -- -- When applied to an IndexedFold the result will most likely be a -- nonsensical monoidal summary of the indices tupled with a monoidal -- summary of the values and probably not whatever it is you wanted. iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a) -- | This is a generalized form of listen that only extracts the -- portion of the log that is focused on by a Getter. If given a -- Fold or a Traversal then a monoidal summary of the parts -- of the log that are visited will be returned. -- --
--   ilistenings :: MonadWriter w m             => IndexedGetter w u     -> (i -> u -> v) -> m a -> m (a, v)
--   ilistenings :: MonadWriter w m             => IndexedLens' w u      -> (i -> u -> v) -> m a -> m (a, v)
--   ilistenings :: (MonadWriter w m, Monoid v) => IndexedFold w u       -> (i -> u -> v) -> m a -> m (a, v)
--   ilistenings :: (MonadWriter w m, Monoid v) => IndexedTraversal' w u -> (i -> u -> v) -> m a -> m (a, v)
--   
ilistenings :: MonadWriter w m => IndexedGetting i v w u -> i -> u -> v -> m a -> m (a, v) -- | This is a generalized form of listen that only extracts the -- portion of the log that is focused on by a Getter. If given a -- Fold or a Traversal then a monoidal summary of the parts -- of the log that are visited will be returned. -- --
--   listenings :: MonadWriter w m             => Getter w u     -> (u -> v) -> m a -> m (a, v)
--   listenings :: MonadWriter w m             => Lens' w u      -> (u -> v) -> m a -> m (a, v)
--   listenings :: MonadWriter w m             => Iso' w u       -> (u -> v) -> m a -> m (a, v)
--   listenings :: (MonadWriter w m, Monoid v) => Fold w u       -> (u -> v) -> m a -> m (a, v)
--   listenings :: (MonadWriter w m, Monoid v) => Traversal' w u -> (u -> v) -> m a -> m (a, v)
--   listenings :: (MonadWriter w m, Monoid v) => Prism' w u     -> (u -> v) -> m a -> m (a, v)
--   
listenings :: MonadWriter w m => Getting v w u -> u -> v -> m a -> m (a, v) -- | This is a generalized form of listen that only extracts the -- portion of the log that is focused on by a Getter. If given a -- Fold or a Traversal then a monoidal summary of the parts -- of the log that are visited will be returned. -- --
--   ilistening :: MonadWriter w m             => IndexedGetter i w u     -> m a -> m (a, (i, u))
--   ilistening :: MonadWriter w m             => IndexedLens' i w u      -> m a -> m (a, (i, u))
--   ilistening :: (MonadWriter w m, Monoid u) => IndexedFold i w u       -> m a -> m (a, (i, u))
--   ilistening :: (MonadWriter w m, Monoid u) => IndexedTraversal' i w u -> m a -> m (a, (i, u))
--   
ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u)) -- | This is a generalized form of listen that only extracts the -- portion of the log that is focused on by a Getter. If given a -- Fold or a Traversal then a monoidal summary of the parts -- of the log that are visited will be returned. -- --
--   listening :: MonadWriter w m             => Getter w u     -> m a -> m (a, u)
--   listening :: MonadWriter w m             => Lens' w u      -> m a -> m (a, u)
--   listening :: MonadWriter w m             => Iso' w u       -> m a -> m (a, u)
--   listening :: (MonadWriter w m, Monoid u) => Fold w u       -> m a -> m (a, u)
--   listening :: (MonadWriter w m, Monoid u) => Traversal' w u -> m a -> m (a, u)
--   listening :: (MonadWriter w m, Monoid u) => Prism' w u     -> m a -> m (a, u)
--   
listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u) -- | Use the target of a Lens, Iso or Getter in the -- current state, or use a summary of a Fold or Traversal -- that points to a monoidal value. -- --
--   >>> evalState (uses _1 length) ("hello","world")
--   5
--   
-- --
--   uses :: MonadState s m             => Getter s a     -> (a -> r) -> m r
--   uses :: (MonadState s m, Monoid r) => Fold s a       -> (a -> r) -> m r
--   uses :: MonadState s m             => Lens' s a      -> (a -> r) -> m r
--   uses :: MonadState s m             => Iso' s a       -> (a -> r) -> m r
--   uses :: (MonadState s m, Monoid r) => Traversal' s a -> (a -> r) -> m r
--   
-- --
--   uses :: MonadState s m => Getting r s t a b -> (a -> r) -> m r
--   
uses :: MonadState s m => LensLike' (Const r :: * -> *) s a -> a -> r -> m r -- | Use the target of a Lens, Iso, or Getter in the -- current state, or use a summary of a Fold or Traversal -- that points to a monoidal value. -- --
--   >>> evalState (use _1) (a,b)
--   a
--   
-- --
--   >>> evalState (use _1) ("hello","world")
--   "hello"
--   
-- --
--   use :: MonadState s m             => Getter s a     -> m a
--   use :: (MonadState s m, Monoid r) => Fold s r       -> m r
--   use :: MonadState s m             => Iso' s a       -> m a
--   use :: MonadState s m             => Lens' s a      -> m a
--   use :: (MonadState s m, Monoid r) => Traversal' s r -> m r
--   
use :: MonadState s m => Getting a s a -> m a -- | View the value pointed to by a Getter or Lens or the -- result of folding over all the results of a Fold or -- Traversal that points at a monoidal values. -- -- This is the same operation as view with the arguments flipped. -- -- The fixity and semantics are such that subsequent field accesses can -- be performed with (.). -- --
--   >>> (a,b)^._2
--   b
--   
-- --
--   >>> ("hello","world")^._2
--   "world"
--   
-- --
--   >>> import Data.Complex
--   
--   >>> ((0, 1 :+ 2), 3)^._1._2.to magnitude
--   2.23606797749979
--   
-- --
--   (^.) ::             s -> Getter s a     -> a
--   (^.) :: Monoid m => s -> Fold s m       -> m
--   (^.) ::             s -> Iso' s a       -> a
--   (^.) ::             s -> Lens' s a      -> a
--   (^.) :: Monoid m => s -> Traversal' s m -> m
--   
(^.) :: () => s -> Getting a s a -> a infixl 8 ^. -- | View a function of the value pointed to by a Getter or -- Lens or the result of folding over the result of mapping the -- targets of a Fold or Traversal. -- --
--   views l f ≡ view (l . to f)
--   
-- --
--   >>> views (to f) g a
--   g (f a)
--   
-- --
--   >>> views _2 length (1,"hello")
--   5
--   
-- -- As views is commonly used to access the target of a -- Getter or obtain a monoidal summary of the targets of a -- Fold, It may be useful to think of it as having one of these -- more restricted signatures: -- --
--   views ::             Getter s a     -> (a -> r) -> s -> r
--   views :: Monoid m => Fold s a       -> (a -> m) -> s -> m
--   views ::             Iso' s a       -> (a -> r) -> s -> r
--   views ::             Lens' s a      -> (a -> r) -> s -> r
--   views :: Monoid m => Traversal' s a -> (a -> m) -> s -> m
--   
-- -- In a more general setting, such as when working with a Monad -- transformer stack you can use: -- --
--   views :: MonadReader s m             => Getter s a     -> (a -> r) -> m r
--   views :: (MonadReader s m, Monoid r) => Fold s a       -> (a -> r) -> m r
--   views :: MonadReader s m             => Iso' s a       -> (a -> r) -> m r
--   views :: MonadReader s m             => Lens' s a      -> (a -> r) -> m r
--   views :: (MonadReader s m, Monoid r) => Traversal' s a -> (a -> r) -> m r
--   
-- --
--   views :: MonadReader s m => Getting r s a -> (a -> r) -> m r
--   
views :: MonadReader s m => LensLike' (Const r :: * -> *) s a -> a -> r -> m r -- | View the value pointed to by a Getter, Iso or -- Lens or the result of folding over all the results of a -- Fold or Traversal that points at a monoidal value. -- --
--   view . toid
--   
-- --
--   >>> view (to f) a
--   f a
--   
-- --
--   >>> view _2 (1,"hello")
--   "hello"
--   
-- --
--   >>> view (to succ) 5
--   6
--   
-- --
--   >>> view (_2._1) ("hello",("world","!!!"))
--   "world"
--   
-- -- As view is commonly used to access the target of a -- Getter or obtain a monoidal summary of the targets of a -- Fold, It may be useful to think of it as having one of these -- more restricted signatures: -- --
--   view ::             Getter s a     -> s -> a
--   view :: Monoid m => Fold s m       -> s -> m
--   view ::             Iso' s a       -> s -> a
--   view ::             Lens' s a      -> s -> a
--   view :: Monoid m => Traversal' s m -> s -> m
--   
-- -- In a more general setting, such as when working with a Monad -- transformer stack you can use: -- --
--   view :: MonadReader s m             => Getter s a     -> m a
--   view :: (MonadReader s m, Monoid a) => Fold s a       -> m a
--   view :: MonadReader s m             => Iso' s a       -> m a
--   view :: MonadReader s m             => Lens' s a      -> m a
--   view :: (MonadReader s m, Monoid a) => Traversal' s a -> m a
--   
view :: MonadReader s m => Getting a s a -> m a -- |
--   ilike :: i -> a -> IndexedGetter i s a
--   
ilike :: (Indexable i p, Contravariant f, Functor f) => i -> a -> Over' p f s a -- | Build an constant-valued (index-preserving) Getter from an -- arbitrary Haskell value. -- --
--   like a . like b ≡ like b
--   a ^. like b ≡ b
--   a ^. like b ≡ a ^. to (const b)
--   
-- -- This can be useful as a second case failing a Fold -- e.g. foo failing like 0 -- --
--   like :: a -> IndexPreservingGetter s a
--   
like :: (Profunctor p, Contravariant f, Functor f) => a -> Optic' p f s a -- |
--   ito :: (s -> (i, a)) -> IndexedGetter i s a
--   
ito :: (Indexable i p, Contravariant f) => s -> (i, a) -> Over' p f s a -- | Build an (index-preserving) Getter from an arbitrary Haskell -- function. -- --
--   to f . to g ≡ to (g . f)
--   
-- --
--   a ^. to f ≡ f a
--   
-- --
--   >>> a ^.to f
--   f a
--   
-- --
--   >>> ("hello","world")^.to snd
--   "world"
--   
-- --
--   >>> 5^.to succ
--   6
--   
-- --
--   >>> (0, -5)^._2.to abs
--   5
--   
-- --
--   to :: (s -> a) -> IndexPreservingGetter s a
--   
to :: (Profunctor p, Contravariant f) => s -> a -> Optic' p f s a -- | When you see this in a type signature it indicates that you can pass -- the function a Lens, Getter, Traversal, -- Fold, Prism, Iso, or one of the indexed variants, -- and it will just "do the right thing". -- -- Most Getter combinators are able to be used with both a -- Getter or a Fold in limited situations, to do so, they -- need to be monomorphic in what we are going to extract with -- Const. To be compatible with Lens, Traversal and -- Iso we also restricted choices of the irrelevant t and -- b parameters. -- -- If a function accepts a Getting r s a, then when -- r is a Monoid, then you can pass a Fold (or -- Traversal), otherwise you can only pass this a Getter or -- Lens. type Getting r s a = a -> Const r a -> s -> Const r s -- | Used to consume an IndexedFold. type IndexedGetting i m s a = Indexed i a Const m a -> s -> Const m s -- | This is a convenient alias used when consuming (indexed) getters and -- (indexed) folds in a highly general fashion. type Accessing (p :: * -> * -> *) m s a = p a Const m a -> s -> Const m s -- | Strict version of _19 _19' :: Field19 s t a b => Lens s t a b -- | Strict version of _18 _18' :: Field18 s t a b => Lens s t a b -- | Strict version of _17 _17' :: Field17 s t a b => Lens s t a b -- | Strict version of _16 _16' :: Field16 s t a b => Lens s t a b -- | Strict version of _15 _15' :: Field15 s t a b => Lens s t a b -- | Strict version of _14 _14' :: Field14 s t a b => Lens s t a b -- | Strict version of _13 _13' :: Field13 s t a b => Lens s t a b -- | Strict version of _12 _12' :: Field12 s t a b => Lens s t a b -- | Strict version of _11 _11' :: Field11 s t a b => Lens s t a b -- | Strict version of _10 _10' :: Field10 s t a b => Lens s t a b -- | Strict version of _9 _9' :: Field9 s t a b => Lens s t a b -- | Strict version of _8 _8' :: Field8 s t a b => Lens s t a b -- | Strict version of _7 _7' :: Field7 s t a b => Lens s t a b -- | Strict version of _6 _6' :: Field6 s t a b => Lens s t a b -- | Strict version of _5 _5' :: Field5 s t a b => Lens s t a b -- | Strict version of _4 _4' :: Field4 s t a b => Lens s t a b -- | Strict version of _3 _3' :: Field3 s t a b => Lens s t a b -- | Strict version of _2 _2' :: Field2 s t a b => Lens s t a b -- | Strict version of _1 _1' :: Field1 s t a b => Lens s t a b -- | Provides access to 1st field of a tuple. class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 1st field of a tuple (and possibly change its type). -- --
--   >>> (1,2)^._1
--   1
--   
-- --
--   >>> _1 .~ "hello" $ (1,2)
--   ("hello",2)
--   
-- --
--   >>> (1,2) & _1 .~ "hello"
--   ("hello",2)
--   
-- --
--   >>> _1 putStrLn ("hello","world")
--   hello
--   ((),"world")
--   
-- -- This can also be used on larger tuples as well: -- --
--   >>> (1,2,3,4,5) & _1 +~ 41
--   (42,2,3,4,5)
--   
-- --
--   _1 :: Lens (a,b) (a',b) a a'
--   _1 :: Lens (a,b,c) (a',b,c) a a'
--   _1 :: Lens (a,b,c,d) (a',b,c,d) a a'
--   ...
--   _1 :: Lens (a,b,c,d,e,f,g,h,i) (a',b,c,d,e,f,g,h,i) a a'
--   
_1 :: Field1 s t a b => Lens s t a b -- | Provides access to the 2nd field of a tuple. class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 2nd field of a tuple. -- --
--   >>> _2 .~ "hello" $ (1,(),3,4)
--   (1,"hello",3,4)
--   
-- --
--   >>> (1,2,3,4) & _2 *~ 3
--   (1,6,3,4)
--   
-- --
--   >>> _2 print (1,2)
--   2
--   (1,())
--   
-- --
--   anyOf _2 :: (s -> Bool) -> (a, s) -> Bool
--   traverse . _2 :: (Applicative f, Traversable t) => (a -> f b) -> t (s, a) -> f (t (s, b))
--   foldMapOf (traverse . _2) :: (Traversable t, Monoid m) => (s -> m) -> t (b, s) -> m
--   
_2 :: Field2 s t a b => Lens s t a b -- | Provides access to the 3rd field of a tuple. class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 3rd field of a tuple. _3 :: Field3 s t a b => Lens s t a b -- | Provide access to the 4th field of a tuple. class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 4th field of a tuple. _4 :: Field4 s t a b => Lens s t a b -- | Provides access to the 5th field of a tuple. class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 5th field of a tuple. _5 :: Field5 s t a b => Lens s t a b -- | Provides access to the 6th element of a tuple. class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 6th field of a tuple. _6 :: Field6 s t a b => Lens s t a b -- | Provide access to the 7th field of a tuple. class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 7th field of a tuple. _7 :: Field7 s t a b => Lens s t a b -- | Provide access to the 8th field of a tuple. class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 8th field of a tuple. _8 :: Field8 s t a b => Lens s t a b -- | Provides access to the 9th field of a tuple. class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 9th field of a tuple. _9 :: Field9 s t a b => Lens s t a b -- | Provides access to the 10th field of a tuple. class Field10 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 10th field of a tuple. _10 :: Field10 s t a b => Lens s t a b -- | Provides access to the 11th field of a tuple. class Field11 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 11th field of a tuple. _11 :: Field11 s t a b => Lens s t a b -- | Provides access to the 12th field of a tuple. class Field12 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 12th field of a tuple. _12 :: Field12 s t a b => Lens s t a b -- | Provides access to the 13th field of a tuple. class Field13 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 13th field of a tuple. _13 :: Field13 s t a b => Lens s t a b -- | Provides access to the 14th field of a tuple. class Field14 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 14th field of a tuple. _14 :: Field14 s t a b => Lens s t a b -- | Provides access to the 15th field of a tuple. class Field15 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 15th field of a tuple. _15 :: Field15 s t a b => Lens s t a b -- | Provides access to the 16th field of a tuple. class Field16 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 16th field of a tuple. _16 :: Field16 s t a b => Lens s t a b -- | Provides access to the 17th field of a tuple. class Field17 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 17th field of a tuple. _17 :: Field17 s t a b => Lens s t a b -- | Provides access to the 18th field of a tuple. class Field18 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 18th field of a tuple. _18 :: Field18 s t a b => Lens s t a b -- | Provides access to the 19th field of a tuple. class Field19 s t a b | s -> a, t -> b, s b -> t, t a -> s -- | Access the 19th field of a tuple. _19 :: Field19 s t a b => Lens s t a b -- | Fuse a composition of lenses using Yoneda to provide -- fmap fusion. -- -- In general, given a pair of lenses foo and bar -- --
--   fusing (foo.bar) = foo.bar
--   
-- -- however, foo and bar are either going to fmap -- internally or they are trivial. -- -- fusing exploits the Yoneda lemma to merge these separate -- uses into a single fmap. -- -- This is particularly effective when the choice of functor f -- is unknown at compile time or when the Lens foo.bar in -- the above description is recursive or complex enough to prevent -- inlining. -- --
--   fusing :: Lens s t a b -> Lens s t a b
--   
fusing :: Functor f => LensLike Yoneda f s t a b -> LensLike f s t a b -- | We can always retrieve a () from any type. -- --
--   >>> "hello"^.united
--   ()
--   
-- --
--   >>> "hello" & united .~ ()
--   "hello"
--   
united :: Functor f => () -> f () -> a -> f a -- | There is a field for every type in the Void. Very zen. -- --
--   >>> [] & mapped.devoid +~ 1
--   []
--   
-- --
--   >>> Nothing & mapped.devoid %~ abs
--   Nothing
--   
-- --
--   devoid :: Lens' Void a
--   
devoid :: () => Over p f Void Void a b -- | A version of (<.=) that works on ALens. (<#=) :: MonadState s m => ALens s s a b -> b -> m b infix 4 <#= -- | A version of (<.~) that works on ALens. -- --
--   >>> ("hello","there") & _2 <#~ "world"
--   ("world",("hello","world"))
--   
(<#~) :: () => ALens s t a b -> b -> s -> (b, t) infixr 4 <#~ -- | A version of (%%=) that works on ALens. (#%%=) :: MonadState s m => ALens s s a b -> a -> (r, b) -> m r infix 4 #%%= -- | A version of (<%=) that works on ALens. (<#%=) :: MonadState s m => ALens s s a b -> a -> b -> m b infix 4 <#%= -- | A version of (<%~) that works on ALens. -- --
--   >>> ("hello","world") & _2 <#%~ length
--   (5,("hello",5))
--   
(<#%~) :: () => ALens s t a b -> a -> b -> s -> (b, t) infixr 4 <#%~ -- | A version of (%=) that works on ALens. (#%=) :: MonadState s m => ALens s s a b -> a -> b -> m () infix 4 #%= -- | A version of (.=) that works on ALens. (#=) :: MonadState s m => ALens s s a b -> b -> m () infix 4 #= -- | A version of (%%~) that works on ALens. -- --
--   >>> ("hello","world") & _2 #%%~ \x -> (length x, x ++ "!")
--   (5,("hello","world!"))
--   
(#%%~) :: Functor f => ALens s t a b -> a -> f b -> s -> f t infixr 4 #%%~ -- | A version of (%~) that works on ALens. -- --
--   >>> ("hello","world") & _2 #%~ length
--   ("hello",5)
--   
(#%~) :: () => ALens s t a b -> a -> b -> s -> t infixr 4 #%~ -- | A version of (.~) that works on ALens. -- --
--   >>> ("hello","there") & _2 #~ "world"
--   ("hello","world")
--   
(#~) :: () => ALens s t a b -> b -> s -> t infixr 4 #~ -- | A version of set that works on ALens. -- --
--   >>> storing _2 "world" ("hello","there")
--   ("hello","world")
--   
storing :: () => ALens s t a b -> b -> s -> t -- | A version of (^.) that works on ALens. -- --
--   >>> ("hello","world")^#_2
--   "world"
--   
(^#) :: () => s -> ALens s t a b -> a infixl 8 ^# -- | Adjust the target of an IndexedLens returning the old value, or -- adjust all of the targets of an IndexedTraversal within the -- current state, and return a monoidal summary of the old values. -- --
--   (<<%@=) :: MonadState s m                 => IndexedLens i s s a b      -> (i -> a -> b) -> m a
--   (<<%@=) :: (MonadState s m, Monoid b) => IndexedTraversal i s s a b -> (i -> a -> b) -> m a
--   
(<<%@=) :: MonadState s m => Over Indexed i (,) a s s a b -> i -> a -> b -> m a infix 4 <<%@= -- | Adjust the target of an IndexedLens returning the intermediate -- result, or adjust all of the targets of an IndexedTraversal -- within the current state, and return a monoidal summary of the -- intermediate results. -- --
--   (<%@=) :: MonadState s m                 => IndexedLens i s s a b      -> (i -> a -> b) -> m b
--   (<%@=) :: (MonadState s m, Monoid b) => IndexedTraversal i s s a b -> (i -> a -> b) -> m b
--   
(<%@=) :: MonadState s m => Over Indexed i (,) b s s a b -> i -> a -> b -> m b infix 4 <%@= -- | Adjust the target of an IndexedLens returning a supplementary -- result, or adjust all of the targets of an IndexedTraversal -- within the current state, and return a monoidal summary of the -- supplementary results. -- --
--   l %%@= f ≡ state (l %%@~ f)
--   
-- --
--   (%%@=) :: MonadState s m                 => IndexedLens i s s a b      -> (i -> a -> (r, b)) -> s -> m r
--   (%%@=) :: (MonadState s m, Monoid r) => IndexedTraversal i s s a b -> (i -> a -> (r, b)) -> s -> m r
--   
(%%@=) :: MonadState s m => Over Indexed i (,) r s s a b -> i -> a -> (r, b) -> m r infix 4 %%@= -- | Adjust the target of an IndexedLens returning a supplementary -- result, or adjust all of the targets of an IndexedTraversal and -- return a monoidal summary of the supplementary results and the answer. -- --
--   (%%@~) ≡ withIndex
--   
-- --
--   (%%@~) :: Functor f => IndexedLens i s t a b      -> (i -> a -> f b) -> s -> f t
--   (%%@~) :: Applicative f => IndexedTraversal i s t a b -> (i -> a -> f b) -> s -> f t
--   
-- -- In particular, it is often useful to think of this function as having -- one of these even more restricted type signatures: -- --
--   (%%@~) ::             IndexedLens i s t a b      -> (i -> a -> (r, b)) -> s -> (r, t)
--   (%%@~) :: Monoid r => IndexedTraversal i s t a b -> (i -> a -> (r, b)) -> s -> (r, t)
--   
(%%@~) :: () => Over Indexed i f s t a b -> i -> a -> f b -> s -> f t infixr 4 %%@~ -- | Adjust the target of an IndexedLens returning the old value, or -- adjust all of the targets of an IndexedTraversal and return a -- monoidal summary of the old values along with the answer. -- --
--   (<<%@~) ::             IndexedLens i s t a b      -> (i -> a -> b) -> s -> (a, t)
--   (<<%@~) :: Monoid a => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> (a, t)
--   
(<<%@~) :: () => Over Indexed i (,) a s t a b -> i -> a -> b -> s -> (a, t) infixr 4 <<%@~ -- | Adjust the target of an IndexedLens returning the intermediate -- result, or adjust all of the targets of an IndexedTraversal and -- return a monoidal summary along with the answer. -- --
--   l <%~ f ≡ l <%@~ const f
--   
-- -- When you do not need access to the index then (<%~) is more -- liberal in what it can accept. -- -- If you do not need the intermediate result, you can use (%@~) -- or even (%~). -- --
--   (<%@~) ::             IndexedLens i s t a b      -> (i -> a -> b) -> s -> (b, t)
--   (<%@~) :: Monoid b => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> (b, t)
--   
(<%@~) :: () => Over Indexed i (,) b s t a b -> i -> a -> b -> s -> (b, t) infixr 4 <%@~ -- | over for Arrows. -- -- Unlike over, overA can't accept a simple Setter, -- but requires a full lens, or close enough. -- --
--   >>> overA _1 ((+1) *** (+2)) ((1,2),6)
--   ((2,4),6)
--   
-- --
--   overA :: Arrow ar => Lens s t a b -> ar a b -> ar s t
--   
overA :: Arrow ar => LensLike Context a b s t a b -> ar a b -> ar s t -- | mappend a monoidal value onto the end of the target of a -- Lens into your Monad's state and return the result. -- -- When you do not need the result of the operation, (<>=) -- is more flexible. (<<>=) :: (MonadState s m, Monoid r) => LensLike' (,) r s r -> r -> m r infix 4 <<>= -- | mappend a monoidal value onto the end of the target of a -- Lens and return the result. -- -- When you do not need the result of the operation, (<>~) -- is more flexible. (<<>~) :: Monoid m => LensLike (,) m s t m m -> m -> s -> (m, t) infixr 4 <<>~ -- | Run a monadic action, and set the target of Lens to its result. -- --
--   (<<~) :: MonadState s m => Iso s s a b   -> m b -> m b
--   (<<~) :: MonadState s m => Lens s s a b  -> m b -> m b
--   
-- -- NB: This is limited to taking an actual Lens than admitting a -- Traversal because there are potential loss of state issues -- otherwise. (<<~) :: MonadState s m => ALens s s a b -> m b -> m b infixr 2 <<~ -- | Modify the target of a Lens into your Monad's state by -- mappending a value and return the old value that was -- replaced. -- -- When you do not need the result of the operation, (<>=) -- is more flexible. -- --
--   (<<<>=) :: (MonadState s m, Monoid r) => Lens' s r -> r -> m r
--   (<<<>=) :: (MonadState s m, Monoid r) => Iso' s r -> r -> m r
--   
(<<<>=) :: (MonadState s m, Monoid r) => LensLike' (,) r s r -> r -> m r infix 4 <<<>= -- | Modify the target of a Lens into your Monad's state by -- taking its logical && with a value and return the -- old value that was replaced. -- -- When you do not need the result of the operation, (&&=) -- is more flexible. -- --
--   (<<&&=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool
--   (<<&&=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool
--   
(<<&&=) :: MonadState s m => LensLike' (,) Bool s Bool -> Bool -> m Bool infix 4 <<&&= -- | Modify the target of a Lens into your Monad's state by -- taking its logical || with a value and return the old -- value that was replaced. -- -- When you do not need the result of the operation, (||=) is more -- flexible. -- --
--   (<<||=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool
--   (<<||=) :: MonadState s m => Iso' s Bool -> Bool -> m Bool
--   
(<<||=) :: MonadState s m => LensLike' (,) Bool s Bool -> Bool -> m Bool infix 4 <<||= -- | Modify the target of a Lens into your Monad's state by -- raising it by an arbitrary power and return the old value that -- was replaced. -- -- When you do not need the result of the operation, (**=) is more -- flexible. -- --
--   (<<**=) :: (MonadState s m, Floating a) => Lens' s a -> a -> m a
--   (<<**=) :: (MonadState s m, Floating a) => Iso' s a -> a -> m a
--   
(<<**=) :: (MonadState s m, Floating a) => LensLike' (,) a s a -> a -> m a infix 4 <<**= -- | Modify the target of a Lens into your Monad's state by -- raising it by an integral power and return the old value that -- was replaced. -- -- When you do not need the result of the operation, (^^=) is more -- flexible. -- --
--   (<<^^=) :: (MonadState s m, Fractional a, Integral e) => Lens' s a -> e -> m a
--   (<<^^=) :: (MonadState s m, Fractional a, Integral e) => Iso' s a -> e -> m a
--   
(<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' (,) a s a -> e -> m a infix 4 <<^^= -- | Modify the target of a Lens into your Monad's state by -- raising it by a non-negative power and return the old value -- that was replaced. -- -- When you do not need the result of the operation, (^=) is more -- flexible. -- --
--   (<<^=) :: (MonadState s m, Num a, Integral e) => Lens' s a -> e -> m a
--   (<<^=) :: (MonadState s m, Num a, Integral e) => Iso' s a -> a -> m a
--   
(<<^=) :: (MonadState s m, Num a, Integral e) => LensLike' (,) a s a -> e -> m a infix 4 <<^= -- | Modify the target of a Lens into your Monads state by -- dividing by a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (//=) is more -- flexible. -- --
--   (<<//=) :: (MonadState s m, Fractional a) => Lens' s a -> a -> m a
--   (<<//=) :: (MonadState s m, Fractional a) => Iso' s a -> a -> m a
--   
(< LensLike' (,) a s a -> a -> m a infix 4 <Lens into your Monad's state by -- multipling a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (*=) is more -- flexible. -- --
--   (<<*=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a
--   (<<*=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a
--   
(<<*=) :: (MonadState s m, Num a) => LensLike' (,) a s a -> a -> m a infix 4 <<*= -- | Modify the target of a Lens into your Monad's state by -- subtracting a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (-=) is more -- flexible. -- --
--   (<<-=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a
--   (<<-=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a
--   
(<<-=) :: (MonadState s m, Num a) => LensLike' (,) a s a -> a -> m a infix 4 <<-= -- | Modify the target of a Lens into your Monad's state by -- adding a value and return the old value that was replaced. -- -- When you do not need the result of the operation, (+=) is more -- flexible. -- --
--   (<<+=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a
--   (<<+=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a
--   
(<<+=) :: (MonadState s m, Num a) => LensLike' (,) a s a -> a -> m a infix 4 <<+= -- | Replace the target of a Lens into your Monad's state -- with Just a user supplied value and return the old value -- that was replaced. -- -- When applied to a Traversal, this will return a monoidal -- summary of all of the old values present. -- -- When you do not need the result of the operation, (?=) is more -- flexible. -- --
--   (<<?=) :: MonadState s m             => Lens s t a (Maybe b)      -> b -> m a
--   (<<?=) :: MonadState s m             => Iso s t a (Maybe b)       -> b -> m a
--   (<<?=) :: (MonadState s m, Monoid a) => Traversal s t a (Maybe b) -> b -> m a
--   
(< LensLike (,) a s s a Maybe b -> b -> m a infix 4 <Lens into your Monad's state -- with a user supplied value and return the old value that was -- replaced. -- -- When applied to a Traversal, this will return a monoidal -- summary of all of the old values present. -- -- When you do not need the result of the operation, (.=) is more -- flexible. -- --
--   (<<.=) :: MonadState s m             => Lens' s a      -> a -> m a
--   (<<.=) :: MonadState s m             => Iso' s a       -> a -> m a
--   (<<.=) :: (MonadState s m, Monoid a) => Traversal' s a -> a -> m a
--   
(<<.=) :: MonadState s m => LensLike (,) a s s a b -> b -> m a infix 4 <<.= -- | Modify the target of a Lens into your Monad's state by -- a user supplied function and return the old value that was -- replaced. -- -- When applied to a Traversal, this will return a monoidal -- summary of all of the old values present. -- -- When you do not need the result of the operation, (%=) is more -- flexible. -- --
--   (<<%=) :: MonadState s m             => Lens' s a      -> (a -> a) -> m a
--   (<<%=) :: MonadState s m             => Iso' s a       -> (a -> a) -> m a
--   (<<%=) :: (MonadState s m, Monoid a) => Traversal' s a -> (a -> a) -> m a
--   
-- --
--   (<<%=) :: MonadState s m => LensLike ((,)a) s s a b -> (a -> b) -> m a
--   
(<<%=) :: (Strong p, MonadState s m) => Over p (,) a s s a b -> p a b -> m a infix 4 <<%= -- | Logically && a Boolean valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the operation, (&&=) -- is more flexible. -- --
--   (<&&=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool
--   (<&&=) :: MonadState s m => Iso' s Bool  -> Bool -> m Bool
--   
(<&&=) :: MonadState s m => LensLike' (,) Bool s Bool -> Bool -> m Bool infix 4 <&&= -- | Logically || a Boolean valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the operation, (||=) is more -- flexible. -- --
--   (<||=) :: MonadState s m => Lens' s Bool -> Bool -> m Bool
--   (<||=) :: MonadState s m => Iso' s Bool  -> Bool -> m Bool
--   
(<||=) :: MonadState s m => LensLike' (,) Bool s Bool -> Bool -> m Bool infix 4 <||= -- | Raise the target of a floating-point valued Lens into your -- Monad's state to an arbitrary power and return the result. -- -- When you do not need the result of the operation, (**=) is more -- flexible. -- --
--   (<**=) :: (MonadState s m, Floating a) => Lens' s a -> a -> m a
--   (<**=) :: (MonadState s m, Floating a) => Iso' s a -> a -> m a
--   
(<**=) :: (MonadState s m, Floating a) => LensLike' (,) a s a -> a -> m a infix 4 <**= -- | Raise the target of a fractionally valued Lens into your -- Monad's state to an Integral power and return the -- result. -- -- When you do not need the result of the operation, (^^=) is more -- flexible. -- --
--   (<^^=) :: (MonadState s m, Fractional b, Integral e) => Lens' s a -> e -> m a
--   (<^^=) :: (MonadState s m, Fractional b, Integral e) => Iso' s a  -> e -> m a
--   
(<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' (,) a s a -> e -> m a infix 4 <^^= -- | Raise the target of a numerically valued Lens into your -- Monad's state to a non-negative Integral power and -- return the result. -- -- When you do not need the result of the operation, (^=) is more -- flexible. -- --
--   (<^=) :: (MonadState s m, Num a, Integral e) => Lens' s a -> e -> m a
--   (<^=) :: (MonadState s m, Num a, Integral e) => Iso' s a -> e -> m a
--   
(<^=) :: (MonadState s m, Num a, Integral e) => LensLike' (,) a s a -> e -> m a infix 4 <^= -- | Divide the target of a fractionally valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the division, (//=) is more -- flexible. -- --
--   (<//=) :: (MonadState s m, Fractional a) => Lens' s a -> a -> m a
--   (<//=) :: (MonadState s m, Fractional a) => Iso' s a -> a -> m a
--   
( LensLike' (,) a s a -> a -> m a infix 4 Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the multiplication, (*=) is -- more flexible. -- --
--   (<*=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a
--   (<*=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a
--   
(<*=) :: (MonadState s m, Num a) => LensLike' (,) a s a -> a -> m a infix 4 <*= -- | Subtract from the target of a numerically valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the subtraction, (-=) is -- more flexible. -- --
--   (<-=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a
--   (<-=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a
--   
(<-=) :: (MonadState s m, Num a) => LensLike' (,) a s a -> a -> m a infix 4 <-= -- | Add to the target of a numerically valued Lens into your -- Monad's state and return the result. -- -- When you do not need the result of the addition, (+=) is more -- flexible. -- --
--   (<+=) :: (MonadState s m, Num a) => Lens' s a -> a -> m a
--   (<+=) :: (MonadState s m, Num a) => Iso' s a -> a -> m a
--   
(<+=) :: (MonadState s m, Num a) => LensLike' (,) a s a -> a -> m a infix 4 <+= -- | Modify the target of a Lens into your Monad's state by -- a user supplied function and return the result. -- -- When applied to a Traversal, it this will return a monoidal -- summary of all of the intermediate results. -- -- When you do not need the result of the operation, (%=) is more -- flexible. -- --
--   (<%=) :: MonadState s m             => Lens' s a      -> (a -> a) -> m a
--   (<%=) :: MonadState s m             => Iso' s a       -> (a -> a) -> m a
--   (<%=) :: (MonadState s m, Monoid a) => Traversal' s a -> (a -> a) -> m a
--   
(<%=) :: MonadState s m => LensLike (,) b s s a b -> a -> b -> m b infix 4 <%= -- | Modify the target of a monoidally valued Lens by -- mappending a new value and return the old value. -- -- When you do not need the old value, (<>~) is more -- flexible. -- --
--   >>> (Sum a,b) & _1 <<<>~ Sum c
--   (Sum {getSum = a},(Sum {getSum = a + c},b))
--   
-- --
--   >>> _2 <<<>~ ", 007" $ ("James", "Bond")
--   ("Bond",("James","Bond, 007"))
--   
-- --
--   (<<<>~) :: Monoid r => Lens' s r -> r -> s -> (r, s)
--   (<<<>~) :: Monoid r => Iso' s r -> r -> s -> (r, s)
--   
(<<<>~) :: Monoid r => LensLike' (,) r s r -> r -> s -> (r, s) infixr 4 <<<>~ -- | Logically && the target of a Bool-valued -- Lens and return the old value. -- -- When you do not need the old value, (&&~) is more -- flexible. -- --
--   >>> (False,6) & _1 <<&&~ True
--   (False,(False,6))
--   
-- --
--   >>> ("hello",True) & _2 <<&&~ False
--   (True,("hello",False))
--   
-- --
--   (<<&&~) :: Lens' s Bool -> Bool -> s -> (Bool, s)
--   (<<&&~) :: Iso' s Bool -> Bool -> s -> (Bool, s)
--   
(<<&&~) :: () => LensLike' (,) Bool s Bool -> Bool -> s -> (Bool, s) infixr 4 <<&&~ -- | Logically || the target of a Bool-valued Lens and -- return the old value. -- -- When you do not need the old value, (||~) is more flexible. -- --
--   >>> (False,6) & _1 <<||~ True
--   (False,(True,6))
--   
-- --
--   >>> ("hello",True) & _2 <<||~ False
--   (True,("hello",True))
--   
-- --
--   (<<||~) :: Lens' s Bool -> Bool -> s -> (Bool, s)
--   (<<||~) :: Iso' s Bool -> Bool -> s -> (Bool, s)
--   
(<<||~) :: () => LensLike' (,) Bool s Bool -> Bool -> s -> (Bool, s) infixr 4 <<||~ -- | Raise the target of a floating-point valued Lens to an -- arbitrary power and return the old value. -- -- When you do not need the old value, (**~) is more flexible. -- --
--   >>> (a,b) & _1 <<**~ c
--   (a,(a**c,b))
--   
-- --
--   >>> (a,b) & _2 <<**~ c
--   (b,(a,b**c))
--   
-- --
--   (<<**~) :: Floating a => Lens' s a -> a -> s -> (a, s)
--   (<<**~) :: Floating a => Iso' s a -> a -> s -> (a, s)
--   
(<<**~) :: Floating a => LensLike' (,) a s a -> a -> s -> (a, s) infixr 4 <<**~ -- | Raise the target of a fractionally valued Lens to an integral -- power and return the old value. -- -- When you do not need the old value, (^^~) is more flexible. -- --
--   (<<^^~) :: (Fractional a, Integral e) => Lens' s a -> e -> s -> (a, s)
--   (<<^^~) :: (Fractional a, Integral e) => Iso' s a -> e -> S -> (a, s)
--   
(<<^^~) :: (Fractional a, Integral e) => LensLike' (,) a s a -> e -> s -> (a, s) infixr 4 <<^^~ -- | Raise the target of a numerically valued Lens to a non-negative -- power and return the old value. -- -- When you do not need the old value, (^~) is more flexible. -- --
--   (<<^~) :: (Num a, Integral e) => Lens' s a -> e -> s -> (a, s)
--   (<<^~) :: (Num a, Integral e) => Iso' s a -> e -> s -> (a, s)
--   
(<<^~) :: (Num a, Integral e) => LensLike' (,) a s a -> e -> s -> (a, s) infixr 4 <<^~ -- | Divide the target of a numerically valued Lens and return the -- old value. -- -- When you do not need the old value, (//~) is more flexible. -- --
--   >>> (a,b) & _1 <<//~ c
--   (a,(a / c,b))
--   
-- --
--   >>> ("Hawaii",10) & _2 <<//~ 2
--   (10.0,("Hawaii",5.0))
--   
-- --
--   (<<//~) :: Fractional a => Lens' s a -> a -> s -> (a, s)
--   (<<//~) :: Fractional a => Iso' s a -> a -> s -> (a, s)
--   
(< LensLike' (,) a s a -> a -> s -> (a, s) infixr 4 <Lens and return the -- old value. -- -- When you do not need the old value, (-~) is more flexible. -- --
--   >>> (a,b) & _1 <<*~ c
--   (a,(a * c,b))
--   
-- --
--   >>> (a,b) & _2 <<*~ c
--   (b,(a,b * c))
--   
-- --
--   (<<*~) :: Num a => Lens' s a -> a -> s -> (a, s)
--   (<<*~) :: Num a => Iso' s a -> a -> s -> (a, s)
--   
(<<*~) :: Num a => LensLike' (,) a s a -> a -> s -> (a, s) infixr 4 <<*~ -- | Decrement the target of a numerically valued Lens and return -- the old value. -- -- When you do not need the old value, (-~) is more flexible. -- --
--   >>> (a,b) & _1 <<-~ c
--   (a,(a - c,b))
--   
-- --
--   >>> (a,b) & _2 <<-~ c
--   (b,(a,b - c))
--   
-- --
--   (<<-~) :: Num a => Lens' s a -> a -> s -> (a, s)
--   (<<-~) :: Num a => Iso' s a -> a -> s -> (a, s)
--   
(<<-~) :: Num a => LensLike' (,) a s a -> a -> s -> (a, s) infixr 4 <<-~ -- | Increment the target of a numerically valued Lens and return -- the old value. -- -- When you do not need the old value, (+~) is more flexible. -- --
--   >>> (a,b) & _1 <<+~ c
--   (a,(a + c,b))
--   
-- --
--   >>> (a,b) & _2 <<+~ c
--   (b,(a,b + c))
--   
-- --
--   (<<+~) :: Num a => Lens' s a -> a -> s -> (a, s)
--   (<<+~) :: Num a => Iso' s a -> a -> s -> (a, s)
--   
(<<+~) :: Num a => LensLike' (,) a s a -> a -> s -> (a, s) infixr 4 <<+~ -- | Replace the target of a Lens with a Just value, but -- return the old value. -- -- If you do not need the old value (?~) is more flexible. -- --
--   >>> import Data.Map as Map
--   
--   >>> _2.at "hello" <<?~ "world" $ (42,Map.fromList [("goodnight","gracie")])
--   (Nothing,(42,fromList [("goodnight","gracie"),("hello","world")]))
--   
-- --
--   (<<?~) :: Iso s t a (Maybe b)       -> b -> s -> (a, t)
--   (<<?~) :: Lens s t a (Maybe b)      -> b -> s -> (a, t)
--   (<<?~) :: Traversal s t a (Maybe b) -> b -> s -> (a, t)
--   
(< LensLike (,) a s t a Maybe b -> b -> s -> (a, t) infixr 4 <Lens, but return the old value. -- -- When you do not need the old value, (.~) is more flexible. -- --
--   (<<.~) ::             Lens s t a b      -> b -> s -> (a, t)
--   (<<.~) ::             Iso s t a b       -> b -> s -> (a, t)
--   (<<.~) :: Monoid a => Traversal s t a b -> b -> s -> (a, t)
--   
(<<.~) :: () => LensLike (,) a s t a b -> b -> s -> (a, t) infixr 4 <<.~ -- | Modify the target of a Lens, but return the old value. -- -- When you do not need the old value, (%~) is more flexible. -- --
--   (<<%~) ::             Lens s t a b      -> (a -> b) -> s -> (a, t)
--   (<<%~) ::             Iso s t a b       -> (a -> b) -> s -> (a, t)
--   (<<%~) :: Monoid a => Traversal s t a b -> (a -> b) -> s -> (a, t)
--   
(<<%~) :: () => LensLike (,) a s t a b -> a -> b -> s -> (a, t) infixr 4 <<%~ -- | Logically && a Boolean valued Lens and return -- the result. -- -- When you do not need the result of the operation, (&&~) -- is more flexible. -- --
--   (<&&~) :: Lens' s Bool -> Bool -> s -> (Bool, s)
--   (<&&~) :: Iso' s Bool  -> Bool -> s -> (Bool, s)
--   
(<&&~) :: () => LensLike (,) Bool s t Bool Bool -> Bool -> s -> (Bool, t) infixr 4 <&&~ -- | Logically || a Boolean valued Lens and return the -- result. -- -- When you do not need the result of the operation, (||~) is more -- flexible. -- --
--   (<||~) :: Lens' s Bool -> Bool -> s -> (Bool, s)
--   (<||~) :: Iso' s Bool  -> Bool -> s -> (Bool, s)
--   
(<||~) :: () => LensLike (,) Bool s t Bool Bool -> Bool -> s -> (Bool, t) infixr 4 <||~ -- | Raise the target of a floating-point valued Lens to an -- arbitrary power and return the result. -- -- When you do not need the result of the operation, (**~) is more -- flexible. -- --
--   (<**~) :: Floating a => Lens' s a -> a -> s -> (a, s)
--   (<**~) :: Floating a => Iso' s a  -> a -> s -> (a, s)
--   
(<**~) :: Floating a => LensLike (,) a s t a a -> a -> s -> (a, t) infixr 4 <**~ -- | Raise the target of a fractionally valued Lens to an -- Integral power and return the result. -- -- When you do not need the result of the operation, (^^~) is more -- flexible. -- --
--   (<^^~) :: (Fractional a, Integral e) => Lens' s a -> e -> s -> (a, s)
--   (<^^~) :: (Fractional a, Integral e) => Iso' s a -> e -> s -> (a, s)
--   
(<^^~) :: (Fractional a, Integral e) => LensLike (,) a s t a a -> e -> s -> (a, t) infixr 4 <^^~ -- | Raise the target of a numerically valued Lens to a non-negative -- Integral power and return the result. -- -- When you do not need the result of the operation, (^~) is more -- flexible. -- --
--   (<^~) :: (Num a, Integral e) => Lens' s a -> e -> s -> (a, s)
--   (<^~) :: (Num a, Integral e) => Iso' s a -> e -> s -> (a, s)
--   
(<^~) :: (Num a, Integral e) => LensLike (,) a s t a a -> e -> s -> (a, t) infixr 4 <^~ -- | Divide the target of a fractionally valued Lens and return the -- result. -- -- When you do not need the result of the division, (//~) is more -- flexible. -- --
--   (<//~) :: Fractional a => Lens' s a -> a -> s -> (a, s)
--   (<//~) :: Fractional a => Iso'  s a -> a -> s -> (a, s)
--   
( LensLike (,) a s t a a -> a -> s -> (a, t) infixr 4 Lens and return the -- result. -- -- When you do not need the result of the multiplication, (*~) is -- more flexible. -- --
--   (<*~) :: Num a => Lens' s a -> a -> s -> (a, s)
--   (<*~) :: Num a => Iso'  s a -> a -> s -> (a, s)
--   
(<*~) :: Num a => LensLike (,) a s t a a -> a -> s -> (a, t) infixr 4 <*~ -- | Decrement the target of a numerically valued Lens and return -- the result. -- -- When you do not need the result of the subtraction, (-~) is -- more flexible. -- --
--   (<-~) :: Num a => Lens' s a -> a -> s -> (a, s)
--   (<-~) :: Num a => Iso' s a  -> a -> s -> (a, s)
--   
(<-~) :: Num a => LensLike (,) a s t a a -> a -> s -> (a, t) infixr 4 <-~ -- | Increment the target of a numerically valued Lens and return -- the result. -- -- When you do not need the result of the addition, (+~) is more -- flexible. -- --
--   (<+~) :: Num a => Lens' s a -> a -> s -> (a, s)
--   (<+~) :: Num a => Iso' s a  -> a -> s -> (a, s)
--   
(<+~) :: Num a => LensLike (,) a s t a a -> a -> s -> (a, t) infixr 4 <+~ -- | Modify the target of a Lens and return the result. -- -- When you do not need the result of the operation, (%~) is more -- flexible. -- --
--   (<%~) ::             Lens s t a b      -> (a -> b) -> s -> (b, t)
--   (<%~) ::             Iso s t a b       -> (a -> b) -> s -> (b, t)
--   (<%~) :: Monoid b => Traversal s t a b -> (a -> b) -> s -> (b, t)
--   
(<%~) :: () => LensLike (,) b s t a b -> a -> b -> s -> (b, t) infixr 4 <%~ -- | Clone an IndexedLens as an IndexedLens with the same -- index. cloneIndexedLens :: () => AnIndexedLens i s t a b -> IndexedLens i s t a b -- | Clone a Lens as an IndexedPreservingLens that just -- passes through whatever index is on any IndexedLens, -- IndexedFold, IndexedGetter or IndexedTraversal it -- is composed with. cloneIndexPreservingLens :: () => ALens s t a b -> IndexPreservingLens s t a b -- | Cloning a Lens is one way to make sure you aren't given -- something weaker, such as a Traversal and can be used as a way -- to pass around lenses that have to be monomorphic in f. -- -- Note: This only accepts a proper Lens. -- --
--   >>> let example l x = set (cloneLens l) (x^.cloneLens l + 1) x in example _2 ("hello",1,"you")
--   ("hello",2,"you")
--   
cloneLens :: () => ALens s t a b -> Lens s t a b -- | This Lens lets you view the current pos of -- any indexed store comonad and seek to a new position. This -- reduces the API for working these instances to a single Lens. -- --
--   ipos w ≡ w ^. locus
--   iseek s w ≡ w & locus .~ s
--   iseeks f w ≡ w & locus %~ f
--   
-- --
--   locus :: Lens' (Context' a s) a
--   locus :: Conjoined p => Lens' (Pretext' p a s) a
--   locus :: Conjoined p => Lens' (PretextT' p g a s) a
--   
locus :: IndexedComonadStore p => Lens p a c s p b c s a b -- | alongside makes a Lens from two other lenses or a -- Getter from two other getters by executing them on their -- respective halves of a product. -- --
--   >>> (Left a, Right b)^.alongside chosen chosen
--   (a,b)
--   
-- --
--   >>> (Left a, Right b) & alongside chosen chosen .~ (c,d)
--   (Left c,Right d)
--   
-- --
--   alongside :: Lens   s t a b -> Lens   s' t' a' b' -> Lens   (s,s') (t,t') (a,a') (b,b')
--   alongside :: Getter s   a   -> Getter s'    a'    -> Getter (s,s')        (a,a')
--   
alongside :: () => LensLike AlongsideLeft f b' s t a b -> LensLike AlongsideRight f t s' t' a' b' -> LensLike f (s, s') (t, t') (a, a') (b, b') -- | This is a Lens that updates either side of an Either, -- where both sides have the same type. -- --
--   chosenchoosing id id
--   
-- --
--   >>> Left a^.chosen
--   a
--   
-- --
--   >>> Right a^.chosen
--   a
--   
-- --
--   >>> Right "hello"^.chosen
--   "hello"
--   
-- --
--   >>> Right a & chosen *~ b
--   Right (a * b)
--   
-- --
--   chosen :: Lens (Either a a) (Either b b) a b
--   chosen f (Left a)  = Left <$> f a
--   chosen f (Right a) = Right <$> f a
--   
chosen :: (Conjoined p, Functor f) => p a f b -> p Either a a f Either b b -- | Merge two lenses, getters, setters, folds or traversals. -- --
--   chosenchoosing id id
--   
-- --
--   choosing :: Getter s a     -> Getter s' a     -> Getter (Either s s') a
--   choosing :: Fold s a       -> Fold s' a       -> Fold (Either s s') a
--   choosing :: Lens' s a      -> Lens' s' a      -> Lens' (Either s s') a
--   choosing :: Traversal' s a -> Traversal' s' a -> Traversal' (Either s s') a
--   choosing :: Setter' s a    -> Setter' s' a    -> Setter' (Either s s') a
--   
choosing :: Functor f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f Either s s' Either t t' a b -- | Lift a Lens so it can run under a function (or other -- corepresentable profunctor). -- --
--   inside :: Lens s t a b -> Lens (e -> s) (e -> t) (e -> a) (e -> b)
--   
-- --
--   >>> (\x -> (x-1,x+1)) ^. inside _1 $ 5
--   4
--   
-- --
--   >>> runState (modify (1:) >> modify (2:)) ^. (inside _2) $ []
--   [2,1]
--   
inside :: Corepresentable p => ALens s t a b -> Lens p e s p e t p e a p e b -- | This is convenient to flip argument order of composite -- functions defined as: -- --
--   fab ?? a = fmap ($ a) fab
--   
-- -- For the Functor instance f = ((->) r) you can -- reason about this function as if the definition was (??) ≡ -- flip: -- --
--   >>> (h ?? x) a
--   h a x
--   
-- --
--   >>> execState ?? [] $ modify (1:)
--   [1]
--   
-- --
--   >>> over _2 ?? ("hello","world") $ length
--   ("hello",5)
--   
-- --
--   >>> over ?? length ?? ("hello","world") $ _2
--   ("hello",5)
--   
(??) :: Functor f => f a -> b -> a -> f b infixl 1 ?? -- | Modify the target of a Lens in the current state returning some -- extra information of type r or modify all targets of a -- Traversal in the current state, extracting extra information of -- type r and return a monoidal summary of the changes. -- --
--   >>> runState (_1 %%= \x -> (f x, g x)) (a,b)
--   (f a,(g a,b))
--   
-- --
--   (%%=) ≡ (state .)
--   
-- -- It may be useful to think of (%%=), instead, as having either -- of the following more restricted type signatures: -- --
--   (%%=) :: MonadState s m             => Iso s s a b       -> (a -> (r, b)) -> m r
--   (%%=) :: MonadState s m             => Lens s s a b      -> (a -> (r, b)) -> m r
--   (%%=) :: (MonadState s m, Monoid r) => Traversal s s a b -> (a -> (r, b)) -> m r
--   
(%%=) :: MonadState s m => Over p (,) r s s a b -> p a (r, b) -> m r infix 4 %%= -- | (%%~) can be used in one of two scenarios: -- -- When applied to a Lens, it can edit the target of the -- Lens in a structure, extracting a functorial result. -- -- When applied to a Traversal, it can edit the targets of the -- traversals, extracting an applicative summary of its actions. -- --
--   >>> [66,97,116,109,97,110] & each %%~ \a -> ("na", chr a)
--   ("nananananana","Batman")
--   
-- -- For all that the definition of this combinator is just: -- --
--   (%%~) ≡ id
--   
-- -- It may be beneficial to think about it as if it had these even more -- restricted types, however: -- --
--   (%%~) :: Functor f =>     Iso s t a b       -> (a -> f b) -> s -> f t
--   (%%~) :: Functor f =>     Lens s t a b      -> (a -> f b) -> s -> f t
--   (%%~) :: Applicative f => Traversal s t a b -> (a -> f b) -> s -> f t
--   
-- -- When applied to a Traversal, it can edit the targets of the -- traversals, extracting a supplemental monoidal summary of its actions, -- by choosing f = ((,) m) -- --
--   (%%~) ::             Iso s t a b       -> (a -> (r, b)) -> s -> (r, t)
--   (%%~) ::             Lens s t a b      -> (a -> (r, b)) -> s -> (r, t)
--   (%%~) :: Monoid m => Traversal s t a b -> (a -> (m, b)) -> s -> (m, t)
--   
(%%~) :: () => LensLike f s t a b -> a -> f b -> s -> f t infixr 4 %%~ -- | This can be used to chain lens operations using op= syntax -- rather than op~ syntax for simple non-type-changing cases. -- --
--   >>> (10,20) & _1 .~ 30 & _2 .~ 40
--   (30,40)
--   
-- --
--   >>> (10,20) &~ do _1 .= 30; _2 .= 40
--   (30,40)
--   
-- -- This does not support type-changing assignment, e.g. -- --
--   >>> (10,20) & _1 .~ "hello"
--   ("hello",20)
--   
(&~) :: () => s -> State s a -> s infixl 1 &~ -- | Build an IndexedLens from a Getter and a Setter. ilens :: () => s -> (i, a) -> s -> b -> t -> IndexedLens i s t a b -- | Build an index-preserving Lens from a Getter and a -- Setter. iplens :: () => s -> a -> s -> b -> t -> IndexPreservingLens s t a b -- | Build a Lens from a getter and a setter. -- --
--   lens :: Functor f => (s -> a) -> (s -> b -> t) -> (a -> f b) -> s -> f t
--   
-- --
--   >>> s ^. lens getter setter
--   getter s
--   
-- --
--   >>> s & lens getter setter .~ b
--   setter s b
--   
-- --
--   >>> s & lens getter setter %~ f
--   setter s (f (getter s))
--   
-- --
--   lens :: (s -> a) -> (s -> a -> s) -> Lens' s a
--   
lens :: () => s -> a -> s -> b -> t -> Lens s t a b -- | When you see this as an argument to a function, it expects a -- Lens. -- -- This type can also be used when you need to store a Lens in a -- container, since it is rank-1. You can turn them back into a -- Lens with cloneLens, or use it directly with combinators -- like storing and (^#). type ALens s t a b = LensLike Pretext ((->) :: * -> * -> *) a b s t a b -- |
--   type ALens' = Simple ALens
--   
type ALens' s a = ALens s s a a -- | When you see this as an argument to a function, it expects an -- IndexedLens type AnIndexedLens i s t a b = Optical Indexed i ((->) :: * -> * -> *) Pretext Indexed i a b s t a b -- |
--   type AnIndexedLens' = Simple (AnIndexedLens i)
--   
type AnIndexedLens' i s a = AnIndexedLens i s s a a -- | Map with index. (Deprecated alias for iover). -- -- When you do not need access to the index, then mapOf is more -- liberal in what it can accept. -- --
--   mapOf l ≡ imapOf l . const
--   
-- --
--   imapOf :: IndexedSetter i s t a b    -> (i -> a -> b) -> s -> t
--   imapOf :: IndexedLens i s t a b      -> (i -> a -> b) -> s -> t
--   imapOf :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t
--   
imapOf :: () => AnIndexedSetter i s t a b -> i -> a -> b -> s -> t -- | mapOf is a deprecated alias for over. mapOf :: () => ASetter s t a b -> a -> b -> s -> t -- | Run an arrow command and use the output to set all the targets of a -- Lens, Setter or Traversal to the result. -- -- assignA can be used very similarly to (<~), except -- that the type of the object being modified can change; for example: -- --
--   runKleisli action ((), (), ()) where
--     action =      assignA _1 (Kleisli (const getVal1))
--              >>> assignA _2 (Kleisli (const getVal2))
--              >>> assignA _3 (Kleisli (const getVal3))
--     getVal1 :: Either String Int
--     getVal1 = ...
--     getVal2 :: Either String Bool
--     getVal2 = ...
--     getVal3 :: Either String Char
--     getVal3 = ...
--   
-- -- has the type Either String (Int, Bool, -- Char) -- --
--   assignA :: Arrow p => Iso s t a b       -> p s b -> p s t
--   assignA :: Arrow p => Lens s t a b      -> p s b -> p s t
--   assignA :: Arrow p => Traversal s t a b -> p s b -> p s t
--   assignA :: Arrow p => Setter s t a b    -> p s b -> p s t
--   
assignA :: Arrow p => ASetter s t a b -> p s b -> p s t -- | Replace every target in the current state of an IndexedSetter, -- IndexedLens or IndexedTraversal with access to the -- index. -- -- When you do not need access to the index then (.=) is more -- liberal in what it can accept. -- --
--   l .= b ≡ l .@= const b
--   
-- --
--   (.@=) :: MonadState s m => IndexedSetter i s s a b    -> (i -> b) -> m ()
--   (.@=) :: MonadState s m => IndexedLens i s s a b      -> (i -> b) -> m ()
--   (.@=) :: MonadState s m => IndexedTraversal i s t a b -> (i -> b) -> m ()
--   
(.@=) :: MonadState s m => AnIndexedSetter i s s a b -> i -> b -> m () infix 4 .@= -- | This is an alias for (%@=). imodifying :: MonadState s m => AnIndexedSetter i s s a b -> i -> a -> b -> m () -- | Adjust every target in the current state of an IndexedSetter, -- IndexedLens or IndexedTraversal with access to the -- index. -- -- When you do not need access to the index then (%=) is more -- liberal in what it can accept. -- --
--   l %= f ≡ l %@= const f
--   
-- --
--   (%@=) :: MonadState s m => IndexedSetter i s s a b    -> (i -> a -> b) -> m ()
--   (%@=) :: MonadState s m => IndexedLens i s s a b      -> (i -> a -> b) -> m ()
--   (%@=) :: MonadState s m => IndexedTraversal i s t a b -> (i -> a -> b) -> m ()
--   
(%@=) :: MonadState s m => AnIndexedSetter i s s a b -> i -> a -> b -> m () infix 4 %@= -- | Replace every target of an IndexedSetter, IndexedLens or -- IndexedTraversal with access to the index. -- --
--   (.@~) ≡ iset
--   
-- -- When you do not need access to the index then (.~) is more -- liberal in what it can accept. -- --
--   l .~ b ≡ l .@~ const b
--   
-- --
--   (.@~) :: IndexedSetter i s t a b    -> (i -> b) -> s -> t
--   (.@~) :: IndexedLens i s t a b      -> (i -> b) -> s -> t
--   (.@~) :: IndexedTraversal i s t a b -> (i -> b) -> s -> t
--   
(.@~) :: () => AnIndexedSetter i s t a b -> i -> b -> s -> t infixr 4 .@~ -- | Adjust every target of an IndexedSetter, IndexedLens or -- IndexedTraversal with access to the index. -- --
--   (%@~) ≡ iover
--   
-- -- When you do not need access to the index then (%~) is more -- liberal in what it can accept. -- --
--   l %~ f ≡ l %@~ const f
--   
-- --
--   (%@~) :: IndexedSetter i s t a b    -> (i -> a -> b) -> s -> t
--   (%@~) :: IndexedLens i s t a b      -> (i -> a -> b) -> s -> t
--   (%@~) :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t
--   
(%@~) :: () => AnIndexedSetter i s t a b -> i -> a -> b -> s -> t infixr 4 %@~ -- | Build an IndexedSetter from an imap-like function. -- -- Your supplied function f is required to satisfy: -- --
--   f idid
--   f g . f h ≡ f (g . h)
--   
-- -- Equational reasoning: -- --
--   isets . ioverid
--   iover . isetsid
--   
-- -- Another way to view isets is that it takes a "semantic editor -- combinator" which has been modified to carry an index and transforms -- it into a IndexedSetter. isets :: () => i -> a -> b -> s -> t -> IndexedSetter i s t a b -- | Set with index. Equivalent to iover with the current value -- ignored. -- -- When you do not need access to the index, then set is more -- liberal in what it can accept. -- --
--   set l ≡ iset l . const
--   
-- --
--   iset :: IndexedSetter i s t a b    -> (i -> b) -> s -> t
--   iset :: IndexedLens i s t a b      -> (i -> b) -> s -> t
--   iset :: IndexedTraversal i s t a b -> (i -> b) -> s -> t
--   
iset :: () => AnIndexedSetter i s t a b -> i -> b -> s -> t -- | Map with index. This is an alias for imapOf. -- -- When you do not need access to the index, then over is more -- liberal in what it can accept. -- --
--   over l ≡ iover l . const
--   iover l ≡ over l . Indexed
--   
-- --
--   iover :: IndexedSetter i s t a b    -> (i -> a -> b) -> s -> t
--   iover :: IndexedLens i s t a b      -> (i -> a -> b) -> s -> t
--   iover :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t
--   
iover :: () => AnIndexedSetter i s t a b -> i -> a -> b -> s -> t -- | This is a generalization of censor that alows you to -- censor just a portion of the resulting MonadWriter, with -- access to the index of an IndexedSetter. icensoring :: MonadWriter w m => IndexedSetter i w w u v -> i -> u -> v -> m a -> m a -- | This is a generalization of censor that alows you to -- censor just a portion of the resulting MonadWriter. censoring :: MonadWriter w m => Setter w w u v -> u -> v -> m a -> m a -- | This is a generalization of pass that alows you to modify just -- a portion of the resulting MonadWriter with access to the index -- of an IndexedSetter. ipassing :: MonadWriter w m => IndexedSetter i w w u v -> m (a, i -> u -> v) -> m a -- | This is a generalization of pass that alows you to modify just -- a portion of the resulting MonadWriter. passing :: MonadWriter w m => Setter w w u v -> m (a, u -> v) -> m a -- | Write to a fragment of a larger Writer format. scribe :: (MonadWriter t m, Monoid s) => ASetter s t a b -> b -> m () -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by mappending a value. -- --
--   >>> execState (do _1 <>= Sum c; _2 <>= Product d) (Sum a,Product b)
--   (Sum {getSum = a + c},Product {getProduct = b * d})
--   
-- --
--   >>> execState (both <>= "!!!") ("hello","world")
--   ("hello!!!","world!!!")
--   
-- --
--   (<>=) :: (MonadState s m, Monoid a) => Setter' s a -> a -> m ()
--   (<>=) :: (MonadState s m, Monoid a) => Iso' s a -> a -> m ()
--   (<>=) :: (MonadState s m, Monoid a) => Lens' s a -> a -> m ()
--   (<>=) :: (MonadState s m, Monoid a) => Traversal' s a -> a -> m ()
--   
(<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m () infix 4 <>= -- | Modify the target of a monoidally valued by mappending another -- value. -- --
--   >>> (Sum a,b) & _1 <>~ Sum c
--   (Sum {getSum = a + c},b)
--   
-- --
--   >>> (Sum a,Sum b) & both <>~ Sum c
--   (Sum {getSum = a + c},Sum {getSum = b + c})
--   
-- --
--   >>> both <>~ "!!!" $ ("hello","world")
--   ("hello!!!","world!!!")
--   
-- --
--   (<>~) :: Monoid a => Setter s t a a    -> a -> s -> t
--   (<>~) :: Monoid a => Iso s t a a       -> a -> s -> t
--   (<>~) :: Monoid a => Lens s t a a      -> a -> s -> t
--   (<>~) :: Monoid a => Traversal s t a a -> a -> s -> t
--   
(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t infixr 4 <>~ -- | Set Just a value with pass-through -- -- This is useful for chaining assignment without round-tripping through -- your Monad stack. -- --
--   do x <- at "foo" <?= ninety_nine_bottles_of_beer_on_the_wall
--   
-- -- If you do not need a copy of the intermediate result, then using l -- ?= d will avoid unused binding warnings. -- --
--   (<?=) :: MonadState s m => Setter s s a (Maybe b)    -> b -> m b
--   (<?=) :: MonadState s m => Iso s s a (Maybe b)       -> b -> m b
--   (<?=) :: MonadState s m => Lens s s a (Maybe b)      -> b -> m b
--   (<?=) :: MonadState s m => Traversal s s a (Maybe b) -> b -> m b
--   
( ASetter s s a Maybe b -> b -> m b infix 4 Monad stack. -- --
--   do x <- _2 <.= ninety_nine_bottles_of_beer_on_the_wall
--   
-- -- If you do not need a copy of the intermediate result, then using l -- .= d will avoid unused binding warnings. -- --
--   (<.=) :: MonadState s m => Setter s s a b    -> b -> m b
--   (<.=) :: MonadState s m => Iso s s a b       -> b -> m b
--   (<.=) :: MonadState s m => Lens s s a b      -> b -> m b
--   (<.=) :: MonadState s m => Traversal s s a b -> b -> m b
--   
(<.=) :: MonadState s m => ASetter s s a b -> b -> m b infix 4 <.= -- | Run a monadic action, and set all of the targets of a Lens, -- Setter or Traversal to its result. -- --
--   (<~) :: MonadState s m => Iso s s a b       -> m b -> m ()
--   (<~) :: MonadState s m => Lens s s a b      -> m b -> m ()
--   (<~) :: MonadState s m => Traversal s s a b -> m b -> m ()
--   (<~) :: MonadState s m => Setter s s a b    -> m b -> m ()
--   
-- -- As a reasonable mnemonic, this lets you store the result of a monadic -- action in a Lens rather than in a local variable. -- --
--   do foo <- bar
--      ...
--   
-- -- will store the result in a variable, while -- --
--   do foo <~ bar
--      ...
--   
-- -- will store the result in a Lens, Setter, or -- Traversal. (<~) :: MonadState s m => ASetter s s a b -> m b -> m () infixr 2 <~ -- | Modify the target(s) of a Lens', 'Iso, Setter or -- Traversal by taking their logical || with a value. -- --
--   >>> execState (do _1 ||= True; _2 ||= False; _3 ||= True; _4 ||= False) (True,True,False,False)
--   (True,True,True,False)
--   
-- --
--   (||=) :: MonadState s m => Setter' s Bool    -> Bool -> m ()
--   (||=) :: MonadState s m => Iso' s Bool       -> Bool -> m ()
--   (||=) :: MonadState s m => Lens' s Bool      -> Bool -> m ()
--   (||=) :: MonadState s m => Traversal' s Bool -> Bool -> m ()
--   
(||=) :: MonadState s m => ASetter' s Bool -> Bool -> m () infix 4 ||= -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by taking their logical && with a -- value. -- --
--   >>> execState (do _1 &&= True; _2 &&= False; _3 &&= True; _4 &&= False) (True,True,False,False)
--   (True,False,False,False)
--   
-- --
--   (&&=) :: MonadState s m => Setter' s Bool    -> Bool -> m ()
--   (&&=) :: MonadState s m => Iso' s Bool       -> Bool -> m ()
--   (&&=) :: MonadState s m => Lens' s Bool      -> Bool -> m ()
--   (&&=) :: MonadState s m => Traversal' s Bool -> Bool -> m ()
--   
(&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m () infix 4 &&= -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to an arbitrary power -- --
--   >>> execState (do _1 **= c; _2 **= d) (a,b)
--   (a**c,b**d)
--   
-- --
--   (**=) ::  (MonadState s m, Floating a) => Setter' s a    -> a -> m ()
--   (**=) ::  (MonadState s m, Floating a) => Iso' s a       -> a -> m ()
--   (**=) ::  (MonadState s m, Floating a) => Lens' s a      -> a -> m ()
--   (**=) ::  (MonadState s m, Floating a) => Traversal' s a -> a -> m ()
--   
(**=) :: (MonadState s m, Floating a) => ASetter' s a -> a -> m () infix 4 **= -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to an integral power. -- --
--   (^^=) ::  (MonadState s m, Fractional a, Integral e) => Setter' s a    -> e -> m ()
--   (^^=) ::  (MonadState s m, Fractional a, Integral e) => Iso' s a       -> e -> m ()
--   (^^=) ::  (MonadState s m, Fractional a, Integral e) => Lens' s a      -> e -> m ()
--   (^^=) ::  (MonadState s m, Fractional a, Integral e) => Traversal' s a -> e -> m ()
--   
(^^=) :: (MonadState s m, Fractional a, Integral e) => ASetter' s a -> e -> m () infix 4 ^^= -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to a non-negative integral power. -- --
--   (^=) ::  (MonadState s m, Num a, Integral e) => Setter' s a    -> e -> m ()
--   (^=) ::  (MonadState s m, Num a, Integral e) => Iso' s a       -> e -> m ()
--   (^=) ::  (MonadState s m, Num a, Integral e) => Lens' s a      -> e -> m ()
--   (^=) ::  (MonadState s m, Num a, Integral e) => Traversal' s a -> e -> m ()
--   
(^=) :: (MonadState s m, Num a, Integral e) => ASetter' s a -> e -> m () infix 4 ^= -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by dividing by a value. -- --
--   >>> execState (do _1 //= c; _2 //= d) (a,b)
--   (a / c,b / d)
--   
-- --
--   (//=) :: (MonadState s m, Fractional a) => Setter' s a    -> a -> m ()
--   (//=) :: (MonadState s m, Fractional a) => Iso' s a       -> a -> m ()
--   (//=) :: (MonadState s m, Fractional a) => Lens' s a      -> a -> m ()
--   (//=) :: (MonadState s m, Fractional a) => Traversal' s a -> a -> m ()
--   
(//=) :: (MonadState s m, Fractional a) => ASetter' s a -> a -> m () infix 4 //= -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by multiplying by value. -- --
--   >>> execState (do _1 *= c; _2 *= d) (a,b)
--   (a * c,b * d)
--   
-- --
--   (*=) :: (MonadState s m, Num a) => Setter' s a    -> a -> m ()
--   (*=) :: (MonadState s m, Num a) => Iso' s a       -> a -> m ()
--   (*=) :: (MonadState s m, Num a) => Lens' s a      -> a -> m ()
--   (*=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m ()
--   
(*=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 *= -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by subtracting a value. -- --
--   >>> execState (do _1 -= c; _2 -= d) (a,b)
--   (a - c,b - d)
--   
-- --
--   (-=) :: (MonadState s m, Num a) => Setter' s a    -> a -> m ()
--   (-=) :: (MonadState s m, Num a) => Iso' s a       -> a -> m ()
--   (-=) :: (MonadState s m, Num a) => Lens' s a      -> a -> m ()
--   (-=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m ()
--   
(-=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 -= -- | Modify the target(s) of a Lens', Iso, Setter or -- Traversal by adding a value. -- -- Example: -- --
--   fresh :: MonadState Int m => m Int
--   fresh = do
--     id += 1
--     use id
--   
-- --
--   >>> execState (do _1 += c; _2 += d) (a,b)
--   (a + c,b + d)
--   
-- --
--   >>> execState (do _1.at 1.non 0 += 10) (Map.fromList [(2,100)],"hello")
--   (fromList [(1,10),(2,100)],"hello")
--   
-- --
--   (+=) :: (MonadState s m, Num a) => Setter' s a    -> a -> m ()
--   (+=) :: (MonadState s m, Num a) => Iso' s a       -> a -> m ()
--   (+=) :: (MonadState s m, Num a) => Lens' s a      -> a -> m ()
--   (+=) :: (MonadState s m, Num a) => Traversal' s a -> a -> m ()
--   
(+=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 += -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state with -- Just a new value, irrespective of the old. -- --
--   >>> execState (do at 1 ?= a; at 2 ?= b) Map.empty
--   fromList [(1,a),(2,b)]
--   
-- --
--   >>> execState (do _1 ?= b; _2 ?= c) (Just a, Nothing)
--   (Just b,Just c)
--   
-- --
--   (?=) :: MonadState s m => Iso' s (Maybe a)       -> a -> m ()
--   (?=) :: MonadState s m => Lens' s (Maybe a)      -> a -> m ()
--   (?=) :: MonadState s m => Traversal' s (Maybe a) -> a -> m ()
--   (?=) :: MonadState s m => Setter' s (Maybe a)    -> a -> m ()
--   
(?=) :: MonadState s m => ASetter s s a Maybe b -> b -> m () infix 4 ?= -- | This is an alias for (%=). modifying :: MonadState s m => ASetter s s a b -> a -> b -> m () -- | Map over the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state. -- --
--   >>> execState (do _1 %= f;_2 %= g) (a,b)
--   (f a,g b)
--   
-- --
--   >>> execState (do both %= f) (a,b)
--   (f a,f b)
--   
-- --
--   (%=) :: MonadState s m => Iso' s a       -> (a -> a) -> m ()
--   (%=) :: MonadState s m => Lens' s a      -> (a -> a) -> m ()
--   (%=) :: MonadState s m => Traversal' s a -> (a -> a) -> m ()
--   (%=) :: MonadState s m => Setter' s a    -> (a -> a) -> m ()
--   
-- --
--   (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
--   
(%=) :: MonadState s m => ASetter s s a b -> a -> b -> m () infix 4 %= -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal in our monadic state with a new -- value, irrespective of the old. -- -- This is an alias for (.=). -- --
--   >>> execState (do assign _1 c; assign _2 d) (a,b)
--   (c,d)
--   
-- --
--   >>> execState (both .= c) (a,b)
--   (c,c)
--   
-- --
--   assign :: MonadState s m => Iso' s a       -> a -> m ()
--   assign :: MonadState s m => Lens' s a      -> a -> m ()
--   assign :: MonadState s m => Traversal' s a -> a -> m ()
--   assign :: MonadState s m => Setter' s a    -> a -> m ()
--   
assign :: MonadState s m => ASetter s s a b -> b -> m () -- | Logically && the target(s) of a Bool-valued -- Lens or Setter. -- --
--   >>> both &&~ True $ (False, True)
--   (False,True)
--   
-- --
--   >>> both &&~ False $ (False, True)
--   (False,False)
--   
-- --
--   (&&~) :: Setter' s Bool    -> Bool -> s -> s
--   (&&~) :: Iso' s Bool       -> Bool -> s -> s
--   (&&~) :: Lens' s Bool      -> Bool -> s -> s
--   (&&~) :: Traversal' s Bool -> Bool -> s -> s
--   
(&&~) :: () => ASetter s t Bool Bool -> Bool -> s -> t infixr 4 &&~ -- | Logically || the target(s) of a Bool-valued Lens -- or Setter. -- --
--   >>> both ||~ True $ (False,True)
--   (True,True)
--   
-- --
--   >>> both ||~ False $ (False,True)
--   (False,True)
--   
-- --
--   (||~) :: Setter' s Bool    -> Bool -> s -> s
--   (||~) :: Iso' s Bool       -> Bool -> s -> s
--   (||~) :: Lens' s Bool      -> Bool -> s -> s
--   (||~) :: Traversal' s Bool -> Bool -> s -> s
--   
(||~) :: () => ASetter s t Bool Bool -> Bool -> s -> t infixr 4 ||~ -- | Raise the target(s) of a floating-point valued Lens, -- Setter or Traversal to an arbitrary power. -- --
--   >>> (a,b) & _1 **~ c
--   (a**c,b)
--   
-- --
--   >>> (a,b) & both **~ c
--   (a**c,b**c)
--   
-- --
--   >>> _2 **~ 10 $ (3,2)
--   (3,1024.0)
--   
-- --
--   (**~) :: Floating a => Setter' s a    -> a -> s -> s
--   (**~) :: Floating a => Iso' s a       -> a -> s -> s
--   (**~) :: Floating a => Lens' s a      -> a -> s -> s
--   (**~) :: Floating a => Traversal' s a -> a -> s -> s
--   
(**~) :: Floating a => ASetter s t a a -> a -> s -> t infixr 4 **~ -- | Raise the target(s) of a fractionally valued Lens, -- Setter or Traversal to an integral power. -- --
--   >>> (1,2) & _2 ^^~ (-1)
--   (1,0.5)
--   
-- --
--   (^^~) :: (Fractional a, Integral e) => Setter' s a    -> e -> s -> s
--   (^^~) :: (Fractional a, Integral e) => Iso' s a       -> e -> s -> s
--   (^^~) :: (Fractional a, Integral e) => Lens' s a      -> e -> s -> s
--   (^^~) :: (Fractional a, Integral e) => Traversal' s a -> e -> s -> s
--   
(^^~) :: (Fractional a, Integral e) => ASetter s t a a -> e -> s -> t infixr 4 ^^~ -- | Raise the target(s) of a numerically valued Lens, Setter -- or Traversal to a non-negative integral power. -- --
--   >>> (1,3) & _2 ^~ 2
--   (1,9)
--   
-- --
--   (^~) :: (Num a, Integral e) => Setter' s a    -> e -> s -> s
--   (^~) :: (Num a, Integral e) => Iso' s a       -> e -> s -> s
--   (^~) :: (Num a, Integral e) => Lens' s a      -> e -> s -> s
--   (^~) :: (Num a, Integral e) => Traversal' s a -> e -> s -> s
--   
(^~) :: (Num a, Integral e) => ASetter s t a a -> e -> s -> t infixr 4 ^~ -- | Divide the target(s) of a numerically valued Lens, Iso, -- Setter or Traversal. -- --
--   >>> (a,b) & _1 //~ c
--   (a / c,b)
--   
-- --
--   >>> (a,b) & both //~ c
--   (a / c,b / c)
--   
-- --
--   >>> ("Hawaii",10) & _2 //~ 2
--   ("Hawaii",5.0)
--   
-- --
--   (//~) :: Fractional a => Setter' s a    -> a -> s -> s
--   (//~) :: Fractional a => Iso' s a       -> a -> s -> s
--   (//~) :: Fractional a => Lens' s a      -> a -> s -> s
--   (//~) :: Fractional a => Traversal' s a -> a -> s -> s
--   
(//~) :: Fractional a => ASetter s t a a -> a -> s -> t infixr 4 //~ -- | Decrement the target(s) of a numerically valued Lens, -- Iso, Setter or Traversal. -- --
--   >>> (a,b) & _1 -~ c
--   (a - c,b)
--   
-- --
--   >>> (a,b) & both -~ c
--   (a - c,b - c)
--   
-- --
--   >>> _1 -~ 2 $ (1,2)
--   (-1,2)
--   
-- --
--   >>> mapped.mapped -~ 1 $ [[4,5],[6,7]]
--   [[3,4],[5,6]]
--   
-- --
--   (-~) :: Num a => Setter' s a    -> a -> s -> s
--   (-~) :: Num a => Iso' s a       -> a -> s -> s
--   (-~) :: Num a => Lens' s a      -> a -> s -> s
--   (-~) :: Num a => Traversal' s a -> a -> s -> s
--   
(-~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 -~ -- | Multiply the target(s) of a numerically valued Lens, -- Iso, Setter or Traversal. -- --
--   >>> (a,b) & _1 *~ c
--   (a * c,b)
--   
-- --
--   >>> (a,b) & both *~ c
--   (a * c,b * c)
--   
-- --
--   >>> (1,2) & _2 *~ 4
--   (1,8)
--   
-- --
--   >>> Just 24 & mapped *~ 2
--   Just 48
--   
-- --
--   (*~) :: Num a => Setter' s a    -> a -> s -> s
--   (*~) :: Num a => Iso' s a       -> a -> s -> s
--   (*~) :: Num a => Lens' s a      -> a -> s -> s
--   (*~) :: Num a => Traversal' s a -> a -> s -> s
--   
(*~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 *~ -- | Increment the target(s) of a numerically valued Lens, -- Setter or Traversal. -- --
--   >>> (a,b) & _1 +~ c
--   (a + c,b)
--   
-- --
--   >>> (a,b) & both +~ c
--   (a + c,b + c)
--   
-- --
--   >>> (1,2) & _2 +~ 1
--   (1,3)
--   
-- --
--   >>> [(a,b),(c,d)] & traverse.both +~ e
--   [(a + e,b + e),(c + e,d + e)]
--   
-- --
--   (+~) :: Num a => Setter' s a    -> a -> s -> s
--   (+~) :: Num a => Iso' s a       -> a -> s -> s
--   (+~) :: Num a => Lens' s a      -> a -> s -> s
--   (+~) :: Num a => Traversal' s a -> a -> s -> s
--   
(+~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 +~ -- | Set to Just a value with pass-through. -- -- This is mostly present for consistency, but may be useful for for -- chaining assignments. -- -- If you do not need a copy of the intermediate result, then using l -- ?~ d directly is a good idea. -- --
--   >>> import Data.Map as Map
--   
--   >>> _2.at "hello" <?~ "world" $ (42,Map.fromList [("goodnight","gracie")])
--   ("world",(42,fromList [("goodnight","gracie"),("hello","world")]))
--   
-- --
--   (<?~) :: Setter s t a (Maybe b)    -> b -> s -> (b, t)
--   (<?~) :: Iso s t a (Maybe b)       -> b -> s -> (b, t)
--   (<?~) :: Lens s t a (Maybe b)      -> b -> s -> (b, t)
--   (<?~) :: Traversal s t a (Maybe b) -> b -> s -> (b, t)
--   
( ASetter s t a Maybe b -> b -> s -> (b, t) infixr 4 l -- .~ t directly is a good idea. -- --
--   >>> (a,b) & _1 <.~ c
--   (c,(c,b))
--   
-- --
--   >>> ("good","morning","vietnam") & _3 <.~ "world"
--   ("world",("good","morning","world"))
--   
-- --
--   >>> (42,Map.fromList [("goodnight","gracie")]) & _2.at "hello" <.~ Just "world"
--   (Just "world",(42,fromList [("goodnight","gracie"),("hello","world")]))
--   
-- --
--   (<.~) :: Setter s t a b    -> b -> s -> (b, t)
--   (<.~) :: Iso s t a b       -> b -> s -> (b, t)
--   (<.~) :: Lens s t a b      -> b -> s -> (b, t)
--   (<.~) :: Traversal s t a b -> b -> s -> (b, t)
--   
(<.~) :: () => ASetter s t a b -> b -> s -> (b, t) infixr 4 <.~ -- | Set the target of a Lens, Traversal or Setter to -- Just a value. -- --
--   l ?~ t ≡ set l (Just t)
--   
-- --
--   >>> Nothing & id ?~ a
--   Just a
--   
-- --
--   >>> Map.empty & at 3 ?~ x
--   fromList [(3,x)]
--   
-- --
--   (?~) :: Setter s t a (Maybe b)    -> b -> s -> t
--   (?~) :: Iso s t a (Maybe b)       -> b -> s -> t
--   (?~) :: Lens s t a (Maybe b)      -> b -> s -> t
--   (?~) :: Traversal s t a (Maybe b) -> b -> s -> t
--   
(?~) :: () => ASetter s t a Maybe b -> b -> s -> t infixr 4 ?~ -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal with a constant value. -- -- This is an infix version of set, provided for consistency with -- (.=). -- --
--   f <$ a ≡ mapped .~ f $ a
--   
-- --
--   >>> (a,b,c,d) & _4 .~ e
--   (a,b,c,e)
--   
-- --
--   >>> (42,"world") & _1 .~ "hello"
--   ("hello","world")
--   
-- --
--   >>> (a,b) & both .~ c
--   (c,c)
--   
-- --
--   (.~) :: Setter s t a b    -> b -> s -> t
--   (.~) :: Iso s t a b       -> b -> s -> t
--   (.~) :: Lens s t a b      -> b -> s -> t
--   (.~) :: Traversal s t a b -> b -> s -> t
--   
(.~) :: () => ASetter s t a b -> b -> s -> t infixr 4 .~ -- | Modifies the target of a Lens or all of the targets of a -- Setter or Traversal with a user supplied function. -- -- This is an infix version of over. -- --
--   fmap f ≡ mapped %~ f
--   fmapDefault f ≡ traverse %~ f
--   
-- --
--   >>> (a,b,c) & _3 %~ f
--   (a,b,f c)
--   
-- --
--   >>> (a,b) & both %~ f
--   (f a,f b)
--   
-- --
--   >>> _2 %~ length $ (1,"hello")
--   (1,5)
--   
-- --
--   >>> traverse %~ f $ [a,b,c]
--   [f a,f b,f c]
--   
-- --
--   >>> traverse %~ even $ [1,2,3]
--   [False,True,False]
--   
-- --
--   >>> traverse.traverse %~ length $ [["hello","world"],["!!!"]]
--   [[5,5],[3]]
--   
-- --
--   (%~) :: Setter s t a b    -> (a -> b) -> s -> t
--   (%~) :: Iso s t a b       -> (a -> b) -> s -> t
--   (%~) :: Lens s t a b      -> (a -> b) -> s -> t
--   (%~) :: Traversal s t a b -> (a -> b) -> s -> t
--   
(%~) :: () => ASetter s t a b -> a -> b -> s -> t infixr 4 %~ -- | Replace the target of a Lens or all of the targets of a -- Setter' or Traversal with a constant value, without -- changing its type. -- -- This is a type restricted version of set, which retains the -- type of the original. -- --
--   >>> set' mapped x [a,b,c,d]
--   [x,x,x,x]
--   
-- --
--   >>> set' _2 "hello" (1,"world")
--   (1,"hello")
--   
-- --
--   >>> set' mapped 0 [1,2,3,4]
--   [0,0,0,0]
--   
-- -- Note: Attempting to adjust set' a Fold or Getter -- will fail at compile time with an relatively nice error message. -- --
--   set' :: Setter' s a    -> a -> s -> s
--   set' :: Iso' s a       -> a -> s -> s
--   set' :: Lens' s a      -> a -> s -> s
--   set' :: Traversal' s a -> a -> s -> s
--   
set' :: () => ASetter' s a -> a -> s -> s -- | Replace the target of a Lens or all of the targets of a -- Setter or Traversal with a constant value. -- --
--   (<$) ≡ set mapped
--   
-- --
--   >>> set _2 "hello" (1,())
--   (1,"hello")
--   
-- --
--   >>> set mapped () [1,2,3,4]
--   [(),(),(),()]
--   
-- -- Note: Attempting to set a Fold or Getter will -- fail at compile time with an relatively nice error message. -- --
--   set :: Setter s t a b    -> b -> s -> t
--   set :: Iso s t a b       -> b -> s -> t
--   set :: Lens s t a b      -> b -> s -> t
--   set :: Traversal s t a b -> b -> s -> t
--   
set :: () => ASetter s t a b -> b -> s -> t -- | Modify the target of a Lens or all the targets of a -- Setter or Traversal with a function. -- --
--   fmapover mapped
--   fmapDefaultover traverse
--   sets . overid
--   over . setsid
--   
-- -- Given any valid Setter l, you can also rely on the -- law: -- --
--   over l f . over l g = over l (f . g)
--   
-- -- e.g. -- --
--   >>> over mapped f (over mapped g [a,b,c]) == over mapped (f . g) [a,b,c]
--   True
--   
-- -- Another way to view over is to say that it transforms a -- Setter into a "semantic editor combinator". -- --
--   >>> over mapped f (Just a)
--   Just (f a)
--   
-- --
--   >>> over mapped (*10) [1,2,3]
--   [10,20,30]
--   
-- --
--   >>> over _1 f (a,b)
--   (f a,b)
--   
-- --
--   >>> over _1 show (10,20)
--   ("10",20)
--   
-- --
--   over :: Setter s t a b -> (a -> b) -> s -> t
--   over :: ASetter s t a b -> (a -> b) -> s -> t
--   
over :: () => ASetter s t a b -> a -> b -> s -> t -- | Clone an IndexedSetter. cloneIndexedSetter :: () => AnIndexedSetter i s t a b -> IndexedSetter i s t a b -- | Build an IndexPreservingSetter from any Setter. cloneIndexPreservingSetter :: () => ASetter s t a b -> IndexPreservingSetter s t a b -- | Restore ASetter to a full Setter. cloneSetter :: () => ASetter s t a b -> Setter s t a b -- | Build a Setter, IndexedSetter or -- IndexPreservingSetter depending on your choice of -- Profunctor. -- --
--   sets :: ((a -> b) -> s -> t) -> Setter s t a b
--   
sets :: (Profunctor p, Profunctor q, Settable f) => p a b -> q s t -> Optical p q f s t a b -- | Build an index-preserving Setter from a map-like function. -- -- Your supplied function f is required to satisfy: -- --
--   f idid
--   f g . f h ≡ f (g . h)
--   
-- -- Equational reasoning: -- --
--   setting . overid
--   over . settingid
--   
-- -- Another way to view sets is that it takes a "semantic editor -- combinator" and transforms it into a Setter. -- --
--   setting :: ((a -> b) -> s -> t) -> Setter s t a b
--   
setting :: () => a -> b -> s -> t -> IndexPreservingSetter s t a b -- | This Setter can be used to map over the input of a -- Profunctor. -- -- The most common Profunctor to use this with is -- (->). -- --
--   >>> (argument %~ f) g x
--   g (f x)
--   
-- --
--   >>> (argument %~ show) length [1,2,3]
--   7
--   
-- --
--   >>> (argument %~ f) h x y
--   h (f x) y
--   
-- -- Map over the argument of the result of a function -- i.e., its second -- argument: -- --
--   >>> (mapped.argument %~ f) h x y
--   h x (f y)
--   
-- --
--   argument :: Setter (b -> r) (a -> r) a b
--   
argument :: Profunctor p => Setter p b r p a r a b -- | This Setter can be used to map over all of the inputs to a -- Contravariant. -- --
--   contramapover contramapped
--   
-- --
--   >>> getPredicate (over contramapped (*2) (Predicate even)) 5
--   True
--   
-- --
--   >>> getOp (over contramapped (*5) (Op show)) 100
--   "500"
--   
-- --
--   >>> Prelude.map ($ 1) $ over (mapped . _Unwrapping' Op . contramapped) (*12) [(*2),(+1),(^3)]
--   [24,13,1728]
--   
contramapped :: Contravariant f => Setter f b f a a b -- | This setter can be used to modify all of the values in a -- Monad. -- -- You sometimes have to use this rather than mapped -- due to -- temporary insanity Functor was not a superclass of Monad -- until GHC 7.10. -- --
--   liftMover lifted
--   
-- --
--   >>> over lifted f [a,b,c]
--   [f a,f b,f c]
--   
-- --
--   >>> set lifted b (Just a)
--   Just b
--   
-- -- If you want an IndexPreservingSetter use setting -- liftM. lifted :: Monad m => Setter m a m b a b -- | This Setter can be used to map over all of the values in a -- Functor. -- --
--   fmapover mapped
--   fmapDefaultover traverse
--   (<$) ≡ set mapped
--   
-- --
--   >>> over mapped f [a,b,c]
--   [f a,f b,f c]
--   
-- --
--   >>> over mapped (+1) [1,2,3]
--   [2,3,4]
--   
-- --
--   >>> set mapped x [a,b,c]
--   [x,x,x]
--   
-- --
--   >>> [[a,b],[c]] & mapped.mapped +~ x
--   [[a + x,b + x],[c + x]]
--   
-- --
--   >>> over (mapped._2) length [("hello","world"),("leaders","!!!")]
--   [("hello",5),("leaders",3)]
--   
-- --
--   mapped :: Functor f => Setter (f a) (f b) a b
--   
-- -- If you want an IndexPreservingSetter use setting -- fmap. mapped :: Functor f => Setter f a f b a b -- | Running a Setter instantiates it to a concrete type. -- -- When consuming a setter directly to perform a mapping, you can use -- this type, but most user code will not need to use this type. type ASetter s t a b = a -> Identity b -> s -> Identity t -- | This is a useful alias for use when consuming a Setter'. -- -- Most user code will never have to use this type. -- --
--   type ASetter' = Simple ASetter
--   
type ASetter' s a = ASetter s s a a -- | Running an IndexedSetter instantiates it to a concrete type. -- -- When consuming a setter directly to perform a mapping, you can use -- this type, but most user code will not need to use this type. type AnIndexedSetter i s t a b = Indexed i a Identity b -> s -> Identity t -- |
--   type AnIndexedSetter' i = Simple (AnIndexedSetter i)
--   
type AnIndexedSetter' i s a = AnIndexedSetter i s s a a -- | This is a convenient alias when defining highly polymorphic code that -- takes both ASetter and AnIndexedSetter as appropriate. -- If a function takes this it is expecting one of those two things based -- on context. type Setting (p :: * -> * -> *) s t a b = p a Identity b -> s -> Identity t -- | This is a convenient alias when defining highly polymorphic code that -- takes both ASetter' and AnIndexedSetter' as appropriate. -- If a function takes this it is expecting one of those two things based -- on context. type Setting' (p :: * -> * -> *) s a = Setting p s s a a -- | A Lens is actually a lens family as described in -- http://comonad.com/reader/2012/mirrored-lenses/. -- -- With great power comes great responsibility and a Lens is -- subject to the three common sense Lens laws: -- -- 1) You get back what you put in: -- --
--   view l (set l v s)  ≡ v
--   
-- -- 2) Putting back what you got doesn't change anything: -- --
--   set l (view l s) s  ≡ s
--   
-- -- 3) Setting twice is the same as setting once: -- --
--   set l v' (set l v s) ≡ set l v' s
--   
-- -- These laws are strong enough that the 4 type parameters of a -- Lens cannot vary fully independently. For more on how they -- interact, read the "Why is it a Lens Family?" section of -- http://comonad.com/reader/2012/mirrored-lenses/. -- -- There are some emergent properties of these laws: -- -- 1) set l s must be injective for every s This -- is a consequence of law #1 -- -- 2) set l must be surjective, because of law #2, which -- indicates that it is possible to obtain any v from some -- s such that set s v = s -- -- 3) Given just the first two laws you can prove a weaker form of law #3 -- where the values v that you are setting match: -- --
--   set l v (set l v s) ≡ set l v s
--   
-- -- Every Lens can be used directly as a Setter or -- Traversal. -- -- You can also use a Lens for Getting as if it were a -- Fold or Getter. -- -- Since every Lens is a valid Traversal, the -- Traversal laws are required of any Lens you create: -- --
--   l purepure
--   fmap (l f) . l g ≡ getCompose . l (Compose . fmap f . g)
--   
-- --
--   type Lens s t a b = forall f. Functor f => LensLike f s t a b
--   
type Lens s t a b = forall (f :: * -> *). Functor f => a -> f b -> s -> f t -- |
--   type Lens' = Simple Lens
--   
type Lens' s a = Lens s s a a -- | Every IndexedLens is a valid Lens and a valid -- IndexedTraversal. type IndexedLens i s t a b = forall (f :: * -> *) (p :: * -> * -> *). (Indexable i p, Functor f) => p a f b -> s -> f t -- |
--   type IndexedLens' i = Simple (IndexedLens i)
--   
type IndexedLens' i s a = IndexedLens i s s a a -- | An IndexPreservingLens leaves any index it is composed with -- alone. type IndexPreservingLens s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Conjoined p, Functor f) => p a f b -> p s f t -- |
--   type IndexPreservingLens' = Simple IndexPreservingLens
--   
type IndexPreservingLens' s a = IndexPreservingLens s s a a -- | 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 purepure
--   fmap (t f) . t g ≡ getCompose . t (Compose . fmap f . g)
--   
-- -- One consequence of this requirement is that a Traversal needs -- to leave the same number of elements as a candidate for subsequent -- Traversal that it started with. Another testament to the -- strength of these laws is that the caveat expressed in section 5.5 of -- the "Essence of the Iterator Pattern" about exotic Traversable -- instances that traverse the same entry multiple times was -- actually already ruled out by the second law in that same paper! type Traversal s t a b = forall (f :: * -> *). Applicative f => a -> f b -> s -> f t -- |
--   type Traversal' = Simple Traversal
--   
type Traversal' s a = Traversal s s a a type Traversal1 s t a b = forall (f :: * -> *). Apply f => a -> f b -> s -> f t type Traversal1' s a = Traversal1 s s a a -- | Every IndexedTraversal is a valid Traversal or -- IndexedFold. -- -- The Indexed constraint is used to allow an -- IndexedTraversal to be used directly as a Traversal. -- -- The Traversal laws are still required to hold. -- -- In addition, the index i should satisfy the requirement that -- it stays unchanged even when modifying the value a, otherwise -- traversals like indices break the Traversal laws. type IndexedTraversal i s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Indexable i p, Applicative f) => p a f b -> s -> f t -- |
--   type IndexedTraversal' i = Simple (IndexedTraversal i)
--   
type IndexedTraversal' i s a = IndexedTraversal i s s a a type IndexedTraversal1 i s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Indexable i p, Apply f) => p a f b -> s -> f t type IndexedTraversal1' i s a = IndexedTraversal1 i s s a a -- | An IndexPreservingLens leaves any index it is composed with -- alone. type IndexPreservingTraversal s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Conjoined p, Applicative f) => p a f b -> p s f t -- |
--   type IndexPreservingTraversal' = Simple IndexPreservingTraversal
--   
type IndexPreservingTraversal' s a = IndexPreservingTraversal s s a a type IndexPreservingTraversal1 s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Conjoined p, Apply f) => p a f b -> p s f t type IndexPreservingTraversal1' s a = IndexPreservingTraversal1 s s a a -- | The only LensLike law that can apply to a Setter -- l is that -- --
--   set l y (set l x a) ≡ set l y a
--   
-- -- You can't view a Setter in general, so the other two -- laws are irrelevant. -- -- However, two Functor laws apply to a Setter: -- --
--   over l idid
--   over l f . over l g ≡ over l (f . g)
--   
-- -- These can be stated more directly: -- --
--   l purepure
--   l f . untainted . l g ≡ l (f . untainted . g)
--   
-- -- You can compose a Setter with a Lens or a -- Traversal using (.) from the Prelude and the -- result is always only a Setter and nothing more. -- --
--   >>> over traverse f [a,b,c,d]
--   [f a,f b,f c,f d]
--   
-- --
--   >>> over _1 f (a,b)
--   (f a,b)
--   
-- --
--   >>> over (traverse._1) f [(a,b),(c,d)]
--   [(f a,b),(f c,d)]
--   
-- --
--   >>> over both f (a,b)
--   (f a,f b)
--   
-- --
--   >>> over (traverse.both) f [(a,b),(c,d)]
--   [(f a,f b),(f c,f d)]
--   
type Setter s t a b = forall (f :: * -> *). Settable f => a -> f b -> s -> f t -- | A Setter' is just a Setter that doesn't change the -- types. -- -- These are particularly common when talking about monomorphic -- containers. e.g. -- --
--   sets Data.Text.map :: Setter' Text Char
--   
-- --
--   type Setter' = Simple Setter
--   
type Setter' s a = Setter s s a a -- | Every IndexedSetter is a valid Setter. -- -- The Setter laws are still required to hold. type IndexedSetter i s t a b = forall (f :: * -> *) (p :: * -> * -> *). (Indexable i p, Settable f) => p a f b -> s -> f t -- |
--   type IndexedSetter' i = Simple (IndexedSetter i)
--   
type IndexedSetter' i s a = IndexedSetter i s s a a -- | An IndexPreservingSetter can be composed with a -- IndexedSetter, IndexedTraversal or IndexedLens -- and leaves the index intact, yielding an IndexedSetter. type IndexPreservingSetter s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Conjoined p, Settable f) => p a f b -> p s f t -- |
--   type IndexedPreservingSetter' i = Simple IndexedPreservingSetter
--   
type IndexPreservingSetter' s a = IndexPreservingSetter s s a a -- | Isomorphism families can be composed with another Lens using -- (.) and id. -- -- Since every Iso is both a valid Lens and a valid -- Prism, the laws for those types imply the following laws for an -- Iso f: -- --
--   f . from f ≡ id
--   from f . f ≡ id
--   
-- -- Note: Composition with an Iso is index- and measure- -- preserving. type Iso s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Profunctor p, Functor f) => p a f b -> p s f t -- |
--   type Iso' = Simple Iso
--   
type Iso' s a = Iso s s a a -- | This is a limited form of a Prism that can only be used for -- re operations. -- -- Like with a Getter, there are no laws to state for a -- Review. -- -- You can generate a Review by using unto. You can also -- use any Prism or Iso directly as a Review. type Review t b = forall (p :: * -> * -> *) (f :: * -> *). (Choice p, Bifunctor p, Settable f) => Optic' p f t b -- | If you see this in a signature for a function, the function is -- expecting a Review (in practice, this usually means a -- Prism). type AReview t b = Optic' (Tagged :: * -> * -> *) Identity t b -- | A Prism l is a Traversal that can also be -- turned around with re to obtain a Getter in the opposite -- direction. -- -- There are two laws that a Prism should satisfy: -- -- First, if I re or review a value with a Prism and -- then preview or use (^?), I will get it back: -- --
--   preview l (review l b) ≡ Just b
--   
-- -- Second, if you can extract a value a using a Prism -- l from a value s, then the value s is -- completely described by l and a: -- -- If preview l s ≡ Just a then -- review l a ≡ s -- -- These two laws imply that the Traversal laws hold for every -- Prism and that we traverse at most 1 element: -- --
--   lengthOf l x <= 1
--   
-- -- It may help to think of this as a Iso that can be partial in -- one direction. -- -- Every Prism is a valid Traversal. -- -- Every Iso is a valid Prism. -- -- For example, you might have a Prism' Integer -- Natural allows you to always go from a Natural to -- an Integer, and provide you with tools to check if an -- Integer is a Natural and/or to edit one if it is. -- --
--   nat :: Prism' Integer Natural
--   nat = prism toInteger $ \ i ->
--      if i < 0
--      then Left i
--      else Right (fromInteger i)
--   
-- -- Now we can ask if an Integer is a Natural. -- --
--   >>> 5^?nat
--   Just 5
--   
-- --
--   >>> (-5)^?nat
--   Nothing
--   
-- -- We can update the ones that are: -- --
--   >>> (-3,4) & both.nat *~ 2
--   (-3,8)
--   
-- -- And we can then convert from a Natural to an Integer. -- --
--   >>> 5 ^. re nat -- :: Natural
--   5
--   
-- -- Similarly we can use a Prism to traverse the -- Left half of an Either: -- --
--   >>> Left "hello" & _Left %~ length
--   Left 5
--   
-- -- or to construct an Either: -- --
--   >>> 5^.re _Left
--   Left 5
--   
-- -- such that if you query it with the Prism, you will get your -- original input back. -- --
--   >>> 5^.re _Left ^? _Left
--   Just 5
--   
-- -- Another interesting way to think of a Prism is as the -- categorical dual of a Lens -- a co-Lens, so to speak. -- This is what permits the construction of outside. -- -- Note: Composition with a Prism is index-preserving. type Prism s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Choice p, Applicative f) => p a f b -> p s f t -- | A Simple Prism. type Prism' s a = Prism s s a a -- | A witness that (a ~ s, b ~ t). -- -- Note: Composition with an Equality is index-preserving. type Equality (s :: k1) (t :: k2) (a :: k1) (b :: k2) = forall k3 (p :: k1 -> k3 -> Type) (f :: k2 -> k3). () => p a f b -> p s f t -- | A Simple Equality. type Equality' (s :: k2) (a :: k2) = Equality s s a a -- | Composable asTypeOf. Useful for constraining excess -- polymorphism, foo . (id :: As Int) . bar. type As (a :: k2) = Equality' a a -- | A Getter describes how to retrieve a single value in a way that -- can be composed with other LensLike constructions. -- -- Unlike a Lens a Getter is read-only. Since a -- Getter cannot be used to write back there are no Lens -- laws that can be applied to it. In fact, it is isomorphic to an -- arbitrary function from (s -> a). -- -- Moreover, a Getter can be used directly as a Fold, since -- it just ignores the Applicative. type Getter s a = forall (f :: * -> *). (Contravariant f, Functor f) => a -> f a -> s -> f s -- | Every IndexedGetter is a valid IndexedFold and can be -- used for Getting like a Getter. type IndexedGetter i s a = forall (p :: * -> * -> *) (f :: * -> *). (Indexable i p, Contravariant f, Functor f) => p a f a -> s -> f s -- | An IndexPreservingGetter can be used as a Getter, but -- when composed with an IndexedTraversal, IndexedFold, or -- IndexedLens yields an IndexedFold, IndexedFold or -- IndexedGetter respectively. type IndexPreservingGetter s a = forall (p :: * -> * -> *) (f :: * -> *). (Conjoined p, Contravariant f, Functor f) => p a f a -> p s f s -- | A Fold describes how to retrieve multiple values in a way that -- can be composed with other LensLike constructions. -- -- A Fold s a provides a structure with operations very -- similar to those of the Foldable typeclass, see -- foldMapOf and the other Fold combinators. -- -- By convention, if there exists a foo method that expects a -- Foldable (f a), then there should be a fooOf -- method that takes a Fold s a and a value of type -- s. -- -- A Getter is a legal Fold that just ignores the supplied -- Monoid. -- -- Unlike a Traversal a Fold is read-only. Since a -- Fold cannot be used to write back there are no Lens laws -- that apply. type Fold s a = forall (f :: * -> *). (Contravariant f, Applicative f) => a -> f a -> s -> f s -- | Every IndexedFold is a valid Fold and can be used for -- Getting. type IndexedFold i s a = forall (p :: * -> * -> *) (f :: * -> *). (Indexable i p, Contravariant f, Applicative f) => p a f a -> s -> f s -- | An IndexPreservingFold can be used as a Fold, but when -- composed with an IndexedTraversal, IndexedFold, or -- IndexedLens yields an IndexedFold respectively. type IndexPreservingFold s a = forall (p :: * -> * -> *) (f :: * -> *). (Conjoined p, Contravariant f, Applicative f) => p a f a -> p s f s -- | A relevant Fold (aka Fold1) has one or more targets. type Fold1 s a = forall (f :: * -> *). (Contravariant f, Apply f) => a -> f a -> s -> f s type IndexedFold1 i s a = forall (p :: * -> * -> *) (f :: * -> *). (Indexable i p, Contravariant f, Apply f) => p a f a -> s -> f s type IndexPreservingFold1 s a = forall (p :: * -> * -> *) (f :: * -> *). (Conjoined p, Contravariant f, Apply f) => p a f a -> p s f s -- | A Simple Lens, Simple Traversal, ... can -- be used instead of a Lens,Traversal, ... whenever the -- type variables don't change upon setting a value. -- --
--   _imagPart :: Simple Lens (Complex a) a
--   traversed :: Simple (IndexedTraversal Int) [a] a
--   
-- -- Note: To use this alias in your own code with LensLike -- f or Setter, you may have to turn on -- LiberalTypeSynonyms. -- -- This is commonly abbreviated as a "prime" marker, e.g. -- Lens' = Simple Lens. type Simple (f :: k -> k -> k1 -> k1 -> k2) (s :: k) (a :: k1) = f s s a a -- | A valid Optic l should satisfy the laws: -- --
--   l purepure
--   l (Procompose f g) = Procompose (l f) (l g)
--   
-- -- This gives rise to the laws for Equality, Iso, -- Prism, Lens, Traversal, Traversal1, -- Setter, Fold, Fold1, and Getter as well -- along with their index-preserving variants. -- --
--   type LensLike f s t a b = Optic (->) f s t a b
--   
type Optic (p :: k1 -> k -> *) (f :: k2 -> k) (s :: k1) (t :: k2) (a :: k1) (b :: k2) = p a f b -> p s f t -- |
--   type Optic' p f s a = Simple (Optic p f) s a
--   
type Optic' (p :: k1 -> k -> *) (f :: k1 -> k) (s :: k1) (a :: k1) = Optic p f s s a a -- |
--   type LensLike f s t a b = Optical (->) (->) f s t a b
--   
-- --
--   type Over p f s t a b = Optical p (->) f s t a b
--   
-- --
--   type Optic p f s t a b = Optical p p f s t a b
--   
type Optical (p :: k2 -> k -> *) (q :: k1 -> k -> *) (f :: k3 -> k) (s :: k1) (t :: k3) (a :: k2) (b :: k3) = p a f b -> q s f t -- |
--   type Optical' p q f s a = Simple (Optical p q f) s a
--   
type Optical' (p :: k1 -> k -> *) (q :: k1 -> k -> *) (f :: k1 -> k) (s :: k1) (a :: k1) = Optical p q f s s a a -- | Many combinators that accept a Lens can also accept a -- Traversal in limited situations. -- -- They do so by specializing the type of Functor that they -- require of the caller. -- -- If a function accepts a LensLike f s t a b for some -- Functor f, then they may be passed a Lens. -- -- Further, if f is an Applicative, they may also be -- passed a Traversal. type LensLike (f :: k -> *) s (t :: k) a (b :: k) = a -> f b -> s -> f t -- |
--   type LensLike' f = Simple (LensLike f)
--   
type LensLike' (f :: * -> *) s a = LensLike f s s a a -- | Convenient alias for constructing indexed lenses and their ilk. type IndexedLensLike i (f :: k -> *) s (t :: k) a (b :: k) = forall (p :: * -> * -> *). Indexable i p => p a f b -> s -> f t -- | Convenient alias for constructing simple indexed lenses and their ilk. type IndexedLensLike' i (f :: * -> *) s a = IndexedLensLike i f s s a a -- | This is a convenient alias for use when you need to consume either -- indexed or non-indexed lens-likes based on context. type Over (p :: k -> * -> *) (f :: k1 -> *) s (t :: k1) (a :: k) (b :: k1) = p a f b -> s -> f t -- | This is a convenient alias for use when you need to consume either -- indexed or non-indexed lens-likes based on context. -- --
--   type Over' p f = Simple (Over p f)
--   
type Over' (p :: * -> * -> *) (f :: * -> *) s a = Over p f s s a a -- | Anything Settable must be isomorphic to the Identity -- Functor. class (Applicative f, Distributive f, Traversable f) => Settable (f :: * -> *) -- | This is a profunctor used internally to implement Review -- -- It plays a role similar to that of Accessor or Const -- do for Control.Lens.Getter retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b -- | This class is provided mostly for backwards compatibility with lens -- 3.8, but it can also shorten type signatures. class (Profunctor p, Bifunctor p) => Reviewable (p :: * -> * -> *) -- | This provides a way to peek at the internal structure of a -- Traversal or IndexedTraversal data Magma i t b a -- | This data type represents a path-compressed copy of one level of a -- source data structure. We can safely use path-compression because we -- know the depth of the tree. -- -- Path compression is performed by viewing a Level as a PATRICIA -- trie of the paths into the structure to leaves at a given depth, -- similar in many ways to a IntMap, but unlike a regular PATRICIA -- trie we do not need to store the mask bits merely the depth of the -- fork. -- -- One invariant of this structure is that underneath a Two node -- you will not find any Zero nodes, so Zero can only occur -- at the root. data Level i a -- | This class provides a generalized notion of list reversal extended to -- other containers. class Reversing t reversing :: Reversing t => t -> t -- | This is used to characterize a Traversal. -- -- a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, -- or an indexed FunList. -- -- http://twanvl.nl/blog/haskell/non-regular1 -- -- A Bazaar is like a Traversal that has already been -- applied to some structure. -- -- Where a Context a b t holds an a and a -- function from b to t, a Bazaar a b t -- holds N as and a function from N -- bs to t, (where N might be infinite). -- -- Mnemonically, a Bazaar holds many stores and you can easily add -- more. -- -- This is a final encoding of Bazaar. newtype Bazaar (p :: * -> * -> *) a b t Bazaar :: forall (f :: * -> *). Applicative f => p a f b -> f t -> Bazaar a b t [runBazaar] :: Bazaar a b t -> forall (f :: * -> *). Applicative f => p a f b -> f t -- | This alias is helpful when it comes to reducing repetition in type -- signatures. -- --
--   type Bazaar' p a t = Bazaar p a a t
--   
type Bazaar' (p :: * -> * -> *) a = Bazaar p a a -- | This is used to characterize a Traversal. -- -- a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, -- or an indexed FunList. -- -- http://twanvl.nl/blog/haskell/non-regular1 -- -- A Bazaar1 is like a Traversal that has already been -- applied to some structure. -- -- Where a Context a b t holds an a and a -- function from b to t, a Bazaar1 a b -- t holds N as and a function from N -- bs to t, (where N might be infinite). -- -- Mnemonically, a Bazaar1 holds many stores and you can easily -- add more. -- -- This is a final encoding of Bazaar1. newtype Bazaar1 (p :: * -> * -> *) a b t Bazaar1 :: forall (f :: * -> *). Apply f => p a f b -> f t -> Bazaar1 a b t [runBazaar1] :: Bazaar1 a b t -> forall (f :: * -> *). Apply f => p a f b -> f t -- | This alias is helpful when it comes to reducing repetition in type -- signatures. -- --
--   type Bazaar1' p a t = Bazaar1 p a a t
--   
type Bazaar1' (p :: * -> * -> *) a = Bazaar1 p a a -- | The indexed store can be used to characterize a Lens and is -- used by cloneLens. -- -- Context a b t is isomorphic to newtype -- Context a b t = Context { runContext :: forall f. -- Functor f => (a -> f b) -> f t }, and to -- exists s. (s, Lens s t a b). -- -- A Context is like a Lens that has already been applied -- to a some structure. data Context a b t Context :: b -> t -> a -> Context a b t -- |
--   type Context' a s = Context a a s
--   
type Context' a = Context a a -- | When composed with an IndexedFold or -- IndexedTraversal this yields an (Indexed) -- Fold of the indices. asIndex :: (Indexable i p, Contravariant f, Functor f) => p i f i -> Indexed i s f s -- | Fold a container with indices returning both the indices and the -- values. -- -- The result is only valid to compose in a Traversal, if you -- don't edit the index as edits to the index have no effect. -- --
--   >>> [10, 20, 30] ^.. ifolded . withIndex
--   [(0,10),(1,20),(2,30)]
--   
-- --
--   >>> [10, 20, 30] ^.. ifolded . withIndex . alongside negated (re _Show)
--   [(0,"10"),(-1,"20"),(-2,"30")]
--   
withIndex :: (Indexable i p, Functor f) => p (i, s) f (j, t) -> Indexed i s f t -- | Transform a Traversal into an IndexedTraversal or a -- Fold into an IndexedFold, etc. -- -- This combinator is like indexing except that it handles large -- traversals and folds gracefully. -- --
--   indexing64 :: Traversal s t a b -> IndexedTraversal Int64 s t a b
--   indexing64 :: Prism s t a b     -> IndexedTraversal Int64 s t a b
--   indexing64 :: Lens s t a b      -> IndexedLens Int64 s t a b
--   indexing64 :: Iso s t a b       -> IndexedLens Int64 s t a b
--   indexing64 :: Fold s a          -> IndexedFold Int64 s a
--   indexing64 :: Getter s a        -> IndexedGetter Int64 s a
--   
-- --
--   indexing64 :: Indexable Int64 p => LensLike (Indexing64 f) s t a b -> Over p f s t a b
--   
indexing64 :: Indexable Int64 p => a -> Indexing64 f b -> s -> Indexing64 f t -> p a f b -> s -> f t -- | Transform a Traversal into an IndexedTraversal or a -- Fold into an IndexedFold, etc. -- --
--   indexing :: Traversal s t a b -> IndexedTraversal Int s t a b
--   indexing :: Prism s t a b     -> IndexedTraversal Int s t a b
--   indexing :: Lens s t a b      -> IndexedLens Int  s t a b
--   indexing :: Iso s t a b       -> IndexedLens Int s t a b
--   indexing :: Fold s a          -> IndexedFold Int s a
--   indexing :: Getter s a        -> IndexedGetter Int s a
--   
-- --
--   indexing :: Indexable Int p => LensLike (Indexing f) s t a b -> Over p f s t a b
--   
indexing :: Indexable Int p => a -> Indexing f b -> s -> Indexing f t -> p a f b -> s -> f t -- | This is a Profunctor that is both Corepresentable by -- f and Representable by g such that f -- is left adjoint to g. From this you can derive a lot of -- structure due to the preservation of limits and colimits. class (Choice p, Corepresentable p, Comonad Corep p, Traversable Corep p, Strong p, Representable p, Monad Rep p, MonadFix Rep p, Distributive Rep p, Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p, Closed p) => Conjoined (p :: * -> * -> *) -- | Conjoined is strong enough to let us distribute every -- Conjoined Profunctor over every Haskell Functor. -- This is effectively a generalization of fmap. distrib :: (Conjoined p, Functor f) => p a b -> p f a f b -- | This permits us to make a decision at an outermost point about whether -- or not we use an index. -- -- Ideally any use of this function should be done in such a way so that -- you compute the same answer, but this cannot be enforced at the type -- level. conjoined :: Conjoined p => p ~ ((->) :: * -> * -> *) -> q a -> b r -> q p a b r -> q p a b r -- | This class permits overloading of function application for things that -- also admit a notion of a key or index. class Conjoined p => Indexable i (p :: * -> * -> *) -- | Build a function from an indexed function. indexed :: Indexable i p => p a b -> i -> a -> b -- | A function with access to a index. This constructor may be useful when -- you need to store an Indexable in a container to avoid -- ImpredicativeTypes. -- --
--   index :: Indexed i a b -> i -> a -> b
--   
newtype Indexed i a b Indexed :: i -> a -> b -> Indexed i a b [runIndexed] :: Indexed i a b -> i -> a -> b -- | Used internally by traverseOf_ and the like. -- -- The argument a of the result should not be used! data Traversed a (f :: * -> *) -- | Used internally by mapM_ and the like. -- -- The argument a of the result should not be used! -- -- See 4.16 Changelog entry for the explanation of "why not Apply f -- =>"? data Sequenced a (m :: * -> *) -- | Used for preview. data Leftmost a -- | Used for lastOf. data Rightmost a class (Foldable1 t, Traversable t) => Traversable1 (t :: * -> *) traverse1 :: (Traversable1 t, Apply f) => a -> f b -> t a -> f t b -- | Fold a value using its Foldable instance using explicitly -- provided Monoid operations. This is like fold where -- the Monoid instance can be manually specified. -- --
--   foldBy mappend memptyfold
--   
-- --
--   >>> foldBy (++) [] ["hello","world"]
--   "helloworld"
--   
foldBy :: Foldable t => a -> a -> a -> a -> t a -> a -- | Fold a value using its Foldable instance using explicitly -- provided Monoid operations. This is like foldMap where -- the Monoid instance can be manually specified. -- --
--   foldMapBy mappend memptyfoldMap
--   
-- --
--   >>> foldMapBy (+) 0 length ["hello","world"]
--   10
--   
foldMapBy :: Foldable t => r -> r -> r -> r -> a -> r -> t a -> r -- | Traverse a container using its Traversable instance using -- explicitly provided Applicative operations. This is like -- traverse where the Applicative instance can be manually -- specified. traverseBy :: Traversable t => forall x. () => x -> f x -> forall x y. () => f x -> y -> f x -> f y -> a -> f b -> t a -> f t b -- | Sequence a container using its Traversable instance using -- explicitly provided Applicative operations. This is like -- sequence where the Applicative instance can be manually -- specified. sequenceBy :: Traversable t => forall x. () => x -> f x -> forall x y. () => f x -> y -> f x -> f y -> t f a -> f t a -- | The generalization of Costar of Functor that is strong -- with respect to Either. -- -- Note: This is also a notion of strength, except with regards to -- another monoidal structure that we can choose to equip Hask with: the -- cocartesian coproduct. class Profunctor p => Choice (p :: * -> * -> *) -- | Laws: -- --
--   left'dimap swapE swapE . right' where
--     swapE :: Either a b -> Either b a
--     swapE = either Right Left
--   rmap Leftlmap Left . left'
--   lmap (right f) . left'rmap (right f) . left'
--   left' . left'dimap assocE unassocE . left' where
--     assocE :: Either (Either a b) c -> Either a (Either b c)
--     assocE (Left (Left a)) = Left a
--     assocE (Left (Right b)) = Right (Left b)
--     assocE (Right c) = Right (Right c)
--     unassocE :: Either a (Either b c) -> Either (Either a b) c
--     unassocE (Left a) = Left (Left a)
--     unassocE (Right (Left b) = Left (Right b)
--     unassocE (Right (Right c)) = Right c)
--   
left' :: Choice p => p a b -> p Either a c Either b c -- | Laws: -- --
--   right'dimap swapE swapE . left' where
--     swapE :: Either a b -> Either b a
--     swapE = either Right Left
--   rmap Rightlmap Right . right'
--   lmap (left f) . right'rmap (left f) . right'
--   right' . right'dimap unassocE assocE . right' where
--     assocE :: Either (Either a b) c -> Either a (Either b c)
--     assocE (Left (Left a)) = Left a
--     assocE (Left (Right b)) = Right (Left b)
--     assocE (Right c) = Right (Right c)
--     unassocE :: Either a (Either b c) -> Either (Either a b) c
--     unassocE (Left a) = Left (Left a)
--     unassocE (Right (Left b) = Left (Right b)
--     unassocE (Right (Right c)) = Right c)
--   
right' :: Choice p => p a b -> p Either c a Either c b -- | Generalized version of onException. -- -- Note, any monadic side effects in m of the "afterward" -- computation will be discarded. onException :: MonadBaseControl IO m => m a -> m b -> m a -- | Generalized version of finally. -- -- Note, any monadic side effects in m of the "afterward" -- computation will be discarded. finally :: MonadBaseControl IO m => m a -> m b -> m a -- | Generalized version of bracketOnError. -- -- Note: -- -- -- -- Note that when your acquire and release computations -- are of type IO it will be more efficient to write: -- --
--   liftBaseOp (bracketOnError acquire release)
--   
bracketOnError :: MonadBaseControl IO m => m a -> a -> m b -> a -> m c -> m c -- | Generalized version of bracket_. -- -- Note any monadic side effects in m of both the -- "acquire" and "release" computations will be discarded. To keep the -- monadic side effects of the "acquire" computation, use bracket -- with constant functions instead. -- -- Note that when your acquire and release computations -- are of type IO it will be more efficient to write: -- --
--   liftBaseOp_ (bracket_ acquire release)
--   
bracket_ :: MonadBaseControl IO m => m a -> m b -> m c -> m c -- | Generalized version of bracket. -- -- Note: -- -- -- -- Note that when your acquire and release computations -- are of type IO it will be more efficient to write: -- --
--   liftBaseOp (bracket acquire release)
--   
bracket :: MonadBaseControl IO m => m a -> a -> m b -> a -> m c -> m c -- | Generalized version of allowInterrupt. allowInterrupt :: MonadBase IO m => m () -- | Generalized version of getMaskingState. getMaskingState :: MonadBase IO m => m MaskingState -- | Generalized version of uninterruptibleMask_. uninterruptibleMask_ :: MonadBaseControl IO m => m a -> m a -- | Generalized version of uninterruptibleMask. uninterruptibleMask :: MonadBaseControl IO m => forall a. () => m a -> m a -> m b -> m b -- | Generalized version of mask_. mask_ :: MonadBaseControl IO m => m a -> m a -- | Generalized version of mask. mask :: MonadBaseControl IO m => forall a. () => m a -> m a -> m b -> m b -- | Generalized version of evaluate. evaluate :: MonadBase IO m => a -> m a -- | Generalized version of tryJust. -- -- Note, when the given computation throws an exception any monadic side -- effects in m will be discarded. tryJust :: (MonadBaseControl IO m, Exception e) => e -> Maybe b -> m a -> m Either b a -- | Generalized version of try. -- -- Note, when the given computation throws an exception any monadic side -- effects in m will be discarded. try :: (MonadBaseControl IO m, Exception e) => m a -> m Either e a -- | Generalized version of handleJust. -- -- Note, when the given computation throws an exception any monadic side -- effects in m will be discarded. handleJust :: (MonadBaseControl IO m, Exception e) => e -> Maybe b -> b -> m a -> m a -> m a -- | Generalized version of handle. -- -- Note, when the given computation throws an exception any monadic side -- effects in m will be discarded. handle :: (MonadBaseControl IO m, Exception e) => e -> m a -> m a -> m a -- | Generalized version of catchJust. -- -- Note, when the given computation throws an exception any monadic side -- effects in m will be discarded. catchJust :: (MonadBaseControl IO m, Exception e) => e -> Maybe b -> m a -> b -> m a -> m a -- | Generalized version of catches. -- -- Note, when the given computation throws an exception any monadic side -- effects in m will be discarded. catches :: MonadBaseControl IO m => m a -> [Handler m a] -> m a -- | Generalized version of catch. -- -- Note, when the given computation throws an exception any monadic side -- effects in m will be discarded. catch :: (MonadBaseControl IO m, Exception e) => m a -> e -> m a -> m a -- | Generalized version of throwTo. throwTo :: (MonadBase IO m, Exception e) => ThreadId -> e -> m () -- | Generalized version of throwIO. throwIO :: (MonadBase IO m, Exception e) => e -> m a -- | Generalized version of Handler. data Handler (m :: * -> *) a [Handler] :: Handler m a headMay :: () => [a] -> Maybe a initMay :: () => [a] -> Maybe [a] -- |
--   tailMay [] = Nothing
--   tailMay [1,3,4] = Just [3,4]
--   
tailMay :: () => [a] -> Maybe [a] -- | maybe with hanging function. maybe' :: Maybe a -> b -> (a -> b) -> b -- | either with hanging function. either' :: Either a b -> (a -> c) -> (b -> c) -> c -- | Maybe that returns () if Nothing maybe_ :: Applicative f => Maybe a -> (a -> f ()) -> f () -- | Throw Exception on either error. eitherThrowIO :: (MonadIO m, Exception e) => Either e a -> m a -- | Throw userError on either error. eitherThrowIO' :: MonadIO m => Either String a -> m a -- | Throw Exception on maybe nothing. maybeThrowIO :: (MonadIO m, Exception e) => e -> Maybe a -> m a -- | Throw userError on maybe nothing. maybeThrowIO' :: MonadIO m => String -> Maybe a -> m a -- | Throw userError on false. boolThrowIO :: MonadIO m => String -> Bool -> m () -- | Reverse of textToString textFromString :: String -> Text -- | Show text with compatibility. textShow :: Show a => a -> Text -- | Show string with compatibility. stringShow :: Show a => a -> String -- | / for IsString. (-/-) :: (IsString s, Monoid s) => s -> s -> s -- | | for IsString. (-|-) :: (IsString s, Monoid s) => s -> s -> s -- | . for IsString. (-.-) :: (IsString s, Monoid s) => s -> s -> s -- | : for IsString. (-:-) :: (IsString s, Monoid s) => s -> s -> s -- | For making tags. (=.) :: a -> b -> (a, b) -- | makeClassy with list of class constraints. makeClassyConstraints :: Name -> [Name] -> DecsQ -- | Run monad transformer, picking up logger from context. runTransT :: HasCtx c => c -> TransT c m a -> m a -- | Run base context. runCtx :: MonadIO m => TransT Ctx m a -> m a -- | Update base context's preamble. preCtx :: MonadCtx c m => Pairs -> TransT Ctx m a -> m a -- | Run stats context. runStatsCtx :: MonadCtx c m => TransT StatsCtx m a -> m a -- | Update stats context's preamble. preStatsCtx :: MonadStatsCtx c m => Pairs -> TransT StatsCtx m a -> m a -- | Update stats context's labels. labStatsCtx :: MonadStatsCtx c m => Tags -> TransT StatsCtx m a -> m a -- | Derive fields with camelCase. camelOptions :: Options -- | Derive fields with snake_case. snakeOptions :: Options -- | Derive fields with spinal-case. spinalOptions :: Options -- | Convert Aeson Result into a Maybe. maybeResult :: Result a -> Maybe a -- | Convert Aeson Result into an Either. eitherResult :: Result a -> Either String a