Movatterモバイル変換


[0]ホーム

URL:


base-4.12.0.0: Basic libraries

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
Maintainerlibraries@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Semigroup

Contents

Description

In mathematics, a semigroup is an algebraic structure consisting of a set together with an associative binary operation. A semigroup generalizes a monoid in that there might not exist an identity element. It also (originally) generalized a group (a monoid with all inverses) to a type where every element did not have to have an inverse, thus the name semigroup.

The use of(<>) in this module conflicts with an operator with the same name that is being exported by Data.Monoid. However, this package re-exports (most of) the contents of Data.Monoid, so to use semigroups and monoids in the same package just

import Data.Semigroup

Since: 4.9.0.0

Synopsis

Documentation

classSemigroup awhereSource#

The class of semigroups (types with an associative binary operation).

Instances should satisfy the associativity law:

Since: 4.9.0.0

Minimal complete definition

(<>)

Methods

(<>) :: a -> a -> ainfixr 6Source#

An associative operation.

sconcat ::NonEmpty a -> aSource#

Reduce a non-empty list with<>

The default definition should be sufficient, but this can be overridden for efficiency.

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

Repeat a valuen times.

Given that this works on aSemigroup it is allowed to fail if you request 0 or fewer repetitions, and the default definition will do so.

By making this a member of the class, idempotent semigroups and monoids can upgrade this to execute inO(1) by pickingstimes =stimesIdempotent orstimes =stimesIdempotentMonoid respectively.

Instances
SemigroupOrderingSource#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Semigroup ()Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Methods

(<>) :: () -> () -> ()Source#

sconcat ::NonEmpty () -> ()Source#

stimes ::Integral b => b -> () -> ()Source#

SemigroupAnySource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

SemigroupAllSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

SemigroupLifetimeSource#

Since: 4.10.0.0

Instance details

Defined inGHC.Event.Internal

SemigroupEventSource#

Since: 4.10.0.0

Instance details

Defined inGHC.Event.Internal

SemigroupVoidSource#

Since: 4.9.0.0

Instance details

Defined inData.Void

Semigroup [a]Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Methods

(<>) :: [a] -> [a] -> [a]Source#

sconcat ::NonEmpty [a] -> [a]Source#

stimes ::Integral b => b -> [a] -> [a]Source#

Semigroup a =>Semigroup (Maybe a)Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Semigroup a =>Semigroup (IO a)Source#

Since: 4.10.0.0

Instance details

Defined inGHC.Base

Methods

(<>) ::IO a ->IO a ->IO aSource#

sconcat ::NonEmpty (IO a) ->IO aSource#

stimes ::Integral b => b ->IO a ->IO aSource#

Semigroup p =>Semigroup (Par1 p)Source#

Since: 4.12.0.0

Instance details

Defined inGHC.Generics

Methods

(<>) ::Par1 p ->Par1 p ->Par1 pSource#

sconcat ::NonEmpty (Par1 p) ->Par1 pSource#

stimes ::Integral b => b ->Par1 p ->Par1 pSource#

Semigroup (NonEmpty a)Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Semigroup a =>Semigroup (Down a)Source#

Since: 4.11.0.0

Instance details

Defined inData.Ord

Methods

(<>) ::Down a ->Down a ->Down aSource#

sconcat ::NonEmpty (Down a) ->Down aSource#

stimes ::Integral b => b ->Down a ->Down aSource#

Num a =>Semigroup (Product a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Num a =>Semigroup (Sum a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

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

Semigroup (Endo a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

(<>) ::Endo a ->Endo a ->Endo aSource#

sconcat ::NonEmpty (Endo a) ->Endo aSource#

stimes ::Integral b => b ->Endo a ->Endo aSource#

Semigroup a =>Semigroup (Dual a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

(<>) ::Dual a ->Dual a ->Dual aSource#

sconcat ::NonEmpty (Dual a) ->Dual aSource#

stimes ::Integral b => b ->Dual a ->Dual aSource#

Semigroup (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Monoid

Methods

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

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

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

Semigroup (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Monoid

Semigroup a =>Semigroup (Identity a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Identity

Semigroup a =>Semigroup (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Monoid m =>Semigroup (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Semigroup (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

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

Semigroup (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Ord a =>Semigroup (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

(<>) ::Max a ->Max a ->Max aSource#

sconcat ::NonEmpty (Max a) ->Max aSource#

stimes ::Integral b => b ->Max a ->Max aSource#

Ord a =>Semigroup (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

(<>) ::Min a ->Min a ->Min aSource#

sconcat ::NonEmpty (Min a) ->Min aSource#

stimes ::Integral b => b ->Min a ->Min aSource#

Semigroup (Equivalence a)Source# 
Instance details

Defined inData.Functor.Contravariant

Semigroup (Comparison a)Source# 
Instance details

Defined inData.Functor.Contravariant

Semigroup (Predicate a)Source# 
Instance details

Defined inData.Functor.Contravariant

Semigroup b =>Semigroup (a -> b)Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Methods

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

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

stimes ::Integral b0 => b0 -> (a -> b) -> a -> bSource#

Semigroup (Either a b)Source#

Since: 4.9.0.0

Instance details

Defined inData.Either

Methods

(<>) ::Either a b ->Either a b ->Either a bSource#

sconcat ::NonEmpty (Either a b) ->Either a bSource#

stimes ::Integral b0 => b0 ->Either a b ->Either a bSource#

Semigroup (V1 p)Source#

Since: 4.12.0.0

Instance details

Defined inGHC.Generics

Methods

(<>) ::V1 p ->V1 p ->V1 pSource#

sconcat ::NonEmpty (V1 p) ->V1 pSource#

stimes ::Integral b => b ->V1 p ->V1 pSource#

Semigroup (U1 p)Source#

Since: 4.12.0.0

Instance details

Defined inGHC.Generics

Methods

(<>) ::U1 p ->U1 p ->U1 pSource#

sconcat ::NonEmpty (U1 p) ->U1 pSource#

stimes ::Integral b => b ->U1 p ->U1 pSource#

(Semigroup a,Semigroup b) =>Semigroup (a, b)Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Methods

(<>) :: (a, b) -> (a, b) -> (a, b)Source#

sconcat ::NonEmpty (a, b) -> (a, b)Source#

stimes ::Integral b0 => b0 -> (a, b) -> (a, b)Source#

Semigroup a =>Semigroup (ST s a)Source#

Since: 4.11.0.0

Instance details

Defined inGHC.ST

Methods

(<>) ::ST s a ->ST s a ->ST s aSource#

sconcat ::NonEmpty (ST s a) ->ST s aSource#

stimes ::Integral b => b ->ST s a ->ST s aSource#

Semigroup (Proxy s)Source#

Since: 4.9.0.0

Instance details

Defined inData.Proxy

Semigroup a =>Semigroup (Op a b)Source# 
Instance details

Defined inData.Functor.Contravariant

Methods

(<>) ::Op a b ->Op a b ->Op a bSource#

sconcat ::NonEmpty (Op a b) ->Op a bSource#

stimes ::Integral b0 => b0 ->Op a b ->Op a bSource#

Semigroup (f p) =>Semigroup (Rec1 f p)Source#

Since: 4.12.0.0

Instance details

Defined inGHC.Generics

Methods

(<>) ::Rec1 f p ->Rec1 f p ->Rec1 f pSource#

sconcat ::NonEmpty (Rec1 f p) ->Rec1 f pSource#

stimes ::Integral b => b ->Rec1 f p ->Rec1 f pSource#

(Semigroup a,Semigroup b,Semigroup c) =>Semigroup (a, b, c)Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c)Source#

sconcat ::NonEmpty (a, b, c) -> (a, b, c)Source#

stimes ::Integral b0 => b0 -> (a, b, c) -> (a, b, c)Source#

Alternative f =>Semigroup (Alt f a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

(<>) ::Alt f a ->Alt f a ->Alt f aSource#

sconcat ::NonEmpty (Alt f a) ->Alt f aSource#

stimes ::Integral b => b ->Alt f a ->Alt f aSource#

(Applicative f,Semigroup a) =>Semigroup (Ap f a)Source#

Since: 4.12.0.0

Instance details

Defined inData.Monoid

Methods

(<>) ::Ap f a ->Ap f a ->Ap f aSource#

sconcat ::NonEmpty (Ap f a) ->Ap f aSource#

stimes ::Integral b => b ->Ap f a ->Ap f aSource#

Semigroup a =>Semigroup (Const a b)Source#

Since: 4.9.0.0

Instance details

Defined inData.Functor.Const

Methods

(<>) ::Const a b ->Const a b ->Const a bSource#

sconcat ::NonEmpty (Const a b) ->Const a bSource#

stimes ::Integral b0 => b0 ->Const a b ->Const a bSource#

Semigroup c =>Semigroup (K1 i c p)Source#

Since: 4.12.0.0

Instance details

Defined inGHC.Generics

Methods

(<>) ::K1 i c p ->K1 i c p ->K1 i c pSource#

sconcat ::NonEmpty (K1 i c p) ->K1 i c pSource#

stimes ::Integral b => b ->K1 i c p ->K1 i c pSource#

(Semigroup (f p),Semigroup (g p)) =>Semigroup ((f:*: g) p)Source#

Since: 4.12.0.0

Instance details

Defined inGHC.Generics

Methods

(<>) :: (f:*: g) p -> (f:*: g) p -> (f:*: g) pSource#

sconcat ::NonEmpty ((f:*: g) p) -> (f:*: g) pSource#

stimes ::Integral b => b -> (f:*: g) p -> (f:*: g) pSource#

(Semigroup a,Semigroup b,Semigroup c,Semigroup d) =>Semigroup (a, b, c, d)Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d)Source#

sconcat ::NonEmpty (a, b, c, d) -> (a, b, c, d)Source#

stimes ::Integral b0 => b0 -> (a, b, c, d) -> (a, b, c, d)Source#

Semigroup (f p) =>Semigroup (M1 i c f p)Source#

Since: 4.12.0.0

Instance details

Defined inGHC.Generics

Methods

(<>) ::M1 i c f p ->M1 i c f p ->M1 i c f pSource#

sconcat ::NonEmpty (M1 i c f p) ->M1 i c f pSource#

stimes ::Integral b => b ->M1 i c f p ->M1 i c f pSource#

Semigroup (f (g p)) =>Semigroup ((f:.: g) p)Source#

Since: 4.12.0.0

Instance details

Defined inGHC.Generics

Methods

(<>) :: (f:.: g) p -> (f:.: g) p -> (f:.: g) pSource#

sconcat ::NonEmpty ((f:.: g) p) -> (f:.: g) pSource#

stimes ::Integral b => b -> (f:.: g) p -> (f:.: g) pSource#

(Semigroup a,Semigroup b,Semigroup c,Semigroup d,Semigroup e) =>Semigroup (a, b, c, d, e)Source#

Since: 4.9.0.0

Instance details

Defined inGHC.Base

Methods

(<>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e)Source#

sconcat ::NonEmpty (a, b, c, d, e) -> (a, b, c, d, e)Source#

stimes ::Integral b0 => b0 -> (a, b, c, d, e) -> (a, b, c, d, e)Source#

stimesMonoid :: (Integral b,Monoid a) => b -> a -> aSource#

This is a valid definition ofstimes for aMonoid.

Unlike the default definition ofstimes, it is defined for 0 and so it should be preferred where possible.

stimesIdempotent ::Integral b => b -> a -> aSource#

This is a valid definition ofstimes for an idempotentSemigroup.

Whenx <> x = x, this definition should be preferred, because it works inO(1) rather thanO(log n).

stimesIdempotentMonoid :: (Integral b,Monoid a) => b -> a -> aSource#

This is a valid definition ofstimes for an idempotentMonoid.

Whenmappend x x = x, this definition should be preferred, because it works inO(1) rather thanO(log n)

mtimesDefault :: (Integral b,Monoid a) => b -> a -> aSource#

Repeat a valuen times.

mtimesDefault n a = a <> a <> ... <> a  -- using <> (n-1) times

Implemented usingstimes andmempty.

This is a suitable definition for anmtimes member ofMonoid.

Semigroups

newtypeMin aSource#

Constructors

Min 

Fields

Instances
MonadMinSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

(>>=) ::Min a -> (a ->Min b) ->Min bSource#

(>>) ::Min a ->Min b ->Min bSource#

return :: a ->Min aSource#

fail ::String ->Min aSource#

FunctorMinSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fmap :: (a -> b) ->Min a ->Min bSource#

(<$) :: a ->Min b ->Min aSource#

MonadFixMinSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

mfix :: (a ->Min a) ->Min aSource#

ApplicativeMinSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

pure :: a ->Min aSource#

(<*>) ::Min (a -> b) ->Min a ->Min bSource#

liftA2 :: (a -> b -> c) ->Min a ->Min b ->Min cSource#

(*>) ::Min a ->Min b ->Min bSource#

(<*) ::Min a ->Min b ->Min aSource#

FoldableMinSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fold ::Monoid m =>Min m -> mSource#

foldMap ::Monoid m => (a -> m) ->Min a -> mSource#

foldr :: (a -> b -> b) -> b ->Min a -> bSource#

foldr' :: (a -> b -> b) -> b ->Min a -> bSource#

foldl :: (b -> a -> b) -> b ->Min a -> bSource#

foldl' :: (b -> a -> b) -> b ->Min a -> bSource#

foldr1 :: (a -> a -> a) ->Min a -> aSource#

foldl1 :: (a -> a -> a) ->Min a -> aSource#

toList ::Min a -> [a]Source#

null ::Min a ->BoolSource#

length ::Min a ->IntSource#

elem ::Eq a => a ->Min a ->BoolSource#

maximum ::Ord a =>Min a -> aSource#

minimum ::Ord a =>Min a -> aSource#

sum ::Num a =>Min a -> aSource#

product ::Num a =>Min a -> aSource#

TraversableMinSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

sequenceA ::Applicative f =>Min (f a) -> f (Min a)Source#

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

sequence ::Monad m =>Min (m a) -> m (Min a)Source#

Bounded a =>Bounded (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Enum a =>Enum (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Eq a =>Eq (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

Data a =>Data (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Min a -> c (Min a)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Min a)Source#

toConstr ::Min a ->ConstrSource#

dataTypeOf ::Min a ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Min a))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Min a))Source#

gmapT :: (forall b.Data b => b -> b) ->Min a ->Min aSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Min a -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Min a -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Min a -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Min a -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Min a -> m (Min a)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Min a -> m (Min a)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Min a -> m (Min a)Source#

Num a =>Num (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Ord a =>Ord (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

compare ::Min a ->Min a ->Ordering#

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

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

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

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

max ::Min a ->Min a ->Min a#

min ::Min a ->Min a ->Min a#

Read a =>Read (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Show a =>Show (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic (Min a)Source# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep (Min a) ::Type ->TypeSource#

Methods

from ::Min a ->Rep (Min a) xSource#

to ::Rep (Min a) x ->Min aSource#

Ord a =>Semigroup (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

(<>) ::Min a ->Min a ->Min aSource#

sconcat ::NonEmpty (Min a) ->Min aSource#

stimes ::Integral b => b ->Min a ->Min aSource#

(Ord a,Bounded a) =>Monoid (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

mempty ::Min aSource#

mappend ::Min a ->Min a ->Min aSource#

mconcat :: [Min a] ->Min aSource#

Generic1MinSource# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep1Min :: k ->TypeSource#

typeRep (Min a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep (Min a) =D1 (MetaData "Min" "Data.Semigroup" "base"True) (C1 (MetaCons "Min"PrefixITrue) (S1 (MetaSel (Just "getMin")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)))
typeRep1MinSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

newtypeMax aSource#

Constructors

Max 

Fields

Instances
MonadMaxSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

(>>=) ::Max a -> (a ->Max b) ->Max bSource#

(>>) ::Max a ->Max b ->Max bSource#

return :: a ->Max aSource#

fail ::String ->Max aSource#

FunctorMaxSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fmap :: (a -> b) ->Max a ->Max bSource#

(<$) :: a ->Max b ->Max aSource#

MonadFixMaxSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

mfix :: (a ->Max a) ->Max aSource#

ApplicativeMaxSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

pure :: a ->Max aSource#

(<*>) ::Max (a -> b) ->Max a ->Max bSource#

liftA2 :: (a -> b -> c) ->Max a ->Max b ->Max cSource#

(*>) ::Max a ->Max b ->Max bSource#

(<*) ::Max a ->Max b ->Max aSource#

FoldableMaxSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fold ::Monoid m =>Max m -> mSource#

foldMap ::Monoid m => (a -> m) ->Max a -> mSource#

foldr :: (a -> b -> b) -> b ->Max a -> bSource#

foldr' :: (a -> b -> b) -> b ->Max a -> bSource#

foldl :: (b -> a -> b) -> b ->Max a -> bSource#

foldl' :: (b -> a -> b) -> b ->Max a -> bSource#

foldr1 :: (a -> a -> a) ->Max a -> aSource#

foldl1 :: (a -> a -> a) ->Max a -> aSource#

toList ::Max a -> [a]Source#

null ::Max a ->BoolSource#

length ::Max a ->IntSource#

elem ::Eq a => a ->Max a ->BoolSource#

maximum ::Ord a =>Max a -> aSource#

minimum ::Ord a =>Max a -> aSource#

sum ::Num a =>Max a -> aSource#

product ::Num a =>Max a -> aSource#

TraversableMaxSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

sequenceA ::Applicative f =>Max (f a) -> f (Max a)Source#

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

sequence ::Monad m =>Max (m a) -> m (Max a)Source#

Bounded a =>Bounded (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Enum a =>Enum (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Eq a =>Eq (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

Data a =>Data (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Max a -> c (Max a)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Max a)Source#

toConstr ::Max a ->ConstrSource#

dataTypeOf ::Max a ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Max a))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Max a))Source#

gmapT :: (forall b.Data b => b -> b) ->Max a ->Max aSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Max a -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Max a -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Max a -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Max a -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Max a -> m (Max a)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Max a -> m (Max a)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Max a -> m (Max a)Source#

Num a =>Num (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Ord a =>Ord (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

compare ::Max a ->Max a ->Ordering#

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

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

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

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

max ::Max a ->Max a ->Max a#

min ::Max a ->Max a ->Max a#

Read a =>Read (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Show a =>Show (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic (Max a)Source# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep (Max a) ::Type ->TypeSource#

Methods

from ::Max a ->Rep (Max a) xSource#

to ::Rep (Max a) x ->Max aSource#

Ord a =>Semigroup (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

(<>) ::Max a ->Max a ->Max aSource#

sconcat ::NonEmpty (Max a) ->Max aSource#

stimes ::Integral b => b ->Max a ->Max aSource#

(Ord a,Bounded a) =>Monoid (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

mempty ::Max aSource#

mappend ::Max a ->Max a ->Max aSource#

mconcat :: [Max a] ->Max aSource#

Generic1MaxSource# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep1Max :: k ->TypeSource#

typeRep (Max a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep (Max a) =D1 (MetaData "Max" "Data.Semigroup" "base"True) (C1 (MetaCons "Max"PrefixITrue) (S1 (MetaSel (Just "getMax")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)))
typeRep1MaxSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

newtypeFirst aSource#

UseOption (First a) to get the behavior ofFirst fromData.Monoid.

Constructors

First 

Fields

Instances
MonadFirstSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

(>>=) ::First a -> (a ->First b) ->First bSource#

(>>) ::First a ->First b ->First bSource#

return :: a ->First aSource#

fail ::String ->First aSource#

FunctorFirstSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fmap :: (a -> b) ->First a ->First bSource#

(<$) :: a ->First b ->First aSource#

MonadFixFirstSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

mfix :: (a ->First a) ->First aSource#

ApplicativeFirstSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

pure :: a ->First aSource#

(<*>) ::First (a -> b) ->First a ->First bSource#

liftA2 :: (a -> b -> c) ->First a ->First b ->First cSource#

(*>) ::First a ->First b ->First bSource#

(<*) ::First a ->First b ->First aSource#

FoldableFirstSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fold ::Monoid m =>First m -> mSource#

foldMap ::Monoid m => (a -> m) ->First a -> mSource#

foldr :: (a -> b -> b) -> b ->First a -> bSource#

foldr' :: (a -> b -> b) -> b ->First a -> bSource#

foldl :: (b -> a -> b) -> b ->First a -> bSource#

foldl' :: (b -> a -> b) -> b ->First a -> bSource#

foldr1 :: (a -> a -> a) ->First a -> aSource#

foldl1 :: (a -> a -> a) ->First a -> aSource#

toList ::First a -> [a]Source#

null ::First a ->BoolSource#

length ::First a ->IntSource#

elem ::Eq a => a ->First a ->BoolSource#

maximum ::Ord a =>First a -> aSource#

minimum ::Ord a =>First a -> aSource#

sum ::Num a =>First a -> aSource#

product ::Num a =>First a -> aSource#

TraversableFirstSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

sequenceA ::Applicative f =>First (f a) -> f (First a)Source#

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

sequence ::Monad m =>First (m a) -> m (First a)Source#

Bounded a =>Bounded (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Enum a =>Enum (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Eq a =>Eq (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

Data a =>Data (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->First a -> c (First a)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (First a)Source#

toConstr ::First a ->ConstrSource#

dataTypeOf ::First a ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (First a))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (First a))Source#

gmapT :: (forall b.Data b => b -> b) ->First a ->First aSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->First a -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->First a -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->First a -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->First a -> m (First a)Source#

Ord a =>Ord (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

compare ::First a ->First a ->Ordering#

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

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

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

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

max ::First a ->First a ->First a#

min ::First a ->First a ->First a#

Read a =>Read (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Show a =>Show (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic (First a)Source# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep (First a) ::Type ->TypeSource#

Methods

from ::First a ->Rep (First a) xSource#

to ::Rep (First a) x ->First aSource#

Semigroup (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic1FirstSource# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep1First :: k ->TypeSource#

typeRep (First a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep (First a) =D1 (MetaData "First" "Data.Semigroup" "base"True) (C1 (MetaCons "First"PrefixITrue) (S1 (MetaSel (Just "getFirst")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)))
typeRep1FirstSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep1First =D1 (MetaData "First" "Data.Semigroup" "base"True) (C1 (MetaCons "First"PrefixITrue) (S1 (MetaSel (Just "getFirst")NoSourceUnpackednessNoSourceStrictnessDecidedLazy)Par1))

newtypeLast aSource#

UseOption (Last a) to get the behavior ofLast fromData.Monoid

Constructors

Last 

Fields

Instances
MonadLastSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

(>>=) ::Last a -> (a ->Last b) ->Last bSource#

(>>) ::Last a ->Last b ->Last bSource#

return :: a ->Last aSource#

fail ::String ->Last aSource#

FunctorLastSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fmap :: (a -> b) ->Last a ->Last bSource#

(<$) :: a ->Last b ->Last aSource#

MonadFixLastSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

mfix :: (a ->Last a) ->Last aSource#

ApplicativeLastSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

pure :: a ->Last aSource#

(<*>) ::Last (a -> b) ->Last a ->Last bSource#

liftA2 :: (a -> b -> c) ->Last a ->Last b ->Last cSource#

(*>) ::Last a ->Last b ->Last bSource#

(<*) ::Last a ->Last b ->Last aSource#

FoldableLastSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fold ::Monoid m =>Last m -> mSource#

foldMap ::Monoid m => (a -> m) ->Last a -> mSource#

foldr :: (a -> b -> b) -> b ->Last a -> bSource#

foldr' :: (a -> b -> b) -> b ->Last a -> bSource#

foldl :: (b -> a -> b) -> b ->Last a -> bSource#

foldl' :: (b -> a -> b) -> b ->Last a -> bSource#

foldr1 :: (a -> a -> a) ->Last a -> aSource#

foldl1 :: (a -> a -> a) ->Last a -> aSource#

toList ::Last a -> [a]Source#

null ::Last a ->BoolSource#

length ::Last a ->IntSource#

elem ::Eq a => a ->Last a ->BoolSource#

maximum ::Ord a =>Last a -> aSource#

minimum ::Ord a =>Last a -> aSource#

sum ::Num a =>Last a -> aSource#

product ::Num a =>Last a -> aSource#

TraversableLastSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

sequenceA ::Applicative f =>Last (f a) -> f (Last a)Source#

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

sequence ::Monad m =>Last (m a) -> m (Last a)Source#

Bounded a =>Bounded (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Enum a =>Enum (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Eq a =>Eq (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

Data a =>Data (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Last a -> c (Last a)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Last a)Source#

toConstr ::Last a ->ConstrSource#

dataTypeOf ::Last a ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Last a))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Last a))Source#

gmapT :: (forall b.Data b => b -> b) ->Last a ->Last aSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Last a -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Last a -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Last a -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Last a -> m (Last a)Source#

Ord a =>Ord (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

compare ::Last a ->Last a ->Ordering#

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

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

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

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

max ::Last a ->Last a ->Last a#

min ::Last a ->Last a ->Last a#

Read a =>Read (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Show a =>Show (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic (Last a)Source# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep (Last a) ::Type ->TypeSource#

Methods

from ::Last a ->Rep (Last a) xSource#

to ::Rep (Last a) x ->Last aSource#

Semigroup (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

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

Generic1LastSource# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep1Last :: k ->TypeSource#

typeRep (Last a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep (Last a) =D1 (MetaData "Last" "Data.Semigroup" "base"True) (C1 (MetaCons "Last"PrefixITrue) (S1 (MetaSel (Just "getLast")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)))
typeRep1LastSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

newtypeWrappedMonoid mSource#

Provide a Semigroup for an arbitrary Monoid.

NOTE: This is not needed anymore sinceSemigroup became a superclass ofMonoid inbase-4.11 and this newtype be deprecated at some point in the future.

Constructors

WrapMonoid 

Fields

Instances
Bounded m =>Bounded (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Enum a =>Enum (WrappedMonoid a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Eq m =>Eq (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Data m =>Data (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->WrappedMonoid m -> c (WrappedMonoid m)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (WrappedMonoid m)Source#

toConstr ::WrappedMonoid m ->ConstrSource#

dataTypeOf ::WrappedMonoid m ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (WrappedMonoid m))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (WrappedMonoid m))Source#

gmapT :: (forall b.Data b => b -> b) ->WrappedMonoid m ->WrappedMonoid mSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->WrappedMonoid m -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->WrappedMonoid m -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->WrappedMonoid m -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->WrappedMonoid m -> uSource#

gmapM ::Monad m0 => (forall d.Data d => d -> m0 d) ->WrappedMonoid m -> m0 (WrappedMonoid m)Source#

gmapMp ::MonadPlus m0 => (forall d.Data d => d -> m0 d) ->WrappedMonoid m -> m0 (WrappedMonoid m)Source#

gmapMo ::MonadPlus m0 => (forall d.Data d => d -> m0 d) ->WrappedMonoid m -> m0 (WrappedMonoid m)Source#

Ord m =>Ord (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Read m =>Read (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Show m =>Show (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic (WrappedMonoid m)Source# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep (WrappedMonoid m) ::Type ->TypeSource#

Monoid m =>Semigroup (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Monoid m =>Monoid (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic1WrappedMonoidSource# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep1WrappedMonoid :: k ->TypeSource#

typeRep (WrappedMonoid m)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep (WrappedMonoid m) =D1 (MetaData "WrappedMonoid" "Data.Semigroup" "base"True) (C1 (MetaCons "WrapMonoid"PrefixITrue) (S1 (MetaSel (Just "unwrapMonoid")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 m)))
typeRep1WrappedMonoidSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep1WrappedMonoid =D1 (MetaData "WrappedMonoid" "Data.Semigroup" "base"True) (C1 (MetaCons "WrapMonoid"PrefixITrue) (S1 (MetaSel (Just "unwrapMonoid")NoSourceUnpackednessNoSourceStrictnessDecidedLazy)Par1))

Re-exported monoids from Data.Monoid

newtypeDual aSource#

The dual of aMonoid, obtained by swapping the arguments ofmappend.

>>>getDual (mappend (Dual "Hello") (Dual "World"))"WorldHello"

Constructors

Dual 

Fields

Instances
MonadDualSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

(>>=) ::Dual a -> (a ->Dual b) ->Dual bSource#

(>>) ::Dual a ->Dual b ->Dual bSource#

return :: a ->Dual aSource#

fail ::String ->Dual aSource#

FunctorDualSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

fmap :: (a -> b) ->Dual a ->Dual bSource#

(<$) :: a ->Dual b ->Dual aSource#

MonadFixDualSource#

Since: 4.8.0.0

Instance details

Defined inControl.Monad.Fix

Methods

mfix :: (a ->Dual a) ->Dual aSource#

ApplicativeDualSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

pure :: a ->Dual aSource#

(<*>) ::Dual (a -> b) ->Dual a ->Dual bSource#

liftA2 :: (a -> b -> c) ->Dual a ->Dual b ->Dual cSource#

(*>) ::Dual a ->Dual b ->Dual bSource#

(<*) ::Dual a ->Dual b ->Dual aSource#

FoldableDualSource#

Since: 4.8.0.0

Instance details

Defined inData.Foldable

Methods

fold ::Monoid m =>Dual m -> mSource#

foldMap ::Monoid m => (a -> m) ->Dual a -> mSource#

foldr :: (a -> b -> b) -> b ->Dual a -> bSource#

foldr' :: (a -> b -> b) -> b ->Dual a -> bSource#

foldl :: (b -> a -> b) -> b ->Dual a -> bSource#

foldl' :: (b -> a -> b) -> b ->Dual a -> bSource#

foldr1 :: (a -> a -> a) ->Dual a -> aSource#

foldl1 :: (a -> a -> a) ->Dual a -> aSource#

toList ::Dual a -> [a]Source#

null ::Dual a ->BoolSource#

length ::Dual a ->IntSource#

elem ::Eq a => a ->Dual a ->BoolSource#

maximum ::Ord a =>Dual a -> aSource#

minimum ::Ord a =>Dual a -> aSource#

sum ::Num a =>Dual a -> aSource#

product ::Num a =>Dual a -> aSource#

TraversableDualSource#

Since: 4.8.0.0

Instance details

Defined inData.Traversable

Methods

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

sequenceA ::Applicative f =>Dual (f a) -> f (Dual a)Source#

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

sequence ::Monad m =>Dual (m a) -> m (Dual a)Source#

MonadZipDualSource#

Since: 4.8.0.0

Instance details

Defined inControl.Monad.Zip

Methods

mzip ::Dual a ->Dual b ->Dual (a, b)Source#

mzipWith :: (a -> b -> c) ->Dual a ->Dual b ->Dual cSource#

munzip ::Dual (a, b) -> (Dual a,Dual b)Source#

Bounded a =>Bounded (Dual a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Eq a =>Eq (Dual a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

Data a =>Data (Dual a)Source#

Since: 4.8.0.0

Instance details

Defined inData.Data

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Dual a -> c (Dual a)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Dual a)Source#

toConstr ::Dual a ->ConstrSource#

dataTypeOf ::Dual a ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Dual a))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Dual a))Source#

gmapT :: (forall b.Data b => b -> b) ->Dual a ->Dual aSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Dual a -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Dual a -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Dual a -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Dual a -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Dual a -> m (Dual a)Source#

Ord a =>Ord (Dual a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Methods

compare ::Dual a ->Dual a ->Ordering#

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

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

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

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

max ::Dual a ->Dual a ->Dual a#

min ::Dual a ->Dual a ->Dual a#

Read a =>Read (Dual a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Show a =>Show (Dual a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Generic (Dual a)Source# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRep (Dual a) ::Type ->TypeSource#

Methods

from ::Dual a ->Rep (Dual a) xSource#

to ::Rep (Dual a) x ->Dual aSource#

Semigroup a =>Semigroup (Dual a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

(<>) ::Dual a ->Dual a ->Dual aSource#

sconcat ::NonEmpty (Dual a) ->Dual aSource#

stimes ::Integral b => b ->Dual a ->Dual aSource#

Monoid a =>Monoid (Dual a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Generic1DualSource# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRep1Dual :: k ->TypeSource#

typeRep (Dual a)Source#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRep (Dual a) =D1 (MetaData "Dual" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "Dual"PrefixITrue) (S1 (MetaSel (Just "getDual")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)))
typeRep1DualSource#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRep1Dual =D1 (MetaData "Dual" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "Dual"PrefixITrue) (S1 (MetaSel (Just "getDual")NoSourceUnpackednessNoSourceStrictnessDecidedLazy)Par1))

newtypeEndo aSource#

The monoid of endomorphisms under composition.

>>>let computation = Endo ("Hello, " ++) <> Endo (++ "!")>>>appEndo computation "Haskell""Hello, Haskell!"

Constructors

Endo 

Fields

Instances
Generic (Endo a)Source# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRep (Endo a) ::Type ->TypeSource#

Methods

from ::Endo a ->Rep (Endo a) xSource#

to ::Rep (Endo a) x ->Endo aSource#

Semigroup (Endo a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

(<>) ::Endo a ->Endo a ->Endo aSource#

sconcat ::NonEmpty (Endo a) ->Endo aSource#

stimes ::Integral b => b ->Endo a ->Endo aSource#

Monoid (Endo a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

typeRep (Endo a)Source#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRep (Endo a) =D1 (MetaData "Endo" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "Endo"PrefixITrue) (S1 (MetaSel (Just "appEndo")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 (a -> a))))

newtypeAllSource#

Boolean monoid under conjunction (&&).

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

Constructors

All 

Fields

Instances
BoundedAllSource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

EqAllSource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

DataAllSource#

Since: 4.8.0.0

Instance details

Defined inData.Data

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->All -> cAllSource#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAllSource#

toConstr ::All ->ConstrSource#

dataTypeOf ::All ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAll)Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAll)Source#

gmapT :: (forall b.Data b => b -> b) ->All ->AllSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->All -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->All -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->All -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->All -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->All -> mAllSource#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->All -> mAllSource#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->All -> mAllSource#

OrdAllSource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

ReadAllSource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

ShowAllSource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

GenericAllSource# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRepAll ::Type ->TypeSource#

SemigroupAllSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

MonoidAllSource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

typeRepAllSource#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRepAll =D1 (MetaData "All" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "All"PrefixITrue) (S1 (MetaSel (Just "getAll")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0Bool)))

newtypeAnySource#

Boolean monoid under disjunction (||).

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

Constructors

Any 

Fields

Instances
BoundedAnySource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

EqAnySource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

DataAnySource#

Since: 4.8.0.0

Instance details

Defined inData.Data

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Any -> cAnySource#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> cAnySource#

toConstr ::Any ->ConstrSource#

dataTypeOf ::Any ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (cAny)Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (cAny)Source#

gmapT :: (forall b.Data b => b -> b) ->Any ->AnySource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Any -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Any -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Any -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Any -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Any -> mAnySource#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Any -> mAnySource#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Any -> mAnySource#

OrdAnySource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

ReadAnySource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

ShowAnySource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

GenericAnySource# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRepAny ::Type ->TypeSource#

SemigroupAnySource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

MonoidAnySource#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

typeRepAnySource#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRepAny =D1 (MetaData "Any" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "Any"PrefixITrue) (S1 (MetaSel (Just "getAny")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0Bool)))

newtypeSum aSource#

Monoid under addition.

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

Constructors

Sum 

Fields

Instances
MonadSumSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

return :: a ->Sum aSource#

fail ::String ->Sum aSource#

FunctorSumSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

MonadFixSumSource#

Since: 4.8.0.0

Instance details

Defined inControl.Monad.Fix

Methods

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

ApplicativeSumSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

pure :: a ->Sum aSource#

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

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

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

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

FoldableSumSource#

Since: 4.8.0.0

Instance details

Defined inData.Foldable

Methods

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

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

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

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

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

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

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

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

toList ::Sum a -> [a]Source#

null ::Sum a ->BoolSource#

length ::Sum a ->IntSource#

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

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

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

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

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

TraversableSumSource#

Since: 4.8.0.0

Instance details

Defined inData.Traversable

Methods

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

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

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

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

MonadZipSumSource#

Since: 4.8.0.0

Instance details

Defined inControl.Monad.Zip

Methods

mzip ::Sum a ->Sum b ->Sum (a, b)Source#

mzipWith :: (a -> b -> c) ->Sum a ->Sum b ->Sum cSource#

munzip ::Sum (a, b) -> (Sum a,Sum b)Source#

Bounded a =>Bounded (Sum a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Eq a =>Eq (Sum a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

Data a =>Data (Sum a)Source#

Since: 4.8.0.0

Instance details

Defined inData.Data

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Sum a -> c (Sum a)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Sum a)Source#

toConstr ::Sum a ->ConstrSource#

dataTypeOf ::Sum a ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Sum a))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Sum a))Source#

gmapT :: (forall b.Data b => b -> b) ->Sum a ->Sum aSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Sum a -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Sum a -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Sum a -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Sum a -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Sum a -> m (Sum a)Source#

Num a =>Num (Sum a)Source#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

Ord a =>Ord (Sum a)Source#

Since: 2.1

Instance details

Defined inData.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)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Show a =>Show (Sum a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Generic (Sum a)Source# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRep (Sum a) ::Type ->TypeSource#

Methods

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

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

Num a =>Semigroup (Sum a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

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

Num a =>Monoid (Sum a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Methods

mempty ::Sum aSource#

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

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

Generic1SumSource# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRep1Sum :: k ->TypeSource#

typeRep (Sum a)Source#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRep (Sum a) =D1 (MetaData "Sum" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "Sum"PrefixITrue) (S1 (MetaSel (Just "getSum")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)))
typeRep1SumSource#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRep1Sum =D1 (MetaData "Sum" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "Sum"PrefixITrue) (S1 (MetaSel (Just "getSum")NoSourceUnpackednessNoSourceStrictnessDecidedLazy)Par1))

newtypeProduct aSource#

Monoid under multiplication.

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

Constructors

Product 

Fields

Instances
MonadProductSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

FunctorProductSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

MonadFixProductSource#

Since: 4.8.0.0

Instance details

Defined inControl.Monad.Fix

Methods

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

ApplicativeProductSource#

Since: 4.8.0.0

Instance details

Defined inData.Semigroup.Internal

Methods

pure :: a ->Product aSource#

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

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

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

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

FoldableProductSource#

Since: 4.8.0.0

Instance details

Defined inData.Foldable

Methods

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

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

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

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

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

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

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

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

toList ::Product a -> [a]Source#

null ::Product a ->BoolSource#

length ::Product a ->IntSource#

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

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

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

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

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

TraversableProductSource#

Since: 4.8.0.0

Instance details

Defined inData.Traversable

Methods

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

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

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

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

MonadZipProductSource#

Since: 4.8.0.0

Instance details

Defined inControl.Monad.Zip

Methods

mzip ::Product a ->Product b ->Product (a, b)Source#

mzipWith :: (a -> b -> c) ->Product a ->Product b ->Product cSource#

munzip ::Product (a, b) -> (Product a,Product b)Source#

Bounded a =>Bounded (Product a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Eq a =>Eq (Product a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Methods

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

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

Data a =>Data (Product a)Source#

Since: 4.8.0.0

Instance details

Defined inData.Data

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Product a -> c (Product a)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Product a)Source#

toConstr ::Product a ->ConstrSource#

dataTypeOf ::Product a ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Product a))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Product a))Source#

gmapT :: (forall b.Data b => b -> b) ->Product a ->Product aSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Product a -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Product a -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Product a -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Product a -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Product a -> m (Product a)Source#

Num a =>Num (Product a)Source#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

Ord a =>Ord (Product a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Read a =>Read (Product a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Show a =>Show (Product a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Generic (Product a)Source# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRep (Product a) ::Type ->TypeSource#

Methods

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

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

Num a =>Semigroup (Product a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup.Internal

Num a =>Monoid (Product a)Source#

Since: 2.1

Instance details

Defined inData.Semigroup.Internal

Generic1ProductSource# 
Instance details

Defined inData.Semigroup.Internal

Associated Types

typeRep1Product :: k ->TypeSource#

typeRep (Product a)Source#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRep (Product a) =D1 (MetaData "Product" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "Product"PrefixITrue) (S1 (MetaSel (Just "getProduct")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)))
typeRep1ProductSource#

Since: 4.7.0.0

Instance details

Defined inData.Semigroup.Internal

typeRep1Product =D1 (MetaData "Product" "Data.Semigroup.Internal" "base"True) (C1 (MetaCons "Product"PrefixITrue) (S1 (MetaSel (Just "getProduct")NoSourceUnpackednessNoSourceStrictnessDecidedLazy)Par1))

A better monoid for Maybe

newtypeOption aSource#

Option is effectivelyMaybe with a better instance ofMonoid, built off of an underlyingSemigroup instead of an underlyingMonoid.

Ideally, this type would not exist at all and we would just fix theMonoid instance ofMaybe.

In GHC 8.4 and higher, theMonoid instance forMaybe has been corrected to lift aSemigroup instance instead of aMonoid instance. Consequently, this type is no longer useful. It will be marked deprecated in GHC 8.8 and removed in GHC 8.10.

Constructors

Option 

Fields

Instances
MonadOptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

FunctorOptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fmap :: (a -> b) ->Option a ->Option bSource#

(<$) :: a ->Option b ->Option aSource#

MonadFixOptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

mfix :: (a ->Option a) ->Option aSource#

ApplicativeOptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

pure :: a ->Option aSource#

(<*>) ::Option (a -> b) ->Option a ->Option bSource#

liftA2 :: (a -> b -> c) ->Option a ->Option b ->Option cSource#

(*>) ::Option a ->Option b ->Option bSource#

(<*) ::Option a ->Option b ->Option aSource#

FoldableOptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fold ::Monoid m =>Option m -> mSource#

foldMap ::Monoid m => (a -> m) ->Option a -> mSource#

foldr :: (a -> b -> b) -> b ->Option a -> bSource#

foldr' :: (a -> b -> b) -> b ->Option a -> bSource#

foldl :: (b -> a -> b) -> b ->Option a -> bSource#

foldl' :: (b -> a -> b) -> b ->Option a -> bSource#

foldr1 :: (a -> a -> a) ->Option a -> aSource#

foldl1 :: (a -> a -> a) ->Option a -> aSource#

toList ::Option a -> [a]Source#

null ::Option a ->BoolSource#

length ::Option a ->IntSource#

elem ::Eq a => a ->Option a ->BoolSource#

maximum ::Ord a =>Option a -> aSource#

minimum ::Ord a =>Option a -> aSource#

sum ::Num a =>Option a -> aSource#

product ::Num a =>Option a -> aSource#

TraversableOptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

sequenceA ::Applicative f =>Option (f a) -> f (Option a)Source#

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

sequence ::Monad m =>Option (m a) -> m (Option a)Source#

MonadPlusOptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

AlternativeOptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Eq a =>Eq (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

Data a =>Data (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

gfoldl :: (forall d b.Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) ->Option a -> c (Option a)Source#

gunfold :: (forall b r.Data b => c (b -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Option a)Source#

toConstr ::Option a ->ConstrSource#

dataTypeOf ::Option a ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Option a))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Option a))Source#

gmapT :: (forall b.Data b => b -> b) ->Option a ->Option aSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Option a -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Option a -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Option a -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Option a -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Option a -> m (Option a)Source#

Ord a =>Ord (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Read a =>Read (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Show a =>Show (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic (Option a)Source# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep (Option a) ::Type ->TypeSource#

Methods

from ::Option a ->Rep (Option a) xSource#

to ::Rep (Option a) x ->Option aSource#

Semigroup a =>Semigroup (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Semigroup a =>Monoid (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic1OptionSource# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep1Option :: k ->TypeSource#

typeRep (Option a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep (Option a) =D1 (MetaData "Option" "Data.Semigroup" "base"True) (C1 (MetaCons "Option"PrefixITrue) (S1 (MetaSel (Just "getOption")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 (Maybe a))))
typeRep1OptionSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep1Option =D1 (MetaData "Option" "Data.Semigroup" "base"True) (C1 (MetaCons "Option"PrefixITrue) (S1 (MetaSel (Just "getOption")NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec1Maybe)))

option :: b -> (a -> b) ->Option a -> bSource#

Fold anOption case-wise, just likemaybe.

Difference lists of a semigroup

diff ::Semigroup m => m ->Endo mSource#

This lets you use a difference list of aSemigroup as aMonoid.

cycle1 ::Semigroup m => m -> mSource#

A generalization ofcycle to an arbitrarySemigroup. May fail to terminate for some values in some semigroups.

ArgMin, ArgMax

dataArg a bSource#

Arg isn't itself aSemigroup in its own right, but it can be placed insideMin andMax to compute an arg min or arg max.

Constructors

Arg a b 
Instances
BifunctorArgSource#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

bimap :: (a -> b) -> (c -> d) ->Arg a c ->Arg b dSource#

first :: (a -> b) ->Arg a c ->Arg b cSource#

second :: (b -> c) ->Arg a b ->Arg a cSource#

BifoldableArgSource#

Since: 4.10.0.0

Instance details

Defined inData.Semigroup

Methods

bifold ::Monoid m =>Arg m m -> mSource#

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

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c ->Arg a b -> cSource#

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c ->Arg a b -> cSource#

BitraversableArgSource#

Since: 4.10.0.0

Instance details

Defined inData.Semigroup

Methods

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

Functor (Arg a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fmap :: (a0 -> b) ->Arg a a0 ->Arg a bSource#

(<$) :: a0 ->Arg a b ->Arg a a0Source#

Foldable (Arg a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

fold ::Monoid m =>Arg a m -> mSource#

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

foldr :: (a0 -> b -> b) -> b ->Arg a a0 -> bSource#

foldr' :: (a0 -> b -> b) -> b ->Arg a a0 -> bSource#

foldl :: (b -> a0 -> b) -> b ->Arg a a0 -> bSource#

foldl' :: (b -> a0 -> b) -> b ->Arg a a0 -> bSource#

foldr1 :: (a0 -> a0 -> a0) ->Arg a a0 -> a0Source#

foldl1 :: (a0 -> a0 -> a0) ->Arg a a0 -> a0Source#

toList ::Arg a a0 -> [a0]Source#

null ::Arg a a0 ->BoolSource#

length ::Arg a a0 ->IntSource#

elem ::Eq a0 => a0 ->Arg a a0 ->BoolSource#

maximum ::Ord a0 =>Arg a a0 -> a0Source#

minimum ::Ord a0 =>Arg a a0 -> a0Source#

sum ::Num a0 =>Arg a a0 -> a0Source#

product ::Num a0 =>Arg a a0 -> a0Source#

Traversable (Arg a)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

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

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

Generic1 (Arg a ::Type ->Type)Source# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep1 (Arg a) :: k ->TypeSource#

Methods

from1 ::Arg a a0 ->Rep1 (Arg a) a0Source#

to1 ::Rep1 (Arg a) a0 ->Arg a a0Source#

Eq a =>Eq (Arg a b)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

(Data a,Data b) =>Data (Arg a b)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

gfoldl :: (forall d b0.Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) ->Arg a b -> c (Arg a b)Source#

gunfold :: (forall b0 r.Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) ->Constr -> c (Arg a b)Source#

toConstr ::Arg a b ->ConstrSource#

dataTypeOf ::Arg a b ->DataTypeSource#

dataCast1 ::Typeable t => (forall d.Data d => c (t d)) ->Maybe (c (Arg a b))Source#

dataCast2 ::Typeable t => (forall d e. (Data d,Data e) => c (t d e)) ->Maybe (c (Arg a b))Source#

gmapT :: (forall b0.Data b0 => b0 -> b0) ->Arg a b ->Arg a bSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Arg a b -> rSource#

gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Arg a b -> rSource#

gmapQ :: (forall d.Data d => d -> u) ->Arg a b -> [u]Source#

gmapQi ::Int -> (forall d.Data d => d -> u) ->Arg a b -> uSource#

gmapM ::Monad m => (forall d.Data d => d -> m d) ->Arg a b -> m (Arg a b)Source#

gmapMp ::MonadPlus m => (forall d.Data d => d -> m d) ->Arg a b -> m (Arg a b)Source#

gmapMo ::MonadPlus m => (forall d.Data d => d -> m d) ->Arg a b -> m (Arg a b)Source#

Ord a =>Ord (Arg a b)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Methods

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

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

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

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

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

max ::Arg a b ->Arg a b ->Arg a b#

min ::Arg a b ->Arg a b ->Arg a b#

(Read a,Read b) =>Read (Arg a b)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

(Show a,Show b) =>Show (Arg a b)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

Generic (Arg a b)Source# 
Instance details

Defined inData.Semigroup

Associated Types

typeRep (Arg a b) ::Type ->TypeSource#

Methods

from ::Arg a b ->Rep (Arg a b) xSource#

to ::Rep (Arg a b) x ->Arg a bSource#

typeRep1 (Arg a ::Type ->Type)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeRep (Arg a b)Source#

Since: 4.9.0.0

Instance details

Defined inData.Semigroup

typeArgMin a b =Min (Arg a b)Source#

typeArgMax a b =Max (Arg a b)Source#

Produced byHaddock version 2.20.0


[8]ページ先頭

©2009-2025 Movatter.jp