lens-family-core-2.0.0: Haskell 2022 Lens Families

Safe HaskellSafe
LanguageHaskell98

Lens.Family

Contents

Description

This is the main module for end-users of lens-families-core. If you are not building your own optics such as lenses, traversals, grates, etc., but just using optics made by others, this is the only module you need.

Synopsis

Lenses

This module provides ^. for accessing fields and .~ and %~ for setting and modifying fields. Lenses are composed with . from the Prelude and id is the identity lens.

Lens composition in this library enjoys the following identities.

  • x^.l1.l2 === x^.l1^.l2
  • l1.l2 %~ f === l1 %~ l2 %~ f

The identity lens behaves as follows.

  • x^.id === x
  • id %~ f === f

The & operator, allows for a convenient way to sequence record updating:

record & l1 .~ value1 & l2 .~ value2

Lenses are implemented in van Laarhoven style. Lenses have type Functor f => (a -> f a) -> s -> f s and lens families have type Functor f => (a i -> f (a j)) -> s i -> f (s j).

Keep in mind that lenses and lens families can be used directly for functorial updates. For example, _2 id gives you strength.

_2 id :: Functor f => (a, f b) -> f (a, b)

Here is an example of code that uses the Maybe functor to preserves sharing during update when possible.

-- | 'sharedUpdate' returns the *identical* object if the update doesn't change anything.
-- This is useful for preserving sharing.
sharedUpdate :: Eq a => LensLike' Maybe s a -> (a -> a) -> s -> s
sharedUpdate l f s = fromMaybe s (l f' s)
 where
  f' a | b == a    = Nothing
       | otherwise = Just b
   where
    b = f a

Traversals

^. can be used with traversals to access monoidal fields. The result will be a mconcat of all the fields referenced. The various fooOf functions can be used to access different monoidal summaries of some kinds of values.

^? can be used to access the first value of a traversal. Nothing is returned when the traversal has no references.

^.. can be used with a traversals and will return a list of all fields referenced.

When .~ is used with a traversal, all referenced fields will be set to the same value, and when %~ is used with a traversal, all referenced fields will be modified with the same function.

A variant of ^? call matching returns Either a Right value which is the first value of the traversal, or a Left value which is a "proof" that the traversal has no elements. The "proof" consists of the original input structure, but in the case of polymorphic families, the type parameter is replaced with a fresh type variable, thus proving that the type parameter was unused.

Like all optics, traversals can be composed with ., and because every lens is automatically a traversal, lenses and traversals can be composed with . yielding a traversal.

Traversals are implemented in van Laarhoven style. Traversals have type Applicative f => (a -> f a) -> s -> f s and traversal families have type Applicative f => (a i -> f (a j)) -> s i -> f (s j).

Grates

zipWithOf can be used with grates to zip two structure together provided a binary operation.

under can be to modify each value in a structure according to a function. This works analogous to how over works for lenses and traversals.

review can be used with grates to construct a constant grate from a single value. This is like a 0-ary zipWith function.

degrating can be used to build higher arity zipWithOf functions:

zipWith3Of :: AGrate s t a b -> (a -> a -> a -> b) -> s -> s -> s -> t
zipWith3Of l f s1 s2 s3 = degrating l (\k -> f (k s1) (k s2) (k s3))

Like all optics, grates can be composed with ., and id is the identity grate.

Grates are implemented in van Laarhoven style.

Grates have type Functor g => (g a -> a) -> g s -> s and grate families have type Functor g => (g (a i) -> a j) -> g (s i) -> s j.

Keep in mind that grates and grate families can be used directly for functorial zipping. For example,

both sum :: Num a => [(a, a)] -> (a, a)

will take a list of pairs return the sum of the first components and the sum of the second components. For another example,

cod id :: Functor f => f (r -> a) -> r -> f a

will turn a functor full of functions into a function returning a functor full of results.

Adapters, Grids, and Prisms

The Adapter, Prism, and Grid optics are all AdapterLike optics and typically not used directly, but either converted to a LensLike optic using under, or into a GrateLike optic using over. See under and over for details about which conversions are possible.

These optics are implemented in van Laarhoven style.

Keep in mind that these optics and their families can sometimes be used directly, without using over and under. Sometimes you can take advantage of the fact that

   LensLike f (g s) t (g a) b
  ==
   AdapterLike f g s t a b
  ==
   GrateLike g s (f t) a (f b)

For example, if you have a grid for your structure to another type that has an Arbitray instance, such as grid from a custom word type to Bool, e.g. myWordBitVector :: (Applicative f, Functor g) => AdapterLike' f g MyWord Bool, you can use the grid to create an Arbitrary instance for your structure by directly applying review:

instance Arbitrary MyWord where
  arbitrary = review myWordBitVector arbitrary

Building and Finding Optics

Documentation

to :: Phantom f => (s -> a) -> LensLike f s t a b Source #

to :: (s -> a) -> Getter s t a b

to promotes a projection function to a read-only lens called a getter. To demote a lens to a projection function, use the section (^.l) or view l.

>>> (3 :+ 4, "example")^._1.to(abs)
5.0 :+ 0.0

view :: FoldLike a s t a b -> s -> a Source #

view :: Getter s t a b -> s -> a

Demote a lens or getter to a projection function.

view :: Monoid a => Fold s t a b -> s -> a

Returns the monoidal summary of a traversal or a fold.

(^.) :: s -> FoldLike a s t a b -> a infixl 8 Source #

(^.) :: s -> Getter s t a b -> a

Access the value referenced by a getter or lens.

(^.) :: Monoid a => s -> Fold s t a b -> a

Access the monoidal summary referenced by a traversal or a fold.

folding :: (Foldable g, Phantom f, Applicative f) => (s -> g a) -> LensLike f s t a b Source #

folding :: (s -> [a]) -> Fold s t a b

folding promotes a "toList" function to a read-only traversal called a fold.

To demote a traversal or fold to a "toList" function use the section (^..l) or toListOf l.

views :: FoldLike r s t a b -> (a -> r) -> s -> r Source #

views :: Monoid r => Fold s t a b -> (a -> r) -> s -> r

Given a fold or traversal, return the foldMap of all the values using the given function.

views :: Getter s t a b -> (a -> r) -> s -> r

views is not particularly useful for getters or lenses, but given a getter or lens, it returns the referenced value passed through the given function.

views l f s = f (view l s)

(^..) :: s -> FoldLike [a] s t a b -> [a] infixl 8 Source #

(^..) :: s -> Fold s t a b -> [a]

Returns a list of all of the referenced values in order.

(^?) :: s -> FoldLike (First a) s t a b -> Maybe a infixl 8 Source #

(^?) :: s -> Fold s t a b -> Maybe a

Returns Just the first referenced value. Returns Nothing if there are no referenced values.

toListOf :: FoldLike [a] s t a b -> s -> [a] Source #

toListOf :: Fold s t a b -> s -> [a]

Returns a list of all of the referenced values in order.

allOf :: FoldLike All s t a b -> (a -> Bool) -> s -> Bool Source #

allOf :: Fold s t a b -> (a -> Bool) -> s -> Bool

Returns true if all of the referenced values satisfy the given predicate.

anyOf :: FoldLike Any s t a b -> (a -> Bool) -> s -> Bool Source #

anyOf :: Fold s t a b -> (a -> Bool) -> s -> Bool

Returns true if any of the referenced values satisfy the given predicate.

firstOf :: FoldLike (First a) s t a b -> s -> Maybe a Source #

firstOf :: Fold s t a b -> s -> Maybe a

Returns Just the first referenced value. Returns Nothing if there are no referenced values. See ^? for an infix version of firstOf

lastOf :: FoldLike (Last a) s t a b -> s -> Maybe a Source #

lastOf :: Fold s t a b -> s -> Maybe a

Returns Just the last referenced value. Returns Nothing if there are no referenced values.

sumOf :: Num a => FoldLike (Sum a) s t a b -> s -> a Source #

sumOf :: Num a => Fold s t a b -> s -> a

Returns the sum of all the referenced values.

productOf :: Num a => FoldLike (Product a) s t a b -> s -> a Source #

productOf :: Num a => Fold s t a b -> s -> a

Returns the product of all the referenced values.

lengthOf :: Num r => FoldLike (Sum r) s t a b -> s -> r Source #

lengthOf :: Num r => Fold s t a b -> s -> r

Counts the number of references in a traversal or fold for the input.

nullOf :: FoldLike All s t a b -> s -> Bool Source #

nullOf :: Fold s t a b -> s -> Bool

Returns true if the number of references in the input is zero.

matching :: LensLike (Either a) s t a b -> s -> Either t a Source #

matching :: Traversal s t a b -> s -> Either t a

Returns Right of the first referenced value. Returns Left the original value when there are no referenced values. In case there are no referenced values, the result might have a fresh type parameter, thereby proving the original value had no referenced values.

over :: ASetter s t a b -> (a -> b) -> s -> t Source #

over :: Setter s t a b -> (a -> b) -> s -> t

Demote a setter to a semantic editor combinator.

over :: Prism s t a b -> Reviwer s t a b
over :: Grid s t a b -> Grate s t a b
over :: Adapter s t a b -> Grate s t a b

Covert an AdapterLike optic into a GrateLike optic.

(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 Source #

Modify all referenced fields.

set :: ASetter s t a b -> b -> s -> t Source #

Set all referenced fields to the given value.

(.~) :: ASetter s t a b -> b -> s -> t infixr 4 Source #

Set all referenced fields to the given value.

review :: GrateLike (Constant ()) s t a b -> b -> t Source #

review :: Grate s t a b -> b -> t
review :: Reviewer s t a b -> b -> t

zipWithOf :: GrateLike (Prod Identity Identity) s t a b -> (a -> a -> b) -> s -> s -> t Source #

zipWithOf :: Grate s t a b -> (a -> a -> b) -> s -> s -> t

Returns a binary instance of a grate.

zipWithOf l f x y = degrating l (k -> f (k x) (k y))

degrating :: AGrate s t a b -> ((s -> a) -> b) -> t Source #

degrating :: Grate s t a b -> ((s -> a) -> b) -> t

Demote a grate to its normal, higher-order function, form.

degrating . grate = id
grate . degrating = id

under :: AResetter s t a b -> (a -> b) -> s -> t Source #

under :: Resetter s t a b -> (a -> b) -> s -> t

Demote a resetter to a semantic editor combinator.

under :: Prism s t a b -> Traversal s t a b
under :: Grid s t a b -> Traversal s t a b
under :: Adapter s t a b -> Lens s t a b

Covert an AdapterLike optic into a LensLike optic.

Note: this function is unrelated to the lens package's under function.

reset :: AResetter s t a b -> b -> s -> t Source #

reset :: Resetter s t a b -> b -> s -> t

Set all referenced fields to the given value.

(&) :: s -> (s -> t) -> t infixl 1 Source #

A flipped version of ($).

Pseudo-imperatives

(+~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 Source #

(*~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 Source #

(-~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 Source #

(//~) :: Fractional a => ASetter s t a a -> a -> s -> t infixr 4 Source #

(&&~) :: ASetter s t Bool Bool -> Bool -> s -> t infixr 4 Source #

(||~) :: ASetter s t Bool Bool -> Bool -> s -> t infixr 4 Source #

(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t infixr 4 Source #

Monoidally append a value to all referenced fields.

Types

type AdapterLike f g s t a b = (g a -> f b) -> g s -> f t Source #

type AdapterLike' f g s a = (g a -> f a) -> g s -> f s Source #

type LensLike f s t a b = (a -> f b) -> s -> f t Source #

type LensLike' f s a = (a -> f a) -> s -> f s Source #

type FoldLike r s t a b = LensLike (Constant r) s t a b Source #

type FoldLike' r s a = LensLike' (Constant r) s a Source #

type GrateLike g s t a b = (g a -> b) -> g s -> t Source #

type GrateLike' g s a = (g a -> a) -> g s -> s Source #

type AGrate s t a b = GrateLike (PCont b a) s t a b Source #

type AGrate' s a = GrateLike' (PCont a a) s a Source #

type ASetter s t a b = LensLike Identity s t a b Source #

type AResetter s t a b = GrateLike Identity s t a b Source #

data PCont i j a Source #

Instances
Functor (PCont i j) Source # 
Instance details

Defined in Lens.Family

Methods

fmap :: (a -> b) -> PCont i j a -> PCont i j b #

(<$) :: a -> PCont i j b -> PCont i j a #

data First a Source #

Instances
Semigroup (First a) Source # 
Instance details

Defined in Lens.Family

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Monoid (First a) Source # 
Instance details

Defined in Lens.Family

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

data Last a Source #

Instances
Semigroup (Last a) Source # 
Instance details

Defined in Lens.Family

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Monoid (Last a) Source # 
Instance details

Defined in Lens.Family

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

class Functor f => Phantom f Source #

Minimal complete definition

coerce

Instances
Phantom (Const a :: Type -> Type) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Const a a0 -> Const a b

Phantom (Constant a :: Type -> Type) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Constant a a0 -> Constant a b

Phantom f => Phantom (Backwards f) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Backwards f a -> Backwards f b

Phantom g => Phantom (FromG e g) Source # 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: FromG e g a -> FromG e g b

Phantom f => Phantom (AlongsideRight f a) Source # 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: AlongsideRight f a a0 -> AlongsideRight f a b

Phantom f => Phantom (AlongsideLeft f a) Source # 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: AlongsideLeft f a a0 -> AlongsideLeft f a b

Phantom g => Phantom (FromF i j g) Source # 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: FromF i j g a -> FromF i j g b

(Phantom f, Functor g) => Phantom (Compose f g) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Compose f g a -> Compose f g b

Re-exports

data Constant a (b :: k) :: forall k. Type -> k -> Type #

Constant functor.

Instances
Bitraversable (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Constant a b -> f (Constant c d) #

Bifoldable (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bifold :: Monoid m => Constant m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Constant a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Constant a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Constant a b -> c #

Bifunctor (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bimap :: (a -> b) -> (c -> d) -> Constant a c -> Constant b d #

first :: (a -> b) -> Constant a c -> Constant b c #

second :: (b -> c) -> Constant a b -> Constant a c #

Eq2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Constant a c -> Constant b d -> Bool #

Ord2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Constant a c -> Constant b d -> Ordering #

Read2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Constant a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Constant a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Constant a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Constant a b] #

Show2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Constant a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Constant a b] -> ShowS #

Functor (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

fmap :: (a0 -> b) -> Constant a a0 -> Constant a b #

(<$) :: a0 -> Constant a b -> Constant a a0 #

Monoid a => Applicative (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

pure :: a0 -> Constant a a0 #

(<*>) :: Constant a (a0 -> b) -> Constant a a0 -> Constant a b #

liftA2 :: (a0 -> b -> c) -> Constant a a0 -> Constant a b -> Constant a c #

(*>) :: Constant a a0 -> Constant a b -> Constant a b #

(<*) :: Constant a a0 -> Constant a b -> Constant a a0 #

Foldable (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

fold :: Monoid m => Constant a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Constant a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

toList :: Constant a a0 -> [a0] #

null :: Constant a a0 -> Bool #

length :: Constant a a0 -> Int #

elem :: Eq a0 => a0 -> Constant a a0 -> Bool #

maximum :: Ord a0 => Constant a a0 -> a0 #

minimum :: Ord a0 => Constant a a0 -> a0 #

sum :: Num a0 => Constant a a0 -> a0 #

product :: Num a0 => Constant a a0 -> a0 #

Traversable (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

traverse :: Applicative f => (a0 -> f b) -> Constant a a0 -> f (Constant a b) #

sequenceA :: Applicative f => Constant a (f a0) -> f (Constant a a0) #

mapM :: Monad m => (a0 -> m b) -> Constant a a0 -> m (Constant a b) #

sequence :: Monad m => Constant a (m a0) -> m (Constant a a0) #

Contravariant (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

contramap :: (a0 -> b) -> Constant a b -> Constant a a0 #

(>$) :: b -> Constant a b -> Constant a a0 #

Eq a => Eq1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftEq :: (a0 -> b -> Bool) -> Constant a a0 -> Constant a b -> Bool #

Ord a => Ord1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftCompare :: (a0 -> b -> Ordering) -> Constant a a0 -> Constant a b -> Ordering #

Read a => Read1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Constant a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Constant a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Constant a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Constant a a0] #

Show a => Show1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Constant a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Constant a a0] -> ShowS #

Phantom (Constant a :: Type -> Type) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Constant a a0 -> Constant a b

Eq a => Eq (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

(==) :: Constant a b -> Constant a b -> Bool #

(/=) :: Constant a b -> Constant a b -> Bool #

Ord a => Ord (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

compare :: Constant a b -> Constant a b -> Ordering #

(<) :: Constant a b -> Constant a b -> Bool #

(<=) :: Constant a b -> Constant a b -> Bool #

(>) :: Constant a b -> Constant a b -> Bool #

(>=) :: Constant a b -> Constant a b -> Bool #

max :: Constant a b -> Constant a b -> Constant a b #

min :: Constant a b -> Constant a b -> Constant a b #

Read a => Read (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Show a => Show (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

showsPrec :: Int -> Constant a b -> ShowS #

show :: Constant a b -> String #

showList :: [Constant a b] -> ShowS #

Semigroup a => Semigroup (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

(<>) :: Constant a b -> Constant a b -> Constant a b #

sconcat :: NonEmpty (Constant a b) -> Constant a b #

stimes :: Integral b0 => b0 -> Constant a b -> Constant a b #

Monoid a => Monoid (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

mempty :: Constant a b #

mappend :: Constant a b -> Constant a b -> Constant a b #

mconcat :: [Constant a b] -> Constant a b #

data Identity a #

Identity functor and monad. (a non-strict monad)

Since: base-4.8.0.0

Instances
Monad Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

fail :: String -> Identity a #

Functor Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

MonadFix Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mfix :: (a -> Identity a) -> Identity a #

Applicative Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Foldable Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Traversable Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Eq1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool #

Ord1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Identity a -> Identity b -> Ordering #

Read1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Identity a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Identity a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Identity a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Identity a] #

Show1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identity a] -> ShowS #

Identical Identity Source # 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Identity a -> a

Bounded a => Bounded (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Enum a => Enum (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Eq a => Eq (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(==) :: Identity a -> Identity a -> Bool #

(/=) :: Identity a -> Identity a -> Bool #

Floating a => Floating (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Fractional a => Fractional (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Integral a => Integral (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Num a => Num (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Ord a => Ord (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

(<=) :: Identity a -> Identity a -> Bool #

(>) :: Identity a -> Identity a -> Bool #

(>=) :: Identity a -> Identity a -> Bool #

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Real a => Real (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

toRational :: Identity a -> Rational #

RealFloat a => RealFloat (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

RealFrac a => RealFrac (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Ix a => Ix (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Semigroup a => Semigroup (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Storable a => Storable (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Bits a => Bits (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

FiniteBits a => FiniteBits (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Generic1 Identity 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep1 Identity :: k -> Type #

Methods

from1 :: Identity a -> Rep1 Identity a #

to1 :: Rep1 Identity a -> Identity a #

type Rep (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep (Identity a) = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep1 Identity = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

data All #

Boolean monoid under conjunction (&&).

>>> getAll (All True <> mempty <> All False)
False
>>> getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))
False
Instances
Bounded All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: All #

maxBound :: All #

Eq All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: All -> All -> Bool #

(/=) :: All -> All -> Bool #

Ord All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: All -> All -> Ordering #

(<) :: All -> All -> Bool #

(<=) :: All -> All -> Bool #

(>) :: All -> All -> Bool #

(>=) :: All -> All -> Bool #

max :: All -> All -> All #

min :: All -> All -> All #

Read All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Semigroup All

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

type Rep All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep All = D1 (MetaData "All" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "All" PrefixI True) (S1 (MetaSel (Just "getAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

data Any #

Boolean monoid under disjunction (||).

>>> getAny (Any True <> mempty <> Any False)
True
>>> getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
True
Instances
Bounded Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Any #

maxBound :: Any #

Eq Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Any -> Any -> Bool #

(/=) :: Any -> Any -> Bool #

Ord Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Any -> Any -> Ordering #

(<) :: Any -> Any -> Bool #

(<=) :: Any -> Any -> Bool #

(>) :: Any -> Any -> Bool #

(>=) :: Any -> Any -> Bool #

max :: Any -> Any -> Any #

min :: Any -> Any -> Any #

Read Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Semigroup Any

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

type Rep Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep Any = D1 (MetaData "Any" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Any" PrefixI True) (S1 (MetaSel (Just "getAny") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

data Sum a #

Monoid under addition.

>>> getSum (Sum 1 <> Sum 2 <> mempty)
3
Instances
Monad Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b #

(>>) :: Sum a -> Sum b -> Sum b #

return :: a -> Sum a #

fail :: String -> Sum a #

Functor Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Sum a -> Sum b #

(<$) :: a -> Sum b -> Sum a #

Applicative Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Foldable Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Sum m -> m #

foldMap :: Monoid m => (a -> m) -> Sum a -> m #

foldr :: (a -> b -> b) -> b -> Sum a -> b #

foldr' :: (a -> b -> b) -> b -> Sum a -> b #

foldl :: (b -> a -> b) -> b -> Sum a -> b #

foldl' :: (b -> a -> b) -> b -> Sum a -> b #

foldr1 :: (a -> a -> a) -> Sum a -> a #

foldl1 :: (a -> a -> a) -> Sum a -> a #

toList :: Sum a -> [a] #

null :: Sum a -> Bool #

length :: Sum a -> Int #

elem :: Eq a => a -> Sum a -> Bool #

maximum :: Ord a => Sum a -> a #

minimum :: Ord a => Sum a -> a #

sum :: Num a => Sum a -> a #

product :: Num a => Sum a -> a #

Traversable Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Sum a -> f (Sum b) #

sequenceA :: Applicative f => Sum (f a) -> f (Sum a) #

mapM :: Monad m => (a -> m b) -> Sum a -> m (Sum b) #

sequence :: Monad m => Sum (m a) -> m (Sum a) #

Bounded a => Bounded (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Sum a #

maxBound :: Sum a #

Eq a => Eq (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Sum a -> Sum a -> Bool #

(/=) :: Sum a -> Sum a -> Bool #

Num a => Num (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Sum a -> Sum a -> Sum a #

(-) :: Sum a -> Sum a -> Sum a #

(*) :: Sum a -> Sum a -> Sum a #

negate :: Sum a -> Sum a #

abs :: Sum a -> Sum a #

signum :: Sum a -> Sum a #

fromInteger :: Integer -> Sum a #

Ord a => Ord (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Sum a -> Sum a -> Ordering #

(<) :: Sum a -> Sum a -> Bool #

(<=) :: Sum a -> Sum a -> Bool #

(>) :: Sum a -> Sum a -> Bool #

(>=) :: Sum a -> Sum a -> Bool #

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Read a => Read (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Num a => Semigroup (Sum a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Generic1 Sum 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Sum :: k -> Type #

Methods

from1 :: Sum a -> Rep1 Sum a #

to1 :: Rep1 Sum a -> Sum a #

type Rep (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Sum a) = D1 (MetaData "Sum" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Sum

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Sum = D1 (MetaData "Sum" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

data Product a #

Monoid under multiplication.

>>> getProduct (Product 3 <> Product 4 <> mempty)
12
Instances
Monad Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b #

(>>) :: Product a -> Product b -> Product b #

return :: a -> Product a #

fail :: String -> Product a #

Functor Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Product a -> Product b #

(<$) :: a -> Product b -> Product a #

Applicative Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Foldable Product

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Product m -> m #

foldMap :: Monoid m => (a -> m) -> Product a -> m #

foldr :: (a -> b -> b) -> b -> Product a -> b #

foldr' :: (a -> b -> b) -> b -> Product a -> b #

foldl :: (b -> a -> b) -> b -> Product a -> b #

foldl' :: (b -> a -> b) -> b -> Product a -> b #

foldr1 :: (a -> a -> a) -> Product a -> a #

foldl1 :: (a -> a -> a) -> Product a -> a #

toList :: Product a -> [a] #

null :: Product a -> Bool #

length :: Product a -> Int #

elem :: Eq a => a -> Product a -> Bool #

maximum :: Ord a => Product a -> a #

minimum :: Ord a => Product a -> a #

sum :: Num a => Product a -> a #

product :: Num a => Product a -> a #

Traversable Product

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Product a -> f (Product b) #

sequenceA :: Applicative f => Product (f a) -> f (Product a) #

mapM :: Monad m => (a -> m b) -> Product a -> m (Product b) #

sequence :: Monad m => Product (m a) -> m (Product a) #

Bounded a => Bounded (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Product a -> Product a -> Bool #

(/=) :: Product a -> Product a -> Bool #

Num a => Num (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Product a -> Product a -> Product a #

(-) :: Product a -> Product a -> Product a #

(*) :: Product a -> Product a -> Product a #

negate :: Product a -> Product a #

abs :: Product a -> Product a #

signum :: Product a -> Product a #

fromInteger :: Integer -> Product a #

Ord a => Ord (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Product a -> Product a -> Ordering #

(<) :: Product a -> Product a -> Bool #

(<=) :: Product a -> Product a -> Bool #

(>) :: Product a -> Product a -> Bool #

(>=) :: Product a -> Product a -> Bool #

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

Read a => Read (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Num a => Semigroup (Product a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Generic1 Product 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Product :: k -> Type #

Methods

from1 :: Product a -> Rep1 Product a #

to1 :: Rep1 Product a -> Product a #

type Rep (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Product a) = D1 (MetaData "Product" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Product

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Product = D1 (MetaData "Product" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))