
#12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | 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: -------------------------------------+------------------------------------- {{{
unboxedsums git:(prim_sums_rebase_5) x cat primop_bug.hs {-# LANGUAGE MagicHash, ScopedTypeVariables, UnboxedTuples #-}
module Main where import GHC.MVar import GHC.Prim import GHC.Types main :: IO () main = IO (\rw -> newMVar# rw) >> return ()
unboxedsums git:(prim_sums_rebase_5) x ghc-stage1 primop_bug.hs -ddump- stg -ddump-cmm -ddump-to-file -fforce-recomp -dumpdir primop_fails -O -fprint-explicit-kinds [1 of 1] Compiling Main ( primop_bug.hs, primop_bug.o )
primop_bug.hs:10:19: error: • Couldn't match a lifted type with an unlifted type Expected type: (# State# RealWorld, MVar# RealWorld a0 #) Actual type: (# State# RealWorld, MVar# RealWorld a0 #) • In the expression: newMVar# rw In the first argument of ‘IO’, namely ‘(\ rw -> newMVar# rw)’ In the first argument of ‘(>>)’, namely ‘IO (\ rw -> newMVar# rw)’ }}} Tried with HEAD, 8.0.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12373 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler