summaryrefslogtreecommitdiff
path: root/ghc/compiler/compMan/CompManager.lhs
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/compiler/compMan/CompManager.lhs')
-rw-r--r--ghc/compiler/compMan/CompManager.lhs25
1 files changed, 12 insertions, 13 deletions
diff --git a/ghc/compiler/compMan/CompManager.lhs b/ghc/compiler/compMan/CompManager.lhs
index 28630ecf35..bf8d0cf137 100644
--- a/ghc/compiler/compMan/CompManager.lhs
+++ b/ghc/compiler/compMan/CompManager.lhs
@@ -149,7 +149,7 @@ cmSetContext cmstate str
Nothing -> do
mod <- moduleNameToModule mn
if isHomeModule mod
- then throwDyn (OtherError (showSDoc
+ then throwDyn (UserError (showSDoc
(quotes (ppr (moduleName mod))
<+> text "is not currently loaded")))
else return mod
@@ -163,7 +163,7 @@ moduleNameToModule :: ModuleName -> IO Module
moduleNameToModule mn
= do maybe_stuff <- findModule mn
case maybe_stuff of
- Nothing -> throwDyn (OtherError ("can't find module `"
+ Nothing -> throwDyn (UserError ("can't find module `"
++ moduleNameUserString mn ++ "'"))
Just (m,_) -> return m
@@ -955,7 +955,7 @@ downsweep rootNm old_summaries
| haskellish_file file
= do exists <- doesFileExist file
if exists then summariseFile file else do
- throwDyn (OtherError ("can't find file `" ++ file ++ "'"))
+ throwDyn (UserError ("can't find file `" ++ file ++ "'"))
| otherwise
= do exists <- doesFileExist hs_file
if exists then summariseFile hs_file else do
@@ -978,7 +978,7 @@ downsweep rootNm old_summaries
let old_summary = findModInSummaries old_summaries mod
summarise mod location old_summary
- Nothing -> throwDyn (OtherError
+ Nothing -> throwDyn (UserError
("can't find module `"
++ showSDoc (ppr nm) ++ "'"))
@@ -1055,10 +1055,10 @@ summarise mod location old_summary
let (srcimps,imps,mod_name) = getImports modsrc
when (mod_name /= moduleName mod) $
- throwDyn (OtherError
- (showSDoc (text "file name does not match module name: "
- <+> ppr (moduleName mod) <+> text "vs"
- <+> ppr mod_name)))
+ throwDyn (UserError
+ (showSDoc (text modsrc
+ <> text ": file name does not match module name"
+ <+> quotes (ppr (moduleName mod)))))
return (Just (ModSummary mod location{ml_hspp_file=Just hspp_fn}
srcimps imps src_timestamp))
@@ -1067,11 +1067,10 @@ summarise mod location old_summary
| otherwise = return Nothing
noHsFileErr mod
- = throwDyn (OtherError (showSDoc (text "no source file for module"
- <+> quotes (ppr mod))))
+ = panic (showSDoc (text "no source file for module" <+> quotes (ppr mod)))
packageModErr mod
- = throwDyn (OtherError (showSDoc (text "module" <+>
- quotes (ppr mod) <+>
- text "is a package module")))
+ = throwDyn (UserError (showSDoc (text "module" <+>
+ quotes (ppr mod) <+>
+ text "is a package module")))
\end{code}