[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Print fully qualified unit names in name mismatch
by Marge Bot (@marge-bot) 16 Sep '25
by Marge Bot (@marge-bot) 16 Sep '25
16 Sep '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
12419e93 by Sylvain Henry at 2025-09-16T19:04:08-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.
- - - - -
54576857 by Ben Gamari at 2025-09-16T19:04:10-04:00
configure: Fix consistency between distrib and source CC check
Previously distrib/configure.ac did not
include `cc`.
Closes #26394.
- - - - -
e5a4a4cc by Oleg Grenrus at 2025-09-16T19:04:10-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.
- - - - -
d0c6e4cd by Oleg Grenrus at 2025-09-16T19:04:10-04:00
Shorten in-module links in hyperlinked source
Instead of href="This.Module#ident" to just "#ident"
- - - - -
e53a16e4 by Oleg Grenrus at 2025-09-16T19:04:10-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.
- - - - -
ecebc5b6 by Stefan Schulze Frielinghaus at 2025-09-16T19:04:11-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.
- - - - -
27 changed files:
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Unit/State.hs
- configure.ac
- distrib/configure.ac.in
- rts/sm/GCThread.h
- 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
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/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
=====================================
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 })
=====================================
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])
=====================================
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
=====================================
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
=====================================
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/4ca1e52587fffd70c7f8e2fdac9c66…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4ca1e52587fffd70c7f8e2fdac9c66…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/testsuite-rm-shell-trick] 32 commits: Handle heap allocation failure in I/O primops
by Cheng Shao (@TerrorJack) 16 Sep '25
by Cheng Shao (@TerrorJack) 16 Sep '25
16 Sep '25
Cheng Shao pushed to branch wip/testsuite-rm-shell-trick at Glasgow Haskell Compiler / GHC
Commits:
62ae97de by Duncan Coutts at 2025-09-12T13:23:33-04:00
Handle heap allocation failure in I/O primops
The current I/O managers do not use allocateMightFail, but future ones
will. To support this properly we need to be able to return to the
primop with a failure. We simply use a bool return value.
Currently however, we will just throw an exception rather than calling
the GC because that's what all the other primops do too.
For the general issue of primops invoking GC and retrying, see
https://gitlab.haskell.org/ghc/ghc/-/issues/24105
- - - - -
cb9093f5 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Move (and rename) scheduleStartSignalHandlers into RtsSignals.h
Previously it was a local helper (static) function in Schedule.c.
Rename it to startPendingSignalHandlers and deifine it as an inline
header function in RtsSignals.h. So it should still be fast.
Each (new style) I/O manager is going to need to do the same, so eliminating
the duplication now makes sense.
- - - - -
9736d44a by Duncan Coutts at 2025-09-12T13:23:33-04:00
Reduce detail in printThreadBlockage I/O blocking cases
The printThreadBlockage is used in debug tracing output.
For the cases BlockedOn{Read,Write,Delay} the output previously included
the fd that was being waited on, and the delay target wake time.
Superficially this sounds useful, but it's clearly not that useful
because it was already wrong for the Win32 non-threaded I/O manager. In
that situation it will print garbage (the async_result pointer, cast to
a fd or a time).
So given that it apparently never mattered that the information was
accurate, then it's hardly a big jump to say it doesn't matter if it is
present at all.
A good reason to remove it is that otherwise we have to make a new
API and a per-I/O manager implementation to fetch the information. And
for some I/O manager implementations, this information is not available.
It is not available in the win32 non-threaded I/O manager. And for some
future Linux ones, there is no need for the fd to be stored, so storing
it would be just extra space used for very little gain.
So the simplest thing is to just remove the detail.
- - - - -
bc0f2d5d by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add TimeoutQueue.{c,h} and corresponding tests
A data structure used to efficiently manage a collection of timeouts.
It is a priority queue based on absolute expiry time. It uses 64bit
high-precision Time for the keys. The values are normal closures which
allows for example using MVars for unblocking.
It is common in many applications for timeouts to be created and then
deleted or altered before they expire. Thus the choice of data structure
for timeouts should support this efficiently. The implementation choice
here is a leftist heap with the extra feature that it supports deleting
arbitrary elements, provided the caller retain a pointer to the element.
While the deleteMin operation takes O(log n) time, as in all heap
structures, the delete operation for arbitrary elements /typically/
takes O(1), and only O(log n) in the worst case. In practice, when
managing thousands of timeouts it can be a factor of 10 faster to delete
a random timeout queue element than to remove the minimum element. This
supports the common use case.
The plan is to use it in some of the RTS-side I/O managers to support
their timer functionality. In this use case the heap value will be an
MVar used for each timeout to unblock waiting threads.
- - - - -
d1679c9d by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add ClosureTable.{c,h} and corresponding tests
A table of pointers to closures on the GC heap with stable indexes.
It provides O(1) alloc, free and lookup. The table can be expanded
using a simple doubling strategy: in which case allocation is typically
O(1) and occasionally O(n) for overall amortised O(1). No shrinking is
used.
The table itself is heap allocated, and points to other heap objects.
As such it's necessary to use markClosureTable to ensure the table is
used as a GC root to keep the table entries alive, and maintain proper
pointers to them as the GC moves heap objects about.
It is designed to be allocated and accesses exclusively from a single
capability, enabling it to work without any locking. It is thus similar
to the StablePtr table, but per-capability which removes the need for
locking. It _should_ also provide lower GC pause times with the
non-moving GC by spending only O(1) time in markClosureTable, vs O(n)
for markStablePtrTable.
The plan is to use it in some of the I/O managers to keep track of
in-flight I/O operations (but not timers). This allows the tracking
info to be kept on the (unpinned) GC heap, and shared with Haskell
code, and by putting a pointer to the tracking information in a table,
the index remains stable and can be passed via foreign code (like the
kernel).
- - - - -
78cb8dd5 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add the StgAsyncIOOp closure type
This is intended to be used by multiple I/O managers to help with
tracking in-flight I/O operations.
It is called asynchronous because from the point of view of the RTS we
have many such operations in progress at once. From the point of view of
a Haskell thread of course it can look synchronous.
- - - - -
a2839896 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add StgAsyncIOOp and StgTimeoutQueue to tso->block_info
These will be used by new I/O managers, for threads blocked on I/O or
timeouts.
- - - - -
fdc2451c by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add a new I/O manager based on poll()
This is a proof of concept I/O manager, to show how to add new ones
neatly, using the ClosureTable and TimeoutQueue infrastructure.
It uses the old unix poll() API, so it is of course limited in
performance by that, but it should have the benefit of wide
compatibility. Also we neatly avoid a name clash with the existing
select() I/O manager.
Compared to the select() I/O manager:
1. beause it uses poll() it is not limited to 1024 file descriptors
(but it's still O(n) so don't expect great performance);
2. it should have much faster threadDelay (when using it in lots of
threads at once) because it's based on the new TimeoutQueue which is
O(log n) rather than O(n).
Some of the code related to timers/timouts is put into a shared module
rts/posix/Timeout.{h,c} since it is intended to be shared with other
similar I/O managers.
- - - - -
6c273b76 by Duncan Coutts at 2025-09-12T13:23:34-04:00
Document the I/O managers in the user guide
and note the new poll I/O manager in the release notes.
- - - - -
824fab74 by Duncan Coutts at 2025-09-12T13:23:34-04:00
Use the poll() I/O manager by default
That is, for the non-threaded RTS, prefer the poll I/O manager over the
legacy select() one, if both can be enabled.
This patch is primarily for CI testing, so we should probably remove
this patch before merging. We can change defaults later after wider
testing and feedback.
- - - - -
39392532 by Luite Stegeman at 2025-09-12T13:24:16-04:00
Support larger unboxed sums
Change known constructor encoding for sums in interfaces to use
11 bits for both the arity and the alternative (up from 8 and 6,
respectively)
- - - - -
2af12e21 by Luite Stegeman at 2025-09-12T13:24:16-04:00
Decompose padding smallest-first in Cmm toplevel data constructors
This makes each individual padding value aligned
- - - - -
418fa78f by Luite Stegeman at 2025-09-12T13:24:16-04:00
Use slots smaller than word as tag for smaller unboxed sums
This packs unboxed sums more efficiently by allowing
Word8, Word16 and Word32 for the tag field if the number of
constructors is small enough
- - - - -
8d7e912f by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Use ByteOrder rather than new Endianness
Don't introduce a duplicate datatype when the previous one is equivalent
and already used elsewhere. This avoids unnecessary translation between
the two.
- - - - -
7d378476 by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
Read Toolchain.Target files rather than 'settings'
This commit makes GHC read `lib/targets/default.target`, a file with a
serialized value of `ghc-toolchain`'s `GHC.Toolchain.Target`.
Moreover, it removes all the now-redundant entries from `lib/settings`
that are configured as part of a `Target` but were being written into
`settings`.
This makes it easier to support multiple targets from the same compiler
(aka runtime retargetability). `ghc-toolchain` can be re-run many times
standalone to produce a `Target` description for different targets, and,
in the future, GHC will be able to pick at runtime amongst different
`Target` files.
This commit only makes it read the default `Target` configured in-tree
or configured when installing the bindist.
The remaining bits of `settings` need to be moved to `Target` in follow
up commits, but ultimately they all should be moved since they are
per-target relevant.
Fixes #24212
On Windows, the constant overhead of parsing a slightly more complex
data structure causes some small-allocation tests to wiggle around 1 to
2 extra MB (1-2% in these cases).
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
T10421
T10547
T12234
T12425
T13035
T18140
T18923
T9198
TcPlugin_RewritePerf
-------------------------
- - - - -
e0780a16 by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Move TgtHasLibm to per-Target file
TargetHasLibm is now part of the per-target configuration
Towards #26227
- - - - -
8235dd8c by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Move UseLibdw to per-Target file
To support DWARF unwinding, the RTS must be built with the -f+libdw flag
and with the -DUSE_LIBDW macro definition. These flags are passed on
build by Hadrian when --enable-dwarf-unwinding is specified at configure
time.
Whether the RTS was built with support for DWARF is a per-target
property, and as such, it was moved to the per-target
GHC.Toolchain.Target.Target file.
Additionally, we keep in the target file the include and library paths
for finding libdw, since libdw should be checked at configure time (be
it by configure, or ghc-toolchain, that libdw is properly available).
Preserving the user-given include paths for libdw facilitates in the
future building the RTS on demand for a given target (if we didn't keep
that user input, we couldn't)
Towards #26227
- - - - -
d5ecf2e8 by Rodrigo Mesquita at 2025-09-12T17:57:25-04:00
ghc-toolchain: Make "Support SMP" a query on a Toolchain.Target
"Support SMP" is merely a function of target, so we can represent it as
such in `ghc-toolchain`.
Hadrian queries the Target using this predicate to determine how to
build GHC, and GHC queries the Target similarly to report under --info
whether it "Support SMP"
Towards #26227
- - - - -
e07b031a by Rodrigo Mesquita at 2025-09-12T17:57:25-04:00
ghc-toolchain: Make "tgt rts linker only supports shared libs" function on Target
Just like with "Support SMP", "target RTS linker only supports shared
libraries" is a predicate on a `Target` so we can just compute it when
necessary from the given `Target`.
Towards #26227
- - - - -
14123ee6 by Simon Peyton Jones at 2025-09-12T17:58:07-04:00
Solve forall-constraints via an implication, again
In this earlier commit:
commit 953fd8f1dc080f1c56e3a60b4b7157456949be29
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jul 21 10:06:43 2025 +0100
Solve forall-constraints immediately, or not at all
I used a all-or-nothing strategy for quantified constraints
(aka forall-constraints). But alas that fell foul of #26315,
and #26376.
So this MR goes back to solving a quantified constraint by
turning it into an implication; UNLESS we are simplifying
constraints from a SPECIALISE pragma, in which case the
all-or-nothing strategy is great. See:
Note [Solving a Wanted forall-constraint]
Other stuff in this MR:
* TcSMode becomes a record of flags, rather than an enumeration
type; much nicer.
* Some fancy footwork to avoid error messages worsening again
(The above MR made them better; we want to retain that.)
See `GHC.Tc.Errors.Ppr.pprQCOriginExtra`.
-------------------------
Metric Decrease:
T24471
-------------------------
- - - - -
e6c192e2 by Simon Peyton Jones at 2025-09-12T17:58:07-04:00
Add a test case for #26396
...same bug ast #26315
- - - - -
8f3d80ff by Luite Stegeman at 2025-09-13T08:43:09+02:00
Use mkVirtHeapOffsets for reconstructing terms in RTTI
This makes mkVirtHeapOffsets the single source of truth for
finding field offsets in closures.
- - - - -
eb389338 by Luite Stegeman at 2025-09-13T08:43:09+02:00
Sort non-pointer fields by size for more efficient packing
This sorts non-pointer fields in mkVirtHeapOffsets, always
storing the largest field first. The relative order of
equally sized fields remains unchanged.
This reduces wasted padding/alignment space in closures with
differently sized fields.
- - - - -
99b233f4 by Alison at 2025-09-13T16:51:04-04:00
ghc-heap: Fix race condition with profiling builds
Apply the same fix from Closures.hs (64fd0fac83) to Heap.hs by adding
empty imports to make way-dependent dependencies visible to `ghc -M`.
Fixes #15197, #26407
- - - - -
77deaa7a by Cheng Shao at 2025-09-14T21:29:45-04:00
hadrian: build in-tree gmp with -fvisibility=hidden
When hadrian builds in-tree gmp, it should build the shared objects
with -fvisibility=hidden. The gmp symbols are only used by bignum
logic in ghc-internal and shouldn't be exported by the ghc-internal
shared library. We should always strive to keep shared library symbol
table lean, which benefits platforms with slow dynamic linker or even
hard limits about how many symbols can be exported (e.g. macos dyld,
win32 dll and wasm dyld).
- - - - -
42a18960 by Cheng Shao at 2025-09-14T21:30:26-04:00
Revert "wasm: add brotli compression for ghci browser mode"
This reverts commit 731217ce68a1093b5f9e26a07d5bd2cdade2b352.
Benchmarks show non-negligible overhead when browser runs on the same
host, which is the majority of actual use cases.
- - - - -
e6755b9f by Cheng Shao at 2025-09-14T21:30:26-04:00
wasm: remove etag logic in ghci browser mode web server
This commit removes the etag logic in dyld script's ghci browser mode
web server. It was meant to support caching logic of wasm shared
libraries, but even if the port is manually specified to make caching
even relevant, for localhost the extra overhead around etag logic is
simply not worth it according to benchmarks.
- - - - -
ac5859b9 by sheaf at 2025-09-16T14:58:38-04:00
Add 'Outputable Natural' instance
This commit adds an Outputable instance for the Natural natural-number type,
as well as a "natural :: Natural -> SDoc" function that mirrors the existing
"integer" function.
- - - - -
d48ebc23 by Cheng Shao at 2025-09-16T14:59:18-04:00
autoconf: emit warning instead of error for FIND_PYTHON logic
This patch makes FIND_PYTHON logic emit warning instead of error, so
when the user doesn't expect to run the testsuite driver (especially
when installing a bindist), python would not be mandatory. Fixes #26347.
- - - - -
6196d4d5 by Cheng Shao at 2025-09-17T00:31:10+02: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>
- - - - -
8701e7d9 by Cheng Shao at 2025-09-17T00:34:00+02: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.
- - - - -
60c9b7c8 by Cheng Shao at 2025-09-17T00:34:05+02:00
docs: document :shell in ghci
This commit documents the :shell command in ghci.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
175 changed files:
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/StgToCmm/DataCon.hs
- compiler/GHC/StgToCmm/Layout.hs
- compiler/GHC/SysTools/BaseDir.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/ghci.rst
- docs/users_guide/runtime_control.rst
- ghc/GHCi/UI.hs
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/src/Base.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Gmp.hs
- hadrian/src/Settings/Packages.hs
- libraries/base/src/GHC/RTS/Flags.hs
- libraries/ghc-boot/GHC/Settings/Utils.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- libraries/ghc-internal/src/GHC/Internal/ResponseFile.hs
- m4/find_python.m4
- m4/fp_find_libdw.m4
- − m4/fp_settings.m4
- m4/fp_setup_windows_toolchain.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- + m4/subst_tooldir.m4
- mk/hsc2hs.in
- + rts/ClosureTable.c
- + rts/ClosureTable.h
- rts/IOManager.c
- rts/IOManager.h
- rts/IOManagerInternals.h
- rts/PrimOps.cmm
- rts/RtsSignals.h
- rts/Schedule.c
- rts/StgMiscClosures.cmm
- rts/Threads.c
- + rts/TimeoutQueue.c
- + rts/TimeoutQueue.h
- rts/configure.ac
- rts/include/rts/Constants.h
- rts/include/rts/Flags.h
- rts/include/rts/storage/Closures.h
- rts/include/rts/storage/TSO.h
- rts/include/stg/MiscClosures.h
- + rts/posix/Poll.c
- + rts/posix/Poll.h
- + rts/posix/Timeout.c
- + rts/posix/Timeout.h
- rts/rts.cabal
- testsuite/tests/backpack/should_fail/bkpfail11.stderr
- testsuite/tests/backpack/should_fail/bkpfail43.stderr
- testsuite/tests/codeGen/should_compile/T25166.stdout → testsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
- + testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
- testsuite/tests/codeGen/should_run/T13825-unit.hs
- + testsuite/tests/deriving/should_compile/T26396.hs
- testsuite/tests/deriving/should_compile/all.T
- testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- testsuite/tests/deriving/should_fail/T21302.stderr
- testsuite/tests/deriving/should_fail/T22696b.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- testsuite/tests/driver/multipleHomeUnits/all.T
- testsuite/tests/ghc-api/T20757.hs
- testsuite/tests/ghc-api/settings-escape/T24265.hs
- testsuite/tests/ghc-api/settings-escape/T24265.stderr
- + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/targets/.gitkeep
- 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/impredicative/T17332.stderr
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/perf/compiler/MultiLayerModulesDefsGhci.script
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/quantified-constraints/T19690.stderr
- testsuite/tests/quantified-constraints/T19921.stderr
- testsuite/tests/quantified-constraints/T21006.stderr
- testsuite/tests/roles/should_fail/RolesIArray.stderr
- + testsuite/tests/rts/ClosureTable.hs
- + testsuite/tests/rts/ClosureTable_c.c
- + testsuite/tests/rts/TimeoutQueue.c
- + testsuite/tests/rts/TimeoutQueue.stdout
- testsuite/tests/rts/all.T
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr
- testsuite/tests/typecheck/should_compile/T14434.hs
- + testsuite/tests/typecheck/should_compile/T26376.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T15801.stderr
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T20666.stderr
- testsuite/tests/typecheck/should_fail/T20666a.stderr
- testsuite/tests/typecheck/should_fail/T20666b.stderr
- testsuite/tests/typecheck/should_fail/T22912.stderr
- testsuite/tests/typecheck/should_fail/T23427.stderr
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
- testsuite/tests/unboxedsums/all.T
- testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs
- utils/ghc-pkg/Main.hs
- utils/ghc-pkg/ghc-pkg.cabal.in
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/ghc-toolchain.cabal
- + utils/ghc-toolchain/src/GHC/Toolchain/Library.hs
- utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
- utils/jsffi/dyld.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7d6d31cc2e89b73cb8a2c405b64401…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7d6d31cc2e89b73cb8a2c405b64401…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/no-cc-supports-tls] rts: remove obsolete CC_SUPPORTS_TLS logic
by Cheng Shao (@TerrorJack) 16 Sep '25
by Cheng Shao (@TerrorJack) 16 Sep '25
16 Sep '25
Cheng Shao pushed to branch wip/no-cc-supports-tls at Glasgow Haskell Compiler / GHC
Commits:
ead887c5 by Cheng Shao at 2025-09-17T00:18:14+02:00
rts: remove obsolete CC_SUPPORTS_TLS logic
This patch removes obsolete CC_SUPPORTS_TLS logic throughout the rts,
given __thread is now uniformly supported by C toolchains of all
platforms we currently support.
- - - - -
9 changed files:
- rts/Task.c
- rts/Task.h
- rts/configure.ac
- rts/include/rts/OSThreads.h
- rts/posix/OSThreads.c
- rts/sm/GCTDecl.h
- rts/sm/GCThread.h
- rts/sm/Storage.c
- rts/win32/OSThreads.c
Changes:
=====================================
rts/Task.c
=====================================
@@ -52,11 +52,7 @@ Mutex all_tasks_mutex;
// A thread-local-storage key that we can use to get access to the
// current thread's Task structure.
#if defined(THREADED_RTS)
-# if CC_SUPPORTS_TLS
__thread Task *my_task;
-# else
-ThreadLocalKey currentTaskKey;
-# endif
#else
Task *my_task;
#endif
@@ -75,9 +71,6 @@ initTaskManager (void)
peakWorkerCount = 0;
tasksInitialized = 1;
#if defined(THREADED_RTS)
-#if !CC_SUPPORTS_TLS
- newThreadLocalKey(¤tTaskKey);
-#endif
initMutex(&all_tasks_mutex);
#endif
}
@@ -109,9 +102,6 @@ freeTaskManager (void)
#if defined(THREADED_RTS)
closeMutex(&all_tasks_mutex);
-#if !CC_SUPPORTS_TLS
- freeThreadLocalKey(¤tTaskKey);
-#endif
#endif
tasksInitialized = 0;
=====================================
rts/Task.h
=====================================
@@ -265,12 +265,8 @@ extern uint32_t peakWorkerCount;
// A thread-local-storage key that we can use to get access to the
// current thread's Task structure.
#if defined(THREADED_RTS)
-#if CC_SUPPORTS_TLS
extern __thread Task *my_task;
#else
-extern ThreadLocalKey currentTaskKey;
-#endif
-#else
extern Task *my_task;
#endif
@@ -283,21 +279,13 @@ extern Task *my_task;
INLINE_HEADER Task *
myTask (void)
{
-#if defined(THREADED_RTS) && !CC_SUPPORTS_TLS
- return (Task*) getThreadLocalVar(¤tTaskKey);
-#else
return my_task;
-#endif
}
INLINE_HEADER void
setMyTask (Task *task)
{
-#if defined(THREADED_RTS) && !CC_SUPPORTS_TLS
- setThreadLocalVar(¤tTaskKey,task);
-#else
my_task = task;
-#endif
}
// Tasks are identified by their OS thread ID, which can be serialised
=====================================
rts/configure.ac
=====================================
@@ -234,19 +234,6 @@ AC_CHECK_FUNCS([eventfd])
AC_CHECK_FUNCS([getpid getuid raise])
-dnl ** Check for __thread support in the compiler
-AC_MSG_CHECKING(for __thread support)
-AC_COMPILE_IFELSE(
- [ AC_LANG_SOURCE([[__thread int tester = 0;]]) ],
- [
- AC_MSG_RESULT(yes)
- AC_DEFINE([CC_SUPPORTS_TLS],[1],[Define to 1 if __thread is supported])
- ],
- [
- AC_MSG_RESULT(no)
- AC_DEFINE([CC_SUPPORTS_TLS],[0],[Define to 1 if __thread is supported])
- ])
-
dnl large address space support (see rts/include/rts/storage/MBlock.h)
dnl
dnl Darwin has vm_allocate/vm_protect
=====================================
rts/include/rts/OSThreads.h
=====================================
@@ -40,7 +40,6 @@ typedef struct {
} Condition;
typedef pthread_mutex_t Mutex;
typedef pthread_t OSThreadId;
-typedef pthread_key_t ThreadLocalKey;
#define OSThreadProcAttr /* nothing */
@@ -107,7 +106,6 @@ typedef CONDITION_VARIABLE Condition;
typedef DWORD OSThreadId;
// don't be tempted to use HANDLE as the OSThreadId: there can be
// many HANDLES to a given thread, so comparison would not work.
-typedef DWORD ThreadLocalKey;
#define OSThreadProcAttr
@@ -168,7 +166,6 @@ typedef SRWLOCK Mutex;
typedef void* Condition;
typedef void* Mutex;
typedef void* OSThreadId;
-typedef void* ThreadLocalKey;
#define OSThreadProcAttr
@@ -216,14 +213,6 @@ extern bool timedWaitCondition ( Condition* pCond, Mutex* pMut, Time timeout)
extern void initMutex ( Mutex* pMut );
extern void closeMutex ( Mutex* pMut );
-//
-// Thread-local storage
-//
-void newThreadLocalKey (ThreadLocalKey *key);
-void *getThreadLocalVar (ThreadLocalKey *key);
-void setThreadLocalVar (ThreadLocalKey *key, void *value);
-void freeThreadLocalKey (ThreadLocalKey *key);
-
// Processors and affinity
void setThreadAffinity (uint32_t n, uint32_t m);
void setThreadNode (uint32_t node);
=====================================
rts/posix/OSThreads.c
=====================================
@@ -286,43 +286,6 @@ closeMutex(Mutex* pMut)
pthread_mutex_destroy(pMut);
}
-void
-newThreadLocalKey (ThreadLocalKey *key)
-{
- int r;
- if ((r = pthread_key_create(key, NULL)) != 0) {
- barf("newThreadLocalKey: %s", strerror(r));
- }
-}
-
-void *
-getThreadLocalVar (ThreadLocalKey *key)
-{
- return pthread_getspecific(*key);
- // Note: a return value of NULL can indicate that either the key
- // is not valid, or the key is valid and the data value has not
- // yet been set. We need to use the latter case, so we cannot
- // detect errors here.
-}
-
-void
-setThreadLocalVar (ThreadLocalKey *key, void *value)
-{
- int r;
- if ((r = pthread_setspecific(*key,value)) != 0) {
- barf("setThreadLocalVar: %s", strerror(r));
- }
-}
-
-void
-freeThreadLocalKey (ThreadLocalKey *key)
-{
- int r;
- if ((r = pthread_key_delete(*key)) != 0) {
- barf("freeThreadLocalKey: %s", strerror(r));
- }
-}
-
#if defined(THREADED_RTS)
static void *
=====================================
rts/sm/GCTDecl.h
=====================================
@@ -50,23 +50,10 @@ extern StgWord8 the_gc_thread[];
/* -------------------------------------------------------------------------- */
-/* Now, llvm-gcc and some older Clang compilers do not support
- __thread. So we have to fallback to the extremely slow case,
- unfortunately.
-
- Also, the iOS Clang compiler doesn't support __thread either for
- some bizarre reason, so there's not much we can do about that... */
-#if defined(CC_LLVM_BACKEND) && (CC_SUPPORTS_TLS == 0)
-#define gct ((gc_thread *)(pthread_getspecific(gctKey)))
-#define SET_GCT(to) (pthread_setspecific(gctKey, to))
-#define DECLARE_GCT ThreadLocalKey gctKey;
-
-/* -------------------------------------------------------------------------- */
-
-/* However, if we *are* using an LLVM based compiler with __thread
+/* If we *are* using an LLVM based compiler with __thread
support, then use that (since LLVM doesn't support global register
variables.) */
-#elif defined(CC_LLVM_BACKEND) && (CC_SUPPORTS_TLS == 1)
+#if defined(CC_LLVM_BACKEND)
extern __thread gc_thread* gct;
#define SET_GCT(to) gct = (to)
#define DECLARE_GCT __thread gc_thread* gct;
@@ -107,16 +94,11 @@ GCT_REG_DECL(gc_thread*, gct, REG_R1);
/* Finally, as an absolute fallback, if none of the above tests check
out but we *do* have __thread support, then use that. */
-#elif CC_SUPPORTS_TLS == 1
+#else
extern __thread gc_thread* gct;
#define SET_GCT(to) gct = (to)
#define DECLARE_GCT __thread gc_thread* gct;
-/* -------------------------------------------------------------------------- */
-
-/* Impossible! */
-#else
-#error Cannot find a way to declare the thread-local gc variable!
#endif
#endif // THREADED_RTS
=====================================
rts/sm/GCThread.h
=====================================
@@ -212,8 +212,4 @@ extern uint32_t n_gc_threads;
extern gc_thread **gc_threads;
-#if defined(THREADED_RTS) && defined(CC_LLVM_BACKEND)
-extern ThreadLocalKey gctKey;
-#endif
-
#include "EndPrivate.h"
=====================================
rts/sm/Storage.c
=====================================
@@ -326,10 +326,6 @@ void storageAddCapabilities (uint32_t from, uint32_t to)
}
}
-#if defined(THREADED_RTS) && defined(CC_LLVM_BACKEND) && (CC_SUPPORTS_TLS == 0)
- newThreadLocalKey(&gctKey);
-#endif
-
initGcThreads(from, to);
}
@@ -351,9 +347,6 @@ freeStorage (bool free_heap)
closeMutex(&sm_mutex);
#endif
stgFree(nurseries);
-#if defined(THREADED_RTS) && defined(CC_LLVM_BACKEND) && (CC_SUPPORTS_TLS == 0)
- freeThreadLocalKey(&gctKey);
-#endif
freeGcThreads();
}
=====================================
rts/win32/OSThreads.c
=====================================
@@ -87,56 +87,6 @@ osThreadIsAlive(OSThreadId id)
return (exit_code == STILL_ACTIVE);
}
-void
-newThreadLocalKey (ThreadLocalKey *key)
-{
- DWORD r;
- r = TlsAlloc();
- if (r == TLS_OUT_OF_INDEXES) {
- barf("newThreadLocalKey: out of keys");
- }
- *key = r;
-}
-
-void *
-getThreadLocalVar (ThreadLocalKey *key)
-{
- void *r;
- r = TlsGetValue(*key);
-#if defined(DEBUG)
- // r is allowed to be NULL - it can mean that either there was an
- // error or the stored value is in fact NULL.
- if (GetLastError() != NO_ERROR) {
- sysErrorBelch("getThreadLocalVar");
- stg_exit(EXIT_FAILURE);
- }
-#endif
- return r;
-}
-
-void
-setThreadLocalVar (ThreadLocalKey *key, void *value)
-{
- BOOL b;
- b = TlsSetValue(*key, value);
- if (!b) {
- sysErrorBelch("setThreadLocalVar");
- stg_exit(EXIT_FAILURE);
- }
-}
-
-void
-freeThreadLocalKey (ThreadLocalKey *key)
-{
- BOOL r;
- r = TlsFree(*key);
- if (r == 0) {
- DWORD dw = GetLastError();
- barf("freeThreadLocalKey failed: %lu", dw);
- }
-}
-
-
static unsigned
forkOS_createThreadWrapper ( void * entry )
{
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ead887c5da81ed333f6862e47755900…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ead887c5da81ed333f6862e47755900…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
16 Sep '25
Cheng Shao pushed new branch wip/no-cc-supports-tls at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/no-cc-supports-tls
You're receiving this email because of your account on gitlab.haskell.org.
1
0
16 Sep '25
Cheng Shao deleted branch wip/gmp-visibility-hidden at Glasgow Haskell Compiler / GHC
--
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Cheng Shao deleted branch wip/faster-maps at Glasgow Haskell Compiler / GHC
--
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: Add 'Outputable Natural' instance
by Marge Bot (@marge-bot) 16 Sep '25
by Marge Bot (@marge-bot) 16 Sep '25
16 Sep '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
ac5859b9 by sheaf at 2025-09-16T14:58:38-04:00
Add 'Outputable Natural' instance
This commit adds an Outputable instance for the Natural natural-number type,
as well as a "natural :: Natural -> SDoc" function that mirrors the existing
"integer" function.
- - - - -
d48ebc23 by Cheng Shao at 2025-09-16T14:59:18-04:00
autoconf: emit warning instead of error for FIND_PYTHON logic
This patch makes FIND_PYTHON logic emit warning instead of error, so
when the user doesn't expect to run the testsuite driver (especially
when installing a bindist), python would not be mandatory. Fixes #26347.
- - - - -
ea6d9927 by Cheng Shao at 2025-09-16T15:32:14-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>
- - - - -
77c8093f by Cheng Shao at 2025-09-16T15:32:14-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.
- - - - -
e1d83486 by Cheng Shao at 2025-09-16T15:32:14-04:00
docs: document :shell in ghci
This commit documents the :shell command in ghci.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
c074086d by Sylvain Henry at 2025-09-16T15:32:42-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.
- - - - -
3453d7bc by Ben Gamari at 2025-09-16T15:32:44-04:00
configure: Fix consistency between distrib and source CC check
Previously distrib/configure.ac did not
include `cc`.
Closes #26394.
- - - - -
dc2b4f21 by Oleg Grenrus at 2025-09-16T15:32:44-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.
- - - - -
4b3378b4 by Oleg Grenrus at 2025-09-16T15:32:44-04:00
Shorten in-module links in hyperlinked source
Instead of href="This.Module#ident" to just "#ident"
- - - - -
3c81595c by Oleg Grenrus at 2025-09-16T15:32:44-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.
- - - - -
4ca1e525 by Stefan Schulze Frielinghaus at 2025-09-16T15:32:45-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.
- - - - -
63 changed files:
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Unit/State.hs
- compiler/GHC/Utils/Outputable.hs
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- m4/find_python.m4
- 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/perf/compiler/MultiLayerModulesDefsGhci.script
- testsuite/tests/perf/compiler/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/19301242a2c284aa4dcff4215c604c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/19301242a2c284aa4dcff4215c604c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] autoconf: emit warning instead of error for FIND_PYTHON logic
by Marge Bot (@marge-bot) 16 Sep '25
by Marge Bot (@marge-bot) 16 Sep '25
16 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
d48ebc23 by Cheng Shao at 2025-09-16T14:59:18-04:00
autoconf: emit warning instead of error for FIND_PYTHON logic
This patch makes FIND_PYTHON logic emit warning instead of error, so
when the user doesn't expect to run the testsuite driver (especially
when installing a bindist), python would not be mandatory. Fixes #26347.
- - - - -
1 changed file:
- m4/find_python.m4
Changes:
=====================================
m4/find_python.m4
=====================================
@@ -17,7 +17,7 @@ AC_DEFUN([FIND_PYTHON],[
dnl If still not found, hard error: we require Python >= 3.7
AS_IF([test -z "$PYTHON"], [
- AC_MSG_ERROR([Python 3.7 or later is required but no python interpreter was found. Please install Python >= 3.7 and re-run configure.])
+ AC_MSG_WARN([Python 3.7 or later is required but no python interpreter was found. This is needed by the testsuite driver.])
])
dnl Query the version string (X.Y.Z) of the selected interpreter
@@ -31,10 +31,10 @@ AC_DEFUN([FIND_PYTHON],[
dnl Enforce minimum version 3.7.0
AS_IF([test -z "$PythonVersion"], [
- AC_MSG_ERROR([Failed to determine Python version for $PYTHON])
+ AC_MSG_WARN([Failed to determine Python version for $PYTHON])
])
FP_COMPARE_VERSIONS([$PythonVersion], [-lt], [3.7.0], [
- AC_MSG_ERROR([Python 3.7 or later is required, but $PYTHON reports $PythonVersion])
+ AC_MSG_WARN([Python 3.7 or later is required, but $PYTHON reports $PythonVersion])
])
dnl Canonicalise path for Windows
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d48ebc2359ec3b6c612c00ae51aca80…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d48ebc2359ec3b6c612c00ae51aca80…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
16 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
ac5859b9 by sheaf at 2025-09-16T14:58:38-04:00
Add 'Outputable Natural' instance
This commit adds an Outputable instance for the Natural natural-number type,
as well as a "natural :: Natural -> SDoc" function that mirrors the existing
"integer" function.
- - - - -
1 changed file:
- compiler/GHC/Utils/Outputable.hs
Changes:
=====================================
compiler/GHC/Utils/Outputable.hs
=====================================
@@ -39,7 +39,7 @@ module GHC.Utils.Outputable (
spaceIfSingleQuote,
isEmpty, nest,
ptext,
- int, intWithCommas, integer, word64, word, float, double, rational, doublePrec,
+ int, intWithCommas, integer, natural, word64, word, float, double, rational, doublePrec,
parens, cparen, brackets, braces, quotes, quote, quoteIfPunsEnabled,
doubleQuotes, angleBrackets,
semi, comma, colon, dcolon, space, equals, dot, vbar,
@@ -150,6 +150,7 @@ import System.IO ( Handle )
import System.FilePath
import Text.Printf
import Numeric (showFFloat)
+import Numeric.Natural (Natural)
import Data.Graph (SCC(..))
import Data.List (intersperse)
import Data.List.NonEmpty (NonEmpty (..))
@@ -684,6 +685,7 @@ docToSDoc d = SDoc (\_ -> d)
ptext :: PtrString -> SDoc
int :: IsLine doc => Int -> doc
+natural :: IsLine doc => Natural -> doc
integer :: IsLine doc => Integer -> doc
word :: Integer -> SDoc
word64 :: IsLine doc => Word64 -> doc
@@ -695,6 +697,8 @@ rational :: Rational -> SDoc
ptext s = docToSDoc $ Pretty.ptext s
{-# INLINE CONLIKE int #-}
int n = text $ show n
+{-# INLINE CONLIKE natural #-}
+natural n = text $ show n
{-# INLINE CONLIKE integer #-}
integer n = text $ show n
{-# INLINE CONLIKE float #-}
@@ -947,6 +951,9 @@ instance Outputable Int64 where
instance Outputable Int where
ppr n = int n
+instance Outputable Natural where
+ ppr n = natural n
+
instance Outputable Integer where
ppr n = integer n
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ac5859b9edb312536eb3c49337a29a0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ac5859b9edb312536eb3c49337a29a0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Oleg Grenrus pushed new branch wip/no-ws-spans at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/no-ws-spans
You're receiving this email because of your account on gitlab.haskell.org.
1
0