generic-deriving-1.13: Generic programming library for generalised deriving.

Safe HaskellSafe
LanguageHaskell2010

Generics.Deriving.Semigroup

Contents

Synopsis

Generic semigroup class

class GSemigroup a where Source #

Minimal complete definition

Nothing

Methods

gsappend :: a -> a -> a infixr 6 Source #

gsappend :: (Generic a, GSemigroup' (Rep a)) => a -> a -> a infixr 6 Source #

gstimes :: Integral b => b -> a -> a Source #

gsconcat :: NonEmpty a -> a Source #

Only available with base-4.9 or later

Instances
GSemigroup Ordering Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

GSemigroup () Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: () -> () -> () Source #

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

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

GSemigroup Void Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

GSemigroup All Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

GSemigroup Any Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

GSemigroup [a] Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

GSemigroup a => GSemigroup (Maybe a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Maybe a -> Maybe a -> Maybe a Source #

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

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

Ord a => GSemigroup (Min a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Min a -> Min a -> Min a Source #

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

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

Ord a => GSemigroup (Max a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Max a -> Max a -> Max a Source #

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

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

GSemigroup (First a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: First a -> First a -> First a Source #

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

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

GSemigroup (Last a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Last a -> Last a -> Last a Source #

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

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

GMonoid m => GSemigroup (WrappedMonoid m) Source # 
Instance details

Defined in Generics.Deriving.Semigroup

GSemigroup a => GSemigroup (Option a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Option a -> Option a -> Option a Source #

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

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

GSemigroup a => GSemigroup (Identity a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

GSemigroup (First a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: First a -> First a -> First a Source #

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

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

GSemigroup (Last a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Last a -> Last a -> Last a Source #

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

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

GSemigroup a => GSemigroup (Dual a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Dual a -> Dual a -> Dual a Source #

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

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

GSemigroup (Endo a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Endo a -> Endo a -> Endo a Source #

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

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

Num a => GSemigroup (Sum a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Sum a -> Sum a -> Sum a Source #

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

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

Num a => GSemigroup (Product a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

GSemigroup a => GSemigroup (Down a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Down a -> Down a -> Down a Source #

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

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

GSemigroup (NonEmpty a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

(Generic a, GSemigroup' (Rep a)) => GSemigroup (Default a) Source #

Semigroups often have many sensible implementations of <> / gsappend, and therefore no sensible default. Indeed, there is no GSemigroup' instance for representations of sum types.

In other cases, one may wish to use the existing wrapper newtypes in base, such as the following (using First):

newtype FirstSemigroup = FirstSemigroup Bool
  deriving stock (Eq, Show)
  deriving (GSemigroup) via (First Bool)
Instance details

Defined in Generics.Deriving.Default

GSemigroup b => GSemigroup (a -> b) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

GSemigroup (Either a b) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Either a b -> Either a b -> Either a b Source #

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

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

(GSemigroup a, GSemigroup b) => GSemigroup (a, b) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

GSemigroup (Proxy s) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: Proxy s -> Proxy s -> Proxy s Source #

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

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

(GSemigroup a, GSemigroup b, GSemigroup c) => GSemigroup (a, b, c) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

GSemigroup a => GSemigroup (Const a b) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

Alternative f => GSemigroup (Alt f a) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

(GSemigroup a, GSemigroup b, GSemigroup c, GSemigroup d) => GSemigroup (a, b, c, d) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

(GSemigroup a, GSemigroup b, GSemigroup c, GSemigroup d, GSemigroup e) => GSemigroup (a, b, c, d, e) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

(GSemigroup a, GSemigroup b, GSemigroup c, GSemigroup d, GSemigroup e, GSemigroup f) => GSemigroup (a, b, c, d, e, f) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

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

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

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

(GSemigroup a, GSemigroup b, GSemigroup c, GSemigroup d, GSemigroup e, GSemigroup f, GSemigroup g) => GSemigroup (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

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

gsconcat :: NonEmpty (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

(GSemigroup a, GSemigroup b, GSemigroup c, GSemigroup d, GSemigroup e, GSemigroup f, GSemigroup g, GSemigroup h) => GSemigroup (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

gstimes :: Integral b0 => b0 -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

gsconcat :: NonEmpty (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

Default definition

gsappenddefault :: (Generic a, GSemigroup' (Rep a)) => a -> a -> a infixr 6 Source #

Internal semigroup class

class GSemigroup' f where Source #

Methods

gsappend' :: f x -> f x -> f x infixr 6 Source #

Instances
GSemigroup' (U1 :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend' :: U1 x -> U1 x -> U1 x Source #

(GSemigroup' f, GSemigroup' g) => GSemigroup' (f :*: g :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend' :: (f :*: g) x -> (f :*: g) x -> (f :*: g) x Source #

GSemigroup a => GSemigroup' (K1 i a :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend' :: K1 i a x -> K1 i a x -> K1 i a x Source #

GSemigroup' f => GSemigroup' (M1 i c f :: k -> Type) Source # 
Instance details

Defined in Generics.Deriving.Semigroup.Internal

Methods

gsappend' :: M1 i c f x -> M1 i c f x -> M1 i c f x Source #

Orphan instances