]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Grid.hs
Add the "zoom" function.
[spline3.git] / src / Grid.hs
index 4b75185ad19b31b4922e5485105b069ec56dba96..63b2cfa122bc6ba5bbb9d496b77f1a00466eebb6 100644 (file)
@@ -4,8 +4,15 @@
 module Grid
 where
 
-import Cube (Cube(Cube))
+import Test.QuickCheck (Arbitrary(..), Gen, Positive(..))
+
+import Cube (Cube(Cube), find_containing_tetrahedra)
 import FunctionValues
+import Misc (flatten)
+import Point (Point)
+import Tetrahedron (polynomial)
+import ThreeDimensional (contains_point)
+
 
 -- | Our problem is defined on a Grid. The grid size is given by the
 --   positive number h. The function values are the values of the
@@ -16,6 +23,13 @@ data Grid = Grid { h :: Double, -- MUST BE GREATER THAN ZERO!
           deriving (Eq, Show)
 
 
+instance Arbitrary Grid where
+    arbitrary = do
+      (Positive h') <- arbitrary :: Gen (Positive Double)
+      fvs <- arbitrary :: Gen [[[Double]]]
+      return (make_grid h' fvs)
+
+
 -- | The constructor that we want people to use. If we're passed a
 --   non-positive grid size, we throw an error.
 make_grid :: Double -> [[[Double]]] -> Grid
@@ -42,8 +56,8 @@ cubes g
     where
       fvs = function_values g
       zsize = (length fvs) - 1
-      ysize = (length $ head fvs) - 1
-      xsize = (length $ head $ head fvs) - 1
+      ysize = length (head fvs) - 1
+      xsize = length (head $ head fvs) - 1
 
 
 -- | Takes a grid and a position as an argument and returns the cube
@@ -58,3 +72,39 @@ cube_at g i j k
     | j >= length ((cubes g) !! i) = Nothing
     | k >= length (((cubes g) !! i) !! j) = Nothing
     | otherwise = Just $ (((cubes g) !! i) !! j) !! k
+
+
+-- | Takes a 'Grid', and returns all 'Cube's belonging to it that
+--   contain the given 'Point'.
+find_containing_cubes :: Grid -> Point -> [Cube]
+find_containing_cubes g p =
+    filter contains_our_point all_cubes
+    where
+      all_cubes = flatten $ cubes g
+      contains_our_point = flip contains_point p
+
+
+
+zoom :: Grid -> Int -> [[[Double]]]
+zoom g scale_factor
+    | fvs == [[[]]] = []
+    | head fvs == [[]] = []
+    | otherwise =
+        [[[f p | i <- [0..scaled_zsize],
+                 let i' = scale_dimension i,
+                 let j' = scale_dimension j,
+                 let k' = scale_dimension k,
+                 let p = (i', j', k') :: Point,
+                 let c = (find_containing_cubes g p) !! 0,
+                 let t = (find_containing_tetrahedra c p) !! 0,
+                 let f = polynomial t]
+                 | j <- [0..scaled_ysize]]
+                   | k <- [0..scaled_xsize]]
+  where
+    scale_dimension :: Int -> Double
+    scale_dimension x = (fromIntegral x) / (fromIntegral scale_factor)
+
+    fvs = function_values g
+    scaled_zsize = ((length fvs) - 1) * scale_factor
+    scaled_ysize = (length (head fvs) - 1) * scale_factor
+    scaled_xsize = (length (head $ head fvs) - 1) * scale_factor