X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverUtil.hs;h=4932b9e48e132012e942c9525c04e57e04694591;hb=70b6c54b3c140d96b69287f8f400f88a0b7e9c18;hp=75cda59078755ecc00c5431651b318239c2691d8;hpb=60bf710865eff2ac5a497aad66c2bccc66a70215;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverUtil.hs b/ghc/compiler/main/DriverUtil.hs index 75cda59..4932b9e 100644 --- a/ghc/compiler/main/DriverUtil.hs +++ b/ghc/compiler/main/DriverUtil.hs @@ -1,5 +1,5 @@ ----------------------------------------------------------------------------- --- $Id: DriverUtil.hs,v 1.1 2000/10/11 11:54:58 simonmar Exp $ +-- $Id: DriverUtil.hs,v 1.38 2003/06/04 15:47:59 simonmar Exp $ -- -- Utils for the driver -- @@ -9,93 +9,98 @@ module DriverUtil where +#include "../includes/config.h" #include "HsVersions.h" -import Config import Util +import Panic +import Config ( cLeadingUnderscore ) -import IOExts -import Exception -import Dynamic +import EXCEPTION ( Exception(..), finally, throwDyn, catchDyn, throw ) +import qualified EXCEPTION as Exception +import DYNAMIC +import DATA_IOREF ( IORef, readIORef, writeIORef ) -import IO -import System import Directory +import IO import List import Char import Monad ----------------------------------------------------------------------------- --- Errors - -short_usage = "Usage: For basic information, try the `--help' option." - -long_usage = do - let usage_file = "ghc-usage.txt" - usage_path = findFile usage_file (cGHC_DRIVER_DIR ++ '/':usage_file) - usage <- readFile usage_path - dump usage - exitWith ExitSuccess +-- Reading OPTIONS pragmas + +getOptionsFromSource + :: String -- input file + -> IO [String] -- options, if any +getOptionsFromSource file + = do h <- openFile file ReadMode + catchJust ioErrors (look h `finally` hClose h) + (\e -> if isEOFError e then return [] else ioError e) where - dump "" = return () - dump ('$':'$':s) = hPutStr stderr get_prog_name >> dump s - dump (c:s) = hPutChar stderr c >> dump s - -version_str = cProjectVersion - -data BarfKind - = PhaseFailed String ExitCode - | Interrupted - | UsageError String -- prints the short usage msg after the error - | OtherError String -- just prints the error message - deriving Eq - -GLOBAL_VAR(prog_name, "ghc", String) + look h = do + l' <- hGetLine h + let l = remove_spaces l' + case () of + () | null l -> look h + | prefixMatch "#" l -> look h + | prefixMatch "{-# LINE" l -> look h -- -} + | Just opts <- matchOptions l + -> do rest <- look h + return (words opts ++ rest) + | otherwise -> return [] + +matchOptions s + | Just s1 <- my_prefix_match "{-#" s, -- -} + Just s2 <- my_prefix_match "OPTIONS" (remove_spaces s1), + Just s3 <- my_prefix_match "}-#" (reverse s2) + = Just (reverse s3) + | otherwise + = Nothing -get_prog_name = unsafePerformIO (readIORef prog_name) -- urk! +----------------------------------------------------------------------------- +-- A version of getDirectoryContents that is non-fatal if the +-- directory doesn't exist. -instance Show BarfKind where - showsPrec _ e = showString get_prog_name . showString ": " . showBarf e +softGetDirectoryContents d + = IO.catch (getDirectoryContents d) + (\_ -> do hPutStrLn stderr + ("WARNING: error while reading directory " ++ d) + return [] + ) -showBarf (UsageError str) = showString str . showChar '\n' . showString short_usage -showBarf (OtherError str) = showString str -showBarf (PhaseFailed phase code) = - showString phase . showString " failed, code = " . shows code -showBarf (Interrupted) = showString "interrupted" +----------------------------------------------------------------------------- +-- Create a hierarchy of directories -unknownFlagErr f = throwDyn (UsageError ("unrecognised flag: " ++ f)) +createDirectoryHierarchy :: FilePath -> IO () +createDirectoryHierarchy dir = do + b <- doesDirectoryExist dir + when (not b) $ do + createDirectoryHierarchy (directoryOf dir) + createDirectory dir -barfKindTc = mkTyCon "BarfKind" -instance Typeable BarfKind where - typeOf _ = mkAppTy barfKindTc [] +----------------------------------------------------------------------------- +-- Verify that the 'dirname' portion of a FilePath exists. +-- +doesDirNameExist :: FilePath -> IO Bool +doesDirNameExist fpath = doesDirectoryExist (directoryOf fpath) ----------------------------------------------------------------------------- --- Finding files in the installation - -GLOBAL_VAR(topDir, clibdir, String) - - -- grab the last -B option on the command line, and - -- set topDir to its value. -setTopDir :: [String] -> IO [String] -setTopDir args = do - let (minusbs, others) = partition (prefixMatch "-B") args - (case minusbs of - [] -> writeIORef topDir clibdir - some -> writeIORef topDir (drop 2 (last some))) - return others - -findFile name alt_path = unsafePerformIO (do - top_dir <- readIORef topDir - let installed_file = top_dir ++ '/':name - let inplace_file = top_dir ++ '/':cCURRENT_DIR ++ '/':alt_path - b <- doesFileExist inplace_file - if b then return inplace_file - else return installed_file - ) +-- Prefixing underscore to linker-level names +prefixUnderscore :: String -> String +prefixUnderscore + | cLeadingUnderscore == "YES" = ('_':) + | otherwise = id ----------------------------------------------------------------------------- -- Utils +unknownFlagErr :: String -> a +unknownFlagErr f = throwDyn (UsageError ("unrecognised flag: " ++ f)) + +unknownFlagsErr :: [String] -> a +unknownFlagsErr fs = throwDyn (UsageError ("unrecognised flags: " ++ unwords fs)) + my_partition :: (a -> Maybe b) -> [a] -> ([(a,b)],[a]) my_partition _ [] = ([],[]) my_partition p (a:as) @@ -105,26 +110,26 @@ my_partition p (a:as) Just b -> ((a,b):bs,cs) my_prefix_match :: String -> String -> Maybe String -my_prefix_match [] rest = Just rest -my_prefix_match (_:_) [] = Nothing +my_prefix_match [] rest = Just rest +my_prefix_match (_:_) [] = Nothing my_prefix_match (p:pat) (r:rest) | p == r = my_prefix_match pat rest | otherwise = Nothing -prefixMatch :: Eq a => [a] -> [a] -> Bool -prefixMatch [] _str = True -prefixMatch _pat [] = False -prefixMatch (p:ps) (s:ss) | p == s = prefixMatch ps ss - | otherwise = False - -postfixMatch :: String -> String -> Bool -postfixMatch pat str = prefixMatch (reverse pat) (reverse str) - later = flip finally handleDyn :: Typeable ex => (ex -> IO a) -> IO a -> IO a handleDyn = flip catchDyn +handle :: (Exception -> IO a) -> IO a -> IO a +#if __GLASGOW_HASKELL__ < 501 +handle = flip Exception.catchAllIO +#else +handle h f = f `Exception.catch` \e -> case e of + ExitException _ -> throw e + _ -> h e +#endif + split :: Char -> String -> [String] split c s = case rest of [] -> [chunk] @@ -141,37 +146,87 @@ addNoDups var x = do xs <- readIORef var unless (x `elem` xs) $ writeIORef var (x:xs) -remove_suffix :: Char -> String -> String +------------------------------------------------------ +-- Filename manipulation +------------------------------------------------------ + +type Suffix = String + +splitFilename :: String -> (String,Suffix) +splitFilename f = split_longest_prefix f (=='.') + +getFileSuffix :: String -> Suffix +getFileSuffix f = drop_longest_prefix f (=='.') + +-- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy.ext") +splitFilenameDir :: String -> (String,String) +splitFilenameDir str + = let (dir, rest) = split_longest_prefix str isPathSeparator + real_dir | null dir = "." + | otherwise = dir + in (real_dir, rest) + +-- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy", ".ext") +splitFilename3 :: String -> (String,String,Suffix) +splitFilename3 str + = let (dir, rest) = split_longest_prefix str isPathSeparator + (name, ext) = splitFilename rest + real_dir | null dir = "." + | otherwise = dir + in (real_dir, name, ext) + +remove_suffix :: Char -> String -> Suffix remove_suffix c s | null pre = reverse suf | otherwise = reverse pre where (suf,pre) = break (==c) (reverse s) -drop_longest_prefix :: String -> Char -> String -drop_longest_prefix s c = reverse suf - where (suf,_pre) = break (==c) (reverse s) - -take_longest_prefix :: String -> Char -> String -take_longest_prefix s c = reverse pre - where (_suf,pre) = break (==c) (reverse s) +drop_longest_prefix :: String -> (Char -> Bool) -> String +drop_longest_prefix s pred = reverse suf + where (suf,_pre) = break pred (reverse s) -newsuf :: String -> String -> String -newsuf suf s = remove_suffix '.' s ++ suf +take_longest_prefix :: String -> (Char -> Bool) -> String +take_longest_prefix s pred = reverse pre + where (_suf,pre) = break pred (reverse s) --- getdir strips the filename off the input string, returning the directory. -getdir :: String -> String -getdir s = if null dir then "." else init dir - where dir = take_longest_prefix s '/' - -newdir :: String -> String -> String -newdir dir s = dir ++ '/':drop_longest_prefix s '/' +-- split a string at the last character where 'pred' is True, +-- returning a pair of strings. The first component holds the string +-- up (but not including) the last character for which 'pred' returned +-- True, the second whatever comes after (but also not including the +-- last character). +-- +-- If 'pred' returns False for all characters in the string, the original +-- string is returned in the second component (and the first one is just +-- empty). +split_longest_prefix :: String -> (Char -> Bool) -> (String,String) +split_longest_prefix s pred + = case pre of + [] -> ([], reverse suf) + (_:pre) -> (reverse pre, reverse suf) + where (suf,pre) = break pred (reverse s) + +replaceFilenameSuffix :: FilePath -> Suffix -> FilePath +replaceFilenameSuffix s suf = remove_suffix '.' s ++ suf + +-- directoryOf strips the filename off the input string, returning +-- the directory. +directoryOf :: FilePath -> String +directoryOf = fst . splitFilenameDir + +replaceFilenameDirectory :: FilePath -> String -> FilePath +replaceFilenameDirectory s dir + = dir ++ '/':drop_longest_prefix s isPathSeparator remove_spaces :: String -> String remove_spaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace -booter_version - = case "\ - \ __GLASGOW_HASKELL__" of - ' ':n:ns -> n:'.':ns - ' ':m -> m +escapeSpaces :: String -> String +escapeSpaces = foldr (\c s -> if isSpace c then '\\':c:s else c:s) "" +isPathSeparator :: Char -> Bool +isPathSeparator ch = +#ifdef mingw32_TARGET_OS + ch == '/' || ch == '\\' +#else + ch == '/' +#endif