Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/8d2c20d78e1bd78ed9fb22633f0191fb05956632

>---------------------------------------------------------------

commit 8d2c20d78e1bd78ed9fb22633f0191fb05956632
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Wed Jan 2 16:48:47 2013 +0000

    Test Trac #7360

>---------------------------------------------------------------

 tests/simplCore/should_compile/T7360.hs     |   16 +++++++++
 tests/simplCore/should_compile/T7360.stderr |   47 +++++++++++++++++++++++++++
 tests/simplCore/should_compile/all.T        |    2 +-
 3 files changed, 64 insertions(+), 1 deletions(-)

diff --git a/tests/simplCore/should_compile/T7360.hs 
b/tests/simplCore/should_compile/T7360.hs
new file mode 100644
index 0000000..b877da6
--- /dev/null
+++ b/tests/simplCore/should_compile/T7360.hs
@@ -0,0 +1,16 @@
+-- Both these functions should successfully simplify
+-- using the combine-identical-alterantives optimisation
+
+module T7360 where
+
+data Foo = Foo1 | Foo2 | Foo3 !Int
+    
+fun1 :: Foo -> ()
+fun1 x = case x of
+               Foo1 -> ()
+               Foo2 -> ()
+               Foo3 {} -> ()
+
+fun2 x = case x of
+          [] -> length x
+          (_:_) -> length x
diff --git a/tests/simplCore/should_compile/T7360.stderr 
b/tests/simplCore/should_compile/T7360.stderr
new file mode 100644
index 0000000..5cc46cb
--- /dev/null
+++ b/tests/simplCore/should_compile/T7360.stderr
@@ -0,0 +1,47 @@
+
+==================== Tidy Core ====================
+Result size of Tidy Core = {terms: 20, types: 17, coercions: 0}
+
+T7360.$WFoo3 [InlPrag=INLINE] :: GHC.Types.Int -> T7360.Foo
+[GblId[DataConWrapper],
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType S,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
+         ConLike=True, WorkFree=True, Expandable=True,
+         Guidance=ALWAYS_IF(unsat_ok=False,boring_ok=False)
+         Tmpl= \ (dt [Occ=Once] :: GHC.Types.Int) ->
+                 case dt of dt { __DEFAULT -> T7360.Foo3 dt }}]
+T7360.$WFoo3 =
+  \ (dt [Occ=Once] :: GHC.Types.Int) ->
+    case dt of dt { __DEFAULT -> T7360.Foo3 dt }
+
+T7360.fun1 :: T7360.Foo -> ()
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType S,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=1, Value=True,
+         ConLike=True, WorkFree=True, Expandable=True,
+         Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=True)}]
+T7360.fun1 =
+  \ (x :: T7360.Foo) -> case x of _ { __DEFAULT -> GHC.Tuple.() }
+
+T7360.fun2 :: forall a. [a] -> GHC.Types.Int
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType Sm,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
+         ConLike=True, WorkFree=True, Expandable=True,
+         Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
+         Tmpl= \ (@ a) (x [Occ=Once] :: [a]) ->
+                 case GHC.List.$wlen @ a x 0 of ww { __DEFAULT ->
+                 GHC.Types.I# ww
+                 }}]
+T7360.fun2 =
+  \ (@ a) (x :: [a]) ->
+    case GHC.List.$wlen @ a x 0 of ww { __DEFAULT -> GHC.Types.I# ww }
+
+
+
diff --git a/tests/simplCore/should_compile/all.T 
b/tests/simplCore/should_compile/all.T
index 7c7138d..b25e25b 100644
--- a/tests/simplCore/should_compile/all.T
+++ b/tests/simplCore/should_compile/all.T
@@ -155,4 +155,4 @@ test('T7165',
      run_command,
      ['$MAKE -s --no-print-directory T7165'])
 test('T7287', normal, compile, [''])
-
+test('T7360', only_ways(['optasm']), compile, ['-ddump-simpl 
-dsuppress-uniques'])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to