module Grid
where
+import qualified Data.Array.Repa as R
import Test.QuickCheck (Arbitrary(..), Gen, Positive(..))
import Cube (Cube(Cube), find_containing_tetrahedra)
import Tetrahedron (polynomial)
import Values (Values3D, dims, empty3d, zoom_shape)
-import qualified Data.Array.Repa as R
-- | 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
-- | Takes a grid and a position as an argument and returns the cube
-- centered on that position. If there is no cube there (i.e. the
--- position is outside of the grid), it will return 'Nothing'.
-cube_at :: Grid -> Int -> Int -> Int -> Maybe Cube
+-- position is outside of the grid), it will throw an error.
+cube_at :: Grid -> Int -> Int -> Int -> Cube
cube_at g i j k
- | i < 0 = Nothing
- | j < 0 = Nothing
- | k < 0 = Nothing
- | k >= length (cubes g) = Nothing
- | j >= length ((cubes g) !! k) = Nothing
- | i >= length (((cubes g) !! k) !! j) = Nothing
- | otherwise = Just $ (((cubes g) !! k) !! j) !! i
-
+ | i < 0 = error "i < 0 in cube_at"
+ | j < 0 = error "j < 0 in cube_at"
+ | k < 0 = error "k < 0 in cube_at"
+ | otherwise =
+ let zsize = length (cubes g) in
+ if k >= zsize then
+ error "k >= xsize in cube_at"
+ else
+ let ysize = length ((cubes g) !! k) in
+ if j >= ysize then
+ error "j >= ysize in cube_at"
+ else
+ let xsize = length (((cubes g) !! k) !! j) in
+ if i >= xsize then
+ error "i >= xsize in cube_at"
+ else
+ (((cubes g) !! k) !! j) !! i
-- The first cube along any axis covers (-h/2, h/2). The second
-- to check every cube.
find_containing_cube :: Grid -> Point -> Cube
find_containing_cube g p =
- case cube_at g i j k of
- Just c -> c
- Nothing -> error "No cube contains the given point."
+ cube_at g i j k
where
(x, y, z) = p
i = calculate_containing_cube_coordinate g x
{-# INLINE zoom_lookup #-}
-zoom_lookup :: Grid -> a -> (R.DIM3 -> Double)
-zoom_lookup g _ = zoom_result g
+zoom_lookup :: Grid -> Int -> a -> (R.DIM3 -> Double)
+zoom_lookup g scale_factor _ = zoom_result g scale_factor
{-# INLINE zoom_result #-}
-zoom_result :: Grid -> R.DIM3 -> Double
-zoom_result g (R.Z R.:. i R.:. j R.:. k) =
+zoom_result :: Grid -> Int -> R.DIM3 -> Double
+zoom_result g scale_factor (R.Z R.:. i R.:. j R.:. k) =
f p
where
- i' = fromIntegral i
- j' = fromIntegral j
- k' = fromIntegral k
+ sf = fromIntegral scale_factor
+ i' = fromIntegral i / sf
+ j' = fromIntegral j / sf
+ k' = fromIntegral k / sf
p = (i', j', k') :: Point
c = find_containing_cube g p
t = head (find_containing_tetrahedra c p)
zoom g scale_factor
| xsize == 0 || ysize == 0 || zsize == 0 = empty3d
| otherwise =
- R.force $ R.traverse arr transExtent (zoom_lookup g)
+ R.force $ R.traverse arr transExtent (zoom_lookup g scale_factor)
where
arr = function_values g
(xsize, ysize, zsize) = dims arr
module Tests.Grid
where
-import Data.Maybe (fromJust)
import Test.HUnit
import Assertions
assertAlmostEqual "c0030 is correct" (c t 0 0 3 0) (17/8)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0003 is correct" (c t 0 0 0 3) (27/8)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0021 is correct" (c t 0 0 2 1) (61/24)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0012 is correct" (c t 0 0 1 2) (71/24)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0120 is correct" (c t 0 1 2 0) (55/24)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0102 is correct" (c t 0 1 0 2) (73/24)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0111 is correct" (c t 0 1 1 1) (8/3)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0210 is correct" (c t 0 2 1 0) (29/12)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0201 is correct" (c t 0 2 0 1) (11/4)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c0300 is correct" (c t 0 3 0 0) (5/2)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c1020 is correct" (c t 1 0 2 0) (8/3)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c1002 is correct" (c t 1 0 0 2) (23/6)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c1011 is correct" (c t 1 0 1 1) (13/4)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c1110 is correct" (c t 1 1 1 0) (23/8)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c1101 is correct" (c t 1 1 0 1) (27/8)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c1200 is correct" (c t 1 2 0 0) 3
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c2010 is correct" (c t 2 0 1 0) (10/3)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c2001 is correct" (c t 2 0 0 1) 4
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c2100 is correct" (c t 2 1 0 0) (7/2)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertAlmostEqual "c3000 is correct" (c t 3 0 0 0) 4
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertEqual "v0 is correct" (v0 t) (1, 1, 1)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertEqual "v1 is correct" (v1 t) (0.5, 1, 1)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertEqual "v2 is correct" (v2 t) (0.5, 0.5, 1.5)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
assertClose "v3 is correct" (v3 t) (0.5, 1.5, 1.5)
where
g = make_grid 1 trilinear
- cube = fromJust $ cube_at g 1 1 1
+ cube = cube_at g 1 1 1
t = tetrahedron0 cube
let k' = fromIntegral k]
where
g = make_grid 1 trilinear
- c0 = fromJust $ cube_at g 1 1 1
+ c0 = cube_at g 1 1 1
test_zeros_reproduced :: Assertion
let k' = fromIntegral k]
where
g = make_grid 1 zeros
- c0 = fromJust $ cube_at g 1 1 1
+ c0 = cube_at g 1 1 1
t0 = tetrahedron0 c0
p = polynomial t0
let k' = (fromIntegral k) * 0.5]
where
g = make_grid 1 trilinear
- c0 = fromJust $ cube_at g 1 1 1
+ c0 = cube_at g 1 1 1
-- | The point 'p' in this test lies on the boundary of tetrahedra 12 and 15.