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

Safe HaskellNone
LanguageHaskell2010

Diagrams.RubiksCube.Draw

Synopsis

Documentation

type RubiksCubeBackend n b = (Renderable (Path V2 n) b, TypeableFloat n, N b ~ n, V b ~ V2) Source

drawSide Source

Arguments

:: RubiksCubeBackend n b 
=> V2 n

dx

-> V2 n

dy

-> Side (Colour Double) 
-> Diagram b 

Draws one 3x3 side of the cube.

drawFoldingPattern :: RubiksCubeBackend n b => RubiksCube (Colour Double) -> Diagram b Source

Draw the folding pattern of the cube. The front side is at the center of the pattern.

data Offsets n Source

Constructors

Offsets 

Fields

_offsetX :: n
 
_offsetY :: n
 

Instances

offsetX :: forall n. Lens' (Offsets n) n Source

offsetY :: forall n. Lens' (Offsets n) n Source

drawRubiksCube :: RubiksCubeBackend n b => Offsets n -> RubiksCube (Colour Double) -> Diagram b Source

Draw the Rubik's cube in parallel perspective.

{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
import Diagrams.RubiksCube
import Control.Lens
drawCubeExample =
  let c = solvedRubiksCube ^. undoMoves [R,U,R',U']
  in drawRubiksCube with c

drawMove :: RubiksCubeBackend n b => Move -> Offsets n -> RubiksCube (Colour Double) -> Diagram b Source

Draw the Rubik's cube in parallel perspective with an arrow indicating the next move. If the the bottom layer is moved, the cube will be shown from below.

{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
import Diagrams.RubiksCube
import Control.Lens
drawMoveExample =
  let c = solvedRubiksCube ^. undoMoves [L,U,L',U']
  in drawMove L with c

data MovesSettings n Source

Constructors

MovesSettings 

Fields

_moveSep :: n

space between cubes

_showStart :: Bool

show the start configuration?

_showEnd :: Bool

show the end configuration?

_offsets :: Offsets n
 

moveSep :: forall n. Lens' (MovesSettings n) n Source

drawMoves Source

Arguments

:: RubiksCubeBackend n b 
=> MovesSettings n 
-> RubiksCube (Colour Double)

the start configuration

-> [Move] 
-> Diagram b 

Draws a sequence of moves.

{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
import Diagrams.RubiksCube
import Control.Lens
drawMovesExample =
  let moves = [B, R, F', R', D', F, F]
      startPos = solvedRubiksCube ^. undoMoves moves
      settings = with & showStart .~ True
  in drawMoves settings startPos moves

drawMovesBackward Source

Arguments

:: RubiksCubeBackend n b 
=> MovesSettings n 
-> RubiksCube (Colour Double)

the end configuration

-> [Move] 
-> Diagram b 

Like drawMoves, but takes the end configuration instead of the start configuration. The previous example can be simplified with this:

import Diagrams.RubiksCube
import Control.Lens
drawMovesExample' =
  let moves = [B, R, F', R', D', F, F]
      endPos = solvedRubiksCube
      settings = with & showStart .~ True
  in drawMovesBackward settings endPos moves