Cabal-2.1.0.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Compat.Semigroup

Description

Compatibility layer for Data.Semigroup

Synopsis

Documentation

class Semigroup a where Source #

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 -> a infixr 6 Source #

An associative operation.

Instances
Semigroup Ordering

Since: 4.9.0.0

Instance details
Semigroup ()

Since: 4.9.0.0

Instance details

Methods

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

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

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

Semigroup Void

Since: 4.9.0.0

Instance details
Semigroup All

Since: 4.9.0.0

Instance details

Methods

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

sconcat :: NonEmpty All -> All Source #

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

Semigroup Any

Since: 4.9.0.0

Instance details

Methods

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

sconcat :: NonEmpty Any -> Any Source #

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

Semigroup Builder 
Instance details
Semigroup ByteString 
Instance details
Semigroup ShortByteString 
Instance details
Semigroup ByteString 
Instance details
Semigroup IntSet 
Instance details
Semigroup Doc 
Instance details

Methods

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

sconcat :: NonEmpty Doc -> Doc Source #

stimes :: Integral b => b -> Doc -> Doc Source #

Semigroup CDialect # 
Instance details
Semigroup ExecutableScope # 
Instance details
Semigroup ForeignLibType # 
Instance details
Semigroup ShortText # 
Instance details
Semigroup TestSuiteInterface # 
Instance details
Semigroup BenchmarkInterface # 
Instance details
Semigroup UnqualComponentName # 
Instance details
Semigroup SetupBuildInfo # 
Instance details
Semigroup DependencyMap # 
Instance details
Semigroup BuildInfo # 
Instance details
Semigroup TestSuite # 
Instance details
Semigroup Library # 
Instance details
Semigroup ForeignLib # 
Instance details
Semigroup Executable # 
Instance details
Semigroup Benchmark # 
Instance details
Semigroup Component # 
Instance details
Semigroup FlagAssignment # 
Instance details
Semigroup BenchmarkFlags # 
Instance details
Semigroup TestFlags # 
Instance details
Semigroup TestShowDetails # 
Instance details
Semigroup ReplFlags # 
Instance details
Semigroup BuildFlags # 
Instance details
Semigroup CleanFlags # 
Instance details
Semigroup HaddockFlags # 
Instance details
Semigroup DoctestFlags # 
Instance details
Semigroup HscolourFlags # 
Instance details
Semigroup RegisterFlags # 
Instance details
Semigroup SDistFlags # 
Instance details
Semigroup InstallFlags # 
Instance details
Semigroup CopyFlags # 
Instance details
Semigroup ConfigFlags # 
Instance details
Semigroup GlobalFlags # 
Instance details
Semigroup GhcOptions # 
Instance details
Semigroup [a]

Since: 4.9.0.0

Instance details

Methods

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

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

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

Semigroup a => Semigroup (Maybe a)

Since: 4.9.0.0

Instance details

Methods

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

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

stimes :: Integral b => b -> Maybe a -> Maybe a Source #

Semigroup a => Semigroup (IO a)

Since: 4.10.0.0

Instance details

Methods

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

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

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

Ord a => Semigroup (Min a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Ord a => Semigroup (Max a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Semigroup (First a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Semigroup (Last a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Monoid m => Semigroup (WrappedMonoid m)

Since: 4.9.0.0

Instance details
Semigroup a => Semigroup (Option a)

Since: 4.9.0.0

Instance details

Methods

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

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

stimes :: Integral b => b -> Option a -> Option a Source #

Semigroup a => Semigroup (Identity a) 
Instance details
Semigroup (First a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Semigroup (Last a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Semigroup a => Semigroup (Dual a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Semigroup (Endo a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Num a => Semigroup (Sum a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Num a => Semigroup (Product a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

Semigroup a => Semigroup (Down a)

Since: 4.11.0.0

Instance details

Methods

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

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

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

Semigroup (NonEmpty a)

Since: 4.9.0.0

Instance details
Semigroup (IntMap a) 
Instance details

Methods

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

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

stimes :: Integral b => b -> IntMap a -> IntMap a Source #

Semigroup (Seq a) 
Instance details

Methods

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

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

stimes :: Integral b => b -> Seq a -> Seq a Source #

Ord a => Semigroup (Set a) 
Instance details

Methods

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

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

stimes :: Integral b => b -> Set a -> Set a Source #

Semigroup (Doc a) 
Instance details

Methods

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

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

stimes :: Integral b => b -> Doc a -> Doc a Source #

Semigroup (PutM ()) 
Instance details

Methods

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

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

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

Semigroup (Last' a) # 
Instance details

Methods

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

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

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

Semigroup (DList a) # 
Instance details

Methods

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

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

stimes :: Integral b => b -> DList a -> DList a Source #

Semigroup (Condition a) # 
Instance details
Semigroup dir => Semigroup (InstallDirs dir) # 
Instance details
Ord a => Semigroup (NubListR a) # 
Instance details
Ord a => Semigroup (NubList a) # 
Instance details

Methods

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

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

stimes :: Integral b => b -> NubList a -> NubList a Source #

Semigroup (PackageIndex InstalledPackageInfo) # 
Instance details
Semigroup (Flag a) # 
Instance details

Methods

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

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

stimes :: Integral b => b -> Flag a -> Flag a Source #

Semigroup b => Semigroup (a -> b)

Since: 4.9.0.0

Instance details

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 (Either a b)

Since: 4.9.0.0

Instance details

Methods

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

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

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

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

Since: 4.9.0.0

Instance details

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)

Since: 4.11.0.0

Instance details

Methods

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

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

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

Semigroup (Proxy s)

Since: 4.9.0.0

Instance details

Methods

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

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

stimes :: Integral b => b -> Proxy s -> Proxy s Source #

Ord k => Semigroup (Map k v) 
Instance details

Methods

(<>) :: Map k v -> Map k v -> Map k v Source #

sconcat :: NonEmpty (Map k v) -> Map k v Source #

stimes :: Integral b => b -> Map k v -> Map k v Source #

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

Since: 4.9.0.0

Instance details

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 #

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

Methods

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

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

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

Alternative f => Semigroup (Alt f a)

Since: 4.9.0.0

Instance details

Methods

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

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

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

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

Since: 4.9.0.0

Instance details

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 a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e)

Since: 4.9.0.0

Instance details

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 #

class Semigroup a => Monoid a where Source #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a Source #

Identity of mappend

mappend :: a -> a -> a Source #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = '(<>)' since base-4.11.0.0.

mconcat :: [a] -> a Source #

Fold a list using the monoid.

For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances
Monoid Ordering

Since: 2.1

Instance details
Monoid ()

Since: 2.1

Instance details

Methods

mempty :: () Source #

mappend :: () -> () -> () Source #

mconcat :: [()] -> () Source #

Monoid All

Since: 2.1

Instance details
Monoid Any

Since: 2.1

Instance details
Monoid Builder 
Instance details
Monoid ByteString 
Instance details
Monoid ShortByteString 
Instance details
Monoid ByteString 
Instance details
Monoid IntSet 
Instance details
Monoid Doc 
Instance details
Monoid CDialect # 
Instance details
Monoid ExecutableScope # 
Instance details
Monoid ForeignLibType # 
Instance details
Monoid ShortText # 
Instance details
Monoid TestSuiteInterface # 
Instance details
Monoid BenchmarkInterface # 
Instance details
Monoid UnqualComponentName # 
Instance details
Monoid SetupBuildInfo # 
Instance details
Monoid DependencyMap # 
Instance details
Monoid BuildInfo # 
Instance details
Monoid TestSuite # 
Instance details
Monoid Library # 
Instance details
Monoid ForeignLib # 
Instance details
Monoid Executable # 
Instance details
Monoid Benchmark # 
Instance details
Monoid FlagAssignment # 
Instance details
Monoid BenchmarkFlags # 
Instance details
Monoid TestFlags # 
Instance details
Monoid TestShowDetails # 
Instance details
Monoid ReplFlags # 
Instance details
Monoid BuildFlags # 
Instance details
Monoid CleanFlags # 
Instance details
Monoid HaddockFlags # 
Instance details
Monoid DoctestFlags # 
Instance details
Monoid HscolourFlags # 
Instance details
Monoid RegisterFlags # 
Instance details
Monoid SDistFlags # 
Instance details
Monoid InstallFlags # 
Instance details
Monoid CopyFlags # 
Instance details
Monoid ConfigFlags # 
Instance details
Monoid GlobalFlags # 
Instance details
Monoid GhcOptions # 
Instance details
Monoid [a]

Since: 2.1

Instance details

Methods

mempty :: [a] Source #

mappend :: [a] -> [a] -> [a] Source #

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

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: 2.1

Instance details

Methods

mempty :: Maybe a Source #

mappend :: Maybe a -> Maybe a -> Maybe a Source #

mconcat :: [Maybe a] -> Maybe a Source #

Monoid a => Monoid (IO a)

Since: 4.9.0.0

Instance details

Methods

mempty :: IO a Source #

mappend :: IO a -> IO a -> IO a Source #

mconcat :: [IO a] -> IO a Source #

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

Since: 4.9.0.0

Instance details

Methods

mempty :: Min a Source #

mappend :: Min a -> Min a -> Min a Source #

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

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

Since: 4.9.0.0

Instance details

Methods

mempty :: Max a Source #

mappend :: Max a -> Max a -> Max a Source #

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

Monoid m => Monoid (WrappedMonoid m)

Since: 4.9.0.0

Instance details
Semigroup a => Monoid (Option a)

Since: 4.9.0.0

Instance details
Monoid a => Monoid (Identity a) 
Instance details
Monoid (First a)

Since: 2.1

Instance details

Methods

mempty :: First a Source #

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

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

Monoid (Last a)

Since: 2.1

Instance details

Methods

mempty :: Last a Source #

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

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

Monoid a => Monoid (Dual a)

Since: 2.1

Instance details

Methods

mempty :: Dual a Source #

mappend :: Dual a -> Dual a -> Dual a Source #

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

Monoid (Endo a)

Since: 2.1

Instance details

Methods

mempty :: Endo a Source #

mappend :: Endo a -> Endo a -> Endo a Source #

mconcat :: [Endo a] -> Endo a Source #

Num a => Monoid (Sum a)

Since: 2.1

Instance details

Methods

mempty :: Sum a Source #

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

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

Num a => Monoid (Product a)

Since: 2.1

Instance details
Monoid a => Monoid (Down a)

Since: 4.11.0.0

Instance details

Methods

mempty :: Down a Source #

mappend :: Down a -> Down a -> Down a Source #

mconcat :: [Down a] -> Down a Source #

Monoid (IntMap a) 
Instance details
Monoid (Seq a) 
Instance details

Methods

mempty :: Seq a Source #

mappend :: Seq a -> Seq a -> Seq a Source #

mconcat :: [Seq a] -> Seq a Source #

Ord a => Monoid (Set a) 
Instance details

Methods

mempty :: Set a Source #

mappend :: Set a -> Set a -> Set a Source #

mconcat :: [Set a] -> Set a Source #

Monoid (Doc a) 
Instance details

Methods

mempty :: Doc a Source #

mappend :: Doc a -> Doc a -> Doc a Source #

mconcat :: [Doc a] -> Doc a Source #

Monoid (PutM ()) 
Instance details

Methods

mempty :: PutM () Source #

mappend :: PutM () -> PutM () -> PutM () Source #

mconcat :: [PutM ()] -> PutM () Source #

Monoid (Last' a) # 
Instance details

Methods

mempty :: Last' a Source #

mappend :: Last' a -> Last' a -> Last' a Source #

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

Monoid (DList a) # 
Instance details

Methods

mempty :: DList a Source #

mappend :: DList a -> DList a -> DList a Source #

mconcat :: [DList a] -> DList a Source #

Monoid (Condition a) # 
Instance details
(Semigroup dir, Monoid dir) => Monoid (InstallDirs dir) # 
Instance details
Ord a => Monoid (NubListR a) # 
Instance details
Ord a => Monoid (NubList a) #

Monoid operations on NubLists. For a valid Monoid instance we need to satistfy the required monoid laws; identity, associativity and closure.

Identity : by inspection: mempty mappend NubList xs == NubList xs mappend mempty

Associativity : by inspection: (NubList xs mappend NubList ys) mappend NubList zs == NubList xs mappend (NubList ys mappend NubList zs)

Closure : appending two lists of type a and removing duplicates obviously does not change the type.

Instance details
Monoid (PackageIndex InstalledPackageInfo) # 
Instance details
Monoid (Flag a) # 
Instance details

Methods

mempty :: Flag a Source #

mappend :: Flag a -> Flag a -> Flag a Source #

mconcat :: [Flag a] -> Flag a Source #

Monoid b => Monoid (a -> b)

Since: 2.1

Instance details

Methods

mempty :: a -> b Source #

mappend :: (a -> b) -> (a -> b) -> a -> b Source #

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

(Monoid a, Monoid b) => Monoid (a, b)

Since: 2.1

Instance details

Methods

mempty :: (a, b) Source #

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

mconcat :: [(a, b)] -> (a, b) Source #

Monoid a => Monoid (ST s a)

Since: 4.11.0.0

Instance details

Methods

mempty :: ST s a Source #

mappend :: ST s a -> ST s a -> ST s a Source #

mconcat :: [ST s a] -> ST s a Source #

Monoid (Proxy s)

Since: 4.7.0.0

Instance details

Methods

mempty :: Proxy s Source #

mappend :: Proxy s -> Proxy s -> Proxy s Source #

mconcat :: [Proxy s] -> Proxy s Source #

Ord k => Monoid (Map k v) 
Instance details

Methods

mempty :: Map k v Source #

mappend :: Map k v -> Map k v -> Map k v Source #

mconcat :: [Map k v] -> Map k v Source #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: 2.1

Instance details

Methods

mempty :: (a, b, c) Source #

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

mconcat :: [(a, b, c)] -> (a, b, c) Source #

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

Methods

mempty :: Const a b Source #

mappend :: Const a b -> Const a b -> Const a b Source #

mconcat :: [Const a b] -> Const a b Source #

Alternative f => Monoid (Alt f a)

Since: 4.8.0.0

Instance details

Methods

mempty :: Alt f a Source #

mappend :: Alt f a -> Alt f a -> Alt f a Source #

mconcat :: [Alt f a] -> Alt f a Source #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: 2.1

Instance details

Methods

mempty :: (a, b, c, d) Source #

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

mconcat :: [(a, b, c, d)] -> (a, b, c, d) Source #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: 2.1

Instance details

Methods

mempty :: (a, b, c, d, e) Source #

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

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) Source #

newtype All :: * Source #

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
Bounded All 
Instance details
Eq All 
Instance details

Methods

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

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

Data All

Since: 4.8.0.0

Instance details

Methods

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

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

toConstr :: All -> Constr Source #

dataTypeOf :: All -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord All 
Instance details

Methods

compare :: All -> All -> Ordering #

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

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

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

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

max :: All -> All -> All #

min :: All -> All -> All #

Read All 
Instance details
Show All 
Instance details
Generic All 
Instance details

Associated Types

type Rep All :: * -> * Source #

Methods

from :: All -> Rep All x Source #

to :: Rep All x -> All Source #

Semigroup All

Since: 4.9.0.0

Instance details

Methods

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

sconcat :: NonEmpty All -> All Source #

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

Monoid All

Since: 2.1

Instance details
NFData All

Since: 1.4.0.0

Instance details

Methods

rnf :: All -> () Source #

Binary All

Since: 0.8.4.0

Instance details

Methods

put :: All -> Put Source #

get :: Get All Source #

putList :: [All] -> Put Source #

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

newtype Any :: * Source #

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
Bounded Any 
Instance details
Eq Any 
Instance details

Methods

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

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

Data Any

Since: 4.8.0.0

Instance details

Methods

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

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

toConstr :: Any -> Constr Source #

dataTypeOf :: Any -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Any 
Instance details

Methods

compare :: Any -> Any -> Ordering #

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

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

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

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

max :: Any -> Any -> Any #

min :: Any -> Any -> Any #

Read Any 
Instance details
Show Any 
Instance details
Generic Any 
Instance details

Associated Types

type Rep Any :: * -> * Source #

Methods

from :: Any -> Rep Any x Source #

to :: Rep Any x -> Any Source #

Semigroup Any

Since: 4.9.0.0

Instance details

Methods

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

sconcat :: NonEmpty Any -> Any Source #

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

Monoid Any

Since: 2.1

Instance details
NFData Any

Since: 1.4.0.0

Instance details

Methods

rnf :: Any -> () Source #

Binary Any

Since: 0.8.4.0

Instance details

Methods

put :: Any -> Put Source #

get :: Get Any Source #

putList :: [Any] -> Put Source #

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

newtype Last' a Source #

Cabal's own Last copy to avoid requiring an orphan Binary instance.

Once the oldest binary version we support provides a Binary instance for Last we can remove this one here.

NB: Last is defined differently and not a Monoid

Constructors

Last' 

Fields

Instances
Functor Last' # 
Instance details

Methods

fmap :: (a -> b) -> Last' a -> Last' b Source #

(<$) :: a -> Last' b -> Last' a Source #

Applicative Last' # 
Instance details

Methods

pure :: a -> Last' a Source #

(<*>) :: Last' (a -> b) -> Last' a -> Last' b Source #

liftA2 :: (a -> b -> c) -> Last' a -> Last' b -> Last' c Source #

(*>) :: Last' a -> Last' b -> Last' b Source #

(<*) :: Last' a -> Last' b -> Last' a Source #

Eq a => Eq (Last' a) # 
Instance details

Methods

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

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

Ord a => Ord (Last' a) # 
Instance details

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) # 
Instance details
Show a => Show (Last' a) # 
Instance details
Generic (Last' a) # 
Instance details

Associated Types

type Rep (Last' a) :: * -> * Source #

Methods

from :: Last' a -> Rep (Last' a) x Source #

to :: Rep (Last' a) x -> Last' a Source #

Semigroup (Last' a) # 
Instance details

Methods

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

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

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

Monoid (Last' a) # 
Instance details

Methods

mempty :: Last' a Source #

mappend :: Last' a -> Last' a -> Last' a Source #

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

Binary a => Binary (Last' a) # 
Instance details

Methods

put :: Last' a -> Put Source #

get :: Get (Last' a) Source #

putList :: [Last' a] -> Put Source #

type Rep (Last' a) # 
Instance details
type Rep (Last' a) = D1 (MetaData "Last'" "Distribution.Compat.Semigroup" "Cabal-2.1.0.0" True) (C1 (MetaCons "Last'" PrefixI True) (S1 (MetaSel (Just "getLast'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))

gmappend :: (Generic a, GSemigroup (Rep a)) => a -> a -> a Source #

Generically generate a Semigroup (<>) operation for any type implementing Generic. This operation will append two values by point-wise appending their component fields. It is only defined for product types.

gmappend a (gmappend b c) = gmappend (gmappend a b) c

gmempty :: (Generic a, GMonoid (Rep a)) => a Source #

Generically generate a Monoid mempty for any product-like type implementing Generic.

It is only defined for product types.

gmappend gmempty a = a = gmappend a gmempty