Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/d1c8731aeb4af1a9ca28278cddd5ffbe9dd401b9

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

commit d1c8731aeb4af1a9ca28278cddd5ffbe9dd401b9
Author: Ian Lynagh <i...@well-typed.com>
Date:   Wed Oct 3 19:05:28 2012 +0100

    Fix the recompilation check for dynamic libraries
    
    I've put mkSOName in HscTypes for now; I'm not sure what the best place
    for it is.

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

 compiler/ghci/Linker.lhs        |    7 -------
 compiler/main/DriverPipeline.hs |   10 ++++++----
 compiler/main/HscTypes.lhs      |   12 ++++++++++++
 3 files changed, 18 insertions(+), 11 deletions(-)

diff --git a/compiler/ghci/Linker.lhs b/compiler/ghci/Linker.lhs
index 6b47db3..0cf98fe 100644
--- a/compiler/ghci/Linker.lhs
+++ b/compiler/ghci/Linker.lhs
@@ -1185,13 +1185,6 @@ searchForLibUsingGcc dflags so dirs = do
 -- ----------------------------------------------------------------------------
 -- Loading a dyanmic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)
 
-mkSOName :: Platform -> FilePath -> FilePath
-mkSOName platform root
-    = case platformOS platform of
-      OSDarwin  -> ("lib" ++ root) <.> "dylib"
-      OSMinGW32 ->           root  <.> "dll"
-      _         -> ("lib" ++ root) <.> "so"
-
 -- 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.
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 483e5c8..08420ef 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -371,7 +371,7 @@ linkingNeeded dflags linkables pkg_deps = do
                           | Just c <- map (lookupPackage pkg_map) pkg_deps,
                             lib <- packageHsLibs dflags c ]
 
-        pkg_libfiles <- mapM (uncurry findHSLib) pkg_hslibs
+        pkg_libfiles <- mapM (uncurry (findHSLib dflags)) pkg_hslibs
         if any isNothing pkg_libfiles then return True else do
         e_lib_times <- mapM (tryIO . getModificationUTCTime)
                           (catMaybes pkg_libfiles)
@@ -408,9 +408,11 @@ ghcLinkInfoSectionName :: String
 ghcLinkInfoSectionName = ".debug-ghc-link-info"
    -- if we use the ".debug" prefix, then strip will strip it by default
 
-findHSLib :: [String] -> String -> IO (Maybe FilePath)
-findHSLib dirs lib = do
-  let batch_lib_file = "lib" ++ lib <.> "a"
+findHSLib :: DynFlags -> [String] -> String -> IO (Maybe FilePath)
+findHSLib dflags dirs lib = do
+  let batch_lib_file = if dopt Opt_Static dflags
+                       then "lib" ++ lib <.> "a"
+                       else mkSOName (targetPlatform dflags) lib
   found <- filterM doesFileExist (map (</> batch_lib_file) dirs)
   case found of
     [] -> return Nothing
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index 7c1f169..ec5f6ee 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -37,6 +37,8 @@ module HscTypes (
 
         PackageInstEnv, PackageRuleBase,
 
+        mkSOName,
+
         -- * Annotations
         prepareAnnotations,
 
@@ -157,6 +159,7 @@ import Fingerprint
 import MonadUtils
 import Bag
 import ErrUtils
+import Platform
 import Util
 
 import Control.Monad    ( mplus, guard, liftM, when )
@@ -1778,6 +1781,15 @@ type OrigNameCache   = ModuleEnv (OccEnv Name)
 \end{code}
 
 
+\begin{code}
+mkSOName :: Platform -> FilePath -> FilePath
+mkSOName platform root
+    = case platformOS platform of
+      OSDarwin  -> ("lib" ++ root) <.> "dylib"
+      OSMinGW32 ->           root  <.> "dll"
+      _         -> ("lib" ++ root) <.> "so"
+\end{code}
+
 
 %************************************************************************
 %*                                                                      *



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to