Add (a) CoreM monad, (b) new Annotations feature
[ghc-hetmet.git] / compiler / main / GHC.hs
index b023885..e8ea87c 100644 (file)
@@ -53,6 +53,7 @@ module GHC (
         parsedSource, coreModule,
         compileToCoreModule, compileToCoreSimplified,
         compileCoreToObj,
+        getModSummary,
 
        -- * Parsing Haddock comments
        parseHaddockComment,
@@ -73,6 +74,7 @@ module GHC (
        modInfoIsExportedName,
        modInfoLookupName,
        lookupGlobalName,
+       findGlobalAnns,
         mkPrintUnqualifiedForModule,
 
        -- * Printing
@@ -195,6 +197,20 @@ module GHC (
         srcSpanStartLine, srcSpanEndLine, 
         srcSpanStartCol, srcSpanEndCol,
 
+        -- ** Located
+       Located(..),
+
+       -- *** Constructing Located
+       noLoc, mkGeneralLocated,
+
+       -- *** Deconstructing Located
+       getLoc, unLoc,
+
+       -- *** Combining and comparing Located values
+       eqLocated, cmpLocated, combineLocs, addCLoc,
+        leftmost_smallest, leftmost_largest, rightmost,
+        spans, isSubspanOf,
+
        -- * Exceptions
        GhcException(..), showGhcException,
 
@@ -263,6 +279,7 @@ import StaticFlagParser
 import qualified StaticFlags
 import SysTools     ( initSysTools, cleanTempFiles, cleanTempFilesExcept,
                       cleanTempDirs )
+import Annotations
 import Module
 import LazyUniqFM
 import UniqSet
@@ -289,6 +306,8 @@ import System.Directory ( getModificationTime, doesFileExist,
 import Data.Maybe
 import Data.List
 import qualified Data.List as List
+import Data.Typeable    ( Typeable )
+import Data.Word        ( Word8 )
 import Control.Monad
 import System.Exit     ( exitWith, ExitCode(..) )
 import System.Time     ( ClockTime, getClockTime )
@@ -297,9 +316,6 @@ import Data.IORef
 import System.FilePath
 import System.IO
 import System.IO.Error ( try, isDoesNotExistError )
-#if __GLASGOW_HASKELL__ >= 609
-import Data.Typeable (cast)
-#endif
 import Prelude hiding (init)
 
 
@@ -313,45 +329,22 @@ import Prelude hiding (init)
 defaultErrorHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m a
 defaultErrorHandler dflags inner =
   -- top-level exception handler: any unrecognised exception is a compiler bug.
-#if __GLASGOW_HASKELL__ < 609
   ghandle (\exception -> liftIO $ do
            hFlush stdout
-           case exception of
-                -- an IO exception probably isn't our fault, so don't panic
-                IOException _ ->
-                  fatalErrorMsg dflags (text (show exception))
-                AsyncException StackOverflow ->
-                  fatalErrorMsg dflags (text "stack overflow: use +RTS -K<size> to increase it")
-                ExitException _ -> throw exception
-                _ ->
-                  fatalErrorMsg dflags (text (show (Panic (show exception))))
-           exitWith (ExitFailure 1)
-         ) $
-#else
-  ghandle (\(SomeException exception) -> liftIO $ do
-           hFlush stdout
-           case cast exception of
+           case fromException exception of
                 -- an IO exception probably isn't our fault, so don't panic
                 Just (ioe :: IOException) ->
                   fatalErrorMsg dflags (text (show ioe))
-                _ -> case cast exception of
+                _ -> case fromException exception of
                      Just StackOverflow ->
                          fatalErrorMsg dflags (text "stack overflow: use +RTS -K<size> to increase it")
-                     _ -> case cast exception of
+                     _ -> case fromException exception of
                           Just (ex :: ExitCode) -> throw ex
                           _ ->
                               fatalErrorMsg dflags
                                   (text (show (Panic (show exception))))
            exitWith (ExitFailure 1)
          ) $
-#endif
-
-  -- program errors: messages with locations attached.  Sometimes it is
-  -- convenient to just throw these as exceptions.
-  handleErrMsg
-            (\em -> liftIO $ do
-                      printBagOfErrors dflags (unitBag em)
-                      exitWith (ExitFailure 1)) $
 
   -- error messages propagated as exceptions
   handleGhcException
@@ -1013,19 +1006,27 @@ type TypecheckedSource = LHsBinds Id
 --     - default methods are turned into top-level decls.
 --     - dictionary bindings
 
+-- | Return the 'ModSummary' of a module with the given name.
+--
+-- The module must be part of the module graph (see 'hsc_mod_graph' and
+-- 'ModuleGraph').  If this is not the case, this function will throw a
+-- 'GhcApiError'.
+--
+-- This function ignores boot modules and requires that there is only one
+-- non-boot module with the given name.
 getModSummary :: GhcMonad m => ModuleName -> m ModSummary
 getModSummary mod = do
    mg <- liftM hsc_mod_graph getSession
-   case [ ms | ms <- mg, ms_mod_name ms == mod ] of
+   case [ ms | ms <- mg, ms_mod_name ms == mod, not (isBootSummary ms) ] of
      [] -> throw $ mkApiErr (text "Module not part of module graph")
-     (ms:_) -> return ms
+     [ms] -> return ms
+     multiple -> throw $ mkApiErr (text "getModSummary is ambiguous: " <+> ppr multiple)
 
 -- | Parse a module.
 --
 -- Throws a 'SourceError' on parse error.
-parseModule :: GhcMonad m => ModuleName -> m ParsedModule
-parseModule mod = do
-   ms <- getModSummary mod
+parseModule :: GhcMonad m => ModSummary -> m ParsedModule
+parseModule ms = do
    hsc_env0 <- getSession
    let hsc_env = hsc_env0 { hsc_dflags = ms_hspp_opts ms }
    rdr_module <- parseFile hsc_env ms
@@ -1176,6 +1177,7 @@ mkModGuts coreModule = ModGuts {
   mg_binds = cm_binds coreModule,
   mg_foreign = NoStubs,
   mg_warns = NoWarnings,
+  mg_anns = [],
   mg_hpc_info = emptyHpcInfo False,
   mg_modBreaks = emptyModBreaks,
   mg_vect_info = noVectInfo,
@@ -1195,9 +1197,8 @@ compileCore simplify fn = do
      Just modSummary -> do
        -- Now we have the module name;
        -- parse, typecheck and desugar the module
-       let mod = ms_mod_name modSummary
        mod_guts <- coreModule `fmap`
-                      (desugarModule =<< typecheckModule =<< parseModule mod)
+                      (desugarModule =<< typecheckModule =<< parseModule modSummary)
        liftM gutsToCoreModule $
          if simplify
           then do
@@ -1707,11 +1708,12 @@ reachableBackwards mod summaries
 type SummaryNode = (ModSummary, Int, [Int])
 
 topSortModuleGraph
-         :: Bool               -- Drop hi-boot nodes? (see below)
+         :: Bool
+          -- ^ Drop hi-boot nodes? (see below)
          -> [ModSummary]
          -> Maybe ModuleName
          -> [SCC ModSummary]
--- Calculate SCCs of the module graph, possibly dropping the hi-boot nodes
+-- ^ Calculate SCCs of the module graph, possibly dropping the hi-boot nodes
 -- The resulting list of strongly-connected-components is in topologically
 -- sorted order, starting with the module(s) at the bottom of the
 -- dependency graph (ie compile them first) and ending with the ones at
@@ -1719,10 +1721,10 @@ topSortModuleGraph
 --
 -- Drop hi-boot nodes (first boolean arg)? 
 --
---   False:    treat the hi-boot summaries as nodes of the graph,
+-- - @False@:  treat the hi-boot summaries as nodes of the graph,
 --             so the graph must be acyclic
 --
---   True:     eliminate the hi-boot nodes, and instead pretend
+-- - @True@:   eliminate the hi-boot nodes, and instead pretend
 --             the a source-import of Foo is an import of Foo
 --             The resulting graph has no hi-boot nodes, but can be cyclic
 
@@ -1875,7 +1877,7 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
                if exists 
                    then summariseFile hsc_env old_summaries file mb_phase 
                                        obj_allowed maybe_buf
-                   else throwErrMsg $ mkPlainErrMsg noSrcSpan $
+                   else throwOneError $ mkPlainErrMsg noSrcSpan $
                           text "can't find file:" <+> text file
        getRootSummary (Target (TargetModule modl) obj_allowed maybe_buf)
           = do maybe_summary <- summariseModule hsc_env old_summary_map False 
@@ -2139,7 +2141,7 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
         (srcimps, the_imps, L mod_loc mod_name) <- liftIO $ getImports dflags' buf hspp_fn src_fn
 
        when (mod_name /= wanted_mod) $
-               throwErrMsg $ mkPlainErrMsg mod_loc $ 
+               throwOneError $ mkPlainErrMsg mod_loc $ 
                              text "File name does not match module name:" 
                              $$ text "Saw:" <+> quotes (ppr mod_name)
                               $$ text "Expected:" <+> quotes (ppr wanted_mod)
@@ -2215,21 +2217,21 @@ preprocessFile hsc_env src_fn mb_phase (Just (buf, _time))
 noModError :: DynFlags -> SrcSpan -> ModuleName -> FindResult -> IO ab
 -- ToDo: we don't have a proper line number for this error
 noModError dflags loc wanted_mod err
-  = throwErrMsg $ mkPlainErrMsg loc $ cannotFindModule dflags wanted_mod err
+  = throwOneError $ mkPlainErrMsg loc $ cannotFindModule dflags wanted_mod err
                                
-noHsFileErr :: SrcSpan -> String -> a
+noHsFileErr :: GhcMonad m => SrcSpan -> String -> m a
 noHsFileErr loc path
-  = throwErrMsg $ mkPlainErrMsg loc $ text "Can't find" <+> text path
+  = throwOneError $ mkPlainErrMsg loc $ text "Can't find" <+> text path
  
-packageModErr :: ModuleName -> a
+packageModErr :: GhcMonad m => ModuleName -> m a
 packageModErr mod
-  = throwErrMsg $ mkPlainErrMsg noSrcSpan $
+  = throwOneError $ mkPlainErrMsg noSrcSpan $
        text "module" <+> quotes (ppr mod) <+> text "is a package module"
 
 multiRootsErr :: [ModSummary] -> IO ()
 multiRootsErr [] = panic "multiRootsErr"
 multiRootsErr summs@(summ1:_)
-  = throwErrMsg $ mkPlainErrMsg noSrcSpan $
+  = throwOneError $ mkPlainErrMsg noSrcSpan $
        text "module" <+> quotes (ppr mod) <+> 
        text "is defined in multiple files:" <+>
        sep (map text files)
@@ -2415,6 +2417,11 @@ lookupGlobalName name = withSession $ \hsc_env -> do
    return $! lookupType (hsc_dflags hsc_env) 
                        (hsc_HPT hsc_env) (eps_PTE eps) name
 
+findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]
+findGlobalAnns deserialize target = withSession $ \hsc_env -> do
+    ann_env <- liftIO $ prepareAnnotations hsc_env Nothing
+    return (findAnns deserialize ann_env target)
+
 #ifdef GHCI
 -- | get the GlobalRdrEnv for a session
 getGRE :: GhcMonad m => m GlobalRdrEnv