Skip to content
Snippets Groups Projects
Commit ec6af9c4 authored by Ryan Scott's avatar Ryan Scott Committed by Ben Gamari
Browse files

Fix #14608 by restoring an unboxed tuple check

Commit 714bebff removed
a check in the bytecode compiler that caught illegal uses of unboxed
tuples (and now sums) in case alternatives, which causes the program
in #14608 to panic. This restores the check (using modern,
levity-polymorphic vocabulary).

Test Plan: make test TEST=T14608

Reviewers: hvr, bgamari, dfeuer, simonpj

Reviewed By: dfeuer, simonpj

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #14608

Differential Revision: https://phabricator.haskell.org/D4276

(cherry picked from commit ecff651f)
parent 2fc621df
No related branches found
No related tags found
No related merge requests found
......@@ -962,6 +962,11 @@ doCase d s p (_,scrut) bndr alts is_unboxed_tuple
| null real_bndrs = do
rhs_code <- schemeE d_alts s p_alts rhs
return (my_discr alt, rhs_code)
-- If an alt attempts to match on an unboxed tuple or sum, we must
-- bail out, as the bytecode compiler can't handle them.
-- (See Trac #14608.)
| any (\bndr -> typePrimRep (idType bndr) `lengthExceeds` 1) bndrs
= multiValException
-- algebraic alt with some binders
| otherwise =
let (tot_wds, _ptrs_wds, args_offsets) =
......
{-# LANGUAGE UnboxedTuples #-}
module T14608 where
data UnboxedTupleData = MkUTD (# (),() #)
doThings :: UnboxedTupleData -> ()
doThings (MkUTD t) = ()
:load T14608.hs
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.
test('T10549', [], ghci_script, ['T10549.script'])
test('T10549a', [], ghci_script, ['T10549a.script'])
test('T14608', [], ghci_script, ['T14608.script'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment