[GHC] #7643: Kind application error

#7643: Kind application error -----------------------------+---------------------------------------------- Reporter: gmainland | Owner: Type: bug | Status: new Priority: normal | Component: Compiler (Type checker) Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Compiling the attached program with -dcore-lint fails. This failure is a reduced version of code taken from the primitive package, version 0.5.0.1. To see the failure: {{{ ghc -dcore-lint --make Main.hs }}} The failure does not occur with GHC 7.4. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7643 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7643: Kind application error -----------------------------+---------------------------------------------- Reporter: gmainland | Owner: Type: bug | Status: new Priority: normal | Component: Compiler (Type checker) Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: #7354 -----------------------------+---------------------------------------------- Changes (by shachaf): * related: => #7354 Comment: I reduced the test case a bit: {{{ {-# LANGUAGE MagicHash, TypeFamilies #-} module T7643 where import GHC.Exts type family T type instance T = RealWorld foo :: () -> State# T foo _ = unsafeCoerce# realWorld# }}} The `unsafeCoerce#`ed type actually matches -- but GHC has a problem with `State# RealWorld ~ State# T` (this isn't specific to `State#` or `RealWorld` -- unboxed tuples etc. work too. The issue is with the kinds). This seems to be a variety of #7354, but it's still broken in HEAD because of the kind issue. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7643#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7643: Kind application error ----------------------------------------+----------------------------------- Reporter: gmainland | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: #7354 | ----------------------------------------+----------------------------------- Changes (by simonpj): * difficulty: => Unknown Comment: There really is an underlying issue here, about how inference interacts with sub-kinding. Sigh. It is shown up here becuase you are doing `unsafeCoerce#` on an unlifted type, which is a deeply dangerous thing to do. Better to do it on a lifted type. Try using this definition of `setIntByteArray#`, which actually uses one fewer `unsafeCoerce#` calls: {{{ setIntByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int -> State# s -> State# s setIntByteArray# arr# i# n# (I# x#) s# = case unsafeCoerce# (internal (setIntArray# arr# i# n# x#)) s# of (# s1#, _ #) -> s1# }}} That makes the attached `Main.hs` compile fine. Don't close the ticket though. The underlying problem (dark corner though it is) remains. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7643#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7643: Kind application error ----------------------------------------+----------------------------------- Reporter: gmainland | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: #7354 | ----------------------------------------+----------------------------------- Comment(by gmainland): Just for reference... This bug was tickled by a change introduced in revision 776368 of the `primitive` library. This revision added the following method to the `Data.Primitive.Types.Prim` type class: {{{ setByteArray# :: MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s }}} Instances for primitive types define this method using FFI imports. For example, the instance for `Int#` uses the following FFI import: {{{ foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setIntArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> IO () }}} Because the FFI import is in `IO`, it needs to be cast from `MutableByteArray# s -> Int# -> Int# -> Int# -> IO ()` to `MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> (# State# s, () #)`. This is currently done as follows: {{{ setByteArray# arr# i# n# (I# x#) s# = case internal (setIntArray# arr# i# n# x#) (unsafeCoerce# s#) of { (# s1#, _ #) -> unsafeCoerce# s1# } }}} For reference, `internal` is defined like this: {{{ class Monad m => PrimMonad m where -- | State token type type PrimState m -- | Execute a primitive operation primitive :: (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a -- | Expose the internal structure of the monad internal :: m a -> State# (PrimState m) -> (# State# (PrimState m), a #) }}} {{{ instance PrimMonad IO where type PrimState IO = RealWorld primitive = IO internal (IO p) = p {-# INLINE primitive #-} {-# INLINE internal #-} }}} Indeed, Simon's fix keeps us safely in the land of kind `*`. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7643#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7643: Kind application error ----------------------------------------+----------------------------------- Reporter: gmainland | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: #7354 | ----------------------------------------+----------------------------------- Changes (by igloo): * owner: => simonpj * milestone: => 7.8.1 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7643#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC