]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Cube.hs
Remove the 'reorient' function from Cube.
[spline3.git] / src / Cube.hs
index 78c5ec21e266a2cc33308bd23a98e67c96577673..8287177ed17edf6307a9517d06e11548320fa7da 100644 (file)
@@ -2,10 +2,10 @@ module Cube
 where
 
 import Cardinal
-import Face (Face(Face, v0, v1, v2, v3))
+import qualified Face (Face(Face, v0, v1, v2, v3))
 import FunctionValues
 import Point
-import Tetrahedron (Tetrahedron(Tetrahedron), fv)
+import Tetrahedron hiding (c)
 import ThreeDimensional
 
 data Cube = Cube { h :: Double,
@@ -26,7 +26,8 @@ instance Show Cube where
         " ymin: " ++ (show (ymin c)) ++ "\n" ++
         " ymax: " ++ (show (ymax c)) ++ "\n" ++
         " zmin: " ++ (show (zmin c)) ++ "\n" ++
-        " zmax: " ++ (show (zmax c)) ++ "\n"
+        " zmax: " ++ (show (zmax c)) ++ "\n" ++
+        " fv: " ++ (show (Cube.fv c)) ++ "\n"
         where
           subscript =
               (show (i c)) ++ "," ++ (show (j c)) ++ "," ++ (show (k c))
@@ -107,82 +108,35 @@ instance ThreeDimensional Cube where
         | otherwise = True
 
 
--- instance Num Cube where
---     (Cube g1 i1 j1 k1 d1) + (Cube _ i2 j2 k2 d2) =
---         Cube g1 (i1 + i2) (j1 + j2) (k1 + k2) (d1 + d2)
-
---     (Cube g1 i1 j1 k1 d1) - (Cube _ i2 j2 k2 d2) =
---         Cube g1 (i1 - i2) (j1 - j2) (k1 - k2) (d1 - d2)
-
---     (Cube g1 i1 j1 k1 d1) * (Cube _ i2 j2 k2 d2) =
---         Cube g1 (i1 * i2) (j1 * j2) (k1 * k2) (d1 * d2)
-
---     abs (Cube g1 i1 j1 k1 d1) =
---         Cube g1 (abs i1) (abs j1) (abs k1) (abs d1)
-
---     signum (Cube g1 i1 j1 k1 d1) =
---         Cube g1 (signum i1) (signum j1) (signum k1) (signum d1)
-
---     fromInteger x = empty_cube { datum = (fromIntegral x) }
-
--- instance Fractional Cube where
---     (Cube g1 i1 j1 k1 d1) / (Cube _ _ _ _ d2) =
---         Cube g1 i1 j1 k1 (d1 / d2)
-
---     recip (Cube g1 i1 j1 k1 d1) =
---         Cube g1 i1 j1 k1 (recip d1)
-
---     fromRational q = empty_cube { datum = fromRational q }
-
-
-
--- | Return the cube corresponding to the grid point i,j,k. The list
---   of cubes is stored as [z][y][x] but we'll be requesting it by
---   [x][y][z] so we flip the indices in the last line.
--- cube_at :: Grid -> Int -> Int -> Int -> Cube
--- cube_at g i' j' k'
---         | i' >= length (function_values g) = Cube g i' j' k' 0
---         | i' < 0                          = Cube g i' j' k' 0
---         | j' >= length ((function_values g) !! i') = Cube g i' j' k' 0
---         | j' < 0                                  = Cube g i' j' k' 0
---         | k' >= length (((function_values g) !! i') !! j') = Cube g i' j' k' 0
---         | k' < 0                                          = Cube g i' j' k' 0
---         | otherwise =
---             (((cubes g) !! k') !! j') !! i'
-
-
-
-
-
 
 -- Face stuff.
 
 -- | The top (in the direction of z) face of the cube.
-top_face :: Cube -> Face
-top_face c = Face v0' v1' v2' v3'
+top_face :: Cube -> Face.Face
+top_face c = Face.Face v0' v1' v2' v3'
     where
       delta = (1/2)*(h c)
-      v0' = (center c) + (delta, delta, delta)
-      v1' = (center c) + (delta, -delta, delta)
-      v2' = (center c) + (-delta, -delta, delta)
-      v3' = (center c) + (-delta, delta, delta)
+      v0' = (center c) + (delta, -delta, delta)
+      v1' = (center c) + (delta, delta, delta)
+      v2' = (center c) + (-delta, delta, delta)
+      v3' = (center c) + (-delta, -delta, delta)
 
 
 
 -- | The back (in the direction of x) face of the cube.
-back_face :: Cube -> Face
-back_face c = Face v0' v1' v2' v3'
+back_face :: Cube -> Face.Face
+back_face c = Face.Face v0' v1' v2' v3'
     where
       delta = (1/2)*(h c)
-      v0' = (center c) + (delta, delta, delta)
+      v0' = (center c) + (delta, -delta, -delta)
       v1' = (center c) + (delta, delta, -delta)
-      v2' = (center c) + (delta, -delta, -delta)
+      v2' = (center c) + (delta, delta, delta)
       v3' = (center c) + (delta, -delta, delta)
 
 
 -- The bottom face (in the direction of -z) of the cube.
-down_face :: Cube -> Face
-down_face c = Face v0' v1' v2' v3'
+down_face :: Cube -> Face.Face
+down_face c = Face.Face v0' v1' v2' v3'
     where
       delta = (1/2)*(h c)
       v0' = (center c) + (delta, delta, -delta)
@@ -193,8 +147,8 @@ down_face c = Face v0' v1' v2' v3'
 
 
 -- | The front (in the direction of -x) face of the cube.
-front_face :: Cube -> Face
-front_face c = Face v0' v1' v2' v3'
+front_face :: Cube -> Face.Face
+front_face c = Face.Face v0' v1' v2' v3'
     where
       delta = (1/2)*(h c)
       v0' = (center c) + (-delta, -delta, delta)
@@ -202,10 +156,9 @@ front_face c = Face v0' v1' v2' v3'
       v2' = (center c) + (-delta, delta, -delta)
       v3' = (center c) + (-delta, -delta, -delta)
 
-
 -- | The left (in the direction of -y) face of the cube.
-left_face :: Cube -> Face
-left_face c = Face v0' v1' v2' v3'
+left_face :: Cube -> Face.Face
+left_face c = Face.Face v0' v1' v2' v3'
     where
       delta = (1/2)*(h c)
       v0' = (center c) + (-delta, -delta, delta)
@@ -215,8 +168,8 @@ left_face c = Face v0' v1' v2' v3'
 
 
 -- | The right (in the direction of y) face of the cube.
-right_face :: Cube -> Face
-right_face c = Face v0' v1' v2' v3'
+right_face :: Cube -> Face.Face
+right_face c = Face.Face v0' v1' v2' v3'
     where
       delta = (1/2)*(h c)
       v0' = (center c) + (-delta, delta, -delta)
@@ -225,15 +178,14 @@ right_face c = Face v0' v1' v2' v3'
       v3' = (center c) + (-delta, delta, delta)
 
 
-
 tetrahedron0 :: Cube -> Tetrahedron
 tetrahedron0 c =
     Tetrahedron (Cube.fv c) v0' v1' v2' v3'
     where
       v0' = center c
       v1' = center (front_face c)
-      v2' = v0 (front_face c)
-      v3' = v1 (front_face c)
+      v2' = Face.v0 (front_face c)
+      v3' = Face.v1 (front_face c)
 
 tetrahedron1 :: Cube -> Tetrahedron
 tetrahedron1 c =
@@ -241,8 +193,8 @@ tetrahedron1 c =
     where
       v0' = center c
       v1' = center (front_face c)
-      v2' = v1 (front_face c)
-      v3' = v2 (front_face c)
+      v2' = Face.v1 (front_face c)
+      v3' = Face.v2 (front_face c)
       fv' = rotate (Cube.fv c) ccwx
 
 tetrahedron2 :: Cube -> Tetrahedron
@@ -251,8 +203,8 @@ tetrahedron2 c =
     where
       v0' = center c
       v1' = center (front_face c)
-      v2' = v2 (front_face c)
-      v3' = v3 (front_face c)
+      v2' = Face.v2 (front_face c)
+      v3' = Face.v3 (front_face c)
       fv' = rotate (Cube.fv c) (ccwx . ccwx)
 
 tetrahedron3 :: Cube -> Tetrahedron
@@ -261,8 +213,8 @@ tetrahedron3 c =
     where
       v0' = center c
       v1' = center (front_face c)
-      v2' = v3 (front_face c)
-      v3' = v1 (front_face c)
+      v2' = Face.v3 (front_face c)
+      v3' = Face.v0 (front_face c)
       fv' = rotate (Cube.fv c) cwx
 
 tetrahedron4 :: Cube -> Tetrahedron
@@ -271,8 +223,8 @@ tetrahedron4 c =
     where
       v0' = center c
       v1' = center (top_face c)
-      v2' = v0 (front_face c)
-      v3' = v1 (front_face c)
+      v2' = Face.v0 (top_face c)
+      v3' = Face.v1 (top_face c)
       fv' = rotate (Cube.fv c) cwy
 
 tetrahedron5 :: Cube -> Tetrahedron
@@ -281,9 +233,9 @@ tetrahedron5 c =
     where
       v0' = center c
       v1' = center (top_face c)
-      v2' = v1 (top_face c)
-      v3' = v2 (top_face c)
-      fv' = rotate (Tetrahedron.fv (tetrahedron0 c)) ccwx
+      v2' = Face.v1 (top_face c)
+      v3' = Face.v2 (top_face c)
+      fv' = rotate (Tetrahedron.fv (tetrahedron4 c)) ccwz
 
 tetrahedron6 :: Cube -> Tetrahedron
 tetrahedron6 c =
@@ -291,9 +243,9 @@ tetrahedron6 c =
     where
       v0' = center c
       v1' = center (top_face c)
-      v2' = v2 (top_face c)
-      v3' = v3 (top_face c)
-      fv' = rotate (Tetrahedron.fv (tetrahedron0 c)) (ccwx . ccwx)
+      v2' = Face.v2 (top_face c)
+      v3' = Face.v3 (top_face c)
+      fv' = rotate (Tetrahedron.fv (tetrahedron4 c)) (ccwz . ccwz)
 
 tetrahedron7 :: Cube -> Tetrahedron
 tetrahedron7 c =
@@ -301,9 +253,51 @@ tetrahedron7 c =
     where
       v0' = center c
       v1' = center (top_face c)
-      v2' = v3 (top_face c)
-      v3' = v1 (top_face c)
-      fv' = rotate (Tetrahedron.fv (tetrahedron0 c)) cwx
+      v2' = Face.v3 (top_face c)
+      v3' = Face.v0 (top_face c)
+      fv' = rotate (Tetrahedron.fv (tetrahedron4 c)) cwz
+
+tetrahedron8 :: Cube -> Tetrahedron
+tetrahedron8 c =
+    Tetrahedron fv' v0' v1' v2' v3'
+    where
+      v0' = center c
+      v1' = center (back_face c)
+      v2' = Face.v0 (back_face c)
+      v3' = Face.v1 (back_face c)
+      fv' = rotate (Tetrahedron.fv (tetrahedron4 c)) cwy
+
+tetrahedron9 :: Cube -> Tetrahedron
+tetrahedron9 c =
+    Tetrahedron fv' v0' v1' v2' v3'
+    where
+      v0' = center c
+      v1' = center (back_face c)
+      v2' = Face.v1 (back_face c)
+      v3' = Face.v2 (back_face c)
+      fv' = rotate (Tetrahedron.fv (tetrahedron8 c)) ccwx
+
+tetrahedron10 :: Cube -> Tetrahedron
+tetrahedron10 c =
+    Tetrahedron fv' v0' v1' v2' v3'
+    where
+      v0' = center c
+      v1' = center (back_face c)
+      v2' = Face.v2 (back_face c)
+      v3' = Face.v3 (back_face c)
+      fv' = rotate (Tetrahedron.fv (tetrahedron8 c)) (ccwx . ccwx)
+
+
+tetrahedron11 :: Cube -> Tetrahedron
+tetrahedron11 c =
+    Tetrahedron fv' v0' v1' v2' v3'
+    where
+      v0' = center c
+      v1' = center (back_face c)
+      v2' = Face.v3 (back_face c)
+      v3' = Face.v0 (back_face c)
+      fv' = rotate (Tetrahedron.fv (tetrahedron8 c)) cwx
+
 
 tetrahedrons :: Cube -> [Tetrahedron]
 tetrahedrons c =
@@ -314,13 +308,12 @@ tetrahedrons c =
      tetrahedron4 c,
      tetrahedron5 c,
      tetrahedron6 c,
-     tetrahedron7 c
-                -- ,
-                --  tetrahedron8 c,
-                --  tetrahedron9 c,
-                --  tetrahedron10 c,
-                --  tetrahedron11 c,
-                --  tetrahedron12 c,
+     tetrahedron7 c,
+     tetrahedron8 c,
+     tetrahedron9 c,
+     tetrahedron10 c,
+     tetrahedron11 c
+     --tetrahedron12 c,
                 --  tetrahedron13 c,
                 --  tetrahedron14 c,
                 --  tetrahedron15 c,