X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverUtil.hs;h=b8796c1244d11479e1c90c924dcece7cacfec684;hb=423d477bfecd490de1449c59325c8776f91d7aac;hp=919fc3b7316067bb4a67c2af9ccba891b30c5484;hpb=9af77fa423926fbda946b31e174173d0ec5ebac8;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverUtil.hs b/ghc/compiler/main/DriverUtil.hs index 919fc3b..b8796c1 100644 --- a/ghc/compiler/main/DriverUtil.hs +++ b/ghc/compiler/main/DriverUtil.hs @@ -1,5 +1,5 @@ ----------------------------------------------------------------------------- --- $Id: DriverUtil.hs,v 1.34 2002/09/13 15:02:34 simonpj Exp $ +-- $Id: DriverUtil.hs,v 1.43 2004/08/13 13:07:02 simonmar Exp $ -- -- Utils for the driver -- @@ -7,20 +7,31 @@ -- ----------------------------------------------------------------------------- -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, replaceFilenameDirectory, + remove_spaces, escapeSpaces, + ) where + +#include "../includes/ghcconfig.h" #include "HsVersions.h" import Util import Panic import Config ( cLeadingUnderscore ) -import EXCEPTION as Exception +import EXCEPTION ( Exception(..), finally, throwDyn, catchDyn, throw ) +import qualified EXCEPTION as Exception import DYNAMIC import DATA_IOREF ( IORef, readIORef, writeIORef ) -import Directory ( getDirectoryContents, doesDirectoryExist ) +import Directory import IO import List import Char @@ -37,6 +48,7 @@ getOptionsFromSource file catchJust ioErrors (look h `finally` hClose h) (\e -> if isEOFError e then return [] else ioError e) where + look h = do l' <- hGetLine h let l = remove_spaces l' @@ -50,9 +62,9 @@ getOptionsFromSource file | 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 s1 <- maybePrefixMatch "{-#" s, -- -} + Just s2 <- maybePrefixMatch "OPTIONS" (remove_spaces s1), + Just s3 <- maybePrefixMatch "}-#" (reverse s2) = Just (reverse s3) | otherwise = Nothing @@ -69,11 +81,20 @@ softGetDirectoryContents d ) ----------------------------------------------------------------------------- +-- Create a hierarchy of directories + +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 (getdir fpath) - +doesDirNameExist fpath = doesDirectoryExist (directoryOf fpath) ----------------------------------------------------------------------------- -- Prefixing underscore to linker-level names @@ -91,20 +112,8 @@ 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) - = 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 +missingArgErr :: String -> a +missingArgErr f = throwDyn (UsageError ("missing argument for flag: " ++ f)) later = flip finally @@ -148,6 +157,14 @@ 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 @@ -159,7 +176,7 @@ splitFilename3 str 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) @@ -187,16 +204,17 @@ split_longest_prefix s pred (_:pre) -> (reverse pre, reverse suf) where (suf,pre) = break pred (reverse s) -newsuf :: String -> Suffix -> String -newsuf suf s = remove_suffix '.' s ++ suf +replaceFilenameSuffix :: FilePath -> Suffix -> FilePath +replaceFilenameSuffix s suf = remove_suffix '.' s ++ suf --- 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 isPathSeparator +-- directoryOf strips the filename off the input string, returning +-- the directory. +directoryOf :: FilePath -> String +directoryOf = fst . splitFilenameDir -newdir :: String -> String -> String -newdir dir s = dir ++ '/':drop_longest_prefix s isPathSeparator +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