
#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