[project @ 2003-08-20 15:07:56 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / DriverUtil.hs
1 -----------------------------------------------------------------------------
2 -- $Id: DriverUtil.hs,v 1.39 2003/08/20 15:07:57 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, 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 my_partition :: (a -> Maybe b) -> [a] -> ([(a,b)],[a])
105 my_partition _ [] = ([],[])
106 my_partition p (a:as)
107   = let (bs,cs) = my_partition p as in
108     case p a of
109         Nothing -> (bs,a:cs)
110         Just b  -> ((a,b):bs,cs)
111
112 later = flip finally
113
114 handleDyn :: Typeable ex => (ex -> IO a) -> IO a -> IO a
115 handleDyn = flip catchDyn
116
117 handle :: (Exception -> IO a) -> IO a -> IO a
118 #if __GLASGOW_HASKELL__ < 501
119 handle = flip Exception.catchAllIO
120 #else
121 handle h f = f `Exception.catch` \e -> case e of
122     ExitException _ -> throw e
123     _               -> h e
124 #endif
125
126 split :: Char -> String -> [String]
127 split c s = case rest of
128                 []     -> [chunk] 
129                 _:rest -> chunk : split c rest
130   where (chunk, rest) = break (==c) s
131
132 add :: IORef [a] -> a -> IO ()
133 add var x = do
134   xs <- readIORef var
135   writeIORef var (x:xs)
136
137 addNoDups :: Eq a => IORef [a] -> a -> IO ()
138 addNoDups var x = do
139   xs <- readIORef var
140   unless (x `elem` xs) $ writeIORef var (x:xs)
141
142 ------------------------------------------------------
143 --              Filename manipulation
144 ------------------------------------------------------
145                 
146 type Suffix = String
147
148 splitFilename :: String -> (String,Suffix)
149 splitFilename f = split_longest_prefix f (=='.')
150
151 getFileSuffix :: String -> Suffix
152 getFileSuffix f = drop_longest_prefix f (=='.')
153
154 -- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy.ext")
155 splitFilenameDir :: String -> (String,String)
156 splitFilenameDir str
157   = let (dir, rest) = split_longest_prefix str isPathSeparator
158         real_dir | null dir  = "."
159                  | otherwise = dir
160     in  (real_dir, rest)
161
162 -- "foo/bar/xyzzy.ext" -> ("foo/bar", "xyzzy", ".ext")
163 splitFilename3 :: String -> (String,String,Suffix)
164 splitFilename3 str
165    = let (dir, rest) = split_longest_prefix str isPathSeparator
166          (name, ext) = splitFilename rest
167          real_dir | null dir  = "."
168                   | otherwise = dir
169      in  (real_dir, name, ext)
170
171 remove_suffix :: Char -> String -> Suffix
172 remove_suffix c s
173   | null pre  = reverse suf
174   | otherwise = reverse pre
175   where (suf,pre) = break (==c) (reverse s)
176
177 drop_longest_prefix :: String -> (Char -> Bool) -> String
178 drop_longest_prefix s pred = reverse suf
179   where (suf,_pre) = break pred (reverse s)
180
181 take_longest_prefix :: String -> (Char -> Bool) -> String
182 take_longest_prefix s pred = reverse pre
183   where (_suf,pre) = break pred (reverse s)
184
185 -- split a string at the last character where 'pred' is True,
186 -- returning a pair of strings. The first component holds the string
187 -- up (but not including) the last character for which 'pred' returned
188 -- True, the second whatever comes after (but also not including the
189 -- last character).
190 --
191 -- If 'pred' returns False for all characters in the string, the original
192 -- string is returned in the second component (and the first one is just
193 -- empty).
194 split_longest_prefix :: String -> (Char -> Bool) -> (String,String)
195 split_longest_prefix s pred
196   = case pre of
197         []      -> ([], reverse suf)
198         (_:pre) -> (reverse pre, reverse suf)
199   where (suf,pre) = break pred (reverse s)
200
201 replaceFilenameSuffix :: FilePath -> Suffix -> FilePath
202 replaceFilenameSuffix s suf = remove_suffix '.' s ++ suf
203
204 -- directoryOf strips the filename off the input string, returning
205 -- the directory.
206 directoryOf :: FilePath -> String
207 directoryOf = fst . splitFilenameDir
208
209 replaceFilenameDirectory :: FilePath -> String -> FilePath
210 replaceFilenameDirectory s dir
211  = dir ++ '/':drop_longest_prefix s isPathSeparator
212
213 remove_spaces :: String -> String
214 remove_spaces = reverse . dropWhile isSpace . reverse . dropWhile isSpace
215
216 escapeSpaces :: String -> String
217 escapeSpaces = foldr (\c s -> if isSpace c then '\\':c:s else c:s) ""
218
219 isPathSeparator :: Char -> Bool
220 isPathSeparator ch =
221 #ifdef mingw32_TARGET_OS
222   ch == '/' || ch == '\\'
223 #else
224   ch == '/'
225 #endif