twentyseven-0.0.0: Rubik's cube solver

Safe HaskellNone
LanguageHaskell2010

Rubik.Cube.Coord

Contents

Description

Encoding cube projections as Int coordinates.

Explicit dictionary passing style: using a class would require explicit type annotations anyway.

Synopsis

Raw coordinates

newtype RawCoord a Source

Encoding to an efficient datatype for which it is possible to build tables instead of computing functions.

Constructors

RawCoord 

newtype RawVector a b Source

Constructors

RawVector 

Fields

unRawVector :: Vector b
 

(!.) :: Unbox b => RawVector a b -> RawCoord a -> b Source

Dictionaries

class RawEncodable a where Source

Encoding dictionary.

Probably synonymous with instances for both (Enum a, Bounded a).

inRange (range d) $ encode x
encode . decode == id
decode . encode == id

A special constructor for dictionaries of product types is particularly useful to create tables of functions if their actions on every projection are independent.

Methods

range :: proxy a -> Int Source

Number of elements that can be converted. Their values are to lie in [0 .. range c - 1].

encode :: a -> RawCoord a Source

decode :: RawCoord a -> a Source

Instances

RawEncodable UDEdgePermu2 Source
8! = 40320
RawEncodable UDSlicePermu2 Source
4! = 24
RawEncodable UDSlice Source
12C4 = 495
RawEncodable UDSlicePermu Source

12! / 8! = 11880

RawEncodable EdgeOrien Source
2^11 = 2048
RawEncodable EdgePermu Source
12! = 479001600

A bit too much to hold in memory.

Holds just right in a Haskell Int (maxInt >= 2^29 - 1).

RawEncodable CornerOrien Source
3^7 = 2187
RawEncodable CornerPermu Source

The number of elements of every set is given.

8! = 40320
(RawEncodable a, RawEncodable b) => RawEncodable (a, b) Source 

Instances

Table building

type Endo a = a -> a Source

Endofunctions

endoVector :: RawEncodable a => Endo a -> RawMove a Source

Lift an endofunction to its coordinate representation, the dictionary provides a RawCoord encoding.

That is, we construct a vector v such that, basically,

decode (v ! encode x) == f x

So function application becomes simply vector indexing.

cubeActionToEndo :: CubeAction a => Cube -> Endo a Source

The cubeAction method is partially applied to a Cube and turned into an Endo function.

The 'CA a' type argument controls the refinement of the endofunction.

symToEndo :: (Cube -> a -> a) -> Cube -> Endo a Source

symTable :: RawEncodable a => (Cube -> a -> a) -> Cube -> RawMove a Source

Miscellaneous

checkCoord :: RawEncodable a => proxy a -> Bool Source

Checks over the range range that:

encode . decode == id

randomRawCoord :: forall a m. (MonadRandom m, RawEncodable a) => m (RawCoord a) Source

Helper

Fixed base

encodeBase :: Int -> [Int] -> Int Source

If all (elem [0 .. b-1]) v then v is the base b representation of encode b v such that its least significant digit is head v.

For any n, encodeBase b is a bijection from lists of length n with elements in [0 .. b-1] to [0 .. b^n - 1]

encodeBaseV :: Int -> Vector Int -> Int Source

Vector version of encodeBase.

decodeBase :: Int -> Int -> Int -> [Int] Source

len is the length of the resulting vector

encodeBase b . decodeBase b len == id
decodeBase b len . encodeBase b == id

Factorial radix

encodeFact :: Int -> [Int] -> Int Source

Input list must be a k-permutation of [0 .. n-1].

encodeFact is a bijection between k-permutations of [0 .. n-1] and [0 .. (fact n / fact (n-k)) - 1].

decodeFact :: Int -> Int -> Int -> [Int] Source

Inverse of encodeFact.

encodeFact n . decodeFact n k == id -- k <= n
decodeFact n k . encodeFact n == id -- on k-permutations

Binomial enumeration

cSum :: Int -> Int -> Int Source

cSum k z == sum [y `choose` k | y <- [k .. z-1]]

requires k < cSum_mMaz and z < cSum_nMaz.

cSum_mMax :: Int Source

Bound on arguments accepted by cSum

cSum_nMax :: Int Source

Bound on arguments accepted by cSum

encodeCV :: Vector Int -> Int Source

encodeCV <y 0 .. y k> == encodeCV <y 0 .. y (k-1)> + cSum k (y k)

where c is a k-combination, that is a sorted list of k nonnegative elements.

encodeCV is in fact a bijection between increasing lists (of non-negative integers) and integers.

Restriction: k < cSum_mMax, y k < cSum_nMax.

decodeCV :: Int -> Int -> Vector Int Source

Inverse of encodeCV.

The length of the resulting list must be supplied as a hint (although it could technically be guessed).