Skip to content
Snippets Groups Projects
Commit 3fa3fe8a authored by Ryan Scott's avatar Ryan Scott
Browse files

Make DeriveFunctor work with unboxed tuples

Summary:
Unboxed tuples have `RuntimeRep` arguments which `-XDeriveFunctor` was
mistaking for actual data constructor arguments. As a result, a derived
`Functor` instance for a datatype that contained an unboxed tuple would
generate twice as many arguments as it needed for an unboxed tuple pattern
match or expression. The solution is to simply put `dropRuntimeRepArgs` in the
right place.

Fixes #12399.

Test Plan: ./validate

Reviewers: austin, hvr, bgamari

Reviewed By: bgamari

Subscribers: thomie, osa1

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

GHC Trac Issues: #12399
parent d213ab3f
No related branches found
No related tags found
No related merge requests found
......@@ -1701,7 +1701,11 @@ functorLikeTraverse var (FT { ft_triv = caseTrivial, ft_var = caseVar
= (caseTyApp fun_ty (last xrs), True)
| otherwise = (caseWrongArg, True) -- Non-decomposable (eg type function)
where
(xrs,xcs) = unzip (map (go co) args)
-- When folding over an unboxed tuple, we must explicitly drop the
-- runtime rep arguments, or else GHC will generate twice as many
-- variables in a unboxed tuple pattern match and expression as it
-- actually needs. See Trac #12399
(xrs,xcs) = unzip (map (go co) (dropRuntimeRepArgs args))
go co (ForAllTy (TvBndr v vis) x)
| isVisibleArgFlag vis = panic "unexpected visible binder"
| v /= var && xc = (caseForAll v xr,True)
......@@ -2813,7 +2817,7 @@ a is the last type variable in a given datatype):
* ft_tup: A tuple type which mentions the last type variable in at least
one of its fields. The TyCon argument of ft_tup represents the
particular tuple's type constructor.
Examples: (a, Int), (Maybe a, [a], Either a Int)
Examples: (a, Int), (Maybe a, [a], Either a Int), (# Int, a #)
* ft_ty_app: A type is being applied to the last type parameter, where the
applied type does not mention the last type parameter (if it
......
{-# LANGUAGE DeriveFunctor, MagicHash, UnboxedTuples #-}
module T12399 where
import GHC.Exts
newtype RmLoopsM a = RmLoopsM { runRmLoops :: Int# -> (# Int#, a #) }
deriving Functor
......@@ -71,3 +71,4 @@ test('T11732b', normal, compile, [''])
test('T11732c', normal, compile, [''])
test('T11833', normal, compile, [''])
test('T12245', normal, compile, [''])
test('T12399', normal, compile, [''])
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