diff options
| -rw-r--r-- | doc/markup.rst | 10 | ||||
| -rw-r--r-- | haddock-api/src/Haddock.hs | 3 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Interface/LexParseRn.hs | 55 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Interface/ParseModuleHeader.hs | 3 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Parser.hs | 13 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Types.hs | 6 | ||||
| -rw-r--r-- | haddock-library/src/Documentation/Haddock/Parser.hs | 22 | ||||
| -rw-r--r-- | haddock-library/src/Documentation/Haddock/Types.hs | 10 | ||||
| -rw-r--r-- | haddock-library/test/Documentation/Haddock/ParserSpec.hs | 6 | ||||
| -rwxr-xr-x | html-test/Main.hs | 2 | ||||
| -rw-r--r-- | html-test/ref/Bug253.html | 16 | ||||
| -rw-r--r-- | html-test/ref/NamespacedIdentifiers.html | 146 | ||||
| -rw-r--r-- | html-test/src/NamespacedIdentifiers.hs | 13 | ||||
| -rw-r--r-- | latex-test/ref/NamespacedIdentifier/NamespacedIdentifiers.tex | 41 | ||||
| -rw-r--r-- | latex-test/ref/NamespacedIdentifier/haddock.sty | 57 | ||||
| -rw-r--r-- | latex-test/ref/NamespacedIdentifier/main.tex | 11 | ||||
| -rw-r--r-- | latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs | 13 | 
17 files changed, 388 insertions, 39 deletions
diff --git a/doc/markup.rst b/doc/markup.rst index 9fb0209a..48a6f4ad 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -913,6 +913,16 @@ If ``M.T`` is not otherwise in scope, then Haddock will simply emit a  link pointing to the entity ``T`` exported from module ``M`` (without  checking to see whether either ``M`` or ``M.T`` exist). +Since values and types live in different namespaces in Haskell, it is +possible for a reference such as ``'X'`` to be ambiguous. In such a case, +Haddock defaults to pointing to the type. The ambiguity can be overcome by explicitly specifying a namespace, by way of a ``v`` (for value) or ``t`` +(for type) immediately before the link: :: + +    -- | An implicit reference to  'X', the type constructor +    --   An explicit reference to v'X', the data constructor +    --   An explicit reference to t'X', the type constructor +    data X = X +  To make life easier for documentation writers, a quoted identifier is  only interpreted as such if the quotes surround a lexically valid  Haskell identifier. This means, for example, that it normally isn't diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 358e5c3a..1378c173 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -42,6 +42,7 @@ import Haddock.Utils  import Haddock.GhcUtils (modifySessionDynFlags, setOutputDir)  import Control.Monad hiding (forM_) +import Data.Bifunctor (second)  import Data.Foldable (forM_, foldl')  import Data.Traversable (for)  import Data.List (isPrefixOf) @@ -662,7 +663,7 @@ getPrologue dflags flags =        h <- openFile filename ReadMode        hSetEncoding h utf8        str <- hGetContents h -- semi-closes the handle -      return . Just $! parseParas dflags Nothing str +      return . Just $! second rdrName $ parseParas dflags Nothing str      _ -> throwE "multiple -p/--prologue options" diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index 59ad4fdf..66083cf5 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -34,8 +34,8 @@ import Haddock.Types  import Name  import Outputable ( showPpr, showSDoc )  import RdrName +import RdrHsSyn (setRdrNameSpace)  import EnumSet -import RnEnv (dataTcOccs)  processDocStrings :: DynFlags -> Maybe Package -> GlobalRdrEnv -> [HsDocString]                    -> ErrMsgM (Maybe (MDoc Name)) @@ -89,24 +89,37 @@ 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 RdrName -> ErrMsgM (Doc Name) +rename :: DynFlags -> GlobalRdrEnv -> Doc NsRdrName -> ErrMsgM (Doc Name)  rename dflags gre = rn    where      rn d = case d of        DocAppend a b -> DocAppend <$> rn a <*> rn b        DocParagraph doc -> DocParagraph <$> rn doc -      DocIdentifier x -> do +      DocIdentifier (NsRdrName ns x) -> do +        let occ = rdrNameOcc x +            isValueName = isDataOcc occ || isVarOcc occ + +        let valueNsChoices | isValueName = [x] +                           | otherwise   = [] -- is this ever possible? +            typeNsChoices  | isValueName = [setRdrNameSpace x tcName] +                           | otherwise   = [x] +          -- Generate the choices for the possible kind of thing this -        -- is. -        let choices = dataTcOccs x +        -- is. We narrow down the possibilities with the namespace (if +        -- there is one). +        let choices = case ns of +                        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 -              -- This shouldn't happen as 'dataTcOccs' always returns at least its input. -              [] -> pure (DocMonospaced (DocString (showPpr dflags x))) +              -- The only way this can happen is if a value namespace was +              -- specified on something that cannot be a value. +              [] -> invalidValue dflags x                -- There was nothing in the environment so we need to                -- pick some default from what's available to us. We @@ -116,7 +129,7 @@ rename dflags gre = rn                -- type constructor names (such as in #253). So now we                -- only get type constructor links if they are actually                -- in scope. -              a:_ -> outOfScope dflags a +              a:_ -> outOfScope dflags ns a            -- There is only one name in the environment that matches so            -- use it. @@ -155,17 +168,23 @@ rename dflags gre = rn  -- users shouldn't rely on this doing the right thing. See tickets  -- #253 and #375 on the confusion this causes depending on which  -- default we pick in 'rename'. -outOfScope :: DynFlags -> RdrName -> ErrMsgM (Doc a) -outOfScope dflags x = +outOfScope :: DynFlags -> Namespace -> RdrName -> ErrMsgM (Doc a) +outOfScope dflags ns x =    case x of      Unqual occ -> warnAndMonospace occ      Qual mdl occ -> pure (DocIdentifierUnchecked (mdl, occ))      Orig _ occ -> warnAndMonospace occ      Exact name -> warnAndMonospace name  -- Shouldn't happen since x is out of scope    where +    prefix = case ns of +               Value -> "the value " +               Type -> "the type " +               None -> "" +      warnAndMonospace a = do -      tell ["Warning: '" ++ showPpr dflags a ++ "' is out of scope.\n" ++ -            "    If you qualify the identifier, haddock can try to link it anyway."] +      tell ["Warning: " ++ prefix ++ "'" ++ showPpr dflags a ++ "' is out of scope.\n" ++ +            "    If you qualify the identifier, haddock can try to link it\n" ++ +            "    it anyway."]        pure (monospaced a)      monospaced a = DocMonospaced (DocString (showPpr dflags a)) @@ -184,7 +203,7 @@ ambiguous dflags x gres = do        msg = "Warning: " ++ x_str ++ " is ambiguous. It is defined\n" ++              concatMap (\n -> "    * " ++ defnLoc n ++ "\n") (map gre_name gres) ++              "    You may be able to disambiguate the identifier by qualifying it or\n" ++ -            "    by hiding some imports.\n" ++ +            "    by specifying the type/value namespace explicitly.\n" ++              "    Defaulting to " ++ x_str ++ " 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 @@ -198,3 +217,13 @@ ambiguous dflags x gres = do      isLocalName _ = False      x_str = '\'' : showPpr dflags x ++ "'"      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 -> RdrName -> ErrMsgM (Doc a) +invalidValue dflags x = do +  tell ["Warning: '" ++ showPpr 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 (showPpr dflags x))) diff --git a/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs b/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs index 050901b6..802ea773 100644 --- a/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs +++ b/haddock-api/src/Haddock/Interface/ParseModuleHeader.hs @@ -16,7 +16,6 @@ import Data.Char  import DynFlags  import Haddock.Parser  import Haddock.Types -import RdrName  -- -----------------------------------------------------------------------------  -- Parsing module headers @@ -24,7 +23,7 @@ import RdrName  -- NB.  The headers must be given in the order Module, Description,  -- Copyright, License, Maintainer, Stability, Portability, except that  -- any or all may be omitted. -parseModuleHeader :: DynFlags -> Maybe Package -> String -> (HaddockModInfo RdrName, MDoc RdrName) +parseModuleHeader :: DynFlags -> Maybe Package -> String -> (HaddockModInfo NsRdrName, MDoc NsRdrName)  parseModuleHeader dflags pkgName str0 =     let        getKey :: String -> String -> (Maybe String,String) diff --git a/haddock-api/src/Haddock/Parser.hs b/haddock-api/src/Haddock/Parser.hs index e31ea6a8..8b7dda7c 100644 --- a/haddock-api/src/Haddock/Parser.hs +++ b/haddock-api/src/Haddock/Parser.hs @@ -15,26 +15,27 @@ module Haddock.Parser ( parseParas  import qualified Documentation.Haddock.Parser as P  import Documentation.Haddock.Types +import Haddock.Types (NsRdrName(..))  import DynFlags     ( DynFlags )  import FastString   ( fsLit )  import Lexer        ( mkPState, unP, ParseResult(POk) )  import Parser       ( parseIdentifier )  import RdrName      ( RdrName ) -import SrcLoc       ( mkRealSrcLoc, unLoc ) +import SrcLoc       ( mkRealSrcLoc, GenLocated(..) )  import StringBuffer ( stringToStringBuffer ) -parseParas :: DynFlags -> Maybe Package -> String -> MetaDoc mod RdrName +parseParas :: DynFlags -> Maybe Package -> String -> MetaDoc mod NsRdrName  parseParas d p = overDoc (P.overIdentifier (parseIdent d)) . P.parseParas p -parseString :: DynFlags -> String -> DocH mod RdrName +parseString :: DynFlags -> String -> DocH mod NsRdrName  parseString d = P.overIdentifier (parseIdent d) . P.parseString -parseIdent :: DynFlags -> String -> Maybe RdrName -parseIdent dflags str0 = +parseIdent :: DynFlags -> Namespace -> String -> Maybe NsRdrName +parseIdent dflags ns str0 =    let buffer = stringToStringBuffer str0        realSrcLc = mkRealSrcLoc (fsLit "<unknown file>") 0 0        pstate = mkPState dflags buffer realSrcLc    in case unP parseIdentifier pstate of -    POk _ name -> Just (unLoc name) +    POk _ (L _ name) -> Just (NsRdrName ns name)      _ -> Nothing diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index a4ef5f82..e8da4120 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -284,6 +284,12 @@ noDocForDecl = (Documentation Nothing Nothing, mempty)  -- | Type of environment used to cross-reference identifiers in the syntax.  type LinkEnv = Map Name Module +-- | An 'RdrName' tagged with some type/value namespace information. +data NsRdrName = NsRdrName +  { namespace :: !Namespace +  , rdrName :: !RdrName +  } +  -- | Extends 'Name' with cross-reference information.  data DocName    = Documented Name Module diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs index 82d65a0a..e9b1c496 100644 --- a/haddock-library/src/Documentation/Haddock/Parser.hs +++ b/haddock-library/src/Documentation/Haddock/Parser.hs @@ -28,6 +28,7 @@ import           Control.Applicative  import           Control.Arrow (first)  import           Control.Monad  import           Data.Char (chr, isUpper, isAlpha, isAlphaNum, isSpace) +import           Data.Foldable (asum)  import           Data.List (intercalate, unfoldr, elemIndex)  import           Data.Maybe (fromMaybe, mapMaybe)  import           Data.Monoid @@ -75,24 +76,24 @@ isSymbolChar c = not (isPuncChar c) && case generalCategory c of  #endif  -- | Identifier string surrounded with opening and closing quotes/backticks. -type Identifier = (Char, String, Char) +data Identifier = Identifier !Namespace !Char String !Char  -- | Drops the quotes/backticks around all identifiers, as if they  -- were valid but still 'String's.  toRegular :: DocH mod Identifier -> DocH mod String -toRegular = fmap (\(_, x, _) -> x) +toRegular = fmap (\(Identifier _ _ x _) -> x)  -- | Maps over 'DocIdentifier's over 'String' with potentially failing  -- conversion using user-supplied function. If the conversion fails,  -- the identifier is deemed to not be valid and is treated as a  -- regular string. -overIdentifier :: (String -> Maybe a) +overIdentifier :: (Namespace -> String -> Maybe a)                 -> DocH mod Identifier                 -> DocH mod a  overIdentifier f d = g d    where -    g (DocIdentifier (o, x, e)) = case f x of -      Nothing -> DocString $ o : x ++ [e] +    g (DocIdentifier (Identifier ns o x e)) = case f ns x of +      Nothing -> DocString $ renderNs ns ++ [o] ++ x ++ [e]        Just x' -> DocIdentifier x'      g DocEmpty = DocEmpty      g (DocAppend x x') = DocAppend (g x) (g x') @@ -314,7 +315,8 @@ markdownImage :: Parser (DocH mod Identifier)  markdownImage = DocPic . fromHyperlink <$> ("!" *> linkParser)    where      fromHyperlink (Hyperlink u l) = Picture u (fmap (markup stringMarkup) l) -    stringMarkup = plainMarkup (const "") (\(l,c,r) -> [l] <> c <> [r]) +    stringMarkup = plainMarkup (const "") renderIdent +    renderIdent (Identifier ns l c r) = renderNs ns <> [l] <> c <> [r]  -- | Paragraph parser, called by 'parseParas'.  paragraph :: Parser (DocH mod Identifier) @@ -857,9 +859,13 @@ parseValid = p some  -- 'String' from the string it deems valid.  identifier :: Parser (DocH mod Identifier)  identifier = do +  ns <- asum [ Value <$ Parsec.char 'v' +             , Type <$ Parsec.char 't' +             , pure None +             ]    o <- idDelim    vid <- parseValid    e <- idDelim -  return $ DocIdentifier (o, vid, e) +  return $ DocIdentifier (Identifier ns o vid e)    where -    idDelim = Parsec.satisfy (\c -> c == '\'' || c == '`') +    idDelim = Parsec.oneOf "'`" diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs index f8f7d353..ba2f873c 100644 --- a/haddock-library/src/Documentation/Haddock/Types.hs +++ b/haddock-library/src/Documentation/Haddock/Types.hs @@ -203,6 +203,16 @@ instance Bitraversable DocH where    bitraverse f g (DocTable (Table header body)) = (\h b -> DocTable (Table h b)) <$> traverse (traverse (bitraverse f g)) header <*> traverse (traverse (bitraverse f g)) body  #endif +-- | The namespace qualification for an identifier. +data Namespace = Value | Type | None deriving (Eq, Ord, Enum, Show) + +-- | Render the a namespace into the same format it was initially parsed. +renderNs :: Namespace -> String +renderNs Value = "v" +renderNs Type = "t" +renderNs None = "" + +  -- | 'DocMarkupH' is a set of instructions for marking up documentation.  -- In fact, it's really just a mapping from 'Doc' to some other  -- type [a], where [a] is usually the type of the output (HTML, say). diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs index 6269184a..e186a5cf 100644 --- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs +++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs @@ -132,6 +132,12 @@ spec = do        it "can parse an identifier that starts with an underscore" $ do          "'_x'" `shouldParseTo` DocIdentifier "_x" +      it "can parse value-namespaced identifiers" $ do +        "v'foo'" `shouldParseTo` DocIdentifier "foo" + +      it "can parse type-namespaced identifiers" $ do +        "t'foo'" `shouldParseTo` DocIdentifier "foo" +      context "when parsing operators" $ do        it "can parse an operator enclosed within single quotes" $ do          "'.='" `shouldParseTo` DocIdentifier ".=" diff --git a/html-test/Main.hs b/html-test/Main.hs index d65a5087..26eefe4a 100755 --- a/html-test/Main.hs +++ b/html-test/Main.hs @@ -45,7 +45,7 @@ stripIfRequired mdl =  -- | List of modules in which we don't 'stripLinks'  preserveLinksModules :: [String] -preserveLinksModules = ["Bug253"] +preserveLinksModules = ["Bug253.html", "NamespacedIdentifiers.html"]  ingoredTests :: [FilePath]  ingoredTests = diff --git a/html-test/ref/Bug253.html b/html-test/ref/Bug253.html index a1c0f905..a01c9578 100644 --- a/html-test/ref/Bug253.html +++ b/html-test/ref/Bug253.html @@ -4,9 +4,9 @@       /><meta name="viewport" content="width=device-width, initial-scale=1"       /><title      >Bug253</title -    ><link href="#" rel="stylesheet" type="text/css" title="NewOcean" -     /><link rel="stylesheet" type="text/css" href="#" -     /><link rel="stylesheet" type="text/css" href="#" +    ><link href="new-ocean.css" rel="stylesheet" type="text/css" title="NewOcean" +     /><link rel="stylesheet" type="text/css" href="quick-jump.css" +     /><link rel="stylesheet" type="text/css" href="https://fonts.googleapis.com/css?family=PT+Sans:400,400i,700"       /><script src="haddock-bundle.min.js" async="async" type="text/javascript"      ></script      ><script type="text/x-mathjax-config" @@ -20,11 +20,11 @@        ></span        ><ul class="links" id="page-menu"        ><li -	><a href="#" +	><a href="index.html"  	  >Contents</a  	  ></li  	><li -	><a href="#" +	><a href="doc-index.html"  	  >Index</a  	  ></li  	></ul @@ -64,7 +64,7 @@  	  >Synopsis</summary  	  ><ul class="details-toggle" data-details-id="syn"  	  ><li class="src short" -	    ><a href="#" +	    ><a href="#v:foo"  	      >foo</a  	      > :: ()</li  	    ></ul @@ -77,7 +77,7 @@  	><p class="src"  	  ><a id="v:foo" class="def"  	    >foo</a -	    > :: () <a href="#" class="selflink" +	    > :: () <a href="#v:foo" class="selflink"  	    >#</a  	    ></p  	  ><div class="doc" @@ -85,7 +85,7 @@  	    >This link should generate <code  	      >#v</code  	      > anchor: <code -	      ><a href="#" title="DoesNotExist" +	      ><a href="DoesNotExist.html#v:fakeFakeFake" title="DoesNotExist"  		>fakeFakeFake</a  		></code  	      ></p diff --git a/html-test/ref/NamespacedIdentifiers.html b/html-test/ref/NamespacedIdentifiers.html new file mode 100644 index 00000000..73beaa7e --- /dev/null +++ b/html-test/ref/NamespacedIdentifiers.html @@ -0,0 +1,146 @@ +<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 +    >NamespacedIdentifiers</title +    ><link href="new-ocean.css" rel="stylesheet" type="text/css" title="NewOcean" +     /><link rel="stylesheet" type="text/css" href="quick-jump.css" +     /><link rel="stylesheet" type="text/css" href="https://fonts.googleapis.com/css?family=PT+Sans:400,400i,700" +     /><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="index.html" +	  >Contents</a +	  ></li +	><li +	><a href="doc-index.html" +	  >Index</a +	  ></li +	></ul +      ></div +    ><div id="content" +    ><div id="module-header" +      ><table class="info" +	><tr +	  ><th +	    >Safe Haskell</th +	    ><td +	    >Safe</td +	    ></tr +	  ></table +	><p class="caption" +	>NamespacedIdentifiers</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="#t:Foo" +	      >Foo</a +	      > = <a href="#v:Bar" +	      >Bar</a +	      ></li +	    ><li class="src short" +	    ><span class="keyword" +	      >data</span +	      > <a href="#t:Bar" +	      >Bar</a +	      ></li +	    ></ul +	  ></details +	></div +      ><div id="interface" +      ><h1 +	>Documentation</h1 +	><div class="top" +	><p class="src" +	  ><span class="keyword" +	    >data</span +	    > <a id="t:Foo" class="def" +	    >Foo</a +	    > <a href="#t:Foo" class="selflink" +	    >#</a +	    ></p +	  ><div class="doc" +	  ><p +	    >A link to:</p +	    ><ul +	    ><li +	      >the type <code +		><a href="NamespacedIdentifiers.html#t:Bar" title="NamespacedIdentifiers" +		  >Bar</a +		  ></code +		></li +	      ><li +	      >the constructor <code +		><a href="NamespacedIdentifiers.html#v:Bar" title="NamespacedIdentifiers" +		  >Bar</a +		  ></code +		></li +	      ><li +	      >the unimported but qualified type <code +		><a href="A.html#t:A" title="A" +		  >A</a +		  ></code +		></li +	      ><li +	      >the unimported but qualified value <code +		><a href="A.html#v:A" title="A" +		  >A</a +		  ></code +		></li +	      ></ul +	    ></div +	  ><div class="subs constructors" +	  ><p class="caption" +	    >Constructors</p +	    ><table +	    ><tr +	      ><td class="src" +		><a id="v:Bar" class="def" +		  >Bar</a +		  ></td +		><td class="doc empty" +		> </td +		></tr +	      ></table +	    ></div +	  ></div +	><div class="top" +	><p class="src" +	  ><span class="keyword" +	    >data</span +	    > <a id="t:Bar" class="def" +	    >Bar</a +	    > <a href="#t:Bar" class="selflink" +	    >#</a +	    ></p +	  ><div class="doc" +	  ><p +	    >A link to the value <code +	      >Foo</code +	      > (which shouldn't exist).</p +	    ></div +	  ></div +	></div +      ></div +    ><div id="footer" +    ></div +    ></body +  ></html +> diff --git a/html-test/src/NamespacedIdentifiers.hs b/html-test/src/NamespacedIdentifiers.hs new file mode 100644 index 00000000..6f59d247 --- /dev/null +++ b/html-test/src/NamespacedIdentifiers.hs @@ -0,0 +1,13 @@ +module NamespacedIdentifiers where + +-- | A link to: +-- +--   * the type t'Bar' +--   * the constructor v'Bar' +--   * the unimported but qualified type t'A.A' +--   * the unimported but qualified value v'A.A' +-- +data Foo = Bar + +-- | A link to the value v'Foo' (which shouldn't exist). +data Bar diff --git a/latex-test/ref/NamespacedIdentifier/NamespacedIdentifiers.tex b/latex-test/ref/NamespacedIdentifier/NamespacedIdentifiers.tex new file mode 100644 index 00000000..f39bd0ec --- /dev/null +++ b/latex-test/ref/NamespacedIdentifier/NamespacedIdentifiers.tex @@ -0,0 +1,41 @@ +\haddockmoduleheading{NamespacedIdentifiers} +\label{module:NamespacedIdentifiers} +\haddockbeginheader +{\haddockverb\begin{verbatim} +module NamespacedIdentifiers ( +    Foo(Bar),  Bar +  ) where\end{verbatim}} +\haddockendheader + +\begin{haddockdesc} +\item[\begin{tabular}{@{}l} +data\ Foo +\end{tabular}]\haddockbegindoc +A link to:\par +\begin{itemize} +\item +the type \haddockid{Bar}\par + +\item +the constructor \haddockid{Bar}\par + +\item +the unimported but qualified type \haddockid{A}\par + +\item +the unimported but qualified value \haddockid{A}\par + +\end{itemize} + +\enspace \emph{Constructors}\par +\haddockbeginconstrs +\haddockdecltt{=} & \haddockdecltt{Bar} & \\ +\end{tabulary}\par +\end{haddockdesc} +\begin{haddockdesc} +\item[\begin{tabular}{@{}l} +data\ Bar +\end{tabular}]\haddockbegindoc +A link to the value \haddocktt{Foo} (which shouldn't exist).\par + +\end{haddockdesc}
\ No newline at end of file diff --git a/latex-test/ref/NamespacedIdentifier/haddock.sty b/latex-test/ref/NamespacedIdentifier/haddock.sty new file mode 100644 index 00000000..6e031a98 --- /dev/null +++ b/latex-test/ref/NamespacedIdentifier/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/NamespacedIdentifier/main.tex b/latex-test/ref/NamespacedIdentifier/main.tex new file mode 100644 index 00000000..75493e12 --- /dev/null +++ b/latex-test/ref/NamespacedIdentifier/main.tex @@ -0,0 +1,11 @@ +\documentclass{book} +\usepackage{haddock} +\begin{document} +\begin{titlepage} +\begin{haddocktitle} + +\end{haddocktitle} +\end{titlepage} +\tableofcontents +\input{NamespacedIdentifiers} +\end{document}
\ No newline at end of file diff --git a/latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs b/latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs new file mode 100644 index 00000000..6f59d247 --- /dev/null +++ b/latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs @@ -0,0 +1,13 @@ +module NamespacedIdentifiers where + +-- | A link to: +-- +--   * the type t'Bar' +--   * the constructor v'Bar' +--   * the unimported but qualified type t'A.A' +--   * the unimported but qualified value v'A.A' +-- +data Foo = Bar + +-- | A link to the value v'Foo' (which shouldn't exist). +data Bar  | 
