free-algebras-0.0.6.0: Free algebras in Haskell.

Safe HaskellNone
LanguageHaskell2010

Data.Semigroup.SSet

Description

Actions of semigroup (SSet).

Synopsis

Documentation

class Semigroup s => SSet s a where Source #

A lawful instance should satisfy:

g `act` h `act` a = g <> h `act` a

This is the same as to say that act is a semigroup homomorphism from s to the monoid of endomorphisms of a (i.e. maps from a to a).

Note that if g is a Group then MAct g is simply a GSet, this is because monoids and groups share the same morphisms (a monoid homomorphis between groups necessarily preserves inverses).

Methods

act :: s -> a -> a Source #

Instances
Semigroup s => SSet s s Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> s -> s Source #

SSet s a => SSet s (IO a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> IO a -> IO a Source #

SSet s a => SSet s (Down a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> Down a -> Down a Source #

SSet s a => SSet s (Maybe a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> Maybe a -> Maybe a Source #

SSet s a => SSet s (Identity a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> Identity a -> Identity a Source #

(SSet s a, Ord a) => SSet s (Set a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> Set a -> Set a Source #

SSet s a => SSet s (NonEmpty a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> NonEmpty a -> NonEmpty a Source #

SSet s a => SSet s [a] Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> [a] -> [a] Source #

SSet s b => SSet s (a -> b) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> (a -> b) -> a -> b Source #

SSet s b => SSet s (Either a b) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> Either a b -> Either a b Source #

(SSet s a, SSet s b) => SSet s (a, b) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> (a, b) -> (a, b) Source #

Semigroup m => SSet m (FreeMSet m a) Source # 
Instance details

Defined in Data.Monoid.MSet

Methods

act :: m -> FreeMSet m a -> FreeMSet m a Source #

SSet s a => SSet s (Const a b) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> Const a b -> Const a b Source #

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

Defined in Data.Semigroup.SSet

Methods

act :: s -> (a, b, c) -> (a, b, c) Source #

(Functor f, Functor h, SSet s a) => SSet s (Sum f h a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> Sum f h a -> Sum f h a Source #

(Functor f, Functor h, SSet s a) => SSet s (Product f h a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> Product f h a -> Product f h a Source #

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

Defined in Data.Semigroup.SSet

Methods

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

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

Defined in Data.Semigroup.SSet

Methods

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

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

Defined in Data.Semigroup.SSet

Methods

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

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

Defined in Data.Semigroup.SSet

Methods

act :: s -> (a, b, c, d, e, f, h) -> (a, b, c, d, e, f, h) Source #

(SSet s a, SSet s b, SSet s c, SSet s d, SSet s e, SSet s f, SSet s h, SSet s i) => SSet s (a, b, c, d, e, f, h, i) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: s -> (a, b, c, d, e, f, h, i) -> (a, b, c, d, e, f, h, i) Source #

SSet s a => SSet (Identity s) a Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: Identity s -> a -> a Source #

SSet (Endo a) a Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: Endo a -> a -> a Source #

Group g => SSet (Sum Integer) g Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: Sum Integer -> g -> g Source #

Num s => SSet (Sum s) s Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: Sum s -> s -> s Source #

Monoid s => SSet (Sum Natural) s Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: Sum Natural -> s -> s Source #

Num s => SSet (Product s) s Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: Product s -> s -> s Source #

SSet s a => SSet (S s) (Endo a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: S s -> Endo a -> Endo a Source #

rep :: SSet s a => s -> Endo a Source #

fact :: (Functor f, SSet s a) => s -> f a -> f a Source #

Any SSet wrapped in a functor is a valid SSet.

newtype S s Source #

A newtype wrapper to avoid overlapping instances.

Constructors

S 

Fields

Instances
Eq s => Eq (S s) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

(==) :: S s -> S s -> Bool #

(/=) :: S s -> S s -> Bool #

Ord s => Ord (S s) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

compare :: S s -> S s -> Ordering #

(<) :: S s -> S s -> Bool #

(<=) :: S s -> S s -> Bool #

(>) :: S s -> S s -> Bool #

(>=) :: S s -> S s -> Bool #

max :: S s -> S s -> S s #

min :: S s -> S s -> S s #

Show s => Show (S s) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

showsPrec :: Int -> S s -> ShowS #

show :: S s -> String #

showList :: [S s] -> ShowS #

Semigroup m => Semigroup (S m) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

(<>) :: S m -> S m -> S m #

sconcat :: NonEmpty (S m) -> S m #

stimes :: Integral b => b -> S m -> S m #

Monoid m => Monoid (S m) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

mempty :: S m #

mappend :: S m -> S m -> S m #

mconcat :: [S m] -> S m #

SSet s a => SSet (S s) (Endo a) Source # 
Instance details

Defined in Data.Semigroup.SSet

Methods

act :: S s -> Endo a -> Endo a Source #

MSet m b => MSet (S m) (Endo b) Source # 
Instance details

Defined in Data.Monoid.MSet

Methods

mact :: S m -> Endo b -> Endo b Source #