Newtype unwrapping in the FFI

Simon Peyton-Jones simonpj at microsoft.com
Thu Feb 12 04:22:31 EST 2009


[This email concerns an infelicity in the FFI spec. I'm directing it primarily to the Haskell Prime mailing list, but ccing the libraries list so that people there know about the thread. I suggest that replies go to Haskell Prime only.]

Consider this program (see http://hackage.haskell.org/trac/ghc/ticket/3008)

  module NT( N ) where
     newtype N = MkN Int

  module FFI where
     foreign import "f" :: N -> IO ()

Is module FFI OK?  It would definitely be OK if N was defined in the module FFI: the FFI spec says that the compiler must automatically unwrap any newtype arguments.
http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise3.html#x6-120003.2

But it's less clear when N is defined in another module *and* its representation isn't exported.  The author of NT might believe that because N's representation is hidden, she can change it to, say
        data N = MkN Int
without affecting the rest of the world.  But she can't.  This is a nasty failure of abstraction.  It is, I believe the only way in which a client of a NT could be affected by N's representation, even though that representation is allegedly hidden.  (ToDo: check on generalised newtype deriving.) This seems Bad to me.

Indeed, the cause of the above bug report is that GHC's implementation assumes that the representation is fully hidden if the constructor is not exported, and does not expose the representation of N even to separately-compiled modules (at least when you are not using -O).

But the point here is not what GHC stumbles on but what is supposed to happen.

Maybe we should fix it.  Proposal:

  * Clarify the spec to say that a newtype can only be automatically
    unwrapped if the newtype constructor (MkN in this case) is in scope

It happens that a large set of types from Foreign.C.Types, such as CInt and friends, are exported without their constructors, so adopting this new rule would require us to change Foreign.C.Types to expose the representation of CInt and friends.  (As it happens, nhc requires this already, so there's some #ifdeffery there already.)

Simon


More information about the Haskell-prime mailing list