{-# language BangPatterns #-}
{-# language PatternSynonyms #-}
{-# language Safe #-}
{-# language ScopedTypeVariables #-}
{-# language TypeApplications #-}
{-# language ViewPatterns #-}
module Data.Group.Permutation
(
Permutation(..)
, permute
, pairwise
, (-$)
, ($-)
, embed
, retract
, pattern Permute
) where
import Data.Group
import Data.Group.Order
import qualified Data.IntSet as ISet
import Data.Function (on)
import Numeric.Natural (Natural)
infixr 0 $-, -$
data Permutation a = Permutation
{ to :: a -> a
, from :: a -> a
}
instance Semigroup (Permutation a) where
a <> b = Permutation (to a . to b) (from b . from a)
instance Monoid (Permutation a) where
mempty = Permutation id id
instance Group (Permutation a) where
invert (Permutation t f) = Permutation f t
instance (Enum a, Bounded a) => Eq (Permutation a) where
(==) = (==) `on` (functionRepr . to)
instance (Enum a, Bounded a) => Ord (Permutation a) where
compare = compare `on` (functionRepr . to)
instance (Enum a, Bounded a) => GroupOrder (Permutation a) where
order Permutation{to = f} = Finite (go 1 fullSet)
where
n = 1 + fromEnum (maxBound @a)
fullSet = ISet.fromDistinctAscList [0 .. n - 1]
f' :: Int -> Int
f' = fromEnum . f . toEnum
go :: Natural -> ISet.IntSet -> Natural
go !ord elements = case ISet.minView elements of
Nothing -> ord
Just (k, elements') ->
let (period, elements'') = takeCycle k elements'
in go (lcm period ord) elements''
takeCycle :: Int -> ISet.IntSet -> (Natural, ISet.IntSet)
takeCycle k = loop 1 (f' k)
where
loop !period j elements
| j `ISet.member` elements = loop (succ period) (f' j) (ISet.delete j elements)
| j == k = (period, elements)
| otherwise = error $ "Non-bijective: witness=toEnum " ++ show j
functionRepr :: (Enum a, Bounded a) => (a -> a) -> [Int]
functionRepr f = fromEnum . f <$> [minBound .. maxBound]
permute :: (a -> a) -> (a -> a) -> Permutation a
permute = Permutation
{-# inline permute #-}
pairwise :: Permutation a -> (a -> a, a -> a)
pairwise p = (to p, from p)
{-# inline pairwise #-}
(-$) :: Permutation a -> a -> a
(-$) = to
{-# inline (-$) #-}
($-) :: Permutation a -> a -> a
($-) = from
{-# inline ($-) #-}
embed :: (Group g) => g -> Permutation g
embed g = Permutation { to = (g <>), from = (invert g <>) }
retract :: (Group g) => Permutation g -> g
retract p = p -$ mempty
pattern Permute :: Group g => Permutation g -> g
pattern Permute p <- (embed -> p)
where Permute p = retract p