Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- Use
Generic
andGenerically
:
> data MyRecord > = MyRecord > { field1 :: Sum Double > , field2 :: Product Double > , field3 :: Ap [] ( Sum Int, Sum Int ) > } > deriving Generic > deriving ( Semigroup, Monoid, Group ) > via Generically MyRecord
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
Group inversion anti-homomorphism.
gtimes :: Integral n => n -> g -> g Source #
Take the n
-th power of an element.
Instances
Group () Source # | Trivial group. |
Group a => Group (IO a) Source # | |
Group g => Group (Par1 g) Source # | |
Group a => Group (Identity a) Source # | |
Group a => Group (Dual a) Source # | Opposite group. |
Num a => Group (Sum a) Source # | Additive groups (via |
Fractional a => Group (Product a) Source # | Multiplicative group (via |
Group a => Group (Down a) Source # | |
(Generic g, Monoid (Rep g ()), GGroup (Rep g)) => Group (Generically g) Source # | |
Defined in Data.Group inverse :: Generically g -> Generically g Source # gtimes :: Integral n => n -> Generically g -> Generically g Source # | |
Monoid a => Group (Isom a) Source # | |
Group a => Group (r -> a) Source # | |
Group (U1 p) Source # | |
(Group g1, Group g2) => Group (g1, g2) Source # | |
Group a => Group (Op a b) Source # | |
Group a => Group (ST s a) Source # | |
Group (Proxy p) Source # | |
Group (f p) => Group (Rec1 f p) Source # | |
(Group g1, Group g2, Group g3) => Group (g1, g2, g3) Source # | |
Group a => Group (Const a b) Source # | |
(Group a, Applicative f) => Group (Ap f a) Source # | Lifting group operations through an applicative functor. |
Group g => Group (K1 i g p) Source # | |
(Group (f1 p), Group (f2 p)) => Group ((f1 :*: f2) p) Source # | |
(Group g1, Group g2, Group g3, Group g4) => Group (g1, g2, g3, g4) Source # | |
Group (f p) => Group (M1 i c f p) Source # | |
(Group g1, Group g2, Group g3, Group g4, Group g5) => Group (g1, g2, g3, g4, g5) Source # | |
anti :: Group g => g -> Dual g Source #
The inverse anti-automorphism of a group lifts to a isomorphism with the opposite group.
reflexive :: Dual (Dual a) -> a Source #
Reflexive property Dual
(should be included in base, maybe under another name).
Data type to keep track of a pair of inverse elements.
Instances
Data a => Data (Isom a) Source # | |
Defined in Data.Group 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 :: (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 # | |
Show a => Show (Isom a) Source # | |
Generic (Isom a) Source # | |
Semigroup a => Semigroup (Isom a) Source # | |
Monoid a => Monoid (Isom a) Source # | |
NFData a => NFData (Isom a) Source # | |
Defined in Data.Group | |
Monoid a => Group (Isom a) Source # | |
Generic1 Isom Source # | |
type Rep (Isom a) Source # | |
Defined in Data.Group type Rep (Isom a) = D1 (MetaData "Isom" "Data.Group" "acts-0.2.0.0-IZeK4JTej10COOINsXz0BM" 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 # | |
Defined in Data.Group type Rep1 Isom = D1 (MetaData "Isom" "Data.Group" "acts-0.2.0.0-IZeK4JTej10COOINsXz0BM" False) (C1 (MetaCons ":|:" PrefixI True) (S1 (MetaSel (Just "to") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "from") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Dual))) |