Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC

Commits:

16 changed files:

Changes:

  • compiler/GHC/Rename/Splice.hs
    ... ... @@ -35,6 +35,7 @@ import GHC.Rename.Pat ( rnPat )
    35 35
     import GHC.Types.Error
    
    36 36
     import GHC.Types.Basic    ( TopLevelFlag, isTopLevel, maxPrec )
    
    37 37
     import GHC.Types.SourceText ( SourceText(..) )
    
    38
    +import GHC.Types.ThLevelIndex
    
    38 39
     import GHC.Utils.Outputable
    
    39 40
     import GHC.Unit.Module
    
    40 41
     import GHC.Types.SrcLoc
    
    ... ... @@ -1001,7 +1002,7 @@ checkCrossLevelLifting dflags reason top_lvl is_local allow_lifting bind_lvl use
    1001 1002
       , xopt LangExt.ImplicitStagePersistence dflags = when (isExternalName name) (keepAlive name) >> return (HsVar noExtField name_var)
    
    1002 1003
       -- 4. Name is in a bracket, and lifting is allowed
    
    1003 1004
       | Brack _ pending <- use_lvl
    
    1004
    -  , any (use_lvl_idx >=) (Set.toList bind_lvl)
    
    1005
    +  , any (\bind_idx -> use_lvl_idx == incThLevelIndex bind_idx) (Set.toList bind_lvl)
    
    1005 1006
       , allow_lifting
    
    1006 1007
       = do
    
    1007 1008
            let mgre = case reason of
    

  • compiler/GHC/Unit/Module/Graph.hs
    ... ... @@ -866,7 +866,7 @@ mkTransZeroDeps = first graphReachability {- module graph is acyclic -} . module
    866 866
     
    
    867 867
     -- | Transitive dependencies, but with the stage that each module is required at.
    
    868 868
     mkStageDeps :: [ModuleGraphNode] -> (ReachabilityIndex StageSummaryNode, (NodeKey, ModuleStage) -> Maybe StageSummaryNode)
    
    869
    -mkStageDeps = first graphReachability . moduleGraphNodesStages
    
    869
    +mkStageDeps = first cyclicGraphReachability . moduleGraphNodesStages
    
    870 870
     
    
    871 871
     type ZeroSummaryNode = Node Int ZeroScopeKey
    
    872 872
     
    

  • docs/users_guide/using-optimisation.rst
    ... ... @@ -547,16 +547,24 @@ as such you shouldn't need to set any of them explicitly. A flag
    547 547
         Eta-expand let-bindings to increase their arity.
    
    548 548
     
    
    549 549
     .. ghc-flag:: -fdo-clever-arg-eta-expansion
    
    550
    -    :shortdesc: Enable sophisticated argument eta-expansion. Implied by :ghc-flag:`-O2`.
    
    550
    +    :shortdesc: Enable sophisticated argument eta-expansion. Implied by :ghc-flag:`-O`.
    
    551 551
         :type: dynamic
    
    552 552
         :reverse: -fno-do-clever-arg-eta-expansion
    
    553 553
         :category:
    
    554 554
     
    
    555 555
         :default: off
    
    556
    +    :since: 9.10.1
    
    556 557
     
    
    557 558
         Eta-expand arguments to increase their arity to avoid allocating unnecessary
    
    558 559
         thunks for them.
    
    559 560
     
    
    561
    +    For example in code like `foo = f (g x)` this flag will determine which analysis
    
    562
    +    is used to decide the arity of `g x`, with the goal of avoiding a thunk for `g x`
    
    563
    +    in cases where `g` is a function with an arity higher than one.
    
    564
    +
    
    565
    +    Enabling the flag enables a more sophisticated analysis, resulting in better
    
    566
    +    runtime but longer compile time.
    
    567
    +
    
    560 568
     .. ghc-flag:: -feager-blackholing
    
    561 569
         :shortdesc: Turn on :ref:`eager blackholing <parallel-compile-options>`
    
    562 570
         :type: dynamic
    
    ... ... @@ -617,6 +625,7 @@ as such you shouldn't need to set any of them explicitly. A flag
    617 625
         :category:
    
    618 626
     
    
    619 627
         :default: off
    
    628
    +    :since: 9.12.1
    
    620 629
     
    
    621 630
         This experimental flag is a slightly less heavy weight alternative
    
    622 631
         to :ghc-flag:`-fexpose-all-unfoldings`.
    

  • libraries/base/src/GHC/Generics.hs
    ... ... @@ -392,9 +392,14 @@ module GHC.Generics (
    392 392
     -- instance (Encode a) => Encode (Tree a)
    
    393 393
     -- @
    
    394 394
     --
    
    395
    --- The generic default is being used. In the future, it will hopefully be
    
    396
    --- possible to use @deriving Encode@ as well, but GHC does not yet support
    
    397
    --- that syntax for this situation.
    
    395
    +-- The generic default is being used. Alternatively the @DeriveAnyClass@ language extension can be
    
    396
    +-- used to derive Encode:
    
    397
    +--
    
    398
    +-- @
    
    399
    +-- {-# LANGUAGE DeriveAnyClass #-}
    
    400
    +-- data Tree a = Leaf a | Node (Tree a) (Tree a)
    
    401
    +--   deriving (Generic, Encode)
    
    402
    +-- @
    
    398 403
     --
    
    399 404
     -- Having @Encode@ as a class has the advantage that we can define
    
    400 405
     -- non-generic special cases, which is particularly useful for abstract
    

  • testsuite/tests/haddock/haddock_testsuite/Makefile
    ... ... @@ -76,3 +76,7 @@ hypsrcTest:
    76 76
     .PHONY: haddockForeignTest
    
    77 77
     haddockForeignTest:
    
    78 78
     	'$(HADDOCK)' A.hs B.hs F.hs arith.c
    
    79
    +
    
    80
    +.PHONY: T26114
    
    81
    +T26114:
    
    82
    +	'$(HADDOCK)' T26114.hs

  • testsuite/tests/haddock/haddock_testsuite/T26114.hs
    1
    +{-# LANGUAGE TypeFamilies #-}
    
    2
    +
    
    3
    +-- | Module
    
    4
    +module T26114 where
    
    5
    +
    
    6
    +-- | C1
    
    7
    +class C1 t where
    
    8
    +  type C2 t
    
    9
    +
    
    10
    +-- | A
    
    11
    +data A = A
    
    12
    +
    
    13
    +instance C1 A where
    
    14
    +  type C2 A = B
    
    15
    +
    
    16
    +-- | B
    
    17
    +data B = B
    
    18
    +
    
    19
    +instance C1 B where
    
    20
    +  type C2 B = C
    
    21
    +
    
    22
    +-- | C
    
    23
    +data C = C

  • testsuite/tests/haddock/haddock_testsuite/T26114.stdout
    1
    +[1 of 1] Compiling T26114           ( T26114.hs, nothing )
    
    2
    +Haddock coverage:
    
    3
    + 100% (  5 /  5) in 'T26114'

  • testsuite/tests/haddock/haddock_testsuite/all.T
    ... ... @@ -24,3 +24,8 @@ test('haddockForeignTest',
    24 24
          [ignore_stdout, ignore_stderr, req_haddock, extra_files(['./haddock-th-foreign-repro/A.hs', './haddock-th-foreign-repro/B.hs', './haddock-th-foreign-repro/F.hs', './haddock-th-foreign-repro/arith.c'])],
    
    25 25
          makefile_test,
    
    26 26
          ['haddockForeignTest'])
    
    27
    +
    
    28
    +test('T26114',
    
    29
    +   [ignore_stderr, req_haddock, extra_files(['T26114.hs'])],
    
    30
    +   makefile_test,
    
    31
    +   ['T26114'])

  • testsuite/tests/splice-imports/T26087.stderr
    1
    +./T26087B.hs: error: [GHC-92213]
    
    2
    +    Module graph contains a cycle:
    
    3
    +                    module ‘main:T26087B’ (./T26087B.hs)
    
    4
    +            imports module ‘main:T26087A’ (T26087A.hs)
    
    5
    +      which imports module ‘main:T26087B’ (./T26087B.hs)
    
    6
    +

  • testsuite/tests/splice-imports/T26087A.hs
    1
    +{-# LANGUAGE ExplicitLevelImports #-}
    
    2
    +module T26087A where
    
    3
    +
    
    4
    +import quote T26087B

  • testsuite/tests/splice-imports/T26087B.hs
    1
    +{-# LANGUAGE ExplicitLevelImports, TemplateHaskell #-}
    
    2
    +module T26087B where
    
    3
    +
    
    4
    +import T26087A

  • testsuite/tests/splice-imports/T26088.stderr
    1
    +T26088A.hs:8:8: error: [GHC-28914]
    
    2
    +    • Level error: ‘a’ is bound at level -1 but used at level 1
    
    3
    +    • Available from the imports:
    
    4
    +      • imported from ‘T26088B’ at -1 at T26088A.hs:4:1-21
    
    5
    +    • In the Template Haskell quotation: [| a |]
    
    6
    +

  • testsuite/tests/splice-imports/T26088A.hs
    1
    +{-# LANGUAGE ExplicitLevelImports, TemplateHaskell #-}
    
    2
    +module T26088A where
    
    3
    +
    
    4
    +import splice T26088B
    
    5
    +import Language.Haskell.TH.Syntax
    
    6
    +
    
    7
    +x :: Q Exp
    
    8
    +x = [| a |]

  • testsuite/tests/splice-imports/T26088B.hs
    1
    +module T26088B where
    
    2
    +
    
    3
    +a = ()

  • testsuite/tests/splice-imports/all.T
    ... ... @@ -46,3 +46,5 @@ test('SI35',
    46 46
          compile_and_run,
    
    47 47
          ['-package ghc'])
    
    48 48
     test('SI36', [extra_files(["SI36_A.hs", "SI36_B1.hs", "SI36_B2.hs", "SI36_B3.hs", "SI36_C1.hs", "SI36_C2.hs", "SI36_C3.hs"])], multimod_compile_fail, ['SI36', '-v0'])
    
    49
    +test('T26087', [], multimod_compile_fail, ['T26087A', ''])
    
    50
    +test('T26088', [], multimod_compile_fail, ['T26088A', '-v0'])

  • utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
    ... ... @@ -110,6 +110,7 @@ renameInterface ignoreSet renamingEnv expInfo warnings hoogle iface = do
    110 110
             && isExternalName name
    
    111 111
             && not (isBuiltInSyntax name)
    
    112 112
             && not (isTyVarName name)
    
    113
    +        && not (isDerivedOccName $ nameOccName name)
    
    113 114
             && Exact name /= eqTyCon_RDR
    
    114 115
             -- Must not be in the set of ignored symbols for the module or the
    
    115 116
             -- unqualified ignored symbols