
#12399: DeriveFunctor fail -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | 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: -------------------------------------+------------------------------------- {{{#!haskell {-# LANGUAGE DeriveFunctor, MagicHash, UnboxedTuples #-} module Lib where import GHC.Exts newtype RmLoopsM a = RmLoopsM { runRmLoops :: Int# -> (# Int#, a #) } }}} Functor instance for this can be derived like this: {{{#!haskell instance Functor RmLoopsM where fmap f (RmLoopsM m) = RmLoopsM $ \i -> case m i of (# i', r #) -> (# i', f r #) }}} `DeriveFunctor` instead generates something like this: {{{#!haskell instance Functor RmLoopsM where fmap f_a2Oh (Lib.RmLoopsM a1_a2Oi) = RmLoopsM ((\ b6_a2Oj b7_a2Ok -> (\ b5_a2Ol -> case b5_a2Ol of { ((#,#) a1_a2Om a2_a2On a3_a2Oo a4_a2Op) -> (#,#) ((\ b2_a2Oq -> b2_a2Oq) a1_a2Om) ((\ b3_a2Or -> b3_a2Or) a2_a2On) ((\ b4_a2Os -> b4_a2Os) a3_a2Oo) (f_a2Oh a4_a2Op) }) (b6_a2Oj ((\ b1_a2Ot -> b1_a2Ot) b7_a2Ok))) a1_a2Oi) }}} which fails with {{{ Main.hs:17:25: error: • The constructor ‘(#,#)’ should have 2 arguments, but has been given 4 • In the pattern: (#,#) a1_a2Om a2_a2On a3_a2Oo a4_a2Op In a case alternative: ((#,#) a1_a2Om a2_a2On a3_a2Oo a4_a2Op) -> (#,#) ((\ b2_a2Oq -> b2_a2Oq) a1_a2Om) ((\ b3_a2Or -> b3_a2Or) a2_a2On) ((\ b4_a2Os -> b4_a2Os) a3_a2Oo) (f_a2Oh a4_a2Op) In the expression: case b5_a2Ol of { ((#,#) a1_a2Om a2_a2On a3_a2Oo a4_a2Op) -> (#,#) ((\ b2_a2Oq -> b2_a2Oq) a1_a2Om) ((\ b3_a2Or -> b3_a2Or) a2_a2On) ((\ b4_a2Os -> b4_a2Os) a3_a2Oo) (f_a2Oh a4_a2Op) } }}} I think it's supposed to ignore RuntimeRep args during the fold (`TcGenDeriv.functorLikeTraverse`). Tried with: HEAD, 8.0.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12399 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler