[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Clarify Note [GlobalId/LocalId] after CorePrep (#23797)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Sep 4 20:27:11 UTC 2023
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
e4af506e by Sebastian Graf at 2023-09-01T14:29:12-04:00
Clarify Note [GlobalId/LocalId] after CorePrep (#23797)
Fixes #23797.
- - - - -
ac29787c by Sylvain Henry at 2023-09-01T14:30:02-04:00
Fix warning with UNPACK on sum type (#23921)
- - - - -
dc18e27d by sheaf at 2023-09-04T16:27:00-04:00
Bump Haddock to fix #23616
This commit updates the Haddock submodule to include
the fix to #23616.
Fixes #23616
- - - - -
9c0ec045 by David Binder at 2023-09-04T16:27:07-04:00
Fix example in GHC user guide in SafeHaskell section
The example given in the SafeHaskell section uses an implementation of
Monad which no longer works. This MR removes the non-canonical return
instance and adds the necessary instances of Functor and Applicative.
- - - - -
4 changed files:
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Types/Var.hs
- docs/users_guide/exts/safe_haskell.rst
- utils/haddock
Changes:
=====================================
compiler/GHC/Core/TyCon.hs
=====================================
@@ -1,4 +1,4 @@
-
+{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DeriveDataTypeable #-}
@@ -1531,13 +1531,19 @@ See Note [RuntimeRep and PrimRep] in GHC.Types.RepType.
-}
+
-- | A 'PrimRep' is an abstraction of a type. It contains information that
-- the code generator needs in order to pass arguments, return results,
-- and store values of this type. See also Note [RuntimeRep and PrimRep] in
-- "GHC.Types.RepType" and Note [VoidRep] in "GHC.Types.RepType".
data PrimRep
= VoidRep
+-- Unpacking of sum types is only supported since 9.6.1
+#if MIN_VERSION_GLASGOW_HASKELL(9,6,0,0)
| BoxedRep {-# UNPACK #-} !(Maybe Levity) -- ^ Boxed, heap value
+#else
+ | BoxedRep !(Maybe Levity) -- ^ Boxed, heap value
+#endif
| Int8Rep -- ^ Signed, 8-bit value
| Int16Rep -- ^ Signed, 16-bit value
| Int32Rep -- ^ Signed, 32-bit value
=====================================
compiler/GHC/Types/Var.hs
=====================================
@@ -322,7 +322,10 @@ A LocalId is
* or defined at top level in the module being compiled
* always treated as a candidate by the free-variable finder
-After CoreTidy, top-level LocalIds are turned into GlobalIds
+In the output of CoreTidy, top level Ids are all GlobalIds, which are then
+serialised into interface files. Do note however that CorePrep may introduce new
+LocalIds for local floats (even at the top level). These will be visible in STG
+and end up in generated code.
Note [Multiplicity of let binders]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
docs/users_guide/exts/safe_haskell.rst
=====================================
@@ -109,8 +109,14 @@ define the plugin interface so that it requires the plugin module,
-- Notice that symbol UnsafeRIO is not exported from this module!
newtype RIO a = UnsafeRIO { runRIO :: IO a }
+ instance Functor RIO where
+ fmap f (UnsafeRIO m) = UnsafeRIO (fmap f m)
+
+ instance Applicative RIO where
+ pure = UnsafeRIO . pure
+ (UnsafeRIO f) <*> (UnsafeRIO m) = UnsafeRIO (f <*> m)
+
instance Monad RIO where
- return = UnsafeRIO . return
(UnsafeRIO m) >>= k = UnsafeRIO $ m >>= runRIO . k
-- Returns True iff access is allowed to file name
=====================================
utils/haddock
=====================================
@@ -1 +1 @@
-Subproject commit 5877bcebce88afad40ae9decb0f6029681c51848
+Subproject commit 394920426d99cee7822d5854bc83bbaab4970c7a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/265c16de7271734bd183016f87ddedaad900872b...9c0ec045edec78fa819a8d5a9f9f6be7e2e89650
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/265c16de7271734bd183016f87ddedaad900872b...9c0ec045edec78fa819a8d5a9f9f6be7e2e89650
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/20230904/b9d1dd27/attachment-0001.html>
More information about the ghc-commits
mailing list