summaryrefslogtreecommitdiff
path: root/compiler/main
diff options
context:
space:
mode:
authorIavor S. Diatchki <iavor.diatchki@gmail.com>2014-07-19 14:29:57 -0700
committerIavor S. Diatchki <iavor.diatchki@gmail.com>2014-07-19 14:29:57 -0700
commit524634641c61ab42c555452f6f87119b27f6c331 (patch)
treef78d17bb6b09fb3b2e22cb4d93c2a3d45accc2d9 /compiler/main
parent79ad1d20c5500e17ce5daaf93b171131669bddad (diff)
parentc41b716d82b1722f909979d02a76e21e9b68886c (diff)
downloadhaskell-wip/ext-solver.tar.gz
Merge branch 'master' into wip/ext-solverwip/ext-solver
Diffstat (limited to 'compiler/main')
-rw-r--r--compiler/main/BreakArray.hs2
-rw-r--r--compiler/main/CmdLineParser.hs2
-rw-r--r--compiler/main/CodeOutput.lhs10
-rw-r--r--compiler/main/DriverMkDepend.hs2
-rw-r--r--compiler/main/DriverPhases.hs18
-rw-r--r--compiler/main/DriverPipeline.hs80
-rw-r--r--compiler/main/DynFlags.hs59
-rw-r--r--compiler/main/DynFlags.hs-boot3
-rw-r--r--compiler/main/DynamicLoading.hs2
-rw-r--r--compiler/main/ErrUtils.lhs1
-rw-r--r--compiler/main/Finder.lhs22
-rw-r--r--compiler/main/GHC.hs45
-rw-r--r--compiler/main/GhcMake.hs2
-rw-r--r--compiler/main/GhcMonad.hs1
-rw-r--r--compiler/main/HeaderInfo.hs6
-rw-r--r--compiler/main/Hooks.lhs2
-rw-r--r--compiler/main/HscMain.hs95
-rw-r--r--compiler/main/HscTypes.lhs92
-rw-r--r--compiler/main/InteractiveEval.hs2
-rw-r--r--compiler/main/InteractiveEvalTypes.hs2
-rw-r--r--compiler/main/PackageConfig.hs17
-rw-r--r--compiler/main/Packages.lhs24
-rw-r--r--compiler/main/PlatformConstants.hs2
-rw-r--r--compiler/main/PprTyThing.hs358
-rw-r--r--compiler/main/StaticFlags.hs3
-rw-r--r--compiler/main/SysTools.lhs19
-rw-r--r--compiler/main/TidyPgm.lhs63
27 files changed, 389 insertions, 545 deletions
diff --git a/compiler/main/BreakArray.hs b/compiler/main/BreakArray.hs
index d16d6f229d..6455912b67 100644
--- a/compiler/main/BreakArray.hs
+++ b/compiler/main/BreakArray.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP, MagicHash, UnboxedTuples #-}
+
-------------------------------------------------------------------------------
--
-- | Break Arrays in the IO monad
diff --git a/compiler/main/CmdLineParser.hs b/compiler/main/CmdLineParser.hs
index 22811d44cc..5ee7086cbc 100644
--- a/compiler/main/CmdLineParser.hs
+++ b/compiler/main/CmdLineParser.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-------------------------------------------------------------------------------
--
-- | Command-line parser
diff --git a/compiler/main/CodeOutput.lhs b/compiler/main/CodeOutput.lhs
index b8b187241b..c0a609ba2e 100644
--- a/compiler/main/CodeOutput.lhs
+++ b/compiler/main/CodeOutput.lhs
@@ -4,6 +4,8 @@
\section{Code output phase}
\begin{code}
+{-# LANGUAGE CPP #-}
+
module CodeOutput( codeOutput, outputForeignStubs ) where
#include "HsVersions.h"
@@ -72,7 +74,6 @@ codeOutput dflags this_mod filenm location foreign_stubs pkg_deps cmm_stream
; return cmm
}
- ; showPass dflags "CodeOutput"
; stubs_exist <- outputForeignStubs dflags this_mod location foreign_stubs
; case hscTarget dflags of {
HscAsm -> outputAsm dflags this_mod filenm linted_cmm_stream;
@@ -190,11 +191,8 @@ outputForeignStubs dflags mod location stubs
stub_c <- newTempName dflags "c"
case stubs of
- NoStubs -> do
- -- When compiling External Core files, may need to use stub
- -- files from a previous compilation
- stub_h_exists <- doesFileExist stub_h
- return (stub_h_exists, Nothing)
+ NoStubs ->
+ return (False, Nothing)
ForeignStubs h_code c_code -> do
let
diff --git a/compiler/main/DriverMkDepend.hs b/compiler/main/DriverMkDepend.hs
index cda0b4729f..03545d4828 100644
--- a/compiler/main/DriverMkDepend.hs
+++ b/compiler/main/DriverMkDepend.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Makefile Dependency Generation
diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs
index 2981269d54..fa8b2d060f 100644
--- a/compiler/main/DriverPhases.hs
+++ b/compiler/main/DriverPhases.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
-- $Id: DriverPhases.hs,v 1.38 2005/05/17 11:01:59 simonmar Exp $
--
@@ -18,7 +20,6 @@ module DriverPhases (
isHaskellSrcSuffix,
isObjectSuffix,
isCishSuffix,
- isExtCoreSuffix,
isDynLibSuffix,
isHaskellUserSrcSuffix,
isSourceSuffix,
@@ -27,7 +28,6 @@ module DriverPhases (
isHaskellSrcFilename,
isObjectFilename,
isCishFilename,
- isExtCoreFilename,
isDynLibFilename,
isHaskellUserSrcFilename,
isSourceFilename
@@ -56,7 +56,7 @@ import System.FilePath
-}
data HscSource
- = HsSrcFile | HsBootFile | ExtCoreFile
+ = HsSrcFile | HsBootFile
deriving( Eq, Ord, Show )
-- Ord needed for the finite maps we build in CompManager
@@ -64,7 +64,6 @@ data HscSource
hscSourceString :: HscSource -> String
hscSourceString HsSrcFile = ""
hscSourceString HsBootFile = "[boot]"
-hscSourceString ExtCoreFile = "[ext core]"
isHsBoot :: HscSource -> Bool
isHsBoot HsBootFile = True
@@ -175,7 +174,6 @@ startPhase "hs" = Cpp HsSrcFile
startPhase "hs-boot" = Cpp HsBootFile
startPhase "hscpp" = HsPp HsSrcFile
startPhase "hspp" = Hsc HsSrcFile
-startPhase "hcr" = Hsc ExtCoreFile
startPhase "hc" = HCc
startPhase "c" = Cc
startPhase "cpp" = Ccpp
@@ -202,7 +200,6 @@ startPhase _ = StopLn -- all unknown file types
phaseInputExt :: Phase -> String
phaseInputExt (Unlit HsSrcFile) = "lhs"
phaseInputExt (Unlit HsBootFile) = "lhs-boot"
-phaseInputExt (Unlit ExtCoreFile) = "lhcr"
phaseInputExt (Cpp _) = "lpp" -- intermediate only
phaseInputExt (HsPp _) = "hscpp" -- intermediate only
phaseInputExt (Hsc _) = "hspp" -- intermediate only
@@ -227,13 +224,12 @@ phaseInputExt MergeStub = "o"
phaseInputExt StopLn = "o"
haskellish_src_suffixes, haskellish_suffixes, cish_suffixes,
- extcoreish_suffixes, haskellish_user_src_suffixes
+ haskellish_user_src_suffixes
:: [String]
haskellish_src_suffixes = haskellish_user_src_suffixes ++
[ "hspp", "hscpp", "hcr", "cmm", "cmmcpp" ]
haskellish_suffixes = haskellish_src_suffixes ++ ["hc", "raw_s"]
cish_suffixes = [ "c", "cpp", "C", "cc", "cxx", "s", "S", "ll", "bc", "lm_s", "m", "M", "mm" ]
-extcoreish_suffixes = [ "hcr" ]
-- Will not be deleted as temp files:
haskellish_user_src_suffixes = [ "hs", "lhs", "hs-boot", "lhs-boot" ]
@@ -250,13 +246,12 @@ dynlib_suffixes platform = case platformOS platform of
OSDarwin -> ["dylib", "so"]
_ -> ["so"]
-isHaskellishSuffix, isHaskellSrcSuffix, isCishSuffix, isExtCoreSuffix,
+isHaskellishSuffix, isHaskellSrcSuffix, isCishSuffix,
isHaskellUserSrcSuffix
:: String -> Bool
isHaskellishSuffix s = s `elem` haskellish_suffixes
isHaskellSrcSuffix s = s `elem` haskellish_src_suffixes
isCishSuffix s = s `elem` cish_suffixes
-isExtCoreSuffix s = s `elem` extcoreish_suffixes
isHaskellUserSrcSuffix s = s `elem` haskellish_user_src_suffixes
isObjectSuffix, isDynLibSuffix :: Platform -> String -> Bool
@@ -267,13 +262,12 @@ isSourceSuffix :: String -> Bool
isSourceSuffix suff = isHaskellishSuffix suff || isCishSuffix suff
isHaskellishFilename, isHaskellSrcFilename, isCishFilename,
- isExtCoreFilename, isHaskellUserSrcFilename, isSourceFilename
+ isHaskellUserSrcFilename, isSourceFilename
:: 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)
-isExtCoreFilename f = isExtCoreSuffix (drop 1 $ takeExtension f)
isHaskellUserSrcFilename f = isHaskellUserSrcSuffix (drop 1 $ takeExtension f)
isSourceFilename f = isSourceSuffix (drop 1 $ takeExtension f)
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index b93cef1fba..11427e27cf 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -1,5 +1,5 @@
-{-# OPTIONS -fno-cse #-}
-{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE CPP, NamedFieldPuns, NondecreasingIndentation #-}
+{-# OPTIONS_GHC -fno-cse #-}
-- -fno-cse is needed for GLOBAL_VAR's to behave properly
-----------------------------------------------------------------------------
@@ -54,7 +54,6 @@ import Util
import StringBuffer ( hGetStringBuffer )
import BasicTypes ( SuccessFlag(..) )
import Maybes ( expectJust )
-import ParserCoreUtils ( getCoreModuleName )
import SrcLoc
import FastString
import LlvmCodeGen ( llvmFixupAsm )
@@ -169,8 +168,6 @@ compileOne' m_tc_result mHscMessage
output_fn <- getOutputFilename next_phase
Temporary basename dflags next_phase (Just location)
- let extCore_filename = basename ++ ".hcr"
-
-- -fforce-recomp should also work with --make
let force_recomp = gopt Opt_ForceRecomp dflags
source_modified
@@ -207,7 +204,7 @@ compileOne' m_tc_result mHscMessage
hm_linkable = maybe_old_linkable })
_ -> do guts0 <- hscDesugar hsc_env summary tc_result
guts <- hscSimplify hsc_env guts0
- (iface, _changed, details, cgguts) <- hscNormalIface hsc_env extCore_filename guts mb_old_hash
+ (iface, _changed, details, cgguts) <- hscNormalIface hsc_env guts mb_old_hash
(hasStub, comp_bc, modBreaks) <- hscInteractive hsc_env cgguts summary
stub_o <- case hasStub of
@@ -231,7 +228,9 @@ compileOne' m_tc_result mHscMessage
hm_iface = iface,
hm_linkable = Just linkable })
HscNothing ->
- do (iface, _changed, details) <- hscSimpleIface hsc_env tc_result mb_old_hash
+ do (iface, changed, details) <- hscSimpleIface hsc_env tc_result mb_old_hash
+ when (gopt Opt_WriteInterface dflags) $
+ hscWriteIface dflags iface changed summary
let linkable = if isHsBoot src_flavour
then maybe_old_linkable
else Just (LM (ms_hs_date summary) this_mod [])
@@ -251,7 +250,7 @@ compileOne' m_tc_result mHscMessage
_ -> do guts0 <- hscDesugar hsc_env summary tc_result
guts <- hscSimplify hsc_env guts0
- (iface, changed, details, cgguts) <- hscNormalIface hsc_env extCore_filename guts mb_old_hash
+ (iface, changed, details, cgguts) <- hscNormalIface hsc_env guts mb_old_hash
hscWriteIface dflags iface changed summary
-- We're in --make mode: finish the compilation pipeline.
@@ -892,16 +891,11 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
setDynFlags dflags
-- gather the imports and module name
- (hspp_buf,mod_name,imps,src_imps) <- liftIO $
- case src_flavour of
- ExtCoreFile -> do -- no explicit imports in ExtCore input.
- m <- getCoreModuleName input_fn
- return (Nothing, mkModuleName m, [], [])
-
- _ -> do
- buf <- hGetStringBuffer input_fn
- (src_imps,imps,L _ mod_name) <- getImports dflags buf input_fn (basename <.> suff)
- return (Just buf, mod_name, imps, src_imps)
+ (hspp_buf,mod_name,imps,src_imps) <- liftIO $ do
+ do
+ buf <- hGetStringBuffer input_fn
+ (src_imps,imps,L _ mod_name) <- getImports dflags buf input_fn (basename <.> suff)
+ return (Just buf, mod_name, imps, src_imps)
-- Take -o into account if present
-- Very like -ohi, but we must *only* do this if we aren't linking
@@ -936,8 +930,6 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
then return SourceUnmodified
else return SourceModified
- let extCore_filename = basename ++ ".hcr"
-
PipeState{hsc_env=hsc_env'} <- getPipeState
-- Tell the finder cache about this module
@@ -957,7 +949,7 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
ms_srcimps = src_imps }
-- run the compiler!
- result <- liftIO $ hscCompileOneShot hsc_env' extCore_filename
+ result <- liftIO $ hscCompileOneShot hsc_env'
mod_summary source_unchanged
return (HscOut src_flavour mod_name result,
@@ -1216,6 +1208,7 @@ runPhase (RealPhase (As with_cpp)) input_fn dflags
-- might be a hierarchical module.
liftIO $ createDirectoryIfMissing True (takeDirectory output_fn)
+ ccInfo <- liftIO $ getCompilerInfo dflags
let runAssembler inputFilename outputFilename
= liftIO $ as_prog dflags
([ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
@@ -1230,7 +1223,9 @@ runPhase (RealPhase (As with_cpp)) input_fn dflags
++ (if platformArch (targetPlatform dflags) == ArchSPARC
then [SysTools.Option "-mcpu=v9"]
else [])
-
+ ++ (if any (ccInfo ==) [Clang, AppleClang, AppleClang51]
+ then [SysTools.Option "-Qunused-arguments"]
+ else [])
++ [ SysTools.Option "-x"
, if with_cpp
then SysTools.Option "assembler-with-cpp"
@@ -2139,26 +2134,27 @@ joinObjectFiles dflags o_files output_fn = do
let mySettings = settings dflags
ldIsGnuLd = sLdIsGnuLd mySettings
osInfo = platformOS (targetPlatform dflags)
- ld_r args ccInfo = SysTools.runLink dflags ([
- SysTools.Option "-nostdlib",
- SysTools.Option "-Wl,-r"
- ]
- ++ (if ccInfo == Clang then []
- else [SysTools.Option "-nodefaultlibs"])
- ++ (if osInfo == OSFreeBSD
- then [SysTools.Option "-L/usr/lib"]
- else [])
- -- gcc on sparc sets -Wl,--relax implicitly, but
- -- -r and --relax are incompatible for ld, so
- -- disable --relax explicitly.
- ++ (if platformArch (targetPlatform dflags) == ArchSPARC
- && ldIsGnuLd
- then [SysTools.Option "-Wl,-no-relax"]
- else [])
- ++ map SysTools.Option ld_build_id
- ++ [ SysTools.Option "-o",
- SysTools.FileOption "" output_fn ]
- ++ args)
+ ld_r args cc = SysTools.runLink dflags ([
+ SysTools.Option "-nostdlib",
+ SysTools.Option "-Wl,-r"
+ ]
+ ++ (if any (cc ==) [Clang, AppleClang, AppleClang51]
+ then []
+ else [SysTools.Option "-nodefaultlibs"])
+ ++ (if osInfo == OSFreeBSD
+ then [SysTools.Option "-L/usr/lib"]
+ else [])
+ -- gcc on sparc sets -Wl,--relax implicitly, but
+ -- -r and --relax are incompatible for ld, so
+ -- disable --relax explicitly.
+ ++ (if platformArch (targetPlatform dflags) == ArchSPARC
+ && ldIsGnuLd
+ then [SysTools.Option "-Wl,-no-relax"]
+ else [])
+ ++ map SysTools.Option ld_build_id
+ ++ [ SysTools.Option "-o",
+ SysTools.FileOption "" output_fn ]
+ ++ args)
-- suppress the generation of the .note.gnu.build-id section,
-- which we don't need and sometimes causes ld to emit a
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 72ebb38fc2..122eafff19 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-------------------------------------------------------------------------------
--
-- | Dynamic flags
@@ -11,7 +13,7 @@
--
-------------------------------------------------------------------------------
-{-# OPTIONS -fno-cse #-}
+{-# OPTIONS_GHC -fno-cse #-}
-- -fno-cse is needed for GLOBAL_VAR's to behave properly
module DynFlags (
@@ -30,6 +32,7 @@ module DynFlags (
wopt, wopt_set, wopt_unset,
xopt, xopt_set, xopt_unset,
lang_set,
+ useUnicodeSyntax,
whenGeneratingDynamicToo, ifGeneratingDynamicToo,
whenCannotGenerateDynamicToo,
dynamicTooMkDynamicDynFlags,
@@ -330,6 +333,7 @@ data GeneralFlag
| Opt_IgnoreInterfacePragmas
| Opt_OmitInterfacePragmas
| Opt_ExposeAllUnfoldings
+ | Opt_WriteInterface -- forces .hi files to be written even with -fno-code
-- profiling opts
| Opt_AutoSccsOnIndividualCafs
@@ -403,8 +407,6 @@ data GeneralFlag
| Opt_SuppressUniques
-- temporary flags
- | Opt_RunCPS
- | Opt_RunCPSZ
| Opt_AutoLinkPackages
| Opt_ImplicitImportQualified
@@ -580,6 +582,7 @@ data ExtensionFlag
| Opt_TraditionalRecordSyntax
| Opt_LambdaCase
| Opt_MultiWayIf
+ | Opt_BinaryLiterals
| Opt_NegativeLiterals
| Opt_EmptyCase
| Opt_PatternSynonyms
@@ -774,7 +777,7 @@ data DynFlags = DynFlags {
pprCols :: Int,
traceLevel :: Int, -- Standard level is 1. Less verbose is 0.
- useUnicodeQuotes :: Bool,
+ useUnicode :: Bool,
-- | what kind of {-# SCC #-} to add automatically
profAuto :: ProfAuto,
@@ -1292,12 +1295,12 @@ initDynFlags dflags = do
refRtldInfo <- newIORef Nothing
refRtccInfo <- newIORef Nothing
wrapperNum <- newIORef emptyModuleEnv
- canUseUnicodeQuotes <- do let enc = localeEncoding
- str = "‘’"
- (withCString enc str $ \cstr ->
- do str' <- peekCString enc cstr
- return (str == str'))
- `catchIOError` \_ -> return False
+ canUseUnicode <- do let enc = localeEncoding
+ str = "‘’"
+ (withCString enc str $ \cstr ->
+ do str' <- peekCString enc cstr
+ return (str == str'))
+ `catchIOError` \_ -> return False
return dflags{
canGenerateDynamicToo = refCanGenerateDynamicToo,
nextTempSuffix = refNextTempSuffix,
@@ -1307,7 +1310,7 @@ initDynFlags dflags = do
generatedDumps = refGeneratedDumps,
llvmVersion = refLlvmVersion,
nextWrapperNum = wrapperNum,
- useUnicodeQuotes = canUseUnicodeQuotes,
+ useUnicode = canUseUnicode,
rtldInfo = refRtldInfo,
rtccInfo = refRtccInfo
}
@@ -1446,7 +1449,7 @@ defaultDynFlags mySettings =
flushErr = defaultFlushErr,
pprUserLength = 5,
pprCols = 100,
- useUnicodeQuotes = False,
+ useUnicode = False,
traceLevel = 1,
profAuto = NoProfAuto,
llvmVersion = panic "defaultDynFlags: No llvmVersion",
@@ -1682,6 +1685,9 @@ lang_set dflags lang =
extensionFlags = flattenExtensionFlags lang (extensions dflags)
}
+useUnicodeSyntax :: DynFlags -> Bool
+useUnicodeSyntax = xopt Opt_UnicodeSyntax
+
-- | Set the Haskell language standard to use
setLanguage :: Language -> DynP ()
setLanguage l = upd (`lang_set` Just l)
@@ -2187,16 +2193,9 @@ dynamic_flags = [
-------- ghc -M -----------------------------------------------------
, Flag "dep-suffix" (hasArg addDepSuffix)
- , Flag "optdep-s" (hasArgDF addDepSuffix "Use -dep-suffix instead")
, Flag "dep-makefile" (hasArg setDepMakefile)
- , Flag "optdep-f" (hasArgDF setDepMakefile "Use -dep-makefile instead")
- , Flag "optdep-w" (NoArg (deprecate "doesn't do anything"))
, Flag "include-pkg-deps" (noArg (setDepIncludePkgDeps True))
- , Flag "optdep--include-prelude" (noArgDF (setDepIncludePkgDeps True) "Use -include-pkg-deps instead")
- , Flag "optdep--include-pkg-deps" (noArgDF (setDepIncludePkgDeps True) "Use -include-pkg-deps instead")
, Flag "exclude-module" (hasArg addDepExcludeMod)
- , Flag "optdep--exclude-module" (hasArgDF addDepExcludeMod "Use -exclude-module instead")
- , Flag "optdep-x" (hasArgDF addDepExcludeMod "Use -exclude-module instead")
-------- Linking ----------------------------------------------------
, Flag "no-link" (noArg (\d -> d{ ghcLink=NoLink }))
@@ -2650,6 +2649,7 @@ fFlags = [
( "pedantic-bottoms", Opt_PedanticBottoms, nop ),
( "ignore-interface-pragmas", Opt_IgnoreInterfacePragmas, nop ),
( "omit-interface-pragmas", Opt_OmitInterfacePragmas, nop ),
+ ( "write-interface", Opt_WriteInterface, nop ),
( "expose-all-unfoldings", Opt_ExposeAllUnfoldings, nop ),
( "do-lambda-eta-expansion", Opt_DoLambdaEtaExpansion, nop ),
( "ignore-asserts", Opt_IgnoreAsserts, nop ),
@@ -2669,8 +2669,6 @@ fFlags = [
( "break-on-error", Opt_BreakOnError, nop ),
( "print-evld-with-show", Opt_PrintEvldWithShow, nop ),
( "print-bind-contents", Opt_PrintBindContents, nop ),
- ( "run-cps", Opt_RunCPS, nop ),
- ( "run-cpsz", Opt_RunCPSZ, nop ),
( "vectorise", Opt_Vectorise, nop ),
( "vectorisation-avoidance", Opt_VectorisationAvoidance, nop ),
( "regs-graph", Opt_RegsGraph, nop ),
@@ -2685,7 +2683,8 @@ fFlags = [
( "fun-to-thunk", Opt_FunToThunk, nop ),
( "gen-manifest", Opt_GenManifest, nop ),
( "embed-manifest", Opt_EmbedManifest, nop ),
- ( "ext-core", Opt_EmitExternalCore, nop ),
+ ( "ext-core", Opt_EmitExternalCore,
+ \_ -> deprecate "it has no effect, and will be removed in GHC 7.12" ),
( "shared-implib", Opt_SharedImplib, nop ),
( "ghci-sandbox", Opt_GhciSandbox, nop ),
( "ghci-history", Opt_GhciHistory, nop ),
@@ -2869,13 +2868,15 @@ xFlags = [
( "FlexibleInstances", Opt_FlexibleInstances, nop ),
( "ConstrainedClassMethods", Opt_ConstrainedClassMethods, nop ),
( "MultiParamTypeClasses", Opt_MultiParamTypeClasses, nop ),
- ( "NullaryTypeClasses", Opt_NullaryTypeClasses, nop ),
+ ( "NullaryTypeClasses", Opt_NullaryTypeClasses,
+ deprecatedForExtension "MultiParamTypeClasses" ),
( "FunctionalDependencies", Opt_FunctionalDependencies, nop ),
( "GeneralizedNewtypeDeriving", Opt_GeneralizedNewtypeDeriving, setGenDeriving ),
( "OverlappingInstances", Opt_OverlappingInstances, nop ),
( "UndecidableInstances", Opt_UndecidableInstances, nop ),
( "IncoherentInstances", Opt_IncoherentInstances, nop ),
( "PackageImports", Opt_PackageImports, nop ),
+ ( "BinaryLiterals", Opt_BinaryLiterals, nop ),
( "NegativeLiterals", Opt_NegativeLiterals, nop ),
( "EmptyCase", Opt_EmptyCase, nop ),
( "PatternSynonyms", Opt_PatternSynonyms, nop )
@@ -2960,6 +2961,9 @@ impliedFlags
, (Opt_ImplicitParams, turnOn, Opt_FlexibleInstances)
, (Opt_JavaScriptFFI, turnOn, Opt_InterruptibleFFI)
+
+ , (Opt_DeriveTraversable, turnOn, Opt_DeriveFunctor)
+ , (Opt_DeriveTraversable, turnOn, Opt_DeriveFoldable)
]
optLevelFlags :: [([Int], GeneralFlag)]
@@ -3187,16 +3191,9 @@ noArg fn = NoArg (upd fn)
noArgM :: (DynFlags -> DynP DynFlags) -> OptKind (CmdLineP DynFlags)
noArgM fn = NoArg (updM fn)
-noArgDF :: (DynFlags -> DynFlags) -> String -> OptKind (CmdLineP DynFlags)
-noArgDF fn deprec = NoArg (upd fn >> deprecate deprec)
-
hasArg :: (String -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg fn = HasArg (upd . fn)
-hasArgDF :: (String -> DynFlags -> DynFlags) -> String -> OptKind (CmdLineP DynFlags)
-hasArgDF fn deprec = HasArg (\s -> do upd (fn s)
- deprecate deprec)
-
sepArg :: (String -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
sepArg fn = SepArg (upd . fn)
@@ -3764,6 +3761,8 @@ data LinkerInfo
data CompilerInfo
= GCC
| Clang
+ | AppleClang
+ | AppleClang51
| UnknownCC
deriving Eq
diff --git a/compiler/main/DynFlags.hs-boot b/compiler/main/DynFlags.hs-boot
index 04ec5a4e7d..5cf21669bd 100644
--- a/compiler/main/DynFlags.hs-boot
+++ b/compiler/main/DynFlags.hs-boot
@@ -9,4 +9,5 @@ targetPlatform :: DynFlags -> Platform
pprUserLength :: DynFlags -> Int
pprCols :: DynFlags -> Int
unsafeGlobalDynFlags :: DynFlags
-useUnicodeQuotes :: DynFlags -> Bool
+useUnicode :: DynFlags -> Bool
+useUnicodeSyntax :: DynFlags -> Bool
diff --git a/compiler/main/DynamicLoading.hs b/compiler/main/DynamicLoading.hs
index ffafc78216..046d13cee5 100644
--- a/compiler/main/DynamicLoading.hs
+++ b/compiler/main/DynamicLoading.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP, MagicHash #-}
+
-- | Dynamically lookup up values from modules and loading them.
module DynamicLoading (
#ifdef GHCI
diff --git a/compiler/main/ErrUtils.lhs b/compiler/main/ErrUtils.lhs
index 12b6bad68a..02f731d3c2 100644
--- a/compiler/main/ErrUtils.lhs
+++ b/compiler/main/ErrUtils.lhs
@@ -4,6 +4,7 @@
\section[ErrsUtils]{Utilities for error reporting}
\begin{code}
+{-# LANGUAGE CPP #-}
module ErrUtils (
ErrMsg, WarnMsg, Severity(..),
diff --git a/compiler/main/Finder.lhs b/compiler/main/Finder.lhs
index 60683b2289..cbfd4e4f1c 100644
--- a/compiler/main/Finder.lhs
+++ b/compiler/main/Finder.lhs
@@ -4,6 +4,8 @@
\section[Finder]{Module Finder}
\begin{code}
+{-# LANGUAGE CPP #-}
+
module Finder (
flushFinderCaches,
FindResult(..),
@@ -432,8 +434,8 @@ mkHomeModLocation2 :: DynFlags
mkHomeModLocation2 dflags mod src_basename ext = do
let mod_basename = moduleNameSlashes mod
- obj_fn <- mkObjPath dflags src_basename mod_basename
- hi_fn <- mkHiPath dflags src_basename mod_basename
+ obj_fn = mkObjPath dflags src_basename mod_basename
+ hi_fn = mkHiPath dflags src_basename mod_basename
return (ModLocation{ ml_hs_file = Just (src_basename <.> ext),
ml_hi_file = hi_fn,
@@ -443,7 +445,7 @@ mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String
-> IO ModLocation
mkHiOnlyModLocation dflags hisuf path basename
= do let full_basename = path </> basename
- obj_fn <- mkObjPath dflags full_basename basename
+ obj_fn = mkObjPath dflags full_basename basename
return ModLocation{ ml_hs_file = Nothing,
ml_hi_file = full_basename <.> hisuf,
-- Remove the .hi-boot suffix from
@@ -459,16 +461,15 @@ mkObjPath
:: DynFlags
-> FilePath -- the filename of the source file, minus the extension
-> String -- the module name with dots replaced by slashes
- -> IO FilePath
-mkObjPath dflags basename mod_basename
- = do let
+ -> FilePath
+mkObjPath dflags basename mod_basename = obj_basename <.> osuf
+ where
odir = objectDir dflags
osuf = objectSuf dflags
obj_basename | Just dir <- odir = dir </> mod_basename
| otherwise = basename
- return (obj_basename <.> osuf)
-- | Constructs the filename of a .hi file for a given source file.
-- Does /not/ check whether the .hi file exists
@@ -476,16 +477,15 @@ mkHiPath
:: DynFlags
-> FilePath -- the filename of the source file, minus the extension
-> String -- the module name with dots replaced by slashes
- -> IO FilePath
-mkHiPath dflags basename mod_basename
- = do let
+ -> FilePath
+mkHiPath dflags basename mod_basename = hi_basename <.> hisuf
+ where
hidir = hiDir dflags
hisuf = hiSuf dflags
hi_basename | Just dir <- hidir = dir </> mod_basename
| otherwise = basename
- return (hi_basename <.> hisuf)
-- -----------------------------------------------------------------------------
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index 7694bc9821..13d4f87009 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP, NondecreasingIndentation, ScopedTypeVariables #-}
+
-- -----------------------------------------------------------------------------
--
-- (c) The University of Glasgow, 2005-2012
@@ -53,7 +55,6 @@ module GHC (
-- ** Compiling to Core
CoreModule(..),
compileToCoreModule, compileToCoreSimplified,
- compileCoreToObj,
-- * Inspecting the module structure of the program
ModuleGraph, ModSummary(..), ms_mod_name, ModLocation(..),
@@ -261,6 +262,7 @@ import InteractiveEval
import TcRnDriver ( runTcInteractive )
#endif
+import PprTyThing ( pprFamInst )
import HscMain
import GhcMake
import DriverPipeline ( compileOne' )
@@ -283,7 +285,7 @@ import DataCon
import Name hiding ( varName )
import Avail
import InstEnv
-import FamInstEnv
+import FamInstEnv ( FamInst )
import SrcLoc
import CoreSyn
import TidyPgm
@@ -310,7 +312,7 @@ import FastString
import qualified Parser
import Lexer
-import System.Directory ( doesFileExist, getCurrentDirectory )
+import System.Directory ( doesFileExist )
import Data.Maybe
import Data.List ( find )
import Data.Time
@@ -925,43 +927,6 @@ compileToCoreModule = compileCore False
-- as to return simplified and tidied Core.
compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
compileToCoreSimplified = compileCore True
--- | Takes a CoreModule and compiles the bindings therein
--- to object code. The first argument is a bool flag indicating
--- whether to run the simplifier.
--- The resulting .o, .hi, and executable files, if any, are stored in the
--- current directory, and named according to the module name.
--- This has only so far been tested with a single self-contained module.
-compileCoreToObj :: GhcMonad m
- => Bool -> CoreModule -> FilePath -> FilePath -> m ()
-compileCoreToObj simplify cm@(CoreModule{ cm_module = mName })
- output_fn extCore_filename = do
- dflags <- getSessionDynFlags
- currentTime <- liftIO $ getCurrentTime
- cwd <- liftIO $ getCurrentDirectory
- modLocation <- liftIO $ mkHiOnlyModLocation dflags (hiSuf dflags) cwd
- ((moduleNameSlashes . moduleName) mName)
-
- let modSum = ModSummary { ms_mod = mName,
- ms_hsc_src = ExtCoreFile,
- ms_location = modLocation,
- -- By setting the object file timestamp to Nothing,
- -- we always force recompilation, which is what we
- -- want. (Thus it doesn't matter what the timestamp
- -- for the (nonexistent) source file is.)
- ms_hs_date = currentTime,
- ms_obj_date = Nothing,
- -- Only handling the single-module case for now, so no imports.
- ms_srcimps = [],
- ms_textual_imps = [],
- -- No source file
- ms_hspp_file = "",
- ms_hspp_opts = dflags,
- ms_hspp_buf = Nothing
- }
-
- hsc_env <- getSession
- liftIO $ hscCompileCore hsc_env simplify (cm_safe cm) modSum (cm_binds cm) output_fn extCore_filename
-
compileCore :: GhcMonad m => Bool -> FilePath -> m CoreModule
compileCore simplify fn = do
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index b7a1282f5c..694778115d 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE BangPatterns, CPP, NondecreasingIndentation, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
-- NB: we specifically ignore deprecations. GHC 7.6 marks the .QSem module as
-- deprecated, although it became un-deprecated later. As a result, using 7.6
diff --git a/compiler/main/GhcMonad.hs b/compiler/main/GhcMonad.hs
index 68b4e2b2a2..5fa6452d58 100644
--- a/compiler/main/GhcMonad.hs
+++ b/compiler/main/GhcMonad.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE RankNTypes #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
-- -----------------------------------------------------------------------------
--
diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs
index a083f4fcd8..fcf235bd23 100644
--- a/compiler/main/HeaderInfo.hs
+++ b/compiler/main/HeaderInfo.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- | Parsing the top of a Haskell source file to get its module name,
@@ -185,8 +187,8 @@ lazyGetToks dflags filename handle = do
-- large module names (#5981)
nextbuf <- hGetStringBufferBlock handle new_size
if (len nextbuf == 0) then lazyLexBuf handle state True new_size else do
- newbuf <- appendStringBuffers (buffer state) nextbuf
- unsafeInterleaveIO $ lazyLexBuf handle state{buffer=newbuf} False new_size
+ newbuf <- appendStringBuffers (buffer state) nextbuf
+ unsafeInterleaveIO $ lazyLexBuf handle state{buffer=newbuf} False new_size
getToks :: DynFlags -> FilePath -> StringBuffer -> [Located Token]
diff --git a/compiler/main/Hooks.lhs b/compiler/main/Hooks.lhs
index 3bd9643dc6..63aaafa2a7 100644
--- a/compiler/main/Hooks.lhs
+++ b/compiler/main/Hooks.lhs
@@ -63,7 +63,7 @@ data Hooks = Hooks
, tcForeignImportsHook :: Maybe ([LForeignDecl Name] -> TcM ([Id], [LForeignDecl Id], Bag GlobalRdrElt))
, tcForeignExportsHook :: Maybe ([LForeignDecl Name] -> TcM (LHsBinds TcId, [LForeignDecl TcId], Bag GlobalRdrElt))
, hscFrontendHook :: Maybe (ModSummary -> Hsc TcGblEnv)
- , hscCompileOneShotHook :: Maybe (HscEnv -> FilePath -> ModSummary -> SourceModified -> IO HscStatus)
+ , hscCompileOneShotHook :: Maybe (HscEnv -> ModSummary -> SourceModified -> IO HscStatus)
, hscCompileCoreExprHook :: Maybe (HscEnv -> SrcSpan -> CoreExpr -> IO HValue)
, ghcPrimIfaceHook :: Maybe ModIface
, runPhaseHook :: Maybe (PhasePlus -> FilePath -> DynFlags -> CompPipeline (PhasePlus, FilePath))
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 748f7480ec..aef6007fb7 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE BangPatterns, CPP, MagicHash, NondecreasingIndentation #-}
+
-------------------------------------------------------------------------------
--
-- | Main API for compiling plain Haskell source code.
@@ -146,7 +148,6 @@ import ErrUtils
import Outputable
import HscStats ( ppSourceStats )
import HscTypes
-import MkExternalCore ( emitExternalCore )
import FastString
import UniqFM ( emptyUFM )
import UniqSupply
@@ -516,8 +517,9 @@ genericHscCompileGetFrontendResult ::
-> (Int,Int) -- (i,n) = module i of n (for msgs)
-> IO (Either ModIface (TcGblEnv, Maybe Fingerprint))
-genericHscCompileGetFrontendResult always_do_basic_recompilation_check m_tc_result
- mHscMessage hsc_env mod_summary source_modified mb_old_iface mod_index
+genericHscCompileGetFrontendResult
+ always_do_basic_recompilation_check m_tc_result
+ mHscMessage hsc_env mod_summary source_modified mb_old_iface mod_index
= do
let msg what = case mHscMessage of
@@ -553,16 +555,19 @@ genericHscCompileGetFrontendResult always_do_basic_recompilation_check m_tc_resu
case mb_checked_iface of
Just iface | not (recompileRequired recomp_reqd) ->
- -- If the module used TH splices when it was last compiled,
- -- then the recompilation check is not accurate enough (#481)
- -- and we must ignore it. However, if the module is stable
- -- (none of the modules it depends on, directly or indirectly,
- -- changed), then we *can* skip recompilation. This is why
- -- the SourceModified type contains SourceUnmodifiedAndStable,
- -- and it's pretty important: otherwise ghc --make would
- -- always recompile TH modules, even if nothing at all has
- -- changed. Stability is just the same check that make is
- -- doing for us in one-shot mode.
+ -- If the module used TH splices when it was last
+ -- compiled, then the recompilation check is not
+ -- accurate enough (#481) and we must ignore
+ -- it. However, if the module is stable (none of
+ -- the modules it depends on, directly or
+ -- indirectly, changed), then we *can* skip
+ -- recompilation. This is why the SourceModified
+ -- type contains SourceUnmodifiedAndStable, and
+ -- it's pretty important: otherwise ghc --make
+ -- would always recompile TH modules, even if
+ -- nothing at all has changed. Stability is just
+ -- the same check that make is doing for us in
+ -- one-shot mode.
case m_tc_result of
Nothing
| mi_used_th iface && not stable ->
@@ -580,31 +585,25 @@ genericHscFrontend mod_summary =
getHooked hscFrontendHook genericHscFrontend' >>= ($ mod_summary)
genericHscFrontend' :: ModSummary -> Hsc TcGblEnv
-genericHscFrontend' mod_summary
- | ExtCoreFile <- ms_hsc_src mod_summary =
- panic "GHC does not currently support reading External Core files"
- | otherwise =
- hscFileFrontEnd mod_summary
+genericHscFrontend' mod_summary = hscFileFrontEnd mod_summary
--------------------------------------------------------------
-- Compilers
--------------------------------------------------------------
hscCompileOneShot :: HscEnv
- -> FilePath
-> ModSummary
-> SourceModified
-> IO HscStatus
hscCompileOneShot env =
lookupHook hscCompileOneShotHook hscCompileOneShot' (hsc_dflags env) env
--- Compile Haskell, boot and extCore in OneShot mode.
+-- Compile Haskell/boot in OneShot mode.
hscCompileOneShot' :: HscEnv
- -> FilePath
-> ModSummary
-> SourceModified
-> IO HscStatus
-hscCompileOneShot' hsc_env extCore_filename mod_summary src_changed
+hscCompileOneShot' hsc_env mod_summary src_changed
= do
-- One-shot mode needs a knot-tying mutable variable for interface
-- files. See TcRnTypes.TcGblEnv.tcg_type_env_var.
@@ -624,7 +623,11 @@ hscCompileOneShot' hsc_env extCore_filename mod_summary src_changed
guts0 <- hscDesugar' (ms_location mod_summary) tc_result
dflags <- getDynFlags
case hscTarget dflags of
- HscNothing -> return HscNotGeneratingCode
+ HscNothing -> do
+ when (gopt Opt_WriteInterface dflags) $ liftIO $ do
+ (iface, changed, _details) <- hscSimpleIface hsc_env tc_result mb_old_hash
+ hscWriteIface dflags iface changed mod_summary
+ return HscNotGeneratingCode
_ ->
case ms_hsc_src mod_summary of
HsBootFile ->
@@ -633,7 +636,7 @@ hscCompileOneShot' hsc_env extCore_filename mod_summary src_changed
return HscUpdateBoot
_ ->
do guts <- hscSimplify' guts0
- (iface, changed, _details, cgguts) <- hscNormalIface' extCore_filename guts mb_old_hash
+ (iface, changed, _details, cgguts) <- hscNormalIface' guts mb_old_hash
liftIO $ hscWriteIface dflags iface changed mod_summary
return $ HscRecomp cgguts mod_summary
@@ -1070,18 +1073,16 @@ hscSimpleIface' tc_result mb_old_iface = do
return (new_iface, no_change, details)
hscNormalIface :: HscEnv
- -> FilePath
-> ModGuts
-> Maybe Fingerprint
-> IO (ModIface, Bool, ModDetails, CgGuts)
-hscNormalIface hsc_env extCore_filename simpl_result mb_old_iface =
- runHsc hsc_env $ hscNormalIface' extCore_filename simpl_result mb_old_iface
+hscNormalIface hsc_env simpl_result mb_old_iface =
+ runHsc hsc_env $ hscNormalIface' simpl_result mb_old_iface
-hscNormalIface' :: FilePath
- -> ModGuts
+hscNormalIface' :: ModGuts
-> Maybe Fingerprint
-> Hsc (ModIface, Bool, ModDetails, CgGuts)
-hscNormalIface' extCore_filename simpl_result mb_old_iface = do
+hscNormalIface' simpl_result mb_old_iface = do
hsc_env <- getHscEnv
(cg_guts, details) <- {-# SCC "CoreTidy" #-}
liftIO $ tidyProgram hsc_env simpl_result
@@ -1096,11 +1097,6 @@ hscNormalIface' extCore_filename simpl_result mb_old_iface = do
ioMsgMaybe $
mkIface hsc_env mb_old_iface details simpl_result
- -- Emit external core
- -- This should definitely be here and not after CorePrep,
- -- because CorePrep produces unqualified constructor wrapper declarations,
- -- so its output isn't valid External Core (without some preprocessing).
- liftIO $ emitExternalCore (hsc_dflags hsc_env) extCore_filename cg_guts
liftIO $ dumpIfaceStats hsc_env
-- Return the prepared code.
@@ -1158,8 +1154,15 @@ hscGenHardCode hsc_env cgguts mod_summary output_filename = do
------------------ Code generation ------------------
- cmms <- {-# SCC "NewCodeGen" #-}
- tryNewCodeGen hsc_env this_mod data_tycons
+ -- The back-end is streamed: each top-level function goes
+ -- from Stg all the way to asm before dealing with the next
+ -- top-level function, so showPass isn't very useful here.
+ -- Hence we have one showPass for the whole backend, the
+ -- next showPass after this will be "Assembler".
+ showPass dflags "CodeGen"
+
+ cmms <- {-# SCC "StgCmm" #-}
+ doCodeGen hsc_env this_mod data_tycons
cost_centre_info
stg_binds hpc_info
@@ -1236,15 +1239,15 @@ hscCompileCmmFile hsc_env filename output_filename = runHsc hsc_env $ do
-------------------- Stuff for new code gen ---------------------
-tryNewCodeGen :: HscEnv -> Module -> [TyCon]
- -> CollectedCCs
- -> [StgBinding]
- -> HpcInfo
- -> IO (Stream IO CmmGroup ())
+doCodeGen :: HscEnv -> Module -> [TyCon]
+ -> CollectedCCs
+ -> [StgBinding]
+ -> HpcInfo
+ -> IO (Stream IO CmmGroup ())
-- Note we produce a 'Stream' of CmmGroups, so that the
-- backend can be run incrementally. Otherwise it generates all
-- the C-- up front, which has a significant space cost.
-tryNewCodeGen hsc_env this_mod data_tycons
+doCodeGen hsc_env this_mod data_tycons
cost_centre_info stg_binds hpc_info = do
let dflags = hsc_dflags hsc_env
@@ -1533,11 +1536,11 @@ hscParseThingWithLocation source linenumber parser str
return thing
hscCompileCore :: HscEnv -> Bool -> SafeHaskellMode -> ModSummary
- -> CoreProgram -> FilePath -> FilePath -> IO ()
-hscCompileCore hsc_env simplify safe_mode mod_summary binds output_filename extCore_filename
+ -> CoreProgram -> FilePath -> IO ()
+hscCompileCore hsc_env simplify safe_mode mod_summary binds output_filename
= runHsc hsc_env $ do
guts <- maybe_simplify (mkModGuts (ms_mod mod_summary) safe_mode binds)
- (iface, changed, _details, cgguts) <- hscNormalIface' extCore_filename guts Nothing
+ (iface, changed, _details, cgguts) <- hscNormalIface' guts Nothing
liftIO $ hscWriteIface (hsc_dflags hsc_env) iface changed mod_summary
_ <- liftIO $ hscGenHardCode hsc_env cgguts mod_summary output_filename
return ()
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index 6fcf8e24a7..9738f590b6 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -4,6 +4,7 @@
\section[HscTypes]{Types for the per-module compiler}
\begin{code}
+{-# LANGUAGE CPP, DeriveDataTypeable, ScopedTypeVariables #-}
-- | Types for the per-module compiler
module HscTypes (
@@ -71,7 +72,7 @@ module HscTypes (
TypeEnv, lookupType, lookupTypeHscEnv, mkTypeEnv, emptyTypeEnv,
typeEnvFromEntities, mkTypeEnvWithImplicits,
extendTypeEnv, extendTypeEnvList,
- extendTypeEnvWithIds, extendTypeEnvWithPatSyns,
+ extendTypeEnvWithIds,
lookupTypeEnv,
typeEnvElts, typeEnvTyCons, typeEnvIds, typeEnvPatSyns,
typeEnvDataCons, typeEnvCoAxioms, typeEnvClasses,
@@ -951,7 +952,8 @@ data ModDetails
-- The next two fields are created by the typechecker
md_exports :: [AvailInfo],
md_types :: !TypeEnv, -- ^ Local type environment for this particular module
- md_insts :: ![ClsInst], -- ^ 'DFunId's for the instances in this module
+ -- Includes Ids, TyCons, PatSyns
+ md_insts :: ![ClsInst], -- ^ 'DFunId's for the instances in this module
md_fam_insts :: ![FamInst],
md_rules :: ![CoreRule], -- ^ Domain may include 'Id's from other modules
md_anns :: ![Annotation], -- ^ Annotations present in this module: currently
@@ -1483,7 +1485,7 @@ Examples:
IfaceClass decl happens to use IfaceDecl recursively for the
associated types, but that's irrelevant here.)
- * Dictionary function Ids are not implict.
+ * Dictionary function Ids are not implicit.
* Axioms for newtypes are implicit (same as above), but axioms
for data/type family instances are *not* implicit (like DFunIds).
@@ -1504,15 +1506,17 @@ implicitTyThings :: TyThing -> [TyThing]
implicitTyThings (AnId _) = []
implicitTyThings (ACoAxiom _cc) = []
implicitTyThings (ATyCon tc) = implicitTyConThings tc
-implicitTyThings (AConLike cl) = case cl of
- RealDataCon dc ->
- -- For data cons add the worker and (possibly) wrapper
- map AnId (dataConImplicitIds dc)
- PatSynCon ps ->
- -- For bidirectional pattern synonyms, add the wrapper
- case patSynWrapper ps of
- Nothing -> []
- Just id -> [AnId id]
+implicitTyThings (AConLike cl) = implicitConLikeThings cl
+
+implicitConLikeThings :: ConLike -> [TyThing]
+implicitConLikeThings (RealDataCon dc)
+ = map AnId (dataConImplicitIds dc)
+ -- For data cons add the worker and (possibly) wrapper
+
+implicitConLikeThings (PatSynCon {})
+ = [] -- Pattern synonyms have no implicit Ids; the wrapper and matcher
+ -- are not "implicit"; they are simply new top-level bindings,
+ -- and they have their own declaration in an interface fiel
implicitClassThings :: Class -> [TyThing]
implicitClassThings cl
@@ -1561,8 +1565,8 @@ implicitCoTyCon tc
-- other declaration.
isImplicitTyThing :: TyThing -> Bool
isImplicitTyThing (AConLike cl) = case cl of
- RealDataCon{} -> True
- PatSynCon ps -> isImplicitId (patSynId ps)
+ RealDataCon {} -> True
+ PatSynCon {} -> False
isImplicitTyThing (AnId id) = isImplicitId id
isImplicitTyThing (ATyCon tc) = isImplicitTyCon tc
isImplicitTyThing (ACoAxiom ax) = isImplicitCoAxiom ax
@@ -1678,17 +1682,6 @@ extendTypeEnvList env things = foldl extendTypeEnv env things
extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
extendTypeEnvWithIds env ids
= extendNameEnvList env [(getName id, AnId id) | id <- ids]
-
-extendTypeEnvWithPatSyns :: TypeEnv -> [PatSyn] -> TypeEnv
-extendTypeEnvWithPatSyns env patsyns
- = extendNameEnvList env $ concatMap pat_syn_things patsyns
- where
- pat_syn_things :: PatSyn -> [(Name, TyThing)]
- pat_syn_things ps = (getName ps, AConLike (PatSynCon ps)):
- case patSynWrapper ps of
- Just wrap_id -> [(getName wrap_id, AnId wrap_id)]
- Nothing -> []
-
\end{code}
\begin{code}
@@ -2207,37 +2200,50 @@ type ModuleGraph = [ModSummary]
emptyMG :: ModuleGraph
emptyMG = []
--- | A single node in a 'ModuleGraph. The nodes of the module graph are one of:
+-- | A single node in a 'ModuleGraph'. The nodes of the module graph
+-- are one of:
--
-- * A regular Haskell source module
---
-- * A hi-boot source module
---
-- * An external-core source module
+--
data ModSummary
= ModSummary {
- ms_mod :: Module, -- ^ Identity of the module
- ms_hsc_src :: HscSource, -- ^ The module source either plain Haskell, hs-boot or external core
- ms_location :: ModLocation, -- ^ Location of the various files belonging to the module
- ms_hs_date :: UTCTime, -- ^ Timestamp of source file
- ms_obj_date :: Maybe UTCTime, -- ^ Timestamp of object, if we have one
- ms_srcimps :: [Located (ImportDecl RdrName)], -- ^ Source imports of the module
- ms_textual_imps :: [Located (ImportDecl RdrName)], -- ^ Non-source imports of the module from the module *text*
- ms_hspp_file :: FilePath, -- ^ Filename of preprocessed source file
- ms_hspp_opts :: DynFlags, -- ^ Cached flags from @OPTIONS@, @INCLUDE@
- -- and @LANGUAGE@ pragmas in the modules source code
- ms_hspp_buf :: Maybe StringBuffer -- ^ The actual preprocessed source, if we have it
+ ms_mod :: Module,
+ -- ^ Identity of the module
+ ms_hsc_src :: HscSource,
+ -- ^ The module source either plain Haskell, hs-boot or external core
+ ms_location :: ModLocation,
+ -- ^ Location of the various files belonging to the module
+ ms_hs_date :: UTCTime,
+ -- ^ Timestamp of source file
+ ms_obj_date :: Maybe UTCTime,
+ -- ^ Timestamp of object, if we have one
+ ms_srcimps :: [Located (ImportDecl RdrName)],
+ -- ^ Source imports of the module
+ ms_textual_imps :: [Located (ImportDecl RdrName)],
+ -- ^ Non-source imports of the module from the module *text*
+ ms_hspp_file :: FilePath,
+ -- ^ Filename of preprocessed source file
+ ms_hspp_opts :: DynFlags,
+ -- ^ Cached flags from @OPTIONS@, @INCLUDE@ and @LANGUAGE@
+ -- pragmas in the modules source code
+ ms_hspp_buf :: Maybe StringBuffer
+ -- ^ The actual preprocessed source, if we have it
}
ms_mod_name :: ModSummary -> ModuleName
ms_mod_name = moduleName . ms_mod
ms_imps :: ModSummary -> [Located (ImportDecl RdrName)]
-ms_imps ms = ms_textual_imps ms ++ map mk_additional_import (dynFlagDependencies (ms_hspp_opts ms))
+ms_imps ms =
+ ms_textual_imps ms ++
+ map mk_additional_import (dynFlagDependencies (ms_hspp_opts ms))
where
- -- This is a not-entirely-satisfactory means of creating an import that corresponds to an
- -- import that did not occur in the program text, such as those induced by the use of
- -- plugins (the -plgFoo flag)
+ -- This is a not-entirely-satisfactory means of creating an import
+ -- that corresponds to an import that did not occur in the program
+ -- text, such as those induced by the use of plugins (the -plgFoo
+ -- flag)
mk_additional_import mod_nm = noLoc $ ImportDecl {
ideclName = noLoc mod_nm,
ideclPkgQual = Nothing,
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index ede519982a..cfcc076235 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP, MagicHash, NondecreasingIndentation, UnboxedTuples #-}
+
-- -----------------------------------------------------------------------------
--
-- (c) The University of Glasgow, 2005-2007
diff --git a/compiler/main/InteractiveEvalTypes.hs b/compiler/main/InteractiveEvalTypes.hs
index e3324a39a1..6ea1a25648 100644
--- a/compiler/main/InteractiveEvalTypes.hs
+++ b/compiler/main/InteractiveEvalTypes.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-- -----------------------------------------------------------------------------
--
-- (c) The University of Glasgow, 2005-2007
diff --git a/compiler/main/PackageConfig.hs b/compiler/main/PackageConfig.hs
index d34d9e1f5c..514a2e004f 100644
--- a/compiler/main/PackageConfig.hs
+++ b/compiler/main/PackageConfig.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-- |
-- Package configuration information: essentially the interface to Cabal, with
-- some utilities
@@ -45,16 +47,11 @@ defaultPackageConfig = emptyInstalledPackageInfo
-- $package_naming
-- #package_naming#
--- Mostly the compiler deals in terms of 'PackageName's, which don't
--- have the version suffix. This is so that we don't need to know the
--- version for the @-package-name@ flag, or know the versions of
--- wired-in packages like @base@ & @rts@. Versions are confined to the
--- package sub-system.
---
--- This means that in theory you could have multiple base packages installed
--- (for example), and switch between them using @-package@\/@-hide-package@.
---
--- A 'PackageId' is a string of the form @<pkg>-<version>@.
+-- Mostly the compiler deals in terms of 'PackageId's, which have the
+-- form @<pkg>-<version>@. You're expected to pass in the version for
+-- the @-package-name@ flag. However, for wired-in packages like @base@
+-- & @rts@, we don't necessarily know what the version is, so these are
+-- handled specially; see #wired_in_packages#.
-- | Turn a Cabal 'PackageIdentifier' into a GHC 'PackageId'
mkPackageId :: PackageIdentifier -> PackageId
diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs
index a13b3599b8..bb2e048cc3 100644
--- a/compiler/main/Packages.lhs
+++ b/compiler/main/Packages.lhs
@@ -2,13 +2,15 @@
% (c) The University of Glasgow, 2006
%
\begin{code}
+{-# LANGUAGE CPP #-}
+
-- | Package manipulation
module Packages (
module PackageConfig,
-- * The PackageConfigMap
PackageConfigMap, emptyPackageConfigMap, lookupPackage,
- extendPackageConfigMap, dumpPackages,
+ extendPackageConfigMap, dumpPackages, simpleDumpPackages,
-- * Reading the package config, and processing cmdline args
PackageState(..),
@@ -1078,12 +1080,26 @@ isDllName dflags _this_pkg this_mod name
-- -----------------------------------------------------------------------------
-- Displaying packages
--- | Show package info on console, if verbosity is >= 3
+-- | Show (very verbose) package info on console, if verbosity is >= 5
dumpPackages :: DynFlags -> IO ()
-dumpPackages dflags
+dumpPackages = dumpPackages' showInstalledPackageInfo
+
+dumpPackages' :: (InstalledPackageInfo -> String) -> DynFlags -> IO ()
+dumpPackages' showIPI dflags
= do let pkg_map = pkgIdMap (pkgState dflags)
putMsg dflags $
- vcat (map (text . showInstalledPackageInfo
+ vcat (map (text . showIPI
. packageConfigToInstalledPackageInfo)
(eltsUFM pkg_map))
+
+-- | Show simplified package info on console, if verbosity == 4.
+-- The idea is to only print package id, and any information that might
+-- be different from the package databases (exposure, trust)
+simpleDumpPackages :: DynFlags -> IO ()
+simpleDumpPackages = dumpPackages' showIPI
+ where showIPI ipi = let InstalledPackageId i = installedPackageId ipi
+ e = if exposed ipi then "E" else " "
+ t = if trusted ipi then "T" else " "
+ in e ++ t ++ " " ++ i
+
\end{code}
diff --git a/compiler/main/PlatformConstants.hs b/compiler/main/PlatformConstants.hs
index 03e146ca7c..b2ca32be68 100644
--- a/compiler/main/PlatformConstants.hs
+++ b/compiler/main/PlatformConstants.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-------------------------------------------------------------------------------
--
-- | Platform constants
diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs
index 1fd5d0cbcf..d993ab87c8 100644
--- a/compiler/main/PprTyThing.hs
+++ b/compiler/main/PprTyThing.hs
@@ -6,7 +6,8 @@
--
-----------------------------------------------------------------------------
-{-# OPTIONS -fno-warn-tabs #-}
+{-# LANGUAGE CPP #-}
+{-# OPTIONS_GHC -fno-warn-tabs #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and
-- detab the module (please do the detabbing in a separate patch). See
@@ -19,51 +20,83 @@ module PprTyThing (
pprTyThingLoc,
pprTyThingInContextLoc,
pprTyThingHdr,
- pprTypeForUser
+ pprTypeForUser,
+ pprFamInst
) where
+#include "HsVersions.h"
+
import TypeRep ( TyThing(..) )
-import DataCon
-import Id
-import TyCon
-import Class
-import Coercion( pprCoAxBranch )
-import CoAxiom( CoAxiom(..), brListMap )
+import CoAxiom ( coAxiomTyCon )
import HscTypes( tyThingParent_maybe )
-import Type( tidyTopType, tidyOpenType, splitForAllTys, funResultTy )
-import Kind( synTyConResKind )
-import TypeRep( pprTvBndrs, pprForAll, suppressKinds )
-import TysPrim( alphaTyVars )
import MkIface ( tyThingToIfaceDecl )
+import Type ( tidyOpenType )
+import IfaceSyn ( pprIfaceDecl, ShowSub(..), ShowHowMuch(..) )
+import FamInstEnv( FamInst( .. ), FamFlavor(..) )
import TcType
import Name
import VarEnv( emptyTidyEnv )
-import StaticFlags( opt_PprStyle_Debug )
-import DynFlags
import Outputable
import FastString
-- -----------------------------------------------------------------------------
-- Pretty-printing entities that we get from the GHC API
--- This should be a good source of sample code for using the GHC API to
--- inspect source code entities.
-
-type ShowSub = [Name]
--- [] <=> print all sub-components of the current thing
--- (n:ns) <=> print sub-component 'n' with ShowSub=ns
--- elide other sub-components to "..."
-showAll :: ShowSub
-showAll = []
+{- Note [Pretty-printing TyThings]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We pretty-print a TyThing by converting it to an IfaceDecl,
+and pretty-printing that (see ppr_ty_thing below).
+Here is why:
+
+* When pretty-printing (a type, say), the idiomatic solution is not to
+ "rename type variables on the fly", but rather to "tidy" the type
+ (which gives each variable a distinct print-name), and then
+ pretty-print it (without renaming). Separate the two
+ concerns. Functions like tidyType do this.
+
+* Alas, for type constructors, TyCon, tidying does not work well,
+ because a TyCon includes DataCons which include Types, which mention
+ TyCons. And tidying can't tidy a mutually recursive data structure
+ graph, only trees.
+
+* One alternative would be to ensure that TyCons get type variables
+ with distinct print-names. That's ok for type variables but less
+ easy for kind variables. Processing data type declarations is
+ already so complicated that I don't think it's sensible to add the
+ extra requirement that it generates only "pretty" types and kinds.
+
+* One place the non-pretty names can show up is in GHCi. But another
+ is in interface files. Look at MkIface.tyThingToIfaceDecl which
+ converts a TyThing (i.e. TyCon, Class etc) to an IfaceDecl. And it
+ already does tidying as part of that conversion! Why? Because
+ interface files contains fast-strings, not uniques, so the names
+ must at least be distinct.
+
+So if we convert to IfaceDecl, we get a nice tidy IfaceDecl, and can
+print that. Of course, that means that pretty-printing IfaceDecls
+must be careful to display nice user-friendly results, but that's ok.
+
+See #7730, #8776 for details -}
+
+--------------------
+-- | Pretty-prints a 'FamInst' (type/data family instance) with its defining location.
+pprFamInst :: FamInst -> SDoc
+-- * For data instances we go via pprTyThing of the represntational TyCon,
+-- because there is already much cleverness associated with printing
+-- data type declarations that I don't want to duplicate
+-- * For type instances we print directly here; there is no TyCon
+-- to give to pprTyThing
+--
+-- FamInstEnv.pprFamInst does a more quick-and-dirty job for internal purposes
-showSub :: NamedThing n => ShowSub -> n -> Bool
-showSub [] _ = True
-showSub (n:_) thing = n == getName thing
+pprFamInst (FamInst { fi_flavor = DataFamilyInst rep_tc })
+ = pprTyThingInContextLoc (ATyCon rep_tc)
-showSub_maybe :: NamedThing n => ShowSub -> n -> Maybe ShowSub
-showSub_maybe [] _ = Just []
-showSub_maybe (n:ns) thing = if n == getName thing then Just ns
- else Nothing
+pprFamInst (FamInst { fi_flavor = SynFamilyInst, fi_axiom = axiom
+ , fi_tys = lhs_tys, fi_rhs = rhs })
+ = showWithLoc (pprDefinedAt (getName axiom)) $
+ hang (ptext (sLit "type instance") <+> pprTypeApp (coAxiomTyCon axiom) lhs_tys)
+ 2 (equals <+> ppr rhs)
----------------------------
-- | Pretty-prints a 'TyThing' with its defining location.
@@ -73,7 +106,13 @@ pprTyThingLoc tyThing
-- | Pretty-prints a 'TyThing'.
pprTyThing :: TyThing -> SDoc
-pprTyThing thing = ppr_ty_thing (Just showAll) thing
+pprTyThing = ppr_ty_thing False []
+
+-- | Pretty-prints the 'TyThing' header. For functions and data constructors
+-- the function is equivalent to 'pprTyThing' but for type constructors
+-- and classes it prints only the header part of the declaration.
+pprTyThingHdr :: TyThing -> SDoc
+pprTyThingHdr = ppr_ty_thing True []
-- | Pretty-prints a 'TyThing' in context: that is, if the entity
-- is a data constructor, record selector, or class method, then
@@ -84,8 +123,8 @@ pprTyThingInContext thing
= go [] thing
where
go ss thing = case tyThingParent_maybe thing of
- Just parent -> go (getName thing : ss) parent
- Nothing -> ppr_ty_thing (Just ss) thing
+ Just parent -> go (getOccName thing : ss) parent
+ Nothing -> ppr_ty_thing False ss thing
-- | Like 'pprTyThingInContext', but adds the defining location.
pprTyThingInContextLoc :: TyThing -> SDoc
@@ -93,256 +132,49 @@ pprTyThingInContextLoc tyThing
= showWithLoc (pprDefinedAt (getName tyThing))
(pprTyThingInContext tyThing)
--- | Pretty-prints the 'TyThing' header. For functions and data constructors
--- the function is equivalent to 'pprTyThing' but for type constructors
--- and classes it prints only the header part of the declaration.
-pprTyThingHdr :: TyThing -> SDoc
-pprTyThingHdr = ppr_ty_thing Nothing
-
------------------------
--- NOTE: We pretty-print 'TyThing' via 'IfaceDecl' so that we can reuse the
--- 'TyCon' tidying happening in 'tyThingToIfaceDecl'. See #8776 for details.
-ppr_ty_thing :: Maybe ShowSub -> TyThing -> SDoc
-ppr_ty_thing mss tyThing = case tyThing of
- AnId id -> pprId id
- ATyCon tyCon -> case mss of
- Nothing -> pprTyConHdr tyCon
- Just ss -> pprTyCon ss tyCon
- _ -> ppr $ tyThingToIfaceDecl tyThing
-
-pprTyConHdr :: TyCon -> SDoc
-pprTyConHdr tyCon
- | Just (fam_tc, tys) <- tyConFamInst_maybe tyCon
- = ptext keyword <+> ptext (sLit "instance") <+> pprTypeApp fam_tc tys
- | Just cls <- tyConClass_maybe tyCon
- = pprClassHdr cls
- | otherwise
- = sdocWithDynFlags $ \dflags ->
- ptext keyword <+> opt_family <+> opt_stupid <+> ppr_bndr tyCon
- <+> pprTvBndrs (suppressKinds dflags (tyConKind tyCon) vars)
- where
- vars | isPrimTyCon tyCon ||
- isFunTyCon tyCon = take (tyConArity tyCon) alphaTyVars
- | otherwise = tyConTyVars tyCon
-
- keyword | isSynTyCon tyCon = sLit "type"
- | isNewTyCon tyCon = sLit "newtype"
- | otherwise = sLit "data"
-
- opt_family
- | isFamilyTyCon tyCon = ptext (sLit "family")
- | otherwise = empty
-
- opt_stupid -- The "stupid theta" part of the declaration
- | isAlgTyCon tyCon = pprThetaArrowTy (tyConStupidTheta tyCon)
- | otherwise = empty -- Returns 'empty' if null theta
-
-pprClassHdr :: Class -> SDoc
-pprClassHdr cls
- = sdocWithDynFlags $ \dflags ->
- ptext (sLit "class") <+>
- sep [ pprThetaArrowTy (classSCTheta cls)
- , ppr_bndr cls
- <+> pprTvBndrs (suppressKinds dflags (tyConKind (classTyCon cls)) tvs)
- , pprFundeps funDeps ]
+ppr_ty_thing :: Bool -> [OccName] -> TyThing -> SDoc
+-- We pretty-print 'TyThing' via 'IfaceDecl'
+-- See Note [Pretty-pringint TyThings]
+ppr_ty_thing hdr_only path ty_thing
+ = pprIfaceDecl ss (tyThingToIfaceDecl ty_thing)
where
- (tvs, funDeps) = classTvsFds cls
-
-pprId :: Var -> SDoc
-pprId ident
- = hang (ppr_bndr ident <+> dcolon)
- 2 (pprTypeForUser (idType ident))
+ ss = ShowSub { ss_how_much = how_much, ss_ppr_bndr = ppr_bndr }
+ how_much | hdr_only = ShowHeader
+ | otherwise = ShowSome path
+ name = getName ty_thing
+ ppr_bndr :: OccName -> SDoc
+ ppr_bndr | isBuiltInSyntax name
+ = ppr
+ | otherwise
+ = case nameModule_maybe name of
+ Just mod -> \ occ -> getPprStyle $ \sty ->
+ pprModulePrefix sty mod occ <> ppr occ
+ Nothing -> WARN( True, ppr name ) ppr
+ -- Nothing is unexpected here; TyThings have External names
pprTypeForUser :: Type -> SDoc
-- We do two things here.
-- a) We tidy the type, regardless
--- b) If Opt_PrintExplicitForAlls is True, we discard the foralls
--- but we do so `deeply'
+-- b) Swizzle the foralls to the top, so that without
+-- -fprint-explicit-foralls we'll suppress all the foralls
-- Prime example: a class op might have type
-- forall a. C a => forall b. Ord b => stuff
-- Then we want to display
-- (C a, Ord b) => stuff
pprTypeForUser ty
- = sdocWithDynFlags $ \ dflags ->
- if gopt Opt_PrintExplicitForalls dflags
- then ppr tidy_ty
- else ppr (mkPhiTy ctxt ty')
+ = pprSigmaType (mkSigmaTy tvs ctxt tau)
where
- (_, ctxt, ty') = tcSplitSigmaTy tidy_ty
- (_, tidy_ty) = tidyOpenType emptyTidyEnv ty
+ (tvs, ctxt, tau) = tcSplitSigmaTy tidy_ty
+ (_, tidy_ty) = tidyOpenType emptyTidyEnv ty
-- Often the types/kinds we print in ghci are fully generalised
-- and have no free variables, but it turns out that we sometimes
-- print un-generalised kinds (eg when doing :k T), so it's
-- better to use tidyOpenType here
-pprTyCon :: ShowSub -> TyCon -> SDoc
-pprTyCon ss tyCon
- | Just syn_rhs <- synTyConRhs_maybe tyCon
- = case syn_rhs of
- OpenSynFamilyTyCon -> pp_tc_with_kind
- BuiltInSynFamTyCon {} -> pp_tc_with_kind
-
- ClosedSynFamilyTyCon (CoAxiom { co_ax_branches = branches })
- -> hang closed_family_header
- 2 (vcat (brListMap (pprCoAxBranch tyCon) branches))
-
- AbstractClosedSynFamilyTyCon
- -> closed_family_header <+> ptext (sLit "..")
-
- SynonymTyCon rhs_ty
- -> hang (pprTyConHdr tyCon <+> equals)
- 2 (ppr rhs_ty) -- Don't suppress foralls on RHS type!
-
- -- e.g. type T = forall a. a->a
- | Just cls <- tyConClass_maybe tyCon
- = (pp_roles (== Nominal)) $$ pprClass ss cls
-
- | otherwise
- = (pp_roles (== Representational)) $$ pprAlgTyCon ss tyCon
-
- where
- -- if, for each role, suppress_if role is True, then suppress the role
- -- output
- pp_roles :: (Role -> Bool) -> SDoc
- pp_roles suppress_if
- = sdocWithDynFlags $ \dflags ->
- let roles = suppressKinds dflags (tyConKind tyCon) (tyConRoles tyCon)
- in ppUnless (isFamInstTyCon tyCon || all suppress_if roles) $
- -- Don't display roles for data family instances (yet)
- -- See discussion on Trac #8672.
- ptext (sLit "type role") <+> ppr tyCon <+> hsep (map ppr roles)
-
- pp_tc_with_kind = vcat [ pp_roles (const True)
- , pprTyConHdr tyCon <+> dcolon
- <+> pprTypeForUser (synTyConResKind tyCon) ]
- closed_family_header
- = pp_tc_with_kind <+> ptext (sLit "where")
-
-pprAlgTyCon :: ShowSub -> TyCon -> SDoc
-pprAlgTyCon ss tyCon
- | gadt = pprTyConHdr tyCon <+> ptext (sLit "where") $$
- nest 2 (vcat (ppr_trim (map show_con datacons)))
- | otherwise = hang (pprTyConHdr tyCon)
- 2 (add_bars (ppr_trim (map show_con datacons)))
- where
- datacons = tyConDataCons tyCon
- gadt = any (not . isVanillaDataCon) datacons
-
- ok_con dc = showSub ss dc || any (showSub ss) (dataConFieldLabels dc)
- show_con dc
- | ok_con dc = Just (pprDataConDecl ss gadt dc)
- | otherwise = Nothing
-
-pprDataConDecl :: ShowSub -> Bool -> DataCon -> SDoc
-pprDataConDecl ss gadt_style dataCon
- | not gadt_style = ppr_fields tys_w_strs
- | otherwise = ppr_bndr dataCon <+> dcolon <+>
- sep [ pp_foralls, pprThetaArrowTy theta, pp_tau ]
- -- Printing out the dataCon as a type signature, in GADT style
- where
- (forall_tvs, theta, tau) = tcSplitSigmaTy (dataConUserType dataCon)
- (arg_tys, res_ty) = tcSplitFunTys tau
- labels = dataConFieldLabels dataCon
- stricts = dataConStrictMarks dataCon
- tys_w_strs = zip (map user_ify stricts) arg_tys
- pp_foralls = sdocWithDynFlags $ \dflags ->
- ppWhen (gopt Opt_PrintExplicitForalls dflags)
- (pprForAll forall_tvs)
-
- pp_tau = foldr add (ppr res_ty) tys_w_strs
- add str_ty pp_ty = pprParendBangTy str_ty <+> arrow <+> pp_ty
-
- pprParendBangTy (bang,ty) = ppr bang <> pprParendType ty
- pprBangTy (bang,ty) = ppr bang <> ppr ty
-
- -- See Note [Printing bangs on data constructors]
- user_ify :: HsBang -> HsBang
- user_ify bang | opt_PprStyle_Debug = bang
- user_ify HsStrict = HsUserBang Nothing True
- user_ify (HsUnpack {}) = HsUserBang (Just True) True
- user_ify bang = bang
-
- maybe_show_label (lbl,bty)
- | showSub ss lbl = Just (ppr_bndr lbl <+> dcolon <+> pprBangTy bty)
- | otherwise = Nothing
-
- ppr_fields [ty1, ty2]
- | dataConIsInfix dataCon && null labels
- = sep [pprParendBangTy ty1, pprInfixName dataCon, pprParendBangTy ty2]
- ppr_fields fields
- | null labels
- = ppr_bndr dataCon <+> sep (map pprParendBangTy fields)
- | otherwise
- = ppr_bndr dataCon
- <+> (braces $ sep $ punctuate comma $ ppr_trim $
- map maybe_show_label (zip labels fields))
-
-pprClass :: ShowSub -> Class -> SDoc
-pprClass ss cls
- | null methods && null assoc_ts
- = pprClassHdr cls
- | otherwise
- = vcat [ pprClassHdr cls <+> ptext (sLit "where")
- , nest 2 (vcat $ ppr_trim $
- map show_at assoc_ts ++ map show_meth methods)]
- where
- methods = classMethods cls
- assoc_ts = classATs cls
- show_meth id | showSub ss id = Just (pprClassMethod id)
- | otherwise = Nothing
- show_at tc = case showSub_maybe ss tc of
- Just ss' -> Just (pprTyCon ss' tc)
- Nothing -> Nothing
-
-pprClassMethod :: Id -> SDoc
-pprClassMethod id
- = hang (ppr_bndr id <+> dcolon) 2 (pprTypeForUser op_ty)
- where
- -- Here's the magic incantation to strip off the dictionary
- -- from the class op type. Stolen from IfaceSyn.tyThingToIfaceDecl.
- --
- -- It's important to tidy it *before* splitting it up, so that if
- -- we have class C a b where
- -- op :: forall a. a -> b
- -- then the inner forall on op gets renamed to a1, and we print
- -- (when dropping foralls)
- -- class C a b where
- -- op :: a1 -> b
-
- tidy_sel_ty = tidyTopType (idType id)
- (_sel_tyvars, rho_ty) = splitForAllTys tidy_sel_ty
- op_ty = funResultTy rho_ty
-
-ppr_trim :: [Maybe SDoc] -> [SDoc]
--- Collapse a group of Nothings to a single "..."
-ppr_trim xs
- = snd (foldr go (False, []) xs)
- where
- go (Just doc) (_, so_far) = (False, doc : so_far)
- go Nothing (True, so_far) = (True, so_far)
- go Nothing (False, so_far) = (True, ptext (sLit "...") : so_far)
-
-add_bars :: [SDoc] -> SDoc
-add_bars [] = empty
-add_bars [c] = equals <+> c
-add_bars (c:cs) = sep ((equals <+> c) : map (char '|' <+>) cs)
-
--- Wrap operators in ()
-ppr_bndr :: NamedThing a => a -> SDoc
-ppr_bndr a = parenSymOcc (getOccName a) (ppr (getName a))
-
showWithLoc :: SDoc -> SDoc -> SDoc
showWithLoc loc doc
= hang doc 2 (char '\t' <> comment <+> loc)
-- The tab tries to make them line up a bit
where
comment = ptext (sLit "--")
-
-{-
-Note [Printing bangs on data constructors]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-For imported data constructors the dataConStrictMarks are the
-representation choices (see Note [Bangs on data constructor arguments]
-in DataCon.lhs). So we have to fiddle a little bit here to turn them
-back into user-printable form.
--}
diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs
index 01dc3b7275..eb7ede00c6 100644
--- a/compiler/main/StaticFlags.hs
+++ b/compiler/main/StaticFlags.hs
@@ -1,4 +1,5 @@
-{-# OPTIONS -fno-cse #-}
+{-# LANGUAGE CPP #-}
+{-# OPTIONS_GHC -fno-cse #-}
-- -fno-cse is needed for GLOBAL_VAR's to behave properly
-----------------------------------------------------------------------------
diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs
index 53240faf48..641b0cb12f 100644
--- a/compiler/main/SysTools.lhs
+++ b/compiler/main/SysTools.lhs
@@ -7,6 +7,8 @@
-----------------------------------------------------------------------------
\begin{code}
+{-# LANGUAGE CPP, ScopedTypeVariables #-}
+
module SysTools (
-- Initialisation
initSysTools,
@@ -233,6 +235,8 @@ initSysTools mbMinusB
-- to make that possible, so for now you can't.
gcc_prog <- getSetting "C compiler command"
gcc_args_str <- getSetting "C compiler flags"
+ cpp_prog <- getSetting "Haskell CPP command"
+ cpp_args_str <- getSetting "Haskell CPP flags"
let unreg_gcc_args = if targetUnregisterised
then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
else []
@@ -241,6 +245,7 @@ initSysTools mbMinusB
| mkTablesNextToCode targetUnregisterised
= ["-DTABLES_NEXT_TO_CODE"]
| otherwise = []
+ cpp_args= map Option (words cpp_args_str)
gcc_args = map Option (words gcc_args_str
++ unreg_gcc_args
++ tntc_gcc_args)
@@ -283,10 +288,7 @@ initSysTools mbMinusB
-- cpp is derived from gcc on all platforms
-- HACK, see setPgmP below. We keep 'words' here to remember to fix
-- Config.hs one day.
- let cpp_prog = gcc_prog
- cpp_args = Option "-E"
- : map Option (words cRAWCPP_FLAGS)
- ++ gcc_args
+
-- Other things being equal, as and ld are simply gcc
gcc_link_args_str <- getSetting "C compiler link flags"
@@ -727,7 +729,7 @@ getLinkerInfo' dflags = do
-- that doesn't support --version. We can just assume that's
-- what we're using.
return $ DarwinLD []
- OSiOS ->
+ OSiOS ->
-- Ditto for iOS
return $ DarwinLD []
OSMinGW32 ->
@@ -786,12 +788,15 @@ getCompilerInfo' dflags = do
-- Regular clang
| any ("clang version" `isPrefixOf`) stde =
return Clang
+ -- XCode 5.1 clang
+ | any ("Apple LLVM version 5.1" `isPrefixOf`) stde =
+ return AppleClang51
-- XCode 5 clang
| any ("Apple LLVM version" `isPrefixOf`) stde =
- return Clang
+ return AppleClang
-- XCode 4.1 clang
| any ("Apple clang version" `isPrefixOf`) stde =
- return Clang
+ return AppleClang
-- Unknown linker.
| otherwise = fail "invalid -v output, or compiler is unsupported"
diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs
index b20658b073..7d47330044 100644
--- a/compiler/main/TidyPgm.lhs
+++ b/compiler/main/TidyPgm.lhs
@@ -4,6 +4,8 @@
\section{Tidying up Core}
\begin{code}
+{-# LANGUAGE CPP #-}
+
module TidyPgm (
mkBootModDetailsTc, tidyProgram, globaliseAndTidyId
) where
@@ -21,11 +23,14 @@ import CorePrep
import CoreUtils
import Literal
import Rules
+import PatSyn
+import ConLike
import CoreArity ( exprArity, exprBotStrictness_maybe )
import VarEnv
import VarSet
import Var
import Id
+import MkId ( mkDictSelRhs )
import IdInfo
import InstEnv
import FamInstEnv
@@ -129,18 +134,20 @@ mkBootModDetailsTc hsc_env
TcGblEnv{ tcg_exports = exports,
tcg_type_env = type_env, -- just for the Ids
tcg_tcs = tcs,
+ tcg_patsyns = pat_syns,
tcg_insts = insts,
tcg_fam_insts = fam_insts
}
= do { let dflags = hsc_dflags hsc_env
; showPass dflags CoreTidy
- ; let { insts' = map (tidyClsInstDFun globaliseAndTidyId) insts
- ; dfun_ids = map instanceDFunId insts'
+ ; let { insts' = map (tidyClsInstDFun globaliseAndTidyId) insts
+ ; pat_syns' = map (tidyPatSynIds globaliseAndTidyId) pat_syns
+ ; dfun_ids = map instanceDFunId insts'
+ ; pat_syn_ids = concatMap patSynIds pat_syns'
; type_env1 = mkBootTypeEnv (availsToNameSet exports)
- (typeEnvIds type_env) tcs fam_insts
- ; type_env2 = extendTypeEnvWithPatSyns type_env1 (typeEnvPatSyns type_env)
- ; type_env' = extendTypeEnvWithIds type_env2 dfun_ids
+ (typeEnvIds type_env) tcs fam_insts
+ ; type_env' = extendTypeEnvWithIds type_env1 (pat_syn_ids ++ dfun_ids)
}
; return (ModDetails { md_types = type_env'
, md_insts = insts'
@@ -333,19 +340,13 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
; let { final_ids = [ id | id <- bindersOfBinds tidy_binds,
isExternalName (idName id)]
- ; final_patsyns = filter (isExternalName . getName) patsyns
-
- ; type_env' = extendTypeEnvWithIds type_env final_ids
- ; type_env'' = extendTypeEnvWithPatSyns type_env' final_patsyns
-
- ; tidy_type_env = tidyTypeEnv omit_prags type_env''
+ ; type_env1 = extendTypeEnvWithIds type_env final_ids
- ; tidy_insts = map (tidyClsInstDFun (lookup_dfun tidy_type_env)) insts
- -- A DFunId will have a binding in tidy_binds, and so
- -- will now be in final_env, replete with IdInfo
- -- Its name will be unchanged since it was born, but
- -- we want Global, IdInfo-rich (or not) DFunId in the
- -- tidy_insts
+ ; tidy_insts = map (tidyClsInstDFun (lookup_aux_id tidy_type_env)) insts
+ -- A DFunId will have a binding in tidy_binds, and so will now be in
+ -- tidy_type_env, replete with IdInfo. Its name will be unchanged since
+ -- it was born, but we want Global, IdInfo-rich (or not) DFunId in the
+ -- tidy_insts. Similarly the Ids inside a PatSyn.
; tidy_rules = tidyRules tidy_env ext_rules
-- You might worry that the tidy_env contains IdInfo-rich stuff
@@ -354,6 +355,16 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
; tidy_vect_info = tidyVectInfo tidy_env vect_info
+ -- Tidy the Ids inside each PatSyn, very similarly to DFunIds
+ -- and then override the PatSyns in the type_env with the new tidy ones
+ -- This is really the only reason we keep mg_patsyns at all; otherwise
+ -- they could just stay in type_env
+ ; tidy_patsyns = map (tidyPatSynIds (lookup_aux_id tidy_type_env)) patsyns
+ ; type_env2 = extendTypeEnvList type_env1
+ [AConLike (PatSynCon ps) | ps <- tidy_patsyns ]
+
+ ; tidy_type_env = tidyTypeEnv omit_prags type_env2
+
-- See Note [Injecting implicit bindings]
; all_tidy_binds = implicit_binds ++ tidy_binds
@@ -405,11 +416,11 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
})
}
-lookup_dfun :: TypeEnv -> Var -> Id
-lookup_dfun type_env dfun_id
- = case lookupTypeEnv type_env (idName dfun_id) of
- Just (AnId dfun_id') -> dfun_id'
- _other -> pprPanic "lookup_dfun" (ppr dfun_id)
+lookup_aux_id :: TypeEnv -> Var -> Id
+lookup_aux_id type_env id
+ = case lookupTypeEnv type_env (idName id) of
+ Just (AnId id') -> id'
+ _other -> pprPanic "lookup_axu_id" (ppr id)
--------------------------
tidyTypeEnv :: Bool -- Compiling without -O, so omit prags
@@ -517,7 +528,7 @@ of exceptions, and finally I gave up the battle:
Note [Injecting implicit bindings]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We inject the implict bindings right at the end, in CoreTidy.
+We inject the implicit bindings right at the end, in CoreTidy.
Some of these bindings, notably record selectors, are not
constructed in an optimised form. E.g. record selector for
data T = MkT { x :: {-# UNPACK #-} !Int }
@@ -559,14 +570,16 @@ Oh: two other reasons for injecting them late:
There is one sort of implicit binding that is injected still later,
namely those for data constructor workers. Reason (I think): it's
really just a code generation trick.... binding itself makes no sense.
-See CorePrep Note [Data constructor workers].
+See Note [Data constructor workers] in CorePrep.
\begin{code}
getTyConImplicitBinds :: TyCon -> [CoreBind]
getTyConImplicitBinds tc = map get_defn (mapMaybe dataConWrapId_maybe (tyConDataCons tc))
getClassImplicitBinds :: Class -> [CoreBind]
-getClassImplicitBinds cls = map get_defn (classAllSelIds cls)
+getClassImplicitBinds cls
+ = [ NonRec op (mkDictSelRhs cls val_index)
+ | (op, val_index) <- classAllSelIds cls `zip` [0..] ]
get_defn :: Id -> CoreBind
get_defn id = NonRec id (unfoldingTemplate (realIdUnfolding id))