[GHC] #13732: Incorrectly suggests ‘TypeOperators’

GHC ghc-devs at haskell.org
Sat May 20 17:15:55 UTC 2017


#13732: Incorrectly suggests ‘TypeOperators’
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:  (none)
               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:
-------------------------------------+-------------------------------------
 Loading the code

 {{{#!hs
 {-# Language RankNTypes, GADTs, MagicHash, PolyKinds, TypeInType,
 ConstraintKinds #-}

 import Data.Kind
 import GHC.Exts
 import qualified Prelude

 class Semi (a :: TYPE rep) where

 data Free :: forall rep. (TYPE rep -> Constraint) -> TYPE rep -> Type
 where
   Free :: (forall q. ctx q => (p -> q) -> q) -> Free ctx p
 }}}

 gives an incorrect suggestion

 {{{
 GHCi, version 8.2.0.20170507: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( tXMX.hs, interpreted )
 Ok, modules loaded: Main.
 *Main> :kind Free Semi
 Free Semi :: * -> *
 *Main> :kind Free Semi Int#

 <interactive>:1:1: error:
     Not in scope: type constructor or class ‘#’

 <interactive>:1:1: error:
     Illegal operator ‘#’ in type ‘Free Semi Int #’
       Use TypeOperators to allow operators in types

 <interactive>:1:1: error:
     Operator applied to too few arguments: Free Semi Int #
 *Main>
 }}}

 This should recommend enabling `MagicHash` instead.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13732>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list