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

Commits:

15 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
    

  • 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/changelog.md
    ... ... @@ -2,6 +2,7 @@
    2 2
     
    
    3 3
     ## 4.23.0.0 *TBA*
    
    4 4
       * Add `Data.List.NonEmpty.mapMaybe`. ([CLC proposal #337](https://github.com/haskell/core-libraries-committee/issues/337))
    
    5
    +  * Fix issues with toRational for types capable to represent infinite and not-a-number values ([CLC proposal #338](https://github.com/haskell/core-libraries-committee/issues/338))
    
    5 6
     
    
    6 7
     ## 4.22.0.0 *TBA*
    
    7 8
       * Shipped with GHC 9.14.1
    

  • libraries/ghc-internal/src/GHC/Internal/Float.hs
    ... ... @@ -430,14 +430,10 @@ naturalToFloat# (NB b) = case integerToBinaryFloat' (IP b) of
    430 430
     
    
    431 431
     -- | @since base-2.01
    
    432 432
     --
    
    433
    --- Beware that 'toRational' generates garbage for non-finite arguments:
    
    434
    ---
    
    435
    --- >>> toRational (1/0 :: Float)
    
    436
    --- 340282366920938463463374607431768211456 % 1
    
    437
    --- >>> toRational (0/0 :: Float)
    
    438
    --- 510423550381407695195061911147652317184 % 1
    
    439
    ---
    
    440 433
     instance  Real Float  where
    
    434
    +    toRational x
    
    435
    +      | isInfinite x = if x > 0 then infinity else -infinity
    
    436
    +      | isNaN x = notANumber
    
    441 437
         toRational (F# x#)  =
    
    442 438
             case decodeFloat_Int# x# of
    
    443 439
               (# m#, e# #)
    
    ... ... @@ -686,14 +682,10 @@ naturalToDouble# (NB b) = case integerToBinaryFloat' (IP b) of
    686 682
     
    
    687 683
     -- | @since base-2.01
    
    688 684
     --
    
    689
    --- Beware that 'toRational' generates garbage for non-finite arguments:
    
    690
    ---
    
    691
    --- >>> toRational (1/0)
    
    692
    --- 179769313 (and 300 more digits...) % 1
    
    693
    --- >>> toRational (0/0)
    
    694
    --- 269653970 (and 300 more digits...) % 1
    
    695
    ---
    
    696 685
     instance  Real Double  where
    
    686
    +    toRational x
    
    687
    +      | isInfinite x = if x > 0 then infinity else -infinity
    
    688
    +      | isNaN x = notANumber
    
    697 689
         toRational (D# x#)  =
    
    698 690
             case integerDecodeDouble# x# of
    
    699 691
               (# m, e# #)
    

  • libraries/ghc-internal/src/GHC/Internal/Real.hs
    ... ... @@ -703,15 +703,6 @@ fromIntegral = fromInteger . toInteger
    703 703
     
    
    704 704
     -- | General coercion to 'Fractional' types.
    
    705 705
     --
    
    706
    --- WARNING: This function goes through the 'Rational' type, which does not have values for 'NaN' for example.
    
    707
    --- This means it does not round-trip.
    
    708
    ---
    
    709
    --- For 'Double' it also behaves differently with or without -O0:
    
    710
    ---
    
    711
    --- > Prelude> realToFrac nan -- With -O0
    
    712
    --- > -Infinity
    
    713
    --- > Prelude> realToFrac nan
    
    714
    --- > NaN
    
    715 706
     realToFrac :: (Real a, Fractional b) => a -> b
    
    716 707
     {-# NOINLINE [1] realToFrac #-}
    
    717 708
     -- See Note [Allow time for type-specialisation rules to fire]
    

  • 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/numeric/should_run/T9810.stdout
    1 1
     ## Double ##
    
    2 2
     Infinity
    
    3 3
     -Infinity
    
    4
    -Infinity
    
    4
    +NaN
    
    5 5
     Infinity
    
    6 6
     -Infinity
    
    7 7
     Infinity
    
    8 8
     ## Float ##
    
    9 9
     Infinity
    
    10 10
     -Infinity
    
    11
    -Infinity
    
    11
    +NaN
    
    12 12
     Infinity
    
    13 13
     -Infinity
    
    14 14
     Infinity

  • 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
    ... ... @@ -47,3 +47,4 @@ test('SI35',
    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 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