-----------------------------------------------------------------------------
-- |
-- Module      :  HCube.Data
-- Copyright   :  (c) Todd Wegner 2012
-- License     :  BSD-style (see the LICENSE file)
-- 
-- Maintainer  :  echbar137@yahoo.co.in
-- Stability   :  provisional
-- Portability :  portable
-- 
-----------------------------------------------------------------------------
{-# LANGUAGE Safe #-}

module HCube.Data where

-- | Integer type used in hcube.
type Numb		= Int

-- | Physical size of cube.  For example a value of 3 refers to original 3x3x3 Rubik's cube.
type Size		= Numb

-- | Point is used in transformations of cubies in a two dimensional plane.
type Point		= (Numb, Numb)

-- | Vector which orientation group matrices act on.
-- Also used for calculating new cubie positions.
type Vec		= (Numb, Numb, Numb)

type Format		= String

-- | String with each character representing a color of a physical cubie.
type ColorTag		= String
type Projection		= [(Numb,Side)]

-- | Type used to specify state of physical cube.
type CubeSurf		= [(Side,[Color])]

-- | Matrices in hcube are constructed from column vectors.
-- The third vector is often chosen as the cross product of the first two
-- such that the determinate of the matrix is one.
data Matrix		= Matrix Vec Vec Vec deriving Show

-- | Used for simplistic processing of console commands.
data Command = Projection View |
	       Operation [Rotation] |
	       Undo |
	       Help |
	       Quit |
	       NoCommand

-- | Left and right 3D view of cube.
data View    = LeftV |
	       RightV deriving (Show, Read, Eq)

-- | Used by Template to map logical structure of cube to display views.
data ViewAssociation	= Sur (Numb,Side) |
			  Ide Numb |
			  Ori Numb

-- | Defines a rotation of an arbitrary cube slice.
data Rotation		= Rotation Slab Direction Numb |
			  RotateCube Slab Direction
			  deriving (Show, Read,Eq)


-- | Defines direction of slab movement.
data Direction 		= Clockwise | Counter | Twice | NoDir deriving (Show, Read,Eq)

-- | Defines an axis for slab movement.
data Slab		= Layer | HSlice | VSlice | NoSlab deriving (Show, Read, Eq)

-- | Sides of a cube.
data Side		= UpS | DownS | FrontS | BackS | LeftS | RightS | NoSide
			  deriving (Show, Read, Eq, Ord)

-- | Represents the color of a cubie face.
data Color		= White | Yellow | Orange | Red | Blue | Green | NoColor
			  deriving (Read, Eq)

instance Show Color where
    show White		= whiteC
    show Yellow		= yellowC
    show Orange		= orangeC
    show Red		= redC
    show Blue		= blueC
    show Green		= greenC
    show NoColor	= ""

data ActualCube		= ActualCube {
			up :: Color,
			front :: Color,
			down :: Color,
			back :: Color,
			left :: Color,
			right :: Color
			} deriving (Show, Read, Eq)

-- | Represents the color white. Modify if the physical cube uses a different coloring scheme
whiteC			= "W"
yellowC			= "Y"
orangeC			= "O"
redC			= "R"
blueC			= "B"
greenC			= "G"
noC			= "-"

-- trivial functions
-- | Gives inverse of a cube operation.
invOpp				:: Rotation -> Rotation
invOpp (Rotation sb dir nm) 	= Rotation sb (invDir dir) nm
invOpp (RotateCube sb dir)	= RotateCube sb (invDir dir)

-- | Reverses direction of rotation.
invDir			:: Direction -> Direction
invDir Clockwise	= Counter
invDir Counter		= Clockwise
invDir Twice		= Twice

-- | Associates a side of a solved cube to a color.
sideToColor		:: Side -> Color
sideToColor UpS		= White
sideToColor DownS	= Yellow
sideToColor FrontS	= Orange
sideToColor BackS	= Red
sideToColor LeftS	= Green
sideToColor RightS	= Blue
sideToColor NoSide	= NoColor

-- | Inverse of sideToColor
colorToSide		:: Color -> Side
colorToSide White	= UpS	
colorToSide Yellow	= DownS		
colorToSide Orange	= FrontS		
colorToSide Red		= BackS		
colorToSide Blue	= RightS		
colorToSide Green	= LeftS
colorToSide NoColor	= NoSide