X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverUtil.hs;h=91fd3ca6fa68dfbdf087a1f1afc9eb19015b86a0;hb=f53c4074ff7554ceedaa6b7a5edb2bca7a2d3886;hp=9a92b83ade9a16c4bfead2bdaee10835813a3174;hpb=6ef5df4a1bc630798e0de5e676afe11086b68606;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverUtil.hs b/ghc/compiler/main/DriverUtil.hs index 9a92b83..91fd3ca 100644 --- a/ghc/compiler/main/DriverUtil.hs +++ b/ghc/compiler/main/DriverUtil.hs @@ -1,5 +1,5 @@ ----------------------------------------------------------------------------- --- $Id: DriverUtil.hs,v 1.5 2000/10/27 13:50:25 sewardj Exp $ +-- $Id: DriverUtil.hs,v 1.16 2000/12/20 15:44:01 rrt Exp $ -- -- Utils for the driver -- @@ -9,10 +9,11 @@ module DriverUtil where +#include "../includes/config.h" #include "HsVersions.h" -import Config import Util +import Panic import IOExts import Exception @@ -21,6 +22,7 @@ import RegexString import IO import System +import Directory ( removeFile ) import List import Char import Monad @@ -28,8 +30,6 @@ import Monad ----------------------------------------------------------------------------- -- Errors -short_usage = "Usage: For basic information, try the `--help' option." - GLOBAL_VAR(v_Path_usage, "", String) long_usage = do @@ -39,39 +39,12 @@ long_usage = do exitWith ExitSuccess where dump "" = return () - dump ('$':'$':s) = hPutStr stderr get_prog_name >> dump s + dump ('$':'$':s) = hPutStr stderr progName >> 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(v_Prog_name, "ghc", String) - -get_prog_name = unsafePerformIO (readIORef v_Prog_name) -- urk! - -instance Show BarfKind where - showsPrec _ e = showString get_prog_name . showString ": " . showBarf e - -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" - -unknownFlagErr f = throwDyn (UsageError ("unrecognised flag: " ++ f)) - -barfKindTc = mkTyCon "BarfKind" -instance Typeable BarfKind where - typeOf _ = mkAppTy barfKindTc [] - ----------------------------------------------------------------------------- -- Reading OPTIONS pragmas + getOptionsFromSource :: String -- input file -> IO [String] -- options, if any @@ -87,7 +60,8 @@ getOptionsFromSource file | prefixMatch "#" l -> look h | prefixMatch "{-# LINE" l -> look h -- -} | Just (opts:_) <- matchRegex optionRegex l - -> return (words opts) + -> do rest <- look h + return (words opts ++ rest) | otherwise -> return [] optionRegex = mkRegex "\\{-#[ \t]+OPTIONS[ \t]+(.*)#-\\}" -- -} @@ -95,6 +69,9 @@ optionRegex = mkRegex "\\{-#[ \t]+OPTIONS[ \t]+(.*)#-\\}" -- -} ----------------------------------------------------------------------------- -- Utils +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) @@ -115,6 +92,9 @@ later = flip finally handleDyn :: Typeable ex => (ex -> IO a) -> IO a -> IO a handleDyn = flip catchDyn +handle :: (Exception -> IO a) -> IO a -> IO a +handle = flip Exception.catchAllIO + split :: Char -> String -> [String] split c s = case rest of [] -> [chunk] @@ -132,10 +112,16 @@ addNoDups var x = do unless (x `elem` xs) $ writeIORef var (x:xs) splitFilename :: String -> (String,String) -splitFilename f = (reverse (stripDot rev_basename), reverse rev_ext) - where (rev_ext, rev_basename) = span ('.' /=) (reverse f) - stripDot ('.':xs) = xs - stripDot xs = xs +splitFilename f = split_longest_prefix f '.' + +-- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy", ".ext") +splitFilename3 :: String -> (String,String,String) +splitFilename3 str + = let (dir, rest) = split_longest_prefix str '/' + (name, ext) = splitFilename rest + real_dir | null dir = "." + | otherwise = dir + in (real_dir, name, ext) remove_suffix :: Char -> String -> String remove_suffix c s @@ -151,6 +137,16 @@ take_longest_prefix :: String -> Char -> String take_longest_prefix s c = reverse pre where (_suf,pre) = break (==c) (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 + = case pre of + [] -> ([], reverse suf) + (_:pre) -> (reverse pre, reverse suf) + where (suf,pre) = break (==c) (reverse s) + newsuf :: String -> String -> String newsuf suf s = remove_suffix '.' s ++ suf @@ -165,9 +161,23 @@ newdir dir s = dir ++ '/':drop_longest_prefix s '/' remove_spaces :: String -> String remove_spaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace -booter_version - = case "\ - \ __GLASGOW_HASKELL__" of - ' ':n:ns -> n:'.':ns - ' ':m -> m +-- system that works feasibly under Windows (i.e. passes the command line to sh, +-- because system() under Windows doesn't look at SHELL, and always uses CMD.EXE) +kludgedSystem cmd phase_name + = do +#ifndef mingw32_TARGET_OS + exit_code <- system cmd `catchAllIO` + (\_ -> throwDyn (PhaseFailed phase_name (ExitFailure 1))) +#else + pid <- myGetProcessID + let tmp = "/tmp/sh" ++ show pid + h <- openFile tmp WriteMode + hPutStrLn h cmd + hClose h + exit_code <- system ("sh - " ++ tmp) `catchAllIO` + (\_ -> removeFile tmp >> + throwDyn (PhaseFailed phase_name (ExitFailure 1))) + removeFile tmp +#endif + return exit_code