Vladislav Zavialov pushed to branch wip/int-index/unusable-unpack-pragma-flag at Glasgow Haskell Compiler / GHC
Commits:
-
a83bbd11
by Vladislav Zavialov at 2025-04-19T17:27:34+03:00
21 changed files:
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Error/Codes.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/using-warnings.rst
- testsuite/tests/simplCore/should_compile/Makefile
- testsuite/tests/simplCore/should_compile/T23307c.stderr
- + testsuite/tests/simplCore/should_compile/T3990c.hs
- + testsuite/tests/simplCore/should_compile/T3990c.stdout
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplCore/should_fail/T25672.stderr
- testsuite/tests/typecheck/should_compile/T7050.stderr
- testsuite/tests/typecheck/should_fail/T3966.stderr
- + testsuite/tests/typecheck/should_fail/T3966b.hs
- + testsuite/tests/typecheck/should_fail/T3966b.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/unboxedsums/unpack_sums_5.stderr
Changes:
| ... | ... | @@ -1098,6 +1098,7 @@ data WarningFlag = |
| 1098 | 1098 | -- ^ @since 9.14, scheduled to be removed in 9.18
|
| 1099 | 1099 | --
|
| 1100 | 1100 | -- See Note [Quantifying over equalities in RULES] in GHC.Tc.Gen.Sig
|
| 1101 | + | Opt_WarnUnusableUnpackPragmas -- Since 9.14
|
|
| 1101 | 1102 | deriving (Eq, Ord, Show, Enum, Bounded)
|
| 1102 | 1103 | |
| 1103 | 1104 | -- | Return the names of a WarningFlag
|
| ... | ... | @@ -1217,6 +1218,7 @@ warnFlagNames wflag = case wflag of |
| 1217 | 1218 | Opt_WarnUselessSpecialisations -> "useless-specialisations" :| ["useless-specializations"]
|
| 1218 | 1219 | Opt_WarnDeprecatedPragmas -> "deprecated-pragmas" :| []
|
| 1219 | 1220 | Opt_WarnRuleLhsEqualities -> "rule-lhs-equalities" :| []
|
| 1221 | + Opt_WarnUnusableUnpackPragmas -> "unusable-unpack-pragmas" :| []
|
|
| 1220 | 1222 | |
| 1221 | 1223 | -- -----------------------------------------------------------------------------
|
| 1222 | 1224 | -- Standard sets of warning options
|
| ... | ... | @@ -1362,7 +1364,8 @@ standardWarnings -- see Note [Documenting warning flags] |
| 1362 | 1364 | Opt_WarnViewPatternSignatures,
|
| 1363 | 1365 | Opt_WarnUselessSpecialisations,
|
| 1364 | 1366 | Opt_WarnDeprecatedPragmas,
|
| 1365 | - Opt_WarnRuleLhsEqualities
|
|
| 1367 | + Opt_WarnRuleLhsEqualities,
|
|
| 1368 | + Opt_WarnUnusableUnpackPragmas
|
|
| 1366 | 1369 | ]
|
| 1367 | 1370 | |
| 1368 | 1371 | -- | Things you get with @-W@.
|
| ... | ... | @@ -2384,6 +2384,7 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of |
| 2384 | 2384 | Opt_WarnUselessSpecialisations -> warnSpec x
|
| 2385 | 2385 | Opt_WarnDeprecatedPragmas -> warnSpec x
|
| 2386 | 2386 | Opt_WarnRuleLhsEqualities -> warnSpec x
|
| 2387 | + Opt_WarnUnusableUnpackPragmas -> warnSpec x
|
|
| 2387 | 2388 | |
| 2388 | 2389 | warningGroupsDeps :: [(Deprecation, FlagSpec WarningGroup)]
|
| 2389 | 2390 | warningGroupsDeps = map mk warningGroups
|
| ... | ... | @@ -2504,6 +2504,8 @@ instance Diagnostic TcRnMessage where |
| 2504 | 2504 | -> WarningWithFlag Opt_WarnIncompleteRecordSelectors
|
| 2505 | 2505 | TcRnBadFieldAnnotation _ _ LazyFieldsDisabled
|
| 2506 | 2506 | -> ErrorWithoutFlag
|
| 2507 | + TcRnBadFieldAnnotation _ _ UnusableUnpackPragma
|
|
| 2508 | + -> WarningWithFlag Opt_WarnUnusableUnpackPragmas
|
|
| 2507 | 2509 | TcRnBadFieldAnnotation{}
|
| 2508 | 2510 | -> WarningWithoutFlag
|
| 2509 | 2511 | TcRnSuperclassCycle{}
|
| ... | ... | @@ -5802,7 +5804,7 @@ pprBadFieldAnnotationReason = \case |
| 5802 | 5804 | text "Lazy field annotations (~) are disabled"
|
| 5803 | 5805 | UnpackWithoutStrictness ->
|
| 5804 | 5806 | text "UNPACK pragma lacks '!'"
|
| 5805 | - BackpackUnpackAbstractType ->
|
|
| 5807 | + UnusableUnpackPragma ->
|
|
| 5806 | 5808 | text "Ignoring unusable UNPACK pragma"
|
| 5807 | 5809 | |
| 5808 | 5810 | pprSuperclassCycleDetail :: SuperclassCycleDetail -> SDoc
|
| ... | ... | @@ -6257,13 +6257,28 @@ data BadFieldAnnotationReason where |
| 6257 | 6257 | T14761a, T7562
|
| 6258 | 6258 | -}
|
| 6259 | 6259 | UnpackWithoutStrictness :: BadFieldAnnotationReason
|
| 6260 | - {-| An UNPACK pragma was applied to an abstract type in an indefinite package
|
|
| 6261 | - in Backpack.
|
|
| 6260 | + {-| An UNPACK pragma is unusable.
|
|
| 6261 | + |
|
| 6262 | + A possible reason for this warning is that the UNPACK pragma was applied to
|
|
| 6263 | + one of the following:
|
|
| 6264 | + |
|
| 6265 | + * a function type @a -> b@
|
|
| 6266 | + * a recursive use of the data type being defined
|
|
| 6267 | + * a sum type that cannot be unpacked, see @Note [UNPACK for sum types]@
|
|
| 6268 | + * a type/data family application with no matching instance in the environment
|
|
| 6269 | + |
|
| 6270 | + However, it is deliberately /not/ emitted if:
|
|
| 6271 | + |
|
| 6272 | + * the failure occurs in an indefinite package in Backpack
|
|
| 6273 | + * the pragma is usable, but unpacking is disabled by @-O0@
|
|
| 6262 | 6274 | |
| 6263 | 6275 | Test cases:
|
| 6264 | - unpack_sums_5, T3966, T7050
|
|
| 6276 | + unpack_sums_5, T3966, T7050, T25672, T23307c
|
|
| 6277 | + |
|
| 6278 | + Negative test cases (must not trigger this warning):
|
|
| 6279 | + T3990
|
|
| 6265 | 6280 | -}
|
| 6266 | - BackpackUnpackAbstractType :: BadFieldAnnotationReason
|
|
| 6281 | + UnusableUnpackPragma :: BadFieldAnnotationReason
|
|
| 6267 | 6282 | deriving (Generic)
|
| 6268 | 6283 | |
| 6269 | 6284 | data SuperclassCycle =
|
| ... | ... | @@ -322,7 +322,7 @@ splice to separate the module and force the desired order of kind-checking: |
| 322 | 322 | data D1 = MkD1 !(F Int) -- now (F Int) surely gets unpacked
|
| 323 | 323 | |
| 324 | 324 | The current version of GHC is more predictable. Neither the (Complex Double) nor
|
| 325 | -the (F Int) example gets unpacking, the type/data instance is put into a
|
|
| 325 | +the (F Int) example gets unpacking unless the type/data instance is put into a
|
|
| 326 | 326 | separate HsGroup, either with $(return []) or by placing it in another module
|
| 327 | 327 | altogether. This is a direct result of placing instances after the other SCCs,
|
| 328 | 328 | as described in Note [Put instances at the end] in GHC.Rename.Module
|
| ... | ... | @@ -449,11 +449,20 @@ tcTyClGroupsPass all_gs thing_inside = go True ttcgs_zero mempty nilOL all_gs |
| 449 | 449 | -- pass, the current group's lexical dependencies must have been
|
| 450 | 450 | -- satisfied by the preceding groups; no need for the ready check,
|
| 451 | 451 | -- this avoids some lookups in tcg_env
|
| 452 | + |
|
| 453 | + -- See Note [Expedient use of diagnostics in tcTyClGroupsPass]
|
|
| 454 | + set_opts action
|
|
| 455 | + | strict = setWOptM Opt_WarnUnusableUnpackPragmas action
|
|
| 456 | + | otherwise = action
|
|
| 457 | + validate _ msgs _
|
|
| 458 | + | strict = not (unpackErrorsFound msgs)
|
|
| 459 | + | otherwise = True
|
|
| 460 | + |
|
| 452 | 461 | if not ready then return on_blocked else
|
| 453 | - tryTcDiscardingErrs' (\_ msgs _ -> not (strict && unpackErrorsFound msgs))
|
|
| 462 | + tryTcDiscardingErrs' validate
|
|
| 454 | 463 | (return on_flawed)
|
| 455 | 464 | (return on_failed)
|
| 456 | - (on_success <$> tcTyClGroup g)
|
|
| 465 | + (on_success <$> set_opts (tcTyClGroup g))
|
|
| 457 | 466 | |
| 458 | 467 | data TcTyClGroupsStats =
|
| 459 | 468 | TcTyClGroupsStats
|
| ... | ... | @@ -479,15 +488,36 @@ instance Outputable TcTyClGroupsStats where |
| 479 | 488 | , text "n_failed =" <+> ppr (ttcgs_n_failed stats)
|
| 480 | 489 | , text "n_flawed =" <+> ppr (ttcgs_n_flawed stats) ]
|
| 481 | 490 | |
| 491 | +-- See Note [Expedient use of diagnostics in tcTyClGroupsPass]
|
|
| 482 | 492 | unpackErrorsFound :: Messages TcRnMessage -> Bool
|
| 483 | 493 | unpackErrorsFound = any is_unpack_error
|
| 484 | 494 | where
|
| 485 | 495 | is_unpack_error :: TcRnMessage -> Bool
|
| 486 | 496 | is_unpack_error (TcRnMessageWithInfo _ (TcRnMessageDetailed _ msg)) = is_unpack_error msg
|
| 487 | 497 | is_unpack_error (TcRnWithHsDocContext _ msg) = is_unpack_error msg
|
| 488 | - is_unpack_error (TcRnBadFieldAnnotation _ _ BackpackUnpackAbstractType) = True
|
|
| 498 | + is_unpack_error (TcRnBadFieldAnnotation _ _ UnusableUnpackPragma) = True
|
|
| 489 | 499 | is_unpack_error _ = False
|
| 490 | 500 | |
| 501 | +{- Note [Expedient use of diagnostics in tcTyClGroupsPass]
|
|
| 502 | +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 503 | +In tcTyClGroupsPass.go with strict=True, we want to skip "flawed" groups, i.e.
|
|
| 504 | +groups with unusable unpack pragmas, as explained in Note [Retrying TyClGroups].
|
|
| 505 | +To detect these unusable {-# UNPACK #-} pragmas, we currently piggy-back on the
|
|
| 506 | +diagnostics infrastructure:
|
|
| 507 | + |
|
| 508 | + 1. (setWOptM Opt_WarnUnusableUnpackPragmas) to enable the warning.
|
|
| 509 | + The warning is on by default, but the user may have disabled it with
|
|
| 510 | + -Wno-unusable-unpack-pragmas, in which case we need to turn it back on.
|
|
| 511 | + |
|
| 512 | + 2. (unpackErrorsFound msgs) to check if UnusableUnpackPragma is one of the
|
|
| 513 | + collected diagnostics. This is somewhat unpleasant because of the need to
|
|
| 514 | + recurse into TcRnMessageWithInfo and TcRnWithHsDocContext.
|
|
| 515 | + |
|
| 516 | +Arguably, this is not a principled solution, because diagnostics are meant for
|
|
| 517 | +the user and here we inspect them to determine the order of type-checking. The
|
|
| 518 | +only reason for the current setup is that it was the easy thing to do.
|
|
| 519 | +-}
|
|
| 520 | + |
|
| 491 | 521 | isReadyTyClGroup :: TcGblEnv -> TyClGroup GhcRn -> Bool
|
| 492 | 522 | isReadyTyClGroup tcg_env TyClGroup{group_ext = deps} =
|
| 493 | 523 | nameSetAll (\n -> n `elemNameEnv` tcg_type_env tcg_env) deps
|
| ... | ... | @@ -5123,7 +5153,7 @@ checkValidDataCon dflags existential_ok tc con |
| 5123 | 5153 | -- warn in this case (it gives users the wrong idea about whether
|
| 5124 | 5154 | -- or not UNPACK on abstract types is supported; it is!)
|
| 5125 | 5155 | , isHomeUnitDefinite (hsc_home_unit hsc_env)
|
| 5126 | - = addDiagnosticTc (bad_bang n BackpackUnpackAbstractType)
|
|
| 5156 | + = addDiagnosticTc (bad_bang n UnusableUnpackPragma)
|
|
| 5127 | 5157 | |
| 5128 | 5158 | | otherwise
|
| 5129 | 5159 | = return ()
|
| ... | ... | @@ -20,7 +20,8 @@ module GHC.Tc.Utils.Monad( |
| 20 | 20 | updTopFlags,
|
| 21 | 21 | getEnvs, setEnvs, updEnvs, restoreEnvs,
|
| 22 | 22 | xoptM, doptM, goptM, woptM,
|
| 23 | - setXOptM, unsetXOptM, unsetGOptM, unsetWOptM,
|
|
| 23 | + setXOptM, setWOptM,
|
|
| 24 | + unsetXOptM, unsetGOptM, unsetWOptM,
|
|
| 24 | 25 | whenDOptM, whenGOptM, whenWOptM,
|
| 25 | 26 | whenXOptM, unlessXOptM,
|
| 26 | 27 | getGhcMode,
|
| ... | ... | @@ -579,6 +580,9 @@ woptM flag = wopt flag <$> getDynFlags |
| 579 | 580 | setXOptM :: LangExt.Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
|
| 580 | 581 | setXOptM flag = updTopFlags (\dflags -> xopt_set dflags flag)
|
| 581 | 582 | |
| 583 | +setWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
|
|
| 584 | +setWOptM flag = updTopFlags (\dflags -> wopt_set dflags flag)
|
|
| 585 | + |
|
| 582 | 586 | unsetXOptM :: LangExt.Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
|
| 583 | 587 | unsetXOptM flag = updTopFlags (\dflags -> xopt_unset dflags flag)
|
| 584 | 588 |
| ... | ... | @@ -711,7 +711,7 @@ type family GhcDiagnosticCode c = n | n -> c where |
| 711 | 711 | -- TcRnBadFieldAnnotation/BadFieldAnnotationReason
|
| 712 | 712 | GhcDiagnosticCode "LazyFieldsDisabled" = 81601
|
| 713 | 713 | GhcDiagnosticCode "UnpackWithoutStrictness" = 10107
|
| 714 | - GhcDiagnosticCode "BackpackUnpackAbstractType" = 40091
|
|
| 714 | + GhcDiagnosticCode "UnusableUnpackPragma" = 40091
|
|
| 715 | 715 | |
| 716 | 716 | -- TcRnRoleValidationFailed/RoleInferenceFailedReason
|
| 717 | 717 | GhcDiagnosticCode "TyVarRoleMismatch" = 22221
|
| ... | ... | @@ -25,17 +25,6 @@ Language |
| 25 | 25 | This deprecation is controlled by the newly introduced ``-Wdeprecated-pragmas``
|
| 26 | 26 | flag in ``-Wdefault``.
|
| 27 | 27 | |
| 28 | -* A new flag, ``-Wuseless-specialisations``, controls warnings emitted when GHC
|
|
| 29 | - determines that a SPECIALISE pragma would have no effect.
|
|
| 30 | - |
|
| 31 | -* A new flag, ``-Wrule-lhs-equalities``, controls warnings emitted for RULES
|
|
| 32 | - whose left-hand side attempts to quantify over equality constraints that
|
|
| 33 | - previous GHC versions accepted quantifying over. GHC will now drop such RULES,
|
|
| 34 | - emitting a warning message controlled by this flag.
|
|
| 35 | - |
|
| 36 | - This warning is intended to give visibility to the fact that the RULES that
|
|
| 37 | - previous GHC versions generated in such circumstances could never fire.
|
|
| 38 | - |
|
| 39 | 28 | * ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified
|
| 40 | 29 | by `GHC Proposal 516: add warning for incomplete record selectors <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0516-incomplete-record-selectors.rst>`_.
|
| 41 | 30 | Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library.
|
| ... | ... | @@ -93,6 +82,25 @@ Compiler |
| 93 | 82 | :ghc-ticket:`20875`, :ghc-ticket:`21172`, :ghc-ticket:`22257`, :ghc-ticket:`25238`,
|
| 94 | 83 | :ghc-ticket:`25834`.
|
| 95 | 84 | |
| 85 | +- A new flag, :ghc-flag:`-Wuseless-specialisations`, controls warnings emitted when GHC
|
|
| 86 | + determines that a SPECIALISE pragma would have no effect.
|
|
| 87 | + |
|
| 88 | +- A new flag, :ghc-flag:`-Wrule-lhs-equalities`, controls warnings emitted for RULES
|
|
| 89 | + whose left-hand side attempts to quantify over equality constraints that
|
|
| 90 | + previous GHC versions accepted quantifying over. GHC will now drop such RULES,
|
|
| 91 | + emitting a warning message controlled by this flag.
|
|
| 92 | + |
|
| 93 | + This warning is intended to give visibility to the fact that the RULES that
|
|
| 94 | + previous GHC versions generated in such circumstances could never fire.
|
|
| 95 | + |
|
| 96 | +- A new flag, :ghc-flag:`-Wunusable-unpack-pragmas`, controls warnings emitted
|
|
| 97 | + when GHC is unable to unpack a data constructor field annotated by the
|
|
| 98 | + ``{-# UNPACK #-}`` pragma.
|
|
| 99 | + |
|
| 100 | + Previous GHC versions issued this warning unconditionally. Now it is possible
|
|
| 101 | + to disable it with ``-Wno-unusable-unpack-pragmas`` or turn it into an error
|
|
| 102 | + with ``-Werror=unusable-unpack-pragmas``.
|
|
| 103 | + |
|
| 96 | 104 | GHCi
|
| 97 | 105 | ~~~~
|
| 98 | 106 |
| ... | ... | @@ -84,6 +84,7 @@ as ``-Wno-...`` for every individual warning in the group. |
| 84 | 84 | * :ghc-flag:`-Wnoncanonical-monad-instances`
|
| 85 | 85 | * :ghc-flag:`-Wdata-kinds-tc`
|
| 86 | 86 | * :ghc-flag:`-Wimplicit-rhs-quantification`
|
| 87 | + * :ghc-flag:`-Wunusable-unpack-pragmas`
|
|
| 87 | 88 | |
| 88 | 89 | .. ghc-flag:: -W
|
| 89 | 90 | :shortdesc: enable normal warnings
|
| ... | ... | @@ -2646,6 +2647,40 @@ of ``-W(no-)*``. |
| 2646 | 2647 | To make the code forwards-compatible and silence the warning, users are
|
| 2647 | 2648 | advised to add parentheses manually.
|
| 2648 | 2649 | |
| 2650 | +.. ghc-flag:: -Wunusable-unpack-pragmas
|
|
| 2651 | + :shortdesc: warn when an ``{-# UNPACK #-}`` pragma is unusable
|
|
| 2652 | + :type: dynamic
|
|
| 2653 | + :reverse: -Wno-unusable-unpack-pragmas
|
|
| 2654 | + |
|
| 2655 | + :since: 9.14.1
|
|
| 2656 | + :default: on
|
|
| 2657 | + |
|
| 2658 | + Warn on unusable ``{-# UNPACK #-}`` pragmas in data type declarations.
|
|
| 2659 | + Examples::
|
|
| 2660 | + |
|
| 2661 | + data T = MkT {-# UNPACK #-} !(Int -> Bool)
|
|
| 2662 | + |
|
| 2663 | + data G where
|
|
| 2664 | + MkG :: {-# UNPACK #-} !G -> G
|
|
| 2665 | + |
|
| 2666 | + type family F a where {}
|
|
| 2667 | + data R a = MkR { fld :: {-# UNPACK #-} !(F a) }
|
|
| 2668 | + |
|
| 2669 | + A possible reason for this warning is that the ``{-# UNPACK #-}`` pragma was
|
|
| 2670 | + applied to one of the following:
|
|
| 2671 | + |
|
| 2672 | + * a function type ``a -> b``
|
|
| 2673 | + * a recursive use of the data type being defined
|
|
| 2674 | + * a sum type that cannot be unpacked
|
|
| 2675 | + * a type/data family application with no matching instance in the environment
|
|
| 2676 | + |
|
| 2677 | + However, it is deliberately **not** emitted if:
|
|
| 2678 | + |
|
| 2679 | + * the failure occurs in an indefinite package in Backpack
|
|
| 2680 | + * the pragma is usable, but unpacking is disabled by :ghc-flag:`-O0`
|
|
| 2681 | + |
|
| 2682 | +----
|
|
| 2683 | + |
|
| 2649 | 2684 | If you're feeling really paranoid, the :ghc-flag:`-dcore-lint` option is a good choice.
|
| 2650 | 2685 | It turns on heavyweight intra-pass sanity-checking within GHC. (It checks GHC's
|
| 2651 | 2686 | sanity, not yours.) |
| ... | ... | @@ -43,6 +43,11 @@ T3990b: |
| 43 | 43 | '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl T3990b.hs | grep 'test_case'
|
| 44 | 44 | # Grep output should show an unpacked constructor
|
| 45 | 45 | |
| 46 | +T3990c:
|
|
| 47 | + $(RM) -f T3990c.o T3990c.hi
|
|
| 48 | + '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl T3990c.hs | grep 'test_case'
|
|
| 49 | + # Grep output should show an unpacked constructor
|
|
| 50 | + |
|
| 46 | 51 | T8848:
|
| 47 | 52 | $(RM) -f T8848.o T8848.hi
|
| 48 | 53 | '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-rule-firings T8848.hs | grep 'SPEC map2'
|
| 1 | - |
|
| 2 | -T23307c.hs:7:13: warning: [GHC-40091]
|
|
| 1 | +T23307c.hs:7:13: warning: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault)]
|
|
| 3 | 2 | • Ignoring unusable UNPACK pragma on the first argument of ‘LCon’
|
| 4 | 3 | • In the definition of data constructor ‘LCon’
|
| 5 | 4 | In the data type declaration for ‘Loop’
|
| 5 | + |
| 1 | +{-# OPTIONS -Wno-unusable-unpack-pragmas #-}
|
|
| 2 | + -- The warning is disabled, but this should not affect unpacking
|
|
| 3 | + |
|
| 4 | +{-# LANGUAGE TypeFamilies #-}
|
|
| 5 | +module T3990c where
|
|
| 6 | + |
|
| 7 | +type family F a
|
|
| 8 | + |
|
| 9 | +data D1 = MkD1 {-# UNPACK #-} !(F Int)
|
|
| 10 | + -- This should actually get unpacked
|
|
| 11 | + |
|
| 12 | +data D2 = MkD2 {-# UNPACK #-} !Int
|
|
| 13 | + {-# UNPACK #-} !Int
|
|
| 14 | + |
|
| 15 | +type instance F Int = D2
|
|
| 16 | + |
|
| 17 | +test_case :: D1
|
|
| 18 | +test_case = MkD1 (MkD2 1 1) |
| 1 | +test_case :: D1
|
|
| 2 | +test_case = T3990c.MkD1 1# 1# |
| ... | ... | @@ -211,6 +211,7 @@ test('T11742', normal, compile, ['-O2']) |
| 211 | 211 | test('T11644', normal, compile, ['-O2'])
|
| 212 | 212 | test('T3990', normal, makefile_test, ['T3990'])
|
| 213 | 213 | test('T3990b', normal, makefile_test, ['T3990b'])
|
| 214 | +test('T3990c', normal, makefile_test, ['T3990c'])
|
|
| 214 | 215 | |
| 215 | 216 | test('T12076', [], multimod_compile, ['T12076', '-v0'])
|
| 216 | 217 | test('T12076lit', normal, compile, ['-O'])
|
| 1 | -T25672.hs:12:7: warning: [GHC-40091]
|
|
| 1 | +T25672.hs:12:7: warning: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault)]
|
|
| 2 | 2 | • Ignoring unusable UNPACK pragma
|
| 3 | 3 | on the first argument of ‘WrapIntOrWord’
|
| 4 | 4 | • In the definition of data constructor ‘WrapIntOrWord’
|
| 1 | - |
|
| 2 | -T7050.hs:3:14: warning: [GHC-40091]
|
|
| 1 | +T7050.hs:3:14: warning: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault)]
|
|
| 3 | 2 | • Ignoring unusable UNPACK pragma on the first argument of ‘Foo’
|
| 4 | 3 | • In the definition of data constructor ‘Foo’
|
| 5 | 4 | In the data type declaration for ‘Foo’
|
| 5 | + |
| 1 | - |
|
| 2 | -T3966.hs:5:16: error: [GHC-40091] [-Werror]
|
|
| 1 | +T3966.hs:5:16: error: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault), Werror=unusable-unpack-pragmas]
|
|
| 3 | 2 | • Ignoring unusable UNPACK pragma on the first argument of ‘Foo’
|
| 4 | 3 | • In the definition of data constructor ‘Foo’
|
| 5 | 4 | In the data type declaration for ‘Foo’
|
| 5 | + |
| 1 | +{-# OPTIONS -Werror=unusable-unpack-pragmas #-}
|
|
| 2 | +{-# LANGUAGE TypeFamilies #-}
|
|
| 3 | + |
|
| 4 | +module T3966b where
|
|
| 5 | + |
|
| 6 | +data T = MkT {-# UNPACK #-} !(Int -> Bool)
|
|
| 7 | + |
|
| 8 | +data G where
|
|
| 9 | + MkG :: {-# UNPACK #-} !G -> G
|
|
| 10 | + |
|
| 11 | +type family F a where {}
|
|
| 12 | +data R a = MkR { fld :: {-# UNPACK #-} !(F a) } |
| 1 | +T3966b.hs:6:10: error: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault), Werror=unusable-unpack-pragmas]
|
|
| 2 | + • Ignoring unusable UNPACK pragma on the first argument of ‘MkT’
|
|
| 3 | + • In the definition of data constructor ‘MkT’
|
|
| 4 | + In the data type declaration for ‘T’
|
|
| 5 | + |
|
| 6 | +T3966b.hs:9:3: error: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault), Werror=unusable-unpack-pragmas]
|
|
| 7 | + • Ignoring unusable UNPACK pragma on the first argument of ‘MkG’
|
|
| 8 | + • In the definition of data constructor ‘MkG’
|
|
| 9 | + In the data type declaration for ‘G’
|
|
| 10 | + |
|
| 11 | +T3966b.hs:12:12: error: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault), Werror=unusable-unpack-pragmas]
|
|
| 12 | + • Ignoring unusable UNPACK pragma on the first argument of ‘MkR’
|
|
| 13 | + • In the definition of data constructor ‘MkR’
|
|
| 14 | + In the data type declaration for ‘R’
|
|
| 15 | + |
| ... | ... | @@ -213,6 +213,7 @@ test('T3613', normal, compile_fail, ['']) |
| 213 | 213 | test('fd-loop', normal, compile_fail, [''])
|
| 214 | 214 | test('T3950', normal, compile_fail, [''])
|
| 215 | 215 | test('T3966', normal, compile_fail, [''])
|
| 216 | +test('T3966b', normal, compile_fail, [''])
|
|
| 216 | 217 | test('IPFail', normal, compile_fail, [''])
|
| 217 | 218 | |
| 218 | 219 | test('T3468', [], multimod_compile_fail, ['T3468', '-v0'])
|
| 1 | - |
|
| 2 | -unpack_sums_5.hs:4:22: warning: [GHC-40091]
|
|
| 1 | +unpack_sums_5.hs:4:22: warning: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault)]
|
|
| 3 | 2 | • Ignoring unusable UNPACK pragma on the first argument of ‘JustT’
|
| 4 | 3 | • In the definition of data constructor ‘JustT’
|
| 5 | 4 | In the data type declaration for ‘SMaybeT’
|
| 6 | 5 | |
| 7 | -unpack_sums_5.hs:7:10: warning: [GHC-40091]
|
|
| 6 | +unpack_sums_5.hs:7:10: warning: [GHC-40091] [-Wunusable-unpack-pragmas (in -Wdefault)]
|
|
| 8 | 7 | • Ignoring unusable UNPACK pragma on the first argument of ‘MkT’
|
| 9 | 8 | • In the definition of data constructor ‘MkT’
|
| 10 | 9 | In the data type declaration for ‘T’
|
| 10 | + |