[GHC] #11473: Levity polymorphism checks are inadequate
GHC
ghc-devs at haskell.org
Thu Jan 21 12:18:23 UTC 2016
#11473: Levity polymorphism checks are inadequate
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
| LevityPolymorphism
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by simonpj:
@@ -40,0 +40,2 @@
+
+ See also #11471
New description:
Ben found
{{{
{-# LANGUAGE PolyKinds, TypeFamilies, MagicHash, DataKinds, TypeInType,
RankNTypes #-}
import GHC.Exts
import GHC.Types
type family Boxed (a :: k) :: *
type instance Boxed Char# = Char
type instance Boxed Char = Char
class BoxIt (a :: TYPE lev) where
boxed :: a -> Boxed a
instance BoxIt Char# where boxed x = C# x
instance BoxIt Char where boxed = id
hello :: forall (lev :: Levity). forall (a :: TYPE lev). BoxIt a => a ->
Boxed a
hello x = boxed x
{-# NOINLINE hello #-}
main :: IO ()
main = do
print $ boxed 'c'#
print $ boxed 'c'
print $ hello 'c'
print $ hello 'c'#
}}}
This is plainly wrong because we have a polymorphic function `boxed` that
is being passed both boxed and unboxed arguments.
You do get a Lint error with `-dcore-lint`.
But the original problem is with the type signature for `boxed`. We
should never have a levity-polymorphic type to the left of an arrow. To
the right yes, but to the left no. I suppose we could check that in
`TcValidity`.
See also #11471
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11473#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list