[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 15 commits: Print fully qualified unit names in name mismatch
by Marge Bot (@marge-bot) 17 Sep '25
by Marge Bot (@marge-bot) 17 Sep '25
17 Sep '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
54b5950e by Sylvain Henry at 2025-09-17T04:45:18-04:00
Print fully qualified unit names in name mismatch
It's more user-friendly to directly print the right thing instead of
requiring the user to retry with the additional `-dppr-debug` flag.
- - - - -
403cb665 by Ben Gamari at 2025-09-17T04:46:00-04:00
configure: Fix consistency between distrib and source CC check
Previously distrib/configure.ac did not
include `cc`.
Closes #26394.
- - - - -
2dcd4cb9 by Oleg Grenrus at 2025-09-17T04:46:41-04:00
Use isPrint in showUnique
The comment say
```
-- Avoid emitting non-printable characters in pretty uniques. See #25989.
```
so let the code do exactly that.
There are tags (at least : and 0 .. 9) which weren't in A .. z range.
- - - - -
e5dd754b by Oleg Grenrus at 2025-09-17T04:46:42-04:00
Shorten in-module links in hyperlinked source
Instead of href="This.Module#ident" to just "#ident"
- - - - -
63189b2c by Oleg Grenrus at 2025-09-17T04:46:42-04:00
Use showUnique in internalAnchorIdent
Showing the key of Unique as a number is generally not a great idea.
GHC Unique has a tag in high bits, so the raw number is unnecessarily
big.
So now we have
```html
<a href="#l-rvgK"><span class="hs-identifier hs-var hs-var">bar</span></a>
```
instead of
```html
<a href="#local-6989586621679015689"><span class="hs-identifier hs-var hs-var">bar</span></a>
```
Together with previous changes of shorter intra-module links the effect
on compressed files is not huge, that is expected as we simply remove
repetitive contents which pack well.
```
12_694_206 Agda-2.9.0-docs-orig.tar.gz
12_566_065 Agda-2.9.0-docs.tar.gz
```
However when unpacked, the difference can be significant,
e.g. Agda's largest module source got 5% reduction:
```
14_230_117 Agda.Syntax.Parser.Parser.html
13_422_109 Agda.Syntax.Parser.Parser.html
```
The whole hyperlinked source code directory got similar reduction
```
121M Agda-2.9.0-docs-orig/src
114M Agda-2.9.0-docs/src
```
For the reference, sources are about 2/3 of the generated haddocks
```
178M Agda-2.9.0-docs-old
172M Agda-2.9.0-docs
```
so we get around 3.5% size reduction overall. Not bad for a small local
changes.
- - - - -
6f63f57b by Stefan Schulze Frielinghaus at 2025-09-17T04:47:22-04:00
rts: Fix alignment for gen_workspace #26334
After a0fa4941903272c48b050d24e93eec819eff51bd bootstrap is broken on
s390x and errors out with
rts/sm/GCThread.h:207:5: error:
error: alignment of array elements is greater than element size
207 | gen_workspace gens[];
| ^~~~~~~~~~~~~
The alignment constraint is applied via the attribute to the type
gen_workspace and leaves the underlying type struct gen_workspace_
untouched. On Aarch64, x86, and s390x the struct has a size of 128
bytes. On Aarch64 and x86 the alignments of 128 and 64 are divisors of
the size, respectively, which is why the type is a viable member type
for an array. However, on s390x, the alignment is 256 and therefore is
not a divisor of the size and hence cannot be used for arrays.
Basically I see two fixes here. Either decrease the alignment
requirement on s390x, or by applying the alignment constraint on the
struct itself. The former might affect performance as noted in
a0fa4941903272c48b050d24e93eec819eff51bd. The latter introduces padding
bits whenever necessary in order to ensure that
sizeof(gen_workspace[N])==N*sizeof(gen_workspace) holds which is done by
this patch.
- - - - -
a1260339 by Cheng Shao at 2025-09-17T05:20:04-04:00
ghci: add :shell command
This patch adds a new :shell command to ghci which works similarly to
:!, except it guarantees to run the command via sh -c. On POSIX hosts
the behavior is identical to :!, but on Windows it uses the msys2
shell instead of system cmd.exe shell. This is convenient when writing
simple ghci scripts that run simple POSIX commands, and the behavior
can be expected to be coherent on both Windows and POSIX.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
56adb4dd by Cheng Shao at 2025-09-17T05:20:04-04:00
testsuite: remove legacy :shell trick
This commit makes use of the built-in :shell functionality in ghci in
the test cases, and remove the legacy :shell trick.
- - - - -
bc60c60e by Cheng Shao at 2025-09-17T05:20:04-04:00
docs: document :shell in ghci
This commit documents the :shell command in ghci.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
afa1041f by sheaf at 2025-09-17T05:20:22-04:00
Enable TcM plugins in initTc
This commit ensures that we run typechecker plugins and defaulting
plugins whenever we call initTc.
In particular, this ensures that the pattern-match checker, which calls
'initTcDsForSolver' which calls 'initTc', runs with typechecker plugins
enabled. This matters for situations like:
merge :: Vec n a -> Vec n a -> Vec (2 * n) a
merge Nil Nil = Nil
merge (a <: as) (b <: bs) = a :< (b <: merge as bs)
in which we need the typechecker plugin to run in order to tell us that
the Givens would be inconsistent in the additional equation
merge (_ <: _) Nil
and thus that the equation is not needed.
Fixes #26395
- - - - -
bb94daa0 by Cheng Shao at 2025-09-17T05:20:23-04:00
ghc-internal: fix codepages program
codepages was not properly updated during the base -> ghc-internal
migration, this commit fixes it.
- - - - -
4d519127 by Cheng Shao at 2025-09-17T05:20:23-04:00
ghc-internal: relax ucd2haskell cabal upper bounds
This commit relaxes ucd2haskell cabal upper bounds to make it runnable
via ghc 9.12/9.14.
- - - - -
36d9a848 by Cheng Shao at 2025-09-17T05:20:23-04:00
ghc-internal: update to unicode 17.0.0
This commit updates the generated code in ghc-internal to match
unicode 17.0.0.
- - - - -
33f9284f by sheaf at 2025-09-17T05:20:28-04:00
Bad record update msg: allow out-of-scope datacons
This commit ensures that, when we encounter an invalid record update
(because no constructor exists which contains all of the record fields
mentioned in the record update), we graciously handle the situation in
which the constructors themselves are not in scope. In that case,
instead of looking up the constructors in the GlobalRdrEnv, directly
look up their GREInfo using the lookupGREInfo function.
Fixes #26391
- - - - -
48d63637 by sheaf at 2025-09-17T05:20:28-04:00
Improve Notes about disambiguating record updates
This commit updates the notes [Disambiguating record updates] and
[Type-directed record disambiguation], in particular adding more
information about the deprecation status of type-directed disambiguation
of record updates.
- - - - -
88 changed files:
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Unit/State.hs
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- libraries/base/tests/unicode002.stdout
- libraries/base/tests/unicode003.stdout
- libraries/ghc-internal/codepages/MakeTable.hs
- libraries/ghc-internal/codepages/Makefile
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs
- libraries/ghc-internal/tools/ucd2haskell/ucd.sh
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghc-internal/tools/ucd2haskell/unicode_version
- rts/sm/GCThread.h
- testsuite/tests/driver/multipleHomeUnits/all.T
- testsuite/tests/ghci.debugger/scripts/break022/all.T
- testsuite/tests/ghci.debugger/scripts/break022/break022.script
- testsuite/tests/ghci.debugger/scripts/break023/all.T
- testsuite/tests/ghci.debugger/scripts/break023/break023.script
- testsuite/tests/ghci/prog001/prog001.T
- testsuite/tests/ghci/prog001/prog001.script
- testsuite/tests/ghci/prog002/prog002.T
- testsuite/tests/ghci/prog002/prog002.script
- testsuite/tests/ghci/prog003/prog003.T
- testsuite/tests/ghci/prog003/prog003.script
- testsuite/tests/ghci/prog005/prog005.T
- testsuite/tests/ghci/prog005/prog005.script
- testsuite/tests/ghci/prog010/all.T
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog012/all.T
- testsuite/tests/ghci/prog012/prog012.script
- testsuite/tests/ghci/recompTHghci/all.T
- testsuite/tests/ghci/recompTHghci/recompTHghci.script
- testsuite/tests/ghci/scripts/T18330.script
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.script
- testsuite/tests/ghci/scripts/T20587.script
- testsuite/tests/ghci/scripts/T6106.script
- testsuite/tests/ghci/scripts/T8353.script
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci038.script
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/scripts/ghci063.script
- − testsuite/tests/ghci/shell.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
- testsuite/tests/perf/compiler/MultiLayerModulesDefsGhci.script
- testsuite/tests/perf/compiler/all.T
- + testsuite/tests/tcplugins/T26395.hs
- + testsuite/tests/tcplugins/T26395.stderr
- + testsuite/tests/tcplugins/T26395_Plugin.hs
- testsuite/tests/tcplugins/all.T
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs
- utils/haddock/hypsrc-test/Main.hs
- utils/haddock/hypsrc-test/ref/src/CPP.html
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Constructors.html
- utils/haddock/hypsrc-test/ref/src/Identifiers.html
- utils/haddock/hypsrc-test/ref/src/LinkingIdentifiers.html
- utils/haddock/hypsrc-test/ref/src/Literals.html
- utils/haddock/hypsrc-test/ref/src/Operators.html
- utils/haddock/hypsrc-test/ref/src/Polymorphism.html
- utils/haddock/hypsrc-test/ref/src/PositionPragmas.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/haddock/hypsrc-test/ref/src/Records.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellSplices.html
- utils/haddock/hypsrc-test/ref/src/Types.html
- utils/haddock/hypsrc-test/ref/src/UsingQuasiquotes.html
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ecebc5b6389beff77f2e29fe27fcb3…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ecebc5b6389beff77f2e29fe27fcb3…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] rts: Fix alignment for gen_workspace #26334
by Marge Bot (@marge-bot) 17 Sep '25
by Marge Bot (@marge-bot) 17 Sep '25
17 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
6f63f57b by Stefan Schulze Frielinghaus at 2025-09-17T04:47:22-04:00
rts: Fix alignment for gen_workspace #26334
After a0fa4941903272c48b050d24e93eec819eff51bd bootstrap is broken on
s390x and errors out with
rts/sm/GCThread.h:207:5: error:
error: alignment of array elements is greater than element size
207 | gen_workspace gens[];
| ^~~~~~~~~~~~~
The alignment constraint is applied via the attribute to the type
gen_workspace and leaves the underlying type struct gen_workspace_
untouched. On Aarch64, x86, and s390x the struct has a size of 128
bytes. On Aarch64 and x86 the alignments of 128 and 64 are divisors of
the size, respectively, which is why the type is a viable member type
for an array. However, on s390x, the alignment is 256 and therefore is
not a divisor of the size and hence cannot be used for arrays.
Basically I see two fixes here. Either decrease the alignment
requirement on s390x, or by applying the alignment constraint on the
struct itself. The former might affect performance as noted in
a0fa4941903272c48b050d24e93eec819eff51bd. The latter introduces padding
bits whenever necessary in order to ensure that
sizeof(gen_workspace[N])==N*sizeof(gen_workspace) holds which is done by
this patch.
- - - - -
1 changed file:
- rts/sm/GCThread.h
Changes:
=====================================
rts/sm/GCThread.h
=====================================
@@ -83,7 +83,7 @@
// platforms.
#define GEN_WORKSPACE_ALIGNMENT CACHELINE_SIZE
-typedef struct gen_workspace_ {
+typedef struct ATTRIBUTE_ALIGNED(GEN_WORKSPACE_ALIGNMENT) gen_workspace_ {
generation * gen; // the gen for this workspace
struct gc_thread_ * my_gct; // the gc_thread that contains this workspace
@@ -109,7 +109,7 @@ typedef struct gen_workspace_ {
bdescr * part_list;
StgWord n_part_blocks; // count of above
StgWord n_part_words;
-} gen_workspace ATTRIBUTE_ALIGNED(GEN_WORKSPACE_ALIGNMENT);
+} gen_workspace;
/* ----------------------------------------------------------------------------
GC thread object
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6f63f57b86fffc8a9102b91a18a6de5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6f63f57b86fffc8a9102b91a18a6de5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
17 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
2dcd4cb9 by Oleg Grenrus at 2025-09-17T04:46:41-04:00
Use isPrint in showUnique
The comment say
```
-- Avoid emitting non-printable characters in pretty uniques. See #25989.
```
so let the code do exactly that.
There are tags (at least : and 0 .. 9) which weren't in A .. z range.
- - - - -
e5dd754b by Oleg Grenrus at 2025-09-17T04:46:42-04:00
Shorten in-module links in hyperlinked source
Instead of href="This.Module#ident" to just "#ident"
- - - - -
63189b2c by Oleg Grenrus at 2025-09-17T04:46:42-04:00
Use showUnique in internalAnchorIdent
Showing the key of Unique as a number is generally not a great idea.
GHC Unique has a tag in high bits, so the raw number is unnecessarily
big.
So now we have
```html
<a href="#l-rvgK"><span class="hs-identifier hs-var hs-var">bar</span></a>
```
instead of
```html
<a href="#local-6989586621679015689"><span class="hs-identifier hs-var hs-var">bar</span></a>
```
Together with previous changes of shorter intra-module links the effect
on compressed files is not huge, that is expected as we simply remove
repetitive contents which pack well.
```
12_694_206 Agda-2.9.0-docs-orig.tar.gz
12_566_065 Agda-2.9.0-docs.tar.gz
```
However when unpacked, the difference can be significant,
e.g. Agda's largest module source got 5% reduction:
```
14_230_117 Agda.Syntax.Parser.Parser.html
13_422_109 Agda.Syntax.Parser.Parser.html
```
The whole hyperlinked source code directory got similar reduction
```
121M Agda-2.9.0-docs-orig/src
114M Agda-2.9.0-docs/src
```
For the reference, sources are about 2/3 of the generated haddocks
```
178M Agda-2.9.0-docs-old
172M Agda-2.9.0-docs
```
so we get around 3.5% size reduction overall. Not bad for a small local
changes.
- - - - -
20 changed files:
- compiler/GHC/Types/Unique.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs
- utils/haddock/hypsrc-test/Main.hs
- utils/haddock/hypsrc-test/ref/src/CPP.html
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Constructors.html
- utils/haddock/hypsrc-test/ref/src/Identifiers.html
- utils/haddock/hypsrc-test/ref/src/LinkingIdentifiers.html
- utils/haddock/hypsrc-test/ref/src/Literals.html
- utils/haddock/hypsrc-test/ref/src/Operators.html
- utils/haddock/hypsrc-test/ref/src/Polymorphism.html
- utils/haddock/hypsrc-test/ref/src/PositionPragmas.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/haddock/hypsrc-test/ref/src/Records.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellSplices.html
- utils/haddock/hypsrc-test/ref/src/Types.html
- utils/haddock/hypsrc-test/ref/src/UsingQuasiquotes.html
Changes:
=====================================
compiler/GHC/Types/Unique.hs
=====================================
@@ -28,6 +28,7 @@ module GHC.Types.Unique (
-- ** Constructors, destructors and operations on 'Unique's
hasKey,
+ showUnique,
pprUniqueAlways,
mkTag,
@@ -61,7 +62,7 @@ import GHC.Utils.Word64 (intToWord64, word64ToInt)
import GHC.Exts (indexCharOffAddr#, Char(..), Int(..))
import GHC.Word ( Word64 )
-import Data.Char ( chr, ord )
+import Data.Char ( chr, ord, isPrint )
import Language.Haskell.Syntax.Module.Name
@@ -308,8 +309,8 @@ showUnique uniq
-- Avoid emitting non-printable characters in pretty uniques.
-- See #25989.
tagStr
- | tag < 'A' || tag > 'z' = show (ord tag) ++ "_"
- | otherwise = [tag]
+ | not (isPrint tag) = show (ord tag) ++ "_"
+ | otherwise = [tag]
pprUniqueAlways :: IsLine doc => Unique -> doc
-- The "always" means regardless of -dsuppress-uniques
=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs
=====================================
@@ -80,6 +80,7 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = do
nc <- freshNameCache
HieFile
{ hie_hs_file = file
+ , hie_module = thisModule
, hie_asts = HieASTs asts
, hie_types = types
, hie_hs_src = rawSrc
@@ -116,7 +117,7 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = do
let tokens = fmap (\tk -> tk{tkSpan = (tkSpan tk){srcSpanFile = srcSpanFile $ nodeSpan fullAst}}) tokens'
-- Produce and write out the hyperlinked sources
- writeUtf8File path . renderToString pretty . render' fullAst $ tokens
+ writeUtf8File path . renderToString pretty . render' thisModule fullAst $ tokens
where
dflags = ifaceDynFlags iface
sDocContext = DynFlags.initSDocContext dflags Outputable.defaultUserStyle
@@ -128,7 +129,7 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = do
False -- lex Haddocks as comment tokens
True -- produce comment tokens
False -- produce position pragmas tokens
- render' = render (Just srcCssFile) (Just highlightScript) srcs
+ render' thisModule = render thisModule (Just srcCssFile) (Just highlightScript) srcs
path = srcdir </> hypSrcModuleFile (ifaceMod iface)
emptyHieAst fileFs =
=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
=====================================
@@ -14,8 +14,8 @@ import GHC.Iface.Ext.Types
import GHC.Iface.Ext.Utils (emptyNodeInfo, isEvidenceContext)
import GHC.Types.Name (Name, getOccString, isInternalName, nameModule, nameUnique)
import GHC.Types.SrcLoc
-import GHC.Types.Unique (getKey)
-import GHC.Unit.Module (ModuleName, moduleNameString)
+import GHC.Types.Unique (showUnique)
+import GHC.Unit.Module (Module, ModuleName, moduleNameString)
import GHC.Utils.Encoding (utf8DecodeByteString)
import System.FilePath.Posix ((</>))
import Text.XHtml (Html, HtmlAttr, (!))
@@ -28,7 +28,9 @@ type StyleClass = String
-- | Produce the HTML corresponding to a hyperlinked Haskell source
render
- :: Maybe FilePath
+ :: Module
+ -- ^ this module
+ -> Maybe FilePath
-- ^ path to the CSS file
-> Maybe FilePath
-- ^ path to the JS file
@@ -39,12 +41,12 @@ render
-> [Token]
-- ^ tokens to render
-> Html
-render mcss mjs srcs ast tokens = header mcss mjs <> body srcs ast tokens
+render thisModule mcss mjs srcs ast tokens = header mcss mjs <> body thisModule srcs ast tokens
-body :: SrcMaps -> HieAST PrintedType -> [Token] -> Html
-body srcs ast tokens = Html.body . Html.pre $ hypsrc
+body :: Module -> SrcMaps -> HieAST PrintedType -> [Token] -> Html
+body thisModule srcs ast tokens = Html.body . Html.pre $ hypsrc
where
- hypsrc = renderWithAst srcs ast tokens
+ hypsrc = renderWithAst thisModule srcs ast tokens
header :: Maybe FilePath -> Maybe FilePath -> Html
header Nothing Nothing = Html.noHtml
@@ -75,9 +77,9 @@ splitTokens ast toks = (before, during, after)
-- | Turn a list of tokens into hyperlinked sources, threading in relevant link
-- information from the 'HieAST'.
-renderWithAst :: SrcMaps -> HieAST PrintedType -> [Token] -> Html
-renderWithAst srcs Node{..} toks = anchored $ case toks of
- [tok] | nodeSpan == tkSpan tok -> richToken srcs nodeInfo tok
+renderWithAst :: Module -> SrcMaps -> HieAST PrintedType -> [Token] -> Html
+renderWithAst thisModule srcs Node{..} toks = anchored $ case toks of
+ [tok] | nodeSpan == tkSpan tok -> richToken thisModule srcs nodeInfo tok
-- NB: the GHC lexer lexes backquoted identifiers and parenthesized operators
-- as multiple tokens.
--
@@ -92,6 +94,7 @@ renderWithAst srcs Node{..} toks = anchored $ case toks of
| realSrcSpanStart s1 == realSrcSpanStart nodeSpan
, realSrcSpanEnd s2 == realSrcSpanEnd nodeSpan ->
richToken
+ thisModule
srcs
nodeInfo
( Token
@@ -104,6 +107,7 @@ renderWithAst srcs Node{..} toks = anchored $ case toks of
| realSrcSpanStart s1 == realSrcSpanStart nodeSpan
, realSrcSpanEnd s2 == realSrcSpanEnd nodeSpan ->
richToken
+ thisModule
srcs
nodeInfo
( Token
@@ -118,7 +122,7 @@ renderWithAst srcs Node{..} toks = anchored $ case toks of
go _ [] = mempty
go [] xs = foldMap renderToken xs
go (cur : rest) xs =
- foldMap renderToken before <> renderWithAst srcs cur during <> go rest after
+ foldMap renderToken before <> renderWithAst thisModule srcs cur during <> go rest after
where
(before, during, after) = splitTokens cur xs
anchored c = Map.foldrWithKey anchorOne c (nodeIdentifiers nodeInfo)
@@ -137,8 +141,8 @@ renderToken Token{..}
tokenSpan = Html.thespan (Html.toHtml tkValue')
-- | Given information about the source position of definitions, render a token
-richToken :: SrcMaps -> NodeInfo PrintedType -> Token -> Html
-richToken srcs details Token{..}
+richToken :: Module -> SrcMaps -> NodeInfo PrintedType -> Token -> Html
+richToken thisModule srcs details Token{..}
| tkType == TkSpace = renderSpace (srcSpanStartLine tkSpan) tkValue'
| otherwise = annotate details $ linked content
where
@@ -155,7 +159,7 @@ richToken srcs details Token{..}
-- If we have name information, we can make links
linked = case identDet of
- Just (n, _) -> hyperlink srcs n
+ Just (n, _) -> hyperlink thisModule srcs n
Nothing -> id
-- | Remove CRLFs from source
@@ -250,11 +254,11 @@ externalAnchorIdent :: Name -> String
externalAnchorIdent = hypSrcNameUrl
internalAnchorIdent :: Name -> String
-internalAnchorIdent = ("local-" ++) . show . getKey . nameUnique
+internalAnchorIdent = ("l-" ++) . showUnique . nameUnique
-- | Generate the HTML hyperlink for an identifier
-hyperlink :: SrcMaps -> Identifier -> Html -> Html
-hyperlink (srcs, srcs') ident = case ident of
+hyperlink :: Module -> SrcMaps -> Identifier -> Html -> Html
+hyperlink thisModule (srcs, srcs') ident = case ident of
Right name
| isInternalName name -> internalHyperlink name
| otherwise -> externalNameHyperlink name
@@ -270,7 +274,7 @@ hyperlink (srcs, srcs') ident = case ident of
externalNameHyperlink name content = case Map.lookup mdl srcs of
Just SrcLocal ->
Html.anchor content
- ! [Html.href $ hypSrcModuleNameUrl mdl name]
+ ! [Html.href $ hypSrcModuleNameUrl' thisModule mdl name]
Just (SrcExternal path) ->
let hyperlinkUrl = hypSrcModuleUrlToNameFormat $ makeHyperlinkUrl path
in Html.anchor content
=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs
=====================================
@@ -9,6 +9,7 @@ module Haddock.Backends.Hyperlinker.Utils
, hypSrcNameUrl
, hypSrcLineUrl
, hypSrcModuleNameUrl
+ , hypSrcModuleNameUrl'
, hypSrcModuleLineUrl
, hypSrcModuleUrlFormat
, hypSrcModuleNameUrlFormat
@@ -71,6 +72,12 @@ hypSrcLineUrl line = "line-" ++ show line
hypSrcModuleNameUrl :: Module -> Name -> String
hypSrcModuleNameUrl mdl name = hypSrcModuleUrl mdl ++ "#" ++ hypSrcNameUrl name
+{-# INLINE hypSrcModuleNameUrl' #-}
+hypSrcModuleNameUrl' :: Module -> Module -> Name -> String
+hypSrcModuleNameUrl' this_mdl mdl name
+ | this_mdl == mdl = "#" ++ hypSrcNameUrl name
+ | otherwise = hypSrcModuleUrl mdl ++ "#" ++ hypSrcNameUrl name
+
{-# INLINE hypSrcModuleLineUrl #-}
hypSrcModuleLineUrl :: Module -> Int -> String
hypSrcModuleLineUrl mdl line = hypSrcModuleUrl mdl ++ "#" ++ hypSrcLineUrl line
=====================================
utils/haddock/hypsrc-test/Main.hs
=====================================
@@ -22,9 +22,9 @@ checkConfig = CheckConfig
where
strip _ = fixPaths . stripAnchors' . stripLinks' . stripIds' . stripFooter
- stripLinks' = stripLinksWhen $ \href -> "#local-" `isPrefixOf` href
- stripAnchors' = stripAnchorsWhen $ \name -> "local-" `isPrefixOf` name
- stripIds' = stripIdsWhen $ \name -> "local-" `isPrefixOf` name
+ stripLinks' = stripLinksWhen $ \href -> "#l-" `isPrefixOf` href
+ stripAnchors' = stripAnchorsWhen $ \name -> "l-" `isPrefixOf` name
+ stripIds' = stripIdsWhen $ \name -> "l-" `isPrefixOf` name
-- One-shot hyperlinked source links to other modules as if they are in another package
fixPaths = fixAttrValueWhen "href" (drop 7) ("../src/" `isPrefixOf`)
=====================================
utils/haddock/hypsrc-test/ref/src/CPP.html
=====================================
@@ -45,7 +45,7 @@
><span id="line-7"
></span
><span class="annot"
- ><a href="CPP.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-type"
>foo</span
></a
@@ -70,7 +70,7 @@
><span class="annottext"
>foo :: String
</span
- ><a href="CPP.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-var hs-var"
>foo</span
></a
@@ -106,7 +106,7 @@
><span id="line-14"
></span
><span class="annot"
- ><a href="CPP.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-type"
>bar</span
></a
@@ -131,7 +131,7 @@
><span class="annottext"
>bar :: String
</span
- ><a href="CPP.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var hs-var"
>bar</span
></a
@@ -192,7 +192,7 @@
><span id="line-26"
></span
><span class="annot"
- ><a href="CPP.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-type"
>baz</span
></a
@@ -217,7 +217,7 @@
><span class="annottext"
>baz :: String
</span
- ><a href="CPP.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var hs-var"
>baz</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Classes.html
=====================================
@@ -48,7 +48,7 @@
> </span
><span id="Foo"
><span class="annot"
- ><a href="Classes.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-var"
>Foo</span
></a
@@ -77,7 +77,7 @@
> </span
><span id="bar"
><span class="annot"
- ><a href="Classes.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-type"
>bar</span
></a
@@ -114,7 +114,7 @@
> </span
><span id="baz"
><span class="annot"
- ><a href="Classes.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-type"
>baz</span
></a
@@ -171,7 +171,7 @@
><span
> </span
><span class="annot"
- ><a href="Classes.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -198,7 +198,7 @@
><span class="annottext"
>bar :: Int -> Int
</span
- ><a href="Classes.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var hs-var hs-var"
>bar</span
></a
@@ -230,7 +230,7 @@ forall a. a -> a
><span class="annottext"
>baz :: Int -> (Int, Int)
</span
- ><a href="Classes.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var hs-var hs-var"
>baz</span
></a
@@ -297,7 +297,7 @@ forall a. a -> a
> </span
><span id=""
><span class="annot"
- ><a href="Classes.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -331,7 +331,7 @@ forall a. a -> a
><span class="annottext"
>bar :: [a] -> Int
</span
- ><a href="Classes.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var hs-var hs-var"
>bar</span
></a
@@ -364,7 +364,7 @@ forall (t :: * -> *) a. Foldable t => t a -> Int
><span class="annottext"
>baz :: Int -> ([a], [a])
</span
- ><a href="Classes.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var hs-var hs-var"
>baz</span
></a
@@ -421,7 +421,7 @@ forall (t :: * -> *) a. Foldable t => t a -> Int
><span
> </span
><span class="annot"
- ><a href="Classes.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -442,7 +442,7 @@ forall (t :: * -> *) a. Foldable t => t a -> Int
> </span
><span id="Foo%27"
><span class="annot"
- ><a href="Classes.html#Foo%27"
+ ><a href="#Foo%27"
><span class="hs-identifier hs-var"
>Foo'</span
></a
@@ -471,7 +471,7 @@ forall (t :: * -> *) a. Foldable t => t a -> Int
> </span
><span id="quux"
><span class="annot"
- ><a href="Classes.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-type"
>quux</span
></a
@@ -524,7 +524,7 @@ forall (t :: * -> *) a. Foldable t => t a -> Int
> </span
><span id=""
><span class="annot"
- ><a href="Classes.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var hs-var"
>quux</span
></a
@@ -572,7 +572,7 @@ forall (t :: * -> *) a. Foldable t => t a -> Int
>[a] -> a
forall a. Foo' a => [a] -> a
</span
- ><a href="Classes.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-var"
>norf</span
></a
@@ -620,7 +620,7 @@ forall a. Foo' a => [a] -> a
> </span
><span id="norf"
><span class="annot"
- ><a href="Classes.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-type"
>norf</span
></a
@@ -663,7 +663,7 @@ forall a. Foo' a => [a] -> a
> </span
><span id=""
><span class="annot"
- ><a href="Classes.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-var hs-var"
>norf</span
></a
@@ -679,7 +679,7 @@ forall a. Foo' a => [a] -> a
>(a, a) -> a
forall a. Foo' a => (a, a) -> a
</span
- ><a href="Classes.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var"
>quux</span
></a
@@ -701,7 +701,7 @@ forall b c a. (b -> c) -> (a -> b) -> a -> c
>Int -> (a, a)
forall a. Foo a => Int -> (a, a)
</span
- ><a href="Classes.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var"
>baz</span
></a
@@ -754,7 +754,7 @@ forall a b. (a -> b) -> [a] -> [b]
>a -> Int
forall a. Foo a => a -> Int
</span
- ><a href="Classes.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var"
>bar</span
></a
@@ -776,7 +776,7 @@ forall a. Foo a => a -> Int
> </span
><span id=""
><span class="annot"
- ><a href="Classes.html#Foo%27"
+ ><a href="#Foo%27"
><span class="hs-identifier hs-type"
>Foo'</span
></a
@@ -804,7 +804,7 @@ forall a. Foo a => a -> Int
><span class="annottext"
>norf :: [Int] -> Int
</span
- ><a href="Classes.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-var hs-var hs-var"
>norf</span
></a
@@ -842,7 +842,7 @@ forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
><span id=""
><span id=""
><span class="annot"
- ><a href="Classes.html#Foo%27"
+ ><a href="#Foo%27"
><span class="hs-identifier hs-type"
>Foo'</span
></a
@@ -877,7 +877,7 @@ forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
><span class="annottext"
>quux :: ([a], [a]) -> [a]
</span
- ><a href="Classes.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var hs-var hs-var"
>quux</span
></a
@@ -928,7 +928,7 @@ forall a. [a] -> [a] -> [a]
> </span
><span id="Plugh"
><span class="annot"
- ><a href="Classes.html#Plugh"
+ ><a href="#Plugh"
><span class="hs-identifier hs-var"
>Plugh</span
></a
@@ -957,7 +957,7 @@ forall a. [a] -> [a] -> [a]
> </span
><span id="plugh"
><span class="annot"
- ><a href="Classes.html#plugh"
+ ><a href="#plugh"
><span class="hs-identifier hs-type"
>plugh</span
></a
@@ -1098,7 +1098,7 @@ forall a. [a] -> [a] -> [a]
><span
> </span
><span class="annot"
- ><a href="Classes.html#Plugh"
+ ><a href="#Plugh"
><span class="hs-identifier hs-type"
>Plugh</span
></a
@@ -1125,7 +1125,7 @@ forall a. [a] -> [a] -> [a]
><span class="annottext"
>plugh :: forall a b. Either a a -> Either b b -> Either (a -> b) (b -> a)
</span
- ><a href="Classes.html#plugh"
+ ><a href="#plugh"
><span class="hs-identifier hs-var hs-var hs-var"
>plugh</span
></a
@@ -1217,7 +1217,7 @@ forall a b. a -> b -> a
><span
> </span
><span class="annot"
- ><a href="Classes.html#plugh"
+ ><a href="#plugh"
><span class="hs-identifier hs-var"
>plugh</span
></a
@@ -1308,7 +1308,7 @@ forall a b. a -> b -> a
><span
> </span
><span class="annot"
- ><a href="Classes.html#plugh"
+ ><a href="#plugh"
><span class="hs-identifier hs-var"
>plugh</span
></a
@@ -1399,7 +1399,7 @@ forall a b. a -> b -> a
><span
> </span
><span class="annot"
- ><a href="Classes.html#plugh"
+ ><a href="#plugh"
><span class="hs-identifier hs-var"
>plugh</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Constructors.html
=====================================
@@ -48,7 +48,7 @@
> </span
><span id="Foo"
><span class="annot"
- ><a href="Constructors.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-var"
>Foo</span
></a
@@ -67,7 +67,7 @@
> </span
><span id="Bar"
><span class="annot"
- ><a href="Constructors.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -86,7 +86,7 @@
> </span
><span id="Baz"
><span class="annot"
- ><a href="Constructors.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -105,7 +105,7 @@
> </span
><span id="Quux"
><span class="annot"
- ><a href="Constructors.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-var"
>Quux</span
></a
@@ -114,7 +114,7 @@
><span
> </span
><span class="annot"
- ><a href="Constructors.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -141,7 +141,7 @@
> </span
><span id="Norf"
><span class="annot"
- ><a href="Constructors.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-var"
>Norf</span
></a
@@ -155,7 +155,7 @@
> </span
><span id="Norf"
><span class="annot"
- ><a href="Constructors.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-var"
>Norf</span
></a
@@ -166,7 +166,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Constructors.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -178,7 +178,7 @@
><span class="hs-special"
>[</span
><span class="annot"
- ><a href="Constructors.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -190,7 +190,7 @@
><span
> </span
><span class="annot"
- ><a href="Constructors.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -213,7 +213,7 @@
><span id="line-13"
></span
><span class="annot"
- ><a href="Constructors.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-type"
>bar</span
></a
@@ -223,7 +223,7 @@
><span
> </span
><span class="annot"
- ><a href="Constructors.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-type"
>baz</span
></a
@@ -233,7 +233,7 @@
><span
> </span
><span class="annot"
- ><a href="Constructors.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-type"
>quux</span
></a
@@ -245,7 +245,7 @@
><span
> </span
><span class="annot"
- ><a href="Constructors.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -260,7 +260,7 @@
><span class="annottext"
>bar :: Foo
</span
- ><a href="Constructors.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var hs-var"
>bar</span
></a
@@ -276,7 +276,7 @@
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -291,7 +291,7 @@
><span class="annottext"
>baz :: Foo
</span
- ><a href="Constructors.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var hs-var"
>baz</span
></a
@@ -307,7 +307,7 @@
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -322,7 +322,7 @@
><span class="annottext"
>quux :: Foo
</span
- ><a href="Constructors.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var hs-var"
>quux</span
></a
@@ -338,7 +338,7 @@
><span class="annottext"
>Foo -> Int -> Foo
</span
- ><a href="Constructors.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-var"
>Quux</span
></a
@@ -349,7 +349,7 @@
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var"
>quux</span
></a
@@ -379,7 +379,7 @@
><span id="line-19"
></span
><span class="annot"
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-type"
>unfoo</span
></a
@@ -391,7 +391,7 @@
><span
> </span
><span class="annot"
- ><a href="Constructors.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -416,7 +416,7 @@
><span class="annottext"
>unfoo :: Foo -> Int
</span
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var hs-var"
>unfoo</span
></a
@@ -428,7 +428,7 @@
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -452,7 +452,7 @@
><span id="line-21"
></span
><span class="annot"
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var"
>unfoo</span
></a
@@ -463,7 +463,7 @@
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -487,7 +487,7 @@
><span id="line-22"
></span
><span class="annot"
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var"
>unfoo</span
></a
@@ -497,7 +497,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Constructors.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -580,7 +580,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo -> Int
</span
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var"
>unfoo</span
></a
@@ -612,7 +612,7 @@ forall a. Num a => a -> a -> a
><span id="line-25"
></span
><span class="annot"
- ><a href="Constructors.html#unnorf"
+ ><a href="#unnorf"
><span class="hs-identifier hs-type"
>unnorf</span
></a
@@ -624,7 +624,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Constructors.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-type"
>Norf</span
></a
@@ -638,7 +638,7 @@ forall a. Num a => a -> a -> a
><span class="hs-special"
>[</span
><span class="annot"
- ><a href="Constructors.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -655,7 +655,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>unnorf :: Norf -> [Foo]
</span
- ><a href="Constructors.html#unnorf"
+ ><a href="#unnorf"
><span class="hs-identifier hs-var hs-var"
>unnorf</span
></a
@@ -666,7 +666,7 @@ forall a. Num a => a -> a -> a
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Constructors.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-type"
>Norf</span
></a
@@ -679,7 +679,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -707,7 +707,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -737,7 +737,7 @@ forall a. Num a => a -> a -> a
><span id="line-27"
></span
><span class="annot"
- ><a href="Constructors.html#unnorf"
+ ><a href="#unnorf"
><span class="hs-identifier hs-var"
>unnorf</span
></a
@@ -747,7 +747,7 @@ forall a. Num a => a -> a -> a
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Constructors.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-type"
>Norf</span
></a
@@ -760,7 +760,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -788,7 +788,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo
</span
- ><a href="Constructors.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -828,7 +828,7 @@ forall a. [a] -> [a]
><span id="line-28"
></span
><span class="annot"
- ><a href="Constructors.html#unnorf"
+ ><a href="#unnorf"
><span class="hs-identifier hs-var"
>unnorf</span
></a
@@ -872,7 +872,7 @@ forall a. HasCallStack => a
><span id="line-31"
></span
><span class="annot"
- ><a href="Constructors.html#unnorf%27"
+ ><a href="#unnorf%27"
><span class="hs-identifier hs-type"
>unnorf'</span
></a
@@ -884,7 +884,7 @@ forall a. HasCallStack => a
><span
> </span
><span class="annot"
- ><a href="Constructors.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-type"
>Norf</span
></a
@@ -909,7 +909,7 @@ forall a. HasCallStack => a
><span class="annottext"
>unnorf' :: Norf -> Int
</span
- ><a href="Constructors.html#unnorf%27"
+ ><a href="#unnorf%27"
><span class="hs-identifier hs-var hs-var"
>unnorf'</span
></a
@@ -933,7 +933,7 @@ forall a. HasCallStack => a
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Constructors.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-type"
>Norf</span
></a
@@ -958,7 +958,7 @@ forall a. HasCallStack => a
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Constructors.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -1018,7 +1018,7 @@ forall a. HasCallStack => a
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Constructors.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -1108,7 +1108,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo -> Int
</span
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var"
>unfoo</span
></a
@@ -1206,7 +1206,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo -> Int
</span
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var"
>unfoo</span
></a
@@ -1238,7 +1238,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo -> Int
</span
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var"
>unfoo</span
></a
@@ -1270,7 +1270,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Foo -> Int
</span
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var"
>unfoo</span
></a
@@ -1345,7 +1345,7 @@ forall a b. (a -> b) -> [a] -> [b]
><span class="annottext"
>Foo -> Int
</span
- ><a href="Constructors.html#unfoo"
+ ><a href="#unfoo"
><span class="hs-identifier hs-var"
>unfoo</span
></a
@@ -1366,7 +1366,7 @@ forall b c a. (b -> c) -> (a -> b) -> a -> c
><span class="annottext"
>Norf -> [Foo]
</span
- ><a href="Constructors.html#unnorf"
+ ><a href="#unnorf"
><span class="hs-identifier hs-var"
>unnorf</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Identifiers.html
=====================================
@@ -43,7 +43,7 @@
><span id="line-5"
></span
><span class="annot"
- ><a href="Identifiers.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-type"
>foo</span
></a
@@ -53,7 +53,7 @@
><span
> </span
><span class="annot"
- ><a href="Identifiers.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-type"
>bar</span
></a
@@ -63,7 +63,7 @@
><span
> </span
><span class="annot"
- ><a href="Identifiers.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-type"
>baz</span
></a
@@ -108,7 +108,7 @@
><span class="annottext"
>foo :: Int -> Int -> Int
</span
- ><a href="Identifiers.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-var hs-var"
>foo</span
></a
@@ -192,7 +192,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="Identifiers.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var"
>bar</span
></a
@@ -271,7 +271,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>bar :: Int -> Int -> Int
</span
- ><a href="Identifiers.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var hs-var"
>bar</span
></a
@@ -355,7 +355,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="Identifiers.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var"
>baz</span
></a
@@ -434,7 +434,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>baz :: Int -> Int -> Int
</span
- ><a href="Identifiers.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var hs-var"
>baz</span
></a
@@ -576,7 +576,7 @@ forall a. Num a => a -> a -> a
><span id="line-10"
></span
><span class="annot"
- ><a href="Identifiers.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-type"
>quux</span
></a
@@ -611,7 +611,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>quux :: Int -> Int
</span
- ><a href="Identifiers.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var hs-var"
>quux</span
></a
@@ -640,7 +640,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="Identifiers.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-var"
>foo</span
></a
@@ -653,7 +653,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="Identifiers.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var"
>bar</span
></a
@@ -690,7 +690,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="Identifiers.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var"
>bar</span
></a
@@ -730,7 +730,7 @@ forall a. Num a => a -> a -> a
><span id="line-13"
></span
><span class="annot"
- ><a href="Identifiers.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-type"
>norf</span
></a
@@ -785,7 +785,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>norf :: Int -> Int -> Int -> Int
</span
- ><a href="Identifiers.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-var hs-var"
>norf</span
></a
@@ -879,7 +879,7 @@ forall a. Ord a => a -> a -> Bool
><span class="annottext"
>Int -> Int
</span
- ><a href="Identifiers.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var"
>quux</span
></a
@@ -944,7 +944,7 @@ forall a. Ord a => a -> a -> Bool
><span class="annottext"
>Int -> Int
</span
- ><a href="Identifiers.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var"
>quux</span
></a
@@ -1009,7 +1009,7 @@ forall a. Ord a => a -> a -> Bool
><span class="annottext"
>Int -> Int
</span
- ><a href="Identifiers.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var"
>quux</span
></a
@@ -1053,7 +1053,7 @@ forall a. Ord a => a -> a -> Bool
><span class="annottext"
>Int -> Int -> Int -> Int
</span
- ><a href="Identifiers.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-var"
>norf</span
></a
@@ -1125,7 +1125,7 @@ forall a. Ord a => a -> a -> Bool
><span id="line-21"
></span
><span class="annot"
- ><a href="Identifiers.html#main"
+ ><a href="#main"
><span class="hs-identifier hs-type"
>main</span
></a
@@ -1156,7 +1156,7 @@ forall a. Ord a => a -> a -> Bool
><span class="annottext"
>main :: IO ()
</span
- ><a href="Identifiers.html#main"
+ ><a href="#main"
><span class="hs-identifier hs-var hs-var"
>main</span
></a
@@ -1220,7 +1220,7 @@ forall a b. (a -> b) -> a -> b
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="Identifiers.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-var"
>foo</span
></a
@@ -1297,7 +1297,7 @@ forall a b. (a -> b) -> a -> b
><span class="annottext"
>Int -> Int
</span
- ><a href="Identifiers.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var"
>quux</span
></a
@@ -1363,7 +1363,7 @@ forall a b. (a -> b) -> a -> b
><span class="annottext"
>Int -> Int -> Int -> Int
</span
- ><a href="Identifiers.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-var"
>Identifiers.norf</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/LinkingIdentifiers.html
=====================================
@@ -73,7 +73,7 @@
><span id="line-9"
></span
><span class="annot"
- ><a href="LinkingIdentifiers.html#ident"
+ ><a href="#ident"
><span class="hs-identifier hs-type"
>ident</span
></a
@@ -131,7 +131,7 @@
><span class="annottext"
>ident :: Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#ident"
+ ><a href="#ident"
><span class="hs-operator hs-var hs-var"
>`ident`</span
></a
@@ -169,7 +169,7 @@
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#ident"
+ ><a href="#ident"
><span class="hs-operator hs-var"
>`ident`</span
></a
@@ -214,7 +214,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#ident"
+ ><a href="#ident"
><span class="hs-operator hs-var"
>`LinkingIdentifiers.ident`</span
></a
@@ -236,7 +236,7 @@ forall a. Num a => a -> a -> a
><span id="line-11"
></span
><span class="annot"
- ><a href="LinkingIdentifiers.html#ident"
+ ><a href="#ident"
><span class="hs-identifier hs-var"
>ident</span
></a
@@ -273,7 +273,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#ident"
+ ><a href="#ident"
><span class="hs-identifier hs-var"
>ident</span
></a
@@ -314,7 +314,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#ident"
+ ><a href="#ident"
><span class="hs-identifier hs-var"
>LinkingIdentifiers.ident</span
></a
@@ -350,7 +350,7 @@ forall a. Num a => a -> a -> a
><span id="line-13"
></span
><span class="annot"
- ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
+ ><a href="#%2B%2B%3A%2B%2B"
><span class="hs-operator hs-type"
>(++:++)</span
></a
@@ -408,7 +408,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>++:++ :: Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
+ ><a href="#%2B%2B%3A%2B%2B"
><span class="hs-operator hs-var hs-var"
>++:++</span
></a
@@ -446,7 +446,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
+ ><a href="#%2B%2B%3A%2B%2B"
><span class="hs-operator hs-var"
>++:++</span
></a
@@ -491,7 +491,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
+ ><a href="#%2B%2B%3A%2B%2B"
><span class="hs-operator hs-var"
>LinkingIdentifiers.++:++</span
></a
@@ -513,7 +513,7 @@ forall a. Num a => a -> a -> a
><span id="line-15"
></span
><span class="annot"
- ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
+ ><a href="#%2B%2B%3A%2B%2B"
><span class="hs-operator hs-var"
>(++:++)</span
></a
@@ -550,7 +550,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
+ ><a href="#%2B%2B%3A%2B%2B"
><span class="hs-operator hs-var"
>(++:++)</span
></a
@@ -591,7 +591,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>Int -> Int -> Int
</span
- ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
+ ><a href="#%2B%2B%3A%2B%2B"
><span class="hs-operator hs-var"
>(LinkingIdentifiers.++:++)</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Literals.html
=====================================
@@ -43,7 +43,7 @@
><span id="line-5"
></span
><span class="annot"
- ><a href="Literals.html#str"
+ ><a href="#str"
><span class="hs-identifier hs-type"
>str</span
></a
@@ -68,7 +68,7 @@
><span class="annottext"
>str :: String
</span
- ><a href="Literals.html#str"
+ ><a href="#str"
><span class="hs-identifier hs-var hs-var"
>str</span
></a
@@ -99,7 +99,7 @@
></span
><span id=""
><span class="annot"
- ><a href="Literals.html#num"
+ ><a href="#num"
><span class="hs-identifier hs-type"
>num</span
></a
@@ -145,7 +145,7 @@
><span class="annottext"
>num :: forall a. Num a => a
</span
- ><a href="Literals.html#num"
+ ><a href="#num"
><span class="hs-identifier hs-var hs-var"
>num</span
></a
@@ -252,7 +252,7 @@ forall a. Num a => a -> a -> a
></span
><span id=""
><span class="annot"
- ><a href="Literals.html#frac"
+ ><a href="#frac"
><span class="hs-identifier hs-type"
>frac</span
></a
@@ -298,7 +298,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>frac :: forall a. Fractional a => a
</span
- ><a href="Literals.html#frac"
+ ><a href="#frac"
><span class="hs-identifier hs-var hs-var"
>frac</span
></a
@@ -329,7 +329,7 @@ forall a. Num a => a -> a -> a
></span
><span id=""
><span class="annot"
- ><a href="Literals.html#list"
+ ><a href="#list"
><span class="hs-identifier hs-type"
>list</span
></a
@@ -373,7 +373,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>list :: forall a. [[[[a]]]]
</span
- ><a href="Literals.html#list"
+ ><a href="#list"
><span class="hs-identifier hs-var hs-var"
>list</span
></a
@@ -432,7 +432,7 @@ forall a. Num a => a -> a -> a
><span id="line-17"
></span
><span class="annot"
- ><a href="Literals.html#pair"
+ ><a href="#pair"
><span class="hs-identifier hs-type"
>pair</span
></a
@@ -497,7 +497,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>pair :: ((), ((), (), ()), ())
</span
- ><a href="Literals.html#pair"
+ ><a href="#pair"
><span class="hs-identifier hs-var hs-var"
>pair</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Operators.html
=====================================
@@ -39,7 +39,7 @@
></span
><span id=""
><span class="annot"
- ><a href="Operators.html#%2B%2B%2B"
+ ><a href="#%2B%2B%2B"
><span class="hs-operator hs-type"
>(+++)</span
></a
@@ -116,7 +116,7 @@
><span class="annottext"
>+++ :: forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%2B%2B%2B"
+ ><a href="#%2B%2B%2B"
><span class="hs-operator hs-var hs-var"
>+++</span
></a
@@ -204,7 +204,7 @@ forall a. [a] -> [a] -> [a]
></span
><span id=""
><span class="annot"
- ><a href="Operators.html#%24%24%24"
+ ><a href="#%24%24%24"
><span class="hs-operator hs-type"
>($$$)</span
></a
@@ -281,7 +281,7 @@ forall a. [a] -> [a] -> [a]
><span class="annottext"
>$$$ :: forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%24%24%24"
+ ><a href="#%24%24%24"
><span class="hs-operator hs-var hs-var"
>$$$</span
></a
@@ -322,7 +322,7 @@ forall a. [a] -> [a] -> [a]
>[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%2B%2B%2B"
+ ><a href="#%2B%2B%2B"
><span class="hs-operator hs-var"
>+++</span
></a
@@ -350,7 +350,7 @@ forall a. [a] -> [a] -> [a]
></span
><span id=""
><span class="annot"
- ><a href="Operators.html#%2A%2A%2A"
+ ><a href="#%2A%2A%2A"
><span class="hs-operator hs-type"
>(***)</span
></a
@@ -414,7 +414,7 @@ forall a. [a] -> [a] -> [a]
><span class="annottext"
>*** :: forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%2A%2A%2A"
+ ><a href="#%2A%2A%2A"
><span class="hs-operator hs-var hs-var"
>(***)</span
></a
@@ -460,7 +460,7 @@ forall a. [a] -> [a] -> [a]
><span id="line-12"
></span
><span class="annot"
- ><a href="Operators.html#%2A%2A%2A"
+ ><a href="#%2A%2A%2A"
><span class="hs-operator hs-var"
>(***)</span
></a
@@ -528,7 +528,7 @@ forall a. [a] -> [a] -> [a]
>[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%2B%2B%2B"
+ ><a href="#%2B%2B%2B"
><span class="hs-operator hs-var"
>+++</span
></a
@@ -553,7 +553,7 @@ forall a. [a] -> [a] -> [a]
>[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%2A%2A%2A"
+ ><a href="#%2A%2A%2A"
><span class="hs-operator hs-var"
>***</span
></a
@@ -583,7 +583,7 @@ forall a. [a] -> [a] -> [a]
></span
><span id=""
><span class="annot"
- ><a href="Operators.html#%2A%2F%5C%2A"
+ ><a href="#%2A%2F%5C%2A"
><span class="hs-operator hs-type"
>(*/\*)</span
></a
@@ -664,7 +664,7 @@ forall a. [a] -> [a] -> [a]
><span class="annottext"
>*/\* :: forall a. [[a]] -> [a] -> [a]
</span
- ><a href="Operators.html#%2A%2F%5C%2A"
+ ><a href="#%2A%2F%5C%2A"
><span class="hs-operator hs-var hs-var"
>*/\*</span
></a
@@ -706,7 +706,7 @@ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
>[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%2A%2A%2A"
+ ><a href="#%2A%2A%2A"
><span class="hs-operator hs-var"
>***</span
></a
@@ -747,7 +747,7 @@ forall a. [a] -> [a] -> [a]
></span
><span id=""
><span class="annot"
- ><a href="Operators.html#%2A%2A%2F%5C%2A%2A"
+ ><a href="#%2A%2A%2F%5C%2A%2A"
><span class="hs-operator hs-type"
>(**/\**)</span
></a
@@ -836,7 +836,7 @@ forall a. [a] -> [a] -> [a]
><span class="annottext"
>**/\** :: forall a. [[a]] -> [[a]] -> [[a]]
</span
- ><a href="Operators.html#%2A%2A%2F%5C%2A%2A"
+ ><a href="#%2A%2A%2F%5C%2A%2A"
><span class="hs-operator hs-var hs-var"
>**/\**</span
></a
@@ -876,7 +876,7 @@ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
>[[a]] -> [a] -> [a]
forall a. [[a]] -> [a] -> [a]
</span
- ><a href="Operators.html#%2A%2F%5C%2A"
+ ><a href="#%2A%2F%5C%2A"
><span class="hs-operator hs-var"
>(*/\*)</span
></a
@@ -901,7 +901,7 @@ forall a. [[a]] -> [a] -> [a]
>[[a]] -> [[a]] -> [[a]]
forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%2B%2B%2B"
+ ><a href="#%2B%2B%2B"
><span class="hs-operator hs-var"
>+++</span
></a
@@ -939,7 +939,7 @@ forall a. [a] -> [a] -> [a]
>[[a]] -> [[a]] -> [[a]]
forall a. [a] -> [a] -> [a]
</span
- ><a href="Operators.html#%24%24%24"
+ ><a href="#%24%24%24"
><span class="hs-operator hs-var"
>$$$</span
></a
@@ -971,7 +971,7 @@ forall a. [a] -> [a] -> [a]
><span id=""
><span id=""
><span class="annot"
- ><a href="Operators.html#%23.%23"
+ ><a href="#%23.%23"
><span class="hs-operator hs-type"
>(#.#)</span
></a
@@ -1068,7 +1068,7 @@ forall a. [a] -> [a] -> [a]
><span class="annottext"
>#.# :: forall a b c. a -> b -> c -> (a, b)
</span
- ><a href="Operators.html#%23.%23"
+ ><a href="#%23.%23"
><span class="hs-operator hs-var hs-var"
>#.#</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Polymorphism.html
=====================================
@@ -68,7 +68,7 @@
></span
><span id=""
><span class="annot"
- ><a href="Polymorphism.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-type"
>foo</span
></a
@@ -120,7 +120,7 @@
><span class="annottext"
>foo :: forall a. a -> a -> a
</span
- ><a href="Polymorphism.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-var hs-var"
>foo</span
></a
@@ -151,7 +151,7 @@ forall a. HasCallStack => a
><span id="line-12"
></span
><span class="annot"
- ><a href="Polymorphism.html#foo%27"
+ ><a href="#foo%27"
><span class="hs-identifier hs-type"
>foo'</span
></a
@@ -218,7 +218,7 @@ forall a. HasCallStack => a
><span class="annottext"
>foo' :: forall a. a -> a -> a
</span
- ><a href="Polymorphism.html#foo%27"
+ ><a href="#foo%27"
><span class="hs-identifier hs-var hs-var"
>foo'</span
></a
@@ -251,7 +251,7 @@ forall a. HasCallStack => a
><span id=""
><span id=""
><span class="annot"
- ><a href="Polymorphism.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-type"
>bar</span
></a
@@ -318,7 +318,7 @@ forall a. HasCallStack => a
><span class="annottext"
>bar :: forall a b. a -> b -> (a, b)
</span
- ><a href="Polymorphism.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var hs-var"
>bar</span
></a
@@ -349,7 +349,7 @@ forall a. HasCallStack => a
><span id="line-18"
></span
><span class="annot"
- ><a href="Polymorphism.html#bar%27"
+ ><a href="#bar%27"
><span class="hs-identifier hs-type"
>bar'</span
></a
@@ -440,7 +440,7 @@ forall a. HasCallStack => a
><span class="annottext"
>bar' :: forall a b. a -> b -> (a, b)
</span
- ><a href="Polymorphism.html#bar%27"
+ ><a href="#bar%27"
><span class="hs-identifier hs-var hs-var"
>bar'</span
></a
@@ -473,7 +473,7 @@ forall a. HasCallStack => a
><span id=""
><span id=""
><span class="annot"
- ><a href="Polymorphism.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-type"
>baz</span
></a
@@ -570,7 +570,7 @@ forall a. HasCallStack => a
><span class="annottext"
>baz :: forall a b. a -> (a -> [a -> a] -> b) -> b
</span
- ><a href="Polymorphism.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var hs-var"
>baz</span
></a
@@ -601,7 +601,7 @@ forall a. HasCallStack => a
><span id="line-24"
></span
><span class="annot"
- ><a href="Polymorphism.html#baz%27"
+ ><a href="#baz%27"
><span class="hs-identifier hs-type"
>baz'</span
></a
@@ -722,7 +722,7 @@ forall a. HasCallStack => a
><span class="annottext"
>baz' :: forall a b. a -> (a -> [a -> a] -> b) -> b
</span
- ><a href="Polymorphism.html#baz%27"
+ ><a href="#baz%27"
><span class="hs-identifier hs-var hs-var"
>baz'</span
></a
@@ -754,7 +754,7 @@ forall a. HasCallStack => a
></span
><span id=""
><span class="annot"
- ><a href="Polymorphism.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-type"
>quux</span
></a
@@ -838,7 +838,7 @@ forall a. HasCallStack => a
><span class="annottext"
>quux :: forall a. a -> (forall a. a -> a) -> a
</span
- ><a href="Polymorphism.html#quux"
+ ><a href="#quux"
><span class="hs-identifier hs-var hs-var"
>quux</span
></a
@@ -908,7 +908,7 @@ forall a. a -> a
><span id="line-30"
></span
><span class="annot"
- ><a href="Polymorphism.html#quux%27"
+ ><a href="#quux%27"
><span class="hs-identifier hs-type"
>quux'</span
></a
@@ -1007,7 +1007,7 @@ forall a. a -> a
><span class="annottext"
>quux' :: forall a. a -> (forall a. a -> a) -> a
</span
- ><a href="Polymorphism.html#quux%27"
+ ><a href="#quux%27"
><span class="hs-identifier hs-var hs-var"
>quux'</span
></a
@@ -1083,7 +1083,7 @@ forall a. a -> a
></span
><span id=""
><span class="annot"
- ><a href="Polymorphism.html#num"
+ ><a href="#num"
><span class="hs-identifier hs-type"
>num</span
></a
@@ -1153,7 +1153,7 @@ forall a. a -> a
><span class="annottext"
>num :: forall a. Num a => a -> a -> a
</span
- ><a href="Polymorphism.html#num"
+ ><a href="#num"
><span class="hs-identifier hs-var hs-var"
>num</span
></a
@@ -1184,7 +1184,7 @@ forall a. HasCallStack => a
><span id="line-37"
></span
><span class="annot"
- ><a href="Polymorphism.html#num%27"
+ ><a href="#num%27"
><span class="hs-identifier hs-type"
>num'</span
></a
@@ -1269,7 +1269,7 @@ forall a. HasCallStack => a
><span class="annottext"
>num' :: forall a. Num a => a -> a -> a
</span
- ><a href="Polymorphism.html#num%27"
+ ><a href="#num%27"
><span class="hs-identifier hs-var hs-var"
>num'</span
></a
@@ -1302,7 +1302,7 @@ forall a. HasCallStack => a
><span id=""
><span id=""
><span class="annot"
- ><a href="Polymorphism.html#eq"
+ ><a href="#eq"
><span class="hs-identifier hs-type"
>eq</span
></a
@@ -1415,7 +1415,7 @@ forall a. HasCallStack => a
><span class="annottext"
>eq :: forall a b. (Eq a, Eq b) => [a] -> [b] -> (a, b)
</span
- ><a href="Polymorphism.html#eq"
+ ><a href="#eq"
><span class="hs-identifier hs-var hs-var"
>eq</span
></a
@@ -1446,7 +1446,7 @@ forall a. HasCallStack => a
><span id="line-43"
></span
><span class="annot"
- ><a href="Polymorphism.html#eq%27"
+ ><a href="#eq%27"
><span class="hs-identifier hs-type"
>eq'</span
></a
@@ -1583,7 +1583,7 @@ forall a. HasCallStack => a
><span class="annottext"
>eq' :: forall a b. (Eq a, Eq b) => [a] -> [b] -> (a, b)
</span
- ><a href="Polymorphism.html#eq%27"
+ ><a href="#eq%27"
><span class="hs-identifier hs-var hs-var"
>eq'</span
></a
@@ -1616,7 +1616,7 @@ forall a. HasCallStack => a
><span id=""
><span id=""
><span class="annot"
- ><a href="Polymorphism.html#mon"
+ ><a href="#mon"
><span class="hs-identifier hs-type"
>mon</span
></a
@@ -1707,7 +1707,7 @@ forall a. HasCallStack => a
><span class="annottext"
>mon :: forall (m :: * -> *) a. Monad m => (a -> m a) -> m a
</span
- ><a href="Polymorphism.html#mon"
+ ><a href="#mon"
><span class="hs-identifier hs-var hs-var"
>mon</span
></a
@@ -1738,7 +1738,7 @@ forall a. HasCallStack => a
><span id="line-49"
></span
><span class="annot"
- ><a href="Polymorphism.html#mon%27"
+ ><a href="#mon%27"
><span class="hs-identifier hs-type"
>mon'</span
></a
@@ -1853,7 +1853,7 @@ forall a. HasCallStack => a
><span class="annottext"
>mon' :: forall (m :: * -> *) a. Monad m => (a -> m a) -> m a
</span
- ><a href="Polymorphism.html#mon%27"
+ ><a href="#mon%27"
><span class="hs-identifier hs-var hs-var"
>mon'</span
></a
@@ -1890,7 +1890,7 @@ forall a. HasCallStack => a
></span
><span id=""
><span class="annot"
- ><a href="Polymorphism.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-type"
>norf</span
></a
@@ -1992,7 +1992,7 @@ forall a. HasCallStack => a
><span class="annottext"
>norf :: forall a. a -> (forall a. Ord a => a -> a) -> a
</span
- ><a href="Polymorphism.html#norf"
+ ><a href="#norf"
><span class="hs-identifier hs-var hs-var"
>norf</span
></a
@@ -2050,7 +2050,7 @@ forall a. HasCallStack => a
><span id="line-56"
></span
><span class="annot"
- ><a href="Polymorphism.html#norf%27"
+ ><a href="#norf%27"
><span class="hs-identifier hs-type"
>norf'</span
></a
@@ -2167,7 +2167,7 @@ forall a. HasCallStack => a
><span class="annottext"
>norf' :: forall a. a -> (forall a. Ord a => a -> a) -> a
</span
- ><a href="Polymorphism.html#norf%27"
+ ><a href="#norf%27"
><span class="hs-identifier hs-var hs-var"
>norf'</span
></a
@@ -2230,7 +2230,7 @@ forall a. HasCallStack => a
><span id="line-60"
></span
><span class="annot"
- ><a href="Polymorphism.html#plugh"
+ ><a href="#plugh"
><span class="hs-identifier hs-type"
>plugh</span
></a
@@ -2285,7 +2285,7 @@ forall a. HasCallStack => a
><span class="annottext"
>plugh :: forall a. a -> a
</span
- ><a href="Polymorphism.html#plugh"
+ ><a href="#plugh"
><span class="hs-identifier hs-var hs-var"
>plugh</span
></a
@@ -2342,7 +2342,7 @@ forall a. HasCallStack => a
><span id="line-63"
></span
><span class="annot"
- ><a href="Polymorphism.html#thud"
+ ><a href="#thud"
><span class="hs-identifier hs-type"
>thud</span
></a
@@ -2449,7 +2449,7 @@ forall a. HasCallStack => a
><span class="annottext"
>thud :: forall a b. (a -> b) -> a -> (a, b)
</span
- ><a href="Polymorphism.html#thud"
+ ><a href="#thud"
><span class="hs-identifier hs-var hs-var"
>thud</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/PositionPragmas.html
=====================================
@@ -57,7 +57,7 @@
><span id="line-9"
></span
><span class="annot"
- ><a href="PositionPragmas.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-type"
>foo</span
></a
@@ -82,7 +82,7 @@
><span class="annottext"
>foo :: String
</span
- ><a href="PositionPragmas.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-var hs-var"
>foo</span
></a
@@ -98,7 +98,7 @@
><span class="annottext"
>String
</span
- ><a href="PositionPragmas.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var"
>bar</span
></a
@@ -126,7 +126,7 @@
><span id="line-24"
></span
><span class="annot"
- ><a href="PositionPragmas.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-type"
>bar</span
></a
@@ -151,7 +151,7 @@
><span class="annottext"
>bar :: String
</span
- ><a href="PositionPragmas.html#bar"
+ ><a href="#bar"
><span class="hs-identifier hs-var hs-var"
>bar</span
></a
@@ -167,7 +167,7 @@
><span class="annottext"
>String
</span
- ><a href="PositionPragmas.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-var"
>foo</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
=====================================
@@ -30,7 +30,7 @@
><span
> </span
><span class="annot"
- ><a href="Quasiquoter.html#string"
+ ><a href="#string"
><span class="hs-identifier"
>string</span
></a
@@ -94,7 +94,7 @@
><span id="line-8"
></span
><span class="annot"
- ><a href="Quasiquoter.html#string"
+ ><a href="#string"
><span class="hs-identifier hs-type"
>string</span
></a
@@ -119,7 +119,7 @@
><span class="annottext"
>string :: QuasiQuoter
</span
- ><a href="Quasiquoter.html#string"
+ ><a href="#string"
><span class="hs-identifier hs-var hs-var"
>string</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Records.html
=====================================
@@ -72,7 +72,7 @@
> </span
><span id="Point"
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-var"
>Point</span
></a
@@ -86,7 +86,7 @@
> </span
><span id="Point"
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-var"
>Point</span
></a
@@ -108,7 +108,7 @@
><span class="annottext"
>Point -> Int
</span
- ><a href="Records.html#x"
+ ><a href="#x"
><span class="hs-identifier hs-var hs-var"
>x</span
></a
@@ -142,7 +142,7 @@
><span class="annottext"
>Point -> Int
</span
- ><a href="Records.html#y"
+ ><a href="#y"
><span class="hs-identifier hs-var hs-var"
>y</span
></a
@@ -185,7 +185,7 @@
><span id="line-15"
></span
><span class="annot"
- ><a href="Records.html#point"
+ ><a href="#point"
><span class="hs-identifier hs-type"
>point</span
></a
@@ -217,7 +217,7 @@
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -232,7 +232,7 @@
><span class="annottext"
>point :: Int -> Int -> Point
</span
- ><a href="Records.html#point"
+ ><a href="#point"
><span class="hs-identifier hs-var hs-var"
>point</span
></a
@@ -271,7 +271,7 @@
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -286,7 +286,7 @@
><span class="annottext"
>x :: Int
</span
- ><a href="Records.html#x"
+ ><a href="#x"
><span class="hs-identifier hs-var"
>x</span
></a
@@ -314,7 +314,7 @@
><span class="annottext"
>y :: Int
</span
- ><a href="Records.html#y"
+ ><a href="#y"
><span class="hs-identifier hs-var"
>y</span
></a
@@ -354,7 +354,7 @@
><span id="line-19"
></span
><span class="annot"
- ><a href="Records.html#lengthSqr"
+ ><a href="#lengthSqr"
><span class="hs-identifier hs-type"
>lengthSqr</span
></a
@@ -366,7 +366,7 @@
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -391,7 +391,7 @@
><span class="annottext"
>lengthSqr :: Point -> Int
</span
- ><a href="Records.html#lengthSqr"
+ ><a href="#lengthSqr"
><span class="hs-identifier hs-var hs-var"
>lengthSqr</span
></a
@@ -402,7 +402,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -417,7 +417,7 @@
><span class="annottext"
>x :: Point -> Int
</span
- ><a href="Records.html#x"
+ ><a href="#x"
><span class="hs-identifier hs-var"
>x</span
></a
@@ -447,7 +447,7 @@
><span class="annottext"
>y :: Point -> Int
</span
- ><a href="Records.html#y"
+ ><a href="#y"
><span class="hs-identifier hs-var"
>y</span
></a
@@ -564,7 +564,7 @@ forall a. Num a => a -> a -> a
><span id="line-22"
></span
><span class="annot"
- ><a href="Records.html#lengthSqr%27"
+ ><a href="#lengthSqr%27"
><span class="hs-identifier hs-type"
>lengthSqr'</span
></a
@@ -576,7 +576,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -601,7 +601,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>lengthSqr' :: Point -> Int
</span
- ><a href="Records.html#lengthSqr%27"
+ ><a href="#lengthSqr%27"
><span class="hs-identifier hs-var hs-var"
>lengthSqr'</span
></a
@@ -612,7 +612,7 @@ forall a. Num a => a -> a -> a
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -630,7 +630,7 @@ forall a. Num a => a -> a -> a
x :: Point -> Int
x :: Int
</span
- ><a href="Records.html#x"
+ ><a href="#x"
><span class="hs-identifier hs-var hs-var"
>x</span
></a
@@ -647,7 +647,7 @@ x :: Int
y :: Point -> Int
y :: Int
</span
- ><a href="Records.html#y"
+ ><a href="#y"
><span class="hs-identifier hs-var hs-var"
>y</span
></a
@@ -753,7 +753,7 @@ forall a. Num a => a -> a -> a
><span id="line-26"
></span
><span class="annot"
- ><a href="Records.html#translateX"
+ ><a href="#translateX"
><span class="hs-identifier hs-type"
>translateX</span
></a
@@ -763,7 +763,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#translateY"
+ ><a href="#translateY"
><span class="hs-identifier hs-type"
>translateY</span
></a
@@ -775,7 +775,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -797,7 +797,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -812,7 +812,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>translateX :: Point -> Int -> Point
</span
- ><a href="Records.html#translateX"
+ ><a href="#translateX"
><span class="hs-identifier hs-var hs-var"
>translateX</span
></a
@@ -866,7 +866,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#x"
+ ><a href="#x"
><span class="hs-identifier hs-var"
>x</span
></a
@@ -878,7 +878,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#x"
+ ><a href="#x"
><span class="hs-identifier hs-var"
>x</span
></a
@@ -919,7 +919,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>translateY :: Point -> Int -> Point
</span
- ><a href="Records.html#translateY"
+ ><a href="#translateY"
><span class="hs-identifier hs-var hs-var"
>translateY</span
></a
@@ -973,7 +973,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#y"
+ ><a href="#y"
><span class="hs-identifier hs-var"
>y</span
></a
@@ -985,7 +985,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#y"
+ ><a href="#y"
><span class="hs-identifier hs-var"
>y</span
></a
@@ -1027,7 +1027,7 @@ forall a. Num a => a -> a -> a
><span id="line-30"
></span
><span class="annot"
- ><a href="Records.html#translate"
+ ><a href="#translate"
><span class="hs-identifier hs-type"
>translate</span
></a
@@ -1059,7 +1059,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -1071,7 +1071,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -1086,7 +1086,7 @@ forall a. Num a => a -> a -> a
><span class="annottext"
>translate :: Int -> Int -> Point -> Point
</span
- ><a href="Records.html#translate"
+ ><a href="#translate"
><span class="hs-identifier hs-var hs-var"
>translate</span
></a
@@ -1261,7 +1261,7 @@ forall a. Num a => a -> a -> a
><span
> </span
><span class="annot"
- ><a href="Records.html#Point"
+ ><a href="#Point"
><span class="hs-identifier hs-type"
>Point</span
></a
@@ -1278,7 +1278,7 @@ y :: Point -> Int
x :: Int
y :: Int
</span
- ><a href="Records.html#x"
+ ><a href="#x"
><span class="hs-glyph hs-var hs-var hs-var hs-var"
>..</span
></a
@@ -1309,7 +1309,7 @@ y :: Int
><span
> </span
><span class="annot"
- ><a href="Records.html#x"
+ ><a href="#x"
><span class="hs-identifier hs-var"
>x</span
></a
@@ -1345,7 +1345,7 @@ y :: Int
><span
> </span
><span class="annot"
- ><a href="Records.html#y"
+ ><a href="#y"
><span class="hs-identifier hs-var"
>y</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
=====================================
@@ -68,7 +68,7 @@
><span id="line-8"
></span
><span class="annot"
- ><a href="TemplateHaskellQuasiquotes.html#aDecl"
+ ><a href="#aDecl"
><span class="hs-identifier hs-type"
>aDecl</span
></a
@@ -93,7 +93,7 @@
><span class="annottext"
>aDecl :: DecsQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#aDecl"
+ ><a href="#aDecl"
><span class="hs-identifier hs-var hs-var"
>aDecl</span
></a
@@ -132,7 +132,7 @@
><span class="annottext"
>TypeQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#aType"
+ ><a href="#aType"
><span class="hs-identifier hs-var"
>aType</span
></a
@@ -190,7 +190,7 @@
><span class="annottext"
>PatQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#aPattern"
+ ><a href="#aPattern"
><span class="hs-identifier hs-var"
>aPattern</span
></a
@@ -207,7 +207,7 @@
><span class="annottext"
>ExpQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#anExpression"
+ ><a href="#anExpression"
><span class="hs-identifier hs-var"
>anExpression</span
></a
@@ -232,7 +232,7 @@
><span id="line-14"
></span
><span class="annot"
- ><a href="TemplateHaskellQuasiquotes.html#aPattern"
+ ><a href="#aPattern"
><span class="hs-identifier hs-type"
>aPattern</span
></a
@@ -257,7 +257,7 @@
><span class="annottext"
>aPattern :: PatQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#aPattern"
+ ><a href="#aPattern"
><span class="hs-identifier hs-var hs-var"
>aPattern</span
></a
@@ -365,7 +365,7 @@
><span class="annottext"
>PatQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#aNumberPattern"
+ ><a href="#aNumberPattern"
><span class="hs-identifier hs-var"
>aNumberPattern</span
></a
@@ -409,7 +409,7 @@
><span id="line-23"
></span
><span class="annot"
- ><a href="TemplateHaskellQuasiquotes.html#aNumberPattern"
+ ><a href="#aNumberPattern"
><span class="hs-identifier hs-type"
>aNumberPattern</span
></a
@@ -434,7 +434,7 @@
><span class="annottext"
>aNumberPattern :: PatQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#aNumberPattern"
+ ><a href="#aNumberPattern"
><span class="hs-identifier hs-var hs-var"
>aNumberPattern</span
></a
@@ -499,7 +499,7 @@
><span id="line-28"
></span
><span class="annot"
- ><a href="TemplateHaskellQuasiquotes.html#anExpression"
+ ><a href="#anExpression"
><span class="hs-identifier hs-type"
>anExpression</span
></a
@@ -509,7 +509,7 @@
><span
> </span
><span class="annot"
- ><a href="TemplateHaskellQuasiquotes.html#anExpression2"
+ ><a href="#anExpression2"
><span class="hs-identifier hs-type"
>anExpression2</span
></a
@@ -534,7 +534,7 @@
><span class="annottext"
>anExpression :: ExpQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#anExpression"
+ ><a href="#anExpression"
><span class="hs-identifier hs-var hs-var"
>anExpression</span
></a
@@ -579,7 +579,7 @@
><span class="annottext"
>ExpQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#anExpression2"
+ ><a href="#anExpression2"
><span class="hs-identifier hs-var"
>anExpression2</span
></a
@@ -617,7 +617,7 @@
><span class="annottext"
>anExpression2 :: ExpQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#anExpression2"
+ ><a href="#anExpression2"
><span class="hs-identifier hs-var hs-var"
>anExpression2</span
></a
@@ -674,7 +674,7 @@
><span id="line-34"
></span
><span class="annot"
- ><a href="TemplateHaskellQuasiquotes.html#aType"
+ ><a href="#aType"
><span class="hs-identifier hs-type"
>aType</span
></a
@@ -699,7 +699,7 @@
><span class="annottext"
>aType :: TypeQ
</span
- ><a href="TemplateHaskellQuasiquotes.html#aType"
+ ><a href="#aType"
><span class="hs-identifier hs-var hs-var"
>aType</span
></a
@@ -764,7 +764,7 @@
><span id="line-39"
></span
><span class="annot"
- ><a href="TemplateHaskellQuasiquotes.html#typedExpr1"
+ ><a href="#typedExpr1"
><span class="hs-identifier hs-type"
>typedExpr1</span
></a
@@ -801,7 +801,7 @@
><span class="annottext"
>typedExpr1 :: Code Q ()
</span
- ><a href="TemplateHaskellQuasiquotes.html#typedExpr1"
+ ><a href="#typedExpr1"
><span class="hs-identifier hs-var hs-var"
>typedExpr1</span
></a
@@ -836,7 +836,7 @@
><span id="line-42"
></span
><span class="annot"
- ><a href="TemplateHaskellQuasiquotes.html#typedExpr"
+ ><a href="#typedExpr"
><span class="hs-identifier hs-type"
>typedExpr</span
></a
@@ -873,7 +873,7 @@
><span class="annottext"
>typedExpr :: Code Q ()
</span
- ><a href="TemplateHaskellQuasiquotes.html#typedExpr"
+ ><a href="#typedExpr"
><span class="hs-identifier hs-var hs-var"
>typedExpr</span
></a
@@ -907,7 +907,7 @@ forall a b. a -> b -> a
><span class="annottext"
>Code Q ()
</span
- ><a href="TemplateHaskellQuasiquotes.html#typedExpr1"
+ ><a href="#typedExpr1"
><span class="hs-identifier hs-var"
>typedExpr1</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/TemplateHaskellSplices.html
=====================================
@@ -89,7 +89,7 @@
><span class="annottext"
>foo :: Integer
</span
- ><a href="TemplateHaskellSplices.html#foo"
+ ><a href="#foo"
><span class="hs-identifier hs-var hs-var"
>foo</span
></a
@@ -138,7 +138,7 @@ forall a. a -> a
><span class="annottext"
>pat :: [(a, String)] -> ()
</span
- ><a href="TemplateHaskellSplices.html#pat"
+ ><a href="#pat"
><span class="hs-identifier hs-var hs-var"
>pat</span
></a
@@ -195,7 +195,7 @@ forall a. a -> a
><span class="annottext"
>qux :: ()
</span
- ><a href="TemplateHaskellSplices.html#qux"
+ ><a href="#qux"
><span class="hs-identifier hs-var hs-var"
>qux</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/Types.html
=====================================
@@ -65,7 +65,7 @@
> </span
><span id="Quux"
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-var"
>Quux</span
></a
@@ -79,7 +79,7 @@
> </span
><span id="Bar"
><span class="annot"
- ><a href="Types.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -93,7 +93,7 @@
> </span
><span id="Baz"
><span class="annot"
- ><a href="Types.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -115,7 +115,7 @@
> </span
><span id="Foo"
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-var"
>Foo</span
></a
@@ -129,7 +129,7 @@
> </span
><span id="Foo"
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-var"
>Foo</span
></a
@@ -157,7 +157,7 @@
> </span
><span id="FooQuux"
><span class="annot"
- ><a href="Types.html#FooQuux"
+ ><a href="#FooQuux"
><span class="hs-identifier hs-var"
>FooQuux</span
></a
@@ -172,7 +172,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -182,7 +182,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -200,7 +200,7 @@
> </span
><span id="QuuxFoo"
><span class="annot"
- ><a href="Types.html#QuuxFoo"
+ ><a href="#QuuxFoo"
><span class="hs-identifier hs-var"
>QuuxFoo</span
></a
@@ -215,7 +215,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -225,7 +225,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -257,7 +257,7 @@
> </span
><span id="Norf"
><span class="annot"
- ><a href="Types.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-var"
>Norf</span
></a
@@ -303,7 +303,7 @@
> </span
><span id="Norf"
><span class="annot"
- ><a href="Types.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-var"
>Norf</span
></a
@@ -312,7 +312,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -320,7 +320,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -333,7 +333,7 @@
> </span
><span id="NFQ"
><span class="annot"
- ><a href="Types.html#NFQ"
+ ><a href="#NFQ"
><span class="hs-identifier hs-var"
>NFQ</span
></a
@@ -342,7 +342,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -350,7 +350,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -370,7 +370,7 @@
> </span
><span id="Norf"
><span class="annot"
- ><a href="Types.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-var"
>Norf</span
></a
@@ -379,7 +379,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -387,7 +387,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -400,7 +400,7 @@
> </span
><span id="NQF"
><span class="annot"
- ><a href="Types.html#NQF"
+ ><a href="#NQF"
><span class="hs-identifier hs-var"
>NQF</span
></a
@@ -409,7 +409,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -417,7 +417,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -447,7 +447,7 @@
> </span
><span id="Norf%27"
><span class="annot"
- ><a href="Types.html#Norf%27"
+ ><a href="#Norf%27"
><span class="hs-identifier hs-var"
>Norf'</span
></a
@@ -493,7 +493,7 @@
> </span
><span id="Norf%27"
><span class="annot"
- ><a href="Types.html#Norf%27"
+ ><a href="#Norf%27"
><span class="hs-identifier hs-var"
>Norf'</span
></a
@@ -502,7 +502,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -510,7 +510,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -524,7 +524,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -534,7 +534,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -556,7 +556,7 @@
> </span
><span id="Norf%27"
><span class="annot"
- ><a href="Types.html#Norf%27"
+ ><a href="#Norf%27"
><span class="hs-identifier hs-var"
>Norf'</span
></a
@@ -565,7 +565,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -573,7 +573,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -587,7 +587,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -597,7 +597,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -620,7 +620,7 @@
><span id="line-28"
></span
><span class="annot"
- ><a href="Types.html#norf1"
+ ><a href="#norf1"
><span class="hs-identifier hs-type"
>norf1</span
></a
@@ -632,7 +632,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-type"
>Norf</span
></a
@@ -640,7 +640,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -648,7 +648,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -673,7 +673,7 @@
><span class="annottext"
>norf1 :: Norf Foo Quux -> Int
</span
- ><a href="Types.html#norf1"
+ ><a href="#norf1"
><span class="hs-identifier hs-var hs-var"
>norf1</span
></a
@@ -684,7 +684,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#NFQ"
+ ><a href="#NFQ"
><span class="hs-identifier hs-type"
>NFQ</span
></a
@@ -694,7 +694,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -713,7 +713,7 @@
><span class="annottext"
>Quux
</span
- ><a href="Types.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -739,7 +739,7 @@
><span id="line-30"
></span
><span class="annot"
- ><a href="Types.html#norf1"
+ ><a href="#norf1"
><span class="hs-identifier hs-var"
>norf1</span
></a
@@ -749,7 +749,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#NFQ"
+ ><a href="#NFQ"
><span class="hs-identifier hs-type"
>NFQ</span
></a
@@ -759,7 +759,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -778,7 +778,7 @@
><span class="annottext"
>Quux
</span
- ><a href="Types.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -809,7 +809,7 @@
><span id="line-32"
></span
><span class="annot"
- ><a href="Types.html#norf2"
+ ><a href="#norf2"
><span class="hs-identifier hs-type"
>norf2</span
></a
@@ -821,7 +821,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Norf"
+ ><a href="#Norf"
><span class="hs-identifier hs-type"
>Norf</span
></a
@@ -829,7 +829,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -837,7 +837,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -862,7 +862,7 @@
><span class="annottext"
>norf2 :: Norf Quux Foo -> Int
</span
- ><a href="Types.html#norf2"
+ ><a href="#norf2"
><span class="hs-identifier hs-var hs-var"
>norf2</span
></a
@@ -873,7 +873,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#NQF"
+ ><a href="#NQF"
><span class="hs-identifier hs-type"
>NQF</span
></a
@@ -884,7 +884,7 @@
><span class="annottext"
>Quux
</span
- ><a href="Types.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -894,7 +894,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -928,7 +928,7 @@
><span id="line-34"
></span
><span class="annot"
- ><a href="Types.html#norf2"
+ ><a href="#norf2"
><span class="hs-identifier hs-var"
>norf2</span
></a
@@ -938,7 +938,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#NQF"
+ ><a href="#NQF"
><span class="hs-identifier hs-type"
>NQF</span
></a
@@ -949,7 +949,7 @@
><span class="annottext"
>Quux
</span
- ><a href="Types.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -959,7 +959,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -1003,7 +1003,7 @@
><span id="line-37"
></span
><span class="annot"
- ><a href="Types.html#norf1%27"
+ ><a href="#norf1%27"
><span class="hs-identifier hs-type"
>norf1'</span
></a
@@ -1015,7 +1015,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Norf%27"
+ ><a href="#Norf%27"
><span class="hs-identifier hs-type"
>Norf'</span
></a
@@ -1023,7 +1023,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -1031,7 +1031,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -1056,7 +1056,7 @@
><span class="annottext"
>norf1' :: Norf' Foo Quux -> Int
</span
- ><a href="Types.html#norf1%27"
+ ><a href="#norf1%27"
><span class="hs-identifier hs-var hs-var"
>norf1'</span
></a
@@ -1067,7 +1067,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -1086,7 +1086,7 @@
><span class="annottext"
>Quux
</span
- ><a href="Types.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -1112,7 +1112,7 @@
><span id="line-39"
></span
><span class="annot"
- ><a href="Types.html#norf1%27"
+ ><a href="#norf1%27"
><span class="hs-identifier hs-var"
>norf1'</span
></a
@@ -1122,7 +1122,7 @@
><span class="hs-special"
>(</span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -1141,7 +1141,7 @@
><span class="annottext"
>Quux
</span
- ><a href="Types.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -1172,7 +1172,7 @@
><span id="line-41"
></span
><span class="annot"
- ><a href="Types.html#norf2%27"
+ ><a href="#norf2%27"
><span class="hs-identifier hs-type"
>norf2'</span
></a
@@ -1184,7 +1184,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Norf%27"
+ ><a href="#Norf%27"
><span class="hs-identifier hs-type"
>Norf'</span
></a
@@ -1192,7 +1192,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Quux"
+ ><a href="#Quux"
><span class="hs-identifier hs-type"
>Quux</span
></a
@@ -1200,7 +1200,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -1225,7 +1225,7 @@
><span class="annottext"
>norf2' :: Norf' Quux Foo -> Int
</span
- ><a href="Types.html#norf2%27"
+ ><a href="#norf2%27"
><span class="hs-identifier hs-var hs-var"
>norf2'</span
></a
@@ -1239,7 +1239,7 @@
><span class="annottext"
>Quux
</span
- ><a href="Types.html#Bar"
+ ><a href="#Bar"
><span class="hs-identifier hs-var"
>Bar</span
></a
@@ -1249,7 +1249,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
@@ -1281,7 +1281,7 @@
><span id="line-43"
></span
><span class="annot"
- ><a href="Types.html#norf2%27"
+ ><a href="#norf2%27"
><span class="hs-identifier hs-var"
>norf2'</span
></a
@@ -1294,7 +1294,7 @@
><span class="annottext"
>Quux
</span
- ><a href="Types.html#Baz"
+ ><a href="#Baz"
><span class="hs-identifier hs-var"
>Baz</span
></a
@@ -1304,7 +1304,7 @@
><span
> </span
><span class="annot"
- ><a href="Types.html#Foo"
+ ><a href="#Foo"
><span class="hs-identifier hs-type"
>Foo</span
></a
=====================================
utils/haddock/hypsrc-test/ref/src/UsingQuasiquotes.html
=====================================
@@ -69,7 +69,7 @@
><span class="annottext"
>baz :: [Char]
</span
- ><a href="UsingQuasiquotes.html#baz"
+ ><a href="#baz"
><span class="hs-identifier hs-var hs-var"
>baz</span
></a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/403cb665019f4e9999615467cef2d1…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/403cb665019f4e9999615467cef2d1…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] configure: Fix consistency between distrib and source CC check
by Marge Bot (@marge-bot) 17 Sep '25
by Marge Bot (@marge-bot) 17 Sep '25
17 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
403cb665 by Ben Gamari at 2025-09-17T04:46:00-04:00
configure: Fix consistency between distrib and source CC check
Previously distrib/configure.ac did not
include `cc`.
Closes #26394.
- - - - -
4 changed files:
- configure.ac
- distrib/configure.ac.in
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
Changes:
=====================================
configure.ac
=====================================
@@ -424,7 +424,7 @@ AC_ARG_WITH([clang],
dnl detect compiler (prefer gcc over clang) and set $CC (unless CC already set),
dnl later CC is copied to CC_STAGE{1,2,3}
AC_PROG_CC([cc gcc clang])
-AC_PROG_CXX([g++ clang++ c++])
+AC_PROG_CXX([c++ g++ clang++])
# Work around #24324
MOVE_TO_FLAGS([CC],[CFLAGS])
MOVE_TO_FLAGS([CXX],[CXXFLAGS])
=====================================
distrib/configure.ac.in
=====================================
@@ -138,8 +138,8 @@ AC_SUBST([EnableStrictGhcToolchainCheck])
dnl ** Which gcc to use?
dnl --------------------------------------------------------------
-AC_PROG_CC([gcc clang])
-AC_PROG_CXX([g++ clang++ c++])
+AC_PROG_CC([cc gcc clang])
+AC_PROG_CXX([c++ g++ clang++])
# Work around #24324
MOVE_TO_FLAGS([CC],[CFLAGS])
MOVE_TO_FLAGS([CXX],[CXXFLAGS])
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
=====================================
@@ -40,7 +40,7 @@ findBasicCc :: ProgOpt -> M Cc
findBasicCc progOpt = checking "for C compiler" $ do
-- TODO: We keep the candidate order we had in configure, but perhaps
-- there's a more optimal one
- ccProgram <- findProgram "C compiler" progOpt ["gcc", "clang", "cc"]
+ ccProgram <- findProgram "C compiler" progOpt ["cc", "gcc", "clang"]
return $ Cc{ccProgram}
findCc :: ArchOS
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
=====================================
@@ -26,7 +26,7 @@ findCxx :: ArchOS
-> ProgOpt -> M Cxx
findCxx archOs target progOpt = checking "for C++ compiler" $ do
-- TODO: We use the search order in configure, but there could be a more optimal one
- cxxProgram <- findProgram "C++ compiler" progOpt ["g++", "clang++", "c++"]
+ cxxProgram <- findProgram "C++ compiler" progOpt ["c++", "g++", "clang++"]
cxx <- cxxSupportsTarget archOs target Cxx{cxxProgram}
checkCxxWorks cxx
return cxx
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/403cb665019f4e9999615467cef2d18…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/403cb665019f4e9999615467cef2d18…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] Print fully qualified unit names in name mismatch
by Marge Bot (@marge-bot) 17 Sep '25
by Marge Bot (@marge-bot) 17 Sep '25
17 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
54b5950e by Sylvain Henry at 2025-09-17T04:45:18-04:00
Print fully qualified unit names in name mismatch
It's more user-friendly to directly print the right thing instead of
requiring the user to retry with the additional `-dppr-debug` flag.
- - - - -
2 changed files:
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Unit/State.hs
Changes:
=====================================
compiler/GHC/Iface/Errors/Ppr.hs
=====================================
@@ -336,8 +336,9 @@ hiModuleNameMismatchWarn requested_mod read_mod
]
]
| otherwise =
- -- ToDo: This will fail to have enough qualification when the package IDs
- -- are the same
+ -- Display fully qualified unit names. Otherwise we may not have enough
+ -- qualification and the printed names could look exactly the same.
+ pprRawUnitIds $
withPprStyle (mkUserStyle alwaysQualify AllTheWay) $
-- we want the Modules below to be qualified with package names,
-- so reset the NamePprCtx setting.
@@ -345,7 +346,6 @@ hiModuleNameMismatchWarn requested_mod read_mod
, ppr requested_mod
, text "differs from name found in the interface file"
, ppr read_mod
- , parens (text "if these names look the same, try again with -dppr-debug")
]
dynamicHashMismatchError :: Module -> ModLocation -> SDoc
=====================================
compiler/GHC/Unit/State.hs
=====================================
@@ -66,6 +66,7 @@ module GHC.Unit.State (
pprUnitInfoForUser,
pprModuleMap,
pprWithUnitState,
+ pprRawUnitIds,
-- * Utils
unwireUnit)
@@ -2269,3 +2270,7 @@ pprWithUnitState :: UnitState -> SDoc -> SDoc
pprWithUnitState state = updSDocContext (\ctx -> ctx
{ sdocUnitIdForUser = \fs -> pprUnitIdForUser state (UnitId fs)
})
+
+-- | Print raw unit-ids, without removing the hash
+pprRawUnitIds :: SDoc -> SDoc
+pprRawUnitIds = updSDocContext (\ctx -> ctx { sdocUnitIdForUser = ftext })
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/54b5950ebfed24429fae5111896ffc1…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/54b5950ebfed24429fae5111896ffc1…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.12.3-backports] 3 commits: haddock: Document instances from other packages
by Zubin (@wz1000) 17 Sep '25
by Zubin (@wz1000) 17 Sep '25
17 Sep '25
Zubin pushed to branch wip/9.12.3-backports at Glasgow Haskell Compiler / GHC
Commits:
351ad869 by Ryan Hendrickson at 2025-09-17T12:54:08+05:30
haddock: Document instances from other packages
When attaching instances to `Interface`s, it isn't enough just to look
for instances in the list of `Interface`s being processed. We also need
to look in the modules on which they depend, including those outside of
this package.
Fixes #25147.
Fixes #26079.
(cherry picked from commit a26243fde4680271712a3d774e17f6cd6da4a652)
- - - - -
6d6d3383 by Zubin Duggal at 2025-09-17T12:54:08+05:30
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
(cherry picked from commit 5dabc718a04bfc4d277c5ff7f815ee3d6b9670cb)
- - - - -
9a280a8d by Zubin Duggal at 2025-09-17T12:54:08+05:30
Prepare 9.12.3
- - - - -
15 changed files:
- configure.ac
- docs/users_guide/9.12.3-notes.rst
- testsuite/driver/testlib.py
- 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
- testsuite/tests/polykinds/T14172.stderr
- utils/haddock/CHANGES.md
- utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs
- utils/haddock/html-test/ref/Bug1004.html
Changes:
=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12.2], [glasgow-ha
AC_CONFIG_MACRO_DIRS([m4])
# Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
# The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
# above. If this is not a released version, then we will append the
=====================================
docs/users_guide/9.12.3-notes.rst
=====================================
@@ -13,6 +13,83 @@ Compiler
- Fixed re-exports of ``MkSolo`` and ``MkSolo#`` (:ghc-ticket:`25182`)
- Fixed the behavior of ``Language.Haskell.TH.mkName "FUN"`` (:ghc-ticket:`25174`)
+- Fixed miscompilation involving ``zonkEqTypes`` on ``AppTy/AppTy`` (:ghc-ticket:`26256`)
+- Fixed CprAnal to detect recursive newtypes (:ghc-ticket:`25944`)
+- Fixed specialisation of incoherent instances (:ghc-ticket:`25883`)
+- Fixed bytecode generation for ``tagToEnum# <LITERAL>`` (:ghc-ticket:`25975`)
+- Fixed panic with EmptyCase and RequiredTypeArguments (:ghc-ticket:`25004`)
+- Fixed ``tyConStupidTheta`` to handle ``PromotedDataCon`` (:ghc-ticket:`25739`)
+- Fixed unused import warnings for duplicate record fields (:ghc-ticket:`24035`)
+- Fixed lexing of ``"\^\"`` (:ghc-ticket:`25937`)
+- Fixed string gap collapsing (:ghc-ticket:`25784`)
+- Fixed lexing of comments in multiline strings (:ghc-ticket:`25609`)
+- Made unexpected LLVM versions a warning rather than an error (:ghc-ticket:`25915`)
+- Disabled ``-fprof-late-overloaded-calls`` for join points to avoid invalid transformations
+- Fixed bugs in ``integerRecipMod`` and ``integerPowMod`` (:ghc-ticket:`26017`)
+- Fixed ``naturalAndNot`` for NB/NS case (:ghc-ticket:`26230`)
+- Fixed ``ds_ev_typeable`` to use ``mkTrAppChecked`` (:ghc-ticket:`25998`)
+- Fixed GHC settings to always unescape escaped spaces (:ghc-ticket:`25204`)
+- Fixed issue with HasCallStack constraint caching (:ghc-ticket:`25529`)
+- Fixed archive member size writing logic in ``GHC.SysTools.Ar`` (:ghc-ticket:`26120`, :ghc-ticket:`22586`)
+
+Runtime System
+~~~~~~~~~~~~~~
+
+- Fixed ``MessageBlackHole.link`` to always be a valid closure
+- Fixed handling of WHITEHOLE in ``messageBlackHole`` (:ghc-ticket:`26205`)
+- Fixed ``rts_clearMemory`` logic when sanity checks are enabled (:ghc-ticket:`26011`)
+- Fixed underflow frame lookups in the bytecode interpreter (:ghc-ticket:`25750`)
+- Fixed overflows and reentrancy in interpreter statistics calculation (:ghc-ticket:`25756`)
+- Fixed INTERP_STATS profiling code (:ghc-ticket:`25695`)
+- Removed problematic ``n_free`` variable from nonmovingGC (:ghc-ticket:`26186`)
+- Fixed incorrect format specifiers in era profiling
+- Improved documentation of SLIDE and PACK bytecode instructions
+- Eliminated redundant ``SLIDE x 0`` bytecode instructions
+- Fixed compile issues on powerpc64 ELF v1
+
+Code Generation
+~~~~~~~~~~~~~~~
+
+- Fixed LLVM built-in variable predicate (was checking ``$llvm`` instead of ``@llvm``)
+- Fixed linkage of built-in arrays for LLVM (:ghc-ticket:`25769`)
+- Fixed code generation for SSE vector operations (:ghc-ticket:`25859`)
+- Fixed ``bswap64`` code generation on i386 (:ghc-ticket:`25601`)
+- Fixed sub-word arithmetic right shift on AArch64 (:ghc-ticket:`26061`)
+- Fixed LLVM vector literal emission to include type information
+- Fixed LLVM version detection
+- Fixed typo in ``padLiveArgs`` that caused segfaults (:ghc-ticket:`25770`, :ghc-ticket:`25773`)
+- Fixed constant-folding for Word->Float bitcasts
+- Added surface syntax for Word/Float bitcast operations
+- Fixed ``MOVD`` format in x86 NCG for ``unpackInt64X2#``
+- Added ``-finter-module-far-jumps`` flag for AArch64
+- Fixed RV64 J instruction handling for non-local jumps (:ghc-ticket:`25738`)
+- Reapplied division by constants optimization
+- Fixed TNTC to set CmmProc entry_label properly (:ghc-ticket:`25565`)
+
+Linker
+~~~~~~
+
+- Improved efficiency of proddable blocks structure (:ghc-ticket:`26009`)
+- Fixed Windows DLL loading to avoid redundant ``LoadLibraryEx`` calls (:ghc-ticket:`26009`)
+- Fixed incorrect use of ``break`` in nested for loop (:ghc-ticket:`26052`)
+- Fixed linker to not fail due to ``RTLD_NOW`` (:ghc-ticket:`25943`)
+- Dropped obsolete Windows XP compatibility checks
+
+GHCi
+~~~~
+
+- Fixed ``mkTopLevEnv`` to use ``loadInterfaceForModule`` instead of ``loadSrcInterface`` (:ghc-ticket:`25951`)
+
+Template Haskell
+~~~~~~~~~~~~~~~~
+
+- Added explicit export lists to all remaining template-haskell modules
+
+Build system
+~~~~~~~~~~~~~~~~
+
+- Exposed all of Backtraces' internals for ghc-internal (:ghc-ticket:`26049`)
+- Fixed cross-compilation configuration override (:ghc-ticket:`26236`)
Included libraries
~~~~~~~~~~~~~~~~~~
=====================================
testsuite/driver/testlib.py
=====================================
@@ -1725,7 +1725,7 @@ async def do_test(name: TestName,
dst_makefile = in_testdir('Makefile')
if src_makefile.exists():
makefile = src_makefile.read_text(encoding='UTF-8')
- makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1)
+ makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, count=1)
dst_makefile.write_text(makefile, encoding='UTF-8')
if opts.pre_cmd:
=====================================
testsuite/tests/haddock/haddock_testsuite/Makefile
=====================================
@@ -76,3 +76,7 @@ hypsrcTest:
.PHONY: haddockForeignTest
haddockForeignTest:
'$(HADDOCK)' A.hs B.hs F.hs arith.c
+
+.PHONY: T26114
+T26114:
+ '$(HADDOCK)' T26114.hs
=====================================
testsuite/tests/haddock/haddock_testsuite/T26114.hs
=====================================
@@ -0,0 +1,23 @@
+{-# LANGUAGE TypeFamilies #-}
+
+-- | Module
+module T26114 where
+
+-- | C1
+class C1 t where
+ type C2 t
+
+-- | A
+data A = A
+
+instance C1 A where
+ type C2 A = B
+
+-- | B
+data B = B
+
+instance C1 B where
+ type C2 B = C
+
+-- | C
+data C = C
=====================================
testsuite/tests/haddock/haddock_testsuite/T26114.stdout
=====================================
@@ -0,0 +1,3 @@
+[1 of 1] Compiling T26114 ( T26114.hs, nothing )
+Haddock coverage:
+ 100% ( 5 / 5) in 'T26114'
=====================================
testsuite/tests/haddock/haddock_testsuite/all.T
=====================================
@@ -24,3 +24,8 @@ test('haddockForeignTest',
[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'])],
makefile_test,
['haddockForeignTest'])
+
+test('T26114',
+ [ignore_stderr, req_haddock, extra_files(['T26114.hs'])],
+ makefile_test,
+ ['T26114'])
=====================================
testsuite/tests/polykinds/T14172.stderr
=====================================
@@ -1,6 +1,6 @@
T14172.hs:7:46: error: [GHC-88464]
- • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
- Where: ‘k0’ is an ambiguous type variable
+ • Found type wildcard ‘_’ standing for ‘a'1 :: k30’
+ Where: ‘k30’ is an ambiguous type variable
‘a'1’ is an ambiguous type variable
To use the inferred type, enable PartialTypeSignatures
• In the first argument of ‘h’, namely ‘_’
=====================================
utils/haddock/CHANGES.md
=====================================
@@ -1,6 +1,8 @@
## Changes in 2.32.0
* Add highlighting for inline-code-blocks (sections enclosed in @'s)
+ * Fix missing documentation for orphan instances from other packages.
+
* Add incremental mode to support rendering documentation one module at a time.
* The flag `--no-compilation` has been added. This flag causes Haddock to avoid
=====================================
utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
=====================================
@@ -93,7 +93,10 @@ attachInstances expInfo ifaces instIfaceMap isOneShot = do
, fromOrig == Just True || not (null reExp)
]
mods_to_load = moduleSetElts mods
- mods_visible = mkModuleSet $ map ifaceMod ifaces
+ -- We need to ensure orphans in modules outside of this package are included.
+ -- See https://gitlab.haskell.org/ghc/ghc/-/issues/25147
+ -- and https://gitlab.haskell.org/ghc/ghc/-/issues/26079
+ mods_visible = mkModuleSet $ concatMap (liftA2 (:) ifaceMod ifaceOrphanDeps) ifaces
(_msgs, mb_index) <- do
hsc_env <- getSession
=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
=====================================
@@ -59,6 +59,7 @@ import GHC.Types.Name.Set
import GHC.Types.SafeHaskell
import qualified GHC.Types.SrcLoc as SrcLoc
import qualified GHC.Types.Unique.Map as UniqMap
+import GHC.Unit.Module.Deps (dep_orphs)
import GHC.Unit.Module.ModIface
import GHC.Unit.State (PackageName (..), UnitState)
import GHC.Utils.Outputable (SDocContext)
@@ -270,6 +271,7 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces
, ifaceVisibleExports = visible_names
, ifaceFixMap = fixities
, ifaceInstances = instances
+ , ifaceOrphanDeps = dep_orphs $ mi_deps mod_iface
, ifaceOrphanInstances = [] -- Filled in attachInstances
, ifaceRnOrphanInstances = [] -- Filled in renameInterfaceRn
, ifaceHaddockCoverage = coverage
=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -104,6 +104,7 @@ renameInterface dflags ignoreSet renamingEnv warnings hoogle iface = do
&& isExternalName name
&& not (isBuiltInSyntax name)
&& not (isTyVarName name)
+ && not (isDerivedOccName $ nameOccName name)
&& Exact name /= eqTyCon_RDR
-- Must not be in the set of ignored symbols for the module or the
-- unqualified ignored symbols
=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -131,6 +131,9 @@ data Interface = Interface
-- Names from modules that are entirely re-exported don't count as visible.
, ifaceInstances :: [ClsInst]
-- ^ Instances exported by the module.
+ , ifaceOrphanDeps :: [Module]
+ -- ^ The list of modules to check for orphan instances if this module is
+ -- imported.
, ifaceOrphanInstances :: [DocInstance GhcRn]
-- ^ Orphan instances
, ifaceRnOrphanInstances :: [DocInstance DocNameI]
=====================================
utils/haddock/haddock-test/src/Test/Haddock/Config.hs
=====================================
@@ -262,6 +262,7 @@ baseDependencies ghcPath = do
pkgs =
[ "array"
, "base"
+ , "deepseq"
, "ghc-prim"
, "process"
, "template-haskell"
=====================================
utils/haddock/html-test/ref/Bug1004.html
=====================================
@@ -797,7 +797,55 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Alternative:8"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:NFData1:8"
+ ></span
+ > (<a href="#" title="Control.DeepSeq"
+ >NFData1</a
+ > f, <a href="#" title="Control.DeepSeq"
+ >NFData1</a
+ > g) => <a href="#" title="Control.DeepSeq"
+ >NFData1</a
+ > (<a href="#" title="Bug1004"
+ >Product</a
+ > f g)</span
+ > <a href="#" class="selflink"
+ >#</a
+ ></td
+ ><td class="doc"
+ ><p
+ ><em
+ >Since: deepseq-1.4.3.0</em
+ ></p
+ ></td
+ ></tr
+ ><tr
+ ><td colspan="2"
+ ><details id="i:id:Product:NFData1:8"
+ ><summary class="hide-when-js-enabled"
+ >Instance details</summary
+ ><p
+ >Defined in <a href="#"
+ >Control.DeepSeq</a
+ ></p
+ > <div class="subs methods"
+ ><p class="caption"
+ >Methods</p
+ ><p class="src"
+ ><a href="#"
+ >liftRnf</a
+ > :: (a -> ()) -> <a href="#" title="Bug1004"
+ >Product</a
+ > f g a -> () <a href="#" class="selflink"
+ >#</a
+ ></p
+ ></div
+ ></details
+ ></td
+ ></tr
+ ><tr
+ ><td class="src clearfix"
+ ><span class="inst-left"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Alternative:9"
></span
> (<a href="#" title="Control.Applicative"
>Alternative</a
@@ -820,7 +868,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Alternative:8"
+ ><details id="i:id:Product:Alternative:9"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -877,7 +925,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Applicative:9"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Applicative:10"
></span
> (<a href="#" title="Control.Applicative"
>Applicative</a
@@ -900,7 +948,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Applicative:9"
+ ><details id="i:id:Product:Applicative:10"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -973,7 +1021,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Functor:10"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Functor:11"
></span
> (<a href="#" title="Control.Monad"
>Functor</a
@@ -996,7 +1044,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Functor:10"
+ ><details id="i:id:Product:Functor:11"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1033,7 +1081,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monad:11"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monad:12"
></span
> (<a href="#" title="Control.Monad"
>Monad</a
@@ -1056,7 +1104,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Monad:11"
+ ><details id="i:id:Product:Monad:12"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1105,7 +1153,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadPlus:12"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadPlus:13"
></span
> (<a href="#" title="Control.Monad"
>MonadPlus</a
@@ -1128,7 +1176,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:MonadPlus:12"
+ ><details id="i:id:Product:MonadPlus:13"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1165,7 +1213,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadFix:13"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadFix:14"
></span
> (<a href="#" title="Control.Monad.Fix"
>MonadFix</a
@@ -1188,7 +1236,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:MonadFix:13"
+ ><details id="i:id:Product:MonadFix:14"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1215,7 +1263,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadZip:14"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadZip:15"
></span
> (<a href="#" title="Control.Monad.Zip"
>MonadZip</a
@@ -1238,7 +1286,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:MonadZip:14"
+ ><details id="i:id:Product:MonadZip:15"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1291,7 +1339,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Foldable:15"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Foldable:16"
></span
> (<a href="#" title="Data.Foldable"
>Foldable</a
@@ -1314,7 +1362,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Foldable:15"
+ ><details id="i:id:Product:Foldable:16"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1489,7 +1537,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Traversable:16"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Traversable:17"
></span
> (<a href="#" title="Data.Traversable"
>Traversable</a
@@ -1512,7 +1560,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Traversable:16"
+ ><details id="i:id:Product:Traversable:17"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1577,7 +1625,59 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monoid:17"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:NFData:18"
+ ></span
+ > (<a href="#" title="Control.DeepSeq"
+ >NFData</a
+ > (f a), <a href="#" title="Control.DeepSeq"
+ >NFData</a
+ > (g a)) => <a href="#" title="Control.DeepSeq"
+ >NFData</a
+ > (<a href="#" title="Bug1004"
+ >Product</a
+ > f g a)</span
+ > <a href="#" class="selflink"
+ >#</a
+ ></td
+ ><td class="doc"
+ ><p
+ >Note: in <code class="inline-code"
+ >deepseq-1.5.0.0</code
+ > this instance's superclasses were changed.</p
+ ><p
+ ><em
+ >Since: deepseq-1.4.3.0</em
+ ></p
+ ></td
+ ></tr
+ ><tr
+ ><td colspan="2"
+ ><details id="i:id:Product:NFData:18"
+ ><summary class="hide-when-js-enabled"
+ >Instance details</summary
+ ><p
+ >Defined in <a href="#"
+ >Control.DeepSeq</a
+ ></p
+ > <div class="subs methods"
+ ><p class="caption"
+ >Methods</p
+ ><p class="src"
+ ><a href="#"
+ >rnf</a
+ > :: <a href="#" title="Bug1004"
+ >Product</a
+ > f g a -> () <a href="#" class="selflink"
+ >#</a
+ ></p
+ ></div
+ ></details
+ ></td
+ ></tr
+ ><tr
+ ><td class="src clearfix"
+ ><span class="inst-left"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monoid:19"
></span
> (<a href="#" title="Data.Monoid"
>Monoid</a
@@ -1600,7 +1700,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Monoid:17"
+ ><details id="i:id:Product:Monoid:19"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1647,7 +1747,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Semigroup:18"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Semigroup:20"
></span
> (<a href="#" title="Prelude"
>Semigroup</a
@@ -1670,7 +1770,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Semigroup:18"
+ ><details id="i:id:Product:Semigroup:20"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1723,7 +1823,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Data:19"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Data:21"
></span
> (<a href="#" title="Data.Dynamic"
>Typeable</a
@@ -1754,7 +1854,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Data:19"
+ ><details id="i:id:Product:Data:21"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -1971,7 +2071,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Generic:20"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Generic:22"
></span
> <a href="#" title="GHC.Generics"
>Generic</a
@@ -1986,7 +2086,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Generic:20"
+ ><details id="i:id:Product:Generic:22"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -2125,7 +2225,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Read:21"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Read:23"
></span
> (<a href="#" title="Prelude"
>Read</a
@@ -2148,7 +2248,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Read:21"
+ ><details id="i:id:Product:Read:23"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -2207,7 +2307,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Show:22"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Show:24"
></span
> (<a href="#" title="Prelude"
>Show</a
@@ -2230,7 +2330,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Show:22"
+ ><details id="i:id:Product:Show:24"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -2279,7 +2379,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Eq:23"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Eq:25"
></span
> (<a href="#" title="Data.Eq"
>Eq</a
@@ -2302,7 +2402,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Eq:23"
+ ><details id="i:id:Product:Eq:25"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -2343,7 +2443,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Ord:24"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Ord:26"
></span
> (<a href="#" title="Data.Ord"
>Ord</a
@@ -2366,7 +2466,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Ord:24"
+ ><details id="i:id:Product:Ord:26"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -2467,7 +2567,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep1:25"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep1:27"
></span
> <span class="keyword"
>type</span
@@ -2490,7 +2590,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Rep1:25"
+ ><details id="i:id:Product:Rep1:27"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
@@ -2565,7 +2665,7 @@
><tr
><td class="src clearfix"
><span class="inst-left"
- ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep:26"
+ ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep:28"
></span
> <span class="keyword"
>type</span
@@ -2586,7 +2686,7 @@
></tr
><tr
><td colspan="2"
- ><details id="i:id:Product:Rep:26"
+ ><details id="i:id:Product:Rep:28"
><summary class="hide-when-js-enabled"
>Instance details</summary
><p
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0337f4ecf2f17e6e9a01439ed67e89…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0337f4ecf2f17e6e9a01439ed67e89…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26415] Fix tabs in string gaps (#26415)
by Brandon Chinn (@brandonchinn178) 17 Sep '25
by Brandon Chinn (@brandonchinn178) 17 Sep '25
17 Sep '25
Brandon Chinn pushed to branch wip/T26415 at Glasgow Haskell Compiler / GHC
Commits:
5795fcb7 by Brandon Chinn at 2025-09-16T22:16:16-07:00
Fix tabs in string gaps (#26415)
- - - - -
5 changed files:
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/Lexer/String.x
- + testsuite/tests/parser/should_run/T26415.hs
- + testsuite/tests/parser/should_run/T26415.stdout
- testsuite/tests/parser/should_run/all.T
Changes:
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -145,7 +145,7 @@ import GHC.Parser.String
$unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
$nl = [\n\r\f]
$space = [\ $unispace]
-$whitechar = [$nl \v $space]
+$whitechar = [$nl \t \v $space]
$white_no_nl = $whitechar # \n -- TODO #8424
$tab = \t
@@ -248,7 +248,7 @@ haskell :-
-- Alex "Rules"
-- everywhere: skip whitespace
-$white_no_nl+ ;
+($white_no_nl # \t)+ ;
$tab { warnTab }
-- Everywhere: deal with nested comments. We explicitly rule out
=====================================
compiler/GHC/Parser/Lexer/String.x
=====================================
@@ -25,7 +25,7 @@ import GHC.Utils.Panic (panic)
$unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
$nl = [\n\r\f]
$space = [\ $unispace]
-$whitechar = [$nl \v $space]
+$whitechar = [$nl \t \v $space]
$tab = \t
$ascdigit = 0-9
=====================================
testsuite/tests/parser/should_run/T26415.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE MultilineStrings #-}
+
+main :: IO ()
+main = do
+ print "\ \"
+ print """\ \"""
=====================================
testsuite/tests/parser/should_run/T26415.stdout
=====================================
@@ -0,0 +1 @@
+""
=====================================
testsuite/tests/parser/should_run/all.T
=====================================
@@ -27,6 +27,7 @@ test('RecordDotSyntax4', [extra_files(['RecordDotSyntaxA.hs'])], multimod_compil
test('RecordDotSyntax5', normal, compile_and_run, [''])
test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script'])
test('T25937', normal, compile_and_run, [''])
+test('T26415', normal, compile_and_run, [''])
# Multiline strings
test('MultilineStrings', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5795fcb7d3f9c408caad82870d52eb2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5795fcb7d3f9c408caad82870d52eb2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26415] Fix tabs in string gaps (#26415)
by Brandon Chinn (@brandonchinn178) 17 Sep '25
by Brandon Chinn (@brandonchinn178) 17 Sep '25
17 Sep '25
Brandon Chinn pushed to branch wip/T26415 at Glasgow Haskell Compiler / GHC
Commits:
f21b8a55 by Brandon Chinn at 2025-09-16T22:15:30-07:00
Fix tabs in string gaps (#26415)
- - - - -
5 changed files:
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/Lexer/String.x
- + testsuite/tests/parser/should_run/T26415.hs
- + testsuite/tests/parser/should_run/T26415.stdout
- testsuite/tests/parser/should_run/all.T
Changes:
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -145,7 +145,7 @@ import GHC.Parser.String
$unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
$nl = [\n\r\f]
$space = [\ $unispace]
-$whitechar = [$nl \v $space]
+$whitechar = [$nl \t \v $space]
$white_no_nl = $whitechar # \n -- TODO #8424
$tab = \t
@@ -248,7 +248,7 @@ haskell :-
-- Alex "Rules"
-- everywhere: skip whitespace
-$white_no_nl+ ;
+($white_no_nl # \t)+ ;
$tab { warnTab }
-- Everywhere: deal with nested comments. We explicitly rule out
=====================================
compiler/GHC/Parser/Lexer/String.x
=====================================
@@ -25,7 +25,7 @@ import GHC.Utils.Panic (panic)
$unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
$nl = [\n\r\f]
$space = [\ $unispace]
-$whitechar = [$nl \v $space]
+$whitechar = [$nl \t \v $space]
$tab = \t
$ascdigit = 0-9
=====================================
testsuite/tests/parser/should_run/T26415.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE MultilineStrings #-}
+
+main :: IO ()
+main = do
+ print "\ \"
+ print """\ \"""
=====================================
testsuite/tests/parser/should_run/T26415.stdout
=====================================
@@ -0,0 +1 @@
+""
=====================================
testsuite/tests/parser/should_run/all.T
=====================================
@@ -27,6 +27,7 @@ test('RecordDotSyntax4', [extra_files(['RecordDotSyntaxA.hs'])], multimod_compil
test('RecordDotSyntax5', normal, compile_and_run, [''])
test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script'])
test('T25937', normal, compile_and_run, [''])
+test('T26415', normal, compile_and_run, [''])
# Multiline strings
test('MultilineStrings', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f21b8a55335b94efb2d75326711fe12…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f21b8a55335b94efb2d75326711fe12…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26415] Fix tabs in string gaps (#26415)
by Brandon Chinn (@brandonchinn178) 17 Sep '25
by Brandon Chinn (@brandonchinn178) 17 Sep '25
17 Sep '25
Brandon Chinn pushed to branch wip/T26415 at Glasgow Haskell Compiler / GHC
Commits:
e6dcdd56 by Brandon Chinn at 2025-09-16T21:58:14-07:00
Fix tabs in string gaps (#26415)
- - - - -
5 changed files:
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/Lexer/String.x
- + testsuite/tests/parser/should_run/T26415.hs
- + testsuite/tests/parser/should_run/T26415.stdout
- testsuite/tests/parser/should_run/all.T
Changes:
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -145,7 +145,7 @@ import GHC.Parser.String
$unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
$nl = [\n\r\f]
$space = [\ $unispace]
-$whitechar = [$nl \v $space]
+$whitechar = [$nl \t \v $space]
$white_no_nl = $whitechar # \n -- TODO #8424
$tab = \t
@@ -248,7 +248,7 @@ haskell :-
-- Alex "Rules"
-- everywhere: skip whitespace
-$white_no_nl+ ;
+($white_no_nl | \t)+ ;
$tab { warnTab }
-- Everywhere: deal with nested comments. We explicitly rule out
=====================================
compiler/GHC/Parser/Lexer/String.x
=====================================
@@ -25,7 +25,7 @@ import GHC.Utils.Panic (panic)
$unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
$nl = [\n\r\f]
$space = [\ $unispace]
-$whitechar = [$nl \v $space]
+$whitechar = [$nl \t \v $space]
$tab = \t
$ascdigit = 0-9
=====================================
testsuite/tests/parser/should_run/T26415.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE MultilineStrings #-}
+
+main :: IO ()
+main = do
+ print "\ \"
+ print """\ \"""
=====================================
testsuite/tests/parser/should_run/T26415.stdout
=====================================
@@ -0,0 +1 @@
+""
=====================================
testsuite/tests/parser/should_run/all.T
=====================================
@@ -27,6 +27,7 @@ test('RecordDotSyntax4', [extra_files(['RecordDotSyntaxA.hs'])], multimod_compil
test('RecordDotSyntax5', normal, compile_and_run, [''])
test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script'])
test('T25937', normal, compile_and_run, [''])
+test('T26415', normal, compile_and_run, [''])
# Multiline strings
test('MultilineStrings', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6dcdd56008c3da6573fb672c665742…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6dcdd56008c3da6573fb672c665742…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
17 Sep '25
Brandon Chinn pushed new branch wip/T26415 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T26415
You're receiving this email because of your account on gitlab.haskell.org.
1
0