[GHC] #12373: Type error but types match
 
            #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
 
            #12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The error message is dire, but the error is real. {{{ -- Type of data constructor for IO: IO :: forall a. State# RealWorld -> (# State# RealWorld, a #) -- Type of newMVar# newMVar# :: forall b. State# s -> (# State# s, MVar# s b #) }}} So when we apply `IO` to `newMVar#` we have to instantiate the `forall a` with `MVar# s b` which isn't allowed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12373#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): This is probably #11198. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12373#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, well spotted. It would be great to nail this since it keeps popping up. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12373#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #12373: Type error but types match
-------------------------------------+-------------------------------------
        Reporter:  osa1              |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler (Type    |              Version:  8.1
  checker)                           |
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg 
 
            #12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T12373 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_fail/T12373 * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12373#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
- 
                 GHC GHC