summaryrefslogtreecommitdiff
path: root/ghc/Main.hs
diff options
context:
space:
mode:
authorKavon Farvardin <kavon@farvard.in>2018-09-23 15:29:37 -0500
committerKavon Farvardin <kavon@farvard.in>2018-09-23 15:29:37 -0500
commit84c2ad99582391005b5e873198b15e9e9eb4f78d (patch)
treecaa8c2f2ec7e97fbb4977263c6817c9af5025cf4 /ghc/Main.hs
parent8ddb47cfcf5776e9a3c55fd37947c8a95e00fa12 (diff)
parente68b439fe5de61b9a2ca51af472185c62ccb8b46 (diff)
downloadhaskell-wip/T13904.tar.gz
update to current master againwip/T13904
Diffstat (limited to 'ghc/Main.hs')
-rw-r--r--ghc/Main.hs64
1 files changed, 44 insertions, 20 deletions
diff --git a/ghc/Main.hs b/ghc/Main.hs
index a75aba3e97..03ac60db2d 100644
--- a/ghc/Main.hs
+++ b/ghc/Main.hs
@@ -40,6 +40,7 @@ import Module ( ModuleName )
-- Various other random stuff that we need
+import GHC.HandleEncoding
import Config
import Constants
import HscTypes
@@ -73,6 +74,7 @@ import Control.Monad
import Data.Char
import Data.List
import Data.Maybe
+import Prelude
-----------------------------------------------------------------------------
-- ToDo:
@@ -92,18 +94,7 @@ main = do
hSetBuffering stdout LineBuffering
hSetBuffering stderr LineBuffering
- -- Handle GHC-specific character encoding flags, allowing us to control how
- -- GHC produces output regardless of OS.
- env <- getEnvironment
- case lookup "GHC_CHARENC" env of
- Just "UTF-8" -> do
- hSetEncoding stdout utf8
- hSetEncoding stderr utf8
- _ -> do
- -- Avoid GHC erroring out when trying to display unhandled characters
- hSetTranslit stdout
- hSetTranslit stderr
-
+ configureHandleEncoding
GHC.defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
-- 1. extract the -B flag from the args
argv0 <- getArgs
@@ -179,10 +170,16 @@ main' postLoadMode dflags0 args flagWarnings = do
-- can be overriden from the command-line
-- XXX: this should really be in the interactive DynFlags, but
-- we don't set that until later in interactiveUI
- dflags2 | DoInteractive <- postLoadMode = imp_qual_enabled
- | DoEval _ <- postLoadMode = imp_qual_enabled
+ -- We also set -fignore-optim-changes and -fignore-hpc-changes,
+ -- which are program-level options. Again, this doesn't really
+ -- feel like the right place to handle this, but we don't have
+ -- a great story for the moment.
+ dflags2 | DoInteractive <- postLoadMode = def_ghci_flags
+ | DoEval _ <- postLoadMode = def_ghci_flags
| otherwise = dflags1
- where imp_qual_enabled = dflags1 `gopt_set` Opt_ImplicitImportQualified
+ where def_ghci_flags = dflags1 `gopt_set` Opt_ImplicitImportQualified
+ `gopt_set` Opt_IgnoreOptimChanges
+ `gopt_set` Opt_IgnoreHpcChanges
-- The rest of the arguments are "dynamic"
-- Leftover ones are presumably files
@@ -216,9 +213,23 @@ main' postLoadMode dflags0 args flagWarnings = do
let
-- To simplify the handling of filepaths, we normalise all filepaths right
- -- away - e.g., for win32 platforms, backslashes are converted
- -- into forward slashes.
- normal_fileish_paths = map (normalise . unLoc) fileish_args
+ -- away. Note the asymmetry of FilePath.normalise:
+ -- Linux: p/q -> p/q; p\q -> p\q
+ -- Windows: p/q -> p\q; p\q -> p\q
+ -- #12674: Filenames starting with a hypen get normalised from ./-foo.hs
+ -- to -foo.hs. We have to re-prepend the current directory.
+ normalise_hyp fp
+ | strt_dot_sl && "-" `isPrefixOf` nfp = cur_dir ++ nfp
+ | otherwise = nfp
+ where
+#if defined(mingw32_HOST_OS)
+ strt_dot_sl = "./" `isPrefixOf` fp || ".\\" `isPrefixOf` fp
+#else
+ strt_dot_sl = "./" `isPrefixOf` fp
+#endif
+ cur_dir = '.' : [pathSeparator]
+ nfp = normalise fp
+ normal_fileish_paths = map (normalise_hyp . unLoc) fileish_args
(srcs, objs) = partition_args normal_fileish_paths [] []
dflags5 = dflags4 { ldInputs = map (FileOption "") objs
@@ -804,12 +815,12 @@ dumpFastStringStats dflags = do
])
-- we usually get more "has z-encoding" than "z-encoded", because
-- when we z-encode a string it might hash to the exact same string,
- -- which will is not counted as "z-encoded". Only strings whose
+ -- which is not counted as "z-encoded". Only strings whose
-- Z-encoding is different from the original string are counted in
-- the "z-encoded" total.
putMsg dflags msg
where
- x `pcntOf` y = int ((x * 100) `quot` y) <> char '%'
+ x `pcntOf` y = int ((x * 100) `quot` y) Outputable.<> char '%'
countFS :: Int -> Int -> Int -> [[FastString]] -> (Int, Int, Int)
countFS entries longest has_z [] = (entries, longest, has_z)
@@ -933,5 +944,18 @@ people since we're linking GHC dynamically, but most things themselves
link statically.
-}
+-- If GHC_LOADED_INTO_GHCI is not set when GHC is loaded into GHCi, then
+-- running it causes an error like this:
+--
+-- Loading temp shared object failed:
+-- /tmp/ghc13836_0/libghc_1872.so: undefined symbol: initGCStatistics
+--
+-- Skipping the foreign call fixes this problem, and the outer GHCi
+-- should have already made this call anyway.
+#if defined(GHC_LOADED_INTO_GHCI)
+initGCStatistics :: IO ()
+initGCStatistics = return ()
+#else
foreign import ccall safe "initGCStatistics"
initGCStatistics :: IO ()
+#endif