summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorRyan Scott <ryan.gl.scott@gmail.com>2019-08-08 17:26:13 (GMT)
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-09-26 18:04:38 (GMT)
commit4f81fab062e521b6b59f3f7b93bc410fd1111166 (patch)
tree41d55a2c4c9a4ba9e3e19d8168138228e4e31c4c
parent0b5eede97804ec3dfbfa9df9f97bcfe2aa369f6b (diff)
downloadghc-4f81fab062e521b6b59f3f7b93bc410fd1111166.zip
ghc-4f81fab062e521b6b59f3f7b93bc410fd1111166.tar.gz
ghc-4f81fab062e521b6b59f3f7b93bc410fd1111166.tar.bz2
Make -fbyte-code prevent unboxed tuples/sums from implying object code (#16876)
This resolves #16876 by making the explicit use of `-fbyte-code` prevent code that enables `UnboxedTuples` or `UnboxedSums` from automatically compiling to object code. This allows for a nice middle ground where most code that enables `UnboxedTuples`/-`Sums` will still benefit from automatically enabling `-fobject-code`, but allows power users who wish to avoid this behavior in certain corner cases (such as `lens`, whose use case is documented in #16876) to do so. Along the way, I did a little cleanup of the relevant code and documentation: * `enableCodeGenForUnboxedTuples` was only checking for the presence of `UnboxedTuples`, but `UnboxedSums` has the same complications. I fixed this and renamed the function to `enableCodeGenForUnboxedTuplesOrSums`. * I amended the users' guide with a discussion of these issues.
-rw-r--r--compiler/main/DynFlags.hs6
-rw-r--r--compiler/main/GhcMake.hs13
-rw-r--r--docs/users_guide/8.10.1-notes.rst11
-rw-r--r--docs/users_guide/ghci.rst25
-rw-r--r--testsuite/tests/ghci/scripts/T16876.script3
-rw-r--r--testsuite/tests/ghci/scripts/T16876.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/T16876A.hs4
-rw-r--r--testsuite/tests/ghci/scripts/T16876B.hs23
-rwxr-xr-xtestsuite/tests/ghci/scripts/all.T1
9 files changed, 71 insertions, 16 deletions
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 07b266d..429857a 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -654,6 +654,7 @@ data GeneralFlag
| Opt_SingleLibFolder
| Opt_KeepCAFs
| Opt_KeepGoing
+ | Opt_ByteCode
-- output style opts
| Opt_ErrorSpans -- Include full span info in error messages,
@@ -3744,7 +3745,10 @@ dynamic_flags_deps = [
, make_ord_flag defFlag "fno-code" (NoArg ((upd $ \d ->
d { ghcLink=NoLink }) >> setTarget HscNothing))
- , make_ord_flag defFlag "fbyte-code" (NoArg (setTarget HscInterpreted))
+ , make_ord_flag defFlag "fbyte-code"
+ (noArgM $ \dflags -> do
+ setTarget HscInterpreted
+ pure $ gopt_set dflags Opt_ByteCode)
, make_ord_flag defFlag "fobject-code" $ NoArg $ do
dflags <- liftEwM getCmdLineState
setTarget $ defaultObjectTarget dflags
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index 6e44a86..f1fb933 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -2078,7 +2078,7 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
(defaultObjectTarget dflags)
map0
else if hscTarget dflags == HscInterpreted
- then enableCodeGenForUnboxedTuples
+ then enableCodeGenForUnboxedTuplesOrSums
(defaultObjectTarget dflags)
map0
else return map0
@@ -2176,16 +2176,19 @@ enableCodeGenForTH =
-- and .o file locations to be temporary files.
--
-- This is used used in order to load code that uses unboxed tuples
--- into GHCi while still allowing some code to be interpreted.
-enableCodeGenForUnboxedTuples :: HscTarget
+-- or sums into GHCi while still allowing some code to be interpreted.
+enableCodeGenForUnboxedTuplesOrSums :: HscTarget
-> NodeMap [Either ErrorMessages ModSummary]
-> IO (NodeMap [Either ErrorMessages ModSummary])
-enableCodeGenForUnboxedTuples =
+enableCodeGenForUnboxedTuplesOrSums =
enableCodeGenWhen condition should_modify TFL_GhcSession TFL_CurrentModule
where
condition ms =
- xopt LangExt.UnboxedTuples (ms_hspp_opts ms) &&
+ unboxed_tuples_or_sums (ms_hspp_opts ms) &&
+ not (gopt Opt_ByteCode (ms_hspp_opts ms)) &&
not (isBootSummary ms)
+ unboxed_tuples_or_sums d =
+ xopt LangExt.UnboxedTuples d || xopt LangExt.UnboxedSums d
should_modify (ModSummary { ms_hspp_opts = dflags }) =
hscTarget dflags == HscInterpreted
diff --git a/docs/users_guide/8.10.1-notes.rst b/docs/users_guide/8.10.1-notes.rst
index 907f7e2..7566f3f 100644
--- a/docs/users_guide/8.10.1-notes.rst
+++ b/docs/users_guide/8.10.1-notes.rst
@@ -132,11 +132,12 @@ Compiler
global state.
- When loading modules that use :extension:`UnboxedTuples` into GHCi,
- it will now automatically enable :ghc-flag:`-fobject-code` for these modules
- and all modules they depend on. Before this change, attempting to
- load these modules into the interpreter would just fail, and the
- only convenient workaround was to enable :ghc-flag:`-fobject-code` for all
- modules.
+ it will now automatically enable :ghc-flag:`-fobject-code` for
+ these modules and all modules they depend on. Before this change,
+ attempting to load these modules into the interpreter would just
+ fail, and the only convenient workaround was to enable
+ :ghc-flag:`-fobject-code` for all modules. See the
+ :ref:`GHCi FAQ <ghci-faq>` for further details.
- The eventlog now contains events for biographical and retainer profiling.
The biographical profiling events all appear at the end of the eventlog but
diff --git a/docs/users_guide/ghci.rst b/docs/users_guide/ghci.rst
index 9138f1d..10a9358 100644
--- a/docs/users_guide/ghci.rst
+++ b/docs/users_guide/ghci.rst
@@ -3429,14 +3429,29 @@ The interpreter can't load modules with foreign export declarations!
need to go fast, rather than interpreting them with optimisation
turned on.
-Modules using unboxed tuples will automatically enable `-fobject-code`
- The interpreter doesn't support unboxed tuples, so GHCi will
- automatically compile these modules, and all modules they depend
- on, to object code instead of bytecode.
+Modules using unboxed tuples or sums will automatically enable :ghc-flag:`-fobject-code`
+
+ .. index::
+ single: unboxed tuples, sums; and GHCi
+
+ The bytecode interpreter doesn't support most uses of unboxed tuples or
+ sums, so GHCi will automatically compile these modules, and all modules
+ they depend on, to object code instead of bytecode.
+
+ GHCi checks for the presence of unboxed tuples and sums in a somewhat
+ conservative fashion: it simply checks to see if a module enables the
+ :extension:`UnboxedTuples` or :extension:`UnboxedSums` language extensions.
+ It is not always the case that code which enables :extension:`UnboxedTuples`
+ or :extension:`UnboxedSums` requires :ghc-flag:`-fobject-code`, so if you
+ *really* want to compile
+ :extension:`UnboxedTuples`/:extension:`UnboxedSums`-using code to
+ bytecode, you can do so explicitly by enabling the :ghc-flag:`-fbyte-code`
+ flag. If you do this, do note that bytecode interpreter will throw an error
+ if it encounters unboxed tuple/sum–related code that it cannot handle.
Incidentally, the previous point, that :ghc-flag:`-O` is
incompatible with GHCi, is because the bytecode compiler can't
- deal with unboxed tuples.
+ deal with unboxed tuples or sums.
Concurrent threads don't carry on running when GHCi is waiting for input.
This should work, as long as your GHCi was built with the
diff --git a/testsuite/tests/ghci/scripts/T16876.script b/testsuite/tests/ghci/scripts/T16876.script
new file mode 100644
index 0000000..09a2e1f
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T16876.script
@@ -0,0 +1,3 @@
+:load T16876A.hs T16876B.hs
+:m *T16876B
+h == (f + g)
diff --git a/testsuite/tests/ghci/scripts/T16876.stdout b/testsuite/tests/ghci/scripts/T16876.stdout
new file mode 100644
index 0000000..0ca9514
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T16876.stdout
@@ -0,0 +1 @@
+True
diff --git a/testsuite/tests/ghci/scripts/T16876A.hs b/testsuite/tests/ghci/scripts/T16876A.hs
new file mode 100644
index 0000000..37bdedb
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T16876A.hs
@@ -0,0 +1,4 @@
+module T16876A where
+
+f :: Int
+f = 1
diff --git a/testsuite/tests/ghci/scripts/T16876B.hs b/testsuite/tests/ghci/scripts/T16876B.hs
new file mode 100644
index 0000000..06703b0
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T16876B.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# OPTIONS_GHC -fbyte-code #-}
+module T16876B where
+
+import T16876A
+import GHC.Exts
+import GHC.IO
+
+inlinePerformIO :: IO a -> a
+inlinePerformIO (IO m) = case m realWorld# of
+ (# _, r #) -> r
+{-# INLINE inlinePerformIO #-}
+
+g :: Int
+g = inlinePerformIO $ return 1
+
+-- |
+--
+-- >>> h == (f + g)
+-- True
+h :: Int
+h = 2
diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index 4b0234d..9ba9751 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/tests/ghci/scripts/all.T
@@ -308,3 +308,4 @@ test('T16509', normal, ghci_script, ['T16509.script'])
# to use hie files
test('T16804', extra_files(['T16804a.hs', 'T16804b.hs', 'T16804c.hs']), ghci_script, ['T16804.script'])
test('T15546', normal, ghci_script, ['T15546.script'])
+test('T16876', normal, ghci_script, ['T16876.script'])