]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Cardinal.hs
Have the show function display the grid size of a cube.
[spline3.git] / src / Cardinal.hs
index e4e9464e1bddef6ef57fd306d6423c8a707660d5..0a1b139ca8b87546b0bd3f9d19ea36a58fe413e5 100644 (file)
 module Cardinal
 where
 
+import Prelude hiding (LT)
+
 data Cardinal = F
               | B
               | L
               | R
-              | T
               | 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
               | Difference Cardinal Cardinal
               | Product Cardinal Cardinal
-              | ScalarProduct Double Cardinal
+              | Quotient Cardinal Cardinal
                 deriving (Show, Eq)
 
 instance Num Cardinal where
     x + y = Sum x y
     x - y = Difference x y
-    x * y = Sum x y
-    negate x = ScalarProduct (-1) x
+    x * y = Product x y
+    negate x = Product (Scalar (-1)) x
     abs x = x
     signum x = x
-    fromInteger _ = F -- Whatever.
+    fromInteger x = Scalar (fromIntegral x)
+
+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
+ccwx B = B
+ccwx L = T
+ccwx R = D
+ccwx D = L
+ccwx T = R
+ccwx FL = FT
+ccwx FR = FD
+ccwx FD = FL
+ccwx FT = FR
+ccwx BL = BT
+ccwx BR = BD
+ccwx BD = BL
+ccwx BT = BR
+ccwx LD = LT
+ccwx LT = RT
+ccwx RD = LD
+ccwx RT = RD
+ccwx FLD = FLT
+ccwx FLT = FRT
+ccwx FRD = FLD
+ccwx FRT = FRD
+ccwx BLD = BLT
+ccwx BLT = BRT
+ccwx BRD = BLD
+ccwx BRT = BRD
+ccwx I = I
+ccwx (Scalar s) = (Scalar s)
+ccwx (Sum c0 c1) = Sum (ccwx c0) (ccwx c1)
+ccwx (Difference c0 c1) = Difference (ccwx c0) (ccwx c1)
+ccwx (Product c0 c1) = Product (ccwx c0) (ccwx c1)
+ccwx (Quotient c0 c1) = Quotient (ccwx c0) (ccwx c1)
+
+-- | Rotate a cardinal direction clockwise about the x-axis.
+cwx :: Cardinal -> Cardinal
+cwx = ccwx . ccwx . ccwx
+
+
+-- | 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 FRT = FRD
+ccwy BLD = BLT
+ccwy BLT = BRT
+ccwy BRD = BLD
+ccwy BRT = BRD
+ccwy I = I
+ccwy (Scalar s) = (Scalar s)
+ccwy (Sum c0 c1) = Sum (ccwy c0) (ccwy c1)
+ccwy (Difference c0 c1) = Difference (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.
+cwy :: Cardinal -> Cardinal
+cwy = ccwy . ccwy . ccwy