]> gitweb.michael.orlitzky.com - spline3.git/blob - src/Values.hs
Merge branch 'uncached_vector'
[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 unsafeIndex,
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, choose, 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 -- I declare not to care about empty lists.
37 x_dim <- choose (1, 27)
38 y_dim <- choose (1, 27)
39 z_dim <- choose (1, 27)
40 elements <- vectorOf (x_dim * y_dim * z_dim) (arbitrary :: Gen Double)
41 let new_shape = (Z :. x_dim :. y_dim :. z_dim)
42 let three_d = Data.Array.Repa.fromList new_shape elements
43 return three_d
44
45
46 read_values_1d :: FilePath -> IO Values1D
47 read_values_1d = readVectorFromTextFile
48
49
50 read_values_3d :: DIM3 -> FilePath -> IO Values3D
51 read_values_3d sh path = do
52 one_d <- read_values_1d path
53 return $ reshape sh one_d
54
55 write_values_1d :: Values3D -> FilePath -> IO ()
56 write_values_1d v3d path = do
57 let size3d = size $ extent v3d
58 let shape1d = (Z :. size3d)
59 let v1d = reshape shape1d v3d
60 writeVectorToTextFile v1d path
61
62 empty3d :: Values3D
63 empty3d = Data.Array.Repa.fromList (Z :. 0 :. 0 :. 0) []
64
65
66 dims :: Values3D -> (Int, Int, Int)
67 dims v3d =
68 let (Z :. x :. y :. z) = extent v3d
69 in
70 (x,y,z)
71
72
73 idx :: Values3D -> Int -> Int -> Int -> Double
74 idx v3d i j k =
75 unsafeIndex v3d shape
76 where
77 shape :: DIM3
78 shape = (Z :. i :. j :. k)
79
80
81 zoom_shape :: ScaleFactor -> DIM3 -> DIM3
82 zoom_shape (sfx, sfy, sfz) sh =
83 let (Z :. x :. y :. z) = sh
84 x' = x * sfx
85 y' = y * sfy
86 z' = z * sfz
87 in
88 (Z :. x' :. y' :. z')