[project @ 2004-11-11 16:07:40 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / DriverState.hs
index cad7f2b..58c85a4 100644 (file)
@@ -1,5 +1,4 @@
 -----------------------------------------------------------------------------
--- $Id: DriverState.hs,v 1.100 2004/02/25 11:31:24 simonmar Exp $
 --
 -- Settings for the driver
 --
@@ -9,7 +8,7 @@
 
 module DriverState where
 
-#include "../includes/config.h"
+#include "../includes/ghcconfig.h"
 #include "HsVersions.h"
 
 import ParsePkgConf    ( loadPackageConfig )
@@ -65,19 +64,19 @@ setMode m flag = do
 
 isCompManagerMode DoMake        = True
 isCompManagerMode DoInteractive = True
+isCompManagerMode (DoEval _)    = True
 isCompManagerMode _             = False
 
 -----------------------------------------------------------------------------
 -- Global compilation flags
 
--- Cpp-related flags
-v_Hs_source_cpp_opts = global
+-- Default CPP defines in Haskell source
+hsSourceCppOpts =
        [ "-D__HASKELL1__="++cHaskell1Version
        , "-D__GLASGOW_HASKELL__="++cProjectVersionInt                          
        , "-D__HASKELL98__"
        , "-D__CONCURRENT_HASKELL__"
        ]
-{-# NOINLINE v_Hs_source_cpp_opts #-}
 
 
 -- Keep output from intermediate phases
@@ -203,7 +202,7 @@ split_marker = ':'   -- not configurable (ToDo)
 
 v_Import_paths, v_Include_paths, v_Library_paths :: IORef [String]
 GLOBAL_VAR(v_Import_paths,  ["."], [String])
-GLOBAL_VAR(v_Include_paths, ["."], [String])
+GLOBAL_VAR(v_Include_paths, [], [String])
 GLOBAL_VAR(v_Library_paths, [],         [String])
 
 #ifdef darwin_TARGET_OS
@@ -211,6 +210,10 @@ GLOBAL_VAR(v_Framework_paths, [], [String])
 GLOBAL_VAR(v_Cmdline_frameworks, [], [String])
 #endif
 
+addToOrDeleteDirList :: IORef [String] -> String -> IO ()
+addToOrDeleteDirList ref ""   = writeIORef ref []
+addToOrDeleteDirList ref path = addToDirList ref path
+
 addToDirList :: IORef [String] -> String -> IO ()
 addToDirList ref path
   = do paths           <- readIORef ref
@@ -292,10 +295,10 @@ mungePackagePaths :: String -> [PackageConfig] -> [PackageConfig]
 -- with the current libdir (obtained from the -B option).
 mungePackagePaths top_dir ps = map munge_pkg ps
  where 
-  munge_pkg p = p{ import_dirs  = munge_paths (import_dirs p),
-                  include_dirs = munge_paths (include_dirs p),
-                  library_dirs = munge_paths (library_dirs p),
-                  framework_dirs = munge_paths (framework_dirs p) }
+  munge_pkg p = p{ importDirs  = munge_paths (importDirs p),
+                  includeDirs = munge_paths (includeDirs p),
+                  libraryDirs = munge_paths (libraryDirs p),
+                  frameworkDirs = munge_paths (frameworkDirs p) }
 
   munge_paths = map munge_path
 
@@ -358,22 +361,22 @@ getPackageImportPath = do
   ps <- getExplicitAndAutoPackageConfigs
                  -- import dirs are always derived from the 'auto' 
                  -- packages as well as the explicit ones
-  return (nub (filter notNull (concatMap import_dirs ps)))
+  return (nub (filter notNull (concatMap importDirs ps)))
 
 getPackageIncludePath :: [PackageName] -> IO [String]
 getPackageIncludePath pkgs = do
   ps <- getExplicitPackagesAnd pkgs
-  return (nub (filter notNull (concatMap include_dirs ps)))
+  return (nub (filter notNull (concatMap includeDirs ps)))
 
        -- includes are in reverse dependency order (i.e. rts first)
 getPackageCIncludes :: [PackageConfig] -> IO [String]
 getPackageCIncludes pkg_configs = do
-  return (reverse (nub (filter notNull (concatMap c_includes pkg_configs))))
+  return (reverse (nub (filter notNull (concatMap includes pkg_configs))))
 
 getPackageLibraryPath :: [PackageName] -> IO [String]
 getPackageLibraryPath pkgs = do 
   ps <- getExplicitPackagesAnd pkgs
-  return (nub (filter notNull (concatMap library_dirs ps)))
+  return (nub (filter notNull (concatMap libraryDirs ps)))
 
 getPackageLinkOpts :: [PackageName] -> IO [String]
 getPackageLinkOpts pkgs = do
@@ -383,9 +386,9 @@ getPackageLinkOpts pkgs = do
   static <- readIORef v_Static
   let 
        imp        = if static then "" else "_imp"
-       libs p     = map addSuffix (hACK (hs_libraries p)) ++ extra_libraries p
+       libs p     = map addSuffix (hACK (hsLibraries p)) ++ extraLibraries p
        imp_libs p = map (++imp) (libs p)
-       all_opts p = map ("-l" ++) (imp_libs p) ++ extra_ld_opts p
+       all_opts p = map ("-l" ++) (imp_libs p) ++ extraLdOpts p
 
        suffix     = if null tag then "" else  '_':tag
        rts_suffix = if null rts_tag then "" else  '_':rts_tag
@@ -426,21 +429,16 @@ getPackageLinkOpts pkgs = do
          libs
 #      endif
 
-getPackageExtraGhcOpts :: IO [String]
-getPackageExtraGhcOpts = do
-  ps <- getExplicitAndAutoPackageConfigs
-  return (concatMap extra_ghc_opts ps)
-
 getPackageExtraCcOpts :: [PackageName] -> IO [String]
 getPackageExtraCcOpts pkgs = do
   ps <- getExplicitPackagesAnd pkgs
-  return (concatMap extra_cc_opts ps)
+  return (concatMap extraCcOpts ps)
 
 #ifdef darwin_TARGET_OS
 getPackageFrameworkPath  :: [PackageName] -> IO [String]
 getPackageFrameworkPath pkgs = do
   ps <- getExplicitPackagesAnd pkgs
-  return (nub (filter notNull (concatMap framework_dirs ps)))
+  return (nub (filter notNull (concatMap frameworkDirs ps)))
 
 getPackageFrameworks  :: [PackageName] -> IO [String]
 getPackageFrameworks pkgs = do
@@ -462,7 +460,7 @@ getExplicitPackagesAnd pkg_names = do
 getExplicitAndAutoPackageConfigs :: IO [PackageConfig]
 getExplicitAndAutoPackageConfigs = do
   pkg_map <- getPackageConfigMap
-  let auto_packages = [ mkPackageName (name p) | p <- eltsUFM pkg_map, auto p ]
+  let auto_packages = [ packageConfigName p | p <- eltsUFM pkg_map, exposed p ]
   getExplicitPackagesAnd auto_packages
 
 -----------------------------------------------------------------------------
@@ -573,7 +571,8 @@ way_details :: [ (WayName, Way) ]
 way_details =
   [ (WayThreaded, Way "thr" True "Threaded" [
 #if defined(freebsd_TARGET_OS)
-       , "-optc-pthread"
+         "-optc-pthread"
+        , "-optl-pthread"
 #endif
        ] ),