[commit: ghc] master: Re-export data family when exporting a data instance without an export list (8cef8af)

git at git.haskell.org git at git.haskell.org
Mon Dec 7 11:14:49 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/8cef8af3286f3c98f2a02e65371b875d8791b687/ghc

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

commit 8cef8af3286f3c98f2a02e65371b875d8791b687
Author: David Kraeutmann <kane at kane.cx>
Date:   Mon Dec 7 11:19:28 2015 +0100

    Re-export data family when exporting a data instance without an export list
    
    Whenever a data instance is exported, the corresponding data family
    is exported, too. This allows one to write
    
    ```
         -- Foo.hs
         module Foo where
    
         data family T a
    
         -- Bar.hs
         module Bar where
    
         import Foo
    
         data instance T Int = MkT
    
         -- Baz.hs
         module Baz where
    
         import Bar (T(MkT))
    ```
    
    In previous versions of GHC, this required a workaround
    explicit export list in `Bar`.
    
    Reviewers: bgamari, goldfire, austin
    
    Reviewed By: bgamari, goldfire
    
    Subscribers: goldfire, thomie
    
    Differential Revision: https://phabricator.haskell.org/D1573
    
    GHC Trac Issues: #11164


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

8cef8af3286f3c98f2a02e65371b875d8791b687
 compiler/rename/RnNames.hs                         | 26 +++++++++++++++-------
 docs/users_guide/7.12.1-notes.rst                  | 23 +++++++++++++++++++
 docs/users_guide/glasgow_exts.rst                  |  8 +++----
 testsuite/tests/ghci/scripts/T5417.stdout          |  2 ++
 .../tests/indexed-types/should_fail/Over.stderr    |  8 +++----
 testsuite/tests/rename/should_compile/T11164.hs    |  3 +++
 testsuite/tests/rename/should_compile/T11164a.hs   |  4 ++++
 testsuite/tests/rename/should_compile/T11164b.hs   |  6 +++++
 testsuite/tests/rename/should_compile/all.T        |  4 ++++
 9 files changed, 68 insertions(+), 16 deletions(-)

diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index b0b79f5..3ee1e69 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -1200,14 +1200,24 @@ exports_from_avail :: Maybe (Located [LIE RdrName])
                    -> RnM (Maybe [LIE Name], [AvailInfo])
 
 exports_from_avail Nothing rdr_env _imports _this_mod
- = -- The same as (module M) where M is the current module name,
-   -- so that's how we handle it.
-   let
-       avails = [ availFromGRE gre
-                | gre <- globalRdrEnvElts rdr_env
-                , isLocalGRE gre ]
-   in
-    return (Nothing, avails)
+   -- The same as (module M) where M is the current module name,
+   -- so that's how we handle it, except we also export the data family
+   -- when a data instance is exported.
+  = let avails = [ fix_faminst $ availFromGRE gre
+                 | gre <- globalRdrEnvElts rdr_env
+                 , isLocalGRE gre ]
+    in return (Nothing, avails)
+  where
+    -- #11164: when we define a data instance
+    -- but not data family, re-export the family
+    -- Generally, whenever we export a part of a declaration,
+    -- export the declaration, too.
+    fix_faminst (AvailTC n ns flds)
+      | not (n `elem` ns)
+      = AvailTC n (n:ns) flds
+
+    fix_faminst avail = avail
+
 
 exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
   = do (ie_names, _, exports) <- foldlM do_litem emptyExportAccum rdr_items
diff --git a/docs/users_guide/7.12.1-notes.rst b/docs/users_guide/7.12.1-notes.rst
index 2e0ae6f..21ec1d3 100644
--- a/docs/users_guide/7.12.1-notes.rst
+++ b/docs/users_guide/7.12.1-notes.rst
@@ -109,6 +109,29 @@ Language
       -- P is imported
       import Foo (T(..))
 
+-  Whenever a data instance is exported, the corresponding data family
+   is exported, too. This allows one to write ::
+
+     -- Foo.hs
+     module Foo where
+     
+     data family T a
+
+     -- Bar.hs
+     module Bar where
+     
+     import Foo
+     
+     data instance T Int = MkT
+
+     -- Baz.hs
+     module Baz where
+     
+     import Bar (T(MkT))
+
+   In previous versions of GHC, this required a workaround via an
+   explicit export list in Bar. 
+
 
 
 Compiler
diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst
index 93261a2..7e448be 100644
--- a/docs/users_guide/glasgow_exts.rst
+++ b/docs/users_guide/glasgow_exts.rst
@@ -6702,10 +6702,10 @@ Two things to watch out for:
            data instance D Int = D1 | D2
 
    Module Y exports all the entities defined in Y, namely the data
-   constructors ``D1`` and ``D2``, *but not the data family* ``D``. That
-   (annoyingly) means that you cannot selectively import Y selectively,
-   thus "``import Y( D(D1,D2) )``", because Y does not export ``D``.
-   Instead you should list the exports explicitly, thus:
+   constructors ``D1`` and ``D2``, and *implicitly* the data family ``D``,
+   even though it's defined in X. 
+   This means you can write "``import Y( D(D1,D2) )``" *without* 
+   giving an explicit export list like this: 
 
    ::
 
diff --git a/testsuite/tests/ghci/scripts/T5417.stdout b/testsuite/tests/ghci/scripts/T5417.stdout
index 06329d9..30178a4 100644
--- a/testsuite/tests/ghci/scripts/T5417.stdout
+++ b/testsuite/tests/ghci/scripts/T5417.stdout
@@ -3,5 +3,7 @@ data instance C.F (B1 a) = B2 a
 data family D a
 class C.C1 a where
   data family C.F a
+class C.C1 a where
+  data family C.F a
   	-- Defined at T5417a.hs:5:5
 data instance C.F (B1 a) = B2 a 	-- Defined at T5417.hs:8:10
diff --git a/testsuite/tests/indexed-types/should_fail/Over.stderr b/testsuite/tests/indexed-types/should_fail/Over.stderr
index 180bb95..63b8b30 100644
--- a/testsuite/tests/indexed-types/should_fail/Over.stderr
+++ b/testsuite/tests/indexed-types/should_fail/Over.stderr
@@ -1,10 +1,10 @@
 
-OverB.hs:7:15:
+OverB.hs:7:15: error:
     Conflicting family instance declarations:
-      OverA.C [Int] [a] = CListList2 -- Defined at OverB.hs:7:15
-      OverA.C [a] [Int] = C9ListList -- Defined at OverC.hs:7:15
+      C [Int] [a] = CListList2 -- Defined at OverB.hs:7:15
+      C [a] [Int] = C9ListList -- Defined at OverC.hs:7:15
 
-OverB.hs:9:15:
+OverB.hs:9:15: error:
     Conflicting family instance declarations:
       OverA.D [Int] [a] = Int -- Defined at OverB.hs:9:15
       OverA.D [a] [Int] = Char -- Defined at OverC.hs:9:15
diff --git a/testsuite/tests/rename/should_compile/T11164.hs b/testsuite/tests/rename/should_compile/T11164.hs
new file mode 100644
index 0000000..b1d9a68
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T11164.hs
@@ -0,0 +1,3 @@
+module T11164 where
+
+import T11164b (T)
diff --git a/testsuite/tests/rename/should_compile/T11164a.hs b/testsuite/tests/rename/should_compile/T11164a.hs
new file mode 100644
index 0000000..f14e96d
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T11164a.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE TypeFamilies #-}
+module T11164a where
+
+data family T a
diff --git a/testsuite/tests/rename/should_compile/T11164b.hs b/testsuite/tests/rename/should_compile/T11164b.hs
new file mode 100644
index 0000000..abe65c4
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T11164b.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE TypeFamilies #-}
+module T11164b where
+
+import T11164a
+
+data instance T Int = MkT
diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T
index c501ecc..05bc250 100644
--- a/testsuite/tests/rename/should_compile/all.T
+++ b/testsuite/tests/rename/should_compile/all.T
@@ -226,3 +226,7 @@ test('T7969',
 test('T9127', normal, compile, [''])
 test('T4426', normal, compile_fail, [''])
 test('T9778', normal, compile, ['-fwarn-unticked-promoted-constructors'])
+test('T11164',
+     extra_clean(['T11164a.hi', 'T11164a.o',
+                  'T11164b.hi', 'T11164b.o']),
+     multimod_compile, ['T11164', '-v0'])



More information about the ghc-commits mailing list