module Rubik.Cube.Facelet.Internal where
import Rubik.Misc
import Control.Monad
import Data.Char ( intToDigit )
import Data.List
import qualified Data.Vector.Unboxed as U
numFacelets :: Int
numFacelets = 6 * 9
newtype Facelets = Facelets {
fromFacelets :: Vector Int
} deriving (Eq, Show)
instance Monoid Facelets where
mempty = Facelets $ idVector numFacelets
mappend (Facelets b) (Facelets c) = Facelets $ composeVector b c
instance Group Facelets where
inverse (Facelets a) = Facelets $ inverseVector a
fromFacelets' :: Facelets -> [Int]
fromFacelets' = U.toList . fromFacelets
facelets' :: [Int] -> Maybe Facelets
facelets' = facelets . U.fromList
facelets :: Vector Int -> Maybe Facelets
facelets v = do
guard $ U.length v == numFacelets
&& isPermutationVector v
return (Facelets v)
unsafeFacelets = Facelets
unsafeFacelets' = Facelets . U.fromList
type Color = Int
newtype ColorFacelets = ColorFacelets {
fromColorFacelets :: Vector Color
} deriving (Eq, Show)
fromColorFacelets' :: ColorFacelets -> [Color]
fromColorFacelets' = U.toList . fromColorFacelets
colorFacelets' :: [Color] -> Maybe ColorFacelets
colorFacelets' = colorFacelets . U.fromList
colorFacelets :: Vector Color -> Maybe ColorFacelets
colorFacelets v = do
guard $ U.length v == numFacelets
&& U.all (\c -> 0 <= c && c < 6) v
&& map (v U.!) centerFacelets == [0 .. 5]
return (ColorFacelets v)
colorOf :: Int -> Color
colorOf = (`div` 9)
colorFaceletsOf :: Facelets -> ColorFacelets
colorFaceletsOf = ColorFacelets . U.map colorOf . fromFacelets
colorChar :: Color -> Char
colorChar = ("ULFRBD" !!)
stringOfFacelets :: Facelets -> String
stringOfFacelets
= intercalate " " . map base9 . U.toList . fromFacelets
where base9 n = map intToDigit [n `div` 9, n `mod` 9]
stringOfColorFacelets :: ColorFacelets -> String
stringOfColorFacelets
= intercalate " " . chunk 9 . map colorChar . U.toList . fromColorFacelets
stringOfColorFacelets' :: Facelets -> String
stringOfColorFacelets' = stringOfColorFacelets . colorFaceletsOf
colorFacelets'' :: Eq a => [a] -> Maybe ColorFacelets
colorFacelets'' colors = do
guard (length colors == numFacelets)
guard (length (nub centers) == 6)
colorFacelets' =<< sequence ((`lookup` zip centers [0 .. 5]) <$> colors)
where
centers = (colors !!) <$> centerFacelets
centerFacelets :: [Int]
centerFacelets = [4, 13 .. 49]
ulb, ufl, urf, ubr, dlf, dfr, drb, dbl :: [Int]
ulb = [ 0, 9, 38]
ufl = [ 6, 18, 11]
urf = [ 8, 27, 20]
ubr = [ 2, 36, 29]
dlf = [45, 17, 24]
dfr = [47, 26, 33]
drb = [53, 35, 42]
dbl = [51, 44, 15]
cornerFacelets :: [[Int]]
cornerFacelets = [ulb, ufl, urf, ubr, dlf, dfr, drb, dbl]
ul, uf, ur, ub, dl, df, dr, db, fl, fr, bl, br :: [Int]
ul = [ 3, 10]
uf = [ 7, 19]
ur = [ 5, 28]
ub = [ 1, 37]
dl = [48, 16]
df = [46, 25]
dr = [50, 34]
db = [52, 43]
fl = [21, 14]
fr = [23, 30]
bl = [41, 12]
br = [39, 32]
edgeFacelets :: [[Int]]
edgeFacelets = [ul, uf, ur, ub, dl, df, dr, db, fl, fr, bl, br]