Cabal-1.24.2.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell98

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).

Since: 4.9.0.0

Methods

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

An associative operation.

(a <> b) <> c = a <> (b <> c)

If a is also a Monoid we further require

(<>) = mappend

Instances

Semigroup Ordering 
Semigroup () 

Methods

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

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

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

Semigroup Void 
Semigroup All 

Methods

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

sconcat :: NonEmpty All -> All Source #

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

Semigroup Any 

Methods

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

sconcat :: NonEmpty Any -> Any Source #

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

Semigroup ShortByteString 
Semigroup ByteString 
Semigroup ByteString 
Semigroup Builder 
Semigroup IntSet 
Semigroup Doc 

Methods

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

sconcat :: NonEmpty Doc -> Doc Source #

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

Semigroup CDialect # 
Semigroup BuildInfo # 
Semigroup BenchmarkInterface # 
Semigroup Benchmark # 
Semigroup TestSuiteInterface # 
Semigroup TestSuite # 
Semigroup Executable # 
Semigroup Library # 
Semigroup ModuleRenaming # 
Semigroup SetupBuildInfo # 
Semigroup BenchmarkFlags # 
Semigroup TestFlags # 
Semigroup TestShowDetails # 
Semigroup ReplFlags # 
Semigroup BuildFlags # 
Semigroup CleanFlags # 
Semigroup HaddockFlags # 
Semigroup HscolourFlags # 
Semigroup RegisterFlags # 
Semigroup SDistFlags # 
Semigroup InstallFlags # 
Semigroup CopyFlags # 
Semigroup ConfigFlags # 
Semigroup AllowNewer # 
Semigroup GlobalFlags # 
Semigroup GhcOptions # 
Semigroup [a] 

Methods

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

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

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

Semigroup a => Semigroup (Maybe a) 

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 (Identity a) 
Ord a => Semigroup (Min a) 

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) 

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) 

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) 

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) 
Semigroup a => Semigroup (Option a) 

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 (NonEmpty a) 
Semigroup a => Semigroup (Dual a) 

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) 

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) 

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) 

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 (First a) 

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) 

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 (PutM ()) 

Methods

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

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

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

Semigroup (IntMap a) 

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) 

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) 

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) 

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 (Last' a) # 

Methods

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

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

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

Ord a => Semigroup (NubListR a) # 
Ord a => Semigroup (NubList a) # 

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 dir => Semigroup (InstallDirs dir) # 
Semigroup (Condition a) # 
HasUnitId a => Semigroup (PackageIndex a) # 
Semigroup (Flag a) # 

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) 

Methods

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

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

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

Semigroup (Either a b) 

Methods

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

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

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

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

Methods

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

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

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

Semigroup (Proxy k s) 

Methods

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

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

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

Ord k => Semigroup (Map k v) 

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) 

Methods

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

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

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

Semigroup a => Semigroup (Const k a b) 

Methods

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

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

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

Alternative f => Semigroup (Alt * f a) 

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) 

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 b => b -> (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) 

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

class Monoid a where Source #

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

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

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.

Minimal complete definition

mempty, mappend

Methods

mempty :: a Source #

Identity of mappend

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

An associative operation

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 
Monoid () 

Methods

mempty :: () Source #

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

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

Monoid All 
Monoid Any 
Monoid ShortByteString 
Monoid ByteString 
Monoid ByteString 
Monoid Builder 
Monoid IntSet 
Monoid Doc 
Monoid CDialect # 
Monoid BuildInfo # 
Monoid BenchmarkInterface # 
Monoid Benchmark # 
Monoid TestSuiteInterface # 
Monoid TestSuite # 
Monoid Executable # 
Monoid Library # 
Monoid ModuleRenaming # 
Monoid SetupBuildInfo # 
Monoid BenchmarkFlags # 
Monoid TestFlags # 
Monoid TestShowDetails # 
Monoid ReplFlags # 
Monoid BuildFlags # 
Monoid CleanFlags # 
Monoid HaddockFlags # 
Monoid HscolourFlags # 
Monoid RegisterFlags # 
Monoid SDistFlags # 
Monoid InstallFlags # 
Monoid CopyFlags # 
Monoid ConfigFlags # 
Monoid AllowNewer # 
Monoid GlobalFlags # 
Monoid GhcOptions # 
Monoid [a] 

Methods

mempty :: [a] Source #

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

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

Monoid 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 there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a Source #

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

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

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a Source #

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

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

Ord a => Monoid (Max a) 

Methods

mempty :: Max a Source #

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

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

Ord a => Monoid (Min a) 

Methods

mempty :: Min a Source #

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

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

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

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) 

Methods

mempty :: Max a Source #

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

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

Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 
Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a Source #

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

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

Monoid (Endo a) 

Methods

mempty :: Endo a Source #

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

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

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a Source #

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

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

Num a => Monoid (Product a) 
Monoid (First a) 

Methods

mempty :: First a Source #

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

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

Monoid (Last a) 

Methods

mempty :: Last a Source #

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

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

Monoid (PutM ()) 

Methods

mempty :: PutM () Source #

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

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

Monoid (IntMap a) 
Monoid (Seq a) 

Methods

mempty :: Seq a Source #

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

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

Ord a => Monoid (Set a) 

Methods

mempty :: Set a Source #

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

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

Monoid (Doc a) 

Methods

mempty :: Doc a Source #

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

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

Monoid (Last' a) # 

Methods

mempty :: Last' a Source #

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

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

Ord a => Monoid (NubListR a) # 
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.

(Semigroup dir, Monoid dir) => Monoid (InstallDirs dir) # 
Monoid (Condition a) # 
HasUnitId a => Monoid (PackageIndex a) # 
Monoid (Flag a) # 

Methods

mempty :: Flag a Source #

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

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

Monoid b => Monoid (a -> b) 

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) 

Methods

mempty :: (a, b) Source #

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

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

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s Source #

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

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

Ord k => Monoid (Map k v) 

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) 

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 k a b) 

Methods

mempty :: Const k a b Source #

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

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

Alternative f => Monoid (Alt * f a) 

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) 

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) 

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 (&&).

Constructors

All 

Fields

Instances

Bounded All 
Eq All 

Methods

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

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

Data All 

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 

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 
Show All 
Generic All 

Associated Types

type Rep All :: * -> * Source #

Methods

from :: All -> Rep All x Source #

to :: Rep All x -> All Source #

Semigroup All 

Methods

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

sconcat :: NonEmpty All -> All Source #

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

Monoid All 
NFData All

Since: 1.4.0.0

Methods

rnf :: All -> () Source #

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

newtype Any :: * Source #

Boolean monoid under disjunction (||).

Constructors

Any 

Fields

Instances

Bounded Any 
Eq Any 

Methods

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

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

Data Any 

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 

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 
Show Any 
Generic Any 

Associated Types

type Rep Any :: * -> * Source #

Methods

from :: Any -> Rep Any x Source #

to :: Rep Any x -> Any Source #

Semigroup Any 

Methods

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

sconcat :: NonEmpty Any -> Any Source #

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

Monoid Any 
NFData Any

Since: 1.4.0.0

Methods

rnf :: Any -> () Source #

type Rep Any 
type Rep Any = D1 (MetaData "Any" "Data.Monoid" "base" True) (C1 (MetaCons "Any" PrefixI True) (S1 (MetaSel (Just Symbol "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' # 

Methods

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

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

Applicative Last' # 

Methods

pure :: a -> Last' a Source #

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

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

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

Eq a => Eq (Last' a) # 

Methods

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

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

Ord a => Ord (Last' a) # 

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

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) # 

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) # 

Methods

mempty :: Last' a Source #

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

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

Binary a => Binary (Last' a) # 

Methods

put :: Last' a -> Put Source #

get :: Get (Last' a) Source #

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

type Rep (Last' a) # 
type Rep (Last' a) = D1 (MetaData "Last'" "Distribution.Compat.Semigroup" "Cabal-1.24.2.0" True) (C1 (MetaCons "Last'" PrefixI True) (S1 (MetaSel (Just Symbol "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