Skip to content
Snippets Groups Projects
Commit 3ad6d4f5 authored by Alan Zimmerman's avatar Alan Zimmerman
Browse files

API Annotations: parens anns discarded for `(*)` operator

The patch from https://phabricator.haskell.org/D4865 introduces

    go _ (HsParTy _ (dL->L l (HsStarTy _ isUni))) acc ann fix
      = do { warnStarBndr l
           ; let name = mkOccName tcClsName (if isUni then "★" else "*")
           ; return (cL l (Unqual name), acc, fix, ann) }

which discards the parens annotations belonging to the HsParTy.

Updates haddock submodule

Closes #16265

(cherry picked from commit 5e9888bd)
parent 91ba643c
Branches wip/ghc-8.8-az
No related tags found
No related merge requests found
......@@ -960,10 +960,10 @@ checkTyClHdr is_cls ty
goL (dL->L l ty) acc ann fix = go l ty acc ann fix
-- workaround to define '*' despite StarIsType
go _ (HsParTy _ (dL->L l (HsStarTy _ isUni))) acc ann fix
go lp (HsParTy _ (dL->L l (HsStarTy _ isUni))) acc ann fix
= do { warnStarBndr l
; let name = mkOccName tcClsName (if isUni then "★" else "*")
; return (cL l (Unqual name), acc, fix, ann) }
; 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)
......
......@@ -161,3 +161,7 @@ T16230:
.PHONY: T16236
T16236:
$(CHECK_API_ANNOTATIONS) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" Test16236.hs
.PHONY: StarBinderAnns
StarBinderAnns:
$(CHECK_API_ANNOTATIONS) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" StarBinderAnns.hs
{-# LANGUAGE TypeOperators, TypeFamilies #-}
{-# OPTIONS -Wno-star-is-type #-}
module X (type (X.*)) where
type family (*) a b where { (*) a b = Either b a }
---Unattached Annotation Problems (should be empty list)---
[]
---Ann before enclosing span problem (should be empty list)---
[
]
---Annotations-----------------------
-- SrcSpan the annotation is attached to, AnnKeywordId,
-- list of locations the keyword item appears in
[
((StarBinderAnns.hs:1:1,AnnModule), [StarBinderAnns.hs:4:1-6]),
((StarBinderAnns.hs:1:1,AnnWhere), [StarBinderAnns.hs:4:23-27]),
((StarBinderAnns.hs:4:10-21,AnnCloseP), [StarBinderAnns.hs:4:21]),
((StarBinderAnns.hs:4:10-21,AnnOpenP), [StarBinderAnns.hs:4:10]),
((StarBinderAnns.hs:4:11-20,AnnType), [StarBinderAnns.hs:4:11-14]),
((StarBinderAnns.hs:4:16-20,AnnCloseP), [StarBinderAnns.hs:4:20]),
((StarBinderAnns.hs:4:16-20,AnnOpenP), [StarBinderAnns.hs:4:16]),
((StarBinderAnns.hs:4:16-20,AnnVal), [StarBinderAnns.hs:4:17-19]),
((StarBinderAnns.hs:6:1-19,AnnCloseC), [StarBinderAnns.hs:6:50]),
((StarBinderAnns.hs:6:1-19,AnnCloseP), [StarBinderAnns.hs:6:15]),
((StarBinderAnns.hs:6:1-19,AnnFamily), [StarBinderAnns.hs:6:6-11]),
((StarBinderAnns.hs:6:1-19,AnnOpenC), [StarBinderAnns.hs:6:27]),
((StarBinderAnns.hs:6:1-19,AnnOpenP), [StarBinderAnns.hs:6:13]),
((StarBinderAnns.hs:6:1-19,AnnSemi), [StarBinderAnns.hs:7:1]),
((StarBinderAnns.hs:6:1-19,AnnType), [StarBinderAnns.hs:6:1-4]),
((StarBinderAnns.hs:6:1-19,AnnWhere), [StarBinderAnns.hs:6:21-25]),
((StarBinderAnns.hs:6:13-15,AnnCloseP), [StarBinderAnns.hs:6:15]),
((StarBinderAnns.hs:6:13-15,AnnOpenP), [StarBinderAnns.hs:6:13]),
((StarBinderAnns.hs:6:29-31,AnnCloseP), [StarBinderAnns.hs:6:31]),
((StarBinderAnns.hs:6:29-31,AnnOpenP), [StarBinderAnns.hs:6:29]),
((StarBinderAnns.hs:6:29-48,AnnCloseP), [StarBinderAnns.hs:6:31]),
((StarBinderAnns.hs:6:29-48,AnnEqual), [StarBinderAnns.hs:6:37]),
((StarBinderAnns.hs:6:29-48,AnnOpenP), [StarBinderAnns.hs:6:29]),
((<no location info>,AnnEofPos), [StarBinderAnns.hs:7:1])
]
\ No newline at end of file
......@@ -67,3 +67,5 @@ test('T16230', [extra_files(['Test16230.hs']),
ignore_stderr], run_command, ['$MAKE -s --no-print-directory T16230'])
test('T16236', [extra_files(['Test16236.hs']),
ignore_stderr], run_command, ['$MAKE -s --no-print-directory T16236'])
test('StarBinderAnns', [extra_files(['StarBinderAnns.hs']),
ignore_stderr], run_command, ['$MAKE -s --no-print-directory StarBinderAnns'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment