+{-# LANGUAGE NoMonomorphismRestriction #-}
+
+--
+-- Disable the MR so that let tp = testProperty does what it should!
+--
+
-- | The Cardinal module contains the Cardinal data type, representing
-- a cardinal direction (one of the 26 directions surrounding the
-- center of a cube. In addition to those 26 directions, we also
import Control.Monad (liftM, liftM2)
import Prelude hiding (LT)
-import Test.QuickCheck (Arbitrary(..), oneof)
+
+import Test.HUnit
+import Test.Framework (Test, testGroup)
+import Test.Framework.Providers.HUnit (testCase)
+import Test.Framework.Providers.QuickCheck2 (testProperty)
+
+import Test.QuickCheck (Arbitrary(..), Property, (==>), oneof)
+
data Cardinal = F -- ^ Front
| B -- ^ Back
-- | Rotate a cardinal direction clockwise about the z-axis.
cwz :: Cardinal -> Cardinal
cwz = ccwz . ccwz . ccwz
+
+
+
+
+-- | We know what (c t6 2 1 0 0) should be from Sorokina and
+-- Zeilfelder, p. 87. This test checks that the directions are
+-- rotated properly. The order of the letters has to be just right
+-- since I haven't defined a proper Eq instance for Cardinals.
+test_c_tilde_2100_rotation_correct :: Assertion
+test_c_tilde_2100_rotation_correct =
+ assertEqual "auto-rotate equals manual rotate" ((ccwz . ccwz . cwy) expr1) expr2
+ where
+ expr1 =
+ (3/8)*I +
+ (1/12)*(T + R + L + D) +
+ (1/64)*(FT + FR + FL + FD) +
+ (7/48)*F +
+ (1/48)*B +
+ (1/96)*(RT + LD + LT + RD) +
+ (1/192)*(BT + BR + BL + BD)
+
+ expr2 =
+ (3/8)*I +
+ (1/12)*(F + L + R + B) +
+ (1/64)*(FT + LT + RT + BT) +
+ (7/48)*T +
+ (1/48)*D +
+ (1/96)*(FL + BR + FR + BL) +
+ (1/192)*(FD + LD + RD + BD)
+
+-- | A list of all directions, sans the interior and composite types.
+all_directions :: [Cardinal]
+all_directions = [L, R, F, B, D, T, FL, FR, FD, FT,
+ BL, BR, BD, BT, LD, LT, RD, RT, FLD,
+ FLT, FRD, FRT, BLD, BLT, BRD, BRT]
+
+
+-- | If we rotate a direction (other than front or back)
+-- counter-clockwise with respect to the x-axis, we should get a new
+-- direction.
+prop_ccwx_rotation_changes_direction :: Cardinal -> Property
+prop_ccwx_rotation_changes_direction c =
+ c `elem` [L, R, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
+ RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
+ ==> ccwx c /= c
+
+-- | If we rotate a direction (other than front or back) clockwise
+-- with respect to the x-axis, we should get a new direction.
+prop_cwx_rotation_changes_direction :: Cardinal -> Property
+prop_cwx_rotation_changes_direction c =
+ -- The front and back faces are unchanged by x-rotation.
+ c `elem` [L, R, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
+ RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
+ ==> cwx c /= c
+
+-- | If we rotate a direction (other than left or right)
+-- counter-clockwise with respect to the y-axis, we should get a new
+-- direction.
+prop_ccwy_rotation_changes_direction :: Cardinal -> Property
+prop_ccwy_rotation_changes_direction c =
+ c `elem` [F, B, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
+ RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
+ ==> ccwy c /= c
+
+
+-- | If we rotate a direction (other than left or right) clockwise
+-- with respect to the y-axis, we should get a new direction.
+prop_cwy_rotation_changes_direction :: Cardinal -> Property
+prop_cwy_rotation_changes_direction c =
+ c `elem` [F, B, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
+ RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
+ ==> cwy c /= c
+
+
+-- | If we rotate a direction (other than top or down)
+-- counter-clockwise with respect to the z-axis, we should get a new
+-- direction.
+prop_ccwz_rotation_changes_direction :: Cardinal -> Property
+prop_ccwz_rotation_changes_direction c =
+ c `elem` [L, R, F, B, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
+ RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
+ ==> ccwz c /= c
+
+
+-- | If we rotate a direction (other than top or down) clockwise with
+-- respect to the z-axis, we should get a new direction.
+prop_cwz_rotation_changes_direction :: Cardinal -> Property
+prop_cwz_rotation_changes_direction c =
+ c `elem` [L, R, F, B, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
+ RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
+ ==> cwz c /= c
+
+
+-- | If we are given a direction c, there should only be one direction
+-- d which, when rotated counter-clockwise with respect to the
+-- x-axis, produces c.
+prop_ccwx_rotation_result_unique :: Cardinal -> Property
+prop_ccwx_rotation_result_unique c =
+ c `elem` all_directions ==>
+ (length [ d | d <- all_directions, ccwx d == c ]) == 1
+
+-- | If we are given a direction c, there should only be one direction
+-- d which, when rotated clockwise with respect to the x-axis,
+-- produces c.
+prop_cwx_rotation_result_unique :: Cardinal -> Property
+prop_cwx_rotation_result_unique c =
+ c `elem` all_directions ==>
+ (length [ d | d <- all_directions, cwx d == c ]) == 1
+
+
+-- | If we are given a direction c, there should only be one direction
+-- d which, when rotated counter-clockwise with respect to the
+-- y-axis, produces c.
+prop_ccwy_rotation_result_unique :: Cardinal -> Property
+prop_ccwy_rotation_result_unique c =
+ c `elem` all_directions ==>
+ (length [ d | d <- all_directions, ccwy d == c ]) == 1
+
+
+-- | If we are given a direction c, there should only be one direction
+-- d which, when rotated clockwise with respect to the y-axis,
+-- produces c.
+prop_cwy_rotation_result_unique :: Cardinal -> Property
+prop_cwy_rotation_result_unique c =
+ c `elem` all_directions ==>
+ (length [ d | d <- all_directions, cwy d == c ]) == 1
+
+
+-- | If we are given a direction c, there should only be one direction
+-- d which, when rotated counter-clockwise with respect to the
+-- z-axis, produces c.
+prop_ccwz_rotation_result_unique :: Cardinal -> Property
+prop_ccwz_rotation_result_unique c =
+ c `elem` all_directions ==>
+ (length [ d | d <- all_directions, ccwz d == c ]) == 1
+
+
+-- | If we are given a direction c, there should only be one direction
+-- d which, when rotated clockwise with respect to the z-axis,
+-- produces c.
+prop_cwz_rotation_result_unique :: Cardinal -> Property
+prop_cwz_rotation_result_unique c =
+ c `elem` all_directions ==>
+ (length [ d | d <- all_directions, cwz d == c ]) == 1
+
+
+-- | If you rotate a cardinal direction four times in the clockwise
+-- (with respect to x) direction, you should wind up with the same
+-- direction.
+prop_four_cwx_is_identity :: Cardinal -> Bool
+prop_four_cwx_is_identity c =
+ (cwx . cwx . cwx . cwx) c == c
+
+-- | If you rotate a cardinal direction four times in the
+-- counter-clockwise (with respect to x) direction, you should wind up
+-- with the same direction.
+prop_four_ccwx_is_identity :: Cardinal -> Bool
+prop_four_ccwx_is_identity c =
+ (ccwx . ccwx . ccwx . ccwx) c == c
+
+-- | If you rotate a cardinal direction four times in the clockwise
+-- (with respect to y) direction, you should wind up with the same
+-- direction.
+prop_four_cwy_is_identity :: Cardinal -> Bool
+prop_four_cwy_is_identity c =
+ (cwy . cwy . cwy . cwy) c == c
+
+-- | If you rotate a cardinal direction four times in the counter-clockwise
+-- (with respect to y) direction, you should wind up with the same
+-- direction.
+prop_four_ccwy_is_identity :: Cardinal -> Bool
+prop_four_ccwy_is_identity c =
+ (ccwy . ccwy . ccwy . ccwy) c == c
+
+-- | If you rotate a cardinal direction four times in the clockwise
+-- (with respect to z) direction, you should wind up with the same
+-- direction.
+prop_four_cwz_is_identity :: Cardinal -> Bool
+prop_four_cwz_is_identity c =
+ (cwz . cwz . cwz . cwz) c == c
+
+-- | If you rotate a cardinal direction four times in the
+-- counter-clockwise (with respect to z) direction, you should wind up
+-- with the same direction.
+prop_four_ccwz_is_identity :: Cardinal -> Bool
+prop_four_ccwz_is_identity c =
+ (ccwz . ccwz . ccwz . ccwz) c == c
+
+
+cardinal_tests :: Test.Framework.Test
+cardinal_tests =
+ testGroup "Cardinal Tests" [
+ testCase "c-tilde_2100 rotation correct"test_c_tilde_2100_rotation_correct ]
+
+
+cardinal_properties :: Test.Framework.Test
+cardinal_properties =
+ let tp = testProperty
+ in
+ testGroup "Cardinal Properties" [
+ tp "ccwx rotation changes direction" prop_ccwx_rotation_changes_direction,
+ tp "cwx rotation changes direction" prop_cwx_rotation_changes_direction,
+ tp "ccwy rotation changes direction" prop_ccwy_rotation_changes_direction,
+ tp "cwy rotation changes direction" prop_cwy_rotation_changes_direction,
+ tp "ccwz rotation changes direction" prop_ccwz_rotation_changes_direction,
+ tp "cwz rotation changes direction" prop_cwz_rotation_changes_direction,
+ tp "ccwx rotation result unique" prop_ccwx_rotation_result_unique,
+ tp "cwx rotation result unique" prop_cwx_rotation_result_unique,
+ tp "ccwy rotation result unique" prop_ccwy_rotation_result_unique,
+ tp "cwy rotation result unique" prop_cwy_rotation_result_unique,
+ tp "ccwz rotation result unique" prop_ccwz_rotation_result_unique,
+ tp "cwz rotation result unique" prop_cwz_rotation_result_unique,
+ tp "four cwx is identity" prop_four_cwx_is_identity,
+ tp "four ccwx is identity" prop_four_ccwx_is_identity,
+ tp "four cwy is identity" prop_four_cwy_is_identity,
+ tp "four ccwy is identity" prop_four_ccwy_is_identity,
+ tp "four cwz is identity" prop_four_cwz_is_identity,
+ tp "four ccwz is identity" prop_four_ccwz_is_identity ]
+++ /dev/null
-module Tests.Cardinal
-where
-
-import Prelude hiding (LT)
-import Test.HUnit
-import Test.QuickCheck (Property, (==>))
-
-import Cardinal
-
--- | We know what (c t6 2 1 0 0) should be from Sorokina and
--- Zeilfelder, p. 87. This test checks that the directions are
--- rotated properly. The order of the letters has to be just right
--- since I haven't defined a proper Eq instance for Cardinals.
-test_c_tilde_2100_rotation_correct :: Assertion
-test_c_tilde_2100_rotation_correct =
- assertEqual "auto-rotate equals manual rotate" ((ccwz . ccwz . cwy) expr1) expr2
- where
- expr1 =
- (3/8)*I +
- (1/12)*(T + R + L + D) +
- (1/64)*(FT + FR + FL + FD) +
- (7/48)*F +
- (1/48)*B +
- (1/96)*(RT + LD + LT + RD) +
- (1/192)*(BT + BR + BL + BD)
-
- expr2 =
- (3/8)*I +
- (1/12)*(F + L + R + B) +
- (1/64)*(FT + LT + RT + BT) +
- (7/48)*T +
- (1/48)*D +
- (1/96)*(FL + BR + FR + BL) +
- (1/192)*(FD + LD + RD + BD)
-
--- | A list of all directions, sans the interior and composite types.
-all_directions :: [Cardinal]
-all_directions = [L, R, F, B, D, T, FL, FR, FD, FT,
- BL, BR, BD, BT, LD, LT, RD, RT, FLD,
- FLT, FRD, FRT, BLD, BLT, BRD, BRT]
-
-
--- | If we rotate a direction (other than front or back)
--- counter-clockwise with respect to the x-axis, we should get a new
--- direction.
-prop_ccwx_rotation_changes_direction :: Cardinal -> Property
-prop_ccwx_rotation_changes_direction c =
- c `elem` [L, R, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
- RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
- ==> ccwx c /= c
-
--- | If we rotate a direction (other than front or back) clockwise
--- with respect to the x-axis, we should get a new direction.
-prop_cwx_rotation_changes_direction :: Cardinal -> Property
-prop_cwx_rotation_changes_direction c =
- -- The front and back faces are unchanged by x-rotation.
- c `elem` [L, R, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
- RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
- ==> cwx c /= c
-
--- | If we rotate a direction (other than left or right)
--- counter-clockwise with respect to the y-axis, we should get a new
--- direction.
-prop_ccwy_rotation_changes_direction :: Cardinal -> Property
-prop_ccwy_rotation_changes_direction c =
- c `elem` [F, B, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
- RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
- ==> ccwy c /= c
-
-
--- | If we rotate a direction (other than left or right) clockwise
--- with respect to the y-axis, we should get a new direction.
-prop_cwy_rotation_changes_direction :: Cardinal -> Property
-prop_cwy_rotation_changes_direction c =
- c `elem` [F, B, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
- RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
- ==> cwy c /= c
-
-
--- | If we rotate a direction (other than top or down)
--- counter-clockwise with respect to the z-axis, we should get a new
--- direction.
-prop_ccwz_rotation_changes_direction :: Cardinal -> Property
-prop_ccwz_rotation_changes_direction c =
- c `elem` [L, R, F, B, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
- RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
- ==> ccwz c /= c
-
-
--- | If we rotate a direction (other than top or down) clockwise with
--- respect to the z-axis, we should get a new direction.
-prop_cwz_rotation_changes_direction :: Cardinal -> Property
-prop_cwz_rotation_changes_direction c =
- c `elem` [L, R, F, B, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT,
- RD, RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT]
- ==> cwz c /= c
-
-
--- | If we are given a direction c, there should only be one direction
--- d which, when rotated counter-clockwise with respect to the
--- x-axis, produces c.
-prop_ccwx_rotation_result_unique :: Cardinal -> Property
-prop_ccwx_rotation_result_unique c =
- c `elem` all_directions ==>
- (length [ d | d <- all_directions, ccwx d == c ]) == 1
-
--- | If we are given a direction c, there should only be one direction
--- d which, when rotated clockwise with respect to the x-axis,
--- produces c.
-prop_cwx_rotation_result_unique :: Cardinal -> Property
-prop_cwx_rotation_result_unique c =
- c `elem` all_directions ==>
- (length [ d | d <- all_directions, cwx d == c ]) == 1
-
-
--- | If we are given a direction c, there should only be one direction
--- d which, when rotated counter-clockwise with respect to the
--- y-axis, produces c.
-prop_ccwy_rotation_result_unique :: Cardinal -> Property
-prop_ccwy_rotation_result_unique c =
- c `elem` all_directions ==>
- (length [ d | d <- all_directions, ccwy d == c ]) == 1
-
-
--- | If we are given a direction c, there should only be one direction
--- d which, when rotated clockwise with respect to the y-axis,
--- produces c.
-prop_cwy_rotation_result_unique :: Cardinal -> Property
-prop_cwy_rotation_result_unique c =
- c `elem` all_directions ==>
- (length [ d | d <- all_directions, cwy d == c ]) == 1
-
-
--- | If we are given a direction c, there should only be one direction
--- d which, when rotated counter-clockwise with respect to the
--- z-axis, produces c.
-prop_ccwz_rotation_result_unique :: Cardinal -> Property
-prop_ccwz_rotation_result_unique c =
- c `elem` all_directions ==>
- (length [ d | d <- all_directions, ccwz d == c ]) == 1
-
-
--- | If we are given a direction c, there should only be one direction
--- d which, when rotated clockwise with respect to the z-axis,
--- produces c.
-prop_cwz_rotation_result_unique :: Cardinal -> Property
-prop_cwz_rotation_result_unique c =
- c `elem` all_directions ==>
- (length [ d | d <- all_directions, cwz d == c ]) == 1
-
-
--- | If you rotate a cardinal direction four times in the clockwise
--- (with respect to x) direction, you should wind up with the same
--- direction.
-prop_four_cwx_is_identity :: Cardinal -> Bool
-prop_four_cwx_is_identity c =
- (cwx . cwx . cwx . cwx) c == c
-
--- | If you rotate a cardinal direction four times in the
--- counter-clockwise (with respect to x) direction, you should wind up
--- with the same direction.
-prop_four_ccwx_is_identity :: Cardinal -> Bool
-prop_four_ccwx_is_identity c =
- (ccwx . ccwx . ccwx . ccwx) c == c
-
--- | If you rotate a cardinal direction four times in the clockwise
--- (with respect to y) direction, you should wind up with the same
--- direction.
-prop_four_cwy_is_identity :: Cardinal -> Bool
-prop_four_cwy_is_identity c =
- (cwy . cwy . cwy . cwy) c == c
-
--- | If you rotate a cardinal direction four times in the counter-clockwise
--- (with respect to y) direction, you should wind up with the same
--- direction.
-prop_four_ccwy_is_identity :: Cardinal -> Bool
-prop_four_ccwy_is_identity c =
- (ccwy . ccwy . ccwy . ccwy) c == c
-
--- | If you rotate a cardinal direction four times in the clockwise
--- (with respect to z) direction, you should wind up with the same
--- direction.
-prop_four_cwz_is_identity :: Cardinal -> Bool
-prop_four_cwz_is_identity c =
- (cwz . cwz . cwz . cwz) c == c
-
--- | If you rotate a cardinal direction four times in the
--- counter-clockwise (with respect to z) direction, you should wind up
--- with the same direction.
-prop_four_ccwz_is_identity :: Cardinal -> Bool
-prop_four_ccwz_is_identity c =
- (ccwz . ccwz . ccwz . ccwz) c == c