summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/deSugar/Desugar.hs2
-rw-r--r--compiler/iface/LoadIface.hs2
-rw-r--r--compiler/iface/MkIface.hs47
-rw-r--r--compiler/main/DriverMkDepend.hs6
-rw-r--r--compiler/main/DriverPhases.hs80
-rw-r--r--compiler/main/DriverPipeline.hs83
-rw-r--r--compiler/main/Finder.hs8
-rw-r--r--compiler/main/GHC.hs2
-rw-r--r--compiler/main/GhcMake.hs103
-rw-r--r--compiler/main/HscMain.hs69
-rw-r--r--compiler/main/HscTypes.hs40
-rw-r--r--compiler/typecheck/TcBinds.hs4
-rw-r--r--compiler/typecheck/TcInstDcls.hs4
-rw-r--r--compiler/typecheck/TcRnDriver.hs43
-rw-r--r--compiler/typecheck/TcRnMonad.hs2
-rw-r--r--compiler/typecheck/TcRnTypes.hs1
-rw-r--r--ghc/Main.hs19
-rw-r--r--testsuite/.gitignore1
-rw-r--r--testsuite/tests/driver/dynamicToo/dynamicToo005/A005.hsig (renamed from testsuite/tests/driver/dynamicToo/dynamicToo005/A005.hs-boot)0
-rw-r--r--testsuite/tests/driver/dynamicToo/dynamicToo005/Makefile8
-rw-r--r--testsuite/tests/driver/dynamicToo/dynamicToo006/A.hsig (renamed from testsuite/tests/driver/dynamicToo/dynamicToo006/A.hs-boot)0
-rw-r--r--testsuite/tests/driver/dynamicToo/dynamicToo006/Makefile2
-rw-r--r--testsuite/tests/driver/recomp014/Makefile33
-rw-r--r--testsuite/tests/driver/recomp014/all.T4
-rw-r--r--testsuite/tests/driver/recomp014/recomp014.stdout4
-rw-r--r--testsuite/tests/driver/sigof01/B.hsig (renamed from testsuite/tests/driver/sigof01/B.hs-boot)0
-rw-r--r--testsuite/tests/driver/sigof01/Makefile9
-rw-r--r--testsuite/tests/driver/sigof01/all.T10
-rw-r--r--testsuite/tests/driver/sigof01/sigof01i.script1
-rw-r--r--testsuite/tests/driver/sigof01/sigof01i.stdout3
-rw-r--r--testsuite/tests/driver/sigof01/sigof01i2.script3
-rw-r--r--testsuite/tests/driver/sigof01/sigof01i2.stdout9
-rw-r--r--testsuite/tests/driver/sigof01/sigof01m.stdout7
-rw-r--r--testsuite/tests/driver/sigof02/Makefile21
-rw-r--r--testsuite/tests/driver/sigof02/Map.hsig (renamed from testsuite/tests/driver/sigof02/Map.hs-boot)0
-rw-r--r--testsuite/tests/driver/sigof02/MapAsSet.hsig (renamed from testsuite/tests/driver/sigof02/MapAsSet.hs-boot)0
-rw-r--r--testsuite/tests/driver/sigof02/sigof02dm.stdout8
-rw-r--r--testsuite/tests/driver/sigof02/sigof02m.stdout10
-rw-r--r--testsuite/tests/driver/sigof03/ASig1.hsig (renamed from testsuite/tests/driver/sigof03/ASig1.hs-boot)0
-rw-r--r--testsuite/tests/driver/sigof03/ASig2.hsig (renamed from testsuite/tests/driver/sigof03/ASig2.hs-boot)0
-rw-r--r--testsuite/tests/driver/sigof03/Makefile5
-rw-r--r--testsuite/tests/driver/sigof04/Makefile2
-rw-r--r--testsuite/tests/driver/sigof04/Sig.hsig (renamed from testsuite/tests/driver/sigof04/Sig.hs-boot)0
-rw-r--r--testsuite/tests/driver/sigof04/sigof04.stderr6
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T2
-rw-r--r--testsuite/tests/typecheck/should_compile/tc264.hsig (renamed from testsuite/tests/typecheck/should_compile/tc264.hs-boot)0
-rw-r--r--testsuite/tests/typecheck/should_compile/tc264.stderr2
-rw-r--r--testsuite/tests/typecheck/should_fail/all.T8
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail219.hsig (renamed from testsuite/tests/typecheck/should_fail/tcfail219.hs-boot)0
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail219.stderr5
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail220.hsig (renamed from testsuite/tests/typecheck/should_fail/tcfail220.hs-boot)0
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail220.stderr10
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail221.hsig (renamed from testsuite/tests/typecheck/should_fail/tcfail221.hs-boot)0
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail221.stderr8
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail222.hsig (renamed from testsuite/tests/typecheck/should_fail/tcfail222.hs-boot)0
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail222.stderr8
-rw-r--r--utils/ghctags/Main.hs7
m---------utils/haddock0
58 files changed, 231 insertions, 480 deletions
diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs
index 77834e0160..4235c5c3d1 100644
--- a/compiler/deSugar/Desugar.hs
+++ b/compiler/deSugar/Desugar.hs
@@ -296,7 +296,7 @@ deSugar hsc_env
hpcInfo = emptyHpcInfo other_hpc_info
; (binds_cvr, ds_hpc_info, modBreaks)
- <- if not (isHsBoot hsc_src)
+ <- if not (isHsBootOrSig hsc_src)
then addTicksToBinds dflags mod mod_loc export_set
(typeEnvTyCons type_env) binds
else return (binds, hpcInfo, emptyModBreaks)
diff --git a/compiler/iface/LoadIface.hs b/compiler/iface/LoadIface.hs
index d2e16c67cb..48acd8dd28 100644
--- a/compiler/iface/LoadIface.hs
+++ b/compiler/iface/LoadIface.hs
@@ -897,7 +897,7 @@ pprModIface iface
]
where
pp_hsc_src HsBootFile = ptext (sLit "[boot]")
- pp_hsc_src HsBootMerge = ptext (sLit "[merge]")
+ pp_hsc_src HsigFile = ptext (sLit "[hsig]")
pp_hsc_src HsSrcFile = Outputable.empty
{-
diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs
index a8d0344e77..98b8830e01 100644
--- a/compiler/iface/MkIface.hs
+++ b/compiler/iface/MkIface.hs
@@ -13,7 +13,6 @@ module MkIface (
-- including computing version information
mkIfaceTc,
- mkIfaceDirect,
writeIfaceFile, -- Write the interface file
@@ -154,35 +153,6 @@ mkIface hsc_env maybe_old_fingerprint mod_details
warns hpc_info self_trust
safe_mode usages mod_details
--- | Make an interface from a manually constructed 'ModIface'. We use
--- this when we are merging 'ModIface's. We assume that the 'ModIface'
--- has accurate entries but not accurate fingerprint information (so,
--- like @intermediate_iface@ in 'mkIface_'.)
-mkIfaceDirect :: HscEnv
- -> Maybe Fingerprint
- -> ModIface
- -> IO (ModIface, Bool)
-mkIfaceDirect hsc_env maybe_old_fingerprint iface0 = do
- -- Sort some things to make sure we're deterministic
- let intermediate_iface = iface0 {
- mi_exports = mkIfaceExports (mi_exports iface0),
- mi_insts = sortBy cmp_inst (mi_insts iface0),
- mi_fam_insts = sortBy cmp_fam_inst (mi_fam_insts iface0),
- mi_rules = sortBy cmp_rule (mi_rules iface0)
- }
- dflags = hsc_dflags hsc_env
- (final_iface, no_change_at_all)
- <- {-# SCC "versioninfo" #-}
- addFingerprints hsc_env maybe_old_fingerprint
- intermediate_iface
- (map snd (mi_decls iface0))
-
- -- Debug printing
- dumpIfSet_dyn dflags Opt_D_dump_hi "FINAL INTERFACE"
- (pprModIface final_iface)
-
- return (final_iface, no_change_at_all)
-
-- | make an interface from the results of typechecking only. Useful
-- for non-optimising compilation, or where we aren't generating any
-- object code at all ('HscNothing').
@@ -320,6 +290,11 @@ mkIface_ hsc_env maybe_old_fingerprint
return (final_iface, no_change_at_all)
where
+ cmp_rule = comparing ifRuleName
+ -- Compare these lexicographically by OccName, *not* by unique,
+ -- because the latter is not stable across compilations:
+ cmp_inst = comparing (nameOccName . ifDFun)
+ cmp_fam_inst = comparing (nameOccName . ifFamInstTcName)
dflags = hsc_dflags hsc_env
@@ -337,6 +312,8 @@ mkIface_ hsc_env maybe_old_fingerprint
deliberatelyOmitted :: String -> a
deliberatelyOmitted x = panic ("Deliberately omitted: " ++ x)
+ ifFamInstTcName = ifFamInstFam
+
flattenVectInfo (VectInfo { vectInfoVar = vVar
, vectInfoTyCon = vTyCon
, vectInfoParallelVars = vParallelVars
@@ -350,16 +327,6 @@ mkIface_ hsc_env maybe_old_fingerprint
, ifaceVectInfoParallelTyCons = nameSetElems vParallelTyCons
}
-cmp_rule :: IfaceRule -> IfaceRule -> Ordering
-cmp_rule = comparing ifRuleName
--- Compare these lexicographically by OccName, *not* by unique,
--- because the latter is not stable across compilations:
-cmp_inst :: IfaceClsInst -> IfaceClsInst -> Ordering
-cmp_inst = comparing (nameOccName . ifDFun)
-
-cmp_fam_inst :: IfaceFamInst -> IfaceFamInst -> Ordering
-cmp_fam_inst = comparing (nameOccName . ifFamInstFam)
-
-----------------------------
writeIfaceFile :: DynFlags -> FilePath -> ModIface -> IO ()
writeIfaceFile dflags hi_file_path new_iface
diff --git a/compiler/main/DriverMkDepend.hs b/compiler/main/DriverMkDepend.hs
index 1541d95c62..611d3964c5 100644
--- a/compiler/main/DriverMkDepend.hs
+++ b/compiler/main/DriverMkDepend.hs
@@ -197,9 +197,9 @@ processDeps dflags _ _ _ _ (CyclicSCC nodes)
throwGhcExceptionIO (ProgramError (showSDoc dflags $ GHC.cyclicModuleErr nodes))
processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC node)
- | Just src_file <- msHsFilePath node
= do { let extra_suffixes = depSuffixes dflags
include_pkg_deps = depIncludePkgDeps dflags
+ src_file = msHsFilePath node
obj_file = msObjFilePath node
obj_files = insertSuffixes obj_file extra_suffixes
@@ -233,10 +233,6 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC node)
; do_imps False (ms_imps node)
}
- | otherwise
- = ASSERT( ms_hsc_src node == HsBootMerge )
- panic "HsBootMerge not supported in DriverMkDepend yet"
-
findDependency :: HscEnv
-> SrcSpan
diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs
index f079212112..ff6f8b8ab1 100644
--- a/compiler/main/DriverPhases.hs
+++ b/compiler/main/DriverPhases.hs
@@ -10,7 +10,7 @@
-----------------------------------------------------------------------------
module DriverPhases (
- HscSource(..), isHsBoot, hscSourceString,
+ HscSource(..), isHsBootOrSig, hscSourceString,
Phase(..),
happensBefore, eqPhase, anyHsc, isStopLn,
startPhase,
@@ -22,10 +22,12 @@ module DriverPhases (
isCishSuffix,
isDynLibSuffix,
isHaskellUserSrcSuffix,
+ isHaskellSigSuffix,
isSourceSuffix,
isHaskellishFilename,
isHaskellSrcFilename,
+ isHaskellSigFilename,
isObjectFilename,
isCishFilename,
isDynLibFilename,
@@ -58,51 +60,63 @@ import Binary
-- Note [HscSource types]
-- ~~~~~~~~~~~~~~~~~~~~~~
--- There are two types of source file for user-written Haskell code:
+-- There are three types of source file for Haskell code:
--
-- * HsSrcFile is an ordinary hs file which contains code,
--
--- * HsBootFile is an hs-boot file. Within a unit, it can
--- be used to break recursive module imports, in which case there's an
--- HsSrcFile associated with it. However, externally, it can
--- also be used to specify the *requirements* of a package,
--- in which case there is an HsBootMerge associated with it.
+-- * HsBootFile is an hs-boot file, which is used to break
+-- recursive module imports (there will always be an
+-- HsSrcFile associated with it), and
--
--- An HsBootMerge is a "fake" source file, which is constructed
--- by collecting up non-recursive HsBootFiles into a single interface.
--- HsBootMerges get an hi and o file, and are treated as "non-boot"
--- sources.
+-- * HsigFile is an hsig file, which contains only type
+-- signatures and is used to specify signatures for
+-- modules.
+--
+-- Syntactically, hs-boot files and hsig files are quite similar: they
+-- only include type signatures and must be associated with an
+-- actual HsSrcFile. isHsBootOrSig allows us to abstract over code
+-- which is indifferent to which. However, there are some important
+-- differences, mostly owing to the fact that hsigs are proper
+-- modules (you `import Sig` directly) whereas HsBootFiles are
+-- temporary placeholders (you `import {-# SOURCE #-} Mod).
+-- When we finish compiling the true implementation of an hs-boot,
+-- we replace the HomeModInfo with the real HsSrcFile. An HsigFile, on the
+-- other hand, is never replaced (in particular, we *cannot* use the
+-- HomeModInfo of the original HsSrcFile backing the signature, since it
+-- will export too many symbols.)
+--
+-- Additionally, while HsSrcFile is the only Haskell file
+-- which has *code*, we do generate .o files for HsigFile, because
+-- this is how the recompilation checker figures out if a file
+-- needs to be recompiled. These are fake object files which
+-- should NOT be linked against.
data HscSource
- = HsSrcFile | HsBootFile | HsBootMerge
+ = HsSrcFile | HsBootFile | HsigFile
deriving( Eq, Ord, Show )
-- Ord needed for the finite maps we build in CompManager
-instance Outputable HscSource where
- ppr HsSrcFile = text "HsSrcFile"
- ppr HsBootFile = text "HsBootFile"
- ppr HsBootMerge = text "HsBootMerge"
-
instance Binary HscSource where
put_ bh HsSrcFile = putByte bh 0
put_ bh HsBootFile = putByte bh 1
- put_ bh HsBootMerge = putByte bh 2
+ put_ bh HsigFile = putByte bh 2
get bh = do
h <- getByte bh
case h of
0 -> return HsSrcFile
1 -> return HsBootFile
- _ -> return HsBootMerge
+ _ -> return HsigFile
hscSourceString :: HscSource -> String
hscSourceString HsSrcFile = ""
hscSourceString HsBootFile = "[boot]"
-hscSourceString HsBootMerge = "[merge]"
+hscSourceString HsigFile = "[sig]"
-isHsBoot :: HscSource -> Bool
-isHsBoot HsBootFile = True
-isHsBoot HsSrcFile = False
-isHsBoot HsBootMerge = False
+-- See Note [isHsBootOrSig]
+isHsBootOrSig :: HscSource -> Bool
+isHsBootOrSig HsBootFile = True
+isHsBootOrSig HsigFile = True
+isHsBootOrSig _ = False
data Phase
= Unlit HscSource
@@ -218,8 +232,10 @@ nextPhase dflags p
startPhase :: String -> Phase
startPhase "lhs" = Unlit HsSrcFile
startPhase "lhs-boot" = Unlit HsBootFile
+startPhase "lhsig" = Unlit HsigFile
startPhase "hs" = Cpp HsSrcFile
startPhase "hs-boot" = Cpp HsBootFile
+startPhase "hsig" = Cpp HsigFile
startPhase "hscpp" = HsPp HsSrcFile
startPhase "hspp" = Hsc HsSrcFile
startPhase "hc" = HCc
@@ -248,9 +264,7 @@ startPhase _ = StopLn -- all unknown file types
phaseInputExt :: Phase -> String
phaseInputExt (Unlit HsSrcFile) = "lhs"
phaseInputExt (Unlit HsBootFile) = "lhs-boot"
-phaseInputExt (Unlit HsBootMerge) = panic "phaseInputExt: Unlit HsBootMerge"
- -- You can't Unlit an HsBootMerge, because there's no source
- -- file to Unlit!
+phaseInputExt (Unlit HsigFile) = "lhsig"
phaseInputExt (Cpp _) = "lpp" -- intermediate only
phaseInputExt (HsPp _) = "hscpp" -- intermediate only
phaseInputExt (Hsc _) = "hspp" -- intermediate only
@@ -275,7 +289,7 @@ phaseInputExt MergeStub = "o"
phaseInputExt StopLn = "o"
haskellish_src_suffixes, haskellish_suffixes, cish_suffixes,
- haskellish_user_src_suffixes
+ haskellish_user_src_suffixes, haskellish_sig_suffixes
:: [String]
-- When a file with an extension in the haskellish_src_suffixes group is
-- loaded in --make mode, its imports will be loaded too.
@@ -286,7 +300,9 @@ haskellish_suffixes = haskellish_src_suffixes ++
cish_suffixes = [ "c", "cpp", "C", "cc", "cxx", "s", "S", "ll", "bc", "lm_s", "m", "M", "mm" ]
-- Will not be deleted as temp files:
-haskellish_user_src_suffixes = [ "hs", "lhs", "hs-boot", "lhs-boot" ]
+haskellish_user_src_suffixes =
+ haskellish_sig_suffixes ++ [ "hs", "lhs", "hs-boot", "lhs-boot" ]
+haskellish_sig_suffixes = [ "hsig", "lhsig" ]
objish_suffixes :: Platform -> [String]
-- Use the appropriate suffix for the system on which
@@ -302,9 +318,10 @@ dynlib_suffixes platform = case platformOS platform of
_ -> ["so"]
isHaskellishSuffix, isHaskellSrcSuffix, isCishSuffix,
- isHaskellUserSrcSuffix
+ isHaskellUserSrcSuffix, isHaskellSigSuffix
:: String -> Bool
isHaskellishSuffix s = s `elem` haskellish_suffixes
+isHaskellSigSuffix s = s `elem` haskellish_sig_suffixes
isHaskellSrcSuffix s = s `elem` haskellish_src_suffixes
isCishSuffix s = s `elem` cish_suffixes
isHaskellUserSrcSuffix s = s `elem` haskellish_user_src_suffixes
@@ -317,7 +334,7 @@ isSourceSuffix :: String -> Bool
isSourceSuffix suff = isHaskellishSuffix suff || isCishSuffix suff
isHaskellishFilename, isHaskellSrcFilename, isCishFilename,
- isHaskellUserSrcFilename, isSourceFilename
+ isHaskellUserSrcFilename, isSourceFilename, isHaskellSigFilename
:: FilePath -> Bool
-- takeExtension return .foo, so we drop 1 to get rid of the .
isHaskellishFilename f = isHaskellishSuffix (drop 1 $ takeExtension f)
@@ -325,6 +342,7 @@ isHaskellSrcFilename f = isHaskellSrcSuffix (drop 1 $ takeExtension f)
isCishFilename f = isCishSuffix (drop 1 $ takeExtension f)
isHaskellUserSrcFilename f = isHaskellUserSrcSuffix (drop 1 $ takeExtension f)
isSourceFilename f = isSourceSuffix (drop 1 $ takeExtension f)
+isHaskellSigFilename f = isHaskellSigSuffix (drop 1 $ takeExtension f)
isObjectFilename, isDynLibFilename :: Platform -> FilePath -> Bool
isObjectFilename platform f = isObjectSuffix platform (drop 1 $ takeExtension f)
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index a1d36a6b54..2e6bac81b8 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -13,7 +13,7 @@
module DriverPipeline (
-- Run a series of compilation steps in a pipeline, for a
-- collection of source files.
- oneShot, compileFile, mergeRequirement,
+ oneShot, compileFile,
-- Interfaces for the batch-mode driver
linkBinary,
@@ -23,9 +23,6 @@ module DriverPipeline (
compileOne, compileOne',
link,
- -- Misc utility
- makeMergeRequirementSummary,
-
-- Exports for hooks to override runPhase and link
PhasePlus(..), CompPipeline(..), PipeEnv(..), PipeState(..),
phaseOutputFilename, getPipeState, getPipeEnv,
@@ -73,7 +70,6 @@ import System.IO
import Control.Monad
import Data.List ( isSuffixOf )
import Data.Maybe
-import Data.Time
import Data.Version
-- ---------------------------------------------------------------------------
@@ -133,6 +129,22 @@ compileOne' m_tc_result mHscMessage
hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
source_modified0
= do
+ let dflags0 = ms_hspp_opts summary
+ this_mod = ms_mod summary
+ src_flavour = ms_hsc_src summary
+ location = ms_location summary
+ input_fnpp = ms_hspp_file summary
+ mod_graph = hsc_mod_graph hsc_env0
+ needsTH = any (xopt Opt_TemplateHaskell . ms_hspp_opts) mod_graph
+ needsQQ = any (xopt Opt_QuasiQuotes . ms_hspp_opts) mod_graph
+ needsLinker = needsTH || needsQQ
+ isDynWay = any (== WayDyn) (ways dflags0)
+ isProfWay = any (== WayProf) (ways dflags0)
+ -- #8180 - when using TemplateHaskell, switch on -dynamic-too so
+ -- the linker can correctly load the object files.
+ let dflags1 = if needsLinker && dynamicGhc && not isDynWay && not isProfWay
+ then gopt_set dflags0 Opt_BuildDynamicToo
+ else dflags0
debugTraceMsg dflags1 2 (text "compile: input file" <+> text input_fnpp)
@@ -146,7 +158,7 @@ compileOne' m_tc_result mHscMessage
ASSERT( isJust maybe_old_linkable || isNoLink (ghcLink dflags) )
return hmi0 { hm_linkable = maybe_old_linkable }
(HscNotGeneratingCode, HscNothing) ->
- let mb_linkable = if isHsBoot src_flavour
+ let mb_linkable = if isHsBootOrSig src_flavour
then Nothing
-- TODO: Questionable.
else Just (LM (ms_hs_date summary) this_mod [])
@@ -158,10 +170,10 @@ compileOne' m_tc_result mHscMessage
(HscUpdateBoot, _) -> do
touchObjectFile dflags object_filename
return hmi0
- (HscUpdateBootMerge, HscInterpreted) ->
+ (HscUpdateSig, HscInterpreted) ->
let linkable = LM (ms_hs_date summary) this_mod []
in return hmi0 { hm_linkable = Just linkable }
- (HscUpdateBootMerge, _) -> do
+ (HscUpdateSig, _) -> do
output_fn <- getOutputFilename next_phase
Temporary basename dflags next_phase (Just location)
@@ -171,7 +183,7 @@ compileOne' m_tc_result mHscMessage
_ <- runPipeline StopLn hsc_env
(output_fn,
Just (HscOut src_flavour
- mod_name HscUpdateBootMerge))
+ mod_name HscUpdateSig))
(Just basename)
Persistent
(Just location)
@@ -218,7 +230,6 @@ compileOne' m_tc_result mHscMessage
where dflags0 = ms_hspp_opts summary
location = ms_location summary
input_fn = expectJust "compile:hs" (ml_hs_file location)
- input_fnpp = ms_hspp_file summary
mod_graph = hsc_mod_graph hsc_env0
needsTH = any (xopt Opt_TemplateHaskell . ms_hspp_opts) mod_graph
needsQQ = any (xopt Opt_QuasiQuotes . ms_hspp_opts) mod_graph
@@ -228,7 +239,6 @@ compileOne' m_tc_result mHscMessage
src_flavour = ms_hsc_src summary
- this_mod = ms_mod summary
mod_name = ms_mod_name summary
next_phase = hscPostBackendPhase dflags src_flavour hsc_lang
object_filename = ml_obj_file location
@@ -489,50 +499,6 @@ oneShot hsc_env stop_phase srcs = do
o_files <- mapM (compileFile hsc_env stop_phase) srcs
doLink (hsc_dflags hsc_env) stop_phase o_files
--- | Constructs a 'ModSummary' for a "signature merge" node.
--- This is a simplified construction function which only checks
--- for a local hs-boot file.
-makeMergeRequirementSummary :: HscEnv -> Bool -> ModuleName -> IO ModSummary
-makeMergeRequirementSummary hsc_env obj_allowed mod_name = do
- let dflags = hsc_dflags hsc_env
- location <- liftIO $ mkHomeModLocation2 dflags mod_name
- (moduleNameSlashes mod_name) (hiSuf dflags)
- obj_timestamp <-
- if isObjectTarget (hscTarget dflags) || obj_allowed -- bug #1205
- then liftIO $ modificationTimeIfExists (ml_obj_file location)
- else return Nothing
- r <- findHomeModule hsc_env mod_name
- let has_local_boot = case r of
- Found _ _ -> True
- _ -> False
- src_timestamp <- case obj_timestamp of
- Just date -> return date
- Nothing -> getCurrentTime -- something fake
- return ModSummary {
- ms_mod = mkModule (thisPackage dflags) mod_name,
- ms_hsc_src = HsBootMerge,
- ms_location = location,
- ms_hs_date = src_timestamp,
- ms_obj_date = obj_timestamp,
- ms_iface_date = Nothing,
- -- TODO: fill this in with all the imports eventually
- ms_srcimps = [],
- ms_textual_imps = [],
- ms_merge_imps = (has_local_boot, []),
- ms_hspp_file = "FAKE",
- ms_hspp_opts = dflags,
- ms_hspp_buf = Nothing
- }
-
--- | Top-level entry point for @ghc -merge-requirement ModName@.
-mergeRequirement :: HscEnv -> ModuleName -> IO ()
-mergeRequirement hsc_env mod_name = do
- mod_summary <- makeMergeRequirementSummary hsc_env True mod_name
- -- Based off of GhcMake handling
- _ <- liftIO $ compileOne' Nothing Nothing hsc_env mod_summary 1 1 Nothing
- Nothing SourceUnmodified
- return ()
-
compileFile :: HscEnv -> Phase -> (FilePath, Maybe Phase) -> IO FilePath
compileFile hsc_env stop_phase (src, mb_phase) = do
exists <- doesFileExist src
@@ -1014,8 +980,7 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
ms_obj_date = Nothing,
ms_iface_date = Nothing,
ms_textual_imps = imps,
- ms_srcimps = src_imps,
- ms_merge_imps = (False, []) }
+ ms_srcimps = src_imps }
-- run the compiler!
let msg hsc_env _ what _ = oneShotMsg hsc_env what
@@ -1048,7 +1013,7 @@ runPhase (HscOut src_flavour mod_name result) _ dflags = do
-- stamp file for the benefit of Make
liftIO $ touchObjectFile dflags o_file
return (RealPhase StopLn, o_file)
- HscUpdateBootMerge ->
+ HscUpdateSig ->
do -- We need to create a REAL but empty .o file
-- because we are going to attempt to put it in a library
PipeState{hsc_env=hsc_env'} <- getPipeState
@@ -2211,7 +2176,7 @@ writeInterfaceOnlyMode dflags =
-- | What phase to run after one of the backend code generators has run
hscPostBackendPhase :: DynFlags -> HscSource -> HscTarget -> Phase
hscPostBackendPhase _ HsBootFile _ = StopLn
-hscPostBackendPhase _ HsBootMerge _ = StopLn
+hscPostBackendPhase _ HsigFile _ = StopLn
hscPostBackendPhase dflags _ hsc_lang =
case hsc_lang of
HscC -> HCc
diff --git a/compiler/main/Finder.hs b/compiler/main/Finder.hs
index 1ccf33f668..c6bbd7583f 100644
--- a/compiler/main/Finder.hs
+++ b/compiler/main/Finder.hs
@@ -228,11 +228,8 @@ findHomeModule hsc_env mod_name =
source_exts =
[ ("hs", mkHomeModLocationSearched dflags mod_name "hs")
, ("lhs", mkHomeModLocationSearched dflags mod_name "lhs")
- -- TODO: This is a giant hack! If we find an hs-boot file,
- -- pretend that there's an hs file here too, even if there isn't.
- -- GhcMake will know what to do next.
- , ("hs-boot", mkHomeModLocationSearched dflags mod_name "hs")
- , ("lhs-boot", mkHomeModLocationSearched dflags mod_name "lhs")
+ , ("hsig", mkHomeModLocationSearched dflags mod_name "hsig")
+ , ("lhsig", mkHomeModLocationSearched dflags mod_name "lhsig")
]
hi_exts = [ (hisuf, mkHiOnlyModLocation dflags hisuf)
@@ -253,6 +250,7 @@ findHomeModule hsc_env mod_name =
then return (Found (error "GHC.Prim ModLocation") mod)
else searchPathExts home_path mod exts
+
-- | Search for a module in external packages only.
findPackageModule :: HscEnv -> Module -> IO FindResult
findPackageModule hsc_env mod = do
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index f64796069f..fa1c2f0beb 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -988,7 +988,7 @@ compileCore simplify fn = do
_ <- load LoadAllTargets
-- Then find dependencies
modGraph <- depanal [] True
- case find ((== Just fn) . msHsFilePath) modGraph of
+ case find ((== fn) . msHsFilePath) modGraph of
Just modSummary -> do
-- Now we have the module name;
-- parse, typecheck and desugar the module
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index 65df44b83d..06cd082d13 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -1424,7 +1424,7 @@ reachableBackwards mod summaries
= [ ms | (ms,_,_) <- reachableG (transposeG graph) root ]
where -- the rest just sets up the graph:
(graph, lookup_node) = moduleGraphNodes False summaries
- root = expectJust "reachableBackwards" (lookup_node IsBoot mod)
+ root = expectJust "reachableBackwards" (lookup_node HsBootFile mod)
-- ---------------------------------------------------------------------------
--
@@ -1463,8 +1463,7 @@ topSortModuleGraph drop_hs_boot_nodes summaries mb_root_mod
-- the specified module. We do this by building a graph with
-- the full set of nodes, and determining the reachable set from
-- the specified node.
- let root | Just node <- lookup_node NotBoot root_mod
- , graph `hasVertexG` node = node
+ let root | Just node <- lookup_node HsSrcFile root_mod, graph `hasVertexG` node = node
| otherwise = throwGhcException (ProgramError "module does not exist")
in graphFromEdgedVertices (seq root (reachableG graph root))
@@ -1477,48 +1476,36 @@ summaryNodeSummary :: SummaryNode -> ModSummary
summaryNodeSummary (s, _, _) = s
moduleGraphNodes :: Bool -> [ModSummary]
- -> (Graph SummaryNode, IsBoot -> ModuleName -> Maybe SummaryNode)
+ -> (Graph SummaryNode, HscSource -> ModuleName -> Maybe SummaryNode)
moduleGraphNodes drop_hs_boot_nodes summaries = (graphFromEdgedVertices nodes, lookup_node)
where
numbered_summaries = zip summaries [1..]
- lookup_node :: IsBoot -> ModuleName -> Maybe SummaryNode
- lookup_node is_boot mod = Map.lookup (mod, is_boot) node_map
+ lookup_node :: HscSource -> ModuleName -> Maybe SummaryNode
+ lookup_node hs_src mod = Map.lookup (mod, hscSourceToIsBoot hs_src) node_map
- lookup_key :: IsBoot -> ModuleName -> Maybe Int
- lookup_key is_boot mod = fmap summaryNodeKey (lookup_node is_boot mod)
+ lookup_key :: HscSource -> ModuleName -> Maybe Int
+ lookup_key hs_src mod = fmap summaryNodeKey (lookup_node hs_src mod)
node_map :: NodeMap SummaryNode
node_map = Map.fromList [ ((moduleName (ms_mod s),
hscSourceToIsBoot (ms_hsc_src s)), node)
| node@(s, _, _) <- nodes ]
- hasImplSet :: Set.Set ModuleName
- hasImplSet = Set.fromList [ ms_mod_name s
- | s <- summaries, ms_hsc_src s == HsSrcFile ]
-
- hasImpl :: ModuleName -> Bool
- hasImpl modname = modname `Set.member` hasImplSet
-
-- We use integers as the keys for the SCC algorithm
nodes :: [SummaryNode]
nodes = [ (s, key, out_keys)
| (s, key) <- numbered_summaries
-- Drop the hi-boot ones if told to do so
- , not (isBootSummary s && hasImpl (ms_mod_name s)
- && drop_hs_boot_nodes)
- , let out_keys
- = out_edge_keys IsBoot (map unLoc (ms_home_srcimps s)) ++
- out_edge_keys NotBoot (map unLoc (ms_home_imps s)) ++
- (if fst (ms_merge_imps s)
- then out_edge_keys IsBoot [moduleName (ms_mod s)]
- else []) ++
- (-- see [boot-edges] below
- if drop_hs_boot_nodes || ms_hsc_src s /= HsSrcFile
- then []
- else case lookup_key IsBoot (ms_mod_name s) of
- Nothing -> []
- Just k -> [k]) ]
+ , not (isBootSummary s && drop_hs_boot_nodes)
+ , let out_keys = out_edge_keys hs_boot_key (map unLoc (ms_home_srcimps s)) ++
+ out_edge_keys HsSrcFile (map unLoc (ms_home_imps s)) ++
+ (-- see [boot-edges] below
+ if drop_hs_boot_nodes || ms_hsc_src s == HsBootFile
+ then []
+ else case lookup_key HsBootFile (ms_mod_name s) of
+ Nothing -> []
+ Just k -> [k]) ]
-- [boot-edges] if this is a .hs and there is an equivalent
-- .hs-boot, add a link from the former to the latter. This
@@ -1528,13 +1515,12 @@ moduleGraphNodes drop_hs_boot_nodes summaries = (graphFromEdgedVertices nodes, l
-- the .hs, and so the HomePackageTable will always have the
-- most up to date information.
- out_edge_keys :: IsBoot -> [ModuleName] -> [Int]
- out_edge_keys hi_boot ms = mapMaybe (lookup_out_edge_key hi_boot) ms
+ -- Drop hs-boot nodes by using HsSrcFile as the key
+ hs_boot_key | drop_hs_boot_nodes = HsSrcFile
+ | otherwise = HsBootFile
- lookup_out_edge_key :: IsBoot -> ModuleName -> Maybe Int
- lookup_out_edge_key hi_boot m
- | hasImpl m, drop_hs_boot_nodes = lookup_key NotBoot m
- | otherwise = lookup_key hi_boot m
+ out_edge_keys :: HscSource -> [ModuleName] -> [Int]
+ out_edge_keys hi_boot ms = mapMaybe (lookup_key hi_boot) ms
-- If we want keep_hi_boot_nodes, then we do lookup_key with
-- IsBoot; else NotBoot
@@ -1623,7 +1609,7 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
-- dependency on what-ever the signature's implementation is.
-- (But not when we're type checking!)
calcDeps summ
- | HsBootFile <- ms_hsc_src summ
+ | HsigFile <- ms_hsc_src summ
, Just m <- getSigOf (hsc_dflags hsc_env) (moduleName (ms_mod summ))
, moduleUnitId m == thisPackage (hsc_dflags hsc_env)
= (noLoc (moduleName m), NotBoot) : msDeps summ
@@ -1707,16 +1693,10 @@ mkRootMap summaries = Map.insertListWith (flip (++))
-- modules always contains B.hs if it contains B.hs-boot.
-- Remember, this pass isn't doing the topological sort. It's
-- just gathering the list of all relevant ModSummaries
---
--- NB: for signatures, (m,NotBoot) is "special"; the Haskell file
--- may not exist; we just synthesize it ourselves.
msDeps :: ModSummary -> [(Located ModuleName, IsBoot)]
msDeps s =
concat [ [(m,IsBoot), (m,NotBoot)] | m <- ms_home_srcimps s ]
++ [ (m,NotBoot) | m <- ms_home_imps s ]
- ++ if fst (ms_merge_imps s)
- then [ (noLoc (moduleName (ms_mod s)), IsBoot) ]
- else []
home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName]
home_imps imps = [ lmodname | (mb_pkg, lmodname) <- imps,
@@ -1798,6 +1778,8 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
new_summary src_timestamp = do
let dflags = hsc_dflags hsc_env
+ let hsc_src = if isHaskellSigFilename file then HsigFile else HsSrcFile
+
(dflags', hspp_fn, buf)
<- preprocessFile hsc_env file mb_phase maybe_buf
@@ -1820,16 +1802,12 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
hi_timestamp <- maybeGetIfaceDate dflags location
- return (ModSummary { ms_mod = mod,
- ms_hsc_src = if "boot" `isSuffixOf` file
- then HsBootFile
- else HsSrcFile,
+ return (ModSummary { ms_mod = mod, ms_hsc_src = hsc_src,
ms_location = location,
ms_hspp_file = hspp_fn,
ms_hspp_opts = dflags',
ms_hspp_buf = Just buf,
ms_srcimps = srcimps, ms_textual_imps = the_imps,
- ms_merge_imps = (False, []),
ms_hs_date = src_timestamp,
ms_iface_date = hi_timestamp,
ms_obj_date = obj_timestamp })
@@ -1875,17 +1853,6 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
Left e | isDoesNotExistError e -> find_it
| otherwise -> ioError e
- | NotBoot <- is_boot
- , Just _ <- getSigOf dflags wanted_mod
- = do mod_summary0 <- makeMergeRequirementSummary hsc_env
- obj_allowed
- wanted_mod
- hi_timestamp <- maybeGetIfaceDate dflags (ms_location mod_summary0)
- let mod_summary = mod_summary0 {
- ms_iface_date = hi_timestamp
- }
- return (Just (Right mod_summary))
-
| otherwise = find_it
where
dflags = hsc_dflags hsc_env
@@ -1948,10 +1915,17 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
(dflags', hspp_fn, buf) <- preprocessFile hsc_env src_fn Nothing maybe_buf
(srcimps, the_imps, L mod_loc mod_name) <- getImports dflags' buf hspp_fn src_fn
- let hsc_src =
- case is_boot of
- IsBoot -> HsBootFile
- NotBoot -> HsSrcFile
+ -- NB: Despite the fact that is_boot is a top-level parameter, we
+ -- don't actually know coming into this function what the HscSource
+ -- of the module in question is. This is because we may be processing
+ -- this module because another module in the graph imported it: in this
+ -- case, we know if it's a boot or not because of the {-# SOURCE #-}
+ -- annotation, but we don't know if it's a signature or a regular
+ -- module until we actually look it up on the filesystem.
+ let hsc_src = case is_boot of
+ IsBoot -> HsBootFile
+ _ | isHaskellSigFilename src_fn -> HsigFile
+ | otherwise -> HsSrcFile
when (mod_name /= wanted_mod) $
throwOneError $ mkPlainErrMsg dflags' mod_loc $
@@ -1976,7 +1950,6 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
ms_hspp_buf = Just buf,
ms_srcimps = srcimps,
ms_textual_imps = the_imps,
- ms_merge_imps = (False, []),
ms_hs_date = src_timestamp,
ms_iface_date = hi_timestamp,
ms_obj_date = obj_timestamp })))
@@ -2082,6 +2055,4 @@ cyclicModuleErr mss
ppr_ms :: ModSummary -> SDoc
ppr_ms ms = quotes (ppr (moduleName (ms_mod ms))) <+>
- case msHsFilePath ms of
- Just path -> parens (text path)
- Nothing -> empty
+ (parens (text (msHsFilePath ms)))
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 1bc37bd7aa..401f049f2b 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -99,12 +99,12 @@ import {- Kind parts of -} Type ( Kind )
import CoreLint ( lintInteractiveExpr )
import VarEnv ( emptyTidyEnv )
import THNames ( templateHaskellNames )
+import Panic
import ConLike
import GHC.Exts
#endif
-import Panic
import Module
import Packages
import RdrName
@@ -118,8 +118,7 @@ import TcRnDriver
import TcIface ( typecheckIface )
import TcRnMonad
import IfaceEnv ( initNameCache )
-import LoadIface ( ifaceStats, initExternalPackageState
- , findAndReadIface )
+import LoadIface ( ifaceStats, initExternalPackageState )
import PrelInfo
import MkIface
import Desugar
@@ -607,9 +606,6 @@ genericHscFrontend mod_summary =
genericHscFrontend' :: ModSummary -> Hsc FrontendResult
genericHscFrontend' mod_summary
- | ms_hsc_src mod_summary == HsBootMerge
- = FrontendInterface `fmap` hscMergeFrontEnd mod_summary
- | otherwise
= FrontendTypecheck `fmap` hscFileFrontEnd mod_summary
--------------------------------------------------------------
@@ -661,32 +657,9 @@ hscIncrementalCompile always_do_basic_recompilation_check m_tc_result
ms_hsc_src mod_summary == HsSrcFile
then finish hsc_env mod_summary tc_result mb_old_hash
else finishTypecheckOnly hsc_env mod_summary tc_result mb_old_hash
- FrontendInterface raw_iface ->
- finishMerge hsc_env mod_summary raw_iface mb_old_hash
liftIO $ hscMaybeWriteIface dflags (hm_iface hmi) no_change mod_summary
return (status, hmi)
--- Generates and writes out the final interface for an hs-boot merge.
-finishMerge :: HscEnv
- -> ModSummary
- -> ModIface
- -> Maybe Fingerprint
- -> Hsc (HscStatus, HomeModInfo, Bool)
-finishMerge hsc_env summary iface0 mb_old_hash = do
- MASSERT( ms_hsc_src summary == HsBootMerge )
- (iface, changed) <- liftIO $ mkIfaceDirect hsc_env mb_old_hash iface0
- details <- liftIO $ genModDetails hsc_env iface
- let dflags = hsc_dflags hsc_env
- hsc_status =
- case hscTarget dflags of
- HscNothing -> HscNotGeneratingCode
- _ -> HscUpdateBootMerge
- return (hsc_status,
- HomeModInfo{ hm_details = details,
- hm_iface = iface,
- hm_linkable = Nothing },
- changed)
-
-- Generates and writes out the final interface for a typecheck.
finishTypecheckOnly :: HscEnv
-> ModSummary
@@ -695,12 +668,12 @@ finishTypecheckOnly :: HscEnv
-> Hsc (HscStatus, HomeModInfo, Bool)
finishTypecheckOnly hsc_env summary tc_result mb_old_hash = do
let dflags = hsc_dflags hsc_env
- MASSERT( hscTarget dflags == HscNothing || ms_hsc_src summary == HsBootFile )
(iface, changed, details) <- liftIO $ hscSimpleIface hsc_env tc_result mb_old_hash
let hsc_status =
case (hscTarget dflags, ms_hsc_src summary) of
(HscNothing, _) -> HscNotGeneratingCode
(_, HsBootFile) -> HscUpdateBoot
+ (_, HsigFile) -> HscUpdateSig
_ -> panic "finishTypecheckOnly"
return (hsc_status,
HomeModInfo{ hm_details = details,
@@ -789,46 +762,10 @@ batchMsg hsc_env mod_index recomp mod_summary =
-- FrontEnds
--------------------------------------------------------------
--- | Given an 'HsBootMerge' 'ModSummary', merges all @hs-boot@ files
--- under this module name into a composite, publically visible 'ModIface'.
-hscMergeFrontEnd :: ModSummary -> Hsc ModIface
-hscMergeFrontEnd mod_summary = do
- hsc_env <- getHscEnv
- MASSERT( ms_hsc_src mod_summary == HsBootMerge )
- let dflags = hsc_dflags hsc_env
- -- TODO: actually merge in signatures from external packages.
- -- Grovel in HPT if necessary
- -- TODO: replace with 'computeInterface'
- let hpt = hsc_HPT hsc_env
- -- TODO multiple mods
- let name = moduleName (ms_mod mod_summary)
- mod = mkModule (thisPackage dflags) name
- is_boot = True
- iface0 <- case lookupHptByModule hpt mod of
- Just hm -> return (hm_iface hm)
- Nothing -> do
- mb_iface0 <- liftIO . initIfaceCheck hsc_env
- $ findAndReadIface (text "merge-requirements")
- mod is_boot
- case mb_iface0 of
- Succeeded (i, _) -> return i
- Failed err -> liftIO $ throwGhcExceptionIO
- (ProgramError (showSDoc dflags err))
- let iface = iface0 {
- mi_hsc_src = HsBootMerge,
- -- TODO: mkDependencies doublecheck
- mi_deps = (mi_deps iface0) {
- dep_mods = (name, is_boot)
- : dep_mods (mi_deps iface0)
- }
- }
- return iface
-
-- | Given a 'ModSummary', parses and typechecks it, returning the
-- 'TcGblEnv' resulting from type-checking.
hscFileFrontEnd :: ModSummary -> Hsc TcGblEnv
hscFileFrontEnd mod_summary = do
- MASSERT( ms_hsc_src mod_summary == HsBootFile || ms_hsc_src mod_summary == HsSrcFile )
hpm <- hscParse' mod_summary
hsc_env <- getHscEnv
tcg_env <- tcRnModule' hsc_env mod_summary False hpm
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index 362164eba4..cb0d2841b7 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -29,7 +29,7 @@ module HscTypes (
-- * Information about the module being compiled
-- (re-exported from DriverPhases)
- HscSource(..), isHsBoot, hscSourceString,
+ HscSource(..), isHsBootOrSig, hscSourceString,
-- * State relating to modules in this package
@@ -162,7 +162,7 @@ import PatSyn
import PrelNames ( gHC_PRIM, ioTyConName, printName, mkInteractiveModule )
import Packages hiding ( Version(..) )
import DynFlags
-import DriverPhases ( Phase, HscSource(..), isHsBoot, hscSourceString )
+import DriverPhases ( Phase, HscSource(..), isHsBootOrSig, hscSourceString )
import BasicTypes
import IfaceSyn
import CoreSyn ( CoreRule, CoreVect )
@@ -202,7 +202,7 @@ data HscStatus
= HscNotGeneratingCode
| HscUpToDate
| HscUpdateBoot
- | HscUpdateBootMerge
+ | HscUpdateSig
| HscRecomp CgGuts ModSummary
-- -----------------------------------------------------------------------------
@@ -2410,8 +2410,6 @@ data ModSummary
-- ^ Source imports of the module
ms_textual_imps :: [(Maybe FastString, Located ModuleName)],
-- ^ Non-source imports of the module from the module *text*
- ms_merge_imps :: (Bool, [Module]),
- -- ^ Non-textual imports computed for HsBootMerge
ms_hspp_file :: FilePath,
-- ^ Filename of preprocessed source file
ms_hspp_opts :: DynFlags,
@@ -2441,10 +2439,8 @@ ms_imps ms =
-- The ModLocation is stable over successive up-sweeps in GHCi, wheres
-- the ms_hs_date and imports can, of course, change
-msHsFilePath :: ModSummary -> Maybe FilePath
-msHsFilePath ms = ml_hs_file (ms_location ms)
-
-msHiFilePath, msObjFilePath :: ModSummary -> FilePath
+msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
+msHsFilePath ms = expectJust "msHsFilePath" (ml_hs_file (ms_location ms))
msHiFilePath ms = ml_hi_file (ms_location ms)
msObjFilePath ms = ml_obj_file (ms_location ms)
@@ -2459,10 +2455,7 @@ instance Outputable ModSummary where
text "ms_mod =" <+> ppr (ms_mod ms)
<> text (hscSourceString (ms_hsc_src ms)) <> comma,
text "ms_textual_imps =" <+> ppr (ms_textual_imps ms),
- text "ms_srcimps =" <+> ppr (ms_srcimps ms),
- if not (null (snd (ms_merge_imps ms)))
- then text "ms_merge_imps =" <+> ppr (ms_merge_imps ms)
- else empty]),
+ text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
char '}'
]
@@ -2470,20 +2463,29 @@ showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String
showModMsg dflags target recomp mod_summary
= showSDoc dflags $
hsep [text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' '),
- char '(',
- case msHsFilePath mod_summary of
- Just path -> text (normalise path) <> comma
- Nothing -> text "nothing" <> comma,
+ char '(', text (normalise $ msHsFilePath mod_summary) <> comma,
case target of
HscInterpreted | recomp
-> text "interpreted"
HscNothing -> text "nothing"
- _ -> text (normalise $ msObjFilePath mod_summary),
+ _ | HsigFile == ms_hsc_src mod_summary -> text "nothing"
+ | otherwise -> text (normalise $ msObjFilePath mod_summary),
char ')']
where
mod = moduleName (ms_mod mod_summary)
mod_str = showPpr dflags mod
- ++ hscSourceString (ms_hsc_src mod_summary)
+ ++ hscSourceString' dflags mod (ms_hsc_src mod_summary)
+
+-- | Variant of hscSourceString which prints more information for signatures.
+-- This can't live in DriverPhases because this would cause a module loop.
+hscSourceString' :: DynFlags -> ModuleName -> HscSource -> String
+hscSourceString' _ _ HsSrcFile = ""
+hscSourceString' _ _ HsBootFile = "[boot]"
+hscSourceString' dflags mod HsigFile =
+ "[" ++ (maybe "abstract sig"
+ (("sig of "++).showPpr dflags)
+ (getSigOf dflags mod)) ++ "]"
+ -- NB: -sig-of could be missing if we're just typechecking
{-
************************************************************************
diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs
index 3115179c2f..ccf8202847 100644
--- a/compiler/typecheck/TcBinds.hs
+++ b/compiler/typecheck/TcBinds.hs
@@ -21,7 +21,7 @@ import {-# SOURCE #-} TcExpr ( tcMonoExpr )
import {-# SOURCE #-} TcPatSyn ( tcInferPatSynDecl, tcCheckPatSynDecl, tcPatSynBuilderBind )
import DynFlags
import HsSyn
-import HscTypes( isHsBoot )
+import HscTypes( isHsBootOrSig )
import TcRnMonad
import TcEnv
import TcUnify
@@ -74,7 +74,7 @@ import Data.List (partition)
addTypecheckedBinds :: TcGblEnv -> [LHsBinds Id] -> TcGblEnv
addTypecheckedBinds tcg_env binds
- | isHsBoot (tcg_src tcg_env) = tcg_env
+ | isHsBootOrSig (tcg_src tcg_env) = tcg_env
-- Do not add the code for record-selector bindings
-- when compiling hs-boot files
| otherwise = tcg_env { tcg_binds = foldr unionBags
diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs
index ef0c4b6c8f..06cb42715a 100644
--- a/compiler/typecheck/TcInstDcls.hs
+++ b/compiler/typecheck/TcInstDcls.hs
@@ -49,7 +49,7 @@ import BasicTypes
import DynFlags
import ErrUtils
import FastString
-import HscTypes ( isHsBoot )
+import HscTypes ( isHsBootOrSig )
import Id
import MkId
import Name
@@ -441,7 +441,7 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls
typeable_err i =
setSrcSpan (getSrcSpan (iSpec i)) $
do env <- getGblEnv
- if isHsBoot (tcg_src env)
+ if isHsBootOrSig (tcg_src env)
then
do warn <- woptM Opt_WarnDerivingTypeable
when warn $ addWarnTc $ vcat
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 1987354dbd..1b2a8d993e 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -164,12 +164,8 @@ tcRnSignature dflags hsc_src
= do { tcg_env <- getGblEnv ;
case tcg_sig_of tcg_env of {
Just sof
- | hsc_src /= HsBootFile -> do
- { modname <- fmap moduleName getModule
- ; addErr (text "Found -sig-of entry for" <+> ppr modname
- <+> text "which is not hs-boot." $$
- text "Try removing" <+> ppr modname <+>
- text "from -sig-of")
+ | hsc_src /= HsigFile -> do
+ { addErr (ptext (sLit "Illegal -sig-of specified for non hsig"))
; return tcg_env
}
| otherwise -> do
@@ -183,7 +179,15 @@ tcRnSignature dflags hsc_src
, tcg_imports = tcg_imports tcg_env `plusImportAvails` avails
})
} ;
- Nothing -> return tcg_env
+ Nothing
+ | HsigFile <- hsc_src
+ , HscNothing <- hscTarget dflags -> do
+ { return tcg_env
+ }
+ | HsigFile <- hsc_src -> do
+ { addErr (ptext (sLit "Missing -sig-of for hsig"))
+ ; failM }
+ | otherwise -> return tcg_env
}
}
@@ -319,7 +323,7 @@ tcRnModuleTcRnM hsc_env hsc_src
-- Rename and type check the declarations
traceRn (text "rn1a") ;
- tcg_env <- if isHsBoot hsc_src then
+ tcg_env <- if isHsBootOrSig hsc_src then
tcRnHsBootDecls hsc_src local_decls
else
{-# SCC "tcRnSrcDecls" #-}
@@ -675,9 +679,9 @@ tcRnHsBootDecls hsc_src decls
-- are written into the interface file.
; let { type_env0 = tcg_type_env gbl_env
; type_env1 = extendTypeEnvWithIds type_env0 val_ids
- -- Don't add the dictionaries for non-recursive case, we don't
- -- actually want to /define/ the instance, just an export list
- ; type_env2 | Just _ <- tcg_impl_rdr_env gbl_env = type_env1
+ -- Don't add the dictionaries for hsig, we don't actually want
+ -- to /define/ the instance
+ ; type_env2 | HsigFile <- hsc_src = type_env1
| otherwise = extendTypeEnvWithIds type_env1 dfun_ids
; dfun_ids = map iDFunId inst_infos
}
@@ -687,9 +691,14 @@ tcRnHsBootDecls hsc_src decls
; traceTc "boot" (ppr lie); return gbl_env }
badBootDecl :: HscSource -> String -> Located decl -> TcM ()
-badBootDecl _hsc_src what (L loc _)
+badBootDecl hsc_src what (L loc _)
= addErrAt loc (char 'A' <+> text what
- <+> text "declaration is not (currently) allowed in a hs-boot file")
+ <+> ptext (sLit "declaration is not (currently) allowed in a")
+ <+> (case hsc_src of
+ HsBootFile -> ptext (sLit "hs-boot")
+ HsigFile -> ptext (sLit "hsig")
+ _ -> panic "badBootDecl: should be an hsig or hs-boot file")
+ <+> ptext (sLit "file"))
{-
Once we've typechecked the body of the module, we want to compare what
@@ -1064,7 +1073,7 @@ emptyRnEnv2 = mkRnEnv2 emptyInScopeSet
missingBootThing :: Bool -> Name -> String -> SDoc
missingBootThing is_boot name what
= quotes (ppr name) <+> ptext (sLit "is exported by the")
- <+> (if is_boot then ptext (sLit "hs-boot") else ptext (sLit "signature"))
+ <+> (if is_boot then ptext (sLit "hs-boot") else ptext (sLit "hsig"))
<+> ptext (sLit "file, but not")
<+> text what <+> ptext (sLit "the module")
@@ -1074,11 +1083,11 @@ bootMisMatch is_boot extra_info real_thing boot_thing
ptext (sLit "has conflicting definitions in the module"),
ptext (sLit "and its") <+>
(if is_boot then ptext (sLit "hs-boot file")
- else ptext (sLit "signature file")),
+ else ptext (sLit "hsig file")),
ptext (sLit "Main module:") <+> PprTyThing.pprTyThing real_thing,
(if is_boot
then ptext (sLit "Boot file: ")
- else ptext (sLit "Signature file: "))
+ else ptext (sLit "Hsig file: "))
<+> PprTyThing.pprTyThing boot_thing,
extra_info]
@@ -1086,7 +1095,7 @@ instMisMatch :: Bool -> ClsInst -> SDoc
instMisMatch is_boot inst
= hang (ppr inst)
2 (ptext (sLit "is defined in the") <+>
- (if is_boot then ptext (sLit "hs-boot") else ptext (sLit "signature"))
+ (if is_boot then ptext (sLit "hs-boot") else ptext (sLit "hsig"))
<+> ptext (sLit "file, but not in the module itself"))
{-
diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs
index 3ad4677742..5544254311 100644
--- a/compiler/typecheck/TcRnMonad.hs
+++ b/compiler/typecheck/TcRnMonad.hs
@@ -608,7 +608,7 @@ getInteractivePrintName :: TcRn Name
getInteractivePrintName = do { hsc <- getTopEnv; return (ic_int_print $ hsc_IC hsc) }
tcIsHsBootOrSig :: TcRn Bool
-tcIsHsBootOrSig = do { env <- getGblEnv; return (isHsBoot (tcg_src env)) }
+tcIsHsBootOrSig = do { env <- getGblEnv; return (isHsBootOrSig (tcg_src env)) }
tcSelfBootInfo :: TcRn SelfBootInfo
tcSelfBootInfo = do { env <- getGblEnv; return (tcg_self_boot env) }
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index f4cfa4f780..d81727a41d 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -341,7 +341,6 @@ data DsMetaVal
-- to have a TcGblEnv which is only defined here.
data FrontendResult
= FrontendTypecheck TcGblEnv
- | FrontendInterface ModIface
-- | 'TcGblEnv' describes the top-level of the module at the
-- point at which the typechecker is finished work.
diff --git a/ghc/Main.hs b/ghc/Main.hs
index 647bbadcf9..d14a897dc7 100644
--- a/ghc/Main.hs
+++ b/ghc/Main.hs
@@ -22,7 +22,7 @@ import CmdLineParser
-- Implementations of the various modes (--show-iface, mkdependHS. etc.)
import LoadIface ( showIface )
import HscMain ( newHscEnv )
-import DriverPipeline ( oneShot, compileFile, mergeRequirement )
+import DriverPipeline ( oneShot, compileFile )
import DriverMkDepend ( doMkDependHS )
#ifdef GHCI
import InteractiveUI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings )
@@ -157,7 +157,6 @@ main' postLoadMode dflags0 args flagWarnings = do
DoMake -> (CompManager, dflt_target, LinkBinary)
DoMkDependHS -> (MkDepend, dflt_target, LinkBinary)
DoAbiHash -> (OneShot, dflt_target, LinkBinary)
- DoMergeRequirements -> (OneShot, dflt_target, LinkBinary)
_ -> (OneShot, dflt_target, LinkBinary)
let dflags1 = case lang of
@@ -253,7 +252,6 @@ main' postLoadMode dflags0 args flagWarnings = do
DoInteractive -> ghciUI srcs Nothing
DoEval exprs -> ghciUI srcs $ Just $ reverse exprs
DoAbiHash -> abiHash (map fst srcs)
- DoMergeRequirements -> doMergeRequirements (map fst srcs)
ShowPackages -> liftIO $ showPackages dflags6
liftIO $ dumpFinalStats dflags6
@@ -459,16 +457,14 @@ data PostLoadMode
| DoEval [String] -- ghc -e foo -e bar => DoEval ["bar", "foo"]
| DoAbiHash -- ghc --abi-hash
| ShowPackages -- ghc --show-packages
- | DoMergeRequirements -- ghc --merge-requirements
doMkDependHSMode, doMakeMode, doInteractiveMode,
- doAbiHashMode, showPackagesMode, doMergeRequirementsMode :: Mode
+ doAbiHashMode, showPackagesMode :: Mode
doMkDependHSMode = mkPostLoadMode DoMkDependHS
doMakeMode = mkPostLoadMode DoMake
doInteractiveMode = mkPostLoadMode DoInteractive
doAbiHashMode = mkPostLoadMode DoAbiHash
showPackagesMode = mkPostLoadMode ShowPackages
-doMergeRequirementsMode = mkPostLoadMode DoMergeRequirements
showInterfaceMode :: FilePath -> Mode
showInterfaceMode fp = mkPostLoadMode (ShowInterface fp)
@@ -608,7 +604,6 @@ mode_flags =
, defFlag "C" (PassFlag (setMode (stopBeforeMode HCc)))
, defFlag "S" (PassFlag (setMode (stopBeforeMode (As False))))
, defFlag "-make" (PassFlag (setMode doMakeMode))
- , defFlag "-merge-requirements" (PassFlag (setMode doMergeRequirementsMode))
, defFlag "-interactive" (PassFlag (setMode doInteractiveMode))
, defFlag "-abi-hash" (PassFlag (setMode doAbiHashMode))
, defFlag "e" (SepArg (\s -> setMode (doEvalMode s) "-e"))
@@ -718,16 +713,6 @@ doMake srcs = do
when (failed ok_flag) (liftIO $ exitWith (ExitFailure 1))
return ()
--- ----------------------------------------------------------------------------
--- Run --merge-requirements mode
-
-doMergeRequirements :: [String] -> Ghc ()
-doMergeRequirements srcs = mapM_ doMergeRequirement srcs
-
-doMergeRequirement :: String -> Ghc ()
-doMergeRequirement src = do
- hsc_env <- getSession
- liftIO $ mergeRequirement hsc_env (mkModuleName src)
-- ---------------------------------------------------------------------------
-- --show-iface mode
diff --git a/testsuite/.gitignore b/testsuite/.gitignore
index 9c3f91f210..c2892e6014 100644
--- a/testsuite/.gitignore
+++ b/testsuite/.gitignore
@@ -634,7 +634,6 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk
/tests/driver/recomp013/C.hs
/tests/driver/recomp014/A.hs
/tests/driver/recomp014/A1.hs
-/tests/driver/recomp014/B.hs-boot
/tests/driver/recomp014/B.hsig
/tests/driver/recomp014/C.hs
/tests/driver/recomp014/recomp014
diff --git a/testsuite/tests/driver/dynamicToo/dynamicToo005/A005.hs-boot b/testsuite/tests/driver/dynamicToo/dynamicToo005/A005.hsig
index 75d621cfec..75d621cfec 100644
--- a/testsuite/tests/driver/dynamicToo/dynamicToo005/A005.hs-boot
+++ b/testsuite/tests/driver/dynamicToo/dynamicToo005/A005.hsig
diff --git a/testsuite/tests/driver/dynamicToo/dynamicToo005/Makefile b/testsuite/tests/driver/dynamicToo/dynamicToo005/Makefile
index a08827a92d..617510eec4 100644
--- a/testsuite/tests/driver/dynamicToo/dynamicToo005/Makefile
+++ b/testsuite/tests/driver/dynamicToo/dynamicToo005/Makefile
@@ -5,15 +5,11 @@ include $(TOP)/mk/test.mk
checkExists = [ -f $1 ] || echo $1 missing
.PHONY: dynamicToo005
-# Check that "-c -dynamic-too" works with signatures
+# Check that "-c -dynamic-too" works with .hsig
dynamicToo005:
"$(TEST_HC)" $(TEST_HC_OPTS) -dynamic-too -v0 \
-sig-of A005=base:Prelude \
- -c A005.hs-boot
- $(call checkExists,A005.o-boot)
- $(call checkExists,A005.hi-boot)
- "$(TEST_HC)" $(TEST_HC_OPTS) -dynamic-too -v0 \
- --merge-requirements A005
+ -c A005.hsig
$(call checkExists,A005.o)
$(call checkExists,A005.hi)
$(call checkExists,A005.dyn_o)
diff --git a/testsuite/tests/driver/dynamicToo/dynamicToo006/A.hs-boot b/testsuite/tests/driver/dynamicToo/dynamicToo006/A.hsig
index f79d5d334f..f79d5d334f 100644
--- a/testsuite/tests/driver/dynamicToo/dynamicToo006/A.hs-boot
+++ b/testsuite/tests/driver/dynamicToo/dynamicToo006/A.hsig
diff --git a/testsuite/tests/driver/dynamicToo/dynamicToo006/Makefile b/testsuite/tests/driver/dynamicToo/dynamicToo006/Makefile
index 6e025f8322..497f2c0942 100644
--- a/testsuite/tests/driver/dynamicToo/dynamicToo006/Makefile
+++ b/testsuite/tests/driver/dynamicToo/dynamicToo006/Makefile
@@ -11,10 +11,8 @@ dynamicToo006:
-sig-of A=base:Prelude \
--make B
$(call checkExists,A.o)
- $(call checkExists,A.o-boot)
$(call checkExists,B.o)
$(call checkExists,A.hi)
- $(call checkExists,A.hi-boot)
$(call checkExists,B.hi)
$(call checkExists,A.dyn_o)
$(call checkExists,B.dyn_o)
diff --git a/testsuite/tests/driver/recomp014/Makefile b/testsuite/tests/driver/recomp014/Makefile
deleted file mode 100644
index 00b2035206..0000000000
--- a/testsuite/tests/driver/recomp014/Makefile
+++ /dev/null
@@ -1,33 +0,0 @@
-TOP=../../..
-include $(TOP)/mk/boilerplate.mk
-include $(TOP)/mk/test.mk
-
-# -fforce-recomp makes lots of driver tests trivially pass, so we
-# filter it out from $(TEST_HC_OPTS).
-TEST_HC_OPTS_NO_RECOMP = $(filter-out -fforce-recomp,$(TEST_HC_OPTS))
-
-# Recompilation tests
-
-clean:
- rm -f *.o *.hi
-
-recomp014: clean
- echo 'module A where a = False' > A.hs
- echo 'module A1 where a = False' > A1.hs
- echo 'module B where a :: Bool' > B.hs-boot
- echo 'first run'
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c A.hs
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c A1.hs
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c B.hs-boot -sig-of "B is main:A"
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) --merge-requirements B
- echo 'import B; main = print a' > C.hs
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c C.hs
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c C.hs
- echo 'second run'
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c B.hs-boot -sig-of "B is main:A1"
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) --merge-requirements B
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c C.hs
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) A1.o C.o -o recomp014
- ./recomp014
-
-.PHONY: clean recomp014
diff --git a/testsuite/tests/driver/recomp014/all.T b/testsuite/tests/driver/recomp014/all.T
deleted file mode 100644
index affccd2f7f..0000000000
--- a/testsuite/tests/driver/recomp014/all.T
+++ /dev/null
@@ -1,4 +0,0 @@
-test('recomp014',
- [ clean_cmd('$MAKE -s clean') ],
- run_command,
- ['$MAKE -s --no-print-directory recomp014'])
diff --git a/testsuite/tests/driver/recomp014/recomp014.stdout b/testsuite/tests/driver/recomp014/recomp014.stdout
deleted file mode 100644
index 7d540716f0..0000000000
--- a/testsuite/tests/driver/recomp014/recomp014.stdout
+++ /dev/null
@@ -1,4 +0,0 @@
-first run
-compilation IS NOT required
-second run
-False
diff --git a/testsuite/tests/driver/sigof01/B.hs-boot b/testsuite/tests/driver/sigof01/B.hsig
index 289d3bcb18..289d3bcb18 100644
--- a/testsuite/tests/driver/sigof01/B.hs-boot
+++ b/testsuite/tests/driver/sigof01/B.hsig
diff --git a/testsuite/tests/driver/sigof01/Makefile b/testsuite/tests/driver/sigof01/Makefile
index 8bed672c07..84dfc33a9f 100644
--- a/testsuite/tests/driver/sigof01/Makefile
+++ b/testsuite/tests/driver/sigof01/Makefile
@@ -11,8 +11,7 @@ sigof01:
rm -rf tmp_sigof01
mkdir tmp_sigof01
'$(TEST_HC)' $(S01_OPTS) -c A.hs
- '$(TEST_HC)' $(S01_OPTS) -c B.hs-boot -sig-of "B is main:A"
- '$(TEST_HC)' $(S01_OPTS) --merge-requirements B
+ '$(TEST_HC)' $(S01_OPTS) -c B.hsig -sig-of "B is main:A"
'$(TEST_HC)' $(S01_OPTS) -c Main.hs
'$(TEST_HC)' $(S01_OPTS) tmp_sigof01/A.o tmp_sigof01/Main.o -o tmp_sigof01/Main
tmp_sigof01/Main
@@ -22,9 +21,3 @@ sigof01m:
mkdir tmp_sigof01m
'$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -outputdir tmp_sigof01m --make Main.hs -sig-of "B is main:A" -o tmp_sigof01m/Main
tmp_sigof01m/Main
-
-sigof01i:
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) --interactive -v0 -ignore-dot-ghci Main.hs -sig-of "B is main:A" < sigof01i.script
-
-sigof01i2:
- '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) --interactive -v0 -ignore-dot-ghci -sig-of "B is main:A" < sigof01i2.script
diff --git a/testsuite/tests/driver/sigof01/all.T b/testsuite/tests/driver/sigof01/all.T
index 5606127f06..d0cdc3c02c 100644
--- a/testsuite/tests/driver/sigof01/all.T
+++ b/testsuite/tests/driver/sigof01/all.T
@@ -7,13 +7,3 @@ test('sigof01m',
[ clean_cmd('rm -rf tmp_sigof01m') ],
run_command,
['$MAKE -s --no-print-directory sigof01m'])
-
-test('sigof01i',
- [],
- run_command,
- ['$MAKE -s --no-print-directory sigof01i'])
-
-test('sigof01i2',
- [],
- run_command,
- ['$MAKE -s --no-print-directory sigof01i2'])
diff --git a/testsuite/tests/driver/sigof01/sigof01i.script b/testsuite/tests/driver/sigof01/sigof01i.script
deleted file mode 100644
index ba2906d066..0000000000
--- a/testsuite/tests/driver/sigof01/sigof01i.script
+++ /dev/null
@@ -1 +0,0 @@
-main
diff --git a/testsuite/tests/driver/sigof01/sigof01i.stdout b/testsuite/tests/driver/sigof01/sigof01i.stdout
deleted file mode 100644
index bb614cd2a0..0000000000
--- a/testsuite/tests/driver/sigof01/sigof01i.stdout
+++ /dev/null
@@ -1,3 +0,0 @@
-False
-T
-True
diff --git a/testsuite/tests/driver/sigof01/sigof01i2.script b/testsuite/tests/driver/sigof01/sigof01i2.script
deleted file mode 100644
index 3a91e377a3..0000000000
--- a/testsuite/tests/driver/sigof01/sigof01i2.script
+++ /dev/null
@@ -1,3 +0,0 @@
-:load B
-:browse B
-:issafe
diff --git a/testsuite/tests/driver/sigof01/sigof01i2.stdout b/testsuite/tests/driver/sigof01/sigof01i2.stdout
deleted file mode 100644
index 1ee81c10d2..0000000000
--- a/testsuite/tests/driver/sigof01/sigof01i2.stdout
+++ /dev/null
@@ -1,9 +0,0 @@
-class Foo a where
- foo :: a -> a
- {-# MINIMAL foo #-}
-data T = A.T
-mkT :: T
-x :: Bool
-Trust type is (Module: Safe, Package: trusted)
-Package Trust: Off
-B is trusted!
diff --git a/testsuite/tests/driver/sigof01/sigof01m.stdout b/testsuite/tests/driver/sigof01/sigof01m.stdout
index 35190ae143..a7fdd8298e 100644
--- a/testsuite/tests/driver/sigof01/sigof01m.stdout
+++ b/testsuite/tests/driver/sigof01/sigof01m.stdout
@@ -1,7 +1,6 @@
-[1 of 4] Compiling A ( A.hs, tmp_sigof01m/A.o )
-[2 of 4] Compiling B[boot] ( B.hs-boot, tmp_sigof01m/B.o-boot )
-[3 of 4] Compiling B[merge] ( B.hi, tmp_sigof01m/B.o )
-[4 of 4] Compiling Main ( Main.hs, tmp_sigof01m/Main.o )
+[1 of 3] Compiling A ( A.hs, tmp_sigof01m/A.o )
+[2 of 3] Compiling B[sig of A] ( B.hsig, nothing )
+[3 of 3] Compiling Main ( Main.hs, tmp_sigof01m/Main.o )
Linking tmp_sigof01m/Main ...
False
T
diff --git a/testsuite/tests/driver/sigof02/Makefile b/testsuite/tests/driver/sigof02/Makefile
index aebff03151..8f153f44ce 100644
--- a/testsuite/tests/driver/sigof02/Makefile
+++ b/testsuite/tests/driver/sigof02/Makefile
@@ -11,13 +11,11 @@ sigof02:
rm -rf tmp_sigof02
mkdir tmp_sigof02
'$(GHC_PKG)' field containers key | sed 's/^.*: *//' > tmp_sigof02/containers
- '$(TEST_HC)' $(S02_OPTS) -c Map.hs-boot -sig-of "Map is `cat tmp_sigof02/containers`:Data.Map.Strict"
- '$(TEST_HC)' $(S02_OPTS) --merge-requirements Map
+ '$(TEST_HC)' $(S02_OPTS) -c Map.hsig -sig-of "Map is `cat tmp_sigof02/containers`:Data.Map.Strict"
'$(TEST_HC)' $(S02_OPTS) -c Main.hs
'$(TEST_HC)' $(S02_OPTS) -package containers tmp_sigof02/Main.o -o tmp_sigof02/StrictMain
! ./tmp_sigof02/StrictMain
- '$(TEST_HC)' $(S02_OPTS) -c Map.hs-boot -sig-of "Map is `cat tmp_sigof02/containers`:Data.Map.Lazy"
- '$(TEST_HC)' $(S02_OPTS) --merge-requirements Map
+ '$(TEST_HC)' $(S02_OPTS) -c Map.hsig -sig-of "Map is `cat tmp_sigof02/containers`:Data.Map.Lazy"
'$(TEST_HC)' $(S02_OPTS) -c Main.hs
'$(TEST_HC)' $(S02_OPTS) -package containers tmp_sigof02/Main.o -o tmp_sigof02/LazyMain
./tmp_sigof02/LazyMain
@@ -26,8 +24,7 @@ S02T_OPTS=$(TEST_HC_OPTS_NO_RECOMP) -fno-code -fwrite-interface -outputdir tmp_s
sigof02t:
rm -rf tmp_sigof02t
mkdir tmp_sigof02t
- '$(TEST_HC)' $(S02T_OPTS) -c Map.hs-boot
- '$(TEST_HC)' $(S02T_OPTS) --merge-requirements Map
+ '$(TEST_HC)' $(S02T_OPTS) -c Map.hsig
'$(TEST_HC)' $(S02T_OPTS) -c Main.hs
S02M_OPTS=$(TEST_HC_OPTS_NO_RECOMP) -outputdir tmp_sigof02m
@@ -50,10 +47,8 @@ sigof02d:
rm -rf tmp_sigof02d
mkdir tmp_sigof02d
'$(GHC_PKG)' field containers key | sed 's/^.*: *//' > tmp_sigof02d/containers
- '$(TEST_HC)' $(S02D_OPTS) -c Map.hs-boot -sig-of "Map is `cat tmp_sigof02d/containers`:Data.Map.Lazy, MapAsSet is `cat tmp_sigof02d/containers`:Data.Map.Lazy"
- '$(TEST_HC)' $(S02D_OPTS) --merge-requirements Map
- '$(TEST_HC)' $(S02D_OPTS) -c MapAsSet.hs-boot -sig-of "Map is `cat tmp_sigof02d/containers`:Data.Map.Lazy, MapAsSet is `cat tmp_sigof02d/containers`:Data.Map.Lazy"
- '$(TEST_HC)' $(S02D_OPTS) --merge-requirements MapAsSet
+ '$(TEST_HC)' $(S02D_OPTS) -c Map.hsig -sig-of "Map is `cat tmp_sigof02d/containers`:Data.Map.Lazy, MapAsSet is `cat tmp_sigof02d/containers`:Data.Map.Lazy"
+ '$(TEST_HC)' $(S02D_OPTS) -c MapAsSet.hsig -sig-of "Map is `cat tmp_sigof02d/containers`:Data.Map.Lazy, MapAsSet is `cat tmp_sigof02d/containers`:Data.Map.Lazy"
'$(TEST_HC)' $(S02D_OPTS) -c Double.hs
'$(TEST_HC)' $(S02D_OPTS) -package containers tmp_sigof02d/Main.o -o tmp_sigof02d/Double
./tmp_sigof02d/Double
@@ -62,10 +57,8 @@ S02DT_OPTS=$(TEST_HC_OPTS_NO_RECOMP) -outputdir tmp_sigof02dt -i -itmp_sigof02dt
sigof02dt:
rm -rf tmp_sigof02dt
mkdir tmp_sigof02dt
- '$(TEST_HC)' $(S02DT_OPTS) -c Map.hs-boot
- '$(TEST_HC)' $(S02DT_OPTS) --merge-requirements Map
- '$(TEST_HC)' $(S02DT_OPTS) -c MapAsSet.hs-boot
- '$(TEST_HC)' $(S02DT_OPTS) --merge-requirements MapAsSet
+ '$(TEST_HC)' $(S02DT_OPTS) -c Map.hsig
+ '$(TEST_HC)' $(S02DT_OPTS) -c MapAsSet.hsig
! '$(TEST_HC)' $(S02DT_OPTS) -c Double.hs
sigof02dm:
diff --git a/testsuite/tests/driver/sigof02/Map.hs-boot b/testsuite/tests/driver/sigof02/Map.hsig
index cd094df17f..cd094df17f 100644
--- a/testsuite/tests/driver/sigof02/Map.hs-boot
+++ b/testsuite/tests/driver/sigof02/Map.hsig
diff --git a/testsuite/tests/driver/sigof02/MapAsSet.hs-boot b/testsuite/tests/driver/sigof02/MapAsSet.hsig
index 1defbc7717..1defbc7717 100644
--- a/testsuite/tests/driver/sigof02/MapAsSet.hs-boot
+++ b/testsuite/tests/driver/sigof02/MapAsSet.hsig
diff --git a/testsuite/tests/driver/sigof02/sigof02dm.stdout b/testsuite/tests/driver/sigof02/sigof02dm.stdout
index a3a5fa8b4b..14ee83789b 100644
--- a/testsuite/tests/driver/sigof02/sigof02dm.stdout
+++ b/testsuite/tests/driver/sigof02/sigof02dm.stdout
@@ -1,8 +1,6 @@
-[1 of 5] Compiling MapAsSet[boot] ( MapAsSet.hs-boot, tmp_sigof02dm/MapAsSet.o-boot )
-[2 of 5] Compiling MapAsSet[merge] ( MapAsSet.hi, tmp_sigof02dm/MapAsSet.o )
-[3 of 5] Compiling Map[boot] ( Map.hs-boot, tmp_sigof02dm/Map.o-boot )
-[4 of 5] Compiling Map[merge] ( Map.hi, tmp_sigof02dm/Map.o )
-[5 of 5] Compiling Main ( Double.hs, tmp_sigof02dm/Main.o )
+[1 of 3] Compiling MapAsSet[sig of Data.Map.Lazy] ( MapAsSet.hsig, nothing )
+[2 of 3] Compiling Map[sig of Data.Map.Lazy] ( Map.hsig, nothing )
+[3 of 3] Compiling Main ( Double.hs, tmp_sigof02dm/Main.o )
Linking tmp_sigof02dm/Double ...
False
fromList [0,6]
diff --git a/testsuite/tests/driver/sigof02/sigof02m.stdout b/testsuite/tests/driver/sigof02/sigof02m.stdout
index 4c80fed188..41cc4a7bb3 100644
--- a/testsuite/tests/driver/sigof02/sigof02m.stdout
+++ b/testsuite/tests/driver/sigof02/sigof02m.stdout
@@ -1,10 +1,8 @@
-[1 of 3] Compiling Map[boot] ( Map.hs-boot, tmp_sigof02m/Map.o-boot )
-[2 of 3] Compiling Map[merge] ( Map.hi, tmp_sigof02m/Map.o )
-[3 of 3] Compiling Main ( Main.hs, tmp_sigof02m/Main.o )
+[1 of 2] Compiling Map[sig of Data.Map.Strict] ( Map.hsig, nothing )
+[2 of 2] Compiling Main ( Main.hs, tmp_sigof02m/Main.o )
Linking tmp_sigof02m/StrictMain ...
-[1 of 3] Compiling Map[boot] ( Map.hs-boot, tmp_sigof02m/Map.o-boot ) [sig-of changed]
-[2 of 3] Compiling Map[merge] ( Map.hi, tmp_sigof02m/Map.o ) [sig-of changed]
-[3 of 3] Compiling Main ( Main.hs, tmp_sigof02m/Main.o ) [Map changed]
+[1 of 2] Compiling Map[sig of Data.Map.Lazy] ( Map.hsig, nothing ) [sig-of changed]
+[2 of 2] Compiling Main ( Main.hs, tmp_sigof02m/Main.o ) [Map changed]
Linking tmp_sigof02m/LazyMain ...
False
[(0,"foo"),(6,"foo")]
diff --git a/testsuite/tests/driver/sigof03/ASig1.hs-boot b/testsuite/tests/driver/sigof03/ASig1.hsig
index 9428e0cf04..9428e0cf04 100644
--- a/testsuite/tests/driver/sigof03/ASig1.hs-boot
+++ b/testsuite/tests/driver/sigof03/ASig1.hsig
diff --git a/testsuite/tests/driver/sigof03/ASig2.hs-boot b/testsuite/tests/driver/sigof03/ASig2.hsig
index 6f278b0a89..6f278b0a89 100644
--- a/testsuite/tests/driver/sigof03/ASig2.hs-boot
+++ b/testsuite/tests/driver/sigof03/ASig2.hsig
diff --git a/testsuite/tests/driver/sigof03/Makefile b/testsuite/tests/driver/sigof03/Makefile
index f39d16ea60..03a0b9b2da 100644
--- a/testsuite/tests/driver/sigof03/Makefile
+++ b/testsuite/tests/driver/sigof03/Makefile
@@ -11,9 +11,8 @@ sigof03:
rm -rf tmp_sigof03
mkdir tmp_sigof03
'$(TEST_HC)' $(S03_OPTS) -c A.hs
- '$(TEST_HC)' $(S03_OPTS) -c ASig1.hs-boot -sig-of "ASig1 is main:A, ASig2 is main:A"
- '$(TEST_HC)' $(S03_OPTS) -c ASig2.hs-boot -sig-of "ASig1 is main:A, ASig2 is main:A"
- '$(TEST_HC)' $(S03_OPTS) --merge-requirements ASig1 ASig2
+ '$(TEST_HC)' $(S03_OPTS) -c ASig1.hsig -sig-of "ASig1 is main:A, ASig2 is main:A"
+ '$(TEST_HC)' $(S03_OPTS) -c ASig2.hsig -sig-of "ASig1 is main:A, ASig2 is main:A"
'$(TEST_HC)' $(S03_OPTS) -c Main.hs
'$(TEST_HC)' $(S03_OPTS) tmp_sigof03/A.o tmp_sigof03/Main.o -o tmp_sigof03/Main
./tmp_sigof03/Main
diff --git a/testsuite/tests/driver/sigof04/Makefile b/testsuite/tests/driver/sigof04/Makefile
index b489174410..f013b0c202 100644
--- a/testsuite/tests/driver/sigof04/Makefile
+++ b/testsuite/tests/driver/sigof04/Makefile
@@ -11,4 +11,4 @@ clean:
sigof04:
'$(GHC_PKG)' field containers key | sed 's/^.*: *//' > containers
- ! '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c Sig.hs-boot -sig-of "Sig is `cat containers`:Data.Map.Strict"
+ ! '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -c Sig.hsig -sig-of "Sig is `cat containers`:Data.Map.Strict"
diff --git a/testsuite/tests/driver/sigof04/Sig.hs-boot b/testsuite/tests/driver/sigof04/Sig.hsig
index 3110f28fff..3110f28fff 100644
--- a/testsuite/tests/driver/sigof04/Sig.hs-boot
+++ b/testsuite/tests/driver/sigof04/Sig.hsig
diff --git a/testsuite/tests/driver/sigof04/sigof04.stderr b/testsuite/tests/driver/sigof04/sigof04.stderr
index 2c2e0c39fc..4be1bfd3e5 100644
--- a/testsuite/tests/driver/sigof04/sigof04.stderr
+++ b/testsuite/tests/driver/sigof04/sigof04.stderr
@@ -1,3 +1,3 @@
-
-<no location info>: error:
- ‘insert’ is exported by the signature file, but not exported by the module
+
+<no location info>:
+ ‘insert’ is exported by the hsig file, but not exported by the module
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index ed0c8e1f19..8acb9a3fe9 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -357,7 +357,7 @@ test('tc262', normal, compile, [''])
test('tc263',
extra_clean(['Tc263_Help.o','Tc263_Help.hi']),
multimod_compile, ['tc263','-v0'])
-test('tc264', normal, multimod_compile, ['tc264.hs-boot', '-sig-of "ShouldCompile is base:Data.STRef"'])
+test('tc264', normal, multimod_compile, ['tc264.hsig', '-sig-of "ShouldCompile is base:Data.STRef"'])
test('tc265', compile_timeout_multiplier(0.01), compile, [''])
test('GivenOverlapping', normal, compile, [''])
diff --git a/testsuite/tests/typecheck/should_compile/tc264.hs-boot b/testsuite/tests/typecheck/should_compile/tc264.hsig
index 0bfdb2b9f4..0bfdb2b9f4 100644
--- a/testsuite/tests/typecheck/should_compile/tc264.hs-boot
+++ b/testsuite/tests/typecheck/should_compile/tc264.hsig
diff --git a/testsuite/tests/typecheck/should_compile/tc264.stderr b/testsuite/tests/typecheck/should_compile/tc264.stderr
index e3d0e175f8..4eb1124cad 100644
--- a/testsuite/tests/typecheck/should_compile/tc264.stderr
+++ b/testsuite/tests/typecheck/should_compile/tc264.stderr
@@ -1 +1 @@
-[1 of 1] Compiling ShouldCompile[boot] ( tc264.hs-boot, tc264.o )
+[1 of 1] Compiling ShouldCompile[sig of Data.STRef] ( tc264.hsig, nothing )
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index c2ec10526f..9f0434e1ae 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -242,10 +242,10 @@ test('tcfail215', normal, compile_fail, [''])
test('tcfail216', normal, compile_fail, [''])
test('tcfail217', normal, compile_fail, [''])
test('tcfail218', normal, compile_fail, [''])
-test('tcfail219', normal, multimod_compile_fail, ['tcfail219.hs-boot', '-sig-of "ShouldFail is base:Data.Bool"'])
-test('tcfail220', normal, multimod_compile_fail, ['tcfail220.hs-boot', '-sig-of "ShouldFail is base:Prelude"'])
-test('tcfail221', normal, multimod_compile_fail, ['tcfail221.hs-boot', '-sig-of "ShouldFail is base:Prelude"'])
-test('tcfail222', normal, multimod_compile_fail, ['tcfail222.hs-boot', '-sig-of "ShouldFail is base:Data.STRef"'])
+test('tcfail219', normal, multimod_compile_fail, ['tcfail219.hsig', '-sig-of "ShouldFail is base:Data.Bool"'])
+test('tcfail220', normal, multimod_compile_fail, ['tcfail220.hsig', '-sig-of "ShouldFail is base:Prelude"'])
+test('tcfail221', normal, multimod_compile_fail, ['tcfail221.hsig', '-sig-of "ShouldFail is base:Prelude"'])
+test('tcfail222', normal, multimod_compile_fail, ['tcfail222.hsig', '-sig-of "ShouldFail is base:Data.STRef"'])
test('tcfail223', normal, compile_fail, [''])
test('SilentParametersOverlapping', normal, compile, [''])
diff --git a/testsuite/tests/typecheck/should_fail/tcfail219.hs-boot b/testsuite/tests/typecheck/should_fail/tcfail219.hsig
index ec6d6076ab..ec6d6076ab 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail219.hs-boot
+++ b/testsuite/tests/typecheck/should_fail/tcfail219.hsig
diff --git a/testsuite/tests/typecheck/should_fail/tcfail219.stderr b/testsuite/tests/typecheck/should_fail/tcfail219.stderr
index d364137c08..53a7edebe0 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail219.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail219.stderr
@@ -1,4 +1,3 @@
-[1 of 1] Compiling ShouldFail[boot] ( tcfail219.hs-boot, tcfail219.o )
+[1 of 1] Compiling ShouldFail[sig of Data.Bool] ( tcfail219.hsig, nothing )
-tcfail219.hs-boot:1:1: error:
- Not in scope: type constructor or class ‘Booly’
+tcfail219.hsig:1:1: Not in scope: type constructor or class ‘Booly’
diff --git a/testsuite/tests/typecheck/should_fail/tcfail220.hs-boot b/testsuite/tests/typecheck/should_fail/tcfail220.hsig
index c9e80e3da2..c9e80e3da2 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail220.hs-boot
+++ b/testsuite/tests/typecheck/should_fail/tcfail220.hsig
diff --git a/testsuite/tests/typecheck/should_fail/tcfail220.stderr b/testsuite/tests/typecheck/should_fail/tcfail220.stderr
index e8d3c810ff..d78fa6d83e 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail220.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail220.stderr
@@ -1,9 +1,9 @@
-[1 of 1] Compiling ShouldFail[boot] ( tcfail220.hs-boot, tcfail220.o )
+[1 of 1] Compiling ShouldFail[sig of Prelude] ( tcfail220.hsig, nothing )
-tcfail220.hs-boot:4:1: error:
+tcfail220.hsig:4:1: error:
Type constructor ‘Either’ has conflicting definitions in the module
- and its signature file
+ and its hsig file
Main module: data Either a b = Left a | Right b
- Signature file: type role Either representational phantom phantom
- data Either a b c = Left a
+ Hsig file: type role Either representational phantom phantom
+ data Either a b c = Left a
The types have different kinds
diff --git a/testsuite/tests/typecheck/should_fail/tcfail221.hs-boot b/testsuite/tests/typecheck/should_fail/tcfail221.hsig
index a60c1a0d80..a60c1a0d80 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail221.hs-boot
+++ b/testsuite/tests/typecheck/should_fail/tcfail221.hsig
diff --git a/testsuite/tests/typecheck/should_fail/tcfail221.stderr b/testsuite/tests/typecheck/should_fail/tcfail221.stderr
index aef6c81a79..8781bd056e 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail221.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail221.stderr
@@ -1,6 +1,6 @@
-[1 of 1] Compiling ShouldFail[boot] ( tcfail221.hs-boot, tcfail221.o )
+[1 of 1] Compiling ShouldFail[sig of Prelude] ( tcfail221.hsig, nothing )
-tcfail221.hs-boot:2:10: error:
+tcfail221.hsig:2:10:
Duplicate instance declarations:
- instance Show Int -- Defined at tcfail221.hs-boot:2:10
- instance Show Int -- Defined at tcfail221.hs-boot:3:10
+ instance Show Int -- Defined at tcfail221.hsig:2:10
+ instance Show Int -- Defined at tcfail221.hsig:3:10
diff --git a/testsuite/tests/typecheck/should_fail/tcfail222.hs-boot b/testsuite/tests/typecheck/should_fail/tcfail222.hsig
index e83f4e3b83..e83f4e3b83 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail222.hs-boot
+++ b/testsuite/tests/typecheck/should_fail/tcfail222.hsig
diff --git a/testsuite/tests/typecheck/should_fail/tcfail222.stderr b/testsuite/tests/typecheck/should_fail/tcfail222.stderr
index 3f1466fede..1293b787a0 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail222.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail222.stderr
@@ -1,4 +1,4 @@
-[1 of 1] Compiling ShouldFail[boot] ( tcfail222.hs-boot, tcfail222.o )
-
-<no location info>: error:
- ‘newSTRef’ is exported by the signature file, but not exported by the module
+[1 of 1] Compiling ShouldFail[sig of Data.STRef] ( tcfail222.hsig, nothing )
+
+<no location info>:
+ ‘newSTRef’ is exported by the hsig file, but not exported by the module
diff --git a/utils/ghctags/Main.hs b/utils/ghctags/Main.hs
index 16b2e95e57..cfc795601d 100644
--- a/utils/ghctags/Main.hs
+++ b/utils/ghctags/Main.hs
@@ -224,9 +224,9 @@ fileTarget filename = Target (TargetFile filename Nothing) True Nothing
graphData :: ModuleGraph -> (Maybe Handle, Maybe Handle) -> Ghc ()
graphData graph handles = do
mapM_ foundthings graph
- where foundthings ms
- | Just filename <- msHsFilePath ms =
- let modname = moduleName $ ms_mod ms
+ where foundthings ms =
+ let filename = msHsFilePath ms
+ modname = moduleName $ ms_mod ms
in handleSourceError (\e -> do
printException e
liftIO $ exitWith (ExitFailure 1)) $
@@ -238,7 +238,6 @@ graphData graph handles = do
liftIO (writeTagsData handles =<< fileData filename modname s)
_otherwise ->
liftIO $ exitWith (ExitFailure 1)
- | otherwise = return ()
fileData :: FileName -> ModuleName -> RenamedSource -> IO FileData
fileData filename modname (group, _imports, _lie, _doc) = do
diff --git a/utils/haddock b/utils/haddock
-Subproject 83a9e9d2c7f0debec9d56e8b3b7cc8a8eb73361
+Subproject e763c004c8eb067ed0ef510fda9cb4ab102ea6a