module Rubik.Symmetry where
import Rubik.Cube
import Rubik.Misc
import Control.DeepSeq
import Control.Monad
import Data.Binary.Storable
import Data.Foldable
import Data.List
import Data.Maybe
import Data.Ord
import qualified Data.Heap as H
import qualified Data.Vector as V
import qualified Data.Vector.Storable.Allocated as S
type SymRepr a = RawCoord a
type SymClass' = Int
newtype SymClass symType a = SymClass { unSymClass :: SymClass' }
deriving (Eq, Ord, Show)
type SymCoord sym a = (SymClass sym a, SymCode sym)
type SymCoord' = Int
type SymOrder' = Int
newtype Action s a = Action [a -> a]
newtype SymClassTable s a = SymClassTable { unSymClassTable :: S.Vector RawCoord' }
deriving (Eq, Ord, Show, Binary, NFData)
newtype SymReprTable s a = SymReprTable { unSymReprTable :: S.Vector Int }
deriving (Eq, Ord, Show, Binary, NFData)
newtype SymMove s a = SymMove (S.Vector SymCoord')
deriving (Eq, Ord, Show, Binary, NFData)
type Symmetries sym a = MoveTag sym (V.Vector (RawMove a))
symClasses
:: RawEncodable a
=> Action s a
-> SymClassTable s a
symClasses = SymClassTable . S.fromList . fmap unRawCoord . symClasses'
symClasses' :: forall a s. RawEncodable a => Action s a -> [RawCoord a]
symClasses' action@(Action sym)
= foldFilter (H.empty :: H.MinHeap (RawCoord a))
(fmap RawCoord [0 .. range action 1])
where
foldFilter _ [] = []
foldFilter (H.view -> Nothing) (x : xs) = x : foldFilter (heapOf x) xs
foldFilter (h@(H.view -> Just (y, ys))) (x : xs)
| x < y = x : foldFilter (H.union h (heapOf x)) xs
| otherwise = foldFilter ys xs
heapOf :: RawCoord a -> H.MinHeap (RawCoord a)
heapOf x
= let dx = decode x
nub' = map head . group . sort
in H.fromAscList . tail . nub' $ map (\z -> (encode . z) dx) sym
symClassTable
:: Int
-> SymReprTable s a
-> SymClassTable s a
symClassTable nSym (SymReprTable s)
= SymClassTable . S.ifilter (==) $ S.map (`div` nSym) s
symReprTable
:: forall a s t. (RawEncodable a, Foldable t)
=> Int
-> (RawCoord a -> t (RawCoord a))
-> SymReprTable s a
symReprTable nSym f
= SymReprTable (symReprTable' (range ([] :: [a])) nSym f')
where
f' = fmap unRawCoord . toList . f . RawCoord
symReprTable'
:: Foldable t
=> Int
-> Int
-> (Int -> t Int)
-> S.Vector Int
symReprTable' n nSym f
= S.create $ do
v <- S.replicate n (1)
forM_ [0 .. n1] $ \x -> do
let ys = f x
y <- S.read v x
when (y == 1) .
forM_ ((zip [0 ..] . toList . f) x) $ \(i, x') ->
S.write v x' (flatIndex nSym x i)
return v
symMoveTable
:: RawEncodable a
=> Action s a
-> SymClassTable s a
-> (a -> a)
-> SymMove s a
symMoveTable action@(Action syms) classes f
= SymMove (S.map move (unSymClassTable classes))
where
n = length syms
move = flat . symCoord action classes . f . decode . RawCoord
flat (SymClass c, SymCode s) = flatIndex n c s
symMoveTable'
:: RawEncodable a
=> Int
-> SymReprTable s a
-> SymClassTable s a
-> (a -> a)
-> SymMove s a
symMoveTable' nSym reps classes f
= SymMove (S.map move (unSymClassTable classes))
where
move = flat . symCoord' nSym reps classes . encode . f . decode . RawCoord
flat (SymClass c, SymCode s) = flatIndex nSym c s
symMove :: SymOrder' -> SymMove s a -> SymClass s a -> SymCoord s a
symMove n (SymMove v) (SymClass x) = (SymClass y, SymCode i)
where (y, i) = (v S.! x) `divMod` n
symMove' n v (x, j) = (y, i `composeSym` j)
where (y, i) = symMove n v x
reprToClass :: SymClassTable s a -> RawCoord a -> SymClass s a
reprToClass (SymClassTable cls) = SymClass . fromJust . flip iFind cls . unRawCoord
symCoord :: RawEncodable a => Action s a -> SymClassTable s a
-> a -> SymCoord s a
symCoord (Action syms) classes x
= (reprToClass classes r, SymCode s)
where
xSym = [ encode (s x) | s <- syms ]
(r, s) = minimumBy (comparing fst) (zip xSym [0 ..])
symCoord' :: Int -> SymReprTable s a -> SymClassTable s a -> RawCoord a -> SymCoord s a
symCoord' nSym (SymReprTable reps) (SymClassTable classes) (RawCoord x)
= (SymClass r, SymCode i)
where
(y, i) = (reps S.! x) `divMod` nSym
r = fromJust $ iFind r classes
symToRaw
:: SymClassTable s a -> (RawCoord a -> SymCode s -> RawCoord a)
-> SymCoord s a -> RawCoord a
symToRaw (SymClassTable classes) sym (SymClass c, i)
= sym (RawCoord (classes S.! c)) i
sym :: Symmetries s a -> RawCoord a -> SymCode s -> RawCoord a
sym (MoveTag syms) r (SymCode i) = syms V.! i !$ r