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