acts-0.1.0.0: Semigroup actions, groups, and torsors.
Safe HaskellNone
LanguageHaskell2010

Data.Group

Description

A Group is a Monoid for which the monoid operation can be undone.

That is, \( G \) is a group if each \( g \in G \) has an inverse element \( g^{ -1 } \) such that

\[ g^{ -1 } < \! > g = \text{mempty} = g < \! > g^{ -1 } \]

Such inverses are necessarily unique.

In Haskell, groups are mostly useful to describe objects possessing certain symmetries (such as translation or rotation).

To automatically derive Group instances, you can:

  • Use DerivingVia to coerce an existing instance:
> newtype Seconds   = Seconds { getSeconds :: Double }
> newtype TimeDelta = TimeDelta { timeDeltaInSeconds :: Seconds }
>   deriving ( Semigroup, Monoid, Group )
>     via Sum Double
> data MyRecord
>   = MyRecord
>   { field1 :: Sum Double
>   , field2 :: Product Double
>   , field3 :: Ap [] ( Sum Int, Sum Int )
>   }
>   deriving Generic
>   deriving ( Semigroup, Monoid, Group )
>     via Generically MyRecord
Synopsis

Documentation

class Monoid g => Group g where Source #

A Group is a Monoid with inverses:

  •  inverse g <> g = g <> inverse g = mempty
  •  inverse (g <> h) = inverse h <> inverse g

Minimal complete definition

inverse | gtimes

Methods

inverse :: g -> g Source #

Group inversion anti-homomorphism.

gtimes :: Integral n => n -> g -> g Source #

Take the n-th power of an element.

Instances

Instances details
Group () Source #

Trivial group.

Instance details

Defined in Data.Group

Methods

inverse :: () -> () Source #

gtimes :: Integral n => n -> () -> () Source #

Group a => Group (IO a) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: IO a -> IO a Source #

gtimes :: Integral n => n -> IO a -> IO a Source #

Group g => Group (Par1 g) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: Par1 g -> Par1 g Source #

gtimes :: Integral n => n -> Par1 g -> Par1 g Source #

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

Defined in Data.Group

Methods

inverse :: Identity a -> Identity a Source #

gtimes :: Integral n => n -> Identity a -> Identity a Source #

Group a => Group (Dual a) Source #

Opposite group.

Instance details

Defined in Data.Group

Methods

inverse :: Dual a -> Dual a Source #

gtimes :: Integral n => n -> Dual a -> Dual a Source #

Num a => Group (Sum a) Source #

Additive groups (via Num).

Instance details

Defined in Data.Group

Methods

inverse :: Sum a -> Sum a Source #

gtimes :: Integral n => n -> Sum a -> Sum a Source #

Fractional a => Group (Product a) Source #

Multiplicative group (via Num).

Instance details

Defined in Data.Group

Methods

inverse :: Product a -> Product a Source #

gtimes :: Integral n => n -> Product a -> Product a Source #

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

Defined in Data.Group

Methods

inverse :: Down a -> Down a Source #

gtimes :: Integral n => n -> Down a -> Down a Source #

(Generic g, Monoid (Rep g ()), GGroup (Rep g)) => Group (Generically g) Source # 
Instance details

Defined in Data.Group

Monoid a => Group (Isom a) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: Isom a -> Isom a Source #

gtimes :: Integral n => n -> Isom a -> Isom a Source #

(KnownNat n, 1 <= n) => Group (Cyclic n) Source # 
Instance details

Defined in Data.Group.Cyclic

Methods

inverse :: Cyclic n -> Cyclic n Source #

gtimes :: Integral n0 => n0 -> Cyclic n -> Cyclic n Source #

Group a => Group (r -> a) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: (r -> a) -> r -> a Source #

gtimes :: Integral n => n -> (r -> a) -> r -> a Source #

Group (U1 p) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: U1 p -> U1 p Source #

gtimes :: Integral n => n -> U1 p -> U1 p Source #

(Group g1, Group g2) => Group (g1, g2) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: (g1, g2) -> (g1, g2) Source #

gtimes :: Integral n => n -> (g1, g2) -> (g1, g2) Source #

Group a => Group (ST s a) Source # 
Instance details

Defined in Data.Group

Methods

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

gtimes :: Integral n => n -> ST s a -> ST s a Source #

Group a => Group (Op a b) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: Op a b -> Op a b Source #

gtimes :: Integral n => n -> Op a b -> Op a b Source #

Group (Proxy p) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: Proxy p -> Proxy p Source #

gtimes :: Integral n => n -> Proxy p -> Proxy p Source #

Group (f p) => Group (Rec1 f p) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: Rec1 f p -> Rec1 f p Source #

gtimes :: Integral n => n -> Rec1 f p -> Rec1 f p Source #

(Group g1, Group g2, Group g3) => Group (g1, g2, g3) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: (g1, g2, g3) -> (g1, g2, g3) Source #

gtimes :: Integral n => n -> (g1, g2, g3) -> (g1, g2, g3) Source #

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

Defined in Data.Group

Methods

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

gtimes :: Integral n => n -> Const a b -> Const a b Source #

(Group a, Applicative f) => Group (Ap f a) Source #

Lifting group operations through an applicative functor.

Instance details

Defined in Data.Group

Methods

inverse :: Ap f a -> Ap f a Source #

gtimes :: Integral n => n -> Ap f a -> Ap f a Source #

Group g => Group (K1 i g p) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: K1 i g p -> K1 i g p Source #

gtimes :: Integral n => n -> K1 i g p -> K1 i g p Source #

(Group (f1 p), Group (f2 p)) => Group ((f1 :*: f2) p) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: (f1 :*: f2) p -> (f1 :*: f2) p Source #

gtimes :: Integral n => n -> (f1 :*: f2) p -> (f1 :*: f2) p Source #

(Group g1, Group g2, Group g3, Group g4) => Group (g1, g2, g3, g4) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: (g1, g2, g3, g4) -> (g1, g2, g3, g4) Source #

gtimes :: Integral n => n -> (g1, g2, g3, g4) -> (g1, g2, g3, g4) Source #

Group (f p) => Group (M1 i c f p) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: M1 i c f p -> M1 i c f p Source #

gtimes :: Integral n => n -> M1 i c f p -> M1 i c f p Source #

(Group g1, Group g2, Group g3, Group g4, Group g5) => Group (g1, g2, g3, g4, g5) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: (g1, g2, g3, g4, g5) -> (g1, g2, g3, g4, g5) Source #

gtimes :: Integral n => n -> (g1, g2, g3, g4, g5) -> (g1, g2, g3, g4, g5) Source #

data Isom a Source #

Data type to keep track of a pair of inverse elements.

Constructors

(:|:) infix 7 

Fields

Instances

Instances details
Data a => Data (Isom a) Source # 
Instance details

Defined in Data.Group

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Isom a -> c (Isom a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Isom a) #

toConstr :: Isom a -> Constr #

dataTypeOf :: Isom a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Isom a -> Isom a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Isom a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Isom a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Isom a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Isom a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Isom a -> m (Isom a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Isom a -> m (Isom a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Isom a -> m (Isom a) #

Read a => Read (Isom a) Source # 
Instance details

Defined in Data.Group

Show a => Show (Isom a) Source # 
Instance details

Defined in Data.Group

Methods

showsPrec :: Int -> Isom a -> ShowS #

show :: Isom a -> String #

showList :: [Isom a] -> ShowS #

Generic (Isom a) Source # 
Instance details

Defined in Data.Group

Associated Types

type Rep (Isom a) :: Type -> Type #

Methods

from :: Isom a -> Rep (Isom a) x #

to :: Rep (Isom a) x -> Isom a #

Semigroup a => Semigroup (Isom a) Source # 
Instance details

Defined in Data.Group

Methods

(<>) :: Isom a -> Isom a -> Isom a #

sconcat :: NonEmpty (Isom a) -> Isom a #

stimes :: Integral b => b -> Isom a -> Isom a #

Monoid a => Monoid (Isom a) Source # 
Instance details

Defined in Data.Group

Methods

mempty :: Isom a #

mappend :: Isom a -> Isom a -> Isom a #

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

NFData a => NFData (Isom a) Source # 
Instance details

Defined in Data.Group

Methods

rnf :: Isom a -> () #

Monoid a => Group (Isom a) Source # 
Instance details

Defined in Data.Group

Methods

inverse :: Isom a -> Isom a Source #

gtimes :: Integral n => n -> Isom a -> Isom a Source #

Generic1 Isom Source # 
Instance details

Defined in Data.Group

Associated Types

type Rep1 Isom :: k -> Type #

Methods

from1 :: forall (a :: k). Isom a -> Rep1 Isom a #

to1 :: forall (a :: k). Rep1 Isom a -> Isom a #

type Rep (Isom a) Source # 
Instance details

Defined in Data.Group

type Rep (Isom a) = D1 ('MetaData "Isom" "Data.Group" "acts-0.1.0.0-inplace" 'False) (C1 ('MetaCons ":|:" 'PrefixI 'True) (S1 ('MetaSel ('Just "to") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "from") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Dual a))))
type Rep1 Isom Source # 
Instance details

Defined in Data.Group

type Rep1 Isom = D1 ('MetaData "Isom" "Data.Group" "acts-0.1.0.0-inplace" 'False) (C1 ('MetaCons ":|:" 'PrefixI 'True) (S1 ('MetaSel ('Just "to") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "from") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Dual)))