[GHC] #14125: Bogus unacceptable type in foreign declaration.
GHC
ghc-devs at haskell.org
Wed Aug 16 13:38:56 UTC 2017
#14125: Bogus unacceptable type in foreign declaration.
-------------------------------------+-------------------------------------
Reporter: winter | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler (FFI) | Version: 8.2.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* priority: normal => high
* failure: None/Unknown => GHC rejects valid program
* component: Compiler => Compiler (FFI)
Comment:
From what I can see, there are two different bugs being reported here:
1. You can't use newtype instances as marshallable argument types. That
is, this should compile, but doesn't:
{{{#!hs
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TypeFamilies #-}
module Bug where
import Foreign.C.String
import Foreign.C.Types
data UnixReturn
data family IOErrno a
newtype instance IOErrno UnixReturn = UnixErrno CInt
foreign import ccall unsafe "string.h" strerror :: IOErrno UnixReturn ->
IO CString
}}}
This is indeed a regression, as this code typechecks in 8.0.2 but not
8.2.1. I'll try to figure out which commit caused this.
2. You can't use newtypes as marshallable return types. However, I'm
having trouble coming up with a minimal program which triggers the error
you're claiming will happen on 8.2. I tried this:
{{{#!hs
{-# LANGUAGE ForeignFunctionInterface #-}
module Bug where
import Foreign
import Foreign.C.Types
import System.Posix.Types
newtype UnixReturn a = UnixReturn a
foreign import ccall unsafe "recv"
c_recv :: CInt -> Ptr Word8 -> CSize -> CInt -> IO (UnixReturn CSsize)
}}}
But this typechecks on GHC 8.2, so there must be something that I'm
missing.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14125#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list