[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Expand synonyms in RoughMap

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Feb 17 18:38:47 UTC 2023



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


Commits:
8988eeef by sheaf at 2023-02-16T20:32:27-05:00
Expand synonyms in RoughMap

We were failing to expand type synonyms in the function
GHC.Core.RoughMap.typeToRoughMatchLookupTc, even though the
RoughMap infrastructure crucially relies on type synonym expansion
to work.

This patch adds the missing type-synonym expansion.

Fixes #22985

- - - - -
3dd50e2f by Matthew Pickering at 2023-02-16T20:33:03-05:00
ghcup-metadata: Add test artifact

Add the released testsuite tarball to the generated ghcup metadata.

- - - - -
c6a967d9 by Matthew Pickering at 2023-02-16T20:33:03-05:00
ghcup-metadata: Use Ubuntu and Rocky bindists

Prefer to use the Ubuntu 20.04 and 18.04 binary distributions on Ubuntu
and Linux Mint. Prefer to use the Rocky 8 binary distribution on
unknown distributions.

- - - - -
be0b7209 by Matthew Pickering at 2023-02-17T09:37:16+00:00
Add INLINABLE pragmas to `generic*` functions in Data.OldList

These functions are

* recursive
* overloaded

So it's important to add an `INLINABLE` pragma to each so that they can be
specialised at the use site when the specific numeric type is known.
Adding these pragmas improves the LazyText replicate benchmark (see https://gitlab.haskell.org/ghc/ghc/-/issues/22886#note_481020)

https://github.com/haskell/core-libraries-committee/issues/129

- - - - -
85120b17 by Sylvain Henry at 2023-02-17T13:38:33-05:00
Merge libiserv with ghci

`libiserv` serves no purpose. As it depends on `ghci` and doesn't have
more dependencies than the `ghci` package, its code could live in the
`ghci` package too.

This commit also moves most of the code from the `iserv` program into
the `ghci` package as well so that it can be reused. This is especially
useful for the implementation of TH for the JS backend (#22261, !9779).

- - - - -


29 changed files:

- .gitlab-ci.yml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC/Core/RoughMap.hs
- docs/users_guide/9.6.1-notes.rst
- docs/users_guide/9.8.1-notes.rst
- hadrian/src/Packages.hs
- hadrian/src/Rules/Documentation.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- libraries/base/Data/OldList.hs
- libraries/base/changelog.md
- libraries/libiserv/src/IServ.hs → libraries/ghci/GHCi/Server.hs
- libraries/libiserv/src/GHCi/Utils.hsc → libraries/ghci/GHCi/Utils.hsc
- libraries/ghci/ghci.cabal.in
- − libraries/libiserv/.gitignore
- − libraries/libiserv/LICENSE
- − libraries/libiserv/Makefile
- − libraries/libiserv/cbits/iservmain.c
- − libraries/libiserv/libiserv.cabal.in
- packages
- + testsuite/tests/typecheck/should_compile/T22985a.hs
- + testsuite/tests/typecheck/should_compile/T22985b.hs
- testsuite/tests/typecheck/should_compile/all.T
- utils/iserv/iserv.cabal.in
- utils/iserv/src/Main.hs
- utils/remote-iserv/remote-iserv.cabal.in


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -1011,6 +1011,12 @@ ghcup-metadata-nightly:
       artifacts: false
     - job: nightly-x86_64-linux-centos7-validate
       artifacts: false
+    - job: nightly-x86_64-linux-ubuntu20_04-validate
+      artifacts: false
+    - job: nightly-x86_64-linux-ubuntu18_04-validate
+      artifacts: false
+    - job: nightly-x86_64-linux-rocky8-validate
+      artifacts: false
     - job: nightly-x86_64-darwin-validate
       artifacts: false
     - job: nightly-aarch64-darwin-validate


=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -73,6 +73,7 @@ class PlatformSpec(NamedTuple):
     subdir: str
 
 source_artifact = Artifact('source-tarball', 'ghc-{version}-src.tar.xz', 'ghc-{version}' )
+test_artifact = Artifact('source-tarball', 'ghc-{version}-testsuite.tar.xz', 'ghc-{version}' )
 
 def debian(arch, n):
     return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n))
@@ -93,6 +94,12 @@ def fedora(n):
 def alpine(n):
     return linux_platform("x86_64", "x86_64-linux-alpine{n}".format(n=n))
 
+def rocky(n):
+    return linux_platform("x86_64", "x86_64-linux-rocky{n}".format(n=n))
+
+def ubuntu(n):
+    return linux_platform("x86_64", "x86_64-linux-ubuntu{n}".format(n=n))
+
 def linux_platform(arch, opsys):
     return PlatformSpec( opsys, 'ghc-{version}-{arch}-unknown-linux'.format(version="{version}", arch=arch) )
 
@@ -156,6 +163,9 @@ def mk_new_yaml(release_mode, version, pipeline_type, job_map):
         eprint("\n=== " + platform.name + " " + ('=' * (75 - len(platform.name))))
         return mk_one_metadata(release_mode, version, job_map, mk_from_platform(pipeline_type, platform))
 
+    ubuntu1804 = mk(ubuntu("18_04"))
+    ubuntu2004 = mk(ubuntu("20_04"))
+    rocky8 = mk(rocky("8"))
     # Here are all the bindists we can distribute
     centos7 = mk(centos(7))
     fedora33 = mk(fedora(33))
@@ -170,6 +180,7 @@ def mk_new_yaml(release_mode, version, pipeline_type, job_map):
     deb9_i386 = mk(debian("i386", 9))
 
     source = mk_one_metadata(release_mode, version, job_map, source_artifact)
+    test = mk_one_metadata(release_mode, version, job_map, test_artifact)
 
     # The actual metadata, this is not a precise science, but just what the ghcup
     # developers want.
@@ -178,18 +189,18 @@ def mk_new_yaml(release_mode, version, pipeline_type, job_map):
                            , "(>= 10 && < 11)": deb10
                            , ">= 11": deb11
                            , "unknown_versioning": deb11 }
-          , "Linux_Ubuntu" : { "unknown_versioning": deb10
-                             , "( >= 16 && < 19 )": deb9
+          , "Linux_Ubuntu" : { "unknown_versioning": ubuntu2004
+                             , "( >= 16 && < 19 )": ubuntu1804
                              }
-          , "Linux_Mint"   : { "< 20": deb9
-                             , ">= 20": deb10 }
+          , "Linux_Mint"   : { "< 20": ubuntu1804
+                             , ">= 20": ubuntu2004 }
           , "Linux_CentOS"  : { "( >= 7 && < 8 )" : centos7
                               , "unknown_versioning" : centos7  }
           , "Linux_Fedora"  : { ">= 33": fedora33
                               , "unknown_versioning": centos7 }
           , "Linux_RedHat"  : { "unknown_versioning": centos7 }
           #MP: Replace here with Rocky8 when that job is in the pipeline
-          , "Linux_UnknownLinux" : { "unknown_versioning": fedora33 }
+          , "Linux_UnknownLinux" : { "unknown_versioning": rocky8 }
           , "Darwin" : { "unknown_versioning" : darwin_x86 }
           , "Windows" : { "unknown_versioning" :  windows }
           , "Linux_Alpine" : { "unknown_versioning": alpine3_12 }
@@ -220,6 +231,7 @@ def mk_new_yaml(release_mode, version, pipeline_type, job_map):
         # Check that this link exists
         , "viChangeLog": change_log
         , "viSourceDL": source
+        , "viTestDL": test
         , "viArch": { "A_64": a64
                     , "A_32": a32
                     , "A_ARM64": arm64


=====================================
CODEOWNERS
=====================================
@@ -59,7 +59,6 @@
 /libraries/template-haskell/      @rae
 
 [Internal utilities and libraries]
-/libraries/libiserv/              @angerman @simonmar
 /utils/iserv-proxy/               @angerman @simonmar
 /utils/iserv/                     @angerman @simonmar
 /utils/fs/                        @Phyx


=====================================
cabal.project-reinstall
=====================================
@@ -24,7 +24,6 @@ packages: ./compiler
           ./libraries/directory
           ./libraries/hpc
           -- ./libraries/integer-gmp
-          ./libraries/libiserv/
           ./libraries/mtl/
           ./libraries/parsec/
           -- ./libraries/pretty/


=====================================
compiler/GHC/Core/RoughMap.hs
=====================================
@@ -320,7 +320,11 @@ roughMatchTcsLookup tys = map typeToRoughMatchLookupTc tys
 
 typeToRoughMatchLookupTc :: Type -> RoughMatchLookupTc
 typeToRoughMatchLookupTc ty
-  | Just (ty', _) <- splitCastTy_maybe ty
+  -- Expand synonyms first, as explained in Note [Rough matching in class and family instances].
+  -- Failing to do so led to #22985.
+  | Just ty' <- coreView ty
+  = typeToRoughMatchLookupTc ty'
+  | CastTy ty' _ <- ty
   = typeToRoughMatchLookupTc ty'
   | otherwise
   = case splitAppTys ty of


=====================================
docs/users_guide/9.6.1-notes.rst
=====================================
@@ -254,7 +254,6 @@ for further change information.
     libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
     libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
     libraries/integer-gmp/integer-gmp.cabal: Core library
-    libraries/libiserv/libiserv.cabal:       Internal compiler library
     libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
     libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
     libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library


=====================================
docs/users_guide/9.8.1-notes.rst
=====================================
@@ -75,7 +75,6 @@ for further change information.
     libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
     libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
     libraries/integer-gmp/integer-gmp.cabal: Core library
-    libraries/libiserv/libiserv.cabal:       Internal compiler library
     libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
     libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
     libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library


=====================================
hadrian/src/Packages.hs
=====================================
@@ -7,7 +7,7 @@ module Packages (
     exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh,
     ghcCompact, ghcConfig, ghcHeap, ghci, ghciWrapper, ghcPkg, ghcPrim, haddock, haskeline,
     hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy,
-    libffi, libiserv, mtl, parsec, pretty, primitive, process, remoteIserv, rts,
+    libffi, mtl, parsec, pretty, primitive, process, remoteIserv, rts,
     runGhc, stm, templateHaskell, terminfo, text, time, timeout, touchy,
     transformers, unlit, unix, win32, xhtml,
     lintersCommon, lintNotes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace,
@@ -38,7 +38,7 @@ ghcPackages =
     , compareSizes, compiler, containers, deepseq, deriveConstants, directory
     , exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh
     , ghcCompact, ghcConfig, ghcHeap, ghci, ghciWrapper, ghcPkg, ghcPrim, haddock, haskeline, hsc2hs
-    , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, libiserv, mtl
+    , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, mtl
     , parsec, pretty, process, rts, runGhc, stm, templateHaskell
     , terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml
     , timeout
@@ -54,7 +54,7 @@ array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, count
   compareSizes, compiler, containers, deepseq, deriveConstants, directory,
   exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh,
   ghcCompact, ghcConfig, ghcHeap, ghci, ghciWrapper, ghcPkg, ghcPrim, haddock, haskeline, hsc2hs,
-  hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy, remoteIserv, libffi, libiserv, mtl,
+  hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy, remoteIserv, libffi, mtl,
   parsec, pretty, primitive, process, rts, runGhc, stm, templateHaskell,
   terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml,
   timeout,
@@ -102,7 +102,6 @@ integerSimple       = lib  "integer-simple"
 iserv               = util "iserv"
 iservProxy          = util "iserv-proxy"
 libffi              = top  "libffi"
-libiserv            = lib  "libiserv"
 mtl                 = lib  "mtl"
 parsec              = lib  "parsec"
 pretty              = lib  "pretty"


=====================================
hadrian/src/Rules/Documentation.hs
=====================================
@@ -76,7 +76,6 @@ needDocDeps = do
             [ ghcBoot
             , ghcBootTh
             , ghci
-            , libiserv
             , compiler
             , ghcHeap
             , templateHaskell


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -326,7 +326,6 @@ templateRules = do
   templateRule "driver/ghci/ghci-wrapper.cabal" $ projectVersion
   templateRule "ghc/ghc-bin.cabal" $ projectVersion
   templateRule "utils/iserv/iserv.cabal" $ projectVersion
-  templateRule "utils/iserv-proxy/iserv-proxy.cabal" $ projectVersion
   templateRule "utils/remote-iserv/remote-iserv.cabal" $ projectVersion
   templateRule "utils/runghc/runghc.cabal" $ projectVersion
   templateRule "libraries/ghc-boot/ghc-boot.cabal" $ projectVersion
@@ -334,7 +333,6 @@ templateRules = do
   templateRule "libraries/ghci/ghci.cabal" $ projectVersion
   templateRule "libraries/ghc-heap/ghc-heap.cabal" $ projectVersion
   templateRule "utils/ghc-pkg/ghc-pkg.cabal" $ projectVersion
-  templateRule "libraries/libiserv/libiserv.cabal" $ projectVersion
   templateRule "libraries/template-haskell/template-haskell.cabal" $ projectVersion
   templateRule "libraries/prologue.txt" $ packageVersions
 


=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -151,7 +151,6 @@ stage1Packages = do
         [ haddock
         , hpcBin
         , iserv
-        , libiserv
         , runGhc
         ]
       , when (winTarget && not cross)


=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -116,9 +116,9 @@ packageArgs = do
           [
           -- The use case here is that we want to build @iserv-proxy@ for the
           -- cross compiler. That one needs to be compiled by the bootstrap
-          -- compiler as it needs to run on the host. Hence @libiserv@ needs
-          -- @GHCi.TH@, @GHCi.Message@ and @GHCi.Run@ from @ghci at . And those are
-          -- behind the @-finternal-interpreter@ flag.
+          -- compiler as it needs to run on the host. Hence @iserv@ needs
+          -- @GHCi.TH@, @GHCi.Message@, @GHCi.Run@, and @GHCi.Server@ from
+          -- @ghci at . And those are behind the @-finternal-interpreter@ flag.
           --
           -- But it may not build if we have made some changes to ghci's
           -- dependencies (see #16051).


=====================================
libraries/base/Data/OldList.hs
=====================================
@@ -842,6 +842,7 @@ strictGenericLength l   =  gl l 0
                         where
                            gl [] a     = a
                            gl (_:xs) a = let a' = a + 1 in a' `seq` gl xs a'
+{-# INLINABLE strictGenericLength #-}
 
 -- | The 'genericTake' function is an overloaded version of 'take', which
 -- accepts any 'Integral' value as the number of elements to take.
@@ -849,6 +850,7 @@ genericTake             :: (Integral i) => i -> [a] -> [a]
 genericTake n _ | n <= 0 = []
 genericTake _ []        =  []
 genericTake n (x:xs)    =  x : genericTake (n-1) xs
+{-# INLINABLE genericTake #-}
 
 -- | The 'genericDrop' function is an overloaded version of 'drop', which
 -- accepts any 'Integral' value as the number of elements to drop.
@@ -856,6 +858,7 @@ genericDrop             :: (Integral i) => i -> [a] -> [a]
 genericDrop n xs | n <= 0 = xs
 genericDrop _ []        =  []
 genericDrop n (_:xs)    =  genericDrop (n-1) xs
+{-# INLINABLE genericDrop #-}
 
 
 -- | The 'genericSplitAt' function is an overloaded version of 'splitAt', which
@@ -865,6 +868,7 @@ genericSplitAt n xs | n <= 0 =  ([],xs)
 genericSplitAt _ []     =  ([],[])
 genericSplitAt n (x:xs) =  (x:xs',xs'') where
     (xs',xs'') = genericSplitAt (n-1) xs
+{-# INLINABLE genericSplitAt #-}
 
 -- | The 'genericIndex' function is an overloaded version of '!!', which
 -- accepts any 'Integral' value as the index.
@@ -874,11 +878,13 @@ genericIndex (_:xs) n
  | n > 0     = genericIndex xs (n-1)
  | otherwise = errorWithoutStackTrace "List.genericIndex: negative argument."
 genericIndex _ _      = errorWithoutStackTrace "List.genericIndex: index too large."
+{-# INLINABLE genericIndex #-}
 
 -- | The 'genericReplicate' function is an overloaded version of 'replicate',
 -- which accepts any 'Integral' value as the number of repetitions to make.
 genericReplicate        :: (Integral i) => i -> a -> [a]
 genericReplicate n x    =  genericTake n (repeat x)
+{-# INLINABLE genericReplicate #-}
 
 -- | The 'zip4' function takes four lists and returns a list of
 -- quadruples, analogous to 'zip'.


=====================================
libraries/base/changelog.md
=====================================
@@ -6,6 +6,7 @@
     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))
 
 ## 4.18.0.0 *TBA*
 


=====================================
libraries/libiserv/src/IServ.hs → libraries/ghci/GHCi/Server.hs
=====================================
@@ -1,17 +1,27 @@
-{-# LANGUAGE RankNTypes, RecordWildCards, GADTs, ScopedTypeVariables #-}
-module IServ (serv) where
+{-# LANGUAGE CPP, RankNTypes, RecordWildCards, GADTs, ScopedTypeVariables #-}
+module GHCi.Server
+  ( serv
+  , defaultServer
+  )
+where
 
+import Prelude
 import GHCi.Run
 import GHCi.TH
 import GHCi.Message
+import GHCi.Signals
+import GHCi.Utils
 
 import Control.DeepSeq
 import Control.Exception
 import Control.Monad
+import Control.Concurrent (threadDelay)
 import Data.Binary
+import Data.IORef
 
 import Text.Printf
-import System.Environment (getProgName)
+import System.Environment (getProgName, getArgs)
+import System.Exit
 
 type MessageHook = Msg -> IO Msg
 
@@ -84,3 +94,55 @@ serv verbose hook pipe restore = loop
       Left UserInterrupt -> return () >> discardCtrlC
       Left e -> throwIO e
       _ -> return ()
+
+-- | Default server
+defaultServer :: IO ()
+defaultServer = do
+  args <- getArgs
+  (outh, inh, rest) <-
+      case args of
+        arg0:arg1:rest -> do
+            inh  <- readGhcHandle arg1
+            outh <- readGhcHandle arg0
+            return (outh, inh, rest)
+        _ -> dieWithUsage
+
+  (verbose, rest') <- case rest of
+    "-v":rest' -> return (True, rest')
+    _ -> return (False, rest)
+
+  (wait, rest'') <- case rest' of
+    "-wait":rest'' -> return (True, rest'')
+    _ -> return (False, rest')
+
+  unless (null rest'') $
+    dieWithUsage
+
+  when verbose $
+    printf "GHC iserv starting (in: %s; out: %s)\n" (show inh) (show outh)
+  installSignalHandlers
+  lo_ref <- newIORef Nothing
+  let pipe = Pipe{pipeRead = inh, pipeWrite = outh, pipeLeftovers = lo_ref}
+
+  when wait $ do
+    when verbose $
+      putStrLn "Waiting 3s"
+    threadDelay 3000000
+
+  uninterruptibleMask $ serv verbose hook pipe
+
+  where hook = return -- empty hook
+    -- we cannot allow any async exceptions while communicating, because
+    -- we will lose sync in the protocol, hence uninterruptibleMask.
+
+dieWithUsage :: IO a
+dieWithUsage = do
+    prog <- getProgName
+    die $ prog ++ ": " ++ msg
+  where
+#if defined(WINDOWS)
+    msg = "usage: iserv <write-handle> <read-handle> [-v]"
+#else
+    msg = "usage: iserv <write-fd> <read-fd> [-v]"
+#endif
+


=====================================
libraries/libiserv/src/GHCi/Utils.hsc → libraries/ghci/GHCi/Utils.hsc
=====================================
@@ -1,12 +1,15 @@
 {-# LANGUAGE CPP #-}
 module GHCi.Utils
-    ( getGhcHandle
-    ) where
+  ( getGhcHandle
+  , readGhcHandle
+  )
+where
 
+import Prelude
 import Foreign.C
 import GHC.IO.Handle (Handle())
 #if defined(mingw32_HOST_OS)
-import Foreign.Ptr (ptrToIntPtr)
+import Foreign.Ptr (ptrToIntPtr,wordPtrToPtr)
 import GHC.IO (onException)
 import GHC.IO.Handle.FD (fdToHandle)
 import GHC.Windows (HANDLE)
@@ -16,12 +19,13 @@ import GHC.IO.Device as IODevice
 import GHC.IO.Encoding (getLocaleEncoding)
 import GHC.IO.IOMode
 import GHC.IO.Windows.Handle (fromHANDLE, Io(), NativeHandle())
+
+#include <fcntl.h>     /* for _O_BINARY */
+
 #else
 import System.Posix
 #endif
 
-#include <fcntl.h>     /* for _O_BINARY */
-
 -- | Gets a GHC Handle File description from the given OS Handle or POSIX fd.
 
 #if defined(mingw32_HOST_OS)
@@ -48,3 +52,20 @@ foreign import ccall "io.h _open_osfhandle" _open_osfhandle ::
 getGhcHandle :: CInt -> IO Handle
 getGhcHandle fd     = fdToHandle $ Fd fd
 #endif
+
+-- | Read a handle passed on the command-line and prepare it to be used with the IO manager
+readGhcHandle :: String -> IO Handle
+readGhcHandle s = do
+#if defined(mingw32_HOST_OS)
+  let fd = wordPtrToPtr (Prelude.read s)
+# if defined(__IO_MANAGER_WINIO__)
+  -- register the handles we received with
+  -- our I/O manager otherwise we can't use
+  -- them correctly.
+  return () <!> associateHandle' fd
+# endif
+#else
+  let fd = Prelude.read s
+#endif
+  getGhcHandle fd
+


=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -57,6 +57,7 @@ library
             GHCi.Signals
             GHCi.StaticPtrTable
             GHCi.TH
+            GHCi.Server
 
     exposed-modules:
         GHCi.BreakArray
@@ -66,6 +67,7 @@ library
         GHCi.RemoteTypes
         GHCi.FFI
         GHCi.TH.Binary
+        GHCi.Utils
 
     Build-Depends:
         rts,


=====================================
libraries/libiserv/.gitignore deleted
=====================================
@@ -1,4 +0,0 @@
-GNUmakefile
-/dist-install/
-/dist/
-ghc.mk


=====================================
libraries/libiserv/LICENSE deleted
=====================================
@@ -1,62 +0,0 @@
-This library (libraries/ghc-prim) is derived from code from several
-sources: 
-
-  * Code from the GHC project which is largely (c) The University of
-    Glasgow, and distributable under a BSD-style license (see below),
-
-  * Code from the Haskell 98 Report which is (c) Simon Peyton Jones
-    and freely redistributable (but see the full license for
-    restrictions).
-
-The full text of these licenses is reproduced below.  All of the
-licenses are BSD-style or compatible.
-
------------------------------------------------------------------------------
-
-The Glasgow Haskell Compiler License
-
-Copyright 2004, The University Court of the University of Glasgow. 
-All rights reserved.
-
-Redistribution and use in source and binary forms, with or without
-modification, are permitted provided that the following conditions are met:
-
-- Redistributions of source code must retain the above copyright notice,
-this list of conditions and the following disclaimer.
- 
-- Redistributions in binary form must reproduce the above copyright notice,
-this list of conditions and the following disclaimer in the documentation
-and/or other materials provided with the distribution.
- 
-- Neither name of the University nor the names of its contributors may be
-used to endorse or promote products derived from this software without
-specific prior written permission. 
-
-THIS SOFTWARE IS PROVIDED BY THE UNIVERSITY COURT OF THE UNIVERSITY OF
-GLASGOW AND THE CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
-INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND
-FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
-UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW OR THE CONTRIBUTORS BE LIABLE
-FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
-DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
-SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
-CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
-LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
-OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH
-DAMAGE.
-
------------------------------------------------------------------------------
-
-Code derived from the document "Report on the Programming Language
-Haskell 98", is distributed under the following license:
-
-  Copyright (c) 2002 Simon Peyton Jones
-
-  The authors intend this Report to belong to the entire Haskell
-  community, and so we grant permission to copy and distribute it for
-  any purpose, provided that it is reproduced in its entirety,
-  including this Notice.  Modified versions of this Report may also be
-  copied and distributed for any purpose, provided that the modified
-  version is clearly presented as such, and that it does not claim to
-  be a definition of the Haskell 98 Language.
-


=====================================
libraries/libiserv/Makefile deleted
=====================================
@@ -1,15 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-#      https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-#      https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = iserv
-TOP = ..
-include $(TOP)/mk/sub-makefile.mk


=====================================
libraries/libiserv/cbits/iservmain.c deleted
=====================================
@@ -1,17 +0,0 @@
-#include <rts/PosixSource.h>
-#include <Rts.h>
-
-#include <HsFFI.h>
-
-int main (int argc, char *argv[])
-{
-    RtsConfig conf = defaultRtsConfig;
-
-    // We never know what symbols GHC will look up in the future, so
-    // we must retain CAFs for running interpreted code.
-    conf.keep_cafs = 1;
-
-    conf.rts_opts_enabled = RtsOptsAll;
-    extern StgClosure ZCMain_main_closure;
-    hs_main(argc, argv, &ZCMain_main_closure, conf);
-}


=====================================
libraries/libiserv/libiserv.cabal.in deleted
=====================================
@@ -1,37 +0,0 @@
--- WARNING: libiserv.cabal is automatically generated from libiserv.cabal.in by
--- ../../configure.  Make sure you are editing libiserv.cabal.in, not
--- libiserv.cabal.
-
-Name: libiserv
-Version: @ProjectVersionMunged@
-Copyright: XXX
-License: BSD3
-License-File: LICENSE
-Author: XXX
-Maintainer: XXX
-Synopsis: Provides shared functionality between iserv and iserv-proxy.
-Description: Provides shared functionality between iserv and iserv-proxy.
-Category: Development
-build-type: Simple
-cabal-version: >=1.10
-
-Flag network
-    Description:   Build libiserv with over-the-network support
-    Default:       False
-
-Library
-    Default-Language: Haskell2010
-    Hs-Source-Dirs: src
-    Exposed-Modules: IServ
-                   , GHCi.Utils
-    Build-Depends: base       >= 4   && < 5,
-                   binary     >= 0.7 && < 0.11,
-                   bytestring >= 0.10 && < 0.12,
-                   containers >= 0.5 && < 0.7,
-                   deepseq    >= 1.4 && < 1.5,
-                   ghci       == @ProjectVersionMunged@
-
-    if os(windows)
-       Cpp-Options: -DWINDOWS
-   else
-       Build-Depends: unix   >= 2.7 && < 2.9


=====================================
packages
=====================================
@@ -52,7 +52,6 @@ libraries/directory          -           -                               ssh://g
 libraries/filepath           -           -                               ssh://git@github.com/haskell/filepath.git
 libraries/haskeline          -           -                               https://github.com/judah/haskeline.git
 libraries/hpc                -           -                               -
-libraries/libiserv           -           -                               -
 libraries/mtl                -           -                               https://github.com/haskell/mtl.git
 libraries/parsec             -           -                               https://github.com/haskell/parsec.git
 libraries/pretty             -           -                               https://github.com/haskell/pretty.git


=====================================
testsuite/tests/typecheck/should_compile/T22985a.hs
=====================================
@@ -0,0 +1,6 @@
+module T22985a where
+
+type Phase n = n
+
+addExpr :: Eq a => Phase a -> ()
+addExpr _ = ()


=====================================
testsuite/tests/typecheck/should_compile/T22985b.hs
=====================================
@@ -0,0 +1,6 @@
+module T22985b where
+
+type Phase n = n
+
+addExpr :: Num a => Phase a -> a
+addExpr x = let t = asTypeOf x 0 in t


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -861,4 +861,5 @@ test('T20666b', normal, compile, [''])
 test('T22891', normal, compile, [''])
 test('T22912', normal, compile, [''])
 test('T22924', normal, compile, [''])
-
+test('T22985a', normal, compile, ['-O'])
+test('T22985b', normal, compile, [''])


=====================================
utils/iserv/iserv.cabal.in
=====================================
@@ -18,9 +18,6 @@ Description:
   compiling Template Haskell, by spawning a separate delegate (so
   called runner on the javascript vm) and evaluating the splices
   there.
-  .
-  To use iserv with cross compilers, please see @libraries/libiserv@
-  and @utils/iserv-proxy at .
 
 Category: Development
 build-type: Simple
@@ -39,8 +36,7 @@ Executable iserv
                    bytestring >= 0.10 && < 0.12,
                    containers >= 0.5 && < 0.7,
                    deepseq    >= 1.4 && < 1.5,
-                   ghci       == @ProjectVersionMunged@,
-                   libiserv   == @ProjectVersionMunged@
+                   ghci       == @ProjectVersionMunged@
 
     if os(windows)
         Cpp-Options: -DWINDOWS


=====================================
utils/iserv/src/Main.hs
=====================================
@@ -1,5 +1,3 @@
-{-# LANGUAGE CPP, GADTs #-}
-
 -- |
 -- The Remote GHCi server.
 --
@@ -8,88 +6,7 @@
 --
 module Main (main) where
 
-import IServ (serv)
-
-import GHCi.Message
-import GHCi.Signals
-import GHCi.Utils
-
-import Control.Exception
-import Control.Concurrent (threadDelay)
-import Control.Monad
-import Data.IORef
-import System.Environment
-import System.Exit
-import Text.Printf
-#if defined(WINDOWS)
-import Foreign.Ptr (wordPtrToPtr)
-# if defined(__IO_MANAGER_WINIO__)
-import GHC.IO.SubSystem ((<!>))
-import GHC.Event.Windows (associateHandle')
-# endif
-#endif
-
-dieWithUsage :: IO a
-dieWithUsage = do
-    prog <- getProgName
-    die $ prog ++ ": " ++ msg
-  where
-#if defined(WINDOWS)
-    msg = "usage: iserv <write-handle> <read-handle> [-v]"
-#else
-    msg = "usage: iserv <write-fd> <read-fd> [-v]"
-#endif
+import GHCi.Server (defaultServer)
 
 main :: IO ()
-main = do
-  args <- getArgs
-  (outh, inh, rest) <-
-      case args of
-        arg0:arg1:rest -> do
-#if defined(WINDOWS)
-            let wfd1 = wordPtrToPtr (read arg0)
-                rfd2 = wordPtrToPtr (read arg1)
-# if defined(__IO_MANAGER_WINIO__)
-            -- register the handles we received with
-            -- our I/O manager otherwise we can't use
-            -- them correctly.
-            return () <!> (do
-              associateHandle' wfd1
-              associateHandle' rfd2)
-# endif
-#else
-            let wfd1 = read arg0
-                rfd2 = read arg1
-#endif
-            inh  <- getGhcHandle rfd2
-            outh <- getGhcHandle wfd1
-            return (outh, inh, rest)
-        _ -> dieWithUsage
-
-  (verbose, rest') <- case rest of
-    "-v":rest' -> return (True, rest')
-    _ -> return (False, rest)
-
-  (wait, rest'') <- case rest' of
-    "-wait":rest'' -> return (True, rest'')
-    _ -> return (False, rest')
-
-  unless (null rest'') $
-    dieWithUsage
-
-  when verbose $
-    printf "GHC iserv starting (in: %s; out: %s)\n" (show inh) (show outh)
-  installSignalHandlers
-  lo_ref <- newIORef Nothing
-  let pipe = Pipe{pipeRead = inh, pipeWrite = outh, pipeLeftovers = lo_ref}
-
-  when wait $ do
-    when verbose $
-      putStrLn "Waiting 3s"
-    threadDelay 3000000
-
-  uninterruptibleMask $ serv verbose hook pipe
-
-  where hook = return -- empty hook
-    -- we cannot allow any async exceptions while communicating, because
-    -- we will lose sync in the protocol, hence uninterruptibleMask.
+main = defaultServer


=====================================
utils/remote-iserv/remote-iserv.cabal.in
=====================================
@@ -13,7 +13,7 @@ Synopsis: iserv allows GHC to delegate Template Haskell computations
 Description:
   This is a very simple remote runner for iserv, to be used together
   with iserv-proxy.  The foundamental idea is that this this wrapper
-  starts running libiserv on a given port to which iserv-proxy will
+  starts running the GHCi server on a given port to which iserv-proxy will
   then connect.
 Category: Development
 build-type: Simple
@@ -24,4 +24,4 @@ Executable remote-iserv
    Main-Is: Cli.hs
    Hs-Source-Dirs: src
    Build-Depends: base       >= 4   && < 5,
-                  libiserv   == @ProjectVersionMunged@
+                  ghci       == @ProjectVersionMunged@



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dcd637ee5aa36ac59e6658ce7f7477a75ec7afd9...85120b17e925cce16d4dbf8e3cb3a7aa0e8ccc54

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dcd637ee5aa36ac59e6658ce7f7477a75ec7afd9...85120b17e925cce16d4dbf8e3cb3a7aa0e8ccc54
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/20230217/76d486eb/attachment-0001.html>


More information about the ghc-commits mailing list