Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

6 changed files:

Changes:

  • compiler/GHC/HsToCore/Ticks.hs
    ... ... @@ -251,7 +251,7 @@ addTickLHsBind (L pos (XHsBindsLR bind@(AbsBinds { abs_binds = binds
    251 251
     
    
    252 252
        add_rec_sels env =
    
    253 253
          env{ recSelBinds = recSelBinds env `extendVarEnvList`
    
    254
    -                          [ (abe_mono, abe_poly)
    
    254
    +                          [ (abe_mono, unitDVarSet abe_poly)
    
    255 255
                               | ABE{ abe_poly, abe_mono } <- abs_exports
    
    256 256
                               , RecSelId{} <- [idDetails abe_poly] ] }
    
    257 257
     
    
    ... ... @@ -270,8 +270,8 @@ addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id, fun_matches = matches
    270 270
       case tickish of { ProfNotes | inline -> return (L pos funBind); _ -> do
    
    271 271
     
    
    272 272
       -- See Note [Record-selector ticks]
    
    273
    -  selTick <- recSelTick id
    
    274
    -  case selTick of { Just tick -> tick_rec_sel tick; _ -> do
    
    273
    +  selTicks <- recSelTick id
    
    274
    +  case selTicks of { Just ticks -> tick_rec_sel ticks; _ -> do
    
    275 275
     
    
    276 276
       (fvs, mg) <-
    
    277 277
             getFreeVars $
    
    ... ... @@ -303,8 +303,8 @@ addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id, fun_matches = matches
    303 303
       } }
    
    304 304
       where
    
    305 305
         -- See Note [Record-selector ticks]
    
    306
    -    tick_rec_sel tick =
    
    307
    -      pure $ L pos $ funBind { fun_ext = second (tick :) (fun_ext funBind) }
    
    306
    +    tick_rec_sel ticks =
    
    307
    +      pure $ L pos $ funBind { fun_ext = second (ticks ++) (fun_ext funBind) }
    
    308 308
     
    
    309 309
     
    
    310 310
     -- Note [Record-selector ticks]
    
    ... ... @@ -319,9 +319,8 @@ addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id, fun_matches = matches
    319 319
     -- coverage purposes to improve the developer experience.
    
    320 320
     --
    
    321 321
     -- This is done by keeping track of which 'Id's are effectively bound to
    
    322
    --- record fields (using NamedFieldPuns or RecordWildCards) in 'TickTransEnv's
    
    323
    --- 'recSelBinds', and making 'HsVar's corresponding to those fields tick the
    
    324
    --- appropriate box when executed.
    
    322
    +-- record fields in 'TickTransEnv's 'recSelBinds', and making 'HsVar's
    
    323
    +-- corresponding to those fields tick the appropriate box when executed.
    
    325 324
     --
    
    326 325
     -- To enable that, we also treat 'FunBind's for record selector functions
    
    327 326
     -- specially. We only create a TopLevelBox for the record selector function,
    
    ... ... @@ -329,11 +328,11 @@ addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id, fun_matches = matches
    329 328
     -- of ticks for the same record selector, and is done by not recursing into
    
    330 329
     -- the fun_matches match group for record selector functions.
    
    331 330
     --
    
    331
    +-- Note that due to the use of 'HsVar's for ticking, certain patterns such
    
    332
    +-- as `Foo{foo = 42}` will not cause the `foo` selector to be ticked.
    
    333
    +--
    
    332 334
     -- This scheme could be extended further in the future, making coverage for
    
    333
    --- constructor fields (named or even positional) mean that the field was
    
    334
    --- accessed at run-time. For the time being, we only cover NamedFieldPuns and
    
    335
    --- RecordWildCards binds to cover most practical use-cases while keeping it
    
    336
    --- simple.
    
    335
    +-- positional constructor fields mean that the field was accessed at run-time.
    
    337 336
     
    
    338 337
     -- TODO: Revisit this
    
    339 338
     addTickLHsBind (L pos (pat@(PatBind { pat_lhs = lhs
    
    ... ... @@ -519,7 +518,7 @@ addTickHsExpr :: HsExpr GhcTc -> TM (HsExpr GhcTc)
    519 518
     -- See Note [Record-selector ticks]
    
    520 519
     addTickHsExpr e@(HsVar _ (L _ id)) =
    
    521 520
         freeVar id >> recSelTick id >>= pure . maybe e wrap
    
    522
    -  where wrap tick = XExpr . HsTick tick . noLocA $ e
    
    521
    +  where wrap = foldr (\tick -> XExpr . HsTick tick . noLocA) e
    
    523 522
     addTickHsExpr e@(HsIPVar {})            = return e
    
    524 523
     addTickHsExpr e@(HsOverLit {})          = return e
    
    525 524
     addTickHsExpr e@(HsOverLabel{})         = return e
    
    ... ... @@ -1086,7 +1085,7 @@ data TickTransEnv = TTE { fileName :: FastString
    1086 1085
                             , blackList    :: Set RealSrcSpan
    
    1087 1086
                             , this_mod     :: Module
    
    1088 1087
                             , tickishType  :: TickishType
    
    1089
    -                        , recSelBinds  :: IdEnv Id
    
    1088
    +                        , recSelBinds  :: IdEnv DVarSet
    
    1090 1089
                             }
    
    1091 1090
     
    
    1092 1091
     --      deriving Show
    
    ... ... @@ -1241,11 +1240,12 @@ allocTickBox boxLabel countEntries topOnly pos m
    1241 1240
           tickish <- mkTickish boxLabel countEntries topOnly pos fvs (declPath env)
    
    1242 1241
           return (this_loc (XExpr $ HsTick tickish $ this_loc e))
    
    1243 1242
     
    
    1244
    -recSelTick :: Id -> TM (Maybe CoreTickish)
    
    1243
    +recSelTick :: Id -> TM (Maybe [CoreTickish])
    
    1245 1244
     recSelTick id = ifDensity TickForCoverage maybe_tick (pure Nothing)
    
    1246 1245
       where
    
    1247 1246
         maybe_tick = getEnv >>=
    
    1248
    -      maybe (pure Nothing) tick . (`lookupVarEnv` id) . recSelBinds
    
    1247
    +      maybe (pure Nothing) tick_all . (`lookupVarEnv` id) . recSelBinds
    
    1248
    +    tick_all = fmap (Just . catMaybes) . mapM tick . dVarSetElems
    
    1249 1249
         tick sel = getState >>=
    
    1250 1250
           maybe (alloc sel) (pure . Just) . (`lookupVarEnv` sel) . recSelTicks
    
    1251 1251
         alloc sel = allocATickBox (box sel) False False (getSrcSpan sel) noFVs
    
    ... ... @@ -1367,7 +1367,7 @@ class CollectBinders a where
    1367 1367
     --
    
    1368 1368
     -- See Note [Record-selector ticks].
    
    1369 1369
     class CollectFldBinders a where
    
    1370
    -  collectFldBinds :: a -> IdEnv Id
    
    1370
    +  collectFldBinds :: a -> IdEnv DVarSet
    
    1371 1371
     
    
    1372 1372
     instance CollectBinders (LocatedA (Pat GhcTc)) where
    
    1373 1373
       collectBinds = collectPatBinders CollNoDictBinders
    
    ... ... @@ -1385,41 +1385,37 @@ instance (CollectFldBinders a) => CollectFldBinders [a] where
    1385 1385
     instance (CollectFldBinders e) => CollectFldBinders (GenLocated l e) where
    
    1386 1386
       collectFldBinds = collectFldBinds . unLoc
    
    1387 1387
     instance CollectFldBinders (Pat GhcTc) where
    
    1388
    -  collectFldBinds ConPat{ pat_args = RecCon HsRecFields{ rec_flds, rec_dotdot } } =
    
    1389
    -    collectFldBinds rec_flds `plusVarEnv` plusVarEnvList (zipWith fld_bnds [0..] rec_flds)
    
    1390
    -    where n_explicit | Just (L _ (RecFieldsDotDot n)) <- rec_dotdot = n
    
    1391
    -                     | otherwise = length rec_flds
    
    1392
    -          fld_bnds n (L _ HsFieldBind{ hfbLHS = L _ FieldOcc{ foLabel = L _ sel }
    
    1393
    -                                     , hfbRHS = L _ (VarPat _ (L _ var))
    
    1394
    -                                     , hfbPun })
    
    1395
    -            | hfbPun || n >= n_explicit = unitVarEnv var sel
    
    1396
    -          fld_bnds _ _ = emptyVarEnv
    
    1397
    -  collectFldBinds ConPat{ pat_args = PrefixCon pats } = collectFldBinds pats
    
    1398
    -  collectFldBinds ConPat{ pat_args = InfixCon p1 p2 } = collectFldBinds [p1, p2]
    
    1399
    -  collectFldBinds (LazyPat _ pat) = collectFldBinds pat
    
    1400
    -  collectFldBinds (BangPat _ pat) = collectFldBinds pat
    
    1401
    -  collectFldBinds (AsPat _ _ pat) = collectFldBinds pat
    
    1402
    -  collectFldBinds (ViewPat _ _ pat) = collectFldBinds pat
    
    1403
    -  collectFldBinds (ParPat _ pat) = collectFldBinds pat
    
    1404
    -  collectFldBinds (ListPat _ pats) = collectFldBinds pats
    
    1405
    -  collectFldBinds (TuplePat _ pats _) = collectFldBinds pats
    
    1406
    -  collectFldBinds (SumPat _ pats _ _) = collectFldBinds pats
    
    1407
    -  collectFldBinds (SigPat _ pat _) = collectFldBinds pat
    
    1408
    -  collectFldBinds (XPat exp) = collectFldBinds exp
    
    1409
    -  collectFldBinds VarPat{} = emptyVarEnv
    
    1410
    -  collectFldBinds WildPat{} = emptyVarEnv
    
    1411
    -  collectFldBinds OrPat{} = emptyVarEnv
    
    1412
    -  collectFldBinds LitPat{} = emptyVarEnv
    
    1413
    -  collectFldBinds NPat{} = emptyVarEnv
    
    1414
    -  collectFldBinds NPlusKPat{} = emptyVarEnv
    
    1415
    -  collectFldBinds SplicePat{} = emptyVarEnv
    
    1416
    -  collectFldBinds EmbTyPat{} = emptyVarEnv
    
    1417
    -  collectFldBinds InvisPat{} = emptyVarEnv
    
    1418
    -instance (CollectFldBinders r) => CollectFldBinders (HsFieldBind l r) where
    
    1419
    -  collectFldBinds = collectFldBinds . hfbRHS
    
    1420
    -instance CollectFldBinders XXPatGhcTc where
    
    1421
    -  collectFldBinds (CoPat _ pat _) = collectFldBinds pat
    
    1422
    -  collectFldBinds (ExpansionPat _ pat) = collectFldBinds pat
    
    1388
    +  collectFldBinds = go emptyDVarSet where
    
    1389
    +    go sels ConPat{ pat_args = RecCon HsRecFields{ rec_flds } } =
    
    1390
    +      plusVarEnvList (map fld_binds rec_flds)
    
    1391
    +        where fld_binds (L _ HsFieldBind{ hfbLHS = L _ FieldOcc{ foLabel = L _ sel }
    
    1392
    +                                        , hfbRHS = L _ rhs })
    
    1393
    +                = go (extendDVarSet sels sel) rhs
    
    1394
    +    go sels ConPat{ pat_args = PrefixCon ps } =
    
    1395
    +      plusVarEnvList (map (go sels . unLoc) ps)
    
    1396
    +    go sels ConPat{ pat_args = InfixCon (L _ p1) (L _ p2) } =
    
    1397
    +      go sels p1 `plusVarEnv` go sels p2
    
    1398
    +    go sels (VarPat _ (L _ var)) | isEmptyDVarSet sels = emptyVarEnv
    
    1399
    +                                 | otherwise = unitVarEnv var sels
    
    1400
    +    go sels (LazyPat _ (L _ p)) = go sels p
    
    1401
    +    go sels (BangPat _ (L _ p)) = go sels p
    
    1402
    +    go sels (AsPat _ _ (L _ p)) = go sels p
    
    1403
    +    go sels (ViewPat _ _ (L _ p)) = go sels p
    
    1404
    +    go sels (ParPat _ (L _ p)) = go sels p
    
    1405
    +    go sels (SigPat _ (L _ p) _) = go sels p
    
    1406
    +    go sels (SumPat _ (L _ p) _ _)  = go sels p
    
    1407
    +    go sels (XPat (CoPat _ p _)) = go sels p
    
    1408
    +    go sels (XPat (ExpansionPat _ p)) = go sels p
    
    1409
    +    go sels (ListPat _ ps) = plusVarEnvList (map (go sels . unLoc) ps)
    
    1410
    +    go sels (TuplePat _ ps _) = plusVarEnvList (map (go sels . unLoc) ps)
    
    1411
    +    go _ WildPat{} = emptyVarEnv
    
    1412
    +    go _ OrPat{} = emptyVarEnv
    
    1413
    +    go _ LitPat{} = emptyVarEnv
    
    1414
    +    go _ NPat{} = emptyVarEnv
    
    1415
    +    go _ NPlusKPat{} = emptyVarEnv
    
    1416
    +    go _ SplicePat{} = emptyVarEnv
    
    1417
    +    go _ EmbTyPat{} = emptyVarEnv
    
    1418
    +    go _ InvisPat{} = emptyVarEnv
    
    1423 1419
     instance CollectFldBinders (HsLocalBinds GhcTc) where
    
    1424 1420
       collectFldBinds (HsValBinds _ bnds) = collectFldBinds bnds
    
    1425 1421
       collectFldBinds HsIPBinds{} = emptyVarEnv
    
    ... ... @@ -1430,9 +1426,9 @@ instance CollectFldBinders (HsValBinds GhcTc) where
    1430 1426
     instance CollectFldBinders (HsBind GhcTc) where
    
    1431 1427
       collectFldBinds PatBind{ pat_lhs } = collectFldBinds pat_lhs
    
    1432 1428
       collectFldBinds (XHsBindsLR AbsBinds{ abs_exports, abs_binds }) =
    
    1433
    -    mkVarEnv [ (abe_poly, sel)
    
    1429
    +    mkVarEnv [ (abe_poly, sels)
    
    1434 1430
                  | ABE{ abe_poly, abe_mono } <- abs_exports
    
    1435
    -             , Just sel <- [lookupVarEnv monos abe_mono] ]
    
    1431
    +             , Just sels <- [lookupVarEnv monos abe_mono] ]
    
    1436 1432
         where monos = collectFldBinds abs_binds
    
    1437 1433
       collectFldBinds VarBind{} = emptyVarEnv
    
    1438 1434
       collectFldBinds FunBind{} = emptyVarEnv
    

  • docs/users_guide/9.14.1-notes.rst deleted
    1
    -.. _release-9-14-1:
    
    2
    -
    
    3
    -Version 9.14.1
    
    4
    -==============
    
    5
    -
    
    6
    -The significant changes to the various parts of the compiler are listed in the
    
    7
    -following sections. See the `migration guide
    
    8
    -<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.14>`_ on the GHC Wiki
    
    9
    -for specific guidance on migrating programs to this release.
    
    10
    -
    
    11
    -Language
    
    12
    -~~~~~~~~
    
    13
    -
    
    14
    -* `GHC proposal 493: allow expressions in SPECIALISE pragmas <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-specialise-expressions.rst>`_
    
    15
    -  has been implemented. SPECIALISE pragmas now allow arbitrary expressions such as: ::
    
    16
    -
    
    17
    -    {-# SPECIALISE f @Int False :: Int -> Char #-}
    
    18
    -
    
    19
    -  The ability to specify multiple specialisations in a single SPECIALISE pragma,
    
    20
    -  with syntax of the form (note the comma between the type signatures): ::
    
    21
    -
    
    22
    -    {-# SPECIALISE g : Int -> Int, Float -> Float #-}
    
    23
    -
    
    24
    -  has been deprecated, and is scheduled to be removed in GHC 9.18.
    
    25
    -  This deprecation is controlled by the newly introduced ``-Wdeprecated-pragmas``
    
    26
    -  flag in ``-Wdefault``.
    
    27
    -
    
    28
    -* ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified
    
    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>`_.
    
    30
    -  Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library.
    
    31
    -  Workaround: add ``-Werror=no-incomplete-record-selectors``.
    
    32
    -
    
    33
    -  Note that this warning is at least
    
    34
    -  as serious as a warning about missing patterns from a function definition, perhaps even
    
    35
    -  more so, since it is invisible in the source program.
    
    36
    -
    
    37
    -* The combination of :extension:`ScopedTypeVariables` and :extension:`TypeApplications`
    
    38
    -  no longer enables type applications in patterns, which now always requires
    
    39
    -  :extension:`TypeAbstractions`. The warning flag``deprecated-type-abstractions``
    
    40
    -  has also been removed from the compiler.
    
    41
    -
    
    42
    -* :extension:`OverloadedRecordUpdate` now passes the arguments to a ``setField`` function
    
    43
    -  in the flipped order, as specified by `GHC Proposal 583: HasField redesign <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0583-hasfield-redesign.rst>`_.
    
    44
    -
    
    45
    -  Previously GHC expected ``setField`` to have this type: ::
    
    46
    -
    
    47
    -    setField :: forall (fld :: Symbol) a r. r -> a -> r
    
    48
    -
    
    49
    -  And that's what GHC expects now: ::
    
    50
    -
    
    51
    -    setField :: forall (fld :: Symbol) a r. a -> r -> r
    
    52
    -
    
    53
    -  That will break the combination of :extension:`OverloadedRecordUpdate` with :extension:`RebindableSyntax`.
    
    54
    -
    
    55
    -* Multiline strings are now accepted in foreign imports. (#25157)
    
    56
    -
    
    57
    -* GHC now does a better job at inferring types in calls to ``coerce``: instead of
    
    58
    -  complaining about ambiguous type variables, GHC will consider that such type
    
    59
    -  variables are determined by the ``Coercible`` constraints they appear in.
    
    60
    -
    
    61
    -* With :extension:`LinearTypes` record fields can now be non-linear. This means that
    
    62
    -  the following record declaration is now valid:
    
    63
    -
    
    64
    -  ::
    
    65
    -
    
    66
    -      data Record = Rec { x %'Many :: Int, y :: Char }
    
    67
    -
    
    68
    -  This causes the constructor to have type ``Rec :: Int %'Many -> Char %1 -> Record``.
    
    69
    -
    
    70
    -* The :extension:`ExplicitNamespaces` extension now allows the ``data``
    
    71
    -  namespace specifier in import and export lists.
    
    72
    -
    
    73
    -* The ``-Wdata-kinds-tc`` warning has been deprecated, and the use of promoted
    
    74
    -  data types in kinds is now an error (rather than a warning) unless the
    
    75
    -  :extension:`DataKinds` extension is enabled. For example, the following code
    
    76
    -  will be rejected unless :extension:`DataKinds` is on:
    
    77
    -
    
    78
    -    import Data.Kind (Type)
    
    79
    -    import GHC.TypeNats (Nat)
    
    80
    -
    
    81
    -    -- Nat shouldn't be allowed here without DataKinds
    
    82
    -    data Vec :: Nat -> Type -> Type
    
    83
    -
    
    84
    -  (The ``-Wdata-kinds-tc`` warning was introduced in GHC 9.10 as part of a fix
    
    85
    -  for an accidental oversight in which programs like the one above were
    
    86
    -  mistakenly accepted without the use of :extension:`DataKinds`.)
    
    87
    -
    
    88
    -* The :extension:`MonadComprehensions` extension now implies :extension:`ParallelListComp` as was originally intended (see `Monad Comprehensions <https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/monad_comprehensions.html>`_).
    
    89
    -
    
    90
    -* In accordance with `GHC Proposal #281 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0281-visible-forall.rst>`_,
    
    91
    -  section 4.7 "Data constructors", the :extension:`RequiredTypeArguments`
    
    92
    -  extension now allows visible forall in types of data constructors
    
    93
    -  (:ghc-ticket:`25127`). The following declaration is now accepted by GHC:
    
    94
    -
    
    95
    -  ::
    
    96
    -
    
    97
    -    data T a where
    
    98
    -      Typed :: forall a -> a -> T a
    
    99
    -
    
    100
    -  See :ref:`visible-forall-in-gadts` for details.
    
    101
    -
    
    102
    -Compiler
    
    103
    -~~~~~~~~
    
    104
    -
    
    105
    -- An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (#25198)
    
    106
    -
    
    107
    -- The kind checker now does a better job of finding type family instances for
    
    108
    -  use in the kinds of other declarations in the same module. This fixes a number
    
    109
    -  of tickets:
    
    110
    -  :ghc-ticket:`12088`, :ghc-ticket:`12239`, :ghc-ticket:`14668`, :ghc-ticket:`15561`,
    
    111
    -  :ghc-ticket:`16410`, :ghc-ticket:`16448`, :ghc-ticket:`16693`, :ghc-ticket:`19611`,
    
    112
    -  :ghc-ticket:`20875`, :ghc-ticket:`21172`, :ghc-ticket:`22257`, :ghc-ticket:`25238`,
    
    113
    -  :ghc-ticket:`25834`.
    
    114
    -
    
    115
    -- The compiler no longer accepts invalid ``type`` namespace specifiers in
    
    116
    -  subordinate import lists (:ghc-ticket:`22581`).
    
    117
    -
    
    118
    -- A new flag, :ghc-flag:`-Wuseless-specialisations`, controls warnings emitted when GHC
    
    119
    -  determines that a SPECIALISE pragma would have no effect.
    
    120
    -
    
    121
    -- A new flag, :ghc-flag:`-Wrule-lhs-equalities`, controls warnings emitted for RULES
    
    122
    -  whose left-hand side attempts to quantify over equality constraints that
    
    123
    -  previous GHC versions accepted quantifying over. GHC will now drop such RULES,
    
    124
    -  emitting a warning message controlled by this flag.
    
    125
    -
    
    126
    -  This warning is intended to give visibility to the fact that the RULES that
    
    127
    -  previous GHC versions generated in such circumstances could never fire.
    
    128
    -
    
    129
    -- A new flag, :ghc-flag:`-Wunusable-unpack-pragmas`, controls warnings emitted
    
    130
    -  when GHC is unable to unpack a data constructor field annotated by the
    
    131
    -  ``{-# UNPACK #-}`` pragma.
    
    132
    -
    
    133
    -  Previous GHC versions issued this warning unconditionally. Now it is possible
    
    134
    -  to disable it with ``-Wno-unusable-unpack-pragmas`` or turn it into an error
    
    135
    -  with ``-Werror=unusable-unpack-pragmas``.
    
    136
    -
    
    137
    -- Introduce a new warning :ghc-flag:`-Wpattern-namespace-specifier` to detect
    
    138
    -  uses of the now deprecated ``pattern`` namespace specifier in import/export
    
    139
    -  lists. See `GHC Proposal #581, section 2.3 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0581-namespace-specified-imports.rst#deprecate-use-of-pattern-in-import-export-lists>`_.
    
    140
    -
    
    141
    -- Code coverage (:ghc-flag:`-fhpc`) now treats uses of record fields via
    
    142
    -  :extension:`RecordWildCards` or :extension:`NamedFieldPuns` as if the fields
    
    143
    -  were accessed using the generated record selector functions, marking the fields
    
    144
    -  as covered in coverage reports (:ghc-ticket:`17834`).
    
    145
    -
    
    146
    -- SIMD support in the X86 native code generator has been extended with 128-bit
    
    147
    -  integer operations.  Also, ``shuffleFloatX4#`` and ``shuffleDoubleX2#`` no longer
    
    148
    -  require ``-mavx``.
    
    149
    -
    
    150
    -- JSON diagnostics produced with (:ghc-flag:`-fdiagnostics-as-json`) now
    
    151
    -  include the `rendered` diagnostics message, in the exact same format as what
    
    152
    -  GHC would have produced without -fdiagnostics-as-json (including ANSI escape
    
    153
    -  sequences).
    
    154
    -
    
    155
    -GHCi
    
    156
    -~~~~
    
    157
    -
    
    158
    -- :ghci-cmd:`:info` now outputs type declarations with @-binders that are
    
    159
    -  considered semantically significant. See the documentation for :ghci-cmd:`:info`
    
    160
    -  itself for a more detailed explanation.
    
    161
    -
    
    162
    -- GHCi errors and warnings now have their own numeric error codes that are
    
    163
    -  displayed alongside the error.
    
    164
    -
    
    165
    -Runtime system
    
    166
    -~~~~~~~~~~~~~~
    
    167
    -
    
    168
    -- Add new runtime flag :rts-flag:`--optimistic-linking` which instructs the
    
    169
    -  runtime linker to continue in the presence of unknown symbols. By default this
    
    170
    -  flag is not passed, preserving previous behavior.
    
    171
    -
    
    172
    -Cmm
    
    173
    -~~~
    
    174
    -
    
    175
    -``base`` library
    
    176
    -~~~~~~~~~~~~~~~~
    
    177
    -
    
    178
    -``ghc-prim`` library
    
    179
    -~~~~~~~~~~~~~~~~~~~~
    
    180
    -
    
    181
    -``ghc`` library
    
    182
    -~~~~~~~~~~~~~~~
    
    183
    -
    
    184
    -* The `UnknownDiagnostic` constructor now takes an additional type argument
    
    185
    -  for the type of hints corresponding to the diagnostic, and an additional
    
    186
    -  value-level argument used for existential wrapping of the hints of the inner
    
    187
    -  diagnostic.
    
    188
    -
    
    189
    -* Changes to the HPT and HUG interface:
    
    190
    -
    
    191
    -  - `addToHpt` and `addListToHPT` were moved from `GHC.Unit.Home.ModInfo` to `GHC.Unit.Home.PackageTable` and deprecated in favour of `addHomeModInfoToHpt` and `addHomeModInfosToHpt`.
    
    192
    -  - `UnitEnvGraph` and operations `unitEnv_lookup_maybe`, `unitEnv_foldWithKey, `unitEnv_singleton`, `unitEnv_adjust`, `unitEnv_insert`, `unitEnv_new` were moved from `GHC.Unit.Env` to `GHC.Unit.Home.Graph`.
    
    193
    -  - The HomePackageTable (HPT) is now exported from `GHC.Unit.Home.PackageTable`,
    
    194
    -    and is now backed by an IORef to avoid by construction very bad memory leaks.
    
    195
    -    This means the API to the HPT now is for the most part in IO. For instance,
    
    196
    -    `emptyHomePackageTable` and `addHomeModInfoToHpt` are now in IO.
    
    197
    -  - `mkHomeUnitEnv` was moved to `GHC.Unit.Home.PackageTable`, and now takes two
    
    198
    -    extra explicit arguments. To restore previous behaviour, pass `emptyUnitState`
    
    199
    -    and `Nothing` as the first two arguments additionally.
    
    200
    -  - `hugElts` was removed. Users should prefer `allUnits` to get the keys of the
    
    201
    -    HUG (the typical use case), or `traverse` or `unitEnv_foldWithKey` in other
    
    202
    -    cases.
    
    203
    -
    
    204
    -* Changes to `Language.Haskell.Syntax.Expr`
    
    205
    -
    
    206
    -  - The `ParStmtBlock` list argument of the `ParStmt` constructor of `StmtLR` is now `NonEmpty`.
    
    207
    -
    
    208
    -* As part of the implementation of `GHC proposal 493 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-specialise-expressions.rst>`_,
    
    209
    -  the `SpecSig` constructor of `Sig` has been deprecated. It is replaced by
    
    210
    -  the constructor `SpecSigE` which supports expressions at the head, rather than
    
    211
    -  a lone variable.
    
    212
    -
    
    213
    -``ghc-heap`` library
    
    214
    -~~~~~~~~~~~~~~~~~~~~
    
    215
    -
    
    216
    -* The functions `getClosureInfoTbl_maybe`, `getClosureInfoTbl`,
    
    217
    -  `getClosurePtrArgs` and `getClosurePtrArgs_maybe` have been added to allow
    
    218
    -  reading of the relevant Closure attributes without reliance on incomplete
    
    219
    -  selectors.
    
    220
    -
    
    221
    -``ghc-experimental`` library
    
    222
    -~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    223
    -
    
    224
    -- ``ghc-experimental`` now exposes ``GHC.RTS.Flags`` and ``GHC.Stats`` as
    
    225
    -  ``GHC.RTS.Flags.Experimental`` and ``GHC.Stats.Experimental``. These are
    
    226
    -  *also* exposed in ``base``, however the ``base`` versions will be deprecated as
    
    227
    -  part of the split base project. See `CLC proposal 289
    
    228
    -  <https://github.com/haskell/core-libraries-committee/issues/289>`__.
    
    229
    -  Downstream consumers of these flags are encouraged to migrate to the
    
    230
    -  ``ghc-experimental`` versions.
    
    231
    -
    
    232
    -
    
    233
    -
    
    234
    -``template-haskell`` library
    
    235
    -~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    236
    -
    
    237
    -- As part of the implementation of `GHC proposal 493 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-specialise-expressions.rst>`_,
    
    238
    -  the ``SpecialiseP`` constructor of the Template Haskell ``Pragma`` type, as
    
    239
    -  well as the helpers ``pragSpecD`` and ``pragSpecInlD``, have been deprecated.
    
    240
    -
    
    241
    -  They are replaced, respectively, by ``SpecialiseEP``, ``pragSpecED`` and
    
    242
    -  ``pragSpecInlED``.
    
    243
    -
    
    244
    -Included libraries
    
    245
    -~~~~~~~~~~~~~~~~~~
    
    246
    -
    
    247
    -The package database provided with this distribution also contains a number of
    
    248
    -packages other than GHC itself. See the changelogs provided with these packages
    
    249
    -for further change information.
    
    250
    -
    
    251
    -.. ghc-package-list::
    
    252
    -
    
    253
    -    libraries/array/array.cabal:                         Dependency of ``ghc`` library
    
    254
    -    libraries/base/base.cabal:                           Core library
    
    255
    -    libraries/binary/binary.cabal:                       Dependency of ``ghc`` library
    
    256
    -    libraries/bytestring/bytestring.cabal:               Dependency of ``ghc`` library
    
    257
    -    libraries/Cabal/Cabal/Cabal.cabal:                   Dependency of ``ghc-pkg`` utility
    
    258
    -    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:     Dependency of ``ghc-pkg`` utility
    
    259
    -    libraries/containers/containers/containers.cabal:    Dependency of ``ghc`` library
    
    260
    -    libraries/deepseq/deepseq.cabal:                     Dependency of ``ghc`` library
    
    261
    -    libraries/directory/directory.cabal:                 Dependency of ``ghc`` library
    
    262
    -    libraries/exceptions/exceptions.cabal:               Dependency of ``ghc`` and ``haskeline`` library
    
    263
    -    libraries/filepath/filepath.cabal:                   Dependency of ``ghc`` library
    
    264
    -    compiler/ghc.cabal:                                  The compiler itself
    
    265
    -    libraries/ghci/ghci.cabal:                           The REPL interface
    
    266
    -    libraries/ghc-boot/ghc-boot.cabal:                   Internal compiler library
    
    267
    -    libraries/ghc-boot-th/ghc-boot-th.cabal:             Internal compiler library
    
    268
    -    libraries/ghc-compact/ghc-compact.cabal:             Core library
    
    269
    -    libraries/ghc-heap/ghc-heap.cabal:                   GHC heap-walking library
    
    270
    -    libraries/ghc-prim/ghc-prim.cabal:                   Core library
    
    271
    -    utils/haddock/haddock-api/haddock-api.cabal:         Dependency of ``haddock`` executable
    
    272
    -    utils/haddock/haddock-library/haddock-library.cabal: Dependency of ``haddock`` executable
    
    273
    -    libraries/haskeline/haskeline.cabal:                 Dependency of ``ghci`` executable
    
    274
    -    libraries/hpc/hpc.cabal:                             Dependency of ``hpc`` executable
    
    275
    -    libraries/integer-gmp/integer-gmp.cabal:             Core library
    
    276
    -    libraries/mtl/mtl.cabal:                             Dependency of ``Cabal`` library
    
    277
    -    libraries/parsec/parsec.cabal:                       Dependency of ``Cabal`` library
    
    278
    -    libraries/pretty/pretty.cabal:                       Dependency of ``ghc`` library
    
    279
    -    libraries/process/process.cabal:                     Dependency of ``ghc`` library
    
    280
    -    libraries/stm/stm.cabal:                             Dependency of ``haskeline`` library
    
    281
    -    libraries/template-haskell/template-haskell.cabal:   Core library
    
    282
    -    libraries/terminfo/terminfo.cabal:                   Dependency of ``haskeline`` library
    
    283
    -    libraries/text/text.cabal:                           Dependency of ``Cabal`` library
    
    284
    -    libraries/time/time.cabal:                           Dependency of ``ghc`` library
    
    285
    -    libraries/transformers/transformers.cabal:           Dependency of ``ghc`` library
    
    286
    -    libraries/unix/unix.cabal:                           Dependency of ``ghc`` library
    
    287
    -    libraries/Win32/Win32.cabal:                         Dependency of ``ghc`` library
    
    288
    -    libraries/xhtml/xhtml.cabal:                         Dependency of ``haddock`` executable
    
    289
    -    libraries/os-string/os-string.cabal:                 Dependency of ``filepath`` library
    
    290
    -    libraries/file-io/file-io.cabal:                     Dependency of ``directory`` library

  • docs/users_guide/9.16.1-notes.rst
    1
    +.. _release-9-16-1:
    
    2
    +
    
    3
    +Version 9.16.1
    
    4
    +==============
    
    5
    +
    
    6
    +The significant changes to the various parts of the compiler are listed in the
    
    7
    +following sections. See the `migration guide
    
    8
    +<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.16>`_ on the GHC Wiki
    
    9
    +for specific guidance on migrating programs to this release.
    
    10
    +
    
    11
    +Language
    
    12
    +~~~~~~~~
    
    13
    +
    
    14
    +Compiler
    
    15
    +~~~~~~~~
    
    16
    +
    
    17
    +- Code coverage's (:ghc-flag:`-fhpc`) treatment of record fields now extends
    
    18
    +  beyond record fields accessed via :extension:`RecordWildCards` and
    
    19
    +  :extension:`NamedFieldPuns`, and also handles access to nested record fields.
    
    20
    +  That is, in a pattern such as ``Foo{bar = Bar{baz = b}}`` both ``bar`` and
    
    21
    +  ``baz`` will now be marked as covered if ``b`` is evaluated. Note that this
    
    22
    +  currently only works when record fields (or values contained within them) are
    
    23
    +  bound to variables. The very similar pattern ``Foo{bar = Bar{baz = 42}}``
    
    24
    +  will will not yet mark ``bar`` or ``baz`` as covered.
    
    25
    +
    
    26
    +GHCi
    
    27
    +~~~~
    
    28
    +
    
    29
    +Runtime system
    
    30
    +~~~~~~~~~~~~~~
    
    31
    +
    
    32
    +Cmm
    
    33
    +~~~
    
    34
    +
    
    35
    +``base`` library
    
    36
    +~~~~~~~~~~~~~~~~
    
    37
    +
    
    38
    +``ghc-prim`` library
    
    39
    +~~~~~~~~~~~~~~~~~~~~
    
    40
    +
    
    41
    +``ghc`` library
    
    42
    +~~~~~~~~~~~~~~~
    
    43
    +
    
    44
    +``ghc-heap`` library
    
    45
    +~~~~~~~~~~~~~~~~~~~~
    
    46
    +
    
    47
    +``ghc-experimental`` library
    
    48
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    49
    +
    
    50
    +``template-haskell`` library
    
    51
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    52
    +
    
    53
    +Included libraries
    
    54
    +~~~~~~~~~~~~~~~~~~
    
    55
    +
    
    56
    +The package database provided with this distribution also contains a number of
    
    57
    +packages other than GHC itself. See the changelogs provided with these packages
    
    58
    +for further change information.
    
    59
    +
    
    60
    +.. ghc-package-list::
    
    61
    +
    
    62
    +    libraries/array/array.cabal:                         Dependency of ``ghc`` library
    
    63
    +    libraries/base/base.cabal:                           Core library
    
    64
    +    libraries/binary/binary.cabal:                       Dependency of ``ghc`` library
    
    65
    +    libraries/bytestring/bytestring.cabal:               Dependency of ``ghc`` library
    
    66
    +    libraries/Cabal/Cabal/Cabal.cabal:                   Dependency of ``ghc-pkg`` utility
    
    67
    +    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:     Dependency of ``ghc-pkg`` utility
    
    68
    +    libraries/containers/containers/containers.cabal:    Dependency of ``ghc`` library
    
    69
    +    libraries/deepseq/deepseq.cabal:                     Dependency of ``ghc`` library
    
    70
    +    libraries/directory/directory.cabal:                 Dependency of ``ghc`` library
    
    71
    +    libraries/exceptions/exceptions.cabal:               Dependency of ``ghc`` and ``haskeline`` library
    
    72
    +    libraries/filepath/filepath.cabal:                   Dependency of ``ghc`` library
    
    73
    +    compiler/ghc.cabal:                                  The compiler itself
    
    74
    +    libraries/ghci/ghci.cabal:                           The REPL interface
    
    75
    +    libraries/ghc-boot/ghc-boot.cabal:                   Internal compiler library
    
    76
    +    libraries/ghc-boot-th/ghc-boot-th.cabal:             Internal compiler library
    
    77
    +    libraries/ghc-compact/ghc-compact.cabal:             Core library
    
    78
    +    libraries/ghc-heap/ghc-heap.cabal:                   GHC heap-walking library
    
    79
    +    libraries/ghc-prim/ghc-prim.cabal:                   Core library
    
    80
    +    utils/haddock/haddock-api/haddock-api.cabal:         Dependency of ``haddock`` executable
    
    81
    +    utils/haddock/haddock-library/haddock-library.cabal: Dependency of ``haddock`` executable
    
    82
    +    libraries/haskeline/haskeline.cabal:                 Dependency of ``ghci`` executable
    
    83
    +    libraries/hpc/hpc.cabal:                             Dependency of ``hpc`` executable
    
    84
    +    libraries/integer-gmp/integer-gmp.cabal:             Core library
    
    85
    +    libraries/mtl/mtl.cabal:                             Dependency of ``Cabal`` library
    
    86
    +    libraries/parsec/parsec.cabal:                       Dependency of ``Cabal`` library
    
    87
    +    libraries/pretty/pretty.cabal:                       Dependency of ``ghc`` library
    
    88
    +    libraries/process/process.cabal:                     Dependency of ``ghc`` library
    
    89
    +    libraries/stm/stm.cabal:                             Dependency of ``haskeline`` library
    
    90
    +    libraries/template-haskell/template-haskell.cabal:   Core library
    
    91
    +    libraries/terminfo/terminfo.cabal:                   Dependency of ``haskeline`` library
    
    92
    +    libraries/text/text.cabal:                           Dependency of ``Cabal`` library
    
    93
    +    libraries/time/time.cabal:                           Dependency of ``ghc`` library
    
    94
    +    libraries/transformers/transformers.cabal:           Dependency of ``ghc`` library
    
    95
    +    libraries/unix/unix.cabal:                           Dependency of ``ghc`` library
    
    96
    +    libraries/Win32/Win32.cabal:                         Dependency of ``ghc`` library
    
    97
    +    libraries/xhtml/xhtml.cabal:                         Dependency of ``haddock`` executable
    
    98
    +    libraries/os-string/os-string.cabal:                 Dependency of ``filepath`` library
    
    99
    +    libraries/file-io/file-io.cabal:                     Dependency of ``directory`` library

  • docs/users_guide/release-notes.rst
    ... ... @@ -4,4 +4,4 @@ Release notes
    4 4
     .. toctree::
    
    5 5
        :maxdepth: 1
    
    6 6
     
    
    7
    -   9.14.1-notes
    7
    +   9.16.1-notes

  • testsuite/tests/hpc/recsel/recsel.hs
    ... ... @@ -10,7 +10,8 @@ import Trace.Hpc.Tix
    10 10
     import Trace.Hpc.Reflect
    
    11 11
     
    
    12 12
     data Foo = Foo { fooA, fooB, fooC, fooD, fooE, fooF, fooG, fooH, fooI
    
    13
    -               , fooJ, fooK, fooL, fooM, fooN, fooO :: Int }
    
    13
    +               , fooJ, fooK, fooL, fooM, fooN, fooO :: Int
    
    14
    +               , fooP, fooQ :: Maybe Int }
    
    14 15
     data Bar = Bar { barFoo :: Foo }
    
    15 16
     
    
    16 17
     fAB Foo{..} = fooA + fooB
    
    ... ... @@ -35,14 +36,17 @@ fL = runIdentity . runKleisli (proc f -> do
    35 36
     fM f | Foo{..} <- f = fooM
    
    36 37
     fN f = fooN f
    
    37 38
     fO = runIdentity . runKleisli (proc Foo{..} -> returnA -< fooO)
    
    39
    +fP Foo{fooP = Just x} = x
    
    40
    +fP _ = 0
    
    41
    +fQ Foo{fooQ = Just 42} = 1
    
    38 42
     
    
    39 43
     recSel (n, TopLevelBox [s]) | any (`isPrefixOf` s) ["foo", "bar"] = Just (n, s)
    
    40 44
     recSel _ = Nothing
    
    41 45
     
    
    42 46
     main = do
    
    43
    -  let foo = Foo 42 23 0 1 2 3 4 5 6 7 0xaffe 9 10 11 12
    
    47
    +  let foo = Foo 42 23 0 1 2 3 4 5 6 7 0xaffe 9 10 11 12 (Just 13) (Just 42)
    
    44 48
       mapM_ (print . ($ foo))
    
    45
    -        [fAB, fC, fD False, fE . Bar, fF, fG, fH, fI, fJ, fK, fL, fM, fN, fO]
    
    49
    +        [fAB, fC, fD False, fE . Bar, fF, fG, fH, fI, fJ, fK, fL, fM, fN, fO, fP, fQ]
    
    46 50
       (Mix _ _ _ _ mixs) <- readMix [".hpc"] (Left "Main")
    
    47 51
       let sels = mapMaybe recSel . zip [0..] $ map snd mixs
    
    48 52
       (Tix [TixModule "Main" _ _ tix]) <- examineTix
    

  • testsuite/tests/hpc/recsel/recsel.stdout
    ... ... @@ -12,13 +12,15 @@
    12 12
     10
    
    13 13
     11
    
    14 14
     12
    
    15
    -(0,"barFoo")
    
    15
    +13
    
    16
    +1
    
    17
    +(1,"barFoo")
    
    16 18
     (1,"fooA")
    
    17 19
     (1,"fooB")
    
    18 20
     (1,"fooC")
    
    19 21
     (0,"fooD")
    
    20 22
     (1,"fooE")
    
    21
    -(0,"fooF")
    
    23
    +(1,"fooF")
    
    22 24
     (1,"fooG")
    
    23 25
     (1,"fooH")
    
    24 26
     (1,"fooI")
    
    ... ... @@ -28,3 +30,5 @@
    28 30
     (1,"fooM")
    
    29 31
     (1,"fooN")
    
    30 32
     (1,"fooO")
    
    33
    +(1,"fooP")
    
    34
    +(0,"fooQ")