]> gitweb.michael.orlitzky.com - spline3.git/blob - src/Values.hs
Fix the broken Arbitrary instance of Values3D.
[spline3.git] / src / Values.hs
1 {-# LANGUAGE FlexibleInstances #-}
2
3 module Values
4 where
5
6 import Data.Array.Repa (
7 Array,
8 Z(..),
9 (:.)(..),
10 DIM1,
11 DIM2,
12 DIM3,
13 extent,
14 fromList,
15 index,
16 reshape,
17 size
18 )
19
20 import Data.Array.Repa.IO.Vector (readVectorFromTextFile,
21 writeVectorToTextFile)
22 import System.FilePath ()
23 import Test.QuickCheck (Arbitrary(..), Gen, Positive(..), vectorOf)
24
25
26 import ScaleFactor
27
28
29 type Values1D = Array DIM1 Double
30 type Values2D = Array DIM2 Double
31 type Values3D = Array DIM3 Double
32
33
34 instance Arbitrary Values3D where
35 arbitrary = do
36 (Positive x_dim) <- arbitrary :: Gen (Positive Int)
37 (Positive y_dim) <- arbitrary :: Gen (Positive Int)
38 (Positive z_dim) <- arbitrary :: Gen (Positive Int)
39 elements <- vectorOf (x_dim * y_dim * z_dim) (arbitrary :: Gen Double)
40 let new_shape = (Z :. x_dim :. y_dim :. z_dim)
41 let three_d = Data.Array.Repa.fromList new_shape elements
42 return three_d
43
44
45 read_values_1d :: FilePath -> IO Values1D
46 read_values_1d = readVectorFromTextFile
47
48
49 read_values_3d :: DIM3 -> FilePath -> IO Values3D
50 read_values_3d sh path = do
51 one_d <- read_values_1d path
52 return $ reshape sh one_d
53
54 write_values_1d :: Values3D -> FilePath -> IO ()
55 write_values_1d v3d path = do
56 let size3d = size $ extent v3d
57 let shape1d = (Z :. size3d)
58 let v1d = reshape shape1d v3d
59 writeVectorToTextFile v1d path
60
61 empty3d :: Values3D
62 empty3d = Data.Array.Repa.fromList (Z :. 0 :. 0 :. 0) []
63
64
65 dims :: Values3D -> (Int, Int, Int)
66 dims v3d =
67 let (Z :. x :. y :. z) = extent v3d
68 in
69 (x,y,z)
70
71
72 idx :: Values3D -> Int -> Int -> Int -> Double
73 idx v3d i j k =
74 index v3d shape
75 where
76 shape :: DIM3
77 shape = (Z :. i :. j :. k)
78
79
80 zoom_shape :: ScaleFactor -> DIM3 -> DIM3
81 zoom_shape (sfx, sfy, sfz) sh =
82 let (Z :. x :. y :. z) = sh
83 x' = x * sfx
84 y' = y * sfy
85 z' = z * sfz
86 in
87 (Z :. x' :. y' :. z')