Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
6caa6508
by Adam Gundry at 2025-04-20T10:54:22-04:00
-
0426fd6c
by Adam Gundry at 2025-04-20T10:54:23-04:00
-
eec96527
by Adam Gundry at 2025-04-20T10:54:23-04:00
16 changed files:
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Tc/Solver/Dict.hs
- docs/users_guide/exts/instances.rst
- + testsuite/tests/simplCore/should_compile/T25883.hs
- + testsuite/tests/simplCore/should_compile/T25883.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883b.hs
- + testsuite/tests/simplCore/should_compile/T25883b.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883c.hs
- + testsuite/tests/simplCore/should_compile/T25883c.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883d.hs
- + testsuite/tests/simplCore/should_compile/T25883d.stderr
- + testsuite/tests/simplCore/should_compile/T25883d_import.hs
- testsuite/tests/simplCore/should_compile/all.T
- + testsuite/tests/simplCore/should_run/T23429.hs
- + testsuite/tests/simplCore/should_run/T23429.stdout
- testsuite/tests/simplCore/should_run/all.T
Changes:
| ... | ... | @@ -599,7 +599,7 @@ These functions implement the carefully-written rules in the user |
| 599 | 599 | manual section on "overlapping instances". At risk of duplication,
|
| 600 | 600 | here are the rules. If the rules change, change this text and the
|
| 601 | 601 | user manual simultaneously. The link may be this:
|
| 602 | -http://www.haskell.org/ghc/docs/latest/html/users_guide/glasgow_exts.html#instance-overlap
|
|
| 602 | +https://downloads.haskell.org/ghc/latest/docs/users_guide/exts/instances.html#instance-overlap
|
|
| 603 | 603 | |
| 604 | 604 | The willingness to be overlapped or incoherent is a property of the
|
| 605 | 605 | instance declaration itself, controlled by its `OverlapMode`, as follows
|
| ... | ... | @@ -627,14 +627,22 @@ of the target constraint (C ty1 .. tyn). The search works like this. |
| 627 | 627 | |
| 628 | 628 | (IL0) If there are any local Givens that match (potentially unifying
|
| 629 | 629 | any metavariables, even untouchable ones) the target constraint,
|
| 630 | - the search fails. See Note [Instance and Given overlap] in
|
|
| 631 | - GHC.Tc.Solver.Dict.
|
|
| 632 | - |
|
| 633 | -(IL1) Find all instances `I` that *match* the target constraint; that is, the target
|
|
| 634 | - constraint is a substitution instance of `I`. These instance declarations are
|
|
| 635 | - the /candidates/.
|
|
| 636 | - |
|
| 637 | -(IL2) If there are no candidates, the search fails.
|
|
| 630 | + the search fails unless -XIncoherentInstances is enabled. See
|
|
| 631 | + Note [Instance and Given overlap] in GHC.Tc.Solver.Dict. This is
|
|
| 632 | + implemented by the first guard in matchClassInst.
|
|
| 633 | + |
|
| 634 | +(IL1) Find `all_matches` and `all_unifs` in `lookupInstEnv`:
|
|
| 635 | + - all_matches: all instances `I` that *match* the target constraint (that
|
|
| 636 | + is, the target constraint is a substitution instance of `I`). These
|
|
| 637 | + instance declarations are the /candidates/.
|
|
| 638 | + - all_unifs: all non-incoherent instances that *unify with but do not match*
|
|
| 639 | + the target constraint. These are not candidates, but might match later if
|
|
| 640 | + the target constraint is furhter instantiated. See
|
|
| 641 | + `data PotentialUnifiers` for more precise details.
|
|
| 642 | + |
|
| 643 | +(IL2) If there are no candidates, the search fails
|
|
| 644 | + (lookupInstEnv returns no final_matches). The PotentialUnifiers are returned
|
|
| 645 | + by lookupInstEnv for use in error message generation (mkDictErr).
|
|
| 638 | 646 | |
| 639 | 647 | (IL3) Eliminate any candidate `IX` for which there is another candidate `IY` such
|
| 640 | 648 | that both of the following hold:
|
| ... | ... | @@ -644,29 +652,39 @@ of the target constraint (C ty1 .. tyn). The search works like this. |
| 644 | 652 | "either/or" design, rather than a "both/and" design, allow a
|
| 645 | 653 | client to deliberately override an instance from a library,
|
| 646 | 654 | without requiring a change to the library.)
|
| 647 | - This is done by `pruneOverlappingMatches`
|
|
| 648 | 655 | |
| 649 | -(IL4) If all the remaining candidates are *incoherent*, the search succeeds,
|
|
| 650 | - returning an arbitrary surviving candidate.
|
|
| 656 | + In addition, provided there is at least one candidate, eliminate any other
|
|
| 657 | + candidates that are *incoherent*. (In particular, if all remaining candidates
|
|
| 658 | + are incoherent, all except an arbitrarily chosen one will be eliminated.)
|
|
| 659 | + |
|
| 660 | + This is implemented by `pruneOverlappedMatches`, producing final_matches in
|
|
| 661 | + lookupInstEnv. See Note [Instance overlap and guards] and
|
|
| 662 | + Note [Incoherent instances].
|
|
| 663 | + |
|
| 664 | +(IL4) If exactly one *incoherent* candidate remains, the search succeeds.
|
|
| 665 | + (By the previous step, there cannot be more than one incoherent candidate
|
|
| 666 | + remaining.)
|
|
| 651 | 667 | |
| 652 | - If any coherent or non-canonical incoherent unifiers were discarded,
|
|
| 653 | - return NoUnifiers EvNonCanonical; if only canonical incoherent unifiers
|
|
| 654 | - were discarded, return NoUnifiers EvCanonical
|
|
| 668 | + In this case, lookupInstEnv returns the successful match, and it returns
|
|
| 669 | + NoUnifiers as the final_unifs, which amounts to skipping the following
|
|
| 670 | + steps.
|
|
| 655 | 671 | |
| 656 | -(IL5) If more than one non-*incoherent* candidate remains, the search
|
|
| 657 | - fails. Otherwise there is exactly one non-*incoherent*
|
|
| 658 | - candidate; call it the "prime candidate".
|
|
| 672 | +(IL5) If more than one candidate remains, the search fails. (We have already
|
|
| 673 | + eliminated the incoherent candidates, and we have no way to select
|
|
| 674 | + between non-incoherent candidates.)
|
|
| 659 | 675 | |
| 660 | -(IL6) Now find all instances that unify with the target constraint,
|
|
| 661 | - but do not match it. Such non-candidate instances might match
|
|
| 662 | - when the target constraint is further instantiated.
|
|
| 676 | +(IL6) Otherwise there is exactly one candidate remaining. The all_unifs
|
|
| 677 | + computed at step (IL1) are returned from lookupInstEnv as final_unifs.
|
|
| 663 | 678 | |
| 664 | - If any are *coherent* (not incoherent) return them
|
|
| 665 | - as PotentialUnifiers.
|
|
| 679 | + If there are no potential unifiers, the search succeeds (in matchInstEnv).
|
|
| 680 | + If there is at least one (non-incoherent) potential unifier, matchInstEnv
|
|
| 681 | + returns a NotSure result and refrains from committing to the instance.
|
|
| 682 | + |
|
| 683 | + Incoherent instances are not returned as part of the potential unifiers. This
|
|
| 684 | + affects error messages: they will not be listed as "potentially matching instances"
|
|
| 685 | + in an "Overlapping instances" or "Ambiguous type variable" error.
|
|
| 686 | + See also Note [Recording coherence information in `PotentialUnifiers`].
|
|
| 666 | 687 | |
| 667 | - If all are *incoherent* (OverlapFlag = Incoherent or NonCanonical)
|
|
| 668 | - return (NoUnifiers nc), where nc is EvNonCanonical if any of the discarded
|
|
| 669 | - unifiers are NonCanonical.
|
|
| 670 | 688 | |
| 671 | 689 | Notice that these rules are not influenced by flag settings in the
|
| 672 | 690 | client module, where the instances are *used*. These rules make it
|
| ... | ... | @@ -894,8 +912,8 @@ instances, i.e. with `-fno-specialise-incoherents`. |
| 894 | 912 | |
| 895 | 913 | To avoid this incoherence breaking the specialiser,
|
| 896 | 914 | |
| 897 | -* We label as "non-canonical" the dictionary constructed by a (potentially)
|
|
| 898 | - incoherent use of an ClsInst whose `OverlapFlag` is `NonCanonical`.
|
|
| 915 | +* We label as "non-canonical" any dictionary constructed by a (potentially)
|
|
| 916 | + incoherent use of an ClsInst.
|
|
| 899 | 917 | |
| 900 | 918 | * We do not specialise a function if there is a non-canonical
|
| 901 | 919 | dictionary in the /transistive dependencies/ of its dictionary
|
| ... | ... | @@ -922,7 +940,9 @@ So `d2` is incoherent, and hence (transitively) so is `d1`. |
| 922 | 940 | Here are the moving parts:
|
| 923 | 941 | |
| 924 | 942 | * GHC.Core.InstEnv.lookupInstEnv tells if any incoherent unifiers were discarded
|
| 925 | - in step (IL6) of the instance lookup.
|
|
| 943 | + in step (IL4) or (IL6) of the instance lookup: see
|
|
| 944 | + Note [Recording coherence information in `PotentialUnifiers`] and
|
|
| 945 | + Note [Canonicity for incoherent matches].
|
|
| 926 | 946 | |
| 927 | 947 | * That info is recorded in the `cir_is_coherent` field of `OneInst`, and thence
|
| 928 | 948 | transferred to the `ep_is_coherent` field of the `EvBind` for the dictionary.
|
| ... | ... | @@ -930,6 +950,47 @@ Here are the moving parts: |
| 930 | 950 | * In the desugarer we exploit this info:
|
| 931 | 951 | see Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr.
|
| 932 | 952 | See also Note [nospecId magic] in GHC.Types.Id.Make.
|
| 953 | + |
|
| 954 | + |
|
| 955 | +Note [Canonicity for incoherent matches]
|
|
| 956 | +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 957 | +When the selected instance is INCOHERENT at step (IL4) of
|
|
| 958 | +Note [Rules for instance lookup], we ignore all unifiers,
|
|
| 959 | +whether or not they are marked with INCOHERENT pragmas.
|
|
| 960 | +This is implemented by returning NoUnifiers in final_unifs.
|
|
| 961 | +NoUnifiers takes an argument indicating whether the match was canonical
|
|
| 962 | +as described in Note [Coherence and specialisation: overview] and
|
|
| 963 | +Note [Recording coherence information in `PotentialUnifiers`].
|
|
| 964 | + |
|
| 965 | +To determine whether an incoherent match was canonical, we look *only*
|
|
| 966 | +at the OverlapFlag of the instance being matched. For example:
|
|
| 967 | + |
|
| 968 | + class C a
|
|
| 969 | + instance {-# INCOHERENT #-} C a -- (1)
|
|
| 970 | + instance C Int -- (2)
|
|
| 971 | + |
|
| 972 | + [W] C tau
|
|
| 973 | + |
|
| 974 | +Here we match instance (1) and discard instance (2). If (1) is Incoherent
|
|
| 975 | +(under -fspecialise-incoherents), it is important that we treat the match
|
|
| 976 | +as EvCanonical so that we do not block specialisation (see #25883).
|
|
| 977 | + |
|
| 978 | +What about the following situation:
|
|
| 979 | + |
|
| 980 | + instance {-# INCOHERENT #-} C a -- (1), in a module with -fspecialise-incoherents (Incoherent)
|
|
| 981 | + instance {-# INCOHERENT #-} C Int -- (2), in a module with -fno-specialise-incoherents (NonCanonical)
|
|
| 982 | + |
|
| 983 | + [W] C tau
|
|
| 984 | + |
|
| 985 | +Again we match instance (1) and discard instance (2). It is not obvious
|
|
| 986 | +whether Incoherent or NonCanonical should "win" here, but it seems more
|
|
| 987 | +consistent with the previous example to look only at the flag on instance (1).
|
|
| 988 | + |
|
| 989 | +What about if the only instance that can match is marked as NonCanonical?
|
|
| 990 | +In this case are no unifiers at all, so all_unifs = NoUnifiers EvCanonical.
|
|
| 991 | +It is not obvious what -fno-specialise-incoherents should do here, but
|
|
| 992 | +currently it returns NoUnifiers EvCanonical.
|
|
| 993 | + |
|
| 933 | 994 | -}
|
| 934 | 995 | |
| 935 | 996 | type DFunInstType = Maybe Type
|
| ... | ... | @@ -1070,8 +1131,8 @@ data PotentialUnifiers |
| 1070 | 1131 | ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
| 1071 | 1132 | When we find a matching instance, there might be other instances that
|
| 1072 | 1133 | could potentially unify with the goal. For `INCOHERENT` instances, we
|
| 1073 | -don't care (see steps IL4 and IL6 in Note [Rules for instance
|
|
| 1074 | -lookup]). But if we have potentially unifying coherent instance, we
|
|
| 1134 | +don't care (see step (IL6) in Note [Rules for instance lookup]).
|
|
| 1135 | +But if we have potentially unifying coherent instance, we
|
|
| 1075 | 1136 | report these `OneOrMoreUnifiers` so that `matchInstEnv` can go down
|
| 1076 | 1137 | the `NotSure` route.
|
| 1077 | 1138 | |
| ... | ... | @@ -1081,6 +1142,21 @@ solution is canonical or not (see Note [Coherence and specialisation: |
| 1081 | 1142 | overview] for why we care at all). So when the set of potential
|
| 1082 | 1143 | unifiers is empty, we record in `NoUnifiers` if the one solution is
|
| 1083 | 1144 | `Canonical`.
|
| 1145 | + |
|
| 1146 | +For example, suppose we have:
|
|
| 1147 | + |
|
| 1148 | + class C x y
|
|
| 1149 | + instance C a Bool -- (1)
|
|
| 1150 | + instance {-# INCOHERENT #-} C Int a -- (2)
|
|
| 1151 | + |
|
| 1152 | + [W] C x Bool
|
|
| 1153 | + |
|
| 1154 | +Here instance (1) matches the Wanted, and since instance (2) is INCOHERENT
|
|
| 1155 | +we want to succeed with the match rather than getting stick at step (IL6).
|
|
| 1156 | +But if -fno-specialise-incoherents was enabled for (2), the specialiser is
|
|
| 1157 | +not permitted to specialise this dictionary later, so lookupInstEnv reports
|
|
| 1158 | +the PotentialUnifiers as NoUnifiers EvNonCanonical.
|
|
| 1159 | + |
|
| 1084 | 1160 | -}
|
| 1085 | 1161 | |
| 1086 | 1162 | instance Outputable CanonicalEvidence where
|
| ... | ... | @@ -1101,10 +1177,18 @@ getCoherentUnifiers :: PotentialUnifiers -> [ClsInst] |
| 1101 | 1177 | getCoherentUnifiers NoUnifiers{} = []
|
| 1102 | 1178 | getCoherentUnifiers (OneOrMoreUnifiers cls) = NE.toList cls
|
| 1103 | 1179 | |
| 1180 | +-- | Are there no *coherent* unifiers?
|
|
| 1104 | 1181 | nullUnifiers :: PotentialUnifiers -> Bool
|
| 1105 | 1182 | nullUnifiers NoUnifiers{} = True
|
| 1106 | 1183 | nullUnifiers _ = False
|
| 1107 | 1184 | |
| 1185 | +-- | Are there any unifiers, ignoring those marked Incoherent (but including any
|
|
| 1186 | +-- marked NonCanonical)?
|
|
| 1187 | +someUnifiers :: PotentialUnifiers -> Bool
|
|
| 1188 | +someUnifiers (NoUnifiers EvCanonical) = False
|
|
| 1189 | +someUnifiers _ = True
|
|
| 1190 | + |
|
| 1191 | + |
|
| 1108 | 1192 | instEnvMatchesAndUnifiers
|
| 1109 | 1193 | :: InstEnv -- InstEnv to look in
|
| 1110 | 1194 | -> VisibleOrphanModules -- But filter against this
|
| ... | ... | @@ -1209,10 +1293,13 @@ lookupInstEnv check_overlap_safe |
| 1209 | 1293 | tys
|
| 1210 | 1294 | = (final_matches, final_unifs, unsafe_overlapped)
|
| 1211 | 1295 | where
|
| 1296 | + -- (IL1): Find all instances that match the target constraint
|
|
| 1212 | 1297 | (home_matches, home_unifs) = instEnvMatchesAndUnifiers home_ie vis_mods cls tys
|
| 1213 | 1298 | (pkg_matches, pkg_unifs) = instEnvMatchesAndUnifiers pkg_ie vis_mods cls tys
|
| 1214 | 1299 | all_matches = home_matches <> pkg_matches
|
| 1215 | 1300 | all_unifs = home_unifs <> pkg_unifs
|
| 1301 | + |
|
| 1302 | + -- (IL3): Eliminate candidates that are overlapped or incoherent
|
|
| 1216 | 1303 | final_matches = pruneOverlappedMatches all_matches
|
| 1217 | 1304 | -- Even if the unifs is non-empty (an error situation)
|
| 1218 | 1305 | -- we still prune the matches, so that the error message isn't
|
| ... | ... | @@ -1230,10 +1317,13 @@ lookupInstEnv check_overlap_safe |
| 1230 | 1317 | (m:ms) | isIncoherent (fst m)
|
| 1231 | 1318 | -- Incoherent match, so discard all unifiers, but
|
| 1232 | 1319 | -- keep track of dropping coherent or non-canonical ones
|
| 1320 | + -- if the match is non-canonical.
|
|
| 1321 | + -- See Note [Canonicity for incoherent matches]
|
|
| 1233 | 1322 | -> assertPpr (null ms) (ppr final_matches) $
|
| 1234 | - case all_unifs of
|
|
| 1235 | - OneOrMoreUnifiers{} -> NoUnifiers EvNonCanonical
|
|
| 1236 | - NoUnifiers{} -> all_unifs
|
|
| 1323 | + NoUnifiers $
|
|
| 1324 | + if isNonCanonical (fst m) && someUnifiers all_unifs
|
|
| 1325 | + then EvNonCanonical
|
|
| 1326 | + else EvCanonical
|
|
| 1237 | 1327 | _ -> all_unifs
|
| 1238 | 1328 | |
| 1239 | 1329 | -- Note [Safe Haskell isSafeOverlap]
|
| ... | ... | @@ -926,7 +926,8 @@ matchClassInst dflags inerts clas tys loc |
| 926 | 926 | -- First check whether there is an in-scope Given that could
|
| 927 | 927 | -- match this constraint. In that case, do not use any instance
|
| 928 | 928 | -- whether top level, or local quantified constraints.
|
| 929 | --- See Note [Instance and Given overlap]
|
|
| 929 | +-- See Note [Instance and Given overlap] and see
|
|
| 930 | +-- (IL0) in Note [Rules for instance lookup] in GHC.Core.InstEnv
|
|
| 930 | 931 | | not (xopt LangExt.IncoherentInstances dflags)
|
| 931 | 932 | , not (isCTupleClass clas)
|
| 932 | 933 | -- It is always safe to unpack constraint tuples
|
| ... | ... | @@ -417,7 +417,7 @@ Overlapping instances |
| 417 | 417 | :status: Deprecated
|
| 418 | 418 | |
| 419 | 419 | Deprecated extension to weaken checks intended to ensure instance resolution
|
| 420 | - termination.
|
|
| 420 | + termination. Use ``OVERLAPPING``, ``OVERLAPPABLE`` or ``OVERLAPS`` pragmas instead.
|
|
| 421 | 421 | |
| 422 | 422 | .. extension:: IncoherentInstances
|
| 423 | 423 | :shortdesc: Allow definitions of instances that may result in incoherence.
|
| ... | ... | @@ -429,7 +429,9 @@ Overlapping instances |
| 429 | 429 | :status: Deprecated
|
| 430 | 430 | |
| 431 | 431 | Deprecated extension to weaken checks intended to ensure instance resolution
|
| 432 | - termination.
|
|
| 432 | + termination. Use ``INCOHERENT`` pragmas instead. Also permits classes to
|
|
| 433 | + have non-nominal roles, and affects the instance resolution algorithm for
|
|
| 434 | + in-scope given constraints.
|
|
| 433 | 435 | |
| 434 | 436 | In general, as discussed in :ref:`instance-resolution`, *GHC requires
|
| 435 | 437 | that it be unambiguous which instance declaration should be used to
|
| ... | ... | @@ -473,11 +475,15 @@ Now suppose that, in some client module, we are searching for an |
| 473 | 475 | instance of the *target constraint* ``(C ty1 .. tyn)``. The search works
|
| 474 | 476 | like this:
|
| 475 | 477 | |
| 478 | +- If there are any in-scope given constraints that might match the target
|
|
| 479 | + constraint (after unifying any metavariables), and
|
|
| 480 | + :extension:`IncoherentInstances` is not enabled, the search fails.
|
|
| 481 | + |
|
| 476 | 482 | - Find all instances :math:`I` that *match* the target constraint; that is, the
|
| 477 | 483 | target constraint is a substitution instance of :math:`I`. These instance
|
| 478 | 484 | declarations are the *candidates*.
|
| 479 | 485 | |
| 480 | -- If no candidates remain, the search fails
|
|
| 486 | +- If there are no candidates, the search fails.
|
|
| 481 | 487 | |
| 482 | 488 | - Eliminate any candidate :math:`IX` for which there is another candidate
|
| 483 | 489 | :math:`IY` such that both of the following hold:
|
| ... | ... | @@ -498,7 +504,7 @@ like this: |
| 498 | 504 | - Otherwise there is exactly one non-incoherent candidate; call it the
|
| 499 | 505 | "prime candidate".
|
| 500 | 506 | |
| 501 | -- Now find all instances, or in-scope given constraints, that *unify* with
|
|
| 507 | +- Now find all instances that *unify* with
|
|
| 502 | 508 | the target constraint,
|
| 503 | 509 | but do not *match* it. Such non-candidate instances might match when
|
| 504 | 510 | the target constraint is further instantiated. If all of them are
|
| ... | ... | @@ -596,8 +602,8 @@ declaration, thus: :: |
| 596 | 602 | |
| 597 | 603 | (You need :extension:`FlexibleContexts` to do this.)
|
| 598 | 604 | |
| 599 | -In the unification check in the final bullet, GHC also uses the
|
|
| 600 | -"in-scope given constraints". Consider for example ::
|
|
| 605 | +As an example of the "in-scope given constraints" in the first bullet,
|
|
| 606 | +consider ::
|
|
| 601 | 607 | |
| 602 | 608 | instance C a Int
|
| 603 | 609 | |
| ... | ... | @@ -609,7 +615,7 @@ top-level instance, because a particular call of ``g`` might |
| 609 | 615 | instantiate both ``b`` and ``c`` to the same type, which would
|
| 610 | 616 | allow the constraint to be solved in a different way. This latter
|
| 611 | 617 | restriction is principally to make the constraint-solver complete.
|
| 612 | -(Interested folk can read ``Note [Instance and Given overlap]`` in ``TcInteract``.)
|
|
| 618 | +(Interested folk can read ``Note [Instance and Given overlap]`` in ``GHC.Tc.Solver.Dict``.)
|
|
| 613 | 619 | It is easy to avoid: in a type signature avoid a constraint that
|
| 614 | 620 | matches a top-level instance. The flag :ghc-flag:`-Wsimplifiable-class-constraints` warns about such signatures.
|
| 615 | 621 | |
| ... | ... | @@ -660,6 +666,22 @@ matches a top-level instance. The flag :ghc-flag:`-Wsimplifiable-class-constrai |
| 660 | 666 | to reject module ``Help`` on the grounds that a later instance
|
| 661 | 667 | declaration might overlap the local one.)
|
| 662 | 668 | |
| 669 | +.. warning::
|
|
| 670 | + GHC's optimiser (in particular, the :ghc-flag:`-fspecialise` option)
|
|
| 671 | + assumes that type-classes are coherent, and hence it may replace
|
|
| 672 | + any type-class dictionary argument with another dictionary of the same
|
|
| 673 | + type.
|
|
| 674 | + |
|
| 675 | + This may cause unexpected results if incoherence occurs due to incoherent
|
|
| 676 | + or overlapping instances, and there is an observable difference between the
|
|
| 677 | + instances (see :ghc-ticket:`22448` and :ghc-ticket:`24924` for examples).
|
|
| 678 | + |
|
| 679 | + The :ghc-flag:`-fno-specialise-incoherents <-fspecialise-incoherents>` will
|
|
| 680 | + inhibit specialisation in the presence of some incoherent instance matches,
|
|
| 681 | + which may help avoid this issue at the cost of runtime performance.
|
|
| 682 | + Alternatively, specialisation can be disabled entirely with
|
|
| 683 | + :ghc-flag:`-fno-specialise <-fspecialise>`.
|
|
| 684 | + |
|
| 663 | 685 | .. _instance-sigs:
|
| 664 | 686 | |
| 665 | 687 | Instance signatures: type signatures in instance declarations
|
| 1 | +-- By default -fspecialise-incoherents is in effect, so the call to m in f
|
|
| 2 | +-- should get specialised even though there is another potential instance.
|
|
| 3 | + |
|
| 4 | +{-# LANGUAGE UndecidableInstances #-}
|
|
| 5 | +module T25833 (y) where
|
|
| 6 | + |
|
| 7 | +class C a where
|
|
| 8 | + m :: a -> a
|
|
| 9 | + |
|
| 10 | +instance {-# INCOHERENT #-} Num a => C a where
|
|
| 11 | + m = (* 3)
|
|
| 12 | + |
|
| 13 | +instance C () where
|
|
| 14 | + m = id
|
|
| 15 | + |
|
| 16 | +f :: Num a => a -> a
|
|
| 17 | +f = m
|
|
| 18 | + |
|
| 19 | +y :: Int
|
|
| 20 | +y = f 2 |
| 1 | +y = I# 6# |
|
| \ No newline at end of file |
| 1 | +-- Under -fno-specialise-incoherents, the call to m in f should not be
|
|
| 2 | +-- specialised, because there is another possible (though unused) instance.
|
|
| 3 | + |
|
| 4 | +{-# OPTIONS_GHC -fno-specialise-incoherents #-}
|
|
| 5 | +{-# LANGUAGE UndecidableInstances #-}
|
|
| 6 | +module T25833b (y) where
|
|
| 7 | + |
|
| 8 | +class C a where
|
|
| 9 | + m :: a -> a
|
|
| 10 | + |
|
| 11 | +instance {-# INCOHERENT #-} Num a => C a where
|
|
| 12 | + m = (* 3)
|
|
| 13 | + |
|
| 14 | +instance C () where
|
|
| 15 | + m = id
|
|
| 16 | + |
|
| 17 | +f :: Num a => a -> a
|
|
| 18 | +f = m
|
|
| 19 | + |
|
| 20 | +y :: Int
|
|
| 21 | +y = f 2 |
| 1 | +y = nospec m |
|
| \ No newline at end of file |
| 1 | +-- Here -fno-specialise-incoherents is in effect, but f refers unambiguously to
|
|
| 2 | +-- a single instance (because there are no others), so it should be specialised.
|
|
| 3 | + |
|
| 4 | +{-# OPTIONS_GHC -fno-specialise-incoherents #-}
|
|
| 5 | +{-# LANGUAGE UndecidableInstances #-}
|
|
| 6 | +module T25833c (y) where
|
|
| 7 | + |
|
| 8 | +class C a where
|
|
| 9 | + m :: a -> a
|
|
| 10 | + |
|
| 11 | +instance {-# INCOHERENT #-} Num a => C a where
|
|
| 12 | + m = (* 3)
|
|
| 13 | + |
|
| 14 | +f :: Num a => a -> a
|
|
| 15 | +f = m
|
|
| 16 | + |
|
| 17 | +y :: Int
|
|
| 18 | +y = f 2 |
| 1 | +y = I# 6# |
|
| \ No newline at end of file |
| 1 | +{-# OPTIONS_GHC -fno-specialise-incoherents #-}
|
|
| 2 | + |
|
| 3 | +module T25883d (y) where
|
|
| 4 | + |
|
| 5 | +import T25883d_import
|
|
| 6 | + |
|
| 7 | +instance {-# INCOHERENT #-} C () where
|
|
| 8 | + m = id
|
|
| 9 | + |
|
| 10 | +f :: Num a => a -> a
|
|
| 11 | +f = m
|
|
| 12 | + |
|
| 13 | +y :: Int
|
|
| 14 | +y = f 2 |
|
| \ No newline at end of file |
| 1 | +y = I# 6# |
| 1 | +-- This module defines an instance with -fspecialise-incoherents in effect,
|
|
| 2 | +-- then it will be imported by a module that uses -fno-specialise-incoherents.
|
|
| 3 | + |
|
| 4 | +{-# LANGUAGE UndecidableInstances #-}
|
|
| 5 | +module T25883d_import where
|
|
| 6 | + |
|
| 7 | +class C a where
|
|
| 8 | + m :: a -> a
|
|
| 9 | + |
|
| 10 | +instance {-# INCOHERENT #-} Num a => C a where
|
|
| 11 | + m = (* 3) |
| ... | ... | @@ -536,3 +536,8 @@ test('T25197', [req_th, extra_files(["T25197_TH.hs"]), only_ways(['optasm'])], m |
| 536 | 536 | test('T25389', normal, compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeable-binds'])
|
| 537 | 537 | test('T24359a', normal, compile, ['-O -ddump-rules'])
|
| 538 | 538 | test('T25713', [grep_errmsg('W:::')], compile, ['-O -ddump-simpl'])
|
| 539 | + |
|
| 540 | +test('T25883', normal, compile_grep_core, [''])
|
|
| 541 | +test('T25883b', normal, compile_grep_core, [''])
|
|
| 542 | +test('T25883c', normal, compile_grep_core, [''])
|
|
| 543 | +test('T25883d', [extra_files(['T25883d_import.hs'])], multimod_compile_filter, ['T25883d', '-O -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques', r'grep -e "y ="']) |
| 1 | +{-# OPTIONS_GHC -fno-specialise-incoherents #-}
|
|
| 2 | +{-# LANGUAGE MonoLocalBinds #-}
|
|
| 3 | +class C a where
|
|
| 4 | + op :: a -> String
|
|
| 5 | + |
|
| 6 | +instance {-# OVERLAPPABLE #-} C a where
|
|
| 7 | + op _ = "C a"
|
|
| 8 | + {-# NOINLINE op #-}
|
|
| 9 | + |
|
| 10 | +instance {-# INCOHERENT #-} C (Maybe a) where
|
|
| 11 | + op _ = "C (Maybe a)"
|
|
| 12 | + {-# NOINLINE op #-}
|
|
| 13 | + |
|
| 14 | +instance {-# INCOHERENT #-} C (Maybe ()) where
|
|
| 15 | + op _ = "C (Maybe ())"
|
|
| 16 | + {-# NOINLINE op #-}
|
|
| 17 | + |
|
| 18 | +-- | Inhibit inlining, but keep specialize-ability
|
|
| 19 | +large :: a -> a
|
|
| 20 | +large x = x
|
|
| 21 | +{-# NOINLINE large #-}
|
|
| 22 | + |
|
| 23 | +bar :: C a => a -> String
|
|
| 24 | +bar x = large (large (large (large (large (large (large (large (large (large (large (large (large (large (op x))))))))))))))
|
|
| 25 | + |
|
| 26 | +gen :: a -> String -- No C a constraint, has to choose the incoherent generic instance
|
|
| 27 | +gen = bar
|
|
| 28 | + |
|
| 29 | +specMaybe :: Maybe a -> String -- C () constraint is resolved to the specialized instance for Maybe a
|
|
| 30 | +specMaybe = bar
|
|
| 31 | + |
|
| 32 | +specMaybeUnit :: Maybe () -> String -- C () constraint is resolved to the specialized instance for Maybe ()
|
|
| 33 | +specMaybeUnit = bar
|
|
| 34 | + |
|
| 35 | +main :: IO ()
|
|
| 36 | +main = do
|
|
| 37 | + putStrLn $ "gen () == " <> gen (Just ())
|
|
| 38 | + putStrLn $ "specMaybe () == " <> specMaybe (Just ())
|
|
| 39 | + putStrLn $ "specMaybeUnit () == " <> specMaybeUnit (Just ()) |
| 1 | +gen () == C a
|
|
| 2 | +specMaybe () == C (Maybe a)
|
|
| 3 | +specMaybeUnit () == C (Maybe ()) |
| ... | ... | @@ -119,3 +119,4 @@ test('T24725', normal, compile_and_run, ['-O -dcore-lint']) |
| 119 | 119 | test('T25096', normal, compile_and_run, ['-O -dcore-lint'])
|
| 120 | 120 | test('AppIsHNF', normal, compile_and_run, ['-O'])
|
| 121 | 121 | test('T24359b', normal, compile_and_run, ['-O'])
|
| 122 | +test('T23429', normal, compile_and_run, ['-O']) |