[Git][ghc/ghc][master] Fix #16632 by using the correct SrcSpan in checkTyClHdr
Marge Bot
gitlab at gitlab.haskell.org
Wed May 8 06:08:02 UTC 2019
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
0eeb4cfa by Ryan Scott at 2019-05-08T06:01:54Z
Fix #16632 by using the correct SrcSpan in checkTyClHdr
`checkTyClHdr`'s case for `HsTyVar` was grabbing the wrong `SrcSpan`,
which lead to error messages pointing to the wrong location. Easily
fixed.
- - - - -
4 changed files:
- compiler/parser/RdrHsSyn.hs
- + testsuite/tests/indexed-types/should_compile/T16632.hs
- + testsuite/tests/indexed-types/should_compile/T16632.stderr
- testsuite/tests/indexed-types/should_compile/all.T
Changes:
=====================================
compiler/parser/RdrHsSyn.hs
=====================================
@@ -955,8 +955,8 @@ checkTyClHdr is_cls ty
; let name = mkOccName tcClsName (starSym isUni)
; return (cL l (Unqual name), acc, fix, (ann ++ mkParensApiAnn lp)) }
- go l (HsTyVar _ _ (dL->L _ tc)) acc ann fix
- | isRdrTc tc = return (cL l tc, acc, fix, ann)
+ go _ (HsTyVar _ _ ltc@(dL->L _ tc)) acc ann fix
+ | isRdrTc tc = return (ltc, acc, fix, ann)
go _ (HsOpTy _ t1 ltc@(dL->L _ tc) t2) acc ann _fix
| isRdrTc tc = return (ltc, HsValArg t1:HsValArg t2:acc, Infix, ann)
go l (HsParTy _ ty) acc ann fix = goL ty acc (ann ++mkParensApiAnn l) fix
=====================================
testsuite/tests/indexed-types/should_compile/T16632.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE TypeFamilies #-}
+module T16632 where
+
+type family F a b c
+type instance F Char b Int = ()
=====================================
testsuite/tests/indexed-types/should_compile/T16632.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T16632.hs:5:22: warning: [-Wunused-type-patterns]
+ Defined but not used on the right hand side: type variable ‘b’
+ |
+5 | type instance F Char b Int = ()
+ | ^
=====================================
testsuite/tests/indexed-types/should_compile/all.T
=====================================
@@ -286,3 +286,4 @@ test('T15711', normal, compile, ['-ddump-types'])
test('T15852', normal, compile, ['-ddump-types'])
test('T15764a', normal, compile, [''])
test('T15740a', normal, compile, [''])
+test('T16632', normal, compile, ['-Wunused-type-patterns -fdiagnostics-show-caret'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/0eeb4cfad732d0b9b278c2274cb6db9633f9d3b5
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/0eeb4cfad732d0b9b278c2274cb6db9633f9d3b5
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190508/2ceac3d3/attachment-0001.html>
More information about the ghc-commits
mailing list