-
Notifications
You must be signed in to change notification settings - Fork 0
/
AstroData.hs
157 lines (135 loc) · 4.78 KB
/
AstroData.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
{-# LANGUAGE BangPatterns #-}
{- Interface to datasets from the IEEE Visualization contest 2008.
This file implements a set of interfaces for reading, accessing
and manipulating these data.
-}
module AstroData where
import Control.Parallel.Strategies
import Data.Array.Repa hiding ( (++), map )
import Data.Array.Repa.IO.Binary
import Data.Array.Repa.Repr.ForeignPtr
import Data.Char
import Prelude hiding (lookup)
import qualified Data.ByteString as BS
import System.IO
import Text.ParserCombinators.Poly
import Dataset
-- Dataset definitions ------------------------------------------------------
data Species = D | G | H | Hp | He | Hep | Hepp | Hm | H2 | H2p
| R | S | H2xD | Cx | Cy | Cz | Mv
deriving (Eq,Ord)
instance Show Species where
show D = "D"
show G = "G"
show H = "H"
show Hp = "H+"
show He = "He"
show Hep = "He+"
show Hepp = "He++"
show Hm = "H-"
show H2 = "H2"
show H2p = "H2+"
show R = "R"
show S = "S"
show H2xD = "H2xD"
show Cx = "Cx"
show Cy = "Cy"
show Cz = "Cz"
show Mv = "Mv"
type Time = Int
data VisData = VisData { xsampling :: Sampling Int
, ysampling :: Sampling Int
, zsampling :: Sampling Int
, time :: Int
, field :: Species
} deriving Eq
instance Show VisData where
show a = concat [ "x", (show $ xsampling a)
, "y", (show $ ysampling a)
, "z", (show $ zsampling a)
, "t", (show $ time a)
, ".", (show $ field a)
]
instance Dataset VisData where
readData = readAstroData
astroFull :: Time -> Species -> VisData
astroFull t s = VisData (Range 0 599) (Range 0 247) (Range 0 247) t s
astroFour :: Time -> Species -> VisData
astroFour t s = VisData (Sampled 0 4 599) (Sampled 0 4 247) (Sampled 0 4 247) t s
sliceZ :: Int -> VisData -> VisData
sliceZ z (VisData x y _ t s) = (VisData x y (Single z) t s)
-- Parsers ------------------------------------------------------------------
species :: Parser Char Species
species = do satisfy (=='D'); return D
`onFail`
do satisfy (=='G'); return G
`onFail`
do satisfy (=='S'); return S
`onFail`
do satisfy (=='R'); return R
`onFail`
do satisfy (=='C');
(do satisfy (=='x'); return Cx
`onFail`
do satisfy (=='y'); return Cy
`onFail`
do satisfy (=='z'); return Cz)
`onFail`
do satisfy (=='M'); satisfy (=='v'); return Mv
`onFail`
do satisfy (=='H');
(do satisfy (=='-'); return Hm
`onFail`
do satisfy (=='+'); return Hp
`onFail`
do satisfy (=='2');
(do satisfy (=='+'); return H2p
`onFail`
do satisfy (=='x');
satisfy (=='D'); return H2xD
`onFail`
return H2)
`onFail`
do satisfy (=='e');
(do satisfy (=='+')
(do satisfy (=='+'); return Hepp
`onFail`
return Hep)
`onFail`
return He)
`onFail`
return H)
slice :: Parser Char VisData
slice = do satisfy (=='x'); x <- (parseRange integer)
satisfy (=='y'); y <- (parseRange integer)
satisfy (=='z'); z <- (parseRange integer)
satisfy (=='t'); t <- integer
satisfy (=='.'); ss <- species
return $ VisData x y z t ss
parseRange :: Num a => Parser Char a -> Parser Char (Sampling a)
parseRange p = do i <- p
(do satisfy (=='-')
j <- p
(do satisfy (=='-')
k <- p
return (Sampled i (j-i) k)
`onFail`
return (Range i j))
`onFail`
return (Single i))
integer :: Parser Char Int -- positive only
integer = do cs <- many1 (satisfy isDigit)
return (foldl1 (\n d-> n*10+d)
(map digitToInt cs))
-- Low-level IO and conversion ----------------------------------------------
readAstroData :: VisData -> IO (FizzData Float)
readAstroData d = do
let name = (show d ++ ".dat")
samps = (xsampling d, ysampling d, zsampling d)
sz <- fileSize name
vs <- readArrayFromStorableFile
name
(Z :. ((fromIntegral sz) `div` 4)) :: IO (Array F DIM1 Float)
deepSeqArray vs $ return ()
let !list = toList vs `using` rseq
return $ FizzData name samps list