Put full ImportDecls in ModSummary instead of just ModuleNames
[ghc-hetmet.git] / compiler / main / HeaderInfo.hs
index 21e6437..9184909 100644 (file)
@@ -1,13 +1,6 @@
-{-# OPTIONS -fno-warn-incomplete-patterns #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and fix
--- any warnings in the module. See
---     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
--- for details
-
 -----------------------------------------------------------------------------
 --
--- Parsing the top of a Haskell source file to get its module name,
+-- | Parsing the top of a Haskell source file to get its module name,
 -- imports and options.
 --
 -- (c) Simon Marlow 2005
@@ -22,6 +15,7 @@ module HeaderInfo ( getImports
 
 #include "HsVersions.h"
 
+import RdrName
 import HscTypes
 import Parser          ( parseHeader )
 import Lexer
@@ -58,7 +52,7 @@ getImports :: GhcMonad m =>
                            --   reporting parse error locations.
            -> FilePath     -- ^ The original source filename (used for locations
                            --   in the function result)
-           -> m ([Located ModuleName], [Located ModuleName], Located ModuleName)
+           -> m ([Located (ImportDecl RdrName)], [Located (ImportDecl RdrName)], Located ModuleName)
               -- ^ The source imports, normal imports, and the module name.
 getImports dflags buf filename source_filename = do
   let loc  = mkSrcLoc (mkFastString filename) 1 0
@@ -75,37 +69,26 @@ getImports dflags buf filename source_filename = do
              let
                 main_loc = mkSrcLoc (mkFastString source_filename) 1 0
                mod = mb_mod `orElse` L (srcLocSpan main_loc) mAIN_NAME
-                imps' = filter isHomeImp (map unLoc imps)
-               (src_idecls, ord_idecls) = partition isSourceIdecl imps'
-               source_imps   = map getImpMod src_idecls
-               ordinary_imps = filter ((/= moduleName gHC_PRIM) . unLoc) 
-                                       (map getImpMod ord_idecls)
+               (src_idecls, ord_idecls) = partition (ideclSource.unLoc) imps
+               ordinary_imps = filter ((/= moduleName gHC_PRIM) . unLoc . ideclName . unLoc) 
+                                       ord_idecls
                     -- GHC.Prim doesn't exist physically, so don't go looking for it.
              in
-             return (source_imps, ordinary_imps, mod)
+             return (src_idecls, ordinary_imps, mod)
   
 parseError :: GhcMonad m => SrcSpan -> Message -> m a
 parseError span err = throwOneError $ mkPlainErrMsg span err
 
--- we aren't interested in package imports here, filter them out
-isHomeImp :: ImportDecl name -> Bool
-isHomeImp (ImportDecl _ (Just p) _ _ _ _) = p == fsLit "this"
-isHomeImp (ImportDecl _ Nothing  _ _ _ _) = True
-
-isSourceIdecl :: ImportDecl name -> Bool
-isSourceIdecl (ImportDecl _ _ s _ _ _) = s
-
-getImpMod :: ImportDecl name -> Located ModuleName
-getImpMod (ImportDecl located_mod _ _ _ _ _) = located_mod
-
 --------------------------------------------------------------
 -- Get options
 --------------------------------------------------------------
 
-
+-- | Parse OPTIONS and LANGUAGE pragmas of the source file.
+--
+-- Throws a 'SourceError' if flag parsing fails (including unsupported flags.)
 getOptionsFromFile :: DynFlags
-                   -> FilePath            -- input file
-                   -> IO [Located String] -- options, if any
+                   -> FilePath            -- ^ Input file
+                   -> IO [Located String] -- ^ Parsed options, if any.
 getOptionsFromFile dflags filename
     = Exception.bracket
              (openBinaryFile filename ReadMode)
@@ -126,7 +109,13 @@ getOptionsFromFile dflags filename
                                              else do opts' <- loop handle newBuf
                                                      return (opts++opts')
 
-getOptions :: DynFlags -> StringBuffer -> FilePath -> [Located String]
+-- | Parse OPTIONS and LANGUAGE pragmas of the source file.
+--
+-- Throws a 'SourceError' if flag parsing fails (including unsupported flags.)
+getOptions :: DynFlags
+           -> StringBuffer -- ^ Input Buffer
+           -> FilePath     -- ^ Source filename.  Used for location info.
+           -> [Located String] -- ^ Parsed options.
 getOptions dflags buf filename
     = case getOptions' dflags buf filename of
         (_,opts) -> opts
@@ -188,8 +177,11 @@ getOptions' dflags buf filename
                   (_,L _loc ITcomma):more -> parseLanguage more
                   (_,L _loc ITclose_prag):more -> parseToks more
                   (_,L loc _):_ -> languagePragParseError loc
+                  [] -> panic "getOptions'.parseLanguage(1) went past eof token"
           parseLanguage (tok:_)
               = languagePragParseError (getLoc tok)
+          parseLanguage []
+              = panic "getOptions'.parseLanguage(2) went past eof token"
           lexToken t = return t
           lexAll state = case unP (lexer lexToken) state of
                            POk _      t@(L _ ITeof) -> [(buffer state,t)]
@@ -197,8 +189,11 @@ getOptions' dflags buf filename
                            _ -> [(buffer state,L (last_loc state) ITeof)]
 
 -----------------------------------------------------------------------------
--- Complain about non-dynamic flags in OPTIONS pragmas
 
+-- | Complain about non-dynamic flags in OPTIONS pragmas.
+--
+-- Throws a 'SourceError' if the input list is non-empty claiming that the
+-- input flags are unknown.
 checkProcessArgsResult :: MonadIO m => [Located String] -> m ()
 checkProcessArgsResult flags
   = when (notNull flags) $