[commit: haddock] 2.15, 2.15.0.1, 2.15.0.2, T6018-injective-type-families, adamse-D1033, clean, fix-travis, ghc-head, master, metainfo, v2.15, wip/10268, wip/10313, wip/D538, wip/D538-1, wip/D538-2, wip/D538-3, wip/D538-4, wip/D538-5, wip/D538-6, wip/D548-master, wip/D548-master-2, wip/T10483, wip/T8584, wip/T9840, wip/api-ann-hstylit, wip/api-ann-hstylit-1, wip/api-ann-hstylit-2, wip/api-ann-hstylit-3, wip/api-ann-hstylit-4, wip/api-ann-hstylit-5, wip/api-annot-tweaks-7.10, wip/api-annots-ghc-7.10-3, wip/ast-annotations-separate, wip/ast-prepare-annotations, wip/ast-prepare-annotations-final, wip/ast-prepare-annotations-final2, wip/ast-prepare-annotations-final3, wip/ast-prepare-annotations-final4, wip/ast-prepare-annotations-final5, wip/ast-prepare-annotations-final6, wip/attoparsec-update, wip/landmine-param-family, wip/orf-new, wip/orf-reboot, wip/pattern-synonyms, wip/rae, wip/remove-cabal-dep, wip/trac-9744: Comment improvements + few words in cabal file (89448ef)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:28:37 UTC 2015


Repository : ssh://git@git.haskell.org/haddock

On branches: 2.15,2.15.0.1,2.15.0.2,T6018-injective-type-families,adamse-D1033,clean,fix-travis,ghc-head,master,metainfo,v2.15,wip/10268,wip/10313,wip/D538,wip/D538-1,wip/D538-2,wip/D538-3,wip/D538-4,wip/D538-5,wip/D538-6,wip/D548-master,wip/D548-master-2,wip/T10483,wip/T8584,wip/T9840,wip/api-ann-hstylit,wip/api-ann-hstylit-1,wip/api-ann-hstylit-2,wip/api-ann-hstylit-3,wip/api-ann-hstylit-4,wip/api-ann-hstylit-5,wip/api-annot-tweaks-7.10,wip/api-annots-ghc-7.10-3,wip/ast-annotations-separate,wip/ast-prepare-annotations,wip/ast-prepare-annotations-final,wip/ast-prepare-annotations-final2,wip/ast-prepare-annotations-final3,wip/ast-prepare-annotations-final4,wip/ast-prepare-annotations-final5,wip/ast-prepare-annotations-final6,wip/attoparsec-update,wip/landmine-param-family,wip/orf-new,wip/orf-reboot,wip/pattern-synonyms,wip/rae,wip/remove-cabal-dep,wip/trac-9744
Link       : http://git.haskell.org/haddock.git/commitdiff/89448ef6c7ef3367f210562306cfa95c95d77250

>---------------------------------------------------------------

commit 89448ef6c7ef3367f210562306cfa95c95d77250
Author: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
Date:   Wed Jun 18 07:44:00 2014 +0200

    Comment improvements + few words in cabal file


>---------------------------------------------------------------

89448ef6c7ef3367f210562306cfa95c95d77250
 haddock-library/haddock-library.cabal              |  6 ++--
 .../src/Documentation/Haddock/Parser.hs            | 37 ++++++++++++++++------
 2 files changed, 32 insertions(+), 11 deletions(-)

diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal
index 8567312..20e0e94 100644
--- a/haddock-library/haddock-library.cabal
+++ b/haddock-library/haddock-library.cabal
@@ -1,10 +1,12 @@
 name:                 haddock-library
 version:              1.0.0
 synopsis:             Library exposing some functionality of Haddock.
-
 description:          Haddock is a documentation-generation tool for Haskell
                       libraries. These modules expose some functionality of it
-                      without pulling in the GHC dependency.
+                      without pulling in the GHC dependency. Please note that the
+                      API is likely to change so specify upper bounds in your
+                      project if you can't release often. For interacting with Haddock
+                      itself, see the ‘haddock’ package.
 license:              BSD3
 license-file:         LICENSE
 maintainer:           Simon Hengel <sol at typeful.net>, Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index f059746..b717884 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -13,7 +13,12 @@
 -- Maintainer  :  haddock at projects.haskell.org
 -- Stability   :  experimental
 -- Portability :  portable
-
+--
+-- Parser used for Haddock comments. For external users of this
+-- library, the most commonly used combination of functions is going
+-- to be
+--
+-- @'toRegular' . 'parseParas'@
 module Documentation.Haddock.Parser ( parseString, parseParas
                                     , overIdentifier, toRegular, Identifier
                                     ) where
@@ -97,15 +102,16 @@ parseStringBS :: BS.ByteString -> DocH mod Identifier
 parseStringBS = parse p
   where
     p :: Parser (DocH mod Identifier)
-    p = mconcat <$> many (monospace <|> anchor <|> identifier
-                          <|> moduleName <|> picture <|> hyperlink <|> autoUrl <|> bold
-                          <|> emphasis <|> encodedChar <|> string' <|> skipSpecialChar)
+    p = mconcat <$> many (monospace <|> anchor <|> identifier <|> moduleName
+                          <|> picture <|> hyperlink <|> autoUrl <|> bold
+                          <|> emphasis <|> encodedChar <|> string'
+                          <|> skipSpecialChar)
 
 -- | Parses and processes
 -- <https://en.wikipedia.org/wiki/Numeric_character_reference Numeric character references>
 --
--- >>> parseOnly encodedChar "ABC"
--- Right (DocString "ABC")
+-- >>> parseOnly encodedChar "A"
+-- Right (DocString "A")
 encodedChar :: Parser (DocH mod a)
 encodedChar = "&#" *> c <* ";"
   where
@@ -183,7 +189,7 @@ moduleName = DocModule <$> (char '"' *> modid <* char '"')
     modid = intercalate "." <$> conid `sepBy1` "."
     conid = (:)
       <$> satisfy isAsciiUpper
-      -- NOTE: According to Haskell 2010 we shouldd actually only
+      -- NOTE: According to Haskell 2010 we should actually only
       -- accept {small | large | digit | ' } here.  But as we can't
       -- match on unicode characters, this is currently not possible.
       <*> (decodeUtf8 <$> takeWhile (`notElem` " .&[{}(=*)+]!#|@/;,^?\"\n"))
@@ -192,9 +198,9 @@ moduleName = DocModule <$> (char '"' *> modid <* char '"')
 -- a title for the picture.
 --
 -- >>> parseOnly picture "<<hello.png>>"
--- Right (DocPic (Picture "hello.png" Nothing))
+-- Right (DocPic (Picture {pictureUri = "hello.png", pictureTitle = Nothing}))
 -- >>> parseOnly picture "<<hello.png world>>"
--- Right (DocPic (Picture "hello.png" (Just "world")))
+-- Right (DocPic (Picture {pictureUri = "hello.png", pictureTitle = Just "world"}))
 picture :: Parser (DocH mod a)
 picture = DocPic . makeLabeled Picture . decodeUtf8
           <$> disallowNewline ("<<" *> takeUntil ">>")
@@ -205,6 +211,8 @@ paragraph = examples <|> skipSpace *> (list <|> birdtracks <|> codeblock
                                        <|> property <|> header
                                        <|> textParagraph)
 
+-- | Headers inside the comment denoted with @=@ signs, up to 6 levels
+-- deep.
 header :: Parser (DocH mod Identifier)
 header = do
   let psers = map (string . encodeUtf8 . concat . flip replicate "=") [6, 5 .. 1]
@@ -330,6 +338,14 @@ takeNonEmptyLine :: Parser String
 takeNonEmptyLine = do
     (++ "\n") . decodeUtf8 <$> (takeWhile1 (/= '\n') >>= nonSpace) <* "\n"
 
+-- | Blocks of text of the form:
+--
+-- @
+-- > foo
+-- > bar
+-- > baz
+-- @
+--
 birdtracks :: Parser (DocH mod a)
 birdtracks = DocCodeBlock . DocString . intercalate "\n" . stripSpace <$> many1 line
   where
@@ -427,11 +443,14 @@ codeblock =
           | isNewline && isSpace c = Just isNewline
           | otherwise = Just $ c == '\n'
 
+-- | Parses links that were specifically marked as such.
 hyperlink :: Parser (DocH mod a)
 hyperlink = DocHyperlink . makeLabeled Hyperlink . decodeUtf8
               <$> disallowNewline ("<" *> takeUntil ">")
             <|> autoUrl
 
+-- | Looks for URL-like things to automatically hyperlink even if they
+-- weren't marked as links.
 autoUrl :: Parser (DocH mod a)
 autoUrl = mkLink <$> url
   where



More information about the ghc-commits mailing list