[commit: haddock] T6018-injective-type-families, adamse-D1033, ghc-head, wip/10268, wip/10313, 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/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/orf-new, wip/orf-reboot, wip/pattern-synonyms, wip/rae, wip/trac-9744: Disambiguate string-literals (3f57c24)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:31:24 UTC 2015


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

On branches: T6018-injective-type-families,adamse-D1033,ghc-head,wip/10268,wip/10313,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/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/orf-new,wip/orf-reboot,wip/pattern-synonyms,wip/rae,wip/trac-9744
Link       : http://git.haskell.org/haddock.git/commitdiff/3f57c2423252731487f66f503b5119c3becf4673

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

commit 3f57c2423252731487f66f503b5119c3becf4673
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Thu Sep 18 23:57:37 2014 +0200

    Disambiguate string-literals
    
    GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem`
    otherwise.


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

3f57c2423252731487f66f503b5119c3becf4673
 haddock-library/src/Documentation/Haddock/Parser.hs | 8 ++++----
 1 file changed, 4 insertions(+), 4 deletions(-)

diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index 68d9ece..e8bc276 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -199,7 +199,7 @@ moduleName = DocModule <$> (char '"' *> modid <* char '"')
       -- accept {small | large | digit | ' } here.  But as we can't
       -- match on unicode characters, this is currently not possible.
       -- Note that we allow ‘#’ to suport anchors.
-      <*> (decodeUtf8 <$> takeWhile (`notElem` " .&[{}(=*)+]!|@/;,^?\"\n"))
+      <*> (decodeUtf8 <$> takeWhile (`notElem` (" .&[{}(=*)+]!|@/;,^?\"\n"::String)))
 
 -- | Picture parser, surrounded by \<\< and \>\>. It's possible to specify
 -- a title for the picture.
@@ -271,7 +271,7 @@ innerList item = do
 -- | Parses definition lists.
 definitionList :: Parser [(DocH mod Identifier, DocH mod Identifier)]
 definitionList = do
-  label <- "[" *> (parseStringBS <$> takeWhile1 (`notElem` "]\n")) <* "]"
+  label <- "[" *> (parseStringBS <$> takeWhile1 (`notElem` ("]\n"::String))) <* "]"
   c <- takeLine
   (cs, items) <- more definitionList
   let contents = parseString . dropNLs . unlines $ c : cs
@@ -456,7 +456,7 @@ autoUrl = mkLink <$> url
     url = mappend <$> ("http://" <|> "https://" <|> "ftp://") <*> takeWhile1 (not . isSpace)
     mkLink :: BS.ByteString -> DocH mod a
     mkLink s = case unsnoc s of
-      Just (xs, x) | x `elem` ",.!?" -> DocHyperlink (Hyperlink (decodeUtf8 xs) Nothing) <> DocString [x]
+      Just (xs, x) | x `elem` (",.!?"::String) -> DocHyperlink (Hyperlink (decodeUtf8 xs) Nothing) <> DocString [x]
       _ -> DocHyperlink (Hyperlink (decodeUtf8 s) Nothing)
 
 -- | Parses strings between identifier delimiters. Consumes all input that it
@@ -473,7 +473,7 @@ parseValid = do
                  <|> return vs
     _ -> fail "outofvalid"
   where
-    idChar = satisfy (`elem` "_.!#$%&*+/<=>?@\\|-~:^")
+    idChar = satisfy (`elem` ("_.!#$%&*+/<=>?@\\|-~:^"::String))
              <|> digit <|> letter_ascii
 
 -- | Parses UTF8 strings from ByteString streams.



More information about the ghc-commits mailing list