[commit: ghc] master: plugins: search for .a files if necessary (be88c81)

git at git.haskell.org git at git.haskell.org
Sun Oct 28 17:41:30 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/be88c818a2962adbdaca0eda539412a9bfec4384/ghc

>---------------------------------------------------------------

commit be88c818a2962adbdaca0eda539412a9bfec4384
Author: sheaf <sam.derbyshire at gmail.com>
Date:   Sun Oct 28 12:30:13 2018 -0400

    plugins: search for .a files if necessary
    
    Summary:
    on windows, plugins are loaded via .a files,
    but those paths were not being searched when loading plugins
    
    Test Plan: ./validate
    
    Reviewers: Phyx, bgamari
    
    Reviewed By: Phyx
    
    Subscribers: RyanGlScott, rwbarton, carter
    
    GHC Trac Issues: #15700
    
    Differential Revision: https://phabricator.haskell.org/D5253


>---------------------------------------------------------------

be88c818a2962adbdaca0eda539412a9bfec4384
 compiler/deSugar/DsUsage.hs | 78 ++++++++++++++++++++++-----------------------
 testsuite/config/ghc        | 21 ++----------
 2 files changed, 40 insertions(+), 59 deletions(-)

diff --git a/compiler/deSugar/DsUsage.hs b/compiler/deSugar/DsUsage.hs
index 58c31ee..39b4855 100644
--- a/compiler/deSugar/DsUsage.hs
+++ b/compiler/deSugar/DsUsage.hs
@@ -140,7 +140,7 @@ with optimisations turned on, and give basically all binders an INLINE pragma.
 
 So instead:
 
-  * For plugins that were build locally: we store the filepath and hash of the
+  * For plugins that were built locally: we store the filepath and hash of the
     object files of the module with the `plugin` binder, and the object files of
     modules that are dependencies of the plugin module and belong to the same
     `UnitId` as the plugin
@@ -165,59 +165,57 @@ One way to improve this is to either:
 mkPluginUsage :: HscEnv -> ModIface -> IO [Usage]
 mkPluginUsage hsc_env pluginModule
   = case lookupPluginModuleWithSuggestions dflags pNm Nothing of
-    -- The plug is from an external package, we just look up the dylib that
-    -- contains the plugin
     LookupFound _ pkg -> do
+    -- The plugin is from an external package:
+    -- search for the library files containing the plugin.
       let searchPaths = collectLibraryPaths dflags [pkg]
-          libs        = packageHsLibs dflags pkg
-          dynlibLocs  = [ searchPath </> mkHsSOName platform lib
-                        | searchPath <- searchPaths
-                        , lib <- libs
-                        ]
-      dynlibs <- filterM doesFileExist dynlibLocs
-      case dynlibs of
-        [] -> pprPanic
-                ("mkPluginUsage: no dylibs, tried:\n" ++ unlines dynlibLocs)
-                (ppr pNm)
-        _  -> mapM hashFile (nub dynlibs)
+          useDyn = WayDyn `elem` ways dflags
+          suffix = if useDyn then soExt platform else "a"
+          libLocs = [ searchPath </> "lib" ++ libLoc <.> suffix
+                    | searchPath <- searchPaths
+                    , libLoc     <- packageHsLibs dflags pkg
+                    ]
+          -- we also try to find plugin library files by adding WayDyn way,
+          -- if it isn't already present (see trac #15492)
+          paths =
+            if useDyn
+              then libLocs
+              else
+                let dflags'  = updateWays (addWay' WayDyn dflags)
+                    dlibLocs = [ searchPath </> mkHsSOName platform dlibLoc
+                               | searchPath <- searchPaths
+                               , dlibLoc    <- packageHsLibs dflags' pkg
+                               ]
+                in libLocs ++ dlibLocs
+      files <- filterM doesFileExist paths
+      case files of
+        [] ->
+          pprPanic
+             ( "mkPluginUsage: missing plugin library, tried:\n"
+              ++ unlines paths
+             )
+             (ppr pNm)
+        _  -> mapM hashFile (nub files)
     _ -> do
       foundM <- findPluginModule hsc_env pNm
       case foundM of
-        -- The plugin was built locally, look up the object file containing
-        -- the `plugin` binder, and all object files belong to modules that are
-        -- transitive dependencies of the plugin that belong to the same package
+      -- The plugin was built locally: look up the object file containing
+      -- the `plugin` binder, and all object files belong to modules that are
+      -- transitive dependencies of the plugin that belong to the same package.
         Found ml _ -> do
-          pluginObject <- hashFile  (ml_obj_file ml)
+          pluginObject <- hashFile (ml_obj_file ml)
           depObjects   <- catMaybes <$> mapM lookupObjectFile deps
           return (nub (pluginObject : depObjects))
-        _ -> pprPanic "mkPluginUsage: no object or dylib" (ppr pNm)
+        _ -> pprPanic "mkPluginUsage: no object file found" (ppr pNm)
   where
-    -- plugins are shared libraries, so WayDyn should be part of the dflags in
-    -- order to get the correct filenames and library paths.
-    --
-    -- We can distinguish two scenarios:
-    --
-    -- 1. The dflags do not contain WayDyn, in this case we need to remove
-    --    all other ways and only add WayDyn. Why? Because other ways change
-    --    the library tags, i.e. WayProf adds `_p`, and we would end up looking
-    --    for a profiled plugin which might not be installed. See #15492
-    --
-    -- 2. The dflags do contain WayDyn, in this case we can leave the ways as
-    --    is, because the plugin must be compiled with the same ways as the
-    --    module that is currently being build, e.g., if the module is
-    --    build with WayDyn and WayProf, then the plugin that was used
-    --    would've also had to been build with WayProf (and WayDyn).
-    dflags1  = hsc_dflags hsc_env
-    dflags   = if WayDyn `elem` ways dflags1
-                 then dflags1
-                 else updateWays (addWay' WayDyn (dflags1 {ways = []}))
+    dflags   = hsc_dflags hsc_env
     platform = targetPlatform dflags
     pNm      = moduleName (mi_module pluginModule)
     pPkg     = moduleUnitId (mi_module pluginModule)
     deps     = map fst (dep_mods (mi_deps pluginModule))
 
-    -- loopup object file for a plugin dependencies from the same package as the
-    -- the plugin
+    -- Lookup object file for a plugin dependency,
+    -- from the same package as the plugin.
     lookupObjectFile nm = do
       foundM <- findImportedModule hsc_env nm Nothing
       case foundM of
diff --git a/testsuite/config/ghc b/testsuite/config/ghc
index b2edfd0..eae88ed 100644
--- a/testsuite/config/ghc
+++ b/testsuite/config/ghc
@@ -185,7 +185,6 @@ def get_compiler_info():
         config.package_conf_cache_file = ''
 
     # See Note [WayFlags]
-    # See Note [PluginWay]
     if config.ghc_dynamic:
         config.ghc_th_way_flags = "-dynamic"
         config.ghci_way_flags   = "-dynamic"
@@ -201,25 +200,9 @@ def get_compiler_info():
     else:
         config.ghc_th_way_flags = "-static"
         config.ghci_way_flags   = "-static"
-        config.plugin_way_flags = "-dynamic"
+        config.plugin_way_flags = "-static"
         config.ghc_th_way       = "normal"
-        config.ghc_plugin_way   = "dyn"
-
-# Note [PluginWay]
-#
-# Unfortunately the implementation has confused the ability to make dynamic
-# libraries with dynamic way.
-#
-# This constraint is only true for systems that require -fPIC for
-# shared libraries.
-#
-# It may not be worth fixing this assumption since the only platform that doesn't
-# require -fPIC is Windows.  These plugins require libghc to be linked so in
-# doing so you would exceed the amount of allowed symbols in a single shared
-# library.  The only way these would ever work is thus with DynWay.
-#
-# Since the implementation has this implicit assumption, mark the tests as
-# always requiring DynWay.
+        config.ghc_plugin_way   = "normal"
 
 # Note [Replacing backward slashes in config.libdir]
 #



More information about the ghc-commits mailing list