twentyseven-0.0.0: Rubik's cube solver

Safe HaskellNone
LanguageHaskell2010

Rubik.Symmetry

Description

  • Tables of symmetry classes

Synopsis

Documentation

type SymRepr a = RawCoord a Source

Smallest representative of a symmetry class. (An element of the symClasses table)

newtype SymClass symType a Source

Symmetry class. (Index of the smallest representative in the symClasses table)

Constructors

SymClass 

Instances

Eq (SymClass symType a) Source 
Ord (SymClass symType a) Source 
Show (SymClass symType a) Source 

type SymCoord sym a = (SymClass sym a, SymCode sym) Source

type SymCoord' = Int Source

An Int representing a pair (Repr, Sym).

If x = symClass * symOrder + symCode, where symClass :: SymClass is the index of the symmetry class with smallest representative r :: SymRepr (for an arbitrary order relation), symOrder is the size of the symmetry group, symCode :: Sym is the index of a symmetry s; then s^(-1) <> r <> s is the value represented by x.

newtype Action s a Source

Constructors

Action [a -> a] 

newtype SymMove s a Source

Constructors

SymMove (Vector SymCoord') 

Instances

type Symmetries sym a = MoveTag sym (Vector (RawMove a)) Source

symClasses Source

Arguments

:: RawEncodable a 
=> Action s a

Symmetry group, including the identity, - represented by its action on a

-> SymClassTable s a

Smallest representative

Compute the table of smallest representatives for all symmetry classes. The RawCoord' coordinate of that representative is a Repr. The table is sorted in increasing order.

symClasses' :: forall a s. RawEncodable a => Action s a -> [RawCoord a] Source

symReprTable Source

Arguments

:: (RawEncodable a, Foldable t) 
=> Int

Number of symmetries nSym

-> (RawCoord a -> t (RawCoord a)) 
-> SymReprTable s a 

symReprTable' Source

Arguments

:: Foldable t 
=> Int

Number of elements n

-> Int

Number of symmetries nSym

-> (Int -> t Int)

f x, symmetrical elements to x, including itself

-> Vector Int

v, where (y, i) = (v ! x) divMod nSym gives the representative y of the symmetry class of x and the index of one symmetry mapping x to y:

f x !! i == y.

symMoveTable Source

Arguments

:: RawEncodable a 
=> Action s a

Symmetry group

-> SymClassTable s a

(Sorted) table of representatives

-> (a -> a)

Endofunction to encode

-> SymMove s a 

symMoveTable' Source

Arguments

:: RawEncodable a 
=> Int

Symmetry group order

-> SymReprTable s a 
-> SymClassTable s a 
-> (a -> a) 
-> SymMove s a 

symMove' :: SymOrder' -> SymMove sym a -> (SymClass sym a, SymCode sym) -> (SymClass sym a, SymCode sym) Source

symCoord :: RawEncodable a => Action s a -> SymClassTable s a -> a -> SymCoord s a Source

Find the representative as the one corresponding to the smallest coordinate