group-theory-0.2.2: The theory of groups
Copyright(c) 2020-2021 Emily Pillmore
LicenseBSD-style
MaintainerReed Mullanix <reedmullanix@gmail.com>, Emily Pillmore <emilypi@cohomolo.gy>
Stabilitystable
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Data.Group.Permutation

Description

This module provides definitions for Permutations along with useful combinators.

Synopsis

Permutation groups

data Permutation a Source #

Isomorphism of a type onto itself. Each entry consists of one half of the isomorphism.

Note: It is the responsibility of the user to provide inverse proofs for to and from. Be responsible!

Examples:

Expand
>>> p1 = permute succ pred :: Permutation Integer
>>> p2 = permute negate negate :: Permutation Integer
>>> to (p1 <> p2) 2
-1
>>> from (p1 <> p2) (-1)
2
>>> to (p2 <> p1) 2
-3

Permutations on a finite set a (, indicated by satisfying (Bounded a, Enum a) constraint,) can be tested their equality and computed their orders.

>>> c1 = permute not not :: Permutation Bool
>>> equalPermutation (c1 <> c1) mempty
True
>>> orderOfPermutation c1
2

Constructors

Permutation 

Fields

  • to :: a -> a

    The forward half of the bijection

  • from :: a -> a

    The inverse half of the bijection

Instances

Instances details
Semigroup (Permutation a) Source # 
Instance details

Defined in Data.Group.Permutation

Monoid (Permutation a) Source # 
Instance details

Defined in Data.Group.Permutation

Group (Permutation a) Source # 
Instance details

Defined in Data.Group.Permutation

Permutation group combinators

equalPermutation :: (Enum a, Bounded a) => Permutation a -> Permutation a -> Bool Source #

Equality test for permutations on a finite type a

This module intentionally omits the following instance, albeit equalPermutation is suitable implementation of (==) operator for many types.

instance (Enum a, Bounded a) => Eq (Permutation a) where
  (==) = equalPermutation

This is because some type satisfying (Enum a, Bounded a) are actually finite but too large to use equalPermutation on. For example, you can call equalPermutation on Permutation Int, but it takes too much computation to be considered usable.

comparePermutation :: (Enum a, Bounded a) => Permutation a -> Permutation a -> Ordering Source #

Comparison for permutations on a finite type a

This module intentionally omits the following instance, albeit comparePermutation is suitable implementation of compare method for many types.

instance (Enum a, Bounded a) => Eq (Permutation a) where
  compare = comparePermutation

This is because some type satisfying (Enum a, Bounded a) are actually finite but too large to use comparePermutation on. For example, you can call comparePermutation on Permutation Int, but it takes too much computation to be considered usable.

orderOfPermutation :: forall a. (Enum a, Bounded a) => Permutation a -> Natural Source #

Order counting for a permutation on a finite type a

This module intentionally omits the following instance, albeit orderOfPermutation is suitable implementation of order method for many types.

instance (Enum a, Bounded a) => GroupOrder (Permutation a) where
  order a = Finite (orderOfPermutation a)

This is because some type satisfying (Enum a, Bounded a) are actually finite but too large to use orderOfPermutation on. For example, you can call orderOfPermutation on Permutation Int, but it takes too much computation to be considered usable.

permute :: (a -> a) -> (a -> a) -> Permutation a Source #

Build a Permutation from a bijective pair.

pairwise :: Permutation a -> (a -> a, a -> a) Source #

Destroy a Permutation, producing the underlying pair of bijections.

(-$) :: Permutation a -> a -> a infixr 0 Source #

Infix alias for the to half of Permutation bijection

($-) :: Permutation a -> a -> a infixr 0 Source #

Infix alias for the from half of Permutation bijection

embed :: Group g => g -> Permutation g Source #

Embed a Group into the Permutation group on it's underlying set.

retract :: Group g => Permutation g -> g Source #

Get a group element out of the permutation group. This is a left inverse to embed, i.e.

   retract . embed = id

Permutation patterns

pattern Permute :: Group g => Permutation g -> g Source #

Bidirectional pattern synonym for embedding/retraction of groups into their permutation groups.