[Git][ghc/ghc][wip/T18078] Move around new regression tests

Sebastian Graf gitlab at gitlab.haskell.org
Tue May 26 20:29:48 UTC 2020



Sebastian Graf pushed to branch wip/T18078 at Glasgow Haskell Compiler / GHC


Commits:
fe99560e by Sebastian Graf at 2020-05-26T22:29:41+02:00
Move around new regression tests

- - - - -


9 changed files:

- testsuite/tests/stranal/should_compile/T17673.hs → testsuite/tests/simplCore/should_compile/T17673.hs
- + testsuite/tests/simplCore/should_compile/T17673.stderr
- testsuite/tests/stranal/should_compile/T18078.hs → testsuite/tests/simplCore/should_compile/T18078.hs
- + testsuite/tests/simplCore/should_compile/T18078.stderr
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/stranal/should_compile/Makefile
- − testsuite/tests/stranal/should_compile/T17673.stdout
- − testsuite/tests/stranal/should_compile/T18078.stdout
- testsuite/tests/stranal/should_compile/all.T


Changes:

=====================================
testsuite/tests/stranal/should_compile/T17673.hs → testsuite/tests/simplCore/should_compile/T17673.hs
=====================================


=====================================
testsuite/tests/simplCore/should_compile/T17673.stderr
=====================================
@@ -0,0 +1,66 @@
+
+==================== Tidy Core ====================
+Result size of Tidy Core = {terms: 56, types: 67, coercions: 5, joins: 0/0}
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T17673.$trModule4 :: GHC.Prim.Addr#
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+T17673.$trModule4 = "main"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T17673.$trModule3 :: GHC.Types.TrName
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T17673.$trModule3 = GHC.Types.TrNameS T17673.$trModule4
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T17673.$trModule2 :: GHC.Prim.Addr#
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
+T17673.$trModule2 = "T17673"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T17673.$trModule1 :: GHC.Types.TrName
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T17673.$trModule1 = GHC.Types.TrNameS T17673.$trModule2
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+T17673.$trModule :: GHC.Types.Module
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
+T17673.$trModule = GHC.Types.Module T17673.$trModule3 T17673.$trModule1
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+lvl :: Int
+[GblId, Unf=OtherCon []]
+lvl = GHC.Types.I# 1#
+
+Rec {
+-- RHS size: {terms: 27, types: 31, coercions: 0, joins: 0/0}
+T17673.$wfacIO [InlPrag=NOINLINE, Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #)
+[GblId, Arity=2, Str=<L,U><L,U>, Unf=OtherCon []]
+T17673.$wfacIO
+  = \ (ww :: GHC.Prim.Int#) (w :: GHC.Prim.State# GHC.Prim.RealWorld) ->
+      case GHC.Prim.<# ww 2# of {
+        __DEFAULT -> case T17673.$wfacIO (GHC.Prim.-# ww 1#) w of { (# ipv, ipv1 #) -> (# ipv, case ipv1 of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.*# ww y) } #) };
+        1# -> (# w, lvl #)
+      }
+end Rec }
+
+-- RHS size: {terms: 8, types: 5, coercions: 0, joins: 0/0}
+T17673.facIO1 [InlPrag=NOUSERINLINE[-1]] :: Int -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #)
+[GblId,
+ Arity=2,
+ Str=<S,1*U(U)><L,U>,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False)
+         Tmpl= \ (w [Occ=Once!] :: Int) (w1 [Occ=Once] :: GHC.Prim.State# GHC.Prim.RealWorld) -> case w of { GHC.Types.I# ww1 [Occ=Once] -> T17673.$wfacIO ww1 w1 }}]
+T17673.facIO1 = \ (w :: Int) (w1 :: GHC.Prim.State# GHC.Prim.RealWorld) -> case w of { GHC.Types.I# ww1 -> T17673.$wfacIO ww1 w1 }
+
+-- RHS size: {terms: 1, types: 0, coercions: 5, joins: 0/0}
+facIO [InlPrag=NOUSERINLINE[-1]] :: Int -> IO Int
+[GblId,
+ Arity=2,
+ Str=<S,1*U(U)><L,U>,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)
+         Tmpl= T17673.facIO1 `cast` (<Int>_R ->_R Sym (GHC.Types.N:IO[0] <Int>_R) :: (Int -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #)) ~R# (Int -> IO Int))}]
+facIO = T17673.facIO1 `cast` (<Int>_R ->_R Sym (GHC.Types.N:IO[0] <Int>_R) :: (Int -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #)) ~R# (Int -> IO Int))
+
+
+


=====================================
testsuite/tests/stranal/should_compile/T18078.hs → testsuite/tests/simplCore/should_compile/T18078.hs
=====================================


=====================================
testsuite/tests/simplCore/should_compile/T18078.stderr
=====================================
@@ -0,0 +1,141 @@
+
+==================== Tidy Core ====================
+Result size of Tidy Core = {terms: 98, types: 40, coercions: 5, joins: 0/0}
+
+-- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0}
+T18078.unN1 :: N -> N
+[GblId,
+ Arity=1,
+ Str=<S,1*U>,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)
+         Tmpl= \ (ds [Occ=Once] :: N) -> ds}]
+T18078.unN1 = \ (ds :: N) -> ds
+
+-- RHS size: {terms: 1, types: 0, coercions: 3, joins: 0/0}
+unN :: N -> Int -> Int
+[GblId[[RecSel]],
+ Arity=1,
+ Str=<S,1*U>,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)
+         Tmpl= T18078.unN1 `cast` (<N>_R ->_R T18078.N:N[0] :: (N -> N) ~R# (N -> Int -> Int))}]
+unN = T18078.unN1 `cast` (<N>_R ->_R T18078.N:N[0] :: (N -> N) ~R# (N -> Int -> Int))
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T18078.$trModule4 :: GHC.Prim.Addr#
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+T18078.$trModule4 = "main"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T18078.$trModule3 :: GHC.Types.TrName
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T18078.$trModule3 = GHC.Types.TrNameS T18078.$trModule4
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T18078.$trModule2 :: GHC.Prim.Addr#
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
+T18078.$trModule2 = "T18078"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T18078.$trModule1 :: GHC.Types.TrName
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T18078.$trModule1 = GHC.Types.TrNameS T18078.$trModule2
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+T18078.$trModule :: GHC.Types.Module
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
+T18078.$trModule = GHC.Types.Module T18078.$trModule3 T18078.$trModule1
+
+-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
+$krep :: GHC.Types.KindRep
+[GblId, Cpr=m1, Unf=OtherCon []]
+$krep = GHC.Types.KindRepTyConApp GHC.Types.$tcInt (GHC.Types.[] @GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep1 :: GHC.Types.KindRep
+[GblId, Cpr=m4, Unf=OtherCon []]
+$krep1 = GHC.Types.KindRepFun $krep $krep
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T18078.$tcN2 :: GHC.Prim.Addr#
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+T18078.$tcN2 = "N"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T18078.$tcN1 :: GHC.Types.TrName
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T18078.$tcN1 = GHC.Types.TrNameS T18078.$tcN2
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+T18078.$tcN :: GHC.Types.TyCon
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+T18078.$tcN = GHC.Types.TyCon 8242209344145137716## 16993518540698548720## T18078.$trModule T18078.$tcN1 0# GHC.Types.krep$*
+
+-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
+$krep2 :: GHC.Types.KindRep
+[GblId, Cpr=m1, Unf=OtherCon []]
+$krep2 = GHC.Types.KindRepTyConApp T18078.$tcN (GHC.Types.[] @GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+T18078.$tc'N1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
+[GblId, Cpr=m4, Unf=OtherCon []]
+T18078.$tc'N1 = GHC.Types.KindRepFun $krep1 $krep2
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T18078.$tc'N3 :: GHC.Prim.Addr#
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+T18078.$tc'N3 = "'N"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T18078.$tc'N2 :: GHC.Types.TrName
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T18078.$tc'N2 = GHC.Types.TrNameS T18078.$tc'N3
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+T18078.$tc'N :: GHC.Types.TyCon
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+T18078.$tc'N = GHC.Types.TyCon 15484649745433776318## 6635095266531093649## T18078.$trModule T18078.$tc'N2 0# T18078.$tc'N1
+
+Rec {
+-- RHS size: {terms: 10, types: 2, coercions: 0, joins: 0/0}
+T18078.$wf [InlPrag=NOINLINE, Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int#
+[GblId, Arity=1, Str=<S,1*U>, Unf=OtherCon []]
+T18078.$wf
+  = \ (ww :: GHC.Prim.Int#) ->
+      case ww of wild {
+        __DEFAULT -> T18078.$wf (GHC.Prim.-# wild 1#);
+        0# -> 0#
+      }
+end Rec }
+
+-- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0}
+T18078.f1 [InlPrag=NOUSERINLINE[-1]] :: Int -> Int
+[GblId,
+ Arity=1,
+ Str=<S(S),1*U(1*U)>,
+ Cpr=m1,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+         Tmpl= \ (w [Occ=Once!] :: Int) -> case w of { GHC.Types.I# ww1 [Occ=Once] -> case T18078.$wf ww1 of ww2 [Occ=Once] { __DEFAULT -> GHC.Types.I# ww2 } }}]
+T18078.f1 = \ (w :: Int) -> case w of { GHC.Types.I# ww1 -> case T18078.$wf ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 } }
+
+-- RHS size: {terms: 1, types: 0, coercions: 2, joins: 0/0}
+f [InlPrag=NOUSERINLINE[-1]] :: N
+[GblId,
+ Arity=1,
+ Str=<S(S),1*U(1*U)>,
+ Cpr=m1,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)
+         Tmpl= T18078.f1 `cast` (Sym (T18078.N:N[0]) :: (Int -> Int) ~R# N)}]
+f = T18078.f1 `cast` (Sym (T18078.N:N[0]) :: (Int -> Int) ~R# N)
+
+-- RHS size: {terms: 12, types: 4, coercions: 0, joins: 0/0}
+g :: Int -> Int
+[GblId,
+ Arity=1,
+ Str=<S,1*U(U)>,
+ Cpr=m1,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+         Tmpl= \ (x [Occ=Once!] :: Int) -> case x of { GHC.Types.I# x1 [Occ=Once] -> T18078.f1 (GHC.Types.I# (GHC.Prim.+# x1 1#)) }}]
+g = \ (x :: Int) -> case x of { GHC.Types.I# x1 -> case T18078.$wf (GHC.Prim.+# x1 1#) of ww { __DEFAULT -> GHC.Types.I# ww } }
+
+
+


=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -319,3 +319,7 @@ test('T17810', normal, multimod_compile, ['T17810', '-fspecialise-aggressively -
 test('T18013', normal, multimod_compile, ['T18013', '-v0 -O'])
 test('T18098', normal, compile, ['-dcore-lint -O2'])
 test('T18120', normal, compile, ['-dcore-lint -O'])
+
+# Cast WW
+test('T17673', [ only_ways(['optasm']), grep_errmsg(r'^\w+\.\$wf') ], compile, ['-ddump-simpl -dsuppress-uniques -dppr-cols=9999'])
+test('T18078', [ only_ways(['optasm']), grep_errmsg(r'^\w+\.\$wf') ], compile, ['-ddump-simpl -dsuppress-uniques -dppr-cols=9999'])


=====================================
testsuite/tests/stranal/should_compile/Makefile
=====================================
@@ -10,9 +10,3 @@ T13031:
 # take only one Int# argument
 T16029:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c -O -fforce-recomp T16029.hs -dsuppress-uniques -ddump-simpl | grep '::.*Int'
-
-T18078:
-	'$(TEST_HC)' $(TEST_HC_OPTS) -c -O -fforce-recomp T18078.hs -dsuppress-uniques -ddump-simpl | grep 'wf'
-
-T17673:
-	'$(TEST_HC)' $(TEST_HC_OPTS) -c -O -fforce-recomp T17673.hs -dsuppress-uniques -ddump-simpl | grep 'wf'


=====================================
testsuite/tests/stranal/should_compile/T17673.stdout deleted
=====================================
@@ -1,5 +0,0 @@
-T17673.$wfacIO [InlPrag=NOINLINE, Occ=LoopBreaker]
-T17673.$wfacIO
-          case T17673.$wfacIO (GHC.Prim.-# ww 1#) w of { (# ipv, ipv1 #) ->
-                 T17673.$wfacIO ww1 w1
-      case w of { GHC.Types.I# ww1 -> T17673.$wfacIO ww1 w1 }


=====================================
testsuite/tests/stranal/should_compile/T18078.stdout deleted
=====================================
@@ -1,6 +0,0 @@
-T18078.$wf [InlPrag=NOINLINE, Occ=LoopBreaker]
-T18078.$wf
-        __DEFAULT -> T18078.$wf (GHC.Prim.-# wild 1#);
-                 case T18078.$wf ww1 of ww2 [Occ=Once] { __DEFAULT ->
-      case T18078.$wf ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 }
-      case T18078.$wf (GHC.Prim.+# x1 1#) of ww { __DEFAULT ->


=====================================
testsuite/tests/stranal/should_compile/all.T
=====================================
@@ -52,6 +52,3 @@ test('T17852',  [ grep_errmsg(r'\\$wf ::') ], compile, ['-ddump-worker-wrapper -
 test('T16029', normal, makefile_test, [])
 test('T10069',  [ grep_errmsg(r'(wc1).*Int#$') ], compile, ['-dppr-cols=200 -ddump-simpl'])
 test('T13380b',  [ grep_errmsg('bigDeadAction') ], compile, ['-dppr-cols=200 -ddump-simpl'])
-test('T18078', normal, makefile_test, [])
-test('T17673', normal, makefile_test, [])
-



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fe99560e3942c64dc5e397ec9c3c8e8423b626aa

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fe99560e3942c64dc5e397ec9c3c8e8423b626aa
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200526/f5dba6d5/attachment-0001.html>


More information about the ghc-commits mailing list