X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverUtil.hs;h=f759f8b196f37854f350ecb4a0c19e9da9fc9aa0;hb=0f0e83390daf09bceb7ed0be5b280f3c662c02a8;hp=9c282f6d520b86254507489f68eb8d6c05e13441;hpb=68de0081f3581b9b15640cac598d980abe9ca424;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverUtil.hs b/ghc/compiler/main/DriverUtil.hs index 9c282f6..f759f8b 100644 --- a/ghc/compiler/main/DriverUtil.hs +++ b/ghc/compiler/main/DriverUtil.hs @@ -1,5 +1,5 @@ ----------------------------------------------------------------------------- --- $Id: DriverUtil.hs,v 1.19 2001/03/08 09:50:18 simonmar Exp $ +-- $Id: DriverUtil.hs,v 1.46 2004/11/09 16:59:31 simonmar Exp $ -- -- Utils for the driver -- @@ -7,41 +7,37 @@ -- ----------------------------------------------------------------------------- -module DriverUtil where - -#include "../includes/config.h" +module DriverUtil ( + getOptionsFromSource, softGetDirectoryContents, + createDirectoryHierarchy, doesDirNameExist, prefixUnderscore, + unknownFlagErr, unknownFlagsErr, missingArgErr, + later, handleDyn, handle, + split, add, addNoDups, + Suffix, splitFilename, getFileSuffix, + splitFilename3, remove_suffix, split_longest_prefix, + replaceFilenameSuffix, directoryOf, filenameOf, + replaceFilenameDirectory, remove_spaces, escapeSpaces, + ) where + +#include "../includes/ghcconfig.h" #include "HsVersions.h" import Util import Panic +import Config ( cLeadingUnderscore ) -import IOExts -import Exception -import Dynamic -import RegexString +import EXCEPTION ( Exception(..), finally, throwDyn, catchDyn, throw ) +import qualified EXCEPTION as Exception +import DYNAMIC +import DATA_IOREF ( IORef, readIORef, writeIORef ) +import Directory import IO -import System import List import Char import Monad ----------------------------------------------------------------------------- --- Errors - -GLOBAL_VAR(v_Path_usage, "", String) - -long_usage = do - usage_path <- readIORef v_Path_usage - usage <- readFile usage_path - dump usage - exitWith ExitSuccess - where - dump "" = return () - dump ('$':'$':s) = hPutStr stderr progName >> dump s - dump (c:s) = hPutChar stderr c >> dump s - ------------------------------------------------------------------------------ -- Reading OPTIONS pragmas getOptionsFromSource @@ -49,21 +45,65 @@ getOptionsFromSource -> IO [String] -- options, if any getOptionsFromSource file = do h <- openFile file ReadMode - catchJust ioErrors (look h) - (\e -> if isEOFError e then return [] else ioError e) + look h `finally` hClose h where look h = do - l <- hGetLine h - case () of - () | null l -> look h - | prefixMatch "#" l -> look h - | prefixMatch "{-# LINE" l -> look h -- -} - | Just (opts:_) <- matchRegex optionRegex l - -> do rest <- look h + r <- tryJust ioErrors (hGetLine h) + case r of + Left e | isEOFError e -> return [] + | otherwise -> ioError e + Right l' -> do + 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 [] + | otherwise -> return [] + +matchOptions s + | Just s1 <- maybePrefixMatch "{-#" s, -- -} + Just s2 <- maybePrefixMatch "OPTIONS" (remove_spaces s1), + Just s3 <- maybePrefixMatch "}-#" (reverse s2) + = Just (reverse s3) + | otherwise + = Nothing + +----------------------------------------------------------------------------- +-- A version of getDirectoryContents that is non-fatal if the +-- directory doesn't exist. + +softGetDirectoryContents d + = IO.catch (getDirectoryContents d) + (\_ -> do hPutStrLn stderr + ("WARNING: error while reading directory " ++ d) + return [] + ) + +----------------------------------------------------------------------------- +-- Create a hierarchy of directories -optionRegex = mkRegex "\\{-#[ \t]+OPTIONS[ \t]+(.*)#-\\}" -- -} +createDirectoryHierarchy :: FilePath -> IO () +createDirectoryHierarchy dir = do + b <- doesDirectoryExist dir + when (not b) $ do + createDirectoryHierarchy (directoryOf dir) + createDirectory dir + +----------------------------------------------------------------------------- +-- Verify that the 'dirname' portion of a FilePath exists. +-- +doesDirNameExist :: FilePath -> IO Bool +doesDirNameExist fpath = doesDirectoryExist (directoryOf fpath) + +----------------------------------------------------------------------------- +-- Prefixing underscore to linker-level names +prefixUnderscore :: String -> String +prefixUnderscore + | cLeadingUnderscore == "YES" = ('_':) + | otherwise = id ----------------------------------------------------------------------------- -- Utils @@ -71,20 +111,11 @@ optionRegex = mkRegex "\\{-#[ \t]+OPTIONS[ \t]+(.*)#-\\}" -- -} unknownFlagErr :: String -> a unknownFlagErr f = throwDyn (UsageError ("unrecognised flag: " ++ f)) -my_partition :: (a -> Maybe b) -> [a] -> ([(a,b)],[a]) -my_partition _ [] = ([],[]) -my_partition p (a:as) - = let (bs,cs) = my_partition p as in - case p a of - Nothing -> (bs,a:cs) - 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 (p:pat) (r:rest) - | p == r = my_prefix_match pat rest - | otherwise = Nothing +unknownFlagsErr :: [String] -> a +unknownFlagsErr fs = throwDyn (UsageError ("unrecognised flags: " ++ unwords fs)) + +missingArgErr :: String -> a +missingArgErr f = throwDyn (UsageError ("missing argument for flag: " ++ f)) later = flip finally @@ -92,7 +123,13 @@ 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 @@ -110,53 +147,92 @@ addNoDups var x = do xs <- readIORef var unless (x `elem` xs) $ writeIORef var (x:xs) -splitFilename :: String -> (String,String) -splitFilename f = split_longest_prefix f '.' +------------------------------------------------------ +-- 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,String) +splitFilename3 :: String -> (String,String,Suffix) splitFilename3 str - = let (dir, rest) = split_longest_prefix 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 -> String +remove_suffix :: Char -> String -> Suffix remove_suffix c s - | null pre = reverse suf + | null pre = s | 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) +drop_longest_prefix :: String -> (Char -> Bool) -> String +drop_longest_prefix s pred = reverse suf + where (suf,_pre) = break pred (reverse s) -take_longest_prefix :: String -> Char -> String -take_longest_prefix s c = reverse pre - where (_suf,pre) = break (==c) (reverse s) +take_longest_prefix :: String -> (Char -> Bool) -> String +take_longest_prefix s pred = reverse pre + where (_suf,pre) = break pred (reverse s) --- split a string at the last occurence of 'c', returning the two --- parts of the string with the 'c' removed. If the string contains --- no 'c's, the entire string is returned in the second component. -split_longest_prefix :: String -> Char -> (String,String) -split_longest_prefix s c +-- 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 (==c) (reverse s) + where (suf,pre) = break pred (reverse s) + +replaceFilenameSuffix :: FilePath -> Suffix -> FilePath +replaceFilenameSuffix s suf = remove_suffix '.' s ++ suf -newsuf :: String -> String -> String -newsuf suf s = remove_suffix '.' s ++ suf +-- directoryOf strips the filename off the input string, returning +-- the directory. +directoryOf :: FilePath -> String +directoryOf = fst . splitFilenameDir --- 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 '/' +-- filenameOf strips the directory off the input string, returning +-- the filename. +filenameOf :: FilePath -> String +filenameOf = snd . splitFilenameDir -newdir :: String -> String -> String -newdir dir s = dir ++ '/':drop_longest_prefix s '/' +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 +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