Skip to content

Commit

Permalink
Revert "Unify hsig and hs-boot; add preliminary "hs-boot" merging."
Browse files Browse the repository at this point in the history
Summary:
This reverts commit 06d46b1.

This also has a Haddock submodule update.

Test Plan: validate

Reviewers: simonpj, austin, bgamari

Subscribers: thomie

Differential Revision: https://phabricator.haskell.org/D1475
  • Loading branch information
ezyang committed Nov 16, 2015
1 parent 9193629 commit ac1a379
Show file tree
Hide file tree
Showing 58 changed files with 232 additions and 481 deletions.
2 changes: 1 addition & 1 deletion compiler/deSugar/Desugar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
2 changes: 1 addition & 1 deletion compiler/iface/LoadIface.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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

{-
Expand Down
47 changes: 7 additions & 40 deletions compiler/iface/MkIface.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ module MkIface (
-- including computing version information

mkIfaceTc,
mkIfaceDirect,

writeIfaceFile, -- Write the interface file

Expand Down Expand Up @@ -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').
Expand Down Expand Up @@ -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

Expand All @@ -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
Expand All @@ -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
Expand Down
6 changes: 1 addition & 5 deletions compiler/main/DriverMkDepend.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down Expand Up @@ -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
Expand Down
80 changes: 49 additions & 31 deletions compiler/main/DriverPhases.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@
-----------------------------------------------------------------------------

module DriverPhases (
HscSource(..), isHsBoot, hscSourceString,
HscSource(..), isHsBootOrSig, hscSourceString,
Phase(..),
happensBefore, eqPhase, anyHsc, isStopLn,
startPhase,
Expand All @@ -22,10 +22,12 @@ module DriverPhases (
isCishSuffix,
isDynLibSuffix,
isHaskellUserSrcSuffix,
isHaskellSigSuffix,
isSourceSuffix,

isHaskellishFilename,
isHaskellSrcFilename,
isHaskellSigFilename,
isObjectFilename,
isCishFilename,
isDynLibFilename,
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand All @@ -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.
Expand All @@ -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
Expand All @@ -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
Expand All @@ -317,14 +334,15 @@ 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)
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)
Expand Down
Loading

0 comments on commit ac1a379

Please sign in to comment.