[project @ 2003-03-04 10:39:58 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / DriverUtil.hs
1 -----------------------------------------------------------------------------
2 -- $Id: DriverUtil.hs,v 1.36 2003/03/04 10:39:58 simonmar 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 )
20 import qualified EXCEPTION as Exception
21 import DYNAMIC
22 import DATA_IOREF       ( IORef, readIORef, writeIORef )
23
24 import Directory        ( getDirectoryContents, doesDirectoryExist )
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 <- my_prefix_match "{-#" s, -- -}
55     Just s2 <- my_prefix_match "OPTIONS" (remove_spaces s1),
56     Just s3 <- my_prefix_match "}-#" (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 -- Verify that the 'dirname' portion of a FilePath exists.
74 -- 
75 doesDirNameExist :: FilePath -> IO Bool
76 doesDirNameExist fpath = doesDirectoryExist (directoryOf fpath)
77
78 -----------------------------------------------------------------------------
79 -- Prefixing underscore to linker-level names
80 prefixUnderscore :: String -> String
81 prefixUnderscore
82  | cLeadingUnderscore == "YES" = ('_':)
83  | otherwise                   = id
84
85 -----------------------------------------------------------------------------
86 -- Utils
87
88 unknownFlagErr :: String -> a
89 unknownFlagErr f = throwDyn (UsageError ("unrecognised flag: " ++ f))
90
91 unknownFlagsErr :: [String] -> a
92 unknownFlagsErr fs = throwDyn (UsageError ("unrecognised flags: " ++ unwords fs))
93
94 my_partition :: (a -> Maybe b) -> [a] -> ([(a,b)],[a])
95 my_partition _ [] = ([],[])
96 my_partition p (a:as)
97   = let (bs,cs) = my_partition p as in
98     case p a of
99         Nothing -> (bs,a:cs)
100         Just b  -> ((a,b):bs,cs)
101
102 my_prefix_match :: String -> String -> Maybe String
103 my_prefix_match []    rest = Just rest
104 my_prefix_match (_:_) []   = Nothing
105 my_prefix_match (p:pat) (r:rest)
106   | p == r    = my_prefix_match pat rest
107   | otherwise = Nothing
108
109 later = flip finally
110
111 handleDyn :: Typeable ex => (ex -> IO a) -> IO a -> IO a
112 handleDyn = flip catchDyn
113
114 handle :: (Exception -> IO a) -> IO a -> IO a
115 #if __GLASGOW_HASKELL__ < 501
116 handle = flip Exception.catchAllIO
117 #else
118 handle h f = f `Exception.catch` \e -> case e of
119     ExitException _ -> throw e
120     _               -> h e
121 #endif
122
123 split :: Char -> String -> [String]
124 split c s = case rest of
125                 []     -> [chunk] 
126                 _:rest -> chunk : split c rest
127   where (chunk, rest) = break (==c) s
128
129 add :: IORef [a] -> a -> IO ()
130 add var x = do
131   xs <- readIORef var
132   writeIORef var (x:xs)
133
134 addNoDups :: Eq a => IORef [a] -> a -> IO ()
135 addNoDups var x = do
136   xs <- readIORef var
137   unless (x `elem` xs) $ writeIORef var (x:xs)
138
139 ------------------------------------------------------
140 --              Filename manipulation
141 ------------------------------------------------------
142                 
143 type Suffix = String
144
145 splitFilename :: String -> (String,Suffix)
146 splitFilename f = split_longest_prefix f (=='.')
147
148 getFileSuffix :: String -> Suffix
149 getFileSuffix f = drop_longest_prefix f (=='.')
150
151 -- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy.ext")
152 splitFilenameDir :: String -> (String,String)
153 splitFilenameDir str
154   = let (dir, rest) = split_longest_prefix str isPathSeparator
155         real_dir | null dir  = "."
156                  | otherwise = dir
157     in  (real_dir, rest)
158
159 -- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy", ".ext")
160 splitFilename3 :: String -> (String,String,Suffix)
161 splitFilename3 str
162    = let (dir, rest) = split_longest_prefix str isPathSeparator
163          (name, ext) = splitFilename rest
164          real_dir | null dir  = "."
165                   | otherwise = dir
166      in  (real_dir, name, ext)
167
168 remove_suffix :: Char -> String -> Suffix
169 remove_suffix c s
170   | null pre  = reverse suf
171   | otherwise = reverse pre
172   where (suf,pre) = break (==c) (reverse s)
173
174 drop_longest_prefix :: String -> (Char -> Bool) -> String
175 drop_longest_prefix s pred = reverse suf
176   where (suf,_pre) = break pred (reverse s)
177
178 take_longest_prefix :: String -> (Char -> Bool) -> String
179 take_longest_prefix s pred = reverse pre
180   where (_suf,pre) = break pred (reverse s)
181
182 -- split a string at the last character where 'pred' is True,
183 -- returning a pair of strings. The first component holds the string
184 -- up (but not including) the last character for which 'pred' returned
185 -- True, the second whatever comes after (but also not including the
186 -- last character).
187 --
188 -- If 'pred' returns False for all characters in the string, the original
189 -- string is returned in the second component (and the first one is just
190 -- empty).
191 split_longest_prefix :: String -> (Char -> Bool) -> (String,String)
192 split_longest_prefix s pred
193   = case pre of
194         []      -> ([], reverse suf)
195         (_:pre) -> (reverse pre, reverse suf)
196   where (suf,pre) = break pred (reverse s)
197
198 replaceFilenameSuffix :: FilePath -> Suffix -> FilePath
199 replaceFilenameSuffix s suf = remove_suffix '.' s ++ suf
200
201 -- directoryOf strips the filename off the input string, returning
202 -- the directory.
203 directoryOf :: FilePath -> String
204 directoryOf = fst . splitFilenameDir
205
206 replaceFilenameDirectory :: FilePath -> String -> FilePath
207 replaceFilenameDirectory s dir
208  = dir ++ '/':drop_longest_prefix s isPathSeparator
209
210 remove_spaces :: String -> String
211 remove_spaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace
212
213 escapeSpaces :: String -> String
214 escapeSpaces = foldr (\c s -> if isSpace c then '\\':c:s else c:s) ""
215
216 isPathSeparator :: Char -> Bool
217 isPathSeparator ch =
218 #ifdef mingw32_TARGET_OS
219   ch == '/' || ch == '\\'
220 #else
221   ch == '/'
222 #endif