On 24/11/2011 15:16, Ian Lynagh wrote:
On Thu, Nov 24, 2011 at 06:57:21AM -0800, Simon Marlow wrote:
| otherwise
- = children_only
+ = return (mkReflCo ty, ty)
+ -- If we have reached an ordinary (non-newtype) type constructor,
+ -- we are done. Note that we don't need to normalise the
arguments,
+ -- because whether an FFI type is legal or not depends only on
+ -- the top-level type constructor (e.g. "Ptr a" is valid for all
a).
That's not true for FunPtr, is it?
Actually, it looks like this was already broken before your changes. We
should be rejecting mkFun2 and mkCallBack2 here, shouldn't we?:
module A where
import Foreign
import Foreign.C
data D = D
foreign import ccall "dynamic"
mkFun1 :: FunPtr (CInt -> IO ()) -> (CInt -> IO ())
foreign import ccall "dynamic"
mkFun2 :: FunPtr (D -> IO ()) -> (CInt -> IO ())
foreign import ccall "wrapper"
mkCallBack1 :: IO () -> IO (FunPtr (IO ()))
foreign import ccall "wrapper"
mkCallBack2 :: IO () -> IO (FunPtr D)
Correct, we're missing some additional checks. For f.i. wrapper, the
type should be f -> IO (FunPtr f), and for f.i. dynamic, the type should
be FunPtr f -> f.
We haven't made anything worse in this respect, since the checks were
already missing, but we should implement the checks anyway.
Cheers,
Simon
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc