[commit: ghc] master: Allow optional instance keyword in associated type family instances (007f255)

git at git.haskell.org git at git.haskell.org
Fri Jun 30 00:18:36 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/007f255644f885d445e47e291e50eb12b5ecd08d/ghc

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

commit 007f255644f885d445e47e291e50eb12b5ecd08d
Author: Tibor Erdesz <erdeszt at gmail.com>
Date:   Thu Jun 29 19:37:13 2017 -0400

    Allow optional instance keyword in associated type family instances
    
    Add the missing branch for parsing the optional 'instance' keyword
    in associated type family instance declarations.
    
    Fixes #13747
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: simonpj, RyanGlScott, rwbarton, thomie, mpickering
    
    Differential Revision: https://phabricator.haskell.org/D3673


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

007f255644f885d445e47e291e50eb12b5ecd08d
 compiler/parser/Parser.y                        | 34 ++++++++++++++++++++-----
 docs/users_guide/8.4.1-notes.rst                |  3 +++
 testsuite/tests/parser/should_compile/T13747.hs | 24 +++++++++++++++++
 testsuite/tests/parser/should_compile/all.T     |  1 +
 4 files changed, 55 insertions(+), 7 deletions(-)

diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 6e4b774..603ac27 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -1215,25 +1215,37 @@ opt_family   :: { [AddAnn] }
               : {- empty -}   { [] }
               | 'family'      { [mj AnnFamily $1] }
 
+opt_instance :: { [AddAnn] }
+              : {- empty -} { [] }
+              | 'instance'  { [mj AnnInstance $1] }
+
 -- Associated type instances
 --
 at_decl_inst :: { LInstDecl GhcPs }
-           -- type instance declarations
-        : 'type' ty_fam_inst_eqn
+           -- type instance declarations, with optional 'instance' keyword
+        : 'type' opt_instance ty_fam_inst_eqn
                 -- Note the use of type for the head; this allows
                 -- infix type constructors and type patterns
-                {% ams $2 (fst $ unLoc $2) >>
-                   amms (mkTyFamInst (comb2 $1 $2) (snd $ unLoc $2))
-                        (mj AnnType $1:(fst $ unLoc $2)) }
+                {% ams $3 (fst $ unLoc $3) >>
+                   amms (mkTyFamInst (comb2 $1 $3) (snd $ unLoc $3))
+                        (mj AnnType $1:$2++(fst $ unLoc $3)) }
 
-        -- data/newtype instance declaration
+        -- data/newtype instance declaration, with optional 'instance' keyword
+        -- (can't use opt_instance because you get reduce/reduce errors)
         | data_or_newtype capi_ctype tycl_hdr constrs maybe_derivings
                {% amms (mkDataFamInst (comb4 $1 $3 $4 $5) (snd $ unLoc $1) $2 $3
                                     Nothing (reverse (snd $ unLoc $4))
                                             (fmap reverse $5))
                        ((fst $ unLoc $1):(fst $ unLoc $4)) }
 
-        -- GADT instance declaration
+        | data_or_newtype 'instance' capi_ctype tycl_hdr constrs maybe_derivings
+               {% amms (mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 $4
+                                    Nothing (reverse (snd $ unLoc $5))
+                                            (fmap reverse $6))
+                       ((fst $ unLoc $1):mj AnnInstance $2:(fst $ unLoc $5)) }
+
+        -- GADT instance declaration, with optional 'instance' keyword
+        -- (can't use opt_instance because you get reduce/reduce errors)
         | data_or_newtype capi_ctype tycl_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
@@ -1242,6 +1254,14 @@ at_decl_inst :: { LInstDecl GhcPs }
                                 (fmap reverse $6))
                         ((fst $ unLoc $1):(fst $ unLoc $4)++(fst $ unLoc $5)) }
 
+        | data_or_newtype 'instance' capi_ctype tycl_hdr opt_kind_sig
+                 gadt_constrlist
+                 maybe_derivings
+                {% amms (mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3
+                                $4 (snd $ unLoc $5) (snd $ unLoc $6)
+                                (fmap reverse $7))
+                        ((fst $ unLoc $1):mj AnnInstance $2:(fst $ unLoc $5)++(fst $ unLoc $6)) }
+
 data_or_newtype :: { Located (AddAnn, NewOrData) }
         : 'data'        { sL1 $1 (mj AnnData    $1,DataType) }
         | 'newtype'     { sL1 $1 (mj AnnNewtype $1,NewType) }
diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst
index f23cb36..7e918f2 100644
--- a/docs/users_guide/8.4.1-notes.rst
+++ b/docs/users_guide/8.4.1-notes.rst
@@ -80,6 +80,9 @@ Now we generate ::
   used to build a GHC using compilers on your ``PATH`` instead of using the
   bundled bindist. See :ghc-ticket:`13792`
 
+- The optional ``instance`` keyword is now usable in type family instance
+  declarations. See :ghc-ticket:`13747`
+
 - Lots of other bugs. See `Trac <https://ghc.haskell.org/trac/ghc/query?status=closed&milestone=8.4.1&col=id&col=summary&col=status&col=type&col=priority&col=milestone&col=component&order=priority>`_
   for a complete list.
 
diff --git a/testsuite/tests/parser/should_compile/T13747.hs b/testsuite/tests/parser/should_compile/T13747.hs
new file mode 100644
index 0000000..749d8d2
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/T13747.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE GADTs #-}
+
+module T13747 where
+
+class C a where
+  type family TC a :: *
+
+class D a where
+  data family TD a :: *
+
+instance C Int where
+  type instance TC Int = Int
+
+instance D Double where
+  data instance TD Double = TDDouble
+
+instance D Int where
+  newtype instance TD Int = TDInt Int
+
+instance D Char where
+    data instance TD Char where
+        C1 :: TD Char
+        C2 :: TD Char
diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T
index 2059979..a9d6830 100644
--- a/testsuite/tests/parser/should_compile/all.T
+++ b/testsuite/tests/parser/should_compile/all.T
@@ -107,3 +107,4 @@ test('T10582', expect_broken(10582), compile, [''])
 test('DumpParsedAst',      normal, compile, ['-dsuppress-uniques -ddump-parsed-ast'])
 test('DumpRenamedAst',     normal, compile, ['-dsuppress-uniques -ddump-rn-ast'])
 test('DumpTypecheckedAst', normal, compile, ['-dsuppress-uniques -ddump-tc-ast'])
+test('T13747', normal, compile, [''])



More information about the ghc-commits mailing list