summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
authorLemmih <lemmih@gmail.com>2006-03-04 16:53:03 +0000
committerLemmih <lemmih@gmail.com>2006-03-04 16:53:03 +0000
commitf1fdf769b432ca383b2033f5c973494905d225d1 (patch)
treefe8362f404003dd3b896625f12068e43b2cddb1e /ghc/compiler
parent3c96346b3685f83885cea7906b0dbc536d7695f6 (diff)
downloadhaskell-f1fdf769b432ca383b2033f5c973494905d225d1.tar.gz
Why name a function 'getGhciMode' when it returns GhcMode?
I've changed the name to 'getGhcMode'. If someone changes it back, please write an explanation above it.
Diffstat (limited to 'ghc/compiler')
-rw-r--r--ghc/compiler/iface/MkIface.lhs4
-rw-r--r--ghc/compiler/iface/TcIface.lhs2
-rw-r--r--ghc/compiler/rename/RnNames.lhs4
-rw-r--r--ghc/compiler/typecheck/TcRnDriver.lhs8
-rw-r--r--ghc/compiler/typecheck/TcRnMonad.lhs4
5 files changed, 11 insertions, 11 deletions
diff --git a/ghc/compiler/iface/MkIface.lhs b/ghc/compiler/iface/MkIface.lhs
index f76ac41773..638e2687dd 100644
--- a/ghc/compiler/iface/MkIface.lhs
+++ b/ghc/compiler/iface/MkIface.lhs
@@ -782,8 +782,8 @@ check_old_iface mod_summary source_unchanged maybe_iface
-- If the source has changed and we're in interactive mode, avoid reading
-- an interface; just return the one we might have been supplied with.
- getGhciMode `thenM` \ ghci_mode ->
- if (ghci_mode == Interactive || ghci_mode == JustTypecheck)
+ getGhcMode `thenM` \ ghc_mode ->
+ if (ghc_mode == Interactive || ghc_mode == JustTypecheck)
&& not source_unchanged then
returnM (outOfDate, maybe_iface)
else
diff --git a/ghc/compiler/iface/TcIface.lhs b/ghc/compiler/iface/TcIface.lhs
index e2a71cedf1..b902c8c5fe 100644
--- a/ghc/compiler/iface/TcIface.lhs
+++ b/ghc/compiler/iface/TcIface.lhs
@@ -232,7 +232,7 @@ tcHiBootIface :: Module -> TcRn ModDetails
tcHiBootIface mod
= do { traceIf (text "loadHiBootInterface" <+> ppr mod)
- ; mode <- getGhciMode
+ ; mode <- getGhcMode
; if not (isOneShot mode)
-- In --make and interactive mode, if this module has an hs-boot file
-- we'll have compiled it already, and it'll be in the HPT
diff --git a/ghc/compiler/rename/RnNames.lhs b/ghc/compiler/rename/RnNames.lhs
index 7ae3cc60d1..fc018e76ca 100644
--- a/ghc/compiler/rename/RnNames.lhs
+++ b/ghc/compiler/rename/RnNames.lhs
@@ -604,11 +604,11 @@ mkExportNameSet explicit_mod exports
-- written "module Main where ..."
-- Reason: don't want to complain about 'main' not in scope
-- in interactive mode
- ghci_mode <- getGhciMode
+ ghc_mode <- getGhcMode
real_exports <- case () of
() | explicit_mod
-> return exports
- | ghci_mode == Interactive
+ | ghc_mode == Interactive
-> return Nothing
| otherwise
-> do mainName <- lookupGlobalOccRn main_RDR_Unqual
diff --git a/ghc/compiler/typecheck/TcRnDriver.lhs b/ghc/compiler/typecheck/TcRnDriver.lhs
index ee0663e686..a9c8f98d58 100644
--- a/ghc/compiler/typecheck/TcRnDriver.lhs
+++ b/ghc/compiler/typecheck/TcRnDriver.lhs
@@ -740,7 +740,7 @@ tcTopSrcDecls boot_details
checkMain :: TcM TcGblEnv
-- If we are in module Main, check that 'main' is defined.
checkMain
- = do { ghci_mode <- getGhciMode ;
+ = do { ghc_mode <- getGhcMode ;
tcg_env <- getGblEnv ;
dflags <- getDOpts ;
let { main_mod = mainModIs dflags ;
@@ -748,11 +748,11 @@ checkMain
Just fn -> mkRdrUnqual (mkVarOccFS (mkFastString fn)) ;
Nothing -> main_RDR_Unqual } } ;
- check_main ghci_mode tcg_env main_mod main_fn
+ check_main ghc_mode tcg_env main_mod main_fn
}
-check_main ghci_mode tcg_env main_mod main_fn
+check_main ghc_mode tcg_env main_mod main_fn
| mod /= main_mod
= traceTc (text "checkMain not" <+> ppr main_mod <+> ppr mod) >>
return tcg_env
@@ -803,7 +803,7 @@ check_main ghci_mode tcg_env main_mod main_fn
where
mod = tcg_mod tcg_env
- complain_no_main | ghci_mode == Interactive = return ()
+ complain_no_main | ghc_mode == Interactive = return ()
| otherwise = failWithTc noMainMsg
-- In interactive mode, don't worry about the absence of 'main'
-- In other modes, fail altogether, so that we don't go on
diff --git a/ghc/compiler/typecheck/TcRnMonad.lhs b/ghc/compiler/typecheck/TcRnMonad.lhs
index 3c5de733a6..91ede2d5da 100644
--- a/ghc/compiler/typecheck/TcRnMonad.lhs
+++ b/ghc/compiler/typecheck/TcRnMonad.lhs
@@ -257,8 +257,8 @@ ifOptM :: DynFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () -- Do it flag is tru
ifOptM flag thing_inside = do { b <- doptM flag;
if b then thing_inside else return () }
-getGhciMode :: TcRnIf gbl lcl GhcMode
-getGhciMode = do { env <- getTopEnv; return (ghcMode (hsc_dflags env)) }
+getGhcMode :: TcRnIf gbl lcl GhcMode
+getGhcMode = do { env <- getTopEnv; return (ghcMode (hsc_dflags env)) }
\end{code}
\begin{code}