Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Alex D
GHC
Commits
20c9800b
Commit
20c9800b
authored
Dec 16, 2009
by
simonpj
Browse files
Test Trac #3717
parent
fb17b356
Changes
3
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/simplCore/should_compile/T3717.hs
0 → 100644
View file @
20c9800b
-- This tests whether a supurious `seq` is eliminated
-- The test output is -ddump-simpl with uniques suppressed,
-- so it may wobble a bit and require updating
module
T3717
where
foo
::
Int
->
Int
foo
0
=
0
foo
n
=
(
if
n
<
5
then
1
else
2
)
`
seq
`
foo
(
n
-
1
)
testsuite/tests/ghc-regress/simplCore/should_compile/T3717.stderr
0 → 100644
View file @
20c9800b
==================== Tidy Core ====================
lvl :: GHC.Integer.Type.Integer
[GblId, Caf=NoCafRefs, Str=DmdType]
lvl = GHC.Integer.Type.S# 1
lvl1 :: GHC.Integer.Type.Integer
[GblId, Caf=NoCafRefs, Str=DmdType]
lvl1 = GHC.Integer.Type.S# 2
Rec {
T3717.$wfoo [Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int#
[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType L]
T3717.$wfoo =
\ (ww :: GHC.Prim.Int#) ->
case ww of ds {
__DEFAULT ->
case case GHC.Prim.<# ds 5 of _ {
GHC.Bool.False -> lvl1; GHC.Bool.True -> lvl
}
of _ { __DEFAULT ->
T3717.$wfoo (GHC.Prim.-# ds 1)
};
0 -> 0
}
end Rec }
T3717.foo :: GHC.Types.Int -> GHC.Types.Int
[GblId,
Arity=1,
Caf=NoCafRefs,
Str=DmdType U(L)m,
Unf=Unf{Src=Worker=T3717.$wfoo, TopLvl=True, Arity=1, Value=True,
ConLike=True, Cheap=True, Expandable=True,
Guidance=ALWAYS_IF(sat_ok=True,boring_ok=False)
Tmpl= \ (w [Occ=Once!] :: GHC.Types.Int) ->
case w of _ { GHC.Types.I# ww [Occ=Once] ->
case T3717.$wfoo ww of ww1 { __DEFAULT -> GHC.Types.I# ww1 }
}}]
T3717.foo =
\ (w :: GHC.Types.Int) ->
case w of _ { GHC.Types.I# ww ->
case T3717.$wfoo ww of ww1 { __DEFAULT -> GHC.Types.I# ww1 }
}
testsuite/tests/ghc-regress/simplCore/should_compile/all.T
View file @
20c9800b
...
...
@@ -59,3 +59,8 @@ test('T3234',
compile
,
['
-ddump-simpl-stats -dsuppress-uniques -fno-code
'])
test
('
T3717
',
only_ways
(['
optc
','
optasm
']),
compile
,
['
-ddump-simpl -dsuppress-uniques -fno-code
'])
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new 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