-----------------------------------------------------------------------------
-- |
-- Module      :  HCube.Test
-- Copyright   :  (c) Todd Wegner 2012
-- License     :  BSD-style (see the LICENSE file)
-- 
-- Maintainer  :  echbar137@yahoo.co.in
-- Stability   :  provisional
-- Portability :  portable
--
-- Test invariants of hcube. 
-----------------------------------------------------------------------------
module HCube.Test (runTests)
where

{-# LANGUAGE Safe #-}

import Data.Int
import Test.QuickCheck.Test(verboseCheckWith,quickCheck,quickCheckWith, Args(..))
import Test.QuickCheck.Arbitrary(Arbitrary, arbitrary, shrink, shrinkIntegral)
import Test.QuickCheck.Gen(Gen,sized, choose)
import HCube.Data (Vec, Numb)
import HCube.Lib (posToId, getPos, initCube)
import HCube.OrientGroup (Orient (..), rawToOrientNumber, rawOrientNum, orientNumberToRaw)
import HCube.Utility (mapVec, modNot, gateMinus, modMinus)

-- invariants

idProperty sz     = f where
	f	  = [posToId sz . getPos sz $ a | a <- [1..g]] == [1..g]
	g	  = sz*sz*sz

-- 24 is a mathematical constant
orientId 	= [f . g $ a | a <- [1..24]] == [1..24] where
    f		= rawToOrientNumber . rawOrientNum . Orient
    g		= h . orientNumberToRaw  where
	h cd		= [j . k $ (i 2, i 3, i 5), k (i 7, i 11,i 13)] where
		i	= modNot cd
		j	= gateMinus cd
		k	= modMinus cd 17

orientProperty   :: Numb -> Bool	
orientProperty _ = orientId

args = Args {
replay = Nothing,
maxDiscardRatio=5,
maxSuccess = 5,
maxSize = 10,
chatty = True
}

args2 = args {maxSuccess = 1,
	      maxDiscardRatio = 1} 

runTests		:: IO ()
runTests		= f where
	f 		=  h orientProperty
			   >> g idProperty
	g		= quickCheckWith args
	h 		= quickCheckWith args2