include an elapsed time table
[ghc-hetmet.git] / utils / nofib-analyse / Slurp.hs
1 -----------------------------------------------------------------------------
2 --
3 -- (c) Simon Marlow 1997-2005
4 --
5 -----------------------------------------------------------------------------
6
7 module Slurp (Status(..), Results(..), ResultTable, parse_log) where
8
9 import Control.Monad
10 import qualified Data.Map as Map
11 import Data.Map (Map)
12 import Text.Regex
13 import Data.Maybe
14 -- import Debug.Trace
15
16 -----------------------------------------------------------------------------
17 -- This is the structure into which we collect our results:
18
19 type ResultTable = Map String Results
20
21 data Status
22         = NotDone
23         | Success
24         | OutOfHeap
25         | OutOfStack
26         | Exit Int
27         | WrongStdout
28         | WrongStderr
29
30 data Results = Results {
31         compile_time    :: Map String Float,
32         module_size     :: Map String Int,
33         binary_size     :: Maybe Int,
34         link_time       :: Maybe Float,
35         run_time        :: [Float],
36         elapsed_time    :: [Float],
37         mut_time        :: [Float],
38         mut_elapsed_time :: [Float],
39         instrs          :: Maybe Integer,
40         mem_reads       :: Maybe Integer,
41         mem_writes      :: Maybe Integer,
42         cache_misses    :: Maybe Integer,
43         gc_work         :: Maybe Integer,
44         gc_time         :: [Float],
45         gc_elapsed_time :: [Float],
46         gc0_time         :: [Float],
47         gc0_elapsed_time :: [Float],
48         gc1_time         :: [Float],
49         gc1_elapsed_time :: [Float],
50         balance         :: [Float],
51         allocs          :: Maybe Integer,
52         run_status      :: Status,
53         compile_status  :: Status
54         }
55
56 emptyResults :: Results
57 emptyResults = Results {
58         compile_time    = Map.empty,
59         module_size     = Map.empty,
60         binary_size     = Nothing,
61         link_time       = Nothing,
62         run_time        = [],
63         elapsed_time    = [],
64         mut_time        = [],
65         mut_elapsed_time = [],
66         instrs          = Nothing,
67         mem_reads       = Nothing,
68         mem_writes      = Nothing,
69         cache_misses    = Nothing,
70         gc_time         = [],
71         gc_elapsed_time = [],
72         gc0_time         = [],
73         gc0_elapsed_time = [],
74         gc1_time         = [],
75         gc1_elapsed_time = [],
76         balance         = [],
77         gc_work         = Nothing,
78         allocs          = Nothing,
79         compile_status  = NotDone,
80         run_status      = NotDone
81         }
82
83 -----------------------------------------------------------------------------
84 -- Parse the log file
85
86 {-
87 Various banner lines:
88
89 ==nofib== awards: size of QSort.o follows...
90 ==nofib== banner: size of banner follows...
91 ==nofib== awards: time to link awards follows...
92 ==nofib== awards: time to run awards follows...
93 ==nofib== boyer2: time to compile Checker follows...
94 -}
95
96 -- NB. the hyphen must come last (or first) inside [...] to stand for itself.
97 banner_re :: Regex
98 banner_re = mkRegex "^==nofib==[ \t]+([A-Za-z0-9_-]+):[ \t]+(size of|time to link|time to run|time to compile|time to compile & run)[ \t]+([A-Za-z0-9_-]+)(\\.o)?[ \t]+follows"
99
100 {-
101 This regexp for the output of "time" works on FreeBSD, other versions
102 of "time" will need different regexps.
103 -}
104
105 time_re :: String -> Maybe (Float, Float, Float)
106 time_re s = case matchRegex re s of
107                 Just [real, user, system] ->
108                     Just (read real, read user, read system)
109                 Just _ -> error "time_re: Can't happen"
110                 Nothing -> Nothing
111     where re = mkRegex "^[ \t]*([0-9.]+)[ \t]+real[ \t]+([0-9.]+)[ \t]+user[ \t]+([0-9.]+)[ \t]+sys[ \t]*$"
112
113 time_gnu17_re :: String -> Maybe (Float, Float, String)
114 time_gnu17_re s = case matchRegex re s of
115                       Just [user, system, elapsed] ->
116                           Just (read user, read system, elapsed)
117                       Just _ -> error "time_gnu17_re: Can't happen"
118                       Nothing -> Nothing
119     where re = mkRegex "^[ \t]*([0-9.]+)user[ \t]+([0-9.]+)system[ \t]+([0-9.:]+)elapsed"
120           -- /usr/bin/time --version reports: GNU time 1.7
121           -- notice the order is different, and the elapsed time
122           -- is [hh:]mm:ss.s
123
124 size_re :: String -> Maybe (Int, Int, Int)
125 size_re s = case matchRegex re s of
126                 Just [text, datas, bss] ->
127                     Just (read text, read datas, read bss)
128                 Just _ -> error "size_re: Can't happen"
129                 Nothing -> Nothing
130     where re = mkRegex "^[ \t]*([0-9]+)[ \t]+([0-9]+)[ \t]+([0-9]+)"
131
132 {-
133 <<ghc: 5820820 bytes, 0 GCs, 0/0 avg/max bytes residency (0 samples), 41087234 bytes GC work, 0.00 INIT (0.05 elapsed), 0.08 MUT (0.18 elapsed), 0.00 GC (0.00 elapsed) :ghc>>
134
135         = (bytes, gcs, avg_resid, max_resid, samples, gc_work,
136            init, init_elapsed, mut, mut_elapsed, gc, gc_elapsed)
137
138 ghc1_re = pre GHC 4.02
139 ghc2_re = GHC 4.02 (includes "xxM in use")
140 ghc3_re = GHC 4.03 (includes "xxxx bytes GC work")
141 ghc5_re = GHC 6.9 (includes GC(0) and GC(1) times)
142 -}
143
144 ghc1_re :: String -> Maybe (Integer, Integer, Integer, Integer, Integer, Integer, Float, Float, Float, Float, Float, Float)
145 ghc1_re s = case matchRegex re s of
146                 Just [allocations, gcs, avg_residency, max_residency, samples, gc_work', initialisation, initialisation_elapsed, mut, mut_elapsed, gc, gc_elapsed] ->
147                     Just (read allocations, read gcs, read avg_residency, read max_residency, read samples, read gc_work', read initialisation, read initialisation_elapsed, read mut, read mut_elapsed, read gc, read gc_elapsed)
148                 Just _ -> error "ghc1_re: Can't happen"
149                 Nothing -> Nothing
150     where re = mkRegex "^<<ghc:[ \t]+([0-9]+)[ \t]+bytes,[ \t]*([0-9]+)[ \t]+GCs,[ \t]*([0-9]+)/([0-9]+)[ \t]+avg/max bytes residency \\(([0-9]+) samples\\), ([0-9]+) bytes GC work, ([0-9.]+) INIT \\(([0-9.]+) elapsed\\), ([0-9.]+) MUT \\(([0-9.]+) elapsed\\), ([0-9.]+) GC \\(([0-9.]+) elapsed\\) :ghc>>"
151
152 ghc2_re :: String -> Maybe (Integer, Integer, Integer, Integer, Integer, Integer, Float, Float, Float, Float, Float, Float)
153 ghc2_re s = case matchRegex re s of
154                 Just [allocations, gcs, avg_residency, max_residency, samples, in_use, initialisation, initialisation_elapsed, mut, mut_elapsed, gc, gc_elapsed] ->
155                     Just (read allocations, read gcs, read avg_residency, read max_residency, read samples, read in_use, read initialisation, read initialisation_elapsed, read mut, read mut_elapsed, read gc, read gc_elapsed)
156                 Just _ -> error "ghc2_re: Can't happen"
157                 Nothing -> Nothing
158     where re = mkRegex "^<<ghc:[ \t]+([0-9]+)[ \t]+bytes,[ \t]*([0-9]+)[ \t]+GCs,[ \t]*([0-9]+)/([0-9]+)[ \t]+avg/max bytes residency \\(([0-9]+) samples\\), ([0-9]+)M in use, ([0-9.]+) INIT \\(([0-9.]+) elapsed\\), ([0-9.]+) MUT \\(([0-9.]+) elapsed\\), ([0-9.]+) GC \\(([0-9.]+) elapsed\\) :ghc>>"
159
160 ghc3_re :: String -> Maybe (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Float, Float, Float, Float, Float, Float)
161 ghc3_re s = case matchRegex re s of
162                 Just [allocations, gcs, avg_residency, max_residency, samples, gc_work', in_use, initialisation, initialisation_elapsed, mut, mut_elapsed, gc, gc_elapsed] ->
163                     Just (read allocations, read gcs, read avg_residency, read max_residency, read samples, read gc_work', read in_use, read initialisation, read initialisation_elapsed, read mut, read mut_elapsed, read gc, read gc_elapsed)
164                 Just _ -> error "ghc3_re: Can't happen"
165                 Nothing -> Nothing
166     where re = mkRegex "^<<ghc:[ \t]+([0-9]+)[ \t]+bytes,[ \t]*([0-9]+)[ \t]+GCs,[ \t]*([0-9]+)/([0-9]+)[ \t]+avg/max bytes residency \\(([0-9]+) samples\\), ([0-9]+) bytes GC work, ([0-9]+)M in use, ([0-9.]+) INIT \\(([0-9.]+) elapsed\\), ([0-9.]+) MUT \\(([0-9.]+) elapsed\\), ([0-9.]+) GC \\(([0-9.]+) elapsed\\) :ghc>>"
167
168 ghc4_re :: String -> Maybe (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Float, Float, Float, Float, Float, Float, Integer, Integer, Integer, Integer)
169 ghc4_re s = case matchRegex re s of
170                 Just [allocations, gcs, avg_residency, max_residency, samples, gc_work', in_use, initialisation, initialisation_elapsed, mut, mut_elapsed, gc, gc_elapsed, instructions, memory_reads, memory_writes, l2_cache_misses] ->
171                     Just (read allocations, read gcs, read avg_residency, read max_residency, read samples, read gc_work', read in_use, read initialisation, read initialisation_elapsed, read mut, read mut_elapsed, read gc, read gc_elapsed, read instructions, read memory_reads, read memory_writes, read l2_cache_misses)
172                 Just _ -> error "ghc4_re: Can't happen"
173                 Nothing -> Nothing
174     where re = mkRegex "^<<ghc-instrs:[ \t]+([0-9]+)[ \t]+bytes,[ \t]*([0-9]+)[ \t]+GCs,[ \t]*([0-9]+)/([0-9]+)[ \t]+avg/max bytes residency \\(([0-9]+) samples\\), ([0-9]+) bytes GC work, ([0-9]+)M in use, ([0-9.]+) INIT \\(([0-9.]+) elapsed\\), ([0-9.]+) MUT \\(([0-9.]+) elapsed\\), ([0-9.]+) GC \\(([0-9.]+) elapsed\\), ([0-9]+) instructions, ([0-9]+) memory reads, ([0-9]+) memory writes, ([0-9]+) L2 cache misses :ghc-instrs>>"
175
176 ghc5_re :: String -> Maybe (Integer, Integer, Integer, Integer, Integer, Integer, Integer, Float, Float, Float, Float, Float, Float,Float,Float,Float,Float,Float)
177 ghc5_re s = case matchRegex re s of
178                 Just [allocations, gcs, avg_residency, max_residency, samples, gc_work', in_use, initialisation, initialisation_elapsed, mut, mut_elapsed, gc, gc_elapsed, gc0, gc0_elapsed, gc1, gc1_elapsed, bal] ->
179                     Just (read allocations, read gcs, read avg_residency, read max_residency, read samples, read gc_work', read in_use, read initialisation, read initialisation_elapsed, read mut, read mut_elapsed, read gc, read gc_elapsed, read gc0, read gc0_elapsed, read gc1, read gc1_elapsed, read bal)
180                 Just _ -> error "ghc3_re: Can't happen"
181                 Nothing -> Nothing
182     where re = mkRegex "^<<ghc:[ \t]+([0-9]+)[ \t]+bytes,[ \t]*([0-9]+)[ \t]+GCs,[ \t]*([0-9]+)/([0-9]+)[ \t]+avg/max bytes residency \\(([0-9]+) samples\\), ([0-9]+) bytes GC work, ([0-9]+)M in use, ([0-9.]+) INIT \\(([0-9.]+) elapsed\\), ([0-9.]+) MUT \\(([0-9.]+) elapsed\\), ([0-9.]+) GC \\(([0-9.]+) elapsed\\), ([0-9.]+) GC\\(0\\) \\(([0-9.]+) elapsed\\), ([0-9.]+) GC\\(1\\) \\(([0-9.]+) elapsed\\), ([0-9.]+) balance :ghc>>"
183
184 wrong_exit_status, wrong_output, out_of_heap, out_of_stack :: Regex
185 wrong_exit_status = mkRegex "^\\**[ \t]*expected exit status ([0-9]+) not seen ; got ([0-9]+)"
186 wrong_output      = mkRegex "^expected (stdout|stderr) not matched by reality$"
187 out_of_heap       = mkRegex "^\\+ Heap exhausted;$"
188 out_of_stack      = mkRegex "^\\+ Stack space overflow:"
189
190 parse_log :: String -> ResultTable
191 parse_log
192         = combine_results               -- collate information
193         . concat
194         . map process_chunk             -- get information from each chunk
195         . tail                          -- first chunk is junk
196         . chunk_log [] []               -- break at banner lines
197         . lines
198
199 combine_results :: [(String,Results)] -> Map String Results
200 combine_results = foldr f Map.empty
201  where
202         f (prog,results) fm = Map.insertWith (flip combine2Results) prog results fm
203
204 combine2Results :: Results -> Results -> Results
205 combine2Results
206              Results{ compile_time = ct1, link_time = lt1,
207                       module_size = ms1,
208                       run_time = rt1, elapsed_time = et1, mut_time = mt1,
209                       mut_elapsed_time = me1,
210                       instrs = is1, mem_reads = mr1, mem_writes = mw1,
211                       cache_misses = cm1,
212                       gc_time = gt1, gc_elapsed_time = ge1, gc_work = gw1,
213                       gc0_time = g0t1, gc0_elapsed_time = g0e1, 
214                       gc1_time = g1t1, gc1_elapsed_time = g1e1, 
215                       balance = b1,
216                       binary_size = bs1, allocs = al1,
217                       run_status = rs1, compile_status = cs1 }
218              Results{ compile_time = ct2, link_time = lt2,
219                       module_size = ms2,
220                       run_time = rt2, elapsed_time = et2, mut_time = mt2,
221                       mut_elapsed_time = me2,
222                       instrs = is2, mem_reads = mr2, mem_writes = mw2,
223                       cache_misses = cm2,
224                       gc_time = gt2, gc_elapsed_time = ge2, gc_work = gw2,
225                       gc0_time = g0t2, gc0_elapsed_time = g0e2, 
226                       gc1_time = g1t2, gc1_elapsed_time = g1e2, 
227                       balance = b2,
228                       binary_size = bs2, allocs = al2,
229                       run_status = rs2, compile_status = cs2 }
230           =  Results{ compile_time   = Map.unionWith (flip const) ct1 ct2,
231                       module_size    = Map.unionWith (flip const) ms1 ms2,
232                       link_time      = lt1 `mplus` lt2,
233                       run_time       = rt1 ++ rt2,
234                       elapsed_time   = et1 ++ et2, 
235                       mut_time       = mt1 ++ mt2,
236                       mut_elapsed_time = me1 ++ me2,
237                       instrs         = is1 `mplus` is2,
238                       mem_reads      = mr1 `mplus` mr2,
239                       mem_writes     = mw1 `mplus` mw2,
240                       cache_misses   = cm1 `mplus` cm2,
241                       gc_time        = gt1 ++ gt2,
242                       gc_elapsed_time= ge1 ++ ge2,
243                       gc0_time        = g0t1 ++ g0t2,
244                       gc0_elapsed_time= g0e1 ++ g0e2,
245                       gc1_time        = g1t1 ++ g1t2,
246                       gc1_elapsed_time= g1e1 ++ g1e2,
247                       balance        = b1 ++ b2,
248                       gc_work        = gw1 `mplus` gw2,
249                       binary_size    = bs1 `mplus` bs2,
250                       allocs         = al1 `mplus` al2,
251                       run_status     = combStatus rs1 rs2,
252                       compile_status = combStatus cs1 cs2 }
253
254 combStatus :: Status -> Status -> Status
255 combStatus NotDone y       = y
256 combStatus x       NotDone = x
257 combStatus x       _       = x
258
259 chunk_log :: [String] -> [String] -> [String] -> [([String],[String])]
260 chunk_log header chunk [] = [(header,chunk)]
261 chunk_log header chunk (l:ls) =
262         case matchRegex banner_re l of
263                 Nothing -> chunk_log header (l:chunk) ls
264                 Just stuff -> (header,chunk) : chunk_log stuff [] ls
265
266 process_chunk :: ([String],[String]) -> [(String,Results)]
267 process_chunk (progName : what : modName : _, chk) =
268  case what of
269         "time to compile" -> parse_compile_time progName modName chk
270         "time to run"     -> parse_run_time progName (reverse chk) emptyResults NotDone
271         "time to compile & run" -> parse_compile_time progName modName chk
272                                 ++ parse_run_time progName (reverse chk) emptyResults NotDone
273         "time to link"    -> parse_link_time progName chk
274         "size of"         -> parse_size progName modName chk
275         _                 -> error ("process_chunk: "++what)
276 process_chunk _ = error "process_chunk: Can't happen"
277
278 parse_compile_time :: String -> String -> [String] -> [(String, Results)]
279 parse_compile_time _    _   [] = []
280 parse_compile_time progName modName (l:ls) =
281         case time_re l of {
282              Just (_real, user, _system) ->
283                 let ct  = Map.singleton modName user
284                 in
285                 [(progName, emptyResults{compile_time = ct})];
286              Nothing ->
287
288         case time_gnu17_re l of {
289              Just (user, _system, _elapsed) ->
290                 let ct  = Map.singleton modName user
291                 in
292                 [(progName, emptyResults{compile_time = ct})];
293              Nothing ->
294
295         case ghc1_re l of {
296             Just (_, _, _, _, _, _, initialisation, _, mut, _, gc, _) ->
297               let
298                   time = (initialisation + mut + gc) :: Float
299                   ct  = Map.singleton modName time
300               in
301                 [(progName, emptyResults{compile_time = ct})];
302             Nothing ->
303
304         case ghc2_re l of {
305            Just (_, _, _, _, _, _, initialisation, _, mut, _, gc, _) ->
306               let ct = Map.singleton modName (initialisation + mut + gc)
307               in
308                 [(progName, emptyResults{compile_time = ct})];
309             Nothing ->
310
311         case ghc3_re l of {
312            Just (_, _, _, _, _, _, _, initialisation, _, mut, _, gc, _) ->
313               let ct = Map.singleton modName (initialisation + mut + gc)
314               in
315                 [(progName, emptyResults{compile_time = ct})];
316             Nothing ->
317
318         case ghc4_re l of {
319            Just (_, _, _, _, _, _, _, initialisation, _, mut, _, gc, _, _, _, _, _) ->
320               let ct = Map.singleton modName (initialisation + mut + gc)
321               in
322                 [(progName, emptyResults{compile_time = ct})];
323             Nothing ->
324
325                 parse_compile_time progName modName ls
326         }}}}}}
327
328 parse_link_time :: String -> [String] -> [(String, Results)]
329 parse_link_time _ [] = []
330 parse_link_time prog (l:ls) =
331           case time_re l of {
332              Just (_real, user, _system) ->
333                 [(prog,emptyResults{link_time = Just user})];
334              Nothing ->
335
336           case time_gnu17_re l of {
337              Just (user, _system, _elapsed) ->
338                 [(prog,emptyResults{link_time = Just user})];
339              Nothing ->
340
341           parse_link_time prog ls
342           }}
343
344
345 -- There might be multiple runs of the program, so we have to collect up
346 -- all the results.  Variable results like runtimes are aggregated into
347 -- a list, whereas the non-variable aspects are just kept singly.
348 parse_run_time :: String -> [String] -> Results -> Status
349                -> [(String, Results)]
350 parse_run_time _ [] _ NotDone = []
351 parse_run_time prog [] res ex = [(prog, res{run_status=ex})]
352 parse_run_time prog (l:ls) res ex =
353         case ghc1_re l of {
354            Just (allocations, _, _, _, _, _, initialisation, init_elapsed, mut, mut_elapsed, gc, gc_elapsed) ->
355                 got_run_result allocations initialisation init_elapsed mut mut_elapsed gc gc_elapsed [] [] [] [] []
356                         Nothing Nothing Nothing Nothing Nothing;
357            Nothing ->
358
359         case ghc2_re l of {
360            Just (allocations, _, _, _, _, _, initialisation, init_elapsed, mut, mut_elapsed, gc, gc_elapsed) ->
361                 got_run_result allocations initialisation init_elapsed mut mut_elapsed gc gc_elapsed [] [] [] [] []
362                         Nothing Nothing Nothing Nothing Nothing;
363
364             Nothing ->
365
366         case ghc3_re l of {
367            Just (allocations, _, _, _, _, gc_work', _, initialisation, init_elapsed, mut, mut_elapsed, gc, gc_elapsed) ->
368                 got_run_result allocations initialisation init_elapsed mut mut_elapsed gc gc_elapsed [] [] [] [] []
369                         (Just gc_work') Nothing Nothing Nothing Nothing;
370
371             Nothing ->
372
373         case ghc4_re l of {
374            Just (allocations, _, _, _, _, gc_work', _, initialisation, init_elapsed, mut, mut_elapsed, gc, gc_elapsed, is, mem_rs, mem_ws, cache_misses') ->
375                 got_run_result allocations initialisation init_elapsed mut mut_elapsed gc gc_elapsed [] [] [] [] []
376                         (Just gc_work') (Just is) (Just mem_rs)
377                         (Just mem_ws) (Just cache_misses');
378
379             Nothing ->
380
381         case ghc5_re l of {
382            Just (allocations, _, _, _, _, gc_work', _, initialisation, init_elapsed, mut, mut_elapsed, gc, gc_elapsed, gc0, gc0_elapsed, gc1, gc1_elapsed, bal) ->
383                 got_run_result allocations initialisation init_elapsed mut mut_elapsed gc gc_elapsed
384                         [gc0] [gc0_elapsed] [gc1] [gc1_elapsed] [bal]
385                         (Just gc_work') Nothing Nothing Nothing Nothing;
386
387             Nothing ->
388
389         case matchRegex wrong_output l of {
390             Just ["stdout"] ->
391                 parse_run_time prog ls res (combineRunResult WrongStdout ex);
392             Just ["stderr"] ->
393                 parse_run_time prog ls res (combineRunResult WrongStderr ex);
394             Just _ -> error "wrong_output: Can't happen";
395             Nothing ->
396
397         case matchRegex wrong_exit_status l of {
398             Just [_wanted, got] ->
399                 parse_run_time prog ls res (combineRunResult (Exit (read got)) ex);
400             Just _ -> error "wrong_exit_status: Can't happen";
401             Nothing ->
402
403         case matchRegex out_of_heap l of {
404             Just _ ->
405                 parse_run_time prog ls res (combineRunResult OutOfHeap ex);
406             Nothing ->
407
408         case matchRegex out_of_stack l of {
409             Just _ ->
410                 parse_run_time prog ls res (combineRunResult OutOfStack ex);
411             Nothing ->
412                 parse_run_time prog ls res ex;
413
414         }}}}}}}}}
415   where
416   got_run_result allocations initialisation init_elapsed mut mut_elapsed gc gc_elapsed gc0 gc0_elapsed gc1 gc1_elapsed bal gc_work' instrs' mem_rs mem_ws cache_misses'
417       = -- trace ("got_run_result: " ++ initialisation ++ ", " ++ mut ++ ", " ++ gc) $
418         let
419           time = initialisation + mut + gc
420           etime = init_elapsed + mut_elapsed + gc_elapsed
421           res' = combine2Results res
422                         emptyResults{   run_time   = [time],
423                                         elapsed_time = [etime],
424                                         mut_time   = [mut],
425                                         mut_elapsed_time   = [mut_elapsed],
426                                         gc_time    = [gc],
427                                         gc_elapsed_time = [gc_elapsed],
428                                         gc0_time    = gc0,
429                                         gc0_elapsed_time = gc0_elapsed,
430                                         gc1_time    = gc1,
431                                         gc1_elapsed_time = gc1_elapsed,
432                                         balance    = bal,
433                                         gc_work    = gc_work',
434                                         allocs     = Just allocations,
435                                         instrs     = instrs',
436                                         mem_reads  = mem_rs,
437                                         mem_writes = mem_ws,
438                                         cache_misses = cache_misses',
439                                         run_status = Success
440                                 }
441         in
442         parse_run_time prog ls res' Success
443
444 combineRunResult :: Status -> Status -> Status
445 combineRunResult OutOfHeap  _           = OutOfHeap
446 combineRunResult _          OutOfHeap   = OutOfHeap
447 combineRunResult OutOfStack _           = OutOfStack
448 combineRunResult _          OutOfStack  = OutOfStack
449 combineRunResult (Exit e)   _           = Exit e
450 combineRunResult _          (Exit e)    = Exit e
451 combineRunResult exit       _            = exit
452
453 parse_size :: String -> String -> [String] -> [(String, Results)]
454 parse_size _ _ [] = []
455 parse_size progName modName (l:ls) =
456         case size_re l of
457             Nothing -> parse_size progName modName ls
458             Just (text, datas, _bss)
459                  | progName == modName ->
460                         [(progName,emptyResults{binary_size = 
461                                              Just (text + datas),
462                                     compile_status = Success})]
463                  | otherwise ->
464                         let ms  = Map.singleton modName (text + datas)
465                         in
466                         [(progName,emptyResults{module_size = ms})]
467