X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FDynFlags.hs;h=a94a3f411f0970acf92b9528fd0c716ccf4a7d7b;hp=8f0faec948c08d984c8fff9a0ef1f28aacffff4c;hb=34c8d0312071f7d0f4d221a997d3408c653ef9e5;hpb=d196d84a6a6fbd128da207c03b1c5f29fb24e6a4 diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 8f0faec..a94a3f4 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -32,7 +32,7 @@ module DynFlags ( Option(..), showOpt, DynLibLoader(..), fFlags, fLangFlags, xFlags, - dphPackage, + DPHBackend(..), dphPackage, wayNames, -- ** Manipulating DynFlags @@ -133,6 +133,7 @@ data DynFlag | Opt_D_dump_foreign | Opt_D_dump_inlinings | Opt_D_dump_rule_firings + | Opt_D_dump_rule_rewrites | Opt_D_dump_occur_anal | Opt_D_dump_parsed | Opt_D_dump_rn @@ -180,6 +181,7 @@ data DynFlag | Opt_WarnHiShadows | Opt_WarnImplicitPrelude | Opt_WarnIncompletePatterns + | Opt_WarnIncompleteUniPatterns | Opt_WarnIncompletePatternsRecUpd | Opt_WarnMissingFields | Opt_WarnMissingImportList @@ -199,6 +201,7 @@ data DynFlag | Opt_WarnDodgyImports | Opt_WarnOrphans | Opt_WarnAutoOrphans + | Opt_WarnIdentities | Opt_WarnTabs | Opt_WarnUnrecognisedPragmas | Opt_WarnDodgyForeignImports @@ -223,7 +226,7 @@ data DynFlag | Opt_DoEtaReduction | Opt_CaseMerge | Opt_UnboxStrictFields - | Opt_MethodSharing + | Opt_MethodSharing -- Now a no-op; remove in GHC 7.2 | Opt_DictsCheap | Opt_EnableRewriteRules -- Apply rewrite rules during simplification | Opt_Vectorise @@ -267,6 +270,7 @@ data DynFlag | Opt_BuildingCabalPackage | Opt_SSE2 | Opt_GhciSandbox + | Opt_HelpfulErrors -- temporary flags | Opt_RunCPS @@ -302,8 +306,9 @@ data ExtensionFlag | Opt_ForeignFunctionInterface | Opt_UnliftedFFITypes | Opt_GHCForeignImportPrim - | Opt_PArr -- Syntactic support for parallel arrays + | Opt_ParallelArrays -- Syntactic support for parallel arrays | Opt_Arrows -- Arrow-notation syntax + | Opt_ModalTypes -- Heterogeneous Metaprogramming (modal types, brackets, escape, CSP) | Opt_TemplateHaskell | Opt_QuasiQuotes | Opt_ImplicitParams @@ -319,6 +324,7 @@ data ExtensionFlag | Opt_RecordPuns | Opt_ViewPatterns | Opt_GADTs + | Opt_GADTSyntax | Opt_NPlusKPatterns | Opt_DoAndIfThenElse | Opt_RebindableSyntax @@ -355,11 +361,12 @@ data ExtensionFlag | Opt_ImpredicativeTypes | Opt_TypeOperators | Opt_PackageImports - | Opt_NewQualifiedOperators | Opt_ExplicitForAll | Opt_AlternativeLayoutRule | Opt_AlternativeLayoutRuleTransitional | Opt_DatatypeContexts + | Opt_NondecreasingIndentation + | Opt_RelaxedLayout deriving (Eq, Show) -- | Contains not only a collection of 'DynFlag's but also a plethora of @@ -381,6 +388,8 @@ data DynFlags = DynFlags { specConstrThreshold :: Maybe Int, -- ^ Threshold for SpecConstr specConstrCount :: Maybe Int, -- ^ Max number of specialisations for any one function liberateCaseThreshold :: Maybe Int, -- ^ Threshold for LiberateCase + floatLamArgs :: Maybe Int, -- ^ Arg count for lambda floating + -- See CoreMonad.FloatOutSwitches #ifndef OMIT_NATIVE_CODEGEN targetPlatform :: Platform, -- ^ The platform we're compiling for. Used by the NCG. @@ -649,6 +658,7 @@ defaultDynFlags = specConstrThreshold = Just 200, specConstrCount = Just 3, liberateCaseThreshold = Just 200, + floatLamArgs = Just 0, -- Default: float only if no fvs strictnessBefore = [], #ifndef OMIT_NATIVE_CODEGEN @@ -661,7 +671,7 @@ defaultDynFlags = mainFunIs = Nothing, ctxtStkDepth = mAX_CONTEXT_REDUCTION_DEPTH, - dphBackend = DPHPar, + dphBackend = DPHNone, thisPackage = mainPackageId, @@ -790,13 +800,21 @@ languageExtensions Nothing -- In due course I'd like Opt_MonoLocalBinds to be on by default -- But NB it's implied by GADTs etc -- SLPJ September 2010 + : Opt_NondecreasingIndentation -- This has been on by default for some time : languageExtensions (Just Haskell2010) languageExtensions (Just Haskell98) = [Opt_ImplicitPrelude, Opt_MonomorphismRestriction, Opt_NPlusKPatterns, - Opt_DatatypeContexts] + Opt_DatatypeContexts, + Opt_NondecreasingIndentation + -- strictly speaking non-standard, but we always had this + -- on implicitly before the option was added in 7.1, and + -- turning it off breaks code, so we're keeping it on for + -- backwards compatibility. Cabal uses -XHaskell98 by + -- default unless you specify another language. + ] languageExtensions (Just Haskell2010) = [Opt_ImplicitPrelude, @@ -1224,6 +1242,7 @@ dynamic_flags = [ , Flag "ddump-foreign" (setDumpFlag Opt_D_dump_foreign) , Flag "ddump-inlinings" (setDumpFlag Opt_D_dump_inlinings) , Flag "ddump-rule-firings" (setDumpFlag Opt_D_dump_rule_firings) + , Flag "ddump-rule-rewrites" (setDumpFlag Opt_D_dump_rule_rewrites) , Flag "ddump-occur-anal" (setDumpFlag Opt_D_dump_occur_anal) , Flag "ddump-parsed" (setDumpFlag Opt_D_dump_parsed) , Flag "ddump-rn" (setDumpFlag Opt_D_dump_rn) @@ -1302,6 +1321,8 @@ dynamic_flags = [ , Flag "frule-check" (SepArg (\s -> upd (\d -> d{ ruleCheck = Just s }))) , Flag "fcontext-stack" (intSuffix (\n d -> d{ ctxtStkDepth = n })) , Flag "fstrictness-before" (intSuffix (\n d -> d{ strictnessBefore = n : strictnessBefore d })) + , Flag "ffloat-lam-args" (intSuffix (\n d -> d{ floatLamArgs = Just n })) + , Flag "ffloat-all-lams" (intSuffix (\n d -> d{ floatLamArgs = Nothing })) ------ Profiling ---------------------------------------------------- @@ -1322,6 +1343,7 @@ dynamic_flags = [ , Flag "fdph-seq" (NoArg (setDPHBackend DPHSeq)) , Flag "fdph-par" (NoArg (setDPHBackend DPHPar)) , Flag "fdph-this" (NoArg (setDPHBackend DPHThis)) + , Flag "fdph-none" (NoArg (setDPHBackend DPHNone)) ------ Compiler flags ----------------------------------------------- @@ -1339,13 +1361,13 @@ dynamic_flags = [ , Flag "fglasgow-exts" (NoArg (enableGlasgowExts >> deprecate "Use individual extensions instead")) , Flag "fno-glasgow-exts" (NoArg (disableGlasgowExts >> deprecate "Use individual extensions instead")) ] - ++ map (mkFlag True "f" setDynFlag ) fFlags - ++ map (mkFlag False "fno-" unSetDynFlag) fFlags - ++ map (mkFlag True "f" setExtensionFlag ) fLangFlags - ++ map (mkFlag False "fno-" unSetExtensionFlag) fLangFlags - ++ map (mkFlag True "X" setExtensionFlag ) xFlags - ++ map (mkFlag False "XNo" unSetExtensionFlag) xFlags - ++ map (mkFlag True "X" setLanguage) languageFlags + ++ map (mkFlag turnOn "f" setDynFlag ) fFlags + ++ map (mkFlag turnOff "fno-" unSetDynFlag) fFlags + ++ map (mkFlag turnOn "f" setExtensionFlag ) fLangFlags + ++ map (mkFlag turnOff "fno-" unSetExtensionFlag) fLangFlags + ++ map (mkFlag turnOn "X" setExtensionFlag ) xFlags + ++ map (mkFlag turnOff "XNo" unSetExtensionFlag) xFlags + ++ map (mkFlag turnOn "X" setLanguage) languageFlags package_flags :: [Flag (CmdLineP DynFlags)] package_flags = [ @@ -1362,37 +1384,39 @@ package_flags = [ ; deprecate "Use -package instead" })) ] -type FlagSpec flag - = ( String -- Flag in string form - , flag -- Flag in internal form - , Bool -> DynP ()) -- Extra action to run when the flag is found - -- Typically, emit a warning or error - -- True <=> we are turning the flag on +type TurnOnFlag = Bool -- True <=> we are turning the flag on -- False <=> we are turning the flag off +turnOn :: TurnOnFlag; turnOn = True +turnOff :: TurnOnFlag; turnOff = False +type FlagSpec flag + = ( String -- Flag in string form + , flag -- Flag in internal form + , TurnOnFlag -> DynP ()) -- Extra action to run when the flag is found + -- Typically, emit a warning or error -mkFlag :: Bool -- ^ True <=> it should be turned on +mkFlag :: TurnOnFlag -- ^ True <=> it should be turned on -> String -- ^ The flag prefix -> (flag -> DynP ()) -- ^ What to do when the flag is found -> FlagSpec flag -- ^ Specification of this particular flag -> Flag (CmdLineP DynFlags) -mkFlag turnOn flagPrefix f (name, flag, extra_action) - = Flag (flagPrefix ++ name) (NoArg (f flag >> extra_action turnOn)) +mkFlag turn_on flagPrefix f (name, flag, extra_action) + = Flag (flagPrefix ++ name) (NoArg (f flag >> extra_action turn_on)) -deprecatedForExtension :: String -> Bool -> DynP () +deprecatedForExtension :: String -> TurnOnFlag -> DynP () deprecatedForExtension lang turn_on = deprecate ("use -X" ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead") where flag | turn_on = lang | otherwise = "No"++lang -useInstead :: String -> Bool -> DynP () +useInstead :: String -> TurnOnFlag -> DynP () useInstead flag turn_on = deprecate ("Use -f" ++ no ++ flag ++ " instead") where no = if turn_on then "" else "no-" -nop :: Bool -> DynP () +nop :: TurnOnFlag -> DynP () nop _ = return () -- | These @-f\@ flags can all be reversed with @-fno-\@ @@ -1405,6 +1429,7 @@ fFlags = [ ( "warn-hi-shadowing", Opt_WarnHiShadows, nop ), ( "warn-implicit-prelude", Opt_WarnImplicitPrelude, nop ), ( "warn-incomplete-patterns", Opt_WarnIncompletePatterns, nop ), + ( "warn-incomplete-uni-patterns", Opt_WarnIncompleteUniPatterns, nop ), ( "warn-incomplete-record-updates", Opt_WarnIncompletePatternsRecUpd, nop ), ( "warn-missing-fields", Opt_WarnMissingFields, nop ), ( "warn-missing-import-lists", Opt_WarnMissingImportList, nop ), @@ -1422,6 +1447,7 @@ fFlags = [ ( "warn-deprecations", Opt_WarnWarningsDeprecations, nop ), ( "warn-deprecated-flags", Opt_WarnDeprecatedFlags, nop ), ( "warn-orphans", Opt_WarnOrphans, nop ), + ( "warn-identities", Opt_WarnIdentities, nop ), ( "warn-auto-orphans", Opt_WarnAutoOrphans, nop ), ( "warn-tabs", Opt_WarnTabs, nop ), ( "warn-unrecognised-pragmas", Opt_WarnUnrecognisedPragmas, nop ), @@ -1446,7 +1472,9 @@ fFlags = [ ( "do-eta-reduction", Opt_DoEtaReduction, nop ), ( "case-merge", Opt_CaseMerge, nop ), ( "unbox-strict-fields", Opt_UnboxStrictFields, nop ), - ( "method-sharing", Opt_MethodSharing, nop ), + ( "method-sharing", Opt_MethodSharing, + \_ -> deprecate "doesn't do anything any more"), + -- Remove altogether in GHC 7.2 ( "dicts-cheap", Opt_DictsCheap, nop ), ( "excess-precision", Opt_ExcessPrecision, nop ), ( "eager-blackholing", Opt_EagerBlackHoling, nop ), @@ -1472,6 +1500,7 @@ fFlags = [ ( "ext-core", Opt_EmitExternalCore, nop ), ( "shared-implib", Opt_SharedImplib, nop ), ( "ghci-sandbox", Opt_GhciSandbox, nop ), + ( "helpful-errors", Opt_HelpfulErrors, nop ), ( "building-cabal-package", Opt_BuildingCabalPackage, nop ), ( "implicit-import-qualified", Opt_ImplicitImportQualified, nop ) ] @@ -1503,8 +1532,10 @@ fLangFlags = [ deprecatedForExtension "ImplicitParams" ), ( "scoped-type-variables", Opt_ScopedTypeVariables, deprecatedForExtension "ScopedTypeVariables" ), - ( "parr", Opt_PArr, - deprecatedForExtension "PArr" ), + ( "parr", Opt_ParallelArrays, + deprecatedForExtension "ParallelArrays" ), + ( "PArr", Opt_ParallelArrays, + deprecatedForExtension "ParallelArrays" ), ( "allow-overlapping-instances", Opt_OverlappingInstances, deprecatedForExtension "OverlappingInstances" ), ( "allow-undecidable-instances", Opt_UndecidableInstances, @@ -1556,7 +1587,8 @@ xFlags = [ deprecatedForExtension "DoRec"), ( "DoRec", Opt_DoRec, nop ), ( "Arrows", Opt_Arrows, nop ), - ( "PArr", Opt_PArr, nop ), + ( "ModalTypes", Opt_ModalTypes, nop ), + ( "ParallelArrays", Opt_ParallelArrays, nop ), ( "TemplateHaskell", Opt_TemplateHaskell, checkTemplateHaskellOk ), ( "QuasiQuotes", Opt_QuasiQuotes, nop ), ( "Generics", Opt_Generics, nop ), @@ -1568,6 +1600,7 @@ xFlags = [ ( "DisambiguateRecordFields", Opt_DisambiguateRecordFields, nop ), ( "OverloadedStrings", Opt_OverloadedStrings, nop ), ( "GADTs", Opt_GADTs, nop ), + ( "GADTSyntax", Opt_GADTSyntax, nop ), ( "ViewPatterns", Opt_ViewPatterns, nop ), ( "TypeFamilies", Opt_TypeFamilies, nop ), ( "BangPatterns", Opt_BangPatterns, nop ), @@ -1580,6 +1613,8 @@ xFlags = [ ( "AlternativeLayoutRule", Opt_AlternativeLayoutRule, nop ), ( "AlternativeLayoutRuleTransitional",Opt_AlternativeLayoutRuleTransitional, nop ), ( "DatatypeContexts", Opt_DatatypeContexts, nop ), + ( "NondecreasingIndentation", Opt_NondecreasingIndentation, nop ), + ( "RelaxedLayout", Opt_RelaxedLayout, nop ), ( "MonoLocalBinds", Opt_MonoLocalBinds, nop ), ( "RelaxedPolyRec", Opt_RelaxedPolyRec, \ turn_on -> if not turn_on @@ -1608,9 +1643,7 @@ xFlags = [ ( "OverlappingInstances", Opt_OverlappingInstances, nop ), ( "UndecidableInstances", Opt_UndecidableInstances, nop ), ( "IncoherentInstances", Opt_IncoherentInstances, nop ), - ( "PackageImports", Opt_PackageImports, nop ), - ( "NewQualifiedOperators", Opt_NewQualifiedOperators, - \_ -> deprecate "The new qualified operator syntax was rejected by Haskell'" ) + ( "PackageImports", Opt_PackageImports, nop ) ] defaultFlags :: [DynFlag] @@ -1618,8 +1651,6 @@ defaultFlags = [ Opt_AutoLinkPackages, Opt_ReadUserPackageConf, - Opt_MethodSharing, - Opt_DoAsmMangling, Opt_SharedImplib, @@ -1627,7 +1658,8 @@ defaultFlags Opt_GenManifest, Opt_EmbedManifest, Opt_PrintBindContents, - Opt_GhciSandbox + Opt_GhciSandbox, + Opt_HelpfulErrors ] ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns] @@ -1635,30 +1667,39 @@ defaultFlags ++ standardWarnings -impliedFlags :: [(ExtensionFlag, ExtensionFlag)] +impliedFlags :: [(ExtensionFlag, TurnOnFlag, ExtensionFlag)] impliedFlags - = [ (Opt_RankNTypes, Opt_ExplicitForAll) - , (Opt_Rank2Types, Opt_ExplicitForAll) - , (Opt_ScopedTypeVariables, Opt_ExplicitForAll) - , (Opt_LiberalTypeSynonyms, Opt_ExplicitForAll) - , (Opt_ExistentialQuantification, Opt_ExplicitForAll) - , (Opt_PolymorphicComponents, Opt_ExplicitForAll) - - , (Opt_RebindableSyntax, Opt_ImplicitPrelude) - - , (Opt_GADTs, Opt_MonoLocalBinds) - , (Opt_TypeFamilies, Opt_MonoLocalBinds) - - , (Opt_TypeFamilies, Opt_KindSignatures) -- Type families use kind signatures + = [ (Opt_RankNTypes, turnOn, Opt_ExplicitForAll) + , (Opt_Rank2Types, turnOn, Opt_ExplicitForAll) + , (Opt_ScopedTypeVariables, turnOn, Opt_ExplicitForAll) + , (Opt_LiberalTypeSynonyms, turnOn, Opt_ExplicitForAll) + , (Opt_ExistentialQuantification, turnOn, Opt_ExplicitForAll) + , (Opt_PolymorphicComponents, turnOn, Opt_ExplicitForAll) + , (Opt_FlexibleInstances, turnOn, Opt_TypeSynonymInstances) + + , (Opt_ModalTypes, turnOn, Opt_RankNTypes) + , (Opt_ModalTypes, turnOn, Opt_ExplicitForAll) + , (Opt_ModalTypes, turnOn, Opt_RebindableSyntax) + , (Opt_ModalTypes, turnOff, Opt_MonomorphismRestriction) + + , (Opt_RebindableSyntax, turnOff, Opt_ImplicitPrelude) -- NB: turn off! + + , (Opt_GADTs, turnOn, Opt_GADTSyntax) + , (Opt_GADTs, turnOn, Opt_MonoLocalBinds) + , (Opt_TypeFamilies, turnOn, Opt_MonoLocalBinds) + + , (Opt_TypeFamilies, turnOn, Opt_KindSignatures) -- Type families use kind signatures -- all over the place - , (Opt_ImpredicativeTypes, Opt_RankNTypes) + , (Opt_ImpredicativeTypes, turnOn, Opt_RankNTypes) -- Record wild-cards implies field disambiguation -- Otherwise if you write (C {..}) you may well get -- stuff like " 'a' not in scope ", which is a bit silly -- if the compiler has just filled in field 'a' of constructor 'C' - , (Opt_RecordWildCards, Opt_DisambiguateRecordFields) + , (Opt_RecordWildCards, turnOn, Opt_DisambiguateRecordFields) + + , (Opt_ParallelArrays, turnOn, Opt_ParallelListComp) ] optLevelFlags :: [([Int], DynFlag)] @@ -1717,6 +1758,7 @@ standardWarnings ] minusWOpts :: [DynFlag] +-- Things you get with -W minusWOpts = standardWarnings ++ [ Opt_WarnUnusedBinds, @@ -1728,6 +1770,7 @@ minusWOpts ] minusWallOpts :: [DynFlag] +-- Things you get with -Wall minusWallOpts = minusWOpts ++ [ Opt_WarnTypeDefaults, @@ -1738,17 +1781,18 @@ minusWallOpts Opt_WarnUnusedDoBind ] --- minuswRemovesOpts should be every warning option minuswRemovesOpts :: [DynFlag] +-- minuswRemovesOpts should be every warning option minuswRemovesOpts = minusWallOpts ++ - [Opt_WarnImplicitPrelude, + [Opt_WarnTabs, Opt_WarnIncompletePatternsRecUpd, + Opt_WarnIncompleteUniPatterns, Opt_WarnMonomorphism, Opt_WarnUnrecognisedPragmas, Opt_WarnAutoOrphans, - Opt_WarnTabs - ] + Opt_WarnImplicitPrelude + ] enableGlasgowExts :: DynP () enableGlasgowExts = do setDynFlag Opt_PrintExplicitForalls @@ -1852,16 +1896,18 @@ unSetDynFlag f = upd (\dfs -> dopt_unset dfs f) -------------------------- setExtensionFlag, unSetExtensionFlag :: ExtensionFlag -> DynP () setExtensionFlag f = do { upd (\dfs -> xopt_set dfs f) - ; mapM_ setExtensionFlag deps } + ; sequence_ deps } where - deps = [ d | (f', d) <- impliedFlags, f' == f ] + deps = [ if turn_on then setExtensionFlag d + else unSetExtensionFlag d + | (f', turn_on, d) <- impliedFlags, f' == f ] -- When you set f, set the ones it implies -- NB: use setExtensionFlag recursively, in case the implied flags -- implies further flags - -- When you un-set f, however, we don't un-set the things it implies - -- (except for -fno-glasgow-exts, which is treated specially) unSetExtensionFlag f = upd (\dfs -> xopt_unset dfs f) + -- When you un-set f, however, we don't un-set the things it implies + -- (except for -fno-glasgow-exts, which is treated specially) -------------------------- setDumpFlag' :: DynFlag -> DynP () @@ -1952,45 +1998,39 @@ setOptLevel n dflags -- -Odph is equivalent to -- -- -O2 optimise as much as possible --- -fno-method-sharing sharing specialisation defeats fusion --- sometimes --- -fdicts-cheap always inline dictionaries -- -fmax-simplifier-iterations20 this is necessary sometimes --- -fsimplifier-phases=3 we use an additional simplifier phase --- for fusion --- -fno-spec-constr-threshold run SpecConstr even for big loops --- -fno-spec-constr-count SpecConstr as much as possible --- -finline-enough-args hack to prevent excessive inlining +-- -fsimplifier-phases=3 we use an additional simplifier phase for fusion -- setDPHOpt :: DynFlags -> DynFlags setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations = 20 , simplPhases = 3 - , specConstrThreshold = Nothing - , specConstrCount = Nothing }) - `dopt_set` Opt_DictsCheap - `dopt_unset` Opt_MethodSharing -data DPHBackend = DPHPar - | DPHSeq - | DPHThis +-- Determines the package used by the vectoriser for the symbols of the vectorised code. +-- 'DPHNone' indicates that no data-parallel backend library is available; hence, the +-- vectoriser cannot be used. +-- +data DPHBackend = DPHPar -- "dph-par" + | DPHSeq -- "dph-seq" + | DPHThis -- the currently compiled package + | DPHNone -- no DPH library available deriving(Eq, Ord, Enum, Show) setDPHBackend :: DPHBackend -> DynP () -setDPHBackend backend - = do - upd $ \dflags -> dflags { dphBackend = backend } - mapM_ exposePackage (dph_packages backend) - where - dph_packages DPHThis = [] - dph_packages DPHPar = ["dph-prim-par", "dph-par"] - dph_packages DPHSeq = ["dph-prim-seq", "dph-seq"] +setDPHBackend backend = upd $ \dflags -> dflags { dphBackend = backend } +-- Query the DPH backend package to be used by the vectoriser. +-- dphPackage :: DynFlags -> PackageId -dphPackage dflags = case dphBackend dflags of - DPHPar -> dphParPackageId - DPHSeq -> dphSeqPackageId - DPHThis -> thisPackage dflags +dphPackage dflags + = case dphBackend dflags of + DPHPar -> dphParPackageId + DPHSeq -> dphSeqPackageId + DPHThis -> thisPackage dflags + DPHNone -> ghcError (CmdLineError dphBackendError) + +dphBackendError :: String +dphBackendError = "To use -fvectorise select a DPH backend with -fdph-par or -fdph-seq" setMainIs :: String -> DynP () setMainIs arg @@ -2259,14 +2299,12 @@ compilerInfo = [("Project name", String cProjectName), ("Project version", String cProjectVersion), ("Booter version", String cBooterVersion), ("Stage", String cStage), - ("Build platform", String cBuildPlatform), - ("Host platform", String cHostPlatform), - ("Target platform", String cTargetPlatform), + ("Build platform", String cBuildPlatformString), + ("Host platform", String cHostPlatformString), + ("Target platform", String cTargetPlatformString), ("Have interpreter", String cGhcWithInterpreter), ("Object splitting", String cSplitObjs), ("Have native code generator", String cGhcWithNativeCodeGen), - ("Have llvm code generator", String cGhcWithLlvmCodeGen), - ("Use archives for ghci", String (show cUseArchivesForGhci)), ("Support SMP", String cGhcWithSMP), ("Unregisterised", String cGhcUnregisterised), ("Tables next to code", String cGhcEnableTablesNextToCode), @@ -2274,6 +2312,9 @@ compilerInfo = [("Project name", String cProjectName), ("Leading underscore", String cLeadingUnderscore), ("Debug on", String (show debugIsOn)), ("LibDir", FromDynFlags topDir), - ("Global Package DB", FromDynFlags systemPackageConfig) + ("Global Package DB", FromDynFlags systemPackageConfig), + ("C compiler flags", String (show cCcOpts)), + ("Gcc Linker flags", String (show cGccLinkerOpts)), + ("Ld Linker flags", String (show cLdLinkerOpts)) ]