Vladislav Zavialov pushed to branch wip/int-index/data-namespace-specifier at Glasgow Haskell Compiler / GHC

Commits:

14 changed files:

Changes:

  • compiler/GHC/Hs/ImpExp.hs
    ... ... @@ -255,15 +255,15 @@ type instance XXIE (GhcPass _) = DataConCantHappen
    255 255
     
    
    256 256
     type instance Anno (LocatedA (IE (GhcPass p))) = SrcSpanAnnA
    
    257 257
     
    
    258
    -ieNameWrapper :: IE (GhcPass p) -> LIEWrappedName (GhcPass p)
    
    259
    -ieNameWrapper (IEVar _ n _)           = n
    
    260
    -ieNameWrapper (IEThingAbs  _ n _)     = n
    
    261
    -ieNameWrapper (IEThingWith _ n _ _ _) = n
    
    262
    -ieNameWrapper (IEThingAll  _ n _)     = n
    
    263
    -ieNameWrapper _ = panic "ieNameWrapper failed pattern match!"
    
    258
    +ieLIEWrappedName :: IE (GhcPass p) -> LIEWrappedName (GhcPass p)
    
    259
    +ieLIEWrappedName (IEVar _ n _)           = n
    
    260
    +ieLIEWrappedName (IEThingAbs  _ n _)     = n
    
    261
    +ieLIEWrappedName (IEThingWith _ n _ _ _) = n
    
    262
    +ieLIEWrappedName (IEThingAll  _ n _)     = n
    
    263
    +ieLIEWrappedName _ = panic "ieLIEWrappedName failed pattern match!"
    
    264 264
     
    
    265 265
     ieName :: IE (GhcPass p) -> IdP (GhcPass p)
    
    266
    -ieName = lieWrappedName . ieNameWrapper
    
    266
    +ieName = lieWrappedName . ieLIEWrappedName
    
    267 267
     
    
    268 268
     ieNames :: IE (GhcPass p) -> [IdP (GhcPass p)]
    
    269 269
     ieNames (IEVar       _ (L _ n) _)      = [ieWrappedName n]
    

  • compiler/GHC/Tc/Errors/Ppr.hs
    ... ... @@ -3294,19 +3294,46 @@ instance Diagnostic TcRnMessage where
    3294 3294
         TcRnImportLookup (ImportLookupBad k _ is ie exts) ->
    
    3295 3295
           let mod_name = moduleName $ is_mod is
    
    3296 3296
               occ = rdrNameOcc $ ieName ie
    
    3297
    -          could_remove kw = [ImportSuggestion occ $ CouldRemoveImportItemKeyword mod_name kw]
    
    3297
    +          could_change_item item_suggestion =
    
    3298
    +            [useExtensionInOrderTo empty LangExt.ExplicitNamespaces | suggest_ext] ++
    
    3299
    +            [ ImportSuggestion occ $
    
    3300
    +              CouldChangeImportItem mod_name item_suggestion ]
    
    3301
    +            where
    
    3302
    +              suggest_ext
    
    3303
    +                | ile_explicit_namespaces exts = False  -- extension already on
    
    3304
    +                | otherwise =
    
    3305
    +                    case item_suggestion of
    
    3306
    +                      -- ImportItemRemove* -> False
    
    3307
    +                      ImportItemRemoveType{}            -> False
    
    3308
    +                      ImportItemRemoveData{}            -> False
    
    3309
    +                      ImportItemRemovePattern{}         -> False
    
    3310
    +                      ImportItemRemoveSubordinateType{} -> False
    
    3311
    +                      ImportItemRemoveSubordinateData{} -> False
    
    3312
    +                      -- ImportItemAdd* -> True
    
    3313
    +                      ImportItemAddType{} -> True
    
    3298 3314
           in case k of
    
    3299
    -        BadImportAvailVar -> could_remove ImportItemUnwantedKeywordType
    
    3315
    +        BadImportAvailVar -> could_change_item ImportItemRemoveType
    
    3300 3316
             BadImportNotExported suggs -> suggs
    
    3301 3317
             BadImportAvailTyCon
    
    3302
    -          | isSymOcc occ -> -- type operators always require the 'type' keyword
    
    3303
    -              [useExtensionInOrderTo empty LangExt.ExplicitNamespaces | not (ile_explicit_namespaces exts) ]
    
    3304
    -              ++ [ ImportSuggestion occ $ CouldAddTypeKeyword mod_name ]
    
    3305
    -          | otherwise    ->
    
    3306
    -              case unLoc (ieNameWrapper ie) of
    
    3307
    -                IEData{}    -> could_remove ImportItemUnwantedKeywordData
    
    3308
    -                IEPattern{} -> could_remove ImportItemUnwantedKeywordPattern
    
    3309
    -                _           -> noHints
    
    3318
    +          -- BadImportAvailTyCon means a name is available in the TcCls namespace
    
    3319
    +          -- but name resolution could not use it. Possible reasons for that:
    
    3320
    +          --   1. Case (TyOp) `import M ((#))` or `import M (data (#))`
    
    3321
    +          --        The user tried to import a type operator without using the `type` keyword,
    
    3322
    +          --        or using a different keyword. Suggested fix: add 'type'.
    
    3323
    +          --   2. Case (DataKw) `import M (data T)`
    
    3324
    +          --        The user tried to import a non-operator type constructor, but mistakenly
    
    3325
    +          --        used the `data` keyword, which restricted the lookup to the value namespace.
    
    3326
    +          --        Suggested fix: remove 'data'; no need to add 'type' for non-operators.
    
    3327
    +          --   3. Case (PatternKw) `import M (pattern T)`
    
    3328
    +          --        Same as the (DataKw) case, mutatis mutandis.
    
    3329
    +          -- Any other case would not have resulted in BadImportAvailTyCon.
    
    3330
    +          | isSymOcc occ    -> could_change_item ImportItemAddType        -- Case (TyOp)
    
    3331
    +          | otherwise       ->  -- Non-operator cases
    
    3332
    +              case unLoc (ieLIEWrappedName ie) of
    
    3333
    +                IEData{}    -> could_change_item ImportItemRemoveData     -- Case (DataKw)
    
    3334
    +                IEPattern{} -> could_change_item ImportItemRemovePattern  -- Case (PatternKw)
    
    3335
    +                _           -> panic "diagnosticHints: unexpected BadImportAvailTyCon"
    
    3336
    +
    
    3310 3337
             BadImportAvailDataCon par  ->
    
    3311 3338
               [ ImportSuggestion occ $
    
    3312 3339
                 ImportDataCon { ies_suggest_import_from = Just mod_name
    
    ... ... @@ -3315,8 +3342,10 @@ instance Diagnostic TcRnMessage where
    3315 3342
                               , ies_suggest_data_keyword    = ile_explicit_namespaces exts
    
    3316 3343
                               , ies_parent = par } ]
    
    3317 3344
             BadImportNotExportedSubordinates{} -> noHints
    
    3318
    -        BadImportNonTypeSubordinates{} -> noHints
    
    3319
    -        BadImportNonDataSubordinates{} -> noHints
    
    3345
    +        BadImportNonTypeSubordinates _ nontype1 ->
    
    3346
    +          could_change_item (ImportItemRemoveSubordinateType (nameOccName . greName <$> nontype1))
    
    3347
    +        BadImportNonDataSubordinates _ nondata1 ->
    
    3348
    +          could_change_item (ImportItemRemoveSubordinateData (nameOccName . greName <$> nondata1))
    
    3320 3349
         TcRnImportLookup{}
    
    3321 3350
           -> noHints
    
    3322 3351
         TcRnUnusedImport{}
    

  • compiler/GHC/Tc/Errors/Types.hs
    ... ... @@ -5841,9 +5841,9 @@ data BadImportKind
    5841 5841
       | BadImportNotExportedSubordinates !GlobalRdrElt (NonEmpty FastString)
    
    5842 5842
       -- | Incorrect @type@ keyword when importing subordinates that aren't types.
    
    5843 5843
       | BadImportNonTypeSubordinates !GlobalRdrElt (NonEmpty GlobalRdrElt)
    
    5844
    -  -- | Incorrect @type@ keyword when importing something which isn't a type.
    
    5845
    -  | BadImportNonDataSubordinates !GlobalRdrElt (NonEmpty GlobalRdrElt)
    
    5846 5844
       -- | Incorrect @data@ keyword when importing something which isn't a term.
    
    5845
    +  | BadImportNonDataSubordinates !GlobalRdrElt (NonEmpty GlobalRdrElt)
    
    5846
    +  -- | Incorrect @type@ keyword when importing something which isn't a type.
    
    5847 5847
       | BadImportAvailVar
    
    5848 5848
       deriving Generic
    
    5849 5849
     
    

  • compiler/GHC/Types/Hint.hs
    ... ... @@ -5,7 +5,7 @@ module GHC.Types.Hint (
    5 5
       , AvailableBindings(..)
    
    6 6
       , InstantiationSuggestion(..)
    
    7 7
       , LanguageExtensionHint(..)
    
    8
    -  , ImportItemUnwantedKeyword(..)
    
    8
    +  , ImportItemSuggestion(..)
    
    9 9
       , ImportSuggestion(..)
    
    10 10
       , HowInScope(..)
    
    11 11
       , SimilarName(..)
    
    ... ... @@ -538,10 +538,13 @@ instance Outputable AssumedDerivingStrategy where
    538 538
     --      replacing <MyStr> as necessary.)
    
    539 539
     data InstantiationSuggestion = InstantiationSuggestion !ModuleName !Module
    
    540 540
     
    
    541
    -data ImportItemUnwantedKeyword =
    
    542
    -    ImportItemUnwantedKeywordType
    
    543
    -  | ImportItemUnwantedKeywordData
    
    544
    -  | ImportItemUnwantedKeywordPattern
    
    541
    +data ImportItemSuggestion =
    
    542
    +    ImportItemRemoveType
    
    543
    +  | ImportItemRemoveData
    
    544
    +  | ImportItemRemovePattern
    
    545
    +  | ImportItemRemoveSubordinateType (NE.NonEmpty OccName)
    
    546
    +  | ImportItemRemoveSubordinateData (NE.NonEmpty OccName)
    
    547
    +  | ImportItemAddType
    
    545 548
     
    
    546 549
     -- | Suggest how to fix an import.
    
    547 550
     data ImportSuggestion
    
    ... ... @@ -549,10 +552,8 @@ data ImportSuggestion
    549 552
       = CouldImportFrom (NE.NonEmpty (Module, ImportedModsVal))
    
    550 553
       -- | Some module exports what we want, but we are explicitly hiding it.
    
    551 554
       | CouldUnhideFrom (NE.NonEmpty (Module, ImportedModsVal))
    
    552
    -  -- | The module exports what we want, but it isn't in the requested namespace.
    
    553
    -  | CouldRemoveImportItemKeyword ModuleName ImportItemUnwantedKeyword
    
    554
    -  -- | The module exports what we want, but it's a type and we have @ExplicitNamespaces@ on.
    
    555
    -  | CouldAddTypeKeyword ModuleName
    
    555
    +  -- | The module exports what we want, but the import item requires modification.
    
    556
    +  | CouldChangeImportItem ModuleName ImportItemSuggestion
    
    556 557
       -- | Suggest importing a data constructor to bring it into scope
    
    557 558
       | ImportDataCon
    
    558 559
           -- | Where to suggest importing the 'DataCon' from.
    

  • compiler/GHC/Types/Hint/Ppr.hs
    ... ... @@ -340,27 +340,39 @@ pprImportSuggestion occ_name (CouldUnhideFrom mods)
    340 340
             [ quotes (ppr mod) <+> parens (text "at" <+> ppr (imv_span imv))
    
    341 341
             | (mod,imv) <- NE.toList mods
    
    342 342
             ])
    
    343
    -pprImportSuggestion occ_name (CouldAddTypeKeyword mod)
    
    344
    -  = vcat [ text "Add the" <+> quotes (text "type")
    
    345
    -          <+> text "keyword to the import statement:"
    
    346
    -         , nest 2 $ text "import"
    
    347
    -            <+> ppr mod
    
    348
    -            <+> parens_sp (text "type" <+> pprPrefixOcc occ_name)
    
    349
    -         ]
    
    343
    +pprImportSuggestion occ_name (CouldChangeImportItem mod kw)
    
    344
    +  = case kw of
    
    345
    +      ImportItemRemoveType    -> remove "type"
    
    346
    +      ImportItemRemoveData    -> remove "data"
    
    347
    +      ImportItemRemovePattern -> remove "pattern"
    
    348
    +      ImportItemRemoveSubordinateType nontype1 -> remove_subordinate "type" (NE.toList nontype1)
    
    349
    +      ImportItemRemoveSubordinateData nondata1 -> remove_subordinate "data" (NE.toList nondata1)
    
    350
    +      ImportItemAddType       -> add "type"
    
    350 351
       where
    
    351 352
         parens_sp d = parens (space <> d <> space)
    
    352
    -pprImportSuggestion occ_name (CouldRemoveImportItemKeyword mod kw)
    
    353
    -  = vcat [ text "Remove the" <+> quotes (text kw_str)
    
    354
    -             <+> text "keyword from the import statement:"
    
    355
    -         , nest 2 $ text "import"
    
    356
    -             <+> ppr mod
    
    357
    -             <+> parens_sp (pprPrefixOcc occ_name) ]
    
    358
    -  where
    
    359
    -    parens_sp d = parens (space <> d <> space)
    
    360
    -    kw_str = case kw of
    
    361
    -      ImportItemUnwantedKeywordType    -> "type"
    
    362
    -      ImportItemUnwantedKeywordData    -> "data"
    
    363
    -      ImportItemUnwantedKeywordPattern -> "pattern"
    
    353
    +    remove kw =
    
    354
    +      vcat [ text "Remove the" <+> quotes (text kw)
    
    355
    +              <+> text "keyword from the import statement:"
    
    356
    +          , nest 2 $ text "import" <+> ppr mod <+> import_list ]
    
    357
    +      where
    
    358
    +        import_list = parens_sp (pprPrefixOcc occ_name)
    
    359
    +    add kw =
    
    360
    +      vcat [ text "Add the" <+> quotes (text kw)
    
    361
    +              <+> text "keyword to the import statement:"
    
    362
    +          , nest 2 $ text "import" <+> ppr mod <+> import_list ]
    
    363
    +      where
    
    364
    +        import_list = parens_sp (text kw <+> pprPrefixOcc occ_name)
    
    365
    +    remove_subordinate kw sub_occs =
    
    366
    +      vcat [ text "Remove the" <+> quotes (text kw)
    
    367
    +              <+> text "keyword" <> plural sub_occs
    
    368
    +              <+> text "from the subordinate import item" <> plural sub_occs <> colon
    
    369
    +          , nest 2 $ text "import" <+> ppr mod <+> import_list ]
    
    370
    +      where
    
    371
    +        parent_item
    
    372
    +          | isSymOcc occ_name = text "type" <+> pprPrefixOcc occ_name
    
    373
    +          | otherwise         = pprPrefixOcc occ_name
    
    374
    +        import_list = parens_sp (parent_item <+> sub_import_list)
    
    375
    +        sub_import_list = parens_sp (hsep (punctuate comma (map pprPrefixOcc sub_occs)))
    
    364 376
     pprImportSuggestion dc_occ (ImportDataCon { ies_suggest_import_from = Nothing
    
    365 377
                                               , ies_parent = parent_occ} )
    
    366 378
       = text "Import the data constructor" <+> quotes (ppr dc_occ) <+>
    

  • docs/users_guide/exts/explicit_namespaces.rst
    1 1
     .. _explicit-namespaces:
    
    2 2
     
    
    3 3
     Explicit namespaces in import/export
    
    4
    -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    4
    +------------------------------------
    
    5 5
     
    
    6 6
     .. extension:: ExplicitNamespaces
    
    7
    -    :shortdesc: Allow use of the keyword ``type`` to specify the namespace of
    
    8
    -        entries in imports and exports.
    
    7
    +    :shortdesc: Allow use of the ``type`` and ``data`` keywords to specify the namespace of
    
    8
    +        entries in import/export lists and in other contexts.
    
    9 9
     
    
    10 10
         :implied by: :extension:`TypeOperators`, :extension:`TypeFamilies`
    
    11 11
         :since: 7.6.1
    
    12 12
         :status: Included in :extension:`GHC2024`
    
    13 13
     
    
    14
    -    Enable use of explicit namespaces in module export lists, patterns, and expressions.
    
    14
    +    Enable use of explicit namespace specifiers ``type`` and ``data``
    
    15
    +    in import declarations, module export lists, fixity declarations,
    
    16
    +    and warning/deprecation pragmas; as well as the ``type`` namespace
    
    17
    +    specifier in expressions and patterns.
    
    18
    +
    
    19
    +The ``type`` keyword in import/export lists
    
    20
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    21
    +
    
    22
    +**Since:** GHC 7.6
    
    15 23
     
    
    16 24
     In an import or export list, such as ::
    
    17 25
     
    
    ... ... @@ -51,17 +59,69 @@ import and export lists:
    51 59
     The extension :extension:`ExplicitNamespaces` is implied by
    
    52 60
     :extension:`TypeOperators` and (for some reason) by :extension:`TypeFamilies`.
    
    53 61
     
    
    54
    -In addition, you can prefix the name of a data constructor in an import or
    
    55
    -export list with the keyword ``data``, to allow the import or export of a data
    
    56
    -constructor without its parent type constructor (see :ref:`patsyn-impexp`).
    
    62
    +The ``data`` keyword in import/export lists
    
    63
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    57 64
     
    
    58
    -Furthermore, :extension:`ExplicitNamespaces` permits the use of the ``type``
    
    59
    -keyword in patterns and expressions::
    
    65
    +**Since:** GHC 9.14
    
    60 66
     
    
    61
    -  f (type t) x = ...       -- in a pattern
    
    62
    -  r = f (type Integer) 10  -- in an expression
    
    67
    +In an import or export list, such as ::
    
    63 68
     
    
    64
    -This is used in conjunction with :extension:`RequiredTypeArguments`.
    
    69
    +  module M( T ) where ...
    
    70
    +    import N( T )
    
    71
    +    ...
    
    72
    +
    
    73
    +the entity ``T`` refers to a *type constructor*, even if there is also a data
    
    74
    +constructor or pattern synonym of the same name.
    
    75
    +
    
    76
    +For a concrete example, consider the declaration ``data Proxy t = Proxy``
    
    77
    +and the following imports: ::
    
    78
    +
    
    79
    +  import Data.Proxy (Proxy(Proxy))  -- imports both constructors
    
    80
    +  import Data.Proxy (Proxy(..))     -- imports both constructors
    
    81
    +  import Data.Proxy (Proxy)         -- imports the type constructor only
    
    82
    +  import Data.Proxy (type Proxy)    -- imports the type constructor only
    
    83
    +
    
    84
    +However, how would one import only the data constructor? There are two options: ::
    
    85
    +
    
    86
    +  import Data.Proxy (data Proxy)     -- imports the data constructor only
    
    87
    +  import Data.Proxy (pattern Proxy)  -- imports the data constructor only
    
    88
    +
    
    89
    +The ``data`` keyword enables the import or export a data constructor without its
    
    90
    +parent type constructor.
    
    91
    +
    
    92
    +The ``pattern`` keyword does the same, with only a few differences:
    
    93
    +
    
    94
    +* Required compiler versions and flags
    
    95
    +
    
    96
    +  - ``pattern`` is provided by the :extension:`PatternSynonyms` extension and requires GHC ≥7.8
    
    97
    +  - ``data`` is enabled by :extension:`ExplicitNamespaces` and requires GHC ≥9.14
    
    98
    +
    
    99
    +  See :ref:`patsyn-impexp`.
    
    100
    +
    
    101
    +* Restrictions on use
    
    102
    +
    
    103
    +  - ``pattern`` is restricted to top-level imports of pattern synonyms and data
    
    104
    +    constructors: ::
    
    105
    +
    
    106
    +      import N (pattern P)      -- ok    (top-level)
    
    107
    +      import N (T(pattern P))   -- error (subordinate)
    
    108
    +      import N (pattern f)      -- error (term or field selector)
    
    109
    +
    
    110
    +  - ``data`` is also permitted in subordinate import/export lists, and is
    
    111
    +    applicable to term declarations (functions and constants) and field
    
    112
    +    selectors: ::
    
    113
    +
    
    114
    +      import N (data P)         -- ok  (top-level)
    
    115
    +      import N (T(data P))      -- ok  (subordinate)
    
    116
    +      import N (data f)         -- ok  (term or field selector)
    
    117
    +
    
    118
    +The ``data`` keyword is preferred over ``pattern`` in import/export lists unless
    
    119
    +there is a need to support older GHC versions.
    
    120
    +
    
    121
    +Explicit namespaces in fixity declarations and warning/deprecation pragmas
    
    122
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    123
    +
    
    124
    +**Since:** GHC 9.10
    
    65 125
     
    
    66 126
     When :extension:`ExplicitNamespaces` is enabled, it is possible to use the
    
    67 127
     ``type`` and ``data`` keywords to specify the namespace of the name used in
    
    ... ... @@ -79,9 +139,9 @@ type-level and term-level operators: ::
    79 139
     
    
    80 140
     Similarly, it can be used in pragmas to deprecate only one name in a namespace: ::
    
    81 141
     
    
    82
    -  data Solo = MkSolo
    
    142
    +  data Solo a = MkSolo a
    
    83 143
     
    
    84
    -  pattern Solo = MkSolo
    
    144
    +  pattern Solo x = MkSolo x
    
    85 145
       {-# DEPRECATED data Solo "Use `MkSolo` instead" #-}
    
    86 146
     
    
    87 147
       type family Head xs where
    
    ... ... @@ -94,3 +154,16 @@ Similarly, it can be used in pragmas to deprecate only one name in a namespace:
    94 154
     It is considered bad practice to use a fixity signature, ``WARNING`` pragma, or
    
    95 155
     ``DEPRECATED`` pragma for a type-level name without an explicit ``type`` namespace, and
    
    96 156
     doing so will become an error in a future version of GHC.
    
    157
    +
    
    158
    +The ``type`` keyword in expressions and patterns
    
    159
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    160
    +
    
    161
    +**Since:** GHC 9.10
    
    162
    +
    
    163
    +Furthermore, :extension:`ExplicitNamespaces` permits the use of the ``type``
    
    164
    +keyword in patterns and expressions::
    
    165
    +
    
    166
    +  f (type t) x = ...       -- in a pattern
    
    167
    +  r = f (type Integer) 10  -- in an expression
    
    168
    +
    
    169
    +This is used in conjunction with :extension:`RequiredTypeArguments`.

  • testsuite/tests/rename/should_compile/T22581d.stdout
    ... ... @@ -2,4 +2,7 @@
    2 2
         In the import of ‘Data.Functor.Product’:
    
    3 3
           a data type called ‘Product’ is exported,
    
    4 4
           but its subordinate item ‘Pair’ is not in the type namespace.
    
    5
    +    Suggested fix:
    
    6
    +      Remove the ‘type’ keyword from the subordinate import item:
    
    7
    +        import Data.Functor.Product ( Product ( Pair ) )
    
    5 8
     

  • testsuite/tests/rename/should_compile/T25899d.stdout
    ... ... @@ -2,6 +2,9 @@
    2 2
         In the import of ‘GHC.Generics’:
    
    3 3
           a class called ‘Generic’ is exported,
    
    4 4
           but its subordinate item ‘Rep’ is not in the data namespace.
    
    5
    +    Suggested fix:
    
    6
    +      Remove the ‘data’ keyword from the subordinate import item:
    
    7
    +        import GHC.Generics ( Generic ( Rep ) )
    
    5 8
     
    
    6 9
     <interactive>:3:22: error: [GHC-56449]
    
    7 10
         In the import of ‘GHC.Generics’:
    

  • testsuite/tests/rename/should_fail/T22581a.stderr
    ... ... @@ -2,4 +2,7 @@ T22581a.hs:5:24: error: [GHC-51433]
    2 2
         In the import of ‘T22581a_helper’:
    
    3 3
           a data type called ‘T’ is exported,
    
    4 4
           but its subordinate item ‘MkT’ is not in the type namespace.
    
    5
    +    Suggested fix:
    
    6
    +      Remove the ‘type’ keyword from the subordinate import item:
    
    7
    +        import T22581a_helper ( T ( MkT ) )
    
    5 8
     

  • testsuite/tests/rename/should_fail/T22581b.stderr
    ... ... @@ -2,6 +2,9 @@ T22581b.hs:5:24: error: [GHC-51433]
    2 2
         In the import of ‘T22581b_helper’:
    
    3 3
           a data type called ‘T’ is exported,
    
    4 4
           but its subordinate item ‘MkT1’ is not in the type namespace.
    
    5
    +    Suggested fix:
    
    6
    +      Remove the ‘type’ keyword from the subordinate import item:
    
    7
    +        import T22581b_helper ( T ( MkT1 ) )
    
    5 8
     
    
    6 9
     T22581b.hs:5:24: error: [GHC-10237]
    
    7 10
         In the import of ‘T22581b_helper’:
    

  • testsuite/tests/rename/should_fail/T25899f.hs
    1
    +{-# LANGUAGE ExplicitNamespaces #-}
    
    2
    +
    
    3
    +module T25899f where
    
    4
    +
    
    5
    +import T25899f_helper
    
    6
    +  ( T(type X, Y, type Z)
    
    7
    +  , type (#)(data F, G, data H)
    
    8
    +  )

  • testsuite/tests/rename/should_fail/T25899f.stderr
    1
    +T25899f.hs:6:5: error: [GHC-51433]
    
    2
    +    In the import of ‘T25899f_helper’:
    
    3
    +      a data type called ‘T’ is exported,
    
    4
    +      but its subordinate items ‘X’, ‘Z’ are not in the type namespace.
    
    5
    +    Suggested fix:
    
    6
    +      Remove the ‘type’ keywords from the subordinate import items:
    
    7
    +        import T25899f_helper ( T ( X, Z ) )
    
    8
    +
    
    9
    +T25899f.hs:7:5: error: [GHC-46557]
    
    10
    +    In the import of ‘T25899f_helper’:
    
    11
    +      a class called ‘(#)’ is exported,
    
    12
    +      but its subordinate items ‘F’, ‘H’ are not in the data namespace.
    
    13
    +    Suggested fix:
    
    14
    +      Remove the ‘data’ keywords from the subordinate import items:
    
    15
    +        import T25899f_helper ( type (#) ( F, H ) )
    
    16
    +

  • testsuite/tests/rename/should_fail/T25899f_helper.hs
    1
    +{-# LANGUAGE TypeFamilies #-}
    
    2
    +
    
    3
    +module T25899f_helper where
    
    4
    +
    
    5
    +data T = X | Y | Z
    
    6
    +
    
    7
    +class a # b where
    
    8
    +  type F a b
    
    9
    +  type G a b
    
    10
    +  type H a b

  • testsuite/tests/rename/should_fail/all.T
    ... ... @@ -245,3 +245,4 @@ test('T25991b2', [extra_files(['T25991b_helper.hs'])], multimod_compile_fail, ['
    245 245
     test('T25899e1', normal, compile_fail, [''])
    
    246 246
     test('T25899e2', normal, compile_fail, [''])
    
    247 247
     test('T25899e3', [extra_files(['T25899e_helper.hs'])], multimod_compile_fail, ['T25899e3', '-v0'])
    
    248
    +test('T25899f',  [extra_files(['T25899f_helper.hs'])], multimod_compile_fail, ['T25899f', '-v0'])