Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
cffcc441
Commit
cffcc441
authored
Jan 17, 2012
by
Simon Peyton Jones
Browse files
Test Trac #5776
parent
cb0f98d0
Changes
4
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/simplCore/should_compile/Makefile
View file @
cffcc441
...
...
@@ -12,6 +12,10 @@ T5658b:
'
$(TEST_HC)
'
$(TEST_HC_OPTS)
-O
-c
T5658b.hs
-ddump-simpl
|
grep
--count
indexIntArray
# Trac 5658 meant that there were three calls to indexIntArray instead of two
T5776
:
$(RM)
-f
T5776.o T5776.hi
'
$(TEST_HC)
'
$(TEST_HC_OPTS)
-O
-c
T5776.hs
-ddump-rules
|
grep
--count
dEq
T3772
:
$(RM)
-f
T3772
*
.hi T3772
*
.o
'
$(TEST_HC)
'
$(TEST_HC_OPTS)
-c
-O
T3772_A.hs
...
...
testsuite/tests/simplCore/should_compile/T5776.hs
0 → 100644
View file @
cffcc441
module
T5776
where
-- The point about this test is that we should get a rule like this:
-- "foo" [ALWAYS]
-- forall (@ a)
-- ($dEq :: GHC.Classes.Eq a)
-- ($dEq1 :: GHC.Classes.Eq a)
-- (x :: a)
-- (y :: a)
-- (z :: a).
-- T5776.f (GHC.Classes.== @ a $dEq1 x y)
-- (GHC.Classes.== @ a $dEq y z)
-- = GHC.Types.True
--
-- Note the *two* forall'd dEq parameters. This is important.
-- See Note [Simplifying RULE lhs constraints] in TcSimplify
{-# RULES "foo" forall x y z.
f (x == y) (y == z) = True
#-}
f
::
Bool
->
Bool
->
Bool
{-# NOINLINE f #-}
f
a
b
=
False
blah
::
Int
->
Int
->
Bool
blah
x
y
=
f
(
x
==
y
)
(
x
==
y
)
testsuite/tests/simplCore/should_compile/T5776.stdout
0 → 100644
View file @
cffcc441
4
testsuite/tests/simplCore/should_compile/all.T
View file @
cffcc441
...
...
@@ -138,3 +138,7 @@ test('T5658b',
normal
,
run_command
,
['
$MAKE -s --no-print-directory T5658b
'])
test
('
T5776
',
normal
,
run_command
,
['
$MAKE -s --no-print-directory T5776
'])
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment