From b19a4bea999c684e092e0ea0feaf02ff8747d2a5 Mon Sep 17 00:00:00 2001 From: Simon Hengel Date: Wed, 4 Apr 2012 16:32:11 +0200 Subject: Add an optional label to URLs --- src/Haddock/Parse.y | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Haddock/Parse.y') diff --git a/src/Haddock/Parse.y b/src/Haddock/Parse.y index e36e8416..0cc783ee 100644 --- a/src/Haddock/Parse.y +++ b/src/Haddock/Parse.y @@ -10,7 +10,7 @@ module Haddock.Parse where import Haddock.Lex -import Haddock.Types (Doc(..), Example(Example)) +import Haddock.Types (Doc(..), Example(Example), Hyperlink(..)) import Haddock.Doc import HsSyn import RdrName @@ -107,7 +107,7 @@ seq1 :: { Doc RdrName } elem1 :: { Doc RdrName } : STRING { DocString $1 } | '/../' { DocEmphasis (DocString $1) } - | URL { DocURL $1 } + | URL { DocHyperlink (Hyperlink $1 Nothing) } | PIC { DocPic $1 } | ANAME { DocAName $1 } | IDENT { DocIdentifier $1 } -- cgit v1.2.3 From b8dcf173c272ebf85bbf2b427f84522e1474d092 Mon Sep 17 00:00:00 2001 From: Simon Hengel Date: Wed, 11 Apr 2012 07:54:33 +0200 Subject: Add support for hyperlink labels to parser --- src/Haddock/Parse.y | 11 ++++++++++- src/Haddock/Types.hs | 2 +- tests/unit-tests/parsetests.hs | 14 ++++++++++++++ 3 files changed, 25 insertions(+), 2 deletions(-) (limited to 'src/Haddock/Parse.y') diff --git a/src/Haddock/Parse.y b/src/Haddock/Parse.y index 0cc783ee..b34b14b9 100644 --- a/src/Haddock/Parse.y +++ b/src/Haddock/Parse.y @@ -107,7 +107,7 @@ seq1 :: { Doc RdrName } elem1 :: { Doc RdrName } : STRING { DocString $1 } | '/../' { DocEmphasis (DocString $1) } - | URL { DocHyperlink (Hyperlink $1 Nothing) } + | URL { DocHyperlink (makeHyperlink $1) } | PIC { DocPic $1 } | ANAME { DocAName $1 } | IDENT { DocIdentifier $1 } @@ -121,6 +121,15 @@ strings :: { String } happyError :: [LToken] -> Maybe a happyError toks = Nothing +-- | Create a `Hyperlink` from given string. +-- +-- A hyperlink consists of a URL and an optional label. The label is separated +-- from the url by one or more whitespace characters. +makeHyperlink :: String -> Hyperlink +makeHyperlink input = case break isSpace $ strip input of + (url, "") -> Hyperlink url Nothing + (url, label) -> Hyperlink url (Just . dropWhile isSpace $ label) + -- | Create an 'Example', stripping superfluous characters as appropriate makeExample :: String -> String -> [String] -> Example makeExample prompt expression result = diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs index f8890ebf..0d486ae8 100644 --- a/src/Haddock/Types.hs +++ b/src/Haddock/Types.hs @@ -318,7 +318,7 @@ instance Monoid (Doc id) where data Hyperlink = Hyperlink { hyperlinkUrl :: String , hyperlinkLabel :: Maybe String - } + } deriving (Eq, Show) data Example = Example diff --git a/tests/unit-tests/parsetests.hs b/tests/unit-tests/parsetests.hs index 7180a79e..0192ebfc 100644 --- a/tests/unit-tests/parsetests.hs +++ b/tests/unit-tests/parsetests.hs @@ -9,6 +9,7 @@ import Haddock.Lex (tokenise) import Haddock.Parse (parseParas) import Haddock.Types import Outputable +import Data.Monoid instance Outputable a => Show a where show = showSDoc . ppr @@ -53,8 +54,21 @@ tests = [ input = ">>> putFooBar\nfoo\n\nbar" , result = Just $ DocExamples $ [Example "putFooBar" ["foo","","bar"]] } + + -- tests for links + , ParseTest { + input = "" + , result = Just . DocParagraph $ hyperlink "http://example.com/" Nothing `mappend` DocString "\n" + } + + , ParseTest { + input = "" + , result = Just . DocParagraph $ hyperlink "http://example.com/" (Just "some link") `mappend` DocString "\n" + } ] +hyperlink :: String -> Maybe String -> Doc RdrName +hyperlink url = DocHyperlink . Hyperlink url main :: IO () main = do -- cgit v1.2.3 From 72675c1bf281b81041a19014b1b7df03a0de9488 Mon Sep 17 00:00:00 2001 From: Kazu Yamamoto Date: Mon, 9 Apr 2012 15:45:57 +0900 Subject: Add markup support for properties --- src/Haddock/Backends/Hoogle.hs | 1 + src/Haddock/Backends/LaTeX.hs | 1 + src/Haddock/Backends/Xhtml/DocMarkup.hs | 1 + src/Haddock/Interface/LexParseRn.hs | 1 + src/Haddock/Interface/Rename.hs | 1 + src/Haddock/InterfaceFile.hs | 6 ++++++ src/Haddock/Lex.x | 8 ++++++++ src/Haddock/Parse.y | 6 ++++++ src/Haddock/Types.hs | 2 ++ src/Haddock/Utils.hs | 2 ++ 10 files changed, 29 insertions(+) (limited to 'src/Haddock/Parse.y') diff --git a/src/Haddock/Backends/Hoogle.hs b/src/Haddock/Backends/Hoogle.hs index 4949daa1..28d35aca 100644 --- a/src/Haddock/Backends/Hoogle.hs +++ b/src/Haddock/Backends/Hoogle.hs @@ -256,6 +256,7 @@ markupTag dflags = Markup { markupCodeBlock = box TagPre, markupHyperlink = \(Hyperlink url mLabel) -> (box (TagInline "a") . str) (fromMaybe url mLabel), markupAName = const $ str "", + markupProperty = box TagPre . str, markupExample = box TagPre . str . unlines . map exampleToString } diff --git a/src/Haddock/Backends/LaTeX.hs b/src/Haddock/Backends/LaTeX.hs index 68cf715a..bf1e6ac3 100644 --- a/src/Haddock/Backends/LaTeX.hs +++ b/src/Haddock/Backends/LaTeX.hs @@ -1003,6 +1003,7 @@ parLatexMarkup ppId = Markup { markupCodeBlock = \p _ -> quote (verb (p Verb)) $$ text "", markupHyperlink = \l _ -> markupLink l, markupAName = \_ _ -> empty, + markupProperty = \p _ -> quote $ verb $ text p, markupExample = \e _ -> quote $ verb $ text $ unlines $ map exampleToString e } where diff --git a/src/Haddock/Backends/Xhtml/DocMarkup.hs b/src/Haddock/Backends/Xhtml/DocMarkup.hs index e75cfaba..aa4ba377 100644 --- a/src/Haddock/Backends/Xhtml/DocMarkup.hs +++ b/src/Haddock/Backends/Xhtml/DocMarkup.hs @@ -50,6 +50,7 @@ parHtmlMarkup qual ppId = Markup { markupHyperlink = \(Hyperlink url mLabel) -> anchor ! [href url] << fromMaybe url mLabel, markupAName = \aname -> namedAnchor aname << "", markupPic = \path -> image ! [src path], + markupProperty = pre . toHtml, markupExample = examplesToHtml } where diff --git a/src/Haddock/Interface/LexParseRn.hs b/src/Haddock/Interface/LexParseRn.hs index 3ad9719e..ced12d8d 100644 --- a/src/Haddock/Interface/LexParseRn.hs +++ b/src/Haddock/Interface/LexParseRn.hs @@ -121,6 +121,7 @@ rename dflags gre = rn DocHyperlink l -> DocHyperlink l DocPic str -> DocPic str DocAName str -> DocAName str + DocProperty p -> DocProperty p DocExamples e -> DocExamples e DocEmpty -> DocEmpty DocString str -> DocString str diff --git a/src/Haddock/Interface/Rename.hs b/src/Haddock/Interface/Rename.hs index 0f702683..55c9a5da 100644 --- a/src/Haddock/Interface/Rename.hs +++ b/src/Haddock/Interface/Rename.hs @@ -202,6 +202,7 @@ renameDoc d = case d of DocHyperlink l -> return (DocHyperlink l) DocPic str -> return (DocPic str) DocAName str -> return (DocAName str) + DocProperty p -> return (DocProperty p) DocExamples e -> return (DocExamples e) diff --git a/src/Haddock/InterfaceFile.hs b/src/Haddock/InterfaceFile.hs index 8fa8ce95..59b83c70 100644 --- a/src/Haddock/InterfaceFile.hs +++ b/src/Haddock/InterfaceFile.hs @@ -481,6 +481,9 @@ instance (Binary id) => Binary (Doc id) where put_ bh (DocWarning ag) = do putByte bh 17 put_ bh ag + put_ bh (DocProperty x) = do + putByte bh 18 + put_ bh x get bh = do h <- getByte bh case h of @@ -538,6 +541,9 @@ instance (Binary id) => Binary (Doc id) where 17 -> do ag <- get bh return (DocWarning ag) + 18 -> do + x <- get bh + return (DocProperty x) _ -> fail "invalid binary data found" diff --git a/src/Haddock/Lex.x b/src/Haddock/Lex.x index b9ebe688..35e6dd8a 100644 --- a/src/Haddock/Lex.x +++ b/src/Haddock/Lex.x @@ -50,6 +50,7 @@ $ident = [$alphanum \'\_\.\!\#\$\%\&\*\+\/\<\=\>\?\@\\\\\^\|\-\~\:] <0,para> { $ws* \n ; $ws* \> { begin birdtrack } + $ws* prop\> { strtoken TokPropertyPrompt `andBegin` propertyexpr } $ws* \>\>\> { strtoken TokExamplePrompt `andBegin` exampleexpr } $ws* [\*\-] { token TokBullet `andBegin` string } $ws* \[ { token TokDefStart `andBegin` def } @@ -61,6 +62,7 @@ $ident = [$alphanum \'\_\.\!\#\$\%\&\*\+\/\<\=\>\?\@\\\\\^\|\-\~\:] -- beginning of a line { $ws* \> { begin birdtrack } + $ws* prop\> { strtoken TokPropertyPrompt `andBegin` propertyexpr } $ws* \>\>\> { strtoken TokExamplePrompt `andBegin` exampleexpr } $ws* \n { token TokPara `andBegin` para } -- Here, we really want to be able to say @@ -84,6 +86,10 @@ $ident = [$alphanum \'\_\.\!\#\$\%\&\*\+\/\<\=\>\?\@\\\\\^\|\-\~\:] .* \n { strtokenNL TokExampleResult `andBegin` example } + .* \n { strtokenNL TokPropertyExpression `andBegin` property } + + () { token TokPara `andBegin` para } + { $special { strtoken $ \s -> TokSpecial (head s) } \<\< [^\>]* \>\> { strtoken $ \s -> TokPic (init $ init $ tail $ tail s) } @@ -129,6 +135,8 @@ data Token | TokEmphasis String | TokAName String | TokBirdTrack String + | TokPropertyPrompt String + | TokPropertyExpression String | TokExamplePrompt String | TokExampleExpression String | TokExampleResult String diff --git a/src/Haddock/Parse.y b/src/Haddock/Parse.y index b34b14b9..c8a1a558 100644 --- a/src/Haddock/Parse.y +++ b/src/Haddock/Parse.y @@ -35,6 +35,8 @@ import Data.List (stripPrefix) '-' { (TokBullet,_) } '(n)' { (TokNumber,_) } '>..' { (TokBirdTrack $$,_) } + PPROMPT { (TokPropertyPrompt $$,_) } + PEXP { (TokPropertyExpression $$,_) } PROMPT { (TokExamplePrompt $$,_) } RESULT { (TokExampleResult $$,_) } EXP { (TokExampleExpression $$,_) } @@ -73,12 +75,16 @@ defpara :: { (Doc RdrName, Doc RdrName) } para :: { Doc RdrName } : seq { docParagraph $1 } | codepara { DocCodeBlock $1 } + | property { DocProperty $1 } | examples { DocExamples $1 } codepara :: { Doc RdrName } : '>..' codepara { docAppend (DocString $1) $2 } | '>..' { DocString $1 } +property :: { String } + : PPROMPT PEXP { strip $2 } + examples :: { [Example] } : example examples { $1 : $2 } | example { [$1] } diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs index fbd05fae..05fc9747 100644 --- a/src/Haddock/Types.hs +++ b/src/Haddock/Types.hs @@ -306,6 +306,7 @@ data Doc id | DocHyperlink Hyperlink | DocPic String | DocAName String + | DocProperty String | DocExamples [Example] deriving (Functor) @@ -350,6 +351,7 @@ data DocMarkup id a = Markup , markupHyperlink :: Hyperlink -> a , markupAName :: String -> a , markupPic :: String -> a + , markupProperty :: String -> a , markupExample :: [Example] -> a } diff --git a/src/Haddock/Utils.hs b/src/Haddock/Utils.hs index b8f32589..4424ad73 100644 --- a/src/Haddock/Utils.hs +++ b/src/Haddock/Utils.hs @@ -432,6 +432,7 @@ markup m (DocCodeBlock d) = markupCodeBlock m (markup m d) markup m (DocHyperlink l) = markupHyperlink m l markup m (DocAName ref) = markupAName m ref markup m (DocPic img) = markupPic m img +markup m (DocProperty p) = markupProperty m p markup m (DocExamples e) = markupExample m e @@ -459,6 +460,7 @@ idMarkup = Markup { markupHyperlink = DocHyperlink, markupAName = DocAName, markupPic = DocPic, + markupProperty = DocProperty, markupExample = DocExamples } -- cgit v1.2.3 From dfbe1c45879d8ae32845c72e5ae241fb1c6fe502 Mon Sep 17 00:00:00 2001 From: Simon Hengel Date: Tue, 9 Oct 2012 12:41:25 +0200 Subject: Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. --- src/Haddock/Lex.x | 10 ++-------- src/Haddock/Parse.y | 16 +++++++++++----- 2 files changed, 13 insertions(+), 13 deletions(-) (limited to 'src/Haddock/Parse.y') diff --git a/src/Haddock/Lex.x b/src/Haddock/Lex.x index 35e6dd8a..aec4c647 100644 --- a/src/Haddock/Lex.x +++ b/src/Haddock/Lex.x @@ -50,7 +50,7 @@ $ident = [$alphanum \'\_\.\!\#\$\%\&\*\+\/\<\=\>\?\@\\\\\^\|\-\~\:] <0,para> { $ws* \n ; $ws* \> { begin birdtrack } - $ws* prop\> { strtoken TokPropertyPrompt `andBegin` propertyexpr } + $ws* prop \> .* \n { strtoken TokProperty } $ws* \>\>\> { strtoken TokExamplePrompt `andBegin` exampleexpr } $ws* [\*\-] { token TokBullet `andBegin` string } $ws* \[ { token TokDefStart `andBegin` def } @@ -62,7 +62,6 @@ $ident = [$alphanum \'\_\.\!\#\$\%\&\*\+\/\<\=\>\?\@\\\\\^\|\-\~\:] -- beginning of a line { $ws* \> { begin birdtrack } - $ws* prop\> { strtoken TokPropertyPrompt `andBegin` propertyexpr } $ws* \>\>\> { strtoken TokExamplePrompt `andBegin` exampleexpr } $ws* \n { token TokPara `andBegin` para } -- Here, we really want to be able to say @@ -86,10 +85,6 @@ $ident = [$alphanum \'\_\.\!\#\$\%\&\*\+\/\<\=\>\?\@\\\\\^\|\-\~\:] .* \n { strtokenNL TokExampleResult `andBegin` example } - .* \n { strtokenNL TokPropertyExpression `andBegin` property } - - () { token TokPara `andBegin` para } - { $special { strtoken $ \s -> TokSpecial (head s) } \<\< [^\>]* \>\> { strtoken $ \s -> TokPic (init $ init $ tail $ tail s) } @@ -135,8 +130,7 @@ data Token | TokEmphasis String | TokAName String | TokBirdTrack String - | TokPropertyPrompt String - | TokPropertyExpression String + | TokProperty String | TokExamplePrompt String | TokExampleExpression String | TokExampleResult String diff --git a/src/Haddock/Parse.y b/src/Haddock/Parse.y index c8a1a558..0befe395 100644 --- a/src/Haddock/Parse.y +++ b/src/Haddock/Parse.y @@ -35,8 +35,7 @@ import Data.List (stripPrefix) '-' { (TokBullet,_) } '(n)' { (TokNumber,_) } '>..' { (TokBirdTrack $$,_) } - PPROMPT { (TokPropertyPrompt $$,_) } - PEXP { (TokPropertyExpression $$,_) } + PROP { (TokProperty $$,_) } PROMPT { (TokExamplePrompt $$,_) } RESULT { (TokExampleResult $$,_) } EXP { (TokExampleExpression $$,_) } @@ -75,15 +74,15 @@ defpara :: { (Doc RdrName, Doc RdrName) } para :: { Doc RdrName } : seq { docParagraph $1 } | codepara { DocCodeBlock $1 } - | property { DocProperty $1 } + | property { $1 } | examples { DocExamples $1 } codepara :: { Doc RdrName } : '>..' codepara { docAppend (DocString $1) $2 } | '>..' { DocString $1 } -property :: { String } - : PPROMPT PEXP { strip $2 } +property :: { Doc RdrName } + : PROP { makeProperty $1 } examples :: { [Example] } : example examples { $1 : $2 } @@ -136,6 +135,13 @@ makeHyperlink input = case break isSpace $ strip input of (url, "") -> Hyperlink url Nothing (url, label) -> Hyperlink url (Just . dropWhile isSpace $ label) +makeProperty :: String -> Doc RdrName +makeProperty s = case strip s of + 'p':'r':'o':'p':'>':xs -> + DocProperty (dropWhile isSpace xs) + xs -> + error $ "makeProperty: invalid input " ++ show xs + -- | Create an 'Example', stripping superfluous characters as appropriate makeExample :: String -> String -> [String] -> Example makeExample prompt expression result = -- cgit v1.2.3 From dfc2cb4e31d6756b2d6ca7f87e80d8913751a4b7 Mon Sep 17 00:00:00 2001 From: Simon Hengel Date: Sun, 14 Oct 2012 11:58:13 +0200 Subject: Allow haddock markup in deprecation messages --- haddock.cabal | 1 + src/Haddock/Interface/Create.hs | 49 +++++++++++++--------- src/Haddock/Parse.y | 2 +- src/Haddock/Types.hs | 39 ++++++++++++++++- tests/html-tests/tests/BugDeprecated.html.ref | 18 +++++--- tests/html-tests/tests/BugExportHeadings.html.ref | 9 ++-- tests/html-tests/tests/DeprecatedClass.html.ref | 12 ++++-- tests/html-tests/tests/DeprecatedData.html.ref | 18 +++++--- tests/html-tests/tests/DeprecatedFunction.hs | 8 +++- tests/html-tests/tests/DeprecatedFunction.html.ref | 28 ++++++++++++- .../html-tests/tests/DeprecatedFunction2.html.ref | 3 +- .../html-tests/tests/DeprecatedFunction3.html.ref | 3 +- tests/html-tests/tests/DeprecatedModule.hs | 2 +- tests/html-tests/tests/DeprecatedModule.html.ref | 5 ++- tests/html-tests/tests/DeprecatedModule2.html.ref | 3 +- tests/html-tests/tests/DeprecatedNewtype.html.ref | 12 ++++-- tests/html-tests/tests/DeprecatedRecord.html.ref | 3 +- .../html-tests/tests/DeprecatedTypeFamily.html.ref | 6 ++- .../tests/DeprecatedTypeSynonym.html.ref | 6 ++- tests/html-tests/tests/ModuleWithWarning.hs | 2 +- tests/html-tests/tests/ModuleWithWarning.html.ref | 5 ++- .../tests/mini_DeprecatedFunction.html.ref | 6 +++ 22 files changed, 179 insertions(+), 61 deletions(-) (limited to 'src/Haddock/Parse.y') diff --git a/haddock.cabal b/haddock.cabal index b77fc5ac..88c18cd3 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -189,6 +189,7 @@ test-suite spec base , ghc , containers + , deepseq , array -- NOTE: As of this writing, Cabal does not properly handle alex/happy for diff --git a/src/Haddock/Interface/Create.hs b/src/Haddock/Interface/Create.hs index 32f287f5..fca1a00e 100644 --- a/src/Haddock/Interface/Create.hs +++ b/src/Haddock/Interface/Create.hs @@ -41,7 +41,7 @@ import Name import Bag import RdrName import TcRnTypes -import FastString (unpackFS) +import FastString (concatFS) -- | Use a 'TypecheckedModule' to produce an 'Interface'. @@ -90,7 +90,8 @@ createInterface tm flags modMap instIfaceMap = do liftErrMsg $ warnAboutFilteredDecls dflags mdl decls - let warningMap = mkWarningMap warnings gre exportedNames + warningMap <- liftErrMsg $ mkWarningMap dflags warnings gre exportedNames + exportItems <- mkExportItems modMap mdl warningMap gre exportedNames decls maps exports instances instIfaceMap dflags @@ -112,11 +113,13 @@ createInterface tm flags modMap instIfaceMap = do let !aliases = mkAliasMap dflags $ tm_renamed_source tm + modWarn <- liftErrMsg $ moduleWarning dflags gre warnings + return $! Interface { ifaceMod = mdl, ifaceOrigFilename = msHsFilePath ms, ifaceInfo = info, - ifaceDoc = Documentation mbDoc (moduleWarning warnings), + ifaceDoc = Documentation mbDoc modWarn, ifaceRnDoc = Documentation Nothing Nothing, ifaceOptions = opts, ifaceDocMap = docMap, @@ -169,29 +172,35 @@ lookupModuleDyn dflags Nothing mdlName = type WarningMap = DocMap Name -mkWarningMap :: Warnings -> GlobalRdrEnv -> [Name] -> WarningMap -mkWarningMap NoWarnings _ _ = M.empty -mkWarningMap (WarnAll _) _ _ = M.empty -mkWarningMap (WarnSome ws) gre exps = M.fromList - [ (n, warnToDoc w) | (occ, w) <- ws, elt <- lookupGlobalRdrEnv gre occ - , let n = gre_name elt, n `elem` exps ] +mkWarningMap :: DynFlags -> Warnings -> GlobalRdrEnv -> [Name] -> ErrMsgM WarningMap +mkWarningMap dflags warnings gre exps = case warnings of + NoWarnings -> return M.empty + WarnAll _ -> return M.empty + WarnSome ws -> do + let ws' = [ (n, w) | (occ, w) <- ws, elt <- lookupGlobalRdrEnv gre occ + , let n = gre_name elt, n `elem` exps ] + M.fromList . catMaybes <$> mapM parse ws' + where + parse (n, w) = (fmap $ (,) n) <$> parseWarning dflags gre w -moduleWarning :: Warnings -> Maybe (Doc id) -moduleWarning ws = +moduleWarning :: DynFlags -> GlobalRdrEnv -> Warnings -> ErrMsgM (Maybe (Doc Name)) +moduleWarning dflags gre ws = case ws of - NoWarnings -> Nothing - WarnSome _ -> Nothing - WarnAll w -> Just $! warnToDoc w + NoWarnings -> return Nothing + WarnSome _ -> return Nothing + WarnAll w -> parseWarning dflags gre w -warnToDoc :: WarningTxt -> Doc id -warnToDoc w = case w of - (DeprecatedTxt msg) -> format "Deprecated: " msg - (WarningTxt msg) -> format "Warning: " msg +parseWarning :: DynFlags -> GlobalRdrEnv -> WarningTxt -> ErrMsgM (Maybe (Doc Name)) +parseWarning dflags gre w = do + r <- case w of + (DeprecatedTxt msg) -> format "Deprecated: " msg + (WarningTxt msg) -> format "Warning: " msg + r `deepseq` return r where - format x xs = let !str = force $ concat (x : map unpackFS xs) - in DocWarning $ DocParagraph $ DocString str + format x xs = fmap (DocWarning . DocParagraph . DocAppend (DocString x)) + <$> processDocString dflags gre (HsDocString $ concatFS xs) ------------------------------------------------------------------------------- diff --git a/src/Haddock/Parse.y b/src/Haddock/Parse.y index 0befe395..f40ff521 100644 --- a/src/Haddock/Parse.y +++ b/src/Haddock/Parse.y @@ -7,7 +7,7 @@ -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings -- for details -module Haddock.Parse where +module Haddock.Parse (parseString, parseParas) where import Haddock.Lex import Haddock.Types (Doc(..), Example(Example), Hyperlink(..)) diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs index 05fc9747..9be46748 100644 --- a/src/Haddock/Types.hs +++ b/src/Haddock/Types.hs @@ -1,5 +1,5 @@ -{-# OPTIONS_HADDOCK hide #-} {-# LANGUAGE DeriveDataTypeable, DeriveFunctor #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock.Types @@ -22,6 +22,7 @@ module Haddock.Types ( import Control.Exception import Control.Arrow +import Control.DeepSeq import Data.Typeable import Data.Map (Map) import Data.Maybe @@ -316,18 +317,54 @@ instance Monoid (Doc id) where mappend = DocAppend +instance NFData a => NFData (Doc a) where + rnf doc = case doc of + DocEmpty -> () + DocAppend a b -> a `deepseq` b `deepseq` () + DocString a -> a `deepseq` () + DocParagraph a -> a `deepseq` () + DocIdentifier a -> a `deepseq` () + DocIdentifierUnchecked a -> a `deepseq` () + DocModule a -> a `deepseq` () + DocWarning a -> a `deepseq` () + DocEmphasis a -> a `deepseq` () + DocMonospaced a -> a `deepseq` () + DocUnorderedList a -> a `deepseq` () + DocOrderedList a -> a `deepseq` () + DocDefList a -> a `deepseq` () + DocCodeBlock a -> a `deepseq` () + DocHyperlink a -> a `deepseq` () + DocPic a -> a `deepseq` () + DocAName a -> a `deepseq` () + DocProperty a -> a `deepseq` () + DocExamples a -> a `deepseq` () + + +instance NFData Name +instance NFData OccName +instance NFData ModuleName + + data Hyperlink = Hyperlink { hyperlinkUrl :: String , hyperlinkLabel :: Maybe String } deriving (Eq, Show) +instance NFData Hyperlink where + rnf (Hyperlink a b) = a `deepseq` b `deepseq` () + + data Example = Example { exampleExpression :: String , exampleResult :: [String] } deriving (Eq, Show) +instance NFData Example where + rnf (Example a b) = a `deepseq` b `deepseq` () + + exampleToString :: Example -> String exampleToString (Example expression result) = ">>> " ++ expression ++ "\n" ++ unlines result diff --git a/tests/html-tests/tests/BugDeprecated.html.ref b/tests/html-tests/tests/BugDeprecated.html.ref index f632d670..913b189d 100644 --- a/tests/html-tests/tests/BugDeprecated.html.ref +++ b/tests/html-tests/tests/BugDeprecated.html.ref @@ -96,7 +96,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_BugDeprecated.html");} >

Deprecated: for foo

Deprecated: for foo +

Deprecated: for baz

Deprecated: for baz +

Deprecated: for bar

Deprecated: for bar +

Deprecated: for one

Deprecated: for one +

some documentation for one, two and three @@ -155,7 +159,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_BugDeprecated.html");} >

Deprecated: for three

Deprecated: for three +

some documentation for one, two and three @@ -172,7 +177,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_BugDeprecated.html");} >

Deprecated: for two

Deprecated: for two +

some documentation for one, two and three diff --git a/tests/html-tests/tests/BugExportHeadings.html.ref b/tests/html-tests/tests/BugExportHeadings.html.ref index d3298b2e..457e2c50 100644 --- a/tests/html-tests/tests/BugExportHeadings.html.ref +++ b/tests/html-tests/tests/BugExportHeadings.html.ref @@ -166,7 +166,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_BugExportHeadings.html >

Deprecated: for one

Deprecated: for one +

Deprecated: for two

Deprecated: for two +

Deprecated: for three

Deprecated: for three +

Deprecated: SomeClass

Deprecated: SomeClass +

some class @@ -106,7 +107,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedClass.html") >

Deprecated: foo

Deprecated: foo +

documentation for foo @@ -126,7 +128,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedClass.html") >

Deprecated: SomeOtherClass

Deprecated: SomeOtherClass +

Deprecated: bar

Deprecated: bar +

Deprecated: Foo

Deprecated: Foo +

type Foo @@ -110,7 +111,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedData.html"); >

Deprecated: Foo

Deprecated: Foo +

constructor Foo @@ -125,7 +127,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedData.html"); >

Deprecated: Bar

Deprecated: Bar +

constructor Bar @@ -145,7 +148,8 @@ window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedData.html"); >

Deprecated: One

Deprecated: One +

Deprecated: One

Deprecated: One +

Deprecated: Two

Deprecated: Two +

:: Int
  • bar :: Int
  • Deprecated: use bar instead

    Deprecated: use bar instead +

    some documentation foo + >some documentation for foo +

    bar :: Int

    some documentation for bar

    Deprecated: use bar instead

    Deprecated: use bar instead +

    Deprecated: use bar instead

    Deprecated: use bar instead +

    Deprecated: Use Foo instead

    Deprecated: Use Foo instead +

    Documentation for