[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: nonmoving: Disable slop-zeroing

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Apr 7 18:57:01 UTC 2023



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


Commits:
d1bb16ed by Ben Gamari at 2023-04-06T03:40:45-04:00
nonmoving: Disable slop-zeroing

As noted in #23170, the nonmoving GC can race with a mutator zeroing the
slop of an updated thunk (in much the same way that two mutators would
race). Consequently, we must disable slop-zeroing when the nonmoving GC
is in use.

Closes #23170

- - - - -
04b80850 by Brandon Chinn at 2023-04-06T03:41:21-04:00
Fix reverse flag for -Wunsupported-llvm-version
- - - - -
0c990e13 by Pierre Le Marre at 2023-04-06T10:16:29+00:00
Add release note for GHC.Unicode refactor in base-4.18.

Also merge CLC proposal 130 in base-4.19 with CLC proposal 59 in
base-4.18 and add proper release date.

- - - - -
78d115c4 by Alex Dixon at 2023-04-07T14:56:55-04:00
Improve documentation for ($) (#22963)

- - - - -
e4169f93 by Alex Dixon at 2023-04-07T14:56:55-04:00
Remove trailing whitespace from ($) commentary

- - - - -
9fe52a1d by Sebastian Graf at 2023-04-07T14:56:55-04:00
Adjust wording wrt representation polymorphism of ($)
- - - - -


4 changed files:

- docs/users_guide/using-warnings.rst
- libraries/base/GHC/Base.hs
- libraries/base/changelog.md
- rts/include/rts/storage/ClosureMacros.h


Changes:

=====================================
docs/users_guide/using-warnings.rst
=====================================
@@ -1615,7 +1615,7 @@ of ``-W(no-)*``.
     :shortdesc: Warn when using :ghc-flag:`-fllvm` with an unsupported
         version of LLVM.
     :type: dynamic
-    :reverse: -Wno-monomorphism-restriction
+    :reverse: -Wno-unsupported-llvm-version
     :category:
 
     :since: 7.8


=====================================
libraries/base/GHC/Base.hs
=====================================
@@ -1606,18 +1606,69 @@ flip f x y              =  f y x
 -- (\x -> undefined x) `seq` () and thus would just evaluate to (), but now
 -- it is equivalent to undefined `seq` () which diverges.
 
--- | Application operator.  This operator is redundant, since ordinary
--- application @(f x)@ means the same as @(f '$' x)@. However, '$' has
--- low, right-associative binding precedence, so it sometimes allows
--- parentheses to be omitted; for example:
---
--- > f $ g $ h x  =  f (g (h x))
---
--- It is also useful in higher-order situations, such as @'map' ('$' 0) xs@,
--- or @'Data.List.zipWith' ('$') fs xs at .
---
--- Note that @('$')@ is representation-polymorphic, so that
--- @foo '$' 4#@ where @foo :: Int# -> Int#@ is well-typed.
+{- | @($)@ is the __function application__ operator.
+
+Applying @($)@ to a function @f@ and an argument @x@ gives the same result as applying @f@ to @x@ directly. The definition is akin to this:
+
+@
+($) :: (a -> b) -> a -> b
+($) f x = f x
+@
+
+On the face of it, this may appear pointless! But it's actually one of the most useful and important operators in Haskell.
+
+The order of operations is very different between @($)@ and normal function application. Normal function application has precedence 10 - higher than any operator - and associates to the left. So these two definitions are equivalent:
+
+@
+expr = min 5 1 + 5
+expr = ((min 5) 1) + 5
+@
+
+@($)@ has precedence 0 (the lowest) and associates to the right, so these are equivalent:
+
+@
+expr = min 5 $ 1 + 5
+expr = (min 5) (1 + 5)
+@
+
+=== Uses
+
+A common use cases of @($)@ is to avoid parentheses in complex expressions.
+
+For example, instead of using nested parentheses in the following
+ Haskell function:
+
+@
+-- | Sum numbers in a string: strSum "100  5 -7" == 98
+strSum :: 'String' -> 'Int'
+strSum s = 'sum' ('Data.Maybe.mapMaybe' 'Text.Read.readMaybe' ('words' s))
+@
+
+we can deploy the function application operator:
+
+@
+-- | Sum numbers in a string: strSum "100  5 -7" == 98
+strSum :: 'String' -> 'Int'
+strSum s = 'sum' '$' 'Data.Maybe.mapMaybe' 'Text.Read.readMaybe' '$' 'words' s
+@
+
+@($)@ is also used as a section (a partially applied operator), in order to indicate that we wish to apply some yet-unspecified function to a given value. For example, to apply the argument @5@ to a list of functions:
+
+@
+applyFive :: [Int]
+applyFive = map ($ 5) [(+1), (2^)]
+>>> [6, 32]
+@
+
+=== Technical Remark (Representation Polymorphism)
+
+@($)@ is fully representation-polymorphic. This allows it to also be used with arguments of unlifted and even unboxed kinds, such as unboxed integers:
+
+@
+fastMod :: Int -> Int -> Int
+fastMod (I# x) (I# m) = I# $ remInt# x m
+@
+-}
 {-# INLINE ($) #-}
 ($) :: forall repa repb (a :: TYPE repa) (b :: TYPE repb). (a -> b) -> a -> b
 ($) f = f


=====================================
libraries/base/changelog.md
=====================================
@@ -7,8 +7,6 @@
   * Add `Data.List.!?` ([CLC proposal #110](https://github.com/haskell/core-libraries-committee/issues/110))
   * `maximumBy`/`minimumBy` are now marked as `INLINE` improving performance for unpackable
     types significantly.
-  * Refactor `generalCategory` to stop very large literal string being inlined to call-sites.
-      ([CLC proposal #130](https://github.com/haskell/core-libraries-committee/issues/130))
   * Add INLINABLE pragmas to `generic*` functions in Data.OldList ([CLC proposal #129](https://github.com/haskell/core-libraries-committee/issues/130))
   * Export `getSolo` from `Data.Tuple`.
       ([CLC proposal #113](https://github.com/haskell/core-libraries-committee/issues/113))
@@ -23,7 +21,7 @@
       ([CLC proposal #149](https://github.com/haskell/core-libraries-committee/issues/149))
   * Make `($)` representation polymorphic ([CLC proposal #132](https://github.com/haskell/core-libraries-committee/issues/132))
 
-## 4.18.0.0 *TBA*
+## 4.18.0.0 *March 2023*
   * Shipped with GHC 9.6.1
   * `Foreign.C.ConstPtr.ConstrPtr` was added to encode `const`-qualified
     pointer types in foreign declarations when using `CApiFFI` extension. ([CLC proposal #117](https://github.com/haskell/core-libraries-committee/issues/117))
@@ -61,6 +59,9 @@
     ([CLC proposal #50](https://github.com/haskell/core-libraries-committee/issues/50),
     [the migration
     guide](https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md))
+  * Switch to a pure Haskell implementation of `GHC.Unicode`
+    ([CLC proposals #59](https://github.com/haskell/core-libraries-committee/issues/59)
+    and [#130](https://github.com/haskell/core-libraries-committee/issues/130))
   * Update to [Unicode 15.0.0](https://www.unicode.org/versions/Unicode15.0.0/).
   * Add standard Unicode case predicates `isUpperCase` and `isLowerCase` to
     `GHC.Unicode` and `Data.Char`. These predicates use the standard Unicode


=====================================
rts/include/rts/storage/ClosureMacros.h
=====================================
@@ -479,11 +479,13 @@ EXTERN_INLINE StgWord8 *mutArrPtrsCard (StgMutArrPtrs *a, W_ n)
    memory we're about to zero.
 
    Thus, with the THREADED RTS and +RTS -N2 or greater we must not zero
-   immutable closure's slop.
+   immutable closure's slop. Similarly, the concurrent GC's mark thread
+   may race when a mutator during slop-zeroing. Consequently, we also disable
+   zeroing when the non-moving GC is in use.
 
    Hence, an immutable closure's slop is zeroed when either:
 
-    - PROFILING && era > 0 (LDV is on) or
+    - PROFILING && era > 0 (LDV is on) && !nonmoving-gc-enabled or
     - !THREADED && DEBUG
 
    Additionally:
@@ -535,8 +537,10 @@ zeroSlop (StgClosure *p,
 #endif
         ;
 
-    // Only if we're running single threaded.
-    const bool can_zero_immutable_slop = getNumCapabilities() == 1;
+    const bool can_zero_immutable_slop =
+        // Only if we're running single threaded.
+        getNumCapabilities() == 1
+        && !RTS_DEREF(RtsFlags).GcFlags.useNonmoving; // see #23170
 
     const bool zero_slop_immutable =
         want_to_zero_immutable_slop && can_zero_immutable_slop;



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2b79e3865d19ec02b3dba02052c2627c8ea0edb2...9fe52a1dbb53f07971f172a8502565109d2385e6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2b79e3865d19ec02b3dba02052c2627c8ea0edb2...9fe52a1dbb53f07971f172a8502565109d2385e6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230407/98cf1bd0/attachment-0001.html>


More information about the ghc-commits mailing list