summaryrefslogtreecommitdiff
path: root/compiler/main
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/main')
-rw-r--r--compiler/main/HeaderInfo.hs3
-rw-r--r--compiler/main/HscMain.hs5
-rw-r--r--compiler/main/HscStats.hs11
-rw-r--r--compiler/main/InteractiveEval.hs4
4 files changed, 14 insertions, 9 deletions
diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs
index 3158335435..76f67b25db 100644
--- a/compiler/main/HeaderInfo.hs
+++ b/compiler/main/HeaderInfo.hs
@@ -122,7 +122,8 @@ mkPrelImports this_mod loc implicit_prelude import_decls
preludeImportDecl :: LImportDecl GhcPs
preludeImportDecl
- = L loc $ ImportDecl { ideclSourceSrc = NoSourceText,
+ = L loc $ ImportDecl { ideclExt = noExt,
+ ideclSourceSrc = NoSourceText,
ideclName = L loc pRELUDE_NAME,
ideclPkgQual = Nothing,
ideclSource = False,
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index b55267d5e3..223886a1fc 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -909,10 +909,11 @@ hscCheckSafeImports tcg_env = do
-> return tcg_env'
warns dflags rules = listToBag $ map (warnRules dflags) rules
- warnRules dflags (L loc (HsRule n _ _ _ _ _ _)) =
+ warnRules dflags (L loc (HsRule _ n _ _ _ _)) =
mkPlainWarnMsg dflags loc $
text "Rule \"" <> ftext (snd $ unLoc n) <> text "\" ignored" $+$
text "User defined rules are disabled under Safe Haskell"
+ warnRules _ (L _ (XRuleDecl _)) = panic "hscCheckSafeImports"
-- | Validate that safe imported modules are actually safe. For modules in the
-- HomePackage (the package the module we are compiling in resides) this just
@@ -1715,7 +1716,7 @@ hscParseExpr expr = do
hsc_env <- getHscEnv
maybe_stmt <- hscParseStmt expr
case maybe_stmt of
- Just (L _ (BodyStmt expr _ _ _)) -> return expr
+ Just (L _ (BodyStmt _ expr _ _)) -> return expr
_ -> throwErrors $ unitBag $ mkPlainErrMsg (hsc_dflags hsc_env) noSrcSpan
(text "not an expression:" <+> quotes (text expr))
diff --git a/compiler/main/HscStats.hs b/compiler/main/HscStats.hs
index 23e5c9289a..ce59ca1877 100644
--- a/compiler/main/HscStats.hs
+++ b/compiler/main/HscStats.hs
@@ -70,18 +70,18 @@ ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _))
trim ls = takeWhile (not.isSpace) (dropWhile isSpace ls)
(fixity_sigs, bind_tys, bind_specs, bind_inlines, generic_sigs)
- = count_sigs [d | SigD d <- decls]
+ = count_sigs [d | SigD _ d <- decls]
-- NB: this omits fixity decls on local bindings and
-- in class decls. ToDo
- tycl_decls = [d | TyClD d <- decls]
+ tycl_decls = [d | TyClD _ d <- decls]
(class_ds, type_ds, data_ds, newt_ds, type_fam_ds) =
countTyClDecls tycl_decls
- inst_decls = [d | InstD d <- decls]
+ inst_decls = [d | InstD _ d <- decls]
inst_ds = length inst_decls
default_ds = count (\ x -> case x of { DefD{} -> True; _ -> False}) decls
- val_decls = [d | ValD d <- decls]
+ val_decls = [d | ValD _ d <- decls]
real_exports = case exports of { Nothing -> []; Just (L _ es) -> es }
n_exports = length real_exports
@@ -120,6 +120,7 @@ ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _))
import_info (L _ (ImportDecl { ideclSafe = safe, ideclQualified = qual
, ideclAs = as, ideclHiding = spec }))
= add7 (1, safe_info safe, qual_info qual, as_info as, 0,0,0) (spec_info spec)
+ import_info (L _ (XImportDecl _)) = panic "import_info"
safe_info = qual_info
qual_info False = 0
qual_info True = 1
@@ -155,6 +156,8 @@ ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _))
ss, is, length ats, length adts)
where
methods = map unLoc $ bagToList inst_meths
+ inst_info (ClsInstD _ (XClsInstDecl _)) = panic "inst_info"
+ inst_info (XInstDecl _) = panic "inst_info"
-- TODO: use Sum monoid
addpr :: (Int,Int,Int) -> Int
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index db6f7f86ac..163bb8de3f 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -810,7 +810,7 @@ isDecl dflags stmt = do
case parseThing Parser.parseDeclaration dflags stmt of
Lexer.POk _ thing ->
case unLoc thing of
- SpliceD _ -> False
+ SpliceD _ _ -> False
_ -> True
Lexer.PFailed _ _ _ -> False
@@ -870,7 +870,7 @@ compileParsedExprRemote expr@(L loc _) = withSession $ \hsc_env -> do
-- create a new binding.
let expr_fs = fsLit "_compileParsedExpr"
expr_name = mkInternalName (getUnique expr_fs) (mkTyVarOccFS expr_fs) loc
- let_stmt = L loc . LetStmt . L loc . (HsValBinds noExt) $
+ let_stmt = L loc . LetStmt noExt . L loc . (HsValBinds noExt) $
ValBinds noExt
(unitBag $ mkHsVarBind loc (getRdrName expr_name) expr) []