diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index d5f58f8f9b19650b98883af291089543e8efa1d8..3cb4034bfab5470a07931ec94f33db9b030cd6e9 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -1430,6 +1430,7 @@ upsweep_mod hsc_env mHscMessage old_hpt (stable_obj, stable_bco) summary mod_ind && (not (isObjectTarget prevailing_target) || not (isObjectTarget local_target)) && not (prevailing_target == HscNothing) + && not (prevailing_target == HscInterpreted) then prevailing_target else local_target @@ -1955,7 +1956,11 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots then enableCodeGenForTH (defaultObjectTarget (targetPlatform dflags)) map0 - else return map0 + else if hscTarget dflags == HscInterpreted + then enableCodeGenForUnboxedTuples + (defaultObjectTarget (targetPlatform dflags)) + map0 + else return map0 return $ concat $ nodeMapElts map1 where calcDeps = msDeps @@ -2034,7 +2039,50 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots enableCodeGenForTH :: HscTarget -> NodeMap [Either ErrMsg ModSummary] -> IO (NodeMap [Either ErrMsg ModSummary]) -enableCodeGenForTH target nodemap = +enableCodeGenForTH = + enableCodeGenWhen condition should_modify TFL_CurrentModule TFL_GhcSession + where + condition = isTemplateHaskellOrQQNonBoot + should_modify (ModSummary { ms_hspp_opts = dflags }) = + hscTarget dflags == HscNothing && + -- Don't enable codegen for TH on indefinite packages; we + -- can't compile anything anyway! See #16219. + not (isIndefinite dflags) + +-- | Update the every ModSummary that is depended on +-- by a module that needs unboxed tuples. We enable codegen to +-- the specified target, disable optimization and change the .hi +-- 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 + -> NodeMap [Either ErrMsg ModSummary] + -> IO (NodeMap [Either ErrMsg ModSummary]) +enableCodeGenForUnboxedTuples = + enableCodeGenWhen condition should_modify TFL_GhcSession TFL_CurrentModule + where + condition ms = + xopt LangExt.UnboxedTuples (ms_hspp_opts ms) && + not (isBootSummary ms) + should_modify (ModSummary { ms_hspp_opts = dflags }) = + hscTarget dflags == HscInterpreted + +-- | Helper used to implement 'enableCodeGenForTH' and +-- 'enableCodeGenForUnboxedTuples'. In particular, this enables +-- unoptimized code generation for all modules that meet some +-- condition (first parameter), or are dependencies of those +-- modules. The second parameter is a condition to check before +-- marking modules for code generation. +enableCodeGenWhen + :: (ModSummary -> Bool) + -> (ModSummary -> Bool) + -> TempFileLifetime + -> TempFileLifetime + -> HscTarget + -> NodeMap [Either ErrMsg ModSummary] + -> IO (NodeMap [Either ErrMsg ModSummary]) +enableCodeGenWhen condition should_modify staticLife dynLife target nodemap = traverse (traverse (traverse enable_code_gen)) nodemap where enable_code_gen ms @@ -2042,18 +2090,15 @@ enableCodeGenForTH target nodemap = { ms_mod = ms_mod , ms_location = ms_location , ms_hsc_src = HsSrcFile - , ms_hspp_opts = dflags@DynFlags - {hscTarget = HscNothing} + , ms_hspp_opts = dflags } <- ms - -- Don't enable codegen for TH on indefinite packages; we - -- can't compile anything anyway! See #16219. - , not (isIndefinite dflags) + , should_modify ms , ms_mod `Set.member` needs_codegen_set = do let new_temp_file suf dynsuf = do - tn <- newTempName dflags TFL_CurrentModule suf + tn <- newTempName dflags staticLife suf let dyn_tn = tn -<.> dynsuf - addFilesToClean dflags TFL_GhcSession [dyn_tn] + addFilesToClean dflags dynLife [dyn_tn] return tn -- We don't want to create .o or .hi files unless we have been asked -- to by the user. But we need them, so we patch their locations in @@ -2076,7 +2121,7 @@ enableCodeGenForTH target nodemap = [ ms | mss <- Map.elems nodemap , Right ms <- mss - , isTemplateHaskellOrQQNonBoot ms + , condition ms ] -- find the set of all transitive dependencies of a list of modules. diff --git a/docs/users_guide/8.8.1-notes.rst b/docs/users_guide/8.8.1-notes.rst index 0a7d4eb5f4a4ffdf3a3d92840d2dd7b444e03fbb..5e9654719504d7ea567f435de3bc2f20b6b6880f 100644 --- a/docs/users_guide/8.8.1-notes.rst +++ b/docs/users_guide/8.8.1-notes.rst @@ -114,6 +114,13 @@ Compiler taking advantage of :extension:`DerivingStrategies`. The warning is supplied at each ``deriving`` site. +- When loading modules that use :extension:`UnboxedTuples` into GHCi, + it will now automatically enable `-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 `-fobject-code` for all + modules. + Runtime system ~~~~~~~~~~~~~~ diff --git a/docs/users_guide/ghci.rst b/docs/users_guide/ghci.rst index f468e80eb027e5f28111581232d492bdf09642af..544b8604ef2af5a4638a9b6ac81124f5920e6626 100644 --- a/docs/users_guide/ghci.rst +++ b/docs/users_guide/ghci.rst @@ -3308,11 +3308,14 @@ The interpreter can't load modules with foreign export declarations! need to go fast, rather than interpreting them with optimisation turned on. -Unboxed tuples don't work with GHCi - That's right. You can always compile a module that uses unboxed - tuples and load it into GHCi, however. (Incidentally the previous - point, namely that :ghc-flag:`-O` is incompatible with GHCi, is because the - bytecode compiler can't deal with unboxed tuples). +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. + + Incidentally, the previous point, that :ghc-flag:`-O` is + incompatible with GHCi, is because the bytecode compiler can't + deal with unboxed tuples. 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/prog014/prog014.stderr b/testsuite/tests/ghci/prog014/prog014.stderr deleted file mode 100644 index 6d7b7fba37e7f2762007c37dbd93ee7a2e429027..0000000000000000000000000000000000000000 --- a/testsuite/tests/ghci/prog014/prog014.stderr +++ /dev/null @@ -1,2 +0,0 @@ -Error: bytecode compiler can't handle some foreign calling conventions - Workaround: use -fobject-code, or compile this module to .o separately. diff --git a/testsuite/tests/ghci/should_fail/T14608.stderr b/testsuite/tests/ghci/should_fail/T14608.stderr deleted file mode 100644 index fe84063af2da17d1574f387abfca510a249c2742..0000000000000000000000000000000000000000 --- a/testsuite/tests/ghci/should_fail/T14608.stderr +++ /dev/null @@ -1,3 +0,0 @@ -Error: bytecode compiler can't handle unboxed tuples and sums. - Possibly due to foreign import/export decls in source. - Workaround: use -fobject-code, or compile this module to .o separately. diff --git a/testsuite/tests/ghci/should_fail/all.T b/testsuite/tests/ghci/should_fail/all.T index da01a98e3ea9c23a406d8d1254e256829f35438c..7205cfd9301f81e2958c3db3cad8b89d33fd9302 100644 --- a/testsuite/tests/ghci/should_fail/all.T +++ b/testsuite/tests/ghci/should_fail/all.T @@ -1,6 +1,5 @@ test('T10549', [], ghci_script, ['T10549.script']) test('T10549a', [], ghci_script, ['T10549a.script']) -test('T14608', [], ghci_script, ['T14608.script']) test('T15055', normalise_version('ghc'), ghci_script, ['T15055.script']) test('T16013', [], ghci_script, ['T16013.script']) test('T16287', [], ghci_script, ['T16287.script']) diff --git a/testsuite/tests/ghci/should_fail/T14608.hs b/testsuite/tests/ghci/should_run/T14608.hs similarity index 100% rename from testsuite/tests/ghci/should_fail/T14608.hs rename to testsuite/tests/ghci/should_run/T14608.hs diff --git a/testsuite/tests/ghci/should_fail/T14608.script b/testsuite/tests/ghci/should_run/T14608.script similarity index 100% rename from testsuite/tests/ghci/should_fail/T14608.script rename to testsuite/tests/ghci/should_run/T14608.script diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T index a9eded46d97234f24d74f6218391f9fa4b870681..43fe935e3e72c2c5d3a67c83e08650c3af1ab401 100644 --- a/testsuite/tests/ghci/should_run/all.T +++ b/testsuite/tests/ghci/should_run/all.T @@ -36,6 +36,7 @@ test('T12549', just_ghci, ghci_script, ['T12549.script']) test('BinaryArray', normal, compile_and_run, ['']) test('T14125a', just_ghci, ghci_script, ['T14125a.script']) test('T13825-ghci',just_ghci, ghci_script, ['T13825-ghci.script']) +test('T14608', just_ghci, ghci_script, ['T14608.script']) test('T14963a', just_ghci, ghci_script, ['T14963a.script']) test('T14963b', just_ghci, ghci_script, ['T14963b.script']) test('T14963c', [extra_hc_opts("-fdefer-type-errors")], ghci_script, ['T14963c.script'])