]> gitweb.michael.orlitzky.com - spline3.git/blob - src/Values.hs
Undo the previous FunctionValues test fix.
[spline3.git] / src / Values.hs
1 {-# LANGUAGE TypeSynonymInstances #-}
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)
24
25
26 type Values1D = Array DIM1 Double
27 type Values2D = Array DIM2 Double
28 type Values3D = Array DIM3 Double
29
30
31 instance Arbitrary Values3D where
32 arbitrary = do
33 x_dim <- arbitrary :: Gen Int
34 y_dim <- arbitrary :: Gen Int
35 z_dim <- arbitrary :: Gen Int
36 one_d <- arbitrary :: Gen Values1D
37 let new_shape = (Z :. x_dim :. y_dim :. z_dim)
38 let three_d = reshape new_shape one_d
39 return three_d
40
41
42 instance Arbitrary Values1D where
43 arbitrary = do
44 x <- arbitrary :: Gen [Double]
45 let shape = (Z :. (length x))
46 let one_d = Data.Array.Repa.fromList shape x
47 return one_d
48
49
50 read_values_1d :: FilePath -> IO Values1D
51 read_values_1d path = readVectorFromTextFile path
52
53
54 read_values_3d :: DIM3 -> FilePath -> IO Values3D
55 read_values_3d sh path = do
56 one_d <- read_values_1d path
57 return $ reshape sh one_d
58
59 write_values_1d :: Values3D -> FilePath -> IO ()
60 write_values_1d v3d path = do
61 let size3d = size $ extent v3d
62 let shape1d = (Z :. size3d)
63 let v1d = reshape shape1d v3d
64 writeVectorToTextFile v1d path
65
66 empty3d :: Values3D
67 empty3d = Data.Array.Repa.fromList (Z :. 0 :. 0 :. 0) []
68
69
70 dims :: Values3D -> (Int, Int, Int)
71 dims v3d =
72 let (Z :. x :. y :. z) = extent v3d
73 in
74 (x,y,z)
75
76
77 idx :: Values3D -> Int -> Int -> Int -> Double
78 idx v3d i j k =
79 index v3d shape
80 where
81 shape :: DIM3
82 shape = (Z :. k :. j :. i)
83
84
85 zoom_shape :: Int -> DIM3 -> DIM3
86 zoom_shape scale_factor sh =
87 let (Z :. x :. y :. z) = sh
88 x' = x * scale_factor
89 y' = y * scale_factor
90 z' = z * scale_factor
91 in
92 (Z :. x' :. y' :. z')