+-- | The Cardinal module contains the Cardinal data type, representing
+-- a cardinal direction (one of the 27 directions surrounding the
+-- center of a cube. In addition to those 27 directions, we also
+-- include the interior point and a number of composite types that
+-- allow us to perform arithmetic on directions.
module Cardinal
where
import Prelude hiding (LT)
-data Cardinal = F
- | B
- | L
- | R
- | D
- | T
- | FL
- | FR
- | FD
- | FT
- | BL
- | BR
- | BD
- | BT
- | LD
- | LT
- | RD
- | RT
- | FLD
- | FLT
- | FRD
- | FRT
- | BLD
- | BLT
- | BRD
- | BRT
- | I
- | Scalar Double
- | Sum Cardinal Cardinal
+data Cardinal = F -- ^ Front
+ | B -- ^ Back
+ | L -- ^ Left
+ | R -- ^ Right
+ | D -- ^ Down
+ | T -- ^ Top
+ | FL -- ^ Front Left
+ | FR -- ^ Front Right
+ | FD -- ^ Front Down
+ | FT -- ^ Front Top
+ | BL -- ^ Back Left
+ | BR -- ^ Back Right
+ | BD -- ^ Back Down
+ | BT -- ^ Back Top
+ | LD -- ^ Left Down
+ | LT -- ^ Left Top
+ | RD -- ^ Right Down
+ | RT -- ^ Right Top
+ | FLD -- ^ Front Left Down
+ | FLT -- ^ Front Left Top
+ | FRD -- ^ Front Right Down
+ | FRT -- ^ Front Right Top
+ | BLD -- ^ Back Left Down
+ | BLT -- ^ Back Left Top
+ | BRD -- ^ Back Right Down
+ | BRT -- ^ Back Right Top
+ | I -- ^ Interior
+ | Scalar Double -- ^ A wrapper around a scalar value.
+ | Sum Cardinal Cardinal -- ^ The sum of two directions.
| Difference Cardinal Cardinal
- | Product Cardinal Cardinal
+ -- ^ The difference of two directions, the first minus the second.
+ | Product Cardinal Cardinal -- ^ The product of two directions.
| Quotient Cardinal Cardinal
+ -- ^ The quotient of two directions, the first divided by the
+ -- second.
deriving (Show, Eq)
+
+-- | By making Cardinal an instance of Num, we gain the ability to
+-- add, subtract, and multiply directions. The results of these
+-- operations are never actually calculated; the types just keep
+-- track of which operations were performed in which order.
instance Num Cardinal where
x + y = Sum x y
x - y = Difference x y
signum x = x
fromInteger x = Scalar (fromIntegral x)
+
+-- | Like the Num instance, the Fractional instance allows us to
+-- take quotients of directions.
instance Fractional Cardinal where
x / y = Quotient x y
recip x = Quotient (Scalar 1) x
fromRational x = Scalar (fromRational x)
+
-- | Rotate a cardinal direction counter-clockwise about the x-axis.
ccwx :: Cardinal -> Cardinal
ccwx F = F
-- | Rotate a cardinal direction counter-clockwise about the y-axis.
--- TODO: Fix these; they still use the x-axis values.
ccwy :: Cardinal -> Cardinal
-ccwy F = F
-ccwy B = B
-ccwy L = T
-ccwy R = D
-ccwy D = L
-ccwy T = R
-ccwy FL = FT
-ccwy FR = FD
-ccwy FD = FL
-ccwy FT = FR
-ccwy BL = BT
-ccwy BR = BD
-ccwy BD = BL
-ccwy BT = BR
-ccwy LD = LT
-ccwy LT = RT
-ccwy RD = LD
-ccwy RT = RD
-ccwy FLD = FLT
-ccwy FLT = FRT
-ccwy FRD = FLD
+ccwy F = D
+ccwy B = T
+ccwy L = L
+ccwy R = R
+ccwy D = B
+ccwy T = F
+ccwy FL = LD
+ccwy FR = RD
+ccwy FD = BD
+ccwy FT = FD
+ccwy BL = LT
+ccwy BR = RT
+ccwy BD = BT
+ccwy BT = FT
+ccwy LD = BL
+ccwy LT = FL
+ccwy RD = BR
+ccwy RT = FR
+ccwy FLD = BLD
+ccwy FLT = FLD
+ccwy FRD = BRD
ccwy FRT = FRD
ccwy BLD = BLT
-ccwy BLT = BRT
-ccwy BRD = BLD
-ccwy BRT = BRD
+ccwy BLT = FLT
+ccwy BRD = BRT
+ccwy BRT = FRT
ccwy I = I
ccwy (Scalar s) = (Scalar s)
ccwy (Sum c0 c1) = Sum (ccwy c0) (ccwy c1)
ccwy (Product c0 c1) = Product (ccwy c0) (ccwy c1)
ccwy (Quotient c0 c1) = Quotient (ccwy c0) (ccwy c1)
--- | Rotate a cardinal direction clockwise about the x-axis.
+-- | Rotate a cardinal direction clockwise about the y-axis.
cwy :: Cardinal -> Cardinal
cwy = ccwy . ccwy . ccwy
+
+
+-- | Rotate a cardinal direction counter-clockwise about the z-axis.
+ccwz :: Cardinal -> Cardinal
+ccwz F = L
+ccwz B = R
+ccwz L = B
+ccwz R = F
+ccwz D = D
+ccwz T = T
+ccwz FL = BL
+ccwz FR = FL
+ccwz FD = LD
+ccwz FT = LT
+ccwz BL = BR
+ccwz BR = FR
+ccwz BD = RD
+ccwz BT = RT
+ccwz LD = BD
+ccwz LT = BT
+ccwz RD = FD
+ccwz RT = FT
+ccwz FLD = BLD
+ccwz FLT = BLT
+ccwz FRD = FLD
+ccwz FRT = FLT
+ccwz BLD = BRD
+ccwz BLT = BRT
+ccwz BRD = FRD
+ccwz BRT = FRT
+ccwz I = I
+ccwz (Scalar s) = (Scalar s)
+ccwz (Sum c0 c1) = Sum (ccwz c0) (ccwz c1)
+ccwz (Difference c0 c1) = Difference (ccwz c0) (ccwz c1)
+ccwz (Product c0 c1) = Product (ccwz c0) (ccwz c1)
+ccwz (Quotient c0 c1) = Quotient (ccwz c0) (ccwz c1)
+
+-- | Rotate a cardinal direction clockwise about the z-axis.
+cwz :: Cardinal -> Cardinal
+cwz = ccwz . ccwz . ccwz