diff options
| author | Hécate Moonlight <Kleidukos@users.noreply.github.com> | 2021-02-07 18:43:19 +0100 | 
|---|---|---|
| committer | GitHub <noreply@github.com> | 2021-02-07 18:43:19 +0100 | 
| commit | a30ebe591c862bcaac321ce9a5c03fa2ce56729e (patch) | |
| tree | 883ee3f8c0e195299925b790cba6f88a537200f6 /haddock-library | |
| parent | 0f7ff041fb824653a7930e1292b81f34df1e967d (diff) | |
| parent | 786d3e69799398c3aac26fbd5017a127bc69cacc (diff) | |
Merge pull request #1321 from Kleidukos/ghc-9.0
Merge ghc-9.0 into ghc-head
Diffstat (limited to 'haddock-library')
| -rw-r--r-- | haddock-library/fixtures/Fixtures.hs | 3 | ||||
| -rw-r--r-- | haddock-library/src/Documentation/Haddock/Markup.hs | 4 | ||||
| -rw-r--r-- | haddock-library/src/Documentation/Haddock/Parser.hs | 50 | ||||
| -rw-r--r-- | haddock-library/src/Documentation/Haddock/Types.hs | 14 | ||||
| -rw-r--r-- | haddock-library/test/Documentation/Haddock/ParserSpec.hs | 84 | 
5 files changed, 127 insertions, 28 deletions
| diff --git a/haddock-library/fixtures/Fixtures.hs b/haddock-library/fixtures/Fixtures.hs index 72ea8525..101bce65 100644 --- a/haddock-library/fixtures/Fixtures.hs +++ b/haddock-library/fixtures/Fixtures.hs @@ -149,6 +149,9 @@ instance ToExpr id => ToExpr (Header id)  deriving instance Generic (Hyperlink id)  instance ToExpr id => ToExpr (Hyperlink id) +deriving instance Generic (ModLink id) +instance ToExpr id => ToExpr (ModLink id) +  deriving instance Generic Picture  instance ToExpr Picture diff --git a/haddock-library/src/Documentation/Haddock/Markup.hs b/haddock-library/src/Documentation/Haddock/Markup.hs index 365041ee..0919737f 100644 --- a/haddock-library/src/Documentation/Haddock/Markup.hs +++ b/haddock-library/src/Documentation/Haddock/Markup.hs @@ -16,7 +16,7 @@ markup m (DocString s)                  = markupString m s  markup m (DocParagraph d)               = markupParagraph m (markup m d)  markup m (DocIdentifier x)              = markupIdentifier m x  markup m (DocIdentifierUnchecked x)     = markupIdentifierUnchecked m x -markup m (DocModule mod0)               = markupModule m mod0 +markup m (DocModule (ModLink mo l))     = markupModule m (ModLink mo (fmap (markup m) l))  markup m (DocWarning d)                 = markupWarning m (markup m d)  markup m (DocEmphasis d)                = markupEmphasis m (markup m d)  markup m (DocBold d)                    = markupBold m (markup m d) @@ -78,7 +78,7 @@ plainMarkup plainMod plainIdent = Markup {    markupAppend               = (++),    markupIdentifier           = plainIdent,    markupIdentifierUnchecked  = plainMod, -  markupModule               = id, +  markupModule               = \(ModLink m lbl) -> fromMaybe m lbl,    markupWarning              = id,    markupEmphasis             = id,    markupBold                 = id, diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs index a3bba38a..de336d45 100644 --- a/haddock-library/src/Documentation/Haddock/Parser.hs +++ b/haddock-library/src/Documentation/Haddock/Parser.hs @@ -72,7 +72,7 @@ overIdentifier f d = g d      g (DocString x) = DocString x      g (DocParagraph x) = DocParagraph $ g x      g (DocIdentifierUnchecked x) = DocIdentifierUnchecked x -    g (DocModule x) = DocModule x +    g (DocModule (ModLink m x)) = DocModule (ModLink m (fmap g x))      g (DocWarning x) = DocWarning $ g x      g (DocEmphasis x) = DocEmphasis $ g x      g (DocMonospaced x) = DocMonospaced $ g x @@ -148,6 +148,7 @@ parseParagraph = snd . parse p                                      , mathDisplay                                      , mathInline                                      , markdownImage +                                    , markdownLink                                      , hyperlink                                      , bold                                      , emphasis @@ -242,7 +243,12 @@ monospace = DocMonospaced . parseParagraph  -- Note that we allow '#' and '\' to support anchors (old style anchors are of  -- the form "SomeModule\#anchor").  moduleName :: Parser (DocH mod a) -moduleName = DocModule <$> ("\"" *> (modid `maybeFollowedBy` anchor_) <* "\"") +moduleName = DocModule . flip ModLink Nothing <$> ("\"" *> moduleNameString <* "\"") + +-- | A module name, optionally with an anchor +-- +moduleNameString :: Parser String +moduleNameString = modid `maybeFollowedBy` anchor_    where      modid = intercalate "." <$> conid `Parsec.sepBy1` "."      anchor_ = (++) @@ -250,13 +256,30 @@ moduleName = DocModule <$> ("\"" *> (modid `maybeFollowedBy` anchor_) <* "\"")        <*> many (Parsec.satisfy (\c -> c /= '"' && not (isSpace c)))      maybeFollowedBy pre suf = (\x -> maybe x (x ++)) <$> pre <*> optional suf - +    conid :: Parser String      conid = (:)        <$> Parsec.satisfy (\c -> isAlpha c && isUpper c)        <*> many conChar      conChar = Parsec.alphaNum <|> Parsec.char '_' +-- | A labeled link to an indentifier, module or url using markdown +-- syntax. +markdownLink :: Parser (DocH mod Identifier) +markdownLink = do +  lbl <- markdownLinkText +  choice' [ markdownModuleName lbl, markdownURL lbl ] +  where +    markdownModuleName lbl = do +      mn <- "(" *> skipHorizontalSpace *> +            "\"" *> moduleNameString <* "\"" +            <* skipHorizontalSpace <* ")" +      pure $ DocModule (ModLink mn (Just lbl)) + +    markdownURL lbl = do +      target <- markdownLinkTarget +      pure $ DocHyperlink $ Hyperlink target (Just lbl) +  -- | Picture parser, surrounded by \<\< and \>\>. It's possible to specify  -- a title for the picture.  -- @@ -290,9 +313,11 @@ mathDisplay = DocMathDisplay . T.unpack  -- >>> parseString ""  -- DocPic (Picture "www.site.com" (Just "some emphasis in a description"))  markdownImage :: Parser (DocH mod Identifier) -markdownImage = DocPic . fromHyperlink <$> ("!" *> linkParser) +markdownImage = do +  text <- markup stringMarkup <$> ("!" *> markdownLinkText) +  url <- markdownLinkTarget +  pure $ DocPic (Picture url (Just text))    where -    fromHyperlink (Hyperlink u l) = Picture u (fmap (markup stringMarkup) l)      stringMarkup = plainMarkup (const "") renderIdent      renderIdent (Identifier ns l c r) = renderNs ns <> [l] <> c <> [r] @@ -772,22 +797,21 @@ codeblock =            | otherwise = Just $ c == '\n'  hyperlink :: Parser (DocH mod Identifier) -hyperlink = choice' [ angleBracketLink, markdownLink, autoUrl ] +hyperlink = choice' [ angleBracketLink, autoUrl ]  angleBracketLink :: Parser (DocH mod a)  angleBracketLink =      DocHyperlink . makeLabeled (\s -> Hyperlink s . fmap DocString)      <$> disallowNewline ("<" *> takeUntil ">") -markdownLink :: Parser (DocH mod Identifier) -markdownLink = DocHyperlink <$> linkParser +-- | The text for a markdown link, enclosed in square brackets. +markdownLinkText :: Parser (DocH mod Identifier) +markdownLinkText = parseParagraph . T.strip <$> ("[" *> takeUntil "]") -linkParser :: Parser (Hyperlink (DocH mod Identifier)) -linkParser = flip Hyperlink <$> label <*> (whitespace *> url) +-- | The target for a markdown link, enclosed in parenthesis. +markdownLinkTarget :: Parser String +markdownLinkTarget = whitespace *> url    where -    label :: Parser (Maybe (DocH mod Identifier)) -    label = Just . parseParagraph . T.strip <$> ("[" *> takeUntil "]") -      whitespace :: Parser ()      whitespace = skipHorizontalSpace <* optional ("\n" *> skipHorizontalSpace) diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs index 12ccd28d..252eb425 100644 --- a/haddock-library/src/Documentation/Haddock/Types.hs +++ b/haddock-library/src/Documentation/Haddock/Types.hs @@ -73,6 +73,11 @@ data Hyperlink id = Hyperlink    , hyperlinkLabel :: Maybe id    } deriving (Eq, Show, Functor, Foldable, Traversable) +data ModLink id = ModLink +  { modLinkName   :: String +  , modLinkLabel :: Maybe id +  } deriving (Eq, Show, Functor, Foldable, Traversable) +  data Picture = Picture    { pictureUri   :: String    , pictureTitle :: Maybe String @@ -111,7 +116,8 @@ data DocH mod id    | DocIdentifier id    | DocIdentifierUnchecked mod    -- ^ A qualified identifier that couldn't be resolved. -  | DocModule String +  | DocModule (ModLink (DocH mod id)) +  -- ^ A link to a module, with an optional label.    | DocWarning (DocH mod id)    -- ^ This constructor has no counterpart in Haddock markup.    | DocEmphasis (DocH mod id) @@ -142,7 +148,7 @@ instance Bifunctor DocH where    bimap f g (DocParagraph doc) = DocParagraph (bimap f g doc)    bimap _ g (DocIdentifier i) = DocIdentifier (g i)    bimap f _ (DocIdentifierUnchecked m) = DocIdentifierUnchecked (f m) -  bimap _ _ (DocModule s) = DocModule s +  bimap f g (DocModule (ModLink m lbl)) = DocModule (ModLink m (fmap (bimap f g) lbl))    bimap f g (DocWarning doc) = DocWarning (bimap f g doc)    bimap f g (DocEmphasis doc) = DocEmphasis (bimap f g doc)    bimap f g (DocMonospaced doc) = DocMonospaced (bimap f g doc) @@ -189,7 +195,7 @@ instance Bitraversable DocH where    bitraverse f g (DocParagraph doc) = DocParagraph <$> bitraverse f g doc    bitraverse _ g (DocIdentifier i) = DocIdentifier <$> g i    bitraverse f _ (DocIdentifierUnchecked m) = DocIdentifierUnchecked <$> f m -  bitraverse _ _ (DocModule s) = pure (DocModule s) +  bitraverse f g (DocModule (ModLink m lbl)) = DocModule <$> (ModLink m <$> traverse (bitraverse f g) lbl)    bitraverse f g (DocWarning doc) = DocWarning <$> bitraverse f g doc    bitraverse f g (DocEmphasis doc) = DocEmphasis <$> bitraverse f g doc    bitraverse f g (DocMonospaced doc) = DocMonospaced <$> bitraverse f g doc @@ -234,7 +240,7 @@ data DocMarkupH mod id a = Markup    , markupAppend               :: a -> a -> a    , markupIdentifier           :: id -> a    , markupIdentifierUnchecked  :: mod -> a -  , markupModule               :: String -> a +  , markupModule               :: ModLink a -> a    , markupWarning              :: a -> a    , markupEmphasis             :: a -> a    , markupBold                 :: a -> a diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs index 1724c664..5fa73ecd 100644 --- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs +++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs @@ -403,20 +403,20 @@ spec = do      context "when parsing module strings" $ do        it "should parse a module on its own" $ do          "\"Module\"" `shouldParseTo` -          DocModule "Module" +          DocModule (ModLink "Module" Nothing)        it "should parse a module inline" $ do          "This is a \"Module\"." `shouldParseTo` -          "This is a " <> DocModule "Module" <> "." +          "This is a " <> DocModule (ModLink "Module" Nothing) <> "."        it "can accept a simple module name" $ do -        "\"Hello\"" `shouldParseTo` DocModule "Hello" +        "\"Hello\"" `shouldParseTo` DocModule (ModLink "Hello" Nothing)        it "can accept a module name with dots" $ do -        "\"Hello.World\"" `shouldParseTo` DocModule "Hello.World" +        "\"Hello.World\"" `shouldParseTo` DocModule (ModLink "Hello.World" Nothing)        it "can accept a module name with unicode" $ do -        "\"Hello.Worldλ\"" `shouldParseTo` DocModule "Hello.Worldλ" +        "\"Hello.Worldλ\"" `shouldParseTo` DocModule (ModLink "Hello.Worldλ" Nothing)        it "parses a module name with a trailing dot as regular quoted string" $ do          "\"Hello.\"" `shouldParseTo` "\"Hello.\"" @@ -428,19 +428,85 @@ spec = do          "\"Hello&[{}(=*)+]!\"" `shouldParseTo` "\"Hello&[{}(=*)+]!\""        it "accepts a module name with unicode" $ do -        "\"Foo.Barλ\"" `shouldParseTo` DocModule "Foo.Barλ" +        "\"Foo.Barλ\"" `shouldParseTo` DocModule (ModLink "Foo.Barλ" Nothing)        it "treats empty module name as regular double quotes" $ do          "\"\"" `shouldParseTo` "\"\""        it "accepts anchor reference syntax as DocModule" $ do -        "\"Foo#bar\"" `shouldParseTo` DocModule "Foo#bar" +        "\"Foo#bar\"" `shouldParseTo` DocModule (ModLink "Foo#bar" Nothing)        it "accepts anchor with hyphen as DocModule" $ do -        "\"Foo#bar-baz\"" `shouldParseTo` DocModule "Foo#bar-baz" +        "\"Foo#bar-baz\"" `shouldParseTo` DocModule (ModLink "Foo#bar-baz" Nothing)        it "accepts old anchor reference syntax as DocModule" $ do -        "\"Foo\\#bar\"" `shouldParseTo` DocModule "Foo\\#bar" +        "\"Foo\\#bar\"" `shouldParseTo` DocModule (ModLink "Foo\\#bar" Nothing) + +    context "when parsing labeled module links" $ do +      it "parses a simple labeled module link" $ do +        "[some label](\"Some.Module\")" `shouldParseTo` +          DocModule (ModLink "Some.Module" (Just "some label")) + +      it "allows escaping in label" $ do +        "[some\\] label](\"Some.Module\")" `shouldParseTo` +          DocModule (ModLink "Some.Module" (Just "some] label")) + +      it "strips leading and trailing whitespace from label" $ do +        "[  some label  ](\"Some.Module\")" `shouldParseTo` +          DocModule (ModLink "Some.Module" (Just "some label")) + +      it "allows whitespace in module name link" $ do +        "[some label]( \"Some.Module\"\t )" `shouldParseTo` +          DocModule (ModLink "Some.Module" (Just "some label")) + +      it "allows inline markup in the label" $ do +        "[something /emphasized/](\"Some.Module\")" `shouldParseTo` +          DocModule (ModLink "Some.Module" (Just ("something " <> DocEmphasis "emphasized"))) + +      it "should parse a labeled module on its own" $ do +        "[label](\"Module\")" `shouldParseTo` +          DocModule (ModLink "Module" (Just "label")) + +      it "should parse a labeled module inline" $ do +        "This is a [label](\"Module\")." `shouldParseTo` +          "This is a " <> DocModule (ModLink "Module" (Just "label")) <> "." + +      it "can accept a labeled module name with dots" $ do +        "[label](\"Hello.World\")" `shouldParseTo` DocModule (ModLink "Hello.World" (Just "label")) + +      it "can accept a labeled module name with unicode" $ do +        "[label](\"Hello.Worldλ\")" `shouldParseTo` DocModule (ModLink "Hello.Worldλ" (Just "label")) + +      it "parses a labeled module name with a trailing dot as a hyperlink" $ do +        "[label](\"Hello.\")" `shouldParseTo` +          hyperlink "\"Hello.\"" (Just "label") + +      it "parses a labeled module name with a space as a regular string" $ do +        "[label](\"Hello World\")" `shouldParseTo` "[label](\"Hello World\")" + +      it "parses a module name with invalid characters as a hyperlink" $ do +        "[label](\"Hello&[{}(=*+]!\")" `shouldParseTo` +          hyperlink "\"Hello&[{}(=*+]!\"" (Just "label") + +      it "accepts a labeled module name with unicode" $ do +        "[label](\"Foo.Barλ\")" `shouldParseTo` +          DocModule (ModLink "Foo.Barλ" (Just "label")) + +      it "treats empty labeled module name as empty hyperlink" $ do +        "[label](\"\")" `shouldParseTo` +          hyperlink "\"\"" (Just "label") + +      it "accepts anchor reference syntax for labeled module name" $ do +        "[label](\"Foo#bar\")" `shouldParseTo` +          DocModule (ModLink "Foo#bar" (Just "label")) + +      it "accepts old anchor reference syntax for labeled module name" $ do +        "[label](\"Foo\\#bar\")" `shouldParseTo` +          DocModule (ModLink "Foo\\#bar" (Just "label")) + +      it "interprets empty label as a unlabeled module name" $ do +        "[](\"Module.Name\")" `shouldParseTo` +          "[](" <> DocModule (ModLink "Module.Name" Nothing) <> ")"    describe "parseParas" $ do      let infix 1 `shouldParseTo` | 
