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

Safe HaskellSafe
LanguageHaskell2010

Generics.Deriving.Monoid

Contents

Synopsis

Introduction

This module provides two main features:

  1. GMonoid, a generic version of the Monoid type class, including instances of the types from Data.Monoid
  2. Default generic definitions for the Monoid methods mempty and mappend

The generic defaults only work for types without alternatives (i.e. they have only one constructor). We cannot in general know how to deal with different constructors.

GMonoid type class

class GSemigroup a => GMonoid a where Source #

Minimal complete definition

Nothing

Methods

gmempty :: a Source #

Generic mempty

gmappend :: a -> a -> a Source #

Generic mappend

gmconcat :: [a] -> a Source #

Generic mconcat

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

Generic mempty

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

Generic mappend

Instances
GMonoid Ordering Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

GMonoid () Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: () Source #

gmappend :: () -> () -> () Source #

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

GMonoid All Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

GMonoid Any Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

GMonoid [a] Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: [a] Source #

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

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

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

Defined in Generics.Deriving.Monoid

Methods

gmempty :: Maybe a Source #

gmappend :: Maybe a -> Maybe a -> Maybe a Source #

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

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

Defined in Generics.Deriving.Monoid

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

Defined in Generics.Deriving.Monoid.Internal

GMonoid (First a) Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: First a Source #

gmappend :: First a -> First a -> First a Source #

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

GMonoid (Last a) Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: Last a Source #

gmappend :: Last a -> Last a -> Last a Source #

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: Dual a Source #

gmappend :: Dual a -> Dual a -> Dual a Source #

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

GMonoid (Endo a) Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: Endo a Source #

gmappend :: Endo a -> Endo a -> Endo a Source #

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: Sum a Source #

gmappend :: Sum a -> Sum a -> Sum a Source #

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

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

Defined in Generics.Deriving.Monoid.Internal

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: Down a Source #

gmappend :: Down a -> Down a -> Down a Source #

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

(Generic a, GMonoid' (Rep a)) => GMonoid (Default a) Source # 
Instance details

Defined in Generics.Deriving.Default

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: a -> b Source #

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

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: (a, b) Source #

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

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

GMonoid (Proxy s) Source # 
Instance details

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: Proxy s Source #

gmappend :: Proxy s -> Proxy s -> Proxy s Source #

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

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

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

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: Const a b Source #

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

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: Alt f a Source #

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

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

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

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

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

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

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

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: (a, b, c, d, e, f) Source #

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

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: (a, b, c, d, e, f, g) Source #

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

gmconcat :: [(a, b, c, d, e, f, g)] -> (a, b, c, d, e, f, g) Source #

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty :: (a, b, c, d, e, f, g, h) Source #

gmappend :: (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 #

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

Default definitions

GMonoid

gmappenddefault :: (Generic a, GMonoid' (Rep a)) => a -> a -> a Source #

Internal auxiliary class for GMonoid

class GSemigroup' f => GMonoid' f where Source #

Methods

gmempty' :: f x Source #

gmappend' :: f x -> f x -> f x Source #

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty' :: U1 x Source #

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty' :: (f :*: h) x Source #

gmappend' :: (f :*: h) x -> (f :*: h) x -> (f :*: h) x Source #

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty' :: K1 i a x Source #

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

gmempty' :: M1 i c f x Source #

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

Monoid

These functions can be used in a Monoid instance. For example:

 -- LANGUAGE DeriveGeneric

 import Generics.Deriving.Base (Generic)
 import Generics.Deriving.Monoid

 data T a = C a (Maybe a) deriving Generic

 instance Monoid a => Monoid (T a) where
   mempty  = memptydefault
   mappend = mappenddefault
 

mappenddefault :: (Generic a, Monoid' (Rep a)) => a -> a -> a Source #

Internal auxiliary class for Monoid

class Monoid' f where Source #

Methods

mempty' :: f x Source #

mappend' :: f x -> f x -> f x Source #

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

Defined in Generics.Deriving.Monoid.Internal

Methods

mempty' :: U1 x Source #

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

mempty' :: (f :*: h) x Source #

mappend' :: (f :*: h) x -> (f :*: h) x -> (f :*: h) x Source #

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

Defined in Generics.Deriving.Monoid.Internal

Methods

mempty' :: K1 i a x Source #

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

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

Defined in Generics.Deriving.Monoid.Internal

Methods

mempty' :: M1 i c f x Source #

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

The Monoid module

This is exported for convenient access to the various wrapper types.

Orphan instances