Sjoerd Visscher pushed to branch wip/T18570 at Glasgow Haskell Compiler / GHC

Commits:

22 changed files:

Changes:

  • compiler/GHC/Core/DataCon.hs
    ... ... @@ -44,6 +44,7 @@ module GHC.Core.DataCon (
    44 44
             dataConInstOrigArgTys, dataConRepArgTys, dataConResRepTyArgs,
    
    45 45
             dataConInstUnivs,
    
    46 46
             dataConFieldLabels, dataConFieldType, dataConFieldType_maybe,
    
    47
    +        dataConOtherFieldsAllMultMany,
    
    47 48
             dataConSrcBangs,
    
    48 49
             dataConSourceArity, dataConVisArity, dataConRepArity,
    
    49 50
             dataConIsInfix,
    
    ... ... @@ -1406,6 +1407,15 @@ dataConFieldType_maybe :: DataCon -> FieldLabelString
    1406 1407
     dataConFieldType_maybe con label
    
    1407 1408
       = find ((== label) . flLabel . fst) (dcFields con `zip` (scaledThing <$> dcOrigArgTys con))
    
    1408 1409
     
    
    1410
    +-- | Check if all the fields of the 'DataCon' have multiplicity 'Many',
    
    1411
    +-- except for the given labelled field. In this case the selector
    
    1412
    +-- of the given field can be a linear function, since it is allowed
    
    1413
    +-- to discard all the other fields.
    
    1414
    +dataConOtherFieldsAllMultMany :: DataCon -> FieldLabelString -> Bool
    
    1415
    +dataConOtherFieldsAllMultMany con label
    
    1416
    +  = all (\(fld, mult) -> flLabel fld == label || isManyTy mult)
    
    1417
    +      (dcFields con `zip` (scaledMult <$> dcOrigArgTys con))
    
    1418
    +
    
    1409 1419
     -- | Strictness/unpack annotations, from user; or, for imported
    
    1410 1420
     -- DataCons, from the interface file
    
    1411 1421
     -- The list is in one-to-one correspondence with the arity of the 'DataCon'
    

  • compiler/GHC/Tc/Errors/Ppr.hs
    ... ... @@ -3541,12 +3541,12 @@ pprHoleFit :: HoleFitDispConfig -> HoleFit -> SDoc
    3541 3541
     pprHoleFit _ (RawHoleFit sd) = sd
    
    3542 3542
     pprHoleFit (HFDC sWrp sWrpVars sTy sProv sMs) (TcHoleFit (HoleFit {..})) =
    
    3543 3543
      hang display 2 provenance
    
    3544
    - where tyApp = sep $ zipWithEqual pprArg vars hfWrap
    
    3544
    + where tyApps = concat $ zipWithEqual pprArg vars hfWrap
    
    3545 3545
              where pprArg b arg = case binderFlag b of
    
    3546
    -                                Specified -> text "@" <> pprParendType arg
    
    3546
    +                                Specified -> [text "@" <> pprParendType arg]
    
    3547 3547
                                       -- Do not print type application for inferred
    
    3548 3548
                                       -- variables (#16456)
    
    3549
    -                                Inferred  -> empty
    
    3549
    +                                Inferred  -> []
    
    3550 3550
                                     Required  -> pprPanic "pprHoleFit: bad Required"
    
    3551 3551
                                                              (ppr b <+> ppr arg)
    
    3552 3552
            tyAppVars = sep $ punctuate comma $
    
    ... ... @@ -3573,9 +3573,9 @@ pprHoleFit (HFDC sWrp sWrpVars sTy sProv sMs) (TcHoleFit (HoleFit {..})) =
    3573 3573
                        IdHFCand id_    -> pprPrefixOcc id_
    
    3574 3574
            tyDisp = ppWhen sTy $ dcolon <+> ppr hfType
    
    3575 3575
            has = not . null
    
    3576
    -       wrapDisp = ppWhen (has hfWrap && (sWrp || sWrpVars))
    
    3576
    +       wrapDisp = ppWhen (has tyApps && (sWrp || sWrpVars))
    
    3577 3577
                        $ text "with" <+> if sWrp || not sTy
    
    3578
    -                                     then occDisp <+> tyApp
    
    3578
    +                                     then occDisp <+> sep tyApps
    
    3579 3579
                                          else tyAppVars
    
    3580 3580
            docs = case hfDoc of
    
    3581 3581
                     Just d -> pprHsDocStrings d
    

  • compiler/GHC/Tc/TyCl.hs
    ... ... @@ -4787,6 +4787,7 @@ checkValidTyCl tc
    4787 4787
       = setSrcSpan (getSrcSpan tc) $
    
    4788 4788
         addTyConCtxt tc            $
    
    4789 4789
         recoverM recovery_code     $
    
    4790
    +    checkNoErrs                $
    
    4790 4791
         do { traceTc "Starting validity for tycon" (ppr tc)
    
    4791 4792
            ; checkValidTyCon tc
    
    4792 4793
            ; checkTyConConsistentWithBoot tc -- See Note [TyCon boot consistency checking]
    
    ... ... @@ -4818,6 +4819,9 @@ See indexed-types/should_fail/BadSock and #10896
    4818 4819
     
    
    4819 4820
     Some notes:
    
    4820 4821
     
    
    4822
    +* Not all errors in `checkValidTyCon` fail in the monad. To make sure
    
    4823
    +  we also recover from these, we use `checkNoErrs`. See (#26149)
    
    4824
    +
    
    4821 4825
     * We must make fakes for promoted DataCons too. Consider (#15215)
    
    4822 4826
           data T a = MkT ...
    
    4823 4827
           data S a = ...T...MkT....
    
    ... ... @@ -4991,7 +4995,7 @@ checkValidTyCon tc
    4991 4995
         check_fields ((label, con1) :| other_fields)
    
    4992 4996
             -- These fields all have the same name, but are from
    
    4993 4997
             -- different constructors in the data type
    
    4994
    -        = recoverM (return ()) $ mapM_ checkOne other_fields
    
    4998
    +        = mapM_ checkOne other_fields
    
    4995 4999
                     -- Check that all the fields in the group have the same type
    
    4996 5000
                     -- NB: this check assumes that all the constructors of a given
    
    4997 5001
                     -- data type use the same type variables
    
    ... ... @@ -5001,8 +5005,9 @@ checkValidTyCon tc
    5001 5005
             lbl = flLabel label
    
    5002 5006
     
    
    5003 5007
             checkOne (_, con2)    -- Do it both ways to ensure they are structurally identical
    
    5004
    -            = do { checkFieldCompat lbl con1 con2 res1 res2 fty1 fty2
    
    5005
    -                 ; checkFieldCompat lbl con2 con1 res2 res1 fty2 fty1 }
    
    5008
    +            = traverse_ addErrTc $ firstJust -- Don't report the same error twice
    
    5009
    +                (checkFieldCompat lbl con1 con2 res1 res2 fty1 fty2)
    
    5010
    +                (checkFieldCompat lbl con2 con1 res2 res1 fty2 fty1)
    
    5006 5011
                 where
    
    5007 5012
                     res2 = dataConOrigResTy con2
    
    5008 5013
                     fty2 = dataConFieldType con2 lbl
    
    ... ... @@ -5027,10 +5032,13 @@ checkPartialRecordField all_cons fld
    5027 5032
         inst_tys = dataConResRepTyArgs con1
    
    5028 5033
     
    
    5029 5034
     checkFieldCompat :: FieldLabelString -> DataCon -> DataCon
    
    5030
    -                 -> Type -> Type -> Type -> Type -> TcM ()
    
    5035
    +                 -> Type -> Type -> Type -> Type -> Maybe TcRnMessage
    
    5031 5036
     checkFieldCompat fld con1 con2 res1 res2 fty1 fty2
    
    5032
    -  = do  { checkTc (isJust mb_subst1) (TcRnCommonFieldResultTypeMismatch con1 con2 fld)
    
    5033
    -        ; checkTc (isJust mb_subst2) (TcRnCommonFieldTypeMismatch con1 con2 fld) }
    
    5037
    +  = if isNothing mb_subst1
    
    5038
    +      then Just $ TcRnCommonFieldResultTypeMismatch con1 con2 fld
    
    5039
    +    else if isNothing mb_subst2
    
    5040
    +      then Just $ TcRnCommonFieldTypeMismatch con1 con2 fld
    
    5041
    +    else Nothing
    
    5034 5042
       where
    
    5035 5043
         mb_subst1 = tcMatchTy res1 res2
    
    5036 5044
         mb_subst2 = tcMatchTyX (expectJust mb_subst1) fty1 fty2
    

  • compiler/GHC/Tc/TyCl/Utils.hs
    ... ... @@ -32,7 +32,7 @@ import GHC.Tc.Utils.Env
    32 32
     import GHC.Tc.Gen.Bind( tcValBinds )
    
    33 33
     import GHC.Tc.Utils.TcType
    
    34 34
     
    
    35
    -import GHC.Builtin.Types( unitTy )
    
    35
    +import GHC.Builtin.Types( unitTy, manyDataConTy, multiplicityTy )
    
    36 36
     import GHC.Builtin.Uniques ( mkBuiltinUnique )
    
    37 37
     
    
    38 38
     import GHC.Hs
    
    ... ... @@ -71,6 +71,7 @@ import GHC.Types.Name.Env
    71 71
     import GHC.Types.Name.Reader ( mkRdrUnqual )
    
    72 72
     import GHC.Types.Id
    
    73 73
     import GHC.Types.Id.Info
    
    74
    +import GHC.Types.Var (mkTyVar)
    
    74 75
     import GHC.Types.Var.Env
    
    75 76
     import GHC.Types.Var.Set
    
    76 77
     import GHC.Types.Unique.Set
    
    ... ... @@ -853,11 +854,11 @@ mkRecSelBinds :: [TyCon] -> [(Id, LHsBind GhcRn)]
    853 854
     --    This makes life easier, because the later type checking will add
    
    854 855
     --    all necessary type abstractions and applications
    
    855 856
     mkRecSelBinds tycons
    
    856
    -  = map mkRecSelBind [ (tc,fld) | tc <- tycons
    
    857
    -                                , fld <- tyConFieldLabels tc ]
    
    857
    +  = [ mkRecSelBind tc fld | tc <- tycons
    
    858
    +                          , fld <- tyConFieldLabels tc ]
    
    858 859
     
    
    859
    -mkRecSelBind :: (TyCon, FieldLabel) -> (Id, LHsBind GhcRn)
    
    860
    -mkRecSelBind (tycon, fl)
    
    860
    +mkRecSelBind :: TyCon -> FieldLabel -> (Id, LHsBind GhcRn)
    
    861
    +mkRecSelBind tycon fl
    
    861 862
       = mkOneRecordSelector all_cons (RecSelData tycon) fl
    
    862 863
             FieldSelectors  -- See Note [NoFieldSelectors and naughty record selectors]
    
    863 864
       where
    
    ... ... @@ -916,17 +917,24 @@ mkOneRecordSelector all_cons idDetails fl has_sel
    916 917
                                                       -- thus suppressing making a binding
    
    917 918
                                                       -- A slight hack!
    
    918 919
     
    
    920
    +    all_other_fields_unrestricted = all all_other_unrestricted all_cons
    
    921
    +      where
    
    922
    +        all_other_unrestricted PatSynCon{} = False
    
    923
    +        all_other_unrestricted (RealDataCon dc) = dataConOtherFieldsAllMultMany dc lbl
    
    924
    +
    
    919 925
         sel_ty | is_naughty = unitTy  -- See Note [Naughty record selectors]
    
    920
    -           | otherwise  = mkForAllTys sel_tvbs $
    
    926
    +           | otherwise  = mkForAllTys (sel_tvbs ++ mult_tvb) $
    
    921 927
                               -- Urgh! See Note [The stupid context] in GHC.Core.DataCon
    
    922
    -                          mkPhiTy (conLikeStupidTheta con1) $
    
    928
    +                          mkPhiTy (conLikeStupidTheta con1)                       $
    
    923 929
                               -- req_theta is empty for normal DataCon
    
    924
    -                          mkPhiTy req_theta                 $
    
    925
    -                          mkVisFunTyMany data_ty            $
    
    926
    -                            -- Record selectors are always typed with Many. We
    
    927
    -                            -- could improve on it in the case where all the
    
    928
    -                            -- fields in all the constructor have multiplicity Many.
    
    930
    +                          mkPhiTy req_theta                                       $
    
    931
    +                          mkVisFunTy sel_mult data_ty                             $
    
    929 932
                               field_ty
    
    933
    +    non_partial = length all_cons == length cons_w_field -- See Note [Multiplicity and partial selectors]
    
    934
    +    (mult_tvb, sel_mult) = if non_partial && all_other_fields_unrestricted
    
    935
    +      then ([mkForAllTyBinder (Invisible InferredSpec) mult_var], mkTyVarTy mult_var)
    
    936
    +      else ([], manyDataConTy)
    
    937
    +    mult_var = mkTyVar (mkSysTvName (mkBuiltinUnique 1) (fsLit "m")) multiplicityTy
    
    930 938
     
    
    931 939
         -- make the binding: sel (C2 { fld = x }) = x
    
    932 940
         --                   sel (C7 { fld = x }) = x
    
    ... ... @@ -1165,4 +1173,13 @@ Therefore, when used in the right-hand side of `unT`, GHC attempts to
    1165 1173
     instantiate `a` with `(forall b. b -> b) -> Int`, which is impredicative.
    
    1166 1174
     To make sure that GHC is OK with this, we enable ImpredicativeTypes internally
    
    1167 1175
     when typechecking these HsBinds so that the user does not have to.
    
    1176
    +
    
    1177
    +Note [Multiplicity and partial selectors]
    
    1178
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    1179
    +While all logic for making record selectors multiplicity-polymorphic also applies
    
    1180
    +to partial selectors, there is a technical difficulty: the catch-all default case
    
    1181
    +that is added throws away its argument, and so cannot be linear. A simple workaround
    
    1182
    +was not found. There may exist a more complicated workaround, but the combination of
    
    1183
    +linear types and partial selectors is not expected to be very popular in practice, so
    
    1184
    +it was decided to not allow multiplicity-polymorphic partial selectors at all.
    
    1168 1185
     -}

  • docs/users_guide/9.14.1-notes.rst
    ... ... @@ -67,6 +67,13 @@ Language
    67 67
     
    
    68 68
       This causes the constructor to have type ``Rec :: Int %'Many -> Char %1 -> Record``.
    
    69 69
     
    
    70
    +  Also record selector functions are now multiplicity-polymorphic when possible.
    
    71
    +  In the above example the selector function ``y`` now has type
    
    72
    +  ``y :: Record %m -> Char``, because the ``x`` field is allowed to be discarded.
    
    73
    +  In particular this always applies to the selector of a newtype wrapper.
    
    74
    +  (Note that in theory this should also work with partial record selectors,
    
    75
    +  but for technical reasons this is not supported.)
    
    76
    +
    
    70 77
     * The :extension:`ExplicitNamespaces` extension now allows the ``data``
    
    71 78
       namespace specifier in import and export lists.
    
    72 79
     
    

  • docs/users_guide/bugs.rst
    ... ... @@ -701,6 +701,9 @@ Bugs in GHC
    701 701
     -  Because of a toolchain limitation we are unable to support full Unicode paths
    
    702 702
        on Windows. On Windows we support up to Latin-1. See :ghc-ticket:`12971` for more.
    
    703 703
     
    
    704
    +-  For technical reasons, partial record selectors cannot be made
    
    705
    +   multiplicity-polymorphic, so they are always unrestricted.
    
    706
    +
    
    704 707
     .. _bugs-ghci:
    
    705 708
     
    
    706 709
     Bugs in GHCi (the interactive GHC)
    

  • docs/users_guide/exts/linear_types.rst
    ... ... @@ -238,7 +238,7 @@ to use ``MkT1`` in higher order functions. The additional multiplicity
    238 238
     argument ``m`` is marked as inferred (see
    
    239 239
     :ref:`inferred-vs-specified`), so that there is no conflict with
    
    240 240
     visible type application. When displaying types, unless
    
    241
    -``-XLinearTypes`` is enabled, multiplicity polymorphic functions are
    
    241
    +``-XLinearTypes`` is enabled, multiplicity-polymorphic functions are
    
    242 242
     printed as regular functions (see :ref:`printing-linear-types`);
    
    243 243
     therefore constructors appear to have regular function types.
    
    244 244
     
    
    ... ... @@ -256,21 +256,33 @@ using GADT syntax or record syntax. Given
    256 256
     ::
    
    257 257
     
    
    258 258
         data T2 a b c where
    
    259
    -        MkT2 :: a -> b %1 -> c %1 -> T2 a b c -- Note unrestricted arrow in the first argument
    
    259
    +        MkT2 :: a -> b %1 -> c -> T2 a b c -- Note the unrestricted arrows on a and c
    
    260 260
     
    
    261
    -the value ``MkT2 x y z`` can be constructed only if ``x`` is
    
    262
    -unrestricted. On the other hand, a linear function which is matching
    
    263
    -on ``MkT2 x y z`` must consume ``y`` and ``z`` exactly once, but there
    
    264
    -is no restriction on ``x``. The same example can be written using record syntax:
    
    261
    +the value ``MkT2 x y z`` can be constructed only if ``x`` and
    
    262
    +``z`` are unrestricted. On the other hand, a linear function which is
    
    263
    +matching on ``MkT2 x y z`` must consume ``y`` exactly once, but there
    
    264
    +is no restriction on ``x`` and ``z``.
    
    265
    +The same example can be written using record syntax:
    
    265 266
     
    
    266 267
     ::
    
    267 268
     
    
    268
    -    data T2 a b c = MkT2 { x %'Many :: a, y :: b, z :: c }
    
    269
    +    data T2 a b c = MkT2 { x %'Many :: a, y :: b, z %'Many :: c }
    
    269 270
     
    
    270 271
     Again, the constructor ``MkT2`` has type ``MkT2 :: a -> b %1 -> c %1 -> T2 a b c``.
    
    271 272
     Note that by default record fields are linear, only unrestricted fields
    
    272
    -require a multiplicity annotation. The annotation has no effect on the record selectors.
    
    273
    -So ``x`` has type ``x :: T2 a b c -> a`` and similarly ``y`` has type ``y :: T2 a b c -> b``.
    
    273
    +require a multiplicity annotation.
    
    274
    +
    
    275
    +The multiplicity of record selectors is inferred from the multiplicity of the fields. Note that
    
    276
    +the effect of a selector is to discard all the other fields, so it can only be linear if all the
    
    277
    +other fields are unrestricted. So ``x`` has type ``x :: T2 a b c -> a``, because the ``y`` field
    
    278
    +is not unrestricted. But the ``x`` and ``z`` fields are unrestricted, so the selector for ``y``
    
    279
    +can be linear, and therefore it is made to be multiplicity-polymorphic: ``y :: T2 a b c %m -> b``.
    
    280
    +In particular this always applies to the selector of a newtype wrapper.
    
    281
    +
    
    282
    +In the case of multiple constructors, this logic is repeated for each constructor. So a selector
    
    283
    +is only made multiplicity-polymorphic if for every constructor all the other fields are unrestricted.
    
    284
    +(For technical reasons, partial record selectors cannot be made multiplicity-polymorphic, so they
    
    285
    +are always unrestricted.)
    
    274 286
     
    
    275 287
     It is also possible to define a multiplicity-polymorphic field:
    
    276 288
     
    

  • testsuite/tests/linear/should_compile/LinearRecordSelector.hs
    1
    +{-# LANGUAGE LinearTypes, DataKinds, OverloadedRecordDot, RebindableSyntax #-}
    
    2
    +module LinearRecordSelector where
    
    3
    +
    
    4
    +import GHC.Exts (Multiplicity(..))
    
    5
    +import Prelude
    
    6
    +
    
    7
    +data Test = A { test :: Int, test2 %Many :: String } | B { test %Many :: Int, test3 %Many :: Char }
    
    8
    +
    
    9
    +test1 :: Test %1 -> Int
    
    10
    +test1 a = test a
    
    11
    +
    
    12
    +testM :: Test -> Int
    
    13
    +testM a = test a
    
    14
    +
    
    15
    +testX :: Test %m -> Int
    
    16
    +testX = test
    
    17
    +
    
    18
    +newtype NT = NT { unNT :: Int }
    
    19
    +
    
    20
    +nt :: NT %m -> Int
    
    21
    +nt a = unNT a

  • testsuite/tests/linear/should_compile/all.T
    ... ... @@ -36,6 +36,7 @@ test('LinearTH3', normal, compile, [''])
    36 36
     test('LinearTH4', req_th, compile, [''])
    
    37 37
     test('LinearHole', normal, compile, [''])
    
    38 38
     test('LinearDataConSections', normal, compile, [''])
    
    39
    +test('LinearRecordSelector', normal, compile, ['-dcore-lint'])
    
    39 40
     test('T18731', normal, compile, [''])
    
    40 41
     test('T19400', unless(compiler_debugged(), skip), compile, [''])
    
    41 42
     test('T20023', normal, compile, [''])
    

  • testsuite/tests/linear/should_fail/LinearRecordSelectorFail.hs
    1
    +{-# LANGUAGE LinearTypes, DataKinds, OverloadedRecordDot, RebindableSyntax #-}
    
    2
    +module LinearRecordSelector where
    
    3
    +
    
    4
    +import GHC.Exts (Multiplicity(..))
    
    5
    +import Prelude
    
    6
    +
    
    7
    +data Test1 = A1 { testA11 :: Int, testA12 :: String }
    
    8
    +
    
    9
    +-- Fails because testA12 is linear
    
    10
    +test1 :: Test1 %1 -> Int
    
    11
    +test1 a = testA11 a
    
    12
    +
    
    13
    +data Test2 = A2 { testA2 :: Int } | B2 { testB2 %Many :: Char }
    
    14
    +
    
    15
    +-- Fails because testA2 is partial
    
    16
    +test2 :: Test2 %1 -> Int
    
    17
    +test2 a = testA2 a

  • testsuite/tests/linear/should_fail/LinearRecordSelectorFail.stderr
    1
    +LinearRecordSelectorFail.hs:11:7: error: [GHC-18872]
    
    2
    +    • Couldn't match type ‘Many’ with ‘One’
    
    3
    +        arising from multiplicity of ‘a’
    
    4
    +    • In an equation for ‘test1’: test1 a = testA11 a
    
    5
    +
    
    6
    +LinearRecordSelectorFail.hs:17:7: error: [GHC-18872]
    
    7
    +    • Couldn't match type ‘Many’ with ‘One’
    
    8
    +        arising from multiplicity of ‘a’
    
    9
    +    • In an equation for ‘test2’: test2 a = testA2 a
    
    10
    +

  • testsuite/tests/linear/should_fail/all.T
    ... ... @@ -11,6 +11,7 @@ test('LinearNoExt', normal, compile_fail, [''])
    11 11
     test('LinearNoExtU', normal, compile_fail, [''])
    
    12 12
     test('LinearAsPat', normal, compile_fail, [''])
    
    13 13
     test('LinearLazyPat', normal, compile_fail, [''])
    
    14
    +test('LinearRecordSelectorFail', normal, compile_fail, [''])
    
    14 15
     test('LinearRecordUpdate', normal, compile_fail, [''])
    
    15 16
     test('LinearSeq', normal, compile_fail, [''])
    
    16 17
     test('LinearViewPattern', normal, compile_fail, [''])
    

  • testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.stderr
    1
    -
    
    2 1
     DRFHoleFits.hs:7:7: error: [GHC-88464]
    
    3 2
         • Found hole: _ :: T -> Int
    
    4 3
         • In the expression: _ :: T -> Int
    
    ... ... @@ -6,8 +5,8 @@ DRFHoleFits.hs:7:7: error: [GHC-88464]
    6 5
         • Relevant bindings include
    
    7 6
             bar :: T -> Int (bound at DRFHoleFits.hs:7:1)
    
    8 7
           Valid hole fits include
    
    9
    -        foo :: T -> Int (defined at DRFHoleFits.hs:5:16)
    
    10 8
             bar :: T -> Int (defined at DRFHoleFits.hs:7:1)
    
    9
    +        foo :: T -> Int (defined at DRFHoleFits.hs:5:16)
    
    11 10
     
    
    12 11
     DRFHoleFits.hs:8:7: error: [GHC-88464]
    
    13 12
         • Found hole: _ :: A.S -> Int
    
    ... ... @@ -20,3 +19,4 @@ DRFHoleFits.hs:8:7: error: [GHC-88464]
    20 19
             A.foo :: A.S -> Int
    
    21 20
               (imported qualified from ‘DRFHoleFits_A’ at DRFHoleFits.hs:3:1-35
    
    22 21
                (and originally defined at DRFHoleFits_A.hs:5:16-18))
    
    22
    +

  • testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout
    1 1
     data Main.R = Main.MkR {Main.foo :: GHC.Internal.Types.Int}
    
    2
    -Main.foo :: Main.R -> GHC.Internal.Types.Int
    
    3
    -Main.foo :: Main.R -> GHC.Internal.Types.Int
    
    4
    -Main.foo :: Main.R -> GHC.Internal.Types.Int
    
    2
    +Main.foo :: forall {m_0 :: GHC.Internal.Types.Multiplicity} .
    
    3
    +            Main.R %m_0 -> GHC.Internal.Types.Int
    
    4
    +Main.foo :: forall {m_0 :: GHC.Internal.Types.Multiplicity} .
    
    5
    +            Main.R %m_0 -> GHC.Internal.Types.Int
    
    6
    +Main.foo :: forall {m_0 :: GHC.Internal.Types.Multiplicity} .
    
    7
    +            Main.R %m_0 -> GHC.Internal.Types.Int
    
    5 8
     42

  • testsuite/tests/perf/compiler/T16875.stderr
    ... ... @@ -6,7 +6,5 @@ T16875.hs:12:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
    6 6
         • In an equation for ‘a’: a = _
    
    7 7
         • Relevant bindings include a :: p (bound at T16875.hs:12:1)
    
    8 8
           Valid hole fits include
    
    9
    -        a :: forall {p}. p
    
    10
    -          with a
    
    11
    -          (defined at T16875.hs:12:1)
    
    9
    +        a :: forall {p}. p (defined at T16875.hs:12:1)
    
    12 10
     

  • testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr
    1 1
     
    
    2 2
     ==================== Tidy Core ====================
    
    3 3
     Result size of Tidy Core
    
    4
    -  = {terms: 82, types: 52, coercions: 29, joins: 0/0}
    
    4
    +  = {terms: 83, types: 55, coercions: 31, joins: 0/0}
    
    5 5
     
    
    6
    --- RHS size: {terms: 3, types: 3, coercions: 0, joins: 0/0}
    
    7
    -unsafeToInteger1 :: forall (n :: Nat). Signed n -> Signed n
    
    6
    +-- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0}
    
    7
    +unsafeToInteger1
    
    8
    +  :: forall (n :: Nat) (m :: GHC.Internal.Types.Multiplicity).
    
    9
    +     Signed n %m -> Signed n
    
    8 10
     [GblId, Arity=1, Unf=OtherCon []]
    
    9
    -unsafeToInteger1 = \ (@(n :: Nat)) (ds :: Signed n) -> ds
    
    11
    +unsafeToInteger1
    
    12
    +  = \ (@(n :: Nat))
    
    13
    +      (@(m :: GHC.Internal.Types.Multiplicity))
    
    14
    +      (ds :: Signed n) ->
    
    15
    +      ds
    
    10 16
     
    
    11
    --- RHS size: {terms: 1, types: 0, coercions: 8, joins: 0/0}
    
    12
    -unsafeToInteger :: forall (n :: Nat). Signed n -> Integer
    
    17
    +-- RHS size: {terms: 1, types: 0, coercions: 10, joins: 0/0}
    
    18
    +unsafeToInteger
    
    19
    +  :: forall (n :: Nat) {m :: GHC.Internal.Types.Multiplicity}.
    
    20
    +     Signed n %m -> Integer
    
    13 21
     [GblId[[RecSel]], Arity=1, Unf=OtherCon []]
    
    14 22
     unsafeToInteger
    
    15 23
       = unsafeToInteger1
    
    16
    -    `cast` (forall (n :: <Nat>_N).
    
    17
    -            <Signed n>_R %<Many>_N ->_R OpaqueNoCastWW.N:Signed <n>_P
    
    18
    -            :: (forall (n :: Nat). Signed n -> Signed n)
    
    19
    -               ~R# (forall (n :: Nat). Signed n -> Integer))
    
    24
    +    `cast` (forall (n :: <Nat>_N) (m :: <GHC.Internal.Types.Multiplicity>_N).
    
    25
    +            <Signed n>_R %<m>_N ->_R OpaqueNoCastWW.N:Signed <n>_P
    
    26
    +            :: (forall (n :: Nat) (m :: GHC.Internal.Types.Multiplicity).
    
    27
    +                Signed n %m -> Signed n)
    
    28
    +               ~R# (forall (n :: Nat) (m :: GHC.Internal.Types.Multiplicity).
    
    29
    +                    Signed n %m -> Integer))
    
    20 30
     
    
    21 31
     -- RHS size: {terms: 8, types: 7, coercions: 21, joins: 0/0}
    
    22 32
     times [InlPrag=OPAQUE]
    

  • testsuite/tests/typecheck/should_fail/CommonFieldTypeMismatch.stderr
    1
    -CommonFieldTypeMismatch.hs:3:1: [GHC-91827]
    
    2
    -     Constructors A1 and A2 give different types for field ‘fld’
    
    3
    -     In the data type declaration for ‘A’
    1
    +CommonFieldTypeMismatch.hs:3:1: error: [GHC-91827]
    
    2
    +    • Constructors A1 and A2 give different types for field ‘fld’
    
    3
    +    • In the data type declaration for ‘A’
    
    4
    +

  • testsuite/tests/typecheck/should_fail/T12083a.hs
    1 1
     {-# LANGUAGE Haskell2010 #-}
    
    2 2
     {-# LANGUAGE TypeFamilies #-}
    
    3 3
     {-# LANGUAGE UnicodeSyntax #-}
    
    4
    +{-# LANGUAGE AllowAmbiguousTypes #-}
    
    4 5
     module T12803a where
    
    5 6
     
    
    6 7
     type Constrd a = Num a  a
    

  • testsuite/tests/typecheck/should_fail/T12083a.stderr
    1
    -
    
    2
    -T12083a.hs:6:1: error: [GHC-91510]
    
    1
    +T12083a.hs:7:1: error: [GHC-91510]
    
    3 2
         • Illegal qualified type: Num a => a
    
    4 3
         • In the type synonym declaration for ‘Constrd’
    
    5 4
         Suggested fix:
    
    6 5
           Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
    
    7 6
     
    
    8
    -T12083a.hs:10:26: error: [GHC-25709]
    
    7
    +T12083a.hs:11:26: error: [GHC-25709]
    
    9 8
         • Data constructor ‘ExistentiallyLost’ has existential type variables, a context, or a specialised result type
    
    10 9
             ExistentiallyLost :: forall u. TC u => u -> ExistentiallyLost
    
    11 10
         • In the definition of data constructor ‘ExistentiallyLost’
    
    12 11
           In the data type declaration for ‘ExistentiallyLost’
    
    13 12
         Suggested fix:
    
    14 13
           Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
    
    14
    +

  • testsuite/tests/typecheck/should_fail/T9739.hs
    1 1
     {-# LANGUAGE MultiParamTypeClasses #-}
    
    2
    +{-# LANGUAGE AllowAmbiguousTypes #-}
    
    2 3
     module T9739 where
    
    3 4
     
    
    4 5
     class Class3 a => Class1 a where
    

  • testsuite/tests/typecheck/should_fail/T9739.stderr
    1
    -
    
    2
    -T9739.hs:4:1: error: [GHC-29210]
    
    1
    +T9739.hs:5:1: error: [GHC-29210]
    
    3 2
         • Superclass cycle for ‘Class1’
    
    4 3
             one of whose superclasses is ‘Class3’
    
    5 4
             one of whose superclasses is ‘Class1’
    
    ... ... @@ -7,10 +6,11 @@ T9739.hs:4:1: error: [GHC-29210]
    7 6
         Suggested fix:
    
    8 7
           Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
    
    9 8
     
    
    10
    -T9739.hs:9:1: error: [GHC-29210]
    
    9
    +T9739.hs:10:1: error: [GHC-29210]
    
    11 10
         • Superclass cycle for ‘Class3’
    
    12 11
             one of whose superclasses is ‘Class1’
    
    13 12
             one of whose superclasses is ‘Class3’
    
    14 13
         • In the class declaration for ‘Class3’
    
    15 14
         Suggested fix:
    
    16 15
           Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
    
    16
    +

  • utils/haddock/html-test/ref/Bug294.html
    ... ... @@ -159,9 +159,13 @@
    159 159
     	><p class="src"
    
    160 160
     	  ><a id="v:problemField" class="def"
    
    161 161
     	    >problemField</a
    
    162
    -	    > :: TO <a href="#" title="Bug294"
    
    162
    +	    > :: <span class="keyword"
    
    163
    +	    >forall</span
    
    164
    +	    > {m :: <a href="#" title="GHC.Exts"
    
    165
    +	    >Multiplicity</a
    
    166
    +	    >}. TO <a href="#" title="Bug294"
    
    163 167
     	    >A</a
    
    164
    -	    > -&gt; <a href="#" title="Bug294"
    
    168
    +	    > %m -&gt; <a href="#" title="Bug294"
    
    165 169
     	    >A</a
    
    166 170
     	    > <a href="#" class="selflink"
    
    167 171
     	    >#</a
    
    ... ... @@ -171,9 +175,13 @@
    171 175
     	><p class="src"
    
    172 176
     	  ><a id="v:problemField-39-" class="def"
    
    173 177
     	    >problemField'</a
    
    174
    -	    > :: DO <a href="#" title="Bug294"
    
    178
    +	    > :: <span class="keyword"
    
    179
    +	    >forall</span
    
    180
    +	    > {m :: <a href="#" title="GHC.Exts"
    
    181
    +	    >Multiplicity</a
    
    182
    +	    >}. DO <a href="#" title="Bug294"
    
    175 183
     	    >A</a
    
    176
    -	    > -&gt; <a href="#" title="Bug294"
    
    184
    +	    > %m -&gt; <a href="#" title="Bug294"
    
    177 185
     	    >A</a
    
    178 186
     	    > <a href="#" class="selflink"
    
    179 187
     	    >#</a