[commit: ghc] ghc-8.2: Fix #14125 by normalizing data family instances more aggressively (c541129)

git at git.haskell.org git at git.haskell.org
Fri Aug 25 19:11:47 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.2
Link       : http://ghc.haskell.org/trac/ghc/changeset/c541129ccc78967a15c67e416bb5f5d5b7499b68/ghc

>---------------------------------------------------------------

commit c541129ccc78967a15c67e416bb5f5d5b7499b68
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Tue Aug 22 09:28:43 2017 -0400

    Fix #14125 by normalizing data family instances more aggressively
    
    Summary:
    Commit 3540d1e1a23926ce0a8a6ae83a36f5f6b2497ccf inadvertently broke
    the ability for newtype instances to be used as marshallable types in FFI
    declarations. The reason is a bit silly: an extra check was added for type
    synonyms with no type families on the RHS in `normalise_tc_app`, but this check
    would only skip over type families, not //data// families, since the predicate
    being used was `not . isTypeFamilyCon`.
    
    The fix is simple: just use `not . isFamilyCon` instead so that data families
    are also skipped by this check.
    
    Test Plan: make test TEST=T14125
    
    Reviewers: goldfire, simonpj, austin, bgamari
    
    Reviewed By: simonpj
    
    Subscribers: rwbarton, thomie
    
    GHC Trac Issues: #14125
    
    Differential Revision: https://phabricator.haskell.org/D3865
    
    (cherry picked from commit 6982ee99fb97c252c3faf37faae34131fb66f67c)


>---------------------------------------------------------------

c541129ccc78967a15c67e416bb5f5d5b7499b68
 compiler/types/FamInstEnv.hs                   | 14 +++++++-------
 testsuite/tests/ffi/should_compile/T14125.hs   | 17 +++++++++++++++++
 testsuite/tests/ffi/should_compile/all.T       |  1 +
 testsuite/tests/ghci/should_run/T14125a.script |  8 ++++++++
 testsuite/tests/ghci/should_run/T14125a.stdout |  5 +++++
 testsuite/tests/ghci/should_run/all.T          |  1 +
 6 files changed, 39 insertions(+), 7 deletions(-)

diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs
index 89f4214..3182475 100644
--- a/compiler/types/FamInstEnv.hs
+++ b/compiler/types/FamInstEnv.hs
@@ -1356,13 +1356,7 @@ normalise_tc_app tc tys
     -- See Note [Normalisation and type synonyms]
     normalise_type (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys')
 
-  | not (isTypeFamilyTyCon tc)
-  = -- A synonym with no type families in the RHS; or data type etc
-    -- Just normalise the arguments and rebuild
-    do { (args_co, ntys) <- normalise_tc_args tc tys
-       ; return (args_co, mkTyConApp tc ntys) }
-
-  | otherwise
+  | isFamilyTyCon tc
   = -- A type-family application
     do { env <- getEnv
        ; role <- getRole
@@ -1376,6 +1370,12 @@ normalise_tc_app tc tys
                 -- we do not do anything
                 return (args_co, mkTyConApp tc ntys) }
 
+  | otherwise
+  = -- A synonym with no type families in the RHS; or data type etc
+    -- Just normalise the arguments and rebuild
+    do { (args_co, ntys) <- normalise_tc_args tc tys
+       ; return (args_co, mkTyConApp tc ntys) }
+
 ---------------
 -- | Normalise arguments to a tycon
 normaliseTcArgs :: FamInstEnvs          -- ^ env't with family instances
diff --git a/testsuite/tests/ffi/should_compile/T14125.hs b/testsuite/tests/ffi/should_compile/T14125.hs
new file mode 100644
index 0000000..daf236d
--- /dev/null
+++ b/testsuite/tests/ffi/should_compile/T14125.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE ForeignFunctionInterface #-}
+{-# LANGUAGE TypeFamilies #-}
+module T14125 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
+
+foreign import ccall unsafe "HsBase.h __hscore_get_errno"
+  get_errno :: IO (IOErrno UnixReturn)
diff --git a/testsuite/tests/ffi/should_compile/all.T b/testsuite/tests/ffi/should_compile/all.T
index 18192d4..0f2f390 100644
--- a/testsuite/tests/ffi/should_compile/all.T
+++ b/testsuite/tests/ffi/should_compile/all.T
@@ -31,3 +31,4 @@ test('cc015', normal, compile, [''])
 test('cc016', normal, compile, [''])
 test('T10460', normal, compile, [''])
 test('T11983', [omit_ways(['ghci'])], compile, ['T11983.c'])
+test('T14125', normal, compile, [''])
diff --git a/testsuite/tests/ghci/should_run/T14125a.script b/testsuite/tests/ghci/should_run/T14125a.script
new file mode 100644
index 0000000..1667349
--- /dev/null
+++ b/testsuite/tests/ghci/should_run/T14125a.script
@@ -0,0 +1,8 @@
+:set -XTypeFamilies
+data family Foo a
+data instance Foo Int = FooInt Int
+:kind! Foo Int
+let f (FooInt i) = i
+:info    f
+:type +v f
+:type    f
diff --git a/testsuite/tests/ghci/should_run/T14125a.stdout b/testsuite/tests/ghci/should_run/T14125a.stdout
new file mode 100644
index 0000000..7b4e85e
--- /dev/null
+++ b/testsuite/tests/ghci/should_run/T14125a.stdout
@@ -0,0 +1,5 @@
+Foo Int :: *
+= Foo Int
+f :: Foo Int -> Int 	-- Defined at <interactive>:5:5
+f :: Foo Int -> Int
+f :: Foo Int -> Int
diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T
index 3dc05ce..f7ec59e 100644
--- a/testsuite/tests/ghci/should_run/all.T
+++ b/testsuite/tests/ghci/should_run/all.T
@@ -27,3 +27,4 @@ test('T11825',     just_ghci, ghci_script, ['T11825.script'])
 test('T12128',     just_ghci, ghci_script, ['T12128.script'])
 test('T12456',     just_ghci, ghci_script, ['T12456.script'])
 test('T12549',     just_ghci, ghci_script, ['T12549.script'])
+test('T14125a',    just_ghci, ghci_script, ['T14125a.script'])



More information about the ghc-commits mailing list