Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
5dabc718
by Zubin Duggal at 2025-07-22T21:14:10-04:00
5 changed files:
- testsuite/tests/haddock/haddock_testsuite/Makefile
- + testsuite/tests/haddock/haddock_testsuite/T26114.hs
- + testsuite/tests/haddock/haddock_testsuite/T26114.stdout
- testsuite/tests/haddock/haddock_testsuite/all.T
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
Changes:
| ... | ... | @@ -76,3 +76,7 @@ hypsrcTest: |
| 76 | 76 | .PHONY: haddockForeignTest
|
| 77 | 77 | haddockForeignTest:
|
| 78 | 78 | '$(HADDOCK)' A.hs B.hs F.hs arith.c
|
| 79 | + |
|
| 80 | +.PHONY: T26114
|
|
| 81 | +T26114:
|
|
| 82 | + '$(HADDOCK)' T26114.hs |
| 1 | +{-# LANGUAGE TypeFamilies #-}
|
|
| 2 | + |
|
| 3 | +-- | Module
|
|
| 4 | +module T26114 where
|
|
| 5 | + |
|
| 6 | +-- | C1
|
|
| 7 | +class C1 t where
|
|
| 8 | + type C2 t
|
|
| 9 | + |
|
| 10 | +-- | A
|
|
| 11 | +data A = A
|
|
| 12 | + |
|
| 13 | +instance C1 A where
|
|
| 14 | + type C2 A = B
|
|
| 15 | + |
|
| 16 | +-- | B
|
|
| 17 | +data B = B
|
|
| 18 | + |
|
| 19 | +instance C1 B where
|
|
| 20 | + type C2 B = C
|
|
| 21 | + |
|
| 22 | +-- | C
|
|
| 23 | +data C = C |
| 1 | +[1 of 1] Compiling T26114 ( T26114.hs, nothing )
|
|
| 2 | +Haddock coverage:
|
|
| 3 | + 100% ( 5 / 5) in 'T26114' |
| ... | ... | @@ -24,3 +24,8 @@ test('haddockForeignTest', |
| 24 | 24 | [ignore_stdout, ignore_stderr, req_haddock, extra_files(['./haddock-th-foreign-repro/A.hs', './haddock-th-foreign-repro/B.hs', './haddock-th-foreign-repro/F.hs', './haddock-th-foreign-repro/arith.c'])],
|
| 25 | 25 | makefile_test,
|
| 26 | 26 | ['haddockForeignTest'])
|
| 27 | + |
|
| 28 | +test('T26114',
|
|
| 29 | + [ignore_stderr, req_haddock, extra_files(['T26114.hs'])],
|
|
| 30 | + makefile_test,
|
|
| 31 | + ['T26114']) |
| ... | ... | @@ -110,6 +110,7 @@ renameInterface ignoreSet renamingEnv expInfo warnings hoogle iface = do |
| 110 | 110 | && isExternalName name
|
| 111 | 111 | && not (isBuiltInSyntax name)
|
| 112 | 112 | && not (isTyVarName name)
|
| 113 | + && not (isDerivedOccName $ nameOccName name)
|
|
| 113 | 114 | && Exact name /= eqTyCon_RDR
|
| 114 | 115 | -- Must not be in the set of ignored symbols for the module or the
|
| 115 | 116 | -- unqualified ignored symbols
|