[Git][ghc/ghc][master] Change printing of sized literals to match the proposal

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Nov 29 08:10:36 UTC 2022



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
646969d4 by Krzysztof Gogolewski at 2022-11-29T03:10:13-05:00
Change printing of sized literals to match the proposal

Literals in Core were printed as e.g. 0xFF#16 :: Int16#.
The proposal 451 now specifies syntax 0xFF#Int16.
This change affects the Core printer only - more to be done later.

Part of #21422.

- - - - -


30 changed files:

- compiler/GHC/Utils/Outputable.hs
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-32
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
- testsuite/tests/patsyn/should_compile/T21531.stderr
- testsuite/tests/roles/should_compile/Roles1.stderr
- testsuite/tests/roles/should_compile/Roles13.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles2.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/simplCore/should_compile/Makefile
- testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr
- testsuite/tests/simplCore/should_compile/OpaqueNoSpecConstr.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T19644.stderr
- testsuite/tests/simplCore/should_compile/T21848.stderr
- testsuite/tests/simplCore/should_compile/T21948.stderr
- testsuite/tests/simplCore/should_compile/T21960.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplCore/should_compile/T8274.stdout
- testsuite/tests/simplCore/should_compile/T8832.stdout
- testsuite/tests/simplCore/should_run/T20203.stderr-ws-32
- testsuite/tests/simplCore/should_run/T20203.stderr-ws-64
- testsuite/tests/stranal/should_compile/T18982.stderr
- testsuite/tests/stranal/should_compile/T20663.stderr
- testsuite/tests/th/TH_Roles2.stderr
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr


Changes:

=====================================
compiler/GHC/Utils/Outputable.hs
=====================================
@@ -1251,14 +1251,14 @@ primFloatSuffix  = char '#'
 primIntSuffix    = char '#'
 primDoubleSuffix = text "##"
 primWordSuffix   = text "##"
-primInt8Suffix   = text "#8"
-primWord8Suffix  = text "##8"
-primInt16Suffix  = text "#16"
-primWord16Suffix = text "##16"
-primInt32Suffix  = text "#32"
-primWord32Suffix = text "##32"
-primInt64Suffix  = text "#64"
-primWord64Suffix = text "##64"
+primInt8Suffix   = text "#Int8"
+primWord8Suffix  = text "#Word8"
+primInt16Suffix  = text "#Int16"
+primWord16Suffix = text "#Word16"
+primInt32Suffix  = text "#Int32"
+primWord32Suffix = text "#Word32"
+primInt64Suffix  = text "#Int64"
+primWord64Suffix = text "#Word64"
 
 -- | Special combinator for showing unboxed literals.
 pprPrimChar :: Char -> SDoc


=====================================
testsuite/tests/deSugar/should_compile/T2431.stderr
=====================================
@@ -59,8 +59,8 @@ T2431.$tc:~: :: GHC.Types.TyCon
 [GblId, Unf=OtherCon []]
 T2431.$tc:~:
   = GHC.Types.TyCon
-      4608886815921030019##64
-      6030312177285011233##64
+      4608886815921030019#Word64
+      6030312177285011233#Word64
       T2431.$trModule
       $tc:~:2
       0#
@@ -98,8 +98,8 @@ T2431.$tc'Refl :: GHC.Types.TyCon
 [GblId, Unf=OtherCon []]
 T2431.$tc'Refl
   = GHC.Types.TyCon
-      2478588351447975921##64
-      2684375695874497811##64
+      2478588351447975921#Word64
+      2684375695874497811#Word64
       T2431.$trModule
       $tc'Refl2
       1#


=====================================
testsuite/tests/numeric/should_compile/T16402.stderr-ws-32
=====================================
@@ -43,7 +43,7 @@ smallWord_foo
       case x of { W64# x# ->
       case {__pkg_ccall ghc-prim Word64#
                       -> Word64# -> State# RealWorld -> (# State# RealWorld, Word64# #)}
-             x# 0xffff##64 realWorld#
+             x# 0xffff#Word64 realWorld#
       of
       { (# ds2, ds3 #) ->
       case {__pkg_ccall ghc-prim Word64#
@@ -86,7 +86,7 @@ $wsmallInt_foo
   = \ ww ->
       case {__pkg_ccall ghc-prim Int64#
                       -> State# RealWorld -> (# State# RealWorld, Word64# #)}
-             1245183#64 realWorld#
+             1245183#Int64 realWorld#
       of
       { (# ds2, ds3 #) ->
       case {__pkg_ccall ghc-prim Int64#


=====================================
testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
=====================================
@@ -37,7 +37,7 @@ smallInt_foo
            (int16ToInt#
               (intToInt16#
                  (int64ToInt#
-                    (word64ToInt64# (and64# (int64ToWord64# x#) 0x0012ffff##64))))))
+                    (word64ToInt64# (and64# (int64ToWord64# x#) 0x0012ffff#Word64))))))
       }
 
 


=====================================
testsuite/tests/patsyn/should_compile/T21531.stderr
=====================================
@@ -68,8 +68,8 @@ T21531.$tcLGate :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 50 10}]
 T21531.$tcLGate
   = GHC.Types.TyCon
-      1751240159874500841##64
-      16519490186165952419##64
+      1751240159874500841#Word64
+      16519490186165952419#Word64
       T21531.$trModule
       (GHC.Types.TrNameS "LGate"#)
       0#
@@ -98,8 +98,8 @@ T21531.$tc'LGate :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 50 10}]
 T21531.$tc'LGate
   = GHC.Types.TyCon
-      4309544208860551001##64
-      1328337796258811871##64
+      4309544208860551001#Word64
+      1328337796258811871#Word64
       T21531.$trModule
       (GHC.Types.TrNameS "'LGate"#)
       0#


=====================================
testsuite/tests/roles/should_compile/Roles1.stderr
=====================================
@@ -20,65 +20,65 @@ DATA CONSTRUCTORS
   K2 :: forall a. a -> T2 a
   K1 :: forall a. a -> T1 a
 Dependent modules: []
-Dependent packages: [base-4.16.0.0]
+Dependent packages: [base-4.17.0.0]
 
 ==================== Typechecker ====================
 Roles1.$tcT7
   = GHC.Types.TyCon
-      178606230775360129##64 14564382578551945561##64 Roles1.$trModule
-      (GHC.Types.TrNameS "T7"#) 1# $krep
+      178606230775360129#Word64 14564382578551945561#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "T7"#) 1# $krep
 Roles1.$tc'K7
   = GHC.Types.TyCon
-      15901479081375327280##64 4842873210599704617##64 Roles1.$trModule
-      (GHC.Types.TrNameS "'K7"#) 3# $krep
+      15901479081375327280#Word64 4842873210599704617#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "'K7"#) 3# $krep
 Roles1.$tcT6
   = GHC.Types.TyCon
-      7244893995195634045##64 6882827069359931041##64 Roles1.$trModule
-      (GHC.Types.TrNameS "T6"#) 1# $krep
+      7244893995195634045#Word64 6882827069359931041#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "T6"#) 1# $krep
 Roles1.$tc'K6
   = GHC.Types.TyCon
-      13928703131159360198##64 9274401506945696896##64 Roles1.$trModule
-      (GHC.Types.TrNameS "'K6"#) 2# $krep
+      13928703131159360198#Word64 9274401506945696896#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "'K6"#) 2# $krep
 Roles1.$tcT5
   = GHC.Types.TyCon
-      12033401645911719002##64 6369139038321702301##64 Roles1.$trModule
-      (GHC.Types.TrNameS "T5"#) 0# GHC.Types.krep$*Arr*
+      12033401645911719002#Word64 6369139038321702301#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "T5"#) 0# GHC.Types.krep$*Arr*
 Roles1.$tc'K5
   = GHC.Types.TyCon
-      5548842497263642061##64 18349261927117571882##64 Roles1.$trModule
-      (GHC.Types.TrNameS "'K5"#) 1# $krep
+      5548842497263642061#Word64 18349261927117571882#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "'K5"#) 1# $krep
 Roles1.$tcT4
   = GHC.Types.TyCon
-      15834077582937152787##64 17059037094835388922##64 Roles1.$trModule
-      (GHC.Types.TrNameS "T4"#) 0# $krep
+      15834077582937152787#Word64 17059037094835388922#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "T4"#) 0# $krep
 Roles1.$tc'K4
   = GHC.Types.TyCon
-      10188453925450404995##64 4762093850599364042##64 Roles1.$trModule
-      (GHC.Types.TrNameS "'K4"#) 2# $krep
+      10188453925450404995#Word64 4762093850599364042#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "'K4"#) 2# $krep
 Roles1.$tcT3
   = GHC.Types.TyCon
-      13341737262627465733##64 14527452670364737316##64 Roles1.$trModule
-      (GHC.Types.TrNameS "T3"#) 1# $krep
+      13341737262627465733#Word64 14527452670364737316#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "T3"#) 1# $krep
 Roles1.$tc'K3
   = GHC.Types.TyCon
-      14534968069054730342##64 6860808298964464185##64 Roles1.$trModule
-      (GHC.Types.TrNameS "'K3"#) 2# $krep
+      14534968069054730342#Word64 6860808298964464185#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "'K3"#) 2# $krep
 Roles1.$tcT2
   = GHC.Types.TyCon
-      12900773996789723956##64 9313087549503346504##64 Roles1.$trModule
-      (GHC.Types.TrNameS "T2"#) 0# GHC.Types.krep$*Arr*
+      12900773996789723956#Word64 9313087549503346504#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "T2"#) 0# GHC.Types.krep$*Arr*
 Roles1.$tc'K2
   = GHC.Types.TyCon
-      11054915488163123841##64 10799789256744079155##64 Roles1.$trModule
-      (GHC.Types.TrNameS "'K2"#) 1# $krep
+      11054915488163123841#Word64 10799789256744079155#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "'K2"#) 1# $krep
 Roles1.$tcT1
   = GHC.Types.TyCon
-      13228660854624297872##64 14494320157476678712##64 Roles1.$trModule
-      (GHC.Types.TrNameS "T1"#) 0# GHC.Types.krep$*Arr*
+      13228660854624297872#Word64 14494320157476678712#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "T1"#) 0# GHC.Types.krep$*Arr*
 Roles1.$tc'K1
   = GHC.Types.TyCon
-      1265606750138351672##64 7033043930969109074##64 Roles1.$trModule
-      (GHC.Types.TrNameS "'K1"#) 1# $krep
+      1265606750138351672#Word64 7033043930969109074#Word64
+      Roles1.$trModule (GHC.Types.TrNameS "'K1"#) 1# $krep
 $krep [InlPrag=[~]] = GHC.Types.KindRepVar 1
 $krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
 $krep [InlPrag=[~]] = GHC.Types.KindRepVar 0


=====================================
testsuite/tests/roles/should_compile/Roles13.stderr
=====================================
@@ -69,8 +69,8 @@ Roles13.$tcAge :: GHC.Types.TyCon
 [GblId, Unf=OtherCon []]
 Roles13.$tcAge
   = GHC.Types.TyCon
-      3456257068627873222##64
-      14056710845110756026##64
+      3456257068627873222#Word64
+      14056710845110756026#Word64
       Roles13.$trModule
       $tcAge2
       0#
@@ -103,8 +103,8 @@ Roles13.$tc'MkAge :: GHC.Types.TyCon
 [GblId, Unf=OtherCon []]
 Roles13.$tc'MkAge
   = GHC.Types.TyCon
-      18264039750958872441##64
-      1870189534242358050##64
+      18264039750958872441#Word64
+      1870189534242358050#Word64
       Roles13.$trModule
       $tc'MkAge2
       0#
@@ -125,8 +125,8 @@ Roles13.$tcWrap :: GHC.Types.TyCon
 [GblId, Unf=OtherCon []]
 Roles13.$tcWrap
   = GHC.Types.TyCon
-      13773534096961634492##64
-      15591525585626702988##64
+      13773534096961634492#Word64
+      15591525585626702988#Word64
       Roles13.$trModule
       $tcWrap2
       0#
@@ -164,8 +164,8 @@ Roles13.$tc'MkWrap :: GHC.Types.TyCon
 [GblId, Unf=OtherCon []]
 Roles13.$tc'MkWrap
   = GHC.Types.TyCon
-      15580677875333883466##64
-      808508687714473149##64
+      15580677875333883466#Word64
+      808508687714473149#Word64
       Roles13.$trModule
       $tc'MkWrap2
       1#


=====================================
testsuite/tests/roles/should_compile/Roles14.stderr
=====================================
@@ -11,12 +11,12 @@ Dependent packages: [base-4.17.0.0]
 ==================== Typechecker ====================
 Roles12.$tcC2
   = GHC.Types.TyCon
-      7996680154108933333##64 9454227235464419996##64 Roles12.$trModule
-      (GHC.Types.TrNameS "C2"#) 0# $krep
+      7996680154108933333#Word64 9454227235464419996#Word64
+      Roles12.$trModule (GHC.Types.TrNameS "C2"#) 0# $krep
 Roles12.$tc'C:C2
   = GHC.Types.TyCon
-      7087988437584478859##64 11477953550142401435##64 Roles12.$trModule
-      (GHC.Types.TrNameS "'C:C2"#) 1# $krep
+      7087988437584478859#Word64 11477953550142401435#Word64
+      Roles12.$trModule (GHC.Types.TrNameS "'C:C2"#) 1# $krep
 $krep [InlPrag=[~]]
   = GHC.Types.KindRepTyConApp Roles12.$tcC2 ((:) $krep [])
 $krep [InlPrag=[~]] = GHC.Types.KindRepVar 0


=====================================
testsuite/tests/roles/should_compile/Roles2.stderr
=====================================
@@ -6,25 +6,25 @@ DATA CONSTRUCTORS
   K2 :: forall a. FunPtr a -> T2 a
   K1 :: forall a. IO a -> T1 a
 Dependent modules: []
-Dependent packages: [base-4.16.0.0]
+Dependent packages: [base-4.17.0.0]
 
 ==================== Typechecker ====================
 Roles2.$tcT2
   = GHC.Types.TyCon
-      9065817229114433861##64 13399581642971864140##64 Roles2.$trModule
-      (GHC.Types.TrNameS "T2"#) 0# GHC.Types.krep$*Arr*
+      9065817229114433861#Word64 13399581642971864140#Word64
+      Roles2.$trModule (GHC.Types.TrNameS "T2"#) 0# GHC.Types.krep$*Arr*
 Roles2.$tc'K2
   = GHC.Types.TyCon
-      17395957229042313563##64 12263882107019815181##64 Roles2.$trModule
-      (GHC.Types.TrNameS "'K2"#) 1# $krep
+      17395957229042313563#Word64 12263882107019815181#Word64
+      Roles2.$trModule (GHC.Types.TrNameS "'K2"#) 1# $krep
 Roles2.$tcT1
   = GHC.Types.TyCon
-      10310640733256438505##64 9162099558816022096##64 Roles2.$trModule
-      (GHC.Types.TrNameS "T1"#) 0# GHC.Types.krep$*Arr*
+      10310640733256438505#Word64 9162099558816022096#Word64
+      Roles2.$trModule (GHC.Types.TrNameS "T1"#) 0# GHC.Types.krep$*Arr*
 Roles2.$tc'K1
   = GHC.Types.TyCon
-      16530009231990968394##64 11761390951471299534##64 Roles2.$trModule
-      (GHC.Types.TrNameS "'K1"#) 1# $krep
+      16530009231990968394#Word64 11761390951471299534#Word64
+      Roles2.$trModule (GHC.Types.TrNameS "'K1"#) 1# $krep
 $krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
 $krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
 $krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep


=====================================
testsuite/tests/roles/should_compile/Roles3.stderr
=====================================
@@ -26,28 +26,28 @@ Dependent packages: [base-4.17.0.0]
 ==================== Typechecker ====================
 Roles3.$tcC4
   = GHC.Types.TyCon
-      6800596812149592130##64 15513203864133461281##64 Roles3.$trModule
-      (GHC.Types.TrNameS "C4"#) 0# $krep
+      6800596812149592130#Word64 15513203864133461281#Word64
+      Roles3.$trModule (GHC.Types.TrNameS "C4"#) 0# $krep
 Roles3.$tcC3
   = GHC.Types.TyCon
-      5076086601454991970##64 10299714674904836194##64 Roles3.$trModule
-      (GHC.Types.TrNameS "C3"#) 0# $krep
+      5076086601454991970#Word64 10299714674904836194#Word64
+      Roles3.$trModule (GHC.Types.TrNameS "C3"#) 0# $krep
 Roles3.$tcC2
   = GHC.Types.TyCon
-      7902873224172523979##64 11840994447152209031##64 Roles3.$trModule
-      (GHC.Types.TrNameS "C2"#) 0# $krep
+      7902873224172523979#Word64 11840994447152209031#Word64
+      Roles3.$trModule (GHC.Types.TrNameS "C2"#) 0# $krep
 Roles3.$tc'C:C2
   = GHC.Types.TyCon
-      11218882737915989529##64 9454910899374397367##64 Roles3.$trModule
-      (GHC.Types.TrNameS "'C:C2"#) 2# $krep
+      11218882737915989529#Word64 9454910899374397367#Word64
+      Roles3.$trModule (GHC.Types.TrNameS "'C:C2"#) 2# $krep
 Roles3.$tcC1
   = GHC.Types.TyCon
-      11013585501375994163##64 16371608655219610659##64 Roles3.$trModule
-      (GHC.Types.TrNameS "C1"#) 0# $krep
+      11013585501375994163#Word64 16371608655219610659#Word64
+      Roles3.$trModule (GHC.Types.TrNameS "C1"#) 0# $krep
 Roles3.$tc'C:C1
   = GHC.Types.TyCon
-      4508088879886988796##64 13962145553903222779##64 Roles3.$trModule
-      (GHC.Types.TrNameS "'C:C1"#) 1# $krep
+      4508088879886988796#Word64 13962145553903222779#Word64
+      Roles3.$trModule (GHC.Types.TrNameS "'C:C1"#) 1# $krep
 $krep [InlPrag=[~]]
   = GHC.Types.KindRepTyConApp
       GHC.Types.$tc~ ((:) GHC.Types.krep$* ((:) $krep ((:) $krep [])))


=====================================
testsuite/tests/roles/should_compile/Roles4.stderr
=====================================
@@ -14,20 +14,20 @@ Dependent packages: [base-4.17.0.0]
 ==================== Typechecker ====================
 Roles4.$tcC3
   = GHC.Types.TyCon
-      7508642517340826358##64 16938219270597865136##64 Roles4.$trModule
-      (GHC.Types.TrNameS "C3"#) 0# $krep
+      7508642517340826358#Word64 16938219270597865136#Word64
+      Roles4.$trModule (GHC.Types.TrNameS "C3"#) 0# $krep
 Roles4.$tc'C:C3
   = GHC.Types.TyCon
-      3133378316178104365##64 15809386433947157376##64 Roles4.$trModule
-      (GHC.Types.TrNameS "'C:C3"#) 1# $krep
+      3133378316178104365#Word64 15809386433947157376#Word64
+      Roles4.$trModule (GHC.Types.TrNameS "'C:C3"#) 1# $krep
 Roles4.$tcC1
   = GHC.Types.TyCon
-      13392243382482428602##64 1780037961948725012##64 Roles4.$trModule
-      (GHC.Types.TrNameS "C1"#) 0# $krep
+      13392243382482428602#Word64 1780037961948725012#Word64
+      Roles4.$trModule (GHC.Types.TrNameS "C1"#) 0# $krep
 Roles4.$tc'C:C1
   = GHC.Types.TyCon
-      3870707671502302648##64 10631907186261837450##64 Roles4.$trModule
-      (GHC.Types.TrNameS "'C:C1"#) 1# $krep
+      3870707671502302648#Word64 10631907186261837450#Word64
+      Roles4.$trModule (GHC.Types.TrNameS "'C:C1"#) 1# $krep
 $krep [InlPrag=[~]]
   = GHC.Types.KindRepTyConApp Roles4.$tcC3 ((:) $krep [])
 $krep [InlPrag=[~]]


=====================================
testsuite/tests/roles/should_compile/T8958.stderr
=====================================
@@ -23,28 +23,29 @@ Dependent packages: [base-4.17.0.0]
 ==================== Typechecker ====================
 T8958.$tcMap
   = GHC.Types.TyCon
-      16542473435673943392##64 5374201132143305512##64 T8958.$trModule
-      (GHC.Types.TrNameS "Map"#) 0# GHC.Types.krep$*->*->*
+      16542473435673943392#Word64 5374201132143305512#Word64
+      T8958.$trModule (GHC.Types.TrNameS "Map"#) 0#
+      GHC.Types.krep$*->*->*
 T8958.$tc'MkMap
   = GHC.Types.TyCon
-      2942839876828444488##64 3989137838066763457##64 T8958.$trModule
-      (GHC.Types.TrNameS "'MkMap"#) 2# $krep
+      2942839876828444488#Word64 3989137838066763457#Word64
+      T8958.$trModule (GHC.Types.TrNameS "'MkMap"#) 2# $krep
 T8958.$tcRepresentational
   = GHC.Types.TyCon
-      12809567151893673426##64 12159693688248149156##64 T8958.$trModule
-      (GHC.Types.TrNameS "Representational"#) 0# $krep
+      12809567151893673426#Word64 12159693688248149156#Word64
+      T8958.$trModule (GHC.Types.TrNameS "Representational"#) 0# $krep
 T8958.$tc'C:Representational
   = GHC.Types.TyCon
-      2358772282532242424##64 5444038897914446879##64 T8958.$trModule
-      (GHC.Types.TrNameS "'C:Representational"#) 1# $krep
+      2358772282532242424#Word64 5444038897914446879#Word64
+      T8958.$trModule (GHC.Types.TrNameS "'C:Representational"#) 1# $krep
 T8958.$tcNominal
   = GHC.Types.TyCon
-      12224997609886144634##64 9866011944332051160##64 T8958.$trModule
-      (GHC.Types.TrNameS "Nominal"#) 0# $krep
+      12224997609886144634#Word64 9866011944332051160#Word64
+      T8958.$trModule (GHC.Types.TrNameS "Nominal"#) 0# $krep
 T8958.$tc'C:Nominal
   = GHC.Types.TyCon
-      10562260635335201742##64 1215478186250709459##64 T8958.$trModule
-      (GHC.Types.TrNameS "'C:Nominal"#) 1# $krep
+      10562260635335201742#Word64 1215478186250709459#Word64
+      T8958.$trModule (GHC.Types.TrNameS "'C:Nominal"#) 1# $krep
 $krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
 $krep [InlPrag=[~]] = GHC.Types.KindRepVar 1
 $krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep


=====================================
testsuite/tests/simplCore/should_compile/Makefile
=====================================
@@ -77,7 +77,7 @@ T11155:
 T8274:
 	$(RM) -f T8274.o T8274.hi
 	# Set -dppr-cols to ensure things don't wrap
-	'$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl -dsuppress-uniques -dsuppress-ticks -dppr-cols=200 T8274.hs | grep '#'
+	'$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl -dsuppress-uniques -dsuppress-ticks -dppr-cols=300 T8274.hs | grep '#'
 
 T7865:
 	$(RM) -f T7865.o T7865.hi


=====================================
testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr
=====================================
@@ -106,8 +106,8 @@ OpaqueNoCastWW.$tcSigned :: GHC.Types.TyCon
 [GblId, Unf=OtherCon []]
 OpaqueNoCastWW.$tcSigned
   = GHC.Types.TyCon
-      12374680438872388605##64
-      16570143229152367467##64
+      12374680438872388605#Word64
+      16570143229152367467#Word64
       OpaqueNoCastWW.$trModule
       $tcSigned2
       0#
@@ -145,8 +145,8 @@ OpaqueNoCastWW.$tc'S :: GHC.Types.TyCon
 [GblId, Unf=OtherCon []]
 OpaqueNoCastWW.$tc'S
   = GHC.Types.TyCon
-      9801584576887380300##64
-      5757617350287545124##64
+      9801584576887380300#Word64
+      5757617350287545124#Word64
       OpaqueNoCastWW.$trModule
       $tc'S2
       1#


=====================================
testsuite/tests/simplCore/should_compile/OpaqueNoSpecConstr.stderr
=====================================
@@ -99,8 +99,8 @@ OpaqueNoSpecConstr.$tcSPEC :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 OpaqueNoSpecConstr.$tcSPEC
   = GHC.Types.TyCon
-      1794519131116102988##
-      1536993820726345194##
+      1794519131116102988#Word64
+      1536993820726345194#Word64
       OpaqueNoSpecConstr.$trModule
       OpaqueNoSpecConstr.$tcSPEC1
       0#
@@ -135,8 +135,8 @@ OpaqueNoSpecConstr.$tc'SPEC :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 OpaqueNoSpecConstr.$tc'SPEC
   = GHC.Types.TyCon
-      9648911419523887824##
-      4100179153648933145##
+      9648911419523887824#Word64
+      4100179153648933145#Word64
       OpaqueNoSpecConstr.$trModule
       OpaqueNoSpecConstr.$tc'SPEC3
       0#
@@ -164,8 +164,8 @@ OpaqueNoSpecConstr.$tc'SPEC2 :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 OpaqueNoSpecConstr.$tc'SPEC2
   = GHC.Types.TyCon
-      4214136204857816792##
-      17253701793498718125##
+      4214136204857816792#Word64
+      17253701793498718125#Word64
       OpaqueNoSpecConstr.$trModule
       OpaqueNoSpecConstr.$tc'SPEC5
       0#


=====================================
testsuite/tests/simplCore/should_compile/T17966.stderr
=====================================
@@ -283,8 +283,8 @@ T17966.$tcC :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T17966.$tcC
   = GHC.Types.TyCon
-      12503088876068780286##64
-      926716241154773768##64
+      12503088876068780286#Word64
+      926716241154773768#Word64
       T17966.$trModule
       $tcC_sRL
       0#


=====================================
testsuite/tests/simplCore/should_compile/T19644.stderr
=====================================
@@ -235,8 +235,8 @@ T19644.$tcC :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T19644.$tcC
   = GHC.Types.TyCon
-      3363473062474234294##64
-      5379444656532611026##64
+      3363473062474234294#Word64
+      5379444656532611026#Word64
       T19644.$trModule
       $tcC_sZJ
       0#


=====================================
testsuite/tests/simplCore/should_compile/T21848.stderr
=====================================
@@ -329,8 +329,8 @@ T21848.$tcC :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T21848.$tcC
   = GHC.Types.TyCon
-      14679919086118427567##64
-      12559744112860329810##64
+      14679919086118427567#Word64
+      12559744112860329810#Word64
       T21848.$trModule
       $tcC_s1fa
       0#
@@ -373,8 +373,8 @@ T21848.$tcD :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T21848.$tcD
   = GHC.Types.TyCon
-      2028775029841869083##64
-      18183109077030380353##64
+      2028775029841869083#Word64
+      18183109077030380353#Word64
       T21848.$trModule
       $tcD_s1fd
       0#
@@ -431,8 +431,8 @@ T21848.$tc'C:D :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T21848.$tc'C:D
   = GHC.Types.TyCon
-      4845813539547459579##64
-      7908713917114703782##64
+      4845813539547459579#Word64
+      7908713917114703782#Word64
       T21848.$trModule
       $tc'C:D_s1fg
       1#


=====================================
testsuite/tests/simplCore/should_compile/T21948.stderr
=====================================
@@ -62,12 +62,12 @@ T21948.nf'1
                    $wgo_s11i (ww_s11e :: GHC.Prim.Int64#)
                              (eta2_s11g [Occ=Once2, OS=OneShot]
                                 :: GHC.Prim.State# GHC.Prim.RealWorld)
-                     = case GHC.Prim.leInt64# ww_s11e 0#64 of {
+                     = case GHC.Prim.leInt64# ww_s11e 0#Int64 of {
                          __DEFAULT ->
                            case lvl_s111 of y_aNQ [Occ=Once1] { __DEFAULT ->
                            case reduce_aBy y_aNQ of { () ->
                            jump go_s10Z
-                             (GHC.Int.I64# (GHC.Prim.subInt64# ww_s11e 1#64)) eta2_s11g
+                             (GHC.Int.I64# (GHC.Prim.subInt64# ww_s11e 1#Int64)) eta2_s11g
                            }
                            };
                          1# -> (# eta2_s11g, GHC.Tuple.() #)
@@ -98,11 +98,11 @@ T21948.nf'1
         [LclId[JoinId(2)(Nothing)], Arity=2, Str=<L><L>, Unf=OtherCon []]
         $wgo_s11i (ww1_X3 :: GHC.Prim.Int64#)
                   (eta2_s11g [OS=OneShot] :: GHC.Prim.State# GHC.Prim.RealWorld)
-          = case GHC.Prim.leInt64# ww1_X3 0#64 of {
+          = case GHC.Prim.leInt64# ww1_X3 0#Int64 of {
               __DEFAULT ->
                 case lvl_s111 of { __DEFAULT ->
                 case lvl1_s11A of { () ->
-                jump $wgo_s11i (GHC.Prim.subInt64# ww1_X3 1#64) eta2_s11g
+                jump $wgo_s11i (GHC.Prim.subInt64# ww1_X3 1#Int64) eta2_s11g
                 }
                 };
               1# -> (# eta2_s11g, GHC.Tuple.() #)


=====================================
testsuite/tests/simplCore/should_compile/T21960.stderr
=====================================
@@ -153,7 +153,7 @@ encodeUtf8BuilderEscaped [InlPrag=INLINE (sat-args=1)]
                                                           GHC.Word.W8# r#_a24P
                                                           } } in
                                                     case GHC.Word.ltWord8
-                                                           w_a1EF (GHC.Word.W8# 128##8)
+                                                           w_a1EF (GHC.Word.W8# 128#Word8)
                                                     of {
                                                       False ->
                                                         (\ (s_a25B [Occ=Once1]
@@ -452,7 +452,7 @@ encodeUtf8BuilderEscaped
                                                                               of r#_a24P
                                                                               { __DEFAULT ->
                                                                               case GHC.Prim.ltWord8#
-                                                                                     r#_a24P 128##8
+                                                                                     r#_a24P 128#Word8
                                                                               of {
                                                                                 __DEFAULT ->
                                                                                   case GHC.Prim.writeWord8OffAddr#
@@ -540,7 +540,7 @@ encodeUtf8BuilderEscaped
                                                                                             { __DEFAULT ->
                                                                                             case GHC.Prim.ltWord8#
                                                                                                    r#1_Xr
-                                                                                                   128##8
+                                                                                                   128#Word8
                                                                                             of {
                                                                                               __DEFAULT ->
                                                                                                 case GHC.Prim.writeWord8OffAddr#
@@ -765,7 +765,7 @@ encodeUtf8BuilderEscaped
                                                                               of r#_a24P
                                                                               { __DEFAULT ->
                                                                               case GHC.Prim.ltWord8#
-                                                                                     r#_a24P 128##8
+                                                                                     r#_a24P 128#Word8
                                                                               of {
                                                                                 __DEFAULT ->
                                                                                   case GHC.Prim.writeWord8OffAddr#
@@ -846,7 +846,7 @@ encodeUtf8BuilderEscaped
                                                                                             { __DEFAULT ->
                                                                                             case GHC.Prim.ltWord8#
                                                                                                    r#1_Xr
-                                                                                                   128##8
+                                                                                                   128#Word8
                                                                                             of {
                                                                                               __DEFAULT ->
                                                                                                 case GHC.Prim.writeWord8OffAddr#
@@ -945,7 +945,7 @@ encodeUtf8BuilderEscaped
                                                                                             { __DEFAULT ->
                                                                                             case GHC.Prim.ltWord8#
                                                                                                    r#1_Xr
-                                                                                                   128##8
+                                                                                                   128#Word8
                                                                                             of {
                                                                                               __DEFAULT ->
                                                                                                 case GHC.Prim.writeWord8OffAddr#
@@ -1208,7 +1208,7 @@ encodeUtf8BuilderEscaped
                                                                                  { __DEFAULT ->
                                                                                  case GHC.Prim.ltWord8#
                                                                                         r#_a24P
-                                                                                        128##8
+                                                                                        128#Word8
                                                                                  of {
                                                                                    __DEFAULT ->
                                                                                      case GHC.Prim.writeWord8OffAddr#
@@ -1298,7 +1298,7 @@ encodeUtf8BuilderEscaped
                                                                                                { __DEFAULT ->
                                                                                                case GHC.Prim.ltWord8#
                                                                                                       r#1_XB
-                                                                                                      128##8
+                                                                                                      128#Word8
                                                                                                of {
                                                                                                  __DEFAULT ->
                                                                                                    case GHC.Prim.writeWord8OffAddr#
@@ -1528,7 +1528,7 @@ encodeUtf8BuilderEscaped
                                                                                  { __DEFAULT ->
                                                                                  case GHC.Prim.ltWord8#
                                                                                         r#_a24P
-                                                                                        128##8
+                                                                                        128#Word8
                                                                                  of {
                                                                                    __DEFAULT ->
                                                                                      case GHC.Prim.writeWord8OffAddr#
@@ -1611,7 +1611,7 @@ encodeUtf8BuilderEscaped
                                                                                                { __DEFAULT ->
                                                                                                case GHC.Prim.ltWord8#
                                                                                                       r#1_XB
-                                                                                                      128##8
+                                                                                                      128#Word8
                                                                                                of {
                                                                                                  __DEFAULT ->
                                                                                                    case GHC.Prim.writeWord8OffAddr#
@@ -1710,7 +1710,7 @@ encodeUtf8BuilderEscaped
                                                                                                { __DEFAULT ->
                                                                                                case GHC.Prim.ltWord8#
                                                                                                       r#1_XB
-                                                                                                      128##8
+                                                                                                      128#Word8
                                                                                                of {
                                                                                                  __DEFAULT ->
                                                                                                    case GHC.Prim.writeWord8OffAddr#
@@ -1829,7 +1829,7 @@ encodeUtf8BuilderEscaped
                                                case GHC.Prim.indexWord8Array# bx_d22M sc2_s2cL
                                                of r#_a24P
                                                { __DEFAULT ->
-                                               case GHC.Prim.ltWord8# r#_a24P 128##8 of {
+                                               case GHC.Prim.ltWord8# r#_a24P 128#Word8 of {
                                                  __DEFAULT ->
                                                    case GHC.Prim.writeWord8OffAddr#
                                                           @GHC.Prim.RealWorld
@@ -1884,7 +1884,7 @@ encodeUtf8BuilderEscaped
                                                                     bx_d22M sc5_s2cS
                                                              of r#1_Xk
                                                              { __DEFAULT ->
-                                                             case GHC.Prim.ltWord8# r#1_Xk 128##8
+                                                             case GHC.Prim.ltWord8# r#1_Xk 128#Word8
                                                              of {
                                                                __DEFAULT ->
                                                                  case GHC.Prim.writeWord8OffAddr#
@@ -1952,7 +1952,7 @@ encodeUtf8BuilderEscaped
                                                                     bx_d22M ww_Xe
                                                              of r#1_Xk
                                                              { __DEFAULT ->
-                                                             case GHC.Prim.ltWord8# r#1_Xk 128##8
+                                                             case GHC.Prim.ltWord8# r#1_Xk 128#Word8
                                                              of {
                                                                __DEFAULT ->
                                                                  case GHC.Prim.writeWord8OffAddr#


=====================================
testsuite/tests/simplCore/should_compile/T7360.stderr
=====================================
@@ -37,7 +37,8 @@ fun1 [InlPrag=NOINLINE[final]] :: Foo -> ()
          Tmpl= \ (x [Occ=Once1] :: Foo) ->
                  case T7360.$wfun1 x of { (# #) -> GHC.Tuple.Prim.() }}]
 fun1
-  = \ (x :: Foo) -> case T7360.$wfun1 x of { (# #) -> GHC.Tuple.Prim.() }
+  = \ (x :: Foo) ->
+      case T7360.$wfun1 x of { (# #) -> GHC.Tuple.Prim.() }
 
 -- RHS size: {terms: 5, types: 1, coercions: 0, joins: 0/0}
 T7360.fun4 :: ()
@@ -132,8 +133,8 @@ T7360.$tcFoo :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T7360.$tcFoo
   = GHC.Types.TyCon
-      1581370841583180512##64
-      13291578023368289311##64
+      1581370841583180512#Word64
+      13291578023368289311#Word64
       T7360.$trModule
       T7360.$tcFoo1
       0#
@@ -167,8 +168,8 @@ T7360.$tc'Foo1 :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T7360.$tc'Foo1
   = GHC.Types.TyCon
-      3986951253261644518##64
-      2515097940992351150##64
+      3986951253261644518#Word64
+      2515097940992351150#Word64
       T7360.$trModule
       T7360.$tc'Foo5
       0#
@@ -195,8 +196,8 @@ T7360.$tc'Foo2 :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T7360.$tc'Foo2
   = GHC.Types.TyCon
-      17325079864060690428##64
-      2969742457748208427##64
+      17325079864060690428#Word64
+      2969742457748208427#Word64
       T7360.$trModule
       T7360.$tc'Foo7
       0#
@@ -228,8 +229,8 @@ T7360.$tc'Foo3 :: GHC.Types.TyCon
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}]
 T7360.$tc'Foo3
   = GHC.Types.TyCon
-      3674231676522181654##64
-      2694749919371021431##64
+      3674231676522181654#Word64
+      2694749919371021431#Word64
       T7360.$trModule
       T7360.$tc'Foo10
       0#


=====================================
testsuite/tests/simplCore/should_compile/T8274.stdout
=====================================
@@ -11,13 +11,13 @@ $krep3 = GHC.Types.KindRepTyConApp GHC.Types.$tcFloat# (GHC.Types.[] @GHC.Types.
 $krep4 = GHC.Types.KindRepTyConApp GHC.Types.$tcInt# (GHC.Types.[] @GHC.Types.KindRep)
 T8274.$tcP2 :: Addr#
 T8274.$tcP2 = "P"#
-T8274.$tcP = GHC.Types.TyCon 7483823267324216774## 12197132127820124256## T8274.$trModule T8274.$tcP1 0# GHC.Types.krep$*
+T8274.$tcP = GHC.Types.TyCon 7483823267324216774#Word64 12197132127820124256#Word64 T8274.$trModule T8274.$tcP1 0# GHC.Types.krep$*
 T8274.$tc'Positives3 :: Addr#
 T8274.$tc'Positives3 = "'Positives"#
-  = GHC.Types.TyCon 14886798270706315033## 15735393004803600911## T8274.$trModule T8274.$tc'Positives2 0# T8274.$tc'Positives1
+T8274.$tc'Positives = GHC.Types.TyCon 14886798270706315033#Word64 15735393004803600911#Word64 T8274.$trModule T8274.$tc'Positives2 0# T8274.$tc'Positives1
 T8274.$tcN2 :: Addr#
 T8274.$tcN2 = "N"#
-T8274.$tcN = GHC.Types.TyCon 17387464673997143412## 16681536026493340311## T8274.$trModule T8274.$tcN1 0# GHC.Types.krep$*
+T8274.$tcN = GHC.Types.TyCon 17387464673997143412#Word64 16681536026493340311#Word64 T8274.$trModule T8274.$tcN1 0# GHC.Types.krep$*
 T8274.$tc'Negatives3 :: Addr#
 T8274.$tc'Negatives3 = "'Negatives"#
-  = GHC.Types.TyCon 14330047746189143983## 12207513731214201811## T8274.$trModule T8274.$tc'Negatives2 0# T8274.$tc'Negatives1
+T8274.$tc'Negatives = GHC.Types.TyCon 14330047746189143983#Word64 12207513731214201811#Word64 T8274.$trModule T8274.$tc'Negatives2 0# T8274.$tc'Negatives1


=====================================
testsuite/tests/simplCore/should_compile/T8832.stdout
=====================================
@@ -1,11 +1,11 @@
 i = GHC.Types.I# 0#
-i8 = GHC.Int.I8# 0#8
-i16 = GHC.Int.I16# 0#16
-i32 = GHC.Int.I32# 0#32
-i64 = GHC.Int.I64# 0#64
+i8 = GHC.Int.I8# 0#Int8
+i16 = GHC.Int.I16# 0#Int16
+i32 = GHC.Int.I32# 0#Int32
+i64 = GHC.Int.I64# 0#Int64
 w = GHC.Types.W# 0##
-w8 = GHC.Word.W8# 0##8
-w16 = GHC.Word.W16# 0##16
-w32 = GHC.Word.W32# 0##32
-w64 = GHC.Word.W64# 0##64
+w8 = GHC.Word.W8# 0#Word8
+w16 = GHC.Word.W16# 0#Word16
+w32 = GHC.Word.W32# 0#Word32
+w64 = GHC.Word.W64# 0#Word64
 z = GHC.Num.Integer.IS 0#


=====================================
testsuite/tests/simplCore/should_run/T20203.stderr-ws-32
=====================================
@@ -25,11 +25,11 @@ bitOrTwoVarInt8
       case y of { I8# x#1 ->
       I8#
         (word8ToInt8#
-           (orWord8# 17##8 (orWord8# (int8ToWord8# x#) (int8ToWord8# x#1))))
+           (orWord8# 17#Word8 (orWord8# (int8ToWord8# x#) (int8ToWord8# x#1))))
       }
       }
 
-bitAndInt1 = I8# 0#8
+bitAndInt1 = I8# 0#Int8
 
 bitAndTwoVarInt8
   = \ x y ->
@@ -38,7 +38,7 @@ bitAndTwoVarInt8
 bitOrInt8
   = \ x ->
       case x of { I8# x# ->
-      I8# (word8ToInt8# (orWord8# 17##8 (int8ToWord8# x#)))
+      I8# (word8ToInt8# (orWord8# 17#Word8 (int8ToWord8# x#)))
       }
 
 bitAndInt8 = \ x -> case x of { I8# x# -> bitAndInt1 }
@@ -50,7 +50,7 @@ bitOrTwoVarInt16
       I16#
         (word16ToInt16#
            (orWord16#
-              255##16 (orWord16# (int16ToWord16# x#) (int16ToWord16# x#1))))
+              255#Word16 (orWord16# (int16ToWord16# x#) (int16ToWord16# x#1))))
       }
       }
 
@@ -61,20 +61,20 @@ bitAndTwoVarInt16
       I16#
         (word16ToInt16#
            (andWord16#
-              170##16 (andWord16# (int16ToWord16# x#) (int16ToWord16# x#1))))
+              170#Word16 (andWord16# (int16ToWord16# x#) (int16ToWord16# x#1))))
       }
       }
 
 bitOrInt16
   = \ x ->
       case x of { I16# x# ->
-      I16# (word16ToInt16# (orWord16# 255##16 (int16ToWord16# x#)))
+      I16# (word16ToInt16# (orWord16# 255#Word16 (int16ToWord16# x#)))
       }
 
 bitAndInt16
   = \ x ->
       case x of { I16# x# ->
-      I16# (word16ToInt16# (andWord16# 170##16 (int16ToWord16# x#)))
+      I16# (word16ToInt16# (andWord16# 170#Word16 (int16ToWord16# x#)))
       }
 
 bitOrTwoVarInt32
@@ -125,7 +125,7 @@ bitOrTwoVarInt64
       case y of { I64# x#1 ->
       I64#
         (word64ToInt64#
-           (or64# 255##64 (or64# (int64ToWord64# x#) (int64ToWord64# x#1)))) 
+           (or64# 255#Word64 (or64# (int64ToWord64# x#) (int64ToWord64# x#1)))) 
       }
       }
 
@@ -135,19 +135,19 @@ bitAndTwoVarInt64
       case y of { I64# x#1 ->
       I64#
         (word64ToInt64#
-           (and64# 170##64 (and64# (int64ToWord64# x#) (int64ToWord64# x#1)))) 
+           (and64# 170#Word64 (and64# (int64ToWord64# x#) (int64ToWord64# x#1)))) 
       }
       }
 
 bitOrInt64
   = / x ->
       case x of { I64# x# ->
-      I64# (word64ToInt64# (or64# 255##64 (int64ToWord64# x#)))
+      I64# (word64ToInt64# (or64# 255#Word64 (int64ToWord64# x#)))
       }
  
 bitAndInt64
   = / x ->
       case x of { I64# x# ->
-      I64# (word64ToInt64# (and64# 170##64 (int64ToWord64# x#)))
+      I64# (word64ToInt64# (and64# 170#Word64 (int64ToWord64# x#)))
       }
 


=====================================
testsuite/tests/simplCore/should_run/T20203.stderr-ws-64
=====================================
@@ -25,11 +25,12 @@ bitOrTwoVarInt8
       case y of { I8# x#1 ->
       I8#
         (word8ToInt8#
-           (orWord8# 17##8 (orWord8# (int8ToWord8# x#) (int8ToWord8# x#1))))
+           (orWord8#
+              17#Word8 (orWord8# (int8ToWord8# x#) (int8ToWord8# x#1))))
       }
       }
 
-bitAndInt1 = I8# 0#8
+bitAndInt1 = I8# 0#Int8
 
 bitAndTwoVarInt8
   = \ x y ->
@@ -38,7 +39,7 @@ bitAndTwoVarInt8
 bitOrInt8
   = \ x ->
       case x of { I8# x# ->
-      I8# (word8ToInt8# (orWord8# 17##8 (int8ToWord8# x#)))
+      I8# (word8ToInt8# (orWord8# 17#Word8 (int8ToWord8# x#)))
       }
 
 bitAndInt8 = \ x -> case x of { I8# x# -> bitAndInt1 }
@@ -50,7 +51,7 @@ bitOrTwoVarInt16
       I16#
         (word16ToInt16#
            (orWord16#
-              255##16 (orWord16# (int16ToWord16# x#) (int16ToWord16# x#1))))
+              255#Word16 (orWord16# (int16ToWord16# x#) (int16ToWord16# x#1))))
       }
       }
 
@@ -61,20 +62,20 @@ bitAndTwoVarInt16
       I16#
         (word16ToInt16#
            (andWord16#
-              170##16 (andWord16# (int16ToWord16# x#) (int16ToWord16# x#1))))
+              170#Word16 (andWord16# (int16ToWord16# x#) (int16ToWord16# x#1))))
       }
       }
 
 bitOrInt16
   = \ x ->
       case x of { I16# x# ->
-      I16# (word16ToInt16# (orWord16# 255##16 (int16ToWord16# x#)))
+      I16# (word16ToInt16# (orWord16# 255#Word16 (int16ToWord16# x#)))
       }
 
 bitAndInt16
   = \ x ->
       case x of { I16# x# ->
-      I16# (word16ToInt16# (andWord16# 170##16 (int16ToWord16# x#)))
+      I16# (word16ToInt16# (andWord16# 170#Word16 (int16ToWord16# x#)))
       }
 
 bitOrTwoVarInt32
@@ -125,7 +126,8 @@ bitOrTwoVarInt64
       case y of { I64# x#1 ->
       I64#
         (word64ToInt64#
-           (or64# 255##64 (or64# (int64ToWord64# x#) (int64ToWord64# x#1))))
+           (or64#
+              255#Word64 (or64# (int64ToWord64# x#) (int64ToWord64# x#1))))
       }
       }
 
@@ -135,20 +137,21 @@ bitAndTwoVarInt64
       case y of { I64# x#1 ->
       I64#
         (word64ToInt64#
-           (and64# 170##64 (and64# (int64ToWord64# x#) (int64ToWord64# x#1))))
+           (and64#
+              170#Word64 (and64# (int64ToWord64# x#) (int64ToWord64# x#1))))
       }
       }
 
 bitOrInt64
   = \ x ->
       case x of { I64# x# ->
-      I64# (word64ToInt64# (or64# 255##64 (int64ToWord64# x#)))
+      I64# (word64ToInt64# (or64# 255#Word64 (int64ToWord64# x#)))
       }
 
 bitAndInt64
   = \ x ->
       case x of { I64# x# ->
-      I64# (word64ToInt64# (and64# 170##64 (int64ToWord64# x#)))
+      I64# (word64ToInt64# (and64# 170#Word64 (int64ToWord64# x#)))
       }
 
 


=====================================
testsuite/tests/stranal/should_compile/T18982.stderr
=====================================
@@ -72,7 +72,7 @@ T18982.$tcBox1 = GHC.Types.TrNameS T18982.$tcBox2
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T18982.$tcBox :: GHC.Types.TyCon
-T18982.$tcBox = GHC.Types.TyCon 16948648223906549518##64 2491460178135962649##64 T18982.$trModule T18982.$tcBox1 0# GHC.Types.krep$*Arr*
+T18982.$tcBox = GHC.Types.TyCon 16948648223906549518#Word64 2491460178135962649#Word64 T18982.$trModule T18982.$tcBox1 0# GHC.Types.krep$*Arr*
 
 -- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
 $krep7 :: [GHC.Types.KindRep]
@@ -96,7 +96,7 @@ T18982.$tc'Box2 = GHC.Types.TrNameS T18982.$tc'Box3
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T18982.$tc'Box :: GHC.Types.TyCon
-T18982.$tc'Box = GHC.Types.TyCon 1412068769125067428##64 8727214667407894081##64 T18982.$trModule T18982.$tc'Box2 1# T18982.$tc'Box1
+T18982.$tc'Box = GHC.Types.TyCon 1412068769125067428#Word64 8727214667407894081#Word64 T18982.$trModule T18982.$tc'Box2 1# T18982.$tc'Box1
 
 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
 T18982.$tcEx2 :: GHC.Prim.Addr#
@@ -108,7 +108,7 @@ T18982.$tcEx1 = GHC.Types.TrNameS T18982.$tcEx2
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T18982.$tcEx :: GHC.Types.TyCon
-T18982.$tcEx = GHC.Types.TyCon 4376661818164435927##64 18005417598910668817##64 T18982.$trModule T18982.$tcEx1 0# GHC.Types.krep$*Arr*
+T18982.$tcEx = GHC.Types.TyCon 4376661818164435927#Word64 18005417598910668817#Word64 T18982.$trModule T18982.$tcEx1 0# GHC.Types.krep$*Arr*
 
 -- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
 $krep9 :: [GHC.Types.KindRep]
@@ -136,7 +136,7 @@ T18982.$tc'Ex2 = GHC.Types.TrNameS T18982.$tc'Ex3
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T18982.$tc'Ex :: GHC.Types.TyCon
-T18982.$tc'Ex = GHC.Types.TyCon 14609381081172201359##64 3077219645053200509##64 T18982.$trModule T18982.$tc'Ex2 2# T18982.$tc'Ex1
+T18982.$tc'Ex = GHC.Types.TyCon 14609381081172201359#Word64 3077219645053200509#Word64 T18982.$trModule T18982.$tc'Ex2 2# T18982.$tc'Ex1
 
 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
 T18982.$tcGADT2 :: GHC.Prim.Addr#
@@ -148,7 +148,7 @@ T18982.$tcGADT1 = GHC.Types.TrNameS T18982.$tcGADT2
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T18982.$tcGADT :: GHC.Types.TyCon
-T18982.$tcGADT = GHC.Types.TyCon 9243924476135839950##64 5096619276488416461##64 T18982.$trModule T18982.$tcGADT1 0# GHC.Types.krep$*Arr*
+T18982.$tcGADT = GHC.Types.TyCon 9243924476135839950#Word64 5096619276488416461#Word64 T18982.$trModule T18982.$tcGADT1 0# GHC.Types.krep$*Arr*
 
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 $krep12 :: GHC.Types.KindRep
@@ -168,7 +168,7 @@ T18982.$tc'GADT2 = GHC.Types.TrNameS T18982.$tc'GADT3
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T18982.$tc'GADT :: GHC.Types.TyCon
-T18982.$tc'GADT = GHC.Types.TyCon 2077850259354179864##64 16731205864486799217##64 T18982.$trModule T18982.$tc'GADT2 0# T18982.$tc'GADT1
+T18982.$tc'GADT = GHC.Types.TyCon 2077850259354179864#Word64 16731205864486799217#Word64 T18982.$trModule T18982.$tc'GADT2 0# T18982.$tc'GADT1
 
 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
 T18982.$tcExGADT2 :: GHC.Prim.Addr#
@@ -180,7 +180,7 @@ T18982.$tcExGADT1 = GHC.Types.TrNameS T18982.$tcExGADT2
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T18982.$tcExGADT :: GHC.Types.TyCon
-T18982.$tcExGADT = GHC.Types.TyCon 6470898418160489500##64 10361108917441214060##64 T18982.$trModule T18982.$tcExGADT1 0# GHC.Types.krep$*Arr*
+T18982.$tcExGADT = GHC.Types.TyCon 6470898418160489500#Word64 10361108917441214060#Word64 T18982.$trModule T18982.$tcExGADT1 0# GHC.Types.krep$*Arr*
 
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 $krep13 :: GHC.Types.KindRep
@@ -208,7 +208,7 @@ T18982.$tc'ExGADT2 = GHC.Types.TrNameS T18982.$tc'ExGADT3
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T18982.$tc'ExGADT :: GHC.Types.TyCon
-T18982.$tc'ExGADT = GHC.Types.TyCon 8468257409157161049##64 5503123603717080600##64 T18982.$trModule T18982.$tc'ExGADT2 1# T18982.$tc'ExGADT1
+T18982.$tc'ExGADT = GHC.Types.TyCon 8468257409157161049#Word64 5503123603717080600#Word64 T18982.$trModule T18982.$tc'ExGADT2 1# T18982.$tc'ExGADT1
 
 -- RHS size: {terms: 11, types: 10, coercions: 0, joins: 0/0}
 T18982.$wi :: forall {a} {e}. (a GHC.Prim.~# Int) => e -> GHC.Prim.Int# -> GHC.Prim.Int#


=====================================
testsuite/tests/stranal/should_compile/T20663.stderr
=====================================
@@ -68,7 +68,7 @@ T20663.$tcGram2 = GHC.Types.TrNameS T20663.$tcGram3
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T20663.$tcGram :: GHC.Types.TyCon
-T20663.$tcGram = GHC.Types.TyCon 14476255489265172493##64 4126058292614824653##64 T20663.$trModule T20663.$tcGram2 0# T20663.$tcGram1
+T20663.$tcGram = GHC.Types.TyCon 14476255489265172493#Word64 4126058292614824653#Word64 T20663.$trModule T20663.$tcGram2 0# T20663.$tcGram1
 
 -- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
 $krep2 :: GHC.Types.KindRep
@@ -92,7 +92,7 @@ T20663.$tc'Gram2 = GHC.Types.TrNameS T20663.$tc'Gram3
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T20663.$tc'Gram :: GHC.Types.TyCon
-T20663.$tc'Gram = GHC.Types.TyCon 6930635511997833813##64 5635348526001679009##64 T20663.$trModule T20663.$tc'Gram2 0# T20663.$tc'Gram1
+T20663.$tc'Gram = GHC.Types.TyCon 6930635511997833813#Word64 5635348526001679009#Word64 T20663.$trModule T20663.$tc'Gram2 0# T20663.$tc'Gram1
 
 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
 T20663.$tcFoo2 :: GHC.Prim.Addr#
@@ -104,7 +104,7 @@ T20663.$tcFoo1 = GHC.Types.TrNameS T20663.$tcFoo2
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T20663.$tcFoo :: GHC.Types.TyCon
-T20663.$tcFoo = GHC.Types.TyCon 4170886864186800403##64 12966498080784616609##64 T20663.$trModule T20663.$tcFoo1 0# GHC.Types.krep$*
+T20663.$tcFoo = GHC.Types.TyCon 4170886864186800403#Word64 12966498080784616609#Word64 T20663.$trModule T20663.$tcFoo1 0# GHC.Types.krep$*
 
 -- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
 $krep4 :: GHC.Types.KindRep
@@ -128,7 +128,7 @@ T20663.$tc'Foo2 = GHC.Types.TrNameS T20663.$tc'Foo3
 
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T20663.$tc'Foo :: GHC.Types.TyCon
-T20663.$tc'Foo = GHC.Types.TyCon 9844518566125716364##64 9262896337475646272##64 T20663.$trModule T20663.$tc'Foo2 0# T20663.$tc'Foo1
+T20663.$tc'Foo = GHC.Types.TyCon 9844518566125716364#Word64 9262896337475646272#Word64 T20663.$trModule T20663.$tc'Foo2 0# T20663.$tc'Foo1
 
 
 


=====================================
testsuite/tests/th/TH_Roles2.stderr
=====================================
@@ -2,12 +2,12 @@ TYPE CONSTRUCTORS
   data type T{2} :: forall k. k -> *
     roles nominal representational
 Dependent modules: []
-Dependent packages: [base-4.16.0.0, template-haskell-2.18.0.0]
+Dependent packages: [base-4.17.0.0, template-haskell-2.19.0.0]
 
 ==================== Typechecker ====================
 TH_Roles2.$tcT
   = GHC.Types.TyCon
-      11651627537942629178##64 11503899791410937231##64
+      11651627537942629178#Word64 11503899791410937231#Word64
       TH_Roles2.$trModule (GHC.Types.TrNameS "T"#) 1# $krep
 $krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
 $krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep GHC.Types.krep$*


=====================================
testsuite/tests/typecheck/should_compile/T18406b.stderr
=====================================
@@ -11,11 +11,11 @@ Dependent packages: [base-4.17.0.0]
 ==================== Typechecker ====================
 Bug.$tcC
   = GHC.Types.TyCon
-      12754692886077552850##64 18375870125396612007##64 Bug.$trModule
-      (GHC.Types.TrNameS "C"#) 0# $krep
+      12754692886077552850#Word64 18375870125396612007#Word64
+      Bug.$trModule (GHC.Types.TrNameS "C"#) 0# $krep
 Bug.$tc'C:C
   = GHC.Types.TyCon
-      302756782745842909##64 14248103394115774781##64 Bug.$trModule
+      302756782745842909#Word64 14248103394115774781#Word64 Bug.$trModule
       (GHC.Types.TrNameS "'C:C"#) 2# $krep
 $krep [InlPrag=[~]]
   = GHC.Types.KindRepTyConApp


=====================================
testsuite/tests/typecheck/should_compile/T18529.stderr
=====================================
@@ -11,11 +11,11 @@ Dependent packages: [base-4.17.0.0]
 ==================== Typechecker ====================
 Bug.$tcC
   = GHC.Types.TyCon
-      12754692886077552850##64 18375870125396612007##64 Bug.$trModule
-      (GHC.Types.TrNameS "C"#) 0# $krep
+      12754692886077552850#Word64 18375870125396612007#Word64
+      Bug.$trModule (GHC.Types.TrNameS "C"#) 0# $krep
 Bug.$tc'C:C
   = GHC.Types.TyCon
-      302756782745842909##64 14248103394115774781##64 Bug.$trModule
+      302756782745842909#Word64 14248103394115774781#Word64 Bug.$trModule
       (GHC.Types.TrNameS "'C:C"#) 2# $krep
 $krep [InlPrag=[~]]
   = GHC.Types.KindRepTyConApp



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/646969d4da90b8c52c3b3320b01f26452d786380
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/20221129/23593836/attachment-0001.html>


More information about the ghc-commits mailing list