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

On branch  : master

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

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

commit a94b80b1b1fa8a24f52a33bb38d1975e52a4037a
Author: Ian Lynagh <[email protected]>
Date:   Tue Aug 28 22:46:31 2012 +0100

    Remove Util.{isDarwinTarget,isWindowsTarget}

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

 compiler/ghci/Linker.lhs |   62 ++++++++++++++++++++++++++-------------------
 compiler/utils/Util.lhs  |   17 +++---------
 2 files changed, 41 insertions(+), 38 deletions(-)

diff --git a/compiler/ghci/Linker.lhs b/compiler/ghci/Linker.lhs
index 06096c3..43bb59d 100644
--- a/compiler/ghci/Linker.lhs
+++ b/compiler/ghci/Linker.lhs
@@ -51,6 +51,7 @@ import qualified Maybes
 import UniqSet
 import FastString
 import Config
+import Platform
 import SysTools
 import PrelNames
 
@@ -302,12 +303,13 @@ reallyInitDynLinker dflags =
         ; classified_ld_inputs <- mapM (classifyLdInput dflags) 
cmdline_ld_inputs
 
           -- (e) Link any MacOS frameworks
-        ; let framework_paths
-               | isDarwinTarget = frameworkPaths dflags
-               | otherwise      = []
-        ; let frameworks
-               | isDarwinTarget = cmdlineFrameworks dflags
-               | otherwise      = []
+        ; let platform = targetPlatform dflags
+        ; let framework_paths = case platformOS platform of
+                                OSDarwin -> frameworkPaths dflags
+                                _        -> []
+        ; let frameworks = case platformOS platform of
+                           OSDarwin -> cmdlineFrameworks dflags
+                           _        -> []
           -- Finally do (c),(d),(e)
         ; let cmdline_lib_specs = [ l | Just l <- classified_ld_inputs ]
                                ++ libspecs
@@ -375,7 +377,7 @@ preloadLib dflags lib_paths framework_paths lib_spec
                                                 else "not found")
 
           DLL dll_unadorned
-             -> do maybe_errstr <- loadDLL (mkSOName dll_unadorned)
+             -> do maybe_errstr <- loadDLL (mkSOName platform dll_unadorned)
                    case maybe_errstr of
                       Nothing -> maybePutStrLn dflags "done"
                       Just mm -> preloadFailed mm lib_paths lib_spec
@@ -386,15 +388,18 @@ preloadLib dflags lib_paths framework_paths lib_spec
                       Nothing -> maybePutStrLn dflags "done"
                       Just mm -> preloadFailed mm lib_paths lib_spec
 
-          Framework framework
-           | isDarwinTarget
-             -> do maybe_errstr <- loadFramework framework_paths framework
+          Framework framework ->
+              case platformOS (targetPlatform dflags) of
+              OSDarwin ->
+                do maybe_errstr <- loadFramework framework_paths framework
                    case maybe_errstr of
                       Nothing -> maybePutStrLn dflags "done"
                       Just mm -> preloadFailed mm framework_paths lib_spec
-           | otherwise -> panic "preloadLib Framework"
+              _ -> panic "preloadLib Framework"
 
   where
+    platform = targetPlatform dflags
+
     preloadFailed :: String -> [String] -> LibrarySpec -> IO ()
     preloadFailed sys_errmsg paths spec
        = do maybePutStr dflags "failed.\n"
@@ -968,7 +973,7 @@ data LibrarySpec
 -- just to get the DLL handle into the list.
 partOfGHCi :: [PackageName]
 partOfGHCi
- | isWindowsTarget || isDarwinTarget = []
+ | isWindowsHost || isDarwinHost = []
  | otherwise = map PackageName
                    ["base", "template-haskell", "editline"]
 
@@ -1033,7 +1038,8 @@ linkPackages' dflags new_pks pls = do
 linkPackage :: DynFlags -> PackageConfig -> IO ()
 linkPackage dflags pkg
    = do
-        let dirs      =  Packages.libraryDirs pkg
+        let platform  = targetPlatform dflags
+            dirs      =  Packages.libraryDirs pkg
 
         let hs_libs   =  Packages.hsLibraries pkg
             -- The FFI GHCi import lib isn't needed as
@@ -1070,8 +1076,8 @@ linkPackage dflags pkg
 
         -- See comments with partOfGHCi
         when (packageName pkg `notElem` partOfGHCi) $ do
-            loadFrameworks pkg
-            mapM_ load_dyn (known_dlls ++ map mkSOName dlls)
+            loadFrameworks platform pkg
+            mapM_ load_dyn (known_dlls ++ map (mkSOName platform) dlls)
 
         -- After loading all the DLLs, we can load the static objects.
         -- Ordering isn't important here, because we do one final link
@@ -1096,10 +1102,11 @@ load_dyn dll = do r <- loadDLL dll
                     Just err -> ghcError (CmdLineError ("can't load .so/.DLL 
for: "
                                                               ++ dll ++ " (" 
++ err ++ ")" ))
 
-loadFrameworks :: InstalledPackageInfo_ ModuleName -> IO ()
-loadFrameworks pkg
- | isDarwinTarget = mapM_ load frameworks
- | otherwise = return ()
+loadFrameworks :: Platform -> InstalledPackageInfo_ ModuleName -> IO ()
+loadFrameworks platform pkg
+    = case platformOS platform of
+      OSDarwin -> mapM_ load frameworks
+      _        -> return ()
   where
     fw_dirs    = Packages.frameworkDirs pkg
     frameworks = Packages.frameworks pkg
@@ -1142,9 +1149,9 @@ locateLib dflags is_hs dirs lib
      mk_arch_path dir = dir </> ("lib" ++ lib <.> "a")
 
      hs_dyn_lib_name = lib ++ "-ghc" ++ cProjectVersion
-     mk_hs_dyn_lib_path dir = dir </> mkSOName hs_dyn_lib_name
+     mk_hs_dyn_lib_path dir = dir </> mkSOName platform hs_dyn_lib_name
 
-     so_name = mkSOName lib
+     so_name = mkSOName platform lib
      mk_dyn_lib_path dir = dir </> so_name
 
      findObject  = liftM (fmap Object)  $ findFile mk_obj_path  dirs
@@ -1160,6 +1167,8 @@ locateLib dflags is_hs dirs lib
                            Just x -> return x
                            Nothing -> g
 
+     platform = targetPlatform dflags
+
 searchForLibUsingGcc :: DynFlags -> String -> [FilePath] -> IO (Maybe FilePath)
 searchForLibUsingGcc dflags so dirs = do
    str <- askCc dflags (map (FileOption "-L") dirs
@@ -1174,11 +1183,12 @@ searchForLibUsingGcc dflags so dirs = do
 -- ----------------------------------------------------------------------------
 -- Loading a dyanmic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)
 
-mkSOName :: FilePath -> FilePath
-mkSOName root
- | isDarwinTarget  = ("lib" ++ root) <.> "dylib"
- | isWindowsTarget = root <.> "dll"
- | otherwise       = ("lib" ++ root) <.> "so"
+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
diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs
index 9d12946..8717154 100644
--- a/compiler/utils/Util.lhs
+++ b/compiler/utils/Util.lhs
@@ -10,7 +10,7 @@ module Util (
         -- * Flags dependent on the compiler build
         ghciSupported, debugIsOn, ncgDebugIsOn,
         ghciTablesNextToCode, isDynamicGhcLib,
-        isWindowsHost, isWindowsTarget, isDarwinTarget,
+        isWindowsHost, isDarwinHost,
 
         -- * General list processing
         zipEqual, zipWithEqual, zipWith3Equal, zipWith4Equal,
@@ -192,18 +192,11 @@ isWindowsHost = True
 isWindowsHost = False
 #endif
 
-isWindowsTarget :: Bool
-#ifdef mingw32_TARGET_OS
-isWindowsTarget = True
+isDarwinHost :: Bool
+#ifdef darwin_HOST_OS
+isDarwinHost = True
 #else
-isWindowsTarget = False
-#endif
-
-isDarwinTarget :: Bool
-#ifdef darwin_TARGET_OS
-isDarwinTarget = True
-#else
-isDarwinTarget = False
+isDarwinHost = False
 #endif
 \end{code}
 



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to