| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Lens.Family
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
- to :: Phantom f => (s -> a) -> LensLike f s t a b
- view :: FoldLike a s t a b -> s -> a
- (^.) :: s -> FoldLike a s t a b -> a
- folding :: (Foldable g, Phantom f, Applicative f) => (s -> g a) -> LensLike f s t a b
- views :: FoldLike r s t a b -> (a -> r) -> s -> r
- (^..) :: s -> FoldLike [a] s t a b -> [a]
- (^?) :: s -> FoldLike (First a) s t a b -> Maybe a
- toListOf :: FoldLike [a] s t a b -> s -> [a]
- allOf :: FoldLike All s t a b -> (a -> Bool) -> s -> Bool
- anyOf :: FoldLike Any s t a b -> (a -> Bool) -> s -> Bool
- firstOf :: FoldLike (First a) s t a b -> s -> Maybe a
- lastOf :: FoldLike (Last a) s t a b -> s -> Maybe a
- sumOf :: Num a => FoldLike (Sum a) s t a b -> s -> a
- productOf :: Num a => FoldLike (Product a) s t a b -> s -> a
- lengthOf :: Num r => FoldLike (Sum r) s t a b -> s -> r
- nullOf :: FoldLike All s t a b -> s -> Bool
- matching :: LensLike (Either a) s t a b -> s -> Either t a
- over :: ASetter s t a b -> (a -> b) -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- (.~) :: ASetter s t a b -> b -> s -> t
- review :: GrateLike (Constant () :: Type -> Type) s t a b -> b -> t
- zipWithOf :: GrateLike (Prod Identity Identity) s t a b -> (a -> a -> b) -> s -> s -> t
- degrating :: AGrate s t a b -> ((s -> a) -> b) -> t
- under :: AResetter s t a b -> (a -> b) -> s -> t
- reset :: AResetter s t a b -> b -> s -> t
- (&) :: s -> (s -> t) -> t
- (+~) :: Num a => ASetter s t a a -> a -> s -> t
- (*~) :: Num a => ASetter s t a a -> a -> s -> t
- (-~) :: Num a => ASetter s t a a -> a -> s -> t
- (//~) :: Fractional a => ASetter s t a a -> a -> s -> t
- (&&~) :: ASetter s t Bool Bool -> Bool -> s -> t
- (||~) :: ASetter s t Bool Bool -> Bool -> s -> t
- (<>~) :: Monoid a => ASetter s t a a -> a -> s -> t
- type AdapterLike (f :: Type -> Type) (g :: Type -> Type) s t a b = (g a -> f b) -> g s -> f t
- type AdapterLike' (f :: Type -> Type) (g :: Type -> Type) s a = (g a -> f a) -> g s -> f s
- type LensLike (f :: Type -> Type) s t a b = (a -> f b) -> s -> f t
- type LensLike' (f :: Type -> Type) s a = (a -> f a) -> s -> f s
- type FoldLike r s t a b = LensLike (Constant r :: Type -> Type) s t a b
- type FoldLike' r s a = LensLike' (Constant r :: Type -> Type) s a
- type GrateLike (g :: Type -> Type) s t a b = (g a -> b) -> g s -> t
- type GrateLike' (g :: Type -> Type) s a = (g a -> a) -> g s -> s
- type AGrate s t a b = GrateLike (PCont b a) s t a b
- type AGrate' s a = GrateLike' (PCont a a) s a
- type ASetter s t a b = LensLike Identity s t a b
- type ASetter' s a = LensLike' Identity s a
- type AResetter s t a b = GrateLike Identity s t a b
- type AResetter' s a = GrateLike' Identity s a
- data PCont i j a
- data First a
- data Last a
- class Functor f => Phantom (f :: Type -> Type)
- data Constant a (b :: k)
- data Identity a
- type Prod = Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type
- data All
- data Any
- data Sum a
- data Product a
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 and lens families have type Functor f => (a -> f a) -> s -> f s.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 aTraversals
^. 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 and traversal families have type Applicative f => (a -> f a) -> s -> f s.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 used 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 and grate families have type Functor g => (g a -> a) -> g s -> s.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.
- Adapters have type
(and Adapters families have typeFunctorf,Functorg) => (g a -> f a) -> g s -> f s(.Functorf,Functorg) => (g (a i) -> f (a j)) -> g (s i) -> f (s j) - Grids have type
(and Grids families have typeApplicativef,Functorg) => (g a -> f a) -> g s -> f s(.Applicativef,Functorg) => (g (a i) -> f (a j)) -> g (s i) -> f (s j) - Prisms have type
(and Prisms families have typeApplicativef,Traversableg) => (g a -> f a) -> g s -> f s(.Applicativef,Traversableg) => (g (a i) -> f (a j)) -> g (s i) -> f (s j)
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
To build your own optics, see Lens.Family.Unchecked.
For stock optics, see Lens.Family.Stock.
References:
Documentation
to :: Phantom f => (s -> a) -> LensLike f s t a b #
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 #
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 #
(^.) :: 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 #
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 #
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 #
(^..) :: s -> Fold s t a b -> [a]
Returns a list of all of the referenced values in order.
toListOf :: FoldLike [a] s t a b -> s -> [a] #
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 #
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 #
anyOf :: Fold s t a b -> (a -> Bool) -> s -> Bool
Returns true if any of the referenced values satisfy the given predicate.
sumOf :: Num a => FoldLike (Sum a) s t a b -> s -> a #
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 #
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 #
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 #
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 #
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 #
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.
review :: GrateLike (Constant () :: Type -> Type) s t a b -> b -> t #
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 #
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 #
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 #
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 #
reset :: Resetter s t a b -> b -> s -> t
Set all referenced fields to the given value.
Pseudo-imperatives
(//~) :: Fractional a => ASetter s t a a -> a -> s -> t infixr 4 #
(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t infixr 4 #
Monoidally append a value to all referenced fields.
Types
type GrateLike' (g :: Type -> Type) s a = (g a -> a) -> g s -> s #
type AGrate' s a = GrateLike' (PCont a a) s a #
type AResetter' s a = GrateLike' Identity s a #
class Functor f => Phantom (f :: Type -> Type) #
Minimal complete definition
coerce
Instances
| Phantom (Const a :: Type -> Type) # | |
Defined in Lens.Family.Phantom | |
| Phantom f => Phantom (AlongsideLeft f a) # | |
Defined in Lens.Family.Stock Methods coerce :: AlongsideLeft f a a0 -> AlongsideLeft f a b | |
| Phantom f => Phantom (AlongsideRight f a) # | |
Defined in Lens.Family.Stock Methods coerce :: AlongsideRight f a a0 -> AlongsideRight f a b | |
| Phantom g => Phantom (FromG e g) # | |
Defined in Lens.Family.Stock | |
| Phantom f => Phantom (Backwards f) # | |
Defined in Lens.Family.Phantom | |
| Phantom (Constant a :: Type -> Type) # | |
Defined in Lens.Family.Phantom | |
| Phantom g => Phantom (FromF i j g) # | |
Defined in Lens.Family.Stock | |
| (Phantom f, Functor g) => Phantom (Compose f g) # | |
Defined in Lens.Family.Phantom | |
Re-exports
Constant functor.
Instances
| Generic1 (Constant a :: k -> Type) | |||||
Defined in Data.Functor.Constant Associated Types
| |||||
| Bifoldable (Constant :: Type -> Type -> Type) | |||||
| Bifunctor (Constant :: Type -> Type -> Type) | |||||
| Bitraversable (Constant :: Type -> Type -> Type) | |||||
Defined in Data.Functor.Constant Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Constant a b -> f (Constant c d) # | |||||
| Eq2 (Constant :: Type -> Type -> Type) | |||||
| Ord2 (Constant :: Type -> Type -> Type) | |||||
Defined in Data.Functor.Constant | |||||
| Read2 (Constant :: Type -> Type -> Type) | |||||
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) | |||||
| Eq a => Eq1 (Constant a :: Type -> Type) | |||||
| Ord a => Ord1 (Constant a :: Type -> Type) | |||||
Defined in Data.Functor.Constant | |||||
| Read a => Read1 (Constant a :: Type -> Type) | |||||
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) | |||||
| Contravariant (Constant a :: Type -> Type) | |||||
| Monoid a => Applicative (Constant a :: Type -> Type) | |||||
Defined in Data.Functor.Constant | |||||
| Functor (Constant a :: Type -> Type) | |||||
| Foldable (Constant a :: Type -> Type) | |||||
Defined in Data.Functor.Constant Methods fold :: Monoid m => Constant a m -> m # foldMap :: Monoid m => (a0 -> m) -> Constant a a0 -> 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 # | |||||
| Traversable (Constant a :: Type -> Type) | |||||
Defined in Data.Functor.Constant | |||||
| Phantom (Constant a :: Type -> Type) # | |||||
Defined in Lens.Family.Phantom | |||||
| Monoid a => Monoid (Constant a b) | |||||
| Semigroup a => Semigroup (Constant a b) | |||||
| (Typeable b, Typeable k, Data a) => Data (Constant a b) | |||||
Defined in Data.Functor.Constant Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Constant a b -> c (Constant a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Constant a b) # toConstr :: Constant a b -> Constr # dataTypeOf :: Constant a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Constant a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Constant a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Constant a b -> Constant a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Constant a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Constant a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Constant a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Constant a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Constant a b -> m (Constant a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Constant a b -> m (Constant a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Constant a b -> m (Constant a b) # | |||||
| Generic (Constant a b) | |||||
Defined in Data.Functor.Constant Associated Types
| |||||
| Read a => Read (Constant a b) | |||||
| Show a => Show (Constant a b) | |||||
| Eq a => Eq (Constant a b) | |||||
| Ord a => Ord (Constant a b) | |||||
Defined in Data.Functor.Constant | |||||
| type Rep1 (Constant a :: k -> Type) | |||||
Defined in Data.Functor.Constant | |||||
| type Rep (Constant a b) | |||||
Defined in Data.Functor.Constant | |||||
Identity functor and monad. (a non-strict monad)
Examples
>>>fmap (+1) (Identity 0)Identity 1
>>>Identity [1, 2, 3] <> Identity [4, 5, 6]Identity [1,2,3,4,5,6]
>>> do
x <- Identity 10
y <- Identity (x + 5)
pure (x + y)
Identity 25
@since base-4.8.0.0
Instances
Boolean monoid under conjunction (&&).
All x <> All y = All (x && y)
Examples
>>>All True <> mempty <> All False)All {getAll = False}
>>>mconcat (map (\x -> All (even x)) [2,4,6,7,8])All {getAll = False}
>>>All True <> memptyAll {getAll = True}
Instances
| NFData All | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
| Monoid All | @since base-2.01 | ||||
| Semigroup All | @since base-4.9.0.0 | ||||
| Bounded All | @since base-2.01 | ||||
| Generic All | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Read All | @since base-2.01 | ||||
| Show All | @since base-2.01 | ||||
| Eq All | @since base-2.01 | ||||
| Ord All | @since base-2.01 | ||||
| type Rep All | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Boolean monoid under disjunction (||).
Any x <> Any y = Any (x || y)
Examples
>>>Any True <> mempty <> Any FalseAny {getAny = True}
>>>mconcat (map (\x -> Any (even x)) [2,4,6,7,8])Any {getAny = True}
>>>Any False <> memptyAny {getAny = False}
Instances
| NFData Any | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
| Monoid Any | @since base-2.01 | ||||
| Semigroup Any | @since base-4.9.0.0 | ||||
| Bounded Any | @since base-2.01 | ||||
| Generic Any | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Read Any | @since base-2.01 | ||||
| Show Any | @since base-2.01 | ||||
| Eq Any | @since base-2.01 | ||||
| Ord Any | @since base-2.01 | ||||
| type Rep Any | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Monoid under addition.
Sum a <> Sum b = Sum (a + b)
Examples
>>>Sum 1 <> Sum 2 <> memptySum {getSum = 3}
>>>mconcat [ Sum n | n <- [3 .. 9]]Sum {getSum = 42}
Instances
| MonadZip Sum | Since: base-4.8.0.0 | ||||
| Foldable1 Sum | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Sum m -> m # foldMap1 :: Semigroup m => (a -> m) -> Sum a -> m # foldMap1' :: Semigroup m => (a -> m) -> Sum a -> m # toNonEmpty :: Sum a -> NonEmpty a # maximum :: Ord a => Sum a -> a # minimum :: Ord a => Sum a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Sum a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Sum a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Sum a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Sum a -> b # | |||||
| NFData1 Sum | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
| Applicative Sum | @since base-4.8.0.0 | ||||
| Functor Sum | @since base-4.8.0.0 | ||||
| Monad Sum | @since base-4.8.0.0 | ||||
| Foldable Sum | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> 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 # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |||||
| Traversable Sum | @since base-4.8.0.0 | ||||
| Generic1 Sum | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| NFData a => NFData (Sum a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
| Num a => Monoid (Sum a) | @since base-2.01 | ||||
| Num a => Semigroup (Sum a) | @since base-4.9.0.0 | ||||
| Bounded a => Bounded (Sum a) | @since base-2.01 | ||||
| Generic (Sum a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Num a => Num (Sum a) | @since base-4.7.0.0 | ||||
| Read a => Read (Sum a) | @since base-2.01 | ||||
| Show a => Show (Sum a) | @since base-2.01 | ||||
| Eq a => Eq (Sum a) | @since base-2.01 | ||||
| Ord a => Ord (Sum a) | @since base-2.01 | ||||
| type Rep1 Sum | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep (Sum a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
Monoid under multiplication.
Product x <> Product y == Product (x * y)
Examples
>>>Product 3 <> Product 4 <> memptyProduct {getProduct = 12}
>>>mconcat [ Product n | n <- [2 .. 10]]Product {getProduct = 3628800}
Instances
| MonadZip Product | Since: base-4.8.0.0 | ||||
| Foldable1 Product | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 :: Semigroup m => Product m -> m # foldMap1 :: Semigroup m => (a -> m) -> Product a -> m # foldMap1' :: Semigroup m => (a -> m) -> Product a -> m # toNonEmpty :: Product a -> NonEmpty a # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Product a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Product a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Product a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Product a -> b # | |||||
| NFData1 Product | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
| Applicative Product | @since base-4.8.0.0 | ||||
| Functor Product | @since base-4.8.0.0 | ||||
| Monad Product | @since base-4.8.0.0 | ||||
| Foldable Product | @since base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => Product m -> m # foldMap :: Monoid m => (a -> m) -> Product a -> 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 # elem :: Eq a => a -> Product a -> Bool # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # | |||||
| Traversable Product | @since base-4.8.0.0 | ||||
| Generic1 Product | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| NFData a => NFData (Product a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
| Num a => Monoid (Product a) | @since base-2.01 | ||||
| Num a => Semigroup (Product a) | @since base-4.9.0.0 | ||||
| Bounded a => Bounded (Product a) | @since base-2.01 | ||||
| Generic (Product a) | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
| Num a => Num (Product a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| Read a => Read (Product a) | @since base-2.01 | ||||
| Show a => Show (Product a) | @since base-2.01 | ||||
| Eq a => Eq (Product a) | @since base-2.01 | ||||
| Ord a => Ord (Product a) | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep1 Product | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
| type Rep (Product a) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||