[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: compiler: remove unused GHC.Linker module

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Jan 26 17:33:58 UTC 2024



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


Commits:
0ac8f385 by Cheng Shao at 2024-01-25T00:27:48-05:00
compiler: remove unused GHC.Linker module

The GHC.Linker module is empty and unused, other than as a hack for
the make build system. We can remove it now that make is long gone;
the note is moved to GHC.Linker.Loader instead.

- - - - -
699da01b by Hécate Moonlight at 2024-01-25T00:28:27-05:00
Clarification for newtype constructors when using `coerce`

- - - - -
b2d8cd85 by Matt Walker at 2024-01-26T09:50:08-05:00
Fix #24308

Add tests for semicolon separated where clauses

- - - - -
54c733c1 by Ben Gamari at 2024-01-26T12:33:52-05:00
hsc2hs: Bump submodule

- - - - -
7888a48f by Ben Gamari at 2024-01-26T12:33:52-05:00
Bump containers submodule to 0.7

- - - - -


18 changed files:

- compiler/GHC/Builtin/primops.txt.pp
- − compiler/GHC/Linker.hs
- compiler/GHC/Linker/Loader.hs
- compiler/ghc.cabal.in
- ghc/ghc-bin.cabal.in
- libraries/Cabal
- libraries/containers
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/template-haskell/Language/Haskell/TH/Ppr.hs
- testsuite/tests/driver/T4437.hs
- + testsuite/tests/th/T24308.hs
- + testsuite/tests/th/T24308.stdout
- testsuite/tests/th/all.T
- utils/hsc2hs
- utils/iserv/iserv.cabal.in


Changes:

=====================================
compiler/GHC/Builtin/primops.txt.pp
=====================================
@@ -3955,10 +3955,25 @@ pseudoop   "coerce"
      more complicated settings, e.g. converting a list of newtypes to a list of
      concrete types.
 
+     When used in conversions involving a newtype wrapper,
+     make sure the newtype constructor is in scope.
+
      This function is representation-polymorphic, but the
      'RuntimeRep' type argument is marked as 'Inferred', meaning
      that it is not available for visible type application. This means
      the typechecker will accept @'coerce' \@'Int' \@Age 42 at .
+
+     === __Examples__
+
+     >>> newtype TTL = TTL Int deriving (Eq, Ord, Show)
+     >>> newtype Age = Age Int deriving (Eq, Ord, Show)
+     >>> coerce (Age 42) :: TTL
+     TTL 42
+     >>> coerce (+ (1 :: Int)) (Age 42) :: TTL
+     TTL 43
+     >>> coerce (map (+ (1 :: Int))) [Age 42, Age 24] :: [TTL]
+     [TTL 43,TTL 25]
+
    }
 
 ------------------------------------------------------------------------


=====================================
compiler/GHC/Linker.hs deleted
=====================================
@@ -1,36 +0,0 @@
-module GHC.Linker
-   (
-   )
-where
-
-import GHC.Prelude ()
-   -- We need this dummy dependency for the make build system. Otherwise it
-   -- tries to load GHC.Types which may not be built yet.
-
--- Note [Linkers and loaders]
--- ~~~~~~~~~~~~~~~~~~~~~~~~~~
---
--- Linkers are used to produce linked objects (.so, executables); loaders are
--- used to link in memory (e.g., in GHCi) with the already loaded libraries
--- (ghc-lib, rts, etc.).
---
--- Linking can usually be done with an external linker program ("ld"), but
--- loading is more tricky:
---
---    * Fully dynamic:
---       when GHC is built as a set of dynamic libraries (ghc-lib, rts, etc.)
---       and the modules to load are also compiled for dynamic linking, a
---       solution is to fully rely on external tools:
---
---       1) link a .so with the external linker
---       2) load the .so with POSIX's "dlopen"
---
---    * When GHC is built as a static program or when libraries we want to load
---    aren't compiled for dynamic linking, GHC uses its own loader ("runtime
---    linker"). The runtime linker is part of the rts (rts/Linker.c).
---
--- Note that within GHC's codebase we often use the word "linker" to refer to
--- the static object loader in the runtime system.
---
--- Loading can be delegated to an external interpreter ("iserv") when
--- -fexternal-interpreter is used.


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -109,6 +109,34 @@ import System.Win32.Info (getSystemDirectory)
 
 import GHC.Utils.Exception
 
+-- Note [Linkers and loaders]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~
+--
+-- Linkers are used to produce linked objects (.so, executables); loaders are
+-- used to link in memory (e.g., in GHCi) with the already loaded libraries
+-- (ghc-lib, rts, etc.).
+--
+-- Linking can usually be done with an external linker program ("ld"), but
+-- loading is more tricky:
+--
+--    * Fully dynamic:
+--       when GHC is built as a set of dynamic libraries (ghc-lib, rts, etc.)
+--       and the modules to load are also compiled for dynamic linking, a
+--       solution is to fully rely on external tools:
+--
+--       1) link a .so with the external linker
+--       2) load the .so with POSIX's "dlopen"
+--
+--    * When GHC is built as a static program or when libraries we want to load
+--    aren't compiled for dynamic linking, GHC uses its own loader ("runtime
+--    linker"). The runtime linker is part of the rts (rts/Linker.c).
+--
+-- Note that within GHC's codebase we often use the word "linker" to refer to
+-- the static object loader in the runtime system.
+--
+-- Loading can be delegated to an external interpreter ("iserv") when
+-- -fexternal-interpreter is used.
+
 uninitialised :: a
 uninitialised = panic "Loader not initialised"
 


=====================================
compiler/ghc.cabal.in
=====================================
@@ -114,7 +114,7 @@ Library
                    bytestring >= 0.9 && < 0.13,
                    binary     == 0.8.*,
                    time       >= 1.4 && < 1.13,
-                   containers >= 0.6.2.1 && < 0.7,
+                   containers >= 0.6.2.1 && < 0.8,
                    array      >= 0.1 && < 0.6,
                    filepath   >= 1   && < 1.5,
                    template-haskell == 2.21.*,
@@ -580,7 +580,6 @@ Library
         GHC.JS.JStg.Syntax
         GHC.JS.JStg.Monad
         GHC.JS.Transform
-        GHC.Linker
         GHC.Linker.Config
         GHC.Linker.Deps
         GHC.Linker.Dynamic


=====================================
ghc/ghc-bin.cabal.in
=====================================
@@ -37,7 +37,7 @@ Executable ghc
                    directory  >= 1   && < 1.4,
                    process    >= 1   && < 1.7,
                    filepath   >= 1   && < 1.5,
-                   containers >= 0.5 && < 0.7,
+                   containers >= 0.5 && < 0.8,
                    transformers >= 0.5 && < 0.7,
                    ghc-boot      == @ProjectVersionMunged@,
                    ghc           == @ProjectVersionMunged@


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit a0d815c4773a9d7aa0f48cc5bd08947d282dc917
+Subproject commit ae3c40a20bf98870488e3b40fc4495009b026e33


=====================================
libraries/containers
=====================================
@@ -1 +1 @@
-Subproject commit f61b0c9104a3c436361f56a0974c5eeef40c1b89
+Subproject commit 4fda06c43ea14f808748aa8988158946c3ce0caf


=====================================
libraries/ghc-boot/ghc-boot.cabal.in
=====================================
@@ -76,7 +76,7 @@ Library
     build-depends: base       >= 4.7 && < 4.20,
                    binary     == 0.8.*,
                    bytestring >= 0.10 && < 0.13,
-                   containers >= 0.5 && < 0.7,
+                   containers >= 0.5 && < 0.8,
                    directory  >= 1.2 && < 1.4,
                    filepath   >= 1.3 && < 1.5,
                    deepseq    >= 1.4 && < 1.6,


=====================================
libraries/ghc-heap/ghc-heap.cabal.in
=====================================
@@ -25,7 +25,7 @@ library
   build-depends:    base             >= 4.9.0 && < 5.0
                   , ghc-prim         > 0.2 && < 0.12
                   , rts              == 1.0.*
-                  , containers       >= 0.6.2.1 && < 0.7
+                  , containers       >= 0.6.2.1 && < 0.8
 
   ghc-options:      -Wall
   if !os(ghcjs)


=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -79,7 +79,7 @@ library
         ghc-prim         >= 0.5.0 && < 0.12,
         binary           == 0.8.*,
         bytestring       >= 0.10 && < 0.13,
-        containers       >= 0.5 && < 0.7,
+        containers       >= 0.5 && < 0.8,
         deepseq          >= 1.4 && < 1.6,
         filepath         == 1.4.*,
         ghc-boot         == @ProjectVersionMunged@,


=====================================
libraries/haskeline
=====================================
@@ -1 +1 @@
-Subproject commit 16ee820fc86f43045365f2c3536ad18147eb0b79
+Subproject commit ab2272336641195d0d087a6ccfd9bf511d208860


=====================================
libraries/template-haskell/Language/Haskell/TH/Ppr.hs
=====================================
@@ -395,7 +395,10 @@ instance Ppr Dec where
 ppr_dec :: Bool     -- ^ declaration on the toplevel?
         -> Dec
         -> Doc
-ppr_dec _ (FunD f cs)   = vcat $ map (\c -> pprPrefixOcc f <+> ppr c) cs
+ppr_dec isTop (FunD f cs)   = layout $ map (\c -> pprPrefixOcc f <+> ppr c) cs
+  where
+    layout :: [Doc] -> Doc
+    layout = if isTop then vcat else semiSepWith id
 ppr_dec _ (ValD p r ds) = ppr p <+> pprBody True r
                           $$ where_clause ds
 ppr_dec _ (TySynD t xs rhs)


=====================================
testsuite/tests/driver/T4437.hs
=====================================
@@ -37,7 +37,7 @@ check title expected got
 -- See Note [Adding a language extension] in compiler/GHC/Driver/Session.hs.
 expectedGhcOnlyExtensions :: [String]
 expectedGhcOnlyExtensions =
-    [ "TypeAbstractions"
+    [
     ]
 
 expectedCabalOnlyExtensions :: [String]


=====================================
testsuite/tests/th/T24308.hs
=====================================
@@ -0,0 +1,14 @@
+{-# LANGUAGE QuasiQuotes, TemplateHaskell #-}
+
+module Main where
+
+import Language.Haskell.TH
+import Language.Haskell.TH.Ppr
+
+main = runQ t1 >>= (putStrLn . pprint)
+
+t1 = [d|
+      fac n = go n
+       where go 0 = 1
+             go x = x * go (x - 1)
+     |]


=====================================
testsuite/tests/th/T24308.stdout
=====================================
@@ -0,0 +1,2 @@
+fac_0 n_1 = go_2 n_1
+          where {go_2 0 = 1; go_2 x_3 = x_3 GHC.Num.* go_2 (x_3 GHC.Num.- 1)}


=====================================
testsuite/tests/th/all.T
=====================================
@@ -600,3 +600,4 @@ test('T23986', normal, compile_and_run, [''])
 test('T24111', normal, compile_and_run, [''])
 test('T23719', normal, compile_fail, [''])
 test('T24190', normal, compile_and_run, [''])
+test('T24308', normal, compile_and_run, [''])


=====================================
utils/hsc2hs
=====================================
@@ -1 +1 @@
-Subproject commit 5bf5c61e7c6e813d03bc069e17289c574185d41c
+Subproject commit a6d9f73689ac51100ed7f6af0ea8cecd34422a91


=====================================
utils/iserv/iserv.cabal.in
=====================================
@@ -34,7 +34,7 @@ Executable iserv
                    base       >= 4   && < 5,
                    binary     >= 0.7 && < 0.11,
                    bytestring >= 0.10 && < 0.13,
-                   containers >= 0.5 && < 0.7,
+                   containers >= 0.5 && < 0.8,
                    deepseq    >= 1.4 && < 1.6,
                    ghci       == @ProjectVersionMunged@
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/33b9eb0a851ec37d31a7ba717f7b33c28156fd72...7888a48f81118c3c258229df297daabd9e7fa9e4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/33b9eb0a851ec37d31a7ba717f7b33c28156fd72...7888a48f81118c3c258229df297daabd9e7fa9e4
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/20240126/9f94f10f/attachment-0001.html>


More information about the ghc-commits mailing list