[GHC] #10462: GHCi doesn't work Any and missing RealWorld foreign prim imports

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Here are two issues with our GHCi support for foreign prim imports: Here is a program that works: {{{ {-# LANGUAGE GHCForeignImportPrim, MagicHash, UnliftedFFITypes, UnboxedTuples #-} module Serum where import GHC.Exts foreign import prim "cheneycopy" cheneycopy :: Word# -> State# RealWorld -> (# State# RealWorld, Word# #) }}} If I remove the world token passing, as in here: {{{ {-# LANGUAGE GHCForeignImportPrim, MagicHash, UnliftedFFITypes, UnboxedTuples #-} module Serum where import GHC.Exts foreign import prim "cheneycopy" cheneycopy :: Word# -> Word# }}} I get: {{{ (GHC version 7.10.1 for x86_64-unknown-linux): ByteCodeGen.generateCCall: missing or invalid World token? }}} Another error is if I try to pass Any as an argument: {{{ {-# LANGUAGE GHCForeignImportPrim, MagicHash, UnliftedFFITypes, UnboxedTuples #-} module Serum where import GHC.Exts foreign import prim "cheneycopy" cheneycopy :: Any -> State# RealWorld -> (# State# RealWorld, Word# #) }}} Then I get: {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): primRepToFFIType }}} Note to anyone who is running into this problem: an easy workaround is to use `-fobject-code` which bypasses bytecode generation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by ezyang): * priority: normal => low -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * cc: hsyl20 (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): I don't think your first example works as expected. It type checks but the calling convention is silently ignored and replaced by the default CCall one (see #3336 and "convToABI" in compiler/ghci/LibFFI.hsc). The other examples fail because "generateCCall" from compiler/ghci/ByteCodeGen.hs shouldn't be called at all for primops and there are errors when parameters are pushed (your first case) or when parameters are converted into types understandable by libffi (second case). I attach a patch with an additional check which fails sooner and in a nicer way (similarily to #1257). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * Attachment "0001-ghci-indicate-that-foreign-primops-are-not- supported.patch" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: patch Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: patch Priority: low | Milestone: 8.0.1 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: patch Priority: low | Milestone: 8.0.1 Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: prog014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D1458 Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * testcase: => prog014 * differential: => D1458 * component: GHCi => Compiler (CodeGen) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner:
Type: bug | Status: patch
Priority: low | Milestone: 8.0.1
Component: Compiler | Version: 7.10.1
(CodeGen) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case: prog014
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): D1458
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10462: GHCi doesn't work Any and missing RealWorld foreign prim imports -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: closed Priority: low | Milestone: 8.0.1 Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: prog014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D1458 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: patch => closed * resolution: => fixed Comment: Marking this as fixed, I guess... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10462#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC