Safe Haskell | None |
---|---|
Language | Haskell2010 |
Encoding cube projections as Int
coordinates.
Explicit dictionary passing style: using a class would require explicit type annotations anyway.
- type RawCoord' = Int
- newtype RawCoord a = RawCoord {}
- newtype RawVector a b = RawVector {
- unRawVector :: Vector b
- newtype RawMove a = RawMove {}
- (!$) :: RawMove a -> RawCoord a -> RawCoord a
- (!.) :: Unbox b => RawVector a b -> RawCoord a -> b
- class RawEncodable a where
- encodeEdgeOrien' :: Vector Int -> Int
- numUDS :: Int
- numUDE :: Int
- flatCoord :: (RawEncodable a, RawEncodable b) => RawCoord a -> RawCoord b -> RawCoord (a, b)
- splitCoord :: (RawEncodable a, RawEncodable b) => RawCoord (a, b) -> (RawCoord a, RawCoord b)
- type Endo a = a -> a
- endoVector :: RawEncodable a => Endo a -> RawMove a
- cubeActionToEndo :: CubeAction a => Cube -> Endo a
- moveTable :: (CubeAction a, RawEncodable a) => Cube -> RawMove a
- symToEndo :: (Cube -> a -> a) -> Cube -> Endo a
- symTable :: RawEncodable a => (Cube -> a -> a) -> Cube -> RawMove a
- checkCoord :: RawEncodable a => proxy a -> Bool
- randomRawCoord :: forall a m. (MonadRandom m, RawEncodable a) => m (RawCoord a)
- encodeBase :: Int -> [Int] -> Int
- encodeBaseV :: Int -> Vector Int -> Int
- decodeBase :: Int -> Int -> Int -> [Int]
- encodeFact :: Int -> [Int] -> Int
- decodeFact :: Int -> Int -> Int -> [Int]
- cSum :: Int -> Int -> Int
- cSum_mMax :: Int
- cSum_nMax :: Int
- encodeCV :: Vector Int -> Int
- decodeCV :: Int -> Int -> Vector Int
Raw coordinates
Encoding to an efficient datatype for which it is possible to build tables instead of computing functions.
RawVector | |
|
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.
range :: proxy a -> Int Source
Number of elements that can be converted.
Their values are to lie in [0 .. range c - 1]
.
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 |
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
encodeEdgeOrien' :: Vector Int -> Int Source
flatCoord :: (RawEncodable a, RawEncodable b) => RawCoord a -> RawCoord b -> RawCoord (a, b) Source
splitCoord :: (RawEncodable a, RawEncodable b) => RawCoord (a, b) -> (RawCoord a, RawCoord b) Source
Table building
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.
moveTable :: (CubeAction a, RawEncodable a) => Cube -> RawMove a Source
Composition of endoVector
and cubeAction
.
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 (
then elem
[0 .. b-1]) vv
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
.
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
.