[Git][ghc/ghc][master] Have GHCi use object code for UnboxedTuples modules #15454

Marge Bot gitlab at gitlab.haskell.org
Wed May 22 20:41:28 UTC 2019



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
21272670 by Michael Sloan at 2019-05-22T20:37:57Z
Have GHCi use object code for UnboxedTuples modules #15454

The idea is to automatically enable -fobject-code for modules that use
UnboxedTuples, along with all the modules they depend on. When looking
into how to solve this, I was pleased to find that there was already
highly similar logic for enabling code generation when -fno-code is
specified but TemplateHaskell is used.

The state before this patch was that if you used unboxed tuples then you
had to enable `-fobject-code` globally rather than on a per module
basis.

- - - - -


9 changed files:

- compiler/main/GhcMake.hs
- docs/users_guide/8.10.1-notes.rst
- docs/users_guide/ghci.rst
- − testsuite/tests/ghci/prog014/prog014.stderr
- − testsuite/tests/ghci/should_fail/T14608.stderr
- testsuite/tests/ghci/should_fail/all.T
- testsuite/tests/ghci/should_fail/T14608.hs → testsuite/tests/ghci/should_run/T14608.hs
- testsuite/tests/ghci/should_fail/T14608.script → testsuite/tests/ghci/should_run/T14608.script
- testsuite/tests/ghci/should_run/all.T


Changes:

=====================================
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 (settings dflags))
            map0
-         else return map0
+         else if hscTarget dflags == HscInterpreted
+           then enableCodeGenForUnboxedTuples
+             (defaultObjectTarget (settings 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 at 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.


=====================================
docs/users_guide/8.10.1-notes.rst
=====================================
@@ -71,6 +71,13 @@ Compiler
   process, as long as there are no native dependencies that rely on
   global state.
 
+- 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
 ~~~~~~~~~~~~~~
 


=====================================
docs/users_guide/ghci.rst
=====================================
@@ -3360,11 +3360,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


=====================================
testsuite/tests/ghci/prog014/prog014.stderr deleted
=====================================
@@ -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.


=====================================
testsuite/tests/ghci/should_fail/T14608.stderr deleted
=====================================
@@ -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.


=====================================
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'])


=====================================
testsuite/tests/ghci/should_fail/T14608.hs → testsuite/tests/ghci/should_run/T14608.hs
=====================================


=====================================
testsuite/tests/ghci/should_fail/T14608.script → testsuite/tests/ghci/should_run/T14608.script
=====================================


=====================================
testsuite/tests/ghci/should_run/all.T
=====================================
@@ -36,6 +36,7 @@ test('T13456',     [just_ghci, combined_output], ghci_script, ['T13456.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'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/21272670581608b96a85cfb942af81ada3cfd450

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/21272670581608b96a85cfb942af81ada3cfd450
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190522/c0c69dd6/attachment-0001.html>


More information about the ghc-commits mailing list