diagrams-rubiks-cube-0.2.0.1: Library for drawing the Rubik's Cube.

Safe HaskellNone
LanguageHaskell2010

Diagrams.RubiksCube.Model

Contents

Synopsis

Constructing cubes

data Side a Source #

One side of the Rubik's Cube with 3*3 facets.

Constructors

Side 

Fields

Instances

Functor Side Source # 

Methods

fmap :: (a -> b) -> Side a -> Side b #

(<$) :: a -> Side b -> Side a #

Applicative Side Source # 

Methods

pure :: a -> Side a #

(<*>) :: Side (a -> b) -> Side a -> Side b #

(*>) :: Side a -> Side b -> Side b #

(<*) :: Side a -> Side b -> Side a #

Foldable Side Source # 

Methods

fold :: Monoid m => Side m -> m #

foldMap :: Monoid m => (a -> m) -> Side a -> m #

foldr :: (a -> b -> b) -> b -> Side a -> b #

foldr' :: (a -> b -> b) -> b -> Side a -> b #

foldl :: (b -> a -> b) -> b -> Side a -> b #

foldl' :: (b -> a -> b) -> b -> Side a -> b #

foldr1 :: (a -> a -> a) -> Side a -> a #

foldl1 :: (a -> a -> a) -> Side a -> a #

toList :: Side a -> [a] #

null :: Side a -> Bool #

length :: Side a -> Int #

elem :: Eq a => a -> Side a -> Bool #

maximum :: Ord a => Side a -> a #

minimum :: Ord a => Side a -> a #

sum :: Num a => Side a -> a #

product :: Num a => Side a -> a #

Traversable Side Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Side a -> f (Side b) #

sequenceA :: Applicative f => Side (f a) -> f (Side a) #

mapM :: Monad m => (a -> m b) -> Side a -> m (Side b) #

sequence :: Monad m => Side (m a) -> m (Side a) #

Eq a => Eq (Side a) Source # 

Methods

(==) :: Side a -> Side a -> Bool #

(/=) :: Side a -> Side a -> Bool #

Show a => Show (Side a) Source # 

Methods

showsPrec :: Int -> Side a -> ShowS #

show :: Side a -> String #

showList :: [Side a] -> ShowS #

Reversing (Side a) Source # 

Methods

reversing :: Side a -> Side a #

topLeft :: forall a. Lens' (Side a) a Source #

topCenter :: forall a. Lens' (Side a) a Source #

topRight :: forall a. Lens' (Side a) a Source #

middleLeft :: forall a. Lens' (Side a) a Source #

middleCenter :: forall a. Lens' (Side a) a Source #

middleRight :: forall a. Lens' (Side a) a Source #

bottomLeft :: forall a. Lens' (Side a) a Source #

bottomCenter :: forall a. Lens' (Side a) a Source #

bottomRight :: forall a. Lens' (Side a) a Source #

rotateSideCW :: Aut (Side a) Source #

Rotate the side clockwise.

rotateSideCCW :: Aut (Side a) Source #

Rotate the side counter-clockwise.

data Cube a Source #

A cube with six sides.

     +---+
     | u |
 +---+---+---+---+
 | l | f | r | b |
 +---+---+---+---+
     | d |
     +---+

Constructors

Cube 

Fields

Instances

Functor Cube Source # 

Methods

fmap :: (a -> b) -> Cube a -> Cube b #

(<$) :: a -> Cube b -> Cube a #

Applicative Cube Source # 

Methods

pure :: a -> Cube a #

(<*>) :: Cube (a -> b) -> Cube a -> Cube b #

(*>) :: Cube a -> Cube b -> Cube b #

(<*) :: Cube a -> Cube b -> Cube a #

Foldable Cube Source # 

Methods

fold :: Monoid m => Cube m -> m #

foldMap :: Monoid m => (a -> m) -> Cube a -> m #

foldr :: (a -> b -> b) -> b -> Cube a -> b #

foldr' :: (a -> b -> b) -> b -> Cube a -> b #

foldl :: (b -> a -> b) -> b -> Cube a -> b #

foldl' :: (b -> a -> b) -> b -> Cube a -> b #

foldr1 :: (a -> a -> a) -> Cube a -> a #

foldl1 :: (a -> a -> a) -> Cube a -> a #

toList :: Cube a -> [a] #

null :: Cube a -> Bool #

length :: Cube a -> Int #

elem :: Eq a => a -> Cube a -> Bool #

maximum :: Ord a => Cube a -> a #

minimum :: Ord a => Cube a -> a #

sum :: Num a => Cube a -> a #

product :: Num a => Cube a -> a #

Traversable Cube Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Cube a -> f (Cube b) #

sequenceA :: Applicative f => Cube (f a) -> f (Cube a) #

mapM :: Monad m => (a -> m b) -> Cube a -> m (Cube b) #

sequence :: Monad m => Cube (m a) -> m (Cube a) #

Eq a => Eq (Cube a) Source # 

Methods

(==) :: Cube a -> Cube a -> Bool #

(/=) :: Cube a -> Cube a -> Bool #

Show a => Show (Cube a) Source # 

Methods

showsPrec :: Int -> Cube a -> ShowS #

show :: Cube a -> String #

showList :: [Cube a] -> ShowS #

frontSide :: forall a. Lens' (Cube a) a Source #

backSide :: forall a. Lens' (Cube a) a Source #

leftSide :: forall a. Lens' (Cube a) a Source #

rightSide :: forall a. Lens' (Cube a) a Source #

upSide :: forall a. Lens' (Cube a) a Source #

downSide :: forall a. Lens' (Cube a) a Source #

newtype RubiksCube a Source #

A normal Rubik's cube with 6 sides with 9 facets each.

Constructors

RubiksCube 

Fields

Instances

cube :: forall a a. Iso (RubiksCube a) (RubiksCube a) (Cube (Side a)) (Cube (Side a)) Source #

Selecting rows and columns

data Vec3 a Source #

A list of fixed length 3.

Constructors

Vec3 a a a 

Instances

Functor Vec3 Source # 

Methods

fmap :: (a -> b) -> Vec3 a -> Vec3 b #

(<$) :: a -> Vec3 b -> Vec3 a #

Applicative Vec3 Source # 

Methods

pure :: a -> Vec3 a #

(<*>) :: Vec3 (a -> b) -> Vec3 a -> Vec3 b #

(*>) :: Vec3 a -> Vec3 b -> Vec3 b #

(<*) :: Vec3 a -> Vec3 b -> Vec3 a #

Foldable Vec3 Source # 

Methods

fold :: Monoid m => Vec3 m -> m #

foldMap :: Monoid m => (a -> m) -> Vec3 a -> m #

foldr :: (a -> b -> b) -> b -> Vec3 a -> b #

foldr' :: (a -> b -> b) -> b -> Vec3 a -> b #

foldl :: (b -> a -> b) -> b -> Vec3 a -> b #

foldl' :: (b -> a -> b) -> b -> Vec3 a -> b #

foldr1 :: (a -> a -> a) -> Vec3 a -> a #

foldl1 :: (a -> a -> a) -> Vec3 a -> a #

toList :: Vec3 a -> [a] #

null :: Vec3 a -> Bool #

length :: Vec3 a -> Int #

elem :: Eq a => a -> Vec3 a -> Bool #

maximum :: Ord a => Vec3 a -> a #

minimum :: Ord a => Vec3 a -> a #

sum :: Num a => Vec3 a -> a #

product :: Num a => Vec3 a -> a #

Traversable Vec3 Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Vec3 a -> f (Vec3 b) #

sequenceA :: Applicative f => Vec3 (f a) -> f (Vec3 a) #

mapM :: Monad m => (a -> m b) -> Vec3 a -> m (Vec3 b) #

sequence :: Monad m => Vec3 (m a) -> m (Vec3 a) #

Distributive Vec3 Source # 

Methods

distribute :: Functor f => f (Vec3 a) -> Vec3 (f a) #

collect :: Functor f => (a -> Vec3 b) -> f a -> Vec3 (f b) #

distributeM :: Monad m => m (Vec3 a) -> Vec3 (m a) #

collectM :: Monad m => (a -> Vec3 b) -> m a -> Vec3 (m b) #

Representable Vec3 Source # 

Associated Types

type Rep (Vec3 :: * -> *) :: * #

Methods

tabulate :: (Rep Vec3 -> a) -> Vec3 a #

index :: Vec3 a -> Rep Vec3 -> a #

Eq a => Eq (Vec3 a) Source # 

Methods

(==) :: Vec3 a -> Vec3 a -> Bool #

(/=) :: Vec3 a -> Vec3 a -> Bool #

Show a => Show (Vec3 a) Source # 

Methods

showsPrec :: Int -> Vec3 a -> ShowS #

show :: Vec3 a -> String #

showList :: [Vec3 a] -> ShowS #

Reversing (Vec3 a) Source # 

Methods

reversing :: Vec3 a -> Vec3 a #

type Rep Vec3 Source # 
type Rep Vec3

topRow :: Lens' (Side a) (Vec3 a) Source #

The top three facets (from left to right).

middleRow :: Lens' (Side a) (Vec3 a) Source #

The middle three facets (from left to right).

bottomRow :: Lens' (Side a) (Vec3 a) Source #

The bottom three facets (from left to right).

leftCol :: Lens' (Side a) (Vec3 a) Source #

The left column (from top to down).

centerCol :: Lens' (Side a) (Vec3 a) Source #

The center column (from top to down).

rightCol :: Lens' (Side a) (Vec3 a) Source #

The right column (from top to down).

Traversing facets

By layer

topLayerFacets :: Traversal' (RubiksCube a) a Source #

The 21=4*3+9 facets in the top layer.

middleLayerFacets :: Traversal' (RubiksCube a) a Source #

The 12=4*3 facets in the middle layer.

bottomLayerFacets :: Traversal' (RubiksCube a) a Source #

The 21=4*3+9 facets in the bottom layer.

By position

centerFacets :: Traversal' (RubiksCube a) a Source #

The six facets that are the center of their side.

cornerFacets :: Traversal' (RubiksCube a) a Source #

The 24=6*4=8*3 corner facets.

edgeFacets :: Traversal' (RubiksCube a) a Source #

The 24=6*4=12*2 edge facets.

Rotating the whole cube

type Aut a = Iso' a a Source #

The type of automorphisms

rotateLeft :: Aut (RubiksCube a) Source #

Rotate the whole Rubik's Cube such that the front side becomes the new left side and the top and bottom sides stay fixed.

rotateRight :: Aut (RubiksCube a) Source #

Rotate the whole Rubik's Cube such that the front side becomes the new right side and the top and bottom sides stay fixed.

rotateDown :: Aut (RubiksCube a) Source #

Rotate the whole Rubik's Cube such that the front side becomes the new bottom side and the left and right sides stay fixed.

rotateUp :: Aut (RubiksCube a) Source #

Rotate the whole Rubik's Cube such that the front side becomes the new top side and the left and right sides stay fixed.

rotateCW :: Aut (RubiksCube a) Source #

Rotate the whole Rubik's Cube such that the top side becomes the new right side and the front and back sides stay fixed.

rotateCCW :: Aut (RubiksCube a) Source #

Rotate the whole Rubik's Cube such that the top side becomes the new left side and the front and back sides stay fixed.

Moving layers of the cube

move :: Move -> Aut (RubiksCube a) Source #

Perform a move.

doMoves :: [Move] -> Aut (RubiksCube a) Source #

Perform a list of moves.

undoMoves :: [Move] -> Aut (RubiksCube a) Source #

Undo the actions of a list of moves.