Skip to content

Commit

Permalink
Test Trac #7797
Browse files Browse the repository at this point in the history
  • Loading branch information
Simon Peyton Jones committed May 30, 2013
1 parent d401d27 commit 442cc21
Show file tree
Hide file tree
Showing 4 changed files with 41 additions and 0 deletions.
15 changes: 15 additions & 0 deletions tests/perf/should_run/T7797.hs
@@ -0,0 +1,15 @@
{-# LANGUAGE ExistentialQuantification #-}
module Main where

import T7797a

data Box = forall a. (Size a) => Box a a

box = Box (go 10000000) (go 10000000) where
go :: Int -> [Int]
go 0 = []
go n = 1 : go (n - 1)
{-# NOINLINE box #-}

main = print $ case box of
Box l r -> size l r
1 change: 1 addition & 0 deletions tests/perf/should_run/T7797.stdout
@@ -0,0 +1 @@
0
12 changes: 12 additions & 0 deletions tests/perf/should_run/T7797a.hs
@@ -0,0 +1,12 @@
module T7797a where

class Size t where
size :: t -> t -> Int
burg :: t -> t

instance (Ord a, Num a) => Size [a] where
{-# SPECIALISE instance Size [Int] #-}
size (x:xs) (y:ys) | x+y > 4 = size xs ys
| otherwise = size xs ys
size _ _ = 0
burg = error "urk"
13 changes: 13 additions & 0 deletions tests/perf/should_run/all.T
Expand Up @@ -261,3 +261,16 @@ test('T7436',
],
compile_and_run,
['-O'])

test('T7797',
[stats_num_field('bytes allocated',
[(wordsize(32), 360940756, 5),
# expected value: 2685858140 (x86/OS X)
# expected: 360940756 (x86/Linux)
(wordsize(64), 480050944, 5)]),
# expected: 480050944 (amd64/Linux)
only_ways(['normal'])
],
compile_and_run,
['-O'])

0 comments on commit 442cc21

Please sign in to comment.