[Git][ghc/ghc][wip/pluginExtFields] 9 commits: Document loadFramework changes. (#18446)

Josh Meredith gitlab at gitlab.haskell.org
Mon Jul 27 03:16:11 UTC 2020



Josh Meredith pushed to branch wip/pluginExtFields at Glasgow Haskell Compiler / GHC


Commits:
a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00
Document loadFramework changes. (#18446)

Adds commentary on the rationale for the changes made in merge request
!3689.

- - - - -
da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00
rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails

Since switching to the two-step allocator, the `outofmem` test fails via
`osCommitMemory` failing to commit. However, this was previously exiting
with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter
is a more reasonable exit code for this case and matches the behavior on
POSIX platforms.

- - - - -
f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00
testsuite: Update win32 output for parseTree

- - - - -
e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00
testsuite: Normalise WinIO error message differences

Previously the old Windows IO manager threw different errors than WinIO.
We now canonicalise these to the WinIO errors.

- - - - -
9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00
gitlab-ci: Kill ssh-agent after pushing test metrics

Otherwise the Windows builds hang forever waiting for the process to
terminate.

- - - - -
8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00
winio: remove dead argument to stg_newIOPortzh

- - - - -
ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00
winio: fix detection of tty terminals

- - - - -
52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00
winio: update codeowners

- - - - -
945bee49 by Josh Meredith at 2020-07-26T23:16:08-04:00
Add machinery for plugins to write data to extensible interface fields

- - - - -


13 changed files:

- .gitlab/test-metrics.sh
- CODEOWNERS
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Types.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Runtime/Linker.hs
- libraries/base/cbits/IOutils.c
- libraries/base/tests/IO/all.T
- rts/PrimOps.cmm
- rts/win32/OSMem.c
- testsuite/driver/testlib.py
- testsuite/tests/ghc-api/annotations/parseTree.stdout-mingw32


Changes:

=====================================
.gitlab/test-metrics.sh
=====================================
@@ -81,6 +81,10 @@ function push() {
     echo ""
     echo "Failed to push git notes. Fetching, appending, and retrying... $MAX_RETRY retries left."
   done
+
+  # Be sure to kill agent before we terminate since otherwise the Windows CI
+  # job won't finish.
+  ssh-agent -k
 }
 
 case $1 in
@@ -88,3 +92,4 @@ case $1 in
   pull) pull ;;
   *) fail "Invalid mode $1" ;;
 esac
+


=====================================
CODEOWNERS
=====================================
@@ -49,3 +49,18 @@
 /utils/gen-dll/                   @Phyx
 /utils/fs/                        @Phyx
 
+# WinIO related code
+/libraries/base/GHC/Event/Windows/                   @Phyx
+/libraries/base/GHC/IO/Windows/                      @Phyx
+/rts/win32/                                          @Phyx
+/libraries/base/GHC/IO/Handle/Lock/Windows.hsc       @Phyx
+/libraries/base/GHC/Event/Windows.hsc                @Phyx
+/libraries/base/GHC/Conc/WinIO.hs                    @Phyx
+/libraries/base/GHC/Conc/Windows.hs                  @Phyx
+/libraries/base/GHC/IO/Handle/Windows.hs             @Phyx
+/libraries/base/GHC/IO/StdHandles.hs                 @Phyx
+/libraries/base/GHC/Windows.hs                       @Phyx
+/libraries/base/cbits/IOutils.c                      @Phyx
+/libraries/base/cbits/Win32Utils.c                   @Phyx
+/libraries/base/cbits/consUtils.c                    @Phyx
+/libraries/base/include/winio_structs.h              @Phyx


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -198,6 +198,7 @@ newHscEnv dflags = do
     us      <- mkSplitUniqSupply 'r'
     nc_var  <- newIORef (initNameCache us knownKeyNames)
     fc_var  <- newIORef emptyInstalledModuleEnv
+    ext_fs  <- newIORef emptyExtensibleFields
     emptyDynLinker <- uninitializedLinker
     return HscEnv {  hsc_dflags       = dflags
                   ,  hsc_targets      = []
@@ -207,6 +208,7 @@ newHscEnv dflags = do
                   ,  hsc_EPS          = eps_var
                   ,  hsc_NC           = nc_var
                   ,  hsc_FC           = fc_var
+                  ,  hsc_ext_fields   = ext_fs
                   ,  hsc_type_env_var = Nothing
                   ,  hsc_interp       = Nothing
                   ,  hsc_dynLinker    = emptyDynLinker
@@ -810,11 +812,10 @@ finish summary tc_result mb_old_hash = do
           (cg_guts, details) <- {-# SCC "CoreTidy" #-}
               liftIO $ tidyProgram hsc_env simplified_guts
 
-          let !partial_iface =
-                {-# SCC "GHC.Driver.Main.mkPartialIface" #-}
+          !partial_iface <- {-# SCC "GHC.Driver.Main.mkPartialIface" #-}
                 -- This `force` saves 2M residency in test T10370
                 -- See Note [Avoiding space leaks in toIface*] for details.
-                force (mkPartialIface hsc_env details simplified_guts)
+                liftIO $ force <$> (mkPartialIface hsc_env details simplified_guts)
 
           return HscRecomp { hscs_guts = cg_guts,
                              hscs_mod_location = ms_location summary,


=====================================
compiler/GHC/Driver/Types.hs
=====================================
@@ -155,6 +155,7 @@ module GHC.Driver.Types (
         readField, readIfaceField, readIfaceFieldWith,
         writeField, writeIfaceField, writeIfaceFieldWith,
         deleteField, deleteIfaceField,
+        registerInterfaceData, registerInterfaceDataWith,
     ) where
 
 #include "HsVersions.h"
@@ -475,6 +476,10 @@ data HscEnv
         hsc_FC   :: {-# UNPACK #-} !(IORef FinderCache),
                 -- ^ The cached result of performing finding in the file system
 
+        hsc_ext_fields :: {-# UNPACK #-} !(IORef ExtensibleFields),
+                -- ^ Extensible interface field data stored by plugins to be later
+                -- output in the `.hi` file.
+
         hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
                 -- ^ Used for one-shot compilation only, to initialise
                 -- the 'IfGblEnv'. See 'GHC.Tc.Utils.tcg_type_env_var' for
@@ -3404,3 +3409,12 @@ deleteField name (ExtensibleFields fs) = ExtensibleFields $ Map.delete name fs
 
 deleteIfaceField :: FieldName -> ModIface -> ModIface
 deleteIfaceField name iface = iface { mi_ext_fields = deleteField name (mi_ext_fields iface) }
+
+registerInterfaceData :: Binary a => FieldName -> HscEnv -> a -> IO ()
+registerInterfaceData name env x = registerInterfaceDataWith name env (`put_` x)
+
+registerInterfaceDataWith :: FieldName -> HscEnv -> (BinHandle -> IO ()) -> IO ()
+registerInterfaceDataWith name env write = do
+  ext_fs  <- readIORef (hsc_ext_fields env)
+  ext_fs' <- writeFieldWith name write ext_fs
+  writeIORef (hsc_ext_fields env) ext_fs'


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -81,7 +81,7 @@ import GHC.Driver.Plugins (LoadedPlugin(..))
 mkPartialIface :: HscEnv
                -> ModDetails
                -> ModGuts
-               -> PartialModIface
+               -> IO PartialModIface
 mkPartialIface hsc_env mod_details
   ModGuts{ mg_module       = this_mod
          , mg_hsc_src      = hsc_src
@@ -98,8 +98,11 @@ mkPartialIface hsc_env mod_details
          , mg_decl_docs    = decl_docs
          , mg_arg_docs     = arg_docs
          }
-  = mkIface_ hsc_env this_mod hsc_src used_th deps rdr_env fix_env warns hpc_info self_trust
-             safe_mode usages doc_hdr decl_docs arg_docs mod_details
+  = do ext_fs <- readIORef $ hsc_ext_fields hsc_env
+       return iface{mi_ext_fields = ext_fs}
+    where
+      iface = mkIface_ hsc_env this_mod hsc_src used_th deps rdr_env fix_env warns hpc_info self_trust
+                       safe_mode usages doc_hdr decl_docs arg_docs mod_details
 
 -- | Fully instantiate an interface. Adds fingerprints and potentially code
 -- generator produced information.


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -20,7 +20,9 @@ module GHC.IfaceToCore (
         tcIfaceAnnotations, tcIfaceCompleteSigs,
         tcIfaceExpr,    -- Desired by HERMIT (#7683)
         tcIfaceGlobal,
-        tcIfaceOneShot
+        tcIfaceOneShot,
+        tcIfaceType,
+        tcJoinInfo,
  ) where
 
 #include "HsVersions.h"


=====================================
compiler/GHC/Runtime/Linker.hs
=====================================
@@ -1695,6 +1695,38 @@ addEnvPaths name list
 -- ----------------------------------------------------------------------------
 -- Loading a dynamic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)
 
+{-
+Note [macOS Big Sur dynamic libraries]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+macOS Big Sur makes the following change to how frameworks are shipped
+with the OS:
+
+> New in macOS Big Sur 11 beta, the system ships with a built-in
+> dynamic linker cache of all system-provided libraries.  As part of
+> this change, copies of dynamic libraries are no longer present on
+> the filesystem.  Code that attempts to check for dynamic library
+> presence by looking for a file at a path or enumerating a directory
+> will fail.  Instead, check for library presence by attempting to
+> dlopen() the path, which will correctly check for the library in the
+> cache. (62986286)
+
+(https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/)
+
+Therefore, the previous method of checking whether a library exists
+before attempting to load it makes GHC.Runtime.Linker.loadFramework
+fail to find frameworks installed at /System/Library/Frameworks.
+Instead, any attempt to load a framework at runtime, such as by
+passing -framework OpenGL to runghc or running code loading such a
+framework with GHCi, fails with a 'not found' message.
+
+GHC.Runtime.Linker.loadFramework now opportunistically loads the
+framework libraries without checking for their existence first,
+failing only if all attempts to load a given framework from any of the
+various possible locations fail.  See also #18446, which this change
+addresses.
+-}
+
 -- Darwin / MacOS X only: load a framework
 -- a framework is a dynamic library packaged inside a directory of the same
 -- name. They are searched for in different paths than normal libraries.
@@ -1714,6 +1746,9 @@ loadFramework hsc_env extraPaths rootname
      -- sorry for the hardcoded paths, I hope they won't change anytime soon:
      defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
 
+     -- Try to call loadDLL for each candidate path.
+     --
+     -- See Note [macOS Big Sur dynamic libraries]
      findLoadDLL [] errs =
        -- Tried all our known library paths, but dlopen()
        -- has no built-in paths for frameworks: give up


=====================================
libraries/base/cbits/IOutils.c
=====================================
@@ -209,8 +209,8 @@ __is_console(HANDLE hFile)
     DWORD handleType = GetFileType (hFile);
 
     /* TTY must be a character device */
-    if (handleType == FILE_TYPE_CHAR)
-        return true;
+    if (handleType != FILE_TYPE_CHAR)
+        return false;
 
     DWORD st;
     /* GetConsoleMode appears to fail when it's not a TTY.  In


=====================================
libraries/base/tests/IO/all.T
=====================================
@@ -10,7 +10,7 @@ test('IOError001', [omit_ways(['ghci']), set_stdin('IOError001.hs')],
 test('IOError002',      normal, compile_and_run, [''])
 test('finalization001', normal, compile_and_run, [''])
 test('hClose001', [], compile_and_run, [''])
-test('hClose002', [], compile_and_run, [''])
+test('hClose002', [normalise_win32_io_errors], compile_and_run, [''])
 test('hClose003',       reqlib('unix'), compile_and_run, ['-package unix'])
 test('hFileSize001',    normal, compile_and_run, [''])
 test('hFileSize002', [omit_ways(['ghci'])], compile_and_run, [''])
@@ -61,8 +61,8 @@ test('misc001', [extra_run_opts('misc001.hs misc001.out')], compile_and_run,
      [''])
 
 test('openFile001',  normal, compile_and_run, [''])
-test('openFile002',  exit_code(1), compile_and_run, [''])
-test('openFile003', [], compile_and_run, [''])
+test('openFile002',  [exit_code(1), normalise_win32_io_errors], compile_and_run, [''])
+test('openFile003', [normalise_win32_io_errors], compile_and_run, [''])
 test('openFile004', [], compile_and_run, [''])
 test('openFile005', [], compile_and_run, [''])
 test('openFile006', [], compile_and_run, [''])


=====================================
rts/PrimOps.cmm
=====================================
@@ -2221,7 +2221,7 @@ loop:
    IOPort primitives
    -------------------------------------------------------------------------- */
 
-stg_newIOPortzh ( gcptr init )
+stg_newIOPortzh ()
 {
     W_ ioport;
 


=====================================
rts/win32/OSMem.c
=====================================
@@ -472,7 +472,7 @@ void osCommitMemory (void *at, W_ size)
     temp = VirtualAlloc(at, size, MEM_COMMIT, PAGE_READWRITE);
     if (temp == NULL) {
         sysErrorBelch("osCommitMemory: VirtualAlloc MEM_COMMIT failed");
-        stg_exit(EXIT_FAILURE);
+        stg_exit(EXIT_HEAPOVERFLOW);
     }
 }
 


=====================================
testsuite/driver/testlib.py
=====================================
@@ -743,6 +743,30 @@ def normalise_whitespace_fun(f):
 def _normalise_whitespace_fun(name, opts, f):
     opts.whitespace_normaliser = f
 
+def normalise_win32_io_errors(name, opts):
+    """
+    On Windows we currently have two IO manager implementations: both WinIO IO
+    manager and the old POSIX-emulated implementation. These currently differ
+    slightly in the error messages that they provide. Normalise these
+    differences away, preferring the new WinIO errors.
+
+    This can be dropped when the old IO manager is removed.
+    """
+
+    SUBS = [
+        ('Bad file descriptor', 'The handle is invalid'),
+        ('Permission denied', 'Access is denied.'),
+        ('No such file or directory', 'The system cannot find the file specified.'),
+    ]
+
+    def f(s: str):
+        for old,new in SUBS:
+            s = s.replace(old, new)
+
+        return s
+
+    return when(opsys('mingw32'), normalise_fun(f))
+
 def normalise_version_( *pkgs ):
     def normalise_version__( str ):
         return re.sub('(' + '|'.join(map(re.escape,pkgs)) + ')-[0-9.]+',


=====================================
testsuite/tests/ghc-api/annotations/parseTree.stdout-mingw32
=====================================
@@ -1,11 +1,11 @@
-[(AnnotationTuple.hs:14:20, [p], Unit 1),
- (AnnotationTuple.hs:14:23-29, [p], Unit "hello"),
- (AnnotationTuple.hs:14:35-37, [p], Unit 6.5),
+[(AnnotationTuple.hs:14:20, [p], Solo 1),
+ (AnnotationTuple.hs:14:23-29, [p], Solo "hello"),
+ (AnnotationTuple.hs:14:35-37, [p], Solo 6.5),
  (AnnotationTuple.hs:14:39, [m], ()),
- (AnnotationTuple.hs:14:41-52, [p], Unit [5, 5, 6, 7]),
- (AnnotationTuple.hs:16:8, [p], Unit 1),
- (AnnotationTuple.hs:16:11-17, [p], Unit "hello"),
- (AnnotationTuple.hs:16:20-22, [p], Unit 6.5),
+ (AnnotationTuple.hs:14:41-52, [p], Solo [5, 5, 6, 7]),
+ (AnnotationTuple.hs:16:8, [p], Solo 1),
+ (AnnotationTuple.hs:16:11-17, [p], Solo "hello"),
+ (AnnotationTuple.hs:16:20-22, [p], Solo 6.5),
  (AnnotationTuple.hs:16:24, [m], ()),
  (AnnotationTuple.hs:16:25, [m], ()),
  (AnnotationTuple.hs:16:26, [m], ()), (<no location info>, [m], ())]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de64ec94d02cbd92c9d96280082c82a342ec1526...945bee49b0b4f0d4ee95c5dde31c630ee445f3a3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de64ec94d02cbd92c9d96280082c82a342ec1526...945bee49b0b4f0d4ee95c5dde31c630ee445f3a3
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/20200726/7b64c5e8/attachment-0001.html>


More information about the ghc-commits mailing list