summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/deSugar/DsExpr.lhs3
-rw-r--r--compiler/deSugar/DsForeign.lhs2
-rw-r--r--compiler/deSugar/DsGRHSs.lhs3
-rw-r--r--compiler/deSugar/DsMonad.lhs4
-rw-r--r--compiler/deSugar/DsUtils.lhs3
-rw-r--r--compiler/vectorise/Vectorise/Generic/PADict.hs4
-rw-r--r--compiler/vectorise/Vectorise/Monad/Naming.hs5
7 files changed, 12 insertions, 12 deletions
diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs
index fb579ab672..6e9a7acbb3 100644
--- a/compiler/deSugar/DsExpr.lhs
+++ b/compiler/deSugar/DsExpr.lhs
@@ -42,6 +42,7 @@ import MkCore
import DynFlags
import CostCentre
import Id
+import Module
import VarSet
import VarEnv
import DataCon
@@ -296,7 +297,7 @@ dsExpr (ExplicitTuple tup_args boxity)
(map (Type . exprType) args ++ args) }
dsExpr (HsSCC cc expr@(L loc _)) = do
- mod_name <- getModuleDs
+ mod_name <- getModule
count <- goptM Opt_ProfCountEntries
uniq <- newUnique
Tick (ProfNote (mkUserCC cc mod_name loc uniq) count True) <$> dsLExpr expr
diff --git a/compiler/deSugar/DsForeign.lhs b/compiler/deSugar/DsForeign.lhs
index daf49eebac..bf06be109f 100644
--- a/compiler/deSugar/DsForeign.lhs
+++ b/compiler/deSugar/DsForeign.lhs
@@ -401,7 +401,7 @@ dsFExportDynamic :: Id
-> DsM ([Binding], SDoc, SDoc)
dsFExportDynamic id co0 cconv = do
fe_id <- newSysLocalDs ty
- mod <- getModuleDs
+ mod <- getModule
dflags <- getDynFlags
let
-- hack: need to get at the name of the C stub we're about to generate.
diff --git a/compiler/deSugar/DsGRHSs.lhs b/compiler/deSugar/DsGRHSs.lhs
index 1af39d1a0f..bc71fa8493 100644
--- a/compiler/deSugar/DsGRHSs.lhs
+++ b/compiler/deSugar/DsGRHSs.lhs
@@ -23,6 +23,7 @@ import DsMonad
import DsUtils
import TysWiredIn
import PrelNames
+import Module
import Name
import SrcLoc
import Outputable
@@ -146,7 +147,7 @@ isTrueLHsExpr (L _ (HsTick tickish e))
isTrueLHsExpr (L _ (HsBinTick ixT _ e))
| Just ticks <- isTrueLHsExpr e
= Just (\x -> do e <- ticks x
- this_mod <- getModuleDs
+ this_mod <- getModule
return (Tick (HpcTick this_mod ixT) e))
isTrueLHsExpr (L _ (HsPar e)) = isTrueLHsExpr e
diff --git a/compiler/deSugar/DsMonad.lhs b/compiler/deSugar/DsMonad.lhs
index 5e94d515d7..bc0e2e14dc 100644
--- a/compiler/deSugar/DsMonad.lhs
+++ b/compiler/deSugar/DsMonad.lhs
@@ -16,7 +16,6 @@ module DsMonad (
duplicateLocalDs, newSysLocalDs, newSysLocalsDs, newUniqueId,
newFailLocalDs, newPredVarDs,
getSrcSpanDs, putSrcSpanDs,
- getModuleDs,
mkPrintUnqualifiedDs,
newUnique,
UniqSupply, newUniqueSupply,
@@ -352,9 +351,6 @@ the @SrcSpan@ being carried around.
getGhcModeDs :: DsM GhcMode
getGhcModeDs = getDynFlags >>= return . ghcMode
-getModuleDs :: DsM Module
-getModuleDs = do { env <- getGblEnv; return (ds_mod env) }
-
getSrcSpanDs :: DsM SrcSpan
getSrcSpanDs = do { env <- getLclEnv; return (ds_loc env) }
diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs
index 0b14946793..609041ba24 100644
--- a/compiler/deSugar/DsUtils.lhs
+++ b/compiler/deSugar/DsUtils.lhs
@@ -67,6 +67,7 @@ import TysWiredIn
import BasicTypes
import UniqSet
import UniqSupply
+import Module
import PrelNames
import Outputable
import SrcLoc
@@ -759,7 +760,7 @@ mkOptTickBox (Just tickish) e = Tick tickish e
mkBinaryTickBox :: Int -> Int -> CoreExpr -> DsM CoreExpr
mkBinaryTickBox ixT ixF e = do
uq <- newUnique
- this_mod <- getModuleDs
+ this_mod <- getModule
let bndr1 = mkSysLocal (fsLit "t1") uq boolTy
let
falseBox = Tick (HpcTick this_mod ixF) (Var falseDataConId)
diff --git a/compiler/vectorise/Vectorise/Generic/PADict.hs b/compiler/vectorise/Vectorise/Generic/PADict.hs
index 96e0dbc225..da95884326 100644
--- a/compiler/vectorise/Vectorise/Generic/PADict.hs
+++ b/compiler/vectorise/Vectorise/Generic/PADict.hs
@@ -13,7 +13,7 @@ import BasicTypes
import CoreSyn
import CoreUtils
import CoreUnfold
-import DsMonad
+import Module
import TyCon
import Type
import Id
@@ -58,7 +58,7 @@ buildPADict vect_tc prepr_ax pdata_tc pdatas_tc repr
= polyAbstract tvs $ \args -> -- The args are the dictionaries we lambda abstract over; and they
-- are put in the envt, so when we need a (PA a) we can find it in
-- the envt; they don't include the silent superclass args yet
- do { mod <- liftDs getModuleDs
+ do { mod <- liftDs getModule
; let dfun_name = mkLocalisedOccName mod mkPADFunOcc vect_tc_name
-- The superclass dictionary is a (silent) argument if the tycon is polymorphic...
diff --git a/compiler/vectorise/Vectorise/Monad/Naming.hs b/compiler/vectorise/Vectorise/Monad/Naming.hs
index 30b8a0e1e4..def1ffa58c 100644
--- a/compiler/vectorise/Vectorise/Monad/Naming.hs
+++ b/compiler/vectorise/Vectorise/Monad/Naming.hs
@@ -19,6 +19,7 @@ import DsMonad
import TcType
import Type
import Var
+import Module
import Name
import SrcLoc
import MkId
@@ -37,7 +38,7 @@ import Control.Monad
--
mkLocalisedName :: (Maybe String -> OccName -> OccName) -> Name -> VM Name
mkLocalisedName mk_occ name
- = do { mod <- liftDs getModuleDs
+ = do { mod <- liftDs getModule
; u <- liftDs newUnique
; let occ_name = mkLocalisedOccName mod mk_occ name
@@ -86,7 +87,7 @@ cloneVar var = liftM (setIdUnique var) (liftDs newUnique)
--
newExportedVar :: OccName -> Type -> VM Var
newExportedVar occ_name ty
- = do mod <- liftDs getModuleDs
+ = do mod <- liftDs getModule
u <- liftDs newUnique
let name = mkExternalName u mod occ_name noSrcSpan