[GHC] #12355: Invalid assembly in foreign prim

#12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: -------------------------------------+------------------------------------- {{{ ➜ prim_panic ghc Lib.hs [1 of 1] Compiling Lib ( Lib.hs, Lib.o ) /tmp/ghc14440_0/ghc_2.s: Assembler messages: /tmp/ghc14440_0/ghc_2.s:65:0: error: Error: number of operands mismatch for `jmp' `gcc' failed in phase `Assembler'. (Exit code: 1) ➜ prim_panic cat Lib.hs {-# LANGUAGE GHCForeignImportPrim, UnliftedFFITypes, MagicHash #-} module Lib where import GHC.Prim foreign import prim f1 :: Int# -> Int# }}} Tried with: HEAD as of today, 8.0.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12355 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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 bgamari): I've proposed to add this example to the testsuite in Phab:D2377. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12355#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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): Does anyone know what the problem actually is here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12355#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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 bgamari): Something is indeed quite fishy. The C-- for this code is as follows, {{{ [section ""data" . Lib.f1_closure" { Lib.f1_closure: const Lib.f1_info; }, Lib.f1_entry() // [R2] { info_tbl: [(cG7, label: Lib.f1_info rep:HeapRep static { Fun {arity: 1 fun_type: ArgSpec 4} })] stack_info: arg_space: 8 updfr_space: Just 8 } {offset cG7: _B1::I64 = R2; goto cG9; cG9: R1 = _B1::I64; call (R1) args: 8, res: 0, upd: 8; } }] }}} It looks like the target is being pretty-printed as `mempty`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12355#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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): Fishy indeed: can you probe further? Thanks -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12355#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12355: Invalid assembly in foreign prim
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
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 Ben Gamari

#12355: Invalid assembly in foreign prim
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
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 Ben Gamari

#12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 2563 Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * status: new => patch * differential: => 2563 Comment: The foreign symbol name is missing. With the "prim" calling convention, the empty entity string doesn't get replaced with the function name "f1" (while it does with the "ccall" convention). Hence the "jmp" without target in the generated asm. Proposed patch: https://phabricator.haskell.org/D2563 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12355#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12355: Invalid assembly in foreign prim
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner:
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): 2563
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2563 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * differential: 2563 => Phab:D2563 * resolution: => fixed * milestone: => 8.0.2 Comment: Merged to `ghc-8.0` as 5eab189b329344630f76b8751c1289ce480ca46b and 0f9a8a9096b3b236b80fe82f2570ca3865903518. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12355#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC