
#13263: cant derive functor on function newtype with unboxed tuple result -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm not sure if this is a bug or a feature request, but i have a simple example that I think should work with deriving functor but falls over {{{ {-# LANGUAGE ScopedTypeVariables, BangPatterns, UnboxedTuples, MagicHash, GADTs #-} {-# LANGUAGE DeriveFunctor #-} module Test where newtype Eww a = Ew# (Int -> (# a, Int #)) deriving (Functor) }}} the error i get is {{{ src/System/Random/SplitMix/Internal.hs:88:13: error: • The constructor ‘(#,#)’ should have 2 arguments, but has been given 4 • In the pattern: (#,#) a1 a2 a3 a4 In a case alternative: ((#,#) a1 a2 a3 a4) -> (#,#) ((\ b2 -> b2) a1) ((\ b3 -> b3) a2) (f a3) ((\ b4 -> b4) a4) In the expression: case b5 of { ((#,#) a1 a2 a3 a4) -> (#,#) ((\ b2 -> b2) a1) ((\ b3 -> b3) a2) (f a3) ((\ b4 -> b4) a4) } When typechecking the code for ‘fmap’ in a derived instance for ‘Functor Eww’: To see the code I am typechecking, use -ddump-deriv }}} and the dumped deriving is {{{ [1 of 1] Compiling System.Random.SplitMix.Internal ( src/System/Random/SplitMix/Internal.hs, /Users/carter/WorkSpace/projects/active/random-hs/dist- newstyle/build/random-2.0.0.0/build/System/Random/SplitMix/Internal.o ) ==================== Derived instances ==================== Derived instances: instance GHC.Base.Functor System.Random.SplitMix.Internal.Eww where GHC.Base.fmap f_a4Vn (System.Random.SplitMix.Internal.Ew# a1_a4Vo) = System.Random.SplitMix.Internal.Ew# ((\ b6_a4Vp b7_a4Vq -> (\ b5_a4Vr -> case b5_a4Vr of { ((#,#) a1_a4Vs a2_a4Vt a3_a4Vu a4_a4Vv) -> (#,#) ((\ b2_a4Vw -> b2_a4Vw) a1_a4Vs) ((\ b3_a4Vx -> b3_a4Vx) a2_a4Vt) (f_a4Vn a3_a4Vu) ((\ b4_a4Vy -> b4_a4Vy) a4_a4Vv) }) (b6_a4Vp ((\ b1_a4Vz -> b1_a4Vz) b7_a4Vq))) a1_a4Vo) GHC.Generics representation types: }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13263 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler