[GHC] #9352: Allow `State# s` argument/result types in `ccall` FFI imports

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.10.1 Component: Compiler (Type | Version: 7.8.2 checker) | Operating System: Keywords: | Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: Difficulty: Unknown | None/Unknown Blocked By: | Test Case: Related Tickets: #9218 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- This ticket is to allowing code like {{{#!hs {-# LANGUAGE UnliftedFFITypes #-} {-# LANGUAGE MagicHash #-} module M where import GHC.Exts foreign import ccall unsafe "foo" c_foo :: Int# -> State# s -> State# s foreign import ccall unsafe "bar" c_foo :: Int# -> State# s -> (# State# s, Int# #) }}} See also discussion in #9218 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature | Status: new request | Milestone: 7.10.1 Priority: normal | Version: 7.8.2 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #9218 Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by hvr): As first proof-of-concept, I made the type-checker allow `State# s` to see if it would just-work(tm), here's the Cmm output resulting from the `foo` declaration: {{{#!c [section "data" { M.c_foo_closure: const M.c_foo_info; }, M.c_foo_entry() // [R2] { info_tbl: [(c1Cx, label: M.c_foo_info rep:HeapRep static { Fun {arity: 2 fun_type: ArgSpec 4} })] stack_info: arg_space: 8 updfr_space: Just 8 } {offset c1Cx: _s1Cl::I64 = R2; goto c1Cz; c1Cz: _c1Cv::I64 = foo; _c1Cw::I64 = _s1Cl::I64; call "ccall" arg hints: [‘signed’] result hints: [] (_c1Cv::I64)(_c1Cw::I64); call (P64[Sp])() args: 8, res: 0, upd: 8; } }] }}} Compiling `bar` however, results in {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.9.20140723 for x86_64-unknown-linux): resultWrapper (# State# s, Int# #) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature | Status: new request | Milestone: 7.10.1 Priority: normal | Version: 7.8.2 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #9281 Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by hvr): * related: #9218 => #9281 Old description:
This ticket is to allowing code like
{{{#!hs {-# LANGUAGE UnliftedFFITypes #-} {-# LANGUAGE MagicHash #-}
module M where
import GHC.Exts
foreign import ccall unsafe "foo" c_foo :: Int# -> State# s -> State# s
foreign import ccall unsafe "bar" c_foo :: Int# -> State# s -> (# State# s, Int# #) }}}
See also discussion in #9218
New description: This ticket is to allowing code like {{{#!hs {-# LANGUAGE UnliftedFFITypes #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} module M where import GHC.Exts foreign import ccall unsafe "foo" c_foo :: Int# -> State# s -> State# s foreign import ccall unsafe "bar" c_foo :: Int# -> State# s -> (# State# s, Int# #) }}} See also discussion in #9281 -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature | Status: new request | Milestone: 7.10.1 Priority: normal | Version: 7.8.2 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #9281 Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by hvr): * cc: simonmar, simonpj (added) Comment: I've cc'ed you both to trigger any comments you might have with respect to the results from comment:1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature | Status: new request | Milestone: 7.10.1 Priority: normal | Version: 7.8.2 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #9281 Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): OK, so here's the patch I'm guessing you tried {{{ Modified compiler/typecheck/TcType.lhs diff --git a/compiler/typecheck/TcType.lhs b/compiler/typecheck/TcType.lhs index a952ce7..d643f6e 100644 --- a/compiler/typecheck/TcType.lhs +++ b/compiler/typecheck/TcType.lhs @@ -1556,10 +1556,11 @@ marshalableTyCon :: DynFlags -> TyCon -> Bool marshalableTyCon dflags tc = (xopt Opt_UnliftedFFITypes dflags && isUnLiftedTyCon tc - && not (isUnboxedTupleTyCon tc) - && case tyConPrimRep tc of -- Note [Marshalling VoidRep] - VoidRep -> False - _ -> True) +-- && not (isUnboxedTupleTyCon tc) +-- && case tyConPrimRep tc of -- Note [Marshalling VoidRep] +-- VoidRep -> False +-- _ -> True + ) || boxedMarshalableTyCon tc }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature | Status: new request | Milestone: 7.10.1 Priority: normal | Version: 7.8.2 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #9281 Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): Simon M: looking into the code, I'm quite perplexed. Have a look at: DsCCall.boxResult. It seems the when we say {{{ foreign import foo :: Int -> Int }}} we actually generate (in effect) an inline use of `unsafePerformIO`. Here's the tidy core: {{{ M.foo :: GHC.Types.Int -> GHC.Types.Int [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType] M.foo = \ (ds_d1A2 :: GHC.Types.Int) -> case ds_d1A2 of _ [Occ=Dead] { GHC.Types.I# ds2_d1A4 -> case {__pkg_ccall main foo Int# -> State# RealWorld -> (# State# RealWorld, Int# #)}_d1A7 ds2_d1A4 GHC.Prim.realWorld# of _ [Occ=Dead] { (# ds3_d1A6, ds4_d1A5 #) -> GHC.Types.I# ds4_d1A5 } } }}} Note that we come up with a `realWorld#` out of thin air and then discard it again... that's the `unsafePerformIO` stuff. Then the code generator has to painstakingly discard all that state-passing nonsense, to get back to a simple C call to "foo". Why do we bother with this? Why not produce this core: {{{ M.foo :: GHC.Types.Int -> GHC.Types.Int M.foo = \ (ds_d1A2 :: GHC.Types.Int) -> case ds_d1A2 of _ [Occ=Dead] { GHC.Types.I# ds2_d1A4 -> case {__pkg_ccall main foo Int# -> Int#}_d1A7 ds2_d1A4 of ds4_d1A5 [Occ=Dead] { DEFAULT -> GHC.Types.I# ds4_d1A5 } } }}} Simpler, more direct, and should generate exactly the same code. At the moment the built-in `FCallId` Ids always have an IO-ish type, but I see no reason to require that. If we did this, then I think the distinction between `boxResult` and `resultWrapper` could disappear, leading to a simpler, compositional structur. Moreover, if we want to accommodate {{{ foreign import foo :: Int -> State# s -> (# State# s, Int #) }}} which doesn't have an IO-ish type (at least not built with the `IO` type constructor), it would seem utterly bizarre to enclose it in the `unsafePerformIO` boilerplate as above. I think Herbert might be able to act on all this, but first let's check that I have not forgotten anything stupid. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature | Status: new request | Milestone: 7.10.1 Priority: normal | Version: 7.8.2 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #9281 Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by hvr): Fyi, just something I just noticed while implementing a new Cmm primop and the associated `prim` FFI import: The following doesn't work, as GHC doesn't deem `State#` an acceptable return type: {{{#!hs foreign import prim "integer_gmp_cmm_shrink_mba" shrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> State# s }}} However, the following works: {{{#!hs foreign import prim "integer_gmp_cmm_shrink_mba" shrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s #) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature | Status: new request | Milestone: 7.10.1 Priority: normal | Version: 7.8.2 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #9281 Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonmar): Simon: so long as the foreign call is treated as having side effects etc. by the simplifier, it should be OK. I think this code dates back to the original implementation of foreign calls and has only had shallow modifications since then (indeed if you look at `git blame` some of the code is very old), it's entirely possible it can be refactored to be simpler. One thing to watch out for is that `resultWrapper` is called from the translation for `CLabel` (i.e. `foreign import "&foo"`) wheras `boxResult` is called from the translation for `foreign import`. I'm not sure whether that's significant or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature | Status: new request | Milestone: 7.10.1 Priority: normal | Version: 7.8.2 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: #9281 Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): Great. Herbert: would you like to proceed with this refactoring? I can help. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9281, #11032 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: #9281 => #9281, #11032 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9281, #11032 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The behavior observed by hvr in comment:7 is (was?) in fact intentional. It is documented in this note in `TyType`, {{{ Note [Marshalling void] ~~~~~~~~~~~~~~~~~~~~~~~ We don't treat State# (whose PrimRep is VoidRep) as marshalable. In turn that means you can't write foreign import foo :: Int -> State# RealWorld Reason: the back end falls over with panic "primRepHint:VoidRep"; and there is no compelling reason to permit it }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9352#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC