diff --git a/doc/cheatsheet/haddocks.md b/doc/cheatsheet/haddocks.md index 5ee285b3ace6be3aacb1a1494fdcf46ebeb2fe2c..1b4f85180801e5957347a1e3dfd1875437eb131b 100644 --- a/doc/cheatsheet/haddocks.md +++ b/doc/cheatsheet/haddocks.md @@ -109,14 +109,13 @@ definitions with "[thing]" Omit this module from the docs {-# OPTIONS_HADDOCK prune #-} Omit definitions without docs -{-# OPTIONS_HADDOCK ignore-exports #-} - Treat this module as though all - top-level items are exported {-# OPTIONS_HADDOCK not-home #-} Do not treat this module as the "home" of identifiers it exports {-# OPTIONS_HADDOCK show-extensions #-} Show all enabled LANGUAGE extensions +{-# OPTIONS_HADDOCK print-explicit-runtime-reps #-} + Show all `RuntimeRep` type variables ``` # Grid tables diff --git a/doc/invoking.rst b/doc/invoking.rst index 4e4b876445650a2e08f0c80fdb3e147ac0b4b76d..ce79f018c7b6b0725059ef2c7acaac477bf2fa4d 100644 --- a/doc/invoking.rst +++ b/doc/invoking.rst @@ -246,10 +246,6 @@ The following options are available: name. Note that for the per-entity URLs this is the name of the *exporting* module. - - The string ``%F`` or ``%{FILE}`` is replaced by the original - source file name. Note that for the per-entity URLs this is the - name of the *defining* module. - - The string ``%N`` or ``%{NAME}`` is replaced by the name of the exported value or type. This is only valid for the :option:`--source-entity` option. @@ -264,9 +260,6 @@ The following options are available: - The string ``%%`` is replaced by ``%``. - For example, if your sources are online under some directory, you - would say ``haddock --source-base=url/ --source-module=url/%F`` - If you have html versions of your sources online with anchors for each type and function name, you would say ``haddock --source-base=url/ --source-module=url/%M.html --source-entity=url/%M.html#%N`` @@ -277,11 +270,6 @@ The following options are available: characters in a file name). To replace it with a character c use ``%{MODULE/./c}``. - Similarly, for the ``%{FILE}`` substitution you may want to replace - the ``/`` character in the file names with some other character - (especially for links to colourised entity source code with a shared - css file). To replace it with a character c use ``%{FILE///c}``/ - One example of a tool that can generate syntax-highlighted HTML from your source code, complete with anchors suitable for use from haddock, is @@ -474,13 +462,6 @@ The following options are available: :option:`-i` or :option:`--read-interface`). This is used to generate a single contents and/or index for multiple sets of Haddock documentation. -.. option:: --ignore-all-exports - - Causes Haddock to behave as if every module has the - ``ignore-exports`` attribute (:ref:`module-attrs`). This might be useful for - generating implementation documentation rather than interface - documentation, for example. - .. option:: --hide <module> Causes Haddock to behave as if module module has the ``hide`` diff --git a/doc/markup.rst b/doc/markup.rst index c0b08a4067ebcb4be0c27b6668cf6ba00968c97d..9e0cc93c15dabb98d7e2cd83ed906bc0810206f1 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -762,7 +762,7 @@ specified in a comma-separated list in an ``{-# OPTIONS_HADDOCK ... #-}`` pragma at the top of the module, either before or after the module description. For example: :: - {-# OPTIONS_HADDOCK hide, prune, ignore-exports #-} + {-# OPTIONS_HADDOCK hide, prune #-} -- |Module description module A where @@ -781,11 +781,6 @@ The following attributes are currently understood by Haddock: Omit definitions that have no documentation annotations from the generated documentation. -``ignore-exports`` - Ignore the export list. Generate documentation as if the module had - no export list - i.e. all the top-level declarations are exported, - and section headings may be given in the body of the module. - ``not-home`` Indicates that the current module should not be considered to be the home module for each entity it exports, unless that entity is not @@ -800,6 +795,12 @@ The following attributes are currently understood by Haddock: be rendered, including those implied by their more powerful versions. +``print-explicit-runtime-reps`` + Print type variables that have kind ``RuntimeRep``. By default, these + are defaulted to ``LiftedRep`` so that end users don't have to see the + underlying levity polymorphism. This flag is analogous to GHC's + ``-fprint-explicit-runtime-reps`` flag. + .. _markup: Markup diff --git a/haddock-api/src/Documentation/Haddock.hs b/haddock-api/src/Documentation/Haddock.hs index e5d84796d42cdca5f981c04ced04dc756a1e11fa..80788b9038f9b308a8623e521ca8d122141d1316 100644 --- a/haddock-api/src/Documentation/Haddock.hs +++ b/haddock-api/src/Documentation/Haddock.hs @@ -43,7 +43,6 @@ module Documentation.Haddock ( DocMarkupH(..), Documentation(..), ArgMap, - AliasMap, WarningMap, DocMap, HaddockModInfo(..), diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 9158d83cafa5dcf78fd4ce554665bbd1b59b3058..51821cf2206b66d378e2f571589145bbe2b34979 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -504,8 +504,16 @@ withGhc' libDir needHieFiles flags ghcActs = runGhc (Just libDir) $ do parseGhcFlags logger dynflags = do -- TODO: handle warnings? - let extra_opts | needHieFiles = [Opt_WriteHie, Opt_Haddock] - | otherwise = [Opt_Haddock] + let extra_opts = + [ Opt_Haddock + -- Include docstrings in .hi-files. + + , Opt_WriteInterface + -- If we can't use an old .hi-file, save the new one. + ] ++ + [ Opt_WriteHie | needHieFiles + -- Generate .hie-files + ] dynflags' = (foldl' gopt_set dynflags extra_opts) { backend = NoBackend , ghcMode = CompManager diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker.hs b/haddock-api/src/Haddock/Backends/Hyperlinker.hs index 39be67625a99ec397bc93dc25d1e8626078c280a..d5fc52e3da5e38fc1b7960186b2e22b8a11e27e3 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker.hs @@ -26,8 +26,6 @@ import GHC.Types.SrcLoc ( realSrcLocSpan, mkRealSrcLoc ) import Data.Map as M import GHC.Data.FastString ( mkFastString ) import GHC.Unit.Module ( Module, moduleName ) -import GHC.Types.Name.Cache ( initNameCache ) -import GHC.Types.Unique.Supply ( mkSplitUniqSupply ) -- | Generate hyperlinked source for given interfaces. @@ -56,8 +54,7 @@ ppHyperlinkedSource verbosity outdir libdir mstyle pretty srcs' ifaces = do -- | Generate hyperlinked source for particular interface. ppHyperlinkedModuleSource :: Verbosity -> FilePath -> Bool -> SrcMaps -> Interface -> IO () -ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = case ifaceHieFile iface of - Just hfp -> do +ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = do -- Parse the GHC-produced HIE file nc <- freshNameCache HieFile { hie_hs_file = file @@ -83,8 +80,8 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = case ifaceHieFile -- Produce and write out the hyperlinked sources writeUtf8File path . renderToString pretty . render' fullAst $ tokens - Nothing -> return () where + hfp = ifaceHieFile iface df = ifaceDynFlags iface render' = render (Just srcCssFile) (Just highlightScript) srcs path = srcdir </> hypSrcModuleFile (ifaceMod iface) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs index 12f37cedf9a7a93614753889ee29bd395a5a6aba..d2920e74e16805172beb3b71528e641e10a61ae6 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs @@ -256,7 +256,7 @@ hyperlink (srcs, srcs') ident = case ident of Just SrcLocal -> Html.anchor content ! [ Html.href $ hypSrcModuleNameUrl mdl name ] Just (SrcExternal path) -> Html.anchor content ! - [ Html.href $ spliceURL Nothing (Just mdl) (Just name) Nothing (".." </> path) ] + [ Html.href $ spliceURL (Just mdl) (Just name) Nothing (".." </> path) ] Nothing -> content where mdl = nameModule name @@ -266,7 +266,7 @@ hyperlink (srcs, srcs') ident = case ident of Just SrcLocal -> Html.anchor content ! [ Html.href $ hypSrcModuleUrl' moduleName ] Just (SrcExternal path) -> Html.anchor content ! - [ Html.href $ spliceURL' Nothing (Just moduleName) Nothing Nothing (".." </> path) ] + [ Html.href $ spliceURL' (Just moduleName) Nothing Nothing (".." </> path) ] Nothing -> content diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs index 5c3bddefc9ee9a68d50c7bbf6d1457884a040425..c2baa37699771b277ef0f20e5a398950977184fa 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs @@ -39,7 +39,7 @@ hypSrcModuleFile m = moduleNameString (moduleName m) <.> "html" hypSrcModuleFile' :: ModuleName -> FilePath hypSrcModuleFile' mdl = spliceURL' - Nothing (Just mdl) Nothing Nothing moduleFormat + (Just mdl) Nothing Nothing moduleFormat hypSrcModuleUrl :: Module -> String hypSrcModuleUrl = hypSrcModuleFile diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index eb524ec70c325cd09c5acccdd625b18d1ea9c7ba..4d9f635a0f7d74dde9c5ea42add22eda0b4f9085 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -27,13 +27,13 @@ import qualified GHC.Utils.Ppr as Pretty import GHC.Types.Basic ( PromotionFlag(..) ) import GHC hiding (fromMaybeContext ) import GHC.Types.Name.Occurrence -import GHC.Types.Name ( nameOccName ) +import GHC.Types.Name ( nameOccName, getOccString, tidyNameOcc ) import GHC.Types.Name.Reader ( rdrNameOcc ) import GHC.Core.Type ( Specificity(..) ) import GHC.Data.FastString ( unpackFS ) import GHC.Utils.Panic ( panic) -import qualified Data.Map as Map +import qualified Data.IntMap as IntMap import System.Directory import System.FilePath import Data.Char @@ -218,7 +218,7 @@ processExports (e : es) = isSimpleSig :: ExportItem DocNameI -> Maybe ([DocName], HsSigType DocNameI) isSimpleSig ExportDecl { expItemDecl = L _ (SigD _ (TypeSig _ lnames t)) , expItemMbDoc = (Documentation Nothing Nothing, argDocs) } - | Map.null argDocs = Just (map unLoc lnames, unLoc (dropWildCards t)) + | IntMap.null argDocs = Just (map unLoc lnames, unLoc (dropWildCards t)) isSimpleSig _ = Nothing @@ -461,7 +461,7 @@ ppTypeOrFunSig :: HsSigType DocNameI -> Bool -- ^ unicode -> LaTeX ppTypeOrFunSig typ (doc, argDocs) (pref1, pref2, sep0) unicode - | Map.null argDocs = declWithDoc pref1 (documentationToLaTeX doc) + | IntMap.null argDocs = declWithDoc pref1 (documentationToLaTeX doc) | otherwise = declWithDoc pref2 $ Just $ text "\\haddockbeginargs" $$ vcat (map (uncurry (<->)) (ppSubSigLike unicode typ argDocs [] sep0)) $$ @@ -492,7 +492,7 @@ ppSubSigLike unicode typ argDocs subdocs leader = do_sig_args 0 leader typ do_largs :: Int -> LaTeX -> LHsType DocNameI -> [(LaTeX, LaTeX)] do_largs n leader (L _ t) = do_args n leader t - arg_doc n = rDoc . fmap _doc $ Map.lookup n argDocs + arg_doc n = rDoc . fmap _doc $ IntMap.lookup n argDocs do_args :: Int -> LaTeX -> HsType DocNameI -> [(LaTeX, LaTeX)] do_args _n leader (HsForAllTy _ tele ltype) @@ -657,11 +657,17 @@ ppClassDecl instances doc subdocs | L _ (ClassOpSig _ is_def lnames typ) <- lsigs , let doc | is_def = noDocForDecl | otherwise = lookupAnySubdoc (head names) subdocs - names = map unLoc lnames + names = map (cleanName . unLoc) lnames leader = if is_def then Just (keyword "default") else Nothing ] -- N.B. taking just the first name is ok. Signatures with multiple -- names are expanded so that each name gets its own signature. + -- Get rid of the ugly '$dm' prefix on default method names + cleanName n + | isDefaultMethodOcc (occName n) + , '$':'d':'m':occStr <- getOccString n + = setName (tidyNameOcc (getName n) (mkOccName varName occStr)) n + | otherwise = n instancesBit = ppDocInstances unicode instances @@ -800,8 +806,8 @@ ppSideBySideConstr subdocs unicode leader (L _ con) = ppOccInfix = cat (punctuate comma (map ppBinderInfix occ)) -- Extract out the map of of docs corresponding to the constructors arguments - argDocs = maybe Map.empty snd (lookup aConName subdocs) - hasArgDocs = not $ Map.null argDocs + argDocs = maybe IntMap.empty snd (lookup aConName subdocs) + hasArgDocs = not $ IntMap.null argDocs -- First line of the constructor (no doc, no fields, single-line) decl = case con of @@ -868,7 +874,7 @@ ppSideBySideConstr subdocs unicode leader (L _ con) = ConDeclH98{} -> [ decltt (ppLParendType unicode arg) <-> rDoc (fmap _doc mdoc) <+> nl | (i, arg) <- zip [0..] args - , let mdoc = Map.lookup i argDocs + , let mdoc = IntMap.lookup i argDocs ] ConDeclGADT{} -> [ l <+> text "\\enspace" <+> r @@ -905,7 +911,7 @@ ppSideBySidePat lnames typ (doc, argDocs) unicode = decltt decl <-> rDoc mDoc <+> nl $$ fieldPart where - hasArgDocs = not $ Map.null argDocs + hasArgDocs = not $ IntMap.null argDocs ppOcc = hsep (punctuate comma (map (ppDocBinder . unLoc) lnames)) decl | hasArgDocs = keyword "pattern" <+> ppOcc diff --git a/haddock-api/src/Haddock/Backends/Xhtml.hs b/haddock-api/src/Haddock/Backends/Xhtml.hs index d390a95ac0215751533a06565097b82459870951..4e435b23b90e136b1643334845db8dd4199cfe55 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml.hs @@ -146,8 +146,7 @@ srcButton :: SourceURLs -> Maybe Interface -> Maybe Html srcButton (Just src_base_url, _, _, _) Nothing = Just (anchor ! [href src_base_url] << "Source") srcButton (_, Just src_module_url, _, _) (Just iface) = - let url = spliceURL (Just $ ifaceOrigFilename iface) - (Just $ ifaceMod iface) Nothing Nothing src_module_url + let url = spliceURL (Just $ ifaceMod iface) Nothing Nothing src_module_url in Just (anchor ! [href url] << "Source") srcButton _ _ = Nothing @@ -158,7 +157,7 @@ wikiButton (Just wiki_base_url, _, _) Nothing = Just (anchor ! [href wiki_base_url] << "User Comments") wikiButton (_, Just wiki_module_url, _) (Just mdl) = - let url = spliceURL Nothing (Just mdl) Nothing Nothing wiki_module_url + let url = spliceURL (Just mdl) Nothing Nothing wiki_module_url in Just (anchor ! [href url] << "User Comments") wikiButton _ _ = @@ -381,8 +380,7 @@ ppJsonIndex odir maybe_source_url maybe_wiki_url unicode pkg qual_opt ifaces = d goInterface iface = concatMap (goExport mdl qual) (ifaceRnExportItems iface) where - aliases = ifaceModuleAliases iface - qual = makeModuleQual qual_opt aliases mdl + qual = makeModuleQual qual_opt mdl mdl = ifaceMod iface goExport :: Module -> Qualification -> ExportItem DocNameI -> [Value] @@ -549,7 +547,6 @@ ppHtmlModule odir doctitle themes maybe_contents_url maybe_index_url unicode pkg qual debug iface = do let mdl = ifaceMod iface - aliases = ifaceModuleAliases iface mdl_str = moduleString mdl mdl_str_annot = mdl_str ++ if ifaceIsSig iface then " (signature)" @@ -561,7 +558,7 @@ ppHtmlModule odir doctitle themes ")" | otherwise = toHtml mdl_str - real_qual = makeModuleQual qual aliases mdl + real_qual = makeModuleQual qual mdl html = headHtml mdl_str_annot themes maybe_mathjax_url +++ bodyHtml doctitle (Just iface) diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 336f23ac588787ef6004c3c697004c514da15f51..5f04169a535cc5b2f72eb7c7a4c72daab4f50b80 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -31,6 +31,7 @@ import Haddock.Doc (combineDocumentation) import Data.List ( intersperse, sort ) import qualified Data.Map as Map +import qualified Data.IntMap as IntMap import Data.Maybe import Data.Void ( absurd ) import Text.XHtml hiding ( name, title, p, quote ) @@ -126,7 +127,7 @@ ppTypeOrFunSig :: Bool -> LinksInfo -> SrcSpan -> [DocName] -> HsSigType DocName ppTypeOrFunSig summary links loc docnames typ (doc, argDocs) (pref1, pref2, sep) splice unicode pkg qual emptyCtxts | summary = pref1 - | Map.null argDocs = topDeclElem links loc splice docnames pref1 +++ docSection curname pkg qual doc + | IntMap.null argDocs = topDeclElem links loc splice docnames pref1 +++ docSection curname pkg qual doc | otherwise = topDeclElem links loc splice docnames pref2 +++ subArguments pkg qual (ppSubSigLike unicode qual typ argDocs [] sep emptyCtxts) +++ docSection curname pkg qual doc @@ -155,7 +156,7 @@ ppSubSigLike unicode qual typ argDocs subdocs sep emptyCtxts = do_sig_args 0 sep where leader' bndrs = leader <+> ppForAllPart unicode qual (mkHsForAllInvisTeleI bndrs) - argDoc n = Map.lookup n argDocs + argDoc n = IntMap.lookup n argDocs do_largs :: Int -> Html -> LHsType DocNameI -> [SubDecl] do_largs n leader (L _ t) = do_args n leader t @@ -600,12 +601,12 @@ ppClassDecl summary links instances fixities loc d subdocs ppDefaultFunSig n (t, d') = ppFunSig summary links loc (keyword "default") d' [n] t [] splice unicode pkg qual - lookupDM name = Map.lookup (getOccString name) defaultMethods + lookupDM name = Map.lookup (occNameString $ mkDefaultMethodOcc $ getOccName name) defaultMethods defaultMethods = Map.fromList [ (nameStr, (typ, doc)) | ClassOpSig _ True lnames typ <- sigs , name <- map unLoc lnames - , let doc = noDocForDecl -- TODO: get docs for method defaults + , let doc = lookupAnySubdoc name subdocs nameStr = getOccString name ] @@ -618,7 +619,7 @@ ppClassDecl summary links instances fixities loc d subdocs -- Minimal complete definition = the only shown method Var (L _ n) : _ | [getName n] == - [getName n' | L _ (ClassOpSig _ _ ns _) <- lsigs, L _ n' <- ns] + [getName n' | ClassOpSig _ _ ns _ <- sigs, L _ n' <- ns] -> noHtml -- Minimal complete definition = nothing @@ -925,8 +926,8 @@ ppSideBySideConstr subdocs fixities unicode pkg qual (L _ con) ppOccInfix = hsep (punctuate comma (map (ppBinderInfix False) occ)) -- Extract out the map of of docs corresponding to the constructors arguments - argDocs = maybe Map.empty snd (lookup aConName subdocs) - hasArgDocs = not $ Map.null argDocs + argDocs = maybe IntMap.empty snd (lookup aConName subdocs) + hasArgDocs = not $ IntMap.null argDocs decl = case con of ConDeclH98{ con_args = det @@ -990,7 +991,7 @@ ppSideBySideConstr subdocs fixities unicode pkg qual (L _ con) ConDeclH98{} -> [ (ppLParendType unicode qual HideEmptyContexts arg, mdoc, []) | (i, arg) <- zip [0..] (map hsScaledThing args) - , let mdoc = Map.lookup i argDocs + , let mdoc = IntMap.lookup i argDocs ] ConDeclGADT{} -> ppSubSigLike unicode qual (unLoc (getGADTConType con)) @@ -1058,7 +1059,7 @@ ppSideBySidePat fixities unicode qual lnames typ (doc, argDocs) = , fieldPart ) where - hasArgDocs = not $ Map.null argDocs + hasArgDocs = not $ IntMap.null argDocs fixity = ppFixities fixities qual ppOcc = hsep (punctuate comma (map (ppBinder False . getOccName) lnames)) diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs index 8f04a21f01d9b9f911381c23c4bb0b8003565480..1812f3cdbdb25d8a57bcabf55e8f86fea2adf3f9 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs @@ -50,7 +50,6 @@ import qualified Data.Map as Map import Text.XHtml hiding ( name, title, quote ) import Data.Maybe (fromMaybe) -import GHC.Data.FastString ( unpackFS ) import GHC hiding (anchor) import GHC.Types.Name (nameOccName) @@ -293,15 +292,14 @@ links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice mdl' docName@(D | otherwise = maybe lineUrl Just nameUrl in case mUrl of Nothing -> noHtml - Just url -> let url' = spliceURL (Just fname) (Just origMod) - (Just n) (Just loc) url + Just url -> let url' = spliceURL (Just origMod) (Just n) (Just loc) + url in anchor ! [href url', theclass "link"] << "Source" wikiLink = case maybe_wiki_url of Nothing -> noHtml - Just url -> let url' = spliceURL (Just fname) (Just mdl) - (Just n) (Just loc) url + Just url -> let url' = spliceURL (Just mdl) (Just n) (Just loc) url in anchor ! [href url', theclass "link"] << "Comments" -- For source links, we want to point to the original module, @@ -311,8 +309,4 @@ links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice mdl' docName@(D -- will point to the module defining the class/family, which is wrong. origMod = fromMaybe (nameModule n) mdl' origPkg = moduleUnit origMod - - fname = case loc of - RealSrcSpan l _ -> unpackFS (srcSpanFile l) - UnhelpfulSpan _ -> error "links: UnhelpfulSpan" links _ _ _ _ _ = noHtml diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Names.hs b/haddock-api/src/Haddock/Backends/Xhtml/Names.hs index 6dfc60fae611a5e9c26c68fd9d8f59cc2a5b0c7e..09b5b603e01ee5e164bc9bc854a02026c83f378a 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Names.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Names.hs @@ -24,7 +24,6 @@ import Haddock.Types import Haddock.Utils import Text.XHtml hiding ( name, p, quote ) -import qualified Data.Map as M import Data.List ( stripPrefix ) import GHC hiding (LexicalFixity(..), anchor) @@ -105,11 +104,6 @@ ppQualifyName qual notation name mdl = Just _ -> ppFullQualName notation mdl name -- some other module, D.x -> D.x Nothing -> ppFullQualName notation mdl name - AliasedQual aliases localmdl -> - case (moduleString mdl == moduleString localmdl, - M.lookup mdl aliases) of - (False, Just alias) -> ppQualName notation alias name - _ -> ppName notation name ppFullQualName :: Notation -> Module -> Name -> Html @@ -117,11 +111,6 @@ ppFullQualName notation mdl name = wrapInfix notation (getOccName name) qname where qname = toHtml $ moduleString mdl ++ '.' : getOccString name -ppQualName :: Notation -> ModuleName -> Name -> Html -ppQualName notation mdlName name = wrapInfix notation (getOccName name) qname - where - qname = toHtml $ moduleNameString mdlName ++ '.' : getOccString name - ppName :: Notation -> Name -> Html ppName notation name = wrapInfix notation (getOccName name) $ toHtml (getOccString name) @@ -148,14 +137,11 @@ ppBinder' notation n = wrapInfix notation n $ ppOccName n wrapInfix :: Notation -> OccName -> Html -> Html wrapInfix notation n = case notation of - Infix | is_star_kind -> id - | not is_sym -> quote - Prefix | is_star_kind -> id - | is_sym -> parens + Infix | not is_sym -> quote + Prefix | is_sym -> parens _ -> id where is_sym = isSymOcc n - is_star_kind = isTcOcc n && occNameString n == "*" linkId :: Module -> Maybe Name -> Html -> Html linkId mdl mbName = linkIdOcc mdl (fmap nameOccName mbName) True diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs b/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs index 238f0046812a6c53b16f8ae55826c67c7f4d444e..2741d2d25d3e1934c67f89fa2367b9847d4d5a48 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs @@ -34,8 +34,6 @@ module Haddock.Backends.Xhtml.Utils ( import Haddock.Utils -import Data.Maybe - import Text.XHtml hiding ( name, title, p, quote ) import qualified Text.XHtml as XHtml @@ -49,19 +47,18 @@ import GHC.Types.Name ( getOccString, nameOccName, isValOcc ) -- Used to generate URL for customized external paths, usually provided with -- @--source-module@, @--source-entity@ and related command-line arguments. -- --- >>> spliceURL Nothing mmod mname Nothing "output/%{MODULE}.hs#%{NAME}" +-- >>> spliceURL mmod mname Nothing "output/%{MODULE}.hs#%{NAME}" -- "output/Foo.hs#foo" -spliceURL :: Maybe FilePath -> Maybe Module -> Maybe GHC.Name -> +spliceURL :: Maybe Module -> Maybe GHC.Name -> Maybe SrcSpan -> String -> String -spliceURL mfile mmod = spliceURL' mfile (moduleName <$> mmod) +spliceURL mmod = spliceURL' (moduleName <$> mmod) -- | Same as 'spliceURL' but takes 'ModuleName' instead of 'Module'. -spliceURL' :: Maybe FilePath -> Maybe ModuleName -> Maybe GHC.Name -> +spliceURL' :: Maybe ModuleName -> Maybe GHC.Name -> Maybe SrcSpan -> String -> String -spliceURL' maybe_file maybe_mod maybe_name maybe_loc = run +spliceURL' maybe_mod maybe_name maybe_loc = run where - file = fromMaybe "" maybe_file mdl = case maybe_mod of Nothing -> "" Just m -> moduleNameString m @@ -82,23 +79,18 @@ spliceURL' maybe_file maybe_mod maybe_name maybe_loc = run run "" = "" run ('%':'M':rest) = mdl ++ run rest - run ('%':'F':rest) = file ++ run rest run ('%':'N':rest) = name ++ run rest run ('%':'K':rest) = kind ++ run rest run ('%':'L':rest) = line ++ run rest run ('%':'%':rest) = '%' : run rest run ('%':'{':'M':'O':'D':'U':'L':'E':'}':rest) = mdl ++ run rest - run ('%':'{':'F':'I':'L':'E':'}':rest) = file ++ run rest run ('%':'{':'N':'A':'M':'E':'}':rest) = name ++ run rest run ('%':'{':'K':'I':'N':'D':'}':rest) = kind ++ run rest run ('%':'{':'M':'O':'D':'U':'L':'E':'/':'.':'/':c:'}':rest) = map (\x -> if x == '.' then c else x) mdl ++ run rest - run ('%':'{':'F':'I':'L':'E':'/':'/':'/':c:'}':rest) = - map (\x -> if x == '/' then c else x) file ++ run rest - run ('%':'{':'L':'I':'N':'E':'}':rest) = line ++ run rest run (c:rest) = c : run rest diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 599404a01276cc604704f781c61073cb4065b5c9..2ab686692ccd23a14c433807daf6bfcf81cdda91 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -45,6 +45,8 @@ import GHC.Types.Var.Env ( TyVarEnv, extendVarEnv, elemVarEnv, emptyVarEnv ) import GHC.Core.TyCo.Rep ( Type(..) ) import GHC.Core.Type ( isRuntimeRepVar ) import GHC.Builtin.Types( liftedRepTy ) +import GHC.Builtin.Names +import GHC.Data.FastString import GHC.Data.StringBuffer ( StringBuffer ) import qualified GHC.Data.StringBuffer as S @@ -53,8 +55,7 @@ import Data.ByteString ( ByteString ) import qualified Data.ByteString as BS import qualified Data.ByteString.Internal as BS -import GHC.HsToCore.Docs - +import GHC.HsToCore.Docs hiding (sigNameNoLoc) moduleString :: Module -> String moduleString = moduleNameString . moduleName @@ -97,6 +98,15 @@ ifTrueJust False = const Nothing sigName :: LSig GhcRn -> [IdP GhcRn] sigName (L _ sig) = sigNameNoLoc sig +sigNameNoLoc :: forall pass. UnXRec pass => Sig pass -> [IdP pass] +sigNameNoLoc (TypeSig _ ns _) = map (unXRec @pass) ns +sigNameNoLoc (ClassOpSig _ _ ns _) = map (unXRec @pass) ns +sigNameNoLoc (PatSynSig _ ns _) = map (unXRec @pass) ns +sigNameNoLoc (SpecSig _ n _ _) = [unXRec @pass n] +sigNameNoLoc (InlineSig _ n _) = [unXRec @pass n] +sigNameNoLoc (FixSig _ (FixitySig _ ns _)) = map (unXRec @pass) ns +sigNameNoLoc _ = [] + -- | Was this signature given by the user? isUserLSig :: forall p. UnXRec p => LSig p -> Bool isUserLSig = isUserSig . unXRec @p @@ -108,6 +118,8 @@ isClassD _ = False pretty :: Outputable a => DynFlags -> a -> String pretty = showPpr +dATA_LIST :: Module +dATA_LIST = mkBaseModule (fsLit "Data.List") -- --------------------------------------------------------------------- -- These functions are duplicated from the GHC API, as they must be diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 2e9b2f7e4242d2497db81ea051ac12e0e3bc3614..0669d9d1ac9407f071cfebc652545210b4d8891a 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -29,8 +29,7 @@ -- using this environment. ----------------------------------------------------------------------------- module Haddock.Interface ( - plugin - , processModules + processModules ) where @@ -52,26 +51,35 @@ import Data.List (foldl', isPrefixOf, nub) import Text.Printf (printf) import qualified Data.Map as Map import qualified Data.Set as Set +import System.Exit (exitFailure ) -- TODO use Haddock's die +import Text.Printf +import Control.Arrow import GHC hiding (verbosity) +import GHC.IfaceToCore +import GHC.Unit.Module.ModDetails import GHC.Data.FastString (unpackFS) import GHC.Data.Graph.Directed (flattenSCCs) import GHC.Driver.Env (hscUpdateFlags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) -import GHC.Driver.Monad (modifySession, withTimingM) +import GHC.Driver.Monad +import GHC.Driver.Make import GHC.Driver.Session hiding (verbosity) import GHC.HsToCore.Docs (getMainDeclBinder) -import GHC.Plugins (Outputable, Plugin (..), PluginWithArgs (..), StaticPlugin (..), defaultPlugin, keepRenamedSource) +import GHC.Plugins (Outputable, Plugin (..), PluginWithArgs (..), StaticPlugin (..), defaultPlugin, keepRenamedSource, text) import GHC.Tc.Types (TcGblEnv (..), TcM) import GHC.Tc.Utils.Env (tcLookupGlobal) -import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv) +import GHC.Tc.Utils.Monad import GHC.Types.Name (nameIsFromExternalPackage, nameOccName) -import GHC.Types.Name.Occurrence (isTcOcc) +import GHC.Types.Name.Occurrence (isTcOcc, emptyOccEnv) import GHC.Types.Name.Reader (globalRdrEnvElts, greMangledName, unQualOK) import GHC.Unit.Module.Env (ModuleSet, emptyModuleSet, mkModuleSet, unionModuleSet) import GHC.Unit.Module.Graph (ModuleGraphNode (..)) import GHC.Unit.Module.ModSummary (emsModSummary, isBootSummary) import GHC.Unit.Types (IsBootInterface (..)) import GHC.Utils.Error (withTiming) +import Control.Monad +import Control.Exception +import GHC.Iface.Load #if defined(mingw32_HOST_OS) import System.IO @@ -105,7 +113,7 @@ processModules verbosity modules flags extIfaces = do , iface <- ifInstalledIfaces ext ] - (interfaces, ms) <- createIfaces verbosity modules flags instIfaceMap + interfaces <- createIfaces verbosity modules flags instIfaceMap let exportedNames = Set.unions $ map (Set.fromList . ifaceExports) $ @@ -114,7 +122,7 @@ processModules verbosity modules flags extIfaces = do out verbosity verbose "Attaching instances..." interfaces' <- {-# SCC attachInstances #-} withTimingM "attachInstances" (const ()) $ do - attachInstances (exportedNames, mods) interfaces instIfaceMap ms + attachInstances (exportedNames, mods) interfaces instIfaceMap out verbosity verbose "Building cross-linking environment..." -- Combine the link envs of the external packages into one @@ -138,204 +146,94 @@ processModules verbosity modules flags extIfaces = do -------------------------------------------------------------------------------- -createIfaces :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc ([Interface], ModuleSet) +createIfaces :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc [Interface] createIfaces verbosity modules flags instIfaceMap = do - (haddockPlugin, getIfaces, getModules) <- liftIO $ plugin - verbosity flags instIfaceMap - - let - installHaddockPlugin :: HscEnv -> HscEnv - installHaddockPlugin hsc_env = hscUpdateFlags (flip gopt_set Opt_PluginTrustworthy) $ hsc_env - { hsc_static_plugins = - haddockPlugin : hsc_static_plugins hsc_env - } - - -- Note that we would rather use withTempSession but as long as we - -- have the separate attachInstances step we need to keep the session - -- alive to be able to find all the instances. - modifySession installHaddockPlugin targets <- mapM (\filePath -> guessTarget filePath Nothing Nothing) modules setTargets targets - - loadOk <- withTimingM "load" (const ()) $ - {-# SCC load #-} GHC.load LoadAllTargets - - case loadOk of - Failed -> - throwE "Cannot typecheck modules" - Succeeded -> do - modGraph <- GHC.getModuleGraph - ifaceMap <- liftIO getIfaces - moduleSet <- liftIO getModules - - let - ifaces :: [Interface] - ifaces = - [ Map.findWithDefault - (error "haddock:iface") - (ms_mod (emsModSummary ems)) - ifaceMap - | ModuleNode ems <- flattenSCCs $ topSortModuleGraph True modGraph Nothing - ] - - return (ifaces, moduleSet) - - --- | A `Plugin` that hooks into GHC's compilation pipeline to generate Haddock --- interfaces. Due to the plugin nature we benefit from GHC's capabilities to --- parallelize the compilation process. -plugin - :: MonadIO m - => Verbosity - -> [Flag] - -> InstIfaceMap - -> m - ( - StaticPlugin -- the plugin to install with GHC - , m IfaceMap -- get the processed interfaces - , m ModuleSet -- get the loaded modules - ) -plugin verbosity flags instIfaceMap = liftIO $ do - ifaceMapRef <- newIORef Map.empty - moduleSetRef <- newIORef emptyModuleSet - - let - processTypeCheckedResult :: ModSummary -> TcGblEnv -> TcM () - processTypeCheckedResult mod_summary tc_gbl_env - -- Don't do anything for hs-boot modules - | IsBoot <- isBootSummary mod_summary = - pure () - | otherwise = do - hsc_env <- getTopEnv - ifaces <- liftIO $ readIORef ifaceMapRef - (iface, modules) <- withTiming (hsc_logger hsc_env) - "processModule" (const ()) $ - processModule1 verbosity flags ifaces instIfaceMap hsc_env mod_summary tc_gbl_env - - liftIO $ do - atomicModifyIORef' ifaceMapRef $ \xs -> - (Map.insert (ms_mod mod_summary) iface xs, ()) - - atomicModifyIORef' moduleSetRef $ \xs -> - (modules `unionModuleSet` xs, ()) - - staticPlugin :: StaticPlugin - staticPlugin = StaticPlugin - { - spPlugin = PluginWithArgs - { - paPlugin = defaultPlugin - { - renamedResultAction = keepRenamedSource - , typeCheckResultAction = \_ mod_summary tc_gbl_env -> setGblEnv tc_gbl_env $ do - processTypeCheckedResult mod_summary tc_gbl_env - pure tc_gbl_env - - } - , paArguments = [] - } - } - - pure - ( staticPlugin - , liftIO (readIORef ifaceMapRef) - , liftIO (readIORef moduleSetRef) - ) - - -processModule1 - :: Verbosity - -> [Flag] - -> IfaceMap - -> InstIfaceMap - -> HscEnv - -> ModSummary - -> TcGblEnv - -> TcM (Interface, ModuleSet) -processModule1 verbosity flags ifaces inst_ifaces hsc_env mod_summary tc_gbl_env = do - out verbosity verbose "Creating interface..." - - let - TcGblEnv { tcg_rdr_env } = tc_gbl_env - - unit_state = hsc_units hsc_env - - (!interface, messages) <- do - logger <- getLogger - {-# SCC createInterface #-} - withTiming logger "createInterface" (const ()) $ runIfM (fmap Just . tcLookupGlobal) $ - createInterface1 flags unit_state mod_summary tc_gbl_env - ifaces inst_ifaces - - -- We need to keep track of which modules were somehow in scope so that when - -- Haddock later looks for instances, it also looks in these modules too. - -- - -- See https://github.com/haskell/haddock/issues/469. - let - mods :: ModuleSet - !mods = mkModuleSet - [ nameModule name - | gre <- globalRdrEnvElts tcg_rdr_env - , let name = greMangledName gre - , nameIsFromExternalPackage (hsc_home_unit hsc_env) name - , isTcOcc (nameOccName name) -- Types and classes only - , unQualOK gre -- In scope unqualified - ] - - liftIO $ mapM_ putStrLn (nub messages) - dflags <- getDynFlags - - let - (haddockable, haddocked) = - ifaceHaddockCoverage interface - - percentage :: Int - percentage = div (haddocked * 100) haddockable - - modString :: String - modString = moduleString (ifaceMod interface) - - coverageMsg :: String - coverageMsg = - printf " %3d%% (%3d /%3d) in '%s'" percentage haddocked haddockable modString - - header :: Bool - header = case ifaceDoc interface of - Documentation Nothing _ -> False - _ -> True - - undocumentedExports :: [String] - undocumentedExports = - [ formatName (locA s) n - | ExportDecl { expItemDecl = L s n - , expItemMbDoc = (Documentation Nothing _, _) - } <- ifaceExportItems interface - ] - where - formatName :: SrcSpan -> HsDecl GhcRn -> String - formatName loc n = p (getMainDeclBinder n) ++ case loc of - RealSrcSpan rss _ -> " (" ++ unpackFS (srcSpanFile rss) ++ ":" ++ - show (srcSpanStartLine rss) ++ ")" - _ -> "" - - p :: Outputable a => [a] -> String - p [] = "" - p (x:_) = let n = pretty dflags x - ms = modString ++ "." - in if ms `isPrefixOf` n - then drop (length ms) n - else n - - when (OptHide `notElem` ifaceOptions interface) $ do - out verbosity normal coverageMsg - when (Flag_NoPrintMissingDocs `notElem` flags - && not (null undocumentedExports && header)) $ do - out verbosity normal " Missing documentation for:" - unless header $ out verbosity normal " Module header" - mapM_ (out verbosity normal . (" " ++)) undocumentedExports - - pure (interface, mods) + modGraph <- depanal [] False + + -- Create (if necessary) and load .hi-files. + success <- withTimingM "load'" (const ()) $ do + load' LoadAllTargets Nothing modGraph + when (failed success) $ do + out verbosity normal "load' failed" + liftIO exitFailure + + -- Visit modules in that order + let sortedMods = flattenSCCs $ topSortModuleGraph False modGraph Nothing + out verbosity normal "Haddock coverage:" + (ifaces, _) <- foldM f ([], Map.empty) sortedMods + return (reverse ifaces) + where + f state (InstantiationNode _) = pure state + f (ifaces, ifaceMap) (ModuleNode modSummary) = do + x <- {-# SCC processModule #-} + withTimingM "processModule" (const ()) $ do + processModule verbosity (emsModSummary modSummary) flags ifaceMap instIfaceMap + return $ case x of + Just iface -> ( iface:ifaces + , Map.insert (ifaceMod iface) iface ifaceMap ) + Nothing -> ( ifaces + , ifaceMap ) -- Boot modules don't generate ifaces. + + +processModule :: Verbosity -> ModSummary -> [Flag] -> IfaceMap -> InstIfaceMap -> Ghc (Maybe Interface) +processModule verbosity modsum flags modMap instIfaceMap = do + out verbosity verbose $ "Checking module " ++ moduleString (ms_mod modsum) ++ "..." + + (mod_iface, insts, unit_state) <- withSession $ \hsc_env -> do + mod_iface <- liftIO $ initIfaceCheck (text "processModule 0") hsc_env $ + loadSysInterface (text "processModule 1") + (ms_mod modsum) + insts <- liftIO $ + (md_insts &&& md_fam_insts) + <$> initIfaceCheck (text "createInterface'") hsc_env + (typecheckIface mod_iface) + pure (mod_iface, insts, hsc_units hsc_env) + + case isBootSummary modsum of + IsBoot -> return Nothing + NotBoot -> do + out verbosity verbose "Creating interface..." + (interface, msgs) <- {-# SCC createIterface #-} + withTimingM "createInterface" (const ()) $ runIfM lookupName + $ createInterface1 flags unit_state modsum mod_iface modMap instIfaceMap insts + + liftIO $ mapM_ putStrLn (show (ml_hs_file . ms_location $ modsum) : nub msgs) + dflags <- getDynFlags + let (haddockable, haddocked) = ifaceHaddockCoverage interface + percentage = round (fromIntegral haddocked * 100 / fromIntegral haddockable :: Double) :: Int + modString = moduleString (ifaceMod interface) + coverageMsg = printf " %3d%% (%3d /%3d) in '%s'" percentage haddocked haddockable modString + header = case ifaceDoc interface of + Documentation Nothing _ -> False + _ -> True + undocumentedExports = [ formatName (locA s) n | ExportDecl { expItemDecl = L s n + , expItemMbDoc = (Documentation Nothing _, _) + } <- ifaceExportItems interface ] + where + formatName :: SrcSpan -> HsDecl GhcRn -> String + formatName loc n = p (getMainDeclBinder emptyOccEnv n) ++ case loc of + RealSrcSpan rss _ -> " (" ++ unpackFS (srcSpanFile rss) ++ ":" ++ show (srcSpanStartLine rss) ++ ")" + _ -> "" + + p [] = "" + p (x:_) = let n = pretty dflags x + ms = modString ++ "." + in if ms `isPrefixOf` n + then drop (length ms) n + else n + + when (OptHide `notElem` ifaceOptions interface) $ do + out verbosity normal coverageMsg + when (Flag_NoPrintMissingDocs `notElem` flags + && not (null undocumentedExports && header)) $ do + out verbosity normal " Missing documentation for:" + unless header $ out verbosity normal " Module header" + mapM_ (out verbosity normal . (" " ++)) undocumentedExports + interface' <- liftIO $ evaluate interface + return (Just interface') -------------------------------------------------------------------------------- diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs index e8a79b2b50bfc34a2613a0cd585a271295bc8807..f89a79a2b4a823903bc22f0a0f7a06bf66336cbe 100644 --- a/haddock-api/src/Haddock/Interface/AttachInstances.hs +++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs @@ -34,7 +34,8 @@ import GHC.Core (isOrphan) import GHC.Core.FamInstEnv import GHC import GHC.Core.InstEnv -import GHC.Unit.Module.Env ( ModuleSet, moduleSetElts ) +import GHC.Unit.Module.Env ( moduleSetElts, mkModuleSet ) +import GHC.Unit.State import GHC.Types.Name import GHC.Types.Name.Env import GHC.Utils.Outputable (text, sep, (<+>)) @@ -44,19 +45,38 @@ import GHC.Core.TyCo.Rep import GHC.Builtin.Types.Prim( funTyConName ) import GHC.Types.Var hiding (varName) import GHC.HsToCore.Docs +import GHC.Driver.Env.Types +import GHC.Unit.Env type ExportedNames = Set.Set Name type Modules = Set.Set Module type ExportInfo = (ExportedNames, Modules) -- Also attaches fixities -attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> ModuleSet -> Ghc [Interface] -attachInstances expInfo ifaces instIfaceMap mods = do +attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> Ghc [Interface] +attachInstances expInfo ifaces instIfaceMap = do + + -- We need to keep load modules in which we will look for instances. We've + -- somewhat arbitrarily decided to load all modules which are available - + -- either directly or from a re-export. + -- + -- See https://github.com/haskell/haddock/issues/469. + env <- getSession + let mod_to_pkg_conf = moduleNameProvidersMap $ ue_units $ hsc_unit_env env + mods = mkModuleSet [ m + | mod_map <- Map.elems mod_to_pkg_conf + , ( m + , ModOrigin { fromOrigUnit = fromOrig + , fromExposedReexport = reExp + } + ) <- Map.assocs mod_map + , fromOrig == Just True || not (null reExp) + ] + mods' = Just (moduleSetElts mods) + (_msgs, mb_index) <- getNameToInstancesIndex (map ifaceMod ifaces) mods' mapM (attach $ fromMaybe emptyNameEnv mb_index) ifaces where - mods' = Just (moduleSetElts mods) - -- TODO: take an IfaceMap as input ifaceMap = Map.fromList [ (ifaceMod i, i) | i <- ifaces ] @@ -136,12 +156,12 @@ attachToExportItem index expInfo getInstDoc getFixity export = , expItemSubDocs = subDocs } = e { expItemFixities = nubByName fst $ expItemFixities e ++ - [ (n',f) | n <- getMainDeclBinder d + [ (n',f) | n <- getMainDeclBinder emptyOccEnv d , n' <- n : (map fst subDocs ++ patsyn_names) , f <- maybeToList (getFixity n') ] } where - patsyn_names = concatMap (getMainDeclBinder . fst) patsyns + patsyn_names = concatMap (getMainDeclBinder emptyOccEnv . fst) patsyns attachFixities e = e -- spanName: attach the location to the name that is the same file as the instance location diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 2782f711fb68e51fa05fd15efdae62870ad20b86..93d3797db36b0835ae083fa19fb4954aef7d6e57 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -31,56 +31,48 @@ ----------------------------------------------------------------------------- module Haddock.Interface.Create (IfM, runIfM, createInterface1) where -import Documentation.Haddock.Doc (metaDocAppend) import Haddock.Convert (PrintRuntimeReps (..), tyThingToLHsDecl) -import Haddock.GhcUtils (addClassContext, filterSigNames, lHsQTyVarsToTypes, mkEmptySigType, moduleString, parents, - pretty, restrictTo, sigName, unL) -import Haddock.Interface.LexParseRn (processDocString, processDocStringParas, processDocStrings, processModuleHeader) +import Haddock.GhcUtils (addClassContext, lHsQTyVarsToTypes, mkEmptySigType, moduleString, + pretty, restrictTo, sigName) +import Haddock.Interface.LexParseRn (processDocString, processDocStringParas, processModuleHeader) import Haddock.Options (Flag (..), modulePackageInfo) import Haddock.Types hiding (liftErrMsg) import Haddock.Utils (replace) -import Control.Applicative ((<|>)) import Control.Monad.Reader (MonadReader (..), ReaderT, asks, runReaderT) import Control.Monad.Writer.Strict hiding (tell) -import Data.Bitraversable (bitraverse) -import Data.List (find, foldl') +import Data.List (foldl') import qualified Data.IntMap as IM -import Data.IntMap (IntMap) import Data.Map (Map) import qualified Data.Map as M -import Data.Maybe (catMaybes, fromJust, isJust, mapMaybe, maybeToList) +import Data.Maybe (catMaybes, isJust, mapMaybe, maybeToList) import Data.Traversable (for) +import qualified Data.List.NonEmpty as NE import GHC hiding (lookupName) -import GHC.Core.Class (ClassMinimalDef, classMinimalDef) import GHC.Core.ConLike (ConLike (..)) -import GHC.Data.FastString (bytesFS, unpackFS) -import GHC.Driver.Ppr (showSDoc) +import GHC.Data.FastString (unpackFS) import GHC.HsToCore.Docs hiding (mkMaps) -import GHC.IORef (readIORef) -import GHC.Parser.Annotation (IsUnicodeSyntax (..)) import GHC.Stack (HasCallStack) -import GHC.Tc.Types hiding (IfM) -import GHC.Tc.Utils.Monad (finalSafeMode) import GHC.Types.Avail hiding (avail) import qualified GHC.Types.Avail as Avail -import GHC.Types.Basic (PromotionFlag (..)) +import GHC.Types.Basic import GHC.Types.Name (getOccString, getSrcSpan, isDataConName, isValName, nameIsLocalOrFrom, nameOccName) -import GHC.Types.Name.Env (lookupNameEnv) -import GHC.Types.Name.Reader (GlobalRdrEnv, greMangledName, lookupGlobalRdrEnv) -import GHC.Types.Name.Set (elemNameSet, mkNameSet) -import GHC.Types.SourceFile (HscSource (..)) -import GHC.Types.SourceText (SourceText (..), sl_fs) +import GHC.Types.Name.Set import qualified GHC.Types.SrcLoc as SrcLoc -import qualified GHC.Unit.Module as Module -import GHC.Unit.Module.ModSummary (msHsFilePath) -import GHC.Unit.Module.Warnings (WarningTxt (..), Warnings (..)) -import GHC.Unit.State (PackageName (..), UnitState, lookupModuleInAllUnits) +import GHC.Unit.Module.Warnings +import GHC.Unit.State (PackageName (..), UnitState) import qualified GHC.Utils.Outputable as O import GHC.Utils.Panic (pprPanic) -import GHC.HsToCore.Docs hiding (mkMaps) -import GHC.Unit.Module.Warnings +import GHC.Driver.Ppr +import GHC.Unit.Module.ModIface +import GHC.Builtin.Names +import GHC.Builtin.Types +import GHC.Builtin.Types.Prim +import GHC.Types.SafeHaskell +import Control.Arrow ((&&&)) +import GHC.Types.Name.Occurrence +import GHC.Iface.Syntax newtype IfEnv m = IfEnv { @@ -140,11 +132,12 @@ createInterface1 => [Flag] -> UnitState -> ModSummary - -> TcGblEnv + -> ModIface -> IfaceMap -> InstIfaceMap + -> ([ClsInst],[FamInst]) -> IfM m Interface -createInterface1 flags unit_state mod_sum tc_gbl_env ifaces inst_ifaces = do +createInterface1 flags unit_state mod_sum mod_iface ifaces inst_ifaces (instances, fam_instances) = do let ModSummary @@ -159,32 +152,14 @@ createInterface1 flags unit_state mod_sum tc_gbl_env ifaces inst_ifaces = do } } = mod_sum - TcGblEnv - { - tcg_mod - , tcg_src - , tcg_semantic_mod - , tcg_rdr_env - , tcg_exports - , tcg_insts - , tcg_fam_insts - , tcg_warns - - -- Renamed source - , tcg_rn_imports - , tcg_rn_exports - , tcg_rn_decls - - , tcg_th_docs - , tcg_doc_hdr - } = tc_gbl_env - - dflags = ms_hspp_opts - - is_sig = tcg_src == HsigFile + dflags = ms_hspp_opts + mdl = mi_module mod_iface + sem_mdl = mi_semantic_module mod_iface + is_sig = isJust (mi_sig_of mod_iface) + safety = getSafeMode (mi_trust mod_iface) (pkg_name_fs, _) = - modulePackageInfo unit_state flags (Just tcg_mod) + modulePackageInfo unit_state flags (Just mdl) pkg_name :: Maybe Package pkg_name = @@ -193,245 +168,179 @@ createInterface1 flags unit_state mod_sum tc_gbl_env ifaces inst_ifaces = do in fmap unpack pkg_name_fs - fixities :: FixMap - fixities = case tcg_rn_decls of - Nothing -> mempty - Just dx -> mkFixMap dx + warnings = mi_warns mod_iface - -- Locations of all the TH splices - loc_splices :: [SrcSpan] - loc_splices = case tcg_rn_decls of - Nothing -> [] - Just HsGroup { hs_splcds } -> [ locA loc | L loc _ <- hs_splcds ] + -- See Note [Exporting built-in items] + special_exports + | mdl == gHC_TYPES = listAvail <> eqAvail + | mdl == gHC_PRIM = funAvail + | mdl == pRELUDE = listAvail <> funAvail + | mdl == dATA_TUPLE = tupsAvail + | mdl == dATA_LIST = listAvail + | otherwise = [] + !exportedNames = concatMap availNamesWithSelectors + (special_exports <> mi_exports mod_iface) - decls <- case tcg_rn_decls of - Nothing -> do - tell [ "Warning: Renamed source is not available" ] - pure [] - Just dx -> - pure (topDecls dx) + fixities :: FixMap + fixities = mkFixMap exportedNames (mi_fixities mod_iface) + + -- This is used for looking up the Name of a default method + -- from its OccName. See Note [default method Name] in GHC.Iface.Recomp + def_meths_env = mkOccEnv def_meths + def_meths = [ (nameOccName nm, nm) + | (_, IfaceId { ifName = nm }) <- mi_decls mod_iface + , let occ = nameOccName nm + , isDefaultMethodOcc occ + ] + mod_iface_docs <- case mi_docs mod_iface of + Just docs -> pure docs + Nothing -> do + liftErrMsg $ tell [showPpr dflags mdl ++ " has no docs in its .hi-file"] + pure emptyDocs -- Derive final options to use for haddocking this module - doc_opts <- liftErrMsg $ mkDocOpts (haddockOptions ms_hspp_opts) flags tcg_mod - - let - -- All elements of an explicit export list, if present - export_list :: Maybe [(IE GhcRn, Avails)] - export_list - | OptIgnoreExports `elem` doc_opts = - Nothing - | Just rn_exports <- tcg_rn_exports = - Just [ (ie, avail) | (L _ ie, avail) <- rn_exports ] - | otherwise = - Nothing - - -- All the exported Names of this module. - exported_names :: [Name] - exported_names = - concatMap availNamesWithSelectors tcg_exports - - -- Module imports of the form `import X`. Note that there is - -- a) no qualification and - -- b) no import list - imported_modules :: Map ModuleName [ModuleName] - imported_modules - | Just{} <- export_list = - unrestrictedModuleImports (map unLoc tcg_rn_imports) - | otherwise = - M.empty - - -- TyThings that have instances defined in this module - local_instances :: [Name] - local_instances = - [ name - | name <- map getName tcg_insts ++ map getName tcg_fam_insts - , nameIsLocalOrFrom tcg_semantic_mod name - ] - - -- Infer module safety - safety <- liftIO (finalSafeMode ms_hspp_opts tc_gbl_env) - - -- The docs added via Template Haskell's putDoc - thDocs@ExtractedTHDocs { ethd_mod_header = thMbDocStr } <- - liftIO $ extractTHDocs <$> readIORef tcg_th_docs - - -- Process the top-level module header documentation. - (!info, header_doc) <- liftErrMsg $ processModuleHeader dflags pkg_name - tcg_rdr_env safety (thMbDocStr <|> (unLoc <$> tcg_doc_hdr)) - - -- Warnings on declarations in this module - decl_warnings <- liftErrMsg (mkWarningMap dflags tcg_warns tcg_rdr_env exported_names) - - -- Warning on the module header - mod_warning <- liftErrMsg (moduleWarning dflags tcg_rdr_env tcg_warns) + doc_opts <- liftErrMsg $ mkDocOpts (docs_haddock_opts mod_iface_docs) flags mdl + + let prr | OptPrintRuntimeRep `elem` doc_opts = ShowRuntimeRep + | otherwise = HideRuntimeRep + + (!info, header_doc) <- liftErrMsg $ processModuleHeader dflags pkg_name safety + (docs_language mod_iface_docs) + (docs_extensions mod_iface_docs) + (docs_mod_hdr mod_iface_docs) + mod_warning <- liftErrMsg $ moduleWarning dflags warnings + + let process = liftErrMsg . processDocStringParas dflags pkg_name + docMap <- traverse process (docs_decls mod_iface_docs) + argMap <- traverse (traverse process) (docs_args mod_iface_docs) + + warningMap <- liftErrMsg $ mkWarningMap dflags warnings exportedNames + + let local_instances = filter (nameIsLocalOrFrom sem_mdl) + $ map getName instances + ++ map getName fam_instances + instanceMap = M.fromList [(l, n) | n <- local_instances, RealSrcSpan l _ <- [getSrcSpan n] ] + + -- See Note [Exporting built-in items] + let builtinTys = DsiSectionHeading 1 (HsDoc (mkHsDocString "Builtin syntax") []) + bonus_ds mods + | mdl == gHC_TYPES = [ DsiExports (listAvail <> eqAvail) ] <> mods + | mdl == gHC_PRIM = [ builtinTys, DsiExports funAvail ] <> mods + | mdl == pRELUDE = let (hs, rest) = splitAt 2 mods + in hs <> [ DsiExports (listAvail <> funAvail) ] <> rest + | mdl == dATA_TUPLE = mods <> [ DsiExports tupsAvail ] + | mdl == dATA_LIST = [ DsiExports listAvail ] <> mods + | otherwise = mods let -- Warnings in this module and transitive warnings from dependend modules - warnings :: Map Name (Doc Name) - warnings = M.unions (decl_warnings : map ifaceWarningMap (M.elems ifaces)) + transitiveWarnings :: Map Name (Doc Name) + transitiveWarnings = M.unions (warningMap : map ifaceWarningMap (M.elems ifaces)) - maps@(!docs, !arg_docs, !decl_map, _) <- - liftErrMsg (mkMaps dflags pkg_name tcg_rdr_env local_instances decls thDocs) - - export_items <- mkExportItems is_sig ifaces pkg_name tcg_mod tcg_semantic_mod - warnings tcg_rdr_env exported_names (map fst decls) maps fixities - imported_modules loc_splices export_list tcg_exports inst_ifaces dflags + export_items <- mkExportItems prr ifaces pkg_name mdl transitiveWarnings + docMap argMap fixities (docs_named_chunks mod_iface_docs) + (bonus_ds $ docs_structure mod_iface_docs) inst_ifaces dflags def_meths_env let visible_names :: [Name] - visible_names = mkVisibleNames maps export_items doc_opts + visible_names = mkVisibleNames instanceMap export_items doc_opts -- Measure haddock documentation coverage. pruned_export_items :: [ExportItem GhcRn] pruned_export_items = pruneExportItems export_items !haddockable = 1 + length export_items -- module + exports - !haddocked = (if isJust tcg_doc_hdr then 1 else 0) + length pruned_export_items + !haddocked = (if isJust header_doc then 1 else 0) + length pruned_export_items coverage :: (Int, Int) !coverage = (haddockable, haddocked) - aliases :: Map Module ModuleName - aliases = mkAliasMap unit_state tcg_rn_imports - return $! Interface { - ifaceMod = tcg_mod + ifaceMod = mdl , ifaceIsSig = is_sig - , ifaceOrigFilename = msHsFilePath mod_sum - , ifaceHieFile = Just ml_hie_file + , ifaceHieFile = ml_hie_file , ifaceInfo = info , ifaceDoc = Documentation header_doc mod_warning , ifaceRnDoc = Documentation Nothing Nothing , ifaceOptions = doc_opts - , ifaceDocMap = docs - , ifaceArgMap = arg_docs + , ifaceDocMap = docMap + , ifaceArgMap = argMap , ifaceRnDocMap = M.empty , ifaceRnArgMap = M.empty , ifaceExportItems = if OptPrune `elem` doc_opts then pruned_export_items else export_items , ifaceRnExportItems = [] - , ifaceExports = exported_names + , ifaceExports = exportedNames , ifaceVisibleExports = visible_names - , ifaceDeclMap = decl_map , ifaceFixMap = fixities - , ifaceModuleAliases = aliases - , ifaceInstances = tcg_insts - , ifaceFamInstances = tcg_fam_insts + , ifaceInstances = instances + , ifaceFamInstances = fam_instances , ifaceOrphanInstances = [] -- Filled in attachInstances , ifaceRnOrphanInstances = [] -- Filled in attachInstances , ifaceHaddockCoverage = coverage - , ifaceWarningMap = warnings + , ifaceWarningMap = warningMap , ifaceDynFlags = dflags + , ifaceDefMeths = def_meths } - - --- | Given all of the @import M as N@ declarations in a package, --- create a mapping from the module identity of M, to an alias N --- (if there are multiple aliases, we pick the last one.) This --- will go in 'ifaceModuleAliases'. -mkAliasMap :: UnitState -> [LImportDecl GhcRn] -> M.Map Module ModuleName -mkAliasMap state impDecls = - M.fromList $ - mapMaybe (\(SrcLoc.L _ impDecl) -> do - SrcLoc.L _ alias <- ideclAs impDecl - return $ - (lookupModuleDyn state - -- TODO: This is supremely dodgy, because in general the - -- UnitId isn't going to look anything like the package - -- qualifier (even with old versions of GHC, the - -- IPID would be p-0.1, but a package qualifier never - -- has a version number it. (Is it possible that in - -- Haddock-land, the UnitIds never have version numbers? - -- I, ezyang, have not quite understand Haddock's package - -- identifier model.) - -- - -- Additionally, this is simulating some logic GHC already - -- has for deciding how to qualify names when it outputs - -- them to the user. We should reuse that information; - -- or at least reuse the renamed imports, which know what - -- they import! - (fmap Module.fsToUnit $ - fmap sl_fs $ ideclPkgQual impDecl) - (case ideclName impDecl of SrcLoc.L _ name -> name), - alias)) - impDecls - --- We want to know which modules are imported without any qualification. This --- way we can display module reexports more compactly. This mapping also looks --- through aliases: --- --- module M (module X) where --- import M1 as X --- import M2 as X --- --- With our mapping we know that we can display exported modules M1 and M2. --- -unrestrictedModuleImports :: [ImportDecl GhcRn] -> M.Map ModuleName [ModuleName] -unrestrictedModuleImports idecls = - M.map (map (unLoc . ideclName)) - $ M.filter (all isInteresting) impModMap where - impModMap = - M.fromListWith (++) (concatMap moduleMapping idecls) - - moduleMapping idecl = - concat [ [ (unLoc (ideclName idecl), [idecl]) ] - , [ (unLoc mod_name, [idecl]) - | Just mod_name <- [ideclAs idecl] - ] - ] - - isInteresting idecl = - case ideclHiding idecl of - -- i) no subset selected - Nothing -> True - -- ii) an import with a hiding clause - -- without any names - Just (True, L _ []) -> True - -- iii) any other case of qualification - _ -> False - --- Similar to GHC.lookupModule --- ezyang: Not really... -lookupModuleDyn :: - UnitState -> Maybe Unit -> ModuleName -> Module -lookupModuleDyn _ (Just pkgId) mdlName = - Module.mkModule pkgId mdlName -lookupModuleDyn state Nothing mdlName = - case lookupModuleInAllUnits state mdlName of - (m,_):_ -> m - [] -> Module.mkModule Module.mainUnit mdlName + -- Note [Exporting built-in items] + -- + -- Some items do not show up in their modules exports simply because Haskell + -- lacks the concrete syntax to represent such an export. We'd still like + -- these to show up in docs, so we manually patch on some extra exports for a + -- small number of modules: + -- + -- * "GHC.Prim" should export @(->)@ + -- * "GHC.Types" should export @[]([], (:))@ and @(~)@ + -- * "Prelude" should export @(->)@ and @[]([], (:))@ + -- * "Data.Tuple" should export tuples up to arity 15 (that is the number + -- that Haskell98 guarantees exist and that is also the point at which + -- GHC stops providing instances) + -- + listAvail = [ availTC listTyConName + [listTyConName, nilDataConName, consDataConName] + [] ] + funAvail = [ availTC funTyConName [funTyConName] [] ] + eqAvail = [ availTC eqTyConName [eqTyConName] [] ] + tupsAvail = [ availTC tyName [tyName, datName] [] + | i<-[0..15] + , let tyName = tupleTyConName BoxedTuple i + , let datName = getName $ tupleDataCon Boxed i + ] ------------------------------------------------------------------------------- -- Warnings ------------------------------------------------------------------------------- -mkWarningMap :: DynFlags -> Warnings -> GlobalRdrEnv -> [Name] -> ErrMsgM WarningMap -mkWarningMap dflags warnings gre exps = case warnings of +mkWarningMap :: DynFlags -> Warnings (HsDoc Name) -> [Name] -> ErrMsgM WarningMap +mkWarningMap dflags warnings exps = case warnings of NoWarnings -> pure M.empty WarnAll _ -> pure M.empty WarnSome ws -> - let ws' = [ (n, w) - | (occ, w) <- ws - , elt <- lookupGlobalRdrEnv gre occ - , let n = greMangledName elt, n `elem` exps ] - in M.fromList <$> traverse (bitraverse pure (parseWarning dflags gre)) ws' - -moduleWarning :: DynFlags -> GlobalRdrEnv -> Warnings -> ErrMsgM (Maybe (Doc Name)) -moduleWarning _ _ NoWarnings = pure Nothing -moduleWarning _ _ (WarnSome _) = pure Nothing -moduleWarning dflags gre (WarnAll w) = Just <$> parseWarning dflags gre w - -parseWarning :: DynFlags -> GlobalRdrEnv -> WarningTxt -> ErrMsgM (Doc Name) -parseWarning dflags gre w = case w of - DeprecatedTxt _ msg -> format "Deprecated: " (foldMap (bytesFS . sl_fs . unLoc) msg) - WarningTxt _ msg -> format "Warning: " (foldMap (bytesFS . sl_fs . unLoc) msg) + let expsOccEnv = mkOccEnv [(nameOccName n, n) | n <- exps] + ws' = flip mapMaybe ws $ \(occ, w) -> + (,w) <$> lookupOccEnv expsOccEnv occ + in M.fromList <$> traverse (traverse (parseWarning dflags)) ws' + +moduleWarning :: DynFlags -> Warnings (HsDoc Name) -> ErrMsgM (Maybe (Doc Name)) +moduleWarning dflags = \case + NoWarnings -> pure Nothing + WarnSome _ -> pure Nothing + WarnAll w -> Just <$> parseWarning dflags w + +parseWarning :: DynFlags -> WarningTxt (HsDoc Name) -> ErrMsgM (Doc Name) +parseWarning dflags w = + -- TODO: Find something more efficient than (foldl' appendHsDoc) + format heading (foldl' appendHsDoc emptyHsDoc msgs) where - format x bs = DocWarning . DocParagraph . DocAppend (DocString x) - <$> processDocString dflags gre (mkHsDocStringUtf8ByteString bs) - + format x msg = DocWarning . DocParagraph . DocAppend (DocString x) + <$> processDocString dflags msg + heading = case sort_ of + WsWarning -> "Warning: " + WsDeprecated -> "Deprecated: " + (sort_, msgs) = warningTxtContents w ------------------------------------------------------------------------------- -- Doc options @@ -455,16 +364,15 @@ mkDocOpts mbOpts flags mdl = do go os m | m == Flag_HideModule mdlStr = OptHide : os | m == Flag_ShowModule mdlStr = filter (/= OptHide) os | m == Flag_ShowAllModules = filter (/= OptHide) os - | m == Flag_IgnoreAllExports = OptIgnoreExports : os - | m == Flag_ShowExtensions mdlStr = OptIgnoreExports : os + | m == Flag_ShowExtensions mdlStr = OptShowExtensions : os | otherwise = os parseOption :: String -> ErrMsgM (Maybe DocOption) parseOption "hide" = return (Just OptHide) parseOption "prune" = return (Just OptPrune) -parseOption "ignore-exports" = return (Just OptIgnoreExports) parseOption "not-home" = return (Just OptNotHome) parseOption "show-extensions" = return (Just OptShowExtensions) +parseOption "print-explicit-runtime-reps" = return (Just OptPrintRuntimeRep) parseOption other = tell ["Unrecognised option: " ++ other] >> return Nothing @@ -472,119 +380,6 @@ parseOption other = tell ["Unrecognised option: " ++ other] >> return Nothing -- Maps -------------------------------------------------------------------------------- - -type Maps = (DocMap Name, ArgMap Name, DeclMap, InstMap) - --- | Create 'Maps' by looping through the declarations. For each declaration, --- find its names, its subordinates, and its doc strings. Process doc strings --- into 'Doc's. -mkMaps :: DynFlags - -> Maybe Package -- this package - -> GlobalRdrEnv - -> [Name] - -> [(LHsDecl GhcRn, [HsDocString])] - -> ExtractedTHDocs -- ^ Template Haskell putDoc docs - -> ErrMsgM Maps -mkMaps dflags pkgName gre instances decls thDocs = do - (a, b, c) <- unzip3 <$> traverse mappings decls - (th_a, th_b) <- thMappings - pure ( th_a `M.union` f' (map (nubByName fst) a) - , fmap intmap2mapint $ - th_b `unionArgMaps` (f (filterMapping (not . IM.null) b)) - , f (filterMapping (not . null) c) - , instanceMap - ) - where - f :: (Ord a, Monoid b) => [[(a, b)]] -> Map a b - f = M.fromListWith (<>) . concat - - f' :: [[(Name, MDoc Name)]] -> Map Name (MDoc Name) - f' = M.fromListWith metaDocAppend . concat - - filterMapping :: (b -> Bool) -> [[(a, b)]] -> [[(a, b)]] - filterMapping p = map (filter (p . snd)) - - -- Convert IntMap -> IntMap - -- TODO: should ArgMap eventually be switched over to IntMap? - intmap2mapint = M.fromList . IM.toList - - -- | Extract the mappings from template haskell. - -- No DeclMap/InstMap is needed since we already have access to the - -- doc strings - thMappings :: ErrMsgM (Map Name (MDoc Name), Map Name (IntMap (MDoc Name))) - thMappings = do - let ExtractedTHDocs - _ - (DeclDocMap declDocs) - (ArgDocMap argDocs) - (DeclDocMap instDocs) = thDocs - ds2mdoc :: HsDocString -> ErrMsgM (MDoc Name) - ds2mdoc = processDocStringParas dflags pkgName gre - - declDocs' <- mapM ds2mdoc declDocs - argDocs' <- mapM (mapM ds2mdoc) argDocs - instDocs' <- mapM ds2mdoc instDocs - return (declDocs' <> instDocs', argDocs') - - - mappings :: (LHsDecl GhcRn, [HsDocString]) - -> ErrMsgM ( [(Name, MDoc Name)] - , [(Name, IntMap (MDoc Name))] - , [(Name, [LHsDecl GhcRn])] - ) - mappings (ldecl@(L (SrcSpanAnn _ (RealSrcSpan l _)) decl), docStrs) = do - let declDoc :: [HsDocString] -> IntMap HsDocString - -> ErrMsgM (Maybe (MDoc Name), IntMap (MDoc Name)) - declDoc strs m = do - doc' <- processDocStrings dflags pkgName gre strs - m' <- traverse (processDocStringParas dflags pkgName gre) m - pure (doc', m') - - (doc, args) <- declDoc docStrs (declTypeDocs decl) - - let - subs :: [(Name, [HsDocString], IntMap HsDocString)] - subs = subordinates instanceMap decl - - (subDocs, subArgs) <- unzip <$> traverse (\(_, strs, m) -> declDoc strs m) subs - - let - ns = names l decl - subNs = [ n | (n, _, _) <- subs ] - dm = [ (n, d) | (n, Just d) <- zip ns (repeat doc) ++ zip subNs subDocs ] - am = [ (n, args) | n <- ns ] ++ zip subNs subArgs - cm = [ (n, [ldecl]) | n <- ns ++ subNs ] - - seqList ns `seq` - seqList subNs `seq` - doc `seq` - seqList subDocs `seq` - seqList subArgs `seq` - pure (dm, am, cm) - mappings (L (SrcSpanAnn _ (UnhelpfulSpan _)) _, _) = pure ([], [], []) - - instanceMap :: Map RealSrcSpan Name - instanceMap = M.fromList [(l, n) | n <- instances, RealSrcSpan l _ <- [getSrcSpan n] ] - - names :: RealSrcSpan -> HsDecl GhcRn -> [Name] - names _ (InstD _ d) = maybeToList (SrcLoc.lookupSrcSpan loc instanceMap) -- See note [2]. - where loc = case d of - -- The CoAx's loc is the whole line, but only for TFs. The - -- workaround is to dig into the family instance declaration and - -- get the identifier with the right location. - TyFamInstD _ (TyFamInstDecl _ d') -> getLocA (feqn_tycon d') - _ -> getInstLoc d - names l (DerivD {}) = maybeToList (M.lookup l instanceMap) -- See note [2]. - names _ decl = getMainDeclBinder decl - --- Note [2]: ------------- --- We relate ClsInsts to InstDecls and DerivDecls using the SrcSpans buried --- inside them. That should work for normal user-written instances (from --- looking at GHC sources). We can assume that commented instances are --- user-written. This lets us relate Names (from ClsInsts) to comments --- (associated with InstDecls and DerivDecls). - -------------------------------------------------------------------------------- -- Declarations -------------------------------------------------------------------------------- @@ -592,11 +387,12 @@ mkMaps dflags pkgName gre instances decls thDocs = do -- | Extract a map of fixity declarations only -mkFixMap :: HsGroup GhcRn -> FixMap -mkFixMap group_ = - M.fromList [ (n,f) - | L _ (FixitySig _ ns f) <- hsGroupTopLevelFixitySigs group_, - L _ n <- ns ] +mkFixMap :: [Name] -> [(OccName, Fixity)] -> FixMap +mkFixMap exps occFixs = + M.fromList $ flip mapMaybe occFixs $ \(occ, fix_) -> + (,fix_) <$> lookupOccEnv expsOccEnv occ + where + expsOccEnv = mkOccEnv (map (nameOccName &&& id) exps) -- | Build the list of items that will become the documentation, from the @@ -606,171 +402,159 @@ mkFixMap group_ = -- We create the export items even if the module is hidden, since they -- might be useful when creating the export items for other modules. mkExportItems - :: Monad m - => Bool -- is it a signature + :: forall m. Monad m + => PrintRuntimeReps -> IfaceMap -> Maybe Package -- this package -> Module -- this module - -> Module -- semantic module -> WarningMap - -> GlobalRdrEnv - -> [Name] -- exported names (orig) - -> [LHsDecl GhcRn] -- renamed source declarations - -> Maps + -> DocMap Name + -> ArgMap Name -> FixMap - -> M.Map ModuleName [ModuleName] - -> [SrcSpan] -- splice locations - -> Maybe [(IE GhcRn, Avails)] - -> Avails -- exported stuff from this module + -> Map String (HsDoc Name) -- named chunks + -> DocStructure -> InstIfaceMap -> DynFlags + -> OccEnv Name -> IfM m [ExportItem GhcRn] mkExportItems - is_sig modMap pkgName thisMod semMod warnings gre exportedNames decls - maps fixMap unrestricted_imp_mods splices exportList allExports - instIfaceMap dflags = - case exportList of - Nothing -> - fullModuleContents is_sig modMap pkgName thisMod semMod warnings gre - exportedNames decls maps fixMap splices instIfaceMap dflags - allExports - Just exports -> liftM concat $ mapM lookupExport exports + prr modMap pkgName thisMod warnings docMap argMap fixMap namedChunks dsItems + instIfaceMap dflags defMeths = + concat <$> traverse lookupExport dsItems where - lookupExport (IEGroup _ lev docStr, _) = liftErrMsg $ do - doc <- processDocString dflags gre docStr - return [ExportGroup lev "" doc] - - lookupExport (IEDoc _ docStr, _) = liftErrMsg $ do - doc <- processDocStringParas dflags pkgName gre docStr - return [ExportDoc doc] - - lookupExport (IEDocNamed _ str, _) = liftErrMsg $ - findNamedDoc str [ unL d | d <- decls ] >>= \case - Nothing -> return [] - Just docStr -> do - doc <- processDocStringParas dflags pkgName gre docStr - return [ExportDoc doc] - - lookupExport (IEModuleContents _ (L _ mod_name), _) - -- only consider exporting a module if we are sure we - -- are really exporting the whole module and not some - -- subset. We also look through module aliases here. - | Just mods <- M.lookup mod_name unrestricted_imp_mods - , not (null mods) - = concat <$> traverse (moduleExport thisMod dflags modMap instIfaceMap) mods - - lookupExport (_, avails) = - concat <$> traverse availExport (nubAvails avails) + lookupExport :: DocStructureItem -> IfM m [ExportItem GhcRn] + lookupExport = \case + DsiSectionHeading lev hsDoc' -> do + doc <- liftErrMsg $ processDocString dflags hsDoc' + pure [ExportGroup lev "" doc] + DsiDocChunk hsDoc' -> do + doc <- liftErrMsg $ processDocStringParas dflags pkgName hsDoc' + pure [ExportDoc doc] + DsiNamedChunkRef ref -> do + case M.lookup ref namedChunks of + Nothing -> do + liftErrMsg $ tell ["Cannot find documentation for: $" ++ ref] + pure [] + Just hsDoc' -> do + doc <- liftErrMsg $ processDocStringParas dflags pkgName hsDoc' + pure [ExportDoc doc] + DsiExports avails -> + -- TODO: We probably don't need nubAvails here. + -- mkDocStructureFromExportList already uses it. + concat <$> traverse availExport (nubAvails avails) + DsiModExport mod_names avails -> do + -- only consider exporting a module if we are sure we are really + -- exporting the whole module and not some subset. + (unrestricted_mods, remaining_avails) <- unrestrictedModExports dflags thisMod modMap instIfaceMap avails (NE.toList mod_names) + avail_exps <- concat <$> traverse availExport remaining_avails + pure (map ExportModule unrestricted_mods ++ avail_exps) availExport avail = - availExportItem is_sig modMap thisMod semMod warnings exportedNames - maps fixMap splices instIfaceMap dflags avail - - --- Extract the minimal complete definition of a Name, if one exists -minimalDef :: Monad m => Name -> IfM m (Maybe ClassMinimalDef) -minimalDef n = do - mty <- lookupName n - case mty of - Just (ATyCon (tyConClass_maybe -> Just c)) -> - return . Just $ classMinimalDef c - _ -> - return Nothing + availExportItem prr modMap thisMod warnings + docMap argMap fixMap instIfaceMap dflags avail defMeths +unrestrictedModExports + :: Monad m + => DynFlags + -> Module -- ^ Current Module + -> IfaceMap -- ^ Already created interfaces + -> InstIfaceMap -- ^ Interfaces in other packages + -> Avails -- ^ Modules to be exporte + -> [ModuleName] + -> IfM m ([Module], Avails) + -- ^ ( modules exported without restriction + -- , remaining exports not included in any + -- of these modules + -- ) +unrestrictedModExports dflags thisMod ifaceMap instIfaceMap avails mod_names = do + mods_and_exports <- fmap catMaybes $ for mod_names $ \mod_name -> do + let m_local = mkModule (moduleUnit thisMod) mod_name + case M.lookup m_local ifaceMap of + -- First lookup locally + Just iface -> pure $ Just (ifaceMod iface, mkNameSet (ifaceExports iface)) + Nothing -> + case M.lookup mod_name instIfaceMap' of + Just iface -> pure $ Just (instMod iface, mkNameSet (instExports iface)) + Nothing -> do + liftErrMsg $ tell ["Warning: " ++ pretty dflags thisMod ++ ": Could not find " ++ + "documentation for exported module: " ++ pretty dflags mod_name] + pure Nothing + let unrestricted = filter everythingVisible mods_and_exports + mod_exps = unionNameSets (map snd unrestricted) + remaining = nubAvails (filterAvails (\n -> not (n `elemNameSet` mod_exps)) avails) + pure (map fst unrestricted, remaining) + where + instIfaceMap' = (M.mapKeys moduleName instIfaceMap) + all_names = availsToNameSetWithSelectors avails + + -- Is everything in this (supposedly re-exported) module visible? + everythingVisible :: (Module, NameSet) -> Bool + everythingVisible (mdl, exps) + | not (exps `isSubsetOf` all_names) = False + | Just iface <- M.lookup mdl ifaceMap = OptHide `notElem` ifaceOptions iface + | Just iface <- M.lookup (moduleName mdl) instIfaceMap' = OptHide `notElem` instOptions iface + | otherwise = True + + -- TODO: Add a utility based on IntMap.isSubmapOfBy + isSubsetOf :: NameSet -> NameSet -> Bool + isSubsetOf a b = nameSetAll (`elemNameSet` b) a + availExportItem :: forall m . Monad m - => Bool -- is it a signature + => PrintRuntimeReps -> IfaceMap -> Module -- this module - -> Module -- semantic module -> WarningMap - -> [Name] -- exported names (orig) - -> Maps + -> DocMap Name -- docs (keyed by 'Name's) + -> ArgMap Name -- docs for arguments (keyed by 'Name's) -> FixMap - -> [SrcSpan] -- splice locations -> InstIfaceMap -> DynFlags -> AvailInfo + -> OccEnv Name -- Default methods -> IfM m [ExportItem GhcRn] -availExportItem is_sig modMap thisMod semMod warnings exportedNames - (docMap, argMap, declMap, _) fixMap splices instIfaceMap - dflags availInfo = declWith availInfo +availExportItem prr modMap thisMod warnings docMap argMap fixMap instIfaceMap + dflags availInfo defMeths = declWith availInfo where declWith :: AvailInfo -> IfM m [ ExportItem GhcRn ] declWith avail = do let t = availName avail - r <- findDecl avail - case r of - ([L l' (ValD _ _)], (doc, _)) -> do - let l = locA l' - -- Top-level binding without type signature - export <- hiValExportItem dflags t l doc (l `elem` splices) $ M.lookup t fixMap - return [export] - (ds, docs_) | decl : _ <- filter (not . isValD . unLoc) ds -> - let declNames = getMainDeclBinder (unL decl) - in case () of - _ - -- We should not show a subordinate by itself if any of its - -- parents is also exported. See note [1]. - | t `notElem` declNames, - Just p <- find isExported (parents t $ unL decl) -> - do liftErrMsg $ tell [ - "Warning: " ++ moduleString thisMod ++ ": " ++ - pretty dflags (nameOccName t) ++ " is exported separately but " ++ - "will be documented under " ++ pretty dflags (nameOccName p) ++ - ". Consider exporting it together with its parent(s)" ++ - " for code clarity." ] - return [] - - -- normal case - | otherwise -> case decl of - -- A single signature might refer to many names, but we - -- create an export item for a single name only. So we - -- modify the signature to contain only that single name. - L loc (SigD _ sig) -> - -- fromJust is safe since we already checked in guards - -- that 't' is a name declared in this declaration. - let newDecl = L loc . SigD noExtField . fromJust $ filterSigNames (== t) sig - in availExportDecl avail newDecl docs_ - - L loc (TyClD _ ClassDecl {..}) -> do - mdef <- minimalDef t - let sig = maybeToList $ fmap (noLocA . MinimalSig noAnn NoSourceText . noLocA . fmap noLocA) mdef - availExportDecl avail - (L loc $ TyClD noExtField ClassDecl { tcdSigs = sig ++ tcdSigs, .. }) docs_ - - _ -> availExportDecl avail decl docs_ - - -- Declaration from another package - ([], _) -> do - mayDecl <- hiDecl dflags t - case mayDecl of - Nothing -> return [ ExportNoDecl t [] ] - Just decl -> - -- We try to get the subs and docs - -- from the installed .haddock file for that package. - -- TODO: This needs to be more sophisticated to deal - -- with signature inheritance - case M.lookup (nameModule t) instIfaceMap of - Nothing -> do - liftErrMsg $ tell - ["Warning: Couldn't find .haddock for export " ++ pretty dflags t] - let subs_ = availNoDocs avail - availExportDecl avail decl (noDocForDecl, subs_) - Just iface -> - availExportDecl avail decl (lookupDocs avail warnings (instDocMap iface) (instArgMap iface)) - - _ -> return [] + mayDecl <- hiDecl dflags prr t + case mayDecl of + Nothing -> return [ ExportNoDecl t [] ] + Just decl -> do + availExportDecl avail decl =<< do + -- Find docs for decl + let tmod = nameModule t + if tmod == thisMod + then pure (lookupDocs avail warnings docMap argMap defMeths) + else case M.lookup tmod modMap of + Just iface -> + pure (lookupDocs avail warnings (ifaceDocMap iface) (ifaceArgMap iface) (mkOccEnv (ifaceDefMeths iface))) + Nothing -> + -- We try to get the subs and docs + -- from the installed .haddock file for that package. + -- TODO: This needs to be more sophisticated to deal + -- with signature inheritance + case M.lookup (nameModule t) instIfaceMap of + Nothing -> do + liftErrMsg $ tell + ["Warning: " ++ pretty dflags thisMod ++ + ": Couldn't find .haddock for export " ++ pretty dflags t] + let subs_ = availNoDocs avail + pure (noDocForDecl, subs_) + Just instIface -> + pure (lookupDocs avail warnings (instDocMap instIface) (instArgMap instIface) (mkOccEnv (instDefMeths instIface))) + -- Tries 'extractDecl' first then falls back to 'hiDecl' if that fails availDecl :: Name -> LHsDecl GhcRn -> IfM m (LHsDecl GhcRn) - availDecl declName parentDecl = - case extractDecl declMap declName parentDecl of + availDecl declName parentDecl = extractDecl prr dflags declName parentDecl >>= \case Right d -> pure d Left err -> do - synifiedDeclOpt <- hiDecl dflags declName + synifiedDeclOpt <- hiDecl dflags prr declName case synifiedDeclOpt of Just synifiedDecl -> pure synifiedDecl Nothing -> pprPanic "availExportItem" (O.text err) @@ -788,7 +572,7 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames let patSynNames = - concatMap (getMainDeclBinder . fst) bundledPatSyns + concatMap (getMainDeclBinder emptyOccEnv . fst) bundledPatSyns fixities = [ (n, f) @@ -820,38 +604,6 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames , expItemSpliced = False } ) - exportedNameSet = mkNameSet exportedNames - isExported n = elemNameSet n exportedNameSet - - findDecl :: AvailInfo -> IfM m ([LHsDecl GhcRn], (DocForDecl Name, [(Name, DocForDecl Name)])) - findDecl avail - | m == semMod = - case M.lookup n declMap of - Just ds -> return (ds, lookupDocs avail warnings docMap argMap) - Nothing - | is_sig -> do - -- OK, so it wasn't in the local declaration map. It could - -- have been inherited from a signature. Reconstitute it - -- from the type. - mb_r <- hiDecl dflags n - case mb_r of - Nothing -> return ([], (noDocForDecl, availNoDocs avail)) - -- TODO: If we try harder, we might be able to find - -- a Haddock! Look in the Haddocks for each thing in - -- requirementContext (unitState) - Just decl -> return ([decl], (noDocForDecl, availNoDocs avail)) - | otherwise -> - return ([], (noDocForDecl, availNoDocs avail)) - | Just iface <- M.lookup (semToIdMod (moduleUnit thisMod) m) modMap - , Just ds <- M.lookup n (ifaceDeclMap iface) = - return (ds, lookupDocs avail warnings - (ifaceDocMap iface) - (ifaceArgMap iface)) - | otherwise = return ([], (noDocForDecl, availNoDocs avail)) - where - n = availName avail - m = nameModule n - findBundledPatterns :: AvailInfo -> IfM m [(HsDecl GhcRn, DocForDecl Name)] findBundledPatterns avail = do patsyns <- for constructor_names $ \name -> do @@ -878,21 +630,14 @@ availNoDocs :: AvailInfo -> [(Name, DocForDecl Name)] availNoDocs avail = zip (availSubordinates avail) (repeat noDocForDecl) --- | Given a 'Module' from a 'Name', convert it into a 'Module' that --- we can actually find in the 'IfaceMap'. -semToIdMod :: Unit -> Module -> Module -semToIdMod this_uid m - | Module.isHoleModule m = mkModule this_uid (moduleName m) - | otherwise = m - -hiDecl :: Monad m => DynFlags -> Name -> IfM m (Maybe (LHsDecl GhcRn)) -hiDecl dflags t = do +hiDecl :: Monad m => DynFlags -> PrintRuntimeReps -> Name -> IfM m (Maybe (LHsDecl GhcRn)) +hiDecl dflags prr t = do mayTyThing <- lookupName t case mayTyThing of Nothing -> do liftErrMsg $ tell ["Warning: Not found in environment: " ++ pretty dflags t] return Nothing - Just x -> case tyThingToLHsDecl ShowRuntimeRep x of + Just x -> case tyThingToLHsDecl prr x of Left m -> liftErrMsg (tell [bugWarn m]) >> return Nothing Right (m, t') -> liftErrMsg (tell $ map bugWarn m) >> return (Just $ noLocA t') @@ -902,69 +647,26 @@ hiDecl dflags t = do O.text "-- Please report this on Haddock issue tracker!" bugWarn = showSDoc dflags . warnLine --- | This function is called for top-level bindings without type signatures. --- It gets the type signature from GHC and that means it's not going to --- have a meaningful 'SrcSpan'. So we pass down 'SrcSpan' for the --- declaration and use it instead - 'nLoc' here. -hiValExportItem - :: Monad m => DynFlags -> Name -> SrcSpan -> DocForDecl Name -> Bool - -> Maybe Fixity -> IfM m (ExportItem GhcRn) -hiValExportItem dflags name nLoc doc splice fixity = do - mayDecl <- hiDecl dflags name - case mayDecl of - Nothing -> return (ExportNoDecl name []) - Just decl -> return (ExportDecl (fixSpan decl) [] doc [] [] fixities splice) - where - fixSpan (L (SrcSpanAnn a l) t) = L (SrcSpanAnn a (SrcLoc.combineSrcSpans l nLoc)) t - fixities = case fixity of - Just f -> [(name, f)] - Nothing -> [] - - -- | Lookup docs for a declaration from maps. -lookupDocs :: AvailInfo -> WarningMap -> DocMap Name -> ArgMap Name +lookupDocs :: AvailInfo -> WarningMap -> DocMap Name -> ArgMap Name -> OccEnv Name -> (DocForDecl Name, [(Name, DocForDecl Name)]) -lookupDocs avail warnings docMap argMap = +lookupDocs avail warnings docMap argMap def_meths_env = let n = availName avail in - let lookupArgDoc x = M.findWithDefault M.empty x argMap in - let doc = (lookupDoc n, lookupArgDoc n) in + let lookupArgDoc x = M.findWithDefault IM.empty x argMap in + let doc = (lookupDoc n, lookupArgDoc n) + subs = availSubordinates avail + def_meths = [ (meth, (lookupDoc meth, lookupArgDoc meth)) + | s <- subs + , let dmOcc = mkDefaultMethodOcc (nameOccName s) + , Just meth <- [lookupOccEnv def_meths_env dmOcc]] in let subDocs = [ (s, (lookupDoc s, lookupArgDoc s)) - | s <- availSubordinates avail - ] in + | s <- subs + ] ++ def_meths in (doc, subDocs) where lookupDoc name = Documentation (M.lookup name docMap) (M.lookup name warnings) --- | Export the given module as `ExportModule`. We are not concerned with the --- single export items of the given module. -moduleExport - :: Monad m - => Module -- ^ Module A (identity, NOT semantic) - -> DynFlags -- ^ The flags used when typechecking A - -> IfaceMap -- ^ Already created interfaces - -> InstIfaceMap -- ^ Interfaces in other packages - -> ModuleName -- ^ The exported module - -> IfM m [ExportItem GhcRn] -- ^ Resulting export items -moduleExport thisMod dflags ifaceMap instIfaceMap expMod = - -- NB: we constructed the identity module when looking up in - -- the IfaceMap. - case M.lookup m ifaceMap of - Just iface - | OptHide `elem` ifaceOptions iface -> return (ifaceExportItems iface) - | otherwise -> return [ ExportModule m ] - - Nothing -> -- We have to try to find it in the installed interfaces - -- (external packages). - case M.lookup expMod (M.mapKeys moduleName instIfaceMap) of - Just iface -> return [ ExportModule (instMod iface) ] - Nothing -> do - liftErrMsg $ tell ["Warning: " ++ pretty dflags thisMod ++ ": Could not find " ++ - "documentation for exported module: " ++ pretty dflags expMod] - return [] - where - m = mkModule (moduleUnit thisMod) expMod -- Identity module! - -- Note [1]: ------------ -- It is unnecessary to document a subordinate by itself at the top level if @@ -982,55 +684,6 @@ moduleExport thisMod dflags ifaceMap instIfaceMap expMod = -- (For more information, see Trac #69) --- | Simplified variant of 'mkExportItems', where we can assume that --- every locally defined declaration is exported; thus, we just --- zip through the renamed declarations. - -fullModuleContents - :: Monad m - => Bool -- is it a signature - -> IfaceMap - -> Maybe Package -- this package - -> Module -- this module - -> Module -- semantic module - -> WarningMap - -> GlobalRdrEnv -- ^ The renaming environment - -> [Name] -- exported names (orig) - -> [LHsDecl GhcRn] -- renamed source declarations - -> Maps - -> FixMap - -> [SrcSpan] -- splice locations - -> InstIfaceMap - -> DynFlags - -> Avails - -> IfM m [ExportItem GhcRn] -fullModuleContents is_sig modMap pkgName thisMod semMod warnings gre exportedNames - decls maps@(_, _, declMap, _) fixMap splices instIfaceMap dflags avails = do - let availEnv = availsToNameEnv (nubAvails avails) - (concat . concat) `fmap` (for decls $ \decl -> do - case decl of - (L _ (DocD _ (DocGroup lev docStr))) -> do - doc <- liftErrMsg (processDocString dflags gre docStr) - return [[ExportGroup lev "" doc]] - (L _ (DocD _ (DocCommentNamed _ docStr))) -> do - doc <- liftErrMsg (processDocStringParas dflags pkgName gre docStr) - return [[ExportDoc doc]] - (L _ (ValD _ valDecl)) - | name:_ <- collectHsBindBinders CollNoDictBinders valDecl - , Just (L _ SigD{}:_) <- filter isSigD <$> M.lookup name declMap - -> return [] - _ -> - for (getMainDeclBinder (unLoc decl)) $ \nm -> do - case lookupNameEnv availEnv nm of - Just avail -> - availExportItem is_sig modMap thisMod - semMod warnings exportedNames maps fixMap - splices instIfaceMap dflags avail - Nothing -> pure []) - where - isSigD (L _ SigD{}) = True - isSigD _ = False - -- | Sometimes the declaration we want to export is not the "main" declaration: -- it might be an individual record selector or a class method. In these -- cases we have to extract the required declaration (and somehow cobble @@ -1039,13 +692,14 @@ fullModuleContents is_sig modMap pkgName thisMod semMod warnings gre exportedNam -- This function looks through the declarations in this module to try to find -- the one with the right name. extractDecl - :: HasCallStack - => DeclMap -- ^ all declarations in the file + :: Monad m + => PrintRuntimeReps + -> DynFlags -> Name -- ^ name of the declaration to extract -> LHsDecl GhcRn -- ^ parent declaration - -> Either ErrMsg (LHsDecl GhcRn) -extractDecl declMap name decl - | name `elem` getMainDeclBinder (unLoc decl) = pure decl + -> IfM m (Either ErrMsg (LHsDecl GhcRn)) +extractDecl prr dflags name decl + | name `elem` getMainDeclBinder emptyOccEnv (unLoc decl) = pure $ Right decl | otherwise = case unLoc decl of TyClD _ d@ClassDecl { tcdLName = L _ clsNm @@ -1070,17 +724,19 @@ extractDecl declMap name decl in case (matchesMethod, matchesAssociatedType) of ([s0], _) -> let tyvar_names = tyClDeclTyVars d L pos sig = addClassContext clsNm tyvar_names s0 - in pure (L pos (SigD noExtField sig)) - (_, [L pos fam_decl]) -> pure (L pos (TyClD noExtField (FamDecl noExtField fam_decl))) + in pure (Right $ L pos (SigD noExtField sig)) + (_, [L pos fam_decl]) -> pure (Right $ L pos (TyClD noExtField (FamDecl noExtField fam_decl))) - ([], []) - | Just (famInstDecl:_) <- M.lookup name declMap - -> extractDecl declMap name famInstDecl - _ -> Left (concat [ "Ambiguous decl for ", getOccString name + ([], []) -> do + famInstDeclOpt <- hiDecl dflags prr name + case famInstDeclOpt of + Nothing -> pure $ Left (concat [ "Ambiguous decl for ", getOccString name + , " in class ", getOccString clsNm ]) + Just famInstDecl -> extractDecl prr dflags name famInstDecl + _ -> pure $ Left (concat [ "Ambiguous decl for ", getOccString name , " in class ", getOccString clsNm ]) - TyClD _ d@DataDecl { tcdLName = L _ dataNm - , tcdDataDefn = HsDataDefn { dd_cons = dataCons } } -> do + , tcdDataDefn = HsDataDefn { dd_cons = dataCons } } -> pure $ do let ty_args = lHsQTyVarsToTypes (tyClDeclTyVars d) lsig <- if isDataConName name then extractPatternSyn name dataNm ty_args dataCons @@ -1088,13 +744,16 @@ extractDecl declMap name decl pure (SigD noExtField <$> lsig) TyClD _ FamDecl {} - | isValName name - , Just (famInst:_) <- M.lookup name declMap - -> extractDecl declMap name famInst + | isValName name -> do + famInstOpt <- hiDecl dflags prr name + case famInstOpt of + Just famInst -> extractDecl prr dflags name famInst + Nothing -> pure $ Left ("extractDecl: Unhandled decl for " ++ getOccString name) + InstD _ (DataFamInstD _ (DataFamInstDecl (FamEqn { feqn_tycon = L _ n , feqn_pats = tys - , feqn_rhs = defn }))) -> + , feqn_rhs = defn }))) -> pure $ if isDataConName name then fmap (SigD noExtField) <$> extractPatternSyn name n tys (dd_cons defn) else fmap (SigD noExtField) <$> extractRecSel name n tys (dd_cons defn) @@ -1104,8 +763,8 @@ extractDecl declMap name decl , name `elem` map unLoc (concatMap (getConNames . unLoc) (dd_cons dd)) ] in case matches of - [d0] -> extractDecl declMap name (noLocA (InstD noExtField (DataFamInstD noExtField d0))) - _ -> Left "internal: extractDecl (ClsInstD)" + [d0] -> extractDecl prr dflags name (noLocA (InstD noExtField (DataFamInstD noExtField d0))) + _ -> pure $ Left "internal: extractDecl (ClsInstD)" | otherwise -> let matches = [ d' | L _ d'@(DataFamInstDecl d ) <- insts @@ -1116,9 +775,9 @@ extractDecl declMap name decl , foExt n == name ] in case matches of - [d0] -> extractDecl declMap name (noLocA . InstD noExtField $ DataFamInstD noExtField d0) - _ -> Left "internal: extractDecl (ClsInstD)" - _ -> Left ("extractDecl: Unhandled decl for " ++ getOccString name) + [d0] -> extractDecl prr dflags name (noLocA . InstD noExtField $ DataFamInstD noExtField d0) + _ -> pure $ Left "internal: extractDecl (ClsInstD)" + _ -> pure $ Left ("extractDecl: Unhandled decl for " ++ getOccString name) extractPatternSyn :: HasCallStack => Name -> Name @@ -1192,18 +851,18 @@ pruneExportItems = filter hasDoc hasDoc _ = True -mkVisibleNames :: Maps -> [ExportItem GhcRn] -> [DocOption] -> [Name] -mkVisibleNames (_, _, _, instMap) exports opts +mkVisibleNames :: InstMap -> [ExportItem GhcRn] -> [DocOption] -> [Name] +mkVisibleNames instMap exports opts | OptHide `elem` opts = [] | otherwise = let ns = concatMap exportName exports in seqList ns `seq` ns where exportName e@ExportDecl {} = name ++ subs ++ patsyns where subs = map fst (expItemSubDocs e) - patsyns = concatMap (getMainDeclBinder . fst) (expItemPats e) + patsyns = concatMap (getMainDeclBinder emptyOccEnv . fst) (expItemPats e) name = case unLoc $ expItemDecl e of InstD _ d -> maybeToList $ SrcLoc.lookupSrcSpan (getInstLoc d) instMap - decl -> getMainDeclBinder decl + decl -> getMainDeclBinder emptyOccEnv decl exportName ExportNoDecl {} = [] -- we don't count these as visible, since -- we don't want links to go to them. exportName _ = [] @@ -1211,15 +870,3 @@ mkVisibleNames (_, _, _, instMap) exports opts seqList :: [a] -> () seqList [] = () seqList (x : xs) = x `seq` seqList xs - --- | Find a stand-alone documentation comment by its name. -findNamedDoc :: String -> [HsDecl GhcRn] -> ErrMsgM (Maybe HsDocString) -findNamedDoc name = search - where - search [] = do - tell ["Cannot find documentation for: $" ++ name] - return Nothing - search (DocD _ (DocCommentNamed name' doc) : rest) - | name == name' = return (Just doc) - | otherwise = search rest - search (_other_decl : rest) = search rest diff --git a/haddock-api/src/Haddock/Interface/Json.hs b/haddock-api/src/Haddock/Interface/Json.hs index 92fb2e754f499e1d227c0cce3033d1ab045422d5..c9f1b5241c3dcbc130381da923dbf5403df147a2 100644 --- a/haddock-api/src/Haddock/Interface/Json.hs +++ b/haddock-api/src/Haddock/Interface/Json.hs @@ -13,7 +13,9 @@ import GHC.Utils.Outputable import Control.Arrow import Data.Map (Map) +import Data.IntMap (IntMap) import qualified Data.Map as Map +import qualified Data.IntMap as IntMap import Haddock.Types import Haddock.InterfaceFile @@ -32,7 +34,7 @@ jsonInstalledInterface InstalledInterface{..} = jsonObject properties , ("is_sig" , jsonBool instIsSig) , ("info" , jsonHaddockModInfo instInfo) , ("doc_map" , jsonMap nameStableString jsonMDoc instDocMap) - , ("arg_map" , jsonMap nameStableString (jsonMap show jsonMDoc) instArgMap) + , ("arg_map" , jsonMap nameStableString (jsonIntMap jsonMDoc) instArgMap) , ("exports" , jsonArray (map jsonName instExports)) , ("visible_exports" , jsonArray (map jsonName instVisibleExports)) , ("options" , jsonArray (map (jsonString . show) instOptions)) @@ -54,6 +56,9 @@ jsonHaddockModInfo HaddockModInfo{..} = jsonMap :: (a -> String) -> (b -> JsonDoc) -> Map a b -> JsonDoc jsonMap f g = jsonObject . map (f *** g) . Map.toList +jsonIntMap :: (b -> JsonDoc) -> IntMap b -> JsonDoc +jsonIntMap g = jsonObject . map (show *** g) . IntMap.toList + jsonMDoc :: MDoc Name -> JsonDoc jsonMDoc MetaDoc{..} = jsonObject [ ("meta", jsonObject [("version", jsonMaybe (jsonString . show) (_version _meta))]) diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index a827cf662eb54272cdfb71ceafae7d2b83447d52..4c1de89aac9d205adaf36885b3e52a16113bb9aa 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -16,7 +16,6 @@ module Haddock.Interface.LexParseRn ( processDocString , processDocStringParas - , processDocStrings , processModuleHeader ) where @@ -25,60 +24,50 @@ import Control.Monad import Data.Functor import Data.List ((\\), maximumBy) import Data.Ord -import Documentation.Haddock.Doc (metaDocConcat) -import GHC.Driver.Session (languageExtensions) +import GHC.Driver.Session import qualified GHC.LanguageExtensions as LangExt import GHC import Haddock.Interface.ParseModuleHeader import Haddock.Parser import Haddock.Types import GHC.Types.Name -import GHC.Types.Avail ( availName ) +import GHC.Types.Name.Set +import GHC.Types.Avail import GHC.Parser.PostProcess import GHC.Driver.Ppr ( showPpr, showSDoc ) import GHC.Types.Name.Reader import GHC.Data.EnumSet as EnumSet -processDocStrings :: DynFlags -> Maybe Package -> GlobalRdrEnv -> [HsDocString] - -> ErrMsgM (Maybe (MDoc Name)) -processDocStrings dflags pkg gre strs = do - mdoc <- metaDocConcat <$> traverse (processDocStringParas dflags pkg gre) strs - case mdoc of - -- We check that we don't have any version info to render instead - -- of just checking if there is no comment: there may not be a - -- comment but we still want to pass through any meta data. - MetaDoc { _meta = Meta Nothing Nothing, _doc = DocEmpty } -> pure Nothing - x -> pure (Just x) +processDocStringParas :: DynFlags -> Maybe Package -> (HsDoc Name) -> ErrMsgM (MDoc Name) +processDocStringParas dflags pkg hds = + overDocF (rename dflags $ hsDocRenamer hds) $ parseParas dflags pkg (unpackHDS $ hsDocString hds) -processDocStringParas :: DynFlags -> Maybe Package -> GlobalRdrEnv -> HsDocString -> ErrMsgM (MDoc Name) -processDocStringParas dflags pkg gre hds = - overDocF (rename dflags gre) $ parseParas dflags pkg (unpackHDS hds) +processDocString :: DynFlags -> (HsDoc Name) -> ErrMsgM (Doc Name) +processDocString dflags hds = + rename dflags (hsDocRenamer hds) $ parseString dflags (unpackHDS $ hsDocString hds) -processDocString :: DynFlags -> GlobalRdrEnv -> HsDocString -> ErrMsgM (Doc Name) -processDocString dflags gre hds = - rename dflags gre $ parseString dflags (unpackHDS hds) - -processModuleHeader :: DynFlags -> Maybe Package -> GlobalRdrEnv -> SafeHaskellMode -> Maybe HsDocString +processModuleHeader :: DynFlags -> Maybe Package -> SafeHaskellMode -> Maybe Language -> EnumSet LangExt.Extension -> Maybe (HsDoc Name) -> ErrMsgM (HaddockModInfo Name, Maybe (MDoc Name)) -processModuleHeader dflags pkgName gre safety mayStr = do +processModuleHeader dflags pkgName safety mayLang extSet mayStr = do (hmi, doc) <- case mayStr of Nothing -> return failure - Just hds -> do - let str = unpackHDS hds + Just hsDoc -> do + let str = unpackHDS (hsDocString hsDoc) (hmi, doc) = parseModuleHeader dflags pkgName str + renamer = hsDocRenamer hsDoc !descr <- case hmi_description hmi of - Just hmi_descr -> Just <$> rename dflags gre hmi_descr + Just hmi_descr -> Just <$> rename dflags renamer hmi_descr Nothing -> pure Nothing let hmi' = hmi { hmi_description = descr } - doc' <- overDocF (rename dflags gre) doc + doc' <- overDocF (rename dflags renamer) doc return (hmi', Just doc') let flags :: [LangExt.Extension] -- We remove the flags implied by the language setting and we display the language instead - flags = EnumSet.toList (extensionFlags dflags) \\ languageExtensions (language dflags) + flags = EnumSet.toList extSet \\ languageExtensions mayLang return (hmi { hmi_safety = Just $ showPpr dflags safety - , hmi_language = language dflags + , hmi_language = mayLang , hmi_extensions = flags } , doc) where @@ -91,8 +80,8 @@ processModuleHeader dflags pkgName gre safety mayStr = do -- fallbacks in case we can't locate the identifiers. -- -- See the comments in the source for implementation commentary. -rename :: DynFlags -> GlobalRdrEnv -> Doc NsRdrName -> ErrMsgM (Doc Name) -rename dflags gre = rn +rename :: DynFlags -> Renamer -> Doc NsRdrName -> ErrMsgM (Doc Name) +rename dflags renamer = rn where rn d = case d of DocAppend a b -> DocAppend <$> rn a <*> rn b @@ -100,13 +89,10 @@ rename dflags gre = rn DocIdentifier i -> do let NsRdrName ns x = unwrap i occ = rdrNameOcc x - isValueName = isDataOcc occ || isVarOcc occ - - let valueNsChoices | isValueName = [x] - | otherwise = [] -- is this ever possible? - typeNsChoices | isValueName = [setRdrNameSpace x tcName] - | otherwise = [x] - + let valueNsChoices | isDataOcc occ = [dataName] + | otherwise = [varName] + typeNsChoices | isDataOcc occ = [tcName] + | otherwise = [tvName] -- Generate the choices for the possible kind of thing this -- is. We narrow down the possibilities with the namespace (if -- there is one). @@ -114,32 +100,13 @@ rename dflags gre = rn Value -> valueNsChoices Type -> typeNsChoices None -> valueNsChoices ++ typeNsChoices - - -- Lookup any GlobalRdrElts that match the choices. - case concatMap (\c -> lookupGRE_RdrName c gre) choices of - -- We found no names in the env so we start guessing. - [] -> - case choices of - -- The only way this can happen is if a value namespace was - -- specified on something that cannot be a value. - [] -> invalidValue dflags i - - -- There was nothing in the environment so we need to - -- pick some default from what's available to us. We - -- diverge here from the old way where we would default - -- to type constructors as we're much more likely to - -- actually want anchors to regular definitions than - -- type constructor names (such as in #253). So now we - -- only get type constructor links if they are actually - -- in scope. - a:_ -> outOfScope dflags ns (i $> a) - - -- There is only one name in the environment that matches so - -- use it. - [a] -> pure $ DocIdentifier (i $> greMangledName a) - + case renamer (showPpr dflags x) choices of + [] -> case ns of + Type -> outOfScope dflags ns (i $> setRdrNameSpace x tcName) + _ -> outOfScope dflags ns (i $> x) + [a] -> pure (DocIdentifier $ i $> a) -- There are multiple names available. - gres -> ambiguous dflags i gres + names -> ambiguous dflags i names DocWarning doc -> DocWarning <$> rn doc DocEmphasis doc -> DocEmphasis <$> rn doc @@ -172,7 +139,7 @@ rename dflags gre = rn -- #253 and #375 on the confusion this causes depending on which -- default we pick in 'rename'. outOfScope :: DynFlags -> Namespace -> Wrap RdrName -> ErrMsgM (Doc a) -outOfScope dflags ns x = +outOfScope dflags ns x = do case unwrap x of Unqual occ -> warnAndMonospace (x $> occ) Qual mdl occ -> pure (DocIdentifierUnchecked (x $> (mdl, occ))) @@ -190,45 +157,32 @@ outOfScope dflags ns x = " If you qualify the identifier, haddock can try to link it anyway."] pure (monospaced a') monospaced = DocMonospaced . DocString - -- | Handle ambiguous identifiers. -- -- Prefers local names primarily and type constructors or class names secondarily. -- -- Emits a warning if the 'GlobalRdrElts's don't belong to the same type or class. -ambiguous :: DynFlags - -> Wrap NsRdrName - -> [GlobalRdrElt] -- ^ More than one @gre@s sharing the same `RdrName` above. +ambiguous :: DynFlags -> Wrap NsRdrName + -> [Name] -- ^ More than one 'Name's that the 'Identifier' may be intended + -- to reference. -> ErrMsgM (Doc Name) -ambiguous dflags x gres = do - let noChildren = map availName (gresToAvailInfo gres) +ambiguous dflags i names = do + let noChildren = map availName (nubAvails (map avail names)) dflt = maximumBy (comparing (isLocalName &&& isTyConName)) noChildren - msg = "Warning: " ++ showNsRdrName dflags x ++ " is ambiguous. It is defined\n" ++ - concatMap (\n -> " * " ++ defnLoc n ++ "\n") (map greMangledName gres) ++ - " You may be able to disambiguate the identifier by qualifying it or\n" ++ - " by specifying the type/value namespace explicitly.\n" ++ - " Defaulting to the one defined " ++ defnLoc dflt - -- TODO: Once we have a syntax for namespace qualification (#667) we may also - -- want to emit a warning when an identifier is a data constructor for a type - -- of the same name, but not the only constructor. - -- For example, for @data D = C | D@, someone may want to reference the @D@ - -- constructor. + dflt_str = '\'' : showPpr dflags dflt ++ "'" + id_str = showNsRdrName dflags i + defnLoc = showSDoc dflags . pprNameDefnLoc + msg = "Warning: " ++ id_str ++ " is ambiguous. It is defined\n" ++ + concatMap (\n -> " * " ++ defnLoc n ++ "\n") names ++ + " You may be able to disambiguate the identifier by qualifying it, specifying its namespace or\n" ++ + " by hiding some imports.\n" ++ + " Defaulting to " ++ showPpr dflags (pprNameSpace $ nameNameSpace dflt) ++ " " + ++ dflt_str ++ " defined " ++ defnLoc dflt when (length noChildren > 1) $ tell [msg] - pure (DocIdentifier (x $> dflt)) + pure (DocIdentifier (i $> dflt)) where isLocalName (nameSrcLoc -> RealSrcLoc {}) = True isLocalName _ = False - defnLoc = showSDoc dflags . pprNameDefnLoc - --- | Handle value-namespaced names that cannot be for values. --- --- Emits a warning that the value-namespace is invalid on a non-value identifier. -invalidValue :: DynFlags -> Wrap NsRdrName -> ErrMsgM (Doc a) -invalidValue dflags x = do - tell ["Warning: " ++ showNsRdrName dflags x ++ " cannot be value, yet it is\n" ++ - " namespaced as such. Did you mean to specify a type namespace\n" ++ - " instead?"] - pure (DocMonospaced (DocString (showNsRdrName dflags x))) -- | Printable representation of a wrapped and namespaced name showNsRdrName :: DynFlags -> Wrap NsRdrName -> String @@ -236,3 +190,9 @@ showNsRdrName dflags = (\p i -> p ++ "'" ++ i ++ "'") <$> prefix <*> ident where ident = showWrapped (showPpr dflags . rdrName) prefix = renderNs . namespace . unwrap + +hsDocRenamer :: HsDoc Name -> Renamer +hsDocRenamer hsDoc = \s cands -> nameSetElemsStable $ filterNameSet (nameMatches s cands) env + where + !env = hsDocIds hsDoc + nameMatches s nss n = nameOccName n `elem` [mkOccName ns s | ns <- nss] diff --git a/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs b/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs index 3e464fbc18e08209cd135dca3a8686bc8ccf9618..e2aa7a7da0e6734dede1a1421752230e09cdb046 100644 --- a/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs +++ b/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs @@ -17,8 +17,8 @@ import Control.Applicative (Alternative (..)) import Control.Monad (ap) import Data.Char import GHC.Driver.Session -import Haddock.Parser import Haddock.Types +import Haddock.Parser -- ----------------------------------------------------------------------------- -- Parsing module headers @@ -27,7 +27,7 @@ import Haddock.Types -- Copyright, License, Maintainer, Stability, Portability, except that -- any or all may be omitted. parseModuleHeader :: DynFlags -> Maybe Package -> String -> (HaddockModInfo NsRdrName, MDoc NsRdrName) -parseModuleHeader dflags pkgName str0 = +parseModuleHeader df pkgName str0 = let kvs :: [(String, String)] str1 :: String @@ -51,7 +51,7 @@ parseModuleHeader dflags pkgName str0 = portabilityOpt = getKey "Portability" in (HaddockModInfo { - hmi_description = parseString dflags <$> descriptionOpt, + hmi_description = parseString df <$> descriptionOpt, hmi_copyright = copyrightOpt, hmi_license = spdxLicenceOpt <|> licenseOpt <|> licenceOpt, hmi_maintainer = maintainerOpt, @@ -60,7 +60,7 @@ parseModuleHeader dflags pkgName str0 = hmi_safety = Nothing, hmi_language = Nothing, -- set in LexParseRn hmi_extensions = [] -- also set in LexParseRn - }, parseParas dflags pkgName str1) + }, parseParas df pkgName str1) ------------------------------------------------------------------------------- -- Small parser to parse module header. diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 98b3a6e67548c957b1080c750fe7b01f4ad8bc2e..472c2346af1feb32284cc6305377c01e4ef8e3e5 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -14,8 +14,7 @@ ----------------------------------------------------------------------------- module Haddock.Interface.Rename (renameInterface) where - -import Data.Traversable (mapM) +import Control.Monad import Haddock.GhcUtils import Haddock.Types @@ -25,10 +24,10 @@ import GHC hiding (NoLink) import GHC.Types.Name import GHC.Types.Name.Reader (RdrName(Exact)) import GHC.Builtin.Types (eqTyCon_RDR) +import GHC.Builtin.Types.Prim import Control.Applicative import Control.Arrow ( first ) -import Control.Monad hiding (mapM) import Data.List (intercalate) import qualified Data.Map as Map hiding ( Map ) import qualified Data.Set as Set @@ -91,7 +90,8 @@ renameInterface _dflags ignoredSymbols renamingEnv warnings iface = , not (qualifiedName n `Set.member` ignoreSet) , not (isSystemName n) , not (isBuiltInSyntax n) - , Exact n /= eqTyCon_RDR + , Exact n /= eqTyCon_RDR -- (~) + , n /= getName eqPrimTyCon -- (~#) ] in do @@ -190,10 +190,8 @@ renameDocumentation :: Documentation Name -> RnM (Documentation DocName) renameDocumentation (Documentation mDoc mWarning) = Documentation <$> mapM renameDoc mDoc <*> mapM renameDoc mWarning - -renameLDocHsSyn :: LHsDocString -> RnM LHsDocString -renameLDocHsSyn = return - +renameLDocHsSyn :: LHsDoc Name -> RnM (LHsDoc DocName) +renameLDocHsSyn = traverse (traverse rename) renameDoc :: Traversable t => t (Wrap Name) -> RnM (t (Wrap DocName)) renameDoc = traverse (traverse rename) diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index 9c4308a61b91fe9fc49491b08822c2c4187db0a2..0e7100b5429483e1574414b47014e59438afba6a 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -24,8 +24,6 @@ module Haddock.InterfaceFile ( import Haddock.Types import Data.IORef -import qualified Data.Map as Map -import Data.Map (Map) import Data.Word import GHC.Iface.Binary (getWithUserData, putSymbolTable) @@ -235,12 +233,6 @@ data BinDictionary = BinDictionary { -- * GhcBinary instances ------------------------------------------------------------------------------- - -instance (Ord k, Binary k, Binary v) => Binary (Map k v) where - put_ bh m = put_ bh (Map.toList m) - get bh = fmap (Map.fromList) (get bh) - - instance Binary InterfaceFile where put_ bh (InterfaceFile env ifaces) = do put_ bh env @@ -253,12 +245,13 @@ instance Binary InterfaceFile where instance Binary InstalledInterface where - put_ bh (InstalledInterface modu is_sig info docMap argMap + put_ bh (InstalledInterface modu is_sig info docMap argMap defMeths exps visExps opts fixMap) = do put_ bh modu put_ bh is_sig put_ bh info lazyPut bh (docMap, argMap) + put_ bh defMeths put_ bh exps put_ bh visExps put_ bh opts @@ -269,12 +262,13 @@ instance Binary InstalledInterface where is_sig <- get bh info <- get bh ~(docMap, argMap) <- lazyGet bh + defMeths <- get bh exps <- get bh visExps <- get bh opts <- get bh fixMap <- get bh - return (InstalledInterface modu is_sig info docMap argMap - exps visExps opts fixMap) + return (InstalledInterface modu is_sig info + docMap argMap defMeths exps visExps opts fixMap) instance Binary DocOption where @@ -282,11 +276,11 @@ instance Binary DocOption where putByte bh 0 put_ bh OptPrune = do putByte bh 1 - put_ bh OptIgnoreExports = do - putByte bh 2 put_ bh OptNotHome = do - putByte bh 3 + putByte bh 2 put_ bh OptShowExtensions = do + putByte bh 3 + put_ bh OptPrintRuntimeRep = do putByte bh 4 get bh = do h <- getByte bh @@ -296,11 +290,11 @@ instance Binary DocOption where 1 -> do return OptPrune 2 -> do - return OptIgnoreExports - 3 -> do return OptNotHome - 4 -> do + 3 -> do return OptShowExtensions + 4 -> do + return OptPrintRuntimeRep _ -> fail "invalid binary data found" diff --git a/haddock-api/src/Haddock/Options.hs b/haddock-api/src/Haddock/Options.hs index 4d22505fe5d0701ead4c62d93ead6a531aec9158..bb805fe6982d7ec872fcc4c0d811f22b1362b6cb 100644 --- a/haddock-api/src/Haddock/Options.hs +++ b/haddock-api/src/Haddock/Options.hs @@ -90,7 +90,6 @@ data Flag | Flag_GenContents | Flag_UseIndex String | Flag_GenIndex - | Flag_IgnoreAllExports | Flag_HideModule String | Flag_ShowModule String | Flag_ShowAllModules @@ -150,9 +149,9 @@ options backwardsCompat = "URL for a source code link on the contents\nand index pages", Option ['s'] (if backwardsCompat then ["source", "source-module"] else ["source-module"]) (ReqArg Flag_SourceModuleURL "URL") - "URL for a source code link for each module\n(using the %{FILE} or %{MODULE} vars)", + "URL for a source code link for each module\n(using the %{MODULE} var)", Option [] ["source-entity"] (ReqArg Flag_SourceEntityURL "URL") - "URL for a source code link for each entity\n(using the %{FILE}, %{MODULE}, %{NAME},\n%{KIND} or %{LINE} vars)", + "URL for a source code link for each entity\n(using the %{MODULE}, %{NAME},\n%{KIND} or %{LINE} vars)", Option [] ["source-entity-line"] (ReqArg Flag_SourceLEntityURL "URL") "URL for a source code link for each entity.\nUsed if name links are unavailable, eg. for TH splices.", Option [] ["comments-base"] (ReqArg Flag_WikiBaseURL "URL") @@ -160,7 +159,7 @@ options backwardsCompat = Option [] ["comments-module"] (ReqArg Flag_WikiModuleURL "URL") "URL for a comments link for each module\n(using the %{MODULE} var)", Option [] ["comments-entity"] (ReqArg Flag_WikiEntityURL "URL") - "URL for a comments link for each entity\n(using the %{FILE}, %{MODULE}, %{NAME},\n%{KIND} or %{LINE} vars)", + "URL for a comments link for each entity\n(using the %{MODULE}, %{NAME},\n%{KIND} or %{LINE} vars)", Option ['c'] ["css", "theme"] (ReqArg Flag_CSS "PATH") "the CSS file or theme directory to use for HTML output", Option [] ["built-in-themes"] (NoArg Flag_BuiltInThemes) @@ -170,7 +169,7 @@ options backwardsCompat = Option ['t'] ["title"] (ReqArg Flag_Heading "TITLE") "page heading", Option ['q'] ["qual"] (ReqArg Flag_Qualification "QUAL") - "qualification of names, one of \n'none' (default), 'full', 'local'\n'relative' or 'aliased'", + "qualification of names, one of \n'none' (default), 'full', 'local'\nor 'relative'", Option ['?'] ["help"] (NoArg Flag_Help) "display this help and exit", Option ['V'] ["version"] (NoArg Flag_Version) @@ -191,8 +190,6 @@ options backwardsCompat = "use a separately-generated HTML index", Option [] ["gen-index"] (NoArg Flag_GenIndex) "generate an HTML index from specified\ninterfaces", - Option [] ["ignore-all-exports"] (NoArg Flag_IgnoreAllExports) - "behave as if all modules have the\nignore-exports attribute", Option [] ["hide"] (ReqArg Flag_HideModule "MODULE") "behave as if MODULE has the hide attribute", Option [] ["show"] (ReqArg Flag_ShowModule "MODULE") @@ -324,7 +321,6 @@ qualification flags = ["full"] -> Right OptFullQual ["local"] -> Right OptLocalQual ["relative"] -> Right OptRelativeQual - ["aliased"] -> Right OptAliasedQual [arg] -> Left $ "unknown qualification type " ++ show arg _:_ -> Left "qualification option given multiple times" diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 7c4aeb80d3e405a55419ed751b7ce1fe99b1c92c..cf0a8861b1a460aca65c96c7a400bee75e406a00 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -24,12 +24,11 @@ -- Types that are commonly used through-out Haddock. Some of the most -- important types are defined here, like 'Interface' and 'DocName'. ----------------------------------------------------------------------------- -module Haddock.Types ( - module Haddock.Types +module Haddock.Types + ( module Haddock.Types , HsDocString, LHsDocString , Fixity(..) , module Documentation.Haddock.Types - -- $ Reexports , runWriter , tell @@ -42,6 +41,7 @@ import Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.Writer.Strict (Writer, WriterT, MonadWriter(..), lift, runWriter, runWriterT) import Data.Typeable (Typeable) import Data.Map (Map) +import Data.IntMap (IntMap) import Data.Data (Data) import Data.Void (Void) import Documentation.Haddock.Types @@ -63,7 +63,7 @@ import GHC.Utils.Outputable type IfaceMap = Map Module Interface type InstIfaceMap = Map Module InstalledInterface -- TODO: rename type DocMap a = Map Name (MDoc a) -type ArgMap a = Map Name (Map Int (MDoc a)) +type ArgMap a = Map Name (IntMap (MDoc a)) type SubMap = Map Name [Name] type DeclMap = Map Name [LHsDecl GhcRn] type InstMap = Map RealSrcSpan Name @@ -89,9 +89,6 @@ data Interface = Interface -- | Is this a signature? , ifaceIsSig :: !Bool - -- | Original file name of the module. - , ifaceOrigFilename :: !FilePath - -- | Textual information about the module. , ifaceInfo :: !(HaddockModInfo Name) @@ -101,19 +98,17 @@ data Interface = Interface -- | Documentation header with cross-reference information. , ifaceRnDoc :: !(Documentation DocName) - -- | Haddock options for this module (prune, ignore-exports, etc). + -- | Haddock options for this module (prune, not-home, etc). , ifaceOptions :: ![DocOption] - -- | Declarations originating from the module. Excludes declarations without - -- names (instances and stand-alone documentation comments). Includes - -- names of subordinate declarations mapped to their parent declarations. - , ifaceDeclMap :: !(Map Name [LHsDecl GhcRn]) - -- | Documentation of declarations originating from the module (including -- subordinates). , ifaceDocMap :: !(DocMap Name) , ifaceArgMap :: !(ArgMap Name) + -- | The names of all the default methods for classes defined in this module + , ifaceDefMeths :: !([(OccName, Name)]) + -- | Documentation of declarations originating from the module (including -- subordinates). , ifaceRnDocMap :: !(DocMap DocName) @@ -130,11 +125,10 @@ data Interface = Interface -- | All \"visible\" names exported by the module. -- A visible name is a name that will show up in the documentation of the -- module. + -- + -- Names from modules that are entirely re-exported don't count as visible. , ifaceVisibleExports :: ![Name] - -- | Aliases of module imports as in @import A.B.C as C@. - , ifaceModuleAliases :: !AliasMap - -- | Instances exported by the module. , ifaceInstances :: ![ClsInst] , ifaceFamInstances :: ![FamInst] @@ -152,7 +146,7 @@ data Interface = Interface -- | Tokenized source code of module (avaliable if Haddock is invoked with -- source generation flag). - , ifaceHieFile :: !(Maybe FilePath) + , ifaceHieFile :: !FilePath , ifaceDynFlags :: !DynFlags } @@ -178,6 +172,9 @@ data InstalledInterface = InstalledInterface , instArgMap :: ArgMap Name + -- | The names of all the default methods for classes defined in this module + , instDefMeths :: [(OccName,Name)] + -- | All names exported by this module. , instExports :: [Name] @@ -186,7 +183,7 @@ data InstalledInterface = InstalledInterface -- module. , instVisibleExports :: [Name] - -- | Haddock options for this module (prune, ignore-exports, etc). + -- | Haddock options for this module (prune, not-home, etc). , instOptions :: [DocOption] , instFixMap :: Map Name Fixity @@ -205,6 +202,7 @@ toInstalledIface interface = InstalledInterface , instVisibleExports = ifaceVisibleExports interface , instOptions = ifaceOptions interface , instFixMap = ifaceFixMap interface + , instDefMeths = ifaceDefMeths interface } @@ -279,7 +277,7 @@ data Documentation name = Documentation -- | Arguments and result are indexed by Int, zero-based from the left, -- because that's the easiest to use when recursing over types. -type FnArgsDoc name = Map Int (MDoc name) +type FnArgsDoc name = IntMap (MDoc name) type DocForDecl name = (Documentation name, FnArgsDoc name) @@ -570,10 +568,11 @@ emptyHaddockModInfo = HaddockModInfo data DocOption = OptHide -- ^ This module should not appear in the docs. | OptPrune - | OptIgnoreExports -- ^ Pretend everything is exported. | OptNotHome -- ^ Not the best place to get docs for things -- exported by this module. | OptShowExtensions -- ^ Render enabled extensions for this module. + | OptPrintRuntimeRep -- ^ Render runtime reps for this module (see + -- the GHC @-fprint-explicit-runtime-reps@ flag) deriving (Eq, Show) @@ -584,23 +583,12 @@ data QualOption | OptLocalQual -- ^ Qualify all imported names fully. | OptRelativeQual -- ^ Like local, but strip module prefix -- from modules in the same hierarchy. - | OptAliasedQual -- ^ Uses aliases of module names - -- as suggested by module import renamings. - -- However, we are unfortunately not able - -- to maintain the original qualifications. - -- Image a re-export of a whole module, - -- how could the re-exported identifiers be qualified? - -type AliasMap = Map Module ModuleName data Qualification = NoQual | FullQual | LocalQual Module | RelativeQual Module - | AliasedQual AliasMap Module - -- ^ @Module@ contains the current module. - -- This way we can distinguish imported and local identifiers. makeContentsQual :: QualOption -> Qualification makeContentsQual qual = @@ -608,12 +596,11 @@ makeContentsQual qual = OptNoQual -> NoQual _ -> FullQual -makeModuleQual :: QualOption -> AliasMap -> Module -> Qualification -makeModuleQual qual aliases mdl = +makeModuleQual :: QualOption -> Module -> Qualification +makeModuleQual qual mdl = case qual of OptLocalQual -> LocalQual mdl OptRelativeQual -> RelativeQual mdl - OptAliasedQual -> AliasedQual aliases mdl OptFullQual -> FullQual OptNoQual -> NoQual @@ -630,6 +617,15 @@ data SinceQual | External -- ^ only qualify when the thing being annotated is from -- an external package +----------------------------------------------------------------------------- +-- * Renaming +----------------------------------------------------------------------------- + +-- | Renames an identifier. +-- The first input is the identifier as it occurred in the comment +-- The second input is the possible namespaces of the identifier +type Renamer = String -> [NameSpace] -> [Name] + ----------------------------------------------------------------------------- -- * Error handling ----------------------------------------------------------------------------- diff --git a/haddock-api/src/Haddock/Utils.hs b/haddock-api/src/Haddock/Utils.hs index 314b8db9e656253c774cffba5b9845f8ad35c24b..ea28967a671bf10e224ee263a454cb0d5a74468e 100644 --- a/haddock-api/src/Haddock/Utils.hs +++ b/haddock-api/src/Haddock/Utils.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE GADTs #-} +{-# LANGUAGE ViewPatterns #-} {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} ----------------------------------------------------------------------------- @@ -120,7 +121,6 @@ out progVerbosity msgVerbosity msg mkMeta :: Doc a -> MDoc a mkMeta x = emptyMetaDoc { _doc = x } - -------------------------------------------------------------------------------- -- * Filename mangling functions stolen from s main/DriverUtil.lhs. -------------------------------------------------------------------------------- diff --git a/hoogle-test/ref/Bug722/test.txt b/hoogle-test/ref/Bug722/test.txt index 2f44ed8fb78cfbefb9b194fc9b7f5b72a7e5da4a..f8a921e7e8f42b893424ce6d607aadb749cbc147 100644 --- a/hoogle-test/ref/Bug722/test.txt +++ b/hoogle-test/ref/Bug722/test.txt @@ -5,12 +5,12 @@ @version 0.0.0 module Bug722 -class Foo a +class () => Foo a (!@#) :: Foo a => a -> a -> a infixl 4 !@# -type family (&*) :: * -> * -> * +type family (&*) :: Type -> Type -> Type infixr 3 &* -data a :-& b +data () => a :-& b (:^&) :: a -> b -> (:-&) a b infixl 6 :-& infixl 6 :^& diff --git a/hoogle-test/ref/Bug806/test.txt b/hoogle-test/ref/Bug806/test.txt index 8abdffaef2b4db1f944b5228b4d6b8acd5747538..aaf73a71a3c7c44db27e66765ecef4be090ae82d 100644 --- a/hoogle-test/ref/Bug806/test.txt +++ b/hoogle-test/ref/Bug806/test.txt @@ -7,19 +7,19 @@ module Bug806 -- | <a>F1</a> docs -type family F1 a b :: * -> * +type family F1 a b :: Type -> Type -- | <a>F2</a> docs -type family F2 a b :: * -> * +type family F2 a b :: Type -> Type -- | <a>D</a> docs -data family D a :: * -> * +data family D a :: Type -> Type v :: Int -- | <a>C</a> docs -class C a where { +class () => C a where { -- | <a>AT</a> docs - type AT a; - type AT a = Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy (Proxy))))))))); + type family AT a; + type AT a = Proxy Proxy Proxy Proxy Proxy Proxy Proxy Proxy Proxy Proxy :: Type -> Type; } diff --git a/hoogle-test/ref/Bug825/test.txt b/hoogle-test/ref/Bug825/test.txt index a88202dcf33546dfd365be33063336c49ff4c641..b30197806b6e1d3ac7b46ebdb3ac367f043eff91 100644 --- a/hoogle-test/ref/Bug825/test.txt +++ b/hoogle-test/ref/Bug825/test.txt @@ -5,5 +5,5 @@ @version 0.0.0 module Bug825 -data a :~: b -data (:~~:) a b +data () => a :~: b +data () => a :~~: b diff --git a/hoogle-test/ref/Bug873/test.txt b/hoogle-test/ref/Bug873/test.txt index 5e1117a4b91d68e81b1e52a6d6b2919a82b41cc9..7c9568146613686b5ba194404ac87c62fb2900fa 100644 --- a/hoogle-test/ref/Bug873/test.txt +++ b/hoogle-test/ref/Bug873/test.txt @@ -21,7 +21,7 @@ module Bug873 -- Note that <tt>(<a>$</a>)</tt> is representation-polymorphic in its -- result type, so that <tt>foo <a>$</a> True</tt> where <tt>foo :: Bool -- -> Int#</tt> is well-typed. -($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b +($) :: (a -> b) -> a -> b infixr 0 $ ($$) :: (a -> b) -> a -> b infixr 0 $$ diff --git a/hoogle-test/ref/Bug946/test.txt b/hoogle-test/ref/Bug946/test.txt index ff63a7661400660ba344f7531c0fb2d90065b877..8b9478f3867c379a06f3ddc6563943454842a190 100644 --- a/hoogle-test/ref/Bug946/test.txt +++ b/hoogle-test/ref/Bug946/test.txt @@ -7,7 +7,7 @@ module Bug946 -- | A wrapper around <a>Int</a> -data AnInt +data () => AnInt -- | some <a>Int</a> AnInt :: Int -> AnInt diff --git a/hoogle-test/ref/Bug992/test.txt b/hoogle-test/ref/Bug992/test.txt index 8ae145c34f56dfae9a9208675f70b5085b030577..1f484d55cb9894a33c1657eb4fe7b6b34c46ac90 100644 --- a/hoogle-test/ref/Bug992/test.txt +++ b/hoogle-test/ref/Bug992/test.txt @@ -5,5 +5,5 @@ @version 0.0.0 module Bug992 -data K (m :: * -> *) -K :: K (m :: * -> *) +data () => K (m :: Type -> Type) +K :: K (m :: Type -> Type) diff --git a/hoogle-test/ref/assoc-types/test.txt b/hoogle-test/ref/assoc-types/test.txt index 0d2aa4a96377a19855fd26fda866ffb0267b0c7d..b465db5c297c431ad1a1495139063853e887f008 100644 --- a/hoogle-test/ref/assoc-types/test.txt +++ b/hoogle-test/ref/assoc-types/test.txt @@ -5,9 +5,9 @@ @version 0.0.0 module AssocTypes -class Foo a where { - type Bar a b; - type Baz a; +class () => Foo a where { + type family Bar a b; + type family Baz a; type Baz a = [(a, a)]; } bar :: Foo a => Bar a a diff --git a/hoogle-test/ref/classes/test.txt b/hoogle-test/ref/classes/test.txt index 69f224eb2c9c88bed6bca86bea4356daaff7a8e8..fef1a5a2b40dd6fefab80e3c2d944965f0096c6a 100644 --- a/hoogle-test/ref/classes/test.txt +++ b/hoogle-test/ref/classes/test.txt @@ -5,10 +5,10 @@ @version 0.0.0 module Classes -class Foo f +class () => Foo (f :: Type -> TYPE LiftedRep) bar :: Foo f => f a -> f b -> f (a, b) baz :: Foo f => f () -class Quux q +class () => Quux q (+++) :: Quux q => q -> q -> q (///) :: Quux q => q -> q -> q (***) :: Quux q => q -> q -> q diff --git a/hoogle-test/ref/type-sigs/test.txt b/hoogle-test/ref/type-sigs/test.txt index 1209279c59b720ad73a047ce96cd99865498297a..47878d830d438479ee1b856c35b991984c15fd01 100644 --- a/hoogle-test/ref/type-sigs/test.txt +++ b/hoogle-test/ref/type-sigs/test.txt @@ -5,12 +5,12 @@ @version 0.0.0 module ReaderT -newtype ReaderT r m a -ReaderT :: (r -> m a) -> ReaderT r m a -[runReaderT] :: ReaderT r m a -> r -> m a +newtype () => ReaderT r (m :: Type -> Type) a +ReaderT :: (r -> m a) -> ReaderT r (m :: Type -> Type) a +[runReaderT] :: ReaderT r (m :: Type -> Type) a -> r -> m a module ReaderTReexport -newtype ReaderT r m a -ReaderT :: (r -> m a) -> ReaderT r m a -[runReaderT] :: ReaderT r m a -> r -> m a +newtype () => ReaderT r (m :: Type -> Type) a +ReaderT :: (r -> m a) -> ReaderT r (m :: Type -> Type) a +[runReaderT] :: ReaderT r (m :: Type -> Type) a -> r -> m a runReaderT :: ReaderT r m a -> r -> m a diff --git a/html-test/ref/Bug1004.html b/html-test/ref/Bug1004.html index 3324fae155bd29012e130fb1d1cc23582228f671..409904ddfc054908edf5e6b3d43affd4f3de4f8b 100644 --- a/html-test/ref/Bug1004.html +++ b/html-test/ref/Bug1004.html @@ -782,7 +782,61 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Traversable:9" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Contravariant:9" + ></span + > (<a href="#" title="Data.Functor.Contravariant" + >Contravariant</a + > f, <a href="#" title="Data.Functor.Contravariant" + >Contravariant</a + > g) => <a href="#" title="Data.Functor.Contravariant" + >Contravariant</a + > (<a href="#" title="Bug1004" + >Product</a + > f g)</span + ></td + ><td class="doc empty" + > </td + ></tr + ><tr + ><td colspan="2" + ><details id="i:id:Product:Contravariant:9" + ><summary class="hide-when-js-enabled" + >Instance details</summary + ><p + >Defined in <a href="#" + >Data.Functor.Contravariant</a + ></p + > <div class="subs methods" + ><p class="caption" + >Methods</p + ><p class="src" + ><a href="#" + >contramap</a + > :: (a' -> a) -> <a href="#" title="Bug1004" + >Product</a + > f g a -> <a href="#" title="Bug1004" + >Product</a + > f g a' <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >(>$)</a + > :: b -> <a href="#" title="Bug1004" + >Product</a + > f g b -> <a href="#" title="Bug1004" + >Product</a + > f g a <a href="#" class="selflink" + >#</a + ></p + ></div + ></details + ></td + ></tr + ><tr + ><td class="src clearfix" + ><span class="inst-left" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Traversable:10" ></span > (<a href="#" title="Data.Traversable" >Traversable</a @@ -803,7 +857,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Traversable:9" + ><details id="i:id:Product:Traversable:10" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -868,7 +922,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Alternative:10" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Alternative:11" ></span > (<a href="#" title="Control.Applicative" >Alternative</a @@ -889,7 +943,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Alternative:10" + ><details id="i:id:Product:Alternative:11" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -946,7 +1000,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Applicative:11" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Applicative:12" ></span > (<a href="#" title="Control.Applicative" >Applicative</a @@ -967,7 +1021,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Applicative:11" + ><details id="i:id:Product:Applicative:12" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1040,7 +1094,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Functor:12" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Functor:13" ></span > (<a href="#" title="Data.Functor" >Functor</a @@ -1061,7 +1115,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Functor:12" + ><details id="i:id:Product:Functor:13" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1098,7 +1152,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monad:13" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monad:14" ></span > (<a href="#" title="Control.Monad" >Monad</a @@ -1119,7 +1173,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Monad:13" + ><details id="i:id:Product:Monad:14" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1168,7 +1222,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadPlus:14" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadPlus:15" ></span > (<a href="#" title="Control.Monad" >MonadPlus</a @@ -1189,7 +1243,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:MonadPlus:14" + ><details id="i:id:Product:MonadPlus:15" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1226,15 +1280,15 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Data:15" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Data:16" ></span - > (<a href="#" title="Data.Typeable" + > (<a href="#" title="Type.Reflection" >Typeable</a - > a, <a href="#" title="Data.Typeable" + > a, <a href="#" title="Type.Reflection" >Typeable</a - > f, <a href="#" title="Data.Typeable" + > f, <a href="#" title="Type.Reflection" >Typeable</a - > g, <a href="#" title="Data.Typeable" + > g, <a href="#" title="Type.Reflection" >Typeable</a > k, <a href="#" title="Data.Data" >Data</a @@ -1255,7 +1309,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Data:15" + ><details id="i:id:Product:Data:16" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1320,7 +1374,7 @@ ><p class="src" ><a href="#" >dataCast1</a - > :: <a href="#" title="Data.Typeable" + > :: <a href="#" title="Type.Reflection" >Typeable</a > t => (<span class="keyword" >forall</span @@ -1336,7 +1390,7 @@ ><p class="src" ><a href="#" >dataCast2</a - > :: <a href="#" title="Data.Typeable" + > :: <a href="#" title="Type.Reflection" >Typeable</a > t => (<span class="keyword" >forall</span @@ -1472,7 +1526,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monoid:16" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monoid:17" ></span > (<a href="#" title="Data.Monoid" >Monoid</a @@ -1493,7 +1547,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Monoid:16" + ><details id="i:id:Product:Monoid:17" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1540,7 +1594,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Semigroup:17" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Semigroup:18" ></span > (<a href="#" title="Prelude" >Semigroup</a @@ -1561,7 +1615,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Semigroup:17" + ><details id="i:id:Product:Semigroup:18" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1614,7 +1668,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Generic:18" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Generic:19" ></span > <a href="#" title="GHC.Generics" >Generic</a @@ -1627,7 +1681,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Generic:18" + ><details id="i:id:Product:Generic:19" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1686,7 +1740,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Read:19" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Read:20" ></span > (<a href="#" title="Data.Functor.Classes" >Read1</a @@ -1709,7 +1763,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Read:19" + ><details id="i:id:Product:Read:20" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1768,7 +1822,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Show:20" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Show:21" ></span > (<a href="#" title="Data.Functor.Classes" >Show1</a @@ -1791,7 +1845,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Show:20" + ><details id="i:id:Product:Show:21" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1840,7 +1894,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Eq:21" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Eq:22" ></span > (<a href="#" title="Data.Functor.Classes" >Eq1</a @@ -1863,7 +1917,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Eq:21" + ><details id="i:id:Product:Eq:22" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -1904,7 +1958,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Ord:22" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Ord:23" ></span > (<a href="#" title="Data.Functor.Classes" >Ord1</a @@ -1927,7 +1981,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Ord:22" + ><details id="i:id:Product:Ord:23" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -2028,7 +2082,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep1:23" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep1:24" ></span > <span class="keyword" >type</span @@ -2049,7 +2103,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Rep1:23" + ><details id="i:id:Product:Rep1:24" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -2124,7 +2178,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep:24" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep:25" ></span > <span class="keyword" >type</span @@ -2143,7 +2197,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:Product:Rep:24" + ><details id="i:id:Product:Rep:25" ><summary class="hide-when-js-enabled" >Instance details</summary ><p diff --git a/html-test/ref/Bug1035.html b/html-test/ref/Bug1035.html index 9df26a95879611ab2bd224d366f4b5f0fbec75e4..891e230d2cc683e668d0cee52daf17d5d1e7c528 100644 --- a/html-test/ref/Bug1035.html +++ b/html-test/ref/Bug1035.html @@ -138,7 +138,7 @@ ><p >A link to <code ><a href="#" title="Bug1035" - >Foo</a + >Bar</a ></code ></p ></div diff --git a/html-test/ref/Bug1050.html b/html-test/ref/Bug1050.html index 89fa19ce304c71ed515c58f6556dbb422bd3adde..71ec19191702ee053b19acfd644fe6db918a3d75 100644 --- a/html-test/ref/Bug1050.html +++ b/html-test/ref/Bug1050.html @@ -57,15 +57,11 @@ >newtype</span > <a id="t:T" class="def" >T</a - > :: (<span class="keyword" + > (a :: <span class="keyword" >forall</span > k. k -> <a href="#" title="Data.Kind" >Type</a - >) -> <span class="keyword" - >forall</span - > k. k -> <a href="#" title="Data.Kind" - >Type</a - > <span class="keyword" + >) (b :: k) <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -80,13 +76,13 @@ >MkT</a > :: <span class="keyword" >forall</span - > (f :: <span class="keyword" + > (a :: <span class="keyword" >forall</span > k. k -> <a href="#" title="Data.Kind" >Type</a - >) k (a :: k). f a -> <a href="#" title="Bug1050" + >) k (b :: k). a b -> <a href="#" title="Bug1050" >T</a - > f a</td + > a b</td ><td class="doc empty" > </td ></tr @@ -101,7 +97,7 @@ >forall</span > {k} {f :: <span class="keyword" >forall</span - > k. k -> <a href="#" title="Data.Kind" + > k1. k1 -> <a href="#" title="Data.Kind" >Type</a >} {a :: k}. f a -> <a href="#" title="Bug1050" >T</a diff --git a/html-test/ref/Bug294.html b/html-test/ref/Bug294.html index c62fc6069e6df2a2ea3b4c6bc8007cb306dfe80f..ff27890727ddb3702444556e0c44031ec22d668f 100644 --- a/html-test/ref/Bug294.html +++ b/html-test/ref/Bug294.html @@ -197,7 +197,7 @@ >data family</span > <a id="t:TP" class="def" >TP</a - > t :: * <a href="#" class="selflink" + > t <a href="#" class="selflink" >#</a ></p ><div class="subs instances" @@ -259,7 +259,7 @@ >data family</span > <a id="t:DP" class="def" >DP</a - > t :: * <a href="#" class="selflink" + > t <a href="#" class="selflink" >#</a ></p ><div class="subs instances" @@ -321,7 +321,7 @@ >data family</span > <a id="t:TO-39-" class="def" >TO'</a - > t :: * <a href="#" class="selflink" + > t <a href="#" class="selflink" >#</a ></p ><div class="subs instances" diff --git a/html-test/ref/Bug466.html b/html-test/ref/Bug466.html index 4fab918a0e8a014fe907e3699327622d1280c2d3..5d8df23d6c74c4d1c1c20339131bf20b93c79301 100644 --- a/html-test/ref/Bug466.html +++ b/html-test/ref/Bug466.html @@ -68,7 +68,9 @@ >type</span > <a id="t:Fam" class="def" >Fam</a - > a :: [*] <a href="#" class="selflink" + > a :: [<a href="#" title="Data.Kind" + >Type</a + >] <a href="#" class="selflink" >#</a ></p ></div diff --git a/html-test/ref/Bug548.html b/html-test/ref/Bug548.html index 594480c7f62e43ccdd1c42092d2947d76e7d77b3..3491224e71740529b6d959061cf01feb0f6ec878 100644 --- a/html-test/ref/Bug548.html +++ b/html-test/ref/Bug548.html @@ -412,7 +412,249 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:WrappedArrow:Generic:5" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:WrappedArrow:Data:5" + ></span + > (<a href="#" title="Type.Reflection" + >Typeable</a + > a, <a href="#" title="Type.Reflection" + >Typeable</a + > b, <a href="#" title="Type.Reflection" + >Typeable</a + > c, <a href="#" title="Data.Data" + >Data</a + > (a b c)) => <a href="#" title="Data.Data" + >Data</a + > (<a href="#" title="Bug548" + >WrappedArrow</a + > a b c)</span + ></td + ><td class="doc" + ><p + ><em + >Since: base-4.14.0.0</em + ></p + ></td + ></tr + ><tr + ><td colspan="2" + ><details id="i:id:WrappedArrow:Data:5" + ><summary class="hide-when-js-enabled" + >Instance details</summary + ><p + >Defined in <a href="#" + >Data.Data</a + ></p + > <div class="subs methods" + ><p class="caption" + >Methods</p + ><p class="src" + ><a href="#" + >gfoldl</a + > :: (<span class="keyword" + >forall</span + > d b0. <a href="#" title="Data.Data" + >Data</a + > d => c0 (d -> b0) -> d -> c0 b0) -> (<span class="keyword" + >forall</span + > g. g -> c0 g) -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> c0 (<a href="#" title="Bug548" + >WrappedArrow</a + > a b c) <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gunfold</a + > :: (<span class="keyword" + >forall</span + > b0 r. <a href="#" title="Data.Data" + >Data</a + > b0 => c0 (b0 -> r) -> c0 r) -> (<span class="keyword" + >forall</span + > r. r -> c0 r) -> <a href="#" title="Data.Data" + >Constr</a + > -> c0 (<a href="#" title="Bug548" + >WrappedArrow</a + > a b c) <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >toConstr</a + > :: <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> <a href="#" title="Data.Data" + >Constr</a + > <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >dataTypeOf</a + > :: <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> <a href="#" title="Data.Data" + >DataType</a + > <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >dataCast1</a + > :: <a href="#" title="Type.Reflection" + >Typeable</a + > t => (<span class="keyword" + >forall</span + > d. <a href="#" title="Data.Data" + >Data</a + > d => c0 (t d)) -> <a href="#" title="Data.Maybe" + >Maybe</a + > (c0 (<a href="#" title="Bug548" + >WrappedArrow</a + > a b c)) <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >dataCast2</a + > :: <a href="#" title="Type.Reflection" + >Typeable</a + > t => (<span class="keyword" + >forall</span + > d e. (<a href="#" title="Data.Data" + >Data</a + > d, <a href="#" title="Data.Data" + >Data</a + > e) => c0 (t d e)) -> <a href="#" title="Data.Maybe" + >Maybe</a + > (c0 (<a href="#" title="Bug548" + >WrappedArrow</a + > a b c)) <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gmapT</a + > :: (<span class="keyword" + >forall</span + > b0. <a href="#" title="Data.Data" + >Data</a + > b0 => b0 -> b0) -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gmapQl</a + > :: (r -> r' -> r) -> r -> (<span class="keyword" + >forall</span + > d. <a href="#" title="Data.Data" + >Data</a + > d => d -> r') -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> r <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gmapQr</a + > :: <span class="keyword" + >forall</span + > r r'. (r' -> r -> r) -> r -> (<span class="keyword" + >forall</span + > d. <a href="#" title="Data.Data" + >Data</a + > d => d -> r') -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> r <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gmapQ</a + > :: (<span class="keyword" + >forall</span + > d. <a href="#" title="Data.Data" + >Data</a + > d => d -> u) -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> [u] <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gmapQi</a + > :: <a href="#" title="Data.Int" + >Int</a + > -> (<span class="keyword" + >forall</span + > d. <a href="#" title="Data.Data" + >Data</a + > d => d -> u) -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> u <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gmapM</a + > :: <a href="#" title="Control.Monad" + >Monad</a + > m => (<span class="keyword" + >forall</span + > d. <a href="#" title="Data.Data" + >Data</a + > d => d -> m d) -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> m (<a href="#" title="Bug548" + >WrappedArrow</a + > a b c) <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gmapMp</a + > :: <a href="#" title="Control.Monad" + >MonadPlus</a + > m => (<span class="keyword" + >forall</span + > d. <a href="#" title="Data.Data" + >Data</a + > d => d -> m d) -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> m (<a href="#" title="Bug548" + >WrappedArrow</a + > a b c) <a href="#" class="selflink" + >#</a + ></p + ><p class="src" + ><a href="#" + >gmapMo</a + > :: <a href="#" title="Control.Monad" + >MonadPlus</a + > m => (<span class="keyword" + >forall</span + > d. <a href="#" title="Data.Data" + >Data</a + > d => d -> m d) -> <a href="#" title="Bug548" + >WrappedArrow</a + > a b c -> m (<a href="#" title="Bug548" + >WrappedArrow</a + > a b c) <a href="#" class="selflink" + >#</a + ></p + ></div + ></details + ></td + ></tr + ><tr + ><td class="src clearfix" + ><span class="inst-left" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:WrappedArrow:Generic:6" ></span > <a href="#" title="GHC.Generics" >Generic</a @@ -425,7 +667,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:WrappedArrow:Generic:5" + ><details id="i:id:WrappedArrow:Generic:6" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -484,7 +726,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:WrappedArrow:Rep1:6" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:WrappedArrow:Rep1:7" ></span > <span class="keyword" >type</span @@ -507,7 +749,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:WrappedArrow:Rep1:6" + ><details id="i:id:WrappedArrow:Rep1:7" ><summary class="hide-when-js-enabled" >Instance details</summary ><p @@ -560,7 +802,7 @@ ><tr ><td class="src clearfix" ><span class="inst-left" - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:WrappedArrow:Rep:7" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:WrappedArrow:Rep:8" ></span > <span class="keyword" >type</span @@ -579,7 +821,7 @@ ></tr ><tr ><td colspan="2" - ><details id="i:id:WrappedArrow:Rep:7" + ><details id="i:id:WrappedArrow:Rep:8" ><summary class="hide-when-js-enabled" >Instance details</summary ><p diff --git a/html-test/ref/Bug613.html b/html-test/ref/Bug613.html index 425fc670b6790082ee65d70b3ec9994b0795e4b6..16cd5b932a82660fbffc67e6bd2ed8a421a6f058 100644 --- a/html-test/ref/Bug613.html +++ b/html-test/ref/Bug613.html @@ -58,7 +58,11 @@ >class</span > <a href="#" >Functor</a - > f <span class="keyword" + > (f :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) <span class="keyword" >where</span ><ul class="subs" ><li @@ -87,7 +91,11 @@ >class</span > <a id="t:Functor" class="def" >Functor</a - > f <span class="keyword" + > (f :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) <span class="keyword" >where</span > <a href="#" class="selflink" >#</a diff --git a/html-test/ref/Bug8.html b/html-test/ref/Bug8.html index e62caae38a4933e7da434c95f3139064c004f8c6..fda107707f5818fe69fb0ee11f706f8e236b27e4 100644 --- a/html-test/ref/Bug8.html +++ b/html-test/ref/Bug8.html @@ -95,7 +95,7 @@ ><p class="src" ><a id="v:-45--45--62-" class="def" >(-->)</a - > :: p -> p -> <a href="#" title="Bug8" + > :: p1 -> p2 -> <a href="#" title="Bug8" >Typ</a > <span class="fixity" >infix 9</span diff --git a/html-test/ref/Bug85.html b/html-test/ref/Bug85.html index c22438c77f30d1d4cf84a60f053f98bcf341c50e..714635da82f3771c07b7b11c688736b2fc61861a 100644 --- a/html-test/ref/Bug85.html +++ b/html-test/ref/Bug85.html @@ -57,7 +57,11 @@ >data</span > <a id="t:Foo" class="def" >Foo</a - > :: (* -> *) -> * -> * <span class="keyword" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -70,9 +74,15 @@ ><td class="src" ><a id="v:Bar" class="def" >Bar</a - > :: f x -> <a href="#" title="Bug85" + > :: <span class="keyword" + >forall</span + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) x. a x -> <a href="#" title="Bug85" >Foo</a - > f (f x)</td + > a (a x)</td ><td class="doc empty" > </td ></tr @@ -85,7 +95,7 @@ >data</span > <a id="t:Baz" class="def" >Baz</a - > :: * <span class="keyword" + > <span class="keyword" >where</span > <a href="#" class="selflink" >#</a diff --git a/html-test/ref/Bug923.html b/html-test/ref/Bug923.html index 7c2872542f48789100a8528623901716d26aa282..2cf1a940013f66284564f0674fe2d1de249356c5 100644 --- a/html-test/ref/Bug923.html +++ b/html-test/ref/Bug923.html @@ -58,17 +58,31 @@ >data</span > <a href="#" >T</a - > :: (* -> (*, *)) -> * <span class="keyword" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> (<a href="#" title="Data.Kind" + >Type</a + >, <a href="#" title="Data.Kind" + >Type</a + >)) <span class="keyword" >where</span ><ul class="subs" ><li ><a href="#" >T</a - > :: a -> <a href="#" title="Bug923" + > :: <span class="keyword" + >forall</span + > a1. a1 -> <a href="#" title="Bug923" >T</a - > ('<a href="#" title="GHC.Tuple" + > ('<a href="#" title="Data.Tuple" >(,)</a - > a)</li + > a1 :: <a href="#" title="Data.Kind" + >Type</a + > -> (<a href="#" title="Data.Kind" + >Type</a + >, <a href="#" title="Data.Kind" + >Type</a + >))</li ></ul ></li ></ul @@ -83,7 +97,13 @@ >data</span > <a id="t:T" class="def" >T</a - > :: (* -> (*, *)) -> * <span class="keyword" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> (<a href="#" title="Data.Kind" + >Type</a + >, <a href="#" title="Data.Kind" + >Type</a + >)) <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -100,11 +120,19 @@ ><td class="src" ><a id="v:T" class="def" >T</a - > :: a -> <a href="#" title="Bug923" + > :: <span class="keyword" + >forall</span + > a1. a1 -> <a href="#" title="Bug923" >T</a - > ('<a href="#" title="GHC.Tuple" + > ('<a href="#" title="Data.Tuple" >(,)</a - > a)</td + > a1 :: <a href="#" title="Data.Kind" + >Type</a + > -> (<a href="#" title="Data.Kind" + >Type</a + >, <a href="#" title="Data.Kind" + >Type</a + >))</td ><td class="doc empty" > </td ></tr @@ -128,7 +156,7 @@ >Eq</a > (<a href="#" title="Bug923" >T</a - > ('<a href="#" title="GHC.Tuple" + > ('<a href="#" title="Data.Tuple" >(,)</a > a :: <a href="#" title="Data.Kind" >Type</a @@ -162,11 +190,11 @@ >(==)</a > :: <a href="#" title="Bug923" >T</a - > ('<a href="#" title="GHC.Tuple" + > ('<a href="#" title="Data.Tuple" >(,)</a > a) -> <a href="#" title="Bug923" >T</a - > ('<a href="#" title="GHC.Tuple" + > ('<a href="#" title="Data.Tuple" >(,)</a > a) -> <a href="#" title="Data.Bool" >Bool</a @@ -178,11 +206,11 @@ >(/=)</a > :: <a href="#" title="Bug923" >T</a - > ('<a href="#" title="GHC.Tuple" + > ('<a href="#" title="Data.Tuple" >(,)</a > a) -> <a href="#" title="Bug923" >T</a - > ('<a href="#" title="GHC.Tuple" + > ('<a href="#" title="Data.Tuple" >(,)</a > a) -> <a href="#" title="Data.Bool" >Bool</a diff --git a/html-test/ref/Bug973.html b/html-test/ref/Bug973.html index 8297b4f4e83c3c78d6ea024d2ff94d142f9ad155..74b3a9e714d0f83563decf50c52af0d811976b59 100644 --- a/html-test/ref/Bug973.html +++ b/html-test/ref/Bug973.html @@ -56,9 +56,7 @@ ><li class="src short" ><a href="#" >showRead</a - > :: <span class="keyword" - >forall</span - > a b. (<a href="#" title="Text.Show" + > :: (<a href="#" title="Text.Show" >Show</a > a, <a href="#" title="Text.Read" >Read</a @@ -92,9 +90,7 @@ ><table ><tr ><td class="src" - >:: <span class="keyword" - >forall</span - > a b. (<a href="#" title="Text.Show" + >:: (<a href="#" title="Text.Show" >Show</a > a, <a href="#" title="Text.Read" >Read</a diff --git a/html-test/ref/BundledPatterns.html b/html-test/ref/BundledPatterns.html index 8ac16a689d21941ece3a24dc292c00561eb43fd6..93b7fe63529b365e9690db49b87234bfc9273c54 100644 --- a/html-test/ref/BundledPatterns.html +++ b/html-test/ref/BundledPatterns.html @@ -36,7 +36,7 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td + >None</td ></tr ><tr ><th @@ -58,17 +58,19 @@ >data</span > <a href="#" >Vec</a - > :: <a href="#" title="GHC.TypeLits" + > (a :: <a href="#" title="GHC.TypeNats" >Nat</a - > -> * -> * <span class="keyword" + >) b <span class="keyword" >where</span ><ul class="subs" ><li ><a href="#" >Nil</a - > :: <a href="#" title="BundledPatterns" + > :: <span class="keyword" + >forall</span + > b. <a href="#" title="BundledPatterns" >Vec</a - > 0 a</li + > 0 b</li ><li ><span class="keyword" >pattern</span @@ -88,9 +90,9 @@ >data</span > <a href="#" >RTree</a - > :: <a href="#" title="GHC.TypeLits" + > (a :: <a href="#" title="GHC.TypeNats" >Nat</a - > -> * -> * <span class="keyword" + >) b <span class="keyword" >where</span ><ul class="subs" ><li @@ -129,9 +131,9 @@ >data</span > <a id="t:Vec" class="def" >Vec</a - > :: <a href="#" title="GHC.TypeLits" + > (a :: <a href="#" title="GHC.TypeNats" >Nat</a - > -> * -> * <span class="keyword" + >) b <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -167,9 +169,11 @@ ><td class="src" ><a id="v:Nil" class="def" >Nil</a - > :: <a href="#" title="BundledPatterns" + > :: <span class="keyword" + >forall</span + > b. <a href="#" title="BundledPatterns" >Vec</a - > 0 a</td + > 0 b</td ><td class="doc empty" > </td ></tr @@ -291,9 +295,9 @@ >data</span > <a id="t:RTree" class="def" >RTree</a - > :: <a href="#" title="GHC.TypeLits" + > (a :: <a href="#" title="GHC.TypeNats" >Nat</a - > -> * -> * <span class="keyword" + >) b <span class="keyword" >where</span > <a href="#" class="selflink" >#</a diff --git a/html-test/ref/BundledPatterns2.html b/html-test/ref/BundledPatterns2.html index fff9d572940cafdf05d371ac0653443e4085d37b..e8c099d97ef6f598c7e0c3e625459f329767a0b1 100644 --- a/html-test/ref/BundledPatterns2.html +++ b/html-test/ref/BundledPatterns2.html @@ -36,7 +36,7 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td + >None</td ></tr ><tr ><th @@ -58,9 +58,9 @@ >data</span > <a href="#" >Vec</a - > :: <a href="#" title="GHC.TypeLits" + > (a :: <a href="#" title="GHC.TypeNats" >Nat</a - > -> * -> * <span class="keyword" + >) b <span class="keyword" >where</span ><ul class="subs" ><li @@ -90,9 +90,9 @@ >data</span > <a href="#" >RTree</a - > :: <a href="#" title="GHC.TypeLits" + > (a :: <a href="#" title="GHC.TypeNats" >Nat</a - > -> * -> * <span class="keyword" + >) b <span class="keyword" >where</span ><ul class="subs" ><li @@ -131,9 +131,9 @@ >data</span > <a id="t:Vec" class="def" >Vec</a - > :: <a href="#" title="GHC.TypeLits" + > (a :: <a href="#" title="GHC.TypeNats" >Nat</a - > -> * -> * <span class="keyword" + >) b <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -289,9 +289,9 @@ >data</span > <a id="t:RTree" class="def" >RTree</a - > :: <a href="#" title="GHC.TypeLits" + > (a :: <a href="#" title="GHC.TypeNats" >Nat</a - > -> * -> * <span class="keyword" + >) b <span class="keyword" >where</span > <a href="#" class="selflink" >#</a diff --git a/html-test/ref/ConstructorPatternExport.html b/html-test/ref/ConstructorPatternExport.html index aa0c1a8f3d3c5d9dae90681d0072c4397314a475..9830ed81132ab32ffdc865e3a7f2cefb372cff11 100644 --- a/html-test/ref/ConstructorPatternExport.html +++ b/html-test/ref/ConstructorPatternExport.html @@ -107,7 +107,7 @@ >pattern</span > <a id="v:MyGADTCons" class="def" >MyGADTCons</a - > :: a -> <a href="#" title="Data.Int" + > :: a1 -> <a href="#" title="Data.Int" >Int</a > -> MyGADT (<a href="#" title="Data.Maybe" >Maybe</a diff --git a/html-test/ref/DefaultAssociatedTypes.html b/html-test/ref/DefaultAssociatedTypes.html index bc4d8a001e3746e48201aaa19c66338a06174c18..470f719ec71bb5f5683b1aa519e53eb6329ca129 100644 --- a/html-test/ref/DefaultAssociatedTypes.html +++ b/html-test/ref/DefaultAssociatedTypes.html @@ -66,11 +66,15 @@ >type</span > <a href="#" >Qux</a - > a :: *</li + > a</li ><li ><a href="#" >bar</a - >, <a href="#" + > :: a -> <a href="#" title="Data.String" + >String</a + ></li + ><li + ><a href="#" >baz</a > :: a -> <a href="#" title="Data.String" >String</a @@ -106,7 +110,7 @@ >type</span > <a id="t:Qux" class="def" >Qux</a - > a :: * <a href="#" class="selflink" + > a <a href="#" class="selflink" >#</a ></p ><div class="doc" diff --git a/html-test/ref/DefaultSignatures.html b/html-test/ref/DefaultSignatures.html index f44cc85970978bb4def9d1996da50449f37e5b28..b0ba01b31cc17b2e51b1e694f919aafa5a6ab83a 100644 --- a/html-test/ref/DefaultSignatures.html +++ b/html-test/ref/DefaultSignatures.html @@ -64,7 +64,11 @@ ><li ><a href="#" >bar</a - >, <a href="#" + > :: a -> <a href="#" title="Data.String" + >String</a + ></li + ><li + ><a href="#" >baz</a > :: a -> <a href="#" title="Data.String" >String</a @@ -136,6 +140,10 @@ > <a href="#" class="selflink" >#</a ></p + ><div class="doc" + ><p + >Documentation for the default signature of bar.</p + ></div ></div ><p class="src" ><a id="v:baz" class="def" @@ -176,6 +184,10 @@ > -> a <a href="#" class="selflink" >#</a ></p + ><div class="doc" + ><p + >Documentation for the default signature of baz'.</p + ></div ></div ></div ></div diff --git a/html-test/ref/DeprecatedTypeFamily.html b/html-test/ref/DeprecatedTypeFamily.html index 4fbaeaa5e997704f29c705050742c0c649461aa9..e923dbd225797a744a2989e87055a8bdc8e5f2ba 100644 --- a/html-test/ref/DeprecatedTypeFamily.html +++ b/html-test/ref/DeprecatedTypeFamily.html @@ -58,13 +58,21 @@ >data family</span > <a href="#" >SomeTypeFamily</a - > k :: * -> *</li + > k :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + ></li ><li class="src short" ><span class="keyword" >data family</span > <a href="#" >SomeOtherTypeFamily</a - > k :: * -> *</li + > k :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + ></li ></ul ></details ></div @@ -77,7 +85,11 @@ >data family</span > <a id="t:SomeTypeFamily" class="def" >SomeTypeFamily</a - > k :: * -> * <a href="#" class="selflink" + > k :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + > <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -95,7 +107,11 @@ >data family</span > <a id="t:SomeOtherTypeFamily" class="def" >SomeOtherTypeFamily</a - > k :: * -> * <a href="#" class="selflink" + > k :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + > <a href="#" class="selflink" >#</a ></p ><div class="doc" diff --git a/html-test/ref/FunArgs.html b/html-test/ref/FunArgs.html index 2fac6d4e31e92364fe26e73bf47552cb61dc6b92..84a16d1087c4ccb2d4a17e820ec8138dd2bf2536 100644 --- a/html-test/ref/FunArgs.html +++ b/html-test/ref/FunArgs.html @@ -64,9 +64,7 @@ ><table ><tr ><td class="src" - >:: <span class="keyword" - >forall</span - > a. <a href="#" title="Data.Ord" + >:: <a href="#" title="Data.Ord" >Ord</a > a</td ><td class="doc empty" @@ -178,9 +176,7 @@ ><table ><tr ><td class="src" - >:: <span class="keyword" - >forall</span - > a b c. a</td + >:: a</td ><td class="doc" ><p >First argument</p @@ -230,9 +226,9 @@ ><td class="src" >:: <span class="keyword" >forall</span - > a (b :: ()) d. d ~ '<a href="#" title="GHC.Tuple" - >()</a - ></td + > a (b :: ()) (d :: ()). d <a href="#" title="GHC.Types" + >~</a + > '()</td ><td class="doc empty" > </td ></tr diff --git a/html-test/ref/GADTRecords.html b/html-test/ref/GADTRecords.html index 834d8f6723d94247658660305a9a6cbde30b1254..7f9f80f67a2420fce4c329e7d66fb7d51eb08425 100644 --- a/html-test/ref/GADTRecords.html +++ b/html-test/ref/GADTRecords.html @@ -64,13 +64,17 @@ ><li ><a href="#" >C1</a - > :: <a href="#" title="GADTRecords" + > :: <span class="keyword" + >forall</span + > a b. <a href="#" title="GADTRecords" >H1</a > a b</li ><li ><a href="#" >C2</a - > :: <a href="#" title="Data.Ord" + > :: <span class="keyword" + >forall</span + > a. <a href="#" title="Data.Ord" >Ord</a > a => [a] -> <a href="#" title="GADTRecords" >H1</a @@ -88,11 +92,13 @@ ><li ><a href="#" >C4</a - > :: {..} -> <a href="#" title="GADTRecords" + > :: <span class="keyword" + >forall</span + > b. {..} -> <a href="#" title="GADTRecords" >H1</a > <a href="#" title="Data.Int" >Int</a - > a</li + > b</li ></ul ></li ></ul @@ -124,7 +130,9 @@ ><td class="src" ><a id="v:C1" class="def" >C1</a - > :: <a href="#" title="GADTRecords" + > :: <span class="keyword" + >forall</span + > a b. <a href="#" title="GADTRecords" >H1</a > a b</td ><td class="doc empty" @@ -134,7 +142,9 @@ ><td class="src" ><a id="v:C2" class="def" >C2</a - > :: <a href="#" title="Data.Ord" + > :: <span class="keyword" + >forall</span + > a. <a href="#" title="Data.Ord" >Ord</a > a => [a] -> <a href="#" title="GADTRecords" >H1</a @@ -200,9 +210,11 @@ ><ul ><li ><dfn class="src" - >:: { <a id="v:field2" class="def" + >:: <span class="keyword" + >forall</span + > b. { <a id="v:field2" class="def" >field2</a - > :: a</dfn + > :: b</dfn ><div class="doc" ><p >hello2 docs</p @@ -214,7 +226,7 @@ >H1</a > <a href="#" title="Data.Int" >Int</a - > a</dfn + > b</dfn ><div class="doc empty" > </div ></li diff --git a/html-test/ref/HideRuntimeReps.html b/html-test/ref/HideRuntimeReps.html new file mode 100644 index 0000000000000000000000000000000000000000..118514f09cde02bec4cf9007afd2ad80d8dc3c37 --- /dev/null +++ b/html-test/ref/HideRuntimeReps.html @@ -0,0 +1,165 @@ +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><meta name="viewport" content="width=device-width, initial-scale=1" + /><title + >HideRuntimeReps</title + ><link href="#" rel="stylesheet" type="text/css" title="Linuwial" + /><link rel="stylesheet" type="text/css" href="#" + /><link rel="stylesheet" type="text/css" href="#" + /><script src="haddock-bundle.min.js" async="async" type="text/javascript" + ></script + ><script type="text/x-mathjax-config" + >MathJax.Hub.Config({ tex2jax: { processClass: "mathjax", ignoreClass: ".*" } });</script + ><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js?config=TeX-AMS-MML_HTMLorMML" type="text/javascript" + ></script + ></head + ><body + ><div id="package-header" + ><span class="caption empty" + > </span + ><ul class="links" id="page-menu" + ><li + ><a href="#" + >Contents</a + ></li + ><li + ><a href="#" + >Index</a + ></li + ></ul + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >HideRuntimeReps</p + ></div + ><div id="synopsis" + ><details id="syn" + ><summary + >Synopsis</summary + ><ul class="details-toggle" data-details-id="syn" + ><li class="src short" + ><a href="#" + >($)</a + > :: (a -> b) -> a -> b</li + ><li class="src short" + ><a href="#" + >error</a + > :: <a href="#" title="GHC.Stack" + >HasCallStack</a + > => [<a href="#" title="Data.Char" + >Char</a + >] -> a</li + ></ul + ></details + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a id="v:-36-" class="def" + >($)</a + > :: (a -> b) -> a -> b <span class="fixity" + >infixr 0</span + ><span class="rightedge" + ></span + > <a href="#" class="selflink" + >#</a + ></p + ><div class="doc" + ><p + >Application operator. This operator is redundant, since ordinary + application <code + >(f x)</code + > means the same as <code + >(f <code + ><a href="#" title="HideRuntimeReps" + >$</a + ></code + > x)</code + >. However, <code + ><a href="#" title="HideRuntimeReps" + >$</a + ></code + > has + low, right-associative binding precedence, so it sometimes allows + parentheses to be omitted; for example:</p + ><pre + >f $ g $ h x = f (g (h x))</pre + ><p + >It is also useful in higher-order situations, such as <code + ><code + ><a href="#" title="GHC.List" + >map</a + ></code + > (<code + ><a href="#" title="HideRuntimeReps" + >$</a + ></code + > 0) xs</code + >, + or <code + ><code + ><a href="#" title="Data.List" + >zipWith</a + ></code + > (<code + ><a href="#" title="HideRuntimeReps" + >$</a + ></code + >) fs xs</code + >.</p + ><p + >Note that <code + >(<code + ><a href="#" title="HideRuntimeReps" + >$</a + ></code + >)</code + > is representation-polymorphic in its result type, so that + <code + >foo <code + ><a href="#" title="HideRuntimeReps" + >$</a + ></code + > True</code + > where <code + >foo :: Bool -> Int#</code + > is well-typed.</p + ></div + ></div + ><div class="top" + ><p class="src" + ><a id="v:error" class="def" + >error</a + > :: <a href="#" title="GHC.Stack" + >HasCallStack</a + > => [<a href="#" title="Data.Char" + >Char</a + >] -> a <a href="#" class="selflink" + >#</a + ></p + ><div class="doc" + ><p + ><code + ><a href="#" title="HideRuntimeReps" + >error</a + ></code + > stops execution and displays an error message.</p + ></div + ></div + ></div + ></div + ></body + ></html +> diff --git a/html-test/ref/Identifiers.html b/html-test/ref/Identifiers.html index b177266d4e679c255e884b2d57bf50b4c97f8383..4f1ebf2a89ae7dc2b6f3e1403f34f76be8cfbd4a 100644 --- a/html-test/ref/Identifiers.html +++ b/html-test/ref/Identifiers.html @@ -147,12 +147,12 @@ ></code >, <code ><a href="#" title="Data.Foldable" - >Foldable</a + >elem</a ></code ></li ><li >Qualified: <code - ><a href="#" title="GHC.List" + ><a href="#" title="Data.List" >++</a ></code >, <code @@ -169,7 +169,7 @@ >++</code >, <code ><a href="#" title="Data.Foldable" - >Foldable</a + >elem</a ></code >, <code >elem</code @@ -207,7 +207,7 @@ ><li >Qualified: <code ><code - ><a href="#" title="GHC.List" + ><a href="#" title="Data.List" >(++)</a ></code > [1,2,3] [4,5,6]</code @@ -238,14 +238,14 @@ >Unqualified: <code >1 <code ><a href="#" title="Data.Foldable" - >`Foldable`</a + >`elem`</a ></code > [-3..3]</code ></li ><li >Qualified: <code >1 <code - ><a href="#" title="GHC.List" + ><a href="#" title="Data.List" >`elem`</a ></code > [-3..3]</code @@ -253,7 +253,7 @@ ><li >Namespaced: <code ><a href="#" title="Data.Foldable" - >`Foldable`</a + >`elem`</a ></code >, <code >`elem`</code diff --git a/html-test/ref/Instances.html b/html-test/ref/Instances.html index e99f82e4b217f6677d7c63c2e814c389fe08672a..a27ee9c9044107cdf9a1b7f951ec4391c133d939 100644 --- a/html-test/ref/Instances.html +++ b/html-test/ref/Instances.html @@ -153,7 +153,13 @@ >class</span > <a id="t:Foo" class="def" >Foo</a - > f <span class="keyword" + > (f :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="GHC.Exts" + >TYPE</a + > <a href="#" title="GHC.Exts" + >LiftedRep</a + >) <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -262,7 +268,9 @@ ></span > <a href="#" title="Instances" >Foo</a - > []</span + > <a href="#" title="Data.List" + >[]</a + ></span > <a href="#" class="selflink" >#</a ></td @@ -438,7 +446,7 @@ >Foo</a > f) => <a href="#" title="Instances" >Foo</a - > (<a href="#" title="GHC.Tuple" + > (<a href="#" title="Data.Tuple" >(,)</a > (f a))</span > <a href="#" class="selflink" @@ -550,7 +558,7 @@ ></span > <a href="#" title="Instances" >Foo</a - > (<a href="#" title="GHC.Tuple" + > (<a href="#" title="Data.Tuple" >(,,)</a > a a)</span > <a href="#" class="selflink" @@ -653,7 +661,13 @@ >Foo</a > f => <a id="t:Bar" class="def" >Bar</a - > f a <span class="keyword" + > (f :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="GHC.Exts" + >TYPE</a + > <a href="#" title="GHC.Exts" + >LiftedRep</a + >) a <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -900,7 +914,9 @@ ></span > <a href="#" title="Instances" >Bar</a - > [] (a, a)</span + > <a href="#" title="Data.List" + >[]</a + > (a, a)</span > <a href="#" class="selflink" >#</a ></td @@ -1150,11 +1166,11 @@ ></span > <a href="#" title="Instances" >Foo</a - > (<a href="#" title="GHC.Tuple" + > (<a href="#" title="Data.Tuple" >(,,)</a > a b) => <a href="#" title="Instances" >Bar</a - > (<a href="#" title="GHC.Tuple" + > (<a href="#" title="Data.Tuple" >(,,)</a > a b) (a, b, a)</span > <a href="#" class="selflink" @@ -1234,9 +1250,9 @@ >baz</a > :: a -> (<span class="keyword" >forall</span - > a. a -> a) -> (b, <span class="keyword" + > a1. a1 -> a1) -> (b, <span class="keyword" >forall</span - > c. c -> a) -> (b, c) <a href="#" class="selflink" + > c1. c1 -> a) -> (b, c) <a href="#" class="selflink" >#</a ></p ><p class="src" @@ -1244,9 +1260,9 @@ >baz'</a > :: b -> (<span class="keyword" >forall</span - > b. b -> a) -> (<span class="keyword" + > b1. b1 -> a) -> (<span class="keyword" >forall</span - > b. b -> a) -> [(b, a)] <a href="#" class="selflink" + > b1. b1 -> a) -> [(b, a)] <a href="#" class="selflink" >#</a ></p ><p class="src" @@ -1254,11 +1270,11 @@ >baz''</a > :: b -> (<span class="keyword" >forall</span - > b. (<span class="keyword" + > b1. (<span class="keyword" >forall</span - > b. b -> a) -> c) -> <span class="keyword" + > b2. b2 -> a) -> c) -> <span class="keyword" >forall</span - > c. c -> b <a href="#" class="selflink" + > c1. c1 -> b <a href="#" class="selflink" >#</a ></p ></div @@ -2141,6 +2157,160 @@ ></details ></div ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data family</span + > <a id="t:Thud" class="def" + >Thud</a + > a c <a href="#" class="selflink" + >#</a + ></p + ><div class="subs instances" + ><h4 class="instances details-toggle-control details-toggle" data-details-id="i:Thud" + >Instances</h4 + ><details id="i:Thud" open="open" + ><summary class="hide-when-js-enabled" + >Instances details</summary + ><table + ><tr + ><td class="src clearfix" + ><span class="inst-left" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:if:Thud:Thud:1" + ></span + > <span class="keyword" + >data</span + > <a href="#" title="Instances" + >Thud</a + > <a href="#" title="Data.Int" + >Int</a + > [a]</span + > <a href="#" class="selflink" + >#</a + ></td + ><td class="doc empty" + > </td + ></tr + ><tr + ><td colspan="2" + ><details id="i:if:Thud:Thud:1" + ><summary class="hide-when-js-enabled" + >Instance details</summary + ><p + >Defined in <a href="#" + >Instances</a + ></p + > <div class="src" + ><span class="keyword" + >data</span + > <a href="#" title="Instances" + >Thud</a + > <a href="#" title="Data.Int" + >Int</a + > [a] = <a id="v:Thuuuud" class="def" + >Thuuuud</a + > <a href="#" title="Data.Bool" + >Bool</a + ></div + ></details + ></td + ></tr + ><tr + ><td class="src clearfix" + ><span class="inst-left" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:if:Thud:Thud:2" + ></span + > <span class="keyword" + >data</span + > <a href="#" title="Instances" + >Thud</a + > <a href="#" title="Data.Int" + >Int</a + > (<a href="#" title="Instances" + >Quux</a + > a [a] c)</span + > <a href="#" class="selflink" + >#</a + ></td + ><td class="doc empty" + > </td + ></tr + ><tr + ><td colspan="2" + ><details id="i:if:Thud:Thud:2" + ><summary class="hide-when-js-enabled" + >Instance details</summary + ><p + >Defined in <a href="#" + >Instances</a + ></p + > <div class="src" + ><span class="keyword" + >data</span + > <a href="#" title="Instances" + >Thud</a + > <a href="#" title="Data.Int" + >Int</a + > (<a href="#" title="Instances" + >Quux</a + > a [a] c) <ul class="inst" + ><li class="inst" + >= <a id="v:Thuud" class="def" + >Thuud</a + > a</li + ><li class="inst" + >| <a id="v:Thuuud" class="def" + >Thuuud</a + > <a href="#" title="Data.Int" + >Int</a + > <a href="#" title="Data.Int" + >Int</a + ></li + ></ul + ></div + ></details + ></td + ></tr + ><tr + ><td class="src clearfix" + ><span class="inst-left" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:if:Thud:Thud:3" + ></span + > <span class="keyword" + >data</span + > <a href="#" title="Instances" + >Thud</a + > [a] (a, a, a)</span + > <a href="#" class="selflink" + >#</a + ></td + ><td class="doc empty" + > </td + ></tr + ><tr + ><td colspan="2" + ><details id="i:if:Thud:Thud:3" + ><summary class="hide-when-js-enabled" + >Instance details</summary + ><p + >Defined in <a href="#" + >Instances</a + ></p + > <div class="src" + ><span class="keyword" + >data</span + > <a href="#" title="Instances" + >Thud</a + > [a] (a, a, a) = <a id="v:Thd" class="def" + >Thd</a + > a</div + ></details + ></td + ></tr + ></table + ></details + ></div + ></div ></div ></div ></body diff --git a/html-test/ref/LinearTypes.html b/html-test/ref/LinearTypes.html index fbece396bd03bbab45ad4b10497cff9117877b8f..3f3d4e808f42eab9b9c3d20372ac6f464cc0979b 100644 --- a/html-test/ref/LinearTypes.html +++ b/html-test/ref/LinearTypes.html @@ -64,7 +64,11 @@ ><li class="src short" ><a href="#" >poly</a - > :: a %m -> b</li + > :: <span class="keyword" + >forall</span + > a b (m :: <a href="#" title="GHC.Base" + >Multiplicity</a + >). a %m -> b</li ></ul ></details ></div @@ -99,7 +103,11 @@ ><p class="src" ><a id="v:poly" class="def" >poly</a - > :: a %m -> b <a href="#" class="selflink" + > :: <span class="keyword" + >forall</span + > a b (m :: <a href="#" title="GHC.Base" + >Multiplicity</a + >). a %m -> b <a href="#" class="selflink" >#</a ></p ><div class="doc" diff --git a/html-test/ref/Operators.html b/html-test/ref/Operators.html index 9ebbe42d064fe0c5486c7db571ff28ba2a20dc9b..ea67771e62c6d74265a9bb501259f623be24521e 100644 --- a/html-test/ref/Operators.html +++ b/html-test/ref/Operators.html @@ -114,7 +114,9 @@ ><li ><a href="#" >(:<->)</a - > :: a -> b -> a <a href="#" title="Operators" + > :: <span class="keyword" + >forall</span + > a b. a -> b -> a <a href="#" title="Operators" ><-></a > b</li ></ul @@ -144,7 +146,7 @@ >type</span > a <a href="#" ><><</a - > b :: *</li + > b</li ><li ><span class="keyword" >data</span @@ -154,17 +156,25 @@ ><li ><a href="#" >(>><)</a - >, <a href="#" + > :: a -> b -> ()</li + ><li + ><a href="#" >(<<>)</a > :: a -> b -> ()</li ><li ><a href="#" >(**>)</a - >, <a href="#" + > :: a -> a -> ()</li + ><li + ><a href="#" >(**<)</a - >, <a href="#" + > :: a -> a -> ()</li + ><li + ><a href="#" >(>**)</a - >, <a href="#" + > :: a -> a -> ()</li + ><li + ><a href="#" >(<**)</a > :: a -> a -> ()</li ></ul @@ -328,7 +338,9 @@ ><td class="src" ><a id="v::-60--45--62-" class="def" >(:<->)</a - > :: a -> b -> a <a href="#" title="Operators" + > :: <span class="keyword" + >forall</span + > a b. a -> b -> a <a href="#" title="Operators" ><-></a > b <span class="fixity" >infixr 6</span @@ -404,7 +416,7 @@ >type</span > a <a id="t:-60--62--60-" class="def" ><><</a - > b :: * <span class="fixity" + > b <span class="fixity" >infixl 2</span ><span class="rightedge" ></span diff --git a/html-test/ref/PatternSyns.html b/html-test/ref/PatternSyns.html index 54c2ce005ca0e5601375e2e655274405418ef11a..66b6bfeb7508ffd1fb5e6efc2291133514ba256d 100644 --- a/html-test/ref/PatternSyns.html +++ b/html-test/ref/PatternSyns.html @@ -104,9 +104,7 @@ >data</span > <a href="#" >BlubType</a - > = <span class="keyword" - >forall</span - > x.<a href="#" title="Text.Show" + > = <a href="#" title="Text.Show" >Show</a > x => <a href="#" >BlubCtor</a @@ -124,9 +122,9 @@ ><li class="src short" ><span class="keyword" >data</span - > (a :: *) <a href="#" + > a <a href="#" >><</a - > b = <a href="#" + > (b :: k) = <a href="#" >Empty</a ></li ><li class="src short" @@ -266,9 +264,7 @@ ><table ><tr ><td class="src" - ><span class="keyword" - >forall</span - > x.<a href="#" title="Text.Show" + ><a href="#" title="Text.Show" >Show</a > x => <a id="v:BlubCtor" class="def" >BlubCtor</a @@ -305,17 +301,15 @@ ><p class="src" ><span class="keyword" >data</span - > (a :: *) <a id="t:-62--60-" class="def" + > a <a id="t:-62--60-" class="def" >><</a - > b <a href="#" class="selflink" + > (b :: k) <a href="#" class="selflink" >#</a ></p ><div class="doc" ><p >Doc for (<code - ><a href="#" title="PatternSyns" - >><</a - ></code + >><</code >)</p ></div ><div class="subs constructors" diff --git a/html-test/ref/IgnoreExports.html b/html-test/ref/PrefixStarOperator.html similarity index 58% rename from html-test/ref/IgnoreExports.html rename to html-test/ref/PrefixStarOperator.html index 029565b8fb787f1a9ec7205480e391aa2a442770..e341fb5b65417fdd090555d99878321d6d169ced 100644 --- a/html-test/ref/IgnoreExports.html +++ b/html-test/ref/PrefixStarOperator.html @@ -3,7 +3,7 @@ ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" /><meta name="viewport" content="width=device-width, initial-scale=1" /><title - >IgnoreExports</title + >PrefixStarOperator</title ><link href="#" rel="stylesheet" type="text/css" title="Linuwial" /><link rel="stylesheet" type="text/css" href="#" /><link rel="stylesheet" type="text/css" href="#" @@ -36,37 +36,11 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td - ></tr - ><tr - ><th - >Language</th - ><td - >Haskell2010</td + >None</td ></tr ></table ><p class="caption" - >IgnoreExports</p - ></div - ><div id="synopsis" - ><details id="syn" - ><summary - >Synopsis</summary - ><ul class="details-toggle" data-details-id="syn" - ><li class="src short" - ><span class="keyword" - >data</span - > <a href="#" - >Foo</a - ></li - ><li class="src short" - ><a href="#" - >foo</a - > :: <a href="#" title="Data.Int" - >Int</a - ></li - ></ul - ></details + >PrefixStarOperator</p ></div ><div id="interface" ><h1 @@ -74,30 +48,14 @@ ><div class="top" ><p class="src" ><span class="keyword" - >data</span - > <a id="t:Foo" class="def" - >Foo</a - > <a href="#" class="selflink" - >#</a - ></p - ><div class="doc" - ><p - >documentation for Foo</p - ></div - ></div - ><div class="top" - ><p class="src" - ><a id="v:foo" class="def" - >foo</a - > :: <a href="#" title="Data.Int" - >Int</a - > <a href="#" class="selflink" + >type</span + > <a id="t:-42-" class="def" + >(*)</a + > a = <a href="#" title="Data.Tuple" + >(,)</a + > a <a href="#" class="selflink" >#</a ></p - ><div class="doc" - ><p - >documentation for foo</p - ></div ></div ></div ></div diff --git a/html-test/ref/PrintRuntimeReps.html b/html-test/ref/PrintRuntimeReps.html new file mode 100644 index 0000000000000000000000000000000000000000..b8ba0a39f961adfd037b8cee08079d6ba229ae7a --- /dev/null +++ b/html-test/ref/PrintRuntimeReps.html @@ -0,0 +1,189 @@ +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><meta name="viewport" content="width=device-width, initial-scale=1" + /><title + >PrintRuntimeReps</title + ><link href="#" rel="stylesheet" type="text/css" title="Linuwial" + /><link rel="stylesheet" type="text/css" href="#" + /><link rel="stylesheet" type="text/css" href="#" + /><script src="haddock-bundle.min.js" async="async" type="text/javascript" + ></script + ><script type="text/x-mathjax-config" + >MathJax.Hub.Config({ tex2jax: { processClass: "mathjax", ignoreClass: ".*" } });</script + ><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js?config=TeX-AMS-MML_HTMLorMML" type="text/javascript" + ></script + ></head + ><body + ><div id="package-header" + ><span class="caption empty" + > </span + ><ul class="links" id="page-menu" + ><li + ><a href="#" + >Contents</a + ></li + ><li + ><a href="#" + >Index</a + ></li + ></ul + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >PrintRuntimeReps</p + ></div + ><div id="synopsis" + ><details id="syn" + ><summary + >Synopsis</summary + ><ul class="details-toggle" data-details-id="syn" + ><li class="src short" + ><a href="#" + >($)</a + > :: <span class="keyword" + >forall</span + > (r :: <a href="#" title="GHC.Exts" + >RuntimeRep</a + >) a (b :: <a href="#" title="GHC.Exts" + >TYPE</a + > r). (a -> b) -> a -> b</li + ><li class="src short" + ><a href="#" + >error</a + > :: <span class="keyword" + >forall</span + > (r :: <a href="#" title="GHC.Exts" + >RuntimeRep</a + >) (a :: <a href="#" title="GHC.Exts" + >TYPE</a + > r). <a href="#" title="GHC.Stack" + >HasCallStack</a + > => [<a href="#" title="Data.Char" + >Char</a + >] -> a</li + ></ul + ></details + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a id="v:-36-" class="def" + >($)</a + > :: <span class="keyword" + >forall</span + > (r :: <a href="#" title="GHC.Exts" + >RuntimeRep</a + >) a (b :: <a href="#" title="GHC.Exts" + >TYPE</a + > r). (a -> b) -> a -> b <span class="fixity" + >infixr 0</span + ><span class="rightedge" + ></span + > <a href="#" class="selflink" + >#</a + ></p + ><div class="doc" + ><p + >Application operator. This operator is redundant, since ordinary + application <code + >(f x)</code + > means the same as <code + >(f <code + ><a href="#" title="PrintRuntimeReps" + >$</a + ></code + > x)</code + >. However, <code + ><a href="#" title="PrintRuntimeReps" + >$</a + ></code + > has + low, right-associative binding precedence, so it sometimes allows + parentheses to be omitted; for example:</p + ><pre + >f $ g $ h x = f (g (h x))</pre + ><p + >It is also useful in higher-order situations, such as <code + ><code + ><a href="#" title="GHC.List" + >map</a + ></code + > (<code + ><a href="#" title="PrintRuntimeReps" + >$</a + ></code + > 0) xs</code + >, + or <code + ><code + ><a href="#" title="Data.List" + >zipWith</a + ></code + > (<code + ><a href="#" title="PrintRuntimeReps" + >$</a + ></code + >) fs xs</code + >.</p + ><p + >Note that <code + >(<code + ><a href="#" title="PrintRuntimeReps" + >$</a + ></code + >)</code + > is representation-polymorphic in its result type, so that + <code + >foo <code + ><a href="#" title="PrintRuntimeReps" + >$</a + ></code + > True</code + > where <code + >foo :: Bool -> Int#</code + > is well-typed.</p + ></div + ></div + ><div class="top" + ><p class="src" + ><a id="v:error" class="def" + >error</a + > :: <span class="keyword" + >forall</span + > (r :: <a href="#" title="GHC.Exts" + >RuntimeRep</a + >) (a :: <a href="#" title="GHC.Exts" + >TYPE</a + > r). <a href="#" title="GHC.Stack" + >HasCallStack</a + > => [<a href="#" title="Data.Char" + >Char</a + >] -> a <a href="#" class="selflink" + >#</a + ></p + ><div class="doc" + ><p + ><code + ><a href="#" title="PrintRuntimeReps" + >error</a + ></code + > stops execution and displays an error message.</p + ></div + ></div + ></div + ></div + ></body + ></html +> diff --git a/html-test/ref/PromotedTypes.html b/html-test/ref/PromotedTypes.html index d13a6bd80ff84145e79269b820601f317686744b..ee98ae66c189535bece453aafdb24534b901e26a 100644 --- a/html-test/ref/PromotedTypes.html +++ b/html-test/ref/PromotedTypes.html @@ -91,7 +91,9 @@ >data</span > <a id="t:Pattern" class="def" >Pattern</a - > :: [*] -> * <span class="keyword" + > (a :: [<a href="#" title="Data.Kind" + >Type</a + >]) <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -106,7 +108,9 @@ >Nil</a > :: <a href="#" title="PromotedTypes" >Pattern</a - > '[]</td + > ('[] :: [<a href="#" title="Data.Kind" + >Type</a + >])</td ><td class="doc empty" > </td ></tr @@ -114,13 +118,19 @@ ><td class="src" ><a id="v:Cons" class="def" >Cons</a - > :: <a href="#" title="Data.Maybe" + > :: <span class="keyword" + >forall</span + > h (t :: [<a href="#" title="Data.Kind" + >Type</a + >]). <a href="#" title="Data.Maybe" >Maybe</a > h -> <a href="#" title="PromotedTypes" >Pattern</a > t -> <a href="#" title="PromotedTypes" >Pattern</a - > (h ': t)</td + > (h '<a href="#" title="Data.List" + >:</a + > t)</td ><td class="doc empty" > </td ></tr @@ -133,9 +143,11 @@ >data</span > <a id="t:RevPattern" class="def" >RevPattern</a - > :: <a href="#" title="PromotedTypes" + > (a :: <a href="#" title="PromotedTypes" >RevList</a - > * -> * <span class="keyword" + > <a href="#" title="Data.Kind" + >Type</a + >) <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -150,9 +162,13 @@ >RevNil</a > :: <a href="#" title="PromotedTypes" >RevPattern</a - > <a href="#" title="PromotedTypes" + > ('<a href="#" title="PromotedTypes" >RNil</a - ></td + > :: <a href="#" title="PromotedTypes" + >RevList</a + > <a href="#" title="Data.Kind" + >Type</a + >)</td ><td class="doc empty" > </td ></tr @@ -160,7 +176,13 @@ ><td class="src" ><a id="v:RevCons" class="def" >RevCons</a - > :: <a href="#" title="Data.Maybe" + > :: <span class="keyword" + >forall</span + > h (t :: <a href="#" title="PromotedTypes" + >RevList</a + > <a href="#" title="Data.Kind" + >Type</a + >). <a href="#" title="Data.Maybe" >Maybe</a > h -> <a href="#" title="PromotedTypes" >RevPattern</a @@ -181,7 +203,11 @@ >data</span > <a id="t:Tuple" class="def" >Tuple</a - > :: (*, *) -> * <span class="keyword" + > (a :: (<a href="#" title="Data.Kind" + >Type</a + >, <a href="#" title="Data.Kind" + >Type</a + >)) <span class="keyword" >where</span > <a href="#" class="selflink" >#</a @@ -194,9 +220,11 @@ ><td class="src" ><a id="v:Tuple" class="def" >Tuple</a - > :: a -> b -> <a href="#" title="PromotedTypes" + > :: <span class="keyword" + >forall</span + > a1 b. a1 -> b -> <a href="#" title="PromotedTypes" >Tuple</a - > '(a, b)</td + > '(a1, b)</td ><td class="doc empty" > </td ></tr diff --git a/html-test/ref/QuasiExpr.html b/html-test/ref/QuasiExpr.html index b7660f202e56db9e737240ae3e3aa24c6e4ee787..70820d486d2c74518c3841934f4580abc7373f6e 100644 --- a/html-test/ref/QuasiExpr.html +++ b/html-test/ref/QuasiExpr.html @@ -36,7 +36,7 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td + >None</td ></tr ><tr ><th diff --git a/html-test/ref/QuasiQuote.html b/html-test/ref/QuasiQuote.html index 210c52481b960428a10be74ca582711ed4e26092..155f27d8e894de3b509222a4d85a50a60f040a7a 100644 --- a/html-test/ref/QuasiQuote.html +++ b/html-test/ref/QuasiQuote.html @@ -36,7 +36,7 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td + >None</td ></tr ><tr ><th diff --git a/html-test/ref/SpuriousSuperclassConstraints.html b/html-test/ref/SpuriousSuperclassConstraints.html index cbdc89561a03a9b72f37321c46781ddda50d31b9..8d4fe075393122a698e0bbdb275660be9526fcdd 100644 --- a/html-test/ref/SpuriousSuperclassConstraints.html +++ b/html-test/ref/SpuriousSuperclassConstraints.html @@ -83,7 +83,11 @@ Fix spurious superclass constraints bug.</pre >data</span > <a id="t:SomeType" class="def" >SomeType</a - > (f :: * -> *) a <a href="#" class="selflink" + > (f :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) a <a href="#" class="selflink" >#</a ></p ><div class="subs instances" diff --git a/html-test/ref/TH.html b/html-test/ref/TH.html index 6019257147befccbdd9e714c0ea9c1015a41a0e8..06fcc70facc800fa950bf0f43003327585afdf74 100644 --- a/html-test/ref/TH.html +++ b/html-test/ref/TH.html @@ -36,7 +36,7 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td + >None</td ></tr ><tr ><th diff --git a/html-test/ref/TH2.html b/html-test/ref/TH2.html index 98f2315fdc65b0709c6237ee3d11c715c2889b7b..f9191fb414a78c456058c8bbcd1bff3215b6e66a 100644 --- a/html-test/ref/TH2.html +++ b/html-test/ref/TH2.html @@ -36,7 +36,7 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td + >None</td ></tr ><tr ><th diff --git a/html-test/ref/Test.html b/html-test/ref/Test.html index 10540c93104cc8d4cc280633053c53cf38dfa032..11f4a63e0bd523cd0faae55441dfdc337605671b 100644 --- a/html-test/ref/Test.html +++ b/html-test/ref/Test.html @@ -285,7 +285,11 @@ >newtype</span > <a href="#" >N2</a - > a b = <a href="#" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b = <a href="#" >N2</a > {<ul class="subs" ><li @@ -299,7 +303,11 @@ >newtype</span > <a href="#" >N3</a - > a b = <a href="#" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b = <a href="#" >N3</a > {<ul class="subs" ><li @@ -319,7 +327,11 @@ >newtype</span > <a href="#" >N5</a - > a b = <a href="#" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b = <a href="#" >N5</a > {<ul class="subs" ><li @@ -333,7 +345,11 @@ >newtype</span > <a href="#" >N6</a - > a b = <a href="#" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b = <a href="#" >N6</a > {<ul class="subs" ><li @@ -347,7 +363,11 @@ >newtype</span > <a href="#" >N7</a - > a b = <a href="#" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b = <a href="#" >N7</a > {<ul class="subs" ><li @@ -381,7 +401,11 @@ ><li ><a href="#" >r</a - >, <a href="#" + > :: <a href="#" title="Data.Int" + >Int</a + ></li + ><li + ><a href="#" >s</a > :: <a href="#" title="Data.Int" >Int</a @@ -419,7 +443,11 @@ ><li ><a href="#" >u</a - >, <a href="#" + > :: <a href="#" title="Data.Int" + >Int</a + ></li + ><li + ><a href="#" >v</a > :: <a href="#" title="Data.Int" >Int</a @@ -585,23 +613,17 @@ >Ex</a > a<ul class="subs" ><li - >= <span class="keyword" - >forall</span - > b.<a href="#" title="Test" + >= <a href="#" title="Test" >C</a > b => <a href="#" >Ex1</a > b</li ><li - >| <span class="keyword" - >forall</span - > b. <a href="#" + >| <a href="#" >Ex2</a > b</li ><li - >| <span class="keyword" - >forall</span - > b.<a href="#" title="Test" + >| <a href="#" title="Test" >C</a > a => <a href="#" >Ex3</a @@ -611,7 +633,7 @@ >Ex4</a > (<span class="keyword" >forall</span - > a. a -> a)</li + > a1. a1 -> a1)</li ></ul ></li ><li class="src short" @@ -991,7 +1013,11 @@ >newtype</span > <a id="t:N2" class="def" >N2</a - > a b <a href="#" class="selflink" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -1037,7 +1063,11 @@ >newtype</span > <a id="t:N3" class="def" >N3</a - > a b <a href="#" class="selflink" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -1104,7 +1134,11 @@ >newtype</span > <a id="t:N5" class="def" >N5</a - > a b <a href="#" class="selflink" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b <a href="#" class="selflink" >#</a ></p ><div class="subs constructors" @@ -1148,7 +1182,11 @@ >newtype</span > <a id="t:N6" class="def" >N6</a - > a b <a href="#" class="selflink" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b <a href="#" class="selflink" >#</a ></p ><div class="subs constructors" @@ -1192,7 +1230,11 @@ >newtype</span > <a id="t:N7" class="def" >N7</a - > a b <a href="#" class="selflink" + > (a :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) b <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -1336,7 +1378,25 @@ ><dfn class="src" ><a id="v:r" class="def" >r</a - >, <a id="v:s" class="def" + > :: <a href="#" title="Data.Int" + >Int</a + ></dfn + ><div class="doc" + ><p + >This comment applies to both <code + ><a href="#" title="Test" + >r</a + ></code + > and <code + ><a href="#" title="Test" + >s</a + ></code + ></p + ></div + ></li + ><li + ><dfn class="src" + ><a id="v:s" class="def" >s</a > :: <a href="#" title="Data.Int" >Int</a @@ -1410,7 +1470,15 @@ ><dfn class="src" ><a id="v:u" class="def" >u</a - >, <a id="v:v" class="def" + > :: <a href="#" title="Data.Int" + >Int</a + ></dfn + ><div class="doc empty" + > </div + ></li + ><li + ><dfn class="src" + ><a id="v:v" class="def" >v</a > :: <a href="#" title="Data.Int" >Int</a @@ -2081,9 +2149,7 @@ is at the beginning of the line).</pre ><table ><tr ><td class="src" - ><span class="keyword" - >forall</span - > b.<a href="#" title="Test" + ><a href="#" title="Test" >C</a > b => <a id="v:Ex1" class="def" >Ex1</a @@ -2093,9 +2159,7 @@ is at the beginning of the line).</pre ></tr ><tr ><td class="src" - ><span class="keyword" - >forall</span - > b. <a id="v:Ex2" class="def" + ><a id="v:Ex2" class="def" >Ex2</a > b</td ><td class="doc empty" @@ -2103,9 +2167,7 @@ is at the beginning of the line).</pre ></tr ><tr ><td class="src" - ><span class="keyword" - >forall</span - > b.<a href="#" title="Test" + ><a href="#" title="Test" >C</a > a => <a id="v:Ex3" class="def" >Ex3</a @@ -2119,7 +2181,7 @@ is at the beginning of the line).</pre >Ex4</a > (<span class="keyword" >forall</span - > a. a -> a)</td + > a1. a1 -> a1)</td ><td class="doc empty" > </td ></tr diff --git a/html-test/ref/Threaded.html b/html-test/ref/Threaded.html index 4a980f9434099cf1500a403935d5fe74e8fd8750..f5ac3046aa53d1f9aa8c968127122d83d6d6a227 100644 --- a/html-test/ref/Threaded.html +++ b/html-test/ref/Threaded.html @@ -36,7 +36,7 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td + >None</td ></tr ><tr ><th diff --git a/html-test/ref/Ticket112.html b/html-test/ref/Ticket112.html index 42c9f7fb11967e078bf35879826517e736f6f826..34998258d32c7c8dff2700c777152214f844e914 100644 --- a/html-test/ref/Ticket112.html +++ b/html-test/ref/Ticket112.html @@ -36,7 +36,7 @@ ><th >Safe Haskell</th ><td - >Safe-Inferred</td + >None</td ></tr ><tr ><th diff --git a/html-test/ref/TypeFamilies.html b/html-test/ref/TypeFamilies.html index faf41370571ab4a63e520a737e941b52a2ea69ef..d30e2fbd41bdd4e76218d8ccaa93748ec50dc9f4 100644 --- a/html-test/ref/TypeFamilies.html +++ b/html-test/ref/TypeFamilies.html @@ -108,7 +108,7 @@ >class</span > <a href="#" >Test</a - > a</li + > (a :: k)</li ><li class="src short" ><span class="keyword" >type family</span @@ -120,13 +120,13 @@ >data family</span > <a href="#" >Bat</a - > (a :: k) :: *</li + > (a :: k)</li ><li class="src short" ><span class="keyword" >class</span > <a href="#" >Assoc</a - > a <span class="keyword" + > (a :: k) <span class="keyword" >where</span ><ul class="subs" ><li @@ -134,13 +134,13 @@ >data</span > <a href="#" >AssocD</a - > a :: *</li + > (a :: k)</li ><li ><span class="keyword" >type</span > <a href="#" >AssocT</a - > a :: *</li + > (a :: k)</li ></ul ></li ><li class="src short" @@ -163,6 +163,12 @@ > (a :: k) <a href="#" >><</a > (b :: k)</li + ><li class="src short" + ><span class="keyword" + >data family</span + > <a href="#" + >AssocD</a + > (a :: k)</li ></ul ></details ></div @@ -1135,7 +1141,7 @@ >class</span > <a id="t:Test" class="def" >Test</a - > a <a href="#" class="selflink" + > (a :: k) <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -1327,7 +1333,7 @@ >data family</span > <a id="t:Bat" class="def" >Bat</a - > (a :: k) :: * <a href="#" class="selflink" + > (a :: k) <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -1523,7 +1529,7 @@ >class</span > <a id="t:Assoc" class="def" >Assoc</a - > a <a href="#" class="selflink" + > (a :: k) <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -1538,7 +1544,7 @@ >data</span > <a id="t:AssocD" class="def" >AssocD</a - > a :: * <a href="#" class="selflink" + > (a :: k) <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -1550,7 +1556,7 @@ >type</span > <a id="t:AssocT" class="def" >AssocT</a - > a :: * <a href="#" class="selflink" + > (a :: k) <a href="#" class="selflink" >#</a ></p ><div class="doc" @@ -1921,6 +1927,110 @@ ></details ></div ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data family</span + > <a id="t:AssocD" class="def" + >AssocD</a + > (a :: k) <a href="#" class="selflink" + >#</a + ></p + ><div class="doc" + ><p + >Doc for: data AssocD a</p + ></div + ><div class="subs instances" + ><h4 class="instances details-toggle-control details-toggle" data-details-id="i:AssocD" + >Instances</h4 + ><details id="i:AssocD" open="open" + ><summary class="hide-when-js-enabled" + >Instances details</summary + ><table + ><tr + ><td class="src clearfix" + ><span class="inst-left" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:if:AssocD:AssocD:1" + ></span + > <span class="keyword" + >data</span + > <a href="#" title="TypeFamilies" + >AssocD</a + > <a href="#" title="TypeFamilies" + >X</a + ></span + > <a href="#" class="selflink" + >#</a + ></td + ><td class="doc empty" + > </td + ></tr + ><tr + ><td colspan="2" + ><details id="i:if:AssocD:AssocD:1" + ><summary class="hide-when-js-enabled" + >Instance details</summary + ><p + >Defined in <a href="#" + >TypeFamilies</a + ></p + > <div class="src" + ><span class="keyword" + >data</span + > <a href="#" title="TypeFamilies" + >AssocD</a + > <a href="#" title="TypeFamilies" + >X</a + > = <a id="v:AssocX" class="def" + >AssocX</a + ></div + ></details + ></td + ></tr + ><tr + ><td class="src clearfix" + ><span class="inst-left" + ><span class="instance details-toggle-control details-toggle" data-details-id="i:if:AssocD:AssocD:2" + ></span + > <span class="keyword" + >data</span + > <a href="#" title="TypeFamilies" + >AssocD</a + > <a href="#" title="TypeFamilies" + >Y</a + ></span + > <a href="#" class="selflink" + >#</a + ></td + ><td class="doc empty" + > </td + ></tr + ><tr + ><td colspan="2" + ><details id="i:if:AssocD:AssocD:2" + ><summary class="hide-when-js-enabled" + >Instance details</summary + ><p + >Defined in <a href="#" + >TypeFamilies</a + ></p + > <div class="src" + ><span class="keyword" + >data</span + > <a href="#" title="TypeFamilies" + >AssocD</a + > <a href="#" title="TypeFamilies" + >Y</a + > = <a id="v:AssocY" class="def" + >AssocY</a + ></div + ></details + ></td + ></tr + ></table + ></details + ></div + ></div ></div ></div ></body diff --git a/html-test/ref/TypeFamilies3.html b/html-test/ref/TypeFamilies3.html index 5e2d1ea72ab47917830cdfbc03b2108f276ce73f..81999bd2fc3d079947c4c52c208417cd4f97362c 100644 --- a/html-test/ref/TypeFamilies3.html +++ b/html-test/ref/TypeFamilies3.html @@ -112,7 +112,7 @@ ><td class="src" ><a href="#" title="TypeFamilies3" >Foo</a - > _ = ()</td + > _1 = ()</td ><td class="doc empty" > </td ></tr diff --git a/html-test/ref/TypeOperators.html b/html-test/ref/TypeOperators.html index ff79e6beb6234777deaa7680cb975be4d9585fb6..1d73ca3e7b5ff9e307a881affaff972b1a5973a4 100644 --- a/html-test/ref/TypeOperators.html +++ b/html-test/ref/TypeOperators.html @@ -87,7 +87,15 @@ >newtype</span > <a id="t:O" class="def" >O</a - > g f a <a href="#" class="selflink" + > (g :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) (f :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) a <a href="#" class="selflink" >#</a ></p ><div class="subs constructors" @@ -137,9 +145,19 @@ ><p class="src" ><a id="v:biO" class="def" >biO</a - > :: (g <a href="#" title="TypeOperators" - >`O`</a - > f) a <a href="#" class="selflink" + > :: <span class="keyword" + >forall</span + > (g :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) (f :: <a href="#" title="Data.Kind" + >Type</a + > -> <a href="#" title="Data.Kind" + >Type</a + >) a. <a href="#" title="TypeOperators" + >O</a + > g f a <a href="#" class="selflink" >#</a ></p ></div @@ -147,7 +165,9 @@ ><p class="src" ><a id="v:f" class="def" >f</a - > :: a ~ b => a -> b <a href="#" class="selflink" + > :: a <a href="#" title="GHC.Types" + >~</a + > b => a -> b <a href="#" class="selflink" >#</a ></p ></div @@ -155,7 +175,11 @@ ><p class="src" ><a id="v:g" class="def" >g</a - > :: (a ~ b, b ~ c) => a -> c <a href="#" class="selflink" + > :: (a <a href="#" title="GHC.Types" + >~</a + > b, b <a href="#" title="GHC.Types" + >~</a + > c) => a -> c <a href="#" class="selflink" >#</a ></p ></div @@ -167,9 +191,9 @@ >:-:</a > a) <a href="#" title="TypeOperators" ><=></a - > (a <a href="#" title="TypeOperators" - >`Op`</a - > a) => a <a href="#" class="selflink" + > <a href="#" title="TypeOperators" + >Op</a + > a a => a <a href="#" class="selflink" >#</a ></p ></div @@ -179,9 +203,9 @@ >y</a > :: (a <a href="#" title="TypeOperators" ><=></a - > a, (a <a href="#" title="TypeOperators" - >`Op`</a - > a) <a href="#" title="TypeOperators" + > a, <a href="#" title="TypeOperators" + >Op</a + > a a <a href="#" title="TypeOperators" ><=></a > a) => a <a href="#" class="selflink" >#</a diff --git a/html-test/ref/mini_IgnoreExports.html b/html-test/ref/mini_IgnoreExports.html deleted file mode 100644 index e97867f4284fff1cd8cf3a4cc35447f18264b761..0000000000000000000000000000000000000000 --- a/html-test/ref/mini_IgnoreExports.html +++ /dev/null @@ -1,39 +0,0 @@ -<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> -<html xmlns="http://www.w3.org/1999/xhtml" -><head - ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" - /><title - >IgnoreExports</title - ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" - /><script src="haddock-util.js" type="text/javascript" - ></script - ><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.0/MathJax.js?config=TeX-AMS-MML_HTMLorMML" type="text/javascript" - ></script - ><script type="text/javascript" - >//<![CDATA[ -window.onload = function () {pageLoad();}; -//]]> -</script - ></head - ><body id="mini" - ><div id="module-header" - ><p class="caption" - >IgnoreExports</p - ></div - ><div id="interface" - ><div class="top" - ><p class="src" - ><a href="" target="main" - >foo</a - ></p - ></div - ><div class="top" - ><p class="src" - ><a href="" target="main" - >bar</a - ></p - ></div - ></div - ></body - ></html -> diff --git a/html-test/src/DefaultSignatures.hs b/html-test/src/DefaultSignatures.hs index 1b1b8257011606b8e08b20be84d9f931bf7c7108..99aad22e4f9a23c8a23e005df7d376ed595c1438 100644 --- a/html-test/src/DefaultSignatures.hs +++ b/html-test/src/DefaultSignatures.hs @@ -12,9 +12,10 @@ class Foo a where default bar :: Show a => a -> String bar = show - -- | Documentation for baz'. - baz' :: String -> a - -- | Documentation for the default signature of baz'. default baz' :: Read a => String -> a baz' = read + + -- | Documentation for baz'. + baz' :: String -> a + diff --git a/html-test/src/HideRuntimeReps.hs b/html-test/src/HideRuntimeReps.hs new file mode 100644 index 0000000000000000000000000000000000000000..9fa035f78d94a3a8e8529fce8599c0c1461c15a2 --- /dev/null +++ b/html-test/src/HideRuntimeReps.hs @@ -0,0 +1,2 @@ +module HideRuntimeReps (($), error) where +-- Type variables of kind 'RuntimeRep' are hidden by default. diff --git a/html-test/src/PrefixStarOperator.hs b/html-test/src/PrefixStarOperator.hs new file mode 100644 index 0000000000000000000000000000000000000000..25320991537f1ed2462361a50c94279683ee0e50 --- /dev/null +++ b/html-test/src/PrefixStarOperator.hs @@ -0,0 +1,3 @@ +{-# LANGUAGE TypeOperators, NoStarIsType #-} +module PrefixStarOperator where +type (*) a = (,) a diff --git a/html-test/src/PrintRuntimeReps.hs b/html-test/src/PrintRuntimeReps.hs new file mode 100644 index 0000000000000000000000000000000000000000..6dce82a77baf47a083d227a411899dc260f5df56 --- /dev/null +++ b/html-test/src/PrintRuntimeReps.hs @@ -0,0 +1,2 @@ +{-# OPTIONS_HADDOCK print-explicit-runtime-reps #-} +module PrintRuntimeReps (($), error) where diff --git a/latex-test/ref/DefaultSignatures/DefaultSignatures.tex b/latex-test/ref/DefaultSignatures/DefaultSignatures.tex index 162f5014d1efb0d93a33e7e7d173232fad5dc06d..8f9099e1803e7d8877e6d0d5d58fa9e61a72484c 100644 --- a/latex-test/ref/DefaultSignatures/DefaultSignatures.tex +++ b/latex-test/ref/DefaultSignatures/DefaultSignatures.tex @@ -16,15 +16,17 @@ Documentation for Foo.\par \haddockpremethods{}\emph{Methods} \begin{haddockdesc} \item[\begin{tabular}{@{}l} -bar, baz :: a -> String +bar :: a -> String \end{tabular}] {\haddockbegindoc Documentation for bar and baz.\par} \end{haddockdesc} \begin{haddockdesc} \item[\begin{tabular}{@{}l} -default bar :: Show a => a -> String +baz :: a -> String \end{tabular}] +{\haddockbegindoc +Documentation for bar and baz.\par} \end{haddockdesc} \begin{haddockdesc} \item[\begin{tabular}{@{}l} @@ -32,10 +34,5 @@ baz' :: String -> a \end{tabular}] {\haddockbegindoc Documentation for baz'.\par} -\end{haddockdesc} -\begin{haddockdesc} -\item[\begin{tabular}{@{}l} -default baz' :: Read a => String -> a -\end{tabular}] \end{haddockdesc}} \end{haddockdesc} \ No newline at end of file diff --git a/latex-test/ref/DefaultSignatures/haddock.sty b/latex-test/ref/DefaultSignatures/haddock.sty new file mode 100644 index 0000000000000000000000000000000000000000..6e031a98b61441ec5feec8830c46504e560b78cf --- /dev/null +++ b/latex-test/ref/DefaultSignatures/haddock.sty @@ -0,0 +1,57 @@ +% Default Haddock style definitions. To use your own style, invoke +% Haddock with the option --latex-style=mystyle. + +\usepackage{tabulary} % see below + +% make hyperlinks in the PDF, and add an expandabale index +\usepackage[pdftex,bookmarks=true]{hyperref} + +\newenvironment{haddocktitle} + {\begin{center}\bgroup\large\bfseries} + {\egroup\end{center}} +\newenvironment{haddockprologue}{\vspace{1in}}{} + +\newcommand{\haddockmoduleheading}[1]{\chapter{\texttt{#1}}} + +\newcommand{\haddockbeginheader}{\hrulefill} +\newcommand{\haddockendheader}{\noindent\hrulefill} + +% a little gap before the ``Methods'' header +\newcommand{\haddockpremethods}{\vspace{2ex}} + +% inserted before \\begin{verbatim} +\newcommand{\haddockverb}{\small} + +% an identifier: add an index entry +\newcommand{\haddockid}[1]{\haddocktt{#1}\index{#1@\texttt{#1}}} + +% The tabulary environment lets us have a column that takes up ``the +% rest of the space''. Unfortunately it doesn't allow +% the \end{tabulary} to be in the expansion of a macro, it must appear +% literally in the document text, so Haddock inserts +% the \end{tabulary} itself. +\newcommand{\haddockbeginconstrs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} +\newcommand{\haddockbeginargs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} + +\newcommand{\haddocktt}[1]{{\small \texttt{#1}}} +\newcommand{\haddockdecltt}[1]{{\small\bfseries \texttt{#1}}} + +\makeatletter +\newenvironment{haddockdesc} + {\list{}{\labelwidth\z@ \itemindent-\leftmargin + \let\makelabel\haddocklabel}} + {\endlist} +\newcommand*\haddocklabel[1]{\hspace\labelsep\haddockdecltt{#1}} +\makeatother + +% after a declaration, start a new line for the documentation. +% Otherwise, the documentation starts right after the declaration, +% because we're using the list environment and the declaration is the +% ``label''. I tried making this newline part of the label, but +% couldn't get that to work reliably (the space seemed to stretch +% sometimes). +\newcommand{\haddockbegindoc}{\hfill\\[1ex]} + +% spacing between paragraphs and no \parindent looks better +\parskip=10pt plus2pt minus2pt +\setlength{\parindent}{0cm} diff --git a/latex-test/ref/DefaultSignatures/main.tex b/latex-test/ref/DefaultSignatures/main.tex new file mode 100644 index 0000000000000000000000000000000000000000..d30eb00840cae1afab01e2b3030b9a8fe64ed03d --- /dev/null +++ b/latex-test/ref/DefaultSignatures/main.tex @@ -0,0 +1,11 @@ +\documentclass{book} +\usepackage{haddock} +\begin{document} +\begin{titlepage} +\begin{haddocktitle} + +\end{haddocktitle} +\end{titlepage} +\tableofcontents +\input{DefaultSignatures} +\end{document} \ No newline at end of file diff --git a/latex-test/ref/Deprecated/haddock.sty b/latex-test/ref/Deprecated/haddock.sty new file mode 100644 index 0000000000000000000000000000000000000000..6e031a98b61441ec5feec8830c46504e560b78cf --- /dev/null +++ b/latex-test/ref/Deprecated/haddock.sty @@ -0,0 +1,57 @@ +% Default Haddock style definitions. To use your own style, invoke +% Haddock with the option --latex-style=mystyle. + +\usepackage{tabulary} % see below + +% make hyperlinks in the PDF, and add an expandabale index +\usepackage[pdftex,bookmarks=true]{hyperref} + +\newenvironment{haddocktitle} + {\begin{center}\bgroup\large\bfseries} + {\egroup\end{center}} +\newenvironment{haddockprologue}{\vspace{1in}}{} + +\newcommand{\haddockmoduleheading}[1]{\chapter{\texttt{#1}}} + +\newcommand{\haddockbeginheader}{\hrulefill} +\newcommand{\haddockendheader}{\noindent\hrulefill} + +% a little gap before the ``Methods'' header +\newcommand{\haddockpremethods}{\vspace{2ex}} + +% inserted before \\begin{verbatim} +\newcommand{\haddockverb}{\small} + +% an identifier: add an index entry +\newcommand{\haddockid}[1]{\haddocktt{#1}\index{#1@\texttt{#1}}} + +% The tabulary environment lets us have a column that takes up ``the +% rest of the space''. Unfortunately it doesn't allow +% the \end{tabulary} to be in the expansion of a macro, it must appear +% literally in the document text, so Haddock inserts +% the \end{tabulary} itself. +\newcommand{\haddockbeginconstrs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} +\newcommand{\haddockbeginargs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} + +\newcommand{\haddocktt}[1]{{\small \texttt{#1}}} +\newcommand{\haddockdecltt}[1]{{\small\bfseries \texttt{#1}}} + +\makeatletter +\newenvironment{haddockdesc} + {\list{}{\labelwidth\z@ \itemindent-\leftmargin + \let\makelabel\haddocklabel}} + {\endlist} +\newcommand*\haddocklabel[1]{\hspace\labelsep\haddockdecltt{#1}} +\makeatother + +% after a declaration, start a new line for the documentation. +% Otherwise, the documentation starts right after the declaration, +% because we're using the list environment and the declaration is the +% ``label''. I tried making this newline part of the label, but +% couldn't get that to work reliably (the space seemed to stretch +% sometimes). +\newcommand{\haddockbegindoc}{\hfill\\[1ex]} + +% spacing between paragraphs and no \parindent looks better +\parskip=10pt plus2pt minus2pt +\setlength{\parindent}{0cm} diff --git a/latex-test/ref/Deprecated/main.tex b/latex-test/ref/Deprecated/main.tex new file mode 100644 index 0000000000000000000000000000000000000000..76def1cddf7a606561cc1a05f112d937a44dc53e --- /dev/null +++ b/latex-test/ref/Deprecated/main.tex @@ -0,0 +1,11 @@ +\documentclass{book} +\usepackage{haddock} +\begin{document} +\begin{titlepage} +\begin{haddocktitle} + +\end{haddocktitle} +\end{titlepage} +\tableofcontents +\input{Deprecated} +\end{document} \ No newline at end of file diff --git a/latex-test/ref/Example/haddock.sty b/latex-test/ref/Example/haddock.sty new file mode 100644 index 0000000000000000000000000000000000000000..6e031a98b61441ec5feec8830c46504e560b78cf --- /dev/null +++ b/latex-test/ref/Example/haddock.sty @@ -0,0 +1,57 @@ +% Default Haddock style definitions. To use your own style, invoke +% Haddock with the option --latex-style=mystyle. + +\usepackage{tabulary} % see below + +% make hyperlinks in the PDF, and add an expandabale index +\usepackage[pdftex,bookmarks=true]{hyperref} + +\newenvironment{haddocktitle} + {\begin{center}\bgroup\large\bfseries} + {\egroup\end{center}} +\newenvironment{haddockprologue}{\vspace{1in}}{} + +\newcommand{\haddockmoduleheading}[1]{\chapter{\texttt{#1}}} + +\newcommand{\haddockbeginheader}{\hrulefill} +\newcommand{\haddockendheader}{\noindent\hrulefill} + +% a little gap before the ``Methods'' header +\newcommand{\haddockpremethods}{\vspace{2ex}} + +% inserted before \\begin{verbatim} +\newcommand{\haddockverb}{\small} + +% an identifier: add an index entry +\newcommand{\haddockid}[1]{\haddocktt{#1}\index{#1@\texttt{#1}}} + +% The tabulary environment lets us have a column that takes up ``the +% rest of the space''. Unfortunately it doesn't allow +% the \end{tabulary} to be in the expansion of a macro, it must appear +% literally in the document text, so Haddock inserts +% the \end{tabulary} itself. +\newcommand{\haddockbeginconstrs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} +\newcommand{\haddockbeginargs}{\begin{tabulary}{\linewidth}{@{}llJ@{}}} + +\newcommand{\haddocktt}[1]{{\small \texttt{#1}}} +\newcommand{\haddockdecltt}[1]{{\small\bfseries \texttt{#1}}} + +\makeatletter +\newenvironment{haddockdesc} + {\list{}{\labelwidth\z@ \itemindent-\leftmargin + \let\makelabel\haddocklabel}} + {\endlist} +\newcommand*\haddocklabel[1]{\hspace\labelsep\haddockdecltt{#1}} +\makeatother + +% after a declaration, start a new line for the documentation. +% Otherwise, the documentation starts right after the declaration, +% because we're using the list environment and the declaration is the +% ``label''. I tried making this newline part of the label, but +% couldn't get that to work reliably (the space seemed to stretch +% sometimes). +\newcommand{\haddockbegindoc}{\hfill\\[1ex]} + +% spacing between paragraphs and no \parindent looks better +\parskip=10pt plus2pt minus2pt +\setlength{\parindent}{0cm} diff --git a/latex-test/ref/Example/main.tex b/latex-test/ref/Example/main.tex new file mode 100644 index 0000000000000000000000000000000000000000..66459115f1d1e05fbac958ec2d3917e729317c11 --- /dev/null +++ b/latex-test/ref/Example/main.tex @@ -0,0 +1,11 @@ +\documentclass{book} +\usepackage{haddock} +\begin{document} +\begin{titlepage} +\begin{haddocktitle} + +\end{haddocktitle} +\end{titlepage} +\tableofcontents +\input{Example} +\end{document} \ No newline at end of file diff --git a/latex-test/ref/LinearTypes/LinearTypes.tex b/latex-test/ref/LinearTypes/LinearTypes.tex index cb583ca8378a474117941d3e586c650c0f7ae1b9..c1bcbe228b8255c1ec037f54f417a0b9c57597ab 100644 --- a/latex-test/ref/LinearTypes/LinearTypes.tex +++ b/latex-test/ref/LinearTypes/LinearTypes.tex @@ -23,7 +23,7 @@ Does something linear.\par} \end{haddockdesc} \begin{haddockdesc} \item[\begin{tabular}{@{}l} -poly :: a {\char '45}m -> b +poly :: forall a b m. a {\char '45}m -> b \end{tabular}] {\haddockbegindoc Does something polymorphic.\par} diff --git a/latex-test/ref/TypeFamilies3/TypeFamilies3.tex b/latex-test/ref/TypeFamilies3/TypeFamilies3.tex index 38c143b0e299967ffcc929c4f117aaf338d84e05..6ceb36864af0a1601d7cdc7b1826375b01b09c81 100644 --- a/latex-test/ref/TypeFamilies3/TypeFamilies3.tex +++ b/latex-test/ref/TypeFamilies3/TypeFamilies3.tex @@ -14,7 +14,7 @@ type family Foo a where {\haddockbegindoc \haddockbeginargs \haddockdecltt{Foo () = Int} \\ -\haddockdecltt{Foo {\char '137} = ()} \\ +\haddockdecltt{Foo {\char '137}1 = ()} \\ \end{tabulary}\par A closed type family\par} \end{haddockdesc}