[GHC] #14091: When PolyKinds is on, suggested type signatures seem to require TypeInType

#14091: When PolyKinds is on, suggested type signatures seem to require TypeInType -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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: -------------------------------------+------------------------------------- We compile the following with -Wall {{{ {-# LANGUAGE PolyKinds #-} import Data.Bits import Data.Word data Hash128 a = Hash128 { hashWord128_0 :: !Word64, hashWord128_1 :: !Word64 } deriving (Show, Read, Eq) -- These instances copied from 'FixedPoint-simple': instance FiniteBits (Hash128 a) where finiteBitSize ~(Hash128 a b) = finiteBitSize a + finiteBitSize b instance Bits (Hash128 a) where popCount (Hash128 h l) = popCount h + popCount l bit i | i >= 64 = Hash128 (bit $ i - 64) 0 | otherwise = Hash128 0 (bit i) complement = pointwise complement (.&.) = pointwise2 (.&.) (.|.) = pointwise2 (.|.) xor = pointwise2 xor setBit (Hash128 h l) i | i >= 64 = Hash128 (setBit h (i - 64)) l | otherwise = Hash128 h (setBit l i) shiftL (Hash128 h l) i | i > finiteBitSize l = shiftL (Hash128 l 0) (i - finiteBitSize l) | otherwise = Hash128 ((h `shiftL` i) .|. (l `shiftR` (finiteBitSize l - i))) (l `shiftL` i) shiftR (Hash128 h l) i | i > finiteBitSize h = shiftR (Hash128 0 h) (i - finiteBitSize h) | otherwise = Hash128 (h `shiftR` i) ((l `shiftR` i) .|. h `shiftL` (finiteBitSize h - i)) isSigned _ = False testBit (Hash128 h l) i | i >= finiteBitSize l = testBit h (i - finiteBitSize l) | otherwise = testBit l i rotateL w i = shiftL w i .|. shiftR w (128 - i) rotateR w i = shiftR w i .|. shiftL w (128 - i) bitSize _ = 128 bitSizeMaybe _ = Just 128 pointwise op (Hash128 a b) = Hash128 (op a) (op b) pointwise2 op (Hash128 a b) (Hash128 c d) = Hash128 (op a c) (op b d) }}} get a warning like: {{{ Top-level binding with no type signature: pointwise2 :: forall k1 k2 k3 (a1 :: k2) (a2 :: k1) (a3 :: k3). (Word64 -> Word64 -> Word64) -> Hash128 a1 -> Hash128 a2 -> Hash128 a3 }}} but that's not a valid signature. Pasting it in causes GHC to suggest RankNTypes with an error, and then to suggest TypeInType, at which point it compiles. I want to just be able to paste in the signature from the warning. Related to #6065 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14091 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14091: When PolyKinds is on, suggested type signatures seem to require TypeInType -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: TypeInType, | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeInType, TypeErrorMessages -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14091#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14091: When PolyKinds is on, suggested type signatures seem to require TypeInType -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: TypeInType, | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): It's not clear to me the best way to fix this. It's tempting to suppress kind quantification with `-XNoTypeInType` and to suppress `forall` with `-XNoExplicitForAll`. But simply suppressing all these might sometimes give us the wrong type. For example, suppose we want `forall (b :: Bool). Proxy b`. Just saying `Proxy b` is plain wrong.... and it seems hard to know, a priori, when it would be wrong. Easier would be to print out the type as-is, but then look at it to determine whether the user might need extra extensions and suggest those, too.... but that's not as good a user experience. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14091#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14091: When PolyKinds is on, suggested type signatures seem to require TypeInType -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: wontfix | Keywords: TypeInType, | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => wontfix Comment: We no longer distinguish between TypeInType and PolyKinds, so I'm closing this ticket. See https://github.com/ghc-proposals/ghc- proposals/blob/master/proposals/0020-no-type-in-type.rst and #15195 for more details. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14091#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC