[Git][ghc/ghc][master] 3 commits: Use isPrint in showUnique
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2dcd4cb9 by Oleg Grenrus at 2025-09-17T04:46:41-04:00 Use isPrint in showUnique The comment say ``` -- Avoid emitting non-printable characters in pretty uniques. See #25989. ``` so let the code do exactly that. There are tags (at least : and 0 .. 9) which weren't in A .. z range. - - - - - e5dd754b by Oleg Grenrus at 2025-09-17T04:46:42-04:00 Shorten in-module links in hyperlinked source Instead of href="This.Module#ident" to just "#ident" - - - - - 63189b2c by Oleg Grenrus at 2025-09-17T04:46:42-04:00 Use showUnique in internalAnchorIdent Showing the key of Unique as a number is generally not a great idea. GHC Unique has a tag in high bits, so the raw number is unnecessarily big. So now we have ```html <a href="#l-rvgK"><span class="hs-identifier hs-var hs-var">bar</span></a> ``` instead of ```html <a href="#local-6989586621679015689"><span class="hs-identifier hs-var hs-var">bar</span></a> ``` Together with previous changes of shorter intra-module links the effect on compressed files is not huge, that is expected as we simply remove repetitive contents which pack well. ``` 12_694_206 Agda-2.9.0-docs-orig.tar.gz 12_566_065 Agda-2.9.0-docs.tar.gz ``` However when unpacked, the difference can be significant, e.g. Agda's largest module source got 5% reduction: ``` 14_230_117 Agda.Syntax.Parser.Parser.html 13_422_109 Agda.Syntax.Parser.Parser.html ``` The whole hyperlinked source code directory got similar reduction ``` 121M Agda-2.9.0-docs-orig/src 114M Agda-2.9.0-docs/src ``` For the reference, sources are about 2/3 of the generated haddocks ``` 178M Agda-2.9.0-docs-old 172M Agda-2.9.0-docs ``` so we get around 3.5% size reduction overall. Not bad for a small local changes. - - - - - 20 changed files: - compiler/GHC/Types/Unique.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs - utils/haddock/hypsrc-test/Main.hs - utils/haddock/hypsrc-test/ref/src/CPP.html - utils/haddock/hypsrc-test/ref/src/Classes.html - utils/haddock/hypsrc-test/ref/src/Constructors.html - utils/haddock/hypsrc-test/ref/src/Identifiers.html - utils/haddock/hypsrc-test/ref/src/LinkingIdentifiers.html - utils/haddock/hypsrc-test/ref/src/Literals.html - utils/haddock/hypsrc-test/ref/src/Operators.html - utils/haddock/hypsrc-test/ref/src/Polymorphism.html - utils/haddock/hypsrc-test/ref/src/PositionPragmas.html - utils/haddock/hypsrc-test/ref/src/Quasiquoter.html - utils/haddock/hypsrc-test/ref/src/Records.html - utils/haddock/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html - utils/haddock/hypsrc-test/ref/src/TemplateHaskellSplices.html - utils/haddock/hypsrc-test/ref/src/Types.html - utils/haddock/hypsrc-test/ref/src/UsingQuasiquotes.html Changes: ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -28,6 +28,7 @@ module GHC.Types.Unique ( -- ** Constructors, destructors and operations on 'Unique's hasKey, + showUnique, pprUniqueAlways, mkTag, @@ -61,7 +62,7 @@ import GHC.Utils.Word64 (intToWord64, word64ToInt) import GHC.Exts (indexCharOffAddr#, Char(..), Int(..)) import GHC.Word ( Word64 ) -import Data.Char ( chr, ord ) +import Data.Char ( chr, ord, isPrint ) import Language.Haskell.Syntax.Module.Name @@ -308,8 +309,8 @@ showUnique uniq -- Avoid emitting non-printable characters in pretty uniques. -- See #25989. tagStr - | tag < 'A' || tag > 'z' = show (ord tag) ++ "_" - | otherwise = [tag] + | not (isPrint tag) = show (ord tag) ++ "_" + | otherwise = [tag] pprUniqueAlways :: IsLine doc => Unique -> doc -- The "always" means regardless of -dsuppress-uniques ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs ===================================== @@ -80,6 +80,7 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = do nc <- freshNameCache HieFile { hie_hs_file = file + , hie_module = thisModule , hie_asts = HieASTs asts , hie_types = types , hie_hs_src = rawSrc @@ -116,7 +117,7 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = do let tokens = fmap (\tk -> tk{tkSpan = (tkSpan tk){srcSpanFile = srcSpanFile $ nodeSpan fullAst}}) tokens' -- Produce and write out the hyperlinked sources - writeUtf8File path . renderToString pretty . render' fullAst $ tokens + writeUtf8File path . renderToString pretty . render' thisModule fullAst $ tokens where dflags = ifaceDynFlags iface sDocContext = DynFlags.initSDocContext dflags Outputable.defaultUserStyle @@ -128,7 +129,7 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = do False -- lex Haddocks as comment tokens True -- produce comment tokens False -- produce position pragmas tokens - render' = render (Just srcCssFile) (Just highlightScript) srcs + render' thisModule = render thisModule (Just srcCssFile) (Just highlightScript) srcs path = srcdir > hypSrcModuleFile (ifaceMod iface) emptyHieAst fileFs = ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs ===================================== @@ -14,8 +14,8 @@ import GHC.Iface.Ext.Types import GHC.Iface.Ext.Utils (emptyNodeInfo, isEvidenceContext) import GHC.Types.Name (Name, getOccString, isInternalName, nameModule, nameUnique) import GHC.Types.SrcLoc -import GHC.Types.Unique (getKey) -import GHC.Unit.Module (ModuleName, moduleNameString) +import GHC.Types.Unique (showUnique) +import GHC.Unit.Module (Module, ModuleName, moduleNameString) import GHC.Utils.Encoding (utf8DecodeByteString) import System.FilePath.Posix ((>)) import Text.XHtml (Html, HtmlAttr, (!)) @@ -28,7 +28,9 @@ type StyleClass = String -- | Produce the HTML corresponding to a hyperlinked Haskell source render - :: Maybe FilePath + :: Module + -- ^ this module + -> Maybe FilePath -- ^ path to the CSS file -> Maybe FilePath -- ^ path to the JS file @@ -39,12 +41,12 @@ render -> [Token] -- ^ tokens to render -> Html -render mcss mjs srcs ast tokens = header mcss mjs <> body srcs ast tokens +render thisModule mcss mjs srcs ast tokens = header mcss mjs <> body thisModule srcs ast tokens -body :: SrcMaps -> HieAST PrintedType -> [Token] -> Html -body srcs ast tokens = Html.body . Html.pre $ hypsrc +body :: Module -> SrcMaps -> HieAST PrintedType -> [Token] -> Html +body thisModule srcs ast tokens = Html.body . Html.pre $ hypsrc where - hypsrc = renderWithAst srcs ast tokens + hypsrc = renderWithAst thisModule srcs ast tokens header :: Maybe FilePath -> Maybe FilePath -> Html header Nothing Nothing = Html.noHtml @@ -75,9 +77,9 @@ splitTokens ast toks = (before, during, after) -- | Turn a list of tokens into hyperlinked sources, threading in relevant link -- information from the 'HieAST'. -renderWithAst :: SrcMaps -> HieAST PrintedType -> [Token] -> Html -renderWithAst srcs Node{..} toks = anchored $ case toks of - [tok] | nodeSpan == tkSpan tok -> richToken srcs nodeInfo tok +renderWithAst :: Module -> SrcMaps -> HieAST PrintedType -> [Token] -> Html +renderWithAst thisModule srcs Node{..} toks = anchored $ case toks of + [tok] | nodeSpan == tkSpan tok -> richToken thisModule srcs nodeInfo tok -- NB: the GHC lexer lexes backquoted identifiers and parenthesized operators -- as multiple tokens. -- @@ -92,6 +94,7 @@ renderWithAst srcs Node{..} toks = anchored $ case toks of | realSrcSpanStart s1 == realSrcSpanStart nodeSpan , realSrcSpanEnd s2 == realSrcSpanEnd nodeSpan -> richToken + thisModule srcs nodeInfo ( Token @@ -104,6 +107,7 @@ renderWithAst srcs Node{..} toks = anchored $ case toks of | realSrcSpanStart s1 == realSrcSpanStart nodeSpan , realSrcSpanEnd s2 == realSrcSpanEnd nodeSpan -> richToken + thisModule srcs nodeInfo ( Token @@ -118,7 +122,7 @@ renderWithAst srcs Node{..} toks = anchored $ case toks of go _ [] = mempty go [] xs = foldMap renderToken xs go (cur : rest) xs = - foldMap renderToken before <> renderWithAst srcs cur during <> go rest after + foldMap renderToken before <> renderWithAst thisModule srcs cur during <> go rest after where (before, during, after) = splitTokens cur xs anchored c = Map.foldrWithKey anchorOne c (nodeIdentifiers nodeInfo) @@ -137,8 +141,8 @@ renderToken Token{..} tokenSpan = Html.thespan (Html.toHtml tkValue') -- | Given information about the source position of definitions, render a token -richToken :: SrcMaps -> NodeInfo PrintedType -> Token -> Html -richToken srcs details Token{..} +richToken :: Module -> SrcMaps -> NodeInfo PrintedType -> Token -> Html +richToken thisModule srcs details Token{..} | tkType == TkSpace = renderSpace (srcSpanStartLine tkSpan) tkValue' | otherwise = annotate details $ linked content where @@ -155,7 +159,7 @@ richToken srcs details Token{..} -- If we have name information, we can make links linked = case identDet of - Just (n, _) -> hyperlink srcs n + Just (n, _) -> hyperlink thisModule srcs n Nothing -> id -- | Remove CRLFs from source @@ -250,11 +254,11 @@ externalAnchorIdent :: Name -> String externalAnchorIdent = hypSrcNameUrl internalAnchorIdent :: Name -> String -internalAnchorIdent = ("local-" ++) . show . getKey . nameUnique +internalAnchorIdent = ("l-" ++) . showUnique . nameUnique -- | Generate the HTML hyperlink for an identifier -hyperlink :: SrcMaps -> Identifier -> Html -> Html -hyperlink (srcs, srcs') ident = case ident of +hyperlink :: Module -> SrcMaps -> Identifier -> Html -> Html +hyperlink thisModule (srcs, srcs') ident = case ident of Right name | isInternalName name -> internalHyperlink name | otherwise -> externalNameHyperlink name @@ -270,7 +274,7 @@ hyperlink (srcs, srcs') ident = case ident of externalNameHyperlink name content = case Map.lookup mdl srcs of Just SrcLocal -> Html.anchor content - ! [Html.href $ hypSrcModuleNameUrl mdl name] + ! [Html.href $ hypSrcModuleNameUrl' thisModule mdl name] Just (SrcExternal path) -> let hyperlinkUrl = hypSrcModuleUrlToNameFormat $ makeHyperlinkUrl path in Html.anchor content ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs ===================================== @@ -9,6 +9,7 @@ module Haddock.Backends.Hyperlinker.Utils , hypSrcNameUrl , hypSrcLineUrl , hypSrcModuleNameUrl + , hypSrcModuleNameUrl' , hypSrcModuleLineUrl , hypSrcModuleUrlFormat , hypSrcModuleNameUrlFormat @@ -71,6 +72,12 @@ hypSrcLineUrl line = "line-" ++ show line hypSrcModuleNameUrl :: Module -> Name -> String hypSrcModuleNameUrl mdl name = hypSrcModuleUrl mdl ++ "#" ++ hypSrcNameUrl name +{-# INLINE hypSrcModuleNameUrl' #-} +hypSrcModuleNameUrl' :: Module -> Module -> Name -> String +hypSrcModuleNameUrl' this_mdl mdl name + | this_mdl == mdl = "#" ++ hypSrcNameUrl name + | otherwise = hypSrcModuleUrl mdl ++ "#" ++ hypSrcNameUrl name + {-# INLINE hypSrcModuleLineUrl #-} hypSrcModuleLineUrl :: Module -> Int -> String hypSrcModuleLineUrl mdl line = hypSrcModuleUrl mdl ++ "#" ++ hypSrcLineUrl line ===================================== utils/haddock/hypsrc-test/Main.hs ===================================== @@ -22,9 +22,9 @@ checkConfig = CheckConfig where strip _ = fixPaths . stripAnchors' . stripLinks' . stripIds' . stripFooter - stripLinks' = stripLinksWhen $ \href -> "#local-" `isPrefixOf` href - stripAnchors' = stripAnchorsWhen $ \name -> "local-" `isPrefixOf` name - stripIds' = stripIdsWhen $ \name -> "local-" `isPrefixOf` name + stripLinks' = stripLinksWhen $ \href -> "#l-" `isPrefixOf` href + stripAnchors' = stripAnchorsWhen $ \name -> "l-" `isPrefixOf` name + stripIds' = stripIdsWhen $ \name -> "l-" `isPrefixOf` name -- One-shot hyperlinked source links to other modules as if they are in another package fixPaths = fixAttrValueWhen "href" (drop 7) ("../src/" `isPrefixOf`) ===================================== utils/haddock/hypsrc-test/ref/src/CPP.html ===================================== @@ -45,7 +45,7 @@ ><span id="line-7" ></span ><a href="#foo" ><span class="hs-identifier hs-type" >foo</span ><span class="annottext" >foo :: String <a href="#foo" ><span class="hs-identifier hs-var hs-var" >foo</span ><span id="line-14" ></span ><a href="#bar" ><span class="hs-identifier hs-type" >bar</span ><span class="annottext" >bar :: String <a href="#bar" ><span class="hs-identifier hs-var hs-var" >bar</span ><span id="line-26" ></span ><a href="#baz" ><span class="hs-identifier hs-type" >baz</span ><span class="annottext" >baz :: String <a href="#baz" ><span class="hs-identifier hs-var hs-var" >baz</span > </span ><span id="Foo" ><a href="#Foo" ><span class="hs-identifier hs-var" >Foo</span > </span ><span id="bar" ><a href="#bar" ><span class="hs-identifier hs-type" >bar</span > </span ><span id="baz" ><a href="#baz" ><span class="hs-identifier hs-type" >baz</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >bar :: Int -> Int <a href="#bar" ><span class="hs-identifier hs-var hs-var hs-var" >bar</span ><span class="annottext" >baz :: Int -> (Int, Int) <a href="#baz" ><span class="hs-identifier hs-var hs-var hs-var" >baz</span > </span ><span id="" ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >bar :: [a] -> Int <a href="#bar" ><span class="hs-identifier hs-var hs-var hs-var" >bar</span ><span class="annottext" >baz :: Int -> ([a], [a]) <a href="#baz" ><span class="hs-identifier hs-var hs-var hs-var" >baz</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span > </span ><span id="Foo%27" ><a href="#Foo%27" ><span class="hs-identifier hs-var" >Foo'</span > </span ><span id="quux" ><a href="#quux" ><span class="hs-identifier hs-type" >quux</span > </span ><span id="" ><a href="#quux" ><span class="hs-identifier hs-var hs-var" >quux</span >[a] -> a forall a. Foo' a => [a] -> a <a href="#norf" ><span class="hs-identifier hs-var" >norf</span > </span ><span id="norf" ><a href="#norf" ><span class="hs-identifier hs-type" >norf</span > </span ><span id="" ><a href="#norf" ><span class="hs-identifier hs-var hs-var" >norf</span >(a, a) -> a forall a. Foo' a => (a, a) -> a <a href="#quux" ><span class="hs-identifier hs-var" >quux</span >Int -> (a, a) forall a. Foo a => Int -> (a, a) <a href="#baz" ><span class="hs-identifier hs-var" >baz</span >a -> Int forall a. Foo a => a -> Int <a href="#bar" ><span class="hs-identifier hs-var" >bar</span > </span ><span id="" ><a href="#Foo%27" ><span class="hs-identifier hs-type" >Foo'</span ><span class="annottext" >norf :: [Int] -> Int <a href="#norf" ><span class="hs-identifier hs-var hs-var hs-var" >norf</span ><span id="" ><span id="" ><a href="#Foo%27" ><span class="hs-identifier hs-type" >Foo'</span ><span class="annottext" >quux :: ([a], [a]) -> [a] <a href="#quux" ><span class="hs-identifier hs-var hs-var hs-var" >quux</span > </span ><span id="Plugh" ><a href="#Plugh" ><span class="hs-identifier hs-var" >Plugh</span > </span ><span id="plugh" ><a href="#plugh" ><span class="hs-identifier hs-type" >plugh</span ><span > </span ><a href="#Plugh" ><span class="hs-identifier hs-type" >Plugh</span ><span class="annottext" >plugh :: forall a b. Either a a -> Either b b -> Either (a -> b) (b -> a) <a href="#plugh" ><span class="hs-identifier hs-var hs-var hs-var" >plugh</span ><span > </span ><a href="#plugh" ><span class="hs-identifier hs-var" >plugh</span ><span > </span ><a href="#plugh" ><span class="hs-identifier hs-var" >plugh</span ><span > </span ><a href="#plugh" ><span class="hs-identifier hs-var" >plugh</span > </span ><span id="Foo" ><a href="#Foo" ><span class="hs-identifier hs-var" >Foo</span > </span ><span id="Bar" ><a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span > </span ><span id="Baz" ><a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span > </span ><span id="Quux" ><a href="#Quux" ><span class="hs-identifier hs-var" >Quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span > </span ><span id="Norf" ><a href="#Norf" ><span class="hs-identifier hs-var" >Norf</span > </span ><span id="Norf" ><a href="#Norf" ><span class="hs-identifier hs-var" >Norf</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="hs-special" >[</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span id="line-13" ></span ><a href="#bar" ><span class="hs-identifier hs-type" >bar</span ><span > </span ><a href="#baz" ><span class="hs-identifier hs-type" >baz</span ><span > </span ><a href="#quux" ><span class="hs-identifier hs-type" >quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >bar :: Foo <a href="#bar" ><span class="hs-identifier hs-var hs-var" >bar</span ><span class="annottext" >Foo <a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span ><span class="annottext" >baz :: Foo <a href="#baz" ><span class="hs-identifier hs-var hs-var" >baz</span ><span class="annottext" >Foo <a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span ><span class="annottext" >quux :: Foo <a href="#quux" ><span class="hs-identifier hs-var hs-var" >quux</span ><span class="annottext" >Foo -> Int -> Foo <a href="#Quux" ><span class="hs-identifier hs-var" >Quux</span ><span class="annottext" >Foo <a href="#quux" ><span class="hs-identifier hs-var" >quux</span ><span id="line-19" ></span ><a href="#unfoo" ><span class="hs-identifier hs-type" >unfoo</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >unfoo :: Foo -> Int <a href="#unfoo" ><span class="hs-identifier hs-var hs-var" >unfoo</span ><span class="annottext" >Foo <a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span ><span id="line-21" ></span ><a href="#unfoo" ><span class="hs-identifier hs-var" >unfoo</span ><span class="annottext" >Foo <a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span ><span id="line-22" ></span ><a href="#unfoo" ><span class="hs-identifier hs-var" >unfoo</span ><span class="hs-special" >(</span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span class="annottext" >Foo -> Int <a href="#unfoo" ><span class="hs-identifier hs-var" >unfoo</span ><span id="line-25" ></span ><a href="#unnorf" ><span class="hs-identifier hs-type" >unnorf</span ><span > </span ><a href="#Norf" ><span class="hs-identifier hs-type" >Norf</span ><span class="hs-special" >[</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >unnorf :: Norf -> [Foo] <a href="#unnorf" ><span class="hs-identifier hs-var hs-var" >unnorf</span ><span class="hs-special" >(</span ><a href="#Norf" ><span class="hs-identifier hs-type" >Norf</span ><span class="annottext" >Foo <a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span ><span class="annottext" >Foo <a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span ><span id="line-27" ></span ><a href="#unnorf" ><span class="hs-identifier hs-var" >unnorf</span ><span class="hs-special" >(</span ><a href="#Norf" ><span class="hs-identifier hs-type" >Norf</span ><span class="annottext" >Foo <a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span ><span class="annottext" >Foo <a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span ><span id="line-28" ></span ><a href="#unnorf" ><span class="hs-identifier hs-var" >unnorf</span ><span id="line-31" ></span ><a href="#unnorf%27" ><span class="hs-identifier hs-type" >unnorf'</span ><span > </span ><a href="#Norf" ><span class="hs-identifier hs-type" >Norf</span ><span class="annottext" >unnorf' :: Norf -> Int <a href="#unnorf%27" ><span class="hs-identifier hs-var hs-var" >unnorf'</span ><span class="hs-special" >(</span ><a href="#Norf" ><span class="hs-identifier hs-type" >Norf</span ><span class="hs-special" >(</span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span class="hs-special" >(</span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span class="annottext" >Foo -> Int <a href="#unfoo" ><span class="hs-identifier hs-var" >unfoo</span ><span class="annottext" >Foo -> Int <a href="#unfoo" ><span class="hs-identifier hs-var" >unfoo</span ><span class="annottext" >Foo -> Int <a href="#unfoo" ><span class="hs-identifier hs-var" >unfoo</span ><span class="annottext" >Foo -> Int <a href="#unfoo" ><span class="hs-identifier hs-var" >unfoo</span ><span class="annottext" >Foo -> Int <a href="#unfoo" ><span class="hs-identifier hs-var" >unfoo</span ><span class="annottext" >Norf -> [Foo] <a href="#unnorf" ><span class="hs-identifier hs-var" >unnorf</span ><span id="line-5" ></span ><a href="#foo" ><span class="hs-identifier hs-type" >foo</span ><span > </span ><a href="#bar" ><span class="hs-identifier hs-type" >bar</span ><span > </span ><a href="#baz" ><span class="hs-identifier hs-type" >baz</span ><span class="annottext" >foo :: Int -> Int -> Int <a href="#foo" ><span class="hs-identifier hs-var hs-var" >foo</span ><span class="annottext" >Int -> Int -> Int <a href="#bar" ><span class="hs-identifier hs-var" >bar</span ><span class="annottext" >bar :: Int -> Int -> Int <a href="#bar" ><span class="hs-identifier hs-var hs-var" >bar</span ><span class="annottext" >Int -> Int -> Int <a href="#baz" ><span class="hs-identifier hs-var" >baz</span ><span class="annottext" >baz :: Int -> Int -> Int <a href="#baz" ><span class="hs-identifier hs-var hs-var" >baz</span ><span id="line-10" ></span ><a href="#quux" ><span class="hs-identifier hs-type" >quux</span ><span class="annottext" >quux :: Int -> Int <a href="#quux" ><span class="hs-identifier hs-var hs-var" >quux</span ><span class="annottext" >Int -> Int -> Int <a href="#foo" ><span class="hs-identifier hs-var" >foo</span ><span class="annottext" >Int -> Int -> Int <a href="#bar" ><span class="hs-identifier hs-var" >bar</span ><span class="annottext" >Int -> Int -> Int <a href="#bar" ><span class="hs-identifier hs-var" >bar</span ><span id="line-13" ></span ><a href="#norf" ><span class="hs-identifier hs-type" >norf</span ><span class="annottext" >norf :: Int -> Int -> Int -> Int <a href="#norf" ><span class="hs-identifier hs-var hs-var" >norf</span ><span class="annottext" >Int -> Int <a href="#quux" ><span class="hs-identifier hs-var" >quux</span ><span class="annottext" >Int -> Int <a href="#quux" ><span class="hs-identifier hs-var" >quux</span ><span class="annottext" >Int -> Int <a href="#quux" ><span class="hs-identifier hs-var" >quux</span ><span class="annottext" >Int -> Int -> Int -> Int <a href="#norf" ><span class="hs-identifier hs-var" >norf</span ><span id="line-21" ></span ><a href="#main" ><span class="hs-identifier hs-type" >main</span ><span class="annottext" >main :: IO () <a href="#main" ><span class="hs-identifier hs-var hs-var" >main</span ><span class="annottext" >Int -> Int -> Int <a href="#foo" ><span class="hs-identifier hs-var" >foo</span ><span class="annottext" >Int -> Int <a href="#quux" ><span class="hs-identifier hs-var" >quux</span ><span class="annottext" >Int -> Int -> Int -> Int <a href="#norf" ><span class="hs-identifier hs-var" >Identifiers.norf</span ><span id="line-9" ></span ><a href="#ident" ><span class="hs-identifier hs-type" >ident</span ><span class="annottext" >ident :: Int -> Int -> Int <a href="#ident" ><span class="hs-operator hs-var hs-var" >`ident`</span ><span class="annottext" >Int -> Int -> Int <a href="#ident" ><span class="hs-operator hs-var" >`ident`</span ><span class="annottext" >Int -> Int -> Int <a href="#ident" ><span class="hs-operator hs-var" >`LinkingIdentifiers.ident`</span ><span id="line-11" ></span ><a href="#ident" ><span class="hs-identifier hs-var" >ident</span ><span class="annottext" >Int -> Int -> Int <a href="#ident" ><span class="hs-identifier hs-var" >ident</span ><span class="annottext" >Int -> Int -> Int <a href="#ident" ><span class="hs-identifier hs-var" >LinkingIdentifiers.ident</span ><span id="line-13" ></span ><a href="#%2B%2B%3A%2B%2B" ><span class="hs-operator hs-type" >(++:++)</span ><span class="annottext" >++:++ :: Int -> Int -> Int <a href="#%2B%2B%3A%2B%2B" ><span class="hs-operator hs-var hs-var" >++:++</span ><span class="annottext" >Int -> Int -> Int <a href="#%2B%2B%3A%2B%2B" ><span class="hs-operator hs-var" >++:++</span ><span class="annottext" >Int -> Int -> Int <a href="#%2B%2B%3A%2B%2B" ><span class="hs-operator hs-var" >LinkingIdentifiers.++:++</span ><span id="line-15" ></span ><a href="#%2B%2B%3A%2B%2B" ><span class="hs-operator hs-var" >(++:++)</span ><span class="annottext" >Int -> Int -> Int <a href="#%2B%2B%3A%2B%2B" ><span class="hs-operator hs-var" >(++:++)</span ><span class="annottext" >Int -> Int -> Int <a href="#%2B%2B%3A%2B%2B" ><span class="hs-operator hs-var" >(LinkingIdentifiers.++:++)</span ><span id="line-5" ></span ><a href="#str" ><span class="hs-identifier hs-type" >str</span ><span class="annottext" >str :: String <a href="#str" ><span class="hs-identifier hs-var hs-var" >str</span ></span ><span id="" ><a href="#num" ><span class="hs-identifier hs-type" >num</span ><span class="annottext" >num :: forall a. Num a => a <a href="#num" ><span class="hs-identifier hs-var hs-var" >num</span ></span ><span id="" ><a href="#frac" ><span class="hs-identifier hs-type" >frac</span ><span class="annottext" >frac :: forall a. Fractional a => a <a href="#frac" ><span class="hs-identifier hs-var hs-var" >frac</span ></span ><span id="" ><a href="#list" ><span class="hs-identifier hs-type" >list</span ><span class="annottext" >list :: forall a. [[[[a]]]] <a href="#list" ><span class="hs-identifier hs-var hs-var" >list</span ><span id="line-17" ></span ><a href="#pair" ><span class="hs-identifier hs-type" >pair</span ><span class="annottext" >pair :: ((), ((), (), ()), ()) <a href="#pair" ><span class="hs-identifier hs-var hs-var" >pair</span ></span ><span id="" ><a href="#%2B%2B%2B" ><span class="hs-operator hs-type" >(+++)</span ><span class="annottext" >+++ :: forall a. [a] -> [a] -> [a] <a href="#%2B%2B%2B" ><span class="hs-operator hs-var hs-var" >+++</span ></span ><span id="" ><a href="#%24%24%24" ><span class="hs-operator hs-type" >($$$)</span ><span class="annottext" >$$$ :: forall a. [a] -> [a] -> [a] <a href="#%24%24%24" ><span class="hs-operator hs-var hs-var" >$$$</span >[a] -> [a] -> [a] forall a. [a] -> [a] -> [a] <a href="#%2B%2B%2B" ><span class="hs-operator hs-var" >+++</span ></span ><span id="" ><a href="#%2A%2A%2A" ><span class="hs-operator hs-type" >(***)</span ><span class="annottext" >*** :: forall a. [a] -> [a] -> [a] <a href="#%2A%2A%2A" ><span class="hs-operator hs-var hs-var" >(***)</span ><span id="line-12" ></span ><a href="#%2A%2A%2A" ><span class="hs-operator hs-var" >(***)</span >[a] -> [a] -> [a] forall a. [a] -> [a] -> [a] <a href="#%2B%2B%2B" ><span class="hs-operator hs-var" >+++</span >[a] -> [a] -> [a] forall a. [a] -> [a] -> [a] <a href="#%2A%2A%2A" ><span class="hs-operator hs-var" >***</span ></span ><span id="" ><a href="#%2A%2F%5C%2A" ><span class="hs-operator hs-type" >(*/\*)</span ><span class="annottext" >*/\* :: forall a. [[a]] -> [a] -> [a] <a href="#%2A%2F%5C%2A" ><span class="hs-operator hs-var hs-var" >*/\*</span >[a] -> [a] -> [a] forall a. [a] -> [a] -> [a] <a href="#%2A%2A%2A" ><span class="hs-operator hs-var" >***</span ></span ><span id="" ><a href="#%2A%2A%2F%5C%2A%2A" ><span class="hs-operator hs-type" >(**/\**)</span ><span class="annottext" >**/\** :: forall a. [[a]] -> [[a]] -> [[a]] <a href="#%2A%2A%2F%5C%2A%2A" ><span class="hs-operator hs-var hs-var" >**/\**</span >[[a]] -> [a] -> [a] forall a. [[a]] -> [a] -> [a] <a href="#%2A%2F%5C%2A" ><span class="hs-operator hs-var" >(*/\*)</span >[[a]] -> [[a]] -> [[a]] forall a. [a] -> [a] -> [a] <a href="#%2B%2B%2B" ><span class="hs-operator hs-var" >+++</span >[[a]] -> [[a]] -> [[a]] forall a. [a] -> [a] -> [a] <a href="#%24%24%24" ><span class="hs-operator hs-var" >$$$</span ><span id="" ><span id="" ><a href="#%23.%23" ><span class="hs-operator hs-type" >(#.#)</span ><span class="annottext" >#.# :: forall a b c. a -> b -> c -> (a, b) <a href="#%23.%23" ><span class="hs-operator hs-var hs-var" >#.#</span ></span ><span id="" ><a href="#foo" ><span class="hs-identifier hs-type" >foo</span ><span class="annottext" >foo :: forall a. a -> a -> a <a href="#foo" ><span class="hs-identifier hs-var hs-var" >foo</span ><span id="line-12" ></span ><a href="#foo%27" ><span class="hs-identifier hs-type" >foo'</span ><span class="annottext" >foo' :: forall a. a -> a -> a <a href="#foo%27" ><span class="hs-identifier hs-var hs-var" >foo'</span ><span id="" ><span id="" ><a href="#bar" ><span class="hs-identifier hs-type" >bar</span ><span class="annottext" >bar :: forall a b. a -> b -> (a, b) <a href="#bar" ><span class="hs-identifier hs-var hs-var" >bar</span ><span id="line-18" ></span ><a href="#bar%27" ><span class="hs-identifier hs-type" >bar'</span ><span class="annottext" >bar' :: forall a b. a -> b -> (a, b) <a href="#bar%27" ><span class="hs-identifier hs-var hs-var" >bar'</span ><span id="" ><span id="" ><a href="#baz" ><span class="hs-identifier hs-type" >baz</span ><span class="annottext" >baz :: forall a b. a -> (a -> [a -> a] -> b) -> b <a href="#baz" ><span class="hs-identifier hs-var hs-var" >baz</span ><span id="line-24" ></span ><a href="#baz%27" ><span class="hs-identifier hs-type" >baz'</span ><span class="annottext" >baz' :: forall a b. a -> (a -> [a -> a] -> b) -> b <a href="#baz%27" ><span class="hs-identifier hs-var hs-var" >baz'</span ></span ><span id="" ><a href="#quux" ><span class="hs-identifier hs-type" >quux</span ><span class="annottext" >quux :: forall a. a -> (forall a. a -> a) -> a <a href="#quux" ><span class="hs-identifier hs-var hs-var" >quux</span ><span id="line-30" ></span ><a href="#quux%27" ><span class="hs-identifier hs-type" >quux'</span ><span class="annottext" >quux' :: forall a. a -> (forall a. a -> a) -> a <a href="#quux%27" ><span class="hs-identifier hs-var hs-var" >quux'</span ></span ><span id="" ><a href="#num" ><span class="hs-identifier hs-type" >num</span ><span class="annottext" >num :: forall a. Num a => a -> a -> a <a href="#num" ><span class="hs-identifier hs-var hs-var" >num</span ><span id="line-37" ></span ><a href="#num%27" ><span class="hs-identifier hs-type" >num'</span ><span class="annottext" >num' :: forall a. Num a => a -> a -> a <a href="#num%27" ><span class="hs-identifier hs-var hs-var" >num'</span ><span id="" ><span id="" ><a href="#eq" ><span class="hs-identifier hs-type" >eq</span ><span class="annottext" >eq :: forall a b. (Eq a, Eq b) => [a] -> [b] -> (a, b) <a href="#eq" ><span class="hs-identifier hs-var hs-var" >eq</span ><span id="line-43" ></span ><a href="#eq%27" ><span class="hs-identifier hs-type" >eq'</span ><span class="annottext" >eq' :: forall a b. (Eq a, Eq b) => [a] -> [b] -> (a, b) <a href="#eq%27" ><span class="hs-identifier hs-var hs-var" >eq'</span ><span id="" ><span id="" ><a href="#mon" ><span class="hs-identifier hs-type" >mon</span ><span class="annottext" >mon :: forall (m :: * -> *) a. Monad m => (a -> m a) -> m a <a href="#mon" ><span class="hs-identifier hs-var hs-var" >mon</span ><span id="line-49" ></span ><a href="#mon%27" ><span class="hs-identifier hs-type" >mon'</span ><span class="annottext" >mon' :: forall (m :: * -> *) a. Monad m => (a -> m a) -> m a <a href="#mon%27" ><span class="hs-identifier hs-var hs-var" >mon'</span ></span ><span id="" ><a href="#norf" ><span class="hs-identifier hs-type" >norf</span ><span class="annottext" >norf :: forall a. a -> (forall a. Ord a => a -> a) -> a <a href="#norf" ><span class="hs-identifier hs-var hs-var" >norf</span ><span id="line-56" ></span ><a href="#norf%27" ><span class="hs-identifier hs-type" >norf'</span ><span class="annottext" >norf' :: forall a. a -> (forall a. Ord a => a -> a) -> a <a href="#norf%27" ><span class="hs-identifier hs-var hs-var" >norf'</span ><span id="line-60" ></span ><a href="#plugh" ><span class="hs-identifier hs-type" >plugh</span ><span class="annottext" >plugh :: forall a. a -> a <a href="#plugh" ><span class="hs-identifier hs-var hs-var" >plugh</span ><span id="line-63" ></span ><a href="#thud" ><span class="hs-identifier hs-type" >thud</span ><span class="annottext" >thud :: forall a b. (a -> b) -> a -> (a, b) <a href="#thud" ><span class="hs-identifier hs-var hs-var" >thud</span ><span id="line-9" ></span ><a href="#foo" ><span class="hs-identifier hs-type" >foo</span ><span class="annottext" >foo :: String <a href="#foo" ><span class="hs-identifier hs-var hs-var" >foo</span ><span class="annottext" >String <a href="#bar" ><span class="hs-identifier hs-var" >bar</span ><span id="line-24" ></span ><a href="#bar" ><span class="hs-identifier hs-type" >bar</span ><span class="annottext" >bar :: String <a href="#bar" ><span class="hs-identifier hs-var hs-var" >bar</span ><span class="annottext" >String <a href="#foo" ><span class="hs-identifier hs-var" >foo</span ><span > </span ><a href="#string" ><span class="hs-identifier" >string</span ><span id="line-8" ></span ><a href="#string" ><span class="hs-identifier hs-type" >string</span ><span class="annottext" >string :: QuasiQuoter <a href="#string" ><span class="hs-identifier hs-var hs-var" >string</span > </span ><span id="Point" ><a href="#Point" ><span class="hs-identifier hs-var" >Point</span > </span ><span id="Point" ><a href="#Point" ><span class="hs-identifier hs-var" >Point</span ><span class="annottext" >Point -> Int <a href="#x" ><span class="hs-identifier hs-var hs-var" >x</span ><span class="annottext" >Point -> Int <a href="#y" ><span class="hs-identifier hs-var hs-var" >y</span ><span id="line-15" ></span ><a href="#point" ><span class="hs-identifier hs-type" >point</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span class="annottext" >point :: Int -> Int -> Point <a href="#point" ><span class="hs-identifier hs-var hs-var" >point</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span class="annottext" >x :: Int <a href="#x" ><span class="hs-identifier hs-var" >x</span ><span class="annottext" >y :: Int <a href="#y" ><span class="hs-identifier hs-var" >y</span ><span id="line-19" ></span ><a href="#lengthSqr" ><span class="hs-identifier hs-type" >lengthSqr</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span class="annottext" >lengthSqr :: Point -> Int <a href="#lengthSqr" ><span class="hs-identifier hs-var hs-var" >lengthSqr</span ><span class="hs-special" >(</span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span class="annottext" >x :: Point -> Int <a href="#x" ><span class="hs-identifier hs-var" >x</span ><span class="annottext" >y :: Point -> Int <a href="#y" ><span class="hs-identifier hs-var" >y</span ><span id="line-22" ></span ><a href="#lengthSqr%27" ><span class="hs-identifier hs-type" >lengthSqr'</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span class="annottext" >lengthSqr' :: Point -> Int <a href="#lengthSqr%27" ><span class="hs-identifier hs-var hs-var" >lengthSqr'</span ><span class="hs-special" >(</span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><a href="#x" ><span class="hs-identifier hs-var hs-var" >x</span ><a href="#y" ><span class="hs-identifier hs-var hs-var" >y</span ><span id="line-26" ></span ><a href="#translateX" ><span class="hs-identifier hs-type" >translateX</span ><span > </span ><a href="#translateY" ><span class="hs-identifier hs-type" >translateY</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span class="annottext" >translateX :: Point -> Int -> Point <a href="#translateX" ><span class="hs-identifier hs-var hs-var" >translateX</span ><span > </span ><a href="#x" ><span class="hs-identifier hs-var" >x</span ><span > </span ><a href="#x" ><span class="hs-identifier hs-var" >x</span ><span class="annottext" >translateY :: Point -> Int -> Point <a href="#translateY" ><span class="hs-identifier hs-var hs-var" >translateY</span ><span > </span ><a href="#y" ><span class="hs-identifier hs-var" >y</span ><span > </span ><a href="#y" ><span class="hs-identifier hs-var" >y</span ><span id="line-30" ></span ><a href="#translate" ><span class="hs-identifier hs-type" >translate</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><span class="annottext" >translate :: Int -> Int -> Point -> Point <a href="#translate" ><span class="hs-identifier hs-var hs-var" >translate</span ><span > </span ><a href="#Point" ><span class="hs-identifier hs-type" >Point</span ><a href="#x" ><span class="hs-glyph hs-var hs-var hs-var hs-var" >..</span ><span > </span ><a href="#x" ><span class="hs-identifier hs-var" >x</span ><span > </span ><a href="#y" ><span class="hs-identifier hs-var" >y</span ><span id="line-8" ></span ><a href="#aDecl" ><span class="hs-identifier hs-type" >aDecl</span ><span class="annottext" >aDecl :: DecsQ <a href="#aDecl" ><span class="hs-identifier hs-var hs-var" >aDecl</span ><span class="annottext" >TypeQ <a href="#aType" ><span class="hs-identifier hs-var" >aType</span ><span class="annottext" >PatQ <a href="#aPattern" ><span class="hs-identifier hs-var" >aPattern</span ><span class="annottext" >ExpQ <a href="#anExpression" ><span class="hs-identifier hs-var" >anExpression</span ><span id="line-14" ></span ><a href="#aPattern" ><span class="hs-identifier hs-type" >aPattern</span ><span class="annottext" >aPattern :: PatQ <a href="#aPattern" ><span class="hs-identifier hs-var hs-var" >aPattern</span ><span class="annottext" >PatQ <a href="#aNumberPattern" ><span class="hs-identifier hs-var" >aNumberPattern</span ><span id="line-23" ></span ><a href="#aNumberPattern" ><span class="hs-identifier hs-type" >aNumberPattern</span ><span class="annottext" >aNumberPattern :: PatQ <a href="#aNumberPattern" ><span class="hs-identifier hs-var hs-var" >aNumberPattern</span ><span id="line-28" ></span ><a href="#anExpression" ><span class="hs-identifier hs-type" >anExpression</span ><span > </span ><a href="#anExpression2" ><span class="hs-identifier hs-type" >anExpression2</span ><span class="annottext" >anExpression :: ExpQ <a href="#anExpression" ><span class="hs-identifier hs-var hs-var" >anExpression</span ><span class="annottext" >ExpQ <a href="#anExpression2" ><span class="hs-identifier hs-var" >anExpression2</span ><span class="annottext" >anExpression2 :: ExpQ <a href="#anExpression2" ><span class="hs-identifier hs-var hs-var" >anExpression2</span ><span id="line-34" ></span ><a href="#aType" ><span class="hs-identifier hs-type" >aType</span ><span class="annottext" >aType :: TypeQ <a href="#aType" ><span class="hs-identifier hs-var hs-var" >aType</span ><span id="line-39" ></span ><a href="#typedExpr1" ><span class="hs-identifier hs-type" >typedExpr1</span ><span class="annottext" >typedExpr1 :: Code Q () <a href="#typedExpr1" ><span class="hs-identifier hs-var hs-var" >typedExpr1</span ><span id="line-42" ></span ><a href="#typedExpr" ><span class="hs-identifier hs-type" >typedExpr</span ><span class="annottext" >typedExpr :: Code Q () <a href="#typedExpr" ><span class="hs-identifier hs-var hs-var" >typedExpr</span ><span class="annottext" >Code Q () <a href="#typedExpr1" ><span class="hs-identifier hs-var" >typedExpr1</span ><span class="annottext" >foo :: Integer <a href="#foo" ><span class="hs-identifier hs-var hs-var" >foo</span ><span class="annottext" >pat :: [(a, String)] -> () <a href="#pat" ><span class="hs-identifier hs-var hs-var" >pat</span ><span class="annottext" >qux :: () <a href="#qux" ><span class="hs-identifier hs-var hs-var" >qux</span > </span ><span id="Quux" ><a href="#Quux" ><span class="hs-identifier hs-var" >Quux</span > </span ><span id="Bar" ><a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span > </span ><span id="Baz" ><a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span > </span ><span id="Foo" ><a href="#Foo" ><span class="hs-identifier hs-var" >Foo</span > </span ><span id="Foo" ><a href="#Foo" ><span class="hs-identifier hs-var" >Foo</span > </span ><span id="FooQuux" ><a href="#FooQuux" ><span class="hs-identifier hs-var" >FooQuux</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span > </span ><span id="QuuxFoo" ><a href="#QuuxFoo" ><span class="hs-identifier hs-var" >QuuxFoo</span ><span class="hs-special" >(</span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span > </span ><span id="Norf" ><a href="#Norf" ><span class="hs-identifier hs-var" >Norf</span > </span ><span id="Norf" ><a href="#Norf" ><span class="hs-identifier hs-var" >Norf</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span > </span ><span id="NFQ" ><a href="#NFQ" ><span class="hs-identifier hs-var" >NFQ</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span > </span ><span id="Norf" ><a href="#Norf" ><span class="hs-identifier hs-var" >Norf</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span > </span ><span id="NQF" ><a href="#NQF" ><span class="hs-identifier hs-var" >NQF</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span > </span ><span id="Norf%27" ><a href="#Norf%27" ><span class="hs-identifier hs-var" >Norf'</span > </span ><span id="Norf%27" ><a href="#Norf%27" ><span class="hs-identifier hs-var" >Norf'</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span > </span ><span id="Norf%27" ><a href="#Norf%27" ><span class="hs-identifier hs-var" >Norf'</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="hs-special" >(</span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span id="line-28" ></span ><a href="#norf1" ><span class="hs-identifier hs-type" >norf1</span ><span > </span ><a href="#Norf" ><span class="hs-identifier hs-type" >Norf</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span class="annottext" >norf1 :: Norf Foo Quux -> Int <a href="#norf1" ><span class="hs-identifier hs-var hs-var" >norf1</span ><span class="hs-special" >(</span ><a href="#NFQ" ><span class="hs-identifier hs-type" >NFQ</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >Quux <a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span ><span id="line-30" ></span ><a href="#norf1" ><span class="hs-identifier hs-var" >norf1</span ><span class="hs-special" >(</span ><a href="#NFQ" ><span class="hs-identifier hs-type" >NFQ</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >Quux <a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span ><span id="line-32" ></span ><a href="#norf2" ><span class="hs-identifier hs-type" >norf2</span ><span > </span ><a href="#Norf" ><span class="hs-identifier hs-type" >Norf</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >norf2 :: Norf Quux Foo -> Int <a href="#norf2" ><span class="hs-identifier hs-var hs-var" >norf2</span ><span class="hs-special" >(</span ><a href="#NQF" ><span class="hs-identifier hs-type" >NQF</span ><span class="annottext" >Quux <a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span id="line-34" ></span ><a href="#norf2" ><span class="hs-identifier hs-var" >norf2</span ><span class="hs-special" >(</span ><a href="#NQF" ><span class="hs-identifier hs-type" >NQF</span ><span class="annottext" >Quux <a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span id="line-37" ></span ><a href="#norf1%27" ><span class="hs-identifier hs-type" >norf1'</span ><span > </span ><a href="#Norf%27" ><span class="hs-identifier hs-type" >Norf'</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span class="annottext" >norf1' :: Norf' Foo Quux -> Int <a href="#norf1%27" ><span class="hs-identifier hs-var hs-var" >norf1'</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >Quux <a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span ><span id="line-39" ></span ><a href="#norf1%27" ><span class="hs-identifier hs-var" >norf1'</span ><span class="hs-special" >(</span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >Quux <a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span ><span id="line-41" ></span ><a href="#norf2%27" ><span class="hs-identifier hs-type" >norf2'</span ><span > </span ><a href="#Norf%27" ><span class="hs-identifier hs-type" >Norf'</span ><span > </span ><a href="#Quux" ><span class="hs-identifier hs-type" >Quux</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >norf2' :: Norf' Quux Foo -> Int <a href="#norf2%27" ><span class="hs-identifier hs-var hs-var" >norf2'</span ><span class="annottext" >Quux <a href="#Bar" ><span class="hs-identifier hs-var" >Bar</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span id="line-43" ></span ><a href="#norf2%27" ><span class="hs-identifier hs-var" >norf2'</span ><span class="annottext" >Quux <a href="#Baz" ><span class="hs-identifier hs-var" >Baz</span ><span > </span ><a href="#Foo" ><span class="hs-identifier hs-type" >Foo</span ><span class="annottext" >baz :: [Char] <a href="#baz" ><span class="hs-identifier hs-var hs-var" >baz</span >
participants (1)
-
Marge Bot (@marge-bot)