[GHC] #11473: Levity polymorphism checks are inadequate
GHC
ghc-devs at haskell.org
Sat Feb 6 19:00:50 UTC 2016
#11473: Levity polymorphism checks are inadequate
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: goldfire
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
| LevityPolymorphism, TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by rwbarton):
This slight variation of Ben's program does produce a garbage result. I
just added an extra function call to `hello` (and turned on
`ScopedTypeVariables`).
{{{
{-# LANGUAGE PolyKinds, TypeFamilies, MagicHash, DataKinds, TypeInType,
RankNTypes, ScopedTypeVariables #-}
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) (a :: TYPE lev). BoxIt a => a -> Boxed a
hello x = boxed (myid x)
where myid :: a -> a
myid y = y
{-# NOINLINE myid #-}
{-# NOINLINE hello #-}
main :: IO ()
main = do
print $ boxed 'c'#
print $ boxed 'c'
print $ hello 'c'
print $ hello 'c'# -- this one prints '\8589966336'
}}}
(Interesting note, `hello :: forall foo. forall bar. t` does ''not'' bring
`bar` into scope in the definition of `hello`. I guess that makes sense.)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11473#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list