]> gitweb.michael.orlitzky.com - spline3.git/blob - src/MRI.hs
52be3f7b1cba92c96d9bb64142ed7b3dd4acb546
[spline3.git] / src / MRI.hs
1 module MRI
2 where
3
4 import Data.Word
5 import Data.Bits
6 import Data.Array.Repa as R
7 import Data.Array.Repa.IO.Binary as R
8 import Data.Array.Repa.IO.ColorRamp as R
9
10 import Values
11
12 mri_depth :: Int
13 mri_depth = 109
14
15 mri_width :: Int
16 mri_width = 256
17
18 mri_height :: Int
19 mri_height = 256
20
21 mri_shape :: DIM3
22 mri_shape = (Z :. mri_depth :. mri_height :. mri_width)
23
24 mri_lower_threshold :: Double
25 mri_lower_threshold = 1400
26
27 mri_upper_threshold :: Double
28 mri_upper_threshold = 2500
29
30 mri_slice3d :: DIM3
31 mri_slice3d = (Z :. 1 :. mri_height :. mri_width)
32
33 type RawData sh = Array sh Word16
34 type RawData3D = RawData DIM3
35
36 type RGB = (Word8, Word8, Word8)
37 type ColorData sh = Array sh RGB
38
39 rgb_to_dbl :: RGB -> (Double, Double, Double)
40 rgb_to_dbl (x,y,z) = (fromIntegral x, fromIntegral y, fromIntegral z)
41
42
43 read_word16s :: FilePath -> IO RawData3D
44 read_word16s path = do
45 arr <- R.readArrayFromStorableFile path mri_shape
46 arr `deepSeqArray` return ()
47 return arr
48
49
50 {-# INLINE bracket #-}
51 bracket :: Double -> Word16
52 bracket x
53 | x < mri_lower_threshold = 0
54 | x > mri_upper_threshold = 255
55 | otherwise = truncate (r * 255)
56 where
57 numerator = x - mri_lower_threshold
58 denominator = mri_upper_threshold - mri_lower_threshold
59 r = numerator/denominator
60
61
62 {-# INLINE flip16 #-}
63 flip16 :: Word16 -> Word16
64 flip16 xx =
65 shift xx 8 .|. (shift xx (-8) .&. 0x00ff)
66
67
68 swap_bytes :: (Shape sh) => (RawData sh) -> (RawData sh)
69 swap_bytes arr =
70 R.force $ R.map flip16 arr
71
72 bracket_array :: (Shape sh) => (Values sh) -> (RawData sh)
73 bracket_array arr =
74 R.force $ R.map f arr
75 where
76 f = bracket
77
78
79 flip_y :: RawData3D -> RawData3D
80 flip_y arr =
81 R.force $ R.traverse arr id
82 (\get (Z :. z :. y :. x) ->
83 get (Z :. z :. (mri_height - 1) - y :. x))
84
85 flip_x :: RawData3D -> RawData3D
86 flip_x arr =
87 R.force $ R.traverse arr id
88 (\get (Z :. z :. y :. x) ->
89 get (Z :. z :. y :. (mri_width - 1) - x))
90
91 write_word16s :: (Shape sh) => FilePath -> (RawData sh) -> IO ()
92 write_word16s = R.writeArrayToStorableFile
93
94
95 values_to_colors :: (Shape sh) => (Values sh) -> (ColorData sh)
96 values_to_colors arr =
97 R.force $ R.map (truncate_rgb . ramp_it) arr
98 where
99 ramp_it :: Double -> (Double, Double, Double)
100 ramp_it x =
101 if x == 0 then
102 (0, 0, 0)
103 else
104 rampColorHotToCold 0 255 x
105
106 truncate_rgb :: (Double, Double, Double) -> (Word8, Word8, Word8)
107 truncate_rgb (r, g, b) =
108 (r', g', b')
109 where
110 r' = truncate (r * 255)
111 g' = truncate (g * 255)
112 b' = truncate (b * 255)
113
114
115 red_dbl_data :: (Shape sh) => (ColorData sh) -> Array sh Double
116 red_dbl_data =
117 R.map (get_r . rgb_to_dbl)
118 where
119 get_r :: (Double, Double, Double) -> Double
120 get_r (r, _, _) = r
121
122 green_dbl_data :: (Shape sh) => (ColorData sh) -> Array sh Double
123 green_dbl_data =
124 R.map (get_g . rgb_to_dbl)
125 where
126 get_g :: (Double, Double, Double) -> Double
127 get_g (_, g, _) = g
128
129
130 blue_dbl_data :: (Shape sh) => (ColorData sh) -> Array sh Double
131 blue_dbl_data =
132 R.map (get_b . rgb_to_dbl)
133 where
134 get_b :: (Double, Double, Double) -> Double
135 get_b (_, _, b) = b
136
137
138
139 z_slice :: Elt a => Int -> Array DIM3 a -> Array DIM2 a
140 z_slice n arr =
141 slice arr (Any :. n :. All :. All)
142
143
144 transpose_zx :: Elt a => Array DIM3 a -> Array DIM3 a
145 transpose_zx arr =
146 traverse arr
147 (\(Z :. zdim :. ydim :. xdim) -> (Z :. xdim :. ydim :. zdim))
148 (\_ -> (\(Z :. z :. y :. x) -> arr ! (Z :. x :. y :. z)))
149
150
151 z_slice3 :: Elt a => Int -> Array DIM3 a -> Array DIM3 a
152 z_slice3 n arr
153 | n == 0 = transpose_zx $ current R.++ next
154 | n == zdim-1 = transpose_zx $ previous R.++ current
155 | otherwise = transpose_zx $ previous R.++ current R.++ next
156 where
157 (Z :. zdim :. _ :. _) = extent arr
158 previous = transpose_zx $ reshape mri_slice3d (z_slice (n-1) arr)
159 current = transpose_zx $ reshape mri_slice3d (z_slice n arr)
160 next = transpose_zx $ reshape mri_slice3d (z_slice (n+1) arr)