Skip to content

Commit

Permalink
Merge pull request jgm#1856 from markwright/master
Browse files Browse the repository at this point in the history
Allow compilation with ghc 7.10.1 RC1 and haddock-library 1.2
  • Loading branch information
jgm committed Jan 5, 2015
2 parents 4866c90 + 9c68017 commit e2d86df
Show file tree
Hide file tree
Showing 15 changed files with 34 additions and 26 deletions.
2 changes: 1 addition & 1 deletion pandoc.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -250,7 +250,7 @@ Library
hslua >= 0.3 && < 0.4,
binary >= 0.5 && < 0.8,
SHA >= 1.6 && < 1.7,
haddock-library >= 1.1 && < 1.2,
haddock-library >= 1.1 && < 1.3,
old-time,
deepseq-generics >= 0.1 && < 0.2,
JuicyPixels >= 3.1.6.1 && < 3.3
Expand Down
8 changes: 7 additions & 1 deletion src/Text/Pandoc/Readers/Haddock.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{- |
Module : Text.Pandoc.Readers.Haddock
Copyright : Copyright (C) 2013 David Lazar
Expand Down Expand Up @@ -29,7 +30,12 @@ import Debug.Trace (trace)
readHaddock :: ReaderOptions -- ^ Reader options
-> String -- ^ String to parse
-> Pandoc
readHaddock opts = B.doc . docHToBlocks . trace' . parseParas
readHaddock opts =
#if MIN_VERSION_haddock_library(1,2,0)
B.doc . docHToBlocks . trace' . _doc . parseParas
#else
B.doc . docHToBlocks . trace' . parseParas
#endif
where trace' x = if readerTrace opts
then trace (show x) x
else x
Expand Down
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Readers/LaTeX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -592,7 +592,7 @@ inNote ils =

unescapeURL :: String -> String
unescapeURL ('\\':x:xs) | isEscapable x = x:unescapeURL xs
where isEscapable c = c `elem` "#$%&~_^\\{}"
where isEscapable c = c `elem` ("#$%&~_^\\{}" :: String)
unescapeURL (x:xs) = x:unescapeURL xs
unescapeURL [] = ""

Expand Down Expand Up @@ -1225,7 +1225,7 @@ citationLabel = optional sp *>
<* optional sp
<* optional (char ',')
<* optional sp)
where isBibtexKeyChar c = isAlphaNum c || c `elem` ".:;?!`'()/*@_+=-[]*"
where isBibtexKeyChar c = isAlphaNum c || c `elem` (".:;?!`'()/*@_+=-[]*" :: String)

cites :: CitationMode -> Bool -> LP [Citation]
cites mode multi = try $ do
Expand Down
7 changes: 4 additions & 3 deletions src/Text/Pandoc/Readers/Org.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-
Copyright (C) 2014 Albert Krewinkel <tarleb@moltkeplatz.de>
Expand Down Expand Up @@ -1168,7 +1169,7 @@ isRelativeFilePath s = (("./" `isPrefixOf` s) || ("../" `isPrefixOf` s)) &&

isUri :: String -> Bool
isUri s = let (scheme, path) = break (== ':') s
in all (\c -> isAlphaNum c || c `elem` ".-") scheme
in all (\c -> isAlphaNum c || c `elem` (".-" :: String)) scheme
&& not (null path)

isAbsoluteFilePath :: String -> Bool
Expand Down Expand Up @@ -1214,7 +1215,7 @@ solidify :: String -> String
solidify = map replaceSpecialChar
where replaceSpecialChar c
| isAlphaNum c = c
| c `elem` "_.-:" = c
| c `elem` ("_.-:" :: String) = c
| otherwise = '-'

-- | Parses an inline code block and marks it as an babel block.
Expand Down Expand Up @@ -1465,7 +1466,7 @@ inlineLaTeX = try $ do
parseAsMathMLSym :: String -> Maybe Inlines
parseAsMathMLSym cs = B.str <$> MathMLEntityMap.getUnicode (clean cs)
-- dropWhileEnd would be nice here, but it's not available before base 4.5
where clean = reverse . dropWhile (`elem` "{}") . reverse . drop 1
where clean = reverse . dropWhile (`elem` ("{}" :: String)) . reverse . drop 1

state :: ParserState
state = def{ stateOptions = def{ readerParseRaw = True }}
Expand Down
3 changes: 2 additions & 1 deletion src/Text/Pandoc/Readers/RST.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
{-
Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu>
Expand Down Expand Up @@ -708,7 +709,7 @@ extractCaption = do
toChunks :: String -> [String]
toChunks = dropWhile null
. map (trim . unlines)
. splitBy (all (`elem` " \t")) . lines
. splitBy (all (`elem` (" \t" :: String))) . lines

codeblock :: Maybe String -> String -> String -> RSTParser Blocks
codeblock numberLines lang body =
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Readers/TWiki.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE RelaxedPolyRec, FlexibleInstances, TypeSynonymInstances #-}
{-# LANGUAGE RelaxedPolyRec, FlexibleInstances, TypeSynonymInstances, FlexibleContexts #-}
-- RelaxedPolyRec needed for inlinesBetween on GHC < 7
{-
Copyright (C) 2014 Alexander Sulfrian <alexander.sulfrian@fu-berlin.de>
Expand Down
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Templates.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ getDefaultTemplate :: (Maybe FilePath) -- ^ User data directory to search first
-> String -- ^ Name of writer
-> IO (Either E.IOException String)
getDefaultTemplate user writer = do
let format = takeWhile (`notElem` "+-") writer -- strip off extensions
let format = takeWhile (`notElem` ("+-" :: String)) writer -- strip off extensions
case format of
"native" -> return $ Right ""
"json" -> return $ Right ""
Expand Down Expand Up @@ -288,7 +288,7 @@ reservedWords :: [Text]
reservedWords = ["else","endif","for","endfor","sep"]

skipEndline :: Parser ()
skipEndline = P.try $ P.skipMany (P.satisfy (`elem` " \t")) >> P.char '\n' >> return ()
skipEndline = P.try $ P.skipMany (P.satisfy (`elem` (" \t" :: String))) >> P.char '\n' >> return ()

pConditional :: Parser Template
pConditional = do
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Writers/ConTeXt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,7 @@ stringToConTeXt opts = concatMap (escapeCharForConTeXt opts)
toLabel :: String -> String
toLabel z = concatMap go z
where go x
| elem x "\\#[]\",{}%()|=" = "ux" ++ printf "%x" (ord x)
| elem x ("\\#[]\",{}%()|=" :: String) = "ux" ++ printf "%x" (ord x)
| otherwise = [x]

-- | Convert Elements to ConTeXt
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Writers/EPUB.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE PatternGuards, CPP, ScopedTypeVariables, ViewPatterns #-}
{-# LANGUAGE PatternGuards, CPP, ScopedTypeVariables, ViewPatterns, FlexibleContexts #-}
{-
Copyright (C) 2010-2014 John MacFarlane <jgm@berkeley.edu>
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Writers/ICML.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}

{- |
Module : Text.Pandoc.Writers.ICML
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Writers/LaTeX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -240,7 +240,7 @@ toLabel z = go `fmap` stringToLaTeX URLString z
where go [] = ""
go (x:xs)
| (isLetter x || isDigit x) && isAscii x = x:go xs
| elem x "-+=:;." = x:go xs
| elem x ("-+=:;." :: String) = x:go xs
| otherwise = "ux" ++ printf "%x" (ord x) ++ go xs

-- | Puts contents into LaTeX command.
Expand Down
12 changes: 6 additions & 6 deletions src/Text/Pandoc/Writers/Markdown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -323,9 +323,9 @@ blockToMarkdown opts (Plain inlines) = do
then Just $ writerColumns opts
else Nothing
let rendered = render colwidth contents
let escapeDelimiter (x:xs) | x `elem` ".()" = '\\':x:xs
| otherwise = x : escapeDelimiter xs
escapeDelimiter [] = []
let escapeDelimiter (x:xs) | x `elem` (".()" :: String) = '\\':x:xs
| otherwise = x : escapeDelimiter xs
escapeDelimiter [] = []
let contents' = if isEnabled Ext_all_symbols_escapable opts &&
not (stPlain st) && beginsWithOrderedListMarker rendered
then text $ escapeDelimiter rendered
Expand Down Expand Up @@ -681,7 +681,7 @@ inlineListToMarkdown opts lst =
mapM (inlineToMarkdown opts) (avoidBadWraps lst) >>= return . cat
where avoidBadWraps [] = []
avoidBadWraps (Space:Str (c:cs):xs)
| c `elem` "-*+>" = Str (' ':c:cs) : avoidBadWraps xs
| c `elem` ("-*+>" :: String) = Str (' ':c:cs) : avoidBadWraps xs
avoidBadWraps (x:xs) = x : avoidBadWraps xs

escapeSpaces :: Inline -> Inline
Expand Down Expand Up @@ -821,8 +821,8 @@ inlineToMarkdown opts (Cite (c:cs) lst)
sdoc <- inlineListToMarkdown opts sinlines
let k' = text (modekey m ++ "@" ++ k)
r = case sinlines of
Str (y:_):_ | y `elem` ",;]@" -> k' <> sdoc
_ -> k' <+> sdoc
Str (y:_):_ | y `elem` (",;]@" :: String) -> k' <> sdoc
_ -> k' <+> sdoc
return $ pdoc <+> r
modekey SuppressAuthor = "-"
modekey _ = ""
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Writers/OpenDocument.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE PatternGuards, OverloadedStrings #-}
{-# LANGUAGE PatternGuards, OverloadedStrings, FlexibleContexts #-}
{-
Copyright (C) 2008-2014 Andrea Rossato <andrea.rossato@ing.unitn.it>
and John MacFarlane.
Expand Down
6 changes: 3 additions & 3 deletions src/Text/Pandoc/Writers/RST.hs
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ keyToRST :: ([Inline], (String, String))
-> State WriterState Doc
keyToRST (label, (src, _)) = do
label' <- inlineListToRST label
let label'' = if ':' `elem` (render Nothing label')
let label'' = if ':' `elem` ((render Nothing label') :: String)
then char '`' <> label' <> char '`'
else label'
return $ nowrap $ ".. _" <> label'' <> ": " <> text src
Expand Down Expand Up @@ -333,12 +333,12 @@ inlineListToRST lst =
okAfterComplex :: Inline -> Bool
okAfterComplex Space = True
okAfterComplex LineBreak = True
okAfterComplex (Str (c:_)) = isSpace c || c `elem` "-.,:;!?\\/'\")]}>–—"
okAfterComplex (Str (c:_)) = isSpace c || c `elem` ("-.,:;!?\\/'\")]}>–—" :: String)
okAfterComplex _ = False
okBeforeComplex :: Inline -> Bool
okBeforeComplex Space = True
okBeforeComplex LineBreak = True
okBeforeComplex (Str (c:_)) = isSpace c || c `elem` "-:/'\"<([{–—"
okBeforeComplex (Str (c:_)) = isSpace c || c `elem` ("-:/'\"<([{–—" :: String)
okBeforeComplex _ = False
isComplex :: Inline -> Bool
isComplex (Emph _) = True
Expand Down
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Writers/Texinfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -368,7 +368,7 @@ inlineListForNode = return . text . stringToTexinfo .

-- periods, commas, colons, and parentheses are disallowed in node names
disallowedInNode :: Char -> Bool
disallowedInNode c = c `elem` ".,:()"
disallowedInNode c = c `elem` (".,:()" :: String)

-- | Convert inline element to Texinfo
inlineToTexinfo :: Inline -- ^ Inline to convert
Expand Down

0 comments on commit e2d86df

Please sign in to comment.