[project @ 2003-11-10 12:04:25 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / DriverUtil.hs
1 -----------------------------------------------------------------------------
2 -- $Id: DriverUtil.hs,v 1.40 2003/11/10 12:04:25 simonpj Exp $
3 --
4 -- Utils for the driver
5 --
6 -- (c) The University of Glasgow 2000
7 --
8 -----------------------------------------------------------------------------
9
10 module DriverUtil where
11
12 #include "../includes/config.h"
13 #include "HsVersions.h"
14
15 import Util
16 import Panic
17 import Config           ( cLeadingUnderscore )
18
19 import EXCEPTION        ( Exception(..), finally, throwDyn, catchDyn, throw )
20 import qualified EXCEPTION as Exception
21 import DYNAMIC
22 import DATA_IOREF       ( IORef, readIORef, writeIORef )
23
24 import Directory
25 import IO
26 import List
27 import Char
28 import Monad
29
30 -----------------------------------------------------------------------------
31 -- Reading OPTIONS pragmas
32
33 getOptionsFromSource 
34         :: String               -- input file
35         -> IO [String]          -- options, if any
36 getOptionsFromSource file
37   = do h <- openFile file ReadMode
38        catchJust ioErrors (look h `finally` hClose h)
39           (\e -> if isEOFError e then return [] else ioError e)
40   where
41         look h = do
42             l' <- hGetLine h
43             let l = remove_spaces l'
44             case () of
45                 () | null l -> look h
46                    | prefixMatch "#" l -> look h
47                    | prefixMatch "{-# LINE" l -> look h   -- -}
48                    | Just opts <- matchOptions l
49                         -> do rest <- look h
50                               return (words opts ++ rest)
51                    | otherwise -> return []
52
53 matchOptions s
54   | Just s1 <- maybePrefixMatch "{-#" s, -- -}
55     Just s2 <- maybePrefixMatch "OPTIONS" (remove_spaces s1),
56     Just s3 <- maybePrefixMatch "}-#" (reverse s2)
57   = Just (reverse s3)
58   | otherwise
59   = Nothing
60
61 -----------------------------------------------------------------------------
62 -- A version of getDirectoryContents that is non-fatal if the
63 -- directory doesn't exist.
64
65 softGetDirectoryContents d
66    = IO.catch (getDirectoryContents d)
67           (\_ -> do hPutStrLn stderr 
68                           ("WARNING: error while reading directory " ++ d)
69                     return []
70           )
71
72 -----------------------------------------------------------------------------
73 -- Create a hierarchy of directories
74
75 createDirectoryHierarchy :: FilePath -> IO ()
76 createDirectoryHierarchy dir = do
77   b <- doesDirectoryExist dir
78   when (not b) $ do
79         createDirectoryHierarchy (directoryOf dir)
80         createDirectory dir
81
82 -----------------------------------------------------------------------------
83 -- Verify that the 'dirname' portion of a FilePath exists.
84 -- 
85 doesDirNameExist :: FilePath -> IO Bool
86 doesDirNameExist fpath = doesDirectoryExist (directoryOf fpath)
87
88 -----------------------------------------------------------------------------
89 -- Prefixing underscore to linker-level names
90 prefixUnderscore :: String -> String
91 prefixUnderscore
92  | cLeadingUnderscore == "YES" = ('_':)
93  | otherwise                   = id
94
95 -----------------------------------------------------------------------------
96 -- Utils
97
98 unknownFlagErr :: String -> a
99 unknownFlagErr f = throwDyn (UsageError ("unrecognised flag: " ++ f))
100
101 unknownFlagsErr :: [String] -> a
102 unknownFlagsErr fs = throwDyn (UsageError ("unrecognised flags: " ++ unwords fs))
103
104 missingArgErr :: String -> a
105 missingArgErr f = throwDyn (UsageError ("missing argument for flag: " ++ f))
106
107 my_partition :: (a -> Maybe b) -> [a] -> ([(a,b)],[a])
108 my_partition _ [] = ([],[])
109 my_partition p (a:as)
110   = let (bs,cs) = my_partition p as in
111     case p a of
112         Nothing -> (bs,a:cs)
113         Just b  -> ((a,b):bs,cs)
114
115 later = flip finally
116
117 handleDyn :: Typeable ex => (ex -> IO a) -> IO a -> IO a
118 handleDyn = flip catchDyn
119
120 handle :: (Exception -> IO a) -> IO a -> IO a
121 #if __GLASGOW_HASKELL__ < 501
122 handle = flip Exception.catchAllIO
123 #else
124 handle h f = f `Exception.catch` \e -> case e of
125     ExitException _ -> throw e
126     _               -> h e
127 #endif
128
129 split :: Char -> String -> [String]
130 split c s = case rest of
131                 []     -> [chunk] 
132                 _:rest -> chunk : split c rest
133   where (chunk, rest) = break (==c) s
134
135 add :: IORef [a] -> a -> IO ()
136 add var x = do
137   xs <- readIORef var
138   writeIORef var (x:xs)
139
140 addNoDups :: Eq a => IORef [a] -> a -> IO ()
141 addNoDups var x = do
142   xs <- readIORef var
143   unless (x `elem` xs) $ writeIORef var (x:xs)
144
145 ------------------------------------------------------
146 --              Filename manipulation
147 ------------------------------------------------------
148                 
149 type Suffix = String
150
151 splitFilename :: String -> (String,Suffix)
152 splitFilename f = split_longest_prefix f (=='.')
153
154 getFileSuffix :: String -> Suffix
155 getFileSuffix f = drop_longest_prefix f (=='.')
156
157 -- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy.ext")
158 splitFilenameDir :: String -> (String,String)
159 splitFilenameDir str
160   = let (dir, rest) = split_longest_prefix str isPathSeparator
161         real_dir | null dir  = "."
162                  | otherwise = dir
163     in  (real_dir, rest)
164
165 -- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy", ".ext")
166 splitFilename3 :: String -> (String,String,Suffix)
167 splitFilename3 str
168    = let (dir, rest) = split_longest_prefix str isPathSeparator
169          (name, ext) = splitFilename rest
170          real_dir | null dir  = "."
171                   | otherwise = dir
172      in  (real_dir, name, ext)
173
174 remove_suffix :: Char -> String -> Suffix
175 remove_suffix c s
176   | null pre  = reverse suf
177   | otherwise = reverse pre
178   where (suf,pre) = break (==c) (reverse s)
179
180 drop_longest_prefix :: String -> (Char -> Bool) -> String
181 drop_longest_prefix s pred = reverse suf
182   where (suf,_pre) = break pred (reverse s)
183
184 take_longest_prefix :: String -> (Char -> Bool) -> String
185 take_longest_prefix s pred = reverse pre
186   where (_suf,pre) = break pred (reverse s)
187
188 -- split a string at the last character where 'pred' is True,
189 -- returning a pair of strings. The first component holds the string
190 -- up (but not including) the last character for which 'pred' returned
191 -- True, the second whatever comes after (but also not including the
192 -- last character).
193 --
194 -- If 'pred' returns False for all characters in the string, the original
195 -- string is returned in the second component (and the first one is just
196 -- empty).
197 split_longest_prefix :: String -> (Char -> Bool) -> (String,String)
198 split_longest_prefix s pred
199   = case pre of
200         []      -> ([], reverse suf)
201         (_:pre) -> (reverse pre, reverse suf)
202   where (suf,pre) = break pred (reverse s)
203
204 replaceFilenameSuffix :: FilePath -> Suffix -> FilePath
205 replaceFilenameSuffix s suf = remove_suffix '.' s ++ suf
206
207 -- directoryOf strips the filename off the input string, returning
208 -- the directory.
209 directoryOf :: FilePath -> String
210 directoryOf = fst . splitFilenameDir
211
212 replaceFilenameDirectory :: FilePath -> String -> FilePath
213 replaceFilenameDirectory s dir
214  = dir ++ '/':drop_longest_prefix s isPathSeparator
215
216 remove_spaces :: String -> String
217 remove_spaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace
218
219 escapeSpaces :: String -> String
220 escapeSpaces = foldr (\c s -> if isSpace c then '\\':c:s else c:s) ""
221
222 isPathSeparator :: Char -> Bool
223 isPathSeparator ch =
224 #ifdef mingw32_TARGET_OS
225   ch == '/' || ch == '\\'
226 #else
227   ch == '/'
228 #endif