Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,334
    • Issues 4,334
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 368
    • Merge Requests 368
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
  • Security & Compliance
    • Security & Compliance
    • Dependency List
    • License Compliance
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Collapse sidebar
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #12399

Closed
Open
Opened Jul 16, 2016 by Ömer Sinan Ağacan@osa1Maintainer

DeriveFunctor fail

{-# 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:

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:

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.

Trac metadata
Trac field Value
Version 8.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler (Type checker)
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Assignee
Assign to
8.0.2
Milestone
8.0.2 (Past due)
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#12399