Enumerate imports and remove dead code.
[ghc-hetmet.git] / ghc / compiler / main / GetImports.hs
index ecb7766..6ccb8be 100644 (file)
 -----------------------------------------------------------------------------
--- $Id: GetImports.hs,v 1.6 2001/05/01 16:01:06 simonmar Exp $
 --
--- GHC Driver program
+-- Parsing the top of a Haskell source file to get its module name
+-- and imports.
 --
--- (c) Simon Marlow 2000
+-- (c) Simon Marlow 2005
 --
 -----------------------------------------------------------------------------
 
 module GetImports ( getImportsFromFile, getImports ) where
 
-import Module
-
+#include "HsVersions.h"
+
+import Parser          ( parseHeader )
+import Lexer           ( P(..), ParseResult(..), mkPState )
+import HsSyn           ( ImportDecl(..), HsModule(..) )
+import Module          ( Module, mkModule )
+import PrelNames        ( gHC_PRIM )
+import StringBuffer    ( StringBuffer, hGetStringBuffer )
+import SrcLoc          ( Located(..), mkSrcLoc, unLoc, noSrcSpan )
+import FastString      ( mkFastString )
+import DynFlags        ( DynFlags )
+import ErrUtils
+import Pretty
+import Panic
+import Bag             ( unitBag )
+
+import EXCEPTION       ( throwDyn )
 import IO
 import List
-import Char
 
 -- getImportsFromFile is careful to close the file afterwards, otherwise
 -- we can end up with a large number of open handles before the garbage
 -- collector gets around to closing them.
-getImportsFromFile :: String -> IO ([ModuleName], [ModuleName], ModuleName)
-getImportsFromFile filename
-  = do  hdl <- openFile filename ReadMode
-        modsrc <- hGetContents hdl
-        let (srcimps,imps,mod_name) = getImports modsrc
-       length srcimps `seq` length imps `seq` return ()
-       hClose hdl
-       return (srcimps,imps,mod_name)
-
-getImports :: String -> ([ModuleName], [ModuleName], ModuleName)
-getImports s
-   = case f [{-accum source imports-}] [{-accum normal imports-}] 
-          Nothing (clean s) of
-        (si, ni, Nothing) -> (si, ni, mkModuleName "Main")
-        (si, ni, Just me) -> (si, ni, me)
-     where
-        -- Only pick up the name following 'module' the first time.
-        -- Otherwise, we would be fooled by 'module Me ( module Wrong )'
-        -- and conclude that the module name is Wrong instead of Me.
-        f si ni old_me  ("eludom" : me : ws) 
-           = case old_me of
-                Nothing -> f si ni (Just (mkMN me)) ws
-                Just _  -> f si ni old_me ws
-
-       f si ni me ("ngierof" : "tropmi" : ws) = f si ni me ws
-        f si ni me ("tropmi" : "#-{" : "ECRUOS" : "}-#" : "deifilauq" : m : ws) 
-           = f ((mkMN m):si) ni me ws
-        f si ni me ("tropmi" : "#-{" : "ECRUOS" : "}-#" : m : ws) 
-           = f ((mkMN m):si) ni me ws
-
-        -- skip other contents of pragma comments
-        f si ni me ("#-{" : ws)
-           = f si ni me (drop 1 (dropWhile (/= "}-#") ws))
-
-        f si ni me ("tropmi" : "deifilauq" : m : ws) 
-           = f si ((mkMN m):ni) me ws
-        f si ni me ("tropmi" : m : ws) 
-           = f si ((mkMN m):ni) me ws
-        f si ni me (w:ws) = f si ni me ws
-        f si ni me [] = (nub si, nub ni, me)
-
-        mkMN str = mkModuleName (takeWhile isModId (reverse str))
-        isModId c = isAlphaNum c || c `elem` "'_"
-
-
--- remove literals and comments from a string, producing a 
--- list of reversed words.
-clean :: String -> [String]
-clean s
-   = keep "" s
-     where
-        -- running through text we want to keep
-        keep acc []                   = cons acc []
-        keep acc (c:cs) | isSpace c   = cons acc (keep "" cs)
-
-        keep acc ('"':cs)             = cons acc (dquote cs)           -- "
-
-       -- don't be fooled by single quotes which are part of an identifier
-       keep acc (c:'\'':cs) 
-           | isAlphaNum c || c == '_' = keep ('\'':c:acc) (c:cs)
-
-        keep acc ('\'':cs)            = cons acc (squote cs)
-        keep acc ('-':'-':cs)         = cons acc (linecomment cs)
-        keep acc ('{':'-':'#':' ':cs) = cons acc (cons "#-{" (keep "" cs))
-        keep acc ('{':'-':cs)         = cons acc (runcomment cs)       -- -}
-        keep acc (c:cs)               = keep (c:acc) cs
-
-        cons [] xs = xs
-        cons x  xs = x : xs
-
-        -- in a double-quoted string
-        dquote []             = []
-        dquote ('\\':'\"':cs) = dquote cs              -- "
-        dquote ('\\':'\\':cs) = dquote cs
-        dquote ('\"':cs)      = keep "" cs             -- "
-        dquote (c:cs)         = dquote cs
-
-        -- in a single-quoted string
-        squote []             = []
-        squote ('\\':'\'':cs) = squote cs
-        squote ('\\':'\\':cs) = squote cs
-        squote ('\'':cs)      = keep "" cs
-        squote (c:cs)         = squote cs
-
-        -- in a line comment
-        linecomment []        = []
-        linecomment ('\n':cs) = keep "" cs
-        linecomment (c:cs)    = linecomment cs
-
-        -- in a running comment
-        runcomment []           = []
-        runcomment ('-':'}':cs) = keep "" cs
-        runcomment (c:cs)       = runcomment cs
+getImportsFromFile :: DynFlags -> FilePath
+   -> IO ([Located Module], [Located Module], Located Module)
+getImportsFromFile dflags filename = do
+  buf <- hGetStringBuffer filename
+  getImports dflags buf filename
+
+getImports :: DynFlags -> StringBuffer -> FilePath
+    -> IO ([Located Module], [Located Module], Located Module)
+getImports dflags buf filename = do
+  let loc  = mkSrcLoc (mkFastString filename) 1 0
+  case unP parseHeader (mkPState buf loc dflags) of
+       PFailed span err -> parseError span err
+       POk _ rdr_module -> 
+         case rdr_module of
+           L _ (HsModule mod _ imps _ _) ->
+             let
+               mod_name | Just located_mod <- mod = located_mod
+                        | otherwise               = L noSrcSpan (mkModule "Main")
+               (src_idecls, ord_idecls) = partition isSourceIdecl (map unLoc imps)
+               source_imps   = map getImpMod src_idecls        
+               ordinary_imps = filter ((/= gHC_PRIM) . unLoc) 
+                                       (map getImpMod ord_idecls)
+                    -- GHC.Prim doesn't exist physically, so don't go looking for it.
+             in
+             return (source_imps, ordinary_imps, mod_name)
+  
+parseError span err = throwDyn $ mkPlainErrMsg span err
+
+isSourceIdecl (ImportDecl _ s _ _ _) = s
+
+getImpMod (ImportDecl located_mod _ _ _ _) = located_mod