eef2899e5083d4a41294714c3ad46691593a8ddb
[ghc-hetmet.git] / utils / ext-core / Dependencies.hs
1 {-# OPTIONS -Wall #-}
2 module Dependencies(getDependencies) where
3
4 import Core
5 import Encoding
6 import ParsecParser
7
8 import Control.Monad.State
9 import Data.Generics
10 import Data.List
11 import qualified Data.Map as M
12 import Data.Maybe
13 import System.Directory
14 import System.FilePath
15 import System.IO
16
17 type DepM a = StateT (FilePath, -- "main" module file path
18                  -- maps module names onto dependencies
19                  M.Map (Either AnMname FilePath) [AnMname],
20                  -- module cache
21                  M.Map (Either AnMname FilePath) (FilePath, Module)) IO a
22
23 -- Given a module, return all the modules it
24 -- depends on (directly or indirectly).
25 getDependencies :: [FilePath] -> IO [(FilePath, Module)]
26 getDependencies ms =
27   evalStateT (do
28     (mapM_ (\ f -> do
29               liftIO $ putStrLn $ "==== Finding deps for " ++ show f ++ "====="
30               -- Every module depends on itself anyway,
31               -- so we ignore the FilePath deps.
32               ds <- go getDeps lefts (map Left) (map Right ms)
33               return (f, ds)) ms)
34     (_,t,c) <- get
35     let modNames = nub $ concat (snd (unzip (leftsPairs (M.toList t))))
36                        
37     res1 <- (liftM catMaybes) $ mapM findModuleP (map Left modNames)
38     return $ res1 `unionByFirst`
39                (snd (unzip (M.toList c))))
40    (last ms, M.empty, M.empty)
41       where unionByFirst = unionBy (\ (f,_) (g,_) -> f == g)
42
43 go :: (Show a, Show b, Eq b, MonadIO m) =>
44   (a -> m [b]) -> ([a] -> [b]) -> ([b] -> [a]) -> [a] -> m [b]
45 go getMore p fixUp start = do
46   next <- concatMapM getMore start
47   let more = nub $ (p start) ++ next
48   if (length start == length more)
49     then return more
50     else go getMore p fixUp (fixUp more)
51
52 varRef :: Exp -> [AnMname]
53 varRef (Var v) | Just m' <- getModule v = [m']
54 varRef (Dcon dc) | Just m' <- getModule dc = [m']
55 varRef _ = []
56
57 tyRef :: Ty -> [AnMname]
58 tyRef (Tcon tc) | Just m' <- getModule tc = [m']
59 tyRef  _ = []
60
61
62 getDeps :: Either AnMname FilePath -> DepM [AnMname]
63 getDeps mn = do
64           (_,t,_) <- get
65           case M.lookup mn t of
66             Just ds -> return ds
67             Nothing -> do
68               maybeM <- findModule mn
69               case maybeM of
70                 Nothing -> return []
71                 Just m@(Module mname _ _) -> do
72                   let ds = (everything union ([] `mkQ` varRef) m)
73                             `union` (everything union ([] `mkQ` tyRef) m) in do
74                   liftIO $ putStrLn (show mn ++ " : " ++ show ds)
75                   (a1,t1,b1) <- get
76                   -- in case we were given a filepath, register the
77                   -- module name too
78                   put (a1, M.insert mn ds (M.insert (Left mname) ds t1), b1)
79                   return ds
80
81 findModule :: Either AnMname FilePath -> DepM (Maybe Module)
82 findModule x = do
83  maybeRes <- findModuleP x
84  case maybeRes of
85    Just (_,m) -> return $ Just m
86    _          -> return Nothing
87
88 findModuleP :: Either AnMname FilePath -> DepM (Maybe (FilePath, Module))
89 findModuleP (Left mn) | mn == wrapperMainMname || mn == mainMname = do
90   (f,_,_) <- get
91   findModuleP (Right f)
92 findModuleP (Left mn) | mn == primMname = return Nothing
93   -- Nothing means that this module is valid; it just doesn't have
94   -- an implementation
95 findModuleP m = tryFindModule m
96
97 tryFindModule :: Either AnMname FilePath -> DepM (Maybe (FilePath, Module))
98 tryFindModule k = do
99   (_,_,mCache) <- get
100   liftM Just $ case M.lookup k mCache of
101     Just p -> return p
102     Nothing -> findModuleNotCached k
103
104 findModuleNotCached :: Either AnMname FilePath -> DepM (FilePath, Module)
105 findModuleNotCached (Left m@(M (P pkgName, encHier, encLeafName))) = do
106       let hier = map zDecodeString encHier
107           leafName = zDecodeString encLeafName
108           possibleFiles = (map (dirs hier leafName) searchPath)
109                      ++ map (dirs (zDecodeString pkgName:hier) leafName) searchPath in do
110       match <- liftIO $ findM doesFileExist possibleFiles
111       case match of
112          Just fp -> findModule' fp
113          Nothing -> error ("findModule: failed to find dependency " ++ show m
114                       ++ " tried " ++ show possibleFiles)
115 findModuleNotCached (Right fp) = findModule' fp
116
117 dirs :: [String] -> String -> FilePath -> FilePath
118 dirs modulePath leafName dir = dir </> 
119                  (foldr (</>) (addExtension leafName "hcr") modulePath)
120
121 findModule' :: FilePath -> DepM (FilePath, Module)
122 findModule' fp = do
123           res <- liftIO $ parseCore fp
124           case res of
125             Left _   -> error ("findModule: error parsing dependency " ++ fp)
126             Right parsedMod@(Module mn _ _) -> do
127                 cacheModule mn fp parsedMod
128                 return (fp, parsedMod)
129
130 cacheModule :: AnMname -> FilePath -> Module -> DepM ()
131 cacheModule mn fp m = modify (\ (a, b, cache) ->
132                            (a, b, M.insert (Left mn) (fp, m)
133                                     (M.insert (Right fp) (fp, m)
134                                     cache)))
135
136 searchPath :: [FilePath]
137 searchPath = overriddenDir:["../../libraries/",
138              -- kludgy: we wouldn't need these if we parsed the
139              -- package.conf file, but for now, we are too lazy
140               "../../libraries/integer-gmp/",
141               "../../libraries/array/"]
142
143 overriddenDir :: FilePath
144 overriddenDir = "./lib/"
145
146 findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)
147 findM p = liftM listToMaybe . filterM p
148
149 concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
150 concatMapM f = (liftM concat) . (mapM f)
151
152 lefts :: [Either a b] -> [a]
153 lefts = foldr lefts' []
154   where lefts' (Left a) xs = a:xs
155         lefts' _        xs = xs
156
157 leftsPairs :: [(Either a b, c)] -> [(a, c)]
158 leftsPairs = foldr leftsPairs' []
159   where leftsPairs' ((Left x), y) xs = (x, y):xs
160         leftsPairs' _             xs = xs
161
162 {-
163 rightsPairs :: [(Either a b, c)] -> [(b, c)]
164 rightsPairs = foldr rightsPairs' []
165   where rightsPairs' ((Right x), y) xs = (x, y):xs
166         rightsPairs' _             xs = xs
167 -}