This deserves a wider audience: if you've encountered failures when compiling FFI code with recent GHCs due to the new requirement that newtypes be non-abstract, note that this will now be a warning, not an error, in 7.4.1. We're deferring turning it into an error until 7.6.1.

Cheers,
        Simon

-------- Original Message --------
Subject: [commit: ghc] master: Relax the restriction on using abstract newtypes in FFI declarations. (c6b0fd6)
Date: Thu, 24 Nov 2011 06:57:21 -0800
From: Simon Marlow <marlo...@gmail.com>
To: cvs-...@haskell.org

Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/c6b0fd62fc715aa6c666eb8afe09073ac7b87a83

---------------------------------------------------------------

commit c6b0fd62fc715aa6c666eb8afe09073ac7b87a83
Author: Simon Marlow <marlo...@gmail.com>
Date:   Thu Nov 24 14:04:23 2011 +0000

    Relax the restriction on using abstract newtypes in FFI declarations.

    Given the high impact of this change, we decided to back off and make
    abstract newtypes give a warning for one release, before we make it an
    error in 7.6.1.

    Codec/Compression/Zlib/Stream.hsc:884:1:
        Warning: newtype `CInt' is used in an FFI declaration,
                 but its constructor is not in scope.
                 This will become an error in GHC 7.6.1.
        When checking declaration:
          foreign import ccall unsafe "static zlib.h deflate" c_deflate
            :: StreamState -> CInt -> IO CInt

---------------------------------------------------------------

 compiler/typecheck/TcForeign.lhs |   22 +++++++++++++++++-----
 1 files changed, 17 insertions(+), 5 deletions(-)

diff --git a/compiler/typecheck/TcForeign.lhs b/compiler/typecheck/TcForeign.lhs
index 886b84d..5a4bf77 100644
--- a/compiler/typecheck/TcForeign.lhs
+++ b/compiler/typecheck/TcForeign.lhs
@@ -121,17 +121,29 @@ normaliseFfiType' env ty0 = go [] ty0
panic "normaliseFfiType': Got more GREs than expected"
                                       _ ->
                                           return False
-                  if newtypeOK
-                      then do let nt_co = mkAxInstCo (newTyConCo tc) tys
-                              add_co nt_co rec_nts' nt_rhs
-                      else children_only
+                  when (not newtypeOK) $
+                     -- later: stop_here
+ addWarnTc (ptext (sLit "newtype") <+> quotes (ppr tc) <+> + ptext (sLit "is used in an FFI declaration,") $$ + ptext (sLit "but its constructor is not in scope.") $$ + ptext (sLit "This will become an error in GHC 7.6.1."))
+
+                  let nt_co = mkAxInstCo (newTyConCo tc) tys
+                  add_co nt_co rec_nts' nt_rhs
+
         | isFamilyTyCon tc              -- Expand open tycons
         , (co, ty) <- normaliseTcApp env tc tys
         , not (isReflCo co)
         = add_co co rec_nts ty
+
         | 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).
         where
+
           children_only = do xs <- mapM (go rec_nts) tys
                              let (cos, tys') = unzip xs
return (mkTyConAppCo tc cos, mkTyConApp tc tys')



_______________________________________________
Cvs-ghc mailing list
cvs-...@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to