Ben Gamari pushed to branch wip/ghc-9.12 at Glasgow Haskell Compiler / GHC

Commits:

23 changed files:

Changes:

  • compiler/GHC/Builtin/Types.hs
    ... ... @@ -78,6 +78,7 @@ module GHC.Builtin.Types (
    78 78
             promotedTupleDataCon,
    
    79 79
             unitTyCon, unitDataCon, unitDataConId, unitTy, unitTyConKey,
    
    80 80
             soloTyCon,
    
    81
    +        soloDataConName,
    
    81 82
             pairTyCon, mkPromotedPairTy, isPromotedPairType,
    
    82 83
             unboxedUnitTy,
    
    83 84
             unboxedUnitTyCon, unboxedUnitDataCon,
    
    ... ... @@ -895,7 +896,6 @@ isBuiltInOcc_maybe occ =
    895 896
           ":"    -> Just consDataConName
    
    896 897
     
    
    897 898
           -- function tycon
    
    898
    -      "FUN"  -> Just fUNTyConName
    
    899 899
           "->"  -> Just unrestrictedFunTyConName
    
    900 900
     
    
    901 901
           -- tuple data/tycon
    
    ... ... @@ -1054,40 +1054,36 @@ isPunOcc_maybe mod occ
    1054 1054
         isCTupleOcc_maybe  mod occ <|>
    
    1055 1055
         isSumTyOcc_maybe   mod occ
    
    1056 1056
     
    
    1057
    -mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName
    
    1058
    --- No need to cache these, the caching is done in mk_tuple
    
    1059
    -mkTupleOcc ns Boxed   ar = mkOccName ns (mkBoxedTupleStr ns ar)
    
    1060
    -mkTupleOcc ns Unboxed ar = mkOccName ns (mkUnboxedTupleStr ns ar)
    
    1057
    +mkTupleOcc :: NameSpace -> Boxity -> Arity -> (OccName, BuiltInSyntax)
    
    1058
    +mkTupleOcc ns b ar = (mkOccName ns str, built_in)
    
    1059
    +  where (str, built_in) = mkTupleStr' ns b ar
    
    1061 1060
     
    
    1062 1061
     mkCTupleOcc :: NameSpace -> Arity -> OccName
    
    1063 1062
     mkCTupleOcc ns ar = mkOccName ns (mkConstraintTupleStr ar)
    
    1064 1063
     
    
    1065 1064
     mkTupleStr :: Boxity -> NameSpace -> Arity -> String
    
    1066
    -mkTupleStr Boxed   = mkBoxedTupleStr
    
    1067
    -mkTupleStr Unboxed = mkUnboxedTupleStr
    
    1068
    -
    
    1069
    -mkBoxedTupleStr :: NameSpace -> Arity -> String
    
    1070
    -mkBoxedTupleStr ns 0
    
    1071
    -  | isDataConNameSpace ns = "()"
    
    1072
    -  | otherwise             = "Unit"
    
    1073
    -mkBoxedTupleStr ns 1
    
    1074
    -  | isDataConNameSpace ns = "MkSolo"  -- See Note [One-tuples]
    
    1075
    -  | otherwise             = "Solo"
    
    1076
    -mkBoxedTupleStr ns ar
    
    1077
    -  | isDataConNameSpace ns = '(' : commas ar ++ ")"
    
    1078
    -  | otherwise             = "Tuple" ++ showInt ar ""
    
    1079
    -
    
    1080
    -
    
    1081
    -mkUnboxedTupleStr :: NameSpace -> Arity -> String
    
    1082
    -mkUnboxedTupleStr ns 0
    
    1083
    -  | isDataConNameSpace ns = "(##)"
    
    1084
    -  | otherwise             = "Unit#"
    
    1085
    -mkUnboxedTupleStr ns 1
    
    1086
    -  | isDataConNameSpace ns = "MkSolo#"  -- See Note [One-tuples]
    
    1087
    -  | otherwise             = "Solo#"
    
    1088
    -mkUnboxedTupleStr ns ar
    
    1089
    -  | isDataConNameSpace ns = "(#" ++ commas ar ++ "#)"
    
    1090
    -  | otherwise             = "Tuple" ++ show ar ++ "#"
    
    1065
    +mkTupleStr b ns ar = str
    
    1066
    +  where (str, _) = mkTupleStr' ns b ar
    
    1067
    +
    
    1068
    +mkTupleStr' :: NameSpace -> Boxity -> Arity -> (String, BuiltInSyntax)
    
    1069
    +mkTupleStr' ns Boxed 0
    
    1070
    +  | isDataConNameSpace ns = ("()", BuiltInSyntax)
    
    1071
    +  | otherwise             = ("Unit", UserSyntax)
    
    1072
    +mkTupleStr' ns Boxed 1
    
    1073
    +  | isDataConNameSpace ns = ("MkSolo", UserSyntax)  -- See Note [One-tuples]
    
    1074
    +  | otherwise             = ("Solo",   UserSyntax)
    
    1075
    +mkTupleStr' ns Boxed ar
    
    1076
    +  | isDataConNameSpace ns = ('(' : commas ar ++ ")", BuiltInSyntax)
    
    1077
    +  | otherwise             = ("Tuple" ++ showInt ar "", UserSyntax)
    
    1078
    +mkTupleStr' ns Unboxed 0
    
    1079
    +  | isDataConNameSpace ns = ("(##)",  BuiltInSyntax)
    
    1080
    +  | otherwise             = ("Unit#", UserSyntax)
    
    1081
    +mkTupleStr' ns Unboxed 1
    
    1082
    +  | isDataConNameSpace ns = ("MkSolo#", UserSyntax) -- See Note [One-tuples]
    
    1083
    +  | otherwise             = ("Solo#",   UserSyntax)
    
    1084
    +mkTupleStr' ns Unboxed ar
    
    1085
    +  | isDataConNameSpace ns = ("(#" ++ commas ar ++ "#)", BuiltInSyntax)
    
    1086
    +  | otherwise             = ("Tuple" ++ show ar ++ "#", UserSyntax)
    
    1091 1087
     
    
    1092 1088
     mkConstraintTupleStr :: Arity -> String
    
    1093 1089
     mkConstraintTupleStr 0 = "CUnit"
    
    ... ... @@ -1243,10 +1239,10 @@ mk_tuple Boxed arity = (tycon, tuple_con)
    1243 1239
     
    
    1244 1240
         boxity  = Boxed
    
    1245 1241
         modu    = gHC_INTERNAL_TUPLE
    
    1246
    -    tc_name = mkWiredInName modu (mkTupleOcc tcName boxity arity) tc_uniq
    
    1247
    -                         (ATyCon tycon) UserSyntax
    
    1248
    -    dc_name = mkWiredInName modu (mkTupleOcc dataName boxity arity) dc_uniq
    
    1249
    -                            (AConLike (RealDataCon tuple_con)) BuiltInSyntax
    
    1242
    +    tc_name = mkWiredInName modu occ tc_uniq (ATyCon tycon) built_in
    
    1243
    +      where (occ, built_in) = mkTupleOcc tcName boxity arity
    
    1244
    +    dc_name = mkWiredInName modu occ dc_uniq (AConLike (RealDataCon tuple_con)) built_in
    
    1245
    +      where (occ, built_in) = mkTupleOcc dataName boxity arity
    
    1250 1246
         tc_uniq = mkTupleTyConUnique   boxity arity
    
    1251 1247
         dc_uniq = mkTupleDataConUnique boxity arity
    
    1252 1248
     
    
    ... ... @@ -1277,10 +1273,10 @@ mk_tuple Unboxed arity = (tycon, tuple_con)
    1277 1273
     
    
    1278 1274
         boxity  = Unboxed
    
    1279 1275
         modu    = gHC_TYPES
    
    1280
    -    tc_name = mkWiredInName modu (mkTupleOcc tcName boxity arity) tc_uniq
    
    1281
    -                         (ATyCon tycon) UserSyntax
    
    1282
    -    dc_name = mkWiredInName modu (mkTupleOcc dataName boxity arity) dc_uniq
    
    1283
    -                            (AConLike (RealDataCon tuple_con)) BuiltInSyntax
    
    1276
    +    tc_name = mkWiredInName modu occ tc_uniq (ATyCon tycon) built_in
    
    1277
    +      where (occ, built_in) = mkTupleOcc tcName boxity arity
    
    1278
    +    dc_name = mkWiredInName modu occ dc_uniq (AConLike (RealDataCon tuple_con)) built_in
    
    1279
    +      where (occ, built_in) = mkTupleOcc dataName boxity arity
    
    1284 1280
         tc_uniq = mkTupleTyConUnique   boxity arity
    
    1285 1281
         dc_uniq = mkTupleDataConUnique boxity arity
    
    1286 1282
     
    
    ... ... @@ -1344,6 +1340,9 @@ soloTyCon = tupleTyCon Boxed 1
    1344 1340
     soloTyConName :: Name
    
    1345 1341
     soloTyConName = tyConName soloTyCon
    
    1346 1342
     
    
    1343
    +soloDataConName :: Name
    
    1344
    +soloDataConName = tupleDataConName Boxed 1
    
    1345
    +
    
    1347 1346
     pairTyCon :: TyCon
    
    1348 1347
     pairTyCon = tupleTyCon Boxed 2
    
    1349 1348
     
    

  • compiler/GHC/Types/Name/Ppr.hs
    ... ... @@ -123,7 +123,8 @@ mkQualName env = qual_name where
    123 123
                 , fUNTyConName, unrestrictedFunTyConName
    
    124 124
                 , oneDataConName
    
    125 125
                 , listTyConName
    
    126
    -            , manyDataConName ]
    
    126
    +            , manyDataConName
    
    127
    +            , soloDataConName ]
    
    127 128
               || isJust (isTupleTyOcc_maybe mod occ)
    
    128 129
               || isJust (isSumTyOcc_maybe mod occ)
    
    129 130
     
    

  • docs/users_guide/9.12.3-notes.rst
    1
    +.. _release-9-12-3:
    
    2
    +
    
    3
    +Version 9.12.3
    
    4
    +==============
    
    5
    +
    
    6
    +The significant changes to the various parts of the compiler are listed in the
    
    7
    +following sections. See the `migration guide
    
    8
    +<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.12>`_ on the GHC Wiki
    
    9
    +for specific guidance on migrating programs to this release.
    
    10
    +
    
    11
    +Compiler
    
    12
    +~~~~~~~~
    
    13
    +
    
    14
    +- Fixed re-exports of ``MkSolo`` and ``MkSolo#`` (:ghc-ticket:`25182`)
    
    15
    +- Fixed the behavior of ``Language.Haskell.TH.mkName "FUN"`` (:ghc-ticket:`25174`)
    
    16
    +
    
    17
    +Included libraries
    
    18
    +~~~~~~~~~~~~~~~~~~
    
    19
    +
    
    20
    +The package database provided with this distribution also contains a number of
    
    21
    +packages other than GHC itself. See the changelogs provided with these packages
    
    22
    +for further change information.
    
    23
    +
    
    24
    +.. ghc-package-list::
    
    25
    +
    
    26
    +    compiler/ghc.cabal:                                  The compiler itself
    
    27
    +    libraries/array/array.cabal:                         Dependency of ``ghc`` library
    
    28
    +    libraries/base/base.cabal:                           Core library
    
    29
    +    libraries/binary/binary.cabal:                       Dependency of ``ghc`` library
    
    30
    +    libraries/bytestring/bytestring.cabal:               Dependency of ``ghc`` library
    
    31
    +    libraries/Cabal/Cabal/Cabal.cabal:                   Dependency of ``ghc-pkg`` utility
    
    32
    +    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:     Dependency of ``ghc-pkg`` utility
    
    33
    +    libraries/containers/containers/containers.cabal:    Dependency of ``ghc`` library
    
    34
    +    libraries/deepseq/deepseq.cabal:                     Dependency of ``ghc`` library
    
    35
    +    libraries/directory/directory.cabal:                 Dependency of ``ghc`` library
    
    36
    +    libraries/exceptions/exceptions.cabal:               Dependency of ``ghc`` and ``haskeline`` library
    
    37
    +    libraries/file-io/file-io.cabal:                     Dependency of ``directory`` library
    
    38
    +    libraries/filepath/filepath.cabal:                   Dependency of ``ghc`` library
    
    39
    +    libraries/ghc-boot/ghc-boot.cabal:                   Internal compiler library
    
    40
    +    libraries/ghc-boot-th/ghc-boot-th.cabal:             Internal compiler library
    
    41
    +    libraries/ghc-compact/ghc-compact.cabal:             Core library
    
    42
    +    libraries/ghc-experimental/ghc-experimental.cabal:   Core library
    
    43
    +    libraries/ghc-heap/ghc-heap.cabal:                   GHC heap-walking library
    
    44
    +    libraries/ghci/ghci.cabal:                           The REPL interface
    
    45
    +    libraries/ghc-internal/ghc-internal.cabal:           Core library
    
    46
    +    libraries/ghc-platform/ghc-platform.cabal:           Internal library
    
    47
    +    libraries/ghc-prim/ghc-prim.cabal:                   Core library
    
    48
    +    libraries/haskeline/haskeline.cabal:                 Dependency of ``ghci`` executable
    
    49
    +    libraries/hpc/hpc.cabal:                             Dependency of ``hpc`` executable
    
    50
    +    libraries/integer-gmp/integer-gmp.cabal:             Core library
    
    51
    +    libraries/mtl/mtl.cabal:                             Dependency of ``Cabal`` library
    
    52
    +    libraries/os-string/os-string.cabal:                 Dependency of ``filepath`` library
    
    53
    +    libraries/parsec/parsec.cabal:                       Dependency of ``Cabal`` library
    
    54
    +    libraries/pretty/pretty.cabal:                       Dependency of ``ghc`` library
    
    55
    +    libraries/process/process.cabal:                     Dependency of ``ghc`` library
    
    56
    +    libraries/semaphore-compat/semaphore-compat.cabal:   Dependency of ``ghc`` library
    
    57
    +    libraries/stm/stm.cabal:                             Dependency of ``haskeline`` library
    
    58
    +    libraries/template-haskell/template-haskell.cabal:   Core library
    
    59
    +    libraries/terminfo/terminfo.cabal:                   Dependency of ``haskeline`` library
    
    60
    +    libraries/text/text.cabal:                           Dependency of ``Cabal`` library
    
    61
    +    libraries/time/time.cabal:                           Dependency of ``ghc`` library
    
    62
    +    libraries/transformers/transformers.cabal:           Dependency of ``ghc`` library
    
    63
    +    libraries/unix/unix.cabal:                           Dependency of ``ghc`` library
    
    64
    +    libraries/Win32/Win32.cabal:                         Dependency of ``ghc`` library
    
    65
    +    libraries/xhtml/xhtml.cabal:                         Dependency of ``haddock`` executable
    
    66
    +    utils/haddock/haddock-api/haddock-api.cabal:         Dependency of ``haddock`` executable
    
    67
    +    utils/haddock/haddock-library/haddock-library.cabal: Dependency of ``haddock`` executable
    
    68
    +
    
    69
    +

  • docs/users_guide/release-notes.rst
    ... ... @@ -6,3 +6,4 @@ Release notes
    6 6
     
    
    7 7
        9.12.1-notes
    
    8 8
        9.12.2-notes
    
    9
    +   9.12.3-notes

  • hadrian/cabal.project
    ... ... @@ -4,7 +4,7 @@ packages: ./
    4 4
     
    
    5 5
     -- This essentially freezes the build plan for hadrian
    
    6 6
     -- It would be wise to keep this up to date with the state set in .gitlab/ci.sh.
    
    7
    -index-state: 2024-10-30T22:56:00Z
    
    7
    +index-state: 2025-03-18T00:00:00Z
    
    8 8
     
    
    9 9
     -- unordered-containers-0.2.20-r1 requires template-haskell < 2.22
    
    10 10
     -- ghc-9.10 has template-haskell-2.22.0.0
    

  • hadrian/hadrian.cabal
    ... ... @@ -191,4 +191,4 @@ executable hadrian
    191 191
         if flag(selftest)
    
    192 192
           other-modules:   Rules.Selftest
    
    193 193
           cpp-options:     -DHADRIAN_ENABLE_SELFTEST
    
    194
    -      build-depends:   QuickCheck           >= 2.6     && < 2.15
    194
    +      build-depends:   QuickCheck           >= 2.6     && < 2.16

  • libraries/base/src/GHC/Base.hs
    ... ... @@ -278,7 +278,7 @@ import GHC.Internal.IO (seq#)
    278 278
     import GHC.Internal.Maybe
    
    279 279
     import GHC.Types hiding (
    
    280 280
       Unit#,
    
    281
    -  Solo#,
    
    281
    +  Solo#(..),
    
    282 282
       Tuple0#,
    
    283 283
       Tuple1#,
    
    284 284
       Tuple2#,
    

  • libraries/base/src/GHC/Exts.hs
    ... ... @@ -267,7 +267,7 @@ import GHC.Types hiding (
    267 267
       -- GHC's internal representation of 'TyCon's, for 'Typeable'
    
    268 268
       Module, TrName, TyCon, TypeLitSort, KindRep, KindBndr,
    
    269 269
       Unit#,
    
    270
    -  Solo#,
    
    270
    +  Solo#(..),
    
    271 271
       Tuple0#,
    
    272 272
       Tuple1#,
    
    273 273
       Tuple2#,
    

  • testsuite/tests/core-to-stg/T24124.stderr
    ... ... @@ -24,7 +24,7 @@ T15226b.testFun1
    24 24
             case y of conrep {
    
    25 25
             __DEFAULT ->
    
    26 26
             case T15226b.MkStrictPair [sat conrep] of sat {
    
    27
    -        __DEFAULT -> MkSolo# [sat];
    
    27
    +        __DEFAULT -> GHC.Types.MkSolo# [sat];
    
    28 28
             };
    
    29 29
             };
    
    30 30
             };
    

  • testsuite/tests/interface-stability/ghc-experimental-exports.stdout
    ... ... @@ -4474,6 +4474,7 @@ module GHC.PrimOps where
    4474 4474
       type role MVar# nominal representational
    
    4475 4475
       type MVar# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType
    
    4476 4476
       data MVar# a b
    
    4477
    +  MkSolo# :: forall (k :: RuntimeRep) (a :: TYPE k). a -> (# a #)
    
    4477 4478
       type MultMul :: Multiplicity -> Multiplicity -> Multiplicity
    
    4478 4479
       type family MultMul a b where
    
    4479 4480
         forall (x :: Multiplicity). MultMul One x = x
    
    ... ... @@ -7331,9 +7332,9 @@ module Prelude.Experimental where
    7331 7332
       data List a = ...
    
    7332 7333
       pattern Solo :: forall a. a -> Solo a
    
    7333 7334
       type Solo :: * -> *
    
    7334
    -  data Solo a = ...
    
    7335
    +  data Solo a = MkSolo a
    
    7335 7336
       type Solo# :: forall (k :: GHC.Types.RuntimeRep). TYPE k -> TYPE (GHC.Types.TupleRep '[k])
    
    7336
    -  data Solo# a = ...
    
    7337
    +  data Solo# a = MkSolo# a
    
    7337 7338
       type Sum10# :: forall (k0 :: GHC.Types.RuntimeRep) (k1 :: GHC.Types.RuntimeRep) (k2 :: GHC.Types.RuntimeRep) (k3 :: GHC.Types.RuntimeRep) (k4 :: GHC.Types.RuntimeRep) (k5 :: GHC.Types.RuntimeRep) (k6 :: GHC.Types.RuntimeRep) (k7 :: GHC.Types.RuntimeRep) (k8 :: GHC.Types.RuntimeRep) (k9 :: GHC.Types.RuntimeRep). TYPE k0 -> TYPE k1 -> TYPE k2 -> TYPE k3 -> TYPE k4 -> TYPE k5 -> TYPE k6 -> TYPE k7 -> TYPE k8 -> TYPE k9 -> TYPE (GHC.Types.SumRep [k0, k1, k2, k3, k4, k5, k6, k7, k8, k9])
    
    7338 7339
       data Sum10# a b c d e f g h i j = ...
    
    7339 7340
       type Sum11# :: forall (k0 :: GHC.Types.RuntimeRep) (k1 :: GHC.Types.RuntimeRep) (k2 :: GHC.Types.RuntimeRep) (k3 :: GHC.Types.RuntimeRep) (k4 :: GHC.Types.RuntimeRep) (k5 :: GHC.Types.RuntimeRep) (k6 :: GHC.Types.RuntimeRep) (k7 :: GHC.Types.RuntimeRep) (k8 :: GHC.Types.RuntimeRep) (k9 :: GHC.Types.RuntimeRep) (k10 :: GHC.Types.RuntimeRep). TYPE k0 -> TYPE k1 -> TYPE k2 -> TYPE k3 -> TYPE k4 -> TYPE k5 -> TYPE k6 -> TYPE k7 -> TYPE k8 -> TYPE k9 -> TYPE k10 -> TYPE (GHC.Types.SumRep [k0, k1, k2, k3, k4, k5, k6, k7, k8, k9, k10])
    

  • testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
    ... ... @@ -4474,6 +4474,7 @@ module GHC.PrimOps where
    4474 4474
       type role MVar# nominal representational
    
    4475 4475
       type MVar# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType
    
    4476 4476
       data MVar# a b
    
    4477
    +  MkSolo# :: forall (k :: RuntimeRep) (a :: TYPE k). a -> (# a #)
    
    4477 4478
       type MultMul :: Multiplicity -> Multiplicity -> Multiplicity
    
    4478 4479
       type family MultMul a b where
    
    4479 4480
         forall (x :: Multiplicity). MultMul One x = x
    
    ... ... @@ -7334,9 +7335,9 @@ module Prelude.Experimental where
    7334 7335
       data List a = ...
    
    7335 7336
       pattern Solo :: forall a. a -> Solo a
    
    7336 7337
       type Solo :: * -> *
    
    7337
    -  data Solo a = ...
    
    7338
    +  data Solo a = MkSolo a
    
    7338 7339
       type Solo# :: forall (k :: GHC.Types.RuntimeRep). TYPE k -> TYPE (GHC.Types.TupleRep '[k])
    
    7339
    -  data Solo# a = ...
    
    7340
    +  data Solo# a = MkSolo# a
    
    7340 7341
       type Sum10# :: forall (k0 :: GHC.Types.RuntimeRep) (k1 :: GHC.Types.RuntimeRep) (k2 :: GHC.Types.RuntimeRep) (k3 :: GHC.Types.RuntimeRep) (k4 :: GHC.Types.RuntimeRep) (k5 :: GHC.Types.RuntimeRep) (k6 :: GHC.Types.RuntimeRep) (k7 :: GHC.Types.RuntimeRep) (k8 :: GHC.Types.RuntimeRep) (k9 :: GHC.Types.RuntimeRep). TYPE k0 -> TYPE k1 -> TYPE k2 -> TYPE k3 -> TYPE k4 -> TYPE k5 -> TYPE k6 -> TYPE k7 -> TYPE k8 -> TYPE k9 -> TYPE (GHC.Types.SumRep [k0, k1, k2, k3, k4, k5, k6, k7, k8, k9])
    
    7341 7342
       data Sum10# a b c d e f g h i j = ...
    
    7342 7343
       type Sum11# :: forall (k0 :: GHC.Types.RuntimeRep) (k1 :: GHC.Types.RuntimeRep) (k2 :: GHC.Types.RuntimeRep) (k3 :: GHC.Types.RuntimeRep) (k4 :: GHC.Types.RuntimeRep) (k5 :: GHC.Types.RuntimeRep) (k6 :: GHC.Types.RuntimeRep) (k7 :: GHC.Types.RuntimeRep) (k8 :: GHC.Types.RuntimeRep) (k9 :: GHC.Types.RuntimeRep) (k10 :: GHC.Types.RuntimeRep). TYPE k0 -> TYPE k1 -> TYPE k2 -> TYPE k3 -> TYPE k4 -> TYPE k5 -> TYPE k6 -> TYPE k7 -> TYPE k8 -> TYPE k9 -> TYPE k10 -> TYPE (GHC.Types.SumRep [k0, k1, k2, k3, k4, k5, k6, k7, k8, k9, k10])
    

  • testsuite/tests/rename/should_compile/ReExportTuples.hs
    1
    +module ReExportTuples (module Data.Tuple) where
    
    2
    +-- Re-export the entire Data.Tuple module at once
    
    3
    +
    
    4
    +import Data.Tuple

  • testsuite/tests/rename/should_compile/T25182.hs
    1
    +module T25182 where
    
    2
    +
    
    3
    +import ReExportTuples
    
    4
    +
    
    5
    +s :: Solo String
    
    6
    +s = MkSolo "hello"
    \ No newline at end of file

  • testsuite/tests/rename/should_compile/all.T
    ... ... @@ -225,3 +225,4 @@ test('T14032d', normal, compile, [''])
    225 225
     test('T24621_normal', normal, compile, [''])
    
    226 226
     test('T24621_th', req_th, compile, [''])
    
    227 227
     test('T24732', normal, compile_and_run, ['-package "base(Prelude, Text.Printf as P\')"'])
    
    228
    +test('T25182', [extra_files(['ReExportTuples.hs'])], multimod_compile, ['T25182', '-v0'])

  • testsuite/tests/simplStg/should_compile/T15226b.stderr
    ... ... @@ -20,7 +20,7 @@ T15226b.bar1
    20 20
               sat [Occ=Once1] :: T15226b.Str (GHC.Internal.Maybe.Maybe a)
    
    21 21
               [LclId] =
    
    22 22
                   T15226b.Str! [sat];
    
    23
    -        } in  MkSolo# [sat];
    
    23
    +        } in  GHC.Types.MkSolo# [sat];
    
    24 24
             };
    
    25 25
     
    
    26 26
     T15226b.bar
    

  • testsuite/tests/th/FunNameTH.hs
    1
    +{-# LANGUAGE TemplateHaskell #-}
    
    2
    +
    
    3
    +module FunNameTH where
    
    4
    +
    
    5
    +import Language.Haskell.TH
    
    6
    +
    
    7
    +f1 :: forall a. $(conT (mkName "->")) [a] Bool
    
    8
    +f1 = null
    
    9
    +
    
    10
    +f2 :: forall a. $(conT ''(->)) [a] Bool
    
    11
    +f2 = null
    \ No newline at end of file

  • testsuite/tests/th/T13776.hs
    ... ... @@ -10,6 +10,9 @@ spliceTy1 = (1,2)
    10 10
     spliceTy2 :: $(conT ''[] `appT` conT ''Int)
    
    11 11
     spliceTy2 = []
    
    12 12
     
    
    13
    +spliceTy3 :: $(conT ''(->)) [Int] Int
    
    14
    +spliceTy3 = sum
    
    15
    +
    
    13 16
     spliceExp1 :: (Int, Int)
    
    14 17
     spliceExp1 = $(conE '(,) `appE` litE (integerL 1) `appE` litE (integerL 1))
    
    15 18
     
    

  • testsuite/tests/th/T13776.stderr
    1
    +T13776.hs:13:15-27: Splicing type conT ''(->) ======> (->)
    
    1 2
     T13776.hs:10:15-43: Splicing type
    
    2 3
         conT ''[] `appT` conT ''Int ======> [] Int
    
    3 4
     T13776.hs:7:15-62: Splicing type
    
    4 5
         conT ''(,) `appT` conT ''Int `appT` conT ''Int ======> (,) Int Int
    
    5
    -T13776.hs:14:15-75: Splicing expression
    
    6
    +T13776.hs:17:15-75: Splicing expression
    
    6 7
         conE '(,) `appE` litE (integerL 1) `appE` litE (integerL 1)
    
    7 8
       ======>
    
    8 9
         (,) 1 1
    
    9
    -T13776.hs:17:15-24: Splicing expression conE '[] ======> []
    
    10
    -T13776.hs:20:13-62: Splicing pattern
    
    10
    +T13776.hs:20:15-24: Splicing expression conE '[] ======> []
    
    11
    +T13776.hs:23:13-62: Splicing pattern
    
    11 12
         conP '(,) [litP (integerL 1), litP (integerL 1)] ======> (,) 1 1
    
    12
    -T13776.hs:23:13-25: Splicing pattern conP '[] [] ======> []
    13
    +T13776.hs:26:13-25: Splicing pattern conP '[] [] ======> []

  • testsuite/tests/th/T25174.hs
    1
    +{-# LANGUAGE TemplateHaskell #-}
    
    2
    +
    
    3
    +module T25174 where
    
    4
    +
    
    5
    +import Language.Haskell.TH
    
    6
    +
    
    7
    +data FUN a b = MkFUN (a -> b)
    
    8
    +
    
    9
    +evenFUN :: $(conT (mkName "FUN")) Int Bool
    
    10
    +evenFUN = MkFUN even
    
    11
    +

  • testsuite/tests/th/all.T
    ... ... @@ -631,3 +631,5 @@ test('T25252',
    631 631
        req_c],
    
    632 632
       compile_and_run, ['-fPIC T25252_c.c'])
    
    633 633
     test('T25083', [extra_files(['T25083_A.hs', 'T25083_B.hs'])], multimod_compile_and_run, ['T25083', '-v0 -j'])
    
    634
    +test('T25174', normal, compile, [''])
    
    635
    +test('FunNameTH', normal, compile, [''])

  • testsuite/tests/typecheck/should_compile/holes.stderr
    ... ... @@ -87,7 +87,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
    87 87
             Nothing :: forall a. Maybe a
    
    88 88
             Just :: forall a. a -> Maybe a
    
    89 89
             [] :: forall a. [a]
    
    90
    -        MkSolo :: forall a. a -> Solo a
    
    91 90
             asTypeOf :: forall a. a -> a -> a
    
    92 91
             id :: forall a. a -> a
    
    93 92
             until :: forall a. (a -> Bool) -> (a -> a) -> a -> a
    

  • testsuite/tests/typecheck/should_compile/holes3.stderr
    ... ... @@ -90,7 +90,6 @@ holes3.hs:11:15: error: [GHC-88464]
    90 90
             Nothing :: forall a. Maybe a
    
    91 91
             Just :: forall a. a -> Maybe a
    
    92 92
             [] :: forall a. [a]
    
    93
    -        MkSolo :: forall a. a -> Solo a
    
    94 93
             asTypeOf :: forall a. a -> a -> a
    
    95 94
             id :: forall a. a -> a
    
    96 95
             until :: forall a. (a -> Bool) -> (a -> a) -> a -> a
    

  • testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
    1 1
     [1 of 2] Compiling ValidHoleFits    ( ValidHoleFits.hs, ValidHoleFits.o )
    
    2 2
     [2 of 2] Compiling Foo              ( valid_hole_fits.hs, valid_hole_fits.o )
    
    3
    -
    
    4 3
     valid_hole_fits.hs:9:6: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)]
    
    5 4
         Variable not in scope: putStrLn :: String -> IO ()
    
    6 5
         Suggested fixes:
    
    ... ... @@ -148,9 +147,6 @@ valid_hole_fits.hs:34:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
    148 147
               with Just @Bool
    
    149 148
               (imported from ‘Data.Maybe’ at valid_hole_fits.hs:5:1-17
    
    150 149
                (and originally defined in ‘GHC.Internal.Maybe’))
    
    151
    -        MkSolo :: forall a. a -> Solo a
    
    152
    -          with MkSolo @Bool
    
    153
    -          (bound at <wired into compiler>)
    
    154 150
             id :: forall a. a -> a
    
    155 151
               with id @Bool
    
    156 152
               (imported from ‘Prelude’ at valid_hole_fits.hs:3:1-40
    
    ... ... @@ -259,3 +255,4 @@ valid_hole_fits.hs:41:8: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
    259 255
               with mempty @(String -> IO ())
    
    260 256
               (imported from ‘Prelude’ at valid_hole_fits.hs:3:1-40
    
    261 257
                (and originally defined in ‘GHC.Internal.Base’))
    
    258
    +